#3330: Type checker hangs
----------------------------------------+-----------------------------------
Reporter: MartijnVanSteenbergen | Owner: chak
Type: bug | Status: new
Priority: normal | Milestone: 6.12.1
Component: Compiler (Type checker) | Version: 6.10.3
Severity: normal | Resolution:
Keywords: | Difficulty: Unknown
Testcase: | Os: MacOS X
Architecture: x86_64 (amd64) |
----------------------------------------+-----------------------------------
Changes (by EduardSergeev):
* os: Unknown/Multiple => MacOS X
* architecture: Unknown/Multiple => x86_64 (amd64)
Comment:
I think I am now facing a similar behavior (hangs while compiling,
continiously consuming memory until the whole system hangs) from GHC
6.10.3 on Mac OS X 10.5.7 (and on Windows XP as well) on the following
simple type family example:
{{{
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
class RFunctor c a b where
type Res c a b :: *
rmap :: (a -> b) -> c -> Res c a b
instance (a ~ c) => RFunctor c a b where
type Res c a b = b
rmap f = f
instance (RFunctor c a b, a ~ c) => RFunctor [c] a b where
type Res [c] a b = [b]
rmap f = map (map f)
}}}
But if these two instances declarations are interchanged it reports:
Conflicting family instance declarations:
type instance Res [c] a b -- Defined at TFTest.hs:14:9-11
type instance Res c a b -- Defined at TFTest.hs:18:9-11
I've also attached the fragment of the output from GHC with -ddump-tc-
trace
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3330#comment:6>
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