rename mconcatTo to sconcat

This commit is contained in:
Harendra Kumar 2020-05-15 08:48:47 +05:30
parent 2e5124fd8b
commit 01fa925af3
2 changed files with 10 additions and 11 deletions

View File

@ -214,7 +214,7 @@ parseIterate :: MonadCatch m => SerialT m Int -> m ()
parseIterate =
S.drain
. S.map getSum
. IP.parseIterate (\b -> (PR.take 2 (FL.mconcatTo b))) (Sum 0)
. IP.parseIterate (\b -> (PR.take 2 (FL.sconcat b))) (Sum 0)
. S.map Sum
-------------------------------------------------------------------------------

View File

@ -57,9 +57,11 @@ module Streamly.Internal.Data.Fold
, rollingHashFirstN
-- , rollingHashLastN
-- ** Fold Semigroups
, sconcat
-- ** Full Folds (Monoidal)
, mconcat
, mconcatTo
, foldMap
, foldMapM
@ -610,18 +612,15 @@ rollingHashFirstN n = ltake n rollingHash
-- Monoidal left folds
------------------------------------------------------------------------------
-- | 'mappend' the elements of an input stream to a provided starting value.
-- | Append the elements of an input stream to a provided starting value.
--
-- > S.fold (FL.mconcatTo 10) (S.map Sum $ S.enumerateFromTo 1 10)
--
-- This could be faster than (fmap (m0 <>) FL.mconcat) especially when we have
-- to perform the operation many times.
-- > S.fold (FL.sconcat 10) (S.map Sum $ S.enumerateFromTo 1 10)
--
-- /Internal/
--
{-# INLINE mconcatTo #-}
mconcatTo :: (Monad m, Monoid a) => a -> Fold m a a
mconcatTo i = Fold (\x a -> return $ mappend x a) (return i) return
{-# INLINE sconcat #-}
sconcat :: (Monad m, Semigroup a) => a -> Fold m a a
sconcat i = Fold (\x a -> return $ x <> a) (return i) return
-- | Fold an input stream consisting of monoidal elements using 'mappend'
-- and 'mempty'.
@ -631,7 +630,7 @@ mconcatTo i = Fold (\x a -> return $ mappend x a) (return i) return
-- @since 0.7.0
{-# INLINE mconcat #-}
mconcat :: (Monad m, Monoid a) => Fold m a a
mconcat = mconcatTo mempty
mconcat = sconcat mempty
-- |
-- > foldMap f = lmap f mconcat