Simon L Peyton Jones <[EMAIL PROTECTED]> writes:

> > So are types not longer allowed in instance declarations?
> 
> Yes they're allowed, but it's just as if you'd written the 
> expanded type.  Any two instance decls that don't overlap are
> allowed.  You can write
> 
>       instance C (Blah,Int) where ..
>       instance C (Int,Int)  where ..
>       instance C (Blah, Bool) where ...

Isn't it more correct to say that overlapping instances are allowed,
as long as they're never both in scope at the same time?  This might
even be useful, except that it's really hard to control the scope of
instance declarations.

What would be really cool would be if you could write

        import Prelude hiding (instance Show (,))
        instance Show (Blah,Int) where ..
        instance Show (Int,Int)  where ..
        instance Show (Blah, Bool) where ...

Cheers,
        Simon



> 
> since none of these overlap.  But Show does have an instance for
> (a,b) so you are stuck.  By "overlap" I mean that the instance
> types can be unified.
> 
> Einar says:
> 
> > With the good old 2.something compiler, I could overwrite
> > the default definition of Show for lists and other type constructors, e.g.:
> > 
> > data Blah = Blah deriving (Read,Show)
> > 
> > instance Show [Blah] where
> >   showsPrec d [] r =  r
> >   showsPrec d _ r  = "bla bla ..." ++ r
> > 
> >     Duplicate or overlapping instance declarations
> >     for `Show [Blah]'
> >         at PrelBase.mc_hi and Blah.hs
> 
> Same issue.  Show [a] exists already and overlaps with Show [Blah].
> 
> There is a full discussion of the bad consequences of overlapping
> instance decls in the multi-parameter type class paper
>       http://www.dcs.gla.ac.uk/~simonpj/multi.ps.gz
> 
> 3.0 is a bit more restrictive than 2.xx, but it is Righter I think.
> Dissenting opinions welcome.
> 
> Simon
> 
> 
> 

-- 
-- 
Simon Marlow                                             [EMAIL PROTECTED]
University of Glasgow                       http://www.dcs.gla.ac.uk/~simonm/
finger for PGP public key

Reply via email to