functor-monad-0.1.1.0: FFunctor: functors on (the usual) Functors
Safe HaskellSafe-Inferred
LanguageHaskell2010

FFunctor.Adjunction

Synopsis

Documentation

class (FFunctor ff, FFunctor uu) => Adjunction ff uu | ff -> uu, uu -> ff where Source #

An adjunction between \(\mathrm{Hask}^{\mathrm{Hask}}\) and \(\mathrm{Hask}^{\mathrm{Hask}}\).

Minimal complete definition

unit, counit | leftAdjunct, rightAdjunct

Methods

unit :: forall g. Functor g => g ~> uu (ff g) Source #

counit :: forall g. Functor g => ff (uu g) ~> g Source #

leftAdjunct :: forall g h. (Functor g, Functor h) => (ff g ~> h) -> g ~> uu h Source #

rightAdjunct :: forall g h. (Functor g, Functor h) => (g ~> uu h) -> ff g ~> h Source #

Instances

Instances details
Adjunction (EnvT e) (ReaderT e) Source # 
Instance details

Defined in FFunctor.Adjunction

Methods

unit :: forall (g :: Type -> Type). Functor g => g ~> ReaderT e (EnvT e g) Source #

counit :: forall (g :: Type -> Type). Functor g => EnvT e (ReaderT e g) ~> g Source #

leftAdjunct :: forall (g :: Type -> Type) (h :: Type -> Type). (Functor g, Functor h) => (EnvT e g ~> h) -> g ~> ReaderT e h Source #

rightAdjunct :: forall (g :: Type -> Type) (h :: Type -> Type). (Functor g, Functor h) => (g ~> ReaderT e h) -> EnvT e g ~> h Source #

Adjunction (StoreT s) (StateT s) Source # 
Instance details

Defined in FFunctor.Adjunction

Methods

unit :: forall (g :: Type -> Type). Functor g => g ~> StateT s (StoreT s g) Source #

counit :: forall (g :: Type -> Type). Functor g => StoreT s (StateT s g) ~> g Source #

leftAdjunct :: forall (g :: Type -> Type) (h :: Type -> Type). (Functor g, Functor h) => (StoreT s g ~> h) -> g ~> StateT s h Source #

rightAdjunct :: forall (g :: Type -> Type) (h :: Type -> Type). (Functor g, Functor h) => (g ~> StateT s h) -> StoreT s g ~> h Source #

Adjunction (TracedT m) (WriterT m) Source # 
Instance details

Defined in FFunctor.Adjunction

Methods

unit :: forall (g :: Type -> Type). Functor g => g ~> WriterT m (TracedT m g) Source #

counit :: forall (g :: Type -> Type). Functor g => TracedT m (WriterT m g) ~> g Source #

leftAdjunct :: forall (g :: Type -> Type) (h :: Type -> Type). (Functor g, Functor h) => (TracedT m g ~> h) -> g ~> WriterT m h Source #

rightAdjunct :: forall (g :: Type -> Type) (h :: Type -> Type). (Functor g, Functor h) => (g ~> WriterT m h) -> TracedT m g ~> h Source #

Functor f => Adjunction (Day f) (Curried f) Source # 
Instance details

Defined in FFunctor.Adjunction

Methods

unit :: forall (g :: Type -> Type). Functor g => g ~> Curried f (Day f g) Source #

counit :: forall (g :: Type -> Type). Functor g => Day f (Curried f g) ~> g Source #

leftAdjunct :: forall (g :: Type -> Type) (h :: Type -> Type). (Functor g, Functor h) => (Day f g ~> h) -> g ~> Curried f h Source #

rightAdjunct :: forall (g :: Type -> Type) (h :: Type -> Type). (Functor g, Functor h) => (g ~> Curried f h) -> Day f g ~> h Source #

