#5287: The 'impossible' happened. solveDerivEqns: probable loop
-------------------------------+--------------------------------------------
Reporter: agocorona | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.0.3
Keywords: solveDerivEqns | Testcase:
Blockedby: | Difficulty:
Os: Windows | Blocking:
Architecture: x86 | Failure: Compile-time crash
-------------------------------+--------------------------------------------
Comment(by YitzGale):
I think this is a minimal case:
{{{
{-# 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
}}}
What exactly should it mean when there are
free type variables as parameters of a multi-parameter
class in the superclass context of an instance declaration?
Perhaps
{{{
instance A a oops => B (D a)
}}}
should mean something like
{{{
-- Illegal instance syntax
instance (forall oops. A a oops => B (D a))
}}}
Has this ever been specified anywhere?
Haskell 98 seems to allow free type variables
in the instance head for single-parameter type classes,
but there you can just ignore those parts of the
context.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5287#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs