Template Haskell

Mike Thomas Mike Thomas" <miketh@brisbane.paradigmgeo.com
Wed, 27 Nov 2002 16:19:11 +1000


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.