INF 231 - Functional Algorithmic and Programming

Lecture 4: Recursion

Below are the commands demonstrated during the lecture session (plus some additional commands).

Remember:

  • Try them yourself.
  • Tweak them: modify them and try variants of those commands.
  • Your curiosity is your best pedagogical tool.

Disclaimer: the functions in the code below are defined most of the times without SPECIFICATION. Remember that defining a function always consists in giving its specification and then implementation.

Defining some recursive functions

In [5]:
(* factorial *)
let rec fact (n:int):int=
  if (n=0) then 1
  else n*fact (n-1) ;;

(* sum of integers *)
let rec sum (n:int):int=
  if (n=0) then 0
  else n + sum (n-1) ;;

(* Quotient of the Euclidean division *)
let rec quotient (a:int) (b:int):int =
  if (a<b) then 0
  else 1 + quotient (a-b) b ;; 


(* Remainder of the Euclidian division *)
let rec remainder (a:int) (b:int):int=
  if (a<b) then a
  else remainder (a-b) b ;;

remainder 7 3 ;;

(* Addition with only incrementation and substraction *)
let incr (n:int):int = n+1 ;;

let rec add (n:int) (m:int):int=
  match n with
    | 0 -> m
    | n -> add (n-1) (incr m) ;;

(* Multiplication with only addition and substraction *)
let rec mult (n:int) (m:int):int=
  match n with
    | 0 -> m
    | n -> m + mult (n-1) m ;;

(* Calling a recursive function *)
fact 3;;
fact (4);;
quotient 10 5 ;;
quotient 22 7 ;;

(* Tracing a function *)
#trace fact;;

fact 3;;
Out[5]:
val fact : int -> int = <fun>
Out[5]:
val sum : int -> int = <fun>
Out[5]:
val quotient : int -> int -> int = <fun>
Out[5]:
val remainder : int -> int -> int = <fun>
Out[5]:
- : int = 1
Out[5]:
val incr : int -> int = <fun>
Out[5]:
val add : int -> int -> int = <fun>
Out[5]:
val mult : int -> int -> int = <fun>
Out[5]:
- : int = 6
Out[5]:
- : int = 24
Out[5]:
- : int = 2
Out[5]:
- : int = 3
fact is now traced.
fact <-- 3
fact <-- 2
fact <-- 1
fact <-- 0
fact --> 1
fact --> 1
fact --> 2
fact --> 6
Out[5]:
- : int = 6

Let's practice !

In [8]:
(* Remainder of the Euclidian division *)
let rec remainder (a:int) (b:int):int =
    if (a<b) then a
    else remainder (a-b) b ;;

remainder 16 7 ;;

(* The Fibonacci series *)
let rec fib (n:int):int=
  if (n<=1) then 1
  else fib(n-1) + fib(n-2) ;;

(* Power *)
let rec power1 (a:float) (n:int):float=
  if (n=0) then 1.
  else (if n>0 then a *. (power1 a (n-1))
        else 1. /. (power1 a (n-1))
       ) ;;

let rec power2 (a:float) (n:int):float=
  match n with
    | 0 -> 1.
    | n when (n mod 2=0) -> power2 (a*.a) (n / 2)
    | _ -> a *. power2 (a*.a) ((n-1) / 2) ;; (* n when (n mod 2=1) *)

power1 8. 10 ;;

power2 4. 6 ;;

#trace power1;;
#trace power2;;

