contravariant-0.4.4: 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

Instances

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 (Const a) 
Contravariant (Proxy *) 
Contravariant f => Contravariant (Reverse f) 
Contravariant f => Contravariant (Backwards f) 
Contravariant (Constant a) 
Contravariant (Op a) 
(Functor f, Contravariant g) => Contravariant (Compose f g) 
(Contravariant f, Contravariant g) => Contravariant (Product f g) 
(Contravariant f, Functor g) => Contravariant (ComposeCF f g) 
(Functor f, Contravariant g) => Contravariant (ComposeFC f g) 
Contravariant (Day f g) 

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.

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.

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