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 the core types and combinators of the Quiver stream processing library.
- data P a a' b b' f r
- type Consumer a a' f r = forall b b'. P a a' b b' f r
- type Producer b b' f r = forall a a'. P a a' b b' f r
- type Effect f r = forall a a' b b'. P a a' b b' f r
- consume :: a -> (a' -> P a a' b b' f r) -> Producer b b' f r -> P a a' b b' f r
- produce :: b -> (b' -> P a a' b b' f r) -> Consumer a a' f r -> P a a' b b' f r
- enclose :: f (P a a' b b' f r) -> P a a' b b' f r
- deliver :: r -> P a a' b b' f r
- decouple :: Functor f => P a a' b b' f r -> Producer b b' f r
- deplete :: Functor f => P a a' b b' f r -> Consumer a a' f r
- fetch :: Functor f => a -> P a a' b b' f (Maybe a')
- fetch_ :: a -> P a a' b b' f ()
- emit :: b -> P a a' b b' f (Maybe b')
- emit_ :: b -> P a a' b b' f ()
- qlift :: Functor f => f r -> P a a' b b' f r
- qhoist :: Functor f => (forall x. f x -> g x) -> P a a' b b' f r -> P a a' b b' g r
- qembed :: Monad g => (forall x. f x -> P a a' b b' g x) -> P a a' b b' f r -> P a a' b b' g r
- qpure :: (b' -> a) -> (a' -> b) -> b' -> P a a' b b' f (Either a b)
- qid :: b -> P b a a b f ()
- qconcat :: [b] -> P [b] [a] a b f ([a], [b])
- qtraverse :: Functor f => (b' -> f a) -> (a' -> f b) -> b' -> P a a' b b' f (Either a b)
- runEffect :: Monad f => Effect f r -> f r
- (>>->) :: Functor f => P a a' b b' f r1 -> P b' b c c' f r2 -> P a a' c c' f (r1, r2)
- (>->>) :: Functor f => P a a' b b' f r1 -> P b' b c c' f r2 -> P a a' c c' f (r1, r2)
- (+>>->) :: Functor f => P a a' b b' f r1 -> P b' b c c' f r2 -> P a a' c c' f (P a a' b b' f r1, r2)
- (>>->+) :: Functor f => P a a' b b' f r1 -> P b' b c c' f r2 -> P a a' c c' f (r1, P b' b c c' f r2)
- (+>->>) :: Functor f => P a a' b b' f r1 -> P b' b c c' f r2 -> P a a' c c' f (P a a' b b' f r1, r2)
- (>->>+) :: Functor f => P a a' b b' f r1 -> P b' b c c' f r2 -> P a a' c c' f (r1, P b' b c c' f r2)
- (>&>) :: Functor f => P a a' b b' f r -> (r -> r') -> P a a' b b' f r'
- qcompose :: Functor f => (r1 -> r2 -> r) -> P a a' b b' f r1 -> P b' b c c' f r2 -> P a a' c c' f r
Documentation
The main Quiver stream processor type P a a' b b' f r
,
representing a producerconsumer structure with bidirectional/,
bounded communication on both the upstream (consumer) and
downstream (producer) channel. The six type parameters have
the following intuitive meaning:
a
is the type of a request values sent by the stream processor to its upstream partner in order to receive the next element of the input stream.a'
is the type of the actual information being consumed by this stream processor (i.e., elements of its input stream.)b
is the type of the actual information being produced by this stream processor (i.e., elements of its output stream.)b'
is the type of the response values received from the downstream partner for each element of the output stream produced by this stream processor.f
is the type of the stream processor's base functor; usually this is a monad used for stateful stream processing, exception handling and/or real-world interaction.r
is the stream processor's delivery type, used for monadic stream processor definition.
Every stream processor is a functor over its delivery type.
However, if the base functor f
meets the additional requirements
of Applicative
or Monad
, so will the stream processor itself.
Note that, unlike most other stream processing libraries, f
is not required to be a monad in most applications, although
only time will tell whether this generalisation has useful
applications in the real world.
type Consumer a a' f r = forall b b'. P a a' b b' f r Source
A Quiver consumer, represented by a stream processor with unspecified output types.
type Producer b b' f r = forall a a'. P a a' b b' f r Source
A Quiver producer, represented by a stream processor with unspecified input types.
type Effect f r = forall a a' b b'. P a a' b b' f r Source
A Quiver effect, represented by a stream processor with unspecified input and output types.
consume :: a -> (a' -> P a a' b b' f r) -> Producer b b' f r -> P a a' b b' f r Source
consume x k q
represents a consumer step, in which
the request x
is sent upstream and the returned input
value is supplied to the continuation processor k
,
or, if the upstream partner has been depleted (i.e.,
delivered its ultimate result, hence reaching the end
of processing), to the decoupled continuation q
.
produce :: b -> (b' -> P a a' b b' f r) -> Consumer a a' f r -> P a a' b b' f r Source
produce y k q
represent a producer step, in which
the output value y
is sent downstream, and the returned
acknowledgement is supplied to the continuation processor
k
, or, if the downstream partner has been decoupled
(i.e., delivered its ultimate result, hence reaching the end
of processing), to the depleted continuation q
.
enclose :: f (P a a' b b' f r) -> P a a' b b' f r Source
enclose
allows for selective application of the base
functor f
the the remainder of the computation.
deliver :: r -> P a a' b b' f r Source
deliver r
completes processing of information, delivering
its ultimate result r
.
decouple :: Functor f => P a a' b b' f r -> Producer b b' f r Source
decouple p
decouples the stream processor p
, by replacing
the first consumer step in p
with that step's decoupled contination,
effectively converting p
into a producer processor that no longer
expects to receive any input.
deplete :: Functor f => P a a' b b' f r -> Consumer a a' f r Source
deplete p
depletes the stream processor p
, by replacing
the first producer step in p
with that step's depleted contination,
effectively converting p
into a consumer processor that will never
produce any more output.
fetch :: Functor f => a -> P a a' b b' f (Maybe a') Source
fetch x
represents a singleton 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.
fetch_ :: a -> P a a' b b' f () Source
fetch_ x
represents a singleton stream processor that
sends the request value x
upstream, discarding any
input received, for symmetry with emit_
.
emit :: b -> P a a' b b' f (Maybe b') Source
emit y
represents a singleton stream processor that
produces a single output value y
and delivers the
response received from the downstream processor, or
Nothing
if the downstream processor has been decoupled.
emit_ :: b -> P a a' b b' f () Source
emit_ y
represents a singleton stream processor that
produces a single output value y
, ignoring any response
received from the downstream processor.
qlift :: Functor f => f r -> P a a' b b' f r Source
Lifts the value of a base functor into a stream processor;
same as lift
from MonadTrans
, but relaxing constraint
on the base structure from Monad
to Functor
.
qembed :: Monad g => (forall x. f x -> P a a' b b' g x) -> P a a' b b' f r -> P a a' b b' g r Source
qpure :: (b' -> a) -> (a' -> b) -> b' -> P a a' b b' f (Either a b) Source
qpure g f z
produces an infinite consumer/producer that
uses a pure function f
to convert every input value into
an output, and g
to convert each downstream response value
into an upstream request; the initial request is obtained
by applying g
to the initial response value z
.
qconcat :: [b] -> P [b] [a] a b f ([a], [b]) Source
A pull-based list flattening processor, delivering the list of inputs that could not be produced and a list of responses that could not be consumed.
qtraverse :: Functor f => (b' -> f a) -> (a' -> f b) -> b' -> P a a' b b' f (Either a b) Source
qtraverse g f z
produces an infinite consumer/producer that
uses a functor f
to convert every input value into
an output, and g
to convert each downstream response value
into an upstream request; the initial request is obtained
by applying g
to the initial response value z
.
runEffect :: Monad f => Effect f r -> f r Source
Evaluates an effect, i.e., a processor that is both detached and depleted and hence neither consumes nor produces any input, returning its delivered value. The base functor must be a monad.
(>>->) :: Functor f => P a a' b b' f r1 -> P b' b c c' f r2 -> P a a' c c' f (r1, r2) infixl 1 Source
The >>->
represents a push-based composition of stream processors.
p1 >>-> p2
represents a stream processor that forwards the output
of p1
to p2
, delivering the result of both processors.
The new processor is driven by p2
, so, if the base functor
represents a non-commutative monad, any effects of p2
will be
observed before those of p1
.
(>->>) :: Functor f => P a a' b b' f r1 -> P b' b c c' f r2 -> P a a' c c' f (r1, r2) infixl 1 Source
The >->>
represents a pull-based composition of stream processors.
p1 >->> p2
represents a stream processor that forwards the output
of p1
to p2
, delivering the result of both processors.
The new processor is driven by p2
, so, if the base functor
represents a non-commutative monad, any effects of p2
will be
observed before those of p1
.
(+>>->) :: Functor f => P a a' b b' f r1 -> P b' b c c' f r2 -> P a a' c c' f (P a a' b b' f r1, r2) infixl 1 Source
The +>>->
represents a pull-based composition of stream processors
that is partial on the left (supply) side, so that p1 +>>-> p2
represents a stream processor that forwards the output of p1
to p2
,
delivering the result of p2
and the remainder (unconsumed portion)
of p1
. The new processor is driven by p1
, so, if the base functor
represents a non-commutative monad, any effects of p1
will be observed
before those of p2
.
(>>->+) :: Functor f => P a a' b b' f r1 -> P b' b c c' f r2 -> P a a' c c' f (r1, P b' b c c' f r2) infixl 1 Source
The >>->+
represents a pull-based composition of stream processors
that is partial on the right (demand) side, so that p1 >>->+ p2
represents a stream processor that forwards the output of p1
to p2
,
delivering the result of p1
and the remainder (unproduced portion)
of p2
. The new processor is driven by p1
, so, if the base functor
represents a non-commutative monad, any effects of p1
will be observed
before those of p2
.
(+>->>) :: Functor f => P a a' b b' f r1 -> P b' b c c' f r2 -> P a a' c c' f (P a a' b b' f r1, r2) infixl 1 Source
The +>->>
represents a pull-based composition of stream processors.
that is partial on the left (supply) side, so that p1 +>->> p2
represents a stream processor that forwards the output of p1
to p2
,
delivering the result of p2
and the remainder (unconsumed portion)
of p1
. The new processor is driven by p2
, so, if the base functor
represents a non-commutative monad, any effects of p2
will be observed
before those of p1
.
(>->>+) :: Functor f => P a a' b b' f r1 -> P b' b c c' f r2 -> P a a' c c' f (r1, P b' b c c' f r2) infixl 1 Source
The >>->+
represents a pull-based composition of stream processors
that is partial on the right (demand) side, so that p1 >->>+ p2
represents a stream processor that forwards the output of p1
to p2
,
delivering the result of p1
and the remainder (unproduced portion)
of p2
. The new processor is driven by p2
, so, if the base functor
represents a non-commutative monad, any effects of p2
will be observed
before those of p1
.