Jeff found a nice bug here. GHC tries not to import too many
instance decls because then it has to import the types they mention,
and that means more instance decls and so on.
But here, an instance decl used a type synonym, and did so in the
interface file; but in the importing module that synonym wasn't used,
so the instance decl didn't get imported.
Solution: expand synonyms when writing instance decls into interface files.
It'll be in 4.02. If you're in a hurry,
1. add deNoteType (defn below) to types/Type.lhs
2. add a call to deNoteType in ifaceInstances in main/MkIface.lhs
thus
pp_inst (InstInfo clas tvs tys theta dfun_id _ _ _)
= let
-- The deNoteType is very important. It removes all type
-- synonyms from the instance type in interface files.
-- That in turn makes sure that when reading in instance
decls
-- from interface files that the 'gating' mechanism works
properly.
-- Otherwise you could have
-- type Tibble = T Int
-- instance Foo Tibble where ...
-- and this instance decl wouldn't get imported into a
module
-- that mentioned T but not Tibble.
forall_ty = mkSigmaTy tvs theta (deNoteType (mkDictTy clas
tys))
renumbered_ty = tidyTopType forall_ty
in
Simon
========================
deNoteType :: Type -> Type
-- Sorry for the cute name
deNoteType ty@(TyVarTy tyvar) = ty
deNoteType (TyConApp tycon tys) = TyConApp tycon (map deNoteType tys)
deNoteType (NoteTy _ ty) = deNoteType ty
deNoteType (AppTy fun arg) = AppTy (deNoteType fun) (deNoteType arg)
deNoteType (FunTy fun arg) = FunTy (deNoteType fun) (deNoteType arg)
deNoteType (ForAllTy tv ty) = ForAllTy tv (deNoteType ty)
> -----Original Message-----
> From: Jeff Lewis [mailto:[EMAIL PROTECTED]]
> Sent: Thursday, December 17, 1998 7:17 PM
> To: [EMAIL PROTECTED]
> Subject: instance bug(?)
>
>
>
> Using 4.01, outa the box, with -fglasgow-exts.
>
> I get the following complaint:
>
> Main.hs:25:
> No instance for `Probe (Trans DLX_Op (DLX_Cell DLXReg Int))'
> arising from use of `processor' at Main.hs:25
>
> Now, scanning the relevant .hi files, I have:
>
> instance __forall [_a] {PrelBase.Show _a} => {Probe.Probe
> (DLX_Trans _a)}
>
> where DLX_Trans is defined as follows (again, from the .hi file):
>
> type DLX_Trans _rxQ = Trans.Trans DLX_Op.DLX_Op (DLXCell _rxQ) ;
>
> and DLXCell is defined as follows:
>
> type DLXCell _rxS = DLX_Cell.DLX_Cell DLX_Reg.DLXReg _rxS ;
>
> Doing a little textual substitution, I get:
>
> instance __forall [_a] {PrelBase.Show _a} =>
> {Probe.Probe(Trans.Trans DLX_Op.DLX_Op
> (DLX_Cell.DLX_Cell DLX_Reg.DLXReg _a))}
>
> which sure looks like it satisfies the instance request (all
> the mentioned modules are directly
> imported in Main.hs). Hugs accepts the same program, no
> complaints. Iz GHC bug?
>
> --Jeff
>