GHC 7.0.4 recursion while trying to derive type

Bogdan Opanchuk mantihor at gmail.com
Sun Jan 8 04:39:23 CET 2012


Hello,

Consider the following code:


{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, OverlappingInstances,
       UndecidableInstances, FunctionalDependencies #-}

class Container a b | a -> b where
       make :: b -> a

data Cont a = Cont a deriving (Show, Eq)

instance Container (Cont a) a where
       make x = Cont x

-- Part A
instance (Container a b, Show a, Eq a, Num b) => Num a where
       fromInteger x = make (fromInteger x)

d = fromInteger 3 :: Cont Integer

-- Part B
class Convertable a where
       fromInt :: Integer -> a

instance Convertable Integer where
       fromInt = id

instance (Container a b, Convertable b) => Convertable a where
       fromInt x = make (fromInt x)

e = fromInt 3 :: Cont Integer

main = do
       print d
       print e


Part A and B are basically the same, the only difference being that A
uses existing Num typeclass, and B creates a new one. The problem is
that it compiles and works in GHC 7.2.2, but in 7.0.4 (which is the
one included in the most recent Haskell Platform, that's why I bumped
into this issue) part A generates the following error:


t4.hs:17:31:
   Context reduction stack overflow; size = 21
   Use -fcontext-stack=N to increase stack size to N
     $dNum :: Num b19
     [ skipped ]
     $dNum :: Num b0
   In the first argument of `make', namely `(fromInteger x)'
   In the expression: make (fromInteger x)
   In an equation for `fromInteger':
       fromInteger x = make (fromInteger x)


My understanding is that in line "fromInteger x = make (fromInteger
x)" compiler should take into account that
1) the signature for make is "make :: b -> a"
2) type b is known at the moment of creating instance (because a ==
Cont Integer, which is an instance of Container (Cont Integer)
Integer).
and cast "fromInteger x" to type b and pass it to make. In 7.0.4 part
B (which is based on the same idea) works correctly, so it may have
something to do with how fromInteger is defined in GHC guts.

So, the question is, could anyone please tell me, is what I am trying
to do actually correct, and what was changed from 7.0.4 to 7.2.2 to
make it work?

Thank you in advance.

Best regards,
Bogdan



More information about the Glasgow-haskell-users mailing list