Seemingly subtle change causes large performance variation

Matthew Danish mdanish at andrew.cmu.edu
Thu Jun 7 17:33:30 EDT 2007


Hello,

I've been playing with the INTEST problem on SPOJ which demonstrates
the ability to write a program which processes large quantities of
input data.  http://www.spoj.pl/problems/INTEST/

I came across some curious behavior while cleaning up the program.
The original program, which runs fast (enough), is:

module Main(main) where
import Control.Monad
import Data.Maybe
import qualified Data.ByteString.Char8 as B

divisibleBy :: Int -> Int -> Bool
a `divisibleBy` n = a `rem` n == 0

main :: IO ()
main = do
    [n,k] <- (map int . B.split ' ') `fmap` B.getLine :: IO [Int]

    let
        doLine :: Int -> Int -> IO Int
        doLine r _ = B.getLine >>= testDiv r
        testDiv r l
         | int l `divisibleBy` k = return (r + 1)
         | otherwise             = return r

    foldM doLine 0 [1..n] >>= print

    where
        int :: B.ByteString -> Int
        int = fst . fromJust . B.readInt 




But when I make a slight modification, the program chews up a ton more memory
and takes more time:

module Main(main) where
import Control.Monad
import Data.Maybe
import qualified Data.ByteString.Char8 as B

divisibleBy :: Int -> Int -> Bool
a `divisibleBy` n = a `rem` n == 0

main :: IO ()
main = do
    [n,k] <- (map int . B.split ' ') `fmap` B.getLine :: IO [Int]

    let
        doLine :: Int -> Int -> IO Int
        doLine r _ = B.getLine >>= return . testDiv r
        -- 'return' moved here      ^^
        testDiv r l
         | int l `divisibleBy` k = r + 1
         | otherwise             = r

    foldM doLine 0 [1..n] >>= print

    where
        int :: B.ByteString -> Int
        int = fst . fromJust . B.readInt 




This program will generate sample data:

import System.Random
import System.Environment
import Control.Monad

main = do
    [n] <- map read `fmap` getArgs :: IO [Int]
    k   <- randomRIO (1, 100)
    putStrLn $ unwords [show n, show k]
    replicateM_ n $ randomRIO (1, 10^9) >>= print


Note that the same behavior occurs even if I manually inline the local
function and try: return (if .. then .. else).

Some sample runs:

$ ghc/compiler/ghc-inplace 
ghc-6.7.20070601: no input files

$ ghc/compiler/ghc-inplace --make -O2 intest.hs
[1 of 1] Compiling Main             ( intest.hs, intest.o )
Linking intest ...
$ ghc/compiler/ghc-inplace --make -O2 intest_slow.hs
[1 of 1] Compiling Main             ( intest_slow.hs, intest_slow.o )
Linking intest_slow ...

$ time ./intest +RTS -tstderr -RTS < test1
./intest +RTS -tstderr
8830
<<ghc: 134876896 bytes, 248 GCs, 28672/28672 avg/max bytes residency
(1 samples), 2M in use, 0.00 INIT (0.00 elapsed), 0.12 MUT (0.12
elapsed), 0.00 GC (0.00 elapsed) :ghc>>

real    0m0.129s
user    0m0.124s
sys     0m0.006s

$ time ./intest_slow +RTS -tstderr -RTS < test1
./intest_slow +RTS -tstderr
8830
<<ghc: 144278584 bytes, 269 GCs, 7030784/21843968 avg/max bytes
residency (6 samples), 38M in use, 0.00 INIT (0.00 elapsed), 0.13 MUT
(0.14 elapsed), 0.10 GC (0.15 elapsed) :ghc>>

real    0m0.296s
user    0m0.238s
sys     0m0.058s

-- 
-- Matthew Danish -- user: mrd domain: cmu.edu
-- OpenPGP public key: C24B6010 on keyring.debian.org


More information about the Glasgow-haskell-users mailing list