[GHC] #8002: Type family causing GHC to hang on recompilation
GHC
ghc-devs at haskell.org
Fri Jun 21 11:02:16 CEST 2013
#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
More information about the ghc-tickets
mailing list