power1 3. 20;;
power2 3. 20;;
Out[8]:
val remainder : int -> int -> int = <fun>
Out[8]:
- : int = 2
Out[8]:
val fib : int -> int = <fun>
Out[8]:
val power1 : float -> int -> float = <fun>
Out[8]:
val power2 : float -> int -> float = <fun>
Out[8]:
- : float = 1073741824.
Out[8]:
- : float = 4096.
power1 is now traced.
power2 is now traced.
power1 <-- 3.
power1 --> <fun>
power1* <-- 20
power1 <-- 3.
power1 --> <fun>
power1* <-- 19
power1 <-- 3.
power1 --> <fun>
power1* <-- 18
power1 <-- 3.
power1 --> <fun>
power1* <-- 17
power1 <-- 3.
power1 --> <fun>
power1* <-- 16
power1 <-- 3.
power1 --> <fun>
power1* <-- 15
power1 <-- 3.
power1 --> <fun>
power1* <-- 14
power1 <-- 3.
power1 --> <fun>
power1* <-- 13
power1 <-- 3.
power1 --> <fun>
power1* <-- 12
power1 <-- 3.
power1 --> <fun>
power1* <-- 11
power1 <-- 3.
power1 --> <fun>
power1* <-- 10
power1 <-- 3.
power1 --> <fun>
power1* <-- 9
power1 <-- 3.
power1 --> <fun>
power1* <-- 8
power1 <-- 3.
Out[8]:
- : float = 3486784401.
power1 --> <fun>
power1* <-- 7
power1 <-- 3.
power1 --> <fun>
power1* <-- 6
power1 <-- 3.
power1 --> <fun>
power1* <-- 5
power1 <-- 3.
power1 --> <fun>
power1* <-- 4
power1 <-- 3.
power1 --> <fun>
power1* <-- 3
power1 <-- 3.
power1 --> <fun>
power1* <-- 2
power1 <-- 3.
power1 --> <fun>
power1* <-- 1
power1 <-- 3.
power1 --> <fun>
power1* <-- 0
power1* --> 1.
power1* --> 3.
power1* --> 9.
power1* --> 27.
power1* --> 81.
power1* --> 243.
power1* --> 729.
power1* --> 2187.
power1* --> 6561.
power1* --> 19683.
power1* --> 59049.
power1* --> 177147.
power1* --> 531441.
power1* --> 1594323.
power1* --> 4782969.
power1* --> 14348907.
power1* --> 43046721.
power1* --> 129140163.
power1* --> 387420489.
power1* --> 1162261467.
power1* --> 3486784401.
power2 <-- 3.
power2 --> <fun>
power2* <-- 20
power2 <-- 9.
power2 --> <fun>
power2* <-- 10
power2 <-- 81.
power2 --> <fun>
power2* <-- 5
power2 <-- 6561.
power2 --> <fun>
power2* <-- 2
power2 <-- 43046721.
power2 --> <fun>
power2* <-- 1
power2 <-- 1853020188851841.
power2 --> <fun>
power2* <-- 0
power2* --> 1.
power2* --> 43046721.
power2* --> 43046721.
power2* --> 3486784401.
power2* --> 3486784401.
power2* --> 3486784401.
Out[8]:
- : float = 3486784401.

Mutually recursive functions, on an example

In [13]:
let rec even (n:int):bool = if n=0 then true else odd (n-1)
   and odd (n:int):bool = if n=0 then false else even (n-1) ;;

even 4;;
even 5;;

#trace even;;
#trace odd;;

even 3;;
Out[13]:
val even : int -> bool = <fun>
val odd : int -> bool = <fun>
Out[13]:
- : bool = true
Out[13]:
- : bool = false
even is now traced.
odd is now traced.
even <-- 3
odd <-- 2
even <-- 1
odd <-- 0
odd --> false
even --> false
odd --> false
even --> false
Out[13]:
- : bool = false

Termination

In [14]:
let rec mc n = if (n> 100) then (n-10) else mc (mc (n+11)) ;;

#trace mc;;

mc 89;;
mc 10;;


let rec weird_fact (n:int):int =
  if n=0 then 1
  else (weird_fact (n+1))/(n+1);;

weird_fact 1;;

let rec sum (n:int):int = if (n=0) then 0 else n + sum (n-1);;

#trace sum;;

