#7369: Simplifier bug(?)
------------------------------+---------------------------------------------
 Reporter:  sweirich          |          Owner:                  
     Type:  bug               |         Status:  new             
 Priority:  normal            |      Component:  Compiler        
  Version:  7.6.1             |       Keywords:                  
       Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  Other             |       Testcase:                  
Blockedby:                    |       Blocking:                  
  Related:                    |  
------------------------------+---------------------------------------------
 Not sure if it is really a bug.  I was playing around with the following
 infinite loop in GHC 7.6:

 {{{

 {-# LANGUAGE GADTs, KindSignatures #-}

 data False

 data I (c :: * -> *)

 data R (c :: *) where
   R :: (a (I a) -> False) -> R (I a)

 delta :: R (I R) -> False
 delta = \ (R f) -> f (R f)

 omega :: False
 omega = delta (R delta)

 main :: IO ()
 main = seq omega (return ())

 }}}

 And I got the following result.  It's supposed to be an infinite loop,
 though, so maybe it is ok. GHC 7.4 just hangs on this example.

 {{{
 spaceman:haskell sweirich$ ghc inj4.hs
 [1 of 1] Compiling Main             ( inj4.hs, inj4.o )
 ghc: panic! (the 'impossible' happened)
   (GHC version 7.6.1 for i386-apple-darwin):
         Simplifier ticks exhausted
     When trying UnfoldingDone main:Main.$WR{v reV} [gid[DataConWrapper]]
     To increase the limit, use -fsimpl-tick-factor=N (default 100)
     If you need to do this, let GHC HQ know, and what factor you needed
     To see detailed counts use -ddump-simpl-stats
     Total ticks: 5160

 Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/7369>
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