[Haskell-cafe] OCaml list sees abysmal Language Shootout results

Ketil Malde ketil+haskell at ii.uib.no
Wed Oct 6 03:49:16 EDT 2004


Greg Buchholz <haskell at sleepingsquirrel.org> writes:

>     I've been looking at the other shootout results (with the hope of
> learning something about making haskell programs faster/less memory
> hungry) and I couldn't quite figure out why the "Hashes, part II" test
> comsumes so much memory ( http://shootout.alioth.debian.org/bench/hash2/ ). 
> So I started to try heap profiling, and generated the following graphs
> for the different types of profiles...

> biography => http://sleepingsquirrel.org/haskell/hash2_b.ps
> retainer  => http://sleepingsquirrel.org/haskell/hash2_r.ps
> closure   => http://sleepingsquirrel.org/haskell/hash2_d.ps
> type      => http://sleepingsquirrel.org/haskell/hash2_y.ps
> cost cntr => http://sleepingsquirrel.org/haskell/hash2_c.ps
>
> ...but I have a hard time figuring out how to prevent something like
> "stg_ap_3_upd_info" or "void" cells from consuming so much memory.

One thing you could do, is to move the pure definitions (constants and
functions) out of the monad.  This will make them separate cost
centres, with their own profile information.  I toyed with this, but
admittedly, it didn't change much in this case.  I think it is better
style, though.

A simple way to improve speed marginally, is to specify Int instead of
letting things default to Integer.  A more complex way, saving about
60% of the time, is to use unboxed arrays instead of strings for the
keys - memory consumption seems to be the same, though. 

To get memory consumption down, I tried a strict "update" function:

   update k fm = let x = (get hash1 k + get fm k) 
                 in x `seq` addToFM fm k x

which slowed the program down(!), but reduced memory consumption from
about 25Mb to 1.5Mb.  So it seems that the memory consumption is due
to unevaluated values in the FMs.

BTW, I looked at the shootout web pages, but I couldn't find the
specification for any of the benchmarks.  What is and isn't allowed? 

-kzm

-------------- next part --------------

import System (getArgs) 
import Data.FiniteMap 
import Data.Array.Unboxed
import Maybe

type Key = UArray Int Char
type Map = FiniteMap (UArray Int Char) Int

hash1, hash2 :: Map
hash1 = listToFM $ zip keys [0..9999] 
hash2 = listToFM $ zip keys (repeat 0) 

keys :: [Key]
keys = map (\x -> listArray (1,4+length (show x)) ("foo_" ++ show x)) [0..9999] 
get :: Map -> Key -> Int
get fm k = fromJust $ lookupFM fm k 

update :: Key -> Map -> Map
update k fm = let x = (get hash1 k + get fm k) in x `seq` addToFM fm k x

foo_1 = keys!!1
foo_9999 = keys!!9999

main = do 
 [n] <- getArgs  
 let res = foldr update hash2 (concat $ replicate (read n) keys) 
 putStrLn $ unwords $ map show [get hash1 foo_1,
                                get hash1 foo_9999, 
                                get res foo_1, 
                                get res foo_9999] 
-------------- next part --------------

-- 
If I haven't seen further, it is by standing in the footprints of giants


More information about the Haskell-Cafe mailing list