contravariant-1.1: Contravariant functors

Portabilityportable
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellSafe

Data.Functor.Contravariant

Contents

Description

Contravariant functors, sometimes referred to colloquially as Cofunctor, even though the dual of a Functor is just a Functor. As with Functor the definition of Contravariant for a given ADT is unambiguous.

Synopsis

Contravariant Functors

class Contravariant f whereSource

Any instance should be subject to the following laws:

 contramap id = id
 contramap f . contramap g = contramap (g . f)

Note, that the second law follows from the free theorem of the type of contramap and the first law, so you need only check that the former condition holds.

Methods

contramap :: (a -> b) -> f b -> f aSource

(>$) :: b -> f b -> f aSource

Replace all locations in the output with the same value. The default definition is contramap . const, but this may be overridden with a more efficient version.

Instances

Contravariant V1 
Contravariant U1 
Contravariant Equivalence

Equivalence relations are Contravariant, because you can apply the contramapped function to each input to the equivalence relation.

Contravariant Comparison

A Comparison is a Contravariant Functor, because contramap can apply its function argument to each input to each input to the comparison function.

Contravariant Predicate

A Predicate is a Contravariant Functor, because contramap can apply its function argument to the input of the predicate.

Contravariant f => Contravariant (Rec1 f) 
Contravariant (Const a) 
Contravariant (Proxy *) 
Contravariant f => Contravariant (Reverse f) 
Contravariant f => Contravariant (Backwards f) 
Contravariant (Constant a) 
Contravariant (Op a) 
Contravariant (K1 i c) 
(Contravariant f, Contravariant g) => Contravariant (:+: f g) 
(Contravariant f, Contravariant g) => Contravariant (:*: f g) 
(Functor f, Contravariant g) => Contravariant (:.: f g) 
(Contravariant f, Contravariant g) => Contravariant (Sum f g) 
(Contravariant f, Contravariant g) => Contravariant (Product f g) 
(Functor f, Contravariant g) => Contravariant (Compose f g) 
(Contravariant f, Functor g) => Contravariant (ComposeCF f g) 
(Functor f, Contravariant g) => Contravariant (ComposeFC f g) 
Contravariant f => Contravariant (M1 i c f) 

Operators

(>$<) :: Contravariant f => (a -> b) -> f b -> f aSource

(>$$<) :: Contravariant f => f b -> (a -> b) -> f aSource

Predicates

newtype Predicate a Source

Constructors

Predicate 

Fields

getPredicate :: a -> Bool
 

Instances

Typeable1 Predicate 
Contravariant Predicate

A Predicate is a Contravariant Functor, because contramap can apply its function argument to the input of the predicate.

Comparisons

newtype Comparison a Source

Defines a total ordering on a type as per compare

Constructors

Comparison 

Fields

getComparison :: a -> a -> Ordering
 

Instances

Typeable1 Comparison 
Contravariant Comparison

A Comparison is a Contravariant Functor, because contramap can apply its function argument to each input to each input to the comparison function.

Monoid (Comparison a) 
Semigroup (Comparison a) 

Equivalence Relations

newtype Equivalence a Source

Define an equivalence relation

Constructors

Equivalence 

Fields

getEquivalence :: a -> a -> Bool
 

Instances

Typeable1 Equivalence 
Contravariant Equivalence

Equivalence relations are Contravariant, because you can apply the contramapped function to each input to the equivalence relation.

Monoid (Equivalence a) 
Semigroup (Equivalence a) 

defaultEquivalence :: Eq a => Equivalence aSource

Check for equivalence with ==

Dual arrows

newtype Op a b Source

Dual function arrows.

Constructors

Op 

Fields

getOp :: b -> a
 

Instances

Typeable2 Op 
Category Op 
Contravariant (Op a) 
Floating a => Floating (Op a b) 
Fractional a => Fractional (Op a b) 
Num a => Num (Op a b) 
Monoid a => Monoid (Op a b) 
Semigroup a => Semigroup (Op a b)