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

TP paratribulations at free.fr
Tue Aug 27 23:36:21 CEST 2013


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





More information about the Haskell-Cafe mailing list