Fix examples in code to work with doctest.

This commit is contained in:
Pranay Sashank 2021-02-04 23:57:59 +05:30
parent c88b23e119
commit da906ce49d
20 changed files with 583 additions and 397 deletions

View File

@ -62,7 +62,7 @@ module Streamly.Data.Fold
-- A 'Fold' can be run over a stream using the 'Streamly.Prelude.fold'
-- combinator:
--
-- >>> S.fold FL.sum (S.enumerateFromTo 1 100)
-- >>> Stream.fold Fold.sum (Stream.enumerateFromTo 1 100)
-- 5050
Fold -- (..)
@ -123,7 +123,7 @@ module Streamly.Data.Fold
-- Transformations can be applied either on the input side or on the output
-- side. The 'Functor' instance of a fold maps on the output of the fold:
--
-- >>> S.fold (fmap show FL.sum) (S.enumerateFromTo 1 100)
-- >>> Stream.fold (fmap show Fold.sum) (Stream.enumerateFromTo 1 100)
-- "5050"
--
-- Note: Output transformations are also known as covariant
@ -199,16 +199,16 @@ module Streamly.Data.Fold
-- To compute the average of numbers in a stream without going through the
-- stream twice:
--
-- >>> let avg = (/) <$> FL.sum <*> fmap fromIntegral FL.length
-- >>> S.fold avg (S.enumerateFromTo 1.0 100.0)
-- >>> let avg = (/) <$> Fold.sum <*> fmap fromIntegral Fold.length
-- >>> Stream.fold avg (Stream.enumerateFromTo 1.0 100.0)
-- 50.5
--
-- The 'Semigroup' and 'Monoid' instances of a distributing fold distribute
-- the input to both the folds and combines the outputs using Monoid or
-- Semigroup instances of the output types:
--
-- >>> import Data.Monoid (Sum)
-- >>> S.fold (FL.head <> FL.last) (fmap Sum $ S.enumerateFromTo 1.0 100.0)
-- >>> import Data.Monoid (Sum(..))
-- >>> Stream.fold (Fold.head <> Fold.last) (fmap Sum $ Stream.enumerateFromTo 1.0 100.0)
-- Just (Sum {getSum = 101.0})
--
-- The 'Num', 'Floating', and 'Fractional' instances work in the same way.
@ -265,3 +265,10 @@ import Prelude
span, splitAt, break, mapM)
import Streamly.Internal.Data.Fold
--
-- $setup
-- >>> :m
-- >>> import Prelude hiding (head, sum, last, length)
-- >>> import qualified Streamly.Prelude as Stream
-- >>> import qualified Streamly.Data.Fold as Fold

View File

@ -117,6 +117,12 @@ import Data.Semigroup (Semigroup(..))
import qualified Data.Foldable as F
#endif
--
-- $setup
-- >>> :m
-- >>> import Prelude hiding (length, foldr, read, unlines, splitAt)
-- >>> import Streamly.Internal.Data.Array.Foreign as Array
-------------------------------------------------------------------------------
-- Array Data Type
-------------------------------------------------------------------------------
@ -230,11 +236,12 @@ fromPtr n ptr = MA.unsafeInlineIO $ do
-- characters that can be encoded in a byte i.e. characters or literal bytes in
-- the range from 0-255.
--
-- >>> fromAddr# 5 "hello world!"#
-- > [104,101,108,108,111]
-- >>> import Data.Word (Word8)
-- >>> Array.fromAddr# 5 "hello world!"# :: Array Word8
-- [104,101,108,108,111]
--
-- >>> fromAddr# 3 "\255\NUL\255"#
-- > [255,0,255]
-- >>> Array.fromAddr# 3 "\255\NUL\255"# :: Array Word8
-- [255,0,255]
--
-- /See also: 'fromString#'/
--
@ -262,11 +269,11 @@ fromAddr# n addr# = fromPtr n (castPtr $ Ptr addr#)
-- of bytes terminated by a NUL byte (a 'CString') corresponding to the
-- given unicode string.
--
-- >>> fromCString# "hello world!"#
-- > [104,101,108,108,111,32,119,111,114,108,100,33]
-- >>> Array.fromCString# "hello world!"#
-- [104,101,108,108,111,32,119,111,114,108,100,33]
--
-- >>> fromCString# "\255\NUL\255"#
-- > [255]
-- >>> Array.fromCString# "\255\NUL\255"#
-- [255]
--
-- /See also: 'fromAddr#'/
--

View File

