[Haskell-cafe] more shootout madness -- hashes in GHC

Robert robdockins at fastmail.fm
Thu Oct 7 15:53:12 EDT 2004


I've been playing around with the "Hashes, Part II" code from the
shootout.  I wanted to try to implement this test using Data.HashTable
instead of Data.FiniteMap to see if that would buy us anything.  In
fact, the HashTable implementation is consistantly faster than
FiniteMap, but not by a lot (thus making the transition to the IO monad
not worthwhile IMO).  The interesting thing, however, is that at a
certain number of iterations (106 in my case), the Hashtable code
segfaults.  GDB shows that it is blowing the top off the program stack
and dying when it tries to write to kernel space.  (can't write to
0xbfffffff).

My question is, why does this happen?  Is it well known that sequence_
ing longish lists has this effect?  It seems to me that there is no
reason to consume stack for sequences of IO like this (especially using
sequence_ or >> where we ONLY care about the side effects of the
operation).  I don't have a stong grasp of how the RTS works, perhaps
someone could explain in small words?

The code in question is attached.  As you can see, I've tried several
approaches to reduce the program stack usage, but they seem to generate
very similar code.
-- 
  Robert
  robdockins at fastmail.fm

-------------- next part --------------
import System
import Maybe
import Data.HashTable

update ht1 ht2 key = do
    (Just x) <- Data.HashTable.lookup ht1 key
    maybey   <- Data.HashTable.lookup ht2 key
    case maybey of
       Just y  -> do delete ht2 key; insert ht2 key (x+y)
       Nothing -> do insert ht2 key x

applyEach [] = return ()
applyEach (x:xs) = x >> applyEach xs

main = do
    [n] <- getArgs

    let elements = [0..9999]
	keys = map (\x -> "foo_"++(show x)) elements

    ht1 <- fromList hashString $ zip keys elements
    ht2 <- new (==) hashString :: IO (HashTable String Int)

    -- foldr (<<) $ concat $ replicate (read n) [ update ht1 ht2 key | key <- keys ]
    -- applyEach [ applyEach $ replicate (read n) $ update ht1 ht2 key | key <- keys ]
    -- sequence_ $ concat $ replicate (read n) [ update ht1 ht2 key | key <- keys ]

    sequence_ [ sequence_ $ replicate (read n) $ update ht1 ht2 key | key <- keys ]

    vals <- sequence [Data.HashTable.lookup ht1 "foo_1"     
                     ,Data.HashTable.lookup ht1 "foo_9999"  
                     ,Data.HashTable.lookup ht2 "foo_1"     
                     ,Data.HashTable.lookup ht2 "foo_9999"  
	             ]
    putStrLn $ unwords $ map (show . fromJust) vals


More information about the Haskell-Cafe mailing list