Template Haskell: let statement in a splice put in the "main = do" part of a program?

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... 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... 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

On Sat, Aug 24, 2013 at 11:00 AM, TP
main = do
$(makeLetStatement "a") -- print a
Is that the actual indentation you used? Because it's wrong if so, and the error you would get is the one you're reporting. Indentation matters in Haskell. In an equation for `main': main = do { $(makeLetStatement "a") }
You cannot *end* a do with a let-statement; it requires something else following it. You have nothing following it, as shown by the above fragment from the error message. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

Brandon Allbery wrote:
main = do
$(makeLetStatement "a") -- print a
Is that the actual indentation you used? Because it's wrong if so, and the error you would get is the one you're reporting. Indentation matters in Haskell.
Yes, it matters, but not after "main = do": all the lines can start at the beginning of the line. Am I wrong? Or do I not understand what you say?
In an equation for `main': main = do { $(makeLetStatement "a") }
You cannot *end* a do with a let-statement; it requires something else following it. You have nothing following it, as shown by the above fragment from the error message.
Yes, I have explained why: to be able to see the evaluation of the splice; otherwise I obtain "Not in scope: `a'" if I uncomment "-- print a" at the end of my code; I have explained everything in my initial post. TP

On Sat, Aug 24, 2013 at 11:00 AM, TP
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...
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?
Hi TP, TH quotes limited as you've noticed. One way to generate similar code is to note that: do let x = y z is the same as let x = y in do z. You can generate the latter with something like the following file, but the `a' isn't in scope for the second argument to makeLetStatement. The uglier $(dyn "a") works, though I suppose it's more verbose than manually in-lining the variable a. {-# LANGUAGE TemplateHaskell #-} import Language.Haskell.TH main = $(let makeLetStatement :: String -> ExpQ -> ExpQ makeLetStatement s rest = letE [ valD (varP (mkName s)) (normalB $ stringE s) []] rest in makeLetStatement "a" [| print $(dyn "a") |] ) -- Adam

adam vogt wrote:
TH quotes limited as you've noticed. One way to generate similar code is to note that:
do let x = y z
is the same as let x = y in do z. You can generate the latter with something like the following file, but the `a' isn't in scope for the second argument to makeLetStatement. The uglier $(dyn "a") works, though I suppose it's more verbose than manually in-lining the variable a.
{-# LANGUAGE TemplateHaskell #-} import Language.Haskell.TH
main = $(let
makeLetStatement :: String -> ExpQ -> ExpQ makeLetStatement s rest = letE [ valD (varP (mkName s)) (normalB $ stringE s) []] rest
in makeLetStatement "a" [| print $(dyn "a") |] )
Thanks Adam. Unfortunately, this solution is not satisfying because the goal is to put only one mention to "a" in the "main" part, putting all the repetitive code and ExpQ's in a separate module. Tonight, I've tried hard one more time without more success. Maybe I have to stick to non-let expressions in the "main" part of a script, when it comes to TH. It should nevertheless allow me to call functions, make tests, etc. Thanks, TP
participants (3)
-
adam vogt
-
Brandon Allbery
-
TP