pandora-0.4.4: A box of patterns and paradigms
Safe HaskellSafe-Inferred
LanguageHaskell2010

Pandora.Pattern.Functor.Adjoint

Synopsis

Documentation

type (-|) = Adjoint infixl 3 Source #

class (Covariant_ t target source, Covariant_ u source target) => Adjoint t u source target where Source #

When providing a new instance, you should ensure it satisfies:
* Left adjunction identity: phi cozero ≡ identity
* Right adjunction identity: psi zero ≡ identity
* Left adjunction interchange: phi f ≡ comap f . eta
* Right adjunction interchange: psi f ≡ epsilon . comap f

Methods

(-|) :: source (t a) b -> target a (u b) infixl 3 Source #

(|-) :: target a (u b) -> source (t a) b infixl 3 Source #

Instances

Instances details
Adjoint Identity Identity ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

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

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Yoneda

Methods

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

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

Adjoint (Store s) (State s) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory

Methods

(-|) :: (Store s a -> b) -> a -> State s b Source #

(|-) :: (a -> State s b) -> Store s a -> b Source #

Adjoint (Equipment e) (Environment e) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory

Methods

(-|) :: (Equipment e a -> b) -> a -> Environment e b Source #

(|-) :: (a -> Environment e b) -> Equipment e a -> b Source #

Adjoint (Accumulator e) (Imprint e) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory

Methods

(-|) :: (Accumulator e a -> b) -> a -> Imprint e b Source #

(|-) :: (a -> Imprint e b) -> Accumulator e a -> b Source #

Adjoint ((:*:) s) ((->) s :: Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic

Methods

(-|) :: ((s :*: a) -> b) -> a -> (s -> b) Source #

(|-) :: (a -> (s -> b)) -> (s :*: a) -> b Source #

Adjoint (Flip (:*:) s) ((->) s :: Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary

Methods

(-|) :: (Flip (:*:) s a -> b) -> a -> (s -> b) Source #

(|-) :: (a -> (s -> b)) -> Flip (:*:) s a -> b Source #

(Covariant (t <.:> v), Covariant (w <:.> u), Adjoint v u ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Adjoint t w ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Adjoint (t <.:> v) (w <:.> u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes

Methods

(-|) :: ((t <.:> v) a -> b) -> a -> (w <:.> u) b Source #

(|-) :: (a -> (w <:.> u) b) -> (t <.:> v) a -> b Source #

(Covariant (t <.:> v), Covariant (w <.:> u), Adjoint t u ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Adjoint v w ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Adjoint (t <.:> v) (w <.:> u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes

Methods

(-|) :: ((t <.:> v) a -> b) -> a -> (w <.:> u) b Source #

(|-) :: (a -> (w <.:> u) b) -> (t <.:> v) a -> b Source #

(Covariant (v <:.> t), Covariant (w <.:> u), Adjoint t u ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Adjoint v w ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Adjoint (v <:.> t) (w <.:> u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes

Methods

(-|) :: ((v <:.> t) a -> b) -> a -> (w <.:> u) b Source #

(|-) :: (a -> (w <.:> u) b) -> (v <:.> t) a -> b Source #

(Covariant (v <:.> t), Covariant (u <:.> w), Adjoint t u ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Adjoint v w ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Adjoint (v <:.> t) (u <:.> w) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes

Methods

(-|) :: ((v <:.> t) a -> b) -> a -> (u <:.> w) b Source #

(|-) :: (a -> (u <:.> w) b) -> (v <:.> t) a -> b Source #

(Covariant ((t <:<.>:> u) t'), Covariant ((v <:<.>:> w) v'), Adjoint t w ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Adjoint t' v' ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Adjoint t v ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Adjoint u v ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Adjoint v' t' ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Adjoint ((t <:<.>:> u) t') ((v <:<.>:> w) v') ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes

Methods

(-|) :: ((t <:<.>:> u) t' a -> b) -> a -> (v <:<.>:> w) v' b Source #

(|-) :: (a -> (v <:<.>:> w) v' b) -> (t <:<.>:> u) t' a -> b Source #