[GHC] #8002: Type family causing GHC to hang on recompilation

#8002: Type family causing GHC to hang on recompilation -----------------------------+---------------------------------------------- Reporter: jweijers | Owner: Type: bug | Status: new Priority: normal | Component: Compiler Version: 7.6.3 | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Blockedby: Blocking: | Related: -----------------------------+---------------------------------------------- I am having a problem with (re)compiling some code I have. I have two modules A and B. In A I have some classes and instances and B uses this. When I try to compile B (with cabal or ghc --make) the first time everything works. When I now modify B (add a space) B is recompiled but the compiler hangs and doesn't seems to be doing anything. I have tested the problem with GHC (x86_64) 7.6.2. 7.6.3 and HEAD (build on 20/06/2013). It seems to be very similar to a problem I had earlier: http://hackage.haskell.org/trac/ghc/ticket/7321 but this time there are no GADTs involved. The code of module A (clutter that doesn't contribute to the problem has been removed): {{{
{-# LANGUAGE FlexibleInstances, UndecidableInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeFamilies, TypeOperators, ScopedTypeVariables #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE DataKinds, PolyKinds #-}
module A where
import GHC.Generics
class QA a where type QRep a type QRep a = QRep (GRep (Rep a))
instance QA () where type QRep () = ()
-- Kind-polymorphic proxies; data Pr (a :: k) = Pr
class (QA (GRep f)) => CaseOf (f :: * -> *) where type Alg f r k :: * type GRep f :: *
-- Only used for the product structure class QA (ProdRep f) => CaseOfProd (f :: * -> *) where type ProdAlg f r :: * type ProdRep f :: * }}}
The code of module B: {{{
module B where import qualified A }}}
Given that the code type checks (and if I do not recompile and make an executable directly it actually works) I think this is a bug that might be similar to the bug mentioned in ticket 7321. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/8002 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8002: Type family causing GHC to hang on recompilation -----------------------------+---------------------------------------------- Reporter: jweijers | Owner: Type: bug | Status: new Priority: normal | Component: Compiler Version: 7.6.3 | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Blockedby: Blocking: | Related: -----------------------------+---------------------------------------------- Comment(by monoidal): Here is a simplified version, with three modules Generics.hs, A.hs, B.hs: {{{ {-# LANGUAGE TypeFamilies #-} module Generics where type family Rep a type instance Rep Int = Int }}} {{{ {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE TypeFamilies #-} module A where import Generics class QA a where type QRep a type QRep a = QRep (Maybe a) instance QA () where type QRep () = () }}} {{{ {-# LANGUAGE TypeFamilies #-} module B where import A }}} -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/8002#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8002: Type family causing GHC to hang on recompilation ---------------------------------+------------------------------------------ Reporter: jweijers | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Keywords: | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: None/Unknown Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: | ---------------------------------+------------------------------------------ Changes (by simonpj): * owner: => simonpj * difficulty: => Unknown Comment: Thanks. I know what is happening. Am fixing. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/8002#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8002: Type family causing GHC to hang on recompilation
---------------------------------+------------------------------------------
Reporter: jweijers | Owner: simonpj
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.6.3
Keywords: | Os: Unknown/Multiple
Architecture: Unknown/Multiple | Failure: None/Unknown
Difficulty: Unknown | Testcase:
Blockedby: | Blocking:
Related: |
---------------------------------+------------------------------------------
Comment(by simonpj@…):
commit 20667021164ff5b30bc3a9d6105dac52077345bc
{{{
Author: Simon Peyton Jones

#8002: Type family causing GHC to hang on recompilation -------------------------------------------------+-------------------------- Reporter: jweijers | Owner: simonpj Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: fixed | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Difficulty: Unknown Testcase: indexed_types/should_compile/T8002 | Blockedby: Blocking: | Related: -------------------------------------------------+-------------------------- Changes (by simonpj): * status: new => closed * testcase: => indexed_types/should_compile/T8002 * resolution: => fixed Comment: Excellent catch, thank you. Now fixed. The test makes earlier versions of GHC hang altogether, and I'm not sure that the testsuite recovers from such a hang... but at least we'll notice! Simon -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/8002#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC