[Haskell-cafe] Template Haskell: let statement in a splice put in the "main = do" part of a program?
adam vogt
vogt.adam at gmail.com
Mon Aug 26 04:00:24 CEST 2013
On Sat, Aug 24, 2013 at 11:00 AM, TP <paratribulations at free.fr> wrote:
> 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?
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
More information about the Haskell-Cafe
mailing list