So, I'm starting to experiment with quasiquotation and template haskell.
I want to modify an existing (large) quasiquotation code, while using the actual value of a variable defined where it is 'called'. To illustrate with a simple example:
main.hs
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
import Language.Haskell.TH
import Exp02
x = "cde"
main = do
putStrLn [str|$x|]
Exp02.hs
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
module Exp02 where
import Language.Haskell.TH
import Language.Haskell.TH.Syntax
import Language.Haskell.TH.Quote
xpto :: String -> ExpQ
xpto [] = stringE []
xpto ('$':rest) = varE (mkName rest)
xpto str = stringE str
str = QuasiQuoter
{ quoteExp = xpto
, quotePat = fail $ "patterns"
, quoteType= fail $ "types"
, quoteDec = fail $ "declarations"
}
While this compiles and prints out "cde", this is not what I want. My understanding is that the resulting code in main after splicing is: putStrLn x
. What I want is to generate putStrLn cde
(I know this is not valid haskell code, but it's just to represent my point).
Thus, to put it in another way, I do not want to 'create a reference to the variable x
in the main file', I want to actually use its value inside the xpto
quasiquoter code.
I am guessing this may not be possible, since it would imply a circular reference between main.hs
and Exp02.hs
, and thus face the TH stage restriction. Is this correct, or is there a way to use x value inside the xpto
code?
Thanks!