Copyright | © 2015 Patryk Zadarnowski <pat@jantar.org> |
---|---|
License | BSD3 |
Maintainer | pat@jantar.org |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
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.
- module Control.Quiver
- type SQ a b f r = forall b'. P () a b b' f r
- type SP a b f e = SQ a b f (SPResult e)
- type SProducer b f e = forall b'. Producer b b' f (SPResult e)
- type SConsumer a f e = Consumer () a f (SPResult e)
- type SEffect f e = Effect f (SPResult e)
- type SPResult e = Maybe (Maybe e)
- pattern SPComplete :: Maybe (Maybe t)
- pattern SPFailed :: t -> Maybe (Maybe t)
- pattern SPIncomplete :: Maybe t
- spcomplete :: P a a' b b' f (SPResult e)
- spfailed :: e -> P a a' b b' f (SPResult e)
- spincomplete :: P a a' b b' f (SPResult e)
- spconsume :: (a' -> P () a' b b' f r) -> Producer b b' f r -> P () a' b b' f r
- spfetch :: Functor f => SQ a b f (Maybe a)
- spemit :: b -> P a a' b b' f (SPResult e)
- (>:>) :: b -> P a a' b b' f (SPResult e) -> P a a' b b' f (SPResult e)
- (>>?) :: 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)
- (>>!) :: 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')
- sppure :: (a -> b) -> SP a b f e
- spid :: SP a a f e
- spconcat :: Foldable t => SP (t a) a f e
- spfilter :: (a -> Bool) -> SP a a f e
- spfold :: Monoid a => SQ a x f a
- spfold' :: Monoid a => SQ a x f a
- spfoldl :: (b -> a -> b) -> b -> SQ a x f b
- spfoldl' :: (b -> a -> b) -> b -> SQ a x f b
- spfoldr :: (a -> b -> b) -> b -> SQ a x f b
- sptraverse :: Functor m => (a -> m b) -> SP a b m e
- sptraverse_ :: Functor m => (a -> m ()) -> SConsumer a m e
- spevery :: Foldable t => t a -> SProducer a f e
- spforever :: Functor f => f a -> SProducer a f e
- spuntil :: (a -> Bool) -> SP a a f e
- spwhile :: (a -> Bool) -> SP a a f e
- spWhileJust :: SP (Maybe a) a f e
- sprun :: Monad f => forall a b. SQ a b f r -> f r
Documentation
module Control.Quiver
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 b'. Producer b b' f (SPResult e) Source
A producer version of a simple processor.
pattern SPComplete :: Maybe (Maybe t) Source
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.
spincomplete :: P a a' b b' f (SPResult e) Source
Delivers an SPIncomplete
result.
spconsume :: (a' -> P () a' b b' f r) -> Producer b b' f r -> P () a' b b' f r Source
Consumes an single input value of a simple stream processor.
spfetch :: Functor f => SQ a b f (Maybe a) Source
spfetch
represents a singleton simple stream processor that
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 ())
.
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.
Note that this can be quite inefficient for long streams, since
the entire chain of applications of f
needs to be materialised
on the heap before it can ever be applied to the final value and
reduced at the end of the stream.
sptraverse :: Functor 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_ :: Functor m => (a -> m ()) -> SConsumer a m e Source
A processor that consumes every input elemnet using a monadic function.
spevery :: Foldable t => t a -> SProducer a f e Source
Produces every element of a foldable structure.
spforever :: Functor f => f a -> SProducer a f e Source
Produces infinite sequence of monadic results.
spuntil :: (a -> Bool) -> SP a a f e Source
Interrupts processing on input that matches a specified predicate.
spwhile :: (a -> Bool) -> SP a a f e Source
Interrupts processing on input that doesn't match a specified predicate.
spWhileJust :: SP (Maybe a) a f e Source
Interrupts processing on a first occurence of Nothing
in the input stream.