| 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 | Safe | 
| Language | Haskell2010 | 
Data.Profunctor.Strong
Contents
Description
Synopsis
- class Profunctor p => Strong p where
- uncurry' :: Strong p => p a (b -> c) -> p (a, b) c
- strong :: Strong p => (a -> b -> c) -> p a b -> p a 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
- pastro :: Strong q => (p :-> q) -> Pastro p :-> q
- unpastro :: (Pastro p :-> q) -> p :-> q
- 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.
Methods
Instances
newtype Tambara p a b Source #
Tambara cofreely makes any Profunctor Strong.
Constructors
| Tambara | |
| Fields 
 | |
Instances
data Pastro p a b where Source #
Pastro -| Tambara
Pastro p ~ exists z. Costar ((,)z)ProcomposepProcomposeStar ((,)z)
Pastro freely makes any Profunctor Strong.
Instances
| ProfunctorMonad Pastro Source # | |
| ProfunctorAdjunction Pastro Tambara Source # | |
| Profunctor (Pastro p) Source # | |
| Defined in Data.Profunctor.Strong Methods dimap :: (a -> b) -> (c -> d) -> Pastro p b c -> Pastro p a d Source # lmap :: (a -> b) -> Pastro p b c -> Pastro p a c Source # rmap :: (b -> c) -> Pastro p a b -> Pastro p a c Source # (#.) :: forall a b c q. Coercible c b => q b c -> Pastro p a b -> Pastro p a c Source # (.#) :: forall a b c q. Coercible b a => Pastro p b c -> q a b -> Pastro p a c Source # | |
| Strong (Pastro p) Source # | |
| ProfunctorFunctor Pastro Source # | |
| Functor (Pastro p a) Source # | |
Costrength
class Profunctor p => Costrong p where Source #
Methods
Instances
data Cotambara q a b where Source #
Cotambara cofreely constructs costrength
Instances
| ProfunctorComonad Cotambara Source # | |
| Defined in Data.Profunctor.Strong Methods proextract :: forall (p :: Type -> Type -> Type). Profunctor p => Cotambara p :-> p Source # produplicate :: forall (p :: Type -> Type -> Type). Profunctor p => Cotambara p :-> Cotambara (Cotambara p) Source # | |
| ProfunctorAdjunction Copastro Cotambara Source # | |
| Profunctor (Cotambara p) Source # | |
| Defined in Data.Profunctor.Strong Methods dimap :: (a -> b) -> (c -> d) -> Cotambara p b c -> Cotambara p a d Source # lmap :: (a -> b) -> Cotambara p b c -> Cotambara p a c Source # rmap :: (b -> c) -> Cotambara p a b -> Cotambara p a c Source # (#.) :: forall a b c q. Coercible c b => q b c -> Cotambara p a b -> Cotambara p a c Source # (.#) :: forall a b c q. Coercible b a => Cotambara p b c -> q a b -> Cotambara p a c Source # | |
| Costrong (Cotambara p) Source # | |
| ProfunctorFunctor Cotambara Source # | |
| Functor (Cotambara p a) Source # | |
uncotambara :: Profunctor q => (p :-> Cotambara q) -> p :-> q Source #
newtype Copastro p a b Source #
Copastro -| Cotambara
Copastro freely constructs costrength
Constructors
| Copastro | |
| Fields 
 | |
Instances
| ProfunctorMonad Copastro Source # | |
| ProfunctorAdjunction Copastro Cotambara Source # | |
| Profunctor (Copastro p) Source # | |
| Defined in Data.Profunctor.Strong Methods dimap :: (a -> b) -> (c -> d) -> Copastro p b c -> Copastro p a d Source # lmap :: (a -> b) -> Copastro p b c -> Copastro p a c Source # rmap :: (b -> c) -> Copastro p a b -> Copastro p a c Source # (#.) :: forall a b c q. Coercible c b => q b c -> Copastro p a b -> Copastro p a c Source # (.#) :: forall a b c q. Coercible b a => Copastro p b c -> q a b -> Copastro p a c Source # | |
| Costrong (Copastro p) Source # | |
| ProfunctorFunctor Copastro Source # | |
| Functor (Copastro p a) Source # | |