#4358: infinite loop on unification with a type family context
--------------------------------+-------------------------------------------
Reporter: patrick_premont | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler (Type checker)
Version: 6.12.1 | Keywords: infinite loop type family
context
Testcase: | Blockedby:
Os: Windows | Blocking:
Architecture: x86_64 (amd64) | Failure: Compile-time crash
--------------------------------+-------------------------------------------
The following throws ghc (and ghci) in a loop (ghc-7.0.0.20100925 for i386
-unknown-mingw32)
and it eventually aborts with "ghc.exe: out of memory".
{{{
> {-# LANGUAGE TypeFamilies, Rank2Types, FlexibleContexts #-}
> type family T a
> t2 :: forall a. ((T a ~ a) => a) -> a
> t2 = t
> t :: forall a. ((T a ~ a) => a) -> a
> t = undefined
}}}
Using ghc 6.12.1 we do not get a loop, but a puzzling error:
typeBug.lhs:9:7:
Couldn't match expected type `(T a ~ a) => a'
against inferred type `(T a ~ a) => a'
Expected type: (T a ~ a) => a
Inferred type: (T a ~ a) => a
In the expression: t
In the definition of `t2': t2 = t
I presume that the non-injectivity of type family T triggers the problem
however
the following produces no errors in either version of the compiler.
{{{
> ok2 :: forall a. T a -> a
> ok2 = ok
> ok :: forall a. T a -> a
> ok = undefined
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4358>
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