profunctors-5.1.1: Profunctors

Copyright(C) 2011-2015 Edward Kmett,
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
PortabilityType-Families
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Profunctor.Rep

Contents

Description

 

Synopsis

Representable Profunctors

class (Sieve p (Rep p), Strong p) => Representable p where Source

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 c Source

Instances

Representable (->) 
(Monad m, Functor m) => Representable (Kleisli m) 
Representable (Forget r) 
Functor f => Representable (Star f) 
(Representable p, Representable q) => Representable (Procompose p q)

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

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

tabulate and sieve 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)

firstRep :: Representable p => p a b -> p (a, c) (b, c) Source

Default definition for first' given that p is Representable.

secondRep :: Representable p => p a b -> p (c, a) (c, b) Source

Default definition for second' given that p is Representable.

Corepresentable Profunctors

class (Cosieve p (Corep p), Costrong p) => Corepresentable p where Source

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 c Source

cotabulated :: (Corepresentable p, Corepresentable q) => Iso (Corep p d -> c) (Corep q d' -> c') (p d c) (q d' c') Source

cotabulate and cosieve form two halves of an isomorphism.

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

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

unfirstCorep :: Corepresentable p => p (a, d) (b, d) -> p a b Source

Default definition for unfirst given that p is Corepresentable.

unsecondCorep :: Corepresentable p => p (d, a) (d, b) -> p a b Source

Default definition for unsecond given that p is Corepresentable.