translating to/from OCaml
[lambda.git] / translating_between_OCaml_Scheme_and_Haskell.mdwn
1 ##Translating between OCaml, SML, and Haskell##
2
3 The functional programming literature tends to use one of four languages: Scheme, OCaml, Standard ML (SML), or Haskell. With experience, you'll grow comfortable switching between these. At the beginning, though, it can be confusing.
4
5 The easiest translations are between OCaml and SML. These languages are both derived from a common ancestor, ML. For the most part, the differences between them are only superficial. [Here's a translatio nmanual](http://www.mpi-sws.org/~rossberg/sml-vs-ocaml.html).
6
7 In some respects these languages are closer to Scheme than to Haskell: Scheme, OCaml and SML all default to call-by-value evaluation order, and all three have native syntax for mutation and other imperative idioms (though that's not central to their design). Haskell is different in both respects: the default evaluation order is call-by-name (strictly speaking, it's "call-by-need", which is a more efficient cousin), and the only way to have mutation or the like is through the use of monads.
8
9 On both sides, however, the non-default evaluation order can also be had by using special syntax. And in other respects, OCaml and SML are more like Haskell than they are like Scheme. For example, OCaml and SML and Haskell all permit you to declare types and those types are *statically checked*: that is, your program won't even start to be interpreted unless all the types are consistent. In Scheme, on the other hand, type-checking only happens when your program is running, and the language is generally much laxer about what it accepts as well typed. (There's no problem having a list of mixed numbers and booleans, for example... and you don't need to wrap them in any sum type to do so.)
10
11 Additionally, the syntax of OCaml and SML is superficially much close to Haskell's than to Scheme's.
12
13 ##Comments, Whitespace, and Brackets##
14
15 *        
16
17                 -- this is a single line comment in Haskell
18
19                 {- this
20                    is a multiline
21                    comment in Haskell -}
22
23                 (* this is a single or multiline
24                    comment in OCaml *)
25
26                 ; this is a single line comment in Scheme
27
28                 #| this is a
29                    multiline comment
30                    in Scheme |#
31
32                 #;(this is
33                     (another way to
34                       (comment out (a block) (of Scheme code))))
35
36 *       Haskell is sensitive to linespace and indentation: it matters how your code is lined up. OCaml and Scheme don't care about this, though they recommend following some conventions for readability.
37
38 *       In Haskell, a block of code can be bracketed with `{` and `}`, with different expressions separated by `;`. But usually one would use line-breaks and proper indentation instead. In OCaml, separating expressions with `;` has a different meaning, having to do with how side-effects are sequenced. Instead, one can bracket a block of code with `(` and `)` or with `begin` and `end`. In Scheme, of course, every parentheses is significant.
39
40
41 ##Scheme and OCaml##
42
43 *       You can [try Scheme in your web browser](http://tryscheme.sourceforge.net/). This is useful if you don't have Racket or another Scheme implementation installed---but don't expect it to have all the bells and whistles of a mature implementation!
44
45 *       **Type Variants and Pattern Matching** If you want to reproduce this kind of OCaml code:
46
47                 type lambda_expression = Var of char | Lam of char * lambda_expression | App of lambda_expression * lambda_expression;;
48
49                 let rec free_vars (expr : lambda_expression) : char list =
50                   match expr with
51                     | Var label -> [label]
52                     | Lam (label, body) -> remove label (free_vars body)
53                     | App (left, right) -> merge (free_vars left) (free_vars right);;
54
55         in Scheme, you have two choices. First, the quick hack:
56
57                 ; we use the symbols 'var and 'lam as tags, and assume
58                 ; that an expression will always be a pair of one of these forms:
59                 ;       (cons 'var symbol)
60                 ;       (cons (cons 'lam symbol) expression)
61                 ;       (cons expression expression)
62
63                 (define (free-vars expr)
64                   (cond
65                     [(eq? (car expr) 'var) (list (cdr expr))]
66                     [(and? (pair? (car expr)) (eq? (car (car expr)) 'lam))
67                       (remove (cdr (car expr)) (free-vars (cdr expr)))]
68                     [else (merge (free-vars (car expr)) (free-vars (cdr expr)))]))
69
70         Second, you can create real datatypes and pattern-match on them. There are several tools for doing this. I'll describe the `define-datatype` and `cases` forms developed for the book *Essentials of Programming Languages* (EoPL) by Friedman and Wand.
71
72         (Alternatives include the `struct` form in Racket, see <http://docs.racket-lang.org/guide/define-struct.html>. Also `define-record-type` from srfi-9 and srfi-57; see also <http://docs.racket-lang.org/r6rs-lib-std/r6rs-lib-Z-H-7.html>.)
73
74         Here is how the tools from EoPL work. You must begin your file either with `#lang eopl` or with the first two lines below:
75
76                 #lang racket
77                 (require eopl/eopl)
78
79                 (define-datatype lambda-expression lambda-expression?
80                   (var (label symbol?))
81                   (lam (label symbol?) (body lambda-expression?))
82                   (app (left lambda-expression?) (right lambda-expression?)))
83
84                 (define (free-vars expr)
85                   (cases lambda-expression expr
86                     (var (label) (list label))
87                     (lam (label body) (remove label (free-vars body)))
88                     (app (left right) (remove-duplicates (append (free-vars left) (free-vars right))))))
89
90
91 *       Scheme has excellent support for working with implicit or "first-class" **continuations**, using either `call/cc` or any of various delimited continuation operators. See <http://docs.racket-lang.org/reference/cont.html?q=shift&q=do#%28part._.Classical_.Control_.Operators%29>.
92
93         In Scheme you can use these forms by default (they're equivalent):
94
95                 (call/cc (lambda (k) ...))
96                 (let/cc k ...)
97
98         If your program declares `(require racket/control)`, you can also use:
99
100                 (begin ... (reset ... (shift k ...) ...) ...)
101
102                 (begin ... (prompt ... (control k ...) ...) ...)
103
104                 (begin ... (prompt ... (abort value) ...) ...)
105
106         These last three forms are also available in OCaml, but to use them you'll need to compile and install Oleg Kiselyov's "delimcc" or "caml-shift" library (these names refer to the same library), which you can find [here](http://okmij.org/ftp/continuations/implementations.html#caml-shift). You'll already need to have OCaml installed. It also helps if you already have the findlib package installed, too, [as we discuss here](http://lambda.jimpryor.net/how_to_get_the_programming_languages_running_on_your_computer/). If you're not familiar with how to compile software on your computer, this might be beyond your reach for the time being.
107
108         But assuming you do manage to compile and install Oleg's library, here's how you'd use it in an OCaml session:
109
110                 #require "delimcc";; (* loading Oleg's library this way requires the findlib package *)
111                 open Delimcc;; (* this lets you say e.g. new_prompt instead of Delimcc.new_prompt *)
112                 let p = new_prompt ();;
113                 let prompt thunk = push_prompt p thunk;;
114                 let foo =
115                   ...
116                   prompt (fun () ->
117                     ...
118                     shift p (fun k -> ...)
119                     ...
120                     (* or *)
121                     control p (fun k -> ...)
122                     ...
123                     (* or *)
124                     abort p value
125                     ...
126                   )
127                   ...
128
129         There is also a library for using *undelimited* continuations in OCaml, but it's shakier than Oleg's delimited continuation library.
130
131 We won't say any more about translating to and from Scheme.
132
133
134 ##Haskell and OCaml##
135
136 We will however try to give some general advice about how to translate between OCaml and Haskell.
137
138 *       Again, it may sometimes be useful to [try Haskell in your web browser](http://tryhaskell.org/)
139 *       There are many Haskell tutorials and textbooks available. This is probably the most actively developed: [Haskell Wikibook](http://en.wikibooks.org/wiki/Haskell)
140 *       [Yet Another Haskell Tutorial](http://www.cs.utah.edu/~hal/docs/daume02yaht.pdf) (much of this excellent book has supposedly been integrated into the Haskell Wikibook)
141 *       All About Monads has supposedly also been integrated into the Haskell Wikibook
142 *       (A not-so-)[Gentle Introduction to Haskell](http://web.archive.org/web/http://www.haskell.org/tutorial/) (archived)
143 *       [Learn You a Haskell for Great Good](http://learnyouahaskell.com/)
144
145
146 #Type expressions#
147
148 *       In Haskell, you say a value has a certain type with: `value :: type`. You express the operation of prepending a new `int` to a list of `int`s with `1 : other_numbers`. In OCaml it's the reverse: you say `value : type` and `1 :: other_numbers`.
149
150 *       In Haskell, type names and constructors both begin with capital letters, and type variables always appear after their constructors, in Curried form. And the primary term for declaring a new type is `data` (short for "abstract datatype").
151 So we have:
152
153                 data Either a b = Left a | Right b;
154                 data FooType a b = Foo_constructor1 a b | Foo_constructor2 a b;
155
156         In printed media, Haskell type variables are often written using Greek letters, like this:
157
158         <pre><code>type Either &alpha; &beta; = Left &alpha; | Right &beta;
159         </code></pre>
160
161         Some terminology: in this type declaration, `Either` is known as a *type-constructor*, since it takes some types <code>&alpha;</code> and <code>&beta;</code> as arguments and yields a new type. We call <code>Left &alpha;</code> one of the *variants* for the type <code>Either &alpha; &beta;</code>. `Left` and `Right` are known as *value constructors* or *data constructors* or just *constructors*. You can use `Left` in any context where you need a function, for example:
162
163                 map Left [1, 2]
164
165         In OCaml, value constructors are still capitalized, but type names are lowercase. Type variables take the form `'a` instead of `a`, and if there are multiple type variables, they're not Curried but instead have to be grouped in a tuple. The syntax for whether they appear first or second is also somewhat different. So we have instead:
166
167                 type ('a,'b) either = Left of 'a | Right of 'b;;
168                 type ('a,'b) foo_type = Foo_constructor1 of 'a * 'b | Foo_constructor2 of 'a * 'b;;
169
170         In OCaml, constructors aren't full-fledged functions, so you need to do this instead:
171
172                 List.map (fun x -> Left x) [1; 2]
173
174         Apart from these differences, there are many similarities between Haskell's and OCaml's use of constructors. For example, in both languages you can do:
175
176                 let Left x = Left 1 in x + 1
177
178 *       In addition to the `data` keyword, Haskell also sometimes uses `type` and `newtype` to declare types. `type` is used just to introduce synonyms. If you say:
179
180                 type Weight = Integer
181                 type Person = (Name, Address)    -- supposing types Name and Address to be declared elsewhere
182
183         then you can use a value of type `Integer` wherever a `Weight` is expected, and vice versa. `newtype` and `data` on the other hand, create genuinely new types. `newtype` is basically just an efficient version of `data` that you can use in special circumstances. `newtype` must always take one type argument and have one value constructor. For example:
184
185                 newtype PersonalData a = PD a
186
187         You could also say:
188
189                 data PersonalData a = PD a
190
191         And `data` also allows multiple type arguments, and multiple variants and value constructors.
192
193         OCaml just uses the one keyword `type` for all of these purposes:
194
195                 type weight = int;;
196                 type person = name * address;;
197                 type 'a personal_data = PD of 'a;;
198
199 *       The type constructors discussed above took simple types as arguments. In Haskell, types are also allowed to take *type constructors* as arguments:
200
201                 data BarType t = Bint (t Integer) | Bstring (t string)
202
203         One does this for example when defining monad transformers---the type constructor `ReaderT` takes some base monad's type constructor as an argument.
204
205         The way to do this this in OCaml is less straightforward. [See here](/code/tree_monadize.ml) for an example.
206
207 *       Haskell has a notion of *type-classes*. They look like this:
208
209                 class Eq a where
210                   (==)    :: a -> a -> Bool
211
212         This declares the type-class `Eq`; in order to belong to this class, a type `a` will have to supply its own implementation of the function ==, with the type a -> a -> Bool. Here is how the `Integer` class signs up to join the type-class:
213
214                 instance Eq Integer where
215                   x == y  =  ...
216
217         Type expressions can be conditional on some of their parameters belonging to certain type-classes. For example:
218
219                 elem      :: (Eq a) => a -> [a] -> Bool
220
221         says that the function `elem` is only defined over types `a` that belong to the type-class `Eq`. For such types `a`, `elem` has the type `a -> [a] -> Bool`.
222
223         Similarly:
224
225                 instance (Eq a) => Eq (Tree a) where
226                   Leaf a         == Leaf b          =  a == b
227                   (Branch l1 r1) == (Branch l2 r2)  =  (l1==l2) && (r1==r2)
228                   _              == _               =  False
229
230         says that if `a` belongs to the typeclass `Eq`, then so too does `Tree a`, and in such cases here is the implementation of `==` for `Tree a`...
231
232 *       OCaml doesn't have type-classes. You can do soemthing similar with OCaml modules that take are parameterized on other modules. Again, [see here](/code/tree_monadize.ml) for an example.
233
234
235 *       Some specific differences in how certain types are expressed. This block in Haskell:
236
237                 Prelude> type Maybe a = Nothing | Just a
238                 Prelude> let x = [] :: [Int]
239                 Prelude> :t x
240                 x :: [Int]
241                 Prelude> let x = () :: ()
242                 Prelude> let x = (1, True) :: (Int, Bool)
243
244 corresponds to this block in OCaml:
245
246                 # type 'a option = None | Some of 'a;;
247                 type 'a option = None | Some of 'a
248                 # let (x : int list) = [];;
249                 val x : int list = []
250                 # let (x : unit) = ();;
251                 val x : unit = ()
252                 # let (x : int * bool) = (1, true);;
253                 val x : int * bool = (1, true)
254
255 *       Haskell has a plethora of numerical types, including the two types `Int` (integers limited to a machine-dependent range) and `Integer` (unbounded integers). The same arithmetic operators (`+` and so on) work for all of these. OCaml also has several different numerical types (though not as many). In OCaml, by default, one has to use a different numerical operator for each type:
256
257                 # 1 + 2;;
258                 - : int = 3
259                 # 1.0 + 2.0;;
260                 Error: This expression has type float but an expression was expected of type int
261                 # 1.0 +. 2.0;;
262                 - : float = 3.
263
264         However the comparison operators are polymorphic. You can equally say:
265
266                 # 1 = 2;;
267                 - : bool = false
268                 # 1.0 = 2.0;;
269                 - : bool = false
270                 # 2 > 1;;
271                 - : bool = true
272                 # 2.0 > 1.0;;
273                 - : bool = true
274
275         But you must still apply these operators to expressions of the same type:
276
277                 # 2.0 > 1;;
278                 Error: This expression has type int but an expression was expected of type float
279
280 * We'll discuss differences between Haskell's and OCaml's record types below.
281
282
283 #Lists, Tuples, Unit, Booleans#
284
285 *       As noted above, Haskell describes the type of a list of `Int`s as `[Int]`. OCaml describes it as `int list`. Haskell describes the type of a pair of `Int`s as `(Int, Int)`. OCaml describes it as `int * int`. Finally, Haskell uses `()` to express both the unit type and a value of that type. In OCaml, one uses `()` for the value and `unit` for the type.
286
287 *       Haskell describes the boolean type as `Bool` and its variants are `True` and `False`. OCaml describes the type as `bool` and its variants are `true` and `false`. This is an inconsistency in OCaml: other value constructors must always be capitalized.
288
289 *       As noted above, in Haskell one builds up a list by saying `1 : [2, 3]`. In OCaml one says `1 :: [2; 3]`. In Haskell, one can test whether a list is empty with either:
290
291                 lst == []
292                 null lst
293
294         In OCaml, there is no predefined `null` or `isempty` function. One can still test whether a list is empty using the comparison `lst = []`.
295
296 *       In Haskell, the expression [1..5] is the same as [1,2,3,4,5], and the expression [0..] is a infinite lazily-evaluated stream of the natural numbers. In OCaml, there is no [1..5] shortcut, lists must be finite, and they are eagerly evaluated. It is possible to create lazy streams in OCaml, even infinite ones, but you have to use other techniques than the native list type.
297
298 *       Haskell has *list comprehensions*:
299
300                 [ x * x | x <- [1..10], odd x]
301
302         In OCaml, one has to write this out longhand:
303
304                 List.map (fun x -> x * x) (List.filter odd [1..10]);;
305
306 *       In Haskell, the expressions "abc" and ['a','b','c'] are equivalent. (Strings are just lists of chars. In OCaml, these expressions have two different types.
307
308         Haskell uses the operator `++` for appending both strings and lists (since Haskell strings are just one kind of list). OCaml uses different operators:
309
310                 "string1" ^ "string2"
311                 ['s';'t'] @ ['r';'i';'n';'g']
312                 (* or equivalently *)
313                 List.append ['s';'t'] ['r';'i';'n';'g']
314
315
316 #Let and Where#
317
318 *       Haskell permits both:
319
320                 foo x =
321                   let result1 = x * x
322                       result2 = x + 1
323                   in result1 + result2
324
325         and:
326
327                 foo x = result1 + result2
328                   where result1 = x * x
329                         result2 = x + 1
330
331         OCaml permits only:
332
333                 let foo x =
334                   let result1 = x * x
335                   in let result2 = x + 1
336                   in result1 + result2;;
337
338 #Patterns#
339
340 *       In OCaml:
341
342                 # let (x, y) as both = (1, 2)
343                   in (both, x, y);;
344                 - : (int * int) * int * int = ((1, 2), 1, 2)
345
346
347         The same in Haskell:
348
349                 let both@(x,y) = (1, 2)
350                   in (both, x, y)
351
352 *       In OCaml:
353
354                 match list_expression with
355                   | y::_ when odd y -> result1
356                   | y::_ when y > 5 -> result2
357                   | y::_ as whole -> (whole, y)
358                   | [] -> result4
359
360         The same in Haskell:
361
362                 case list_expression of
363                   (y:_) | odd y -> result1
364                         | y > 5 -> result2
365                   whole@(y:_) -> (whole, y)
366                   [] -> result4
367
368
369 #Records#
370
371 Haskell and OCaml both have `records`, which are essentially just tuples with a pretty interface. The syntax for declaring and using these is a little bit different in the two languages.
372
373 *       In Haskell one says:
374
375                 -- declare a record type
376                 data Color = C { red, green, blue :: Int }
377                 -- create a value of that type
378                 let c = C { red = 0, green = 127, blue = 255 }
379
380         In OCaml one says instead:
381
382                 type color = { red : int; green : int; blue : int};;
383                 let c = { red = 0; green = 127; blue = 255 }
384
385         Notice that OCaml doesn't use any value constructor `C`. The record syntax `{ red = ...; green = ...; blue = ... }` is by itself the constructor. The record labels `red`, `green`, and `blue` cannot be re-used for any other record type.
386
387 *       In Haskell, one may have multiple constructors for a single record type, and one may re-use record labels within that type, so long as the labels go with fields of the same type:
388
389                 data FooType = Constructor1 {f :: Int, g :: Float} | Constructor2 {f :: Int, h :: Bool}
390
391 *       In Haskell, one can extract the field of a record like this:
392
393                 let c = C { red = 0, green = 127, blue = 255 }
394                 in red c    -- evaluates to 0
395
396         In OCaml:
397
398                 let c = { red = 0; green = 127; blue = 255 }
399                 in c.red    (* evaluates to 0 *)
400
401 *       In both languages, there is a special syntax for creating a copy of an existing record, with some specified fields altered. In Haskell:
402
403                 let c2 = c { green = 50, blue = 50 }
404                 -- evaluates to C { red = red c, green = 50, blue = 50 }
405
406         In OCaml:
407
408                 let c2 = { c with green = 50; blue = 50 }
409                 (* evaluates to { red = c.red; green = 50; blue = 50 }
410
411 *       One pattern matches on records in similar ways. In Haskell:
412
413                 let C { red = r, green = g } = c
414                 in r
415
416         In OCaml:
417
418                 let { red = r; green = g } = c
419                 in r
420
421         In Haskell:
422
423                 makegray c@(C { red = r} ) = c { green = r, blue = r }
424
425         is equivalent to:
426
427                 makegray c = let C { red = r } = c
428                              in { red = r, green = r, blue = r }
429
430         In OCaml it's:
431
432                 # let makegray ({red = r} as c) = { c with green=r; blue=r };;
433                 val makegray : color -> color = <fun>
434                 # makegray { red = 0; green = 127; blue = 255 };;
435                 - : color = {red = 0; green = 0; blue = 0}
436
437
438 #Functions#
439
440 *       In Haskell functions are assumed to be recursive, and their types and applications to values matching different patterns are each declared on different lines. So we have:
441
442                 factorial    :: int -> int
443                 factorial 0  =  1
444                 factorial n  =  n * factorial (n-1)
445
446         In OCaml you must explicitly say when a function is recursive; and this would be written instead as:
447
448                 let rec factorial (n : int) : int =
449                   match n with
450                     | 0 -> 1
451                     | x -> x * factorial (x-1)
452
453         or:
454
455                 let rec factorial : int -> int =
456                   fun n -> match n with
457                     | 0 -> 1
458                     | x -> x * factorial (x-1)
459
460         or (though we recommend not using this last form):
461
462                 let rec factorial : int -> int =
463                   function
464                     | 0 -> 1
465                     | x -> x * factorial (x-1)
466
467 *       Another example, in Haskell:
468
469                 length         :: [a] -> Integer
470                 length []      =  0
471                 length (x:xs)  =  1 + length xs
472
473         In OCaml:
474
475                 let rec length : 'a list -> int =
476                   fun lst -> match lst with
477                     | [] -> 0
478                     | x::xs -> 1 + length xs
479
480 *       Another example, in Haskell:
481
482                 sign x | x >  0      = 1
483                        | x == 0      = 0
484                        | otherwise   = -1
485
486         In OCaml:
487
488                 let sign x = match x with
489                   | x' when x' > 0 -> 1
490                   | x' when x' = 0 -> 0
491                   | _ -> -1
492
493 *       In Haskell the equality comparison operator is `==`, and the non-equality operator is `/=`. In OCaml, `==` expresses "physical identity", which has no analogue in Haskell because Haskell has no mutable types. See our discussion of "Four grades of mutable involvement" in the [[Week9]] notes. In OCaml the operator corresponding to Haskell's `==` is just `=`, and the corresponding non-equality operator is `<>`.
494
495 *       In both Haskell and OCaml, one can use many infix operators as prefix functions by parenthesizing them. So for instance:
496
497                 (+) 1 2
498
499         will work in both languages. One notable exception is that in OCaml you can't do this with the list constructor `::`:
500
501         # (::) 1 [1;2];;
502         Error: Syntax error
503         # (fun x xs -> x :: xs) 1 [1; 2];;
504         - : int list = [1; 1; 2]
505
506 *       Haskell also permits two further shortcuts here that OCaml has no analogue for. In Haskell, in addition to writing:
507
508                 (>) 2 1
509
510         you can also write either of:
511
512                 (1 >) 2
513                 (> 2) 1
514
515         In OCaml one has to write these out longhand:
516
517                 (fun y -> 1 > y) 2;;
518                 (fun x -> x > 2) 1;;
519
520         Also, in Haskell, there's a special syntax for using what are ordinarily prefix functions into infix operators:
521
522                 Prelude> elem 1 [1, 2]
523                 True
524                 Prelude> 1 `elem` [1, 2]
525                 True
526
527         In OCaml one can't do that. There's only:
528
529                 # List.mem 1 [1; 2];;
530                 - : bool = true
531
532 *       In Haskell one writes anonymous functions like this:
533
534                 \x -> x + 1
535
536         In OCaml it's:
537
538                 fun x -> x + 1
539
540 *       Haskell uses the period `.` as a composition operator:
541
542                 g . f
543                 -- same as
544                 \x -> g (f x)
545
546         In OCaml one has to write it out longhand:
547
548                 fun x -> g (f x)
549
550 *       In Haskell, expressions like this:
551
552                 g $ f x y
553
554         are equivalent to:
555
556                 g (f x y)
557
558         (Think of the period in our notation for the untyped lambda calculus.)
559
560 *       The names of standard functions, and the order in which they take their arguments, may differ. In Haskell:
561
562                 Prelude> :t foldr
563                 foldr :: (a -> b -> b) -> b -> [a] -> b
564
565         In OCaml:
566
567                 # List.fold_right;;
568                 - : ('a -> 'b -> 'b) -> 'a list -> 'b -> 'b = <fun>
569
570 *       Some functions are predefined in Haskell but not in OCaml. Here are OCaml definitions for some common ones:
571
572         let id x = x;;
573         let const x _ = x;;
574         let flip f x y = f y x;;
575         let curry (f : ('a, 'b) -> 'c) = fun x y -> f (x, y);;
576         let uncurry (f : 'a -> 'b -> 'c) = fun (x, y) -> f x y;;
577         let null lst = lst = [];;
578
579         `fst` and `snd` (defined only on pairs) are provided in both languages. Haskell has `head` and `tail` for lists; these will raise an exception if applied to []. In OCaml the corresponding functions are `List.hd` and `List.tl`. Many other Haskell list functions like `length` are available in OCaml as `List.length`, but OCaml's standard libraries are leaner that Haskell's.
580
581 *       The `until` function in Haskell is used like this:
582
583                 until (\l -> length l == 4) (1 : ) []
584                 -- evaluates to [1,1,1,1]
585
586                 until (\x -> x == 10) succ 0
587                 -- evaluates to 10
588
589         This can be defined in OCaml as:
590
591     let rec until test f z =
592         if test z then z else until test f (f z)
593
594
595 #Lazy or Eager#
596
597 *       As we've mentioned several times, Haskell's evaluation is by default *lazy* or "call-by-need" (that's an efficient version of "call-by-name" that avoids computing the same results again and again). In some places Haskell will force evaluation to be *eager* or "strict". This is done in several different ways; the symbols `!` and `seq` are signs that it's being used.
598
599 *       Like Scheme and most other languages, OCaml is by default eager. Laziness can be achieved either by using thunks:
600
601                 # let eval_later1 () = 2 / 2;;
602                 val eval_later1 : unit -> int = <fun>
603                 # let eval_later2 () = 2 / 0;;
604                 val eval_later2 : unit -> int = <fun>
605                 # eval_later1 ();;
606                 - : int = 1
607                 # eval_later2 ();;
608                 Exception: Division_by_zero.
609
610         or by using the special forms `lazy` and `Lazy.force`:
611
612                 # let eval_later3 = lazy (2 / 2);;
613                 val eval_later3 : int lazy_t = <lazy>
614                 # Lazy.force eval_later3;;
615                 - : int = 1
616                 # eval_later3;;
617                 - : int lazy_t = lazy 1
618
619         Notice in the last line the value is reported as being `lazy 1` instead of `<lazy>`. Since the value has once been forced, it won't ever need to be recomputed. The thunks are less efficient in this respect. Even though OCaml will now remember that `eval_later3` should be forced to, `eval_later3` is still type distinct from a plain `int`.
620
621
622 #Monads#
623
624 Haskell has more built-in support for monads, but one can define the monads one needs in OCaml.
625
626 *       In our seminar, we've been calling one monadic operation `unit`, in Haskell the same operation is called `return`. We've been calling another monadic operation `bind`, used in prefix form, like this:
627
628                 bind u f
629
630         In Haskell, one uses the infix operator `>>=` to express bind instead:
631
632                 u >>= f
633
634         If you like this Haskell convention, you can define (>>=) in OCaml like this:
635
636                 let (>>=) = bind;;
637
638 *       Haskell also uses the operator `>>`, where `u >> v` means the same as `u >>= \_ -> v`.
639
640 *       In Haskell, one can generally just use plain `return` and `>>=` and the compiler will infer what monad you must be talking about from the surrounding type constraints. In OCaml, you generally need to be specific about which monad you're using. So in these notes, when mutiple monads are on the table, we've defined operations as `reader_unit` and `reader_bind`.
641
642 *       Haskell has a special syntax for working conveniently with monads. It looks like this. Assume `u` `v` and `w` are values of some monadic type `M a`. Then `x` `y` and `z` will be variables of type `a`:
643
644                 do
645                   x <- u
646                   y <- v
647                   w
648                   let z = foo x y
649                   return z
650
651         This is equivalent in meaning to the following:
652
653                 u >>= \ x ->
654                 v >>= \ y ->
655                 w >>= \ _ ->
656                 let z = foo x y
657                 in unit z
658
659         which can be translated straightforwardly into OCaml.
660
661 *       If you like the Haskell do-notation, there's [a library](http://www.cas.mcmaster.ca/~carette/pa_monad/) you can compile and install to let you use something similar in OCaml.
662
663 *       In order to do any printing, Haskell has to use a special `IO` monad. So programs will look like this:
664
665                 main :: IO ()
666                 main = do
667                   let s = "hello world"
668                   putStrLn s
669         
670                 main :: IO String
671                 main = do
672                   let s = "hello world"
673                   putStrLn s
674                   return s
675         
676                 main :: IO String
677                 main = let s = "hello world"
678                        in putStrLn s >> return s
679
680         OCaml permits you to mix side-effects with regular code, so you can just print, without needing to bring in any monad:
681
682                 let main =
683                   let s = "hello world"
684                   in let () = print_endline s
685                   in s;;
686
687         or:
688
689                 let main =
690                   let s = "hello world"
691                   in print_endline s ; s;;
692