Copyright | (C) 2011-2015 Edward Kmett, |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Stability | provisional |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
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/
- class Profunctor p where
- class Profunctor p => Strong p where
- uncurry' :: Strong p => p a (b -> c) -> p (a, b) c
- class Profunctor p => Choice p where
- class Profunctor p => Closed p where
- curry' :: Closed p => p (a, b) c -> p a (b -> c)
- class (Traversing p, Closed p) => Mapping p where
- class Profunctor p => Costrong p where
- class Profunctor p => Cochoice p where
- newtype Star f d c = Star {
- runStar :: d -> f c
- newtype Costar f d c = Costar {
- runCostar :: f d -> c
- newtype WrappedArrow p a b = WrapArrow {
- unwrapArrow :: p a b
- newtype Forget r a b = Forget {
- runForget :: a -> r
- type (:->) p q = forall a b. p a b -> q a b
Profunctors
class Profunctor p where Source #
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
id
≡id
If you supply lmap
and rmap
, ensure:
lmap
id
≡id
rmap
id
≡id
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 ilmap
(f.
g) ≡lmap
g.
lmap
frmap
(f.
g) ≡rmap
f.
rmap
g
Profunctorial Strength
class Profunctor p => Strong p where Source #
Generalizing Star
of a strong Functor
Note: Every Functor
in Haskell is strong with respect to (,)
.
This describes profunctor strength with respect to the product structure of Hask.
http://www-kb.is.s.u-tokyo.ac.jp/~asada/papers/arrStrMnd.pdf
Strong (->) Source # | |
Monad m => Strong (Kleisli m) Source # | |
Strong (Forget r) Source # | |
Arrow p => Strong (WrappedArrow p) Source # | |
Functor m => Strong (Star m) Source # | |
Strong (Pastro p) Source # | |
Profunctor p => Strong (Tambara p) Source # | |
Strong p => Strong (Closure p) Source # | |
Strong (FreeTraversing p) Source # | |
Profunctor p => Strong (CofreeTraversing p) Source # | |
Strong (FreeMapping p) Source # | |
Profunctor p => Strong (CofreeMapping p) Source # | |
(Functor f, Strong p) => Strong (Cayley f p) Source # | |
(Strong p, Strong q) => Strong (Procompose p q) Source # | |
Contravariant f => Strong (Clown * * f) Source # | |
(Strong p, Strong q) => Strong (Product * * p q) Source # | |
(Functor f, Strong p) => Strong (Tannen * * * f p) Source # | |
class Profunctor p => Choice p where Source #
The generalization of Costar
of Functor
that is strong with respect
to Either
.
Note: This is also a notion of strength, except with regards to another monoidal structure that we can choose to equip Hask with: the cocartesian coproduct.
Choice (->) Source # | |
Monad m => Choice (Kleisli m) Source # | |
Comonad w => Choice (Cokleisli w) Source # |
|
Choice (Tagged *) Source # | |
Monoid r => Choice (Forget r) Source # | |
ArrowChoice p => Choice (WrappedArrow p) Source # | |
Traversable w => Choice (Costar w) Source # | |
Applicative f => Choice (Star f) Source # | |
Choice p => Choice (Tambara p) Source # | |
Choice (PastroSum p) Source # | |
Profunctor p => Choice (TambaraSum p) Source # | |
Choice (FreeTraversing p) Source # | |
Profunctor p => Choice (CofreeTraversing p) Source # | |
Choice (FreeMapping p) Source # | |
Profunctor p => Choice (CofreeMapping p) Source # | |
(Functor f, Choice p) => Choice (Cayley f p) Source # | |
(Choice p, Choice q) => Choice (Procompose p q) Source # | |
Functor f => Choice (Joker * * f) Source # | |
(Choice p, Choice q) => Choice (Product * * p q) Source # | |
(Functor f, Choice p) => Choice (Tannen * * * f p) Source # | |
Closed
class Profunctor p => Closed p where Source #
A strong profunctor allows the monoidal structure to pass through.
A closed profunctor allows the closed structure to pass through.
Closed (->) Source # | |
(Distributive f, Monad f) => Closed (Kleisli f) Source # | |
Functor f => Closed (Cokleisli f) Source # | |
Closed (Tagged *) Source # | |
Functor f => Closed (Costar f) Source # | |
Distributive f => Closed (Star f) Source # | |
Closed (Environment p) Source # | |
Profunctor p => Closed (Closure p) Source # | |
Closed (FreeMapping p) Source # | |
Profunctor p => Closed (CofreeMapping p) Source # | |
(Closed p, Closed q) => Closed (Procompose p q) Source # | |
(Closed p, Closed q) => Closed (Product * * p q) Source # | |
(Functor f, Closed p) => Closed (Tannen * * * f p) Source # | |
class (Traversing p, Closed p) => Mapping p where Source #
Mapping (->) Source # | |
(Monad m, Distributive m) => Mapping (Kleisli m) Source # | |
(Applicative m, Distributive m) => Mapping (Star m) Source # | |
Mapping (FreeMapping p) Source # | |
Profunctor p => Mapping (CofreeMapping p) Source # | |
Profunctorial Costrength
class Profunctor p => Costrong p where Source #
Costrong (->) Source # | |
MonadFix m => Costrong (Kleisli m) Source # | |
Functor f => Costrong (Cokleisli f) Source # | |
Costrong (Tagged *) Source # | |
ArrowLoop p => Costrong (WrappedArrow p) Source # | |
Functor f => Costrong (Costar f) Source # | |
Costrong (Copastro p) Source # | |
Costrong (Cotambara p) Source # | |
(Corepresentable p, Corepresentable q) => Costrong (Procompose p q) Source # | |
(Costrong p, Costrong q) => Costrong (Product * * p q) Source # | |
(Functor f, Costrong p) => Costrong (Tannen * * * f p) Source # | |
class Profunctor p => Cochoice p where Source #
Cochoice (->) Source # | |
Applicative f => Cochoice (Costar f) Source # | |
Traversable f => Cochoice (Star f) Source # | |
Cochoice (CopastroSum p) Source # | |
Cochoice (CotambaraSum p) Source # | |
(Cochoice p, Cochoice q) => Cochoice (Product * * p q) Source # | |
(Functor f, Cochoice p) => Cochoice (Tannen * * * f p) Source # | |
Common Profunctors
Lift a Functor
into a Profunctor
(forwards).
Functor f => Profunctor (Star f) Source # | |
Functor m => Strong (Star m) Source # | |
Traversable f => Cochoice (Star f) Source # | |
Applicative f => Choice (Star f) Source # | |
Distributive f => Closed (Star f) Source # | |
Applicative m => Traversing (Star m) Source # | |
(Applicative m, Distributive m) => Mapping (Star m) Source # | |
Functor f => Representable (Star f) Source # | |
Functor f => Sieve (Star f) f Source # | |
Monad f => Monad (Star f a) Source # | |
Functor f => Functor (Star f a) Source # | |
Applicative f => Applicative (Star f a) Source # | |
Alternative f => Alternative (Star f a) Source # | |
MonadPlus f => MonadPlus (Star f a) Source # | |
Distributive f => Distributive (Star f a) Source # | |
type Rep (Star f) Source # | |
Lift a Functor
into a Profunctor
(backwards).
Functor f => Profunctor (Costar f) Source # | |
Functor f => Costrong (Costar f) Source # | |
Applicative f => Cochoice (Costar f) Source # | |
Traversable w => Choice (Costar w) Source # | |
Functor f => Closed (Costar f) Source # | |
Functor f => Corepresentable (Costar f) Source # | |
Functor f => Cosieve (Costar f) f Source # | |
Monad (Costar f a) Source # | |
Functor (Costar f a) Source # | |
Applicative (Costar f a) Source # | |
Distributive (Costar f d) Source # | |
type Corep (Costar f) Source # | |
newtype WrappedArrow p a b Source #
Wrap an arrow for use as a Profunctor
.
WrapArrow | |
|
Arrow p => Arrow (WrappedArrow p) Source # | |
ArrowZero p => ArrowZero (WrappedArrow p) Source # | |
ArrowChoice p => ArrowChoice (WrappedArrow p) Source # | |
ArrowApply p => ArrowApply (WrappedArrow p) Source # | |
ArrowLoop p => ArrowLoop (WrappedArrow p) Source # | |
Arrow p => Profunctor (WrappedArrow p) Source # | |
ArrowLoop p => Costrong (WrappedArrow p) Source # | |
Arrow p => Strong (WrappedArrow p) Source # | |
ArrowChoice p => Choice (WrappedArrow p) Source # | |
Category * p => Category * (WrappedArrow p) Source # | |