Template Haskell

Simon Peyton-Jones simonpj@microsoft.com
Wed, 27 Nov 2002 08:45:36 -0000


If you look in the manual you'll see that it says you can only
compile-time-call a function that is in a separate module.  So put
'pr/gen/parse' in a separate module and you'll be fine.

The manual may not be very clear... pls help me improve it.

S

| -----Original Message-----
| From: Mike Thomas [mailto:miketh@brisbane.paradigmgeo.com]
| Sent: 27 November 2002 06:19
| To: glasgow-haskell-users@haskell.org
| Subject: Template Haskell
|=20
| Hi there.
|=20
| Could somebody please let me know where I've gone wrong in the program
below
| (yesterday's CVS HEAD stage 3 compiler on Windows)?
|=20
| ------------- TH - printf.hs ---
|=20
| module Main where
|=20
| import Language.Haskell.THSyntax
|=20
| data Format =3D D | S | L String
|=20
| main =3D putStrLn ( $(pr "Hello") )
|=20
| parse :: String -> [Format]
| parse s   =3D [ L s ]
|=20
| gen :: [Format] -> Expr
| gen [D]   =3D [| \n -> show n |]
| gen [S]   =3D [| \s -> s |]
| gen [L s] =3D string s
|=20
| pr :: String -> Expr
| pr s      =3D gen (parse s)
|=20
|=20
| ------------- Command Line -----
|=20
| /c/cvs/i386-unknown-mingw32/stage3/ghc/compiler/ghc-inplace
-fglasgow-exts -
| package haskell-src printf.hs -o printf.exe
|=20
| ------------- GHC output---------
|=20
| printf.hs:7:
|     Stage error: `pr' is bound at stage 1 but used at stage 0
|     In the first argument of `putStrLn', namely `($[splice](pr
"Hello"))'
|     In a right-hand side of function `main':
|  putStrLn ($[splice](pr "Hello"))
|     In the definition of `main': main =3D putStrLn ($[splice](pr
"Hello"))
|=20
| -----------------------------------
|=20
| Thanks
|=20
| Mike Thomas.
|=20
|=20
| _______________________________________________
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users@haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users