[Haskell-cafe] Confused by instances

Fraser Wilson blancolioni at gmail.com
Mon Apr 28 16:22:41 EDT 2008


Hello, Haskellers,

I feel like I'm missing something obvious, but here's some example code:

> module Instance where
>
> data Value = Value Integer
>
> class ValueClass a where
>     fromValue :: Value -> a
>
> instance ValueClass Bool where
>     fromValue (Value n) = n /= 0
>
> instance ValueClass String where
>     fromValue (Value n) = show n
>
> instance (Num a) => ValueClass a where
>     fromValue (Value n) = fromInteger n
>

The Bool instance compiles fine.  The String instance fails, and that would
be because String is a synonym for [Char], and we can't create instances for
those.  There's a slight hack in the Prelude which allows you to define your
own list show function, and that's exactly what gets done by Show Char,
right?  I'm sorry about calling it a hack but, well, it is.  :)


What I'm really confused by is the response to instance (Num a) =>
ValueClass a -- 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".  But ghc says:

Instance.hs:14:0:
    Illegal instance declaration for `ValueClass a'
        (All instance types must be of the form (T a1 ... an)
         where a1 ... an are distinct type *variables*
         Use -XFlexibleInstances if you want to disable this.)
    In the instance declaration for `ValueClass a'

I don't understand why what I'm doing above is different from, for example,
instance Show a => Show [a], or Monad m => MonadState s (StateT s m) ... I
imagine that it's related to the fact that the difference between those two
and what I have is that they have either the same class on each side of the
=>, or new type variables on the right.  But I'm having trouble abstracting
from that to the general rule.

Any help would be greatly appreciated.  In context, I'm attempting to wrap
up different types inside a data type, and rather than extracting the value
with getBoolean, getInteger, getString etc, I thought I would let type
classes work for me, and just say fromValue instead.  Is this silly?  You
can tell me, I won't be hurt.

cheers,
Fraser.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20080428/b2b2cd5b/attachment.htm


More information about the Haskell-Cafe mailing list