Here's a test case for the problem I'm having; I'm using runhaskell from ghc
v6.6.

Problem #1) Without -fallow-undecidable-instances, I get the following
error:
   Constraint is no smaller than the instance head
     in the constraint: ConvertToInt a
   (Use -fallow-undecidable-instances to permit this)
   In the instance declaration for `ConvertToIntList a'
Problem #2) With -fallow-undecidable-instances, I get this error instead:
   Overlapping instances for ConvertToIntList ()
     arising from use of `convl' at testcase.hs:28:6-15
   Matching instances:
     instance (ConvertToInt a) => ConvertToIntList a
-- Defined at testcase.hs:15:0
     instance ConvertToIntList () -- Defined at testcase.hs:18:0
   In the expression: convl [()]
   In the definition of `xl2': xl2 = convl [()]
I don't understand why there is an overlapping instances error; () is not an
instance of ConvertToInt so how could that instance ever apply?

Is there something basic about type-classes that I'm not understanding
here?  My actual problem is more complicated than this, but this test-case
covers the basic issue; something being an instance of class A means that I
can derive an instance of class B for it, but I want to implement other
instances of class B as well.

Code below:
{-# OPTIONS -fglasgow-exts -fallow-undecidable-instances #-}

module TestCase
where

class ConvertToInt a where
  conv :: a -> Int

class ConvertToIntList a where
  convl :: [a] -> [Int]

instance ConvertToInt Int where
  conv = id

instance ConvertToInt a => ConvertToIntList a where
  convl = map conv

instance ConvertToIntList () where
  convl x = []

x :: Int
x = 5

xl :: [Int]
xl = convl [x]

xl2 :: [Int]
xl2 = convl [()]
_______________________________________________
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell

Reply via email to