|
3 | 3 | {-# LANGUAGE DeriveLift #-}
|
4 | 4 | {-# LANGUAGE LambdaCase #-}
|
5 | 5 | {-# LANGUAGE MagicHash #-}
|
6 |
| -{-# LANGUAGE MultiWayIf #-} |
7 | 6 | {-# LANGUAGE PatternGuards #-}
|
8 | 7 | {-# LANGUAGE RoleAnnotations #-}
|
9 | 8 | {-# LANGUAGE ScopedTypeVariables #-}
|
@@ -144,9 +143,8 @@ import Control.Applicative (Const (..))
|
144 | 143 | import Control.DeepSeq (NFData (..), NFData1 (..), NFData2 (..))
|
145 | 144 | import Control.Monad.ST (ST, runST)
|
146 | 145 | 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) |
150 | 148 | import Data.Coerce (coerce)
|
151 | 149 | import Data.Data (Constr, Data (..), DataType)
|
152 | 150 | import Data.Functor.Classes (Eq1 (..), Eq2 (..), Ord1 (..), Ord2 (..),
|
@@ -1627,24 +1625,26 @@ unionArrayBy f !b1 !b2 !ary1 !ary2 = A.run $ do
|
1627 | 1625 | let b' = b1 .|. b2
|
1628 | 1626 | mary <- A.new_ (popCount b')
|
1629 | 1627 | -- 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' |
1648 | 1648 | return mary
|
1649 | 1649 | -- TODO: For the case where b1 .&. b2 == b1, i.e. when one is a
|
1650 | 1650 | -- subset of the other, we could use a slightly simpler algorithm,
|
|
0 commit comments