sum 10 ;;
Out[14]:
val mc : int -> int = <fun>
mc is now traced.
mc <-- 89
mc <-- 100
mc <-- 111
mc --> 101
mc <-- 101
mc --> 91
mc --> 91
mc <-- 91
mc <-- 102
mc --> 92
mc <-- 92
mc <-- 103
mc --> 93
mc <-- 93
mc <-- 104
mc --> 94
mc <-- 94
mc <-- 105
mc --> 95
mc <-- 95
mc <-- 106
mc --> 96
mc <-- 96
mc <-- 107
mc --> 97
mc <-- 97
mc <-- 108
mc --> 98
mc <-- 98
mc <-- 109
mc --> 99
mc <-- 99
mc <-- 110
mc --> 100
mc <-- 100
mc <-- 111
mc --> 101
mc <-- 101
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc <-- 10
mc <-- 21
mc <-- 32
mc <-- 43
mc <-- 54
mc <-- 65
mc <-- 76
mc <-- 87
mc <-- 98
mc <-- 109
mc --> 99
mc <-- 99
mc <-- 110
mc --> 100
mc <-- 100
mc <-- 111
mc --> 101
mc <-- 101
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc <-- 91
mc <-- 102
mc --> 92
mc <-- 92
mc <-- 103
mc --> 93
mc <-- 93
mc <-- 104
mc --> 94
mc <-- 94
mc <-- 105
mc --> 95
mc <-- 95
mc <-- 106
mc --> 96
mc <-- 96
mc <-- 107
mc --> 97
mc <-- 97
mc <-- 108
mc --> 98
mc <-- 98
mc <-- 109
mc --> 99
mc <-- 99
mc <-- 110
mc --> 100
mc <-- 100
mc <-- 111
mc --> 101
mc <-- 101
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc <-- 91
mc <-- 102
mc --> 92
mc <-- 92
mc <-- 103
mc --> 93
mc <-- 93
mc <-- 104
mc --> 94
mc <-- 94
mc <-- 105
mc --> 95
mc <-- 95
mc <-- 106
mc --> 96
mc <-- 96
mc <-- 107
mc --> 97
mc <-- 97
mc <-- 108
mc --> 98
mc <-- 98
mc <-- 109
mc --> 99
mc <-- 99
mc <-- 110
mc --> 100
mc <-- 100
mc <-- 111
mc --> 101
mc <-- 101
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc <-- 91
mc <-- 102
mc --> 92
Out[14]:
- : int = 91
Out[14]:
- : int = 91
Out[14]:
val weird_fact : int -> int = <fun>
mc <-- 92
mc <-- 103
mc --> 93
mc <-- 93
mc <-- 104
mc --> 94
mc <-- 94
mc <-- 105
mc --> 95
mc <-- 95
mc <-- 106
mc --> 96
mc <-- 96
mc <-- 107
mc --> 97
mc <-- 97
mc <-- 108
mc --> 98
mc <-- 98
mc <-- 109
mc --> 99
mc <-- 99
mc <-- 110
mc --> 100
mc <-- 100
mc <-- 111
mc --> 101
mc <-- 101
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc <-- 91
mc <-- 102
mc --> 92
mc <-- 92
mc <-- 103
mc --> 93
mc <-- 93
mc <-- 104
mc --> 94
mc <-- 94
mc <-- 105
mc --> 95
mc <-- 95
mc <-- 106
mc --> 96
mc <-- 96
mc <-- 107
mc --> 97
mc <-- 97
mc <-- 108
mc --> 98
mc <-- 98
mc <-- 109
mc --> 99
mc <-- 99
mc <-- 110
mc --> 100
mc <-- 100
mc <-- 111
mc --> 101
mc <-- 101
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc <-- 91
mc <-- 102
mc --> 92
mc <-- 92
mc <-- 103
mc --> 93
mc <-- 93
mc <-- 104
mc --> 94
mc <-- 94
mc <-- 105
mc --> 95
mc <-- 95
mc <-- 106
mc --> 96
mc <-- 96
mc <-- 107
mc --> 97
mc <-- 97
mc <-- 108
mc --> 98
mc <-- 98
mc <-- 109
mc --> 99
mc <-- 99
mc <-- 110
mc --> 100
mc <-- 100
mc <-- 111
mc --> 101
mc <-- 101
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc <-- 91
mc <-- 102
mc --> 92
mc <-- 92
mc <-- 103
mc --> 93
mc <-- 93
mc <-- 104
mc --> 94
mc <-- 94
mc <-- 105
mc --> 95
mc <-- 95
mc <-- 106
mc --> 96
mc <-- 96
mc <-- 107
mc --> 97
mc <-- 97
mc <-- 108
mc --> 98
mc <-- 98
mc <-- 109
mc --> 99
mc <-- 99
mc <-- 110
mc --> 100
mc <-- 100
mc <-- 111
mc --> 101
mc <-- 101
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc <-- 91
mc <-- 102
mc --> 92
mc <-- 92
mc <-- 103
mc --> 93
mc <-- 93
mc <-- 104
mc --> 94
mc <-- 94
mc <-- 105
mc --> 95
mc <-- 95
mc <-- 106
mc --> 96
mc <-- 96
mc <-- 107
mc --> 97
mc <-- 97
mc <-- 108
mc --> 98
mc <-- 98
mc <-- 109
mc --> 99
mc <-- 99
mc <-- 110
mc --> 100
mc <-- 100
mc <-- 111
mc --> 101
mc <-- 101
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc <-- 91
mc <-- 102
mc --> 92
mc <-- 92
mc <-- 103
mc --> 93
mc <-- 93
mc <-- 104
mc --> 94
mc <-- 94
mc <-- 105
mc --> 95
mc <-- 95
mc <-- 106
mc --> 96
mc <-- 96
mc <-- 107
mc --> 97
mc <-- 97
mc <-- 108
mc --> 98
mc <-- 98
mc <-- 109
mc --> 99
mc <-- 99
mc <-- 110
mc --> 100
mc <-- 100
mc <-- 111
mc --> 101
mc <-- 101
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
mc --> 91
Stack overflow during evaluation (looping recursion?).
Raised by primitive operation at file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25
Called from file "[14]", line 11, characters 7-25

