"contexts differ in length" fires when using splices in non-recursive bindings?
My TH is a bit rusty, so I'm probably doing something wrong here: {-# LANGUAGE TemplateHaskell #-} module TH where import Language.Haskell.TH monad qe = qe >>= return . AppE (VarE 'return) 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, but where the native version compiles just fine, the spliced version yields: THtest.hs:10:0: Contexts differ in length (Use -XRelaxedPolyRec to allow this) When matching the contexts of the signatures for y :: forall (m :: * -> *) a. (Monad m) => a -> m a x :: forall (m :: * -> *) a. (Monad m, Eq a) => m a The signature contexts in a mutually recursive group should all be identical When generalising the type(s) for y, x Failed, modules loaded: TH. Could someone please tell me what is causing this? In the real code, the errors are even more confusing. Try removing the type signatures, for instance, or just remove the 'Eq a' constraint, then try evaluating '[y (),x]' in GHCi. Claus
Not that this helps, but the following simplified version exhibits the same problem:
{-# LANGUAGE TemplateHaskell #-} y :: Monad m => a -> m a y a = -- return a $([| return a |])
x :: (Monad m,Eq a) => m a x = -- return undefined $([| return undefined |])
My understanding is that a splice of a quoted expression should be equivalent to the expression itself (with the caveat that different scoping rules for names apply)... e.g.
$([| x |]) == x
more or less. The error this produces seems to violate this principle.
This seems to traces back to something going on in TcBinds.generalise and related functions, but looking at this made me woozy, so I have given up for the moment...
--- On Sat, 7/12/08, Claus Reinke
From: Claus Reinke
Subject: [Template-haskell] "contexts differ in length" fires when using splices in non-recursive bindings? To: template-haskell@haskell.org Date: Saturday, July 12, 2008, 12:50 AM My TH is a bit rusty, so I'm probably doing something wrong here: {-# LANGUAGE TemplateHaskell #-} module TH where import Language.Haskell.TH monad qe = qe >>= return . AppE (VarE 'return)
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, but where the native version compiles just fine, the spliced version yields:
THtest.hs:10:0: Contexts differ in length (Use -XRelaxedPolyRec to allow this) When matching the contexts of the signatures for y :: forall (m :: * -> *) a. (Monad m) => a -> m a x :: forall (m :: * -> *) a. (Monad m, Eq a) => m a The signature contexts in a mutually recursive group should all be identical When generalising the type(s) for y, x Failed, modules loaded: TH.
Could someone please tell me what is causing this? In the real code, the errors are even more confusing. Try removing the type signatures, for instance, or just remove the 'Eq a' constraint, then try evaluating '[y (),x]' in GHCi.
Claus
_______________________________________________ template-haskell mailing list template-haskell@haskell.org http://www.haskell.org/mailman/listinfo/template-haskell
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
Thanks everyone, for confirmation, simplification, and explanation.
I think the problem is that the SCC analysis is done before the splices are run (which is during type checking),
If that is the case, shouldn't the analysis results be updated with the information emerging from splices? It still feels like a bug, and the symptoms can be very confusing.
$( [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, that works, but is rather ugly and not very practical (pity that staging splices in this way doesn't work around the we-need-two-modules issue;-). Another workaround is {-# LANGUAGE RelaxedPolyRec #-}, combined with explicit type signatures that keep the dependency analysis happy (users guide, 8.7.7). Claus
Ian has this exactly right. Yes, it is confusing, but because splices are run (and must be run) during typechecking, I don't see a reasonably easy way to fix it. A radical version would be: do a complete pass of the typechecker to run any splices; then re-dependency analyse the whole program; then do another complete typechecker pass. But I'm reluctant to do this. Meanwhile, as Claus says -XRelaxedPolyRec will help a lot. Simon | -----Original Message----- | From: template-haskell-bounces@haskell.org [mailto:template-haskell- | bounces@haskell.org] On Behalf Of Ian Lynagh | Sent: 12 July 2008 12:34 | To: template-haskell@haskell.org | Subject: Re: [Template-haskell] "contexts differ in length" fires when using | splices in non-recursive bindings? | | 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 | | _______________________________________________ | template-haskell mailing list | template-haskell@haskell.org | http://www.haskell.org/mailman/listinfo/template-haskell
participants (4)
-
Claus Reinke -
Ian Lynagh -
Robert Greayer -
Simon Peyton-Jones