Skip to content

Commit

Permalink
Add mapMaybeM and imapMaybeM
Browse files Browse the repository at this point in the history
Add

```haskell
mapMaybeM :: Monad m => (a -> m (Maybe b)) -> Vector a -> m (Vector b)
imapMaybeM :: Monad m => (Int -> a -> m (Maybe b)) -> Vector a -> m (Vector b)
```

`mapMaybeM` is similar to `wither`, but the stream fusion framework
seems to require that we use a `Monad` constraint rather than an
`Applicative` one to get good performance. `imapMaybeM` is the
indexed variant.

Resolves #183
  • Loading branch information
treeowl authored and lehins committed Jan 16, 2021
1 parent bccb37e commit 8318efd
Show file tree
Hide file tree
Showing 8 changed files with 81 additions and 6 deletions.
12 changes: 10 additions & 2 deletions Data/Vector.hs
Original file line number Diff line number Diff line change
Expand Up @@ -115,8 +115,8 @@ module Data.Vector (

-- ** Filtering
filter, ifilter, uniq,
mapMaybe, imapMaybe, catMaybes,
filterM,
mapMaybe, imapMaybe, imapMaybeM, catMaybes,
filterM, mapMaybeM,
takeWhile, dropWhile,

-- ** Partitioning
Expand Down Expand Up @@ -1321,6 +1321,14 @@ filterM :: Monad m => (a -> m Bool) -> Vector a -> m (Vector a)
{-# INLINE filterM #-}
filterM = G.filterM

mapMaybeM :: Monad m => (a -> m (Maybe b)) -> Vector a -> m (Vector b)
{-# INLINE mapMaybeM #-}
mapMaybeM = G.mapMaybeM

imapMaybeM :: Monad m => (Int -> a -> m (Maybe b)) -> Vector a -> m (Vector b)
{-# INLINE imapMaybeM #-}
imapMaybeM = G.imapMaybeM

-- | /O(n)/ Yield the longest prefix of elements satisfying the predicate
-- without copying.
takeWhile :: (a -> Bool) -> Vector a -> Vector a
Expand Down
6 changes: 5 additions & 1 deletion Data/Vector/Fusion/Bundle.hs
Original file line number Diff line number Diff line change
Expand Up @@ -71,7 +71,7 @@ module Data.Vector.Fusion.Bundle (
fromVector, reVector, fromVectors, concatVectors,

-- * Monadic combinators
mapM, mapM_, zipWithM, zipWithM_, filterM, foldM, fold1M, foldM', fold1M',
mapM, mapM_, zipWithM, zipWithM_, filterM, mapMaybeM, foldM, fold1M, foldM', fold1M',

eq, cmp, eqBy, cmpBy
) where
Expand Down Expand Up @@ -552,6 +552,10 @@ filterM :: Monad m => (a -> m Bool) -> Bundle v a -> M.Bundle m v a
{-# INLINE filterM #-}
filterM f = M.filterM f . lift

mapMaybeM :: Monad m => (a -> m (Maybe b)) -> Bundle v a -> M.Bundle m v b
{-# INLINE mapMaybeM #-}
mapMaybeM f = M.mapMaybeM f . lift

-- | Monadic fold
foldM :: Monad m => (a -> b -> m a) -> a -> Bundle v b -> m a
{-# INLINE foldM #-}
Expand Down
6 changes: 5 additions & 1 deletion Data/Vector/Fusion/Bundle/Monadic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ module Data.Vector.Fusion.Bundle.Monadic (
eqBy, cmpBy,

-- * Filtering
filter, filterM, takeWhile, takeWhileM, dropWhile, dropWhileM,
filter, filterM, mapMaybeM, takeWhile, takeWhileM, dropWhile, dropWhileM,

-- * Searching
elem, notElem, find, findM, findIndex, findIndexM,
Expand Down Expand Up @@ -464,6 +464,10 @@ filterM :: Monad m => (a -> m Bool) -> Bundle m v a -> Bundle m v a
{-# INLINE_FUSED filterM #-}
filterM f Bundle{sElems = s, sSize = n} = fromStream (S.filterM f s) (toMax n)

mapMaybeM :: Monad m => (a -> m (Maybe b)) -> Bundle m v a -> Bundle m v b
{-# INLINE_FUSED mapMaybeM #-}
mapMaybeM f Bundle{sElems = s, sSize = n} = fromStream (S.mapMaybeM f s) (toMax n)

-- | Longest prefix of elements that satisfy the predicate
takeWhile :: Monad m => (a -> Bool) -> Bundle m v a -> Bundle m v a
{-# INLINE takeWhile #-}
Expand Down
18 changes: 17 additions & 1 deletion Data/Vector/Fusion/Stream/Monadic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -40,7 +40,7 @@ module Data.Vector.Fusion.Stream.Monadic (
eqBy, cmpBy,

-- * Filtering
filter, filterM, uniq, mapMaybe, catMaybes, takeWhile, takeWhileM, dropWhile, dropWhileM,
filter, filterM, uniq, mapMaybe, mapMaybeM, catMaybes, takeWhile, takeWhileM, dropWhile, dropWhileM,

-- * Searching
elem, notElem, find, findM, findIndex, findIndexM,
Expand Down Expand Up @@ -718,6 +718,22 @@ filterM f (Stream step t) = Stream step' t
Skip s' -> return $ Skip s'
Done -> return $ Done

mapMaybeM :: Monad m => (a -> m (Maybe b)) -> Stream m a -> Stream m b
{-# INLINE_FUSED mapMaybeM #-}
mapMaybeM f (Stream step t) = Stream step' t
where
{-# INLINE_INNER step' #-}
step' s = do
r <- step s
case r of
Yield x s' -> do
fx <- f x
return $ case fx of
Nothing -> Skip s'
Just b -> Yield b s'
Skip s' -> return $ Skip s'
Done -> return $ Done

-- | Drop repeated adjacent elements.
uniq :: (Eq a, Monad m) => Stream m a -> Stream m a
{-# INLINE_FUSED uniq #-}
Expand Down
10 changes: 9 additions & 1 deletion Data/Vector/Generic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -99,7 +99,7 @@ module Data.Vector.Generic (
-- ** Filtering
filter, ifilter, uniq,
mapMaybe, imapMaybe,
filterM,
filterM, mapMaybeM, imapMaybeM,
takeWhile, dropWhile,

-- ** Partitioning
Expand Down Expand Up @@ -1392,6 +1392,14 @@ filterM :: (Monad m, Vector v a) => (a -> m Bool) -> v a -> m (v a)
{-# INLINE filterM #-}
filterM f = unstreamM . Bundle.filterM f . stream

mapMaybeM :: (Monad m, Vector v a, Vector v b) => (a -> m (Maybe b)) -> v a -> m (v b)
{-# INLINE mapMaybeM #-}
mapMaybeM f = unstreamM . Bundle.mapMaybeM f . stream

imapMaybeM :: (Monad m, Vector v a, Vector v b)
=> (Int -> a -> m (Maybe b)) -> v a -> m (v b)
imapMaybeM f = unstreamM . Bundle.mapMaybeM (\(i, a) -> f i a) . Bundle.indexed . stream

-- | /O(n)/ Yield the longest prefix of elements satisfying the predicate
-- without copying.
takeWhile :: Vector v a => (a -> Bool) -> v a -> v a
Expand Down
13 changes: 13 additions & 0 deletions Data/Vector/Primitive.hs
Original file line number Diff line number Diff line change
Expand Up @@ -96,6 +96,7 @@ module Data.Vector.Primitive (
-- ** Filtering
filter, ifilter, uniq,
mapMaybe, imapMaybe,
mapMaybeM, imapMaybeM,
filterM,
takeWhile, dropWhile,

Expand Down Expand Up @@ -1038,11 +1039,23 @@ mapMaybe :: (Prim a, Prim b) => (a -> Maybe b) -> Vector a -> Vector b
{-# INLINE mapMaybe #-}
mapMaybe = G.mapMaybe

mapMaybeM
:: (Monad m, Prim a, Prim b)
=> (a -> m (Maybe b)) -> Vector a -> m (Vector b)
{-# INLINE mapMaybeM #-}
mapMaybeM = G.mapMaybeM

-- | /O(n)/ Drop elements when predicate, applied to index and value, returns Nothing
imapMaybe :: (Prim a, Prim b) => (Int -> a -> Maybe b) -> Vector a -> Vector b
{-# INLINE imapMaybe #-}
imapMaybe = G.imapMaybe

imapMaybeM
:: (Monad m, Prim a, Prim b)
=> (Int -> a -> m (Maybe b)) -> Vector a -> m (Vector b)
{-# INLINE imapMaybeM #-}
imapMaybeM = G.imapMaybeM

-- | /O(n)/ Drop elements that do not satisfy the monadic predicate
filterM :: (Monad m, Prim a) => (a -> m Bool) -> Vector a -> m (Vector a)
{-# INLINE filterM #-}
Expand Down
13 changes: 13 additions & 0 deletions Data/Vector/Storable.hs
Original file line number Diff line number Diff line change
Expand Up @@ -93,6 +93,7 @@ module Data.Vector.Storable (
-- ** Filtering
filter, ifilter, uniq,
mapMaybe, imapMaybe,
mapMaybeM, imapMaybeM,
filterM,
takeWhile, dropWhile,

Expand Down Expand Up @@ -1055,6 +1056,18 @@ imapMaybe :: (Storable a, Storable b) => (Int -> a -> Maybe b) -> Vector a -> Ve
{-# INLINE imapMaybe #-}
imapMaybe = G.imapMaybe

mapMaybeM
:: (Monad m, Storable a, Storable b)
=> (a -> m (Maybe b)) -> Vector a -> m (Vector b)
{-# INLINE mapMaybeM #-}
mapMaybeM = G.mapMaybeM

imapMaybeM
:: (Monad m, Storable a, Storable b)
=> (Int -> a -> m (Maybe b)) -> Vector a -> m (Vector b)
{-# INLINE imapMaybeM #-}
imapMaybeM = G.imapMaybeM

-- | /O(n)/ Drop elements that do not satisfy the monadic predicate
filterM :: (Monad m, Storable a) => (a -> m Bool) -> Vector a -> m (Vector a)
{-# INLINE filterM #-}
Expand Down
9 changes: 9 additions & 0 deletions Data/Vector/Unboxed.hs
Original file line number Diff line number Diff line change
Expand Up @@ -122,6 +122,7 @@ module Data.Vector.Unboxed (
-- ** Filtering
filter, ifilter, uniq,
mapMaybe, imapMaybe,
mapMaybeM, imapMaybeM,
filterM,
takeWhile, dropWhile,

Expand Down Expand Up @@ -1052,6 +1053,14 @@ imapMaybe :: (Unbox a, Unbox b) => (Int -> a -> Maybe b) -> Vector a -> Vector b
{-# INLINE imapMaybe #-}
imapMaybe = G.imapMaybe

mapMaybeM :: (Monad m, Unbox a, Unbox b) => (a -> m (Maybe b)) -> Vector a -> m (Vector b)
{-# INLINE mapMaybeM #-}
mapMaybeM = G.mapMaybeM

imapMaybeM :: (Monad m, Unbox a, Unbox b) => (Int -> a -> m (Maybe b)) -> Vector a -> m (Vector b)
{-# INLINE imapMaybeM #-}
imapMaybeM = G.imapMaybeM

-- | /O(n)/ Drop elements that do not satisfy the monadic predicate
filterM :: (Monad m, Unbox a) => (a -> m Bool) -> Vector a -> m (Vector a)
{-# INLINE filterM #-}
Expand Down

0 comments on commit 8318efd

Please sign in to comment.