machines-0.6.2: Networked stream transducers

Copyright(C) 2015 Yorick Laupa Gabriel Gonzalez
LicenseBSD-style (see the file LICENSE)
MaintainerYorick Laupa <yo.eight@gmail.com>
Stabilityprovisional
PortabilityRank-2 Types, GADTs
Safe HaskellNone
LanguageHaskell2010

Data.Machine.Pipe

Description

Allows bidirectional communication between two MachineT. Exposed the same interface of Pipes library.

Synopsis

Documentation

data Exchange a' a b' b c where Source #

Constructors

Request :: a' -> Exchange a' a b' b a 
Respond :: b -> Exchange a' a b' b b' 

type Proxy a' a b' b m c = MachineT m (Exchange a' a b' b) c Source #

type Effect m r = Proxy Void () () Void m r Source #

Effects neither request nor respond

type Client a' a m r = Proxy a' a () Void m r Source #

Client a' a sends requests of type a' and receives responses of type a. Clients only request and never respond.

type Server b' b m r = Proxy Void () b' b m r Source #

Server b' b receives requests of type b' and sends responses of type b. Servers only respond and never request.

type Effect' m r = forall x' x y' y. Proxy x' x y' y m r Source #

Like Effect, but with a polymorphic type

type Server' b' b m r = forall x' x. Proxy x' x b' b m r Source #

Like Server, but with a polymorphic type

type Client' a' a m r = forall y' y. Proxy a' a y' y m r Source #

Like Client, but with a polymorphic type

request :: a' -> PlanT (Exchange a' a y' y) o m a Source #

Send a value of type a' upstream and block waiting for a reply of type a. request is the identity of the request category.

respond :: a -> PlanT (Exchange x' x a' a) o m a' Source #

Send a value of type a downstream and block waiting for a reply of type a' respond is the identity of the respond category.

push :: Monad m => a -> Proxy a' a a' a m r Source #

Forward responses followed by requests. push is the identity of the push category.

(>~>) :: Monad m => (_a -> Proxy a' a b' b m r) -> (b -> Proxy b' b c' c m r) -> _a -> Proxy a' a c' c m r infixl 8 Source #

Compose two proxies blocked while requesting data, creating a new proxy blocked while requesting data. (>~>) is the composition operator of the push category.

(>>~) :: Monad m => Proxy a' a b' b m r -> (b -> Proxy b' b c' c m r) -> Proxy a' a c' c m r infixl 7 Source #

(p >>~ f) pairs each respond in p with an request in f.

pull :: Monad m => a' -> Proxy a' a a' a m r Source #

Forward requests followed by responses. pull is the identity of the pull category.

(>+>) :: Monad m => (b' -> Proxy a' a b' b m r) -> (_c' -> Proxy b' b c' c m r) -> _c' -> Proxy a' a c' c m r infixl 7 Source #

Compose two proxies blocked in the middle of responding, creating a new proxy blocked in the middle of responding. (>+>) is the composition operator of the pull category.

(+>>) :: Monad m => (b' -> Proxy a' a b' b m r) -> Proxy b' b c' c m r -> Proxy a' a c' c m r infixr 6 Source #

(f +>> p) pairs each request in p with a respond in f.

absurdExchange :: Exchange Void a b Void t -> c Source #

It is impossible for an Exchange to hold a Void value.

runEffect :: Monad m => Effect m o -> m [o] Source #

Run a self-contained Effect, converting it back to the base monad.

runEffect_ :: Monad m => Effect m o -> m () Source #

Like runEffect but discarding any produced value.