profunctors-4.0: Profunctors

PortabilityType-Families
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellTrustworthy

Data.Profunctor.Rep

Contents

Description

 

Synopsis

Representable Profunctors

class (Functor (Rep p), Profunctor p) => Representable p whereSource

A Profunctor p is Representable if there exists a Functor f such that p d c is isomorphic to d -> f c.

Associated Types

type Rep p :: * -> *Source

Methods

tabulate :: (d -> Rep p c) -> p d cSource

rep :: p d c -> d -> Rep p cSource

Instances

Representable (->) 
(Monad m, Functor m) => Representable (Kleisli m) 
Functor f => Representable (UpStar f) 
(Representable p, Representable q) => Representable (Procompose p q)

The composition of two Representable Profunctors is Representable by the composition of their representations.

tabulated :: (Profunctor r, Functor f, Representable p, Representable q) => r (p d c) (f (q d' c')) -> r (d -> Rep p c) (f (d' -> Rep q c'))Source

tabulate and rep form two halves of an isomorphism.

This can be used with the combinators from the lens package.

tabulated :: Representable p => Iso' (d -> Rep p c) (p d c)

Corepresentable Profunctors

class (Functor (Corep p), Profunctor p) => Corepresentable p whereSource

A Profunctor p is Corepresentable if there exists a Functor f such that p d c is isomorphic to f d -> c.

Associated Types

type Corep p :: * -> *Source

Methods

cotabulate :: (Corep p d -> c) -> p d cSource

corep :: p d c -> Corep p d -> cSource

cotabulated :: (Profunctor r, Functor h, Corepresentable p, Corepresentable q) => r (p d c) (h (q d' c')) -> r (Corep p d -> c) (h (Corep q d' -> c'))Source

cotabulate and corep form two halves of an isomorphism.

This can be used with the combinators from the lens package.

tabulated :: Corep f p => Iso' (f d -> c) (p d c)