[Haskell-cafe] Template Haskell: let statement in a splice put in the "main = do" part of a program?
TP
paratribulations at free.fr
Sat Aug 24 17:00:48 CEST 2013
Hi,
I continue to test Template Haskell, and I have some difficulties to use a
splice $() in a "do" contained in the "main" part of a program. Here is an
example. I want to make a splice that does `let a="a"` in my code.
$ cat MakeLetStatement.hs
----------------------------
{-# LANGUAGE TemplateHaskell #-}
module MakeLetStatement where
import Language.Haskell.TH
makeLetStatement :: String -> ExpQ
makeLetStatement s = return $ DoE $ [ LetS $ [ ValD (VarP $ mkName s)
(NormalB $ LitE $ StringL s) [] ]]
----------------------------
$ cat test_MakeLetStatement.hs
----------------------------
{-# LANGUAGE TemplateHaskell #-}
import MakeLetStatement
main = do
$(makeLetStatement "a")
-- print a
----------------------------
Note I have commented "print a" because otherwise I obtain "Not in scope:
`a'" that shows that `a` has not been defined correctly, but does not show
whether my splice has been correctly expanded (I use --dump-splices GHC
option, but it seems it is not working for splices in the "main = do" part).
I obtain:
$ runghc -ddump-splices test_MakeLetStatement.hs
test_MakeLetStatement.hs:7:3:
Illegal last statement of a 'do' block:
let a = "a"
(It should be an expression.)
When splicing a TH expression: do let a = "a"
In a stmt of a 'do' block: $(makeLetStatement "a")
In the expression: do { $(makeLetStatement "a") }
In an equation for `main': main = do { $(makeLetStatement "a") }
That shows that my splice has been correctly expanded: we have `let a =
"a"`. However, what happens is the same as in the following dummy script, we
have in fact defined a "do" inside the first "do" (with DoE), and so we
obtain an error because the last statement in a do block should be an
expression.
----------------------------
main = do
do let a = "a"
print a
----------------------------
So my code does not work, without surprise, but in fact my problem is to
transform a LetS statement:
http://www.haskell.org/ghc/docs/latest/html/libraries/template-haskell-2.8.0.0/Language-Haskell-TH.html#v:LetS
that has type Stmt, in an ExpQ that seems to be the only thing that we can
put in a splice. I have found that it can only be done by doE (or DoE) and
compE (or CompE) according to
http://www.haskell.org/ghc/docs/latest/html/libraries/template-haskell-2.8.0.0/Language-Haskell-TH.html#v:doE
But doE is not a solution as we have seen above, and compE is to construct
list comprehensions, which is a different thing.
So, is there any solution to my problem?
Thanks in advance,
TP
More information about the Haskell-Cafe
mailing list