ML: Local Environments, Exceptions, I/O


Eager vs. Lazy Evaluation
    ML uses lazy eval only with boolean expressions. Eager eval otherwise. All arguments are evaluated, for example, before the function is called on the values... strict call-by-value.
Consider this
  fun looper x = looper(x);
  looper(5);

  fun heaper x = x*heaper(x);
  heaper(5);

  fun higher (flag, arg, func) = 
     if flag 
        then func(arg):int
        else 1
     ;

  higher(false,5,heaper);
  higher(true,5,heaper);
  
  fun yurk (flag, arg) = 
     if flag 
        then arg
        else 1
     ;

  yurk(true,17);
  yurk(false,heaper(5));
  yurk(true,heaper(5));
Lazy evaluations is called Normal-order evaluation

Eager evaluations is called Applicative order evaluation

These come from lambda calculus, the mathematical foundation for claiming that a language of functions can express all possible computable computations.


Binding is not assignment

   val x = 5;

is not the ML equivalent of 

   x := 5;

in imperative languages.

x := 5     says "there is a storage location... we have bound the 
           name x to that storage location, and now we would
           like to place this bit pattern in that storage
           location"
           subsequent references to x will go to the storage
           location and use what value is there

val x = 5  says "make a new entry in the symbol table (environment)
           binding the name x to the integer value 5"

it is a matter of indirection... what is the name bound to?

   x  --->  storage loc  --->  value  (imperative)
   x  --->  value                     (functional)

The name "x" is not refered to as a "variable"
rather it is an identifier
Local Environments: LET

Let will define a local scope... allowing symbol definitions that 
live only for part of a function definition


  fun hunPower (x:real) =
    let val four = x*x*x*x ;
        val twenty = four*four*four*four*four ;
    in
        twenty*twenty*twenty*twenty*twenty
    end;


Perverse example:


  fun hunPower (x:real) =
    let val x = x*x*x*x ;
        val x = x*x*x*x*x 
    in
        x*x*x*x*x 
    end;


Bindings work fine this way... x keeps on getting a new binding, which
is added successively to the symbol table and hides previous bindings.
At end of LET all bindings created in the block are removed.

LET can be used in conjunction with patterns in several useful ways 

  (* function to split a list into two lists, alternating elements *)
  fun split(nil) = (nil,nil)
   |  split([a]) = ([a],nil)
   |  split(a::b::cs) =
        let val (M,N) = split(cs)
        in  (a::M,b::N)
        end;

Now we're getting somewhere... here's MergeSort

  (* using split as previously defined *)

  (* remember merge? *)
  (* merges two sorted lists, sorted smallest first *)
    fun merge(nil,M) = M
     |  merge(L,nil) = L
     |  merge(L as x::xs, M as y::ys) =
          if (x:int) < y then x::merge(xs,M)
          else y::merge(L,ys) ;

  fun mst (nil) = nil
   |  mst ([a]) = [a]
   |  mst (L) =
        let val (M,N) = split(L) ; 
            val M = mst(M) ;
            val N = mst(N) 
        in  merge(M,N)
        end;


Simple Output

Traditionally I/O is a side effect... but it is useful even in 
a functional PL 

"print" function puts value of its argument to STDOUT

   fun tz(0) = print("zero\n")
    |  tz(_) = print("not zero\n") ;
   >> val tz = fn : int -> unit

Note the type "unit" for print "result"

print takes arguments of int, bool, real, or string
but you must be careful when mixing types in a function definition

   fun prhd(nil) = print("oops... list has no head\n")
    |  prhd(x::_) = print(x) ;
   >> Error: overloaded variable cannot be resolved: print

You have to help the type inference system

   fun prhd(nil) = print("oops... list has no head\n")
    |  prhd(x::_) = print(x:int) ;
   >>  val prhd = fn : int list -> unit

Note that this now works only for int list... not generic list.

This sometimes prints string, sometimes integer... which is ok,
since printing is a side effect.  Type of prhd is "int list -> unit"
You can combine statements into a statement list with ( )
Here is a print list example

  fun prlst(nil) = ()
   |  prlst(x::xs) = 
        ( print(x:int); 
          print("\n");
          prlst(xs)
        );

