Rename: ltakeWhile -> takeSepBy & drainWhile -> drainSepBy

This commit is contained in:
adithyaov 2020-11-24 03:35:31 +05:30
parent 8f7c0ddd1e
commit 0032f35e96
3 changed files with 26 additions and 11 deletions

View File

@ -70,7 +70,7 @@ module Streamly.Internal.Data.Fold
-- ** Partial Folds
, drainN
, drainWhile
, drainSepBy
-- , lastN
-- , (!!)
-- , genericIndex
@ -131,7 +131,7 @@ module Streamly.Internal.Data.Fold
-- ** Trimming
, ltake
-- , lrunFor -- time
, ltakeWhile
, takeSepBy
{-
, ltakeWhileM
, ldrop
@ -818,9 +818,9 @@ drainN n = ltake n drain
-- | A fold that drains elements of its input as long as the predicate succeeds,
-- running the effects and discarding the results.
{-# INLINABLE drainWhile #-}
drainWhile :: Monad m => (a -> Bool) -> Fold m a ()
drainWhile p = ltakeWhile p drain
{-# INLINABLE drainSepBy #-}
drainSepBy :: Monad m => (a -> Bool) -> Fold m a ()
drainSepBy p = takeSepBy p drain
------------------------------------------------------------------------------
-- To Elements

View File

@ -132,7 +132,7 @@ module Streamly.Internal.Data.Fold.Types
, lfilterM
, lcatMaybes
, ltake
, ltakeWhile
, takeSepBy
, teeWith
, teeWithFst
@ -587,10 +587,9 @@ ltake n (Fold fstep finitial fextract) = Fold step initial extract
-- | Takes elements from the input as long as the predicate succeeds.
--
-- @since 0.7.0
{-# INLINE ltakeWhile #-}
ltakeWhile :: Monad m => (a -> Bool) -> Fold m a b -> Fold m a b
ltakeWhile predicate (Fold fstep finitial fextract) =
Fold step finitial fextract
{-# INLINE takeSepBy #-}
takeSepBy :: Monad m => (a -> Bool) -> Fold m a b -> Fold m a b
takeSepBy predicate (Fold fstep finitial fextract) = Fold step finitial fextract
where

View File

@ -384,7 +384,23 @@ takeGE cnt (Fold fstep finitial fextract) = Parser step initial extract
--
{-# INLINE takeWhile #-}
takeWhile :: Monad m => (a -> Bool) -> Fold m a b -> Parser m a b
takeWhile predicate fld = fromFold (FL.ltakeWhile predicate fld)
takeWhile predicate (Fold fstep finitial fextract) =
Parser step initial fextract
where
initial = finitial
step s a =
if predicate a
then do
fres <- fstep s a
return
$ case fres of
FL.Partial s1 -> Partial 0 s1
FL.Done b -> Done 0 b
else Done 1 <$> fextract s
-- | See 'Streamly.Internal.Data.Parser.takeWhile1'.
--