profunctors-4.0.2: Profunctors

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

Data.Profunctor

Contents

Description

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

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

For more information on strength and costrength, see:

http://comonad.com/reader/2008/deriving-strength-from-laziness/

Synopsis

Profunctors

class Profunctor p whereSource

Formally, the class Profunctor represents a profunctor from Hask -> Hask.

Intuitively it is a bifunctor where the first argument is contravariant and the second argument is covariant.

You can define a Profunctor by either defining dimap or by defining both lmap and rmap.

If you supply dimap, you should ensure that:

dimap id idid

If you supply lmap and rmap, ensure:

 lmap idid
 rmap idid

If you supply both, you should also ensure:

dimap f g ≡ lmap f . rmap g

These ensure by parametricity:

 dimap (f . g) (h . i) ≡ dimap g h . dimap f i
 lmap (f . g) ≡ lmap g . lmap f
 rmap (f . g) ≡ rmap f . rmap g

Methods

dimap :: (a -> b) -> (c -> d) -> p b c -> p a dSource

Map over both arguments at the same time.

dimap f g ≡ lmap f . rmap g

lmap :: (a -> b) -> p b c -> p a cSource

Map the first argument contravariantly.

lmap f ≡ dimap f id

rmap :: (b -> c) -> p a b -> p a cSource

Map the second argument covariantly.

rmapdimap id

Profunctorial Strength

class Profunctor p => Strong p whereSource

Generalizing upstar of a strong Functor

Minimal complete definition: first' or second'

Note: Every Functor in Haskell is strong.

http://takeichi.ipl-lab.org/~asada/papers/arrStrMnd.pdf

Methods

first' :: p a b -> p (a, c) (b, c)Source

second' :: p a b -> p (c, a) (c, b)Source

Instances

Strong (->) 
Monad m => Strong (Kleisli m) 
Strong (Forget r) 
Arrow p => Strong (WrappedArrow p)

Every Arrow is a Strong Monad in Prof

Functor m => Strong (UpStar m) 
(Strong p, Strong q) => Strong (Procompose p q) 

class Profunctor p => Choice p whereSource

The generalization of DownStar of a "costrong" Functor

Minimal complete definition: left' or right'

Note: We use traverse and extract as approximate costrength as needed.

Methods

left' :: p a b -> p (Either a c) (Either b c)Source

right' :: p a b -> p (Either c a) (Either c b)Source

Instances

Choice (->) 
Monad m => Choice (Kleisli m) 
Comonad w => Choice (Cokleisli w)

extract approximates costrength

Choice (Tagged *) 
Monoid r => Choice (Forget r) 
ArrowChoice p => Choice (WrappedArrow p) 
Traversable w => Choice (DownStar w)

sequence approximates costrength

Applicative f => Choice (UpStar f) 
(Choice p, Choice q) => Choice (Procompose p q) 

Common Profunctors

newtype UpStar f d c Source

Lift a Functor into a Profunctor (forwards).

Constructors

UpStar 

Fields

runUpStar :: d -> f c
 

Instances

newtype DownStar f d c Source

Lift a Functor into a Profunctor (backwards).

Constructors

DownStar 

Fields

runDownStar :: f d -> c
 

Instances

Functor f => Profunctor (DownStar f) 
Traversable w => Choice (DownStar w)

sequence approximates costrength

Functor f => Corepresentable (DownStar f) 
Functor (DownStar f a) 

newtype WrappedArrow p a b Source

Wrap an arrow for use as a Profunctor.

Constructors

WrapArrow 

Fields

unwrapArrow :: p a b
 

newtype Forget r a b Source

Constructors

Forget 

Fields

runForget :: a -> r
 

Instances