[Haskell-cafe] Re: Metaprogramming in Haskell vs. Ocaml

Nicolas Pouillard nicolas.pouillard at gmail.com
Tue Apr 6 09:51:03 EDT 2010


On Tue, 06 Apr 2010 09:37:59 -0400, Jacques Carette <carette at mcmaster.ca> wrote:
> One thing I should have mentionned - TH and camlp4 are really 
> equivalents.  And camlp4 is as-typed-as TH (or not, depending on your 
> point of view).  I am co-author of a camlp4 extension, and I must admit 
> that coding in camlp4 was not enjoyable, while coding in metaocaml 
> (eventually) is.

This is not exactly the same, TH is a bit more typed than camlp4 here is two
examples:

{-# LANGUAGE TemplateHaskell #-}
module Thtest1 (test) where
test = [d| f :: Int
           f = True |]

{-# LANGUAGE TemplateHaskell #-}
module Thtest2 (test) where
test = [e| 1 + x |]

These two files are rejected at compile time before being spliced in.
So there is a limited scope checking, and type checking (limited because
manually using the AST constructors allow to workaround the typechecker).

Second point, the Q monad allows to generate names in a rather safe way
compared to camlp4.

Third reification can be done on declarations done in other files. So
that we can easily inspect the types and definitions of previous things,
which a rather hard (near to impossible) in camlp4.

Best regards,

-- 
Nicolas Pouillard
http://nicolaspouillard.fr


More information about the Haskell-Cafe mailing list