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

Data.Functor.Module

Synopsis

LeftModule

class LeftModule cat t1 f where Source #

Methods

lstrength :: cat (f a) (f (t1 a x)) Source #

Examples

Expand
>>> :t lstrength @(->) @(,) @Predicate (Predicate @Int (> 10))
lstrength @(->) @(,) @Predicate (Predicate @Int (> 10)) :: Predicate (Int, x)
>>> :t lstrength @(->) @Either @[]
lstrength @(->) @Either @[] :: a -> [Either a x]
>>> lstrength @(->) @Either @[] [True, False]
[Left True,Left False]

Instances

Instances details
LeftModule Op Either Comparison Source # 
Instance details

Defined in Data.Functor.Module

LeftModule Op Either Equivalence Source # 
Instance details

Defined in Data.Functor.Module

LeftModule Op Either Predicate Source # 
Instance details

Defined in Data.Functor.Module

Methods

lstrength :: Op (Predicate a) (Predicate (Either a x)) Source #

LeftModule Op (,) ZipList Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

LeftModule Op (,) Identity Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

LeftModule Op (,) IO Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

LeftModule Op (,) NonEmpty Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

LeftModule Op (,) Maybe Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

LeftModule Op (,) [] Source # 
Instance details

Defined in Data.Functor.Module

Methods

lstrength :: Op [a] [(a, x)] Source #

LeftModule Op Either (Op a) Source # 
Instance details

Defined in Data.Functor.Module

Methods

lstrength :: Op (Op a a0) (Op a (Either a0 x)) Source #

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

Defined in Data.Functor.Module

Methods

lstrength :: Op (Proxy a) (Proxy (Either a x)) Source #

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

Defined in Data.Functor.Module

Methods

lstrength :: Op (U1 a) (U1 (Either a x)) Source #

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

Defined in Data.Functor.Module

Methods

lstrength :: Op (V1 a) (V1 (Either a x)) Source #

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

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

lstrength :: Op (Const a a0) (Const a (Either a0 x)) Source #

Contravariant f => LeftModule Op Either (Alt f) Source # 
Instance details

Defined in Data.Functor.Module

Methods

lstrength :: Op (Alt f a) (Alt f (Either a x)) Source #

Contravariant f => LeftModule Op Either (Rec1 f) Source # 
Instance details

Defined in Data.Functor.Module

Methods

lstrength :: Op (Rec1 f a) (Rec1 f (Either a x)) Source #

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

Defined in Data.Functor.Module

Methods

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

