@@ -215,22 +215,18 @@ data HashMap k v
215215 -- * Only the lower @maxChildren@ bits of the 'Bitmap' may be set. The
216216 -- remaining upper bits must be 0. (INV2)
217217 -- * The array of a 'BitmapIndexed' node stores at least 1 and at most
218- -- @ 'maxChildren' - 1@ sub-nodes. (INV3)
218+ -- 'maxChildren' sub-nodes. (INV3)
219219 -- * The number of sub-nodes is equal to the number of 1-bits in its
220220 -- 'Bitmap'. (INV4)
221221 -- * If a 'BitmapIndexed' node has only one sub-node, this sub-node must
222- -- be a 'BitmapIndexed' or a 'Full' node . (INV5)
222+ -- be a 'BitmapIndexed'. (INV5)
223223 | Leaf ! Hash ! (Leaf k v )
224224 -- ^ Invariants:
225225 --
226226 -- * The location of a 'Leaf' or 'Collision' node in the tree must be
227227 -- compatible with its 'Hash'. (INV6)
228228 -- (TODO: Document this properly (#425))
229229 -- * The 'Hash' of a 'Leaf' node must be the 'hash' of its key. (INV7)
230- | Full ! (A. Array (HashMap k v ))
231- -- ^ Invariants:
232- --
233- -- * The array of a 'Full' node stores exactly 'maxChildren' sub-nodes. (INV8)
234230 | Collision ! Hash ! (A. Array (Leaf k v ))
235231 -- ^ Invariants:
236232 --
@@ -252,7 +248,6 @@ instance (NFData k, NFData v) => NFData (HashMap k v) where
252248 rnf Empty = ()
253249 rnf (BitmapIndexed _ ary) = rnf ary
254250 rnf (Leaf _ l) = rnf l
255- rnf (Full ary) = rnf ary
256251 rnf (Collision _ ary) = rnf ary
257252
258253-- | @since 0.2.14.0
@@ -264,7 +259,6 @@ instance NFData2 HashMap where
264259 liftRnf2 _ _ Empty = ()
265260 liftRnf2 rnf1 rnf2 (BitmapIndexed _ ary) = liftRnf (liftRnf2 rnf1 rnf2) ary
266261 liftRnf2 rnf1 rnf2 (Leaf _ l) = liftRnf2 rnf1 rnf2 l
267- liftRnf2 rnf1 rnf2 (Full ary) = liftRnf (liftRnf2 rnf1 rnf2) ary
268262 liftRnf2 rnf1 rnf2 (Collision _ ary) = liftRnf (liftRnf2 rnf1 rnf2) ary
269263
270264instance Functor (HashMap k ) where
@@ -426,7 +420,6 @@ equal1 eq = go
426420 go (BitmapIndexed bm1 ary1) (BitmapIndexed bm2 ary2)
427421 = bm1 == bm2 && A. sameArray1 go ary1 ary2
428422 go (Leaf h1 l1) (Leaf h2 l2) = h1 == h2 && leafEq l1 l2
429- go (Full ary1) (Full ary2) = A. sameArray1 go ary1 ary2
430423 go (Collision h1 ary1) (Collision h2 ary2)
431424 = h1 == h2 && isPermutationBy leafEq (A. toList ary1) (A. toList ary2)
432425 go _ _ = False
@@ -514,7 +507,6 @@ equalKeys = go
514507 go (BitmapIndexed bm1 ary1) (BitmapIndexed bm2 ary2)
515508 = bm1 == bm2 && A. sameArray1 go ary1 ary2
516509 go (Leaf h1 l1) (Leaf h2 l2) = h1 == h2 && leafEq l1 l2
517- go (Full ary1) (Full ary2) = A. sameArray1 go ary1 ary2
518510 go (Collision h1 ary1) (Collision h2 ary2)
519511 = h1 == h2 && isPermutationBy leafEq (A. toList ary1) (A. toList ary2)
520512 go _ _ = False
@@ -557,7 +549,6 @@ instance (Hashable k, Hashable v) => Hashable (HashMap k v) where
557549 = s `H.hashWithSalt` h `H.hashWithSalt` v
558550 -- For collisions we hashmix hash value
559551 -- and then array of values' hashes sorted
560- go s (Full a) = A. foldl' go s a
561552 go s (Collision h a)
562553 = (s `H.hashWithSalt` h) `hashCollisionWithSalt` a
563554
@@ -574,7 +565,6 @@ instance (Hashable k, Hashable v) => Hashable (HashMap k v) where
574565-- | Helper to get 'Leaf's and 'Collision's as a list.
575566leavesAndCollisions :: HashMap k v -> [HashMap k v ] -> [HashMap k v ]
576567leavesAndCollisions (BitmapIndexed _ ary) a = A. foldr leavesAndCollisions a ary
577- leavesAndCollisions (Full ary) a = A. foldr leavesAndCollisions a ary
578568leavesAndCollisions l@ (Leaf _ _) a = l : a
579569leavesAndCollisions c@ (Collision _ _) a = c : a
580570leavesAndCollisions Empty a = a
@@ -611,7 +601,6 @@ size t = go t 0
611601 go Empty ! n = n
612602 go (Leaf _ _) n = n + 1
613603 go (BitmapIndexed _ ary) n = A. foldl' (flip go) n ary
614- go (Full ary) n = A. foldl' (flip go) n ary
615604 go (Collision _ ary) n = n + A. length ary
616605
617606-- | \(O(\log n)\) Return 'True' if the specified key is present in the
@@ -719,8 +708,6 @@ lookupCont absent present !h0 !k0 !s0 !m0 = go h0 k0 s0 m0
719708 | otherwise =
720709 go h k (nextShift s) (A. index v (sparseIndex b m))
721710 where m = mask h s
722- go h k s (Full v) =
723- go h k (nextShift s) (A. index v (index h s))
724711 go h k _ (Collision hx v)
725712 | h == hx = lookupInArrayCont absent present k v
726713 | otherwise = absent (# # )
@@ -786,8 +773,7 @@ bitmapIndexedOrFull :: Bitmap -> A.Array (HashMap k v) -> HashMap k v
786773-- @unionWith[Key]@ with GHC 9.2.2. See the Core diffs in
787774-- https://github.com/haskell-unordered-containers/unordered-containers/pull/376.
788775bitmapIndexedOrFull b ! ary
789- | b == fullBitmap = Full ary
790- | otherwise = BitmapIndexed b ary
776+ = BitmapIndexed b ary
791777{-# INLINE bitmapIndexedOrFull #-}
792778
793779-- | \(O(\log n)\) Associate the specified value with the specified
@@ -820,13 +806,6 @@ insert' h0 k0 v0 m0 = go h0 k0 v0 0 m0
820806 else BitmapIndexed b (A. update ary i st')
821807 where m = mask h s
822808 i = sparseIndex b m
823- go h k x s t@ (Full ary) =
824- let ! st = A. index ary i
825- ! st' = go h k x (nextShift s) st
826- in if st' `ptrEq` st
827- then t
828- else Full (updateFullArray ary i st')
829- where i = index h s
830809 go h k x s t@ (Collision hy v)
831810 | h == hy = Collision h (updateOrSnocWith (\ a _ -> (# a # )) k x v)
832811 | otherwise = go h k x s $ BitmapIndexed (mask hy s) (A. singleton t)
@@ -856,11 +835,6 @@ insertNewKey !h0 !k0 x0 !m0 = go h0 k0 x0 0 m0
856835 in BitmapIndexed b (A. update ary i st')
857836 where m = mask h s
858837 i = sparseIndex b m
859- go h k x s (Full ary) =
860- let ! st = A. index ary i
861- ! st' = go h k x (nextShift s) st
862- in Full (updateFullArray ary i st')
863- where i = index h s
864838 go h k x s t@ (Collision hy v)
865839 | h == hy = Collision h (A. snoc v (L k x))
866840 | otherwise =
@@ -885,11 +859,6 @@ insertKeyExists !collPos0 !h0 !k0 x0 !m0 = go collPos0 h0 k0 x0 m0
885859 in BitmapIndexed b (A. update ary i st')
886860 where m = maskSH shiftedHash
887861 i = sparseIndex b m
888- go collPos shiftedHash k x (Full ary) =
889- let ! st = A. index ary i
890- ! st' = go collPos (nextSH shiftedHash) k x st
891- in Full (updateFullArray ary i st')
892- where i = indexSH shiftedHash
893862 go collPos _shiftedHash k x (Collision h v)
894863 | collPos >= 0 = Collision h (setAtPosition collPos k x v)
895864 | otherwise = Empty -- error "Internal error: go {collPos negative}"
@@ -928,12 +897,6 @@ unsafeInsert k0 v0 m0 = runST (go h0 k0 v0 0 m0)
928897 return t
929898 where m = mask h s
930899 i = sparseIndex b m
931- go h k x s t@ (Full ary) = do
932- st <- A. indexM ary i
933- st' <- go h k x (nextShift s) st
934- A. unsafeUpdateM ary i st'
935- return t
936- where i = index h s
937900 go h k x s t@ (Collision hy v)
938901 | h == hy = return $! Collision h (updateOrSnocWith (\ a _ -> (# a # )) k x v)
939902 | otherwise = go h k x s $ BitmapIndexed (mask hy s) (A. singleton t)
@@ -1019,14 +982,6 @@ insertModifying x f k0 m0 = go h0 k0 0 m0
1019982 else BitmapIndexed b ary'
1020983 where m = mask h s
1021984 i = sparseIndex b m
1022- go h k s t@ (Full ary) =
1023- let ! st = A. index ary i
1024- ! st' = go h k (nextShift s) st
1025- ary' = updateFullArray ary i $! st'
1026- in if ptrEq st st'
1027- then t
1028- else Full ary'
1029- where i = index h s
1030985 go h k s t@ (Collision hy v)
1031986 | h == hy =
1032987 let ! v' = insertModifyingArr x f k v
@@ -1084,12 +1039,6 @@ unsafeInsertWithKey f k0 v0 m0 = runST (go h0 k0 v0 0 m0)
10841039 return t
10851040 where m = mask h s
10861041 i = sparseIndex b m
1087- go h k x s t@ (Full ary) = do
1088- st <- A. indexM ary i
1089- st' <- go h k x (nextShift s) st
1090- A. unsafeUpdateM ary i st'
1091- return t
1092- where i = index h s
10931042 go h k x s t@ (Collision hy v)
10941043 | h == hy = return $! Collision h (updateOrSnocWithKey f k x v)
10951044 | otherwise = go h k x s $ BitmapIndexed (mask hy s) (A. singleton t)
@@ -1129,18 +1078,6 @@ delete' h0 k0 m0 = go h0 k0 0 m0
11291078 _ -> BitmapIndexed b (A. update ary i st')
11301079 where m = mask h s
11311080 i = sparseIndex b m
1132- go h k s t@ (Full ary) =
1133- let ! st = A. index ary i
1134- ! st' = go h k (nextShift s) st
1135- in if st' `ptrEq` st
1136- then t
1137- else case st' of
1138- Empty ->
1139- let ary' = A. delete ary i
1140- bm = fullBitmap .&. complement (1 `unsafeShiftL` i)
1141- in BitmapIndexed bm ary'
1142- _ -> Full (A. update ary i st')
1143- where i = index h s
11441081 go h k _ t@ (Collision hy v)
11451082 | h == hy = case indexOf k v of
11461083 Just i
@@ -1180,16 +1117,6 @@ deleteKeyExists !collPos0 !h0 !k0 !m0 = go collPos0 h0 k0 m0
11801117 _ -> BitmapIndexed b (A. update ary i st')
11811118 where m = maskSH shiftedHash
11821119 i = sparseIndex b m
1183- go collPos shiftedHash k (Full ary) =
1184- let ! st = A. index ary i
1185- ! st' = go collPos (nextSH shiftedHash) k st
1186- in case st' of
1187- Empty ->
1188- let ary' = A. delete ary i
1189- bm = fullBitmap .&. complement (1 `unsafeShiftL` i)
1190- in BitmapIndexed bm ary'
1191- _ -> Full (A. update ary i st')
1192- where i = indexSH shiftedHash
11931120 go collPos _shiftedHash _k (Collision h v)
11941121 | A. length v == 2
11951122 = if collPos == 0
@@ -1233,14 +1160,6 @@ adjust# f k0 m0 = go h0 k0 0 m0
12331160 else BitmapIndexed b ary'
12341161 where m = mask h s
12351162 i = sparseIndex b m
1236- go h k s t@ (Full ary) =
1237- let i = index h s
1238- ! st = A. index ary i
1239- ! st' = go h k (nextShift s) st
1240- ary' = updateFullArray ary i $! st'
1241- in if ptrEq st st'
1242- then t
1243- else Full ary'
12441163 go h k _ t@ (Collision hy v)
12451164 | h == hy = let ! v' = updateWith# f k v
12461165 in if A. unsafeSameArray v v'
@@ -1492,27 +1411,16 @@ isSubmapOfBy comp !m1 !m2 = go 0 m1 m2
14921411 go (nextShift s) t1 (A. index ls2 (sparseIndex b m))
14931412 where m = mask h1 s
14941413
1495- -- Similar to the previous case we need to traverse l2 at the index for the hash h1.
1496- go s t1@ (Collision h1 _) (Full ls2) =
1497- go (nextShift s) t1 (A. index ls2 (index h1 s))
1498-
1499- -- In cases where the first and second map are BitmapIndexed or Full,
1414+ -- In cases where the first and second map are BitmapIndexed,
15001415 -- traverse down the tree at the appropriate indices.
15011416 go s (BitmapIndexed b1 ls1) (BitmapIndexed b2 ls2) =
15021417 submapBitmapIndexed (go (nextShift s)) b1 ls1 b2 ls2
1503- go s (BitmapIndexed b1 ls1) (Full ls2) =
1504- submapBitmapIndexed (go (nextShift s)) b1 ls1 fullBitmap ls2
1505- go s (Full ls1) (Full ls2) =
1506- submapBitmapIndexed (go (nextShift s)) fullBitmap ls1 fullBitmap ls2
15071418
15081419 -- Collision and Full nodes always contain at least two entries. Hence it
15091420 -- cannot be a map of a leaf.
15101421 go _ (Collision {}) (Leaf {}) = False
15111422 go _ (BitmapIndexed {}) (Leaf {}) = False
1512- go _ (Full {}) (Leaf {}) = False
15131423 go _ (BitmapIndexed {}) (Collision {}) = False
1514- go _ (Full {}) (Collision {}) = False
1515- go _ (Full {}) (BitmapIndexed {}) = False
15161424{-# INLINABLE isSubmapOfBy #-}
15171425
15181426-- | \(O(\min n m))\) Checks if a bitmap indexed node is a submap of another.
@@ -1594,16 +1502,6 @@ unionWithKey f = go 0
15941502 let b' = b1 .|. b2
15951503 ary' = unionArrayBy (go (nextShift s)) b1 b2 ary1 ary2
15961504 in bitmapIndexedOrFull b' ary'
1597- go s (BitmapIndexed b1 ary1) (Full ary2) =
1598- let ary' = unionArrayBy (go (nextShift s)) b1 fullBitmap ary1 ary2
1599- in Full ary'
1600- go s (Full ary1) (BitmapIndexed b2 ary2) =
1601- let ary' = unionArrayBy (go (nextShift s)) fullBitmap b2 ary1 ary2
1602- in Full ary'
1603- go s (Full ary1) (Full ary2) =
1604- let ary' = unionArrayBy (go (nextShift s)) fullBitmap fullBitmap
1605- ary1 ary2
1606- in Full ary'
16071505 -- leaf vs. branch
16081506 go s (BitmapIndexed b1 ary1) t2
16091507 | b1 .&. m2 == 0 = let ary' = A. insert ary1 i t2
@@ -1627,16 +1525,6 @@ unionWithKey f = go 0
16271525 h1 = leafHashCode t1
16281526 m1 = mask h1 s
16291527 i = sparseIndex b2 m1
1630- go s (Full ary1) t2 =
1631- let h2 = leafHashCode t2
1632- i = index h2 s
1633- ary' = updateFullArrayWith' ary1 i $ \ st1 -> go (nextShift s) st1 t2
1634- in Full ary'
1635- go s t1 (Full ary2) =
1636- let h1 = leafHashCode t1
1637- i = index h1 s
1638- ary' = updateFullArrayWith' ary2 i $ \ st2 -> go (nextShift s) t1 st2
1639- in Full ary'
16401528
16411529 leafHashCode (Leaf h _) = h
16421530 leafHashCode (Collision h _) = h
@@ -1724,7 +1612,6 @@ mapWithKey f = go
17241612 go Empty = Empty
17251613 go (Leaf h (L k v)) = Leaf h $ L k (f k v)
17261614 go (BitmapIndexed b ary) = BitmapIndexed b $ A. map go ary
1727- go (Full ary) = Full $ A. map go ary
17281615 -- Why map strictly over collision arrays? Because there's no
17291616 -- point suspending the O(1) work this does for each leaf.
17301617 go (Collision h ary) = Collision h $
@@ -1752,7 +1639,6 @@ traverseWithKey f = go
17521639 go Empty = pure Empty
17531640 go (Leaf h (L k v)) = Leaf h . L k <$> f k v
17541641 go (BitmapIndexed b ary) = BitmapIndexed b <$> A. traverse go ary
1755- go (Full ary) = Full <$> A. traverse go ary
17561642 go (Collision h ary) =
17571643 Collision h <$> A. traverse' (\ (L k v) -> L k <$> f k v) ary
17581644{-# INLINE traverseWithKey #-}
@@ -1842,12 +1728,6 @@ intersectionWithKey# f = go 0
18421728 -- branch vs. branch
18431729 go s (BitmapIndexed b1 ary1) (BitmapIndexed b2 ary2) =
18441730 intersectionArrayBy (go (nextShift s)) b1 b2 ary1 ary2
1845- go s (BitmapIndexed b1 ary1) (Full ary2) =
1846- intersectionArrayBy (go (nextShift s)) b1 fullBitmap ary1 ary2
1847- go s (Full ary1) (BitmapIndexed b2 ary2) =
1848- intersectionArrayBy (go (nextShift s)) fullBitmap b2 ary1 ary2
1849- go s (Full ary1) (Full ary2) =
1850- intersectionArrayBy (go (nextShift s)) fullBitmap fullBitmap ary1 ary2
18511731 -- collision vs. branch
18521732 go s (BitmapIndexed b1 ary1) t2@ (Collision h2 _ls2)
18531733 | b1 .&. m2 == 0 = Empty
@@ -1861,12 +1741,6 @@ intersectionWithKey# f = go 0
18611741 where
18621742 m1 = mask h1 s
18631743 i = sparseIndex b2 m1
1864- go s (Full ary1) t2@ (Collision h2 _ls2) = go (nextShift s) (A. index ary1 i) t2
1865- where
1866- i = index h2 s
1867- go s t1@ (Collision h1 _ls1) (Full ary2) = go (nextShift s) t1 (A. index ary2 i)
1868- where
1869- i = index h1 s
18701744{-# INLINE intersectionWithKey# #-}
18711745
18721746intersectionArrayBy ::
@@ -1994,7 +1868,6 @@ foldlWithKey' f = go
19941868 go ! z Empty = z
19951869 go z (Leaf _ (L k v)) = f z k v
19961870 go z (BitmapIndexed _ ary) = A. foldl' go z ary
1997- go z (Full ary) = A. foldl' go z ary
19981871 go z (Collision _ ary) = A. foldl' (\ z' (L k v) -> f z' k v) z ary
19991872{-# INLINE foldlWithKey' #-}
20001873
@@ -2009,7 +1882,6 @@ foldrWithKey' f = flip go
20091882 go Empty z = z
20101883 go (Leaf _ (L k v)) ! z = f k v z
20111884 go (BitmapIndexed _ ary) ! z = A. foldr' go z ary
2012- go (Full ary) ! z = A. foldr' go z ary
20131885 go (Collision _ ary) ! z = A. foldr' (\ (L k v) z' -> f k v z') z ary
20141886{-# INLINE foldrWithKey' #-}
20151887
@@ -2036,7 +1908,6 @@ foldrWithKey f = flip go
20361908 go Empty z = z
20371909 go (Leaf _ (L k v)) z = f k v z
20381910 go (BitmapIndexed _ ary) z = A. foldr go z ary
2039- go (Full ary) z = A. foldr go z ary
20401911 go (Collision _ ary) z = A. foldr (\ (L k v) z' -> f k v z') z ary
20411912{-# INLINE foldrWithKey #-}
20421913
@@ -2049,7 +1920,6 @@ foldlWithKey f = go
20491920 go z Empty = z
20501921 go z (Leaf _ (L k v)) = f z k v
20511922 go z (BitmapIndexed _ ary) = A. foldl go z ary
2052- go z (Full ary) = A. foldl go z ary
20531923 go z (Collision _ ary) = A. foldl (\ z' (L k v) -> f z' k v) z ary
20541924{-# INLINE foldlWithKey #-}
20551925
@@ -2061,7 +1931,6 @@ foldMapWithKey f = go
20611931 go Empty = mempty
20621932 go (Leaf _ (L k v)) = f k v
20631933 go (BitmapIndexed _ ary) = A. foldMap go ary
2064- go (Full ary) = A. foldMap go ary
20651934 go (Collision _ ary) = A. foldMap (\ (L k v) -> f k v) ary
20661935{-# INLINE foldMapWithKey #-}
20671936
@@ -2111,7 +1980,6 @@ filterMapAux onLeaf onColl = go
21111980 | Just t' <- onLeaf t = t'
21121981 | otherwise = Empty
21131982 go (BitmapIndexed b ary) = filterA ary b
2114- go (Full ary) = filterA ary fullBitmap
21151983 go (Collision h ary) = filterC ary h
21161984
21171985 filterA ary0 b0 =
@@ -2133,9 +2001,7 @@ filterMapAux onLeaf onColl = go
21332001 _ -> BitmapIndexed b <$> (A. unsafeFreeze =<< A. shrink mary 1 )
21342002 _ -> do
21352003 ary2 <- A. unsafeFreeze =<< A. shrink mary j
2136- return $! if j == maxChildren
2137- then Full ary2
2138- else BitmapIndexed b ary2
2004+ return $! BitmapIndexed b ary2
21392005 | bi .&. b == 0 = step ary mary b i j (bi `unsafeShiftL` 1 ) n
21402006 | otherwise = case go (A. index ary i) of
21412007 Empty -> step ary mary (b .&. complement bi) (i+ 1 ) j
0 commit comments