[Haskell-cafe] Prevent replicateM_ from repeating expensive (pure) computations

suhorng Y suhorng at gmail.com
Thu May 1 17:16:53 UTC 2014


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
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20140502/5332d1d6/attachment.html>


More information about the Haskell-Cafe mailing list