
#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