Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Pandora.Pattern.Functor.Contravariant
Synopsis
- class (Category source, Category target) => Contravariant source target t where
- (>-|-) :: source a b -> target (t b) (t a)
- (>-|-|-) :: (Contravariant source (Betwixt source target) u, Contravariant (Betwixt source target) target t) => source a b -> target (t (u a)) (t (u b))
- (>$<) :: Contravariant source target t => source a b -> target (t b) (t a)
- (>$$<) :: (Contravariant source target t, Contravariant source (Betwixt source target) u, Contravariant (Betwixt source target) target t) => source a b -> target (t (u a)) (t (u b))
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 >-|-)
Minimal complete definition
Methods
(>-|-) :: source a b -> target (t b) (t a) infixl 4 Source #
(>-|-|-) :: (Contravariant source (Betwixt source target) u, Contravariant (Betwixt source target) target t) => source a b -> target (t (u a)) (t (u b)) infixl 3 Source #
Instances
(Category m, Covariant m m t) => Contravariant m (Flip m) t Source # | |
(Category m, Covariant m m t) => Contravariant (Flip m) m t Source # | |
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 Methods (>-|-) :: (a -> b) -> Convergence r b -> Convergence r a Source # (>-|-|-) :: (Contravariant (->) (Betwixt (->) (->)) u, Contravariant (Betwixt (->) (->)) (->) (Convergence r)) => (a -> b) -> Convergence r (u a) -> Convergence r (u b) Source # | |
Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Flip Provision a) Source # | |
Defined in Pandora.Paradigm.Inventory.Some.Provision | |
Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Flip Imprint a) Source # | |
Defined in Pandora.Paradigm.Inventory.Some.Imprint | |
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 # | |
(Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, forall a. Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (p (t a)), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u, forall b. Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Flip p (u b))) => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((t >:.:> u) := p) Source # | |
Defined in Pandora.Paradigm.Schemes.T_U Methods (<-|-) :: (a -> b) -> ((t >:.:> u) := p) a -> ((t >:.:> u) := p) b Source # (<-|-|-) :: (Covariant (->) (Betwixt (->) (->)) u0, Covariant (Betwixt (->) (->)) (->) ((t >:.:> u) := p)) => (a -> b) -> ((t >:.:> u) := p) (u0 a) -> ((t >:.:> u) := p) (u0 b) Source # (<-|-|-|-) :: (Covariant (->) (Betwixt (->) (Betwixt (->) (->))) v, Covariant (Betwixt (->) (Betwixt (->) (->))) (Betwixt (Betwixt (->) (->)) (->)) u0, Covariant (Betwixt (Betwixt (->) (->)) (->)) (->) ((t >:.:> u) := p)) => (a -> b) -> ((t >:.:> u) := p) (u0 (v a)) -> ((t >:.:> u) := p) (u0 (v b)) Source # | |
Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Kan ('Left :: Type -> Wye Type) t u b) Source # | |
Defined in Pandora.Paradigm.Primary.Transformer.Kan |
(>$<) :: Contravariant source target t => source a b -> target (t b) (t a) infixl 4 Source #
(>$$<) :: (Contravariant source target t, Contravariant source (Betwixt source target) u, Contravariant (Betwixt source target) target t) => source a b -> target (t (u a)) (t (u b)) infixl 3 Source #