Copyright | (C) 2014-2015 Edward Kmett |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Stability | provisional |
Portability | Rank2Types |
Safe Haskell | None |
Language | Haskell2010 |
- class Profunctor p => Strong p where
- uncurry' :: Strong p => p a (b -> c) -> p (a, b) c
- newtype Tambara p a b = Tambara {
- runTambara :: forall c. p (a, c) (b, c)
- tambara :: Strong p => (p :-> q) -> p :-> Tambara q
- untambara :: Profunctor q => (p :-> Tambara q) -> p :-> q
- data Pastro p a b where
- class Profunctor p => Costrong p where
- data Cotambara q a b where
- cotambara :: Costrong p => (p :-> q) -> p :-> Cotambara q
- uncotambara :: Profunctor q => (p :-> Cotambara q) -> p :-> q
- newtype Copastro p a b = Copastro {
- runCopastro :: forall r. Costrong r => (forall x y. p x y -> r x y) -> r a b
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 # | |
newtype Tambara p a b Source #
Tambara
cofreely makes any Profunctor
Strong
.
Tambara | |
|
ProfunctorComonad Tambara Source # | |
ProfunctorFunctor Tambara Source # | |
ProfunctorAdjunction Pastro Tambara Source # | |
Arrow p => Arrow (Tambara p) Source # | |
ArrowZero p => ArrowZero (Tambara p) Source # | |
ArrowPlus p => ArrowPlus (Tambara p) Source # | |
ArrowChoice p => ArrowChoice (Tambara p) Source # | |
ArrowApply p => ArrowApply (Tambara p) Source # | |
ArrowLoop p => ArrowLoop (Tambara p) Source # | |
Profunctor p => Profunctor (Tambara p) Source # | |
Profunctor p => Strong (Tambara p) Source # | |
Choice p => Choice (Tambara p) Source # | |
Category * p => Category * (Tambara p) Source # | |
Profunctor p => Functor (Tambara p a) Source # | |
(Profunctor p, Arrow p) => Applicative (Tambara p a) Source # | |
(Profunctor p, ArrowPlus p) => Alternative (Tambara p a) Source # | |
ArrowPlus p => Monoid (Tambara p a b) Source # | |
data Pastro p a b where Source #
Pastro -| Tambara
Pastro p ~ exists z. Costar ((,)z)Procompose
pProcompose
Star ((,)z)
Pastro
freely makes any Profunctor
Strong
.
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 # | |
uncotambara :: Profunctor q => (p :-> Cotambara q) -> p :-> q Source #