distributed-process-0.2.0.1: Cloud Haskell: Erlang-style concurrency in Haskell

Safe HaskellNone

Control.Distributed.Process.Internal.Closure.Combinators

Contents

Synopsis

Generic combinators

closureConst :: forall a b. (Typeable a, Typeable b) => Closure (a -> b -> a)Source

Arrow combinators for processes

type CP a b = Closure (a -> Process b)Source

cpId :: forall a. Typeable a => CP a aSource

cpComp :: forall a b c. (Typeable a, Typeable b, Typeable c) => CP a b -> CP b c -> CP a cSource

cpFirst :: forall a b c. (Typeable a, Typeable b, Typeable c) => CP a b -> CP (a, c) (b, c)Source

cpSwap :: forall a b. (Typeable a, Typeable b) => CP (a, b) (b, a)Source

cpSecond :: (Typeable a, Typeable b, Typeable c) => CP a b -> CP (c, a) (c, b)Source

cpPair :: (Typeable a, Typeable a', Typeable b, Typeable b') => CP a b -> CP a' b' -> CP (a, a') (b, b')Source

cpCopy :: forall a. Typeable a => CP a (a, a)Source

cpFanOut :: (Typeable a, Typeable b, Typeable c) => CP a b -> CP a c -> CP a (b, c)Source

cpLeft :: forall a b c. (Typeable a, Typeable b, Typeable c) => CP a b -> CP (Either a c) (Either b c)Source

cpMirror :: forall a b. (Typeable a, Typeable b) => CP (Either a b) (Either b a)Source

cpRight :: forall a b c. (Typeable a, Typeable b, Typeable c) => CP a b -> CP (Either c a) (Either c b)Source

cpEither :: (Typeable a, Typeable a', Typeable b, Typeable b') => CP a b -> CP a' b' -> CP (Either a a') (Either b b')Source

cpUntag :: forall a. Typeable a => CP (Either a a) aSource

cpFanIn :: (Typeable a, Typeable b, Typeable c) => CP a c -> CP b c -> CP (Either a b) cSource

cpApply :: forall a b. (Typeable a, Typeable b) => CP (CP a b, a) bSource

Derived process operators