streamly-core-0.1.0: Streaming, parsers, arrays and more
Copyright(c) 2018 Composewell Technologies
(c) Roman Leshchinskiy 2008-2010
LicenseBSD-3-Clause
Maintainerstreamly@composewell.com
Stabilityexperimental
PortabilityGHC
Safe HaskellSafe-Inferred
LanguageHaskell2010

Streamly.Internal.Data.Stream.StreamD.Eliminate

Description

 
Synopsis

Running a Fold

fold :: Monad m => Fold m a b -> Stream m a -> m b Source #

Fold a stream using the supplied left Fold and reducing the resulting expression strictly at each step. The behavior is similar to foldl'. A Fold can terminate early without consuming the full stream. See the documentation of individual Folds for termination behavior.

Definitions:

>>> fold f = fmap fst . Stream.foldBreak f
>>> fold f = Stream.parse (Parser.fromFold f)

Example:

>>> Stream.fold Fold.sum (Stream.enumerateFromTo 1 100)
5050

parse :: Monad m => Parser a m b -> Stream m a -> m (Either ParseError b) Source #

Parse a stream using the supplied Parser.

Parsers (See Streamly.Internal.Data.Parser) are more powerful folds that add backtracking and error functionality to terminating folds. Unlike folds, parsers may not always result in a valid output, they may result in an error. For example:

>>> Stream.parse (Parser.takeEQ 1 Fold.drain) Stream.nil
Left (ParseError "takeEQ: Expecting exactly 1 elements, input terminated on 0")

Note: parse p is not the same as head . parseMany p on an empty stream.

parseD :: Monad m => Parser a m b -> Stream m a -> m (Either ParseError b) Source #

Run a Parse over a stream.

parseBreak :: Monad m => Parser a m b -> Stream m a -> m (Either ParseError b, Stream m a) Source #

Parse a stream using the supplied Parser.

parseBreakD :: Monad m => Parser a m b -> Stream m a -> m (Either ParseError b, Stream m a) Source #

Run a Parse over a stream and return rest of the Stream.

Stream Deconstruction

uncons :: Monad m => Stream m a -> m (Maybe (a, Stream m a)) Source #

Decompose a stream into its head and tail. If the stream is empty, returns Nothing. If the stream is non-empty, returns Just (a, ma), where a is the head of the stream and ma its tail.

Properties:

>>> Nothing <- Stream.uncons Stream.nil
>>> Just ("a", t) <- Stream.uncons (Stream.cons "a" Stream.nil)

This can be used to consume the stream in an imperative manner one element at a time, as it just breaks down the stream into individual elements and we can loop over them as we deem fit. For example, this can be used to convert a streamly stream into other stream types.

All the folds in this module can be expressed in terms of uncons, however, this is generally less efficient than specific folds because it takes apart the stream one element at a time, therefore, does not take adavantage of stream fusion.

foldBreak is a more general way of consuming a stream piecemeal.

>>> :{
uncons xs = do
    r <- Stream.foldBreak Fold.one xs
    return $ case r of
        (Nothing, _) -> Nothing
        (Just h, t) -> Just (h, t)
:}

Right Folds

foldrM :: Monad m => (a -> m b -> m b) -> m b -> Stream m a -> m b Source #

Right associative/lazy pull fold. foldrM build final stream constructs an output structure using the step function build. build is invoked with the next input element and the remaining (lazy) tail of the output structure. It builds a lazy output expression using the two. When the "tail structure" in the output expression is evaluated it calls build again thus lazily consuming the input stream until either the output expression built by build is free of the "tail" or the input is exhausted in which case final is used as the terminating case for the output structure. For more details see the description in the previous section.

Example, determine if any element is odd in a stream:

>>> s = Stream.fromList (2:4:5:undefined)
>>> step x xs = if odd x then return True else xs
>>> Stream.foldrM step (return False) s
True

foldr :: Monad m => (a -> b -> b) -> b -> Stream m a -> m b Source #

Right fold, lazy for lazy monads and pure streams, and strict for strict monads.

Please avoid using this routine in strict monads like IO unless you need a strict right fold. This is provided only for use in lazy monads (e.g. Identity) or pure streams. Note that with this signature it is not possible to implement a lazy foldr when the monad m is strict. In that case it would be strict in its accumulator and therefore would necessarily consume all its input.

>>> foldr f z = Stream.foldrM (\a b -> f a <$> b) (return z)

Note: This is similar to Fold.foldr' (the right fold via left fold), but could be more efficient.

foldrMx :: Monad m => (a -> m x -> m x) -> m x -> (m x -> m b) -> Stream m a -> m b Source #

foldr1 :: Monad m => (a -> a -> a) -> Stream m a -> m (Maybe a) Source #

Left Folds

foldlM' :: Monad m => (b -> a -> m b) -> m b -> Stream m a -> m b Source #

foldl' :: Monad m => (b -> a -> b) -> b -> Stream m a -> m b Source #

foldlMx' :: Monad m => (x -> a -> m x) -> m x -> (x -> m b) -> Stream m a -> m b Source #

foldlx' :: Monad m => (x -> a -> x) -> x -> (x -> b) -> Stream m a -> m b Source #

Specific Fold Functions

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

Definitions:

>>> drain = Stream.fold Fold.drain
>>> drain = Stream.foldrM (\_ xs -> xs) (return ())

Run a stream, discarding the results.

mapM_ :: Monad m => (a -> m b) -> Stream m a -> m () Source #

Execute a monadic action for each element of the Stream

