[Haskell-cafe] known, I know: class contexts and mutual recursion

Iavor Diatchki iavor.diatchki at gmail.com
Mon Dec 4 12:58:30 EST 2006


Hello,

> I just tripped over the "Contexts differ in length" error message. I
> know it's not a new problem, but I thought I'd enquire as to its status.

I have run into that a number of times.  There aren't any technical
issues with solving it, in fact, depending on how one implements the
type checker, it is more work to implement this extra restriction
(Hugs and THIH don't impose this restriction).  The basic idea is that
we check values with explicit signatures after we have finished type
inference.  While we do type inference we may simply assume that the
values have their specified types.

It is proposed for fixing in Haskell' but I was surprised that it did
not seem to appear on the "definitely in" list (as far as I can
recall---I might be wrong).  Hopefully the report will be fixed
though.  Otherwise, as Ian mentioned, it works in GHC 6.6 with
-fglasgow-exts.  Also, there should be no problems with higher-ranked
types etc.

-Iavor



On 11/29/06, Conor McBride <ctm at cs.nott.ac.uk> wrote:
> For those of you who haven't seen it, here's an example, contrived but
> compact.
>
>  > data Thing
>  >   = Val Int
>  >   | Grok Thing (Maybe Int -> Int)
>
>  > eval :: Monad m => Thing -> m Int
>  > eval (Val i) = return i
>  > eval (Grok t f) = return (f (eval t))
>
> My eval function compiles ok. See? The recursive call to eval targets
> the Maybe monad, so I get
>
> *Mmm> eval (Grok (Val 5) (maybe 0 (1 +))) :: Maybe Int
> Just 6
>
> However, when I try to decompose eval as a pair of mutually recursive
> functions, namely
>
>  > foo :: Monad m => Thing -> m Int
>  > foo (Val i) = return i
>  > foo (Grok t f) = return (goo t f)
>
>  > goo :: Thing -> (Maybe Int -> Int) -> Int
>  > goo t f = f (foo t)
>
> I get
>
> Mmm.lhs:15:1:
>    Contexts differ in length
>    When matching the contexts of the signatures for
>      foo :: forall (m :: * -> *). (Monad m) => Thing -> m Int
>      goo :: Thing -> (Maybe Int -> Int) -> Int
>    The signature contexts in a mutually recursive group should all be
> identical
>
> Poking about on the web, I got the impression that this was a known
> infelicity in ghc 6.4 (which I'm using), due to be ironed out. However,
> an early-adopting colleague with 6.6 alleges that foo-goo is still
> poisonous. I'm wondering what the story is. I mean, is there some nasty
> problem lurking here which prevents the lifting of this peculiar
> restriction?
>
> I'm not in a panic about this. I have a workaround for the problem as I
> encountered it in practice. Mind you, it's the sort of thing that's
> likely to happen more often, the more you localise the effects you tend
> to use. In the above, goo doesn't throw exceptions; rather, because goo
> has a handler, it can offer a /local/ exception-throwing capability to foo.
>
> Curious
>
> Conor
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list