
I have an "'impossible' happened" error. The code may look a little bit convoluted but it is part of my real code.: --------- begin of code------ {-# LANGUAGE FlexibleInstances, UndecidableInstances , MultiParamTypeClasses #-} class Serializable a b class IResource a --The rest of the instance definitions does not matter for the error instance Serializable a b => IResource a data DBRef a= DBRef String a instance (IResource a) => Read (DBRef a) data Votation a= Votation{ content :: DBRef a } deriving (Read) ------------------------------- end of code --- gives the following error at compilation time: tests>runghc impossiblelloop.hs ghc: panic! (the 'impossible' happened) (GHC version 7.0.3 for i386-unknown-mingw32): solveDerivEqns: probable loop (impossiblelloop.hs:20:13-16 main:Main.$fReadVotation{v rhI} [a{tv abB} [tv] ] base:GHC.Read.Read{tc 2d} [main:Main.Votation{tc rbo} a{tv abB} [tv]] = [base:GHC.Read.Read{tc 2d} (main:Main.DBRef{tc rbu} a{tv abB} [tv])]) [[main:Main.Serializable{tc rbA} a{tv abB} [tv] b{tv ajE} [tcs]]] Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug

On Tue, Jun 28, 2011 at 3:43 AM, Alberto G. Corona
I have an "'impossible' happened" error. The code may look a little bit convoluted but it is part of my real code.:
I don't know why it's crashing, but did you already report it as a bug? If not, you definitely should.
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
That URL should have the info you need to report it. Jason

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.
-- ryan
On Tue, Jun 28, 2011 at 3:43 AM, Alberto G. Corona
I have an "'impossible' happened" error.
The code may look a little bit convoluted but it is part of my real code.:
--------- begin of code------
{-# LANGUAGE FlexibleInstances, UndecidableInstances , MultiParamTypeClasses #-}
class Serializable a b
class IResource a --The rest of the instance definitions does not matter for the error
instance Serializable a b => IResource a
data DBRef a= DBRef String a
instance (IResource a) => Read (DBRef a)
data Votation a= Votation{ content :: DBRef a } deriving (Read)
------------------------------- end of code ---
gives the following error at compilation time:
tests>runghc impossiblelloop.hs ghc: panic! (the 'impossible' happened) (GHC version 7.0.3 for i386-unknown-mingw32): solveDerivEqns: probable loop (impossiblelloop.hs:20:13-16 main:Main.$fReadVotation{v rhI} [a{tv abB} [tv] ] base:GHC.Read.Read{tc 2d} [main:Main.Votation{tc rbo}
a{tv abB} [tv]] = [base:GHC.Read.Read{tc 2d}
(main:Main.DBRef{tc rbu}
a{tv abB} [tv])]) [[main:Main.Serializable{tc rbA} a{tv abB} [tv] b{tv ajE} [tcs]]]
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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

http://hackage.haskell.org/trac/ghc/ticket/5287
El 29/06/2011 10:22, "Yitzchak Gale"
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

On Wednesday 29 June 2011, 10:22:20, Yitzchak Gale wrote:
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.
No, the instance head is just a type variable, not a type constructor applied to type variables, so it's not allowed by H98 (nor H2010, I think, haven't looked it up, but since GHC defaults to 2010 now, I'm pretty sure). So GHC rightly complains about the malformed instance head. If you enable FlexibleInstances, it gives ClassContextBug.hs:5:10: Ambiguous constraint `A a' At least one of the forall'd type variables mentioned by the constraint must be reachable from the type after the '=>' In the instance declaration for `B b' ClassContextBug.hs:5:10: Variable occurs more often in a constraint than in the instance head in the constraint: A a (Use -XUndecidableInstances to permit this) In the instance declaration for `B b' which is exactly what is wrong with the instance declaration.
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

Daniel Fischer wrote:
No, the instance head is just a type variable, not a type constructor applied to type variables
Oops, you're right. GHC was telling the truth, I should have paid closer attention! Fixing my minimal example, I get: {-# LANGUAGE MultiParamTypeClasses, UndecidableInstances #-} module ClassContextBug where class A a oops class B b data D d = D d instance A a oops => B (D a) and now GHC compiles it happily. So it's the derived Read instance in this context that is causing the problem. Here is a slightly smaller test case that triggers the bug: {-# LANGUAGE MultiParamTypeClasses, UndecidableInstances #-} module Bug where class A a oops data D d = D d instance A a oops => Read (D a) data E e = E (D e) deriving Read Thanks, Yitz

On Wednesday 29 June 2011, 11:37:39, Yitzchak Gale wrote:
So it's the derived Read instance in this context that is causing the problem. Here is a slightly smaller test case that triggers the bug:
{-# LANGUAGE MultiParamTypeClasses, UndecidableInstances #-} module Bug where class A a oops data D d = D d instance A a oops => Read (D a) data E e = E (D e) deriving Read
Just for the record, same panic with 7.0.2 and 7.0.4 (and deriving Show or Eq too). 6.12.3 reports: Can't derive instances where the instance context mentions type variables that are not data type parameters Offending constraint: A e oops When deriving the instance for (Read (E e)) which seems reasonable.
participants (5)
-
Alberto G. Corona
-
Daniel Fischer
-
Jason Dagit
-
Ryan Ingram
-
Yitzchak Gale