null :: Monad m => Stream m a -> m Bool Source #

head :: Monad m => Stream m a -> m (Maybe a) Source #

headElse :: Monad m => a -> Stream m a -> m a Source #

tail :: Monad m => Stream m a -> m (Maybe (Stream m a)) Source #

last :: Monad m => Stream m a -> m (Maybe a) Source #

elem :: (Monad m, Eq a) => a -> Stream m a -> m Bool Source #

notElem :: (Monad m, Eq a) => a -> Stream m a -> m Bool Source #

all :: Monad m => (a -> Bool) -> Stream m a -> m Bool Source #

any :: Monad m => (a -> Bool) -> Stream m a -> m Bool Source #

maximum :: (Monad m, Ord a) => Stream m a -> m (Maybe a) Source #

maximumBy :: Monad m => (a -> a -> Ordering) -> Stream m a -> m (Maybe a) Source #

minimum :: (Monad m, Ord a) => Stream m a -> m (Maybe a) Source #

minimumBy :: Monad m => (a -> a -> Ordering) -> Stream m a -> m (Maybe a) Source #

lookup :: (Monad m, Eq a) => a -> Stream m (a, b) -> m (Maybe b) Source #

findM :: Monad m => (a -> m Bool) -> Stream m a -> m (Maybe a) Source #

find :: Monad m => (a -> Bool) -> Stream m a -> m (Maybe a) Source #

(!!) :: Monad m => Stream m a -> Int -> m (Maybe a) Source #

the :: (Eq a, Monad m) => Stream m a -> m (Maybe a) Source #

To containers

toList :: Monad m => Stream m a -> m [a] Source #

Definitions:

>>> toList = Stream.foldr (:) []
>>> toList = Stream.fold Fold.toList

Convert a stream into a list in the underlying monad. The list can be consumed lazily in a lazy monad (e.g. Identity). In a strict monad (e.g. IO) the whole list is generated and buffered before it can be consumed.

Warning! working on large lists accumulated as buffers in memory could be very inefficient, consider using Streamly.Data.Array instead.

Note that this could a bit more efficient compared to Stream.fold Fold.toList, and it can fuse with pure list consumers.

toListRev :: Monad m => Stream m a -> m [a] Source #

Multi-Stream Folds

Comparisons

These should probably be expressed using zipping operations.

eqBy :: Monad m => (a -> b -> Bool) -> Stream m a -> Stream m b -> m Bool Source #

Compare two streams for equality

cmpBy :: Monad m => (a -> b -> Ordering) -> Stream m a -> Stream m b -> m Ordering Source #

Compare two streams lexicographically.

Substreams

These should probably be expressed using parsers.

isPrefixOf :: (Monad m, Eq a) => Stream m a -> Stream m a -> m Bool Source #

Returns True if the first stream is the same as or a prefix of the second. A stream is a prefix of itself.

>>> Stream.isPrefixOf (Stream.fromList "hello") (Stream.fromList "hello" :: Stream IO Char)
True

isInfixOf :: (MonadIO m, Eq a, Enum a, Storable a, Unbox a) => Stream m a -> Stream m a -> m Bool Source #

Returns True if the first stream is an infix of the second. A stream is considered an infix of itself.

>>> s = Stream.fromList "hello" :: Stream IO Char
>>> Stream.isInfixOf s s
True

Space: O(n) worst case where n is the length of the infix.

Pre-release

Requires Storable constraint

isSuffixOf :: (Monad m, Eq a) => Stream m a -> Stream m a -> m Bool Source #

Returns True if the first stream is a suffix of the second. A stream is considered a suffix of itself.

>>> Stream.isSuffixOf (Stream.fromList "hello") (Stream.fromList "hello" :: Stream IO Char)
True

Space: O(n), buffers entire input stream and the suffix.

Pre-release

Suboptimal - Help wanted.

isSuffixOfUnbox :: (MonadIO m, Eq a, Unbox a) => Stream m a -> Stream m a -> m Bool Source #

Much faster than isSuffixOf.

isSubsequenceOf :: (Monad m, Eq a) => Stream m a -> Stream m a -> m Bool Source #

Returns True if all the elements of the first stream occur, in order, in the second stream. The elements do not have to occur consecutively. A stream is a subsequence of itself.

>>> Stream.isSubsequenceOf (Stream.fromList "hlo") (Stream.fromList "hello" :: Stream IO Char)
True

stripPrefix :: (Monad m, Eq a) => Stream m a -> Stream m a -> m (Maybe (Stream m a)) Source #

stripPrefix prefix input strips the prefix stream from the input stream if it is a prefix of input. Returns Nothing if the input does not start with the given prefix, stripped input otherwise. Returns Just nil when the prefix is the same as the input stream.

Space: O(1)

stripSuffix :: (Monad m, Eq a) => Stream m a -> Stream m a -> m (Maybe (Stream m a)) Source #

Drops the given suffix from a stream. Returns Nothing if the stream does not end with the given suffix. Returns Just nil when the suffix is the same as the stream.

It may be more efficient to convert the stream to an Array and use stripSuffix on that especially if the elements have a Storable or Prim instance.

See also "Streamly.Internal.Data.Stream.Reduce.dropSuffix".

Space: O(n), buffers the entire input stream as well as the suffix

Pre-release

stripSuffixUnbox :: (MonadIO m, Eq a, Unbox a) => Stream m a -> Stream m a -> m (Maybe (Stream m a)) Source #

Much faster than stripSuffix.