Bug in undecidable instances?

Roman Cheplyaka roma at ro-che.info
Mon Jan 31 23:00:49 CET 2011


The following looks like a bug in (undecidable) instances resolution.

    {-# LANGUAGE MultiParamTypeClasses,FlexibleInstances,UndecidableInstances,
                 OverlappingInstances,IncoherentInstances #-}
    class C a b

    instance C a (a,b)

    class D a b

    instance (D a b, C b c) => D a c

    data Foo = Foo deriving Show
    data Bar = Bar deriving Show

    instance D Foo Foo

    c :: C x y => x -> y -> ()
    c _ _ = ()

    d :: D x y => x -> y -> ()
    d _ _ = ()


*Main> d Foo Foo
() -- as expected
*Main> c Foo (Foo,Bar)
() -- as expected
*Main> d Foo (Foo,Bar)

<interactive>:1:1:
    Context reduction stack overflow; size = 21
    Use -fcontext-stack=N to increase stack size to N
      [skip]
      $dD :: D Foo b1
      $dD :: D Foo b
      $dD :: D Foo (Foo, Bar)
    In the expression: d Foo (Foo, Bar)
    In an equation for `it': it = d Foo (Foo, Bar)

I.e. for some reason on the second step resolver fails to pick up the
most specific (and the most obvious) instance D Foo Foo and continues to
apply the instance (D a b, C b c) => D a c.

Reproduced with GHC 6.12.1 and 7.0.1.

-- 
Roman I. Cheplyaka :: http://ro-che.info/
Don't worry what people think, they don't do it very often.



More information about the Glasgow-haskell-users mailing list