
in the code below, finalmap seems fast enough ... but it has a space leak. otoh, finalmap'rnf runs in constant space, but its performance is terrible, at least 4x slower than finalmap. this is a common problem i'm having ... foldl' isn't strict enough, but foldl'rnf kills performance. and not only with IntMap as the cumulating data structure, but others as well. any ideas on this one? how can i get a fast fold in constant space? thanks again, travis {-# LANGUAGE BangPatterns #-} import System.Environment import Foreign (unsafePerformIO) import System.Random.Mersenne import Data.List import Control.DeepSeq import Control.Parallel.Strategies import qualified Data.IntMap as IntMap mersennegen = unsafePerformIO $ newMTGen Nothing infrandoms = unfoldr ( Just . splitAt 3) $ map (\x -> abs (x `mod` n)) (unsafePerformIO $ (randoms mersennegen)::[Int]) n = 200 foldl'rnf :: NFData a => (a -> b -> a) -> a -> [b] -> a foldl'rnf f z xs = lgo z xs where lgo z [] = z lgo !z (x:xs) = lgo (runEval (rdeepseq (f z x))) xs startmap = IntMap.fromDistinctAscList $ zip [0..] [1..n] finalmap x = foldl' g startmap (take x infrandoms) finalmap'rnf x = foldl'rnf g startmap (take x infrandoms) g:: IntMap.IntMap Int -> [Int] -> IntMap.IntMap Int g !a [x,y,z] = IntMap.adjust (const $ y + (a IntMap.! z) `mod` n) x a main = do args <- getArgs print $ finalmap (read $ head args)