#4093: compiler hangs (type checking?)
-----------------------+----------------------------------------------------
    Reporter:  dias    |       Owner:                    
        Type:  bug     |      Status:  new               
    Priority:  normal  |   Component:  Compiler          
     Version:  6.13    |    Keywords:                    
          Os:  Linux   |    Testcase:                    
Architecture:  x86     |     Failure:  Compile-time crash
-----------------------+----------------------------------------------------

Comment(by cam):

 The following code (with fewer extensions enabled) gives me the same
 result, and is presumably the same bug:

 {{{
 {-# LANGUAGE TypeFamilies #-}
 module Test () where

 type family Foo x
 type instance Foo () = Maybe ()

 hang :: (Foo e ~ Maybe e) => Foo e
 hang = Just ()
 }}}

 The above, and the earlier code, both result in 100% CPU until GHC falls
 over with a stack overflow. Tested on GHC 6.10.4 (Linux and Windows), GHC
 6.12.2 (Windows), and GHC 6.13.20100522 (Linux).

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4093#comment:1>
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

Reply via email to