[Haskell-beginners] Overlapping instances
Daniel Fischer
daniel.is.fischer at googlemail.com
Tue Dec 25 17:11:34 CET 2012
On Dienstag, 25. Dezember 2012, 16:52:00, Nathan Hüsken wrote:
> Hi,
>
> I have a test file:
>
> module Main where
>
> class A a where
> doSomething :: a -> IO ()
> class B b where
> doMore :: b -> IO ()
>
> instance B b => A b where
> doSomething = doMore
>
> instance A String where
> doSomething = putStrLn
>
> main = doSomething "Hello, World!
>
> So there is a class A, and a class B. If something is part of B it is
> automatically part of A (so A is kind of a superclass to B). But String
> is just part of A.
> I try to compile it with:
>
> ghc Test.hs -XFlexibleInstances -XUndecidableInstances
>
> I get:
>
> Test.hs:14:8:
> Overlapping instances for A [Char]
> arising from a use of `doSomething'
> Matching instances:
> instance B b => A b -- Defined at Test.hs:8:10
> instance A String -- Defined at Test.hs:11:10
> In the expression: doSomething "Hello, World!"
> In an equation for `main': main = doSomething "Hello, World!"
>
> Why are the instances overlapping? String is not part of B???
For instance resolution, only the instance head is taken into account, that
does not include the constraints.
So the instance head of
instance B b => A b where
is only the `b' type variable, and that matches every type, in particular
String, so the instances overlap (with an instance of the form
instance context => Class a where
any further instance declaration overlaps, since that instance effectively
says every type is an instance of Class, but if `context' isn't satisfied,
that is a static error).
> How can I do this?
Allow overlapping instances if you must. But maybe you can restructure your
code to not use overlapping instances.
More information about the Beginners
mailing list