streamly-0.8.2: Dataflow programming and declarative concurrency
Copyright(c) 2019 Composewell Technologies
LicenseBSD3-3-Clause
Maintainerstreamly@composewell.com
Stabilitypre-release
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

Streamly.Internal.Data.Array.Stream.Foreign

Description

Combinators to efficiently manipulate streams of immutable arrays.

Synopsis

Creation

arraysOf :: (IsStream t, MonadIO m, Storable a) => Int -> t m a -> t m (Array a) Source #

arraysOf n stream groups the elements in the input stream into arrays of n elements each.

arraysOf n = Stream.chunksOf n (Array.writeN n)

Pre-release

Flattening to elements

concat :: (IsStream t, Monad m, Storable a) => t m (Array a) -> t m a Source #

Convert a stream of arrays into a stream of their elements.

Same as the following:

concat = Stream.unfoldMany Array.read

Since: 0.7.0

concatRev :: (IsStream t, Monad m, Storable a) => t m (Array a) -> t m a Source #

Convert a stream of arrays into a stream of their elements reversing the contents of each array before flattening.

concatRev = Stream.unfoldMany Array.readRev

Since: 0.7.0

interpose :: (Monad m, IsStream t, Storable a) => a -> t m (Array a) -> t m a Source #

Flatten a stream of arrays after inserting the given element between arrays.

Pre-release

interposeSuffix :: (Monad m, IsStream t, Storable a) => a -> t m (Array a) -> t m a Source #

Flatten a stream of arrays appending the given element after each array.

Since: 0.7.0

intercalateSuffix :: (Monad m, IsStream t, Storable a) => Array a -> t m (Array a) -> t m a Source #

unlines :: forall m a. (MonadIO m, Storable a) => a -> Stream m (Array a) -> Stream m a Source #

Elimination

Element Folds

fold :: (MonadIO m, Storable a) => Fold m a b -> SerialT m (Array a) -> m (b, SerialT m (Array a)) Source #

Fold an array stream using the supplied Fold. Returns the fold result and the unconsumed stream.

Internal

parse :: (MonadIO m, MonadThrow m, Storable a) => Parser m a b -> SerialT m (Array a) -> m (b, SerialT m (Array a)) Source #

Parse an array stream using the supplied Parser. Returns the parse result and the unconsumed stream. Throws ParseError if the parse fails.

Internal

parseD :: forall m a b. (MonadIO m, MonadThrow m, Storable a) => Parser m a b -> Stream m (Array a) -> m (b, Stream m (Array a)) Source #

Array Folds

foldArr :: (MonadIO m, MonadThrow m, Storable a) => Fold m a b -> SerialT m (Array a) -> m b Source #

Fold an array stream using the supplied array stream Fold.

Pre-release

foldArr_ :: (MonadIO m, MonadThrow m, Storable a) => Fold m a b -> SerialT m (Array a) -> m (b, SerialT m (Array a)) Source #

Like fold but also returns the remaining stream.

Pre-release

parseArrD :: forall m a b. (MonadIO m, MonadThrow m, Storable a) => Parser m (Array a) b -> Stream m (Array a) -> m (b, Stream m (Array a)) Source #

foldArrMany :: (IsStream t, MonadThrow m, Storable a) => Fold m a b -> t m (Array a) -> t m b Source #

Apply an array stream Fold repeatedly on an array stream and emit the fold outputs in the output stream.

See "Streamly.Prelude.foldMany" for more details.

Pre-release

toArray :: (MonadIO m, Storable a) => SerialT m (Array a) -> m (Array a) Source #

Given a stream of arrays, splice them all together to generate a single array. The stream must be finite.

Since: 0.7.0

Compaction

lpackArraysChunksOf :: (MonadIO m, Storable a) => Int -> Fold m (Array a) () -> Fold m (Array a) () Source #

compact :: (MonadIO m, Storable a) => Int -> SerialT m (Array a) -> SerialT m (Array a) Source #

Coalesce adjacent arrays in incoming stream to form bigger arrays of a maximum specified size in bytes.

Since: 0.7.0

Splitting

splitOn :: (IsStream t, MonadIO m) => Word8 -> t m (Array Word8) -> t m (Array Word8) Source #

Split a stream of arrays on a given separator byte, dropping the separator and coalescing all the arrays between two separators into a single array.

Since: 0.7.0

splitOnSuffix :: (IsStream t, MonadIO m) => Word8 -> t m (Array Word8) -> t m (Array Word8) Source #