Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- class (Category source, Category target) => Contravariant source target t where
- (>-|-) :: source a b -> target (t b) (t a)
- (>$<) :: Contravariant source target t => source a b -> target (t b) (t a)
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 >-|-)
Instances
(Category m, Covariant m m t) => Contravariant m (Flip m) t Source # | |
Defined in Pandora.Pattern.Morphism.Flip | |
(Category m, Covariant m m t) => Contravariant (Flip m) m t Source # | |
Defined in Pandora.Pattern.Morphism.Flip | |
Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Predicate Source # | |
Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((<--) a) Source # | |
Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Proxy :: Type -> Type) Source # | |
Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Convergence r) Source # | |
Defined in Pandora.Paradigm.Primary.Functor.Convergence (>-|-) :: (a -> b) -> Convergence r b -> Convergence r a Source # | |
Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Flip Imprint a) Source # | |
Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Flip Environment a) Source # | |
Defined in Pandora.Paradigm.Inventory.Environment (>-|-) :: (a0 -> b) -> Flip Environment a b -> Flip Environment a a0 Source # | |
Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Constant a :: Type -> Type) Source # | |
Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Backwards t) Source # | |
Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Reverse t) 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 # | |
(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 # | |
Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Kan ('Left :: Type -> Wye Type) t u b) Source # | |
(>$<) :: Contravariant source target t => source a b -> target (t b) (t a) infixl 4 Source #