quiver-1.0.2: Quiver finite stream processing library

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

Control.Quiver.Internal

Description

This module provides a host of common definitions, including the main Quiver processor type P, that are reexported by other Quiver modules as required.

This is the only module in the Quiver library that exposes the actual four constructors of the stream processor type P, allowing for definition of low level stream processor transformations, such as conversions between P and other stream processing libraries.

As a matter of style, Quiver users should strive to avoid explicit pattern matching on the P type and rely instead on the various high level combinators exported elsewhere, in order to improve chances of successful deforestation by the various Quiver rewrite rules.

Synopsis

Documentation

data P a a' b b' f r Source

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.

Constructors

Consume a (a' -> P a a' b b' f r) (Producer b b' f r)

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)

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))

Enclose allows for selective application of the base functor f the the remainder of the computation.

Deliver r

Deliver r completes processing of information, delivering its ultimate result r.

Instances

MFunctor (P a a' b b') Source 
MMonad (P a a' b b') Source 
MonadTrans (P a a' b b') Source 
Monad f => Monad (P a a' b b' f) Source 
Functor f => Functor (P a a' b b' f) Source 
Applicative f => Applicative (P a a' b b' f) Source 
MonadIO f => MonadIO (P a a' b b' f) Source 

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 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 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.

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.

qhoist :: Functor f => (forall x. f x -> g x) -> P a a' b b' f r -> P a a' b b' g r Source

Morphs the value of a base functor into another functor by applying the supplied functor morphism to every Enclose step of a stream processor; same as hoist from MFunctor but relaxing the 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

Embeds a monad within another monad transformer; same as embed from MMonad.