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

Streamly.Internal.Data.Fold.Chunked

Description

Use Streamly.Data.Parser.Chunked instead.

Fold a stream of foreign arrays. Fold m a b in this module works on a stream of "Array a" and produces an output of type b.

Though Fold m a b in this module works on a stream of Array a it is different from Data.Fold m (Array a) b. While the latter works on arrays as a whole treating them as atomic elements, the folds in this module can work on the stream of arrays as if it is an element stream with all the arrays coalesced together. This module allows adapting the element stream folds in Data.Fold to correctly work on an array stream as if it is an element stream. For example:

>>> import qualified Streamly.Data.Fold as Fold
>>> import qualified Streamly.Internal.Data.Stream.Chunked as ArrayStream
>>> import qualified Streamly.Internal.Data.Fold.Chunked as ChunkFold
>>> import qualified Streamly.Data.Stream as Stream
>>> import qualified Streamly.Data.StreamK as StreamK
>>> f = ChunkFold.fromFold (Fold.take 7 Fold.toList)
>>> s = Stream.chunksOf 5 $ Stream.fromList "hello world"
>>> ArrayStream.runArrayFold f (StreamK.fromStream s)
Right "hello w"
Synopsis

Documentation

newtype ChunkFold m a b Source #

Array stream fold.

An array stream fold is basically an array stream Parser that does not fail. In case of array stream folds the count in Partial, Continue and Done is a count of elements that includes the leftover element count in the array that is currently being processed by the parser. If none of the elements is consumed by the parser the count is at least the whole array length. If the whole array is consumed by the parser then the count will be 0.

Pre-release

Constructors

ChunkFold (Parser (Array a) m b) 

Instances

Instances details
Monad m => Applicative (ChunkFold m a) Source #

Applicative form of splitWith. > (*) = splitWith id

Instance details

Defined in Streamly.Internal.Data.Fold.Chunked

Methods

pure :: a0 -> ChunkFold m a a0 #

(<*>) :: ChunkFold m a (a0 -> b) -> ChunkFold m a a0 -> ChunkFold m a b #

liftA2 :: (a0 -> b -> c) -> ChunkFold m a a0 -> ChunkFold m a b -> ChunkFold m a c #

(*>) :: ChunkFold m a a0 -> ChunkFold m a b -> ChunkFold m a b #

(<*) :: ChunkFold m a a0 -> ChunkFold m a b -> ChunkFold m a a0 #

Functor m => Functor (ChunkFold m a) Source #

Maps a function over the result of fold.

Pre-release

Instance details

Defined in Streamly.Internal.Data.Fold.Chunked

Methods

fmap :: (a0 -> b) -> ChunkFold m a a0 -> ChunkFold m a b #

(<$) :: a0 -> ChunkFold m a b -> ChunkFold m a a0 #

Monad m => Monad (ChunkFold m a) Source #

Monad instance applies folds sequentially. Next fold can depend on the output of the previous fold. See concatMap.

(>>=) = flip concatMap
Instance details

Defined in Streamly.Internal.Data.Fold.Chunked

Methods

(>>=) :: ChunkFold m a a0 -> (a0 -> ChunkFold m a b) -> ChunkFold m a b #

(>>) :: ChunkFold m a a0 -> ChunkFold m a b -> ChunkFold m a b #

return :: a0 -> ChunkFold m a a0 #

Construction

fromFold :: forall m a b. (MonadIO m, Unbox a) => Fold m a b -> ChunkFold m a b Source #

Convert an element Fold into an array stream fold.

Pre-release

adaptFold :: forall m a b. MonadIO m => Fold m (Array a) b -> ChunkFold m a b Source #

Adapt an array stream fold.

Pre-release

fromParser :: forall m a b. (MonadIO m, Unbox a) => Parser a m b -> ChunkFold m a b Source #

Convert an element Parser into an array stream fold. If the parser fails the fold would throw an exception.

Pre-release

fromParserD :: forall m a b. (MonadIO m, Unbox a) => Parser a m b -> ChunkFold m a b Source #

Convert an element Parser into an array stream fold. If the parser fails the fold would throw an exception.

Pre-release

Mapping

rmapM :: Monad m => (b -> m c) -> ChunkFold m a b -> ChunkFold m a c Source #

Map a monadic function on the output of a fold.

Pre-release

Applicative

fromPure :: Monad m => b -> ChunkFold m a b Source #

A fold that always yields a pure value without consuming any input.

Pre-release

fromEffect :: Monad m => m b -> ChunkFold m a b Source #

A fold that always yields the result of an effectful action without consuming any input.

Pre-release

splitWith :: Monad m => (a -> b -> c) -> ChunkFold m x a -> ChunkFold m x b -> ChunkFold m x c Source #

Applies two folds sequentially on the input stream and combines their results using the supplied function.

Pre-release

Monad

concatMap :: Monad m => (b -> ChunkFold m a c) -> ChunkFold m a b -> ChunkFold m a c Source #

Applies a fold on the input stream, generates the next fold from the output of the previously applied fold and then applies that fold.

Pre-release

Combinators

take :: forall m a b. (Monad m, Unbox a) => Int -> ChunkFold m a b -> ChunkFold m a b Source #

Take n array elements (a) from a stream of arrays (Array a).