Skip to content

Commit

Permalink
Revert "unionArrayBy: Find next 1-bits with countTrailingZeros"
Browse files Browse the repository at this point in the history
This reverts commit a780a8d.
  • Loading branch information
sjakobi committed Mar 24, 2022
1 parent b00fbd7 commit e88d075
Showing 1 changed file with 19 additions and 22 deletions.
41 changes: 19 additions & 22 deletions Data/HashMap/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,6 @@
{-# LANGUAGE DeriveLift #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE RoleAnnotations #-}
{-# LANGUAGE ScopedTypeVariables #-}
Expand Down Expand Up @@ -144,9 +143,8 @@ import Control.Applicative (Const (..))
import Control.DeepSeq (NFData (..), NFData1 (..), NFData2 (..))
import Control.Monad.ST (ST, runST)
import Data.Bifoldable (Bifoldable (..))
import Data.Bits (bit, clearBit, complement,
countTrailingZeros, popCount, testBit,
unsafeShiftL, unsafeShiftR, (.&.), (.|.))
import Data.Bits (complement, popCount, unsafeShiftL,
unsafeShiftR, (.&.), (.|.))
import Data.Coerce (coerce)
import Data.Data (Constr, Data (..), DataType)
import Data.Functor.Classes (Eq1 (..), Eq2 (..), Ord1 (..), Ord2 (..),
Expand Down Expand Up @@ -1627,24 +1625,23 @@ unionArrayBy f !b1 !b2 !ary1 !ary2 = A.run $ do
let b' = b1 .|. b2
mary <- A.new_ (popCount b')
-- iterate over nonzero bits of b1 .|. b2
let go !b
| b == 0 = return ()
| otherwise = do
let ba = b1 .&. b2
c = countTrailingZeros b
m = bit c
i = sparseIndex b' m
i1 = sparseIndex b1 m
i2 = sparseIndex b2 m
t <- if | testBit ba c -> do
x1 <- A.indexM ary1 i1
x2 <- A.indexM ary2 i2
return $! f x1 x2
| testBit b1 c -> A.indexM ary1 i1
| otherwise -> A.indexM ary2 i2
A.write mary i t
go (clearBit b c)
go b'
-- it would be nice if we could shift m by more than 1 each time
let ba = b1 .&. b2
go !i !i1 !i2 !m
| m > b' = return ()
| b' .&. m == 0 = go i i1 i2 (m `unsafeShiftL` 1)
| ba .&. m /= 0 = do
x1 <- A.indexM ary1 i1
x2 <- A.indexM ary2 i2
A.write mary i $! f x1 x2
go (i+1) (i1+1) (i2+1) (m `unsafeShiftL` 1)
| b1 .&. m /= 0 = do
A.write mary i =<< A.indexM ary1 i1
go (i+1) (i1+1) i2 (m `unsafeShiftL` 1)
| otherwise = do
A.write mary i =<< A.indexM ary2 i2
go (i+1) i1 (i2+1) (m `unsafeShiftL` 1)
go 0 0 0 (b' .&. negate b') -- XXX: b' must be non-zero
return mary
-- TODO: For the case where b1 .&. b2 == b1, i.e. when one is a
-- subset of the other, we could use a slightly simpler algorithm,
Expand Down

0 comments on commit e88d075

Please sign in to comment.