Hello!
The following program executes 1.5 seconds on my computer:
-----------------------CODE BEGIN-------------------------
module Main where
import Data.Array.IArray
main = print (answers ! 1000000)
nextAns :: (Int, Int, Float) -> (Int, Int, Float)
nextAns (a, n, r) = if r2 > 1 then (a+1, n+2, r2) else (a+1, n+3, r3)
where
a' = fromIntegral a
n' = fromIntegral n
r2 = r * (a'/(a'+1))**n' * (n'+1)*(n'+2)/(a'+1)^2
r3 = r2 * (n'+3) / (a'+1)
answers :: Array Int Int
answers = listArray (1, 1000000) (map snd3 $ iterate nextAns (1, 2, 2))
where snd3 (a, b, c) = b
------------------------CODE END--------------------------
From these 1.5 seconds, 1 second is spent on doing GC. If I run it with
"-A200M", it executes for only 0.5 seconds (total).
Which is more interesting, when I use UArray instead of Array, it spends
only 0.02 seconds in GC, but total running time is still 1.5 seconds.
Why are... these things?
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe