Make minor refactoring changes for fromPure/fromEffect

* Move deprecated functions next to original ones, keep them in the generate
  section itself.
* Rename constructWithYield to constructWithFromPure
* Fix typo
This commit is contained in:
Harendra Kumar 2021-05-29 11:36:23 +05:30
parent 70faf014ca
commit 79defeb5ec
4 changed files with 20 additions and 21 deletions

View File

@ -136,7 +136,7 @@ import Prelude hiding (map)
-- XXX It may be a good idea to increment sequence numbers for each yield,
-- currently a stream on the left side of the expression may yield many
-- elements with the same sequene number. We can then use the seq number to
-- enforce fromEffectax and yieldLImit as well.
-- enforce yieldMax and yieldLImit as well.
-- Invariants:
--

View File

@ -119,6 +119,14 @@ import Prelude hiding (take, takeWhile, drop, reverse, concatMap)
fromPure :: IsStream t => a -> t m a
fromPure = K.fromPure
-- | Same as 'fromPure'
--
-- @since 0.4.0
{-# DEPRECATED yield "Please use fromPure instead." #-}
{-# INLINE yield #-}
yield :: IsStream t => a -> t m a
yield = fromPure
-- |
-- @
-- fromEffect m = m \`consM` nil
@ -138,6 +146,13 @@ fromPure = K.fromPure
fromEffect :: (Monad m, IsStream t) => m a -> t m a
fromEffect = K.fromEffect
-- | Same as 'fromEffect'
--
-- @since 0.4.0
{-# DEPRECATED yieldM "Please use fromEffect instead." #-}
{-# INLINE yieldM #-}
yieldM :: (Monad m, IsStream t) => m a -> t m a
yieldM = fromEffect
-- |
-- @
-- repeatM = fix . consM
@ -551,19 +566,3 @@ splitOnSeq
:: (IsStream t, MonadIO m, Storable a, Enum a, Eq a)
=> Array a -> Fold m a b -> t m a -> t m b
splitOnSeq patt f m = D.fromStreamD $ D.splitOnSeq patt f (D.toStreamD m)
-- | Same as 'fromPure'
--
-- @since 0.4.0
{-# DEPRECATED yield "Please use fromPure instead." #-}
{-# INLINE yield #-}
yield :: IsStream t => a -> t m a
yield = fromPure
-- | Same as 'fromEffect'
--
-- @since 0.4.0
{-# DEPRECATED yieldM "Please use fromEffect instead." #-}
{-# INLINE yieldM #-}
yieldM :: (Monad m, IsStream t) => m a -> t m a
yieldM = fromEffect

View File

@ -558,7 +558,7 @@ main = hspec
serialOps $ prop "serially fromList" . constructWithFromList id
serialOps $ prop "serially fromListM" . constructWithFromListM id
serialOps $ prop "serially unfoldr" . constructWithUnfoldr id
serialOps $ prop "serially fromPure" . constructWithYield id
serialOps $ prop "serially fromPure" . constructWithFromPure id
serialOps $ prop "serially fromEffect" . constructWithFromEffect id
serialOps $ prop "serially cons" . constructWithCons S.cons
serialOps $ prop "serially consM" . constructWithConsM S.consM id

View File

@ -29,7 +29,7 @@ module Streamly.Test.Prelude.Common
, constructWithUnfoldr
, constructWithCons
, constructWithConsM
, constructWithYield
, constructWithFromPure
, constructWithFromEffect
, simpleOps
-- * Applicative operations
@ -395,7 +395,7 @@ constructWithUnfoldr listT op len =
then Nothing
else Just (seed, seed + 1)
constructWithYield ::
constructWithFromPure ::
(IsStream t
#if __GLASGOW_HASKELL__ < 806
, Monoid (t IO Int)
@ -405,7 +405,7 @@ constructWithYield ::
-> (t IO Int -> SerialT IO Int)
-> Word8
-> Property
constructWithYield listT op len =
constructWithFromPure listT op len =
withMaxSuccess maxTestCount $
monadicIO $ do
strm <-