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 => Choice p where
- newtype TambaraSum p a b = TambaraSum {
- runTambaraSum :: forall c. p (Either a c) (Either b c)
- tambaraSum :: Choice p => (p :-> q) -> p :-> TambaraSum q
- untambaraSum :: Profunctor q => (p :-> TambaraSum q) -> p :-> q
- data PastroSum p a b where
- class Profunctor p => Cochoice p where
- data CotambaraSum q a b where
- CotambaraSum :: Cochoice r => (r :-> q) -> r a b -> CotambaraSum q a b
- cotambaraSum :: Cochoice p => (p :-> q) -> p :-> CotambaraSum q
- uncotambaraSum :: Profunctor q => (p :-> CotambaraSum q) -> p :-> q
- newtype CopastroSum p a b = CopastroSum {
- runCopastroSum :: forall r. Cochoice r => (forall x y. p x y -> r x y) -> r a b
Strength
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 # | |
newtype TambaraSum p a b Source #
TambaraSum is cofreely adjoins strength with respect to Either.
Note: this is not dual to Tambara
. It is Tambara
with respect to a different tensor.
TambaraSum | |
|
ProfunctorComonad TambaraSum Source # | |
ProfunctorFunctor TambaraSum Source # | |
ProfunctorAdjunction PastroSum TambaraSum Source # | |
Profunctor p => Profunctor (TambaraSum p) Source # | |
Profunctor p => Choice (TambaraSum p) Source # | |
Category * p => Category * (TambaraSum p) Source # | |
Profunctor p => Functor (TambaraSum p a) Source # | |
tambaraSum :: Choice p => (p :-> q) -> p :-> TambaraSum q Source #
untambaraSum :: Profunctor q => (p :-> TambaraSum q) -> p :-> q Source #
data PastroSum p a b where Source #
PastroSum -| TambaraSum
PastroSum freely constructs strength with respect to Either.
Costrength
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 # | |
data CotambaraSum q a b where Source #
CotambaraSum
cofreely constructs costrength with respect to Either
(aka Choice
)
CotambaraSum :: Cochoice r => (r :-> q) -> r a b -> CotambaraSum q a b |
cotambaraSum :: Cochoice p => (p :-> q) -> p :-> CotambaraSum q Source #
uncotambaraSum :: Profunctor q => (p :-> CotambaraSum q) -> p :-> q Source #
newtype CopastroSum p a b Source #
CopastroSum -| CotambaraSum
CopastroSum
freely constructs costrength with respect to Either
(aka Choice
)
CopastroSum | |
|