pipes-3.1.0: Compositional pipelines

Safe HaskellSafe
LanguageHaskell98

Control.PFunctor

Contents

Description

This module defines functors in the category of proxies

Synopsis

Functors over Proxies

class PFunctor t where Source #

A functor in the category of proxies

hoistP f . hoistP g = hoistP (f . g)

hoistP id = id

If f is a proxy morphism, then hoistP f is a proxy morphism, meaning that hoistPK f = (hoistP f .) defines a functor between five categories.

Functor between Kleisli categories:

hoistPK f p1 >=> hoistPK f p2 = hoistPK f (p1 >=> p2)

hoistPK f return = return

Functor between Proxy categories:

hoistPK f p1 >-> hoistPK f p2 = hoistPK f (p1 >-> p2)

hoistPK f idT = idT
hoistPK f p1 >~> hoistPK f p2 = hoistPK f (p1 >~> p2)

hoistPK f coidT = coidT

Functor between "request" categories:

hoistPK f p1 \>\ hoistPK f p2 = hoistPK f (p2 \>\ p2)

hoistPK f request = request

Functor between "respond" categories:

hoistPK f p1 />/ hoistPK f p2 = hoistPK f (p2 />/ p2)

hoistPK f respond = respond

Minimal complete definition

hoistP

Methods

hoistP :: (Monad m, Proxy p1) => (forall r1. p1 a' a b' b m r1 -> p2 a' a b' b n r1) -> t p1 a' a b' b m r2 -> t p2 a' a b' b n r2 Source #

Lift a proxy morphism from p1 to p2 into a proxy morphism from (t p1) to (t p2)

Instances

PFunctor IdentityP Source # 

Methods

hoistP :: (Monad m, Proxy p1) => (forall r1. p1 a' a b' b m r1 -> p2 a' a b' b n r1) -> IdentityP p1 a' a b' b m r2 -> IdentityP p2 a' a b' b n r2 Source #

PFunctor MaybeP Source # 

Methods

hoistP :: (Monad m, Proxy p1) => (forall r1. p1 a' a b' b m r1 -> p2 a' a b' b n r1) -> MaybeP p1 a' a b' b m r2 -> MaybeP p2 a' a b' b n r2 Source #

PFunctor (EitherP e) Source # 

Methods

hoistP :: (Monad m, Proxy p1) => (forall r1. p1 a' a b' b m r1 -> p2 a' a b' b n r1) -> EitherP e p1 a' a b' b m r2 -> EitherP e p2 a' a b' b n r2 Source #

PFunctor (ReaderP i) Source # 

Methods

hoistP :: (Monad m, Proxy p1) => (forall r1. p1 a' a b' b m r1 -> p2 a' a b' b n r1) -> ReaderP i p1 a' a b' b m r2 -> ReaderP i p2 a' a b' b n r2 Source #

PFunctor (StateP s) Source # 

Methods

hoistP :: (Monad m, Proxy p1) => (forall r1. p1 a' a b' b m r1 -> p2 a' a b' b n r1) -> StateP s p1 a' a b' b m r2 -> StateP s p2 a' a b' b n r2 Source #

PFunctor (WriterP w) Source # 

Methods

hoistP :: (Monad m, Proxy p1) => (forall r1. p1 a' a b' b m r1 -> p2 a' a b' b n r1) -> WriterP w p1 a' a b' b m r2 -> WriterP w p2 a' a b' b n r2 Source #

hoistPK Source #

Arguments

:: (Monad m, Proxy p1, PFunctor t) 
=> (forall r1. p1 a' a b' b m r1 -> p2 a' a b' b n r1)

Proxy morphism

-> (q -> t p1 a' a b' b m r2)

Proxy Kleisli arrow

-> q -> t p2 a' a b' b n r2 

Convenience function equivalent to (hoistP f .)

raiseP Source #

Arguments

:: (Monad m, Proxy p, PFunctor t1, ProxyTrans t2) 
=> t1 p a' a b' b m r

Proxy

-> t1 (t2 p) a' a b' b m r 

Lift the base proxy

raiseP = hoistP liftP

raisePK Source #

Arguments

:: (Monad m, Proxy p, PFunctor t1, ProxyTrans t2) 
=> (q -> t1 p a' a b' b m r)

Proxy Kleisli arrow

-> q -> t1 (t2 p) a' a b' b m r 

Lift the base proxy of a 'K'leisli arrow

raisePK = hoistPK liftP