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

Pandora.Pattern.Functor.Contravariant

Synopsis

Documentation

class (Category source, Category target) => Contravariant source target t where Source #

When providing a new instance, you should ensure it satisfies:
* Identity morphism: (identity ->$<-) ≡ identity
* Interpreted of morphisms: (f ->$<-) . (g ->$<-) ≡ (g . f ->$<-)

Methods

(->$<-) :: source a b -> target (t b) (t a) infixl 4 Source #

Instances

Instances details
Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Predicate Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Predicate

Methods

(->$<-) :: (a -> b) -> Predicate b -> Predicate a Source #

Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((<--) a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Algebraic.Exponential

Methods

(->$<-) :: (a0 -> b) -> (a <-- b) -> (a <-- a0) Source #

Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Proxy :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Proxy

Methods

(->$<-) :: (a -> b) -> Proxy b -> Proxy a Source #

Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Convergence r) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Convergence

Methods

(->$<-) :: (a -> b) -> Convergence r b -> Convergence r a Source #

Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Flip Imprint a) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Imprint

Methods

(->$<-) :: (a0 -> b) -> Flip Imprint a b -> Flip Imprint a a0 Source #

Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Flip Environment a) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Environment

Methods

(->$<-) :: (a0 -> b) -> Flip Environment a b -> Flip Environment a a0 Source #

Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Constant a :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Constant

Methods

(->$<-) :: (a0 -> b) -> Constant a b -> Constant a a0 Source #

Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Backwards t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Backwards

Methods

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

Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Reverse t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Reverse

Methods

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

(Divariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) p, Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u) => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((t >:.:> u) := p) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.T_U

Methods

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

(forall i. Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (p i), Bivariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) p, Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u) => Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((t >:.:< u) := p) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.T_U

Methods

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

Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Kan ('Left :: Type -> Wye Type) t u b) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Kan

Methods

(->$<-) :: (a -> b0) -> Kan 'Left t u b b0 -> Kan 'Left t u b a Source #