[GHC] #8221: Type checker hangs

#8221: Type checker hangs ----------------------------+---------------------------------------------- Reporter: maxs | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Keywords: hangs | Operating System: MacOS X Architecture: arm | Type of failure: GHC rejects valid program Difficulty: Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | ----------------------------+---------------------------------------------- The following program gets GHC stuck in Renamer/typechecker. This compiles correctly in 7.6.3. {{{ {-# LANGUAGE DeriveDataTypeable #-} module Type.Type where import Data.Data import qualified Data.UnionFind.IO as UF data SrcSpan = Span String | NoSpan String deriving (Eq, Ord, Data, Typeable) data Located e = L SrcSpan e deriving (Eq, Ord, Data, Typeable) }}} Removing either the: {{{ import qualified Data.UnionFind.IO as UF }}} or {{{ data Located e = L SrcSpan e deriving (Eq, Ord, Data, Typeable) }}} or Removing the Eq Ord from Located: {{{ data Located e = L SrcSpan e deriving (Data, Typeable) }}} will allow it to terminate. ddump-tc-trace shows it is related to the derived typeable instance. The log is attached. I am compiling with: {{{ arm-apple-darwin10-ghc -staticlib -ddump-tc-trace Type/Type.hs -v -threaded }}} I don't have a x86 build of HEAD handy, I think if someone could try this program in HEAD then we will know if it is ARM / GHC iOS / stage1 specific or not. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8221 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8221: Type checker hangs ----------------------------------------------+--------------------------- Reporter: maxs | Owner: dreixel Type: bug | Status: new Priority: highest | Milestone: 7.8.1 Component: Compiler | Version: 7.7 Resolution: | Keywords: hangs Operating System: Unknown/Multiple | Architecture: arm Type of failure: GHC rejects valid program | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: ----------------------------------------------+--------------------------- Changes (by thoughtpolice): * owner: => dreixel * priority: normal => highest * os: MacOS X => Unknown/Multiple * milestone: => 7.8.1 Comment: I can confirm this behavior with a copy of HEAD build from Friday (my HEAD is `7e91e5bf84c2b3f461934b43911c0defb61dd9c6`.) This is obviously quite a problem. José, will you take a look please? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8221#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8221: Type checker hangs ----------------------------------------------+--------------------------- Reporter: maxs | Owner: dreixel Type: bug | Status: new Priority: highest | Milestone: 7.8.1 Component: Compiler | Version: 7.7 Resolution: | Keywords: hangs Operating System: Unknown/Multiple | Architecture: arm Type of failure: GHC rejects valid program | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: ----------------------------------------------+--------------------------- Comment (by monoidal): Here is a smaller testcase. The bug is not related to Typeable. File A.hs: {{{ module A where import Data.IORef data Link a = Link !(IORef (Link a)) | X deriving Eq }}} File T.hs: {{{ module T where import A data Located e = L () e deriving Eq }}} Run `ghc-7.7 -O A.hs` and then `ghc-7.7 T.hs`, the second command should hang. While investigating this, I also found that compiling this contrived file with HEAD and -O hangs, while 7.6.3 succeeds. However, it is probably a different issue because deriving is not used: {{{ module M where data Link a = Link !(Link a) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8221#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8221: Type checker hangs ----------------------------------------------+--------------------------- Reporter: maxs | Owner: dreixel Type: bug | Status: new Priority: highest | Milestone: 7.8.1 Component: Compiler | Version: 7.7 Resolution: | Keywords: hangs Operating System: Unknown/Multiple | Architecture: arm Type of failure: GHC rejects valid program | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: ----------------------------------------------+--------------------------- Comment (by simonpj): Ugh. I'm on this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8221#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8221: Type checker hangs
----------------------------------------------+---------------------------
Reporter: maxs | Owner: dreixel
Type: bug | Status: new
Priority: highest | Milestone: 7.8.1
Component: Compiler | Version: 7.7
Resolution: | Keywords: hangs
Operating System: Unknown/Multiple | Architecture: arm
Type of failure: GHC rejects valid program | Difficulty: Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
----------------------------------------------+---------------------------
Comment (by Simon Peyton Jones

#8221: Type checker hangs
----------------------------------------------+---------------------------
Reporter: maxs | Owner: dreixel
Type: bug | Status: new
Priority: highest | Milestone: 7.8.1
Component: Compiler | Version: 7.7
Resolution: | Keywords: hangs
Operating System: Unknown/Multiple | Architecture: arm
Type of failure: GHC rejects valid program | Difficulty: Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
----------------------------------------------+---------------------------
Comment (by Simon Peyton Jones

#8221: Type checker hangs
----------------------------------------------+---------------------------
Reporter: maxs | Owner: dreixel
Type: bug | Status: new
Priority: highest | Milestone: 7.8.1
Component: Compiler | Version: 7.7
Resolution: | Keywords: hangs
Operating System: Unknown/Multiple | Architecture: arm
Type of failure: GHC rejects valid program | Difficulty: Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
----------------------------------------------+---------------------------
Comment (by Simon Peyton Jones

#8221: Type checker hangs -------------------------------------------------+------------------------- Reporter: maxs | Owner: Type: bug | dreixel Priority: highest | Status: Component: Compiler | closed Resolution: fixed | Milestone: 7.8.1 Operating System: Unknown/Multiple | Version: 7.7 Type of failure: GHC rejects valid program | Keywords: hangs Test Case: | Architecture: arm simplCore/should_compile/T8221,T8221b | Difficulty: Blocking: | Unknown | Blocked By: | Related Tickets: -------------------------------------------------+------------------------- Changes (by simonpj): * status: new => closed * testcase: => simplCore/should_compile/T8221,T8221b * resolution: => fixed Comment: Great catch guys. There were indeed two bugs, both now fixed. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8221#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC