Repurpose the streamk build flag

Fix review comments

Fix review comments

Rename stramk CI to no-fusion
This commit is contained in:
Ranjeet Kumar Ranjan 2022-08-11 13:54:55 +05:30 committed by Harendra Kumar
parent 9cce0ebeed
commit ca76876369
13 changed files with 82 additions and 148 deletions

View File

@ -132,13 +132,13 @@ jobs:
cabal_project: cabal.project cabal_project: cabal.project
cabal_build_options: "--flag fusion-plugin" cabal_build_options: "--flag fusion-plugin"
ignore_error: false ignore_error: false
- name: 8.6.5-sdist-streamk-unoptimized - name: 8.6.5-sdist-no-fusion-unoptimized
ghc_version: 8.6.5 ghc_version: 8.6.5
runner: ubuntu-latest runner: ubuntu-latest
build: cabal build: cabal
cabal_version: 3.6 cabal_version: 3.6
cabal_project: cabal.project cabal_project: cabal.project
cabal_build_options: "--flag streamk --flag -opt" cabal_build_options: "--flag no-fusion --flag -opt"
ignore_error: false ignore_error: false
- name: 8.6.5-sdist-debug-unoptimized - name: 8.6.5-sdist-debug-unoptimized
ghc_version: 8.6.5 ghc_version: 8.6.5

View File