Recursive types

In [12]:
type weird_road =
   LEFT of weird_road
  | RIGHT of weird_road ;;

type safer_road =
   LEFT of safer_road
  | RIGHT of safer_road
  | Stop ;;

let r1 = LEFT (RIGHT Stop) ;;

type meal = KFC of chicken | HOME of egg and chicken = COMEFROM of egg and egg = COMEFROM of chicken ;;
Out[12]:
type weird_road = LEFT of weird_road | RIGHT of weird_road
Out[12]:
type safer_road = LEFT of safer_road | RIGHT of safer_road | Stop
Out[12]:
val r1 : safer_road = LEFT (RIGHT Stop)
File "[12]", line 12, characters 81-100:
Warning 30: the constructor COMEFROM is defined in both types chicken and egg.
Out[12]:
type meal = KFC of chicken | HOME of egg
and chicken = COMEFROM of egg
and egg = COMEFROM of chicken

Peano natural numbers

In [23]:
type natPeano = Zero | Suc of natPeano;;

Zero ;;

(* 
Suc Suc Zero ;; (* parenthesis needed *)
*)

Suc (Suc Zero) ;; 

let three = Suc (Suc (Suc Zero));;

let rec natPeano2int (n:natPeano):int =
  match n with
      Zero -> 0
    | Suc nprime -> 1 + natPeano2int nprime ;;

natPeano2int three;;

let rec int2natPeano (n:int):natPeano =
  match n with
      0 -> Zero
    | nprime -> Suc (int2natPeano (n-1)) ;; 

