#5539: GHC panic -  Simplifier ticks exhausted
---------------------------------+------------------------------------------
  Reporter:  hvr                 |          Owner:  simonpj       
      Type:  bug                 |         Status:  new           
  Priority:  high                |      Milestone:  7.6.1         
 Component:  Compiler            |        Version:  7.3           
Resolution:                      |       Keywords:                
        Os:  Linux               |   Architecture:  x86_64 (amd64)
   Failure:  Compile-time crash  |     Difficulty:  Unknown       
  Testcase:                      |      Blockedby:                
  Blocking:                      |        Related:                
---------------------------------+------------------------------------------

Comment(by pcapriotti):

 Here is a simple example (by kosmikus) which blows up the simplifier
 without any INLINE pragma:

 {{{

 module TestCase where

 import Control.Applicative

 data X = X
   (Maybe String)
   (Maybe String)
   (Maybe String)
   (Maybe String)
   (Maybe String)
   (Maybe String)
   (Maybe String)
   (Maybe String)
   (Maybe String)

 mb :: (String -> Maybe a) -> String -> Maybe (Maybe a)
 mb _ ""  = Just Nothing
 mb _ "-" = Just Nothing
 mb p xs  = Just <$> p xs

 run :: [String] -> Maybe X
 run
   [ x1
   , x2
   , x3
   , x4
   , x5
   , x6
   , x7
   , x8
   , x9
   ] = X
   <$> mb pure x1
   <*> mb pure x2
   <*> mb pure x3
   <*> mb pure x4
   <*> mb pure x5
   <*> mb pure x6
   <*> mb pure x7
   <*> mb pure x8
   <*> mb pure x9
 }}}

 Unless `mb` is marked as NOINLINE, it gets expanded in the body of `run` a
 number of times that seems to grow exponentially with the size of the list
 (9 in the example).

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