Skip to content

Commit e5adbf5

Browse files
committed
Make size run in constant time
1 parent efa43a2 commit e5adbf5

File tree

4 files changed

+712
-356
lines changed

4 files changed

+712
-356
lines changed

Data/HashMap/Array.hs

Lines changed: 43 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
{-# LANGUAGE BangPatterns, CPP, MagicHash, Rank2Types, UnboxedTuples, ScopedTypeVariables #-}
2+
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
23
{-# OPTIONS_GHC -fno-full-laziness -funbox-strict-fields #-}
34

45
-- | Zero based arrays.
@@ -7,6 +8,11 @@
78
module Data.HashMap.Array
89
( Array
910
, MArray
11+
, RunRes (..)
12+
, RunResA
13+
, RunResM
14+
, Size (..)
15+
, Sized (..)
1016

1117
-- * Creation
1218
, new
@@ -25,6 +31,7 @@ module Data.HashMap.Array
2531
, index#
2632
, update
2733
, updateWith'
34+
, updateWithInternal'
2835
, unsafeUpdateM
2936
, insert
3037
, insertM
@@ -36,6 +43,7 @@ module Data.HashMap.Array
3643
, unsafeThaw
3744
, unsafeSameArray
3845
, run
46+
, runInternal
3947
, run2
4048
, copy
4149
, copyM
@@ -313,10 +321,24 @@ unsafeThaw ary
313321
(# s', mary #) -> (# s', marray mary (length ary) #)
314322
{-# INLINE unsafeThaw #-}
315323

324+
-- | Helper datatype used in 'runInternal' and 'updateWithInternal'
325+
data RunRes f e = RunRes {-# UNPACK #-} !Size !(f e)
326+
327+
type RunResA e = RunRes Array e
328+
329+
type RunResM s e = RunRes (MArray s) e
330+
316331
run :: (forall s . ST s (MArray s e)) -> Array e
317332
run act = runST $ act >>= unsafeFreeze
318333
{-# INLINE run #-}
319334

335+
runInternal :: (forall s . ST s (RunResM s e)) -> RunResA e
336+
runInternal act = runST $ do
337+
RunRes s mary <- act
338+
ary <- unsafeFreeze mary
339+
return (RunRes s ary)
340+
{-# INLINE runInternal #-}
341+
320342
run2 :: (forall s. ST s (MArray s e, a)) -> (Array e, a)
321343
run2 k = runST (do
322344
(marr,b) <- k
@@ -388,7 +410,7 @@ updateM ary idx b =
388410
where !count = length ary
389411
{-# INLINE updateM #-}
390412

391-
-- | /O(n)/ Update the element at the given positio in this array, by
413+
-- | /O(n)/ Update the element at the given position in this array, by
392414
-- applying a function to it. Evaluates the element to WHNF before
393415
-- inserting it into the array.
394416
updateWith' :: Array e -> Int -> (e -> e) -> Array e
@@ -397,6 +419,26 @@ updateWith' ary idx f
397419
= update ary idx $! f x
398420
{-# INLINE updateWith' #-}
399421

422+
-- | This newtype wrapper is to avoid confusion when local functions
423+
-- take more than one paramenter of 'Int' type (see 'go' in
424+
-- 'Data.HashMap.Base.unionWithKeyInternal').
425+
newtype Size = Size { unSize :: Int }
426+
deriving (Eq, Ord, Num, Integral, Enum, Real)
427+
428+
-- | Helper datatype used in 'updateWithInternal''. Used when a change in
429+
-- a value's size must be returned along with the value itself (typically
430+
-- a hashmap).
431+
data Sized a = Sized {-# UNPACK #-} !Size !a
432+
433+
-- | /O(n)/ Update the element at the given position in this array, by
434+
-- applying a function to it. Evaluates the element to WHNF before
435+
-- inserting it into the array.
436+
updateWithInternal' :: Array e -> Int -> (e -> Sized e) -> RunResA e
437+
updateWithInternal' ary idx f =
438+
let Sized sz e = f (index ary idx)
439+
in RunRes sz (update ary idx e)
440+
{-# INLINE updateWithInternal' #-}
441+
400442
-- | /O(1)/ Update the element at the given position in this array,
401443
-- without copying.
402444
unsafeUpdateM :: Array e -> Int -> e -> ST s ()

0 commit comments

Comments
 (0)