int2natPeano 5;;
Out[23]:
type natPeano = Zero | Suc of natPeano
Out[23]:
- : natPeano = Zero
Out[23]:
- : natPeano = Suc (Suc Zero)
Out[23]:
val three : natPeano = Suc (Suc (Suc Zero))
Out[23]:
val natPeano2int : natPeano -> int = <fun>
Out[23]:
- : int = 3
Out[23]:
val int2natPeano : int -> natPeano = <fun>
Out[23]:
- : natPeano = Suc (Suc (Suc (Suc (Suc Zero))))

Some functions around Peano numbers

In [26]:
let rec sumPeano (n1:natPeano) (n2:natPeano):natPeano =
  match n1 with
      Zero -> n2
    | Suc n1prime -> sumPeano n1prime (Suc n2) ;;

let two = Suc (Suc Zero);;

sumPeano two three ;;

sumPeano Zero three;;

let rec prodPeano (n1:natPeano) (n2:natPeano):natPeano =
  match n1 with
      Zero -> Zero
    | Suc Zero -> n2
    | Suc nprime1 -> sumPeano (prodPeano nprime1 n2) n2 ;;

let six = prodPeano three two ;;

prodPeano three Zero ;;

prodPeano Zero three ;;

let rec factPeano (n:natPeano):natPeano = 
  match n with 
      Zero -> Suc Zero
    | Suc Zero -> Suc Zero
    | Suc nprime -> prodPeano n (factPeano nprime) ;;

factPeano (Suc (Suc Zero)) ;;

factPeano six ;;

natPeano2int (factPeano six) ;;

let rec fact (n:int):int = 
  match n with 
      0 | 1 -> 1
    | n -> n * (fact (n-1)) ;;

