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