translating tweaks
[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 closer to Haskell's than to Scheme's.
12
13 ##Comments, Whitespace, and Brackets##
14
15                 -- this is a single line comment in Haskell
16
17                 {- this
18                    is a multiline
19                    comment in Haskell -}
20
21                 (* this is a single or multiline
22                    comment in OCaml *)
23
24                 ; this is a single line comment in Scheme
25
26                 #| this is a
27                    multiline comment
28                    in Scheme |#
29
30                 #;(this is
31                     (another way to
32                       (comment out (a block) (of Scheme code))))
33
34 *       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.
35
36 *       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.
37
38
39 ##Scheme and OCaml##
40
41 *       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!
42
43 *       **Type Variants and Pattern Matching** If you want to reproduce this kind of OCaml code:
44
45                 type lambda_expression = Var of char | Lam of char * lambda_expression | App of lambda_expression * lambda_expression;;
46
47                 let rec free_vars (expr : lambda_expression) : char list =
48                   match expr with
49                     | Var label -> [label]
50                     | Lam (label, body) -> remove label (free_vars body)
51                     | App (left, right) -> merge (free_vars left) (free_vars right);;
52
53         in Scheme, you have two choices. First, the quick hack:
54
55                 ; we use the symbols 'var and 'lam as tags, and assume
56                 ; that an expression will always be a pair of one of these forms:
57                 ;       (cons 'var symbol)
58                 ;       (cons (cons 'lam symbol) expression)
59                 ;       (cons expression expression)
60
61                 (define (free-vars expr)
62                   (cond
63                     [(eq? (car expr) 'var) (list (cdr expr))]
64                     [(and? (pair? (car expr)) (eq? (car (car expr)) 'lam))
65                       (remove (cdr (car expr)) (free-vars (cdr expr)))]
66                     [else (merge (free-vars (car expr)) (free-vars (cdr expr)))]))
67
68         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.
69
70         (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>.)
71
72         Here is how the tools from EoPL work. You must begin your file either with `#lang eopl` or with the first two lines below:
73
74                 #lang racket
75                 (require eopl/eopl)
76
77                 (define-datatype lambda-expression lambda-expression?
78                   (var (label symbol?))
79                   (lam (label symbol?) (body lambda-expression?))
80                   (app (left lambda-expression?) (right lambda-expression?)))
81
82                 (define (free-vars expr)
83                   (cases lambda-expression expr
84                     (var (label) (list label))
85                     (lam (label body) (remove label (free-vars body)))
86                     (app (left right) (remove-duplicates (append (free-vars left) (free-vars right))))))
87
88
89 *       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>.
90
91         In Scheme you can use these forms by default (they're equivalent):
92
93                 (call/cc (lambda (k) ...))
94                 (let/cc k ...)
95
96         If your program declares `(require racket/control)`, you can also use:
97
98                 (begin ... (reset ... (shift k ...) ...) ...)
99
100                 (begin ... (prompt ... (control k ...) ...) ...)
101
102                 (begin ... (prompt ... (abort value) ...) ...)
103
104         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.
105
106         But assuming you do manage to compile and install Oleg's library, here's how you'd use it in an OCaml session:
107
108                 #require "delimcc";; (* loading Oleg's library this way requires the findlib package *)
109                 open Delimcc;; (* this lets you say e.g. new_prompt instead of Delimcc.new_prompt *)
110                 let p = new_prompt ();;
111                 let prompt thunk = push_prompt p thunk;;
112                 let foo =
113                   ...
114                   prompt (fun () ->
115                     ...
116                     shift p (fun k -> ...)
117                     ...
118                     (* or *)
119                     control p (fun k -> ...)
120                     ...
121                     (* or *)
122                     abort p value
123                     ...
124                   )
125                   ...
126
127         There is also a library for using *undelimited* continuations in OCaml, but it's shakier than Oleg's delimited continuation library.
128
129 We won't say any more about translating to and from Scheme.
130
131
132 ##Haskell and OCaml##
133
134 We will however try to give some general advice about how to translate between OCaml and Haskell.
135
136 *       Again, it may sometimes be useful to [try Haskell in your web browser](http://tryhaskell.org/)
137 *       There are many Haskell tutorials and textbooks available. This is probably the most actively developed: [Haskell Wikibook](http://en.wikibooks.org/wiki/Haskell)
138 *       [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)
139 *       All About Monads has supposedly also been integrated into the Haskell Wikibook
140 *       (A not-so-)[Gentle Introduction to Haskell](http://web.archive.org/web/http://www.haskell.org/tutorial/) (archived)
141 *       [Learn You a Haskell for Great Good](http://learnyouahaskell.com/)
142
143
144 #Type expressions#
145
146 *       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`.
147
148 *       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").
149 So we have:
150
151                 data Either a b = Left a | Right b;
152                 data FooType a b = Foo_constructor1 a b | Foo_constructor2 a b;
153
154         In printed media, Haskell type variables are often written using Greek letters, like this:
155
156         <pre><code>type Either &alpha; &beta; = Left &alpha; | Right &beta;
157         </code></pre>
158
159         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:
160
161                 map Left [1, 2]
162
163         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:
164
165                 type ('a,'b) either = Left of 'a | Right of 'b;;
166                 type ('a,'b) foo_type = Foo_constructor1 of 'a * 'b | Foo_constructor2 of 'a * 'b;;
167
168         In OCaml, constructors aren't full-fledged functions, so you need to do this instead:
169
170                 List.map (fun x -> Left x) [1; 2]
171
172         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:
173
174                 let Left x = Left 1 in x + 1
175
176 *       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:
177
178                 type Weight = Integer
179                 type Person = (Name, Address)    -- supposing types Name and Address to be declared elsewhere
180
181         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:
182
183                 newtype PersonalData a = PD a
184
185         You could also say:
186
187                 data PersonalData a = PD a
188
189         And `data` also allows multiple type arguments, and multiple variants and value constructors.
190
191         OCaml just uses the one keyword `type` for all of these purposes:
192
193                 type weight = int;;
194                 type person = name * address;;
195                 type 'a personal_data = PD of 'a;;
196
197 *       The type constructors discussed above took simple types as arguments. In Haskell, types are also allowed to take *type constructors* as arguments:
198
199                 data BarType t = Bint (t Integer) | Bstring (t string)
200
201         One does this for example when defining monad transformers---the type constructor `ReaderT` takes some base monad's type constructor as an argument.
202
203         The way to do this this in OCaml is less straightforward. [See here](/code/tree_monadize.ml) for an example.
204
205 *       Haskell has a notion of *type-classes*. They look like this:
206
207                 class Eq a where
208                   (==)    :: a -> a -> Bool
209
210         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:
211
212                 instance Eq Integer where
213                   x == y  =  ...
214
215         Type expressions can be conditional on some of their parameters belonging to certain type-classes. For example:
216
217                 elem      :: (Eq a) => a -> [a] -> Bool
218
219         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`.
220
221         Similarly:
222
223                 instance (Eq a) => Eq (Tree a) where
224                   Leaf a         == Leaf b          =  a == b
225                   (Branch l1 r1) == (Branch l2 r2)  =  (l1==l2) && (r1==r2)
226                   _              == _               =  False
227
228         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`...
229
230 *       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.
231
232
233 *       Some specific differences in how certain types are expressed. This block in Haskell:
234
235                 Prelude> type Maybe a = Nothing | Just a
236                 Prelude> let x = [] :: [Int]
237                 Prelude> :t x
238                 x :: [Int]
239                 Prelude> let x = () :: ()
240                 Prelude> let x = (1, True) :: (Int, Bool)
241
242 corresponds to this block in OCaml:
243
244                 # type 'a option = None | Some of 'a;;
245                 type 'a option = None | Some of 'a
246                 # let (x : int list) = [];;
247                 val x : int list = []
248                 # let (x : unit) = ();;
249                 val x : unit = ()
250                 # let (x : int * bool) = (1, true);;
251                 val x : int * bool = (1, true)
252
253 *       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:
254
255                 # 1 + 2;;
256                 - : int = 3
257                 # 1.0 + 2.0;;
258                 Error: This expression has type float but an expression was expected of type int
259                 # 1.0 +. 2.0;;
260                 - : float = 3.
261
262         However the comparison operators are polymorphic. You can equally say:
263
264                 # 1 = 2;;
265                 - : bool = false
266                 # 1.0 = 2.0;;
267                 - : bool = false
268                 # 2 > 1;;
269                 - : bool = true
270                 # 2.0 > 1.0;;
271                 - : bool = true
272
273         But you must still apply these operators to expressions of the same type:
274
275                 # 2.0 > 1;;
276                 Error: This expression has type int but an expression was expected of type float
277
278 * We'll discuss differences between Haskell's and OCaml's record types below.
279
280
281 #Lists, Tuples, Unit, Booleans#
282
283 *       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.
284
285 *       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.
286
287 *       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:
288
289                 lst == []
290                 null lst
291
292         In OCaml, there is no predefined `null` or `isempty` function. One can still test whether a list is empty using the comparison `lst = []`.
293
294 *       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.
295
296 *       Haskell has *list comprehensions*:
297
298                 [ x * x | x <- [1..10], odd x]
299
300         In OCaml, one has to write this out longhand:
301
302                 List.map (fun x -> x * x) (List.filter odd [1..10]);;
303
304 *       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.
305
306         Haskell uses the operator `++` for appending both strings and lists (since Haskell strings are just one kind of list). OCaml uses different operators:
307
308                 "string1" ^ "string2"
309                 ['s';'t'] @ ['r';'i';'n';'g']
310                 (* or equivalently *)
311                 List.append ['s';'t'] ['r';'i';'n';'g']
312
313
314 #Let and Where#
315
316 *       Haskell permits both:
317
318                 foo x =
319                   let result1 = x * x
320                       result2 = x + 1
321                   in result1 + result2
322
323         and:
324
325                 foo x = result1 + result2
326                   where result1 = x * x
327                         result2 = x + 1
328
329         OCaml permits only:
330
331                 let foo x =
332                   let result1 = x * x
333                   in let result2 = x + 1
334                   in result1 + result2;;
335
336 #Patterns#
337
338 *       In OCaml:
339
340                 # let (x, y) as both = (1, 2)
341                   in (both, x, y);;
342                 - : (int * int) * int * int = ((1, 2), 1, 2)
343
344
345         The same in Haskell:
346
347                 let both@(x,y) = (1, 2)
348                   in (both, x, y)
349
350 *       In OCaml:
351
352                 match list_expression with
353                   | y::_ when odd y -> result1
354                   | y::_ when y > 5 -> result2
355                   | y::_ as whole -> (whole, y)
356                   | [] -> result4
357
358         The same in Haskell:
359
360                 case list_expression of
361                   (y:_) | odd y -> result1
362                         | y > 5 -> result2
363                   whole@(y:_) -> (whole, y)
364                   [] -> result4
365
366
367 #Records#
368
369 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.
370
371 *       In Haskell one says:
372
373                 -- declare a record type
374                 data Color = C { red, green, blue :: Int }
375                 -- create a value of that type
376                 let c = C { red = 0, green = 127, blue = 255 }
377
378         In OCaml one says instead:
379
380                 type color = { red : int; green : int; blue : int};;
381                 let c = { red = 0; green = 127; blue = 255 }
382
383         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.
384
385 *       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:
386
387                 data FooType = Constructor1 {f :: Int, g :: Float} | Constructor2 {f :: Int, h :: Bool}
388
389 *       In Haskell, one can extract the field of a record like this:
390
391                 let c = C { red = 0, green = 127, blue = 255 }
392                 in red c    -- evaluates to 0
393
394         In OCaml:
395
396                 let c = { red = 0; green = 127; blue = 255 }
397                 in c.red    (* evaluates to 0 *)
398
399 *       In both languages, there is a special syntax for creating a copy of an existing record, with some specified fields altered. In Haskell:
400
401                 let c2 = c { green = 50, blue = 50 }
402                 -- evaluates to C { red = red c, green = 50, blue = 50 }
403
404         In OCaml:
405
406                 let c2 = { c with green = 50; blue = 50 }
407                 (* evaluates to { red = c.red; green = 50; blue = 50 }
408
409 *       One pattern matches on records in similar ways. In Haskell:
410
411                 let C { red = r, green = g } = c
412                 in r
413
414         In OCaml:
415
416                 let { red = r; green = g } = c
417                 in r
418
419         In Haskell:
420
421                 makegray c@(C { red = r} ) = c { green = r, blue = r }
422
423         is equivalent to:
424
425                 makegray c = let C { red = r } = c
426                              in { red = r, green = r, blue = r }
427
428         In OCaml it's:
429
430                 # let makegray ({red = r} as c) = { c with green=r; blue=r };;
431                 val makegray : color -> color = <fun>
432                 # makegray { red = 0; green = 127; blue = 255 };;
433                 - : color = {red = 0; green = 0; blue = 0}
434
435
436 #Functions#
437
438 *       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:
439
440                 factorial    :: int -> int
441                 factorial 0  =  1
442                 factorial n  =  n * factorial (n-1)
443
444         In OCaml you must explicitly say when a function is recursive; and this would be written instead as:
445
446                 let rec factorial (n : int) : int =
447                   match n with
448                     | 0 -> 1
449                     | x -> x * factorial (x-1)
450
451         or:
452
453                 let rec factorial : int -> int =
454                   fun n -> match n with
455                     | 0 -> 1
456                     | x -> x * factorial (x-1)
457
458         or (though we recommend not using this last form):
459
460                 let rec factorial : int -> int =
461                   function
462                     | 0 -> 1
463                     | x -> x * factorial (x-1)
464
465 *       Another example, in Haskell:
466
467                 length         :: [a] -> Integer
468                 length []      =  0
469                 length (x:xs)  =  1 + length xs
470
471         In OCaml:
472
473                 let rec length : 'a list -> int =
474                   fun lst -> match lst with
475                     | [] -> 0
476                     | x::xs -> 1 + length xs
477
478 *       Another example, in Haskell:
479
480                 sign x | x >  0      = 1
481                        | x == 0      = 0
482                        | otherwise   = -1
483
484         In OCaml:
485
486                 let sign x = match x with
487                   | x' when x' > 0 -> 1
488                   | x' when x' = 0 -> 0
489                   | _ -> -1
490
491 *       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 `<>`.
492
493 *       In both Haskell and OCaml, one can use many infix operators as prefix functions by parenthesizing them. So for instance:
494
495                 (+) 1 2
496
497         will work in both languages. One notable exception is that in OCaml you can't do this with the list constructor `::`:
498
499         # (::) 1 [1;2];;
500         Error: Syntax error
501         # (fun x xs -> x :: xs) 1 [1; 2];;
502         - : int list = [1; 1; 2]
503
504 *       Haskell also permits two further shortcuts here that OCaml has no analogue for. In Haskell, in addition to writing:
505
506                 (>) 2 1
507
508         you can also write either of:
509
510                 (1 >) 2
511                 (> 2) 1
512
513         In OCaml one has to write these out longhand:
514
515                 (fun y -> 1 > y) 2;;
516                 (fun x -> x > 2) 1;;
517
518         Also, in Haskell, there's a special syntax for using what are ordinarily prefix functions into infix operators:
519
520                 Prelude> elem 1 [1, 2]
521                 True
522                 Prelude> 1 `elem` [1, 2]
523                 True
524
525         In OCaml one can't do that. There's only:
526
527                 # List.mem 1 [1; 2];;
528                 - : bool = true
529
530 *       In Haskell one writes anonymous functions like this:
531
532                 \x -> x + 1
533
534         In OCaml it's:
535
536                 fun x -> x + 1
537
538 *       Haskell uses the period `.` as a composition operator:
539
540                 g . f
541                 -- same as
542                 \x -> g (f x)
543
544         In OCaml one has to write it out longhand:
545
546                 fun x -> g (f x)
547
548 *       In Haskell, expressions like this:
549
550                 g $ f x y
551
552         are equivalent to:
553
554                 g (f x y)
555
556         (Think of the period in our notation for the untyped lambda calculus.)
557
558 *       The names of standard functions, and the order in which they take their arguments, may differ. In Haskell:
559
560                 Prelude> :t foldr
561                 foldr :: (a -> b -> b) -> b -> [a] -> b
562
563         In OCaml:
564
565                 # List.fold_right;;
566                 - : ('a -> 'b -> 'b) -> 'a list -> 'b -> 'b = <fun>
567
568 *       Some functions are predefined in Haskell but not in OCaml. Here are OCaml definitions for some common ones:
569
570         let id x = x;;
571         let const x _ = x;;
572         let flip f x y = f y x;;
573         let curry (f : ('a, 'b) -> 'c) = fun x y -> f (x, y);;
574         let uncurry (f : 'a -> 'b -> 'c) = fun (x, y) -> f x y;;
575         let null lst = lst = [];;
576
577         `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.
578
579 *       The `until` function in Haskell is used like this:
580
581                 until (\l -> length l == 4) (1 : ) []
582                 -- evaluates to [1,1,1,1]
583
584                 until (\x -> x == 10) succ 0
585                 -- evaluates to 10
586
587         This can be defined in OCaml as:
588
589     let rec until test f z =
590         if test z then z else until test f (f z)
591
592
593 #Lazy or Eager#
594
595 *       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.
596
597 *       Like Scheme and most other languages, OCaml is by default eager. Laziness can be achieved either by using thunks:
598
599                 # let eval_later1 () = 2 / 2;;
600                 val eval_later1 : unit -> int = <fun>
601                 # let eval_later2 () = 2 / 0;;
602                 val eval_later2 : unit -> int = <fun>
603                 # eval_later1 ();;
604                 - : int = 1
605                 # eval_later2 ();;
606                 Exception: Division_by_zero.
607
608         or by using the special forms `lazy` and `Lazy.force`:
609
610                 # let eval_later3 = lazy (2 / 2);;
611                 val eval_later3 : int lazy_t = <lazy>
612                 # Lazy.force eval_later3;;
613                 - : int = 1
614                 # eval_later3;;
615                 - : int lazy_t = lazy 1
616
617         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`.
618
619
620 #Monads#
621
622 Haskell has more built-in support for monads, but one can define the monads one needs in OCaml.
623
624 *       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:
625
626                 bind u f
627
628         In Haskell, one uses the infix operator `>>=` to express bind instead:
629
630                 u >>= f
631
632         If you like this Haskell convention, you can define (>>=) in OCaml like this:
633
634                 let (>>=) = bind;;
635
636 *       Haskell also uses the operator `>>`, where `u >> v` means the same as `u >>= \_ -> v`.
637
638 *       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`.
639
640 *       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`:
641
642                 do
643                   x <- u
644                   y <- v
645                   w
646                   let z = foo x y
647                   return z
648
649         This is equivalent in meaning to the following:
650
651                 u >>= \ x ->
652                 v >>= \ y ->
653                 w >>= \ _ ->
654                 let z = foo x y
655                 in unit z
656
657         which can be translated straightforwardly into OCaml.
658
659 *       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.
660
661 *       In order to do any printing, Haskell has to use a special `IO` monad. So programs will look like this:
662
663                 main :: IO ()
664                 main = do
665                   let s = "hello world"
666                   putStrLn s
667         
668                 main :: IO String
669                 main = do
670                   let s = "hello world"
671                   putStrLn s
672                   return s
673         
674                 main :: IO String
675                 main = let s = "hello world"
676                        in putStrLn s >> return s
677
678         OCaml permits you to mix side-effects with regular code, so you can just print, without needing to bring in any monad:
679
680                 let main =
681                   let s = "hello world"
682                   in let () = print_endline s
683                   in s;;
684
685         or:
686
687                 let main =
688                   let s = "hello world"
689                   in print_endline s ; s;;
690