#3330: Type checker hangs
-------------------------------------+--------------------------------------
 Reporter:  MartijnVanSteenbergen    |          Owner:                  
     Type:  bug                      |         Status:  new             
 Priority:  normal                   |      Milestone:                  
Component:  Compiler (Type checker)  |        Version:  6.10.3          
 Severity:  normal                   |     Resolution:                  
 Keywords:                           |       Testcase:                  
       Os:  Unknown/Multiple         |   Architecture:  Unknown/Multiple
-------------------------------------+--------------------------------------
Comment (by MartijnVanSteenbergen):

 I'm afraid that will take me a significant amount of time. :-(

 What I've done instead is change the example to be independent of
 multirec, moving some definitions into the snippet. I've also tried to
 make it smaller, removing some function arguments, type arguments and
 class constraints and replacing definitions by undefined. In what is left
 I cannot find anything else I can remove without causing GHC not to hang
 anymore.

 {{{
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE TypeFamilies #-}

 import Control.Monad.Writer

 data AnyF (s :: * -> *) = AnyF
 class HFunctor (f :: (* -> *) -> * -> *)
 type family PF (phi :: * -> *) :: (* -> *) -> * -> *

 children :: s ix -> (PF s) r ix -> [AnyF s]
 children p x = execWriter (hmapM p collect x)

 collect :: HFunctor (PF s) => s ix -> r ix -> Writer [AnyF s] (r ix)
 collect = undefined

 hmapM :: (forall ix. phi ix -> r ix -> m (r' ix))
   -> phi ix -> f r ix -> m (f r' ix)
 hmapM = undefined
 }}}

 Does that help?

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3330#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to