(Contravariant f, Contravariant g) => LeftModule Op Either (Product f g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

lstrength :: Op (Product f g a) (Product f g (Either a x)) Source #

(Contravariant f, Contravariant g) => LeftModule Op Either (Sum f g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

lstrength :: Op (Sum f g a) (Sum f g (Either a x)) Source #

(Contravariant f, Contravariant g) => LeftModule Op Either (f :*: g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

lstrength :: Op ((f :*: g) a) ((f :*: g) (Either a x)) Source #

(Contravariant f, Contravariant g) => LeftModule Op Either (f :+: g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

lstrength :: Op ((f :+: g) a) ((f :+: g) (Either a x)) Source #

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

Defined in Data.Functor.Module

Methods

lstrength :: Op (K1 i c a) (K1 i c (Either a x)) Source #

(Functor f, Functor g) => LeftModule Op (,) (Product f g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

lstrength :: Op (Product f g a) (Product f g (a, x)) Source #

(Functor f, Functor g) => LeftModule Op (,) (Sum f g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

lstrength :: Op (Sum f g a) (Sum f g (a, x)) Source #

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

Defined in Data.Functor.Module

Methods

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

(Functor f, Contravariant g) => LeftModule Op Either (Compose f g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

lstrength :: Op (Compose f g a) (Compose f g (Either a x)) Source #

(Functor f, Contravariant g) => LeftModule Op Either (f :.: g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

lstrength :: Op ((f :.: g) a) ((f :.: g) (Either a x)) Source #

Contravariant f => LeftModule Op Either (M1 i c f) Source # 
Instance details

Defined in Data.Functor.Module

Methods

lstrength :: Op (M1 i c f a) (M1 i c f (Either a x)) Source #

(Functor f, Functor g) => LeftModule Op (,) (Compose f g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

lstrength :: Op (Compose f g a) (Compose f g (a, x)) Source #

LeftModule (->) Either ZipList Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

LeftModule (->) Either Identity Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

LeftModule (->) Either IO Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

LeftModule (->) Either NonEmpty Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

LeftModule (->) Either Maybe Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

lstrength :: [a] -> [Either a x] Source #

LeftModule (->) These ZipList Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

LeftModule (->) These Identity Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

LeftModule (->) These IO Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

LeftModule (->) These NonEmpty Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

LeftModule (->) These Maybe Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

lstrength :: [a] -> [These a x] Source #

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

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

lstrength :: Op a a0 -> Op a (a0, x) Source #

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

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

lstrength :: Const a a0 -> Const a (a0, x) Source #

Contravariant f => LeftModule (->) (,) (Alt f) Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

Contravariant f => LeftModule (->) (,) (Rec1 f) Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

(Functor f, Functor g) => LeftModule (->) Either (Product f g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

lstrength :: Product f g a -> Product f g (Either a x) Source #

(Functor f, Functor g) => LeftModule (->) Either (Sum f g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

lstrength :: Sum f g a -> Sum f g (Either a x) Source #

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

Defined in Data.Functor.Module

Methods

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

(Functor f, Functor g) => LeftModule (->) These (Product f g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

lstrength :: Product f g a -> Product f g (These a x) Source #

(Functor f, Functor g) => LeftModule (->) These (Sum f g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

lstrength :: Sum f g a -> Sum f g (These a x) Source #

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

Defined in Data.Functor.Module

Methods

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

(Contravariant f, Contravariant g) => LeftModule (->) (,) (Product f g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

lstrength :: Product f g a -> Product f g (a, x) Source #

(Contravariant f, Contravariant g) => LeftModule (->) (,) (Sum f g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

lstrength :: Sum f g a -> Sum f g (a, x) Source #

(Contravariant f, Contravariant g) => LeftModule (->) (,) (f :*: g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

lstrength :: (f :*: g) a -> (f :*: g) (a, x) Source #

(Contravariant f, Contravariant g) => LeftModule (->) (,) (f :+: g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

lstrength :: (f :+: g) a -> (f :+: g) (a, x) Source #

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

Defined in Data.Functor.Module

Methods

lstrength :: K1 i c a -> K1 i c (a, x) Source #

(Functor f, Functor g) => LeftModule (->) Either (Compose f g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

lstrength :: Compose f g a -> Compose f g (Either a x) Source #

(Functor f, Functor g) => LeftModule (->) These (Compose f g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

lstrength :: Compose f g a -> Compose f g (These a x) Source #

(Functor f, Contravariant g) => LeftModule (->) (,) (Compose f g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

lstrength :: Compose f g a -> Compose f g (a, x) Source #

(Functor f, Contravariant g) => LeftModule (->) (,) (f :.: g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

lstrength :: (f :.: g) a -> (f :.: g) (a, x) Source #

Contravariant f => LeftModule (->) (,) (M1 i c f) Source # 
Instance details

Defined in Data.Functor.Module

Methods

lstrength :: M1 i c f a -> M1 i c f (a, x) Source #

RightModule

class RightModule cat t1 f where Source #

Methods

rstrength :: cat (f a) (f (t1 x a)) Source #

Examples

Expand
>>> :t rstrength @(->) @(,) @Predicate (Predicate @Int (> 10))
rstrength @(->) @(,) @Predicate (Predicate @Int (> 10)) :: Predicate (x, Int)
>>> :t rstrength @(->) @Either @[]
rstrength @(->) @Either @[] :: [a] -> [Either x a]
>>> rstrength @(->) @Either @[] [True, False]
[Right True,Right False]

Instances

Instances details
RightModule Op Either Comparison Source # 
Instance details

Defined in Data.Functor.Module

RightModule Op Either Equivalence Source # 
Instance details

Defined in Data.Functor.Module

RightModule Op Either Predicate Source # 
Instance details

Defined in Data.Functor.Module

Methods

rstrength :: Op (Predicate a) (Predicate (Either x a)) Source #

RightModule Op (,) ZipList Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

RightModule Op (,) Identity Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

RightModule Op (,) IO Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

RightModule Op (,) NonEmpty Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

RightModule Op (,) Maybe Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

RightModule Op (,) [] Source # 
Instance details

Defined in Data.Functor.Module

Methods

rstrength :: Op [a] [(x, a)] Source #

RightModule Op Either (Op a) Source # 
Instance details

Defined in Data.Functor.Module

Methods

rstrength :: Op (Op a a0) (Op a (Either x a0)) Source #

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

Defined in Data.Functor.Module

Methods

rstrength :: Op (Proxy a) (Proxy (Either x a)) Source #

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

Defined in Data.Functor.Module

Methods

rstrength :: Op (U1 a) (U1 (Either x a)) Source #

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

Defined in Data.Functor.Module

Methods

rstrength :: Op (V1 a) (V1 (Either x a)) Source #

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

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

rstrength :: Op (Const a a0) (Const a (Either x a0)) Source #

Contravariant f => RightModule Op Either (Alt f) Source # 
Instance details

Defined in Data.Functor.Module

Methods

rstrength :: Op (Alt f a) (Alt f (Either x a)) Source #

Contravariant f => RightModule Op Either (Rec1 f) Source # 
Instance details

Defined in Data.Functor.Module

Methods

rstrength :: Op (Rec1 f a) (Rec1 f (Either x a)) Source #

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

Defined in Data.Functor.Module

Methods

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

(Contravariant f, Contravariant g) => RightModule Op Either (Product f g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

rstrength :: Op (Product f g a) (Product f g (Either x a)) Source #

(Contravariant f, Contravariant g) => RightModule Op Either (Sum f g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

rstrength :: Op (Sum f g a) (Sum f g (Either x a)) Source #

(Contravariant f, Contravariant g) => RightModule Op Either (f :*: g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

rstrength :: Op ((f :*: g) a) ((f :*: g) (Either x a)) Source #

(Contravariant f, Contravariant g) => RightModule Op Either (f :+: g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

rstrength :: Op ((f :+: g) a) ((f :+: g) (Either x a)) Source #

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

Defined in Data.Functor.Module

Methods

rstrength :: Op (K1 i c a) (K1 i c (Either x a)) Source #

(Functor f, Functor g) => RightModule Op (,) (Product f g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

rstrength :: Op (Product f g a) (Product f g (x, a)) Source #

(Functor f, Functor g) => RightModule Op (,) (Sum f g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

rstrength :: Op (Sum f g a) (Sum f g (x, a)) Source #

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

Defined in Data.Functor.Module

Methods

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

(Functor f, Contravariant g) => RightModule Op Either (Compose f g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

rstrength :: Op (Compose f g a) (Compose f g (Either x a)) Source #

(Functor f, Contravariant g) => RightModule Op Either (f :.: g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

rstrength :: Op ((f :.: g) a) ((f :.: g) (Either x a)) Source #

Contravariant f => RightModule Op Either (M1 i c f) Source # 
Instance details

Defined in Data.Functor.Module

Methods

rstrength :: Op (M1 i c f a) (M1 i c f (Either x a)) Source #

(Functor f, Functor g) => RightModule Op (,) (Compose f g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

rstrength :: Op (Compose f g a) (Compose f g (x, a)) Source #

RightModule (->) Either ZipList Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

RightModule (->) Either Identity Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

RightModule (->) Either IO Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

RightModule (->) Either NonEmpty Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

RightModule (->) Either Maybe Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

rstrength :: [a] -> [Either x a] Source #

RightModule (->) These ZipList Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

RightModule (->) These Identity Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

RightModule (->) These IO Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

RightModule (->) These NonEmpty Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

RightModule (->) These Maybe Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

rstrength :: [a] -> [These x a] Source #

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

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

rstrength :: Op a a0 -> Op a (x, a0) Source #

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

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

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

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

Defined in Data.Functor.Module

Methods

rstrength :: Const a a0 -> Const a (x, a0) Source #

Contravariant f => RightModule (->) (,) (Alt f) Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

Contravariant f => RightModule (->) (,) (Rec1 f) Source # 
Instance details

Defined in Data.Functor.Module

Methods

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

(Functor f, Functor g) => RightModule (->) Either (Product f g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

rstrength :: Product f g a -> Product f g (Either x a) Source #

(Functor f, Functor g) => RightModule (->) Either (Sum f g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

rstrength :: Sum f g a -> Sum f g (Either x a) Source #

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

Defined in Data.Functor.Module

Methods

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

(Functor f, Functor g) => RightModule (->) These (Product f g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

rstrength :: Product f g a -> Product f g (These x a) Source #

(Functor f, Functor g) => RightModule (->) These (Sum f g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

rstrength :: Sum f g a -> Sum f g (These x a) Source #

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

Defined in Data.Functor.Module

Methods

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

(Contravariant f, Contravariant g) => RightModule (->) (,) (Product f g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

rstrength :: Product f g a -> Product f g (x, a) Source #

(Contravariant f, Contravariant g) => RightModule (->) (,) (Sum f g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

rstrength :: Sum f g a -> Sum f g (x, a) Source #

(Contravariant f, Contravariant g) => RightModule (->) (,) (f :*: g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

rstrength :: (f :*: g) a -> (f :*: g) (x, a) Source #

(Contravariant f, Contravariant g) => RightModule (->) (,) (f :+: g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

rstrength :: (f :+: g) a -> (f :+: g) (x, a) Source #

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

Defined in Data.Functor.Module

Methods

rstrength :: K1 i c a -> K1 i c (x, a) Source #

(Functor f, Functor g) => RightModule (->) Either (Compose f g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

rstrength :: Compose f g a -> Compose f g (Either x a) Source #

(Functor f, Functor g) => RightModule (->) These (Compose f g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

rstrength :: Compose f g a -> Compose f g (These x a) Source #

(Functor f, Contravariant g) => RightModule (->) (,) (Compose f g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

rstrength :: Compose f g a -> Compose f g (x, a) Source #

(Functor f, Contravariant g) => RightModule (->) (,) (f :.: g) Source # 
Instance details

Defined in Data.Functor.Module

Methods

rstrength :: (f :.: g) a -> (f :.: g) (x, a) Source #

Contravariant f => RightModule (->) (,) (M1 i c f) Source # 
Instance details

Defined in Data.Functor.Module

Methods

rstrength :: M1 i c f a -> M1 i c f (x, a) Source #

Bimodule

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

Instances

Instances details
Bimodule Op Either Comparison Source # 
Instance details

Defined in Data.Functor.Module

Bimodule Op Either Equivalence Source # 
Instance details

Defined in Data.Functor.Module

Bimodule Op Either Predicate Source # 
Instance details

Defined in Data.Functor.Module

Bimodule Op (,) ZipList Source # 
Instance details

Defined in Data.Functor.Module

Bimodule Op (,) Identity Source # 
Instance details

Defined in Data.Functor.Module

Bimodule Op (,) IO Source # 
Instance details

Defined in Data.Functor.Module

Bimodule Op (,) NonEmpty Source # 
Instance details

Defined in Data.Functor.Module

Bimodule Op (,) Maybe Source # 
Instance details

Defined in Data.Functor.Module

Bimodule Op (,) [] Source # 
Instance details

Defined in Data.Functor.Module

Bimodule Op Either (Op a) Source # 
Instance details

Defined in Data.Functor.Module

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

Defined in Data.Functor.Module

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

Defined in Data.Functor.Module

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

Defined in Data.Functor.Module

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

Defined in Data.Functor.Module

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

Defined in Data.Functor.Module

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

Defined in Data.Functor.Module

Contravariant f => Bimodule Op Either (Alt f) Source # 
Instance details

Defined in Data.Functor.Module

Contravariant f => Bimodule Op Either (Rec1 f) Source # 
Instance details

Defined in Data.Functor.Module

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

Defined in Data.Functor.Module

(Contravariant f, Contravariant g) => Bimodule Op Either (Product f g) Source # 
Instance details

Defined in Data.Functor.Module

(Contravariant f, Contravariant g) => Bimodule Op Either (Sum f g) Source # 
Instance details

Defined in Data.Functor.Module

(Contravariant f, Contravariant g) => Bimodule Op Either (f :*: g) Source # 
Instance details

Defined in Data.Functor.Module

(Contravariant f, Contravariant g) => Bimodule Op Either (f :+: g) Source # 
Instance details

Defined in Data.Functor.Module

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

Defined in Data.Functor.Module

(Functor f, Functor g) => Bimodule Op (,) (Product f g) Source # 
Instance details

Defined in Data.Functor.Module

(Functor f, Functor g) => Bimodule Op (,) (Sum f g) Source # 
Instance details

Defined in Data.Functor.Module

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

Defined in Data.Functor.Module

(Functor f, Contravariant g) => Bimodule Op Either (Compose f g) Source # 
Instance details

Defined in Data.Functor.Module

(Functor f, Contravariant g) => Bimodule Op Either (f :.: g) Source # 
Instance details

Defined in Data.Functor.Module

Contravariant f => Bimodule Op Either (M1 i c f) Source # 
Instance details

Defined in Data.Functor.Module

(Functor f, Functor g) => Bimodule Op (,) (Compose f g) Source # 
Instance details

Defined in Data.Functor.Module

Bimodule (->) Either ZipList Source # 
Instance details

Defined in Data.Functor.Module

Bimodule (->) Either Identity Source # 
Instance details

Defined in Data.Functor.Module

Bimodule (->) Either IO Source # 
Instance details

Defined in Data.Functor.Module

Bimodule (->) Either NonEmpty Source # 
Instance details

Defined in Data.Functor.Module

Bimodule (->) Either Maybe Source # 
Instance details

Defined in Data.Functor.Module

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

Defined in Data.Functor.Module

Bimodule (->) These ZipList Source # 
Instance details

Defined in Data.Functor.Module

Bimodule (->) These Identity Source # 
Instance details

Defined in Data.Functor.Module

Bimodule (->) These IO Source # 
Instance details

Defined in Data.Functor.Module

Bimodule (->) These NonEmpty Source # 
Instance details

Defined in Data.Functor.Module

Bimodule (->) These Maybe Source # 
Instance details

Defined in Data.Functor.Module

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

Defined in Data.Functor.Module

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

Defined in Data.Functor.Module

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

Defined in Data.Functor.Module

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

Defined in Data.Functor.Module

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

Defined in Data.Functor.Module

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

Defined in Data.Functor.Module

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

Defined in Data.Functor.Module

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

Defined in Data.Functor.Module

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

Defined in Data.Functor.Module

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

Defined in Data.Functor.Module

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

Defined in Data.Functor.Module

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

Defined in Data.Functor.Module

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

Defined in Data.Functor.Module

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

Defined in Data.Functor.Module

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

Defined in Data.Functor.Module

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

Defined in Data.Functor.Module

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

Defined in Data.Functor.Module

Contravariant f => Bimodule (->) (,) (Alt f) Source # 
Instance details

Defined in Data.Functor.Module

Contravariant f => Bimodule (->) (,) (Rec1 f) Source # 
Instance details

Defined in Data.Functor.Module

(Functor f, Functor g) => Bimodule (->) Either (Product f g) Source # 
Instance details

Defined in Data.Functor.Module

(Functor f, Functor g) => Bimodule (->) Either (Sum f g) Source # 
Instance details

Defined in Data.Functor.Module

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

Defined in Data.Functor.Module

(Functor f, Functor g) => Bimodule (->) These (Product f g) Source # 
Instance details

Defined in Data.Functor.Module

(Functor f, Functor g) => Bimodule (->) These (Sum f g) Source # 
Instance details

Defined in Data.Functor.Module

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

Defined in Data.Functor.Module

(Contravariant f, Contravariant g) => Bimodule (->) (,) (Product f g) Source # 
Instance details

Defined in Data.Functor.Module

(Contravariant f, Contravariant g) => Bimodule (->) (,) (Sum f g) Source # 
Instance details

Defined in Data.Functor.Module

(Contravariant f, Contravariant g) => Bimodule (->) (,) (f :*: g) Source # 
Instance details

Defined in Data.Functor.Module

(Contravariant f, Contravariant g) => Bimodule (->) (,) (f :+: g) Source # 
Instance details

Defined in Data.Functor.Module

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

Defined in Data.Functor.Module

(Functor f, Functor g) => Bimodule (->) Either (Compose f g) Source # 
Instance details

Defined in Data.Functor.Module

(Functor f, Functor g) => Bimodule (->) These (Compose f g) Source # 
Instance details

Defined in Data.Functor.Module

(Functor f, Contravariant g) => Bimodule (->) (,) (Compose f g) Source # 
Instance details

Defined in Data.Functor.Module

(Functor f, Contravariant g) => Bimodule (->) (,) (f :.: g) Source # 
Instance details

Defined in Data.Functor.Module

Contravariant f => Bimodule (->) (,) (M1 i c f) Source # 
Instance details

Defined in Data.Functor.Module