@ -254,6 +254,15 @@ import Prelude hiding
, span, splitAt, break, mapM, zip)
import Streamly.Internal.Data.Fold.Types
-- $setup
-- >>> :m
-- >>> import Prelude hiding (break, map, span, splitAt)
-- >>> import qualified Streamly.Prelude as Stream
-- >>> import qualified Streamly.Internal.Data.Stream.IsStream as Stream (parse, foldMany)
-- >>> import qualified Streamly.Data.Fold as Fold
-- >>> import qualified Streamly.Internal.Data.Fold as Fold
-- >>> import qualified Streamly.Internal.Data.Parser as Parser
------------------------------------------------------------------------------
-- hoist
------------------------------------------------------------------------------
@ -327,7 +336,7 @@ mapM = rmapM
-- >>> f x = if even x then Just x else Nothing
-- >>> fld = Fold.mapMaybe f Fold.toList
-- >>> Stream.fold fld (Stream.enumerateFromTo 1 10)
-- [2,4,6,8]
-- [2,4,6,8,10]
--
-- /Internal/
{-# INLINE mapMaybe #-}
@ -847,7 +856,7 @@ null = mkFold (\() _ -> Done False) (Partial ()) (const True)
-- | Returns 'True' if any of the elements of a stream satisfies a predicate.
--
-- >>> Stream.fold (Fold.any (== 0)) $ Stream.fromList [1,0,1]
-- > True
-- True
--
-- @since 0.7.0
{-# INLINE any #-}
@ -879,7 +888,7 @@ elem a = any (a ==)
-- | Returns 'True' if all elements of a stream satisfy a predicate.
--
-- >>> Stream.fold (Fold.all (== 0)) $ Stream.fromList [1,0,1]
-- > False
-- False
--
-- @since 0.7.0
{-# INLINABLE all #-}
@ -942,25 +951,25 @@ or = any (== True)
-- elements of its input are consumed by fold @f1@ and the rest of the stream
-- is consumed by fold @f2@.
--
-- > let splitAt_ n xs = S.fold (FL.splitAt n FL.toList FL.toList) $ S.fromList xs
-- >>> let splitAt_ n xs = Stream.fold (Fold.splitAt n Fold.toList Fold.toList) $ Stream.fromList xs
--
-- >>> splitAt_ 6 "Hello World!"
-- > ("Hello ","World!")
-- ("Hello ","World!")
--
-- >>> splitAt_ (-1) [1,2,3]
-- > ([],[1,2,3])
-- ([],[1,2,3])
--
-- >>> splitAt_ 0 [1,2,3]
-- > ([],[1,2,3])
-- ([],[1,2,3])
--
-- >>> splitAt_ 1 [1,2,3]
-- > ([1],[2,3])
-- ([1],[2,3])
--
-- >>> splitAt_ 3 [1,2,3]
-- > ([1,2,3],[])
-- ([1,2,3],[])
--
-- >>> splitAt_ 4 [1,2,3]
-- > ([1,2,3],[])
-- ([1,2,3],[])
--
-- > splitAt n f1 f2 = splitWith (,) (takeLE n f1) f2
--
@ -1009,9 +1018,9 @@ splitAt n fld = splitWith (,) (takeLE n fld)
--
-- Let's use the following definition for illustration:
--
-- > splitOn p = Stream.foldMany (Fold.sliceSepBy pred Fold.toList)
-- > splitOn' p = Stream.toList . splitOn p . Stream.fromList
--
-- >>> splitOn p = Stream.foldMany (Fold.sliceSepBy pred Fold.toList)
-- >>> splitOn' p = Stream.toList . splitOn p . Stream.fromList
-- >>> splitOn' (== '.') ""
-- [""]
--
@ -1019,16 +1028,16 @@ splitAt n fld = splitWith (,) (takeLE n fld)
-- ["",""]
--
-- >>> splitOn' (== '.') ".a"
-- > ["","a"]
-- ["","a"]
--
-- >>> splitOn' (== '.') "a."
-- > ["a",""]
-- ["a",""]
--
-- >>> splitOn' (== '.') "a.b"
-- > ["a","b"]
-- ["a","b"]
--
-- >>> splitOn' (== '.') "a..b"
-- > ["a","","b"]
-- ["a","","b"]
--
-- Stops - when the predicate succeeds.
--
@ -1102,7 +1111,7 @@ breakOn pat f m = undefined
-- ---stream m a---| |---m (b,c)
-- |-------Fold m a c--------|
-- @
-- >>> S.fold (FL.tee FL.sum FL.length) (S.enumerateFromTo 1.0 100.0)
-- >>> Stream.fold (Fold.tee Fold.sum Fold.length) (Stream.enumerateFromTo 1.0 100.0)
-- (5050.0,100)
--
-- @since 0.7.0
@ -1126,7 +1135,7 @@ tee = teeWith (,)
-- ...
-- @
--
-- >>> S.fold (FL.distribute [FL.sum, FL.length]) (S.enumerateFromTo 1 5)
-- >>> Stream.fold (Fold.distribute [Fold.sum, Fold.length]) (Stream.enumerateFromTo 1 5)
-- [15,5]
--
-- This is the consumer side dual of the producer side 'sequence' operation.
@ -1154,10 +1163,12 @@ distribute = foldr (teeWith (:)) (yield [])
--
-- Send input to either fold randomly:
--
-- >>> import System.Random (randomIO)
-- >>> randomly a = randomIO >>= \x -> return $ if x then Left a else Right a
-- >>> S.fold (FL.partitionByM randomly FL.length FL.length) (S.enumerateFromTo 1 100)
-- @
-- > import System.Random (randomIO)
-- > randomly a = randomIO >>= \\x -> return $ if x then Left a else Right a
-- > Stream.fold (Fold.partitionByM randomly Fold.length Fold.length) (Stream.enumerateFromTo 1 100)
-- (59,41)
-- @
--
-- Send input to the two folds in a proportion of 2:1:
--
@ -1279,13 +1290,13 @@ partitionByMinM = undefined
--
-- Count even and odd numbers in a stream:
--
-- @
-- >>> let f = FL.partitionBy (\\n -> if even n then Left n else Right n)
-- (fmap (("Even " ++) . show) FL.length)
-- (fmap (("Odd " ++) . show) FL.length)
-- in S.fold f (S.enumerateFromTo 1 100)
-- >>> :{
-- let f = Fold.partitionBy (\n -> if even n then Left n else Right n)
-- (fmap (("Even " ++) . show) Fold.length)
-- (fmap (("Odd " ++) . show) Fold.length)
-- in Stream.fold f (Stream.enumerateFromTo 1 100)
-- :}
-- ("Even 50","Odd 50")
-- @
--
-- @since 0.7.0
{-# INLINE partitionBy #-}
@ -1355,12 +1366,13 @@ demuxWith f kv = fmap fst $ demuxDefaultWith f kv drain
-- key into a map from keys to the results of fold outputs of the corresponding
-- values.
--
-- @
-- > let table = Data.Map.fromList [(\"SUM", FL.sum), (\"PRODUCT", FL.product)]
-- input = S.fromList [(\"SUM",1),(\"PRODUCT",2),(\"SUM",3),(\"PRODUCT",4)]
-- in S.fold (FL.demux table) input
-- >>> import qualified Data.Map
-- >>> :{
-- let table = Data.Map.fromList [("SUM", Fold.sum), ("PRODUCT", Fold.product)]
-- input = Stream.fromList [("SUM",1),("PRODUCT",2),("SUM",3),("PRODUCT",4)]
-- in Stream.fold (Fold.demux table) input
-- :}
-- fromList [("PRODUCT",8),("SUM",4)]
-- @
--
-- @since 0.7.0
{-# INLINE demux #-}
@ -1505,11 +1517,11 @@ demuxDefault = demuxDefaultWith id
-- given fold. Useful for map/reduce, bucketizing the input in different bins
-- or for generating histograms.
--
-- @
-- > let input = S.fromList [(\"ONE",1),(\"ONE",1.1),(\"TWO",2), (\"TWO",2.2)]
-- in S.fold (FL.classify FL.toList) input
-- fromList [(\"ONE",[1.1,1.0]),(\"TWO",[2.2,2.0])]
-- @
-- >>> :{
-- let input = Stream.fromList [("ONE",1),("ONE",1.1),("TWO",2), ("TWO",2.2)]
-- in Stream.fold (Fold.classifyWith fst (Fold.map snd Fold.toList)) input
-- :}
-- fromList [("ONE",[1.0,1.1]),("TWO",[2.0,2.2])]
--
-- If the classifier fold stops for a particular key any further inputs in that
-- bucket are ignored.
@ -1564,14 +1576,14 @@ classifyWith f (Fold step1 initial1 extract1) = mkAccumM step initial extract
-- the values belonging to each key. Useful for map/reduce, bucketizing the
-- input in different bins or for generating histograms.
--
-- @
-- > let input = S.fromList [(\"ONE",1),(\"ONE",1.1),(\"TWO",2), (\"TWO",2.2)]
-- in S.fold (FL.classify FL.toList) input
-- fromList [(\"ONE",[1.1,1.0]),(\"TWO",[2.2,2.0])]
-- @
-- >>> :{
-- let input = Stream.fromList [("ONE",1),("ONE",1.1),("TWO",2), ("TWO",2.2)]
-- in Stream.fold (Fold.classify Fold.toList) input
-- :}
-- fromList [("ONE",[1.0,1.1]),("TWO",[2.0,2.2])]
--
-- @since 0.7.0
--
-- Same as:
--
-- > classify fld = classifyWith fst (map snd fld)

View File

@ -247,6 +247,13 @@ import Streamly.Internal.Data.SVar (MonadAsync)
import Prelude hiding (concatMap, filter, map)
-- $setup
-- >>> :m
-- >>> import Prelude hiding (concatMap, filter, map)
-- >>> import qualified Streamly.Prelude as Stream
-- >>> import qualified Streamly.Data.Fold as Fold
-- >>> import qualified Streamly.Internal.Data.Fold as Fold
------------------------------------------------------------------------------
-- Monadic left folds
------------------------------------------------------------------------------
@ -693,7 +700,8 @@ data ConcatMapState m sa a c
--
-- Compare with 'Monad' instance method '>>='.
--
-- >>> Stream.fold (concatMap (flip Fold.takeLE Fold.sum) (Fold.rmapM (return . fromJust) Fold.head)) $ Stream.fromList [10,9..1]
-- >>> import Data.Maybe (fromJust)
-- >>> Stream.fold (Fold.concatMap (flip Fold.takeLE Fold.sum) (Fold.rmapM (return . fromJust) Fold.head)) $ Stream.fromList [10,9..1]
-- 45
--
-- /Internal/
@ -848,7 +856,7 @@ instance (Monad m, Floating b) => Floating (Fold m a b) where
-- | @(map f fold)@ maps the function @f@ on the input of the fold.
--
-- >>> S.fold (FL.map (\x -> x * x) FL.sum) (S.enumerateFromTo 1 100)
-- >>> Stream.fold (Fold.map (\x -> x * x) Fold.sum) (Stream.enumerateFromTo 1 100)
-- 338350
--
-- __Note__: This is not the same as 'fmap'. @map@ is contravariant where as
@ -876,9 +884,12 @@ lmapM f (Fold step begin done) = Fold step' begin done
-- | Include only those elements that pass a predicate.
--
-- >>> S.fold (filter (> 5) FL.sum) [1..10]
-- >>> Stream.fold (Fold.filter (> 5) Fold.sum) $ Stream.fromList [1..10]
-- 40
--
-- >>> Stream.fold (Fold.filter (< 5) Fold.sum) $ Stream.fromList [1..10]
-- 10
--
-- @since 0.7.0
{-# INLINABLE filter #-}
filter :: Monad m => (a -> Bool) -> Fold m a r -> Fold m a r

View File

@ -206,6 +206,15 @@ import qualified Streamly.Internal.Data.Fold.Types as FL
import qualified Streamly.Internal.Data.Parser.ParserD as D
import qualified Streamly.Internal.Data.Parser.ParserK.Types as K
--
-- $setup
-- >>> :m
-- >>> import Prelude hiding (any, all, take, takeWhile, sequence, concatMap, maybe, either)
-- >>> import qualified Streamly.Prelude as Stream
-- >>> import qualified Streamly.Internal.Data.Stream.IsStream as Stream (parse, parseMany)
-- >>> import qualified Streamly.Data.Fold as Fold
-- >>> import qualified Streamly.Internal.Data.Parser as Parser
-------------------------------------------------------------------------------
-- Upgrade folds to parses
-------------------------------------------------------------------------------
@ -276,7 +285,7 @@ dieM = K.toParserK . D.dieM
-- | Peek the head element of a stream, without consuming it. Fails if it
-- encounters end of input.
--
-- >>> S.parse ((,) <$> PR.peek <*> PR.satisfy (> 0)) $ S.fromList [1]
-- >>> Stream.parse ((,) <$> Parser.peek <*> Parser.satisfy (> 0)) $ Stream.fromList [1]
-- (1,1)
--
-- @
@ -291,8 +300,8 @@ peek = K.toParserK D.peek
-- | Succeeds if we are at the end of input, fails otherwise.
--
-- >>> S.parse ((,) <$> PR.satisfy (> 0) <*> PR.eof) $ S.fromList [1]
-- > (1,())
-- >>> Stream.parse ((,) <$> Parser.satisfy (> 0) <*> Parser.eof) $ Stream.fromList [1]
-- (1,())
--
-- /Internal/
--
@ -302,8 +311,8 @@ eof = K.toParserK D.eof
-- | Returns the next element if it passes the predicate, fails otherwise.
--
-- >>> S.parse (PR.satisfy (== 1)) $ S.fromList [1,0,1]
-- > 1
-- >>> Stream.parse (Parser.satisfy (== 1)) $ Stream.fromList [1,0,1]
-- 1
--
-- /Internal/
--
@ -344,24 +353,27 @@ either = K.toParserK . D.either
-- Examples: -
--
-- @
-- takeBetween' low high ls = S.parse prsr (S.fromList ls)
-- where prsr = P.takeBetween low high FL.toList
-- >>> :{
-- takeBetween' low high ls = Stream.parse prsr (Stream.fromList ls)
-- where prsr = Parser.takeBetween low high Fold.toList
-- :}
--
-- @
--
-- >>> takeBetween' 2 4 [1, 2, 3, 4, 5]
-- > [1,2,3,4]
-- [1,2,3,4]
--
-- >>> takeBetween' 2 4 [1, 2]
-- > [1,2]
-- [1,2]
--
-- >>> takeBetween' 2 4 [1]
-- > ParseError "takeBetween: Expecting alteast 2 elements, got 1"
-- *** Exception: ParseError "takeBetween: Expecting alteast 2 elements, got 1"
--
-- >>> takeBetween' 0 0 [1, 2]
-- > []
-- []
--
-- >>> takeBetween' 0 1 []
-- > []
-- []
--
-- @takeBetween@ is the most general take operation, other take operations can
-- be defined in terms of takeBetween. For example:
@ -386,8 +398,8 @@ takeBetween m n = K.toParserK . D.takeBetween m n
-- * Fails - if the stream or the collecting fold ends before it can collect
-- exactly @n@ elements.
--
-- >>> S.parse (PR.takeEQ 4 FL.toList) $ S.fromList [1,0,1]
-- > "takeEQ: Expecting exactly 4 elements, got 3"
-- >>> Stream.parse (Parser.takeEQ 4 Fold.toList) $ Stream.fromList [1,0,1]
-- *** Exception: ParseError "takeEQ: Expecting exactly 4 elements, input terminated on 3"
--
-- /Internal/
--
@ -401,11 +413,11 @@ takeEQ n = K.toParserK . D.takeEQ n
-- * Fails - if the stream or the collecting fold ends before producing @n@
-- elements.
--
-- >>> S.parse (PR.takeGE 4 FL.toList) $ S.fromList [1,0,1]
-- > "takeGE: Expecting at least 4 elements, got only 3"
-- >>> Stream.parse (Parser.takeGE 4 Fold.toList) $ Stream.fromList [1,0,1]
-- *** Exception: ParseError "takeGE: Expecting at least 4 elements, input terminated on 3"
--
-- >>> S.parse (PR.takeGE 4 FL.toList) $ S.fromList [1,0,1,0,1]
-- > [1,0,1,0,1]
-- >>> Stream.parse (Parser.takeGE 4 Fold.toList) $ Stream.fromList [1,0,1,0,1]
-- [1,0,1,0,1]
--
-- /Internal/
--
@ -443,8 +455,8 @@ takeWhileP _cond = undefined -- K.toParserK . D.takeWhileP cond
-- * Stops - when the predicate fails or the collecting fold stops.
-- * Fails - never.
--
-- >>> S.parse (PR.takeWhile (== 0) FL.toList) $ S.fromList [0,0,1,0,1]
-- > [0,0]
-- >>> Stream.parse (Parser.takeWhile (== 0) Fold.toList) $ Stream.fromList [0,0,1,0,1]
-- [0,0]
--
-- We can implement a @breakOn@ using 'takeWhile':
--
@ -518,22 +530,24 @@ sliceSepWith _cond = undefined -- K.toParserK . D.sliceSepBy cond
--
-- Examples: -
--
-- @
-- sliceBeginWithOdd ls = S.parse prsr (S.fromList ls)
-- where prsr = P.sliceBeginWith odd FL.toList
-- @
-- >>> :{
-- sliceBeginWithOdd ls = Stream.parse prsr (Stream.fromList ls)
-- where prsr = Parser.sliceBeginWith odd Fold.toList
-- :}
--
--
-- >>> sliceBeginWithOdd [2, 4, 6, 3]
-- > [2,4,6]
-- *** Exception: sliceBeginWith : slice begins with an element which fails the predicate
-- ...
--
-- >>> sliceBeginWithOdd [3, 5, 7, 4]
-- > [3]
-- [3]
--
-- >>> sliceBeginWithOdd [3, 4, 6, 8, 5]
-- > [3,4,6,8]
-- [3,4,6,8]
--
-- >>> sliceBeginWithOdd []
-- > []
-- []
--
-- /Internal/
--
@ -560,17 +574,20 @@ escapedSliceSepBy _cond _esc = undefined
--
-- For example,
--
-- >>> escapedFrameBy (== '{') (== '}') (== '\\') S.toList $ S.fromList "{hello}"
-- > "hello"
-- @
-- > Stream.parse (Parser.escapedFrameBy (== '{') (== '}') (== '\\') Fold.toList) $ Stream.fromList "{hello}"
-- "hello"
--
-- >>> escapedFrameBy (== '{') (== '}') (== '\\') S.toList $ S.fromList "{hello {world}}"
-- > "hello world"
-- > Stream.parse (Parser.escapedFrameBy (== '{') (== '}') (== '\\') Fold.toList) $ Stream.fromList "{hello {world}}"
-- "hello world"
--
-- >>> escapedFrameBy (== '{') (== '}') (== '\\') S.toList $ S.fromList "{hello \\{world\\}}"
-- > "hello {world}"
-- > Stream.parse (Parser.escapedFrameBy (== '{') (== '}') (== '\\') Fold.toList) $ Stream.fromList "{hello \\{world\\}}"
-- "hello {world}"
--
-- >>> escapedFrameBy (== '{') (== '}') (== '\\') S.toList $ S.fromList "{hello {world}"
-- > ParseError "Unterminated '{'"
-- > Stream.parse (Parser.escapedFrameBy (== '{') (== '}') (== '\\') Fold.toList) $ Stream.fromList "{hello {world}"
-- ParseError "Unterminated '{'"
--
-- @
--
-- /Unimplemented/
{-# INLINABLE escapedFrameBy #-}
@ -605,10 +622,12 @@ wordBy f = K.toParserK . D.wordBy f
-- * Stops - when the comparison fails.
-- * Fails - never.
--
-- > runGroupsBy eq =
-- > Stream.toList
-- > . Stream.parseMany (groupBy eq Fold.toList)
-- > . Stream.fromList
-- >>> :{
-- runGroupsBy eq =
-- Stream.toList
-- . Stream.parseMany (Parser.groupBy eq Fold.toList)
-- . Stream.fromList
-- :}
--
-- >>> runGroupsBy (<) []
-- []
@ -617,7 +636,7 @@ wordBy f = K.toParserK . D.wordBy f
-- [[1]]
--
-- >>> runGroupsBy (<) [3, 5, 4, 1, 2, 0]
-- [[3, 5, 4], [1, 2], [0]]
-- [[3,5,4],[1,2],[0]]
--
-- /Internal/
--
@ -637,10 +656,12 @@ groupBy eq = K.toParserK . D.groupBy eq
-- * Stops - when the comparison fails.
-- * Fails - never.
--
-- > runGroupsByRolling eq =
-- > Stream.toList
-- > . Stream.parseMany (groupByRolling eq Fold.toList)
-- > . Stream.fromList
-- >>> :{
-- runGroupsByRolling eq =
-- Stream.toList
-- . Stream.parseMany (Parser.groupByRolling eq Fold.toList)
-- . Stream.fromList
-- :}
--
-- >>> runGroupsByRolling (<) []
-- []
@ -649,7 +670,7 @@ groupBy eq = K.toParserK . D.groupBy eq
-- [[1]]
--
-- >>> runGroupsByRolling (<) [3, 5, 4, 1, 2, 0]
-- [[3, 5], [4], [1, 2], [0]]
-- [[3,5],[4],[1,2],[0]]
--
-- /Internal/
--
@ -659,10 +680,10 @@ groupByRolling eq = K.toParserK . D.groupByRolling eq
-- | Match the given sequence of elements using the given comparison function.
--
-- >>> S.parse $ S.eqBy (==) "string" $ S.fromList "string"
-- >>> Stream.parse (Parser.eqBy (==) "string") $ Stream.fromList "string"
--
-- >>> S.parse $ S.eqBy (==) "mismatch" $ S.fromList "match"
-- > *** Exception: ParseError "eqBy: failed, yet to match 7 elements"
-- >>> Stream.parse (Parser.eqBy (==) "mismatch") $ Stream.fromList "match"
-- *** Exception: ParseError "eqBy: failed, yet to match 7 elements"
--
-- /Internal/
--
@ -687,7 +708,9 @@ eqBy cmp = K.toParserK . D.eqBy cmp
-- This implementation is strict in the second argument, therefore, the
-- following will fail:
--
-- >>> S.parse (PR.splitWith const (PR.satisfy (> 0)) undefined) $ S.fromList [1]
-- >>> Stream.parse (Parser.splitWith const (Parser.satisfy (> 0)) undefined) $ Stream.fromList [1]
-- *** Exception: Prelude.undefined
-- ...
--
-- Compare with 'Applicative' instance method '<*>'. This implementation allows
-- stream fusion but has quadratic complexity. This can fuse with other
@ -729,7 +752,9 @@ splitWith f p1 p2 =
-- This implementation is strict in the second argument, therefore, the
-- following will fail:
--
-- >>> S.parse (split_ (PR.satisfy (> 0)) undefined) $ S.fromList [1]
-- >>> Stream.parse (Parser.split_ (Parser.satisfy (> 0)) undefined) $ Stream.fromList [1]
-- *** Exception: Prelude.undefined
-- ...
--
-- Compare with 'Applicative' instance method '*>'. This implementation allows
-- stream fusion but has quadratic complexity. This can fuse with other
@ -783,7 +808,8 @@ teeWithMin f p1 p2 =
-- Note: This implementation is not lazy in the second argument. The following
-- will fail:
--
-- >>> S.parse (PR.satisfy (> 0) `PR.alt` undefined) $ S.fromList [1..10]
-- >>> Stream.parse (Parser.satisfy (> 0) `Parser.alt` undefined) $ Stream.fromList [1..10]
-- 1
--
-- Compare with 'Alternative' instance method '<|>'. This implementation allows
-- stream fusion but has quadratic complexity. This can fuse with other

View File

@ -172,6 +172,15 @@ import Prelude hiding
import Streamly.Internal.Data.Parser.ParserD.Tee
import Streamly.Internal.Data.Parser.ParserD.Types
--
-- $setup
-- >>> :m
-- >>> import Prelude hiding ()
-- >>> import qualified Streamly.Prelude as Stream
-- >>> import qualified Streamly.Internal.Data.Stream.IsStream as Stream
-- >>> import qualified Streamly.Data.Fold as Fold
-- >>> import qualified Streamly.Internal.Data.Parser as Parser
-------------------------------------------------------------------------------
-- Upgrade folds to parses
-------------------------------------------------------------------------------
@ -571,7 +580,7 @@ sliceBeginWith cond (Fold fstep finitial fextract) =
step (Left' s) a =
if cond a
then process s a
else error $ "sliceBeginWith : slice begins with an element which"
else error $ "sliceBeginWith : slice begins with an element which "
++ "fails the predicate"
step (Right' s) a =
if not (cond a)
@ -739,16 +748,19 @@ eqBy cmp str = Parser step initial extract
-- input as long as the predicate @p@ is 'True'. @f2@ consumes the rest of the
-- input.
--
-- > let span_ p xs = S.parse (FL.span p FL.toList FL.toList) $ S.fromList xs
-- @
-- > let span_ p xs = Stream.parse (Parser.span p Fold.toList Fold.toList) $ Stream.fromList xs
--
-- >>> span_ (< 1) [1,2,3]
-- > ([],[1,2,3])
-- > span_ (< 1) [1,2,3]
-- ([],[1,2,3])
--
-- >>> span_ (< 2) [1,2,3]
-- > ([1],[2,3])
-- > span_ (< 2) [1,2,3]
-- ([1],[2,3])
--
-- >>> span_ (< 4) [1,2,3]
-- > ([1,2,3],[])
-- > span_ (< 4) [1,2,3]
-- ([1,2,3],[])
--
-- @
--
-- /Internal/
{-# INLINE span #-}

View File

@ -142,6 +142,14 @@ import Streamly.Internal.Data.Tuple.Strict (Tuple3'(..))
import qualified Streamly.Internal.Data.Fold.Types as FL
import Prelude hiding (concatMap)
--
-- $setup
-- >>> :m
-- >>> import Control.Applicative ((<|>))
-- >>> import Prelude hiding (concatMap)
-- >>> import qualified Streamly.Prelude as Stream
-- >>> import qualified Streamly.Internal.Data.Stream.IsStream as Stream (parse)
-- >>> import qualified Streamly.Internal.Data.Parser as Parser
-- | The return type of a 'Parser' step.
--
@ -634,7 +642,8 @@ dieM err =
-- Note: The implementation of '<|>' is not lazy in the second
-- argument. The following code will fail:
--
-- >>> S.parse (PR.satisfy (> 0) <|> undefined) $ S.fromList [1..10]
-- >>> Stream.parse (Parser.satisfy (> 0) <|> undefined) $ Stream.fromList [1..10]
-- 1
--
instance MonadCatch m => Alternative (Parser m a) where
{-# INLINE empty #-}

View File

@ -74,6 +74,15 @@ import qualified Streamly.Internal.Data.Stream.StreamD as S
import Prelude hiding (take, takeWhile, drop, reverse)
--
-- $setup
-- >>> :m
-- >>> import Prelude hiding (take, takeWhile, drop, reverse)
-- >>> import qualified Streamly.Prelude as Stream
-- >>> import Streamly.Internal.Data.Stream.IsStream as Stream
-- >>> import qualified Streamly.Data.Fold as Fold
-- >>> import qualified Streamly.Data.Array.Foreign as Array
------------------------------------------------------------------------------
-- Generation
------------------------------------------------------------------------------
@ -112,7 +121,7 @@ yield = K.yield
-- Create a singleton stream from a monadic action.
--
-- @
-- > toList $ yieldM getLine
-- > Stream.toList $ Stream.yieldM getLine
-- hello
-- ["hello"]
-- @
@ -159,12 +168,12 @@ repeatMSerial = fromStreamS . S.repeatM
-- A lower granularity clock gives higher precision but is more expensive in
-- terms of CPU usage. Any granularity lower than 1 ms is treated as 1 ms.
--
-- @
-- >>> S.mapM_ (\x -> print x >> threadDelay 1000000) $ S.timesWith 0.01
-- > (AbsTime (TimeSpec {sec = 2496295, nsec = 536223000}),RelTime64 (NanoSecond64 0))
-- > (AbsTime (TimeSpec {sec = 2496295, nsec = 536223000}),RelTime64 (NanoSecond64 1002028000))
-- > (AbsTime (TimeSpec {sec = 2496295, nsec = 536223000}),RelTime64 (NanoSecond64 1996656000))
-- @
-- >>> import Control.Concurrent (threadDelay)
-- >>> import Streamly.Internal.Data.Stream.IsStream.Common as Stream (timesWith)
-- >>> Stream.mapM_ (\x -> print x >> threadDelay 1000000) $ Stream.take 3 $ Stream.timesWith 0.01
-- (AbsTime (TimeSpec {sec = ..., nsec = ...}),RelTime64 (NanoSecond64 ...))
-- (AbsTime (TimeSpec {sec = ..., nsec = ...}),RelTime64 (NanoSecond64 ...))
-- (AbsTime (TimeSpec {sec = ..., nsec = ...}),RelTime64 (NanoSecond64 ...))
--
-- Note: This API is not safe on 32-bit machines.
--
@ -179,9 +188,10 @@ timesWith g = fromStreamD $ D.times g
-- expensive in terms of CPU usage. Any granularity lower than 1 ms is treated
-- as 1 ms.
--
-- @
-- >>> S.mapM_ print $ S.delayPre 1 $ S.absTimesWith 0.01
-- @
-- >>> Stream.mapM_ print $ Stream.delayPre 1 $ Stream.take 3 $ absTimesWith 0.01
-- AbsTime (TimeSpec {sec = ..., nsec = ...})
-- AbsTime (TimeSpec {sec = ..., nsec = ...})
-- AbsTime (TimeSpec {sec = ..., nsec = ...})
--
-- Note: This API is not safe on 32-bit machines.
--
@ -197,12 +207,10 @@ absTimesWith = fmap (uncurry addToAbsTime64) . timesWith
-- clock is more expensive in terms of CPU usage. Any granularity lower than 1
-- ms is treated as 1 ms.
--
-- @
-- >>> S.mapM_ print $ S.delayPre 1 $ S.relTimesWith 0.01
-- > RelTime64 (NanoSecond64 0)
-- > RelTime64 (NanoSecond64 91139000)
-- > RelTime64 (NanoSecond64 204052000)
-- @
-- >>> Stream.mapM_ print $ Stream.delayPre 1 $ Stream.take 3 $ Stream.relTimesWith 0.01
-- RelTime64 (NanoSecond64 ...)
-- RelTime64 (NanoSecond64 ...)
-- RelTime64 (NanoSecond64 ...)
--
-- Note: This API is not safe on 32-bit machines.
--
@ -222,7 +230,7 @@ relTimesWith = fmap snd . timesWith
-- 'Fold' can terminate early without consuming the full stream. See the
-- documentation of individual 'Fold's for termination behavior.
--
-- >>> S.fold FL.sum (S.enumerateFromTo 1 100)
-- >>> Stream.fold Fold.sum (Stream.enumerateFromTo 1 100)
-- 5050
--
-- @fold f = parse (Parser.fromFold f)@
@ -368,10 +376,8 @@ findIndices p m = fromStreamS $ S.findIndices p (toStreamS m)
-- | Insert an effect and its output before consuming an element of a stream
-- except the first one.
--
-- @
-- >>> S.toList $ S.trace putChar $ S.intersperseM (putChar '.' >> return ',') $ S.fromList "hello"
-- > h.,e.,l.,l.,o"h,e,l,l,o"
-- @
-- >>> Stream.toList $ Stream.trace putChar $ Stream.intersperseM (putChar '.' >> return ',') $ Stream.fromList "hello"
-- h.,e.,l.,l.,o"h,e,l,l,o"
--
-- @since 0.5.0
{-# INLINE intersperseM #-}
@ -382,8 +388,9 @@ intersperseM m = fromStreamS . S.intersperseM m . toStreamS
-- seconds.
--
-- @
-- > S.drain $ S.interjectSuffix 1 (putChar ',') $ S.mapM (\\x -> threadDelay 1000000 >> putChar x) $ S.fromList "hello"
-- "h,e,l,l,o"
-- > import Control.Concurrent (threadDelay)
-- > Stream.drain $ Stream.interjectSuffix 1 (putChar ',') $ Stream.mapM (\x -> threadDelay 1000000 >> putChar x) $ Stream.fromList "hello"
-- h,e,l,l,o
-- @
--
-- /Internal/
@ -463,36 +470,34 @@ concatM generator = concatMapM (\() -> generator) (yield ())
--
-- For illustration, let's define a function that operates on pure lists:
--
-- @
-- splitOnSeq' pat xs = S.toList $ S.splitOnSeq (A.fromList pat) (FL.toList) (S.fromList xs)
-- @
-- >>> splitOnSeq' pat xs = Stream.toList $ Stream.splitOnSeq (Array.fromList pat) Fold.toList (Stream.fromList xs)
--
-- >>> splitOnSeq' "" "hello"
-- > ["h","e","l","l","o"]
-- ["h","e","l","l","o"]
--
-- >>> splitOnSeq' "hello" ""
-- > [""]
-- [""]
--
-- >>> splitOnSeq' "hello" "hello"
-- > ["",""]
-- ["",""]
--
-- >>> splitOnSeq' "x" "hello"
-- > ["hello"]
-- ["hello"]
--
-- >>> splitOnSeq' "h" "hello"
-- > ["","ello"]
-- ["","ello"]
--
-- >>> splitOnSeq' "o" "hello"
-- > ["hell",""]
-- ["hell",""]
--
-- >>> splitOnSeq' "e" "hello"
-- > ["h","llo"]
-- ["h","llo"]
--
-- >>> splitOnSeq' "l" "hello"
-- > ["he","","o"]
-- ["he","","o"]
--
-- >>> splitOnSeq' "ll" "hello"
-- > ["he","o"]
-- ["he","o"]
--
-- 'splitOnSeq' is an inverse of 'intercalate'. The following law always holds:
--

View File

@ -177,6 +177,13 @@ import Prelude hiding
, null , reverse, init, and, or, lookup, foldr1, (!!) , splitAt, break
, mconcat)
-- $setup
-- >>> :m
-- >>> import qualified Streamly.Prelude as Stream
-- >>> import qualified Streamly.Internal.Data.Stream.IsStream as Stream (parse)
-- >>> import qualified Streamly.Internal.Data.Parser as Parser
-- >>> import qualified Streamly.Data.Fold as Fold
------------------------------------------------------------------------------
-- Deconstruction
------------------------------------------------------------------------------
@ -212,8 +219,8 @@ uncons m = K.uncons (K.adapt m)
--
-- Example, determine if any element is 'odd' in a stream:
--
-- >>> S.foldrM (\x xs -> if odd x then return True else xs) (return False) $ S.fromList (2:4:5:undefined)
-- > True
-- >>> Stream.foldrM (\x xs -> if odd x then return True else xs) (return False) $ Stream.fromList (2:4:5:undefined)
-- True
--
-- /Since: 0.7.0 (signature changed)/
--

View File

@ -116,13 +116,24 @@ import qualified System.IO as IO
import Prelude hiding (iterate, replicate, repeat)
-- $setup
-- >>> :m
-- >>> import Prelude hiding (iterate, replicate, repeat)
-- >>> import qualified Streamly.Prelude as Stream
-- >>> import qualified Streamly.Internal.Data.Stream.IsStream as Stream
-- >>> import qualified Streamly.Internal.Data.Unfold as Unfold
-- >>> import Control.Concurrent (threadDelay)
------------------------------------------------------------------------------
-- From Unfold
------------------------------------------------------------------------------
-- | Convert an 'Unfold' into a stream by supplying it an input seed.
--
-- >>> unfold (UF.replicateM 10) (putStrLn "hello")
-- >>> Stream.drain $ Stream.unfold (Unfold.replicateM 3) (putStrLn "hello")
-- hello
-- hello
-- hello
--
-- /Since: 0.7.0/
{-# INLINE unfold #-}
@ -278,12 +289,10 @@ replicateMSerial n = fromStreamS . S.replicateM n
-- (epoch) denoting the start of the stream and the second component is a time
-- relative to the reference.
--
-- @
-- >>> S.mapM_ (\x -> print x >> threadDelay 1000000) $ S.times
-- > (AbsTime (TimeSpec {sec = 2496295, nsec = 536223000}),RelTime64 (NanoSecond64 0))
-- > (AbsTime (TimeSpec {sec = 2496295, nsec = 536223000}),RelTime64 (NanoSecond64 1002028000))
-- > (AbsTime (TimeSpec {sec = 2496295, nsec = 536223000}),RelTime64 (NanoSecond64 1996656000))
-- @
-- >>> Stream.mapM_ (\x -> print x >> threadDelay 1000000) $ Stream.take 3 $ Stream.times
-- (AbsTime (TimeSpec {sec = ..., nsec = ...}),RelTime64 (NanoSecond64 ...))
-- (AbsTime (TimeSpec {sec = ..., nsec = ...}),RelTime64 (NanoSecond64 ...))
-- (AbsTime (TimeSpec {sec = ..., nsec = ...}),RelTime64 (NanoSecond64 ...))
--
-- Note: This API is not safe on 32-bit machines.
--
@ -296,9 +305,10 @@ times = timesWith 0.01
-- | @absTimes@ returns a stream of absolute timestamps using a clock of 10 ms
-- granularity.
--
-- @
-- >>> S.mapM_ print $ S.delayPre 1 $ S.absTimes
-- @
-- >>> Stream.mapM_ print $ Stream.delayPre 1 $ Stream.take 3 $ Stream.absTimes
-- AbsTime (TimeSpec {sec = ..., nsec = ...})
-- AbsTime (TimeSpec {sec = ..., nsec = ...})
-- AbsTime (TimeSpec {sec = ..., nsec = ...})
--
-- Note: This API is not safe on 32-bit machines.
--
@ -317,9 +327,10 @@ currentTime = absTimesWith
-- | @relTimes@ returns a stream of relative time values starting from 0,
-- using a clock of granularity 10 ms.
--
-- @
-- >>> S.mapM_ print $ S.delayPre 1 $ S.relTimes
-- @
-- >>> Stream.mapM_ print $ Stream.delayPre 1 $ Stream.take 3 $ Stream.relTimes
-- RelTime64 (NanoSecond64 ...)
-- RelTime64 (NanoSecond64 ...)
-- RelTime64 (NanoSecond64 ...)
--
-- Note: This API is not safe on 32-bit machines.
--
@ -386,10 +397,8 @@ timeout = undefined
-- Generate an infinite stream, whose values are the output of a function @f@
-- applied on the corresponding index. Index starts at 0.
--
-- @
-- > Stream.toList $ Stream.take 5 $ Stream.fromIndices id
-- >>> Stream.toList $ Stream.take 5 $ Stream.fromIndices id
-- [0,1,2,3,4]
-- @
--
-- @since 0.6.0
{-# INLINE fromIndices #-}

View File

@ -303,6 +303,17 @@ import qualified Streamly.Internal.Data.Stream.StreamD as S
import Prelude hiding (zipWith, concatMap, concat)
-- $setup
-- >>> :m
-- >>> import Prelude hiding (zipWith, concatMap, concat)
-- >>> import qualified Streamly.Prelude as Stream
-- >>> import Streamly.Internal.Data.Stream.IsStream as Stream
-- >>> import qualified Streamly.Data.Fold as Fold
-- >>> import qualified Streamly.Internal.Data.Fold as Fold
-- >>> import qualified Streamly.Internal.Data.Unfold as Unfold
-- >>> import qualified Streamly.Internal.Data.Parser as Parser
-- >>> import qualified Streamly.Data.Array.Foreign as Array
-------------------------------------------------------------------------------
-- Appending
-------------------------------------------------------------------------------
@ -339,9 +350,10 @@ append m1 m2 = fromStreamD $ D.append (toStreamD m1) (toStreamD m2)
-- early the other stream continues alone until it too finishes.
--
-- >>> :set -XOverloadedStrings
-- >>> interleave "ab" ",,,," :: SerialT Identity Char
-- >>> import Data.Functor.Identity (Identity)
-- >>> Stream.interleave "ab" ",,,," :: Stream.SerialT Identity Char
-- fromList "a,b,,,"
-- >>> interleave "abcd" ",," :: SerialT Identity Char
-- >>> Stream.interleave "abcd" ",," :: Stream.SerialT Identity Char
-- fromList "a,b,cd"
--
-- 'interleave' is dual to 'interleaveMin', it can be called @interleaveMax@.
@ -361,9 +373,10 @@ interleave m1 m2 = fromStreamD $ D.interleave (toStreamD m1) (toStreamD m2)
-- still continues to yield elements until it finishes.
--
-- >>> :set -XOverloadedStrings
-- >>> interleaveSuffix "abc" ",,,," :: SerialT Identity Char
-- >>> import Data.Functor.Identity (Identity)
-- >>> Stream.interleaveSuffix "abc" ",,,," :: Stream.SerialT Identity Char
-- fromList "a,b,c,"
-- >>> interleaveSuffix "abc" "," :: SerialT Identity Char
-- >>> Stream.interleaveSuffix "abc" "," :: Stream.SerialT Identity Char
-- fromList "a,bc"
--
-- 'interleaveSuffix' is a dual of 'interleaveInfix'.
@ -384,9 +397,10 @@ interleaveSuffix m1 m2 =
-- has finished.
--
-- >>> :set -XOverloadedStrings
-- >>> interleaveInfix "abc" ",,,," :: SerialT Identity Char
-- >>> import Data.Functor.Identity (Identity)
-- >>> Stream.interleaveInfix "abc" ",,,," :: Stream.SerialT Identity Char
-- fromList "a,b,c"
-- >>> interleaveInfix "abc" "," :: SerialT Identity Char
-- >>> Stream.interleaveInfix "abc" "," :: Stream.SerialT Identity Char
-- fromList "a,bc"
--
-- 'interleaveInfix' is a dual of 'interleaveSuffix'.
@ -406,9 +420,10 @@ interleaveInfix m1 m2 =
-- stream.
--
-- >>> :set -XOverloadedStrings
-- >>> interleaveMin "ab" ",,,," :: SerialT Identity Char
-- >>> import Data.Functor.Identity (Identity)
-- >>> Stream.interleaveMin "ab" ",,,," :: Stream.SerialT Identity Char
-- fromList "a,b,"
-- >>> interleaveMin "abcd" ",," :: SerialT Identity Char
-- >>> Stream.interleaveMin "abcd" ",," :: Stream.SerialT Identity Char
-- fromList "a,b,c"
--
-- 'interleaveMin' is dual to 'interleave'.
@ -453,8 +468,9 @@ roundrobin m1 m2 = fromStreamD $ D.roundRobin (toStreamD m1) (toStreamD m2)
-- also remain sorted in ascending order.
--
-- @
-- > S.toList $ S.mergeBy compare (S.fromList [1,3,5]) (S.fromList [2,4,6,8])
-- >>> Stream.toList $ Stream.mergeBy compare (Stream.fromList [1,3,5]) (Stream.fromList [2,4,6,8])
-- [1,2,3,4,5,6,8]
--
-- @
--
-- @since 0.6.0
@ -763,10 +779,10 @@ gintercalate unf1 str1 unf2 str2 =
--
-- | 'intersperse' followed by unfold and concat.
--
-- > unwords = intercalate " " UF.fromList
-- > unwords = intercalate " " Unfold.fromList
--
-- >>> intercalate " " UF.fromList ["abc", "def", "ghi"]
-- > "abc def ghi"
-- >>> Stream.toList $ Stream.intercalate " " Unfold.fromList $ Stream.fromList ["abc", "def", "ghi"]
-- "abc def ghi"
--
-- /Internal/
{-# INLINE intercalate #-}
@ -792,10 +808,10 @@ gintercalateSuffix unf1 str1 unf2 str2 =
--
-- | 'intersperseSuffix' followed by unfold and concat.
--
-- > unlines = intercalateSuffix "\n" UF.fromList
-- > unlines = intercalateSuffix "\n" Unfold.fromList
--
-- >>> intercalate "\n" UF.fromList ["abc", "def", "ghi"]
-- > "abc\ndef\nghi\n"
-- >>> Stream.toList $ Stream.intercalateSuffix "\n" Unfold.fromList $ Stream.fromList ["abc", "def", "ghi"]
-- "abc\ndef\nghi\n"
--
-- /Internal/
{-# INLINE intercalateSuffix #-}
@ -932,11 +948,11 @@ iterateMapLeftsWith combine f = iterateMapWith combine (either f (const K.nil))
--
-- >>> f = Fold.takeLE 2 Fold.sum
-- >>> Stream.toList $ Stream.foldManyPost f $ Stream.fromList []
-- > [0]
-- [0]
-- >>> Stream.toList $ Stream.foldManyPost f $ Stream.fromList [1..9]
-- > [3,7,11,15,9]
-- [3,7,11,15,9]
-- >>> Stream.toList $ Stream.foldManyPost f $ Stream.fromList [1..10]
-- > [3,7,11,15,19,0]
-- [3,7,11,15,19,0]
--
-- /Internal/
--
@ -955,12 +971,12 @@ foldManyPost f m = D.fromStreamD $ D.foldManyPost f (D.toStreamD m)
--
-- >>> f = Fold.takeLE 2 Fold.sum
-- >>> Stream.toList $ Stream.foldMany f $ Stream.fromList [1..10]
-- > [3,7,11,15,19]
-- [3,7,11,15,19]
--
-- On an empty stream the output is empty:
--
-- >>> Stream.toList $ Stream.foldMany f $ Stream.fromList []
-- > []
-- []
--
-- Note @foldMany (takeLE 0)@ would result in an infinite loop in a non-empty
-- stream.
@ -992,10 +1008,14 @@ foldSequence _f _m = undefined
-- generate the first fold, the fold is applied on the stream and the result of
-- the fold is used to generate the next fold and so on.
--
-- >>> f x = Fold.takeLE 2 (Fold.mconcatTo x)
-- >>> s = Stream.map Sum $ Stream.fromList [1..10]
-- >>> Stream.toList $ Stream.map getSum $ Stream.foldIterate f 0 s
-- > [3,10,21,36,55,55]
-- @
-- > import Data.Monoid (Sum(..))
-- > f x = Fold.takeLE 2 (Fold.sconcat x)
-- > s = Stream.map Sum $ Stream.fromList [1..10]
-- > Stream.toList $ Stream.map getSum $ Stream.foldIterate f 0 s
-- [3,10,21,36,55,55]
--
-- @
--
-- This is the streaming equivalent of monad like sequenced application of
-- folds where next fold is dependent on the previous fold.
@ -1022,11 +1042,14 @@ foldIterate _f _i _m = undefined
-- This is the streaming equivalent of the 'Streamly.Internal.Data.Parser.many'
-- parse combinator.
--
-- >>> S.toList $ S.parseMany (PR.take 2 $ PR.fromFold FL.sum) $ S.fromList [1..10]
-- > [3,7,11,15,19]
-- >>> Stream.toList $ Stream.parseMany (Parser.takeBetween 0 2 Fold.sum) $ Stream.fromList [1..10]
-- [3,7,11,15,19]
--
-- >>> S.toList $ S.parseMany (PR.line FL.toList) $ S.fromList "hello\nworld"
-- > ["hello\n","world"]
-- @
-- > Stream.toList $ Stream.parseMany (Parser.line Fold.toList) $ Stream.fromList "hello\\nworld"
-- ["hello\\n","world"]
--
-- @
--
-- @
-- foldMany f = parseMany (fromFold f)
@ -1089,8 +1112,9 @@ parseManyTill = undefined
-- used to generate the first parser, the parser is applied on the stream and
-- the result is used to generate the next parser and so on.
--
-- >>> S.toList $ S.map getSum $ S.parseIterate (\b -> PR.take 2 (FL.mconcatTo b)) 0 $ S.map Sum $ S.fromList [1..10]
-- > [3,10,21,36,55,55]
-- >>> import Data.Monoid (Sum(..))
-- >>> Stream.toList $ Stream.map getSum $ Stream.parseIterate (\b -> Parser.takeBetween 0 2 (Fold.sconcat b)) 0 $ Stream.map Sum $ Stream.fromList [1..10]
-- [3,10,21,36,55,55]
--
-- This is the streaming equivalent of monad like sequenced application of
-- parsers where next parser is dependent on the previous parser.
@ -1196,8 +1220,8 @@ groupScan split fold m = undefined
-- group is folded using the fold @f@ and the result of the fold is emitted in
-- the output stream.
--
-- >>> S.toList $ S.groupsBy (>) FL.toList $ S.fromList [1,3,7,0,2,5]
-- > [[1,3,7],[0,2,5]]
-- >>> Stream.toList $ Stream.groupsBy (>) Fold.toList $ Stream.fromList [1,3,7,0,2,5]
-- [[1,3,7],[0,2,5]]
--
-- @since 0.7.0
{-# INLINE groupsBy #-}
@ -1217,8 +1241,8 @@ groupsBy cmp f m = D.fromStreamD $ D.groupsBy cmp f (D.toStreamD m)
-- comparison fails a new group is started. Each group is folded using the fold
-- @f@.
--
-- >>> S.toList $ S.groupsByRolling (\a b -> a + 1 == b) FL.toList $ S.fromList [1,2,3,7,8,9]
-- > [[1,2,3],[7,8,9]]
-- >>> Stream.toList $ Stream.groupsByRolling (\a b -> a + 1 == b) Fold.toList $ Stream.fromList [1,2,3,7,8,9]
-- [[1,2,3],[7,8,9]]
--
-- @since 0.7.0
{-# INLINE groupsByRolling #-}
@ -1236,8 +1260,8 @@ groupsByRolling cmp f m = D.fromStreamD $ D.groupsRollingBy cmp f (D.toStreamD
--
-- Groups contiguous spans of equal elements together in individual groups.
--
-- >>> S.toList $ S.groups FL.toList $ S.fromList [1,1,2,2]
-- > [[1,1],[2,2]]
-- >>> Stream.toList $ Stream.groups Fold.toList $ Stream.fromList [1,1,2,2]
-- [[1,1],[2,2]]
--
-- @since 0.7.0
{-# INLINE groups #-}
@ -1262,9 +1286,9 @@ groups = groupsBy (==)
-- separator elements determined by the supplied predicate, separator is
-- considered as infixed between two segments:
--
-- >>> splitOn' p xs = S.toList $ S.splitOn p FL.toList (S.fromList xs)
-- >>> splitOn' p xs = Stream.toList $ Stream.splitOn p Fold.toList (Stream.fromList xs)
-- >>> splitOn' (== '.') "a.b"
-- > ["a","b"]
-- ["a","b"]
--
-- An empty stream is folded to the default value of the fold:
--
@ -1278,13 +1302,13 @@ groups = groupsBy (==)
-- ["",""]
--
-- >>> splitOn' (== '.') ".a"
-- > ["","a"]
-- ["","a"]
--
-- >>> splitOn' (== '.') "a."
-- > ["a",""]
-- ["a",""]
--
-- >>> splitOn' (== '.') "a..b"
-- > ["a","","b"]
-- ["a","","b"]
--
-- splitOn is an inverse of intercalating single element:
--
@ -1318,12 +1342,12 @@ splitOn predicate f =
-- | Split on a suffixed separator element, dropping the separator. The
-- supplied 'Fold' is applied on the split segments.
--
-- > splitOnSuffix' p xs = S.toList $ S.splitOnSuffix p (FL.toList) (S.fromList xs)
-- >>> splitOnSuffix' p xs = Stream.toList $ Stream.splitOnSuffix p Fold.toList (Stream.fromList xs)
-- >>> splitOnSuffix' (== '.') "a.b."
-- > ["a","b"]
-- ["a","b"]
--
-- >>> splitOnSuffix' (== '.') "a."
-- > ["a"]
-- ["a"]
--
-- An empty stream results in an empty output stream:
--
@ -1337,7 +1361,7 @@ splitOn predicate f =
-- [""]
--
-- >>> splitOnSuffix' (== '.') "a..b.."
-- > ["a","","b",""]
-- ["a","","b",""]
--
-- A suffix is optional at the end of the stream:
--
@ -1345,10 +1369,10 @@ splitOn predicate f =
-- ["a"]
--
-- >>> splitOnSuffix' (== '.') ".a"
-- > ["","a"]
-- ["","a"]
--
-- >>> splitOnSuffix' (== '.') "a.b"
-- > ["a","b"]
-- ["a","b"]
--
-- > lines = splitOnSuffix (== '\n')
--
@ -1371,33 +1395,42 @@ splitOnSuffix predicate f = foldMany (FL.sliceSepBy predicate f)
-- | Split on a prefixed separator element, dropping the separator. The
-- supplied 'Fold' is applied on the split segments.
--
-- >>> splitOnPrefix' p xs = S.toList $ S.splitOnPrefix p (FL.toList) (S.fromList xs)
-- >>> splitOnPrefix' (== '.') ".a.b"
-- > ["a","b"]
-- @
-- > splitOnPrefix' p xs = Stream.toList $ Stream.splitOnPrefix p (Fold.toList) (Stream.fromList xs)
-- > splitOnPrefix' (== '.') ".a.b"
-- ["a","b"]
-- @
--
-- An empty stream results in an empty output stream:
-- >>> splitOnPrefix' (== '.') ""
-- @
-- > splitOnPrefix' (== '.') ""
-- []
-- @
--
-- An empty segment consisting of only a prefix is folded to the default output
-- of the fold:
--
-- >>> splitOnPrefix' (== '.') "."
-- @
-- > splitOnPrefix' (== '.') "."
-- [""]
--
-- >>> splitOnPrefix' (== '.') ".a.b."
-- > ["a","b",""]
-- > splitOnPrefix' (== '.') ".a.b."
-- ["a","b",""]
--
-- >>> splitOnPrefix' (== '.') ".a..b"
-- > ["a","","b"]
-- > splitOnPrefix' (== '.') ".a..b"
-- ["a","","b"]
--
-- @
--
-- A prefix is optional at the beginning of the stream:
--
-- >>> splitOnPrefix' (== '.') "a"
-- @
-- > splitOnPrefix' (== '.') "a"
-- ["a"]
--
-- >>> splitOnPrefix' (== '.') "a.b"
-- > ["a","b"]
-- > splitOnPrefix' (== '.') "a.b"
-- ["a","b"]
-- @
--
-- 'splitOnPrefix' is an inverse of 'intercalatePrefix' with a single element:
--
@ -1420,16 +1453,16 @@ splitOnPrefix _predicate _f = undefined
-- @["a","b"]@. In other words, its like parsing words from whitespace
-- separated text.
--
-- > wordsBy' p xs = S.toList $ S.wordsBy p (FL.toList) (S.fromList xs)
-- >>> wordsBy' p xs = Stream.toList $ Stream.wordsBy p Fold.toList (Stream.fromList xs)
--
-- >>> wordsBy' (== ',') ""
-- > []
-- []
--
-- >>> wordsBy' (== ',') ","
-- > []
-- []
--
-- >>> wordsBy' (== ',') ",a,,b,"
-- > ["a","b"]
-- ["a","b"]
--
-- > words = wordsBy isSpace
--
@ -1447,7 +1480,7 @@ wordsBy predicate f m =
-- | Like 'splitOnSuffix' but keeps the suffix attached to the resulting
-- splits.
--
-- > splitWithSuffix' p xs = S.toList $ S.splitWithSuffix p (FL.toList) (S.fromList xs)
-- >>> splitWithSuffix' p xs = Stream.toList $ splitWithSuffix p Fold.toList (Stream.fromList xs)
--
-- >>> splitWithSuffix' (== '.') ""
-- []
@ -1459,19 +1492,19 @@ wordsBy predicate f m =
-- ["a"]
--
-- >>> splitWithSuffix' (== '.') ".a"
-- > [".","a"]
-- [".","a"]
--
-- >>> splitWithSuffix' (== '.') "a."
-- > ["a."]
-- ["a."]
--
-- >>> splitWithSuffix' (== '.') "a.b"
-- > ["a.","b"]
-- ["a.","b"]
--
-- >>> splitWithSuffix' (== '.') "a.b."
-- > ["a.","b."]
-- ["a.","b."]
--
-- >>> splitWithSuffix' (== '.') "a..b.."
-- > ["a.",".","b.","."]
-- ["a.",".","b.","."]
--
-- @since 0.7.0
@ -1529,34 +1562,34 @@ splitOnAny subseq f m = undefined -- D.fromStreamD $ D.splitOnAny f subseq (D.to
--
-- | Like 'splitOnSeq' but splits the separator as well, as an infix token.
--
-- > splitOn'_ pat xs = S.toList $ S.splitOn' (A.fromList pat) (FL.toList) (S.fromList xs)
-- >>> splitOn'_ pat xs = Stream.toList $ Stream.splitBySeq (Array.fromList pat) Fold.toList (Stream.fromList xs)
--
-- >>> splitOn'_ "" "hello"
-- > ["h","","e","","l","","l","","o"]
-- ["h","","e","","l","","l","","o"]
--
-- >>> splitOn'_ "hello" ""
-- > [""]
-- [""]
--
-- >>> splitOn'_ "hello" "hello"
-- > ["","hello",""]
-- ["","hello",""]
--
-- >>> splitOn'_ "x" "hello"
-- > ["hello"]
-- ["hello"]
--
-- >>> splitOn'_ "h" "hello"
-- > ["","h","ello"]
-- ["","h","ello"]
--
-- >>> splitOn'_ "o" "hello"
-- > ["hell","o",""]
-- ["hell","o",""]
--
-- >>> splitOn'_ "e" "hello"
-- > ["h","e","llo"]
-- ["h","e","llo"]
--
-- >>> splitOn'_ "l" "hello"
-- > ["he","l","","l","o"]
-- ["he","l","","l","o"]
--
-- >>> splitOn'_ "ll" "hello"
-- > ["he","ll","o"]
-- ["he","ll","o"]
--
-- /Internal/
{-# INLINE splitBySeq #-}
@ -1569,7 +1602,7 @@ splitBySeq patt f m =
-- | Like 'splitSuffixBy' but the separator is a sequence of elements, instead
-- of a predicate for a single element.
--
-- > splitOnSuffixSeq_ pat xs = S.toList $ S.splitOnSuffixSeq (A.fromList pat) (FL.toList) (S.fromList xs)
-- >>> splitOnSuffixSeq_ pat xs = Stream.toList $ Stream.splitOnSuffixSeq (Array.fromList pat) Fold.toList (Stream.fromList xs)
--
-- >>> splitOnSuffixSeq_ "." ""
-- []
@ -1581,19 +1614,19 @@ splitBySeq patt f m =
-- ["a"]
--
-- >>> splitOnSuffixSeq_ "." ".a"
-- > ["","a"]
-- ["","a"]
--
-- >>> splitOnSuffixSeq_ "." "a."
-- > ["a"]
-- ["a"]
--
-- >>> splitOnSuffixSeq_ "." "a.b"
-- > ["a","b"]
-- ["a","b"]
--
-- >>> splitOnSuffixSeq_ "." "a.b."
-- > ["a","b"]
-- ["a","b"]
--
-- >>> splitOnSuffixSeq_ "." "a..b.."
-- > ["a","","b",""]
-- ["a","","b",""]
--
-- > lines = splitOnSuffixSeq "\n"
--
@ -1627,10 +1660,10 @@ wordsOn subseq f m = undefined -- D.fromStreamD $ D.wordsOn f subseq (D.toStream
-- | Like 'splitOnSuffixSeq' but keeps the suffix intact in the splits.
--
-- > splitWithSuffixSeq'_ pat xs = S.toList $ S.splitWithSuffixSeq (A.fromList pat) (FL.toList) (S.fromList xs)
-- >>> splitWithSuffixSeq' pat xs = Stream.toList $ Stream.splitWithSuffixSeq (Array.fromList pat) Fold.toList (Stream.fromList xs)
--
-- >>> splitWithSuffixSeq' "." ""
-- [""]
-- []
--
-- >>> splitWithSuffixSeq' "." "."
-- ["."]
@ -1639,19 +1672,19 @@ wordsOn subseq f m = undefined -- D.fromStreamD $ D.wordsOn f subseq (D.toStream
-- ["a"]
--
-- >>> splitWithSuffixSeq' "." ".a"
-- > [".","a"]
-- [".","a"]
--
-- >>> splitWithSuffixSeq' "." "a."
-- > ["a."]
-- ["a."]
--
-- >>> splitWithSuffixSeq' "." "a.b"
-- > ["a.","b"]
-- ["a.","b"]
--
-- >>> splitWithSuffixSeq' "." "a.b."
-- > ["a.","b."]
-- ["a.","b."]
--
-- >>> splitWithSuffixSeq' "." "a..b.."
-- > ["a.",".","b.","."]
-- ["a.",".","b.","."]
--
-- /Internal/
{-# INLINE splitWithSuffixSeq #-}
@ -1679,8 +1712,8 @@ splitOnSuffixSeqAny subseq f m = undefined
-- | Group the input stream into groups of @n@ elements each and then fold each
-- group using the provided fold function.
--
-- >> S.toList $ S.chunksOf 2 FL.sum (S.enumerateFromTo 1 10)
-- > [3,7,11,15,19]
-- >>> Stream.toList $ Stream.chunksOf 2 Fold.sum (Stream.enumerateFromTo 1 10)
-- [3,7,11,15,19]
--
-- This can be considered as an n-fold version of 'takeLE' where we apply
-- 'takeLE' repeatedly on the leftover stream until the stream exhausts.
@ -1718,12 +1751,13 @@ arraysOf n = D.fromStreamD . A.arraysOf n . D.toStreamD
-- XXX we can implement this by repeatedly applying the 'lrunFor' fold.
-- XXX add this example after fixing the serial stream rate control
-- >>> S.toList $ S.take 5 $ intervalsOf 1 FL.sum $ constRate 2 $ S.enumerateFrom 1
-- > [3,7,11,15,19]
--
-- | Group the input stream into windows of @n@ second each and then fold each
-- group using the provided fold function.
--
-- >>> Stream.toList $ Stream.take 5 $ Stream.intervalsOf 1 Fold.sum $ Stream.constRate 2 $ Stream.enumerateFrom 1
-- [...,...,...,...,...]
--
-- @since 0.7.0
{-# INLINE intervalsOf #-}
intervalsOf
@ -2188,12 +2222,18 @@ classifyChunksOf wsize = classifyChunksBy wsize False
-- @
--
-- @
-- >>> S.mapM_ print
-- $ S.classifySessionsOf 3 (const (return False)) (fmap Right FL.toList)
-- $ S.map (\(ts,(k,a)) -> (k, a, ts))
-- $ S.timestamped
-- $ S.delay 1
-- $ (,) <$> S.fromList [1,2,3] <*> S.fromList [1,2,3]
-- > :{
-- Stream.mapM_ print
-- $ Stream.classifySessionsOf 3 (const (return False)) (fmap Right Fold.toList)
-- $ Stream.map (\\(ts,(k,a)) -> (k, a, ts))
-- $ Stream.timestamped
-- $ Stream.delay 1
-- $ (,) <$> Stream.fromList [1,2,3] <*> Stream.fromList [1,2,3]
-- :}
-- (1,Right [1,2,3])
-- (2,Right [1,2,3])
-- (3,Right [1,2,3])
--
-- @
--
-- /Internal/

View File

@ -78,6 +78,12 @@ import qualified Streamly.Internal.Data.Stream.StreamK as StreamK
import Prelude hiding (filter, zipWith, concatMap, concat)
-- $setup
-- >>> :m
-- >>> import Prelude hiding (filter, zipWith, concatMap, concat)
-- >>> import qualified Streamly.Prelude as Stream
-- >>> import qualified Streamly.Internal.Data.Stream.IsStream as Stream
------------------------------------------------------------------------------
-- Sampling
------------------------------------------------------------------------------
@ -88,10 +94,8 @@ import Prelude hiding (filter, zipWith, concatMap, concat)
-- | @sampleFromthen offset stride@ samples the element at @offset@ index and
-- then every element at strides of @stride@.
--
-- @
-- >>> Stream.toList $ Stream.sampleFromThen 2 3 $ Stream.enumerateFromTo 0 10
-- [1,4,7,10]
-- @
-- [2,5,8]
--
-- /Internal/
--
@ -468,15 +472,15 @@ mergeOuterJoin _eq _s1 _s2 = undefined
-- elements in the first stream that are present in the second stream.
--
-- >>> Stream.toList $ Stream.intersectBy (==) (Stream.fromList [1,2,2,4]) (Stream.fromList [2,1,1,3])
-- > [1,2,2]
-- [1,2,2]
--
-- >>> Stream.toList $ Stream.intersectBy (==) (Stream.fromList [2,1,1,3]) (Stream.fromList [1,2,2,4])
-- > [2,1,1]
-- [2,1,1]
--
-- 'intersectBy' is similar to but not the same as 'innerJoin':
--
-- >>> Stream.toList $ fmap fst $ Stream.innerJoin (==) (Stream.fromList [1,2,2,4]) (Stream.fromList [2,1,1,3])
-- > [1,1,2,2]
-- [1,1,2,2]
--
-- Space: O(n) where @n@ is the number of elements in the second stream.
--
@ -513,7 +517,7 @@ mergeIntersectBy _eq _s1 _s2 = undefined
-- second stream as many occurrences of it are deleted from the first stream.
--
-- >>> Stream.toList $ Stream.differenceBy (==) (Stream.fromList [1,2,2]) (Stream.fromList [1,2,3])
-- > [2]
-- [2]
--
-- The following laws hold:
--
@ -559,7 +563,7 @@ mergeDifferenceBy _eq _s1 _s2 = undefined
-- in the first stream.
--
-- >>> Stream.toList $ Stream.unionBy (==) (Stream.fromList [1,2,2,4]) (Stream.fromList [1,1,2,3])
-- > [1,2,2,4,1,3]
-- [1,2,2,4,3]
--
-- Equivalent to the following except that @s1@ is evaluated only once:
--

View File

@ -260,6 +260,15 @@ import Prelude hiding
( filter, drop, dropWhile, take, takeWhile, foldr, map, mapM, sequence
, reverse, foldr1 , scanl, scanl1)
--
-- $setup
-- >>> :m
-- >>> import Prelude hiding ( filter, drop, dropWhile, take, takeWhile, foldr, map, mapM, sequence, reverse, foldr1 , scanl, scanl1)
-- >>> import qualified Streamly.Prelude as Stream
-- >>> import Streamly.Internal.Data.Stream.IsStream as Stream
-- >>> import qualified Streamly.Data.Fold as Fold
-- >>> import qualified Streamly.Internal.Data.Fold as Fold
------------------------------------------------------------------------------
-- Piping
------------------------------------------------------------------------------
@ -285,18 +294,18 @@ transform pipe xs = fromStreamD $ D.transform pipe (toStreamD xs)
-- stateful transformations. However, note that the custom map and filter
-- routines can be much more efficient than this due to better stream fusion.
--
-- >>> S.toList $ S.foldrS S.cons S.nil $ S.fromList [1..5]
-- > [1,2,3,4,5]
-- >>> Stream.toList $ Stream.foldrS Stream.cons Stream.nil $ Stream.fromList [1..5]
-- [1,2,3,4,5]
--
-- Find if any element in the stream is 'True':
--
-- >>> S.toList $ S.foldrS (\x xs -> if odd x then return True else xs) (return False) $ (S.fromList (2:4:5:undefined) :: SerialT IO Int)
-- > [True]
-- >>> Stream.toList $ Stream.foldrS (\x xs -> if odd x then return True else xs) (return False) $ (Stream.fromList (2:4:5:undefined) :: Stream.SerialT IO Int)
-- [True]
--
-- Map (+2) on odd elements and filter out the even elements:
--
-- >>> S.toList $ S.foldrS (\x xs -> if odd x then (x + 2) `S.cons` xs else xs) S.nil $ (S.fromList [1..5] :: SerialT IO Int)
-- > [3,5,7]
-- >>> Stream.toList $ Stream.foldrS (\x xs -> if odd x then (x + 2) `Stream.cons` xs else xs) Stream.nil $ (Stream.fromList [1..5] :: Stream.SerialT IO Int)
-- [3,5,7]
--
-- 'foldrM' can also be represented in terms of 'foldrS', however, the former
-- is much more efficient:
@ -400,11 +409,9 @@ sequence m = fromStreamS $ S.sequence (toStreamS m)
--
-- @
--
-- @
-- > S.drain $ S.tap (FL.drainBy print) (S.enumerateFromTo 1 2)
-- >>> Stream.drain $ Stream.tap (Fold.drainBy print) (Stream.enumerateFromTo 1 2)
-- 1
-- 2
-- @
--
-- Compare with 'trace'.
--
@ -420,10 +427,9 @@ tap f xs = D.fromStreamD $ D.tap f (D.toStreamD xs)
-- means start at the first element in the stream. If the offset is outside
-- this range then @offset `mod` n@ is used as offset.
--
-- @
-- >>> S.drain $ S.tapOffsetEvery 0 2 (FL.rmapM print FL.toList) $ S.enumerateFromTo 0 10
-- > [0,2,4,6,8,10]
-- @
-- >>> Stream.drain $ Stream.tapOffsetEvery 0 2 (Fold.rmapM print Fold.toList) $ Stream.enumerateFromTo 0 10
-- [0,2,4,6,8,10]
--
-- /Internal/
--
@ -798,8 +804,10 @@ uniq = fromStreamD . D.uniq . toStreamD
-- prune p = dropWhileAround p $ uniqBy (x y -> p x && p y)
-- @
--
-- >>> Stream.pruneBy isSpace (Stream.fromList " hello world! ")
-- @
-- > Stream.pruneBy isSpace (Stream.fromList " hello world! ")
-- "hello world!"
-- @
--
-- Space: @O(1)@
--
@ -1084,10 +1092,8 @@ insertBy cmp x m = fromStreamS $ S.insertBy cmp x (toStreamS m)
-- | Insert a pure value between successive elements of a stream.
--
-- @
-- > S.toList $ S.intersperse ',' $ S.fromList "hello"
-- >>> Stream.toList $ Stream.intersperse ',' $ Stream.fromList "hello"
-- "h,e,l,l,o"
-- @
--
-- @since 0.7.0
{-# INLINE intersperse #-}
@ -1097,10 +1103,8 @@ intersperse a = fromStreamS . S.intersperse a . toStreamS
-- | Insert a side effect before consuming an element of a stream except the
-- first one.
--
-- @
-- >>> S.drain $ S.trace putChar $ S.intersperseM_ (putChar '.') $ S.fromList "hello"
-- > h.e.l.l.o
-- @
-- >>> Stream.drain $ Stream.trace putChar $ Stream.intersperseM_ (putChar '.') $ Stream.fromList "hello"
-- h.e.l.l.o
--
-- /Internal/
{-# INLINE intersperseM_ #-}
@ -1123,10 +1127,8 @@ intersperseBySpan _n _f _xs = undefined
-- | Insert an effect and its output after consuming an element of a stream.
--
-- @
-- >>> S.toList $ S.trace putChar $ S.intersperseSuffix (putChar '.' >> return ',') $ S.fromList "hello"
-- > h.,e.,l.,l.,o.,"h,e,l,l,o,"
-- @
-- >>> Stream.toList $ Stream.trace putChar $ intersperseSuffix (putChar '.' >> return ',') $ Stream.fromList "hello"
-- h.,e.,l.,l.,o.,"h,e,l,l,o,"
--
-- /Internal/
{-# INLINE intersperseSuffix #-}
@ -1150,10 +1152,8 @@ intersperseSuffix_ m = fromStreamD . D.intersperseSuffix_ m . toStreamD
-- | Like 'intersperseSuffix' but intersperses an effectful action into the
-- input stream after every @n@ elements and after the last element.
--
-- @
-- > S.toList $ S.intersperseSuffixBySpan 2 (return ',') $ S.fromList "hello"
-- >>> Stream.toList $ Stream.intersperseSuffixBySpan 2 (return ',') $ Stream.fromList "hello"
-- "he,ll,o,"
-- @
--
-- /Internal/
--
@ -1165,10 +1165,8 @@ intersperseSuffixBySpan n eff =
-- | Insert a side effect before consuming an element of a stream.
--
-- @
-- >>> S.toList $ S.trace putChar $ S.interspersePrefix_ (putChar '.' >> return ',') $ S.fromList "hello"
-- > .h.e.l.l.o"hello"
-- @
-- >>> Stream.toList $ Stream.trace putChar $ Stream.interspersePrefix_ (putChar '.' >> return ',') $ Stream.fromList "hello"
-- .h.e.l.l.o"hello"
--
-- Same as 'trace_' but may be concurrent.
--
@ -1189,12 +1187,10 @@ interspersePrefix_ m = mapM (\x -> void m >> return x)
-- | Introduce a delay of specified seconds before consuming an element of the
-- stream except the first one.
--
-- @
-- >>> S.mapM_ print $ S.timestamped $ S.delay 1 $ S.enumerateFromTo 1 3
-- > (AbsTime (TimeSpec {sec = 2502706, nsec = 751137000}),1)
-- > (AbsTime (TimeSpec {sec = 2502707, nsec = 743535000}),2)
-- > (AbsTime (TimeSpec {sec = 2502708, nsec = 749758000}),3)
-- @
-- >>> Stream.mapM_ print $ Stream.timestamped $ Stream.delay 1 $ Stream.enumerateFromTo 1 3
-- (AbsTime (TimeSpec {sec = ..., nsec = ...}),1)
-- (AbsTime (TimeSpec {sec = ..., nsec = ...}),2)
-- (AbsTime (TimeSpec {sec = ..., nsec = ...}),3)
--
-- /Internal/
--
@ -1207,12 +1203,10 @@ delay n = intersperseM_ $ liftIO $ threadDelay $ round $ n * 1000000
-- | Introduce a delay of specified seconds after consuming an element of a
-- stream.
--
-- @
-- >>> S.mapM_ print $ S.timestamped $ S.delayPost 1 $ S.enumerateFromTo 1 3
-- > (AbsTime (TimeSpec {sec = 2502826, nsec = 119030000}),1)
-- > (AbsTime (TimeSpec {sec = 2502827, nsec = 111393000}),2)
-- > (AbsTime (TimeSpec {sec = 2502828, nsec = 112221000}),3)
-- @
-- >>> Stream.mapM_ print $ Stream.timestamped $ Stream.delayPost 1 $ Stream.enumerateFromTo 1 3
-- (AbsTime (TimeSpec {sec = ..., nsec = ...}),1)
-- (AbsTime (TimeSpec {sec = ..., nsec = ...}),2)
-- (AbsTime (TimeSpec {sec = ..., nsec = ...}),3)
--
-- /Internal/
--
@ -1225,12 +1219,10 @@ delayPost n = intersperseSuffix_ $ liftIO $ threadDelay $ round $ n * 1000000
-- | Introduce a delay of specified seconds before consuming an element of a
-- stream.
--
-- @
-- >>> S.mapM_ print $ S.timestamped $ S.delayPre 1 $ S.enumerateFromTo 1 3
-- > (AbsTime (TimeSpec {sec = 2502207, nsec = 533177000}),1)
-- > (AbsTime (TimeSpec {sec = 2502208, nsec = 530859000}),2)
-- > (AbsTime (TimeSpec {sec = 2502209, nsec = 531619000}),3)
-- @
-- >>> Stream.mapM_ print $ Stream.timestamped $ Stream.delayPre 1 $ Stream.enumerateFromTo 1 3
-- (AbsTime (TimeSpec {sec = ..., nsec = ...}),1)
-- (AbsTime (TimeSpec {sec = ..., nsec = ...}),2)
-- (AbsTime (TimeSpec {sec = ..., nsec = ...}),3)
--
-- /Internal/
--
@ -1267,10 +1259,8 @@ reassembleBy = undefined
--
-- Pair each element in a stream with its index, starting from index 0.
--
-- @
-- > S.toList $ S.indexed $ S.fromList "hello"
-- >>> Stream.toList $ Stream.indexed $ Stream.fromList "hello"
-- [(0,'h'),(1,'e'),(2,'l'),(3,'l'),(4,'o')]
-- @
--
-- @since 0.6.0
{-# INLINE indexed #-}
@ -1284,10 +1274,8 @@ indexed = fromStreamD . D.indexed . toStreamD
-- Pair each element in a stream with its index, starting from the
-- given index @n@ and counting down.
--
-- @
-- > S.toList $ S.indexedR 10 $ S.fromList "hello"
-- >>> Stream.toList $ Stream.indexedR 10 $ Stream.fromList "hello"
-- [(10,'h'),(9,'e'),(8,'l'),(7,'l'),(6,'o')]
-- @
--
-- @since 0.6.0
{-# INLINE indexedR #-}
@ -1309,9 +1297,10 @@ indexedR n = fromStreamD . D.indexedR n . toStreamD
-- specified granularity. The timestamp is generated just before the element
-- is consumed.
--
-- @
-- >>> S.mapM_ print $ S.timestampWith 0.01 $ S.delay 1 $ S.enumerateFromTo 1 3
-- @
-- >>> Stream.mapM_ print $ Stream.timestampWith 0.01 $ Stream.delay 1 $ Stream.enumerateFromTo 1 3
-- (AbsTime (TimeSpec {sec = ..., nsec = ...}),1)
-- (AbsTime (TimeSpec {sec = ..., nsec = ...}),2)
-- (AbsTime (TimeSpec {sec = ..., nsec = ...}),3)
--
-- /Internal/
--
@ -1333,9 +1322,10 @@ timestamped = timestampWith 0.01
-- clock with the specified granularity. The time is measured just before the
-- element is consumed.
--
-- @
-- >>> S.mapM_ print $ S.timeIndexWith 0.01 $ S.delay 1 $ S.enumerateFromTo 1 3
-- @
-- >>> Stream.mapM_ print $ Stream.timeIndexWith 0.01 $ Stream.delay 1 $ Stream.enumerateFromTo 1 3
-- (RelTime64 (NanoSecond64 ...),1)
-- (RelTime64 (NanoSecond64 ...),2)
-- (RelTime64 (NanoSecond64 ...),3)
--
-- /Internal/
--
@ -1348,12 +1338,10 @@ timeIndexWith g stream = Z.zipWith (flip (,)) stream (relTimesWith g)
-- 10 ms granularity clock. The time is measured just before the element is
-- consumed.
--
-- @
-- >>> S.mapM_ print $ S.timeIndexed $ S.delay 1 $ S.enumerateFromTo 1 3
-- (RelTime64 (NanoSecond64 0),1)
-- (RelTime64 (NanoSecond64 996239000),2)
-- (RelTime64 (NanoSecond64 1996712000),3)
-- @
-- >>> Stream.mapM_ print $ Stream.timeIndexed $ Stream.delay 1 $ Stream.enumerateFromTo 1 3
-- (RelTime64 (NanoSecond64 ...),1)
-- (RelTime64 (NanoSecond64 ...),2)
-- (RelTime64 (NanoSecond64 ...),3)
--
-- /Internal/
--

View File

@ -72,6 +72,13 @@ import qualified Streamly.Internal.Data.Stream.SVar as SVar
#include "Instances.hs"
--
-- $setup
-- >>> :m
-- >>> import Prelude hiding (map)
-- >>> import qualified Streamly.Prelude as Stream
-- >>> import Streamly.Internal.Data.Stream.IsStream as Stream
-------------------------------------------------------------------------------
-- Parallel
-------------------------------------------------------------------------------
@ -228,27 +235,28 @@ infixr 6 `parallel`
-- singleton streams. The following trivial example is semantically equivalent
-- to running the action @putStrLn "hello"@ in the current thread:
--
-- >>> S.toList $ S.yieldM (putStrLn "hello") `parallel` S.nil
-- > hello
-- > [()]
-- >>> Stream.toList $ Stream.yieldM (putStrLn "hello") `Stream.parallel` Stream.nil
-- hello
-- [()]
--
-- Run two actions concurrently:
--
-- >>> S.toList $ S.yieldM (putStrLn "hello") `parallel` S.yieldM (putStrLn "world")
-- > hello
-- > world
-- > [(),()]
-- >>> import Control.Concurrent (threadDelay)
-- >>> Stream.toList $ Stream.yieldM (putStrLn "hello") `Stream.parallel` Stream.yieldM (threadDelay 100000 >> putStrLn "world")
-- hello
-- world
-- [(),()]
--
-- Run effects concurrently, disregarding their outputs:
--
-- >>> S.toList $ S.nilM (putStrLn "hello") `parallel` S.nilM (putStrLn "world")
-- > hello
-- > world
-- > []
-- >>> Stream.toList $ nilM (putStrLn "hello") `parallel` Stream.nilM (threadDelay 100000 >> putStrLn "world")
-- hello
-- world
-- []
--
-- Run an effectful action, and a pure effect without any output, concurrently:
--
-- >>> S.toList $ S.yieldM (return 1) `parallel` S.nilM (putStrLn "world")
-- >>> Stream.toList $ Stream.yieldM (return 1) `Stream.parallel` Stream.nilM (putStrLn "world")
-- world
-- [1]
--
@ -449,7 +457,14 @@ tapAsyncF f (D.Stream step1 state1) = D.Stream step TapInit
-- | Concurrently distribute a stream to a collection of fold functions,
-- discarding the outputs of the folds.
--
-- >>> S.drain $ distributeAsync_ [S.mapM_ print, S.mapM_ print] (S.enumerateFromTo 1 2)
-- @
-- > Stream.drain $ Stream.distributeAsync_ [Stream.mapM_ print, Stream.mapM_ print] (Stream.enumerateFromTo 1 2)
-- 1
-- 2
-- 1
-- 2
--
-- @
--
-- @
-- distributeAsync_ = flip (foldr tapAsync)

View File

@ -202,6 +202,9 @@ import Streamly.Internal.Data.Stream.StreamK.Type
import qualified Streamly.Internal.Data.Fold.Types as FL
-- $setup
-- >>> :m
-------------------------------------------------------------------------------
-- Deconstruction
-------------------------------------------------------------------------------
@ -524,6 +527,7 @@ tailPartial m = mkStream $ \st yld sng stp ->
-- lazy value @x@ i.e. the same location in memory. Thus @x@ can be defined
-- in terms of itself, creating structures with cyclic references.
--
-- >>> import Data.Function (fix)
-- >>> f ~(a, b) = ([1, b], head a)
-- >>> fix f
-- ([1,1],1)

View File

@ -35,6 +35,12 @@ import Streamly.Internal.Data.Stream.StreamD.Step (Step(..))
import Prelude hiding (const, map, concat, concatMap, zipWith)
-- $setup
-- >>> :m
-- >>> import qualified Streamly.Prelude as Stream
-- >>> import qualified Streamly.Internal.Data.Stream.IsStream as Stream
-- >>> import qualified Streamly.Internal.Data.Unfold as Unfold
------------------------------------------------------------------------------
-- Monadic Unfolds
------------------------------------------------------------------------------

View File

@ -26,12 +26,19 @@ import Streamly.Internal.Data.Stream.IsStream (IsStream)
import qualified Streamly.Internal.Unicode.Stream as S
import qualified Streamly.Data.Array.Foreign as A
-- $setup
-- >>> :m
-- >>> :set -XOverloadedStrings
-- >>> import Prelude hiding (String, lines, words, unlines, unwords)
-- >>> import qualified Streamly.Prelude as Stream
-- >>> import qualified Streamly.Internal.Unicode.Array.Char as Unicode
-- | Break a string up into a stream of strings at newline characters.
-- The resulting strings do not contain newlines.
--
-- > lines = S.lines A.write
--
-- >>> S.toList $ lines $ S.fromList "lines\nthis\nstring\n\n\n"
-- >>> Stream.toList $ Unicode.lines $ Stream.fromList "lines\nthis\nstring\n\n\n"
-- ["lines","this","string","",""]
--
{-# INLINE lines #-}
@ -43,8 +50,8 @@ lines = S.lines A.write
--
-- > words = S.words A.write
--
-- >>> S.toList $ words $ S.fromList "A newline\nis considered white space?"
-- ["A", "newline", "is", "considered", "white", "space?"]
-- >>> Stream.toList $ Unicode.words $ Stream.fromList "A newline\nis considered white space?"
-- ["A","newline","is","considered","white","space?"]
--
{-# INLINE words #-}
words :: (MonadIO m, IsStream t) => t m Char -> t m (Array Char)
@ -55,7 +62,7 @@ words = S.words A.write
--
-- 'unlines' is an inverse operation to 'lines'.
--
-- >>> S.toList $ unlines $ S.fromList ["lines", "this", "string"]
-- >>> Stream.toList $ Unicode.unlines $ Stream.fromList ["lines", "this", "string"]
-- "lines\nthis\nstring\n"
--
-- > unlines = S.unlines A.read
@ -72,7 +79,7 @@ unlines = S.unlines A.read
--
-- 'unwords' is an inverse operation to 'words'.
--
-- >>> S.toList $ unwords $ S.fromList ["unwords", "this", "string"]
-- >>> Stream.toList $ Unicode.unwords $ Stream.fromList ["unwords", "this", "string"]
-- "unwords this string"
--
-- > unwords = S.unwords A.read

View File

@ -26,13 +26,19 @@ import Streamly.Internal.Data.Array.Prim.Pinned (Array)
import qualified Streamly.Internal.Unicode.Stream as S
import qualified Streamly.Internal.Data.Array.Prim.Pinned as A
-- $setup
-- >>> :m
-- >>> :set -XOverloadedStrings
-- >>> import qualified Streamly.Prelude as Stream
-- >>> import qualified Streamly.Internal.Unicode.Array.Prim.Pinned as Unicode
-- | Break a string up into a stream of strings at newline characters.
-- The resulting strings do not contain newlines.
--
-- > lines = S.lines A.write
--
-- >>> S.toList $ lines $ S.fromList "lines\nthis\nstring\n\n\n"
-- ["lines","this","string","",""]
-- >>> Stream.toList $ Unicode.lines $ Stream.fromList "lines\nthis\nstring\n\n\n"
-- [fromListN 5 "lines",fromListN 4 "this",fromListN 6 "string",fromListN 0 "",fromListN 0 ""]
--
{-# INLINE lines #-}
lines :: (MonadIO m, IsStream t) => t m Char -> t m (Array Char)
@ -43,8 +49,8 @@ lines = S.lines A.write
--
-- > words = S.words A.write
--
-- >>> S.toList $ words $ S.fromList "A newline\nis considered white space?"
-- ["A", "newline", "is", "considered", "white", "space?"]
-- >>> Stream.toList $ Unicode.words $ Stream.fromList "A newline\nis considered white space?"
-- [fromListN 1 "A",fromListN 7 "newline",fromListN 2 "is",fromListN 10 "considered",fromListN 5 "white",fromListN 6 "space?"]
--
{-# INLINE words #-}
words :: (MonadIO m, IsStream t) => t m Char -> t m (Array Char)
@ -55,7 +61,7 @@ words = S.words A.write
--
-- 'unlines' is an inverse operation to 'lines'.
--
-- >>> S.toList $ unlines $ S.fromList ["lines", "this", "string"]
-- >>> Stream.toList $ Unicode.unlines $ Stream.fromList ["lines", "this", "string"]
-- "lines\nthis\nstring\n"
--
-- > unlines = S.unlines A.read
@ -72,7 +78,7 @@ unlines = S.unlines A.read
--
-- 'unwords' is an inverse operation to 'words'.
--
-- >>> S.toList $ unwords $ S.fromList ["unwords", "this", "string"]
-- >>> Stream.toList $ Unicode.unwords $ Stream.fromList ["unwords", "this", "string"]
-- "unwords this string"
--
-- > unwords = S.unwords A.read

View File

@ -94,6 +94,13 @@ import qualified Streamly.Internal.Data.Stream.StreamD as D
import Prelude hiding (String, lines, words, unlines, unwords)
-- $setup
-- >>> :m
-- >>> import Prelude hiding (String, lines, words, unlines, unwords)
-- >>> import qualified Streamly.Prelude as Stream
-- >>> import qualified Streamly.Data.Fold as Fold
-- >>> import Streamly.Internal.Unicode.Stream
-------------------------------------------------------------------------------
-- Encoding/Decoding Unicode (UTF-8) Characters
-------------------------------------------------------------------------------
@ -859,8 +866,8 @@ stripStart = S.dropWhile isSpace
-- | Fold each line of the stream using the supplied 'Fold'
-- and stream the result.
--
-- >>> S.toList $ lines FL.toList (S.fromList "lines\nthis\nstring\n\n\n")
-- ["lines", "this", "string", "", ""]
-- >>> Stream.toList $ lines Fold.toList (Stream.fromList "lines\nthis\nstring\n\n\n")
-- ["lines","this","string","",""]
--
-- > lines = S.splitOnSuffix (== '\n')
--
@ -884,8 +891,8 @@ isSpace c
-- | Fold each word of the stream using the supplied 'Fold'
-- and stream the result.
--
-- >>> S.toList $ words FL.toList (S.fromList "fold these words")
-- ["fold", "these", "words"]
-- >>> Stream.toList $ words Fold.toList (Stream.fromList "fold these words")
-- ["fold","these","words"]
--
-- > words = S.wordsBy isSpace
--

View File

@ -655,6 +655,10 @@ import Prelude
import Streamly.Internal.Data.Stream.IsStream
-- $setup
-- >>> :m
-- >>> import qualified Streamly.Prelude as Stream
-- >>> import qualified Streamly.Data.Fold as Fold
-- $streamtypes
-- The basic stream type is 'Serial', it represents a sequence of IO actions,
@ -964,9 +968,9 @@ import Streamly.Internal.Data.Stream.IsStream
-- The following two ways of folding are equivalent in functionality and
-- performance,
--
-- >>> S.fold FL.sum (S.enumerateFromTo 1 100)
-- >>> Stream.fold Fold.sum (Stream.enumerateFromTo 1 100)
-- 5050
-- >>> S.sum (S.enumerateFromTo 1 100)
-- >>> Stream.sum (Stream.enumerateFromTo 1 100)
-- 5050
--
-- However, left folds cannot terminate early even if it does not need to
@ -978,30 +982,30 @@ import Streamly.Internal.Data.Stream.IsStream
-- fold in parallel the performance is not impacted as we anyway have to
-- consume the whole stream due to the full fold.
--
-- >>> S.head (1 `S.cons` undefined)
-- >>> Stream.head (1 `Stream.cons` undefined)
-- Just 1
-- >>> Stream.fold Fold.head (1 `Stream.cons` undefined)
-- Just 1
-- >>> S.fold FL.head (1 `S.cons` undefined)
-- *** Exception: Prelude.undefined
--
-- However, we can wrap the fold in a scan to convert it into a lazy stream of
-- fold steps. We can then terminate the stream whenever we want. For example,
--
-- >>> S.toList $ S.take 1 $ S.scan FL.head (1 `S.cons` undefined)
-- >>> Stream.toList $ Stream.take 1 $ Stream.scan Fold.head (1 `Stream.cons` undefined)
-- [Nothing]
--
-- The following example extracts the input stream up to a point where the
-- running average of elements is no more than 10:
--
-- @
-- > S.toList
-- $ S.map (fromJust . fst)
-- $ S.takeWhile (\\(_,x) -> x <= 10)
-- $ S.postscan ((,) \<$> FL.last \<*> avg) (S.enumerateFromTo 1.0 100.0)
-- @
-- @
-- [1.0,2.0,3.0,4.0,5.0,6.0,7.0,8.0,9.0,10.0,11.0,12.0,13.0,14.0,15.0,16.0,17.0,18.0,19.0]
-- @
-- >>> import Data.Maybe (fromJust)
-- >>> let avg = (/) <$> Fold.sum <*> fmap fromIntegral Fold.length
-- >>> :{
-- Stream.toList
-- $ Stream.map (fromJust . fst)
-- $ Stream.takeWhile (\(_,x) -> x <= 10)
-- $ Stream.postscan ((,) <$> Fold.last <*> avg) (Stream.enumerateFromTo 1.0 100.0)
-- :}
-- [1.0,2.0,3.0,4.0,5.0,6.0,7.0,8.0,9.0,10.0,11.0,12.0,13.0,14.0,15.0,16.0,17.0,18.0,19.0]
--
-- $application
--
-- Stream processing functions can be composed in a chain using function