
On Sun, Oct 14, 2007 at 11:54:54PM +0200, ntupel wrote:
On Sat, 2007-10-13 at 09:56 -0400, Brandon S. Allbery KF8NH wrote:
Now you need to start forcing things; given laziness, things tend to only get forced when in IO, which leads to time being accounted to the routine where the forcing happened. If random / randomR are invoked with large unevaluated thunks, their forcing will generally be attributed to them, not to functions within the thunks.
(Yes, this means profiling lazy programs is a bit of a black art.)
After more testing I finally realized how right you are. It appears that my problem is not related to random/randomR but only to laziness. I came up with a test that doesn't use random numbers at all and still needs about 2.5 seconds to complete (it is really just meaningless computations):
Here's a modified version of your code that prints out a real result, by
using sum rather than seq to force the computation:
module Main where
main :: IO ()
main = do let n = 1000000 :: Int
print $ sum (take n $ test 1 [1,2..])
test :: Int -> [Int] -> [Int]
test t g =
let (n, g') = next t g
in
n:test t g'
next :: Int -> [Int] -> (Int, [Int])
next x (y:ys) =
let n = func y
in
if n <= 0.5 then (x, ys) else (0, ys)
where
func x = fromIntegral x / (10 ^ len x)
where
len 0 = 0
len n = 1 + len (n `div` 10)
On my computer this takes 4 seconds to run. I can speed it up by an order
of magnitude by writing code that is friendlier to the compiler:
module Main where
main :: IO ()
main = do let n = 1000000 :: Int
print $ sum (take n $ test 1 [1,2..])
test :: Int -> [Int] -> [Int]
test t g = map f g
where f :: Int -> Int
f y = if func y <= 0.5 then t else 0
func :: Int -> Double
func x = fromIntegral x / mypow x
mypow 0 = 1
mypow n = 10*(mypow (n `div` 10))
Switching to map and simplifying the structure gained me 30% or so, but the
big improvement came from the elimination of the use of (^) by writing
mypow (ill-named).
I have no idea if this example will help your actual code, but it
illustrates that at least in this example, it's pretty easy to gain an
order of magnitude in speed. (That "func" is a weird function, by the
way.)
Incidentally, implementing the same program in C, I get:
#include