From 90be38762bc085c57ac2f3fdfb49286cfb1436a4 Mon Sep 17 00:00:00 2001 From: Pranay Sashank Date: Sat, 29 May 2021 23:03:45 +0530 Subject: [PATCH] Rename Fold.yield, yieldM to fromPure, fromEffect. --- benchmark/Streamly/Benchmark/Data/Fold.hs | 2 +- .../Data/Array/Stream/Fold/Foreign.hs | 18 +++++++------- src/Streamly/Internal/Data/Fold.hs | 8 +++---- src/Streamly/Internal/Data/Fold/Tee.hs | 2 +- src/Streamly/Internal/Data/Fold/Type.hs | 24 +++++++++---------- 5 files changed, 27 insertions(+), 27 deletions(-) diff --git a/benchmark/Streamly/Benchmark/Data/Fold.hs b/benchmark/Streamly/Benchmark/Data/Fold.hs index bee8fc68..000ab2f0 100644 --- a/benchmark/Streamly/Benchmark/Data/Fold.hs +++ b/benchmark/Streamly/Benchmark/Data/Fold.hs @@ -70,7 +70,7 @@ take value = IP.fold (FL.take value FL.drain) {-# INLINE sequence_ #-} sequence_ :: Monad m => Int -> Fold m a () sequence_ value = - foldr f (FL.yield ()) (Prelude.replicate value (FL.take 1 FL.drain)) + foldr f (FL.fromPure ()) (Prelude.replicate value (FL.take 1 FL.drain)) where diff --git a/src/Streamly/Internal/Data/Array/Stream/Fold/Foreign.hs b/src/Streamly/Internal/Data/Array/Stream/Fold/Foreign.hs index ac9c6762..0ddf0c5f 100644 --- a/src/Streamly/Internal/Data/Array/Stream/Fold/Foreign.hs +++ b/src/Streamly/Internal/Data/Array/Stream/Fold/Foreign.hs @@ -39,8 +39,8 @@ module Streamly.Internal.Data.Array.Stream.Fold.Foreign , rmapM -- * Applicative - , yield - , yieldM + , fromPure + , fromEffect , serialWith -- * Monad @@ -204,18 +204,18 @@ rmapM f (Fold p) = Fold $ ParserD.rmapM f p -- -- /Pre-release/ -- -{-# INLINE yield #-} -yield :: Monad m => b -> Fold m a b -yield = Fold . ParserD.yield +{-# INLINE fromPure #-} +fromPure :: Monad m => b -> Fold m a b +fromPure = Fold . ParserD.yield -- | A fold that always yields the result of an effectful action without -- consuming any input. -- -- /Pre-release/ -- -{-# INLINE yieldM #-} -yieldM :: Monad m => m b -> Fold m a b -yieldM = Fold . ParserD.yieldM +{-# INLINE fromEffect #-} +fromEffect :: Monad m => m b -> Fold m a b +fromEffect = Fold . ParserD.yieldM -- | Applies two folds sequentially on the input stream and combines their -- results using the supplied function. @@ -239,7 +239,7 @@ serialWith f (Fold p1) (Fold p2) = -- > (<*>) = serialWith id instance MonadThrow m => Applicative (Fold m a) where {-# INLINE pure #-} - pure = yield + pure = fromPure {-# INLINE (<*>) #-} (<*>) = serialWith id diff --git a/src/Streamly/Internal/Data/Fold.hs b/src/Streamly/Internal/Data/Fold.hs index 26771429..cf3f7212 100644 --- a/src/Streamly/Internal/Data/Fold.hs +++ b/src/Streamly/Internal/Data/Fold.hs @@ -31,8 +31,8 @@ module Streamly.Internal.Data.Fold -- * Folds -- ** Identity - , yield - , yieldM + , fromPure + , fromEffect -- ** Accumulators -- *** Semigroups and Monoids @@ -1092,7 +1092,7 @@ tee = teeWith (,) -- >>> Stream.fold (Fold.distribute [Fold.sum, Fold.length]) (Stream.enumerateFromTo 1 5) -- [15,5] -- --- > distribute = Prelude.foldr (Fold.teeWith (:)) (Fold.yield []) +-- > distribute = Prelude.foldr (Fold.teeWith (:)) (Fold.fromPure []) -- -- This is the consumer side dual of the producer side 'sequence' operation. -- @@ -1101,7 +1101,7 @@ tee = teeWith (,) -- @since 0.7.0 {-# INLINE distribute #-} distribute :: Monad m => [Fold m a b] -> Fold m a [b] -distribute = Prelude.foldr (teeWith (:)) (yield []) +distribute = Prelude.foldr (teeWith (:)) (fromPure []) ------------------------------------------------------------------------------ -- Partitioning diff --git a/src/Streamly/Internal/Data/Fold/Tee.hs b/src/Streamly/Internal/Data/Fold/Tee.hs index 783a7072..de405afc 100644 --- a/src/Streamly/Internal/Data/Fold/Tee.hs +++ b/src/Streamly/Internal/Data/Fold/Tee.hs @@ -37,7 +37,7 @@ newtype Tee m a b = instance Monad m => Applicative (Tee m a) where {-# INLINE pure #-} - pure a = Tee (Fold.yield a) + pure a = Tee (Fold.fromPure a) {-# INLINE (<*>) #-} (<*>) a b = Tee (Fold.teeWith ($) (toFold a) (toFold b)) diff --git a/src/Streamly/Internal/Data/Fold/Type.hs b/src/Streamly/Internal/Data/Fold/Type.hs index 1de1ae8a..af8932d4 100644 --- a/src/Streamly/Internal/Data/Fold/Type.hs +++ b/src/Streamly/Internal/Data/Fold/Type.hs @@ -207,8 +207,8 @@ module Streamly.Internal.Data.Fold.Type , mkFoldM_ -- * Folds - , yield - , yieldM + , fromPure + , fromEffect , drain , toList @@ -616,26 +616,26 @@ instance Functor m => Functor (Fold m a) where step s b = fmap2 f (step1 s b) fmap2 g = fmap (fmap g) --- This is the dual of stream "yield". +-- This is the dual of stream "fromPure". -- -- | A fold that always yields a pure value without consuming any input. -- -- /Pre-release/ -- -{-# INLINE yield #-} -yield :: Applicative m => b -> Fold m a b -yield b = Fold undefined (pure $ Done b) pure +{-# INLINE fromPure #-} +fromPure :: Applicative m => b -> Fold m a b +fromPure b = Fold undefined (pure $ Done b) pure --- This is the dual of stream "yieldM". +-- This is the dual of stream "fromEffect". -- -- | A fold that always yields the result of an effectful action without -- consuming any input. -- -- /Pre-release/ -- -{-# INLINE yieldM #-} -yieldM :: Applicative m => m b -> Fold m a b -yieldM b = Fold undefined (Done <$> b) pure +{-# INLINE fromEffect #-} +fromEffect :: Applicative m => m b -> Fold m a b +fromEffect b = Fold undefined (Done <$> b) pure {-# ANN type Step Fuse #-} data SeqFoldState sl f sr = SeqFoldL !sl | SeqFoldR !f !sr @@ -1030,9 +1030,9 @@ duplicate (Fold step1 initial1 extract1) = where - initial = second yield <$> initial1 + initial = second fromPure <$> initial1 - step s a = second yield <$> step1 s a + step s a = second fromPure <$> step1 s a -- | Run the initialization effect of a fold. The returned fold would use the -- value returned by this effect as its initial value.