monoidal-functors-0.2.3.0: Monoidal Functors Library
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Bifunctor.Module

Synopsis

LeftModule

class LeftModule cat t1 t2 p where Source #

A Profunctor \(P : \mathcal{C}^{op} \times \mathcal{D} \to Set\) is a Tambara LeftModule if it is equipped with a morphism \(s_{a,b,m} : P(a, b) \to P(a \odot m, b \odot m)\), which we call lstrength.

Laws

lmap projlrmap projl . lstrength
lmap (rstrength f) . lstrengthrmap (rstrength f) . lstrength
lstrength . lstrengthdimap (bwd assoc) (fwd assoc) . lstrength

Methods

lstrength :: cat (p a b) (p (t1 a x) (t2 b x)) Source #

Examples

Expand

first':

>>> :t lstrength @(->) @(,) @(,)
lstrength @(->) @(,) @(,) :: LeftModule (->) (,) (,) p => p a b -> p (a, x) (b, x)

left':

>>> :t lstrength @(->) @Either @Either
lstrength @(->) @Either @Either :: LeftModule (->) Either Either p => p a b -> p (Either a x) (Either b x)

Instances

Instances details
LeftModule Op (,) (,) Either Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Op (Either a b) (Either (a, x) (b, x)) Source #

LeftModule Op (,) (,) Arg Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Op (Arg a b) (Arg (a, x) (b, x)) Source #

LeftModule Op (,) (,) These Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Op (These a b) (These (a, x) (b, x)) Source #

LeftModule Op (,) (,) (,) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Op (a, b) ((a, x), (b, x)) Source #

