[Haskell-beginners] Problems with typeclasses instances

David McBride dmcbride at neondsl.com
Wed Jul 13 15:10:21 CEST 2011


You can add OverlappingInstances to allow for both [a] and [Char]
intstances be used.  It will choose the least general instance for
you.

On Wed, Jul 13, 2011 at 8:56 AM, ARJANEN Loïc Jean David
<arjanen.loic at gmail.com> wrote:
> I have the following problem with typeclasses : I have created a type
> class in a manner similar to the following
>
> module Dummy where
> import Char
> class (Show t) => Dummy t where
>    kite :: t -> t
> instance (Dummy t) => Dummy [t] where
>    kite = reverse
> instance Dummy String where
>    kite = map toUpper
>
> And use it thus :
>
> import Dummy
> main :: IO ()
> main = do
>    print.kite $ "Rest in peace"
>
> If I compile without any option, I get as expected an error because of
> the type synonym instance. If I remove the instance for String, I also
> get as expected an error because Char is not an instance of Dummy. But
> if I add (as suggested in the first error message) the GHC's option
> -XTypeSynonymInstances, I get an error because of overlapping
> instances, even if Char is still not an instance of Dummy and I don't
> see how String could be eligible for the (Dummy t) => Dummy [t]
> instance...
>
> Thanks in advance for your help,
> ARJANEN Loic.
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>



More information about the Beginners mailing list