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