quiver-1.0.0: Quiver finite stream processing library

Copyright© 2015 Patryk Zadarnowski <pat@jantar.org>
LicenseBSD3
Maintainerpat@jantar.org
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Control.Quiver.SP

Description

This module provides a definition of a simple processor with a unit request type and an unspecified acknowledgement type, together with a number of common combinators for their definitions.

Synopsis

Documentation

type SQ a b f r = forall b'. P () a b b' f r Source

A simple processor step with a unit request type and an unspecified response type:

type SP a b f e = SQ a b f (SPResult e) Source

A simple processor with a unit request type, an unspecified response type and a result type tailored towards reporting the terminating condition of an intermediate component in a composed “processor stack”.

type SProducer b f e = forall a. SP a b f e Source

A producer version of a simple processor.

type SConsumer a f e = forall b. SP a b f e Source

A consumer version of a simple processor.

type SEffect f e = forall a b. SP a b f e Source

An effect version of a simple processor.

type SPResult e = Maybe (Maybe e) Source

Simple processor result type.

pattern SPComplete :: Maybe (Maybe t) Source

('Just Nothing') Simple processor result value indicating successful processing of the entire input stream.

pattern SPFailed :: t -> Maybe (Maybe t) Source

('Just (Just e)') Simple processor result value indicating unsuccessful processing of the input stream.

pattern SPIncomplete :: Maybe t Source

(Nothing) Simple processor result value indicating premature termination of the consumer.

spcomplete :: P a a' b b' f (SPResult e) Source

Delivers an SPComplete result.

spfailed :: e -> P a a' b b' f (SPResult e) Source

Delivers an SPFailed result.

spincomplete :: P a a' b b' f (SPResult e) Source

Delivers an SPIncomplete result.

spfetch :: Functor f => SQ a b f (Maybe a) Source

spfetch represents a singleton simple stream processor that sends the request value x upstream and delivers the next input value received, or Nothing if the upstream processor has been depleted.

spemit :: b -> P a a' b b' f (SPResult e) Source

spemit y represents a singleton stream processor that produces a single output value y, delivering either SPComplete if y was consumed by the downstream processor, or SPIncomplete otherwise.

(>:>) :: b -> P a a' b b' f (SPResult e) -> P a a' b b' f (SPResult e) infixr 5 Source

y >:> p represents a singleton stream processor that produces a single output value y and continues with the processor p, deliverying SPIncomplete if y could not be consumed by the downstream processor.

(>>?) :: Monad f => P a a' b b' f (SPResult e) -> P a a' b b' f (SPResult e) -> P a a' b b' f (SPResult e) infixl 1 Source

p >>? q continues processing of p with q but only if p completes successsfully by delivering SPComplete, short-circuiting q if p fails with SPIncomplete or SPFailed.

(>>!) :: Monad f => P a a' b b' f (SPResult e) -> (e -> P a a' b b' f (SPResult e')) -> P a a' b b' f (SPResult e') infixl 1 Source

p >>! k is equivalent to p, with any failures in p supplied to the continuation processor k. Note that k is not executed if p completes successfully with SPComplete or is interrupted by the downstream processor, delivering SPIncomplete.

sppure :: (a -> b) -> SP a b f e Source

sppure f produces an infinite consumer/producer that uses a pure function f to convert every input value into an output; equivalent to qpure id f (const ()).

spid :: SP a a f e Source

A simple identity processor, equivalent to 'sppure id'.

spconcat :: SP [a] a f e Source

A simple list flattening processor requests.

spfold :: Monoid a => SQ a x f a Source

A processor that delivers the entire input of the stream folded into a single value using mappend.

spfold' :: Monoid a => SQ a x f a Source

A processor that delivers the entire input of the stream folded into a single value using strict application of mappend.

spfoldl :: (b -> a -> b) -> b -> SQ a x f b Source

A processor that delivers the entire input of the stream folded into a single value using the supplied left-associative function and initial value.

spfoldl' :: (b -> a -> b) -> b -> SQ a x f b Source

A processor that delivers the entire input of the stream folded into a single value using strict application of the supplied left-associative function and initial value.

spfoldr :: (a -> b -> b) -> b -> SQ a x f b Source

A processor that delivers the entire input of the stream folded into a single value using the supplied right-associative function and initial value.

spfoldr' :: (a -> b -> b) -> b -> SQ a x f b Source

A processor that delivers the entire input of the stream folded into a single value using strict application of the supplied right-associative function and initial value.

sptraverse :: Monad m => (a -> m b) -> SP a b m e Source

A processor that applies a monadic function to every input element and emits the resulting value.

sptraverse_ :: Monad m => (a -> m ()) -> SP a b m e Source

A processor that consumes every input elemnet using a monadic function.