fact 6 ;;
Out[26]:
val sumPeano : natPeano -> natPeano -> natPeano = <fun>
Out[26]:
val two : natPeano = Suc (Suc Zero)
Out[26]:
- : natPeano = Suc (Suc (Suc (Suc (Suc Zero))))
Out[26]:
- : natPeano = Suc (Suc (Suc Zero))
Out[26]:
val prodPeano : natPeano -> natPeano -> natPeano = <fun>
Out[26]:
val six : natPeano = Suc (Suc (Suc (Suc (Suc (Suc Zero)))))
Out[26]:
- : natPeano = Zero
Out[26]:
- : natPeano = Zero
Out[26]:
val factPeano : natPeano -> natPeano = <fun>
Out[26]:
- : natPeano = Suc (Suc Zero)
Out[26]:
- : natPeano =
Suc
 (Suc
   (Suc
     (Suc
       (Suc
         (Suc
           (Suc
             (Suc
               (Suc
                 (Suc
                   (Suc
                     (Suc
                       (Suc
                         (Suc
                           (Suc
                             (Suc
                               (Suc
                                 (Suc
                                   (Suc
                                     (Suc
                                       (Suc
                                         (Suc
                                           (Suc
                                             (Suc
                                               (Suc
                                                 (Suc
                                                   (Suc
                                                     (Suc
                                                       (Suc
                                                         (Suc
                                                           (Suc
                                                             (Suc
                                                               (Suc
                                                                 (Suc
                                                                   (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc
                                                                    (Suc ...))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
Out[26]:
- : int = 720
Out[26]:
val fact : int -> int = <fun>
Out[26]:
- : int = 720

Polynomials of one variable

In [27]:
type coef = int ;;
type degree = int ;;
type monomial = coef * degree ;;

type polynomial = Mn of monomial | Plus of monomial * polynomial ;;

let x4:coef*degree = (1,4);;

let two_x:coef*degree = (2,1);;
let three:monomial = (3,0);;

let poly:polynomial = Plus (x4, Plus (two_x, Mn three)) ;;
let polyprime:polynomial = Plus (three, Plus (two_x, Mn x4)) ;;

let rec dg_max (p:polynomial):int =
  match p with
      Mn (c,d) -> d
    | Plus ((c,d), pprime) -> max d (dg_max pprime) ;; 
    
dg_max poly ;;
dg_max polyprime ;;
Out[27]:
type coef = int
Out[27]:
type degree = int
Out[27]:
type monomial = coef * degree
Out[27]:
type polynomial = Mn of monomial | Plus of monomial * polynomial
Out[27]:
val x4 : coef * degree = (1, 4)
Out[27]:
val two_x : coef * degree = (2, 1)
Out[27]:
val three : monomial = (3, 0)
Out[27]:
val poly : polynomial = Plus ((1, 4), Plus ((2, 1), Mn (3, 0)))
Out[27]:
val polyprime : polynomial = Plus ((3, 0), Plus ((2, 1), Mn (1, 4)))
Out[27]:
val dg_max : polynomial -> int = <fun>
Out[27]:
- : int = 4
Out[27]:
- : int = 4

Disadvantages of this modelisation

In [29]:
poly = polyprime ;;

let poly1 = Plus ((0,5), poly) and poly2 = Plus ((-1,4),poly) in (dg_max poly1, dg_max poly2) ;;
Out[29]:
- : bool = false
Out[29]:
- : int * int = (5, 4)

Model 2

In [34]:
type polynomial = Zero | Plus of monomial * polynomial ;;

let poly = Plus (x4, Plus (two_x, Plus (three, Zero))) ;;

let polyprime = Plus (three, Plus (x4, Plus (two_x, Zero)));;

let rec well_formed_acc (p:polynomial) (n:int):bool=
  match p with 
    | Zero -> true
    | Plus ((c,d),pprime) -> c <> 0 && d<n && well_formed_acc pprime d ;;

let well_formed (p:polynomial):bool=
  match p with
    | Zero -> true
    | Plus ((c,d),pprime) -> c <> 0 && well_formed_acc pprime d ;;

well_formed poly ;;
well_formed polyprime ;;

let dg_max (p:polynomial):int=
  if well_formed p then
    match p with 
    Zero -> 0
    | Plus ((c,d),pprime) -> d
  else
    failwith "Polynomial is ill-formed" ;;

dg_max poly ;;

let rec add_mono_poly (m:monomial) (p:polynomial):polynomial=
  let (c,d)=m in
    if (c=0 || not (well_formed p)) then failwith "Ill-formed arugments"
    else (
    match p with 
      | Zero -> Plus (m,Zero)
      | Plus ((cc,dd), pp) -> 
      if (d> dd) then Plus (m, p)
      else (
        if (d=dd) then 
          let coef = c+cc in if coef=0 then pp else Plus ((coef,dd),pp)
        else (* dd > d*)
        Plus  ((cc,dd), add_mono_poly m pp)
      )
    )
;;

let rec add_polynomials (p1:polynomial) (p2:polynomial):polynomial=
  match p1,p2 with
      Zero,p -> p
    | p,Zero -> p
    | Plus (m,p), _ -> add_polynomials p (add_mono_poly m p2)
;;

poly;;
add_polynomials poly poly;;
Out[34]:
type polynomial = Zero | Plus of monomial * polynomial
Out[34]:
val poly : polynomial = Plus ((1, 4), Plus ((2, 1), Plus ((3, 0), Zero)))
Out[34]:
val polyprime : polynomial =
  Plus ((3, 0), Plus ((1, 4), Plus ((2, 1), Zero)))
Out[34]:
val well_formed_acc : polynomial -> int -> bool = <fun>
Out[34]:
val well_formed : polynomial -> bool = <fun>
Out[34]:
- : bool = true
Out[34]:
- : bool = false
Out[34]:
val dg_max : polynomial -> int = <fun>
Out[34]:
- : int = 4
Out[34]:
val add_mono_poly : monomial -> polynomial -> polynomial = <fun>
Out[34]:
val add_polynomials : polynomial -> polynomial -> polynomial = <fun>
Out[34]:
- : polynomial = Plus ((1, 4), Plus ((2, 1), Plus ((3, 0), Zero)))
Out[34]:
- : polynomial = Plus ((2, 4), Plus ((4, 1), Plus ((6, 0), Zero)))
In [ ]: