streamly-core-0.1.0: Streaming, parsers, arrays and more
Copyright(c) 2017 Composewell Technologies
LicenseBSD3
Maintainerstreamly@composewell.com
Stabilityreleased
PortabilityGHC
Safe HaskellSafe-Inferred
LanguageHaskell2010

Streamly.Data.StreamK

Description

Streams using Continuation Passing Style (CPS). See the Stream vs StreamK section in the Streamly.Data.Stream module to know when to use this module.

Please refer to Streamly.Internal.Data.Stream.StreamK for more functions that have not yet been released.

Synopsis

Setup

To execute the code examples provided in this module in ghci, please run the following commands first.

>>> :m
>>> import Data.Function (fix, (&))
>>> import Data.Semigroup (cycle1)
>>> effect n = print n >> return n
>>> import Streamly.Data.StreamK (StreamK)
>>> import qualified Streamly.Data.Fold as Fold
>>> import qualified Streamly.Data.Parser as Parser
>>> import qualified Streamly.Data.Stream as Stream
>>> import qualified Streamly.Data.StreamK as StreamK
>>> import qualified Streamly.FileSystem.Dir as Dir

For APIs that have not been released yet.

>>> import qualified Streamly.Internal.Data.Stream.StreamK as StreamK
>>> import qualified Streamly.Internal.FileSystem.Dir as Dir

Overview

Continuation passing style (CPS) stream implementation. The K in StreamK stands for Kontinuation.

StreamK can be constructed like lists, except that they use nil instead of '[]' and cons instead of :.

cons adds a pure value at the head of the stream:

>>> import Streamly.Data.StreamK (StreamK, cons, consM, nil)
>>> stream = 1 `cons` 2 `cons` nil :: StreamK IO Int

You can use operations from Streamly.Data.Stream for StreamK as well by converting StreamK to Stream (toStream), and vice-versa (fromStream).

>>> Stream.fold Fold.toList $ StreamK.toStream stream -- IO [Int]
[1,2]

consM adds an effect at the head of the stream:

>>> stream = effect 1 `consM` effect 2 `consM` nil
>>> Stream.fold Fold.toList $ StreamK.toStream stream
1
2
[1,2]

Exception Handling

There are no native exception handling operations in the StreamK module, please convert to Stream type and use exception handling operations from Streamly.Data.Stream.

Type

data StreamK m a Source #

Instances

Instances details
(Foldable m, Monad m) => Foldable (StreamK m) Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamK.Type

Methods

fold :: Monoid m0 => StreamK m m0 -> m0 #

foldMap :: Monoid m0 => (a -> m0) -> StreamK m a -> m0 #

foldMap' :: Monoid m0 => (a -> m0) -> StreamK m a -> m0 #

foldr :: (a -> b -> b) -> b -> StreamK m a -> b #

foldr' :: (a -> b -> b) -> b -> StreamK m a -> b #

foldl :: (b -> a -> b) -> b -> StreamK m a -> b #

foldl' :: (b -> a -> b) -> b -> StreamK m a -> b #

foldr1 :: (a -> a -> a) -> StreamK m a -> a #

foldl1 :: (a -> a -> a) -> StreamK m a -> a #

toList :: StreamK m a -> [a] #

null :: StreamK m a -> Bool #

length :: StreamK m a -> Int #

elem :: Eq a => a -> StreamK m a -> Bool #

maximum :: Ord a => StreamK m a -> a #

minimum :: Ord a => StreamK m a -> a #

sum :: Num a => StreamK m a -> a #

product :: Num a => StreamK m a -> a #

Traversable (StreamK Identity) Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamK.Type

Methods

traverse :: Applicative f => (a -> f b) -> StreamK Identity a -> f (StreamK Identity b) #

sequenceA :: Applicative f => StreamK Identity (f a) -> f (StreamK Identity a) #

mapM :: Monad m => (a -> m b) -> StreamK Identity a -> m (StreamK Identity b) #

sequence :: Monad m => StreamK Identity (m a) -> m (StreamK Identity a) #

Monad m => Functor (StreamK m) Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamK.Type

