[GHC] #11271: Costly let binding gets duplicated in IO action value

GHC ghc-devs at haskell.org
Mon Dec 21 06:00:56 UTC 2015


#11271: Costly let binding gets duplicated in IO action value
-------------------------------------+-------------------------------------
           Reporter:  dramforever    |             Owner:
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  7.10.2
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  Runtime
  Unknown/Multiple                   |  performance bug
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 The following code is much slower when optimized.

 {{{#!hs
 module Main where

 import Control.Monad
 import Data.Char
 import System.IO

 -- getInt: read a integer from stdin, skipping spaces
 {-# NOINLINE getInt #-} -- to simplify generated core
 getInt :: IO Int
 getInt = skipSpaces >> go 0
   where skipSpaces = do next <- hLookAhead stdin
                         if isSpace next
                            then getChar >> skipSpaces
                            else return ()
         go n = do next <- hLookAhead stdin
                   if isNumber next
                     then getChar >> go (10 * n + digitToInt next)
                     else return n

 {-# NOINLINE generateSlowList #-}
 generateSlowList :: Int -> [Int]
 generateSlowList 0 = [1]
 generateSlowList n = scanl (+) 1 (generateSlowList (n-1))

 main = do
   n <- getInt
   let ls = generateSlowList n --- !!!
   replicateM_ n $ do
     i <- getInt
     print (ls !! i)
 }}}

 How to run:

 {{{
 (echo 10000; yes 5000) | time ./slow > /dev/null
 }}}

 After a rough look through the generated core, it seems that the `ls` was
 moved into the argument to `replicateM_`, which is a lambda taking a
 `State# RealWorld`. It means that a list is rebuilt every time it's
 indexed, even though a let binding could have caused sharing. By the way
 it seems that `-fno-state-hack`, which seems related, doesn't seem to
 help.

 Interesting to note that using a bang pattern (`let !ls = ...`) would make
 the problem go away.

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11271>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list