[Haskell-cafe] [Template Haskell]

Michael Sloan mgsloan at gmail.com
Mon Jan 25 20:14:01 UTC 2016


Hi!

The issue is that "extract k = ..." is a binding of k which will be present
in the generated code (and so will be available at runtime).  The
anti-quote $(tsel k n) cannot depend on k, because it gets run at
compiletime.

Seems to me like that error message could use some improvement.  Why not
something more like "Stage error: `k' is bound in generated code but used
in compiletime code"?  AFAIK there is no such thing as stage 3 or stage 0,
so the numbering seems a bit arbitrary.

-Michael

On Mon, Jan 25, 2016 at 2:58 AM, Dominik Bollmann <dominikbollmann at gmail.com
> wrote:

>
> 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.
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20160125/1f98e9a0/attachment.html>


More information about the Haskell-Cafe mailing list