LeftModule Op (,) (,) (Const :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Op (Const a b) (Const (a, x) (b, x)) Source #

LeftModule Op (,) (,) ((,,) x1) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Op (x1, a, b) (x1, (a, x), (b, x)) Source #

LeftModule Op (,) (,) (K1 i :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Op (K1 i a b) (K1 i (a, x) (b, x)) Source #

LeftModule Op (,) (,) ((,,,) x1 x2) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Op (x1, x2, a, b) (x1, x2, (a, x), (b, x)) Source #

LeftModule Op (,) (,) ((,,,,) x1 x2 x3) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Op (x1, x2, x3, a, b) (x1, x2, x3, (a, x), (b, x)) Source #

LeftModule Op (,) (,) ((,,,,,) x1 x2 x3 x4) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Op (x1, x2, x3, x4, a, b) (x1, x2, x3, x4, (a, x), (b, x)) Source #

LeftModule Op (,) (,) ((,,,,,,) x1 x2 x3 x4 x5) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Op (x1, x2, x3, x4, x5, a, b) (x1, x2, x3, x4, x5, (a, x), (b, x)) Source #

LeftModule (->) Either Either Either Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Either a b -> Either (Either a x) (Either b x) Source #

LeftModule (->) Either Either Arg Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Arg a b -> Arg (Either a x) (Either b x) Source #

LeftModule (->) Either Either These Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: These a b -> These (Either a x) (Either b x) Source #

LeftModule (->) Either Either (,) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: (a, b) -> (Either a x, Either b x) Source #

LeftModule (->) These These Either Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Either a b -> Either (These a x) (These b x) Source #

LeftModule (->) These These Arg Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Arg a b -> Arg (These a x) (These b x) Source #

LeftModule (->) These These These Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: These a b -> These (These a x) (These b x) Source #

LeftModule (->) These These (,) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: (a, b) -> (These a x, These b x) Source #

Monad m => LeftModule (->) Either Either (Kleisli m) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Kleisli m a b -> Kleisli m (Either a x) (Either b x) Source #

LeftModule (->) Either Either (Const :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Const a b -> Const (Either a x) (Either b x) Source #

LeftModule (->) Either Either (PastroSum p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: PastroSum p a b -> PastroSum p (Either a x) (Either b x) Source #

Profunctor p => LeftModule (->) Either Either (TambaraSum p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: TambaraSum p a b -> TambaraSum p (Either a x) (Either b x) Source #

Profunctor p => LeftModule (->) Either Either (CofreeMapping p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: CofreeMapping p a b -> CofreeMapping p (Either a x) (Either b x) Source #

LeftModule (->) Either Either (FreeMapping p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: FreeMapping p a b -> FreeMapping p (Either a x) (Either b x) Source #

Choice p => LeftModule (->) Either Either (Tambara p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Tambara p a b -> Tambara p (Either a x) (Either b x) Source #

Profunctor p => LeftModule (->) Either Either (CofreeTraversing p) Source # 
Instance details

Defined in Data.Bifunctor.Module

LeftModule (->) Either Either (FreeTraversing p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: FreeTraversing p a b -> FreeTraversing p (Either a x) (Either b x) Source #

Choice p => LeftModule (->) Either Either (Coyoneda p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Coyoneda p a b -> Coyoneda p (Either a x) (Either b x) Source #

Choice p => LeftModule (->) Either Either (Yoneda p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Yoneda p a b -> Yoneda p (Either a x) (Either b x) Source #

LeftModule (->) Either Either (Tagged :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Tagged a b -> Tagged (Either a x) (Either b x) Source #

LeftModule (->) Either Either ((,,) x1) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: (x1, a, b) -> (x1, Either a x, Either b x) Source #

LeftModule (->) These These (Const :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Const a b -> Const (These a x) (These b x) Source #

LeftModule (->) These These ((,,) x1) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: (x1, a, b) -> (x1, These a x, These b x) Source #

Monad m => LeftModule (->) (,) (,) (Kleisli m) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Kleisli m a b -> Kleisli m (a, x) (b, x) Source #

Strong p => LeftModule (->) (,) (,) (Closure p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Closure p a b -> Closure p (a, x) (b, x) Source #

Profunctor p => LeftModule (->) (,) (,) (CofreeMapping p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: CofreeMapping p a b -> CofreeMapping p (a, x) (b, x) Source #

LeftModule (->) (,) (,) (FreeMapping p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: FreeMapping p a b -> FreeMapping p (a, x) (b, x) Source #

LeftModule (->) (,) (,) (Pastro p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Pastro p a b -> Pastro p (a, x) (b, x) Source #

Profunctor p => LeftModule (->) (,) (,) (Tambara p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Tambara p a b -> Tambara p (a, x) (b, x) Source #

Profunctor p => LeftModule (->) (,) (,) (CofreeTraversing p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: CofreeTraversing p a b -> CofreeTraversing p (a, x) (b, x) Source #

LeftModule (->) (,) (,) (FreeTraversing p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: FreeTraversing p a b -> FreeTraversing p (a, x) (b, x) Source #

Strong p => LeftModule (->) (,) (,) (Coyoneda p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Coyoneda p a b -> Coyoneda p (a, x) (b, x) Source #

Strong p => LeftModule (->) (,) (,) (Yoneda p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Yoneda p a b -> Yoneda p (a, x) (b, x) Source #

LeftModule (->) Either Either (K1 i :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: K1 i a b -> K1 i (Either a x) (Either b x) Source #

Comonad w => LeftModule (->) Either Either (Cokleisli w) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Cokleisli w a b -> Cokleisli w (Either a x) (Either b x) Source #

Monoid r => LeftModule (->) Either Either (Forget r :: Type -> Type -> TYPE LiftedRep) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Forget r a b -> Forget r (Either a x) (Either b x) Source #

Applicative f => LeftModule (->) Either Either (Star f) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Star f a b -> Star f (Either a x) (Either b x) Source #

LeftModule (->) Either Either ((,,,) x1 x2) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: (x1, x2, a, b) -> (x1, x2, Either a x, Either b x) Source #

LeftModule (->) Either Either (->) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: (a -> b) -> (Either a x -> Either b x) Source #

LeftModule (->) These These (K1 i :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: K1 i a b -> K1 i (These a x) (These b x) Source #

LeftModule (->) These These ((,,,) x1 x2) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: (x1, x2, a, b) -> (x1, x2, These a x, These b x) Source #

LeftModule (->) (,) (,) (Forget r :: Type -> Type -> TYPE LiftedRep) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Forget r a b -> Forget r (a, x) (b, x) Source #

Functor m => LeftModule (->) (,) (,) (Star m) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Star m a b -> Star m (a, x) (b, x) Source #

LeftModule (->) (,) (,) (->) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: (a -> b) -> ((a, x) -> (b, x)) Source #

Functor f => LeftModule (->) Either Either (Joker f :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Joker f a b -> Joker f (Either a x) (Either b x) Source #

ArrowChoice p => LeftModule (->) Either Either (WrappedArrow p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: WrappedArrow p a b -> WrappedArrow p (Either a x) (Either b x) Source #

LeftModule (->) Either Either ((,,,,) x1 x2 x3) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: (x1, x2, x3, a, b) -> (x1, x2, x3, Either a x, Either b x) Source #

LeftModule (->) These These ((,,,,) x1 x2 x3) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: (x1, x2, x3, a, b) -> (x1, x2, x3, These a x, These b x) Source #

Contravariant f => LeftModule (->) (,) (,) (Clown f :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Clown f a b -> Clown f (a, x) (b, x) Source #

Arrow p => LeftModule (->) (,) (,) (WrappedArrow p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: WrappedArrow p a b -> WrappedArrow p (a, x) (b, x) Source #

(Choice p, Choice q) => LeftModule (->) Either Either (Product p q) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Product p q a b -> Product p q (Either a x) (Either b x) Source #

(Choice p, Choice q) => LeftModule (->) Either Either (Sum p q) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Sum p q a b -> Sum p q (Either a x) (Either b x) Source #

LeftModule (->) Either Either ((,,,,,) x1 x2 x3 x4) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: (x1, x2, x3, x4, a, b) -> (x1, x2, x3, x4, Either a x, Either b x) Source #

LeftModule (->) These These ((,,,,,) x1 x2 x3 x4) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: (x1, x2, x3, x4, a, b) -> (x1, x2, x3, x4, These a x, These b x) Source #

(Strong p, Strong q) => LeftModule (->) (,) (,) (Product p q) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Product p q a b -> Product p q (a, x) (b, x) Source #

(Strong p, Strong q) => LeftModule (->) (,) (,) (Sum p q) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Sum p q a b -> Sum p q (a, x) (b, x) Source #

(Functor f, Choice p) => LeftModule (->) Either Either (Tannen f p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Tannen f p a b -> Tannen f p (Either a x) (Either b x) Source #

(Functor f, Choice q) => LeftModule (->) Either Either (Cayley f q) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Cayley f q a b -> Cayley f q (Either a x) (Either b x) Source #

(Choice p, Choice q) => LeftModule (->) Either Either (Procompose p q) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Procompose p q a b -> Procompose p q (Either a x) (Either b x) Source #

LeftModule (->) Either Either ((,,,,,,) x1 x2 x3 x4 x5) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: (x1, x2, x3, x4, x5, a, b) -> (x1, x2, x3, x4, x5, Either a x, Either b x) Source #

LeftModule (->) These These ((,,,,,,) x1 x2 x3 x4 x5) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: (x1, x2, x3, x4, x5, a, b) -> (x1, x2, x3, x4, x5, These a x, These b x) Source #

(Functor f, Strong q) => LeftModule (->) (,) (,) (Tannen f q) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Tannen f q a b -> Tannen f q (a, x) (b, x) Source #

(Functor f, Strong q) => LeftModule (->) (,) (,) (Cayley f q) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Cayley f q a b -> Cayley f q (a, x) (b, x) Source #

(Strong p, Strong q) => LeftModule (->) (,) (,) (Procompose p q) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lstrength :: Procompose p q a b -> Procompose p q (a, x) (b, x) Source #

RightModule

class RightModule cat t1 t2 f where Source #

A Profunctor \(P : \mathcal{C}^{op} \times \mathcal{D} \to Set\) is a Tambara RightModule if it is equipped with a morphism \(s_{a,b,m} : P(a, b) \to P(m \odot a, m \odot b)\), which we call rstrength.

Laws

lmap projrrmap projr . rstrength
lmap (lstrength f) . rstrengthrmap (lstrength f) . rstrength
rstrength . rstrengthdimap (fwd assoc) (bwd assoc) . rstrength

Methods

rstrength :: cat (f a b) (f (x `t1` a) (x `t2` b)) Source #

Examples

Expand

second':

>>> :t rstrength @(->) @(,) @(,)
rstrength @(->) @(,) @(,) :: RightModule (->) (,) (,) f => f a b -> f (x, a) (x, b)

right':

>>> :t rstrength @(->) @Either @Either
rstrength @(->) @Either @Either :: RightModule (->) Either Either f => f a b -> f (Either x a) (Either x b)

Instances

Instances details
RightModule Op (,) (,) Either Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Op (Either a b) (Either (x, a) (x, b)) Source #

RightModule Op (,) (,) Arg Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Op (Arg a b) (Arg (x, a) (x, b)) Source #

RightModule Op (,) (,) These Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Op (These a b) (These (x, a) (x, b)) Source #

RightModule Op (,) (,) (,) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Op (a, b) ((x, a), (x, b)) Source #

RightModule Op (,) (,) (Const :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Op (Const a b) (Const (x, a) (x, b)) Source #

RightModule Op (,) (,) ((,,) x1) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Op (x1, a, b) (x1, (x, a), (x, b)) Source #

RightModule Op (,) (,) (K1 i :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Op (K1 i a b) (K1 i (x, a) (x, b)) Source #

RightModule Op (,) (,) ((,,,) x1 x2) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Op (x1, x2, a, b) (x1, x2, (x, a), (x, b)) Source #

RightModule Op (,) (,) ((,,,,) x1 x2 x3) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Op (x1, x2, x3, a, b) (x1, x2, x3, (x, a), (x, b)) Source #

RightModule Op (,) (,) ((,,,,,) x1 x2 x3 x4) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Op (x1, x2, x3, x4, a, b) (x1, x2, x3, x4, (x, a), (x, b)) Source #

RightModule Op (,) (,) ((,,,,,,) x1 x2 x3 x4 x5) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Op (x1, x2, x3, x4, x5, a, b) (x1, x2, x3, x4, x5, (x, a), (x, b)) Source #

RightModule (->) Either Either Either Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Either a b -> Either (Either x a) (Either x b) Source #

RightModule (->) Either Either Arg Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Arg a b -> Arg (Either x a) (Either x b) Source #

RightModule (->) Either Either These Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: These a b -> These (Either x a) (Either x b) Source #

RightModule (->) Either Either (,) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: (a, b) -> (Either x a, Either x b) Source #

RightModule (->) These These Either Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Either a b -> Either (These x a) (These x b) Source #

RightModule (->) These These Arg Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Arg a b -> Arg (These x a) (These x b) Source #

RightModule (->) These These These Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: These a b -> These (These x a) (These x b) Source #

RightModule (->) These These (,) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: (a, b) -> (These x a, These x b) Source #

Monad m => RightModule (->) Either Either (Kleisli m) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Kleisli m a b -> Kleisli m (Either x a) (Either x b) Source #

RightModule (->) Either Either (Const :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Const a b -> Const (Either x a) (Either x b) Source #

RightModule (->) Either Either (PastroSum p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: PastroSum p a b -> PastroSum p (Either x a) (Either x b) Source #

Profunctor p => RightModule (->) Either Either (TambaraSum p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: TambaraSum p a b -> TambaraSum p (Either x a) (Either x b) Source #

Profunctor p => RightModule (->) Either Either (CofreeMapping p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: CofreeMapping p a b -> CofreeMapping p (Either x a) (Either x b) Source #

RightModule (->) Either Either (FreeMapping p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: FreeMapping p a b -> FreeMapping p (Either x a) (Either x b) Source #

Choice p => RightModule (->) Either Either (Tambara p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Tambara p a b -> Tambara p (Either x a) (Either x b) Source #

Profunctor p => RightModule (->) Either Either (CofreeTraversing p) Source # 
Instance details

Defined in Data.Bifunctor.Module

RightModule (->) Either Either (FreeTraversing p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: FreeTraversing p a b -> FreeTraversing p (Either x a) (Either x b) Source #

Choice p => RightModule (->) Either Either (Coyoneda p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Coyoneda p a b -> Coyoneda p (Either x a) (Either x b) Source #

Choice p => RightModule (->) Either Either (Yoneda p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Yoneda p a b -> Yoneda p (Either x a) (Either x b) Source #

RightModule (->) Either Either (Tagged :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Tagged a b -> Tagged (Either x a) (Either x b) Source #

RightModule (->) Either Either ((,,) x1) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: (x1, a, b) -> (x1, Either x a, Either x b) Source #

RightModule (->) These These (Const :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Const a b -> Const (These x a) (These x b) Source #

RightModule (->) These These ((,,) x1) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: (x1, a, b) -> (x1, These x a, These x b) Source #

Monad m => RightModule (->) (,) (,) (Kleisli m) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Kleisli m a b -> Kleisli m (x, a) (x, b) Source #

Strong p => RightModule (->) (,) (,) (Closure p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Closure p a b -> Closure p (x, a) (x, b) Source #

Profunctor p => RightModule (->) (,) (,) (CofreeMapping p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: CofreeMapping p a b -> CofreeMapping p (x, a) (x, b) Source #

RightModule (->) (,) (,) (FreeMapping p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: FreeMapping p a b -> FreeMapping p (x, a) (x, b) Source #

RightModule (->) (,) (,) (Pastro p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Pastro p a b -> Pastro p (x, a) (x, b) Source #

Profunctor p => RightModule (->) (,) (,) (Tambara p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Tambara p a b -> Tambara p (x, a) (x, b) Source #

Profunctor p => RightModule (->) (,) (,) (CofreeTraversing p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: CofreeTraversing p a b -> CofreeTraversing p (x, a) (x, b) Source #

RightModule (->) (,) (,) (FreeTraversing p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: FreeTraversing p a b -> FreeTraversing p (x, a) (x, b) Source #

Strong p => RightModule (->) (,) (,) (Coyoneda p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Coyoneda p a b -> Coyoneda p (x, a) (x, b) Source #

Strong p => RightModule (->) (,) (,) (Yoneda p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Yoneda p a b -> Yoneda p (x, a) (x, b) Source #

RightModule (->) Either Either (K1 i :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: K1 i a b -> K1 i (Either x a) (Either x b) Source #

Comonad w => RightModule (->) Either Either (Cokleisli w) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Cokleisli w a b -> Cokleisli w (Either x a) (Either x b) Source #

Monoid r => RightModule (->) Either Either (Forget r :: Type -> Type -> TYPE LiftedRep) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Forget r a b -> Forget r (Either x a) (Either x b) Source #

Applicative f => RightModule (->) Either Either (Star f) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Star f a b -> Star f (Either x a) (Either x b) Source #

RightModule (->) Either Either ((,,,) x1 x2) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: (x1, x2, a, b) -> (x1, x2, Either x a, Either x b) Source #

RightModule (->) Either Either (->) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: (a -> b) -> (Either x a -> Either x b) Source #

RightModule (->) These These (K1 i :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: K1 i a b -> K1 i (These x a) (These x b) Source #

RightModule (->) These These ((,,,) x1 x2) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: (x1, x2, a, b) -> (x1, x2, These x a, These x b) Source #

RightModule (->) (,) (,) (Forget r :: Type -> Type -> TYPE LiftedRep) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Forget r a b -> Forget r (x, a) (x, b) Source #

Functor m => RightModule (->) (,) (,) (Star m) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Star m a b -> Star m (x, a) (x, b) Source #

RightModule (->) (,) (,) (->) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: (a -> b) -> ((x, a) -> (x, b)) Source #

Functor f => RightModule (->) Either Either (Joker f :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Joker f a b -> Joker f (Either x a) (Either x b) Source #

ArrowChoice p => RightModule (->) Either Either (WrappedArrow p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: WrappedArrow p a b -> WrappedArrow p (Either x a) (Either x b) Source #

RightModule (->) Either Either ((,,,,) x1 x2 x3) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: (x1, x2, x3, a, b) -> (x1, x2, x3, Either x a, Either x b) Source #

RightModule (->) These These ((,,,,) x1 x2 x3) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: (x1, x2, x3, a, b) -> (x1, x2, x3, These x a, These x b) Source #

Contravariant f => RightModule (->) (,) (,) (Clown f :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Clown f a b -> Clown f (x, a) (x, b) Source #

Arrow p => RightModule (->) (,) (,) (WrappedArrow p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: WrappedArrow p a b -> WrappedArrow p (x, a) (x, b) Source #

(Choice p, Choice q) => RightModule (->) Either Either (Product p q) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Product p q a b -> Product p q (Either x a) (Either x b) Source #

(Choice p, Choice q) => RightModule (->) Either Either (Sum p q) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Sum p q a b -> Sum p q (Either x a) (Either x b) Source #

RightModule (->) Either Either ((,,,,,) x1 x2 x3 x4) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: (x1, x2, x3, x4, a, b) -> (x1, x2, x3, x4, Either x a, Either x b) Source #

RightModule (->) These These ((,,,,,) x1 x2 x3 x4) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: (x1, x2, x3, x4, a, b) -> (x1, x2, x3, x4, These x a, These x b) Source #

(Strong p, Strong q) => RightModule (->) (,) (,) (Product p q) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Product p q a b -> Product p q (x, a) (x, b) Source #

(Strong p, Strong q) => RightModule (->) (,) (,) (Sum p q) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Sum p q a b -> Sum p q (x, a) (x, b) Source #

(Functor f, Choice p) => RightModule (->) Either Either (Tannen f p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Tannen f p a b -> Tannen f p (Either x a) (Either x b) Source #

(Functor f, Choice q) => RightModule (->) Either Either (Cayley f q) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Cayley f q a b -> Cayley f q (Either x a) (Either x b) Source #

(Choice p, Choice q) => RightModule (->) Either Either (Procompose p q) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Procompose p q a b -> Procompose p q (Either x a) (Either x b) Source #

RightModule (->) Either Either ((,,,,,,) x1 x2 x3 x4 x5) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: (x1, x2, x3, x4, x5, a, b) -> (x1, x2, x3, x4, x5, Either x a, Either x b) Source #

RightModule (->) These These ((,,,,,,) x1 x2 x3 x4 x5) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: (x1, x2, x3, x4, x5, a, b) -> (x1, x2, x3, x4, x5, These x a, These x b) Source #

(Functor f, Strong q) => RightModule (->) (,) (,) (Tannen f q) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Tannen f q a b -> Tannen f q (x, a) (x, b) Source #

(Functor f, Strong q) => RightModule (->) (,) (,) (Cayley f q) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Cayley f q a b -> Cayley f q (x, a) (x, b) Source #

(Strong p, Strong q) => RightModule (->) (,) (,) (Procompose p q) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rstrength :: Procompose p q a b -> Procompose p q (x, a) (x, b) Source #

Bimodule

class (LeftModule cat t1 t2 f, RightModule cat t1 t2 f) => Bimodule cat t1 t2 f Source #

A Profunctor equipped with both a Tambara LeftModule and Tambara RightModule is a Bimodule.

Laws

rstrengthdimap swap swap . lstrength
lstrengthdimap swap swap . rstrength

Instances

Instances details
Bimodule Op (,) (,) Either Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule Op (,) (,) Arg Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule Op (,) (,) These Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule Op (,) (,) (,) Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule Op (,) (,) (Const :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule Op (,) (,) ((,,) x1) Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule Op (,) (,) (K1 i :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule Op (,) (,) ((,,,) x1 x2) Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule Op (,) (,) ((,,,,) x1 x2 x3) Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule Op (,) (,) ((,,,,,) x1 x2 x3 x4) Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule Op (,) (,) ((,,,,,,) x1 x2 x3 x4 x5) Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule (->) Either Either Either Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule (->) Either Either Arg Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule (->) Either Either These Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule (->) Either Either (,) Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule (->) These These Either Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule (->) These These Arg Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule (->) These These These Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule (->) These These (,) Source # 
Instance details

Defined in Data.Bifunctor.Module

Monad m => Bimodule (->) Either Either (Kleisli m) Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule (->) Either Either (Const :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule (->) Either Either (PastroSum p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Profunctor p => Bimodule (->) Either Either (TambaraSum p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Profunctor p => Bimodule (->) Either Either (CofreeMapping p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule (->) Either Either (FreeMapping p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Choice p => Bimodule (->) Either Either (Tambara p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Profunctor p => Bimodule (->) Either Either (CofreeTraversing p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule (->) Either Either (FreeTraversing p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Choice p => Bimodule (->) Either Either (Coyoneda p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Choice p => Bimodule (->) Either Either (Yoneda p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule (->) Either Either (Tagged :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule (->) Either Either ((,,) x1) Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule (->) These These (Const :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule (->) These These ((,,) x1) Source # 
Instance details

Defined in Data.Bifunctor.Module

Monad m => Bimodule (->) (,) (,) (Kleisli m) Source # 
Instance details

Defined in Data.Bifunctor.Module

Strong p => Bimodule (->) (,) (,) (Closure p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Profunctor p => Bimodule (->) (,) (,) (CofreeMapping p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule (->) (,) (,) (FreeMapping p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule (->) (,) (,) (Pastro p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Profunctor p => Bimodule (->) (,) (,) (Tambara p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Profunctor p => Bimodule (->) (,) (,) (CofreeTraversing p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule (->) (,) (,) (FreeTraversing p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Strong p => Bimodule (->) (,) (,) (Coyoneda p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Strong p => Bimodule (->) (,) (,) (Yoneda p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule (->) Either Either (K1 i :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Comonad w => Bimodule (->) Either Either (Cokleisli w) Source # 
Instance details

Defined in Data.Bifunctor.Module

Monoid r => Bimodule (->) Either Either (Forget r :: Type -> Type -> TYPE LiftedRep) Source # 
Instance details

Defined in Data.Bifunctor.Module

Applicative f => Bimodule (->) Either Either (Star f) Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule (->) Either Either ((,,,) x1 x2) Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule (->) Either Either (->) Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule (->) These These (K1 i :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule (->) These These ((,,,) x1 x2) Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule (->) (,) (,) (Forget r :: Type -> Type -> TYPE LiftedRep) Source # 
Instance details

Defined in Data.Bifunctor.Module

Functor m => Bimodule (->) (,) (,) (Star m) Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule (->) (,) (,) (->) Source # 
Instance details

Defined in Data.Bifunctor.Module

Functor f => Bimodule (->) Either Either (Joker f :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

ArrowChoice p => Bimodule (->) Either Either (WrappedArrow p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule (->) Either Either ((,,,,) x1 x2 x3) Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule (->) These These ((,,,,) x1 x2 x3) Source # 
Instance details

Defined in Data.Bifunctor.Module

Contravariant f => Bimodule (->) (,) (,) (Clown f :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Arrow p => Bimodule (->) (,) (,) (WrappedArrow p) Source # 
Instance details

Defined in Data.Bifunctor.Module

(Choice p, Choice q) => Bimodule (->) Either Either (Product p q) Source # 
Instance details

Defined in Data.Bifunctor.Module

(Choice p, Choice q) => Bimodule (->) Either Either (Sum p q) Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule (->) Either Either ((,,,,,) x1 x2 x3 x4) Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule (->) These These ((,,,,,) x1 x2 x3 x4) Source # 
Instance details

Defined in Data.Bifunctor.Module

(Strong p, Strong q) => Bimodule (->) (,) (,) (Product p q) Source # 
Instance details

Defined in Data.Bifunctor.Module

(Strong p, Strong q) => Bimodule (->) (,) (,) (Sum p q) Source # 
Instance details

Defined in Data.Bifunctor.Module

(Functor f, Choice p) => Bimodule (->) Either Either (Tannen f p) Source # 
Instance details

Defined in Data.Bifunctor.Module

(Functor f, Choice q) => Bimodule (->) Either Either (Cayley f q) Source # 
Instance details

Defined in Data.Bifunctor.Module

(Choice p, Choice q) => Bimodule (->) Either Either (Procompose p q) Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule (->) Either Either ((,,,,,,) x1 x2 x3 x4 x5) Source # 
Instance details

Defined in Data.Bifunctor.Module

Bimodule (->) These These ((,,,,,,) x1 x2 x3 x4 x5) Source # 
Instance details

Defined in Data.Bifunctor.Module

(Functor f, Strong q) => Bimodule (->) (,) (,) (Tannen f q) Source # 
Instance details

Defined in Data.Bifunctor.Module

(Functor f, Strong q) => Bimodule (->) (,) (,) (Cayley f q) Source # 
Instance details

Defined in Data.Bifunctor.Module

(Strong p, Strong q) => Bimodule (->) (,) (,) (Procompose p q) Source # 
Instance details

Defined in Data.Bifunctor.Module

LeftCoModule

class LeftCoModule cat t1 t2 f where Source #

A Profunctor \(P : \mathcal{C}^{op} \times \mathcal{D} \to Set\) is a Tambara LeftCoModule if it is equipped with a morphism \(s^{-1}_{a,b,m} : P(a \odot m, a \odot m) \to P(a, b) \), which we call lcostrength.

Laws

lmap inclllcostrength . rmap incll
lcostrength . lmap (rstrength f) ≡ lcostrength . rmap (rstrength f)
lcostrength . lcostrengthlcostrength . dimap (fwd assoc) (bwd assoc)

Methods

lcostrength :: cat (f (t1 a x) (t2 b x)) (f a b) Source #

Examples

Expand

unfirst:

>>> :t lcostrength @(->) @(,) @(,)
lcostrength @(->) @(,) @(,) :: LeftCoModule (->) (,) (,) f => f (a, x) (b, x) -> f a b

unleft:

>>> :t lcostrength @(->) @Either @Either
lcostrength @(->) @Either @Either :: LeftCoModule (->) Either Either f => f (Either a x) (Either b x) -> f a b

Instances

Instances details
LeftCoModule Op Either Either Either Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Op (Either (Either a x) (Either b x)) (Either a b) Source #

LeftCoModule Op Either Either Arg Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Op (Arg (Either a x) (Either b x)) (Arg a b) Source #

LeftCoModule Op Either Either These Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Op (These (Either a x) (Either b x)) (These a b) Source #

LeftCoModule Op Either Either (,) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Op (Either a x, Either b x) (a, b) Source #

LeftCoModule Op These These Either Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Op (Either (These a x) (These b x)) (Either a b) Source #

LeftCoModule Op These These Arg Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Op (Arg (These a x) (These b x)) (Arg a b) Source #

LeftCoModule Op These These These Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Op (These (These a x) (These b x)) (These a b) Source #

LeftCoModule Op These These (,) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Op (These a x, These b x) (a, b) Source #

LeftCoModule Op Either Either (Const :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Op (Const (Either a x) (Either b x)) (Const a b) Source #

LeftCoModule Op Either Either ((,,) x1) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Op (x1, Either a x, Either b x) (x1, a, b) Source #

LeftCoModule Op These These (Const :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Op (Const (These a x) (These b x)) (Const a b) Source #

LeftCoModule Op These These ((,,) x1) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Op (x1, These a x, These b x) (x1, a, b) Source #

LeftCoModule Op Either Either (K1 i :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Op (K1 i (Either a x) (Either b x)) (K1 i a b) Source #

LeftCoModule Op Either Either ((,,,) x1 x2) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Op (x1, x2, Either a x, Either b x) (x1, x2, a, b) Source #

LeftCoModule Op These These (K1 i :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Op (K1 i (These a x) (These b x)) (K1 i a b) Source #

LeftCoModule Op These These ((,,,) x1 x2) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Op (x1, x2, These a x, These b x) (x1, x2, a, b) Source #

LeftCoModule Op Either Either ((,,,,) x1 x2 x3) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Op (x1, x2, x3, Either a x, Either b x) (x1, x2, x3, a, b) Source #

LeftCoModule Op These These ((,,,,) x1 x2 x3) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Op (x1, x2, x3, These a x, These b x) (x1, x2, x3, a, b) Source #

LeftCoModule Op Either Either ((,,,,,) x1 x2 x3 x4) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Op (x1, x2, x3, x4, Either a x, Either b x) (x1, x2, x3, x4, a, b) Source #

LeftCoModule Op These These ((,,,,,) x1 x2 x3 x4) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Op (x1, x2, x3, x4, These a x, These b x) (x1, x2, x3, x4, a, b) Source #

LeftCoModule Op Either Either ((,,,,,,) x1 x2 x3 x4 x5) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Op (x1, x2, x3, x4, x5, Either a x, Either b x) (x1, x2, x3, x4, x5, a, b) Source #

LeftCoModule Op These These ((,,,,,,) x1 x2 x3 x4 x5) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Op (x1, x2, x3, x4, x5, These a x, These b x) (x1, x2, x3, x4, x5, a, b) Source #

LeftCoModule (->) (,) (,) Either Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Either (a, x) (b, x) -> Either a b Source #

LeftCoModule (->) (,) (,) Arg Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Arg (a, x) (b, x) -> Arg a b Source #

LeftCoModule (->) (,) (,) These Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: These (a, x) (b, x) -> These a b Source #

LeftCoModule (->) (,) (,) (,) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: ((a, x), (b, x)) -> (a, b) Source #

LeftCoModule (->) Either Either (CopastroSum p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: CopastroSum p (Either a x) (Either b x) -> CopastroSum p a b Source #

LeftCoModule (->) Either Either (CotambaraSum p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: CotambaraSum p (Either a x) (Either b x) -> CotambaraSum p a b Source #

Cochoice p => LeftCoModule (->) Either Either (Coyoneda p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Coyoneda p (Either a x) (Either b x) -> Coyoneda p a b Source #

Cochoice p => LeftCoModule (->) Either Either (Yoneda p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Yoneda p (Either a x) (Either b x) -> Yoneda p a b Source #

MonadFix m => LeftCoModule (->) (,) (,) (Kleisli m) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Kleisli m (a, x) (b, x) -> Kleisli m a b Source #

LeftCoModule (->) (,) (,) (Const :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Const (a, x) (b, x) -> Const a b Source #

Cochoice p => LeftCoModule (->) (,) (,) (Copastro p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Copastro p (a, x) (b, x) -> Copastro p a b Source #

Costrong p => LeftCoModule (->) (,) (,) (Coyoneda p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Coyoneda p (a, x) (b, x) -> Coyoneda p a b Source #

Costrong p => LeftCoModule (->) (,) (,) (Yoneda p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Yoneda p (a, x) (b, x) -> Yoneda p a b Source #

LeftCoModule (->) (,) (,) (Tagged :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Tagged (a, x) (b, x) -> Tagged a b Source #

LeftCoModule (->) (,) (,) ((,,) x1) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: (x1, (a, x), (b, x)) -> (x1, a, b) Source #

Applicative f => LeftCoModule (->) Either Either (Costar f) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Costar f (Either a x) (Either b x) -> Costar f a b Source #

LeftCoModule (->) Either Either (Forget r :: Type -> Type -> TYPE LiftedRep) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Forget r (Either a x) (Either b x) -> Forget r a b Source #

Traversable f => LeftCoModule (->) Either Either (Star f) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Star f (Either a x) (Either b x) -> Star f a b Source #

LeftCoModule (->) Either Either (->) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: (Either a x -> Either b x) -> (a -> b) Source #

LeftCoModule (->) (,) (,) (K1 i :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: K1 i (a, x) (b, x) -> K1 i a b Source #

Functor f => LeftCoModule (->) (,) (,) (Cokleisli f) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Cokleisli f (a, x) (b, x) -> Cokleisli f a b Source #

Functor f => LeftCoModule (->) (,) (,) (Costar f) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Costar f (a, x) (b, x) -> Costar f a b Source #

LeftCoModule (->) (,) (,) ((,,,) x1 x2) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: (x1, x2, (a, x), (b, x)) -> (x1, x2, a, b) Source #

LeftCoModule (->) (,) (,) (->) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: ((a, x) -> (b, x)) -> (a -> b) Source #

ArrowLoop p => LeftCoModule (->) (,) (,) (WrappedArrow p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: WrappedArrow p (a, x) (b, x) -> WrappedArrow p a b Source #

LeftCoModule (->) (,) (,) ((,,,,) x1 x2 x3) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: (x1, x2, x3, (a, x), (b, x)) -> (x1, x2, x3, a, b) Source #

(Cochoice p, Cochoice q) => LeftCoModule (->) Either Either (Product p q) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Product p q (Either a x) (Either b x) -> Product p q a b Source #

(Cochoice p, Cochoice q) => LeftCoModule (->) Either Either (Sum p q) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Sum p q (Either a x) (Either b x) -> Sum p q a b Source #

(Costrong p, Costrong q) => LeftCoModule (->) (,) (,) (Product p q) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Product p q (a, x) (b, x) -> Product p q a b Source #

(Costrong p, Costrong q) => LeftCoModule (->) (,) (,) (Sum p q) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Sum p q (a, x) (b, x) -> Sum p q a b Source #

LeftCoModule (->) (,) (,) ((,,,,,) x1 x2 x3 x4) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: (x1, x2, x3, x4, (a, x), (b, x)) -> (x1, x2, x3, x4, a, b) Source #

(Functor f, Cochoice p) => LeftCoModule (->) Either Either (Tannen f p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Tannen f p (Either a x) (Either b x) -> Tannen f p a b Source #

(Functor f, Cochoice p) => LeftCoModule (->) Either Either (Cayley f p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Cayley f p (Either a x) (Either b x) -> Cayley f p a b Source #

(Functor f, Costrong p) => LeftCoModule (->) (,) (,) (Tannen f p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Tannen f p (a, x) (b, x) -> Tannen f p a b Source #

(Functor f, Costrong p) => LeftCoModule (->) (,) (,) (Cayley f p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Cayley f p (a, x) (b, x) -> Cayley f p a b Source #

(Corepresentable p, Corepresentable q) => LeftCoModule (->) (,) (,) (Procompose p q) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: Procompose p q (a, x) (b, x) -> Procompose p q a b Source #

LeftCoModule (->) (,) (,) ((,,,,,,) x1 x2 x3 x4 x5) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

lcostrength :: (x1, x2, x3, x4, x5, (a, x), (b, x)) -> (x1, x2, x3, x4, x5, a, b) Source #

RightCoModule

class RightCoModule cat t1 t2 f where Source #

A Profunctor \(P : \mathcal{C}^{op} \times \mathcal{D} \to Set\) is a Tambara RightCoModule if it is equipped with a morphism \(s^{-1}_{a,b,m} : P(m \odot a, m \odot a) \to P(a, b) \), which we call rcostrength.

Laws

lmap inclrrcostrength . rmap inclr
rcostrength . lmap (lstrength f) ≡ rcostrength . rmap (lstrength f)
rcostrength . rcostrengthrcostrength . dimap (bwd assoc) (fwd assoc)

Methods

rcostrength :: cat (f (x `t1` a) (x `t2` b)) (f a b) Source #

Examples

Expand

unsecond:

>>> :t rcostrength @(->) @(,) @(,)
rcostrength @(->) @(,) @(,) :: RightCoModule (->) (,) (,) f => f (x, a) (x, b) -> f a b

unright:

>>> :t rcostrength @(->) @Either @Either
rcostrength @(->) @Either @Either :: RightCoModule (->) Either Either f => f (Either x a) (Either x b) -> f a b

Instances

Instances details
RightCoModule Op Either Either Either Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Op (Either (Either x a) (Either x b)) (Either a b) Source #

RightCoModule Op Either Either Arg Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Op (Arg (Either x a) (Either x b)) (Arg a b) Source #

RightCoModule Op Either Either These Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Op (These (Either x a) (Either x b)) (These a b) Source #

RightCoModule Op Either Either (,) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Op (Either x a, Either x b) (a, b) Source #

RightCoModule Op These These Either Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Op (Either (These x a) (These x b)) (Either a b) Source #

RightCoModule Op These These Arg Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Op (Arg (These x a) (These x b)) (Arg a b) Source #

RightCoModule Op These These These Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Op (These (These x a) (These x b)) (These a b) Source #

RightCoModule Op These These (,) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Op (These x a, These x b) (a, b) Source #

RightCoModule Op Either Either (Const :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Op (Const (Either x a) (Either x b)) (Const a b) Source #

RightCoModule Op Either Either ((,,) x1) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Op (x1, Either x a, Either x b) (x1, a, b) Source #

RightCoModule Op These These (Const :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Op (Const (These x a) (These x b)) (Const a b) Source #

RightCoModule Op These These ((,,) x1) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Op (x1, These x a, These x b) (x1, a, b) Source #

RightCoModule Op Either Either (K1 i :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Op (K1 i (Either x a) (Either x b)) (K1 i a b) Source #

RightCoModule Op Either Either ((,,,) x1 x2) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Op (x1, x2, Either x a, Either x b) (x1, x2, a, b) Source #

RightCoModule Op These These (K1 i :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Op (K1 i (These x a) (These x b)) (K1 i a b) Source #

RightCoModule Op These These ((,,,) x1 x2) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Op (x1, x2, These x a, These x b) (x1, x2, a, b) Source #

RightCoModule Op Either Either ((,,,,) x1 x2 x3) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Op (x1, x2, x3, Either x a, Either x b) (x1, x2, x3, a, b) Source #

RightCoModule Op These These ((,,,,) x1 x2 x3) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Op (x1, x2, x3, These x a, These x b) (x1, x2, x3, a, b) Source #

RightCoModule Op Either Either ((,,,,,) x1 x2 x3 x4) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Op (x1, x2, x3, x4, Either x a, Either x b) (x1, x2, x3, x4, a, b) Source #

RightCoModule Op These These ((,,,,,) x1 x2 x3 x4) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Op (x1, x2, x3, x4, These x a, These x b) (x1, x2, x3, x4, a, b) Source #

RightCoModule Op Either Either ((,,,,,,) x1 x2 x3 x4 x5) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Op (x1, x2, x3, x4, x5, Either x a, Either x b) (x1, x2, x3, x4, x5, a, b) Source #

RightCoModule Op These These ((,,,,,,) x1 x2 x3 x4 x5) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Op (x1, x2, x3, x4, x5, These x a, These x b) (x1, x2, x3, x4, x5, a, b) Source #

RightCoModule (->) (,) (,) Either Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Either (x, a) (x, b) -> Either a b Source #

RightCoModule (->) (,) (,) Arg Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Arg (x, a) (x, b) -> Arg a b Source #

RightCoModule (->) (,) (,) These Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: These (x, a) (x, b) -> These a b Source #

RightCoModule (->) (,) (,) (,) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: ((x, a), (x, b)) -> (a, b) Source #

RightCoModule (->) Either Either (CopastroSum p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: CopastroSum p (Either x a) (Either x b) -> CopastroSum p a b Source #

RightCoModule (->) Either Either (CotambaraSum p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: CotambaraSum p (Either x a) (Either x b) -> CotambaraSum p a b Source #

Cochoice p => RightCoModule (->) Either Either (Coyoneda p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Coyoneda p (Either x a) (Either x b) -> Coyoneda p a b Source #

Cochoice p => RightCoModule (->) Either Either (Yoneda p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Yoneda p (Either x a) (Either x b) -> Yoneda p a b Source #

MonadFix m => RightCoModule (->) (,) (,) (Kleisli m) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Kleisli m (x, a) (x, b) -> Kleisli m a b Source #

RightCoModule (->) (,) (,) (Const :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Const (x, a) (x, b) -> Const a b Source #

Cochoice p => RightCoModule (->) (,) (,) (Copastro p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Copastro p (x, a) (x, b) -> Copastro p a b Source #

Costrong p => RightCoModule (->) (,) (,) (Coyoneda p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Coyoneda p (x, a) (x, b) -> Coyoneda p a b Source #

Costrong p => RightCoModule (->) (,) (,) (Yoneda p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Yoneda p (x, a) (x, b) -> Yoneda p a b Source #

RightCoModule (->) (,) (,) (Tagged :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Tagged (x, a) (x, b) -> Tagged a b Source #

RightCoModule (->) (,) (,) ((,,) x1) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: (x1, (x, a), (x, b)) -> (x1, a, b) Source #

Applicative f => RightCoModule (->) Either Either (Costar f) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Costar f (Either x a) (Either x b) -> Costar f a b Source #

RightCoModule (->) Either Either (Forget r :: Type -> Type -> TYPE LiftedRep) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Forget r (Either x a) (Either x b) -> Forget r a b Source #

Traversable f => RightCoModule (->) Either Either (Star f) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Star f (Either x a) (Either x b) -> Star f a b Source #

RightCoModule (->) Either Either (->) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: (Either x a -> Either x b) -> (a -> b) Source #

RightCoModule (->) (,) (,) (K1 i :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: K1 i (x, a) (x, b) -> K1 i a b Source #

Functor f => RightCoModule (->) (,) (,) (Cokleisli f) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Cokleisli f (x, a) (x, b) -> Cokleisli f a b Source #

Functor f => RightCoModule (->) (,) (,) (Costar f) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Costar f (x, a) (x, b) -> Costar f a b Source #

RightCoModule (->) (,) (,) ((,,,) x1 x2) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: (x1, x2, (x, a), (x, b)) -> (x1, x2, a, b) Source #

RightCoModule (->) (,) (,) (->) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: ((x, a) -> (x, b)) -> (a -> b) Source #

ArrowLoop p => RightCoModule (->) (,) (,) (WrappedArrow p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: WrappedArrow p (x, a) (x, b) -> WrappedArrow p a b Source #

RightCoModule (->) (,) (,) ((,,,,) x1 x2 x3) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: (x1, x2, x3, (x, a), (x, b)) -> (x1, x2, x3, a, b) Source #

(Cochoice p, Cochoice q) => RightCoModule (->) Either Either (Product p q) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Product p q (Either x a) (Either x b) -> Product p q a b Source #

(Cochoice p, Cochoice q) => RightCoModule (->) Either Either (Sum p q) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Sum p q (Either x a) (Either x b) -> Sum p q a b Source #

(Costrong p, Costrong q) => RightCoModule (->) (,) (,) (Product p q) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Product p q (x, a) (x, b) -> Product p q a b Source #

(Costrong p, Costrong q) => RightCoModule (->) (,) (,) (Sum p q) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Sum p q (x, a) (x, b) -> Sum p q a b Source #

RightCoModule (->) (,) (,) ((,,,,,) x1 x2 x3 x4) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: (x1, x2, x3, x4, (x, a), (x, b)) -> (x1, x2, x3, x4, a, b) Source #

(Functor f, Cochoice p) => RightCoModule (->) Either Either (Tannen f p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Tannen f p (Either x a) (Either x b) -> Tannen f p a b Source #

(Functor f, Cochoice p) => RightCoModule (->) Either Either (Cayley f p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Cayley f p (Either x a) (Either x b) -> Cayley f p a b Source #

(Functor f, Costrong p) => RightCoModule (->) (,) (,) (Tannen f p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Tannen f p (x, a) (x, b) -> Tannen f p a b Source #

(Functor f, Costrong p) => RightCoModule (->) (,) (,) (Cayley f p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Cayley f p (x, a) (x, b) -> Cayley f p a b Source #

(Corepresentable p, Corepresentable q) => RightCoModule (->) (,) (,) (Procompose p q) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: Procompose p q (x, a) (x, b) -> Procompose p q a b Source #

RightCoModule (->) (,) (,) ((,,,,,,) x1 x2 x3 x4 x5) Source # 
Instance details

Defined in Data.Bifunctor.Module

Methods

rcostrength :: (x1, x2, x3, x4, x5, (x, a), (x, b)) -> (x1, x2, x3, x4, x5, a, b) Source #

CoBimodule

class (LeftCoModule cat t1 t2 f, RightCoModule cat t1 t2 f) => CoBimodule cat t1 t2 f Source #

Instances

Instances details
CoBimodule Op Either Either Either Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule Op Either Either Arg Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule Op Either Either These Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule Op Either Either (,) Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule Op These These Either Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule Op These These Arg Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule Op These These These Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule Op These These (,) Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule Op Either Either (Const :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule Op Either Either ((,,) x1) Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule Op These These (Const :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule Op These These ((,,) x1) Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule Op Either Either (K1 i :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule Op Either Either ((,,,) x1 x2) Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule Op These These (K1 i :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule Op These These ((,,,) x1 x2) Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule Op Either Either ((,,,,) x1 x2 x3) Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule Op These These ((,,,,) x1 x2 x3) Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule Op Either Either ((,,,,,) x1 x2 x3 x4) Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule Op These These ((,,,,,) x1 x2 x3 x4) Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule Op Either Either ((,,,,,,) x1 x2 x3 x4 x5) Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule Op These These ((,,,,,,) x1 x2 x3 x4 x5) Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule (->) (,) (,) Either Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule (->) (,) (,) Arg Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule (->) (,) (,) These Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule (->) (,) (,) (,) Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule (->) Either Either (CopastroSum p) Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule (->) Either Either (CotambaraSum p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Cochoice p => CoBimodule (->) Either Either (Coyoneda p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Cochoice p => CoBimodule (->) Either Either (Yoneda p) Source # 
Instance details

Defined in Data.Bifunctor.Module

MonadFix m => CoBimodule (->) (,) (,) (Kleisli m) Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule (->) (,) (,) (Const :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Cochoice p => CoBimodule (->) (,) (,) (Copastro p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Costrong p => CoBimodule (->) (,) (,) (Coyoneda p) Source # 
Instance details

Defined in Data.Bifunctor.Module

Costrong p => CoBimodule (->) (,) (,) (Yoneda p) Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule (->) (,) (,) (Tagged :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule (->) (,) (,) ((,,) x1) Source # 
Instance details

Defined in Data.Bifunctor.Module

Applicative f => CoBimodule (->) Either Either (Costar f) Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule (->) Either Either (Forget r :: Type -> Type -> TYPE LiftedRep) Source # 
Instance details

Defined in Data.Bifunctor.Module

Traversable f => CoBimodule (->) Either Either (Star f) Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule (->) Either Either (->) Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule (->) (,) (,) (K1 i :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Module

Functor f => CoBimodule (->) (,) (,) (Cokleisli f) Source # 
Instance details

Defined in Data.Bifunctor.Module

Functor f => CoBimodule (->) (,) (,) (Costar f) Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule (->) (,) (,) ((,,,) x1 x2) Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule (->) (,) (,) (->) Source # 
Instance details

Defined in Data.Bifunctor.Module

ArrowLoop p => CoBimodule (->) (,) (,) (WrappedArrow p) Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule (->) (,) (,) ((,,,,) x1 x2 x3) Source # 
Instance details

Defined in Data.Bifunctor.Module

(Cochoice p, Cochoice q) => CoBimodule (->) Either Either (Product p q) Source # 
Instance details

Defined in Data.Bifunctor.Module

(Cochoice p, Cochoice q) => CoBimodule (->) Either Either (Sum p q) Source # 
Instance details

Defined in Data.Bifunctor.Module

(Costrong p, Costrong q) => CoBimodule (->) (,) (,) (Product p q) Source # 
Instance details

Defined in Data.Bifunctor.Module

(Costrong p, Costrong q) => CoBimodule (->) (,) (,) (Sum p q) Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule (->) (,) (,) ((,,,,,) x1 x2 x3 x4) Source # 
Instance details

Defined in Data.Bifunctor.Module

(Functor f, Cochoice p) => CoBimodule (->) Either Either (Tannen f p) Source # 
Instance details

Defined in Data.Bifunctor.Module

(Functor f, Cochoice p) => CoBimodule (->) Either Either (Cayley f p) Source # 
Instance details

Defined in Data.Bifunctor.Module

(Functor f, Costrong p) => CoBimodule (->) (,) (,) (Tannen f p) Source # 
Instance details

Defined in Data.Bifunctor.Module

(Functor f, Costrong p) => CoBimodule (->) (,) (,) (Cayley f p) Source # 
Instance details

Defined in Data.Bifunctor.Module

(Corepresentable p, Corepresentable q) => CoBimodule (->) (,) (,) (Procompose p q) Source # 
Instance details

Defined in Data.Bifunctor.Module

CoBimodule (->) (,) (,) ((,,,,,,) x1 x2 x3 x4 x5) Source # 
Instance details

Defined in Data.Bifunctor.Module