[Haskell-cafe] Confused by instances

Luke Palmer lrpalmer at gmail.com
Mon Apr 28 17:33:05 EDT 2008


2008/4/28 Fraser Wilson <blancolioni at gmail.com>:
> On Mon, Apr 28, 2008 at 10:50 PM, Brandon S. Allbery KF8NH
> <allbery at ece.cmu.edu> wrote:
> > The format is instance [context =>] classname instance.
> > Your classname is ValueClass.
> > Your instance is a.  a is not of the form (T a1 ... an).
>
> But neither is
>      instance (Show a) => Show [a] ...

Yes it is, it's just a weird looking T, (namely []).  This works just as well:

    instance (Show a) => Show ([] a) ...

(Unless that's not H98, but I think it is)

Instances have to have concrete constructors at their heads is for
technical reasons, namely you can't in general do type inference with
unrestricted instances.  It is a pattern-matching algorithm as you'd
expect, but it goes *backwards*, from right to left; i.e it sees the
pattern [a] and generates a new constraint Show a. This is contrary to
the intuition that it has a big set of instances, and when it sees,
say, Show Int it adds Show [Int].   The direction of the arrow can be
misleading :-)

To answer your other question, no, there is no list show hack.  What
is being complained about is that you're using a type synonym as an
instance.  If you just expand the synonym everything works fine.  This
is not specific to lists, nor show.  You're just not allowed to use
synonyms in instances (and as the compiler suggests, this restriction
can be lifted with {-# LANGUAGE FlexibleInstances #-}).

Luke


More information about the Haskell-Cafe mailing list