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

Pandora.Paradigm.Primary.Transformer.Yoneda

Documentation

newtype Yoneda t a Source #

Constructors

Yoneda 

Fields

  • yoneda :: forall b. (a -> b) -> t b
     

Instances

Instances details
Liftable Yoneda Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Yoneda

Methods

lift :: forall (u :: Type -> Type). Covariant u => u ~> Yoneda u Source #

Covariant (Yoneda t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Yoneda

Methods

(<$>) :: (a -> b) -> Yoneda t a -> Yoneda t b Source #

comap :: (a -> b) -> Yoneda t a -> Yoneda t b Source #

(<$) :: a -> Yoneda t b -> Yoneda t a Source #

($>) :: Yoneda t a -> b -> Yoneda t b Source #

void :: Yoneda t a -> Yoneda t () Source #

loeb :: Yoneda t (a <:= Yoneda t) -> Yoneda t a Source #

(<&>) :: Yoneda t a -> (a -> b) -> Yoneda t b Source #

(<$$>) :: Covariant u => (a -> b) -> ((Yoneda t :. u) := a) -> (Yoneda t :. u) := b Source #

(<$$$>) :: (Covariant u, Covariant v) => (a -> b) -> ((Yoneda t :. (u :. v)) := a) -> (Yoneda t :. (u :. v)) := b Source #

(<$$$$>) :: (Covariant u, Covariant v, Covariant w) => (a -> b) -> ((Yoneda t :. (u :. (v :. w))) := a) -> (Yoneda t :. (u :. (v :. w))) := b Source #

(<&&>) :: Covariant u => ((Yoneda t :. u) := a) -> (a -> b) -> (Yoneda t :. u) := b Source #

(<&&&>) :: (Covariant u, Covariant v) => ((Yoneda t :. (u :. v)) := a) -> (a -> b) -> (Yoneda t :. (u :. v)) := b Source #

(<&&&&>) :: (Covariant u, Covariant v, Covariant w) => ((Yoneda t :. (u :. (v :. w))) := a) -> (a -> b) -> (Yoneda t :. (u :. (v :. w))) := b Source #

(.#..) :: (Yoneda t ~ v a, Category v) => v c d -> ((v a :. v b) := c) -> (v a :. v b) := d Source #

(.#...) :: (Yoneda t ~ v a, Yoneda t ~ v b, Category v, Covariant (v a), Covariant (v b)) => v d e -> ((v a :. (v b :. v c)) := d) -> (v a :. (v b :. v c)) := e Source #

(.#....) :: (Yoneda t ~ v a, Yoneda t ~ v b, Yoneda t ~ v c, Category v, Covariant (v a), Covariant (v b), Covariant (v c)) => v e f -> ((v a :. (v b :. (v c :. v d))) := e) -> (v a :. (v b :. (v c :. v d))) := f Source #

(<$$) :: Covariant u => b -> ((Yoneda t :. u) := a) -> (Yoneda t :. u) := b Source #

(<$$$) :: (Covariant u, Covariant v) => b -> ((Yoneda t :. (u :. v)) := a) -> (Yoneda t :. (u :. v)) := b Source #

(<$$$$) :: (Covariant u, Covariant v, Covariant w) => b -> ((Yoneda t :. (u :. (v :. w))) := a) -> (Yoneda t :. (u :. (v :. w))) := b Source #

($$>) :: Covariant u => ((Yoneda t :. u) := a) -> b -> (Yoneda t :. u) := b Source #

($$$>) :: (Covariant u, Covariant v) => ((Yoneda t :. (u :. v)) := a) -> b -> (Yoneda t :. (u :. v)) := b Source #

($$$$>) :: (Covariant u, Covariant v, Covariant w) => ((Yoneda t :. (u :. (v :. w))) := a) -> b -> (Yoneda t :. (u :. (v :. w))) := b Source #

Applicative t => Applicative (Yoneda t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Yoneda

Methods

(<*>) :: Yoneda t (a -> b) -> Yoneda t a -> Yoneda t b Source #

apply :: Yoneda t (a -> b) -> Yoneda t a -> Yoneda t b Source #

(*>) :: Yoneda t a -> Yoneda t b -> Yoneda t b Source #

(<*) :: Yoneda t a -> Yoneda t b -> Yoneda t a Source #

forever :: Yoneda t a -> Yoneda t b Source #

(<%>) :: Yoneda t a -> Yoneda t (a -> b) -> Yoneda t b Source #

(<**>) :: Applicative u => ((Yoneda t :. u) := (a -> b)) -> ((Yoneda t :. u) := a) -> (Yoneda t :. u) := b Source #

(<***>) :: (Applicative u, Applicative v) => ((Yoneda t :. (u :. v)) := (a -> b)) -> ((Yoneda t :. (u :. v)) := a) -> (Yoneda t :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => ((Yoneda t :. (u :. (v :. w))) := (a -> b)) -> ((Yoneda t :. (u :. (v :. w))) := a) -> (Yoneda t :. (u :. (v :. w))) := b Source #

Alternative t => Alternative (Yoneda t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Yoneda

Methods

(<+>) :: Yoneda t a -> Yoneda t a -> Yoneda t a Source #

alter :: Yoneda t a -> Yoneda t a -> Yoneda t a Source #

Avoidable t => Avoidable (Yoneda t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Yoneda

Methods

empty :: Yoneda t a Source #

Extractable t => Extractable (Yoneda t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Yoneda

Methods

extract :: a <:= Yoneda t Source #

Pointable t => Pointable (Yoneda t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Yoneda

Methods

point :: a :=> Yoneda t Source #

pass :: Yoneda t () Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Yoneda

Methods

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

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

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 #

(-|$) :: Covariant v => v a -> (Yoneda t a -> b) -> v (Yoneda u b) Source #

($|-) :: Covariant v => v (Yoneda t a) -> (a -> Yoneda u b) -> v b Source #

($$|-) :: (Covariant v, Covariant w) => ((v :. (w :. Yoneda t)) := a) -> (a -> Yoneda u b) -> (v :. w) := b Source #

($$$|-) :: (Covariant v, Covariant w, Covariant x) => ((v :. (w :. (x :. Yoneda t))) := a) -> (a -> Yoneda u b) -> (v :. (w :. x)) := b Source #

($$$$|-) :: (Covariant v, Covariant w, Covariant x, Covariant y) => ((v :. (w :. (x :. (y :. Yoneda t)))) := a) -> (a -> Yoneda u b) -> (v :. (w :. (x :. y))) := b Source #