Prevent replicateM_ from repeating expensive (pure) computations

Hi all, I've been writing loops in a monad using `replicateM_`. However, recently I discovered that it caused my program become extremely slow. For example,
module Main where
import Control.Monad (replicateM_)
fib :: Int -> Int fib 0 = 0 fib 1 = 1 fib n = fib (n-1) + fib (n-2)
main = do n <- readLn let fn = fib n replicateM_ 20 (print fn)
The program ran fine if no optimization is turned on. However, when I used `-O` or `-O2` with GHC (7.4/7.6), the program became extremely slow, and if I replaced `replicateM_` by `mapM_`, the problem disappeared. I suspected that GHC inlined `fn`, causing `replicateM_` to recalculate the value in every loop. Though the problem could be solved by either using `mapM_`, lifting `print fn` to a global definition or manually demanding it be evaluated strictly, I would expected `fn` not to be computed multiple times. Any suggestions around this? Thanks! Sincerely, suhorng

You seem to be right about the inlining. This seems to work import Control.Monad (replicateM_) fib :: Int -> Int fib 0 = 0 fib 1 = 1 fib n = fib (n-1) + fib (n-2) main = do n <- readLn fn <- return $! fib n -- force one and only one evaluation replicateM_ 20 (print fn) Otherwise you can make inline fn more difficult (impossible?) with seq main = do n <- readLn let fn = fib n fn `seq` replicateM_ 20 (print fn) Note that GHC seems to be too smart for itself and will inline something like flip const fn $ .... since it can see that const isn't strict in fn. Cheers, Danny Gratzer
participants (2)
-
Danny Gratzer
-
suhorng Y