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 | None |
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
- 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
Documentation
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
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 # | |