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

FComonad.Adjoint

Documentation

type Adjoint ff uu = AdjointT ff uu IdentityT Source #

adjoint :: (FFunctor ff, FFunctor uu, Functor x) => ff (uu x) ~> Adjoint ff uu x Source #

runAdjoint :: (FFunctor ff, FFunctor uu, Functor x) => Adjoint ff uu x ~> ff (uu x) Source #

newtype AdjointT ff uu ww g x Source #

Constructors

AdjointT 

Fields

Instances

Instances details
(Adjunction ff uu, FComonad ww) => FComonad (AdjointT ff uu ww) Source # 
Instance details

Defined in FComonad.Adjoint

Methods

fextract :: forall (g :: Type -> Type). Functor g => AdjointT ff uu ww g ~> g Source #

fextend :: forall (g :: Type -> Type) (h :: Type -> Type). (Functor g, Functor h) => (AdjointT ff uu ww g ~> h) -> AdjointT ff uu ww g ~> AdjointT ff uu ww h Source #

(FFunctor ff, FFunctor ww, FFunctor uu) => FFunctor (AdjointT ff uu ww) Source # 
Instance details

Defined in FComonad.Adjoint

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> AdjointT ff uu ww g x -> AdjointT ff uu ww h x Source #

(FStrong ff, FStrong ww, FStrong uu) => FStrong (AdjointT ff uu ww) Source # 
Instance details

Defined in FComonad.Adjoint

Methods

fstrength :: forall (g :: Type -> Type) (h :: Type -> Type). Functor g => Day (AdjointT ff uu ww g) h ~> AdjointT ff uu ww (Day g h) Source #

mapCurried :: forall (g :: Type -> Type) (h :: Type -> Type). (Functor g, Functor h) => Curried g h ~> Curried (AdjointT ff uu ww g) (AdjointT ff uu ww h) Source #

Functor (ff (ww (uu g))) => Functor (AdjointT ff uu ww g) Source # 
Instance details

Defined in FComonad.Adjoint

Methods

fmap :: (a -> b) -> AdjointT ff uu ww g a -> AdjointT ff uu ww g b #

(<$) :: a -> AdjointT ff uu ww g b -> AdjointT ff uu ww g a #

fffmap :: forall mm nn ff uu x. (FFunctor mm, FFunctor nn, FFunctor ff, FFunctor uu, Functor x) => (forall y. Functor y => mm y ~> nn y) -> AdjointT ff uu mm x ~> AdjointT ff uu nn x Source #

ungeneralize :: (FComonad ww, FFunctor ff, FFunctor uu, Functor x) => AdjointT ff uu ww x ~> Adjoint ff uu x Source #