Hi everyone,

Here's some code that's giving me an error message I don't understand:

{-# LANGUAGE EmptyDataDecls,
             MultiParamTypeClasses,
             UndecidableInstances,
             FlexibleInstances #-}

data Z
data S n

class Nat n where
  toInt :: n -> Int

instance Nat Z where
  toInt _ = 0

instance (Nat n) => Nat (S n) where
  toInt _ = 1 + toInt (undefined :: n)

instance (Nat n) => Show n where
  show _ = show $ toInt (undefined :: n)

-- end of code sample

When I run this through ghci, I get this:

test.hs:19:11:
    Overlapping instances for Show Int
      arising from a use of `show' at test.hs:19:11-14
    Matching instances:
      instance Show Int -- Defined in GHC.Show
      instance (Nat n) => Show n -- Defined at test.hs:18:9-25
    In the first argument of `($)', namely `show'
    In the expression: show $ toInt (undefined :: n)
    In the definition of `show': show _ = show $ toInt (undefined :: n)

Adding OverlappingInstances to the language pragmas fixes the problem. My question is: why is this an overlapping instance? It would make sense if Int was an instance of Nat, but it isn't. Is this just a limitation in the way overlapping instances are identified?

Mike

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

Reply via email to