[Haskell-cafe] Possible bug in GHC 7.0.3

Yitzchak Gale gale at sefer.org
Wed Jun 29 10:22:20 CEST 2011


Ryan Ingram wrote:
> So this is definitely a GHC bug, but I think the problem is probably
> triggered by this line:
>
> instance  Serializable a b => IResource a
>
> I don't think this is a valid instance declaration without a functional
> dependency on Serializable, as it's impossible to know which type 'b' to use
> in the methods of IResource.

That's not exactly the reason why that line is a problem.
The methods of IResource don't use b. Presumably, some of
the methods of Serializable don't mention b either, and those
could be used in the instance.

But what exactly does this instance mean? Where does the
implicit "forall b" go? For this to make any sense, it would
need to be:

-- Illegal syntax for instance
instance (forall b. Serializable a b => IResource a)

I don't think it has ever been specified whether it is legal
to have free type variables as parameters of a multi-parameter
class in the superclass context of an instance declaration,
and if so, how to interpret that.

Haskell 98/2010 does seem to allow it for single-parameter
classes, but there the obvious meaning would be just to
ignore those parts of the context.

In any case, GHC does seem to be getting very confused.
Here is a smaller test case. While it does not trigger the
crash, it does cause GHC to give a seemingly nonsensical
error message:

module ClassContextBug where
class A a
class B b
instance A a => B b

ClassContextBug.hs:5:17:
    Illegal instance declaration for `B b'
      (All instance types must be of the form (T a1 ... an)
       where a1 ... an are *distinct type variables*,
       and each type variable appears at most once in the instance head.
       Use -XFlexibleInstances if you want to disable this.)
    In the instance declaration for `B b'

I believe this is valid Haskell 98, so GHC should accept it.
But even if not, what GHC is claiming in the error message
is simply not true.

I would like to add this to the bug report.
Alberto, have you filed the bug report yet? Can you please post a link?

Thanks,
Yitz



More information about the Haskell-Cafe mailing list