[Haskell-beginners] Class and Instance Question

Antoine Latter aslatter at gmail.com
Fri May 20 06:08:30 CEST 2011


On Thu, May 19, 2011 at 8:05 PM, Adam C. Emerson <azure at umich.edu> wrote:
> Good morning,
>
> As my first "real" toy project (something trivial but with some
> pretense of usefulness at least to me) in Haskell, I had been trying
> to write an XDR encoder/decoder based on top of Data.Binary.  As such,
> I have a typeclass:
>
> class Encodable t where
>    -- | Encode a value in the Put monad.
>    put :: t -> Put
>    -- | Decode a value in the Get monad
>    get :: Get t
>
> And I have various instances, all of which seem to work, except for
> two.  My thought was to treat a list of Chars as a string and a list
> of "encodable" types as a counted array.  Thus, I tried:
>
> instance Encodable [Char] where
>  put s = put $ runPut (putUTF8str s)
>  get   = do bs <- get
>             return (runGet getUTF8str bs)
>
> and
>
> instance (Encodable e) => Encodable [e] where
>  put l = if (length l) > xdrmaxlen
>          then fail "Length of data exceeds XDR maximum for arrays."
>          else (put (length l) >> putFixed (length l) l)
>  get   = do n <- get
>             getFixed n
>
> This failed, and the compiler suggested I try adding:
>
> {-# LANGUAGE FlexibleInstances #-}
> {-# LANGUAGE OverlappingInstances #-}
>
> But even with these two statements, I get:
>
> *Data.XDR.Encodable> encode [1, 2, 3]
>
> <interactive>:1:0:
>    Overlapping instances for Encodable [t]
>      arising from a use of `encode' at <interactive>:1:0-15
>    Matching instances:
>      instance [overlap ok] (Encodable e) => Encodable [e]
>        -- Defined at /home/azure/programming/xdr/src/Data/XDR/Encodable.hs:226:9-38
>      instance [overlap ok] Encodable [Char]
>        -- Defined at /home/azure/programming/xdr/src/Data/XDR/Encodable.hs:160:9-24
>    (The choice depends on the instantiation of `t'
>     To pick the first instance above, use -XIncoherentInstances
>     when compiling the other instance declarations)
>    In the expression: encode [1, 2, 3]
>
> So, the question I have, more than wondering how to get this to work
> (I suspect I shouldn't even be doing this, and instead I should
> newtype XDRInt and XDRString and so on), is why the two instances
> overlap.  I have no instance for Char, so the first instance should
> apply to lists of Char (which isn't Encodable.)  And the second should
> apply to lists of Encodable things (which Char isn't.)
>

A key point about instance resolution - when GHC tries to find an
instance to useit only looks at what is on the left-hand side of the
(=>) mark.

So an instance of the form:

> instance (Constraint a) => MyClass [a] where ...

can be read aloud as:

"[a] is an instance of MyClass. Also, it is an error if Constraint a
is not satisfied".

One way to get around this is to do what the 'Show' class does:

> class Show a where
>   show :: a -> String
>
>   showList :: [a] -> String
>   showList [] = "[]"
>   showList (x:xs) = "[" ++ ... ++ "]"

and then:

> instance Show a => Show [a] where
>   show xs = showList xs

> instance Show Char where
>   show x = ...
>   showList xs = "\"" + ... + "\"

This way, the special handling that strings need is put in the Char instance.

The above instances are an approximation only, the Show class is a bit
more complex, but I just wanted to show the trick it uses for strings.

The other approach is to use the OverlappingInstances extension, which
I'm less able to explain as readily.

Antoine

> Is there a fairly comprehensible source I should read to understand
> typeclasses and instances better?  (I've read my way through Real
> World Haskell, the Wikibook, and A Gentle Introduction, though it's
> possible they covered this and I just missed it.)
>
> Thank you.
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>



More information about the Beginners mailing list