Type families causing the compiler to hang on recompilation

Richard Eisenberg eir at cis.upenn.edu
Fri Jun 21 10:35:28 CEST 2013


If the problem is happening in HEAD, it's a legitimate bug. Please file a
report and I'll take a look at it, as I'm in that area of the codebase right
now.

 

Thanks!

Richard

 

From: glasgow-haskell-users-bounces at haskell.org
[mailto:glasgow-haskell-users-bounces at haskell.org] On Behalf Of Jeroen
Weijers
Sent: 21 June 2013 09:01
To: glasgow-haskell-users at haskell.org
Subject: Type families causing the compiler to hang on recompilation

 

Hello,

 

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.

 

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. 

 

Does anybody recognise the problem? Should I create a ticket?

 

Cheers,

 

Jeroen Weijers

-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20130621/c12d2bf4/attachment-0001.htm>


More information about the Glasgow-haskell-users mailing list