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:[EMAIL PROTECTED]]
| Sent: 27 November 2002 06:19
| To: [EMAIL PROTECTED]
| Subject: Template Haskell
| 
| Hi there.
| 
| Could somebody please let me know where I've gone wrong in the program
below
| (yesterday's CVS HEAD stage 3 compiler on Windows)?
| 
| ------------- TH - printf.hs ---
| 
| module Main where
| 
| import Language.Haskell.THSyntax
| 
| data Format = D | S | L String
| 
| main = putStrLn ( $(pr "Hello") )
| 
| parse :: String -> [Format]
| parse s   = [ L s ]
| 
| gen :: [Format] -> Expr
| gen [D]   = [| \n -> show n |]
| gen [S]   = [| \s -> s |]
| gen [L s] = string s
| 
| pr :: String -> Expr
| pr s      = gen (parse s)
| 
| 
| ------------- Command Line -----
| 
| /c/cvs/i386-unknown-mingw32/stage3/ghc/compiler/ghc-inplace
-fglasgow-exts -
| package haskell-src printf.hs -o printf.exe
| 
| ------------- GHC output---------
| 
| 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 = putStrLn ($[splice](pr
"Hello"))
| 
| -----------------------------------
| 
| Thanks
| 
| Mike Thomas.
| 
| 
| _______________________________________________
| Glasgow-haskell-users mailing list
| [EMAIL PROTECTED]
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
_______________________________________________
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to