Sorry, I forgot the attachment earlier. Daniel
-- | Build up random strings for use in a wc stress test.
module Main where import Control.Monad import Data.Array import Data.List import System.Environment import System.IO import System.Random listToArray lst = listArray (0, length lst - 1) lst lineChars = listToArray $ ['a'..'z'] ++ ['A' .. 'Z'] ++ (replicate 10 ' ') randomLineLength = 40 -- | Generate a vaguely random list that's definitely -- lazy, without calling randomRs. scramble lower upper | upper < lower = scramble upper lower | otherwise = map (+lower) $ scramble' 0 1 where scramble' n m = (n `mod` spread):scramble' m (n + m) spread = upper - lower + 1 -- | Maybe the problem is that randomRs is a separate function? iterRandom lower upper g = let (x, g') = randomR (lower, upper) g in x:(iterRandom lower upper g) randomLines g = map fst $ tail $ splitPairs where splitPairs = scanl (flip ($) . snd) ([], toSplit) splitters toSplit = {-# SCC "toSplit" #-} map (lineChars!) $ randomRs (bounds lineChars) g --toSplit = {-# SCC "toSplit" #-} map (lineChars!) $ (uncurry iterRandom) (bounds lineChars) g --toSplit = {-# SCC "toSplit" #-} map (lineChars!) $ uncurry scramble $ bounds lineChars --toSplit = {-# SCC "toSplit" #-} map (lineChars!) $ unfoldr (Just . randomR (bounds lineChars)) g splitters = map splitAt splitPoints splitPoints = randomRs ((randomLineLength * 3) `div` 4, (randomLineLength * 5) `div` 4) g2 (g1, g2) = split g -- | Chop a list up into pieces of (at most) a given length. segment :: Int -> [a] -> [[a]] segment n = unfoldr (doSplit n) where doSplit n [] = Nothing doSplit n lst = Just $ splitAt n lst main = do g <- getStdGen a <- getArgs when (length a > 1) (print "Too many arguments") let count = if null a then 10 else read $ head a output = unlines $ take count $ randomLines g putStr output -- This doesn't take more or less heap, so putStr -- must be doing something similarly lazy. --sequence_ $ map putStr $ segment 60000 output
signature.asc
Description: Digital signature