Skip to content

Missed optimization: unused result

In this recent stackoverflow question the asker writes this code:

import Control.Monad.State
import System.Environment

sumState:: [Int] -> Int
sumState xs = execState (traverse f xs) 0
    where f n = modify (n+)

main :: IO ()
main = do
  x <- (read . head ) <$> getArgs
  print $ sumState [1..x]

Here is the relevant part of the core that GHC 8.10.4 generates (with -O2):

letrec {
  $s$wgo
    = \ sc sc1 ->
        let {
          ds2
            = case ==# sc1 y of {
                __DEFAULT ->
                  case $s$wgo (+# sc1 sc) (+# sc1 1#) of { (# ww1, ww2 #) ->
                  (ww1, ww2) `cast` <Co:6>
                  };
                1# -> ([], I# (+# sc1 sc)) `cast` <Co:9>
              } } in
        (# : () (case ds2 `cast` <Co:5> of { (x1, s'') -> x1 }),
           case ds2 `cast` <Co:5> of { (x1, s'') -> s'' } #); } in
case $s$wgo 0# 1# of { (# ww1, ww2 #) ->
case ww2 of { I# ww4 ->
case $wshowSignedInt 0# ww4 [] of { (# ww6, ww7 #) -> : ww6 ww7 }

The first element ww1 of the tuple that $s$wgo outputs is never used, so the $s$wgo function could be optimized to never build up this list. Why does GHC miss this optmization?

Here is the full dump: SumState.dump-simpl

Here is a smaller reproducer that doesn't use external libraries:

mysum :: [Int] -> Int -> ([()], Int)
mysum [] s = ([], s)
mysum (x:xs) s = let (xs', s') = mysum xs (s + x) in (() : xs', s')

main :: IO ()
main = print (snd (mysum [1..100] 0))
Edited by Jaro Reinders
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information