
#12522: GHC 8.0.1 hangs, looping forever in type-checker -------------------------------------+------------------------------------- Reporter: clinton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by andreash): I think I may just have hit the same bug. I've extracted a small example: {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE TypeFamilyDependencies #-} {-# LANGUAGE TypeOperators #-} newtype I a = I a type family Curry (as :: [*]) b = f | f -> as b where Curry '[] b = I b Curry (a:as) b = a -> Curry as b data Uncurried (as :: [*]) b def :: Curry as b -> Uncurried as b def = undefined test :: Uncurried [Int, String] String test = def $ \n s -> I $ show n ++ s test2 :: Uncurried [Bool, Bool] Bool test2 = def $ \a b -> I $ a && b }}} Removing the type signatures from either `test`, or `test2` will hang ghc. If the type family is not defined as injective, then ghc doesn't hang, but instead gives an error message about ambiguous type variables. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12522#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler