[Template-haskell] "contexts differ in length" fires when using splices in non-recursive bindings?

Ian Lynagh igloo at earth.li
Sat Jul 12 07:34:07 EDT 2008


On Sat, Jul 12, 2008 at 12:50:50AM +0100, Claus Reinke wrote:
> 
> The symptom appears in the following module, when I replace
> the native 'return's with the spliced ones:
> 
>    {-# LANGUAGE TemplateHaskell #-}
>    import TH
> 
>    y :: Monad m => a -> m a
>    y a = return a 
>      -- $(monad [| a |])
> 
>    x :: (Monad m,Eq a) => m a
>    x = return undefined 
>      -- $(monad [| undefined |]) 
> 
> There is no recursion, at least no intended one

I think the problem is that the SCC analysis is done before the splices
are run (which is during type checking), so GHC doesn't know that you
haven't written something like

    {-# LANGUAGE TemplateHaskell #-}
    module Main where

    main = putStrLn $ take 10 x

    y :: String
    y = $( [| 'b':x |] )

    x :: String
    x = $( [| 'a':y |] )

in which the functions /are/ recursive.

If you put

    $( [d| |] )

between the two definitions then that forces GHC to consider them as
separate binding groups (as it type checks the first binding, then runs
the splice, then type checks the second one).


Thanks
Ian



More information about the template-haskell mailing list