Methods

fmap :: (a -> b) -> StreamK m a -> StreamK m b #

(<$) :: a -> StreamK m b -> StreamK m a #

a ~ Char => IsString (StreamK Identity a) Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamK.Type

Monoid (StreamK m a) Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamK.Type

Methods

mempty :: StreamK m a #

mappend :: StreamK m a -> StreamK m a -> StreamK m a #

mconcat :: [StreamK m a] -> StreamK m a #

Semigroup (StreamK m a) Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamK.Type

Methods

(<>) :: StreamK m a -> StreamK m a -> StreamK m a #

sconcat :: NonEmpty (StreamK m a) -> StreamK m a #

stimes :: Integral b => b -> StreamK m a -> StreamK m a #

IsList (StreamK Identity a) Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamK.Type

Associated Types

type Item (StreamK Identity a) #

Read a => Read (StreamK Identity a) Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamK.Type

Show a => Show (StreamK Identity a) Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamK.Type

type Item (StreamK Identity a) Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamK.Type

type Item (StreamK Identity a) = a

Construction

Primitives

nil :: StreamK m a Source #

A stream that terminates without producing any output or side effect.

>>> Stream.fold Fold.toList (StreamK.toStream StreamK.nil)
[]

nilM :: Applicative m => m b -> StreamK m a Source #

A stream that terminates without producing any output, but produces a side effect.

>>> Stream.fold Fold.toList (StreamK.toStream (StreamK.nilM (print "nil")))
"nil"
[]

Pre-release

cons :: a -> StreamK m a -> StreamK m a infixr 5 Source #

A right associative prepend operation to add a pure value at the head of an existing stream::

>>> s = 1 `StreamK.cons` 2 `StreamK.cons` 3 `StreamK.cons` StreamK.nil
>>> Stream.fold Fold.toList (StreamK.toStream s)
[1,2,3]

It can be used efficiently with foldr:

>>> fromFoldable = Prelude.foldr StreamK.cons StreamK.nil

Same as the following but more efficient:

>>> cons x xs = return x `StreamK.consM` xs

consM :: Monad m => m a -> StreamK m a -> StreamK m a infixr 5 Source #

A right associative prepend operation to add an effectful value at the head of an existing stream::

>>> s = putStrLn "hello" `StreamK.consM` putStrLn "world" `StreamK.consM` StreamK.nil
>>> Stream.fold Fold.drain (StreamK.toStream s)
hello
world

It can be used efficiently with foldr:

>>> fromFoldableM = Prelude.foldr StreamK.consM StreamK.nil

Same as the following but more efficient:

>>> consM x xs = StreamK.fromEffect x `StreamK.append` xs

From Values

fromPure :: a -> StreamK m a Source #

Create a singleton stream from a pure value.

>>> fromPure a = a `StreamK.cons` StreamK.nil
>>> fromPure = pure
>>> fromPure = StreamK.fromEffect . pure

fromEffect :: Monad m => m a -> StreamK m a Source #

Create a singleton stream from a monadic action.

>>> fromEffect m = m `StreamK.consM` StreamK.nil
>>> Stream.fold Fold.drain $ StreamK.toStream $ StreamK.fromEffect (putStrLn "hello")
hello

From Stream

fromStream :: Monad m => Stream m a -> StreamK m a Source #

From Containers

fromFoldable :: Foldable f => f a -> StreamK m a Source #

>>> fromFoldable = Prelude.foldr StreamK.cons StreamK.nil

Construct a stream from a Foldable containing pure values:

Elimination

Primitives

uncons :: Applicative m => StreamK m a -> m (Maybe (a, StreamK m a)) Source #

drain :: Monad m => StreamK m a -> m () Source #

drain = foldl' (\_ _ -> ()) ()
drain = mapM_ (\_ -> return ())

Parsing

parseBreakChunks :: (Monad m, Unbox a) => ParserK a m b -> StreamK m (Array a) -> m (Either ParseError b, StreamK m (Array a)) Source #

Run a ParserK over a chunked StreamK and return the rest of the Stream.

