#3330: Type checker hangs
----------------------------------+-----------------------------------------
Reporter:  MartijnVanSteenbergen  |          Owner:                         
    Type:  bug                    |         Status:  new                    
Priority:  normal                 |      Component:  Compiler (Type checker)
 Version:  6.10.1                 |       Severity:  normal                 
Keywords:                         |       Testcase:                         
      Os:  Unknown/Multiple       |   Architecture:  Unknown/Multiple       
----------------------------------+-----------------------------------------
 The following module causes `ghc --make` and `ghci` to hang. `-ddump-tc-
 trace` produces output indefinitely.

 {{{
 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE FlexibleContexts #-}

 import Generics.MultiRec
 import Control.Monad.Writer

 data AnyF s f where
   AnyF :: s ix -> f ix -> AnyF s f

 children :: HFunctor s (PF s) => s ix -> (PF s) r ix -> [AnyF s r]
 children p x = execWriter (hmapM p collect x) where
   collect :: (HFunctor s (PF s)) => s ix -> r ix -> Writer [AnyF s r] (r
 ix)
   collect w x = tell [AnyF w x] >> return x
 }}}

 Module `Generics.MultiRec` is from Hackage package `multirec-0.4`.

 The code contains a type error: if arguments `p` and `collect` are swapped
 the code compiles fine.

 I haven't tried making this example any smaller.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3330>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to