Skip to content

Navigation Menu

Sign in
Appearance settings

Search code, repositories, users, issues, pull requests...

Provide feedback

We read every piece of feedback, and take your input very seriously.

Saved searches

Use saved searches to filter your results more quickly

Sign up
Appearance settings

Commit f687e48

Browse files
Improve some Int{Map,Set} bitwise ops (#1126)
* mask: Now creates the Prefix, skipping some unnecessary operations * branchMask: Shift the high bit right instead of the low bit left * branchPrefix: New function to directly create a Prefix instead of going via mask. The performance improvements appear to be too small to show up in benchmarks, but these changes also make the code nicer.
1 parent f602764 commit f687e48

File tree

3 files changed

+31
-34
lines changed

3 files changed

+31
-34
lines changed

‎containers/src/Data/IntMap/Internal.hs

Lines changed: 7 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -286,7 +286,6 @@ module Data.IntMap.Internal (
286286
-- * Utility
287287
, link
288288
, linkKey
289-
, linkWithMask
290289
, bin
291290
, binCheckLeft
292291
, binCheckRight
@@ -330,6 +329,7 @@ import Data.IntSet.Internal.IntTreeCommons
330329
, signBranch
331330
, mask
332331
, branchMask
332+
, branchPrefix
333333
, TreeTreeBranch(..)
334334
, treeTreeBranch
335335
, i2w
@@ -2180,8 +2180,7 @@ mergeA
21802180
| i2w k1 < i2w k2 = binA p t1 t2
21812181
| otherwise = binA p t2 t1
21822182
where
2183-
m = branchMask k1 k2
2184-
p = Prefix (mask k1 m .|. m)
2183+
p = branchPrefix k1 k2
21852184
{-# INLINE linkA #-}
21862185

21872186
-- A variant of 'bin' that ensures that effects for negative keys are executed
@@ -3461,7 +3460,7 @@ ascLinkTop :: Stack a -> Int -> IntMap a -> Int -> Stack a
34613460
ascLinkTop stk !rk r !rm = case stk of
34623461
Nada -> Push rm r stk
34633462
Push m l stk'
3464-
| i2w m < i2w rm -> let p = Prefix (mask rk m.|. m)
3463+
| i2w m < i2w rm -> let p = mask rk m
34653464
in ascLinkTop stk' rk (Bin p l r) rm
34663465
| otherwise -> Push rm r stk
34673466

@@ -3478,7 +3477,7 @@ ascLinkStack stk !rk r = case stk of
34783477
| signBranch p -> Bin p r l
34793478
| otherwise -> ascLinkStack stk' rk (Bin p l r)
34803479
where
3481-
p = Prefix (mask rk m.|. m)
3480+
p = mask rk m
34823481

34833482
{--------------------------------------------------------------------
34843483
Eq
@@ -3652,17 +3651,12 @@ linkKey k1 t1 p2 t2 = link k1 t1 (unPrefix p2) t2
36523651
-- maps must be different. @k1@ must share the prefix of @t1@ and @k2@ must
36533652
-- share the prefix of @t2@.
36543653
link :: Int -> IntMap a -> Int -> IntMap a -> IntMap a
3655-
link k1 t1 k2 t2 = linkWithMask (branchMask k1 k2) k1 t1 k2 t2
3656-
{-# INLINE link #-}
3657-
3658-
-- `linkWithMask` is useful when the `branchMask` has already been computed
3659-
linkWithMask :: Int -> Key -> IntMap a -> Key -> IntMap a -> IntMap a
3660-
linkWithMask m k1 t1 k2 t2
3654+
link k1 t1 k2 t2
36613655
| i2w k1 < i2w k2 = Bin p t1 t2
36623656
| otherwise = Bin p t2 t1
36633657
where
3664-
p = Prefix (mask k1 m .|. m)
3665-
{-# INLINE linkWithMask #-}
3658+
p = branchPrefix k1 k2
3659+
{-# INLINE link #-}
36663660

36673661
{--------------------------------------------------------------------
36683662
@bin@ assures that we never have empty trees within a tree.

‎containers/src/Data/IntSet/Internal.hs

Lines changed: 7 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -207,6 +207,7 @@ import Data.IntSet.Internal.IntTreeCommons
207207
, signBranch
208208
, mask
209209
, branchMask
210+
, branchPrefix
210211
, TreeTreeBranch(..)
211212
, treeTreeBranch
212213
, i2w
@@ -1355,8 +1356,7 @@ fromRange (lx,rx)
13551356
| lx > rx = empty
13561357
| lp == rp = Tip lp (bitmapOf rx `shiftLL` 1 - bitmapOf lx)
13571358
| otherwise =
1358-
let m = branchMask lx rx
1359-
p = Prefix (mask lx m .|. m)
1359+
let p = branchPrefix lx rx
13601360
in if signBranch p -- handle negative numbers
13611361
then Bin p (goR 0) (goL 0)
13621362
else Bin p (goL (unPrefix p)) (goR (unPrefix p))
@@ -1444,7 +1444,7 @@ ascLinkTop :: Stack -> Int -> IntSet -> Int -> Stack
14441444
ascLinkTop stk !rk r !rm = case stk of
14451445
Nada -> Push rm r stk
14461446
Push m l stk'
1447-
| i2w m < i2w rm -> let p = Prefix (mask rk m.|. m)
1447+
| i2w m < i2w rm -> let p = mask rk m
14481448
in ascLinkTop stk' rk (Bin p l r) rm
14491449
| otherwise -> Push rm r stk
14501450

@@ -1461,7 +1461,7 @@ ascLinkStack stk !rk r = case stk of
14611461
| signBranch p -> Bin p r l
14621462
| otherwise -> ascLinkStack stk' rk (Bin p l r)
14631463
where
1464-
p = Prefix (mask rk m.|. m)
1464+
p = mask rk m
14651465

14661466
{--------------------------------------------------------------------
14671467
Eq
@@ -1698,17 +1698,12 @@ linkKey k1 t1 p2 t2 = link k1 t1 (unPrefix p2) t2
16981698
-- sets must be different. @k1@ must share the prefix of @t1@ and @k2@ must
16991699
-- share the prefix of @t2@.
17001700
link :: Int -> IntSet -> Int -> IntSet -> IntSet
1701-
link k1 t1 k2 t2 = linkWithMask (branchMask k1 k2) k1 t1 k2 t2
1702-
{-# INLINE link #-}
1703-
1704-
-- `linkWithMask` is useful when the `branchMask` has already been computed
1705-
linkWithMask :: Int -> Key -> IntSet -> Key -> IntSet -> IntSet
1706-
linkWithMask m k1 t1 k2 t2
1701+
link k1 t1 k2 t2
17071702
| i2w k1 < i2w k2 = Bin p t1 t2
17081703
| otherwise = Bin p t2 t1
17091704
where
1710-
p = Prefix (mask k1 m .|. m)
1711-
{-# INLINE linkWithMask #-}
1705+
p = branchPrefix k1 k2
1706+
{-# INLINE link #-}
17121707

17131708
{--------------------------------------------------------------------
17141709
@bin@ assures that we never have empty trees within a tree.

‎containers/src/Data/IntSet/Internal/IntTreeCommons.hs

Lines changed: 17 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -35,12 +35,13 @@ module Data.IntSet.Internal.IntTreeCommons
3535
, treeTreeBranch
3636
, mask
3737
, branchMask
38+
, branchPrefix
3839
, i2w
3940
, Order(..)
4041
) where
4142

4243
import Data.Bits (Bits(..), countLeadingZeros)
43-
import Utils.Containers.Internal.BitUtil (wordSize)
44+
import Utils.Containers.Internal.BitUtil (iShiftRL)
4445

4546
#ifdef __GLASGOW_HASKELL__
4647
import Language.Haskell.TH.Syntax (Lift)
@@ -144,20 +145,27 @@ signBranch :: Prefix -> Bool
144145
signBranch p = unPrefix p == (minBound :: Int)
145146
{-# INLINE signBranch #-}
146147

147-
-- | The prefix of key @i@ up to (but not including) the switching
148-
-- bit @m@.
149-
mask :: Key -> Int -> Int
150-
mask i m = i .&. ((-m) `xor` m)
148+
-- | The prefix of @Int@ @i@ up to the switching bit @m@.
149+
mask :: Int -> Int -> Prefix
150+
mask i m = Prefix ((i .&. negate m) .|. m)
151151
{-# INLINE mask #-}
152152

153-
-- | The first switching bit where the two prefixes disagree.
153+
-- | The first switching bit where the two @Int@s disagree.
154154
--
155-
-- Precondition for defined behavior: p1 /= p2
155+
-- Precondition for defined behavior: i1 /= i2
156156
branchMask :: Int -> Int -> Int
157-
branchMask p1 p2 =
158-
unsafeShiftL 1 (wordSize - 1 - countLeadingZeros (p1 `xor` p2))
157+
branchMask i1 i2 = iShiftRL (minBound :: Int) (countLeadingZeros (i1 `xor` i2))
159158
{-# INLINE branchMask #-}
160159

160+
-- | The shared prefix of two @Int@s.
161+
--
162+
-- Precondition for defined behavior: i1 /= i2
163+
branchPrefix :: Int -> Int -> Prefix
164+
branchPrefix i1 i2 = Prefix ((i1 .|. i2) .&. m)
165+
where
166+
m = unsafeShiftR (minBound :: Int) (countLeadingZeros (i1 `xor` i2))
167+
{-# INLINE branchPrefix #-}
168+
161169
i2w :: Int -> Word
162170
i2w = fromIntegral
163171
{-# INLINE i2w #-}

0 commit comments

Comments
(0)

AltStyle によって変換されたページ (->オリジナル) /