Move rmapM to Fold/Types.hs

This commit is contained in:
Harendra Kumar 2021-03-10 01:40:42 +05:30
parent e95d056453
commit e9a0e7c118
5 changed files with 25 additions and 13 deletions

View File

@ -64,9 +64,9 @@
* `encodeLatin1Lax` to `encodeLatin1`
* `decodeUtf8Lenient` to `decodeUtf8`
* Drop support for GHC 7.10.3.
* The following functions in `Streamly.Data.Fold` have been renamed:
* `mapM` to `rmapM`
* `sequence` to `rsequence`
* The following functions in `Streamly.Data.Fold` have been deprecated:
* `mapM` is replaced by `rmapM`
* `sequence` is dprecated, please use `rmapM id` instead.
### Internal APIs

View File

@ -260,7 +260,7 @@ o_1_space_serial_transformation value =
, benchIOSink
value
"rsequence"
(S.fold (FL.rsequence (return <$> FL.drain)))
(S.fold (FL.rmapM id (return <$> FL.drain)))
, benchIOSink value "rmapM" (S.fold (FL.rmapM return FL.drain))
, benchIOSink
value

View File

@ -128,7 +128,6 @@ module Streamly.Data.Fold
--
-- Note: Output transformations are also known as covariant
-- transformations.
, rsequence
, sequence
, rmapM
, mapM

View File

@ -307,14 +307,7 @@ rsequence (Fold step initial extract) = Fold step' initial1 extract'
{-# DEPRECATED sequence "Use rsequence instead" #-}
{-# INLINE sequence #-}
sequence :: Monad m => Fold m a (m b) -> Fold m a b
sequence = rsequence
-- | Map a monadic function on the output of a fold.
--
-- @since 0.8.0
{-# INLINE rmapM #-}
rmapM :: Monad m => (b -> m c) -> Fold m a b -> Fold m a c
rmapM f = sequence . fmap f
sequence = rmapM id
-- | Map a monadic function on the output of a fold.
--

View File

@ -198,6 +198,7 @@ module Streamly.Internal.Data.Fold.Types
, yieldM
-- * Transformations
, rmapM
, map
, lmap
, lmapM
@ -300,6 +301,13 @@ instance Functor (Step s) where
{-# INLINE fmap #-}
fmap = second
{-# INLINE mapMStep #-}
mapMStep :: Applicative m => (a -> m b) -> Step s a -> m (Step s b)
mapMStep f res =
case res of
Partial s -> pure $ Partial s
Done b -> Done <$> f b
-- The Step functor around b allows expressing early termination like a right
-- fold. Traditional list right folds use function composition and laziness to
-- terminate early whereas we use data constructors. It allows stream fusion in
@ -326,6 +334,18 @@ data Fold m a b =
-- | @Fold @ @ step @ @ initial @ @ extract@
forall s. Fold (s -> a -> m (Step s b)) (m (Step s b)) (s -> m b)
-- | Map a monadic function on the output of a fold.
--
-- @since 0.8.0
{-# INLINE rmapM #-}
rmapM :: Monad m => (b -> m c) -> Fold m a b -> Fold m a c
rmapM f (Fold step initial extract) = Fold step1 initial1 (extract >=> f)
where
initial1 = initial >>= mapMStep f
step1 s a = step s a >>= mapMStep f
------------------------------------------------------------------------------
-- Left fold constructors
------------------------------------------------------------------------------