Laziness (was: [Haskell-cafe] Performance problem with random numbers)

ntupel ntupel at googlemail.com
Sun Oct 14 17:54:54 EDT 2007


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):


module Main where

import Data.List

main :: IO ()
main = do let n = 1000000 :: Int
          print $ foldl' (\x y -> seq y x) 0 (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)


Now my problem still is, that I don't know how to speed things up. I
tried putting seq and $! at various places with no apparent improvement.
Maybe I need to find a different data structure for my random module and
lazy lists are simply not working well enough here?

Thanks,
Thoralf




More information about the Haskell-Cafe mailing list