On Mon, Dec 8, 2008 at 4:43 AM, Tobias Bexelius
<[EMAIL PROTECTED]> wrote:
> {-# LANGUAGE OverlappingInstances #-}
>
> With this extension, the most specific instance will be used, i.e.
> "instance TShow Engine" for Engine's, no matter if it is an instance of
> Show.

Of course, down this way madness lies :)

For example, this code:

> uhoh :: Show a => a -> IO String
> uhoh x = tshow x

won't compile.  The question is, what should this code do?

> instance Show (TVar a) where show _ = "TVAR"
> broken :: TVar a -> String
> broken x = uhoh x

"broken" will construct the Show dictionary for TVars and pass it to
"uhoh", which no longer knows that it is getting called on a TVar.
Then uhoh will construct a TShow (TVar a) dictionary using the Show
(TVar a) dictionary and the instance "Show a => TShow a", even though
there is a more specific instance.

So the compiler will just not let "uhoh" compile if overlapping is allowed.

You can force it to compile using the wrong instance with the
"IncoherentInstances" extension, but it's aptly named; the result is
bad because each type is supposed to only have one instance for a
particular typeclass.  It's worse because it breaks referential
transparency; if you inline "uhoh" into "broken", now you get the
specific instance!

  -- ryan
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to