What happens here (without parens)?

  fun prlst(nil) = ()
   |  prlst(x::xs) = 
        print(x:int); 
        print("\n");
        prlst(xs)
        ;
What is the difference between STATEMENT LIST and LET?

Between LET ... IN we must find declarations (val, fun, etc.)

Simple Input

Reading a file... open_in , end_of_stream , input 

  fun rdlst (file) = 
    if end_of_stream(file) then nil
    else input(file,1) :: rdlst(file) ;
  >>  val rdlst = fn : instream -> string list

  rdlst(open_in("foo"));
  >> val it = ["1","2","3","4","5","\n","6","7","8",...] : string list

Here, input(fn,n) says read "n" characters from file handle "fn"

open_in creates a file handle of type "instream"

  val inf = open_in("foo");
  >> val inf = - : instream

instream is a sequence of characters, includes "\n" from files.
A more complex I/O example

read a list of integers from a file and compute their sum
 -- positive integers only
 -- integers separated by one or more white-space chars 
 -- last int may or may not have white-space after it
 -- any char except ws and digit is error

exception BadChar;

val END = ~1;

fun white(c) =
c=" " orelse c="\n" orelse c="\t";

fun digit(c) =
c >= "0" andalso c <= "9";

fun startInt(file) = 
  (* get the first digit from file;
     return END if there is no integer *)
  if end_of_stream(file) then END
  else let val c = input(file,1)
       in  if digit(c) then ord(c)-ord("0")
	   else if white(c) then startInt(file)
	   else raise BadChar
       end;

fun finishInt(i,file) = 
  (* return the integer whose first digits have value i and 
     whose remaining digits are found on file, up to the end or 
     the first white space *)
  if end_of_stream(file) then i
  else let val c = input(file,1)
       in if digit(c) then finishInt(10*i+ord(c)-ord("0"), file)
	  else if white(c) then i
	  else raise BadChar
       end;

fun getInt(file) = 
  (* read an integer from file *)
  finishInt(startInt(file), file) ;

fun sumInts1(file) = 
  (* sum the integers on file *)
  let val i = getInt(file)
  in if i=END then 0
     else i + sumInts1(file) 
  end;

fun sumInts(filename) = 
  (* sum the integers on file "filename" relative to the 
     current UNIX directory *)
  sumInts1(open_in(filename));

Useful I/O Functions

(*
======================================================================= 

  ML (before ML97) has limited I/O functions built-in
  they are:

  INPUT

    val inf = open_in ("");
       opens an instream

    ch = input(inf,1)  
       reads 1 character from instream "inf"

    str = input(inf,)
       reads n character from instream "inf"

    ch = lookahead(inf)
       gets the next character in "inf" but leaves the character 
       in the instream

    end_of_stream(inf)
       tells if there are more characters to input

    can_input(inf)
       returns an integer that tells how many characters can be
       obtained from instream "inf"
       for some reason, this function seems to return 0 when an
       instream has just been opened, then works as expected after
       the first character is input, or after an "end_of"stream"
       inquiry...

    close_in(inf)
       terminates the instream

  OUTPUT

    val outf = open_out("");
       opens an outstream "opuf" which will be connected to the
       indicated file.  This stomps the indicated file.

    val outf = open_append("");
       opens an outstream "opuf" which will be connected to the
       indicated file.  This DOES NOT stomp the indicated file,
       but will have output begin at the end of the information
       that is already there.

    output(outf,st)
       appends the string "st" to the outstream "outf"

    flush_out(outf)
       forces output for output to a screen 

    close_out(outf)
       terminates the outstream

  EXCEPTIONS
   
    these raise "Io" if you try to write or read a stream that has
    been closed.

  STANDARD I/O

    std_in
    std_out
      preopened instream, outstream connected to keyboard and screen
   
========================================================================
*)

(*
======================================================================= 

Here are some functions I have written to help with I/O
feel free to modify, rename, or ignore them

  inAll(inf)
    returns a string that contains all remaining characters
    from the instream

  inAllList(inf)
    returns a list composed of all the remaining characters in instream

  inLine(inf)
    returns a string containing all the characters up to (but not
    including) the next "\n" characters in the instream... 
    note that two successive calls to inLine will skip over the
    "\n" and neither will return it.

  inLineList(inf)
    returns a list containing all the characters up to (but not
    including) the next "\n" character in the instream

========================================================================
*)

