morphisms-functors-0.1.7: Functors, theirs compositions and transformations

Safe HaskellSafe
LanguageHaskell2010

Control.Functor.Covariant.Composition.Adjoint

Synopsis

Documentation

class (Covariant t, Covariant u) => Adjoint t u where Source #

When providing a new instance, you should ensure it satisfies the four laws:
* Left adjunction identity: phi counit ≡ identity
* Right adjunction identity: psi unit ≡ identity
* Left adjunction interchange: phi f ≡ comap f . eta
* Right adjunction interchange: psi f ≡ epsilon . comap f

Minimal complete definition

phi, psi

Methods

phi :: (t a -> b) -> a -> u b Source #

Left adjunction

psi :: (a -> u b) -> t a -> b Source #

Right adjunction

eta :: a -> (u :.: t) a Source #

epsilon :: (t :.: u) a -> a Source #

Instances
Adjoint Identity Identity Source # 
Instance details

Defined in Data.Functor.Identity

Methods

phi :: (Identity a -> b) -> a -> Identity b Source #

psi :: (a -> Identity b) -> Identity a -> b Source #

eta :: a -> (Identity :.: Identity) a Source #

epsilon :: (Identity :.: Identity) a -> a Source #

(Extractable t, Pointable t, Extractable u, Pointable u) => Adjoint (Yoneda t) (Yoneda u) Source # 
Instance details

Defined in Data.Functor.Yoneda

Methods

phi :: (Yoneda t a -> b) -> a -> Yoneda u b Source #

psi :: (a -> Yoneda u b) -> Yoneda t a -> b Source #

eta :: a -> (Yoneda u :.: Yoneda t) a Source #

epsilon :: (Yoneda t :.: Yoneda u) a -> a Source #

(Adjunctive t u, Adjunctive v w) => Adjoint (T Co Co t v) (T Co Co u w) Source # 
Instance details

Defined in Data.Functor.Composition.T

Methods

phi :: (T Co Co t v a -> b) -> a -> T Co Co u w b Source #

psi :: (a -> T Co Co u w b) -> T Co Co t v a -> b Source #

eta :: a -> (T Co Co u w :.: T Co Co t v) a Source #

epsilon :: (T Co Co t v :.: T Co Co u w) a -> a Source #

(Adjunctive t w, Adjunctive v x, Adjunctive u y) => Adjoint (TT Co Co Co t v u) (TT Co Co Co w x y) Source # 
Instance details

Defined in Data.Functor.Composition.TT

Methods

phi :: (TT Co Co Co t v u a -> b) -> a -> TT Co Co Co w x y b Source #

psi :: (a -> TT Co Co Co w x y b) -> TT Co Co Co t v u a -> b Source #

eta :: a -> (TT Co Co Co w x y :.: TT Co Co Co t v u) a Source #

epsilon :: (TT Co Co Co t v u :.: TT Co Co Co w x y) a -> a Source #

(Adjunctive t u, Adjunctive t' u', Adjunctive t'' u'', Adjunctive t''' u''') => Adjoint (TTT Co Co Co Co t t' t'' t''') (TTT Co Co Co Co u u' u'' u''') Source # 
Instance details

Defined in Data.Functor.Composition.TTT

Methods

phi :: (TTT Co Co Co Co t t' t'' t''' a -> b) -> a -> TTT Co Co Co Co u u' u'' u''' b Source #

psi :: (a -> TTT Co Co Co Co u u' u'' u''' b) -> TTT Co Co Co Co t t' t'' t''' a -> b Source #

eta :: a -> (TTT Co Co Co Co u u' u'' u''' :.: TTT Co Co Co Co t t' t'' t''') a Source #

epsilon :: (TTT Co Co Co Co t t' t'' t''' :.: TTT Co Co Co Co u u' u'' u''') a -> a Source #