@ -33,13 +33,6 @@ where
import Streamly.Internal.Data.Fold.Type (Fold (..)) import Streamly.Internal.Data.Fold.Type (Fold (..))
#ifdef USE_STREAMK_ONLY
import qualified Streamly.Internal.Data.Stream.StreamK as S
import qualified Streamly.Internal.Data.Stream.StreamK.Type as S
#else
import qualified Streamly.Internal.Data.Stream.StreamD.Type as S
#endif
import qualified Streamly.Internal.Data.Stream.StreamK.Type as K import qualified Streamly.Internal.Data.Stream.StreamK.Type as K
import qualified Streamly.Internal.Data.Stream.StreamD.Type as D import qualified Streamly.Internal.Data.Stream.StreamD.Type as D
@ -59,15 +52,15 @@ import Prelude hiding (foldr, repeat)
-- --
{-# INLINE_EARLY fromList #-} {-# INLINE_EARLY fromList #-}
fromList :: Monad m => [a] -> K.Stream m a fromList :: Monad m => [a] -> K.Stream m a
fromList = S.toStreamK . S.fromList fromList = D.toStreamK . D.fromList
{-# RULES "fromList fallback to StreamK" [1] {-# RULES "fromList fallback to StreamK" [1]
forall a. S.toStreamK (S.fromList a) = K.fromFoldable a #-} forall a. D.toStreamK (D.fromList a) = K.fromFoldable a #-}
-- | Convert a stream into a list in the underlying monad. -- | Convert a stream into a list in the underlying monad.
-- --
{-# INLINE toList #-} {-# INLINE toList #-}
toList :: Monad m => K.Stream m a -> m [a] toList :: Monad m => K.Stream m a -> m [a]
toList m = S.toList $ S.fromStreamK m toList m = D.toList $ D.fromStreamK m
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
-- Folds -- Folds
@ -75,7 +68,7 @@ toList m = S.toList $ S.fromStreamK m
{-# INLINE foldrM #-} {-# INLINE foldrM #-}
foldrM :: Monad m => (a -> m b -> m b) -> m b -> K.Stream m a -> m b foldrM :: Monad m => (a -> m b -> m b) -> m b -> K.Stream m a -> m b
foldrM step acc m = S.foldrM step acc $ S.fromStreamK m foldrM step acc m = D.foldrM step acc $ D.fromStreamK m
{-# INLINE foldr #-} {-# INLINE foldr #-}
foldr :: Monad m => (a -> b -> b) -> b -> K.Stream m a -> m b foldr :: Monad m => (a -> b -> b) -> b -> K.Stream m a -> m b
@ -86,12 +79,12 @@ foldr f z = foldrM (\a b -> f a <$> b) (return z)
{-# INLINE foldl' #-} {-# INLINE foldl' #-}
foldl' :: foldl' ::
Monad m => (b -> a -> b) -> b -> K.Stream m a -> m b Monad m => (b -> a -> b) -> b -> K.Stream m a -> m b
foldl' step begin m = S.foldl' step begin $ S.fromStreamK m foldl' step begin m = D.foldl' step begin $ D.fromStreamK m
{-# INLINE fold #-} {-# INLINE fold #-}
fold :: Monad m => Fold m a b -> K.Stream m a -> m b fold :: Monad m => Fold m a b -> K.Stream m a -> m b
fold fld m = S.fold fld $ S.fromStreamK m fold fld m = D.fold fld $ D.fromStreamK m
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
-- Comparison -- Comparison

View File

@ -9,7 +9,7 @@
-- --
-- {-# INLINE_EARLY unfoldr #-} -- {-# INLINE_EARLY unfoldr #-}
-- unfoldr :: (Monad m, IsStream t) => (b -> Maybe (a, b)) -> b -> t m a -- unfoldr :: (Monad m, IsStream t) => (b -> Maybe (a, b)) -> b -> t m a
-- unfoldr step seed = fromStreamS (S.unfoldr step seed) -- unfoldr step seed = fromStreamD (S.unfoldr step seed)
-- {-# RULES "unfoldr fallback to StreamK" [1] -- {-# RULES "unfoldr fallback to StreamK" [1]
-- forall a b. S.toStreamK (S.unfoldr a b) = K.unfoldr a b #-}``` -- forall a b. S.toStreamK (S.unfoldr a b) = K.unfoldr a b #-}```
-- --

View File

@ -57,11 +57,6 @@ flag no-fusion
manual: True manual: True
default: False default: False
flag streamk
description: Use CPS style streams when possible
manual: True
default: False
flag use-c-malloc flag use-c-malloc
description: Use C malloc instead of GHC malloc description: Use C malloc instead of GHC malloc
manual: True manual: True
@ -99,9 +94,6 @@ flag use-folds
common compile-options common compile-options
default-language: Haskell2010 default-language: Haskell2010
if flag(streamk)
cpp-options: -DUSE_STREAMK_ONLY
if flag(no-fusion) if flag(no-fusion)
cpp-options: -DDISABLE_FUSION cpp-options: -DDISABLE_FUSION

View File

@ -75,7 +75,7 @@ import Streamly.Internal.Data.Array.Unboxed.Type (Array)
import Streamly.Internal.Data.Fold.Type (Fold (..)) import Streamly.Internal.Data.Fold.Type (Fold (..))
import Streamly.Internal.Data.Stream.IsStream.Combinators (maxYields) import Streamly.Internal.Data.Stream.IsStream.Combinators (maxYields)
import Streamly.Internal.Data.Stream.IsStream.Type import Streamly.Internal.Data.Stream.IsStream.Type
(IsStream(..), fromStreamD, toStreamD, fromStreamS, toStreamS) (IsStream(..), fromStreamD, toStreamD)
import Streamly.Internal.Data.Stream.Serial (SerialT) import Streamly.Internal.Data.Stream.Serial (SerialT)
import Streamly.Internal.Data.Time.Units (AbsTime, RelTime64, addToAbsTime64) import Streamly.Internal.Data.Time.Units (AbsTime, RelTime64, addToAbsTime64)
import Streamly.Internal.System.IO (defaultChunkSize) import Streamly.Internal.System.IO (defaultChunkSize)
@ -87,11 +87,6 @@ import qualified Streamly.Internal.Data.Stream.IsStream.Type as IsStream
import qualified Streamly.Internal.Data.Stream.Parallel as Par import qualified Streamly.Internal.Data.Stream.Parallel as Par
import qualified Streamly.Internal.Data.Stream.StreamK.Type as K import qualified Streamly.Internal.Data.Stream.StreamK.Type as K
import qualified Streamly.Internal.Data.Stream.StreamD as D import qualified Streamly.Internal.Data.Stream.StreamD as D
#ifdef USE_STREAMK_ONLY
import qualified Streamly.Internal.Data.Stream.StreamK as S
#else
import qualified Streamly.Internal.Data.Stream.StreamD as S
#endif
import qualified Streamly.Internal.Data.Stream as Stream import qualified Streamly.Internal.Data.Stream as Stream
import Prelude hiding (take, takeWhile, drop, reverse, concatMap, map, zipWith) import Prelude hiding (take, takeWhile, drop, reverse, concatMap, map, zipWith)
@ -202,7 +197,7 @@ repeatM = K.repeatMWith IsStream.consM
{-# RULES "repeatM serial" repeatM = repeatMSerial #-} {-# RULES "repeatM serial" repeatM = repeatMSerial #-}
{-# INLINE repeatMSerial #-} {-# INLINE repeatMSerial #-}
repeatMSerial :: MonadAsync m => m a -> SerialT m a repeatMSerial :: MonadAsync m => m a -> SerialT m a
repeatMSerial = fromStreamS . S.repeatM repeatMSerial = fromStreamD . D.repeatM
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
-- Generation - Time related -- Generation - Time related
@ -298,7 +293,7 @@ foldContinue f s = D.foldContinue f $ IsStream.toStreamD s
-- Same as 'fmap'. -- Same as 'fmap'.
-- --
-- @ -- @
-- > S.toList $ S.map (+1) $ S.fromList [1,2,3] -- > D.toList $ D.map (+1) $ D.fromList [1,2,3]
-- [2,3,4] -- [2,3,4]
-- @ -- @
-- --
@ -397,7 +392,7 @@ smapM step initial stream =
-- @since 0.1.0 -- @since 0.1.0
{-# INLINE take #-} {-# INLINE take #-}
take :: (IsStream t, Monad m) => Int -> t m a -> t m a take :: (IsStream t, Monad m) => Int -> t m a -> t m a
take n m = fromStreamS $ S.take n $ toStreamS take n m = fromStreamD $ D.take n $ toStreamD
(maxYields (Just (fromIntegral n)) m) (maxYields (Just (fromIntegral n)) m)
-- | End the stream as soon as the predicate fails on an element. -- | End the stream as soon as the predicate fails on an element.
@ -405,7 +400,7 @@ take n m = fromStreamS $ S.take n $ toStreamS
-- @since 0.1.0 -- @since 0.1.0
{-# INLINE takeWhile #-} {-# INLINE takeWhile #-}
takeWhile :: (IsStream t, Monad m) => (a -> Bool) -> t m a -> t m a takeWhile :: (IsStream t, Monad m) => (a -> Bool) -> t m a -> t m a
takeWhile p m = fromStreamS $ S.takeWhile p $ toStreamS m takeWhile p m = fromStreamD $ D.takeWhile p $ toStreamD m
{-# INLINE takeEndBy #-} {-# INLINE takeEndBy #-}
takeEndBy :: (IsStream t, Monad m) => (a -> Bool) -> t m a -> t m a takeEndBy :: (IsStream t, Monad m) => (a -> Bool) -> t m a -> t m a
@ -416,7 +411,7 @@ takeEndBy p m = fromStreamD $ D.takeEndBy p $ toStreamD m
-- @since 0.1.0 -- @since 0.1.0
{-# INLINE drop #-} {-# INLINE drop #-}
drop :: (IsStream t, Monad m) => Int -> t m a -> t m a drop :: (IsStream t, Monad m) => Int -> t m a -> t m a
drop n m = fromStreamS $ S.drop n $ toStreamS m drop n m = fromStreamD $ D.drop n $ toStreamD m
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
-- Searching -- Searching
@ -430,7 +425,7 @@ drop n m = fromStreamS $ S.drop n $ toStreamS m
-- @since 0.5.0 -- @since 0.5.0
{-# INLINE findIndices #-} {-# INLINE findIndices #-}
findIndices :: (IsStream t, Monad m) => (a -> Bool) -> t m a -> t m Int findIndices :: (IsStream t, Monad m) => (a -> Bool) -> t m a -> t m Int
findIndices p m = fromStreamS $ S.findIndices p (toStreamS m) findIndices p m = fromStreamD $ D.findIndices p (toStreamD m)
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
-- Transformation by Inserting -- Transformation by Inserting
@ -454,7 +449,7 @@ findIndices p m = fromStreamS $ S.findIndices p (toStreamS m)
-- @since 0.5.0 -- @since 0.5.0
{-# INLINE intersperseM #-} {-# INLINE intersperseM #-}
intersperseM :: (IsStream t, MonadAsync m) => m a -> t m a -> t m a intersperseM :: (IsStream t, MonadAsync m) => m a -> t m a -> t m a
intersperseM m = fromStreamS . S.intersperseM m . toStreamS intersperseM m = fromStreamD . D.intersperseM m . toStreamD
-- | Intersperse a monadic action into the input stream after every @n@ -- | Intersperse a monadic action into the input stream after every @n@
-- seconds. -- seconds.
@ -493,7 +488,7 @@ interjectSuffix n f xs = xs `parallelFst` repeatM timed
-- /Since: 0.1.1/ -- /Since: 0.1.1/
{-# INLINE reverse #-} {-# INLINE reverse #-}
reverse :: (IsStream t, Monad m) => t m a -> t m a reverse :: (IsStream t, Monad m) => t m a -> t m a
reverse s = fromStreamS $ S.reverse $ toStreamS s reverse s = fromStreamD $ D.reverse $ toStreamD s
-- | Like 'reverse' but several times faster, requires a 'Storable' instance. -- | Like 'reverse' but several times faster, requires a 'Storable' instance.
-- --
@ -699,8 +694,8 @@ splitOnSeq patt f m =
{-# INLINE zipWithM #-} {-# INLINE zipWithM #-}
zipWithM :: (IsStream t, Monad m) => (a -> b -> m c) -> t m a -> t m b -> t m c zipWithM :: (IsStream t, Monad m) => (a -> b -> m c) -> t m a -> t m b -> t m c
zipWithM f m1 m2 = zipWithM f m1 m2 =
IsStream.fromStreamS IsStream.fromStreamD
$ S.zipWithM f (IsStream.toStreamS m1) (IsStream.toStreamS m2) $ D.zipWithM f (IsStream.toStreamD m1) (IsStream.toStreamD m2)
-- | Stream @a@ is evaluated first, followed by stream @b@, the resulting -- | Stream @a@ is evaluated first, followed by stream @b@, the resulting
-- elements @a@ and @b@ are then zipped using the supplied zip function and the -- elements @a@ and @b@ are then zipped using the supplied zip function and the
@ -710,7 +705,7 @@ zipWithM f m1 m2 =
-- first, the element @a@ from previous evaluation of stream @a@ is discarded. -- first, the element @a@ from previous evaluation of stream @a@ is discarded.
-- --
-- @ -- @
-- > S.toList $ S.zipWith (+) (S.fromList [1,2,3]) (S.fromList [4,5,6]) -- > D.toList $ D.zipWith (+) (D.fromList [1,2,3]) (D.fromList [4,5,6])
-- [5,7,9] -- [5,7,9]
-- @ -- @
-- --
@ -718,5 +713,5 @@ zipWithM f m1 m2 =
{-# INLINE zipWith #-} {-# INLINE zipWith #-}
zipWith :: (IsStream t, Monad m) => (a -> b -> c) -> t m a -> t m b -> t m c zipWith :: (IsStream t, Monad m) => (a -> b -> c) -> t m a -> t m b -> t m c
zipWith f m1 m2 = zipWith f m1 m2 =
IsStream.fromStreamS IsStream.fromStreamD
$ S.zipWith f (IsStream.toStreamS m1) (IsStream.toStreamS m2) $ D.zipWith f (IsStream.toStreamD m1) (IsStream.toStreamD m2)

View File

@ -163,7 +163,7 @@ import Streamly.Internal.Data.Stream.IsStream.Common
( fold, foldBreak, foldContinue, drop, findIndices, reverse, splitOnSeq ( fold, foldBreak, foldContinue, drop, findIndices, reverse, splitOnSeq
, take , takeWhile, mkParallel) , take , takeWhile, mkParallel)
import Streamly.Internal.Data.Stream.IsStream.Type import Streamly.Internal.Data.Stream.IsStream.Type
(IsStream, toStreamS, fromStreamD, toStreamD) (IsStream, toStreamD, fromStreamD, toStreamD)
import Streamly.Internal.Data.Stream.Serial (SerialT) import Streamly.Internal.Data.Stream.Serial (SerialT)
import Streamly.Internal.Data.Unboxed (Unboxed) import Streamly.Internal.Data.Unboxed (Unboxed)
@ -172,11 +172,6 @@ import qualified Streamly.Internal.Data.Fold as FL
import qualified Streamly.Internal.Data.Stream.IsStream.Type as IsStream import qualified Streamly.Internal.Data.Stream.IsStream.Type as IsStream
import qualified Streamly.Internal.Data.Stream.StreamD as D import qualified Streamly.Internal.Data.Stream.StreamD as D
import qualified Streamly.Internal.Data.Stream.StreamK.Type as K import qualified Streamly.Internal.Data.Stream.StreamK.Type as K
#ifdef USE_STREAMK_ONLY
import qualified Streamly.Internal.Data.Stream.StreamK as S
#else
import qualified Streamly.Internal.Data.Stream.StreamD as S
#endif
import qualified Streamly.Internal.Data.Stream as Stream import qualified Streamly.Internal.Data.Stream as Stream
import qualified System.IO as IO import qualified System.IO as IO
@ -240,7 +235,7 @@ uncons = fmap (fmap (fmap IsStream.fromStream)) . K.uncons . Stream.toStreamK
{-# INLINE foldr1 #-} {-# INLINE foldr1 #-}
{-# DEPRECATED foldr1 "Use foldrM instead." #-} {-# DEPRECATED foldr1 "Use foldrM instead." #-}
foldr1 :: Monad m => (a -> a -> a) -> SerialT m a -> m (Maybe a) foldr1 :: Monad m => (a -> a -> a) -> SerialT m a -> m (Maybe a)
foldr1 f m = S.foldr1 f (toStreamS m) foldr1 f m = D.foldr1 f (toStreamD m)
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
-- Left Folds -- Left Folds
@ -260,12 +255,12 @@ foldlS f z =
-- --
-- For example, to reverse a stream: -- For example, to reverse a stream:
-- --
-- > S.toList $ S.foldlT (flip S.cons) S.nil $ (S.fromList [1..5] :: SerialT IO Int) -- > D.toList $ D.foldlT (flip D.cons) D.nil $ (D.fromList [1..5] :: SerialT IO Int)
-- --
{-# INLINE foldlT #-} {-# INLINE foldlT #-}
foldlT :: (Monad m, IsStream t, Monad (s m), MonadTrans s) foldlT :: (Monad m, IsStream t, Monad (s m), MonadTrans s)
=> (s m b -> a -> s m b) -> s m b -> t m a -> s m b => (s m b -> a -> s m b) -> s m b -> t m a -> s m b
foldlT f z s = S.foldlT f z (toStreamS s) foldlT f z s = D.foldlT f z (toStreamD s)
-- | Strict left fold with an extraction function. Like the standard strict -- | Strict left fold with an extraction function. Like the standard strict
-- left fold, but applies a user supplied extraction function (the third -- left fold, but applies a user supplied extraction function (the third
@ -320,7 +315,7 @@ foldxM = IsStream.foldlMx'
-- /Since: 0.8.0 (signature change)/ -- /Since: 0.8.0 (signature change)/
{-# INLINE foldlM' #-} {-# INLINE foldlM' #-}
foldlM' :: Monad m => (b -> a -> m b) -> m b -> SerialT m a -> m b foldlM' :: Monad m => (b -> a -> m b) -> m b -> SerialT m a -> m b
foldlM' step begin = S.foldlM' step begin . IsStream.toStreamS foldlM' step begin = D.foldlM' step begin . IsStream.toStreamD
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
-- Running a sink -- Running a sink
@ -347,7 +342,7 @@ runSink = fold . toFold
-- @since 0.1.0 -- @since 0.1.0
{-# INLINE mapM_ #-} {-# INLINE mapM_ #-}
mapM_ :: Monad m => (a -> m b) -> SerialT m a -> m () mapM_ :: Monad m => (a -> m b) -> SerialT m a -> m ()
mapM_ f = S.mapM_ f . IsStream.toStreamS mapM_ f = D.mapM_ f . IsStream.toStreamD
-- | -- |
-- > drain = mapM_ (\_ -> return ()) -- > drain = mapM_ (\_ -> return ())
@ -422,7 +417,7 @@ runStream = drain
-- @since 0.1.1 -- @since 0.1.1
{-# INLINE null #-} {-# INLINE null #-}
null :: Monad m => SerialT m a -> m Bool null :: Monad m => SerialT m a -> m Bool
null = S.null . toStreamS null = D.null . toStreamD
-- | Extract the first element of the stream, if any. -- | Extract the first element of the stream, if any.
-- --
@ -432,7 +427,7 @@ null = S.null . toStreamS
-- @since 0.1.0 -- @since 0.1.0
{-# INLINE head #-} {-# INLINE head #-}
head :: Monad m => SerialT m a -> m (Maybe a) head :: Monad m => SerialT m a -> m (Maybe a)
head = S.head . toStreamS head = D.head . toStreamD
-- | Extract the first element of the stream, if any, otherwise use the -- | Extract the first element of the stream, if any, otherwise use the
-- supplied default value. It can help avoid one branch in high performance -- supplied default value. It can help avoid one branch in high performance
@ -468,7 +463,7 @@ init m = fmap (fmap IsStream.fromStream) $ K.init $ Stream.toStreamK m
-- @since 0.1.1 -- @since 0.1.1
{-# INLINE last #-} {-# INLINE last #-}
last :: Monad m => SerialT m a -> m (Maybe a) last :: Monad m => SerialT m a -> m (Maybe a)
last m = S.last $ toStreamS m last m = D.last $ toStreamD m
-- | Determine whether an element is present in the stream. -- | Determine whether an element is present in the stream.
-- --
@ -477,7 +472,7 @@ last m = S.last $ toStreamS m
-- @since 0.1.0 -- @since 0.1.0
{-# INLINE elem #-} {-# INLINE elem #-}
elem :: (Monad m, Eq a) => a -> SerialT m a -> m Bool elem :: (Monad m, Eq a) => a -> SerialT m a -> m Bool
elem e m = S.elem e (toStreamS m) elem e m = D.elem e (toStreamD m)
-- | Determine whether an element is not present in the stream. -- | Determine whether an element is not present in the stream.
-- --
@ -486,7 +481,7 @@ elem e m = S.elem e (toStreamS m)
-- @since 0.1.0 -- @since 0.1.0
{-# INLINE notElem #-} {-# INLINE notElem #-}
notElem :: (Monad m, Eq a) => a -> SerialT m a -> m Bool notElem :: (Monad m, Eq a) => a -> SerialT m a -> m Bool
notElem e m = S.notElem e (toStreamS m) notElem e m = D.notElem e (toStreamD m)
-- | Determine the length of the stream. -- | Determine the length of the stream.
-- --
@ -502,7 +497,7 @@ length = foldl' (\n _ -> n + 1) 0
-- @since 0.1.0 -- @since 0.1.0
{-# INLINE all #-} {-# INLINE all #-}
all :: Monad m => (a -> Bool) -> SerialT m a -> m Bool all :: Monad m => (a -> Bool) -> SerialT m a -> m Bool
all p m = S.all p (toStreamS m) all p m = D.all p (toStreamD m)
-- | Determine whether any of the elements of a stream satisfy a predicate. -- | Determine whether any of the elements of a stream satisfy a predicate.
-- --
@ -511,7 +506,7 @@ all p m = S.all p (toStreamS m)
-- @since 0.1.0 -- @since 0.1.0
{-# INLINE any #-} {-# INLINE any #-}
any :: Monad m => (a -> Bool) -> SerialT m a -> m Bool any :: Monad m => (a -> Bool) -> SerialT m a -> m Bool
any p m = S.any p (toStreamS m) any p m = D.any p (toStreamD m)
-- | Determines if all elements of a boolean stream are True. -- | Determines if all elements of a boolean stream are True.
-- --
@ -572,7 +567,7 @@ mconcat = Stream.foldr mappend mempty
-- @since 0.1.0 -- @since 0.1.0
{-# INLINE minimum #-} {-# INLINE minimum #-}
minimum :: (Monad m, Ord a) => SerialT m a -> m (Maybe a) minimum :: (Monad m, Ord a) => SerialT m a -> m (Maybe a)
minimum m = S.minimum (toStreamS m) minimum m = D.minimum (toStreamD m)
-- | Determine the minimum element in a stream using the supplied comparison -- | Determine the minimum element in a stream using the supplied comparison
-- function. -- function.
@ -582,7 +577,7 @@ minimum m = S.minimum (toStreamS m)
-- @since 0.6.0 -- @since 0.6.0
{-# INLINE minimumBy #-} {-# INLINE minimumBy #-}
minimumBy :: Monad m => (a -> a -> Ordering) -> SerialT m a -> m (Maybe a) minimumBy :: Monad m => (a -> a -> Ordering) -> SerialT m a -> m (Maybe a)
minimumBy cmp m = S.minimumBy cmp (toStreamS m) minimumBy cmp m = D.minimumBy cmp (toStreamD m)
-- | -- |
-- @ -- @
@ -595,7 +590,7 @@ minimumBy cmp m = S.minimumBy cmp (toStreamS m)
-- @since 0.1.0 -- @since 0.1.0
{-# INLINE maximum #-} {-# INLINE maximum #-}
maximum :: (Monad m, Ord a) => SerialT m a -> m (Maybe a) maximum :: (Monad m, Ord a) => SerialT m a -> m (Maybe a)
maximum m = S.maximum (toStreamS m) maximum m = D.maximum (toStreamD m)
-- | Determine the maximum element in a stream using the supplied comparison -- | Determine the maximum element in a stream using the supplied comparison
-- function. -- function.
@ -605,7 +600,7 @@ maximum m = S.maximum (toStreamS m)
-- @since 0.6.0 -- @since 0.6.0
{-# INLINE maximumBy #-} {-# INLINE maximumBy #-}
maximumBy :: Monad m => (a -> a -> Ordering) -> SerialT m a -> m (Maybe a) maximumBy :: Monad m => (a -> a -> Ordering) -> SerialT m a -> m (Maybe a)
maximumBy cmp m = S.maximumBy cmp (toStreamS m) maximumBy cmp m = D.maximumBy cmp (toStreamD m)
-- | Ensures that all the elements of the stream are identical and then returns -- | Ensures that all the elements of the stream are identical and then returns
-- that unique element. -- that unique element.
@ -613,7 +608,7 @@ maximumBy cmp m = S.maximumBy cmp (toStreamS m)
-- @since 0.6.0 -- @since 0.6.0
{-# INLINE the #-} {-# INLINE the #-}
the :: (Eq a, Monad m) => SerialT m a -> m (Maybe a) the :: (Eq a, Monad m) => SerialT m a -> m (Maybe a)
the m = S.the (toStreamS m) the m = D.the (toStreamD m)
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
-- Searching -- Searching
@ -624,7 +619,7 @@ the m = S.the (toStreamS m)
-- @since 0.6.0 -- @since 0.6.0
{-# INLINE (!!) #-} {-# INLINE (!!) #-}
(!!) :: Monad m => SerialT m a -> Int -> m (Maybe a) (!!) :: Monad m => SerialT m a -> Int -> m (Maybe a)
m !! i = toStreamS m S.!! i m !! i = toStreamD m D.!! i
-- | In a stream of (key-value) pairs @(a, b)@, return the value @b@ of the -- | In a stream of (key-value) pairs @(a, b)@, return the value @b@ of the
-- first pair where the key equals the given value @a@. -- first pair where the key equals the given value @a@.
@ -635,7 +630,7 @@ m !! i = toStreamS m S.!! i
-- @since 0.5.0 -- @since 0.5.0
{-# INLINE lookup #-} {-# INLINE lookup #-}
lookup :: (Monad m, Eq a) => a -> SerialT m (a, b) -> m (Maybe b) lookup :: (Monad m, Eq a) => a -> SerialT m (a, b) -> m (Maybe b)
lookup a m = S.lookup a (toStreamS m) lookup a m = D.lookup a (toStreamD m)
-- | Like 'findM' but with a non-monadic predicate. -- | Like 'findM' but with a non-monadic predicate.
-- --
@ -645,7 +640,7 @@ lookup a m = S.lookup a (toStreamS m)
-- @since 0.5.0 -- @since 0.5.0
{-# INLINE find #-} {-# INLINE find #-}
find :: Monad m => (a -> Bool) -> SerialT m a -> m (Maybe a) find :: Monad m => (a -> Bool) -> SerialT m a -> m (Maybe a)
find p m = S.find p (toStreamS m) find p m = D.find p (toStreamD m)
-- | Returns the first element that satisfies the given predicate. -- | Returns the first element that satisfies the given predicate.
-- --
@ -654,7 +649,7 @@ find p m = S.find p (toStreamS m)
-- @since 0.6.0 -- @since 0.6.0
{-# INLINE findM #-} {-# INLINE findM #-}
findM :: Monad m => (a -> m Bool) -> SerialT m a -> m (Maybe a) findM :: Monad m => (a -> m Bool) -> SerialT m a -> m (Maybe a)
findM p m = S.findM p (toStreamS m) findM p m = D.findM p (toStreamD m)
-- | Returns the first index that satisfies the given predicate. -- | Returns the first index that satisfies the given predicate.
-- --
@ -712,7 +707,7 @@ toListRev = D.toListRev . toStreamD
-- | -- |
-- @ -- @
-- toHandle h = S.mapM_ $ hPutStrLn h -- toHandle h = D.mapM_ $ hPutStrLn h
-- @ -- @
-- --
-- Write a stream of Strings to an IO Handle. -- Write a stream of Strings to an IO Handle.

View File

@ -763,7 +763,7 @@ mergeMinBy _f _m1 _m2 = undefined
mergeFstBy :: -- (IsStream t, Monad m) => mergeFstBy :: -- (IsStream t, Monad m) =>
(a -> a -> m Ordering) -> t m a -> t m a -> t m a (a -> a -> m Ordering) -> t m a -> t m a -> t m a
mergeFstBy _f _m1 _m2 = undefined mergeFstBy _f _m1 _m2 = undefined
-- fromStreamS $ D.mergeFstBy f (toStreamD m1) (toStreamD m2) -- fromStreamD $ D.mergeFstBy f (toStreamD m1) (toStreamD m2)
-- XXX we may want to use the name "merge" differently -- XXX we may want to use the name "merge" differently
-- | Same as @'mergeBy' 'compare'@. -- | Same as @'mergeBy' 'compare'@.

View File

@ -99,7 +99,7 @@ import Streamly.Internal.Data.Stream.IsStream.Common
( absTimesWith, concatM, relTimesWith, timesWith, fromPure, fromEffect ( absTimesWith, concatM, relTimesWith, timesWith, fromPure, fromEffect
, yield, yieldM, repeatM) , yield, yieldM, repeatM)
import Streamly.Internal.Data.Stream.IsStream.Type import Streamly.Internal.Data.Stream.IsStream.Type
(IsStream (..), fromSerial, consM, fromStreamD, fromStreamS) (IsStream (..), fromSerial, consM, fromStreamD)
import Streamly.Internal.Data.Stream.Serial (SerialT) import Streamly.Internal.Data.Stream.Serial (SerialT)
import Streamly.Internal.Data.Stream.WSerial (WSerialT) import Streamly.Internal.Data.Stream.WSerial (WSerialT)
import Streamly.Internal.Data.Stream.Zip (ZipSerialM) import Streamly.Internal.Data.Stream.Zip (ZipSerialM)
@ -112,12 +112,6 @@ import qualified Streamly.Internal.Data.Stream.Parallel as Par
import qualified Streamly.Internal.Data.Stream.Serial as Serial import qualified Streamly.Internal.Data.Stream.Serial as Serial
import qualified Streamly.Internal.Data.Stream.StreamD.Generate as D import qualified Streamly.Internal.Data.Stream.StreamD.Generate as D
import qualified Streamly.Internal.Data.Stream.StreamK.Type as K import qualified Streamly.Internal.Data.Stream.StreamK.Type as K
#ifdef USE_STREAMK_ONLY
import qualified Streamly.Internal.Data.Stream.StreamK as S
import qualified Streamly.Internal.Data.Stream.StreamK.Type as S
#else
import qualified Streamly.Internal.Data.Stream.StreamD.Generate as S
#endif
import qualified Streamly.Internal.Data.Stream.Type as Stream import qualified Streamly.Internal.Data.Stream.Type as Stream
import qualified System.IO as IO import qualified System.IO as IO
@ -187,9 +181,9 @@ unfold0 unf = unfold unf (error "unfold0: unexpected void evaluation")
-- @since 0.1.0 -- @since 0.1.0
{-# INLINE_EARLY unfoldr #-} {-# INLINE_EARLY unfoldr #-}
unfoldr :: (Monad m, IsStream t) => (b -> Maybe (a, b)) -> b -> t m a unfoldr :: (Monad m, IsStream t) => (b -> Maybe (a, b)) -> b -> t m a
unfoldr step seed = fromStreamS (S.unfoldr step seed) unfoldr step seed = fromStreamD (D.unfoldr step seed)
{-# RULES "unfoldr fallback to StreamK" [1] {-# RULES "unfoldr fallback to StreamK" [1]
forall a b. S.toStreamK (S.unfoldr a b) = K.unfoldr a b #-} forall a b. D.toStreamK (D.unfoldr a b) = K.unfoldr a b #-}
-- | Build a stream by unfolding a /monadic/ step function starting from a -- | Build a stream by unfolding a /monadic/ step function starting from a
-- seed. The step function returns the next element in the stream and the next -- seed. The step function returns the next element in the stream and the next
@ -253,7 +247,7 @@ unfoldrMZipSerial f = fromSerial . Serial.unfoldrM f
-- @since 0.4.0 -- @since 0.4.0
{-# INLINE_NORMAL repeat #-} {-# INLINE_NORMAL repeat #-}
repeat :: (IsStream t, Monad m) => a -> t m a repeat :: (IsStream t, Monad m) => a -> t m a
repeat = fromStreamS . S.repeat repeat = fromStreamD . D.repeat
-- | -- |
-- >>> replicate n = Stream.take n . Stream.repeat -- >>> replicate n = Stream.take n . Stream.repeat
@ -263,7 +257,7 @@ repeat = fromStreamS . S.repeat
-- @since 0.6.0 -- @since 0.6.0
{-# INLINE_NORMAL replicate #-} {-# INLINE_NORMAL replicate #-}
replicate :: (IsStream t, Monad m) => Int -> a -> t m a replicate :: (IsStream t, Monad m) => Int -> a -> t m a
replicate n = fromStreamS . S.replicate n replicate n = fromStreamD . D.replicate n
-- | -- |
-- >>> replicateM n = Stream.take n . Stream.repeatM -- >>> replicateM n = Stream.take n . Stream.repeatM
@ -297,7 +291,7 @@ replicateM count =
{-# RULES "replicateM serial" replicateM = replicateMSerial #-} {-# RULES "replicateM serial" replicateM = replicateMSerial #-}
{-# INLINE replicateMSerial #-} {-# INLINE replicateMSerial #-}
replicateMSerial :: MonadAsync m => Int -> m a -> SerialT m a replicateMSerial :: MonadAsync m => Int -> m a -> SerialT m a
replicateMSerial n = fromStreamS . S.replicateM n replicateMSerial n = fromStreamD . D.replicateM n
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
-- Time Enumeration -- Time Enumeration
@ -420,7 +414,7 @@ timeout = undefined
-- @since 0.6.0 -- @since 0.6.0
{-# INLINE fromIndices #-} {-# INLINE fromIndices #-}
fromIndices :: (IsStream t, Monad m) => (Int -> a) -> t m a fromIndices :: (IsStream t, Monad m) => (Int -> a) -> t m a
fromIndices = fromStreamS . S.fromIndices fromIndices = fromStreamD . D.fromIndices
-- --
-- | -- |
@ -441,7 +435,7 @@ fromIndicesM = fromStream . K.fromIndicesMWith (IsStream.toConsK (consM @t))
{-# RULES "fromIndicesM serial" fromIndicesM = fromIndicesMSerial #-} {-# RULES "fromIndicesM serial" fromIndicesM = fromIndicesMSerial #-}
{-# INLINE fromIndicesMSerial #-} {-# INLINE fromIndicesMSerial #-}
fromIndicesMSerial :: MonadAsync m => (Int -> m a) -> SerialT m a fromIndicesMSerial :: MonadAsync m => (Int -> m a) -> SerialT m a
fromIndicesMSerial = fromStreamS . S.fromIndicesM fromIndicesMSerial = fromStreamD . D.fromIndicesM
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
-- Iterating functions -- Iterating functions
@ -460,7 +454,7 @@ fromIndicesMSerial = fromStreamS . S.fromIndicesM
-- @since 0.1.2 -- @since 0.1.2
{-# INLINE_NORMAL iterate #-} {-# INLINE_NORMAL iterate #-}
iterate :: (IsStream t, Monad m) => (a -> a) -> a -> t m a iterate :: (IsStream t, Monad m) => (a -> a) -> a -> t m a
iterate step = fromStreamS . S.iterate step iterate step = fromStreamD . D.iterate step
-- | -- |
-- >>> iterateM f m = m >>= \a -> return a `Stream.consM` iterateM f (f a) -- >>> iterateM f m = m >>= \a -> return a `Stream.consM` iterateM f (f a)
@ -509,7 +503,7 @@ iterateM f = fromStream . K.iterateMWith (IsStream.toConsK (consM @t)) f
{-# RULES "iterateM serial" iterateM = iterateMSerial #-} {-# RULES "iterateM serial" iterateM = iterateMSerial #-}
{-# INLINE iterateMSerial #-} {-# INLINE iterateMSerial #-}
iterateMSerial :: MonadAsync m => (a -> m a) -> m a -> SerialT m a iterateMSerial :: MonadAsync m => (a -> m a) -> m a -> SerialT m a
iterateMSerial step = fromStreamS . S.iterateM step iterateMSerial step = fromStreamD . D.iterateM step
-- | We can define cyclic structures using @let@: -- | We can define cyclic structures using @let@:
-- --

View File

@ -29,15 +29,10 @@ import Control.Monad.Trans.State.Strict (StateT)
import Control.Monad.Trans.Class (MonadTrans(..)) import Control.Monad.Trans.Class (MonadTrans(..))
import Data.Functor.Identity (Identity (..)) import Data.Functor.Identity (Identity (..))
import Streamly.Internal.Data.Stream.IsStream.Type import Streamly.Internal.Data.Stream.IsStream.Type
(IsStream(..), fromStreamS, toStreamS, fromStreamD, toStreamD) (IsStream(..), fromStreamD, toStreamD)
import Streamly.Internal.Data.Stream.Serial (SerialT) import Streamly.Internal.Data.Stream.Serial (SerialT)
import qualified Streamly.Internal.Data.Stream.StreamD as D import qualified Streamly.Internal.Data.Stream.StreamD as D
#ifdef USE_STREAMK_ONLY
import qualified Streamly.Internal.Data.Stream.StreamK as S
#else
import qualified Streamly.Internal.Data.Stream.StreamD as S
#endif
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
-- Generalize the underlying monad -- Generalize the underlying monad
@ -50,7 +45,7 @@ import qualified Streamly.Internal.Data.Stream.StreamD as S
{-# INLINE hoist #-} {-# INLINE hoist #-}
hoist :: (Monad m, Monad n) hoist :: (Monad m, Monad n)
=> (forall x. m x -> n x) -> SerialT m a -> SerialT n a => (forall x. m x -> n x) -> SerialT m a -> SerialT n a
hoist f xs = fromStreamS $ S.hoist f (toStreamS xs) hoist f xs = fromStreamD $ D.hoist f (toStreamD xs)
-- | Generalize the inner monad of the stream from 'Identity' to any monad. -- | Generalize the inner monad of the stream from 'Identity' to any monad.
-- --
@ -58,7 +53,7 @@ hoist f xs = fromStreamS $ S.hoist f (toStreamS xs)
-- --
{-# INLINE generally #-} {-# INLINE generally #-}
generally :: (IsStream t, Monad m) => t Identity a -> t m a generally :: (IsStream t, Monad m) => t Identity a -> t m a
generally xs = fromStreamS $ S.hoist (return . runIdentity) (toStreamS xs) generally xs = fromStreamD $ D.hoist (return . runIdentity) (toStreamD xs)
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
-- Add and remove a monad transformer -- Add and remove a monad transformer

View File

@ -247,7 +247,7 @@ import Streamly.Internal.Data.Stream.IsStream.Common
) )
import Streamly.Internal.Control.Concurrent (MonadAsync) import Streamly.Internal.Control.Concurrent (MonadAsync)
import Streamly.Internal.Data.Stream.IsStream.Type import Streamly.Internal.Data.Stream.IsStream.Type
(IsStream(..), fromStreamS, toStreamS, fromStreamD, toStreamD, toConsK) (IsStream(..), fromStreamD, toStreamD, toConsK)
import Streamly.Internal.Data.Stream.Serial (SerialT) import Streamly.Internal.Data.Stream.Serial (SerialT)
import Streamly.Internal.Data.SVar (Rate(..)) import Streamly.Internal.Data.SVar (Rate(..))
import Streamly.Internal.Data.Time.Units (TimeUnit64, AbsTime, RelTime64) import Streamly.Internal.Data.Time.Units (TimeUnit64, AbsTime, RelTime64)
@ -257,11 +257,6 @@ import qualified Streamly.Internal.Data.Stream.Parallel as Par
import qualified Streamly.Internal.Data.Stream.Serial as Serial import qualified Streamly.Internal.Data.Stream.Serial as Serial
import qualified Streamly.Internal.Data.Stream.StreamD as D import qualified Streamly.Internal.Data.Stream.StreamD as D
import qualified Streamly.Internal.Data.Stream.StreamK.Type as K import qualified Streamly.Internal.Data.Stream.StreamK.Type as K
#ifdef USE_STREAMK_ONLY
import qualified Streamly.Internal.Data.Stream.StreamK as S
#else
import qualified Streamly.Internal.Data.Stream.StreamD as S
#endif
import qualified Prelude import qualified Prelude
import Prelude hiding import Prelude hiding
@ -359,7 +354,7 @@ foldrSShared f z xs =
{-# INLINE foldrT #-} {-# INLINE foldrT #-}
foldrT :: (IsStream t, Monad m, Monad (s m), MonadTrans s) foldrT :: (IsStream t, Monad m, Monad (s m), MonadTrans s)
=> (a -> s m b -> s m b) -> s m b -> t m a -> s m b => (a -> s m b -> s m b) -> s m b -> t m a -> s m b
foldrT f z s = S.foldrT f z (toStreamS s) foldrT f z s = D.foldrT f z (toStreamD s)
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
-- Transformation by Mapping -- Transformation by Mapping
@ -681,7 +676,7 @@ postscan fld = fromStreamD . D.postscanOnce fld . toStreamD
{-# DEPRECATED scanx "Please use scanl followed by map instead." #-} {-# DEPRECATED scanx "Please use scanl followed by map instead." #-}
{-# INLINE scanx #-} {-# INLINE scanx #-}
scanx :: (IsStream t, Monad m) => (x -> a -> x) -> x -> (x -> b) -> t m a -> t m b scanx :: (IsStream t, Monad m) => (x -> a -> x) -> x -> (x -> b) -> t m a -> t m b
scanx step begin done = fromStreamS . S.scanlx' step begin done . toStreamS scanx step begin done = fromStreamD . D.scanlx' step begin done . toStreamD
-- XXX this needs to be concurrent -- XXX this needs to be concurrent
-- XXX because of the use of D.cons for appending, scanlM' has quadratic -- XXX because of the use of D.cons for appending, scanlM' has quadratic
@ -760,7 +755,7 @@ scanlM' step begin m = fromStreamD $ D.scanlM' step begin $ toStreamD m
-- @since 0.2.0 -- @since 0.2.0
{-# INLINE scanl' #-} {-# INLINE scanl' #-}
scanl' :: (IsStream t, Monad m) => (b -> a -> b) -> b -> t m a -> t m b scanl' :: (IsStream t, Monad m) => (b -> a -> b) -> b -> t m a -> t m b
scanl' step z m = fromStreamS $ S.scanl' step z $ toStreamS m scanl' step z m = fromStreamD $ D.scanl' step z $ toStreamD m
-- | Like 'scanl'' but does not stream the initial value of the accumulator. -- | Like 'scanl'' but does not stream the initial value of the accumulator.
-- --
@ -841,7 +836,7 @@ with f comb g = fmap snd . comb g . f
-- @since 0.1.0 -- @since 0.1.0
{-# INLINE filter #-} {-# INLINE filter #-}
filter :: (IsStream t, Monad m) => (a -> Bool) -> t m a -> t m a filter :: (IsStream t, Monad m) => (a -> Bool) -> t m a -> t m a
filter p m = fromStreamS $ S.filter p $ toStreamS m filter p m = fromStreamD $ D.filter p $ toStreamD m
-- | Same as 'filter' but with a monadic predicate. -- | Same as 'filter' but with a monadic predicate.
-- --
@ -953,7 +948,7 @@ nubBy = undefined -- fromStreamD . D.nubBy . toStreamD
-- @since 0.6.0 -- @since 0.6.0
{-# INLINE deleteBy #-} {-# INLINE deleteBy #-}
deleteBy :: (IsStream t, Monad m) => (a -> a -> Bool) -> a -> t m a -> t m a deleteBy :: (IsStream t, Monad m) => (a -> a -> Bool) -> a -> t m a -> t m a
deleteBy cmp x m = fromStreamS $ S.deleteBy cmp x (toStreamS m) deleteBy cmp x m = fromStreamD $ D.deleteBy cmp x (toStreamD m)
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
-- Lossy Buffering -- Lossy Buffering
@ -1082,7 +1077,7 @@ takeInterval d = fromStreamD . D.takeByTime d . toStreamD
-- @since 0.1.0 -- @since 0.1.0
{-# INLINE dropWhile #-} {-# INLINE dropWhile #-}
dropWhile :: (IsStream t, Monad m) => (a -> Bool) -> t m a -> t m a dropWhile :: (IsStream t, Monad m) => (a -> Bool) -> t m a -> t m a
dropWhile p m = fromStreamS $ S.dropWhile p $ toStreamS m dropWhile p m = fromStreamD $ D.dropWhile p $ toStreamD m
-- | Same as 'dropWhile' but with a monadic predicate. -- | Same as 'dropWhile' but with a monadic predicate.
-- --
@ -1171,7 +1166,7 @@ dropWhileAround = undefined -- fromStreamD $ D.dropWhileAround n $ toStreamD m
{-# INLINE insertBy #-} {-# INLINE insertBy #-}
insertBy :: insertBy ::
(IsStream t, Monad m) => (a -> a -> Ordering) -> a -> t m a -> t m a (IsStream t, Monad m) => (a -> a -> Ordering) -> a -> t m a -> t m a
insertBy cmp x m = fromStreamS $ S.insertBy cmp x (toStreamS m) insertBy cmp x m = fromStreamD $ D.insertBy cmp x (toStreamD m)
-- | Insert a pure value between successive elements of a stream. -- | Insert a pure value between successive elements of a stream.
-- --
@ -1181,7 +1176,7 @@ insertBy cmp x m = fromStreamS $ S.insertBy cmp x (toStreamS m)
-- @since 0.7.0 -- @since 0.7.0
{-# INLINE intersperse #-} {-# INLINE intersperse #-}
intersperse :: (IsStream t, MonadAsync m) => a -> t m a -> t m a intersperse :: (IsStream t, MonadAsync m) => a -> t m a -> t m a
intersperse a = fromStreamS . S.intersperse a . toStreamS intersperse a = fromStreamD . D.intersperse a . toStreamD
-- | Insert a side effect before consuming an element of a stream except the -- | Insert a side effect before consuming an element of a stream except the
-- first one. -- first one.
@ -1503,7 +1498,7 @@ rollingMap2 f m = fromStreamD $ D.rollingMap2 f $ toStreamD m
-- @since 0.3.0 -- @since 0.3.0
{-# INLINE mapMaybe #-} {-# INLINE mapMaybe #-}
mapMaybe :: (IsStream t, Monad m) => (a -> Maybe b) -> t m a -> t m b mapMaybe :: (IsStream t, Monad m) => (a -> Maybe b) -> t m a -> t m b
mapMaybe f m = fromStreamS $ S.mapMaybe f $ toStreamS m mapMaybe f m = fromStreamD $ D.mapMaybe f $ toStreamD m
-- | Like 'mapMaybe' but maps a monadic function. -- | Like 'mapMaybe' but maps a monadic function.
-- --

View File

@ -17,8 +17,6 @@ module Streamly.Internal.Data.Stream.IsStream.Type
, K.Stream (..) , K.Stream (..)
-- * Type Conversion -- * Type Conversion
, fromStreamS
, toStreamS
, fromStreamD , fromStreamD
, toStreamD , toStreamD
, adapt , adapt
@ -121,12 +119,6 @@ import qualified Streamly.Internal.Data.Stream.Serial as Serial
import qualified Streamly.Internal.Data.Stream.WSerial as WSerial import qualified Streamly.Internal.Data.Stream.WSerial as WSerial
import qualified Streamly.Internal.Data.Stream.StreamD.Type as D import qualified Streamly.Internal.Data.Stream.StreamD.Type as D
import qualified Streamly.Internal.Data.Stream.StreamK.Type as K import qualified Streamly.Internal.Data.Stream.StreamK.Type as K
#ifdef USE_STREAMK_ONLY
import qualified Streamly.Internal.Data.Stream.StreamK as S
import qualified Streamly.Internal.Data.Stream.StreamK.Type as S
#else
import qualified Streamly.Internal.Data.Stream.StreamD.Type as S
#endif
import qualified Streamly.Internal.Data.Stream.Type as Stream import qualified Streamly.Internal.Data.Stream.Type as Stream
import qualified Streamly.Internal.Data.Stream.Zip as Zip import qualified Streamly.Internal.Data.Stream.Zip as Zip
import qualified Streamly.Internal.Data.Stream.ZipAsync as ZipAsync import qualified Streamly.Internal.Data.Stream.ZipAsync as ZipAsync
@ -230,15 +222,6 @@ toConsK cns x xs = toStream $ x `cns` fromStream xs
-- Conversion to and from direct style stream -- Conversion to and from direct style stream
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
-- These definitions are dependent on what is imported as S
{-# INLINE fromStreamS #-}
fromStreamS :: (IsStream t, Monad m) => S.Stream m a -> t m a
fromStreamS = fromStream . S.toStreamK
{-# INLINE toStreamS #-}
toStreamS :: (IsStream t, Monad m) => t m a -> S.Stream m a
toStreamS = S.fromStreamK . toStream
{-# INLINE toStreamD #-} {-# INLINE toStreamD #-}
toStreamD :: (IsStream t, Monad m) => t m a -> D.Stream m a toStreamD :: (IsStream t, Monad m) => t m a -> D.Stream m a
toStreamD = D.fromStreamK . toStream toStreamD = D.fromStreamK . toStream
@ -289,16 +272,16 @@ cmpBy f m1 m2 = D.cmpBy f (toStreamD m1) (toStreamD m2)
-- @since 0.4.0 -- @since 0.4.0
{-# INLINE_EARLY fromList #-} {-# INLINE_EARLY fromList #-}
fromList :: (Monad m, IsStream t) => [a] -> t m a fromList :: (Monad m, IsStream t) => [a] -> t m a
fromList = fromStreamS . S.fromList fromList = fromStreamD . D.fromList
{-# RULES "fromList fallback to StreamK" [1] {-# RULES "fromList fallback to StreamK" [1]
forall a. S.toStreamK (S.fromList a) = K.fromFoldable a #-} forall a. D.toStreamK (D.fromList a) = K.fromFoldable a #-}
-- | Convert a stream into a list in the underlying monad. -- | Convert a stream into a list in the underlying monad.
-- --
-- @since 0.1.0 -- @since 0.1.0
{-# INLINE toList #-} {-# INLINE toList #-}
toList :: (IsStream t, Monad m) => t m a -> m [a] toList :: (IsStream t, Monad m) => t m a -> m [a]
toList m = S.toList $ toStreamS m toList m = D.toList $ toStreamD m
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
-- Building a stream -- Building a stream
@ -364,7 +347,7 @@ foldrMx step final project m = D.foldrMx step final project $ toStreamD m
foldlMx' :: foldlMx' ::
(IsStream t, Monad m) (IsStream t, Monad m)
=> (x -> a -> m x) -> m x -> (x -> m b) -> t m a -> m b => (x -> a -> m x) -> m x -> (x -> m b) -> t m a -> m b
foldlMx' step begin done m = S.foldlMx' step begin done $ toStreamS m foldlMx' step begin done m = D.foldlMx' step begin done $ toStreamD m
-- | Strict left fold with an extraction function. Like the standard strict -- | Strict left fold with an extraction function. Like the standard strict
-- left fold, but applies a user supplied extraction function (the third -- left fold, but applies a user supplied extraction function (the third
@ -375,7 +358,7 @@ foldlMx' step begin done m = S.foldlMx' step begin done $ toStreamS m
{-# INLINE foldlx' #-} {-# INLINE foldlx' #-}
foldlx' :: foldlx' ::
(IsStream t, Monad m) => (x -> a -> x) -> x -> (x -> b) -> t m a -> m b (IsStream t, Monad m) => (x -> a -> x) -> x -> (x -> b) -> t m a -> m b
foldlx' step begin done m = S.foldlx' step begin done $ toStreamS m foldlx' step begin done m = D.foldlx' step begin done $ toStreamD m
-- | Strict left associative fold. -- | Strict left associative fold.
-- --
@ -383,12 +366,12 @@ foldlx' step begin done m = S.foldlx' step begin done $ toStreamS m
{-# INLINE foldl' #-} {-# INLINE foldl' #-}
foldl' :: foldl' ::
(IsStream t, Monad m) => (b -> a -> b) -> b -> t m a -> m b (IsStream t, Monad m) => (b -> a -> b) -> b -> t m a -> m b
foldl' step begin m = S.foldl' step begin $ toStreamS m foldl' step begin m = D.foldl' step begin $ toStreamD m
{-# INLINE fold #-} {-# INLINE fold #-}
fold :: (IsStream t, Monad m) => Fold m a b -> t m a -> m b fold :: (IsStream t, Monad m) => Fold m a b -> t m a -> m b
fold fld m = S.fold fld $ toStreamS m fold fld m = D.fold fld $ toStreamD m
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
-- Folding a stream -- Folding a stream
@ -746,8 +729,8 @@ concatMapFoldableWith f g = Prelude.foldr (f . g) nil
-- Equivalent to: -- Equivalent to:
-- --
-- @ -- @
-- concatForFoldableWith f xs g = Prelude.foldr (f . g) S.nil xs -- concatForFoldableWith f xs g = Prelude.foldr (f . g) D.nil xs
-- concatForFoldableWith f = flip (S.concatMapFoldableWith f) -- concatForFoldableWith f = flip (D.concatMapFoldableWith f)
-- @ -- @
-- --
-- /Since: 0.8.0 (Renamed forEachWith to concatForFoldableWith)/ -- /Since: 0.8.0 (Renamed forEachWith to concatForFoldableWith)/
@ -766,8 +749,8 @@ concatForFoldableWith f = flip (concatMapFoldableWith f)
-- Equivalent to: -- Equivalent to:
-- --
-- @ -- @
-- concatFoldableWith f = Prelude.foldr f S.nil -- concatFoldableWith f = Prelude.foldr f D.nil
-- concatFoldableWith f = S.concatMapFoldableWith f id -- concatFoldableWith f = D.concatMapFoldableWith f id
-- @ -- @
-- --
-- /Since: 0.8.0 (Renamed foldWith to concatFoldableWith)/ -- /Since: 0.8.0 (Renamed foldWith to concatFoldableWith)/

View File

@ -9,7 +9,7 @@
-- --
-- {-# INLINE_EARLY unfoldr #-} -- {-# INLINE_EARLY unfoldr #-}
-- unfoldr :: (Monad m, IsStream t) => (b -> Maybe (a, b)) -> b -> t m a -- unfoldr :: (Monad m, IsStream t) => (b -> Maybe (a, b)) -> b -> t m a
-- unfoldr step seed = fromStreamS (S.unfoldr step seed) -- unfoldr step seed = fromStreamD (S.unfoldr step seed)
-- {-# RULES "unfoldr fallback to StreamK" [1] -- {-# RULES "unfoldr fallback to StreamK" [1]
-- forall a b. S.toStreamK (S.unfoldr a b) = K.unfoldr a b #-}``` -- forall a b. S.toStreamK (S.unfoldr a b) = K.unfoldr a b #-}```
-- --

View File

@ -285,11 +285,6 @@ flag has-llvm
manual: True manual: True
default: False default: False
flag streamk
description: Use CPS style streams when possible
manual: True
default: False
flag use-c-malloc flag use-c-malloc
description: Use C malloc instead of GHC malloc description: Use C malloc instead of GHC malloc
manual: True manual: True
@ -321,9 +316,6 @@ common compile-options
if os(windows) if os(windows)
cpp-options: -DCABAL_OS_WINDOWS cpp-options: -DCABAL_OS_WINDOWS
if flag(streamk)
cpp-options: -DUSE_STREAMK_ONLY
if flag(dev) if flag(dev)
cpp-options: -DDEVBUILD cpp-options: -DDEVBUILD