fun inAllList (x) =
  if end_of_stream(x) then nil
  else input(x,1) :: inAllList(x);

fun inAll (x) =
  implode(inAllList(x));


fun inLineList (x) =
  if end_of_stream(x) 
    then nil
    else if lookahead(x) = "\n" 
      then (input(x,1);nil)
      else input(x,1) :: inLineList(x);

fun inLine (x) =
  implode(inLineList(x));



Exceptions

"exception" is a type (exn, built-in like int, etc.).  
Any function can return type "exception" no matter what its defined 
result type is normally. 

Exceptions can be user-defined as follows:

  exception Foo ;
  >> exception Foo
  exception Bar and Baz ;
  >> exception Bar
  >> exception Baz

"Foo" is now a value of type "exception", as are "Bar" and "Baz"

A defined exception can be raised as follows: 

  raise Foo ;
  >> uncaught exception Foo

Exceptions can also be defined to have parameters:

  exception Foo of string;
  >> exception Foo of string

When raised, the parameter must be supplied a value:

  raise Foo("bar");
  >> uncaught exception Foo

Handling Exceptions

If a raised exception is not handled, computation always stops.

  < expression > handle < match >
  here we fear that some exception may be raised in < expression >
  the "handle" section will deal with all exceptions we fear


  exception OutOfRange of int * int * string;

  fun safe_comb(n,m) =
    if n <= 0 then raise OutOfRange(n,m,"")
    else if m < 0 then raise OutOfRange(n,m,"m must be greater than 0")
    else if m > n then raise OutOfRange(n,m,"n must be greater than m")
    else if m=0 orelse m=n then 1
    else safe_comb(n-1,m) + safe_comb(n-1,m-1);

  fun comb(n,m) = safe_comb(n,m) 
    handle
      OutOfRange(0,0,mess) => 1
    | OutOfRange(n,m,mess) => 
         ( print("out of range: n="); print(n); 
           print(" m="); print(m); 
           print("\n"); print(mess); print("\n"); 
           0 
         ) ;


Built-in exceptions

MORE EXAMPLES

fun expo (x, 1) = x
  | expo (x:int, y) = x * expo(x, y-1) ;

fun inverse x = 1.0 / x
  handle Div => ( print("divide by zero produces 'infinite' value: "); 
                  real(expo(10,10))
                );

Higher-Order Functions

Higher-order function generates a function value as result
  or take functions as parameters

Example is often integration... take a function, produces another
  function that is the integral

  fun trap (a,b,n,F) =
    if n<=0 orelse b-a<=0.0 then 0.0
    else 
      let val delta = (b-a)/real(n)
      in  delta*(F(a)+F(a+delta))/2.0 
            + trap(a+delta,b,n-1,F)
      end;

  >> val trap = fn : real * real * int * (real -> real) -> real

  fun sq(x) = x*x : real;

  trap(0.0,1.0,100,sq);  gens .333...  1/3 is analytical result

Common Higher-order Function

MAP
  applies a function F to a list [a, b, c, ...] 
    producing [F(a), F(b), F(c), ... ]

  fun map(F,nil) = nil
   |  map(F,x::xs) = F(x)::map(F,xs) ;
  >> val map = f : ('a -> 'b) * 'a list -> b' list
  (rem built-in >> val it = fn : ('a -> 'b) -> 'a list -> 'b list )

  how's that for polymorphic??
Anonymous functions

We don't always have to define named functions:

  map(fn(x) => x*x, [3,5,8]);
  >> val it = [9,25,64] : int list

Here, the square function is defined inline, as an anonymous
(nameless) function.
Let's practice currying... here's the "real" internal map function:
what does this mean?

  map ;
  val it = fn : ('a -> 'b) -> 'a list -> 'b list

map takes a function and a list and gens a list of function values
Look at the type notation...

  map ~ [1,2,3,4]
  >> val it = [~1,~2,~3,~4] : int list


