[Template-haskell] quasi quotes and Q monad
Tomasz Zielonka
tomasz.zielonka at gmail.com
Tue Jan 3 15:32:56 EST 2006
On Tue, Jan 03, 2006 at 04:13:53PM +0100, Ch. A. Herrmann wrote:
> the comparison doesn't work with the IO monad because the user runs the
> Q monad every time when splicing a generated expression.
I am not sure about it. At least it seems that the "name generation
state" is passed between splices. Try this:
module Gen where
import Language.Haskell.TH
gen :: Q [Dec]
gen = do
a <- newName "a"
b <- newName "b"
expr <- [| (1, 2) |]
return [ValD (TupP [VarP a, VarP b]) (NormalB expr) []]
----------------------------------------
module X where
import Gen
$(gen)
$(gen)
$(gen)
$(gen)
$(gen)
:browse X shows something like this:
a[a2ss] :: Integer
a[a2us] :: Integer
a[a2vj] :: Integer
a[a2wa] :: Integer
a[a2x1] :: Integer
b[a2su] :: Integer
b[a2uu] :: Integer
b[a2vl] :: Integer
b[a2wc] :: Integer
b[a2x3] :: Integer
BTW, you can use such a definition g:
(\x -> [| h $(return x) |])
now x can be Expr. It's just moving "return" into g.
Best regards
Tomasz
--
I am searching for programmers who are good at least in
(Haskell || ML) && (Linux || FreeBSD || math)
for work in Warsaw, Poland
More information about the template-haskell
mailing list