Here it is in haskell.  This shows some of the strengths of
haskell, but also some of its weaknesses.  Dealing with random
numbers is more tedious than it should be.  Some of the awkwardness
could be caused by the programmer's lack of experience with the
language.

----- e.lhs -----
Literate haskell for computing "e" the hard way. Translated from lisp code by Jim Thompson (see e.lisp)

module E where
import Time
import System.Random

Some siliness so that the random numbers are different for each run.

randomSeed :: IO Int
randomSeed = do                       -- XXX Could be a lot better.
      t <- getClockTime >>= toCalendarTime
      return $ hashStr $ show t where
              hashStr s = foldl hashAdd 0 $ map fromEnum s
              hashAdd a b = (a*13) + b

A sum is the accumulation from 0.  We call it sum' because there's already
an integer sum function. A list of accumulated sums is made by keeping each intermediate sum value.

sum' = foldl (+) 0.0
sums = scanl (+) 0.0

Average of a list is its sum divided by its length.

average x = sum' (map fromIntegral x) / (fromIntegral $ length x)

length of series items whose sum does not exceed 1.0.

waitTime x = length $ takeWhile (< 1.0) (sums x)

A number of waitTimes drawn from successive items in x.

waitTimes x 0 = []
waitTimes x n = let wt = waitTime x in wt : waitTimes (drop wt x) (n - 1)

putLine x = putStr $ (show x) ++ "\n"

main :: IO ()
main = do
      seed <- randomSeed
      let variates = randoms $ mkStdGen seed
      mapM_ putLine $ [average $ waitTimes variates n | n <- [1,10,100,1000]]

Tim Newsham
http://www.lava.net/~newsham/

Reply via email to