From 44616ee3f1bff3eccf169f8e3a1527b309f9bcdb Mon Sep 17 00:00:00 2001 From: Adithya Kumar Date: Mon, 27 Jan 2025 20:49:01 +0530 Subject: [PATCH] Implement multiple folds using scans --- .../Internal/Data/Fold/Combinators.hs | 160 +++--------------- .../Streamly/Internal/Data/Fold/Container.hs | 32 +--- core/src/Streamly/Internal/Data/Fold/Type.hs | 95 +++-------- .../Internal/Data/Scanl/Combinators.hs | 1 + 4 files changed, 58 insertions(+), 230 deletions(-) diff --git a/core/src/Streamly/Internal/Data/Fold/Combinators.hs b/core/src/Streamly/Internal/Data/Fold/Combinators.hs index 258b93a579..8bb6c5b15e 100644 --- a/core/src/Streamly/Internal/Data/Fold/Combinators.hs +++ b/core/src/Streamly/Internal/Data/Fold/Combinators.hs @@ -32,7 +32,7 @@ module Streamly.Internal.Data.Fold.Combinators , the , mean , rollingHash - , defaultSalt + , Scanl.defaultSalt , rollingHashWithSalt , rollingHashFirstN -- , rollingHashLastN @@ -67,6 +67,7 @@ module Streamly.Internal.Data.Fold.Combinators -- usually a transformation of the current element rather than an -- aggregation of all elements till now. -- , nthLast -- using RingArray array + , rollingMap , rollingMapM -- *** Filters @@ -242,12 +243,10 @@ import Streamly.Internal.Data.Unfold.Type (Unfold(..)) import qualified Prelude import qualified Streamly.Internal.Data.MutArray.Type as MA import qualified Streamly.Internal.Data.Array.Type as Array -import qualified Streamly.Internal.Data.Fold.Type as Fold import qualified Streamly.Internal.Data.Pipe.Type as Pipe import qualified Streamly.Internal.Data.RingArray as RingArray import qualified Streamly.Internal.Data.Scanl.Combinators as Scanl import qualified Streamly.Internal.Data.Scanl.Type as Scanl -import qualified Streamly.Internal.Data.Scanl.Window as Scanl import qualified Streamly.Internal.Data.Stream.Type as StreamD import Prelude hiding @@ -500,17 +499,7 @@ pipe (Pipe consume produce pinitial) (Fold fstep finitial fextract ffinal) = -- {-# INLINE_NORMAL deleteBy #-} deleteBy :: Monad m => (a -> a -> Bool) -> a -> Fold m a (Maybe a) -deleteBy eq x0 = fmap extract $ foldl' step (Tuple' False Nothing) - - where - - step (Tuple' False _) x = - if eq x x0 - then Tuple' True Nothing - else Tuple' False (Just x) - step (Tuple' True _) x = Tuple' True (Just x) - - extract (Tuple' _ x) = x +deleteBy eq = fromScanl . Scanl.deleteBy eq -- | Provide a sliding window of length 2 elements. -- @@ -550,14 +539,7 @@ slide2 (Fold step1 initial1 extract1 final1) = Fold step initial extract final -- {-# INLINE uniqBy #-} uniqBy :: Monad m => (a -> a -> Bool) -> Fold m a (Maybe a) -uniqBy eq = rollingMap f - - where - - f pre curr = - case pre of - Nothing -> Just curr - Just x -> if x `eq` curr then Nothing else Just curr +uniqBy = fromScanl . Scanl.uniqBy -- | See 'uniqBy'. -- @@ -567,7 +549,7 @@ uniqBy eq = rollingMap f -- {-# INLINE uniq #-} uniq :: (Monad m, Eq a) => Fold m a (Maybe a) -uniq = uniqBy (==) +uniq = fromScanl Scanl.uniq -- | Strip all leading and trailing occurrences of an element passing a -- predicate and make all other consecutive occurrences uniq. @@ -628,17 +610,7 @@ drainBy = drainMapM -- {-# INLINE the #-} the :: (Monad m, Eq a) => Fold m a (Maybe a) -the = foldt' step initial id - - where - - initial = Partial Nothing - - step Nothing x = Partial (Just x) - step old@(Just x0) x = - if x0 == x - then Partial old - else Done Nothing +the = fromScanl Scanl.the ------------------------------------------------------------------------------ -- To Summary @@ -657,7 +629,7 @@ the = foldt' step initial id -- {-# INLINE sum #-} sum :: (Monad m, Num a) => Fold m a a -sum = Fold.fromScanl $ Scanl.cumulativeScan Scanl.incrSum +sum = fromScanl Scanl.sum -- | Determine the product of all elements of a stream of numbers. Returns -- multiplicative identity (@1@) when the stream is empty. The fold terminates @@ -669,14 +641,7 @@ sum = Fold.fromScanl $ Scanl.cumulativeScan Scanl.incrSum -- {-# INLINE product #-} product :: (Monad m, Num a, Eq a) => Fold m a a -product = foldt' step (Partial 1) id - - where - - step x a = - if a == 0 - then Done 0 - else Partial $ x * a +product = fromScanl Scanl.product ------------------------------------------------------------------------------ -- To Summary (Maybe) @@ -761,17 +726,7 @@ range = fromScanl Scanl.range -- {-# INLINE mean #-} mean :: (Monad m, Fractional a) => Fold m a a -mean = fmap done $ foldl' step begin - - where - - begin = Tuple' 0 0 - - step (Tuple' x n) y = - let n1 = n + 1 - in Tuple' (x + (y - x) / n1) n1 - - done (Tuple' x _) = x +mean = fromScanl Scanl.mean -- | Compute a numerically stable (population) variance over all elements in -- the input stream. @@ -817,18 +772,7 @@ stdDev = sqrt <$> variance -- {-# INLINE rollingHashWithSalt #-} rollingHashWithSalt :: (Monad m, Enum a) => Int64 -> Fold m a Int64 -rollingHashWithSalt = foldl' step - - where - - k = 2891336453 :: Int64 - - step cksum a = cksum * k + fromIntegral (fromEnum a) - --- | A default salt used in the implementation of 'rollingHash'. -{-# INLINE defaultSalt #-} -defaultSalt :: Int64 -defaultSalt = -2578643520546668380 +rollingHashWithSalt = fromScanl . Scanl.rollingHashWithSalt -- | Compute an 'Int' sized polynomial rolling hash of a stream. -- @@ -836,7 +780,7 @@ defaultSalt = -2578643520546668380 -- {-# INLINE rollingHash #-} rollingHash :: (Monad m, Enum a) => Fold m a Int64 -rollingHash = rollingHashWithSalt defaultSalt +rollingHash = fromScanl Scanl.rollingHash -- | Compute an 'Int' sized polynomial rolling hash of the first n elements of -- a stream. @@ -846,7 +790,7 @@ rollingHash = rollingHashWithSalt defaultSalt -- /Pre-release/ {-# INLINE rollingHashFirstN #-} rollingHashFirstN :: (Monad m, Enum a) => Int -> Fold m a Int64 -rollingHashFirstN n = take n rollingHash +rollingHashFirstN = fromScanl . Scanl.rollingHashFirstN -- XXX Compare this with the implementation in Fold.Window, preferrably use the -- latter if performance is good. @@ -860,26 +804,14 @@ rollingHashFirstN n = take n rollingHash -- {-# INLINE rollingMapM #-} rollingMapM :: Monad m => (Maybe a -> a -> m b) -> Fold m a b -rollingMapM f = Fold step initial extract extract - - where - - -- XXX We need just a postscan. We do not need an initial result here. - -- Or we can supply a default initial result as an argument to rollingMapM. - initial = return $ Partial (Nothing, error "Empty stream") - - step (prev, _) cur = do - x <- f prev cur - return $ Partial (Just cur, x) - - extract = return . snd +rollingMapM = fromScanl . Scanl.rollingMapM -- | -- >>> rollingMap f = Fold.rollingMapM (\x y -> return $ f x y) -- {-# INLINE rollingMap #-} rollingMap :: Monad m => (Maybe a -> a -> b) -> Fold m a b -rollingMap f = rollingMapM (\x y -> return $ f x y) +rollingMap = fromScanl . Scanl.rollingMap ------------------------------------------------------------------------------ -- Monoidal left folds @@ -898,7 +830,7 @@ rollingMap f = rollingMapM (\x y -> return $ f x y) -- {-# INLINE sconcat #-} sconcat :: (Monad m, Semigroup a) => a -> Fold m a a -sconcat = foldl' (<>) +sconcat = fromScanl . Scanl.sconcat -- | Monoid concat. Fold an input stream consisting of monoidal elements using -- 'mappend' and 'mempty'. @@ -915,7 +847,7 @@ sconcat = foldl' (<>) mconcat :: ( Monad m , Monoid a) => Fold m a a -mconcat = sconcat mempty +mconcat = fromScanl Scanl.mconcat -- | -- Definition: @@ -931,7 +863,7 @@ mconcat = sconcat mempty -- {-# INLINE foldMap #-} foldMap :: (Monad m, Monoid b) => (a -> b) -> Fold m a b -foldMap f = lmap f mconcat +foldMap = fromScanl . Scanl.foldMap -- | -- Definition: @@ -947,13 +879,7 @@ foldMap f = lmap f mconcat -- {-# INLINE foldMapM #-} foldMapM :: (Monad m, Monoid b) => (a -> m b) -> Fold m a b -foldMapM act = foldlM' step (pure mempty) - - where - - step m a = do - m' <- act a - return $! mappend m m' +foldMapM = fromScanl . Scanl.foldMapM ------------------------------------------------------------------------------ -- Partial Folds @@ -969,7 +895,7 @@ foldMapM act = foldlM' step (pure mempty) -- /Pre-release/ {-# INLINE drainN #-} drainN :: Monad m => Int -> Fold m a () -drainN n = take n drain +drainN = fromScanl . Scanl.drainN ------------------------------------------------------------------------------ -- To Elements @@ -1134,16 +1060,7 @@ findIndex predicate = foldt' step (Partial 0) (const Nothing) -- {-# INLINE findIndices #-} findIndices :: Monad m => (a -> Bool) -> Fold m a (Maybe Int) -findIndices predicate = - -- XXX implement by combining indexing and filtering scans - fmap (either (const Nothing) Just) $ foldl' step (Left (-1)) - - where - - step i a = - if predicate a - then Right (either id id i + 1) - else Left (either id id i + 1) +findIndices = fromScanl . Scanl.findIndices -- | Returns the index of the latest element if the element matches the given -- value. @@ -1154,7 +1071,7 @@ findIndices predicate = -- {-# INLINE elemIndices #-} elemIndices :: (Monad m, Eq a) => a -> Fold m a (Maybe Int) -elemIndices a = findIndices (== a) +elemIndices = fromScanl . Scanl.elemIndices -- | Returns the first index where a given value is found in the stream. -- @@ -2256,7 +2173,7 @@ chunksBetween _low _high _f1 _f2 = undefined -- /Pre-release/ {-# INLINE toStream #-} toStream :: (Monad m, Monad n) => Fold m a (Stream n a) -toStream = fmap StreamD.fromList toList +toStream = fromScanl Scanl.toStream -- This is more efficient than 'toStream'. toStream is exactly the same as -- reversing the stream after toStreamRev. @@ -2274,7 +2191,7 @@ toStream = fmap StreamD.fromList toList -- xn : ... : x2 : x1 : [] {-# INLINE toStreamRev #-} toStreamRev :: (Monad m, Monad n) => Fold m a (Stream n a) -toStreamRev = fmap StreamD.fromList toListRev +toStreamRev = fromScanl Scanl.toStreamRev -- XXX This does not fuse. It contains a recursive step function. We will need -- a Skip input constructor in the fold type to make it fuse. @@ -2316,32 +2233,7 @@ bottomBy :: (MonadIO m, Unbox a) => (a -> a -> Ordering) -> Int -> Fold m a (MutArray a) -bottomBy cmp n = Fold step initial extract extract - - where - - initial = do - arr <- MA.emptyOf' n - if n <= 0 - then return $ Done arr - else return $ Partial (arr, 0) - - step (arr, i) x = - if i < n - then do - arr' <- MA.snoc arr x - MA.bubble cmp arr' - return $ Partial (arr', i + 1) - else do - x1 <- MA.unsafeGetIndex (i - 1) arr - case x `cmp` x1 of - LT -> do - MA.unsafePutIndex (i - 1) arr x - MA.bubble cmp arr - return $ Partial (arr, i) - _ -> return $ Partial (arr, i) - - extract = return . fst +bottomBy cmp = fromScanl . Scanl.bottomBy cmp -- | Get the top @n@ elements using the supplied comparison function. -- @@ -2377,7 +2269,7 @@ topBy cmp = bottomBy (flip cmp) -- /Pre-release/ {-# INLINE top #-} top :: (MonadIO m, Unbox a, Ord a) => Int -> Fold m a (MutArray a) -top = bottomBy $ flip compare +top = fromScanl . Scanl.top -- | Fold the input stream to bottom n elements. -- @@ -2392,7 +2284,7 @@ top = bottomBy $ flip compare -- /Pre-release/ {-# INLINE bottom #-} bottom :: (MonadIO m, Unbox a, Ord a) => Int -> Fold m a (MutArray a) -bottom = bottomBy compare +bottom = fromScanl . Scanl.bottom ------------------------------------------------------------------------------ -- Interspersed parsing diff --git a/core/src/Streamly/Internal/Data/Fold/Container.hs b/core/src/Streamly/Internal/Data/Fold/Container.hs index b09c90890a..4be18bee7a 100644 --- a/core/src/Streamly/Internal/Data/Fold/Container.hs +++ b/core/src/Streamly/Internal/Data/Fold/Container.hs @@ -119,9 +119,9 @@ import Streamly.Internal.Data.IsMap (IsMap(..)) import Streamly.Internal.Data.Scanl.Type (Scanl(..)) import Streamly.Internal.Data.Tuple.Strict (Tuple'(..), Tuple3'(..)) -import qualified Data.IntSet as IntSet import qualified Data.Set as Set import qualified Streamly.Internal.Data.IsMap as IsMap +import qualified Streamly.Internal.Data.Scanl.Container as Scanl import Prelude hiding (Foldable(..)) import Streamly.Internal.Data.Fold.Type @@ -136,7 +136,7 @@ import Streamly.Internal.Data.Fold.Type -- {-# INLINE toSet #-} toSet :: (Monad m, Ord a) => Fold m a (Set a) -toSet = foldl' (flip Set.insert) Set.empty +toSet = fromScanl Scanl.toSet -- | Fold the input to an int set. For integer inputs this performs better than -- 'toSet'. @@ -147,7 +147,7 @@ toSet = foldl' (flip Set.insert) Set.empty -- {-# INLINE toIntSet #-} toIntSet :: Monad m => Fold m Int IntSet -toIntSet = foldl' (flip IntSet.insert) IntSet.empty +toIntSet = fromScanl Scanl.toIntSet -- XXX Name as nubOrd? Or write a nubGeneric @@ -164,32 +164,14 @@ toIntSet = foldl' (flip IntSet.insert) IntSet.empty -- /Pre-release/ {-# INLINE nub #-} nub :: (Monad m, Ord a) => Fold m a (Maybe a) -nub = fmap (\(Tuple' _ x) -> x) $ foldl' step initial - - where - - initial = Tuple' Set.empty Nothing - - step (Tuple' set _) x = - if Set.member x set - then Tuple' set Nothing - else Tuple' (Set.insert x set) (Just x) +nub = fromScanl Scanl.nub -- | Like 'nub' but specialized to a stream of 'Int', for better performance. -- -- /Pre-release/ {-# INLINE nubInt #-} nubInt :: Monad m => Fold m Int (Maybe Int) -nubInt = fmap (\(Tuple' _ x) -> x) $ foldl' step initial - - where - - initial = Tuple' IntSet.empty Nothing - - step (Tuple' set _) x = - if IntSet.member x set - then Tuple' set Nothing - else Tuple' (IntSet.insert x set) (Just x) +nubInt = fromScanl Scanl.nubInt -- XXX Try Hash set -- XXX Add a countDistinct window fold @@ -213,7 +195,7 @@ nubInt = fmap (\(Tuple' _ x) -> x) $ foldl' step initial {-# INLINE countDistinct #-} countDistinct :: (Monad m, Ord a) => Fold m a Int -- countDistinct = postscan nub $ catMaybes length -countDistinct = fmap Set.size toSet +countDistinct = fromScanl Scanl.countDistinct {- countDistinct = fmap (\(Tuple' _ n) -> n) $ foldl' step initial @@ -242,7 +224,7 @@ countDistinct = fmap (\(Tuple' _ n) -> n) $ foldl' step initial {-# INLINE countDistinctInt #-} countDistinctInt :: Monad m => Fold m Int Int -- countDistinctInt = postscan nubInt $ catMaybes length -countDistinctInt = fmap IntSet.size toIntSet +countDistinctInt = fromScanl Scanl.countDistinctInt {- countDistinctInt = fmap (\(Tuple' _ n) -> n) $ foldl' step initial diff --git a/core/src/Streamly/Internal/Data/Fold/Type.hs b/core/src/Streamly/Internal/Data/Fold/Type.hs index 6144a4f39d..f4348cdc8d 100644 --- a/core/src/Streamly/Internal/Data/Fold/Type.hs +++ b/core/src/Streamly/Internal/Data/Fold/Type.hs @@ -475,13 +475,13 @@ import Data.Either (fromLeft, fromRight, isLeft, isRight) import Data.Functor.Identity (Identity(..)) import Fusion.Plugin.Types (Fuse(..)) import Streamly.Internal.Data.Either.Strict (Either'(..)) -import Streamly.Internal.Data.Maybe.Strict (Maybe'(..), toMaybe) import Streamly.Internal.Data.Refold.Type (Refold(..)) import Streamly.Internal.Data.Scanl.Type (Scanl(..)) import Streamly.Internal.Data.Tuple.Strict (Tuple'(..)) -- import qualified Streamly.Internal.Data.Stream.Step as Stream import qualified Streamly.Internal.Data.StreamK.Type as K +import qualified Streamly.Internal.Data.Scanl.Type as Scanl import Prelude hiding (Foldable(..), concatMap, filter, map, take, scanl, last) @@ -601,6 +601,11 @@ rmapM f (Fold step initial extract final) = -- Left fold constructors ------------------------------------------------------------------------------ +-- | Convert a left scan to a fold. +{-# INLINE fromScanl #-} +fromScanl :: Scanl m a b -> Fold m a b +fromScanl (Scanl step initial extract final) = Fold step initial extract final + -- | Make a fold from a left fold style pure step function and initial value of -- the accumulator. -- @@ -616,12 +621,7 @@ rmapM f (Fold step initial extract final) = -- {-# INLINE foldl' #-} foldl' :: Monad m => (b -> a -> b) -> b -> Fold m a b -foldl' step initial = - Fold - (\s a -> return $ Partial $ step s a) - (return (Partial initial)) - return - return +foldl' step = fromScanl . Scanl.mkScanl step -- | Make a fold from a left fold style monadic step function and initial value -- of the accumulator. @@ -635,8 +635,7 @@ foldl' step initial = -- {-# INLINE foldlM' #-} foldlM' :: Monad m => (b -> a -> m b) -> m b -> Fold m a b -foldlM' step initial = - Fold (\s a -> Partial <$> step s a) (Partial <$> initial) return return +foldlM' step = fromScanl . Scanl.mkScanlM step -- | Make a strict left fold, for non-empty streams, using first element as the -- starting value. Returns Nothing if the stream is empty. @@ -644,12 +643,7 @@ foldlM' step initial = -- /Pre-release/ {-# INLINE foldl1' #-} foldl1' :: Monad m => (a -> a -> a) -> Fold m a (Maybe a) -foldl1' step = fmap toMaybe $ foldl' step1 Nothing' - - where - - step1 Nothing' a = Just' a - step1 (Just' x) a = Just' $ step x a +foldl1' = fromScanl . Scanl.mkScanl1 -- | Like 'foldl1\'' but with a monadic step function. -- @@ -664,12 +658,7 @@ foldlM1' = foldl1M' -- /Pre-release/ {-# INLINE foldl1M' #-} foldl1M' :: Monad m => (a -> a -> m a) -> Fold m a (Maybe a) -foldl1M' step = fmap toMaybe $ foldlM' step1 (return Nothing') - - where - - step1 Nothing' a = return $ Just' a - step1 (Just' x) a = Just' <$> step x a +foldl1M' = fromScanl . Scanl.mkScanl1M {- data FromScan s b = FromScanInit !s | FromScanGo !s !b @@ -713,11 +702,6 @@ fromScan (Scan consume initial) = fextract (FromScanGo _ acc) = return (Just acc) -} --- | Convert a left scan to a fold. -{-# INLINE fromScanl #-} -fromScanl :: Scanl m a b -> Fold m a b -fromScanl (Scanl step initial extract final) = Fold step initial extract final - ------------------------------------------------------------------------------ -- Right fold constructors ------------------------------------------------------------------------------ @@ -739,7 +723,7 @@ fromScanl (Scanl step initial extract final) = Fold step initial extract final -- {-# INLINE foldr' #-} foldr' :: Monad m => (a -> b -> b) -> b -> Fold m a b -foldr' f z = fmap ($ z) $ foldl' (\g x -> g . f x) id +foldr' f = fromScanl . Scanl.mkScanr f {-# DEPRECATED foldr "Please use foldr' instead." #-} {-# INLINE foldr #-} @@ -760,8 +744,7 @@ foldr = foldr' -- /Pre-release/ {-# INLINE foldrM' #-} foldrM' :: Monad m => (a -> b -> m b) -> m b -> Fold m a b -foldrM' g z = - rmapM (z >>=) $ foldlM' (\f x -> return $ g x >=> f) (return return) +foldrM' g = fromScanl . Scanl.mkScanrM g ------------------------------------------------------------------------------ -- General fold constructors @@ -788,12 +771,7 @@ foldrM' g z = -- {-# INLINE foldt' #-} foldt' :: Monad m => (s -> a -> Step s b) -> Step s b -> (s -> b) -> Fold m a b -foldt' step initial extract = - Fold - (\s a -> return $ step s a) - (return initial) - (return . extract) - (return . extract) +foldt' step initial = fromScanl . Scanl.mkScant step initial -- | Make a terminating fold with an effectful step function and initial state, -- and a state extraction function. @@ -834,7 +812,7 @@ fromRefold (Refold step inject extract) c = -- {-# INLINE drain #-} drain :: Monad m => Fold m a () -drain = foldl' (\_ _ -> ()) () +drain = fromScanl Scanl.drain ------------------------------------------------------------------------------ -- To Containers @@ -850,7 +828,7 @@ drain = foldl' (\_ _ -> ()) () -- {-# INLINE toList #-} toList :: Monad m => Fold m a [a] -toList = foldr' (:) [] +toList = fromScanl Scanl.toList -- $toListRev -- This is more efficient than 'Streamly.Internal.Data.Fold.toList'. toList is @@ -884,7 +862,7 @@ toListRev = foldl' (flip (:)) [] -- xn : ... : x2 : x1 : [] {-# INLINE toStreamKRev #-} toStreamKRev :: Monad m => Fold m a (K.StreamK n a) -toStreamKRev = foldl' (flip K.cons) K.nil +toStreamKRev = fromScanl Scanl.toStreamKRev -- | A fold that buffers its input to a pure stream. -- @@ -894,7 +872,7 @@ toStreamKRev = foldl' (flip K.cons) K.nil -- /Internal/ {-# INLINE toStreamK #-} toStreamK :: Monad m => Fold m a (K.StreamK n a) -toStreamK = foldr K.cons K.nil +toStreamK = fromScanl Scanl.toStreamK -- | Like 'length', except with a more general 'Num' return value -- @@ -906,7 +884,7 @@ toStreamK = foldr K.cons K.nil -- /Pre-release/ {-# INLINE genericLength #-} genericLength :: (Monad m, Num b) => Fold m a b -genericLength = foldl' (\n _ -> n + 1) 0 +genericLength = fromScanl Scanl.genericLength -- | Determine the length of the input stream. -- @@ -917,7 +895,7 @@ genericLength = foldl' (\n _ -> n + 1) 0 -- {-# INLINE length #-} length :: Monad m => Fold m a Int -length = genericLength +length = fromScanl Scanl.length -- | Returns the latest element of the input stream, if any. -- @@ -926,7 +904,7 @@ length = genericLength -- {-# INLINE latest #-} latest :: Monad m => Fold m a (Maybe a) -latest = foldl1' (\_ x -> x) +latest = fromScanl Scanl.latest {-# DEPRECATED last "Please use 'latest' instead." #-} {-# INLINE last #-} @@ -976,7 +954,7 @@ instance Functor m => Functor (Fold m a) where -- {-# INLINE fromPure #-} fromPure :: Applicative m => b -> Fold m a b -fromPure b = Fold undefined (pure $ Done b) pure pure +fromPure = fromScanl . Scanl.const -- | Make a fold that yields the result of the supplied effectful action -- without consuming any further input. @@ -985,7 +963,7 @@ fromPure b = Fold undefined (pure $ Done b) pure pure -- {-# INLINE fromEffect #-} fromEffect :: Applicative m => m b -> Fold m a b -fromEffect b = Fold undefined (Done <$> b) pure pure +fromEffect = fromScanl . Scanl.constM {-# ANN type SeqFoldState Fuse #-} data SeqFoldState sl f sr = SeqFoldL !sl | SeqFoldR !f !sr @@ -1850,36 +1828,11 @@ data Tuple'Fused a b = Tuple'Fused !a !b deriving Show {-# INLINE taking #-} taking :: Monad m => Int -> Fold m a (Maybe a) -taking n = foldt' step initial extract - - where - - initial = - if n <= 0 - then Done Nothing - else Partial (Tuple'Fused n Nothing) - - step (Tuple'Fused i _) a = - if i > 1 - then Partial (Tuple'Fused (i - 1) (Just a)) - else Done (Just a) - - extract (Tuple'Fused _ r) = r +taking = fromScanl . Scanl.taking {-# INLINE dropping #-} dropping :: Monad m => Int -> Fold m a (Maybe a) -dropping n = foldt' step initial extract - - where - - initial = Partial (Tuple'Fused n Nothing) - - step (Tuple'Fused i _) a = - if i > 0 - then Partial (Tuple'Fused (i - 1) Nothing) - else Partial (Tuple'Fused i (Just a)) - - extract (Tuple'Fused _ r) = r +dropping = fromScanl . Scanl.dropping -- | Take at most @n@ input elements and fold them using the supplied fold. A -- negative count is treated as 0. diff --git a/core/src/Streamly/Internal/Data/Scanl/Combinators.hs b/core/src/Streamly/Internal/Data/Scanl/Combinators.hs index 5b0a8464a2..0422f5c994 100644 --- a/core/src/Streamly/Internal/Data/Scanl/Combinators.hs +++ b/core/src/Streamly/Internal/Data/Scanl/Combinators.hs @@ -58,6 +58,7 @@ module Streamly.Internal.Data.Scanl.Combinators , indexingWith , indexing , indexingRev + , rollingMap , rollingMapM -- *** Filters