In last lecture we saw functors and basic examples. Today we will see more examples of those.
Recall that a functor is a module that is parameterized by other modules. Functors allow us to create a module whose implementation depends on the implementation of one or several other module, the argument(s) of the functor. Thus, functor allow to define several modules with very slight differences. This is done without any code duplication, by making the argument module implement those differences.
Here is an example of a functor allowing us to easily implement maps. We reuse the SETSIG and EQUALSIG implementations we had seen last time.
A map is a structure allowing us to easily map keys to values. Since we want a very general map here, we define a functor taking two arguments: the first argument is an implementation of the keys, and the second argument is an implementation of the values.
module type MAPSIG = sig
  type map
  type key
  type value
  val empty : map
  val add : map -> key -> value -> map
  val find : map -> key -> value
end
module type VALUESIG = sig
  type value
end
module MakeMap (Equal : EQUALSIG) (Value : VALUESIG) : MAPSIG
  with type key = Equal.t with type value = Value.value =
struct
  type key = Equal.t
  type value = Value.value
  (* The actual map is a Set of Pair(key,value); the Key construct
     is only there to be able to implement the find fonction 
     No Key construct shall be in a real set *)
  type item = Key of key | Pair of key * value
  module EqualItem = struct
  (* implementing the equality of items, of type EQUALSIG *)
    type t = item
    let equal (Key key1 | Pair (key1, _)) (Key key2 | Pair (key2, _)) =
      Equal.equal key1 key2
  end
  module Set = MakeSet (EqualItem)
  type map = Set.set
  let empty = Set.empty
  let add map key value =
    Set.add (Pair (key, value)) map
  let find map key =
    match Set.find (Key key) map with
	Pair (_, value) -> value
      | Key _ -> raise (Invalid_argument "find")
end
module BoolVal = struct
  type value = bool
end
module SMap = MakeMap (StringNoCase) (BoolVal)
let m = SMap.add SMap.empty "I like CS 3110" true
SMap.find m "i LiKe cs 3110";;
SMap.find m "Foo";;
MakePolynomial functor that takes a ring module as argument and creates a module for handling polynomials in that ring. This example was inspired by this page, and slightly modified.
We first define module types for a ring and a polynomial:
module type RING = sig type t val zero : t val one : t val plus : t -> t -> t val mult : t -> t -> t val equal : t -> t -> bool val print : t -> unit end module type POLYNOMIAL = sig type c (* type of numbers used in the polynomial *) type t (* type of the polynomials *) val zero : t val one : t val monom : c -> int -> t val plus : t -> t -> t val mult : t -> t -> t val equal : t -> t -> bool val print : t -> unit val eval : t -> c -> c endNow we can implement the
MakePolynomial functor. In the following implementation, we implement polynomials using lists of (coefficient,power) pair, ordered by power; no coefficient shall be 0, and no power shall repeat. For example, the only valid implementation of 3*x^2+5 would be [(3,2);(5,0)].
module MakePolynomial (A : RING) : POLYNOMIAL
  with type c=A.t =
struct
  type c = A.t
  type monom = (c * int)  (* a monom is a pair (coefficient,power) *)
  type t = monom list
  (* a polynomial of type t is a list of monoms, where powers are
     all different and ordered, and where coefficients are all non-zero *)
  let zero = [] 
  let one = [A.one, 0]
  let rec equal p1 p2 =  match p1, p2 with  
    | [],[] -> true  
    | (a1, k1)::q1, (a2, k2)::q2 -> k1 = k2 && 
                          A.equal a1 a2 && equal q1 q2  
    | _ -> false
  let monom a k =  
    if k < 0 
    then failwith "fail monom: negative power"
    else if A.equal a A.zero 
         then []
         else [(a,k)]
  let rec plus p1 p2 =  match p1, p2 with
    (x1, k1)::r1, ((x2, k2)::r2) ->  
       if k1 < k2 then  
         (x1, k1):: (plus r1 p2)  
       else if k1 = k2 then
         let x = A.plus x1 x2 in
         if A.equal x A.zero then plus r1 r2 
           (* in some rings, like Z/2Z, x=0 can happen *)
         else (A.plus x1 x2, k1):: (plus r1 r2)
       else
         (x2, k2):: (plus p1 r2)
  | [], _ -> p2  
  | _ , [] -> p1
 
  let rec times (a, k) p = 
  (* auxiliary function, multiplies p by aX^k *)
  (* supposes a <> 0 *)
    match p with
  | [] -> []
  | (a1, k1)::q ->  
     let a2 = A.mult a a1 in
     if A.equal a2 A.zero (* in some rings, like Z/2Z, a2=0 can happen *)
     then times (a,k) q
     else (a2, k + k1) :: times (a,k) q
  let mult p = List.fold_left (fun r m -> plus r (times m p)) zero
  let print p =
    print_string "(";
    let b = List.fold_left 
      (fun acc (a,k) -> 
         (* acc is false only for the first monom printed *) 
          if acc then print_string "+";
          A.print a; print_string "X^"; print_int k;
          true
      ) false p in
    if (not b) then (A.print A.zero);
    print_string ")"
      
  let rec pow c k = match k with
   (* auxiliary function for eval *)
   (* given c and k, calculates c^k *)
    0 -> A.one  
  | 1 -> c 
  | k -> 
      let l = pow c (k/2) in
      let l2 = A.mult l l in
        if k mod 2 = 0 then l2 else A.mult c l2
  let eval p c = match List.rev p with
    [] -> A.zero
  | (h::t) ->  
       let (* supposes k >= l. *)  dmeu (a, k) (b, l) =
         A.plus (A.mult (pow c (k-l)) a) b, l
       in let a, k = List.fold_left dmeu h t in
       A.mult (pow c k) a
end
Now we can create two examples with ints, and bools:
module IntRing = struct
  type t=int
  let zero=0
  let one=1
  let plus a b=a+b
  let mult a b=a*b
  let equal a b=(a=b)
  let print=print_int
end
module BoolRing = struct
  type t=bool
  let zero=false
  let one=true
  let plus a b=a || b
  let mult a b=a && b
  let equal a b=(a=b)
  let print a=if a then print_string "true" 
                   else print_string "false"
end
module IntPolynomial=MakePolynomial(IntRing)
module BoolPolynomial=MakePolynomial(BoolRing)
Here are examples of using the module IntPolynomial:
# open IntPolynomial;; # let a=monom 5 4;; val a : IntPolynomial.t = <abstr> # print a;; (5X^4)- : unit = () # let b=monom 1 8;; val b : IntPolynomial.t = <abstr> # print b;; (1X^8)- : unit = () # print (plus a b);; (5X^4+1X^8)- : unit = () # print (mult a b);; (5X^12)- : unit = ()Finally, we can see that any set of polynomials on a variable X is itself a ring! By creating a polynomial type on that new ring, we get the polynomials in two variables, say X and Y:
module IntPolynomial2Vars=MakePolynomial(IntPolynomial)