Skip to content

Commit 0cf1ae4

Browse files
authored
Merge pull request #74 from chadaustin/master
add mapMaybe and imapMaybe
2 parents ec03656 + 23d6ffd commit 0cf1ae4

File tree

8 files changed

+94
-6
lines changed

8 files changed

+94
-6
lines changed

Data/Vector.hs

Lines changed: 13 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -112,7 +112,9 @@ module Data.Vector (
112112
-- * Working with predicates
113113

114114
-- ** Filtering
115-
filter, ifilter, filterM,
115+
filter, ifilter,
116+
mapMaybe, imapMaybe,
117+
filterM,
116118
takeWhile, dropWhile,
117119

118120
-- ** Partitioning
@@ -1097,6 +1099,16 @@ ifilter :: (Int -> a -> Bool) -> Vector a -> Vector a
10971099
{-# INLINE ifilter #-}
10981100
ifilter = G.ifilter
10991101

1102+
-- | /O(n)/ Drop elements when predicate returns Nothing
1103+
mapMaybe :: (a -> Maybe b) -> Vector a -> Vector b
1104+
{-# INLINE mapMaybe #-}
1105+
mapMaybe = G.mapMaybe
1106+
1107+
-- | /O(n)/ Drop elements when predicate, applied to index and value, returns Nothing
1108+
imapMaybe :: (Int -> a -> Maybe b) -> Vector a -> Vector b
1109+
{-# INLINE imapMaybe #-}
1110+
imapMaybe = G.imapMaybe
1111+
11001112
-- | /O(n)/ Drop elements that do not satisfy the monadic predicate
11011113
filterM :: Monad m => (a -> m Bool) -> Vector a -> m (Vector a)
11021114
{-# INLINE filterM #-}

Data/Vector/Fusion/Stream/Monadic.hs

Lines changed: 16 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -40,7 +40,7 @@ module Data.Vector.Fusion.Stream.Monadic (
4040
eq, cmp,
4141

4242
-- * Filtering
43-
filter, filterM, takeWhile, takeWhileM, dropWhile, dropWhileM,
43+
filter, filterM, mapMaybe, takeWhile, takeWhileM, dropWhile, dropWhileM,
4444

4545
-- * Searching
4646
elem, notElem, find, findM, findIndex, findIndexM,
@@ -688,6 +688,21 @@ filter :: Monad m => (a -> Bool) -> Stream m a -> Stream m a
688688
{-# INLINE filter #-}
689689
filter f = filterM (return . f)
690690

691+
mapMaybe :: Monad m => (a -> Maybe b) -> Stream m a -> Stream m b
692+
{-# INLINE_FUSED mapMaybe #-}
693+
mapMaybe f (Stream step t) = Stream step' t
694+
where
695+
{-# INLINE_INNER step' #-}
696+
step' s = do
697+
r <- step s
698+
case r of
699+
Yield x s' -> do
700+
return $ case f x of
701+
Nothing -> Skip s'
702+
Just b' -> Yield b' s'
703+
Skip s' -> return $ Skip s'
704+
Done -> return $ Done
705+
691706
-- | Drop elements which do not satisfy the monadic predicate
692707
filterM :: Monad m => (a -> m Bool) -> Stream m a -> Stream m a
693708
{-# INLINE_FUSED filterM #-}

Data/Vector/Generic.hs

Lines changed: 16 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -95,7 +95,9 @@ module Data.Vector.Generic (
9595
-- * Working with predicates
9696

9797
-- ** Filtering
98-
filter, ifilter, filterM,
98+
filter, ifilter,
99+
mapMaybe, imapMaybe,
100+
filterM,
99101
takeWhile, dropWhile,
100102

101103
-- ** Partitioning
@@ -1287,6 +1289,19 @@ ifilter f = unstream
12871289
. inplace (S.map snd . S.filter (uncurry f) . S.indexed) toMax
12881290
. stream
12891291

1292+
-- | /O(n)/ Drop elements when predicate returns Nothing
1293+
mapMaybe :: (Vector v a, Vector v b) => (a -> Maybe b) -> v a -> v b
1294+
{-# INLINE mapMaybe #-}
1295+
mapMaybe f = unstream . inplace (S.mapMaybe f) toMax . stream
1296+
1297+
-- | /O(n)/ Drop elements when predicate, applied to index and value, returns Nothing
1298+
imapMaybe :: (Vector v a, Vector v b) => (Int -> a -> Maybe b) -> v a -> v b
1299+
{-# INLINE imapMaybe #-}
1300+
imapMaybe f = unstream
1301+
. inplace (S.mapMaybe (uncurry f) . S.indexed) toMax
1302+
. stream
1303+
1304+
12901305
-- | /O(n)/ Drop elements that do not satisfy the monadic predicate
12911306
filterM :: (Monad m, Vector v a) => (a -> m Bool) -> v a -> m (v a)
12921307
{-# INLINE filterM #-}

Data/Vector/Primitive.hs

Lines changed: 13 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -91,7 +91,9 @@ module Data.Vector.Primitive (
9191
-- * Working with predicates
9292

9393
-- ** Filtering
94-
filter, ifilter, filterM,
94+
filter, ifilter,
95+
mapMaybe, imapMaybe,
96+
filterM,
9597
takeWhile, dropWhile,
9698

9799
-- ** Partitioning
@@ -903,6 +905,16 @@ ifilter :: Prim a => (Int -> a -> Bool) -> Vector a -> Vector a
903905
{-# INLINE ifilter #-}
904906
ifilter = G.ifilter
905907

908+
-- | /O(n)/ Drop elements when predicate returns Nothing
909+
mapMaybe :: (Prim a, Prim b) => (a -> Maybe b) -> Vector a -> Vector b
910+
{-# INLINE mapMaybe #-}
911+
mapMaybe = G.mapMaybe
912+
913+
-- | /O(n)/ Drop elements when predicate, applied to index and value, returns Nothing
914+
imapMaybe :: (Prim a, Prim b) => (Int -> a -> Maybe b) -> Vector a -> Vector b
915+
{-# INLINE imapMaybe #-}
916+
imapMaybe = G.imapMaybe
917+
906918
-- | /O(n)/ Drop elements that do not satisfy the monadic predicate
907919
filterM :: (Monad m, Prim a) => (a -> m Bool) -> Vector a -> m (Vector a)
908920
{-# INLINE filterM #-}

Data/Vector/Storable.hs

Lines changed: 13 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -88,7 +88,9 @@ module Data.Vector.Storable (
8888
-- * Working with predicates
8989

9090
-- ** Filtering
91-
filter, ifilter, filterM,
91+
filter, ifilter,
92+
mapMaybe, imapMaybe,
93+
filterM,
9294
takeWhile, dropWhile,
9395

9496
-- ** Partitioning
@@ -913,6 +915,16 @@ ifilter :: Storable a => (Int -> a -> Bool) -> Vector a -> Vector a
913915
{-# INLINE ifilter #-}
914916
ifilter = G.ifilter
915917

918+
-- | /O(n)/ Drop elements when predicate returns Nothing
919+
mapMaybe :: (Storable a, Storable b) => (a -> Maybe b) -> Vector a -> Vector b
920+
{-# INLINE mapMaybe #-}
921+
mapMaybe = G.mapMaybe
922+
923+
-- | /O(n)/ Drop elements when predicate, applied to index and value, returns Nothing
924+
imapMaybe :: (Storable a, Storable b) => (Int -> a -> Maybe b) -> Vector a -> Vector b
925+
{-# INLINE imapMaybe #-}
926+
imapMaybe = G.imapMaybe
927+
916928
-- | /O(n)/ Drop elements that do not satisfy the monadic predicate
917929
filterM :: (Monad m, Storable a) => (a -> m Bool) -> Vector a -> m (Vector a)
918930
{-# INLINE filterM #-}

Data/Vector/Unboxed.hs

Lines changed: 13 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -118,7 +118,9 @@ module Data.Vector.Unboxed (
118118
-- * Working with predicates
119119

120120
-- ** Filtering
121-
filter, ifilter, filterM,
121+
filter, ifilter,
122+
mapMaybe, imapMaybe,
123+
filterM,
122124
takeWhile, dropWhile,
123125

124126
-- ** Partitioning
@@ -960,6 +962,16 @@ ifilter :: Unbox a => (Int -> a -> Bool) -> Vector a -> Vector a
960962
{-# INLINE ifilter #-}
961963
ifilter = G.ifilter
962964

965+
-- | /O(n)/ Drop elements when predicate returns Nothing
966+
mapMaybe :: (Unbox a, Unbox b) => (a -> Maybe b) -> Vector a -> Vector b
967+
{-# INLINE mapMaybe #-}
968+
mapMaybe = G.mapMaybe
969+
970+
-- | /O(n)/ Drop elements when predicate, applied to index and value, returns Nothing
971+
imapMaybe :: (Unbox a, Unbox b) => (Int -> a -> Maybe b) -> Vector a -> Vector b
972+
{-# INLINE imapMaybe #-}
973+
imapMaybe = G.imapMaybe
974+
963975
-- | /O(n)/ Drop elements that do not satisfy the monadic predicate
964976
filterM :: (Monad m, Unbox a) => (a -> m Bool) -> Vector a -> m (Vector a)
965977
{-# INLINE filterM #-}

tests/Tests/Vector.hs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -160,6 +160,7 @@ testPolymorphicFunctions _ = $(testProperties [
160160

161161
-- Filtering
162162
'prop_filter, 'prop_ifilter, {- prop_filterM, -}
163+
'prop_mapMaybe, 'prop_imapMaybe,
163164
'prop_takeWhile, 'prop_dropWhile,
164165

165166
-- Paritioning
@@ -298,6 +299,8 @@ testPolymorphicFunctions _ = $(testProperties [
298299

299300
prop_filter :: P ((a -> Bool) -> v a -> v a) = V.filter `eq` filter
300301
prop_ifilter :: P ((Int -> a -> Bool) -> v a -> v a) = V.ifilter `eq` ifilter
302+
prop_mapMaybe :: P ((a -> Maybe a) -> v a -> v a) = V.mapMaybe `eq` mapMaybe
303+
prop_imapMaybe :: P ((Int -> a -> Maybe a) -> v a -> v a) = V.imapMaybe `eq` imapMaybe
301304
prop_takeWhile :: P ((a -> Bool) -> v a -> v a) = V.takeWhile `eq` takeWhile
302305
prop_dropWhile :: P ((a -> Bool) -> v a -> v a) = V.dropWhile `eq` dropWhile
303306
prop_partition :: P ((a -> Bool) -> v a -> (v a, v a))

tests/Utilities.hs

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -16,6 +16,7 @@ import Data.Function (on)
1616
import Data.Functor.Identity
1717
import Data.List ( sortBy )
1818
import Data.Monoid
19+
import Data.Maybe (catMaybes)
1920

2021
instance Show a => Show (S.Bundle v a) where
2122
show s = "Data.Vector.Fusion.Bundle.fromList " ++ show (S.toList s)
@@ -292,6 +293,12 @@ izipWith3 = withIndexFirst zipWith3
292293
ifilter :: (Int -> a -> Bool) -> [a] -> [a]
293294
ifilter f = map snd . withIndexFirst filter f
294295

296+
mapMaybe :: (a -> Maybe b) -> [a] -> [b]
297+
mapMaybe f = catMaybes . map f
298+
299+
imapMaybe :: (Int -> a -> Maybe b) -> [a] -> [b]
300+
imapMaybe f = catMaybes . withIndexFirst map f
301+
295302
indexedLeftFold fld f z = fld (uncurry . f) z . zip [0..]
296303

297304
ifoldl :: (a -> Int -> a -> a) -> a -> [a] -> a

0 commit comments

Comments
 (0)