[Haskell-cafe] [Template Haskell]
Dominik Bollmann
dominikbollmann at gmail.com
Mon Jan 25 10:58:49 UTC 2016
Hi all,
I'm just getting my feet wet with template haskell, and I tried to write
a tmap function which maps a function over the ith component of an
n-tuple (which uses a slightly different approach than the given
version on the TH wiki):
-- | Selects the ith component of an n-tuple
tsel :: Int -> Int -> ExpQ -- n-tuple a -> a
tsel i n = [| \t -> $(caseE [| t |] [alt]) |]
where alt = match (tupP pats) body []
pats = map varP xs
xs = [ mkName ("x" ++ show k) | k <- [1..n] ]
body = normalB . varE $ xs !! (i-1)
-- | Maps a function over the ith component of an n-tuple
tmap :: Int -> Int -> ExpQ -- :: (a -> b) -> n-tuple -> n-tuple
tmap i n = do
f <- newName "f"
t <- newName "t"
lamE [varP f, varP t] $ [|
let prefix = map extract [1..(i-1)]
new = $f ($(tsel i n) $t)
suffix = map extract [(i+1)..n]
extract k = $(tsel k n) t
in tupE $ prefix ++ [new] ++ suffix |]
However, this code results in the following error:
Sandbox.hs:26:29: Stage error: ‘k’ is bound at stage 2 but used at stage 1 …
In the splice: $(tsel k n)
In the Template Haskell quotation
[| let
prefix = map extract [1 .. (i - 1)]
new = $f ($(tsel i n) ($t))
suffix = map extract [(i + 1) .. n]
extract k = $(tsel k n) $t
in tupE $ prefix ++ [new] ++ suffix |]
Compilation failed.
Could anyone explain to me what stage 2 and stage 1 refer to, and
further, what the logical flaw in the above snippet is? What exactly is
wrong with line `extract k = $(tsel k n) $t' ?
Thanks!
Dominik.
More information about the Haskell-Cafe
mailing list