@@ -67,6 +67,7 @@ module Data.Array
67
67
, concatMap
68
68
, filter
69
69
, partition
70
+ , filterA
70
71
, filterM
71
72
, mapMaybe
72
73
, catMaybes
@@ -110,21 +111,18 @@ module Data.Array
110
111
) where
111
112
112
113
import Prelude
113
-
114
114
import Control.Alt ((<|>))
115
115
import Control.Alternative (class Alternative )
116
116
import Control.Lazy (class Lazy , defer )
117
117
import Control.Monad.Rec.Class (class MonadRec , Step (..), tailRecM2 )
118
-
119
118
import Data.Foldable (class Foldable , foldl , foldr )
120
119
import Data.Foldable (foldl , foldr , foldMap , fold , intercalate , elem , notElem , find , findMap , any , all ) as Exports
121
120
import Data.Maybe (Maybe (..), maybe , isJust , fromJust )
122
121
import Data.NonEmpty (NonEmpty , (:|))
123
122
import Data.Traversable (scanl , scanr ) as Exports
124
- import Data.Traversable (sequence )
123
+ import Data.Traversable (sequence , traverse )
125
124
import Data.Tuple (Tuple (..))
126
125
import Data.Unfoldable (class Unfoldable , unfoldr )
127
-
128
126
import Partial.Unsafe (unsafePartial )
129
127
130
128
-- | Convert an `Array` into an `Unfoldable` structure.
@@ -417,17 +415,20 @@ foreign import partition
417
415
-> Array a
418
416
-> { yes :: Array a , no :: Array a }
419
417
420
- -- | Filter where the predicate returns a monadic `Boolean`.
418
+ -- | Filter where the predicate returns a `Boolean` in some `Applicative `.
421
419
-- |
422
420
-- | ```purescript
423
- -- | powerSet :: forall a. [a] -> [[a]]
424
- -- | powerSet = filterM (const [true, false])
421
+ -- | powerSet :: forall a. Array a -> Array (Array a)
422
+ -- | powerSet = filterA (const [true, false])
425
423
-- | ```
424
+ filterA :: forall a f . Applicative f => (a -> f Boolean ) -> Array a -> f (Array a )
425
+ filterA p =
426
+ traverse (\x -> Tuple x <$> p x)
427
+ >>> map (mapMaybe (\(Tuple x b) -> if b then Just x else Nothing ))
428
+
429
+ -- | Deprecated alias for `filterA`.
426
430
filterM :: forall a m . Monad m => (a -> m Boolean ) -> Array a -> m (Array a )
427
- filterM p = uncons' (\_ -> pure [] ) \x xs -> do
428
- b <- p x
429
- xs' <- filterM p xs
430
- pure if b then x : xs' else xs'
431
+ filterM = filterA
431
432
432
433
-- | Apply a function to each element in an array, keeping only the results
433
434
-- | which contain a value, creating a new array.
0 commit comments