#6048: Exponential inlining code blowup
---------------------------------+------------------------------------------
    Reporter:  simonpj           |       Owner:                  
        Type:  bug               |      Status:  new             
    Priority:  normal            |   Milestone:                  
   Component:  Compiler          |     Version:  7.4.1           
    Keywords:                    |          Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |     Failure:  None/Unknown    
  Difficulty:  Unknown           |    Testcase:                  
   Blockedby:                    |    Blocking:                  
     Related:                    |  
---------------------------------+------------------------------------------
 (Transferring a new thread from #5539 to a new ticket, since it's really a
 separate problem.)  kosmikus helpfully provided this program
 {{{
 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/6048>
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