Dean's version certainly seems the neatest, but just for interest you can also do it with a cps fold instead of foldl' too:

table xs = assocs $! cpsfold f empty xs
    where
    f x m k = case Map.lookup x m of
               Just v  -> v `seq` (k $ Map.adjust (+1) x m)
               Nothing -> k $ Map.insert x 1 m


cpsfold f a [] = a
cpsfold f a (x:xs) = f x a (\y -> cpsfold f y xs)


As far as I understand it this just makes sure the "seq" happens before the folding continues.

When compiled with ghc, both solutions are very well behaved, and seem to take the same small amount of memory whether for 10000000 or 100000000.

Amanda


Dean Herington wrote:
The following version seems to do the trick (and still remain quite readable). It worked for 100000000 as well.

import Data.Map as Map
import System.Random
import Data.List (foldl')

table :: (Ord a) => [a] -> [(a,Int)]
table xs = Map.assocs $! foldl' f Map.empty xs
    where f m x = let  m' = Map.insertWith (+) x 1 m
                       Just v = Map.lookup x m'
                  in v `seq` m'

unif :: [Int]
unif = randomRs (1,10) $ mkStdGen 1

f :: Int -> [(Int, Int)]
f n = table $ take n unif
main = print $ f 10000000

- Dean

_______________________________________________
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell

Reply via email to