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
3032import Control.Monad.Primitive
@@ -68,12 +70,14 @@ import GHC.Exts (runRW#)
6870import 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)
7476import Data.Functor.Classes (Eq1 (.. ),Ord1 (.. ),Show1 (.. ),Read1 (.. ))
7577#endif
7678
79+ import Data.Primitive.Internal.Bit
80+
7781-- | Boxed arrays
7882data Array a = Array
7983 { array# :: Array# a }
@@ -591,6 +595,49 @@ arrayFromListN n l =
591595arrayFromList :: [a ] -> Array a
592596arrayFromList 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)
595642instance Exts. IsList (Array a ) where
596643 type Item (Array a ) = a
0 commit comments