Copyright | (C) 2007-2014 Edward Kmett |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell98 |
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.
- class Contravariant f where
- (>$<) :: Contravariant f => (a -> b) -> f b -> f a
- (>$$<) :: Contravariant f => f b -> (a -> b) -> f a
- newtype Predicate a = Predicate {
- getPredicate :: a -> Bool
- newtype Comparison a = Comparison {
- getComparison :: a -> a -> Ordering
- defaultComparison :: Ord a => Comparison a
- newtype Equivalence a = Equivalence {
- getEquivalence :: a -> a -> Bool
- defaultEquivalence :: Eq a => Equivalence a
- comparisonEquivalence :: Comparison a -> Equivalence a
- newtype Op a b = Op {
- getOp :: b -> a
Contravariant Functors
class Contravariant f where Source
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.
Operators
(>$<) :: Contravariant f => (a -> b) -> f b -> f a infixl 4 Source
(>$$<) :: Contravariant f => f b -> (a -> b) -> f a infixl 4 Source
Predicates
Predicate | |
|
Comparisons
newtype Comparison a Source
Defines a total ordering on a type as per compare
Comparison | |
|
Contravariant Comparison | A |
Decidable Comparison | |
Divisible Comparison | |
Monoid (Comparison a) | |
Semigroup (Comparison a) | |
Typeable (* -> *) Comparison |
defaultComparison :: Ord a => Comparison a Source
Compare using compare
Equivalence Relations
newtype Equivalence a Source
Define an equivalence relation
Equivalence | |
|
Contravariant Equivalence | Equivalence relations are |
Decidable Equivalence | |
Divisible Equivalence | |
Monoid (Equivalence a) | |
Semigroup (Equivalence a) | |
Typeable (* -> *) Equivalence |
defaultEquivalence :: Eq a => Equivalence a Source
Check for equivalence with ==
comparisonEquivalence :: Comparison a -> Equivalence a Source
Dual arrows
Dual function arrows.