typeclass relations

Abraham Egnor aegnor@antioch-college.edu
Mon, 9 Sep 2002 12:40:36 -0400 (EDT)


I have two typeclasses, Foo and Bar, with some instances, defined as such:

module Test where

class Foo a where
  foo :: a -> String

class Bar a where
  bar :: a -> String

instance Foo Int where
  foo = show

instance Bar Int where
  bar a = (show a) ++ " bar!"

instance Foo Char where
  foo = show

instance Foo a => Bar a where
  bar = foo

If I try to compile this via GHC it complains loudly unless I feed it
"-fglasgow-exts -fallow-undecidable-instances 
-fallow-overlapping-instances", in which case it seems to do the right
thing.  However, the warnings (and the names of the flags - "undecidable
instances" doesn't sound good) make me nervous, and confused.  Why is
there a problem with saying "every instance of Foo is also an instance of
Bar, and here's how"?

Abe