c407abf43632d70421d7d21d0f53bc391c17bf75
[ghc-base.git] / Data / HashTable.hs
1 {-# OPTIONS_GHC -XNoImplicitPrelude -funbox-strict-fields -fno-warn-name-shadowing #-}
2
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  Data.HashTable
6 -- Copyright   :  (c) The University of Glasgow 2003
7 -- License     :  BSD-style (see the file libraries/base/LICENSE)
8 --
9 -- Maintainer  :  libraries@haskell.org
10 -- Stability   :  provisional
11 -- Portability :  portable
12 --
13 -- An implementation of extensible hash tables, as described in
14 -- Per-Ake Larson, /Dynamic Hash Tables/, CACM 31(4), April 1988,
15 -- pp. 446--457.  The implementation is also derived from the one
16 -- in GHC's runtime system (@ghc\/rts\/Hash.{c,h}@).
17 --
18 -----------------------------------------------------------------------------
19
20 module Data.HashTable (
21         -- * Basic hash table operations
22         HashTable, new, newHint, insert, delete, lookup, update,
23         -- * Converting to and from lists
24         fromList, toList,
25         -- * Hash functions
26         -- $hash_functions
27         hashInt, hashString,
28         prime,
29         -- * Diagnostics
30         longestChain
31  ) where
32
33 -- This module is imported by Data.Dynamic, which is pretty low down in the
34 -- module hierarchy, so don't import "high-level" modules
35
36 #ifdef __GLASGOW_HASKELL__
37 import GHC.Base
38 #else
39 import Prelude  hiding  ( lookup )
40 #endif
41 import Data.Tuple       ( fst )
42 import Data.Bits
43 import Data.Maybe
44 import Data.List        ( maximumBy, length, concat, foldl', partition )
45 import Data.Int         ( Int32 )
46
47 #if defined(__GLASGOW_HASKELL__)
48 import GHC.Num
49 import GHC.Real         ( fromIntegral )
50 import GHC.Show         ( Show(..) )
51 import GHC.Int          ( Int64 )
52
53 import GHC.IO
54 import GHC.IOArray
55 import GHC.IORef
56 #else
57 import Data.Char        ( ord )
58 import Data.IORef       ( IORef, newIORef, readIORef, writeIORef )
59 import System.IO.Unsafe ( unsafePerformIO )
60 import Data.Int         ( Int64 )
61 #  if defined(__HUGS__)
62 import Hugs.IOArray     ( IOArray, newIOArray,
63                           unsafeReadIOArray, unsafeWriteIOArray )
64 #  elif defined(__NHC__)
65 import NHC.IOExtras     ( IOArray, newIOArray, readIOArray, writeIOArray )
66 #  endif
67 #endif
68 import Control.Monad    ( mapM, mapM_, sequence_ )
69
70
71 -----------------------------------------------------------------------
72
73 iNSTRUMENTED :: Bool
74 iNSTRUMENTED = False
75
76 -----------------------------------------------------------------------
77
78 readHTArray  :: HTArray a -> Int32 -> IO a
79 writeMutArray :: MutArray a -> Int32 -> a -> IO ()
80 newMutArray   :: (Int32, Int32) -> a -> IO (MutArray a)
81 newMutArray = newIOArray
82 type MutArray a = IOArray Int32 a
83 type HTArray a = MutArray a
84 #if defined(DEBUG) || defined(__NHC__)
85 readHTArray  = readIOArray
86 writeMutArray = writeIOArray
87 #else
88 readHTArray arr i = unsafeReadIOArray arr (fromIntegral i)
89 writeMutArray arr i x = unsafeWriteIOArray arr (fromIntegral i) x
90 #endif
91
92 data HashTable key val = HashTable {
93                                      cmp     :: !(key -> key -> Bool),
94                                      hash_fn :: !(key -> Int32),
95                                      tab     :: !(IORef (HT key val))
96                                    }
97 -- TODO: the IORef should really be an MVar.
98
99 data HT key val
100   = HT {
101         kcount  :: !Int32,              -- Total number of keys.
102         bmask   :: !Int32,
103         buckets :: !(HTArray [(key,val)])
104        }
105
106 -- ------------------------------------------------------------
107 -- Instrumentation for performance tuning
108
109 -- This ought to be roundly ignored after optimization when
110 -- iNSTRUMENTED=False.
111
112 -- STRICT version of modifyIORef!
113 modifyIORef :: IORef a -> (a -> a) -> IO ()
114 modifyIORef r f = do
115   v <- readIORef r
116   let z = f v in z `seq` writeIORef r z
117
118 data HashData = HD {
119   tables :: !Integer,
120   insertions :: !Integer,
121   lookups :: !Integer,
122   totBuckets :: !Integer,
123   maxEntries :: !Int32,
124   maxChain :: !Int,
125   maxBuckets :: !Int32
126 } deriving (Eq, Show)
127
128 {-# NOINLINE hashData #-}
129 hashData :: IORef HashData
130 hashData =  unsafePerformIO (newIORef (HD { tables=0, insertions=0, lookups=0,
131                                             totBuckets=0, maxEntries=0,
132                                             maxChain=0, maxBuckets=tABLE_MIN } ))
133
134 instrument :: (HashData -> HashData) -> IO ()
135 instrument i | iNSTRUMENTED = modifyIORef hashData i
136              | otherwise    = return ()
137
138 recordNew :: IO ()
139 recordNew = instrument rec
140   where rec hd@HD{ tables=t, totBuckets=b } =
141                hd{ tables=t+1, totBuckets=b+fromIntegral tABLE_MIN }
142
143 recordIns :: Int32 -> Int32 -> [a] -> IO ()
144 recordIns i sz bkt = instrument rec
145   where rec hd@HD{ insertions=ins, maxEntries=mx, maxChain=mc } =
146                hd{ insertions=ins+fromIntegral i, maxEntries=mx `max` sz,
147                    maxChain=mc `max` length bkt }
148
149 recordResize :: Int32 -> Int32 -> IO ()
150 recordResize older newer = instrument rec
151   where rec hd@HD{ totBuckets=b, maxBuckets=mx } =
152                hd{ totBuckets=b+fromIntegral (newer-older),
153                    maxBuckets=mx `max` newer }
154
155 recordLookup :: IO ()
156 recordLookup = instrument lkup
157   where lkup hd@HD{ lookups=l } = hd{ lookups=l+1 }
158
159 -- stats :: IO String
160 -- stats =  fmap show $ readIORef hashData
161
162 -- ----------------------------------------------------------------------------
163 -- Sample hash functions
164
165 -- $hash_functions
166 --
167 -- This implementation of hash tables uses the low-order /n/ bits of the hash
168 -- value for a key, where /n/ varies as the hash table grows.  A good hash
169 -- function therefore will give an even distribution regardless of /n/.
170 --
171 -- If your keyspace is integrals such that the low-order bits between
172 -- keys are highly variable, then you could get away with using 'fromIntegral'
173 -- as the hash function.
174 --
175 -- We provide some sample hash functions for 'Int' and 'String' below.
176
177 golden :: Int32
178 golden = 1013904242 -- = round ((sqrt 5 - 1) * 2^32) :: Int32
179 -- was -1640531527 = round ((sqrt 5 - 1) * 2^31) :: Int32
180 -- but that has bad mulHi properties (even adding 2^32 to get its inverse)
181 -- Whereas the above works well and contains no hash duplications for
182 -- [-32767..65536]
183
184 hashInt32 :: Int32 -> Int32
185 hashInt32 x = mulHi x golden + x
186
187 -- | A sample (and useful) hash function for Int and Int32,
188 -- implemented by extracting the uppermost 32 bits of the 64-bit
189 -- result of multiplying by a 33-bit constant.  The constant is from
190 -- Knuth, derived from the golden ratio:
191 --
192 -- > golden = round ((sqrt 5 - 1) * 2^32)
193 --
194 -- We get good key uniqueness on small inputs
195 -- (a problem with previous versions):
196 --  (length $ group $ sort $ map hashInt [-32767..65536]) == 65536 + 32768
197 --
198 hashInt :: Int -> Int32
199 hashInt x = hashInt32 (fromIntegral x)
200
201 -- hi 32 bits of a x-bit * 32 bit -> 64-bit multiply
202 mulHi :: Int32 -> Int32 -> Int32
203 mulHi a b = fromIntegral (r `shiftR` 32)
204    where r :: Int64
205          r = fromIntegral a * fromIntegral b
206
207 -- | A sample hash function for Strings.  We keep multiplying by the
208 -- golden ratio and adding.  The implementation is:
209 --
210 -- > hashString = foldl' f golden
211 -- >   where f m c = fromIntegral (ord c) * magic + hashInt32 m
212 -- >         magic = 0xdeadbeef
213 --
214 -- Where hashInt32 works just as hashInt shown above.
215 --
216 -- Knuth argues that repeated multiplication by the golden ratio
217 -- will minimize gaps in the hash space, and thus it's a good choice
218 -- for combining together multiple keys to form one.
219 --
220 -- Here we know that individual characters c are often small, and this
221 -- produces frequent collisions if we use ord c alone.  A
222 -- particular problem are the shorter low ASCII and ISO-8859-1
223 -- character strings.  We pre-multiply by a magic twiddle factor to
224 -- obtain a good distribution.  In fact, given the following test:
225 --
226 -- > testp :: Int32 -> Int
227 -- > testp k = (n - ) . length . group . sort . map hs . take n $ ls
228 -- >   where ls = [] : [c : l | l <- ls, c <- ['\0'..'\xff']]
229 -- >         hs = foldl' f golden
230 -- >         f m c = fromIntegral (ord c) * k + hashInt32 m
231 -- >         n = 100000
232 --
233 -- We discover that testp magic = 0.
234
235 hashString :: String -> Int32
236 hashString = foldl' f golden
237    where f m c = fromIntegral (ord c) * magic + hashInt32 m
238          magic = 0xdeadbeef
239
240 -- | A prime larger than the maximum hash table size
241 prime :: Int32
242 prime = 33554467
243
244 -- -----------------------------------------------------------------------------
245 -- Parameters
246
247 tABLE_MAX :: Int32
248 tABLE_MAX  = 32 * 1024 * 1024   -- Maximum size of hash table
249 tABLE_MIN :: Int32
250 tABLE_MIN  = 8
251
252 hLOAD :: Int32
253 hLOAD = 7                       -- Maximum average load of a single hash bucket
254
255 hYSTERESIS :: Int32
256 hYSTERESIS = 64                 -- entries to ignore in load computation
257
258 {- Hysteresis favors long association-list-like behavior for small tables. -}
259
260 -- -----------------------------------------------------------------------------
261 -- Creating a new hash table
262
263 -- | Creates a new hash table.  The following property should hold for the @eq@
264 -- and @hash@ functions passed to 'new':
265 --
266 -- >   eq A B  =>  hash A == hash B
267 --
268 new
269   :: (key -> key -> Bool)    -- ^ @eq@: An equality comparison on keys
270   -> (key -> Int32)          -- ^ @hash@: A hash function on keys
271   -> IO (HashTable key val)  -- ^ Returns: an empty hash table
272
273 new cmpr hash = do
274   recordNew
275   -- make a new hash table with a single, empty, segment
276   let mask = tABLE_MIN-1
277   bkts <- newMutArray (0,mask) []
278
279   let
280     kcnt = 0
281     ht = HT {  buckets=bkts, kcount=kcnt, bmask=mask }
282
283   table <- newIORef ht
284   return (HashTable { tab=table, hash_fn=hash, cmp=cmpr })
285
286 {- 
287    bitTwiddleSameAs takes as arguments positive Int32s less than maxBound/2 and 
288    returns the smallest power of 2 that is greater than or equal to the 
289    argument.
290    http://graphics.stanford.edu/~seander/bithacks.html#RoundUpPowerOf2
291 -}
292 bitTwiddleSameAs :: Int32 -> Int32
293 bitTwiddleSameAs v0 = 
294     let v1 = v0-1
295         v2 = v1 .|. (v1`shiftR`1)
296         v3 = v2 .|. (v2`shiftR`2)
297         v4 = v3 .|. (v3`shiftR`4)
298         v5 = v4 .|. (v4`shiftR`8)
299         v6 = v5 .|. (v5`shiftR`16)
300     in v6+1
301
302 {-
303   powerOver takes as arguments Int32s and returns the smallest power of 2 
304   that is greater than or equal to the argument if that power of 2 is 
305   within [tABLE_MIN,tABLE_MAX]
306 -}
307 powerOver :: Int32 -> Int32
308 powerOver n = 
309     if n <= tABLE_MIN
310     then tABLE_MIN
311     else if n >= tABLE_MAX
312          then tABLE_MAX
313          else bitTwiddleSameAs n 
314
315 -- | Creates a new hash table with the given minimum size.
316 newHint
317   :: (key -> key -> Bool)    -- ^ @eq@: An equality comparison on keys
318   -> (key -> Int32)          -- ^ @hash@: A hash function on keys
319   -> Int                     -- ^ @minSize@: initial table size
320   -> IO (HashTable key val)  -- ^ Returns: an empty hash table
321
322 newHint cmpr hash minSize = do
323   recordNew
324   -- make a new hash table with a single, empty, segment
325   let mask = powerOver $ fromIntegral minSize
326   bkts <- newMutArray (0,mask) []
327
328   let
329     kcnt = 0
330     ht = HT {  buckets=bkts, kcount=kcnt, bmask=mask }
331
332   table <- newIORef ht
333   return (HashTable { tab=table, hash_fn=hash, cmp=cmpr })
334
335 -- -----------------------------------------------------------------------------
336 -- Inserting a key\/value pair into the hash table
337
338 -- | Inserts a key\/value mapping into the hash table.
339 --
340 -- Note that 'insert' doesn't remove the old entry from the table -
341 -- the behaviour is like an association list, where 'lookup' returns
342 -- the most-recently-inserted mapping for a key in the table.  The
343 -- reason for this is to keep 'insert' as efficient as possible.  If
344 -- you need to update a mapping, then we provide 'update'.
345 --
346 insert :: HashTable key val -> key -> val -> IO ()
347
348 insert ht key val =
349   updatingBucket CanInsert (\bucket -> ((key,val):bucket, 1, ())) ht key
350
351
352 -- ------------------------------------------------------------
353 -- The core of the implementation is lurking down here, in findBucket,
354 -- updatingBucket, and expandHashTable.
355
356 tooBig :: Int32 -> Int32 -> Bool
357 tooBig k b = k-hYSTERESIS > hLOAD * b
358
359 -- index of bucket within table.
360 bucketIndex :: Int32 -> Int32 -> Int32
361 bucketIndex mask h = h .&. mask
362
363 -- find the bucket in which the key belongs.
364 -- returns (key equality, bucket index, bucket)
365 --
366 -- This rather grab-bag approach gives enough power to do pretty much
367 -- any bucket-finding thing you might want to do.  We rely on inlining
368 -- to throw away the stuff we don't want.  I'm proud to say that this
369 -- plus updatingBucket below reduce most of the other definitions to a
370 -- few lines of code, while actually speeding up the hashtable
371 -- implementation when compared with a version which does everything
372 -- from scratch.
373 {-# INLINE findBucket #-}
374 findBucket :: HashTable key val -> key -> IO (HT key val, Int32, [(key,val)])
375 findBucket HashTable{ tab=ref, hash_fn=hash} key = do
376   table@HT{ buckets=bkts, bmask=b } <- readIORef ref
377   let indx = bucketIndex b (hash key)
378   bucket <- readHTArray bkts indx
379   return (table, indx, bucket)
380
381 data Inserts = CanInsert
382              | Can'tInsert
383              deriving (Eq)
384
385 -- updatingBucket is the real workhorse of all single-element table
386 -- updates.  It takes a hashtable and a key, along with a function
387 -- describing what to do with the bucket in which that key belongs.  A
388 -- flag indicates whether this function may perform table insertions.
389 -- The function returns the new contents of the bucket, the number of
390 -- bucket entries inserted (negative if entries were deleted), and a
391 -- value which becomes the return value for the function as a whole.
392 -- The table sizing is enforced here, calling out to expandSubTable as
393 -- necessary.
394
395 -- This function is intended to be inlined and specialized for every
396 -- calling context (eg every provided bucketFn).
397 {-# INLINE updatingBucket #-}
398
399 updatingBucket :: Inserts -> ([(key,val)] -> ([(key,val)], Int32, a)) ->
400                   HashTable key val -> key ->
401                   IO a
402 updatingBucket canEnlarge bucketFn
403                ht@HashTable{ tab=ref, hash_fn=hash } key = do
404   (table@HT{ kcount=k, buckets=bkts, bmask=b },
405    indx, bckt) <- findBucket ht key
406   (bckt', inserts, result) <- return $ bucketFn bckt
407   let k' = k + inserts
408       table1 = table { kcount=k' }
409   writeMutArray bkts indx bckt'
410   table2 <- if canEnlarge == CanInsert && inserts > 0 then do
411                recordIns inserts k' bckt'
412                if tooBig k' b
413                   then expandHashTable hash table1
414                   else return table1
415             else return table1
416   writeIORef ref table2
417   return result
418
419 expandHashTable :: (key -> Int32) -> HT key val -> IO (HT key val)
420 expandHashTable hash table@HT{ buckets=bkts, bmask=mask } = do
421    let
422       oldsize = mask + 1
423       newmask = mask + mask + 1
424    recordResize oldsize (newmask+1)
425    --
426    if newmask > tABLE_MAX-1
427       then return table
428       else do
429    --
430     newbkts <- newMutArray (0,newmask) []
431
432     let
433      splitBucket oldindex = do
434        bucket <- readHTArray bkts oldindex
435        let (oldb,newb) =
436               partition ((oldindex==). bucketIndex newmask . hash . fst) bucket
437        writeMutArray newbkts oldindex oldb
438        writeMutArray newbkts (oldindex + oldsize) newb
439     mapM_ splitBucket [0..mask]
440
441     return ( table{ buckets=newbkts, bmask=newmask } )
442
443 -- -----------------------------------------------------------------------------
444 -- Deleting a mapping from the hash table
445
446 -- Remove a key from a bucket
447 deleteBucket :: (key -> Bool) -> [(key,val)] -> ([(key, val)], Int32, ())
448 deleteBucket _   [] = ([],0,())
449 deleteBucket del (pair@(k,_):bucket) =
450   case deleteBucket del bucket of
451     (bucket', dels, _) | del k     -> dels' `seq` (bucket', dels', ())
452                        | otherwise -> (pair:bucket', dels, ())
453       where dels' = dels - 1
454
455 -- | Remove an entry from the hash table.
456 delete :: HashTable key val -> key -> IO ()
457
458 delete ht@HashTable{ cmp=eq } key =
459   updatingBucket Can'tInsert (deleteBucket (eq key)) ht key
460
461 -- -----------------------------------------------------------------------------
462 -- Updating a mapping in the hash table
463
464 -- | Updates an entry in the hash table, returning 'True' if there was
465 -- already an entry for this key, or 'False' otherwise.  After 'update'
466 -- there will always be exactly one entry for the given key in the table.
467 --
468 -- 'insert' is more efficient than 'update' if you don't care about
469 -- multiple entries, or you know for sure that multiple entries can't
470 -- occur.  However, 'update' is more efficient than 'delete' followed
471 -- by 'insert'.
472 update :: HashTable key val -> key -> val -> IO Bool
473
474 update ht@HashTable{ cmp=eq } key val =
475   updatingBucket CanInsert
476     (\bucket -> let (bucket', dels, _) = deleteBucket (eq key) bucket
477                 in  ((key,val):bucket', 1+dels, dels/=0))
478     ht key
479
480 -- -----------------------------------------------------------------------------
481 -- Looking up an entry in the hash table
482
483 -- | Looks up the value of a key in the hash table.
484 lookup :: HashTable key val -> key -> IO (Maybe val)
485
486 lookup ht@HashTable{ cmp=eq } key = do
487   recordLookup
488   (_, _, bucket) <- findBucket ht key
489   let firstHit (k,v) r | eq key k  = Just v
490                        | otherwise = r
491   return (foldr firstHit Nothing bucket)
492
493 -- -----------------------------------------------------------------------------
494 -- Converting to/from lists
495
496 -- | Convert a list of key\/value pairs into a hash table.  Equality on keys
497 -- is taken from the Eq instance for the key type.
498 --
499 fromList :: (Eq key) => (key -> Int32) -> [(key,val)] -> IO (HashTable key val)
500 fromList hash list = do
501   table <- new (==) hash
502   sequence_ [ insert table k v | (k,v) <- list ]
503   return table
504
505 -- | Converts a hash table to a list of key\/value pairs.
506 --
507 toList :: HashTable key val -> IO [(key,val)]
508 toList = mapReduce id concat
509
510 {-# INLINE mapReduce #-}
511 mapReduce :: ([(key,val)] -> r) -> ([r] -> r) -> HashTable key val -> IO r
512 mapReduce m r HashTable{ tab=ref } = do
513   HT{ buckets=bckts, bmask=b } <- readIORef ref
514   fmap r (mapM (fmap m . readHTArray bckts) [0..b])
515
516 -- -----------------------------------------------------------------------------
517 -- Diagnostics
518
519 -- | This function is useful for determining whether your hash
520 -- function is working well for your data set.  It returns the longest
521 -- chain of key\/value pairs in the hash table for which all the keys
522 -- hash to the same bucket.  If this chain is particularly long (say,
523 -- longer than 14 elements or so), then it might be a good idea to try
524 -- a different hash function.
525 --
526 longestChain :: HashTable key val -> IO [(key,val)]
527 longestChain = mapReduce id (maximumBy lengthCmp)
528   where lengthCmp (_:x)(_:y) = lengthCmp x y
529         lengthCmp []   []    = EQ
530         lengthCmp []   _     = LT
531         lengthCmp _    []    = GT