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