[Haskell-cafe] multiple instances or contexts?

John Lato jwlato at gmail.com
Tue Jan 18 12:29:52 CET 2011


Hello,

This post is (hopefully) literate Haskell.  I recently noticed that there
are two ways to specify instances in a common situation.  Suppose I have
something like this:

> {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances,
NoMonomorphismRestriction, OverlappingInstances #-}
>
> data A = A
> data B = B
> data C = C
>
> newtype Repr a = Repr { unRepr :: State MyState a }
>
> class SomeClass a b where
>

If I want to make instances of SomeClass for Repr, A and Repr, B, I have two
choices:

> instance SomeClass Repr A where
> instance SomeClass Repr B where
>

or I can introduce a new class and make an instance with a context,

> class RClass c where
>
> instance RClass A where
> instance RClass B where
> -- no C instance for RClass
>
> instance RClass x => SomeClass Repr x

is there any reason to prefer one form over the other?  Of course the first
requires more instance declarations, but they're auto-generated so that
doesn't bother me.

Thanks,
John L.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110118/05ebe1dd/attachment.htm>


More information about the Haskell-Cafe mailing list