GADT regression
alcremi at free.fr
alcremi at free.fr
Tue Oct 5 07:07:51 EDT 2004
Hi,
I am unable to compile the following program with ghc-6.3.20041004, due to a
regression introduced by GADT (I suppose) :
module Definition where
data UnOp a b =
OpNegate
| OpRecip
| OpNot
| OpConst
| OpUnFunc (a -> b)
instance Show (UnOp a b) where
show OpNegate = "OpNegate"
show OpRecip = "OpRecip"
show OpNot = "OpNot"
show OpConst = "OpConst"
show (OpUnFunc _) = "OpUnFunc <function>"
data (Show a) => Obs a =
KonstObs a
| forall b. (Show b) => LiftObs (UnOp b a) (Obs b)
instance (Show a) => Show (Obs a) where
show (KonstObs x) = "KonstObs " ++ show x
I get the following message :
bug.hs:23:10:
Ambiguous type variable `a' in the top-level constraint:
`Show a' arising from use of `LiftObs' at bug.hs:23:10-21
It compiles OK with 'hugs -98'
Alain
More information about the Glasgow-haskell-users
mailing list