parseChunks :: (Monad m, Unbox a) => ParserK a m b -> StreamK m (Array a) -> m (Either ParseError b) Source #

Transformation

mapM :: Monad m => (a -> m b) -> StreamK m a -> StreamK m b Source #

dropWhile :: (a -> Bool) -> StreamK m a -> StreamK m a Source #

take :: Int -> StreamK m a -> StreamK m a Source #

Combining Two Streams

Appending

append :: StreamK m a -> StreamK m a -> StreamK m a infixr 6 Source #

Appends two streams sequentially, yielding all elements from the first stream, and then all elements from the second stream.

>>> s1 = StreamK.fromStream $ Stream.fromList [1,2]
>>> s2 = StreamK.fromStream $ Stream.fromList [3,4]
>>> Stream.fold Fold.toList $ StreamK.toStream $ s1 `StreamK.append` s2
[1,2,3,4]

This has O(n) append performance where n is the number of streams. It can be used to efficiently fold an infinite lazy container of streams using concatMapWith et. al.

Interleaving

interleave :: StreamK m a -> StreamK m a -> StreamK m a infixr 6 Source #

Interleaves two streams, yielding one element from each stream alternately. When one stream stops the rest of the other stream is used in the output stream.

When joining many streams in a left associative manner earlier streams will get exponential priority than the ones joining later. Because of exponential weighting it can be used with concatMapWith even on a large number of streams.

Merging

mergeBy :: (a -> a -> Ordering) -> StreamK m a -> StreamK m a -> StreamK m a Source #

mergeByM :: Monad m => (a -> a -> m Ordering) -> StreamK m a -> StreamK m a -> StreamK m a Source #

Zipping

zipWith :: Monad m => (a -> b -> c) -> StreamK m a -> StreamK m b -> StreamK m c Source #

Zip two streams serially using a pure zipping function.

zipWithM :: Monad m => (a -> b -> m c) -> StreamK m a -> StreamK m b -> StreamK m c Source #

Zip two streams serially using a monadic zipping function.

Cross Product

crossWith :: Monad m => (a -> b -> c) -> StreamK m a -> StreamK m b -> StreamK m c Source #

Definition:

>>> crossWith f m1 m2 = fmap f m1 `StreamK.crossApply` m2

Note that the second stream is evaluated multiple times.

Stream of streams

concatEffect :: Monad m => m (StreamK m a) -> StreamK m a Source #

concat . fromEffect

concatMapWith :: (StreamK m b -> StreamK m b -> StreamK m b) -> (a -> StreamK m b) -> StreamK m a -> StreamK m b Source #

Perform a concatMap using a specified concat strategy. The first argument specifies a merge or concat function that is used to merge the streams generated by the map function.

mergeMapWith :: (StreamK m b -> StreamK m b -> StreamK m b) -> (a -> StreamK m b) -> StreamK m a -> StreamK m b Source #

Combine streams in pairs using a binary combinator, the resulting streams are then combined again in pairs recursively until we get to a single combined stream. The composition would thus form a binary tree.

For example, you can sort a stream using merge sort like this:

>>> s = StreamK.fromStream $ Stream.fromList [5,1,7,9,2]
>>> generate = StreamK.fromPure
>>> combine = StreamK.mergeBy compare
>>> Stream.fold Fold.toList $ StreamK.toStream $ StreamK.mergeMapWith combine generate s
[1,2,5,7,9]

Note that if the stream length is not a power of 2, the binary tree composed by mergeMapWith would not be balanced, which may or may not be important depending on what you are trying to achieve.

Caution: the stream of streams must be finite

Pre-release

Buffered Operations

sortBy :: Monad m => (a -> a -> Ordering) -> StreamK m a -> StreamK m a Source #

Sort the input stream using a supplied comparison function.

Sorting can be achieved by simply:

>>> sortBy cmp = StreamK.mergeMapWith (StreamK.mergeBy cmp) StreamK.fromPure

However, this combinator uses a parser to first split the input stream into down and up sorted segments and then merges them to optimize sorting when pre-sorted sequences exist in the input stream.

O(n) space