Skip to content

Commit 19674b5

Browse files
authored
Improve name of fullNodeMask -> fullBitmap (#431)
It's not a mask!
1 parent 2de3be2 commit 19674b5

File tree

2 files changed

+21
-23
lines changed

2 files changed

+21
-23
lines changed

Data/HashMap/Internal.hs

+17-19
Original file line numberDiff line numberDiff line change
@@ -117,7 +117,7 @@ module Data.HashMap.Internal
117117
, mask
118118
, index
119119
, bitsPerSubkey
120-
, fullNodeMask
120+
, fullBitmap
121121
, sparseIndex
122122
, two
123123
, unionArrayBy
@@ -315,7 +315,7 @@ hashMapDataType = Data.mkDataType "Data.HashMap.Internal.HashMap" [fromListConst
315315
-- | This type is used to store the hash of a key, as produced with 'hash'.
316316
type Hash = Word
317317

318-
-- | A bitmap as contained by a 'BitmapIndexed' node, or a 'fullNodeMask'
318+
-- | A bitmap as contained by a 'BitmapIndexed' node, or a 'fullBitmap'
319319
-- corresponding to a 'Full' node.
320320
--
321321
-- Only the lower 'maxChildren' bits are used. The remaining bits must be zeros.
@@ -758,7 +758,7 @@ bitmapIndexedOrFull :: Bitmap -> A.Array (HashMap k v) -> HashMap k v
758758
-- @unionWith[Key]@ with GHC 9.2.2. See the Core diffs in
759759
-- https://github.com/haskell-unordered-containers/unordered-containers/pull/376.
760760
bitmapIndexedOrFull b !ary
761-
| b == fullNodeMask = Full ary
761+
| b == fullBitmap = Full ary
762762
| otherwise = BitmapIndexed b ary
763763
{-# INLINE bitmapIndexedOrFull #-}
764764

@@ -1110,7 +1110,7 @@ delete' h0 k0 m0 = go h0 k0 0 m0
11101110
else case st' of
11111111
Empty ->
11121112
let ary' = A.delete ary i
1113-
bm = fullNodeMask .&. complement (1 `unsafeShiftL` i)
1113+
bm = fullBitmap .&. complement (1 `unsafeShiftL` i)
11141114
in BitmapIndexed bm ary'
11151115
_ -> Full (A.update ary i st')
11161116
where i = index h s
@@ -1162,7 +1162,7 @@ deleteKeyExists !collPos0 !h0 !k0 !m0 = go collPos0 h0 k0 0 m0
11621162
in case st' of
11631163
Empty ->
11641164
let ary' = A.delete ary i
1165-
bm = fullNodeMask .&. complement (1 `unsafeShiftL` i)
1165+
bm = fullBitmap .&. complement (1 `unsafeShiftL` i)
11661166
in BitmapIndexed bm ary'
11671167
_ -> Full (A.update ary i st')
11681168
where i = index h s
@@ -1471,9 +1471,9 @@ isSubmapOfBy comp !m1 !m2 = go 0 m1 m2
14711471
go s (BitmapIndexed b1 ls1) (BitmapIndexed b2 ls2) =
14721472
submapBitmapIndexed (go (s+bitsPerSubkey)) b1 ls1 b2 ls2
14731473
go s (BitmapIndexed b1 ls1) (Full ls2) =
1474-
submapBitmapIndexed (go (s+bitsPerSubkey)) b1 ls1 fullNodeMask ls2
1474+
submapBitmapIndexed (go (s+bitsPerSubkey)) b1 ls1 fullBitmap ls2
14751475
go s (Full ls1) (Full ls2) =
1476-
submapBitmapIndexed (go (s+bitsPerSubkey)) fullNodeMask ls1 fullNodeMask ls2
1476+
submapBitmapIndexed (go (s+bitsPerSubkey)) fullBitmap ls1 fullBitmap ls2
14771477

14781478
-- Collision and Full nodes always contain at least two entries. Hence it
14791479
-- cannot be a map of a leaf.
@@ -1562,13 +1562,13 @@ unionWithKey f = go 0
15621562
ary' = unionArrayBy (go (s+bitsPerSubkey)) b1 b2 ary1 ary2
15631563
in bitmapIndexedOrFull b' ary'
15641564
go s (BitmapIndexed b1 ary1) (Full ary2) =
1565-
let ary' = unionArrayBy (go (s+bitsPerSubkey)) b1 fullNodeMask ary1 ary2
1565+
let ary' = unionArrayBy (go (s+bitsPerSubkey)) b1 fullBitmap ary1 ary2
15661566
in Full ary'
15671567
go s (Full ary1) (BitmapIndexed b2 ary2) =
1568-
let ary' = unionArrayBy (go (s+bitsPerSubkey)) fullNodeMask b2 ary1 ary2
1568+
let ary' = unionArrayBy (go (s+bitsPerSubkey)) fullBitmap b2 ary1 ary2
15691569
in Full ary'
15701570
go s (Full ary1) (Full ary2) =
1571-
let ary' = unionArrayBy (go (s+bitsPerSubkey)) fullNodeMask fullNodeMask
1571+
let ary' = unionArrayBy (go (s+bitsPerSubkey)) fullBitmap fullBitmap
15721572
ary1 ary2
15731573
in Full ary'
15741574
-- leaf vs. branch
@@ -1814,11 +1814,11 @@ intersectionWithKey# f = go 0
18141814
go s (BitmapIndexed b1 ary1) (BitmapIndexed b2 ary2) =
18151815
intersectionArrayBy (go (s + bitsPerSubkey)) b1 b2 ary1 ary2
18161816
go s (BitmapIndexed b1 ary1) (Full ary2) =
1817-
intersectionArrayBy (go (s + bitsPerSubkey)) b1 fullNodeMask ary1 ary2
1817+
intersectionArrayBy (go (s + bitsPerSubkey)) b1 fullBitmap ary1 ary2
18181818
go s (Full ary1) (BitmapIndexed b2 ary2) =
1819-
intersectionArrayBy (go (s + bitsPerSubkey)) fullNodeMask b2 ary1 ary2
1819+
intersectionArrayBy (go (s + bitsPerSubkey)) fullBitmap b2 ary1 ary2
18201820
go s (Full ary1) (Full ary2) =
1821-
intersectionArrayBy (go (s + bitsPerSubkey)) fullNodeMask fullNodeMask ary1 ary2
1821+
intersectionArrayBy (go (s + bitsPerSubkey)) fullBitmap fullBitmap ary1 ary2
18221822
-- collision vs. branch
18231823
go s (BitmapIndexed b1 ary1) t2@(Collision h2 _ls2)
18241824
| b1 .&. m2 == 0 = Empty
@@ -2081,7 +2081,7 @@ filterMapAux onLeaf onColl = go
20812081
| Just t' <- onLeaf t = t'
20822082
| otherwise = Empty
20832083
go (BitmapIndexed b ary) = filterA ary b
2084-
go (Full ary) = filterA ary fullNodeMask
2084+
go (Full ary) = filterA ary fullBitmap
20852085
go (Collision h ary) = filterC ary h
20862086

20872087
filterA ary0 b0 =
@@ -2427,15 +2427,13 @@ sparseIndex
24272427
sparseIndex b m = popCount (b .&. (m - 1))
24282428
{-# INLINE sparseIndex #-}
24292429

2430-
-- TODO: Should be named _(bit)map_ instead of _mask_
2431-
24322430
-- | A bitmap with the 'maxChildren' least significant bits set, i.e.
24332431
-- @0xFF_FF_FF_FF@.
2434-
fullNodeMask :: Bitmap
2432+
fullBitmap :: Bitmap
24352433
-- This needs to use 'shiftL' instead of 'unsafeShiftL', to avoid UB.
24362434
-- See issue #412.
2437-
fullNodeMask = complement (complement 0 `shiftL` maxChildren)
2438-
{-# INLINE fullNodeMask #-}
2435+
fullBitmap = complement (complement 0 `shiftL` maxChildren)
2436+
{-# INLINE fullBitmap #-}
24392437

24402438
------------------------------------------------------------------------
24412439
-- Pointer equality

Data/HashMap/Internal/Strict.hs

+4-4
Original file line numberDiff line numberDiff line change
@@ -130,7 +130,7 @@ import Data.Functor.Identity (Identity (..))
130130
-- See Note [Imports from Data.HashMap.Internal]
131131
import Data.Hashable (Hashable)
132132
import Data.HashMap.Internal (Hash, HashMap (..), Leaf (..), LookupRes (..),
133-
bitsPerSubkey, fullNodeMask, hash, index, mask,
133+
bitsPerSubkey, fullBitmap, hash, index, mask,
134134
ptrEq, sparseIndex)
135135
import Prelude hiding (lookup, map)
136136

@@ -474,13 +474,13 @@ unionWithKey f = go 0
474474
ary' = HM.unionArrayBy (go (s+bitsPerSubkey)) b1 b2 ary1 ary2
475475
in HM.bitmapIndexedOrFull b' ary'
476476
go s (BitmapIndexed b1 ary1) (Full ary2) =
477-
let ary' = HM.unionArrayBy (go (s+bitsPerSubkey)) b1 fullNodeMask ary1 ary2
477+
let ary' = HM.unionArrayBy (go (s+bitsPerSubkey)) b1 fullBitmap ary1 ary2
478478
in Full ary'
479479
go s (Full ary1) (BitmapIndexed b2 ary2) =
480-
let ary' = HM.unionArrayBy (go (s+bitsPerSubkey)) fullNodeMask b2 ary1 ary2
480+
let ary' = HM.unionArrayBy (go (s+bitsPerSubkey)) fullBitmap b2 ary1 ary2
481481
in Full ary'
482482
go s (Full ary1) (Full ary2) =
483-
let ary' = HM.unionArrayBy (go (s+bitsPerSubkey)) fullNodeMask fullNodeMask
483+
let ary' = HM.unionArrayBy (go (s+bitsPerSubkey)) fullBitmap fullBitmap
484484
ary1 ary2
485485
in Full ary'
486486
-- leaf vs. branch

0 commit comments

Comments
 (0)