| Copyright | (C) 2011-2013 Edward Kmett, | 
|---|---|
| License | BSD-style (see the file LICENSE) | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
| Stability | provisional | 
| Portability | portable | 
| Safe Haskell | Trustworthy | 
| Language | Haskell2010 | 
Data.Profunctor
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/
- class Profunctor p where
- class Profunctor p => Strong p where
- class Profunctor p => Choice p where
- class Profunctor p => Costrong p where
- class Profunctor p => Cochoice p where
- newtype UpStar f d c = UpStar {- runUpStar :: d -> f c
 
- newtype DownStar f d c = DownStar {- runDownStar :: 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:
dimapidid≡id
If you supply lmap and rmap, ensure:
lmapid≡idrmapid≡id
If you supply both, you should also ensure:
dimapf g ≡lmapf.rmapg
These ensure by parametricity:
dimap(f.g) (h.i) ≡dimapg h.dimapf ilmap(f.g) ≡lmapg.lmapfrmap(f.g) ≡rmapf.rmapg
Methods
dimap :: (a -> b) -> (c -> d) -> p b c -> p a d Source
Instances
| Profunctor (->) | |
| Monad m => Profunctor (Kleisli m) | |
| Functor w => Profunctor (Cokleisli w) | |
| Profunctor (Tagged *) | |
| Profunctor (Forget r) | |
| Arrow p => Profunctor (WrappedArrow p) | |
| Functor f => Profunctor (DownStar f) | |
| Functor f => Profunctor (UpStar f) | |
| Profunctor p => Profunctor (Environment p) | |
| Profunctor p => Profunctor (Closure p) | |
| Profunctor p => Profunctor (Codensity p) | |
| Profunctor p => Profunctor (Copastro p) | |
| Profunctor p => Profunctor (Cotambara p) | |
| Profunctor p => Profunctor (Pastro p) | |
| Profunctor p => Profunctor (Tambara p) | |
| (Functor f, Profunctor p) => Profunctor (Cayley f p) | |
| (Profunctor p, Profunctor q) => Profunctor (Rift p q) | |
| (Profunctor p, Profunctor q) => Profunctor (Procompose p q) | |
| (Profunctor p, Profunctor q) => Profunctor (Ran p q) | 
Profunctorial Strength
class Profunctor p => Strong p where Source
Generalizing UpStar 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
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 (Closure p) | |
| Profunctor p => Strong (Tambara p) | |
| (Functor f, Strong p) => Strong (Cayley f p) | |
| (Strong p, Strong q) => Strong (Procompose p q) | 
class Profunctor p => Choice p where Source
The generalization of DownStar 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.
Instances
| Choice (->) | |
| Monad m => Choice (Kleisli m) | |
| Comonad w => Choice (Cokleisli w) | 
 | 
| Choice (Tagged *) | |
| Monoid r => Choice (Forget r) | |
| ArrowChoice p => Choice (WrappedArrow p) | |
| Traversable w => Choice (DownStar w) | |
| Applicative f => Choice (UpStar f) | |
| Profunctor p => Choice (Cotambara p) | |
| Choice p => Choice (Tambara p) | |
| (Functor f, Choice p) => Choice (Cayley f p) | |
| (Choice p, Choice q) => Choice (Procompose p q) | 
Profunctorial Costrength
class Profunctor p => Costrong p where Source
Minimal complete definition
Nothing
class Profunctor p => Cochoice p where Source
Minimal complete definition
Nothing
Common Profunctors
Lift a Functor into a Profunctor (forwards).
Instances
| Functor f => Profunctor (UpStar f) | |
| Applicative f => Choice (UpStar f) | |
| Functor m => Strong (UpStar m) | |
| Distributive f => Closed (UpStar f) | |
| Functor f => Representable (UpStar f) | |
| Alternative f => Alternative (UpStar f a) | |
| Monad f => Monad (UpStar f a) | |
| Functor f => Functor (UpStar f a) | |
| MonadPlus f => MonadPlus (UpStar f a) | |
| Applicative f => Applicative (UpStar f a) | |
| type Rep (UpStar f) = f | 
Lift a Functor into a Profunctor (backwards).
Constructors
| DownStar | |
| Fields 
 | |
Instances
| Functor f => Profunctor (DownStar f) | |
| Traversable w => Choice (DownStar w) | |
| Functor f => Closed (DownStar f) | |
| Functor f => Corepresentable (DownStar f) | |
| Monad (DownStar f a) | |
| Functor (DownStar f a) | |
| Applicative (DownStar f a) | |
| type Corep (DownStar f) = f | 
newtype WrappedArrow p a b Source
Wrap an arrow for use as a Profunctor.
Constructors
| WrapArrow | |
| Fields 
 | |
Instances
| Category * p => Category * (WrappedArrow p) | |
| Arrow p => Arrow (WrappedArrow p) | |
| ArrowZero p => ArrowZero (WrappedArrow p) | |
| ArrowChoice p => ArrowChoice (WrappedArrow p) | |
| ArrowApply p => ArrowApply (WrappedArrow p) | |
| ArrowLoop p => ArrowLoop (WrappedArrow p) | |
| Arrow p => Profunctor (WrappedArrow p) | |
| ArrowLoop p => Costrong (WrappedArrow p) | |
| ArrowChoice p => Choice (WrappedArrow p) | |
| Arrow p => Strong (WrappedArrow p) | Every Arrow is a Strong Monad in Prof |