#3500: Type functions and recursive dictionaries
-------------------------------+--------------------------------------------
Reporter: simonpj | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 6.10.4
Severity: normal | Keywords:
Difficulty: Unknown | Testcase:
Os: Unknown/Multiple | Architecture: Unknown/Multiple
-------------------------------+--------------------------------------------
Stefan Holdermans reports:
I've spotted a hopefully small but for us quite annoying bug in GHC's
type checker: it loops when overloading resolving involves a circular
constraint graph containing type-family applications.
The following program demonstrates the problem:
{{{
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
type family F a :: *
type instance F Int = (Int, ())
class C a
instance C ()
instance (C (F a), C b) => C (a, b)
f :: C (F a) => a -> Int
f _ = 2
main :: IO ()
main = print (f (3 :: Int))
}}}
My guess is that the loop is caused by the constraint `C (F Int)` that
arises from the use of f in main:
{{{
C (F Int) = C (Int, ()) <= C (F Int)
}}}
Indeed, overloading can be resolved successfully by "black-holing" the
initial constraint, but it seems like the type checker refuses to do so.
Can you confirm my findings?
Since this problem arises in a piece of very mission-critical code, I
would be pleased to learn about any workarounds.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3500>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs