[Haskell-cafe] Confused by instances

Luke Palmer lrpalmer at gmail.com
Mon Apr 28 17:46:22 EDT 2008


2008/4/28 Fraser Wilson <blancolioni at gmail.com>:
> what I am trying to say is "if a is an instance of Num, then
> can be an instance of ValueClass too, and here's how".

Oh, didn't answer this one.  This is almost canned response, questions
like this get asked weekly on this list.

Short answer: you can't.

Longer answer: you can, but you have to wrap it in a newtype, which is
irritating.

    newtype NumValue a = NumV a
    instance (Num a) => ValueClass (NumV a) where
        fromValue (Value n) = NumV (fromInteger n)

Essentially you have to "tell the compiler" when you use this
instance.  So you still get all the power, but with less convenience
(than the impossible thing you want).

Abridged longest answer:  you can, and you don't need a newtype, but
only if you're The Devil.  Here's an explanation, but *please do not
do this*!  It's unpredictable, poor style, a bad habit, nonmodular,
etc. etc. etc.

First enable undecidable instances:

    {-# LANGUAGE UndecidableInstances #-}

With this pragma you are forfeiting your right to a terminating
compiler.  The compiler may "instance stack overflow" or run forever
for no discernible reason.

Now you are allowed exactly one instance of the form you desire:

    instance (Num a) => ValueClass a where
        fromValue (Value n) = fromInteger n

If you're lucky, you might be able to define some well-formed
instances in addition and have everything behave.  It *will* break if
you add another such instance, for example:

    instance (Read a) => ValueClass a where ...

Because when the compiler sees fromValue, it will try to match it
against the head of an instance.  Both the Num and the Read forms
match every type, so it will *pick one arbitrarily*, without
backtracking.  So if you wanted the Read one and it picked the Num
one, you are permanently out of luck and you basically have to scrap
everything.

So, yeah, there's a little excursion into the dirty corners of the
typeclass system.  If you don't want to get spontaneously eaten by a
bear, use a newtype as above :-).

And now it's time to go make/edit a wiki page on the subject.

Luke


More information about the Haskell-Cafe mailing list