Skip to content

Commit a780a8d

Browse files
committed
unionArrayBy: Find next 1-bits with countTrailingZeros
Closes #374.
1 parent f721b9d commit a780a8d

File tree

1 file changed

+22
-19
lines changed

1 file changed

+22
-19
lines changed

Data/HashMap/Internal.hs

+22-19
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@
33
{-# LANGUAGE DeriveLift #-}
44
{-# LANGUAGE LambdaCase #-}
55
{-# LANGUAGE MagicHash #-}
6+
{-# LANGUAGE MultiWayIf #-}
67
{-# LANGUAGE PatternGuards #-}
78
{-# LANGUAGE RoleAnnotations #-}
89
{-# LANGUAGE ScopedTypeVariables #-}
@@ -143,8 +144,9 @@ import Control.Applicative (Const (..))
143144
import Control.DeepSeq (NFData (..), NFData1 (..), NFData2 (..))
144145
import Control.Monad.ST (ST, runST)
145146
import Data.Bifoldable (Bifoldable (..))
146-
import Data.Bits (complement, popCount, unsafeShiftL,
147-
unsafeShiftR, (.&.), (.|.))
147+
import Data.Bits (bit, clearBit, complement,
148+
countTrailingZeros, popCount, testBit,
149+
unsafeShiftL, unsafeShiftR, (.&.), (.|.))
148150
import Data.Coerce (coerce)
149151
import Data.Data (Constr, Data (..), DataType)
150152
import Data.Functor.Classes (Eq1 (..), Eq2 (..), Ord1 (..), Ord2 (..),
@@ -1625,23 +1627,24 @@ unionArrayBy f !b1 !b2 !ary1 !ary2 = A.run $ do
16251627
let b' = b1 .|. b2
16261628
mary <- A.new_ (popCount b')
16271629
-- iterate over nonzero bits of b1 .|. b2
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 !m
1631-
| m > b' = return ()
1632-
| b' .&. m == 0 = go i i1 i2 (m `unsafeShiftL` 1)
1633-
| ba .&. m /= 0 = do
1634-
x1 <- A.indexM ary1 i1
1635-
x2 <- A.indexM ary2 i2
1636-
A.write mary i $! f x1 x2
1637-
go (i+1) (i1+1) (i2+1) (m `unsafeShiftL` 1)
1638-
| b1 .&. m /= 0 = do
1639-
A.write mary i =<< A.indexM ary1 i1
1640-
go (i+1) (i1+1) i2 (m `unsafeShiftL` 1)
1641-
| otherwise = do
1642-
A.write mary i =<< A.indexM ary2 i2
1643-
go (i+1) i1 (i2+1) (m `unsafeShiftL` 1)
1644-
go 0 0 0 (b' .&. negate b') -- XXX: b' must be non-zero
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'
16451648
return mary
16461649
-- TODO: For the case where b1 .&. b2 == b1, i.e. when one is a
16471650
-- subset of the other, we could use a slightly simpler algorithm,

0 commit comments

Comments
 (0)