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