Skip to content

Commit 467d161

Browse files
committed
Avoid boxing arrays
Previously, we used a lot of things that looked like runST (act >>= unsafeFreeze) The trouble is that GHC can't unbox past the `runRW#` primitive that `runST` is based on. So this actually allocates an `Array` constructor which we will then throw away immediately. The way to avoid this is to call `runRW#` manually to produce a raw `SmallArray#`, then apply the `Array` constructor on the outside.
1 parent 53eb7eb commit 467d161

File tree

3 files changed

+52
-31
lines changed

3 files changed

+52
-31
lines changed

Data/HashMap/Array.hs

Lines changed: 41 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -36,7 +36,6 @@ module Data.HashMap.Array
3636
, unsafeThaw
3737
, unsafeSameArray
3838
, run
39-
, run2
4039
, copy
4140
, copyM
4241

@@ -59,6 +58,11 @@ import Control.Applicative (Applicative (..), (<$>))
5958
import Control.Applicative (liftA2)
6059
import Control.DeepSeq
6160
import GHC.Exts(Int(..), Int#, reallyUnsafePtrEquality#, tagToEnum#, unsafeCoerce#, State#)
61+
#if MIN_VERSION_base(4,10,0)
62+
import GHC.Exts (runRW#)
63+
#elif MIN_VERSION_base(4,9,0)
64+
import GHC.Base (runRW#)
65+
#endif
6266
import GHC.ST (ST(..))
6367
import Control.Monad.ST (stToIO)
6468

@@ -256,13 +260,17 @@ new_ :: Int -> ST s (MArray s a)
256260
new_ n = new n undefinedElem
257261

258262
singleton :: a -> Array a
259-
singleton x = runST (singletonM x)
263+
singleton x = run (singletonMut x)
260264
{-# INLINE singleton #-}
261265

262266
singletonM :: a -> ST s (Array a)
263267
singletonM x = new 1 x >>= unsafeFreeze
264268
{-# INLINE singletonM #-}
265269

270+
singletonMut :: a -> ST s (MArray s a)
271+
singletonMut x = new 1 x
272+
{-# INLINE singletonMut #-}
273+
266274
pair :: a -> a -> Array a
267275
pair x y = run $ do
268276
ary <- new 2 x
@@ -314,15 +322,19 @@ unsafeThaw ary
314322
{-# INLINE unsafeThaw #-}
315323

316324
run :: (forall s . ST s (MArray s e)) -> Array e
317-
run act = runST $ act >>= unsafeFreeze
325+
#if MIN_VERSION_base(4,9,0)
326+
-- GHC can't unbox across the runRW# boundary, so we apply the Array constructor
327+
-- on the outside.
328+
run (ST act) =
329+
case runRW# $ \s ->
330+
case act s of { (# s', MArray mary #) ->
331+
unsafeFreezeArray# mary s' } of
332+
(# _, ary #) -> Array ary
333+
#else
334+
run act = runST (act >>= unsafeFreeze)
335+
#endif
318336
{-# INLINE run #-}
319337

320-
run2 :: (forall s. ST s (MArray s e, a)) -> (Array e, a)
321-
run2 k = runST (do
322-
(marr,b) <- k
323-
arr <- unsafeFreeze marr
324-
return (arr,b))
325-
326338
-- | Unsafely copy the elements of an array. Array bounds are not checked.
327339
copy :: Array e -> Int -> MArray s e -> Int -> Int -> ST s ()
328340
copy !src !_sidx@(I# sidx#) !dst !_didx@(I# didx#) _n@(I# n#) =
@@ -357,34 +369,38 @@ trim mary n = cloneM mary 0 n >>= unsafeFreeze
357369
-- | /O(n)/ Insert an element at the given position in this array,
358370
-- increasing its size by one.
359371
insert :: Array e -> Int -> e -> Array e
360-
insert ary idx b = runST (insertM ary idx b)
372+
insert ary idx b = run (insertMut ary idx b)
361373
{-# INLINE insert #-}
362374

363375
-- | /O(n)/ Insert an element at the given position in this array,
364376
-- increasing its size by one.
365377
insertM :: Array e -> Int -> e -> ST s (Array e)
366-
insertM ary idx b =
378+
insertM ary idx b = insertMut ary idx b >>= unsafeFreeze
379+
{-# INLINE insertM #-}
380+
381+
insertMut :: Array e -> Int -> e -> ST s (MArray s e)
382+
insertMut ary idx b =
367383
CHECK_BOUNDS("insertM", count + 1, idx)
368384
do mary <- new_ (count+1)
369385
copy ary 0 mary 0 idx
370386
write mary idx b
371387
copy ary idx mary (idx+1) (count-idx)
372-
unsafeFreeze mary
388+
return mary
373389
where !count = length ary
374-
{-# INLINE insertM #-}
390+
{-# INLINE insertMut #-}
375391

376392
-- | /O(n)/ Update the element at the given position in this array.
377393
update :: Array e -> Int -> e -> Array e
378-
update ary idx b = runST (updateM ary idx b)
394+
update ary idx b = run (updateM ary idx b)
379395
{-# INLINE update #-}
380396

381397
-- | /O(n)/ Update the element at the given position in this array.
382-
updateM :: Array e -> Int -> e -> ST s (Array e)
398+
updateM :: Array e -> Int -> e -> ST s (MArray s e)
383399
updateM ary idx b =
384400
CHECK_BOUNDS("updateM", count, idx)
385401
do mary <- thaw ary 0 count
386402
write mary idx b
387-
unsafeFreeze mary
403+
return mary
388404
where !count = length ary
389405
{-# INLINE updateM #-}
390406

@@ -442,18 +458,18 @@ thaw !ary !_o@(I# o#) !n@(I# n#) =
442458
-- | /O(n)/ Delete an element at the given position in this array,
443459
-- decreasing its size by one.
444460
delete :: Array e -> Int -> Array e
445-
delete ary idx = runST (deleteM ary idx)
461+
delete ary idx = run (deleteM ary idx)
446462
{-# INLINE delete #-}
447463

448464
-- | /O(n)/ Delete an element at the given position in this array,
449465
-- decreasing its size by one.
450-
deleteM :: Array e -> Int -> ST s (Array e)
466+
deleteM :: Array e -> Int -> ST s (MArray s e)
451467
deleteM ary idx = do
452468
CHECK_BOUNDS("deleteM", count, idx)
453469
do mary <- new_ (count-1)
454470
copy ary 0 mary 0 idx
455471
copy ary (idx+1) mary idx (count-(idx+1))
456-
unsafeFreeze mary
472+
return mary
457473
where !count = length ary
458474
{-# INLINE deleteM #-}
459475

@@ -463,9 +479,10 @@ map f = \ ary ->
463479
in run $ do
464480
mary <- new_ n
465481
go ary mary 0 n
482+
return mary
466483
where
467484
go ary mary i n
468-
| i >= n = return mary
485+
| i >= n = return ()
469486
| otherwise = do
470487
x <- indexM ary i
471488
write mary i $ f x
@@ -479,9 +496,10 @@ map' f = \ ary ->
479496
in run $ do
480497
mary <- new_ n
481498
go ary mary 0 n
499+
return mary
482500
where
483501
go ary mary i n
484-
| i >= n = return mary
502+
| i >= n = return ()
485503
| otherwise = do
486504
x <- indexM ary i
487505
write mary i $! f x
@@ -494,8 +512,9 @@ fromList n xs0 =
494512
run $ do
495513
mary <- new_ n
496514
go xs0 mary 0
515+
return mary
497516
where
498-
go [] !mary !_ = return mary
517+
go [] !_ !_ = return ()
499518
go (x:xs) mary i = do write mary i x
500519
go xs mary (i+1)
501520

Data/HashMap/Base.hs

Lines changed: 10 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -90,7 +90,6 @@ module Data.HashMap.Base
9090
, two
9191
, unionArrayBy
9292
, update16
93-
, update16M
9493
, update16With'
9594
, updateOrConcatWith
9695
, updateOrConcatWithKey
@@ -653,7 +652,10 @@ collision h !e1 !e2 =
653652

654653
-- | Create a 'BitmapIndexed' or 'Full' node.
655654
bitmapIndexedOrFull :: Bitmap -> A.Array (HashMap k v) -> HashMap k v
656-
bitmapIndexedOrFull b ary
655+
-- I don't know if it ever matters in context (once inlined),
656+
-- but the Core for this function looks a lot nicer if we force
657+
-- the array argument manually. I don't know why that is.
658+
bitmapIndexedOrFull b !ary
657659
| b == fullNodeMask = Full ary
658660
| otherwise = BitmapIndexed b ary
659661
{-# INLINE bitmapIndexedOrFull #-}
@@ -1394,7 +1396,7 @@ unionWithKey f = go 0
13941396
-- | Strict in the result of @f@.
13951397
unionArrayBy :: (a -> a -> a) -> Bitmap -> Bitmap -> A.Array a -> A.Array a
13961398
-> A.Array a
1397-
unionArrayBy f b1 b2 ary1 ary2 = A.run $ do
1399+
unionArrayBy f !b1 !b2 !ary1 !ary2 = A.run $ do
13981400
let b' = b1 .|. b2
13991401
mary <- A.new_ (popCount b')
14001402
-- iterate over nonzero bits of b1 .|. b2
@@ -1836,16 +1838,16 @@ updateOrConcatWithKey f ary1 ary2 = A.run $ do
18361838

18371839
-- | /O(n)/ Update the element at the given position in this array.
18381840
update16 :: A.Array e -> Int -> e -> A.Array e
1839-
update16 ary idx b = runST (update16M ary idx b)
1841+
update16 ary idx b = A.run (update16Mut ary idx b)
18401842
{-# INLINE update16 #-}
18411843

18421844
-- | /O(n)/ Update the element at the given position in this array.
1843-
update16M :: A.Array e -> Int -> e -> ST s (A.Array e)
1844-
update16M ary idx b = do
1845+
update16Mut :: A.Array e -> Int -> e -> ST s (A.MArray s e)
1846+
update16Mut ary idx b = do
18451847
mary <- clone16 ary
18461848
A.write mary idx b
1847-
A.unsafeFreeze mary
1848-
{-# INLINE update16M #-}
1849+
return mary
1850+
{-# INLINE update16Mut #-}
18491851

18501852
-- | /O(n)/ Update the element at the given position in this array, by applying a function to it.
18511853
update16With' :: A.Array e -> Int -> (e -> e) -> A.Array e

unordered-containers.cabal

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -200,7 +200,7 @@ benchmark benchmarks
200200
base >= 4.8.0,
201201
bytestring,
202202
containers,
203-
criterion >= 1.0 && < 1.3,
203+
criterion >= 1.0,
204204
deepseq >= 1.1,
205205
deepseq-generics,
206206
hashable >= 1.0.1.1,

0 commit comments

Comments
 (0)