profunctor-extras-3.2.1: Profunctor extras

PortabilityGADTs
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellTrustworthy

Data.Profunctor.Composition

Contents

Description

 

Synopsis

Profunctor Composition

data Procompose p q d c whereSource

Procompose p q is the Profunctor composition of the profunctors p and q.

For a good explanation of profunctor composition in Haskell see Dan Piponi's article:

http://blog.sigfpe.com/2011/07/profunctors-in-haskell.html

Constructors

Procompose :: p d a -> q a c -> Procompose p q d c 

Instances

(Profunctor p, Profunctor q) => Profunctor (Procompose p q) 
(Functor (Corep (Procompose p q)), Profunctor (Procompose p q), Corepresentable p, Corepresentable q) => Corepresentable (Procompose p q) 
(Functor (Rep (Procompose p q)), Profunctor (Procompose p q), Representable p, Representable q) => Representable (Procompose p q)

The composition of two representable profunctors is representable by the composition of their representations.

Profunctor q => Functor (Procompose p q a) 

Lax identity

idl :: (Profunctor p, Profunctor q, Functor f) => p (q d c) (f (r d' c')) -> p (Procompose (->) q d c) (f (Procompose (->) r d' c'))Source

(->) functions as a lax identity for profunctor composition.

This provides an Iso for the lens package that witnesses the isomorphism between Procompose (->) q d c and q d c, which is the left identity law.

 idl :: Profunctor q => Iso' (Procompose (->) q d c) (q d c)

idr :: (Profunctor p, Profunctor q, Functor f) => p (q d c) (f (r d' c')) -> p (Procompose q (->) d c) (f (Procompose r (->) d' c'))Source

(->) functions as a lax identity for profunctor composition.

This provides an Iso for the lens package that witnesses the isomorphism between Procompose q (->) d c and q d c, which is the right identity law.

 idr :: Profunctor q => Iso' (Procompose q (->) d c) (q d c)

Generalized Composition

upstars :: (Profunctor p, Functor f, Functor h) => p (UpStar (Compose f g) d c) (h (UpStar (Compose f' g') d' c')) -> p (Procompose (UpStar f) (UpStar g) d c) (h (Procompose (UpStar f') (UpStar g') d' c'))Source

Profunctor composition generalizes functor composition in two ways.

This is the first, which shows that exists b. (a -> f b, b -> g c) is isomorphic to a -> f (g c).

upstars :: Functor f => Iso' (Procompose (UpStar f) (UpStar g) d c) (UpStar (Compose f g) d c)

kleislis :: (Profunctor p, Monad f, Functor h) => p (Kleisli (Compose f g) d c) (h (Kleisli (Compose f' g') d' c')) -> p (Procompose (Kleisli f) (Kleisli g) d c) (h (Procompose (Kleisli f') (Kleisli g') d' c'))Source

This is a variant on upstars that uses Kleisli instead of UpStar.

kleislis :: Monad f => Iso' (Procompose (Kleisli f) (Kleisli g) d c) (Kleisli (Compose f g) d c)

downstars :: (Profunctor p, Functor g, Functor h) => p (DownStar (Compose g f) d c) (h (DownStar (Compose g' f') d' c')) -> p (Procompose (DownStar f) (DownStar g) d c) (h (Procompose (DownStar f') (DownStar g') d' c'))Source

Profunctor composition generalizes functor composition in two ways.

This is the second, which shows that exists b. (f a -> b, g b -> c) is isomorphic to g (f a) -> c.

downstars :: Functor f => Iso' (Procompose (DownStar f) (DownStar g) d c) (DownStar (Compose g f) d c)

cokleislis :: (Profunctor p, Functor g, Functor h) => p (Cokleisli (Compose g f) d c) (h (Cokleisli (Compose g' f') d' c')) -> p (Procompose (Cokleisli f) (Cokleisli g) d c) (h (Procompose (Cokleisli f') (Cokleisli g') d' c'))Source

This is a variant on downstars that uses Cokleisli instead of DownStar.

cokleislis :: Functor f => Iso' (Procompose (Cokleisli f) (Cokleisli g) d c) (Cokleisli (Compose g f) d c)