Adjunction (IdentityT :: (Type -> Type) -> Type -> Type) (IdentityT :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in FFunctor.Adjunction

Methods

unit :: forall (g :: Type -> Type). Functor g => g ~> IdentityT (IdentityT g) Source #

counit :: forall (g :: Type -> Type). Functor g => IdentityT (IdentityT g) ~> g Source #

leftAdjunct :: forall (g :: Type -> Type) (h :: Type -> Type). (Functor g, Functor h) => (IdentityT g ~> h) -> g ~> IdentityT h Source #

rightAdjunct :: forall (g :: Type -> Type) (h :: Type -> Type). (Functor g, Functor h) => (g ~> IdentityT h) -> IdentityT g ~> h Source #

Functor f => Adjunction ((:*:) f) (Exp1 f) Source # 
Instance details

Defined in FFunctor.Adjunction

Methods

unit :: forall (g :: Type -> Type). Functor g => g ~> Exp1 f (f :*: g) Source #

counit :: forall (g :: Type -> Type). Functor g => (f :*: Exp1 f g) ~> g Source #

leftAdjunct :: forall (g :: Type -> Type) (h :: Type -> Type). (Functor g, Functor h) => ((f :*: g) ~> h) -> g ~> Exp1 f h Source #

rightAdjunct :: forall (g :: Type -> Type) (h :: Type -> Type). (Functor g, Functor h) => (g ~> Exp1 f h) -> (f :*: g) ~> h Source #

(Adjunction ff uu, Adjunction gg vv) => Adjunction (FCompose ff gg) (FCompose vv uu) Source # 
Instance details

Defined in FFunctor.Adjunction

Methods

unit :: forall (g :: Type -> Type). Functor g => g ~> FCompose vv uu (FCompose ff gg g) Source #

counit :: forall (g :: Type -> Type). Functor g => FCompose ff gg (FCompose vv uu g) ~> g Source #

leftAdjunct :: forall (g :: Type -> Type) (h :: Type -> Type). (Functor g, Functor h) => (FCompose ff gg g ~> h) -> g ~> FCompose vv uu h Source #

rightAdjunct :: forall (g :: Type -> Type) (h :: Type -> Type). (Functor g, Functor h) => (g ~> FCompose vv uu h) -> FCompose ff gg g ~> h Source #

Functor f => Adjunction (Lan f) (Precompose f) Source # 
Instance details

Defined in FFunctor.Adjunction

Methods

unit :: forall (g :: Type -> Type). Functor g => g ~> Precompose f (Lan f g) Source #

counit :: forall (g :: Type -> Type). Functor g => Lan f (Precompose f g) ~> g Source #

leftAdjunct :: forall (g :: Type -> Type) (h :: Type -> Type). (Functor g, Functor h) => (Lan f g ~> h) -> g ~> Precompose f h Source #

rightAdjunct :: forall (g :: Type -> Type) (h :: Type -> Type). (Functor g, Functor h) => (g ~> Precompose f h) -> Lan f g ~> h Source #

Functor f => Adjunction (Precompose f) (Ran f) Source # 
Instance details

Defined in FFunctor.Adjunction

Methods

unit :: forall (g :: Type -> Type). Functor g => g ~> Ran f (Precompose f g) Source #

counit :: forall (g :: Type -> Type). Functor g => Precompose f (Ran f g) ~> g Source #

leftAdjunct :: forall (g :: Type -> Type) (h :: Type -> Type). (Functor g, Functor h) => (Precompose f g ~> h) -> g ~> Ran f h Source #

rightAdjunct :: forall (g :: Type -> Type) (h :: Type -> Type). (Functor g, Functor h) => (g ~> Ran f h) -> Precompose f g ~> h Source #

Adjunction f u => Adjunction (Compose f :: (Type -> Type) -> Type -> Type) (Compose u :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in FFunctor.Adjunction

Methods

unit :: forall (g :: Type -> Type). Functor g => g ~> Compose u (Compose f g) Source #

counit :: forall (g :: Type -> Type). Functor g => Compose f (Compose u g) ~> g Source #

leftAdjunct :: forall (g :: Type -> Type) (h :: Type -> Type). (Functor g, Functor h) => (Compose f g ~> h) -> g ~> Compose u h Source #

rightAdjunct :: forall (g :: Type -> Type) (h :: Type -> Type). (Functor g, Functor h) => (g ~> Compose u h) -> Compose f g ~> h Source #

(Adjunction ff uu, Adjunction gg vv) => Adjunction (Sum ff gg) (Product uu vv) Source # 
Instance details

Defined in FFunctor.Adjunction

Methods

unit :: forall (g :: Type -> Type). Functor g => g ~> Product uu vv (Sum ff gg g) Source #

counit :: forall (g :: Type -> Type). Functor g => Sum ff gg (Product uu vv g) ~> g Source #

leftAdjunct :: forall (g :: Type -> Type) (h :: Type -> Type). (Functor g, Functor h) => (Sum ff gg g ~> h) -> g ~> Product uu vv h Source #

rightAdjunct :: forall (g :: Type -> Type) (h :: Type -> Type). (Functor g, Functor h) => (g ~> Product uu vv h) -> Sum ff gg g ~> h Source #