interesting example of lazyness/ghc optimisation
Julian Assange
proff@iq.org
01 Mar 2001 13:25:46 +1100
Brian Gregor wrote a haskell entrant for the random number
generation in Doug's language shootout
(http://www.bagley.org/~doug/shootout). Which is as follows:
module Main where
import System
import Numeric
iMi :: Int
iMi = 139968
iMd :: Double
iMd = 139968.0
iA ::Int
iA = 3877
iC ::Int
iC = 29573
nrRandom :: Int -> Double -> (Int,Double)
nrRandom last max = (newlast,(max * (fromIntegral newlast)/iMd))
where newlast = (last*iA+iC) `mod` iMi
runRandom :: Int -> Double -> Int -> Double
runRandom last max num
| num > 1 = runRandom (fst new) max (num-1)
| otherwise = snd new
where
new = nrRandom last max
main = do
~[n] <- getArgs
putStrLn (showFFloat (Just 12) (runRandom 42 100.0 (read n::Int)) "")
Noticing the use of tuples and normalisation at each step of
the iteration, I re-wrote this as:
module Main(main) where
import System(getArgs)
import Numeric(showFFloat)
main = do
~[n] <- getArgs
putStrLn (showFFloat (Just 12) (random 42 (read n::Int) 100.0) "")
return 1
random :: Int -> Int -> Double -> Double
random seed n max = norm (rand n seed) max
where norm x max = (fromIntegral x) * (max / imd)
rand n x = if n > 0 then rand (n-1) ((x * ia + ic) `mod` im) else x
im = 139968
imd = fromIntegral im
ia = 3877
ic = 29573
Interestingly, ghc / lazyness is able to detect that Brian's
normalisation etc at each step is uneeded, and only perform it at the
end. Consequently both of these programs are the the same speed (well,
almost; bizarrely, Brian's seems to be about 2% faster).
Julian.