[Haskell-cafe] Re: Ocaml for Haskellers tutorial

Pierre-Etienne Meunier pierreetienne.meunier at gmail.com
Fri Apr 16 10:27:08 EDT 2010


Hi,

Strangely enough, I did the opposit some time ago. Ocaml is way simpler than haskell, in fact. There is no referential transparency, no laziness (though it can be simulated with "fun ()->x", but the type of a lazy expression is not the same as the reduced expressions), no parallelism (the GC is not parallel). There are no list comprehensions.
The syntax for pattern matching is simpler but more restrictive, and there are loops. There are also objects, but even good caml programmers (i.e. at ICFP level) do not use it. Also, there are fewer available libraries, due to a quite immature FFI.

I should also say that the top-level is of much greater help than ghci, and I strongly recommend using tuareg-mode with emacs, which make up a very powerful combination. Have a look at these examples :

let fact n=
	if n=0 then 1 else n*(fact (n-1))

This function is of type Int->Int because the arithmetic operations are monomorphic (there are no typeclasses). If you wanted to do it with Doubles, you would have used *. +. and -. For other types, you would have been on your own ;-)

let quickSort l=match l with
	[]->[]
	| h::t -> 	let (a,b)=List.partition (fun x->x<=h) t in
			List.append (quickSort a) (h::(quickSort b))

As you can see, match is pretty close to case, except that it requires | between clauses, because the indentation is not significative. Also, lambda abstractions are called fun x-> instead of \x->. There is a syntactic sugar for combining lambdas and match :

function []->M
	| h::t->M'
which translates as fun x->match x with ...

You cannot see it here, but camlists do not define variables with indentations as in :

let 	a=
	b=
in

This would be "let a=... in let b=... in" with any number of lines and arbitrary indentation. Or "let a=... and b=... in", for instance if you want mutually recursive functions. This is because an ocaml file is evaluated in the order in which it is written, which allows for a cool top-level (by the way, the cool emacs command is C-x-e, "evaluate last expression" in tuareg mode).
The module system seems sometimes obscure, as modules do not correspond always to files, and you can define several modules in a file. You can read http://caml.inria.fr/pub/docs/manual-ocaml/manual004.html to get an idea. 

You can define custom types. There is not newtype in haskell, and the keywords for type and data are the same :

type tree a = Leaf of a | Node of (tree a)*(tree a)

Then you can match on it :
match t with
	Leaf x->
	Node (x,y)->

How to do monads ? It is very simple, actually. Some expressions are of type (), with great similarity to IO (). >>= is expressed like in C, with ;

print_string "This is a string";
print_int (a+b);
a

Would translate in haskell as :

do
	putStr "This is a string"
	print $ a+b
	return a

But the typesystem of ocaml does not require you to use monads. Also, you may have notice that there is no $ in ocaml. There is also a very fine exception system :

exception MyException;
exception MyException';
try
	if a=0 then raise MyException else raise MyException'
with
	MyException -> print_string "MyException"
	| MyException' -> print_string "MyException'"
	
Which allows you to match the value of what error you program did. The last thing you can use is references and loops :

for i=0 to n do
	...
done;

let a=ref 10
while (!a)=0 do
	print_int (!a);
	a := (!a)-1
done;

Most of the time you use mapM_ in haskell, you can do it with loops and references in ocaml, and you save the memory allocation of the list (which is not a lot, I know). You can also notice that references are much simpler to use than in haskell, due to "implicit monads" and unsafePerformIO everywhere.

What else ? Records and record updates (you may find this in the manual). And objects : maybe your future boss smokes objects, thus you can learn about this in the manual.
A good point in ocaml is that the program does, to a large extent, exactly what you write, in the order you write it.Thus, it is often simpler to know where exceptions occur, and performance is less an issue than in haskell. In fact, haskell waited more than ten years before producing fast code, whereas ocaml did it almost from the beginning.


Good luck !
Pierre-Etienne
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20100416/d8ce5e41/attachment.html


More information about the Haskell-Cafe mailing list