- fun product [] : int = 1
    | product (fst::rest) = fst * (product rest);
Can also use integers in patterns:
- fun oneTo 0 = [] = | oneTo n = n::(oneTo (n-1)); - fun fact n = product (oneTo n);Note oneTo 5 = [5,4,3,2,1]
Could have written
val fact = product o oneTo (* o is fcn. comp. *)
Here is how we could define a reverse fcn if it were not provided:
- fun reverse [] = [] = | reverse (h::t) = reverse(t)@[h]; (* pattern matching *)
Rarely use hd or tl - list operators giving head and tail of list.
Note that hd (a::x) = a, tl(a::x) = x, and ((hd x) :: (tl x)) = x if x is a list with at least one element.
Can use pattern matching in relatively complex ways to bind variables:
- val (x,y) = (5 div 2, 5 mod 2);
> val x = 2 : int
> val y = 1 : int
- val head::tail = [1,2,3];
> val head = 1 : int
> val tail = [2,3] : int list
- val {a = x, b = y} = {b = 3, a = "one"};
> val x = "one" : string
> val y = 3 : int
- val head::_ = [4,5,6];  (* note use of wildcard "_" *)
> val head = 4 : int
Thus
	hd : ('a list) -> 'a
	tl : ('a list) -> ('a list)
Definefun last [x] = x | last (fst::snd::rest) = last (snd::rest);has type 'a list -> 'a, but don't have to declare it!
Also need to distinguish "equality" types:
- fun search item [] = false
=   | search item (fst::rest) = if item = fst then true
=                                      else search item rest;
> val search = fn : ''a -> ((''a list) -> bool)
Double quote before variable name indicates "equality" type.  Cannot
use "=" on
types which are function types or contain function types.  Also only type
variables allowed in equality types are those with ''.
- val x = 3 * 3; > val x = 9 : int; - 2 * x; > val it = 18 : intCan also give local declarations of function and variables.
- fun roots (a,b,c) = = let val disc = sqrt (b * b - 4.0 * a * c) = in = ((~b + disc)/(2.0*a),(~b - disc)/(2.0*a)) = end;Static scoping (unlike original LISP)- roots (1.0,5.0,6.0); > (~2.0,~3.0) : real * real - disc;
Type checking error in: disc Unbound value identifier: disc
- val x = 3; > val x = 3 : int - fun f y = x + y; > val f = fn : int -> int - val x = 6; > val x = 6 : int - f 0;What is answer? 3!!
Why? Because definition of f used first "x", not second.
ML employs "eager" or call-by-value parameter passing
Talk later about "lazy" or "call-by-need".
Order of operations:
Can have sequential or parallel declarations:- val x = 12 = val y = x +2; > val x = 12 : int > val y = 14 : int - val x = 2 = and y = x + 3; > val x = 2 : int > val y = 15 : intHowever, when defining functions, simultaneous declaration supports mutual recursion.
- fun f n = if n = 0 then 1 else g n = and g m = m * f(m-1);
fun partition (pivot, nil) : int list * int list = (nil,nil)
  | partition (pivot, first :: others) =
    let val (smalls, bigs) = partition(pivot, others)
    in
        if first < pivot then (first::smalls, bigs)
                         else (smalls, first::bigs)
    end;
(* Must type fcn since uses overloaded "<"  *)
 
fun qsort nil = nil
  | qsort [singleton] = [singleton]
  | qsort (first::rest) =
        let val (smalls, bigs) = partition(first,rest)
        in  qsort(smalls) @ [first] @ qsort(bigs)
        end;
Can make polymorphic if pass in less than operator:
fun partition (pivot, nil) (lessThan) = (nil,nil)
  | partition (pivot, first :: others) (lessThan) =
    let val (smalls, bigs) = partition(pivot, others) (lessThan)
    in
        if (lessThan first pivot) then (first::smalls, bigs)
                          else (smalls, first::bigs)
    end;
> val partition = fn : ('a * ('b list)) -> 
		(('b -> ('a -> bool)) -> (('b list) * ('b list)))
fun qsort nil lessThan = nil
  | qsort [singleton] lessThan = [singleton]
  | qsort (first::rest) lessThan =
        let 
		val (smalls, bigs) = partition(first,rest) lessThan
        in  
		(qsort smalls lessThan) @ [first] @ (qsort bigs lessThan)
        end;
> val qsort = fn : ('a list) -> (('a -> ('a -> bool)) -> ('a list))
Now if define:
- intLt (x:int) (y:int) = x < y; - qsort [6,3,8,4,7,1] intLt; > val [1,3,4,6,7,8] : int listNote: could define
- val PIntLt :int * int -> bool = op <;but wrong type for what needed here!
Ex. Obvious recursive def in ML:
- fun fib 0 : int = 1 = | fib 1 = 1 = | fib n = fib (n-2) + fib (n-1);Iterative solution in Pascal - faster!
Function fastfib (n:integer):integer; val a,b : integer; begin a := 1; b := 1; while n > 0 do begin a := b; b := a + b; n := n - 1 (* all done in parallel *) end; fib := a end;ML equivalent
fun fastfib n : int = let 
		fun fibLoop a b 0 = a
        	  | fibLoop a b n : int = fibLoop  b (a+b) (n-1)
        in fibLoop 1 1 n
        end;
(* Must type result because of overloaded "+" *)
type point = int * int (* nullary *) type 'a pair = 'a * 'a (* unary *)
Types are disjoint unions (w/constructors as tags)
Support recursive type definitions!
Generative (support pattern matching as well)
- datatype color = Red | Green | Blue; > datatype color = Blue | Green | Red con Red = Red : color con Green = Green : color con Blue = Blue : color"con" stands for constructor.
Write constructor tags with capital letter as convention to distinguish from variables.
datatype 'a tree = Niltree | Maketree of 'a * ('a tree) * ('a tree)
> datatype 'a tree = Maketree of 'a * ('a tree) * ('a tree) | Niltree
  con Niltree = Niltree : 'a tree
  con Maketree = fn : ('a * ('a tree) * ('a tree)) -> ('a tree)
Write binary search program using trees!
fun insert (new:int) Niltree = Maketree (new,Niltree,Niltree) | insert new (Maketree (root,l,r)) = if new < root then Maketree (root,(insert new l),r) else Maketree (root,l,(insert new r)) fun buildtree [] = Niltree | buildtree (fst :: rest) = insert fst (buildtree rest) fun find (elt:int) Niltree = false | find elt (Maketree (root,left,right)) = if elt = root then true else if elt < root then find elt left else find elt right (* elt > root *) fun bsearch elt list = find elt (buildtree list); - buildtree [8,3,6,8,3,4,9,10]; > Maketree (10,Maketree (9,Maketree (4,Maketree (3,Niltree, Maketree (3,Niltree,Niltree)),Maketree (8,Maketree (6,Niltree,Niltree),Maketree (8,Niltree,Niltree))),Niltree), Niltree) : int tree - bsearch 4 [8,3,6,8,3,4,9,10]; > true : bool - bsearch 7 [8,3,6,8,3,4,9,10]; > false : bool fun sumtree Niltree = 0 | sumtree (Maketree(root,left,right)) = root + sumtree left + sumtree right;Can also have any kind of tagged unions:
- datatype sum = IntTag of int | RealTag of real | ComplexTag of real * real;Worth remarking that updating of data structures based on sharing:
Ex.: If define
- fun updatehd newhd (head::tail) = newhd :: tail;then get sharing:

Safe, because list elt's not updateable!
Abstract data types - later