Skip to content

Commit 25d07e3

Browse files
committed
First draft of filterArray
1 parent 2ad7128 commit 25d07e3

File tree

3 files changed

+113
-2
lines changed

3 files changed

+113
-2
lines changed

Data/Primitive/Array.hs

Lines changed: 49 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
{-# LANGUAGE CPP, MagicHash, UnboxedTuples, DeriveDataTypeable, BangPatterns #-}
22
{-# LANGUAGE RankNTypes #-}
33
{-# LANGUAGE TypeFamilies #-}
4+
{-# LANGUAGE ScopedTypeVariables #-}
45

56
-- |
67
-- Module : Data.Primitive.Array
@@ -24,7 +25,8 @@ module Data.Primitive.Array (
2425
sizeofArray, sizeofMutableArray,
2526
fromListN, fromList,
2627
mapArray',
27-
traverseArrayP
28+
traverseArrayP,
29+
filterArray
2830
) where
2931

3032
import Control.Monad.Primitive
@@ -68,12 +70,14 @@ import GHC.Exts (runRW#)
6870
import GHC.Base (runRW#)
6971
#endif
7072

71-
import Text.ParserCombinators.ReadP
73+
import Text.ParserCombinators.ReadP (string, skipSpaces, readS_to_P, readP_to_S)
7274

7375
#if MIN_VERSION_base(4,9,0) || MIN_VERSION_transformers(0,4,0)
7476
import Data.Functor.Classes (Eq1(..),Ord1(..),Show1(..),Read1(..))
7577
#endif
7678

79+
import Data.Primitive.Internal.Bit
80+
7781
-- | Boxed arrays
7882
data Array a = Array
7983
{ array# :: Array# a }
@@ -591,6 +595,49 @@ arrayFromListN n l =
591595
arrayFromList :: [a] -> Array a
592596
arrayFromList l = arrayFromListN (length l) l
593597

598+
filterArray :: forall a. (a -> Bool) -> Array a -> Array a
599+
filterArray f arr = runArray $
600+
newBitArray s >>= check 0 0
601+
where
602+
s = sizeofArray arr
603+
check :: Int -> Int -> MutableBitArray s -> ST s (MutableArray s a)
604+
check i count ba
605+
| i /= s
606+
= do
607+
v <- indexArrayM arr i
608+
if f v
609+
then setBitArray ba i >> check (i + 1) (count + 1) ba
610+
else check (i + 1) count ba
611+
| otherwise
612+
= do
613+
mary <- newArray count (die "filterArray" "invalid")
614+
fill 0 0 ba mary
615+
616+
-- This performs a few bit operations and a conditional
617+
-- jump for every element of the original array. This is
618+
-- not so great if most element are filtered out. We should
619+
-- consider going word by word through the bit array and
620+
-- using countTrailingZeroes. We could even choose
621+
-- a different strategy for each word depending on its
622+
-- popCount.
623+
fill :: forall s. Int -> Int -> MutableBitArray s -> MutableArray s a -> ST s (MutableArray s a)
624+
fill !i0 !i'0 !ba !mary = go i0 i'0
625+
where
626+
go :: Int -> Int -> ST s (MutableArray s a)
627+
go i i'
628+
| i == s
629+
= return mary
630+
| otherwise
631+
= do
632+
b <- readBitArray ba i
633+
if b
634+
then do
635+
v <- indexArrayM arr i
636+
writeArray mary i' v
637+
go (i + 1) (i' + 1)
638+
else go (i + 1) i'
639+
640+
594641
#if MIN_VERSION_base(4,7,0)
595642
instance Exts.IsList (Array a) where
596643
type Item (Array a) = a

Data/Primitive/Internal/Bit.hs

Lines changed: 63 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,63 @@
1+
{-# LANGUAGE CPP #-}
2+
{-# LANGUAGE ScopedTypeVariables #-}
3+
module Data.Primitive.Internal.Bit
4+
(
5+
MutableBitArray
6+
, newBitArray
7+
, readBitArray
8+
, setBitArray
9+
) where
10+
11+
import Data.Primitive.ByteArray
12+
import Control.Monad.Primitive
13+
import Data.Bits
14+
15+
newtype MutableBitArray s = MBA (MutableByteArray s)
16+
17+
newBitArray :: PrimMonad m => Int -> m (MutableBitArray (PrimState m))
18+
newBitArray n = do
19+
let s = ((n + wordSize - 1) `unsafeShiftR` 3)
20+
mary <- newByteArray s
21+
fillByteArray mary 0 s 0
22+
return (MBA mary)
23+
24+
readBitArray :: PrimMonad m => MutableBitArray (PrimState m) -> Int -> m Bool
25+
readBitArray (MBA mry) i = do
26+
wd :: Word <- readByteArray mry (whichWord i)
27+
return $! (((wd `unsafeShiftR` whichBit i) .&. 1) == 1)
28+
29+
setBitArray :: PrimMonad m => MutableBitArray (PrimState m) -> Int -> m ()
30+
setBitArray (MBA mry) i = do
31+
let ww = whichWord i
32+
wd :: Word <- readByteArray mry ww
33+
let wd' = wd .|. (1 `unsafeShiftL` (whichBit i))
34+
writeByteArray mry ww wd'
35+
36+
wordSize :: Int
37+
wordSize = finiteBitSize (undefined :: Word)
38+
39+
ctlws :: Int
40+
ctlws
41+
| wordSize == 64 = 6
42+
| wordSize == 32 = 5
43+
| otherwise = countTrailingZeros wordSize
44+
45+
whichWord :: Int -> Int
46+
whichWord i = i `unsafeShiftR` ctlws
47+
48+
whichBit :: Int -> Int
49+
whichBit i = i .&. (wordSize - 1)
50+
51+
{-
52+
-- For debugging
53+
freezeByteArray
54+
:: PrimMonad m => MutableByteArray (PrimState m) -> m ByteArray
55+
freezeByteArray mary = do
56+
s <- getSizeofMutableByteArray mary
57+
cop <- newByteArray s
58+
copyMutableByteArray cop 0 mary 0 s
59+
unsafeFreezeByteArray cop
60+
61+
prant :: MutableBitArray RealWorld -> IO ()
62+
prant (MBA x) = freezeByteArray x >>= print
63+
-}

primitive.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -49,6 +49,7 @@ Library
4949
Data.Primitive.MutVar
5050

5151
Other-Modules:
52+
Data.Primitive.Internal.Bit
5253
Data.Primitive.Internal.Compat
5354
Data.Primitive.Internal.Operations
5455

0 commit comments

Comments
 (0)