[Haskell-cafe] Resolving overloading loops for circular constraint
graph
Stefan Holdermans
stefan at cs.uu.nl
Wed Sep 9 09:37:55 EDT 2009
Manuel, Simon,
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 (also attached) 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?
I'm not sure whether this is a known defect. If it isn't, I'd be more
than happy to issue a report.
Since this problem arises in a piece of very mission-critical code, I
would be pleased to learn about any workarounds.
Thanks in advance,
Stefan
More information about the Haskell-Cafe
mailing list