Not a typechecker bug; more a bizarre consequence of
overlapping instance decls.
The instance decl
instance Holidays a => Eq a
overlaps with absolutely every other instance decl for Eq.
In order to make Lattice (Inv a) an instance of Eq, we have
to satisfy Eq (Inv a), since Eq is a superclass of Lattice.
>From the data decl, we can get Eq (Inv a) if we can get Eq a.
>From the instance decl you commented out, we can get Eq a
if we can get Holidays a. But then we get stuck.
Admittedly, we can also get Eq a from Lattice a, but GHC's search
doesn't spot that (I'm not quite certain why).
Overlapping instance decls are pretty strong medicine. use
with care.
Simon
> -----Original Message-----
> From: Alex Ferguson [mailto:[EMAIL PROTECTED]]
> Sent: Wednesday, February 17, 1999 5:21 PM
> To: [EMAIL PROTECTED]
> Subject: Strange ghc-4.02 TC bug?
>
>
>
> Discern that the following program is apparently well-typed:
>
>
> module M2 where
>
> class Eq a => Lattice a where
> bottom :: a
>
> data Inv a = INV a
> deriving Eq
>
> instance Lattice a => Lattice (Inv a)
>
>
> class Holidays a where
> holCode :: a -> Int
>
> -- instance Holidays a => Eq a
>
>
> Now, uncomment the last line, and suddenly:
>
>
> ghc-4.02 -c M2.hs -H30m -K2M -recomp -fglasgow-exts
> -cpp -syslib misc
> -Rgc-stats -dshow-passes -fmax-simplifier-iterations4
> -funfolding-use-threshold-0 -optC-fallow-undecidable-instances
> -optC-fallow-overlapping-instances
> *** Reader:
> *** Renamer:
> *** TypeCheck:
>
> M2.hs:9:
> Warning: No explicit method nor default method for `bottom'
> in an instance declaration for `Lattice'
>
>
>
> M2.hs:9:
> Could not deduce `Holidays a'
> (arising from an instance declaration at M2.hs:9)
> from the context: (Lattice a)
> Probable cause: missing `Holidays a'
> in instance declaration context
> When checking the superclasses of an instance declaration
>
>
>
>
> What gives? Even more oddly, if this last line is moved to a
> different
> module, then the problem vanishes.
>
> Slan libh,
> Alex.
>