Skip to content

Commit eedc326

Browse files
committed
Avoid range checks due to bit, clearBit, testBit
…and bring back array indices.
1 parent b00fbd7 commit eedc326

File tree

1 file changed

+22
-22
lines changed

1 file changed

+22
-22
lines changed

Data/HashMap/Internal.hs

Lines changed: 22 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,6 @@
33
{-# LANGUAGE DeriveLift #-}
44
{-# LANGUAGE LambdaCase #-}
55
{-# LANGUAGE MagicHash #-}
6-
{-# LANGUAGE MultiWayIf #-}
76
{-# LANGUAGE PatternGuards #-}
87
{-# LANGUAGE RoleAnnotations #-}
98
{-# LANGUAGE ScopedTypeVariables #-}
@@ -144,9 +143,8 @@ import Control.Applicative (Const (..))
144143
import Control.DeepSeq (NFData (..), NFData1 (..), NFData2 (..))
145144
import Control.Monad.ST (ST, runST)
146145
import Data.Bifoldable (Bifoldable (..))
147-
import Data.Bits (bit, clearBit, complement,
148-
countTrailingZeros, popCount, testBit,
149-
unsafeShiftL, unsafeShiftR, (.&.), (.|.))
146+
import Data.Bits (complement, popCount, unsafeShiftL,
147+
unsafeShiftR, (.&.), (.|.), countTrailingZeros)
150148
import Data.Coerce (coerce)
151149
import Data.Data (Constr, Data (..), DataType)
152150
import Data.Functor.Classes (Eq1 (..), Eq2 (..), Ord1 (..), Ord2 (..),
@@ -1627,24 +1625,26 @@ unionArrayBy f !b1 !b2 !ary1 !ary2 = A.run $ do
16271625
let b' = b1 .|. b2
16281626
mary <- A.new_ (popCount b')
16291627
-- iterate over nonzero bits of b1 .|. b2
1630-
let go !b
1631-
| b == 0 = return ()
1632-
| otherwise = do
1633-
let ba = b1 .&. b2
1634-
c = countTrailingZeros b
1635-
m = bit c
1636-
i = sparseIndex b' m
1637-
i1 = sparseIndex b1 m
1638-
i2 = sparseIndex b2 m
1639-
t <- if | testBit ba c -> do
1640-
x1 <- A.indexM ary1 i1
1641-
x2 <- A.indexM ary2 i2
1642-
return $! f x1 x2
1643-
| testBit b1 c -> A.indexM ary1 i1
1644-
| otherwise -> A.indexM ary2 i2
1645-
A.write mary i t
1646-
go (clearBit b c)
1647-
go b'
1628+
-- it would be nice if we could shift m by more than 1 each time
1629+
let ba = b1 .&. b2
1630+
go !i !i1 !i2 !b
1631+
| b == 0 = return ()
1632+
| testBit ba = do
1633+
x1 <- A.indexM ary1 i1
1634+
x2 <- A.indexM ary2 i2
1635+
A.write mary i $! f x1 x2
1636+
go (i+1) (i1+1) (i2+1) b''
1637+
| testBit b1 = do
1638+
A.write mary i =<< A.indexM ary1 i1
1639+
go (i+1) (i1+1) i2 b''
1640+
| otherwise = do
1641+
A.write mary i =<< A.indexM ary2 i2
1642+
go (i+1) i1 (i2+1) b''
1643+
where
1644+
m = 1 `unsafeShiftL` (countTrailingZeros b)
1645+
testBit x = x .&. m /= 0
1646+
b'' = b .&. complement m
1647+
go 0 0 0 b'
16481648
return mary
16491649
-- TODO: For the case where b1 .&. b2 == b1, i.e. when one is a
16501650
-- subset of the other, we could use a slightly simpler algorithm,

0 commit comments

Comments
 (0)