REDUCE
  takes function F of two args and a list [a,b,c,...]
    and produces F(a,F(b,F(c,...))) 

  example: reduce(+,[1,2,3,4,5]) gives the sum of the integers 
    in the list... gives 1+2+3+4+5

    exception EmptyList;
    fun reduce (F,nil) = raise EmptyList
     |  reduce (F,[a]) = a (* rem we want F to take two args *)
     |  reduce (F,x::xs) = F(x,reduce(F,xs)) ;
    >> val reduce = fn : ('a * 'a -> 'a) * 'a list -> 'a

  example of use: variance

    fun sq(x) = x*x : real;

    fun plus(x,y) = x+y : real;

    fun len(nil) = 0.0
     |  len(x::xs) = 1.0 + len(xs);

    fun var(L) =
      let val n = len(L)
      in  reduce(plus,map(sq,L))/n - sq(reduce(plus,L)/n)
      end;
BTW, we could do without the function "plus" above in this way:
  fun var(L) =
    let val n = len(L)
    in  reduce(op +, map(sq,L))/n - sq(reduce(op +, L)/n)
    end;

In sml the reduce funtion is "fold"

  fold;
  val it = fn : ('a * 'b -> 'b) -> 'a list -> 'b -> 'b

What's the difference?
  fold doesn't require operators with same types
  fold allows...


FILTER
  takes a predicate P (boolean function) and a list A = [a,b,c,...]
    and produces a list of elements from A where P(A) is true

    fun filter(P,nil) = nil
     |  filter(P,x::xs) =
          if P(x) then x::filter(P,xs)
          else filter(P,xs);
    >> val filter = fn : ('a -> bool) * 'a list -> 'a list

    filter(fn(x) => x>10, [1,10,23,5,16]);

    >> val it = [23,16] : int list 

  We have used an anonymous function here to provide the predicate.
More on Functions...
Example: Function Composition

  fun comp(F,G,x) = G(F(x)) ;
  >> val comp = fn : ('a -> 'b) * ('b -> 'c) * 'a -> 'c

  comp(fn(x)=>x+3, fn(y)=>y*y+2*y,10);
  >> val it = 195 : int

This approach produces the values of F o G, but not the function 
itself as a value we can "carry around" with us.

We really want comp to generate a function for us, using its function
parameters.

  fun comp(F,G) =
    let fun C(x) = G(F(x))
    in  C
    end;
  >> val comp = fn : ('a -> 'b) * ('b -> 'c) -> 'a -> 'c

Here, the let allows us to return the entire function rather than
an evaluation of it.

Another way:

  fun comp(F,G) = 
    fn(x) => G(F(x)) ;
  >> val comp = fn : ('a -> 'b) * ('b -> 'c) -> 'a -> 'c


Yet another (curried):

  fun compC F G x = G ( F ( x ) ) ;
  >> val compC = fn : ('a -> 'b) -> ('b -> 'c) -> 'a -> 'c

ML does have a built-in composition operator "o", BTW...

  fun sq(x) = x*x : int;
  fun cu(x) = x*x*x : int;

  val sqcu = sq o cu ; (* sq of cu *)
  >> val sqcu = fn : int -> int

  sqcu 2;
  >> val it = 64 : int
real version of MAP

  fun map(F) =
    let fun M(nil) = nil
         |  M(x::xs) = F(x)::M(xs)
    in  M
    end;
  >> val map = fn : ('a -> 'b) -> 'a list -> 'b list

As mentioned before, predefined map returns a function... so

  val ms = map sq;
  >> val ms = fn : real list -> real list

will make a function ms that will take a list and gen 
a list of squares
An Interesting Example... with HOFunctions, LET, and Curried form

   Design a small ML function that will take a function G (of one argument) 
   and an integer x and produces a function that computes G composed x times 
   on an argument. If we call this function "CUF", then one simple 
   example of its use would be to create a function to raise an argument 
   to the 64th power: CUF(sq,6) would return this function (assuming "sq" 
   is an integer square function). 
 
   The function CUF should not use ML library functions or built-ins 
   (like "o" composition or map). 

   (i) Write such a function in Curried form (call it "CUF"). 

      fun CUF G x =
        if x = 1 then 
           G
        else let val F = CUF G (x-1) ;
                 fun C(p) = G(F(p)) ;
             in C
      end;

      use of this:

      fun t2 x = 2 * x;  this is a function that will multiply it's arg by 2

      val fff = CUF t2 3 ;  this makes a function that will apply the
                            t2 function 3 times to its argument 

      fff 4 ;    makes t2(t2(t2(4))) = 32.