Copyright | (C) 2007-2015 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
- phantom :: (Functor f, Contravariant f) => f a -> f b
- (>$<) :: 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.
phantom :: (Functor f, Contravariant f) => f a -> f b Source
If f
is both Functor
and Contravariant
then by the time you factor in the laws
of each of those classes, it can't actually use it's argument in any meaningful capacity.
This method is surprisingly useful. Where both instances exist and are lawful we have the following laws:
fmap
f ≡phantom
contramap
f ≡phantom
Operators
(>$<) :: Contravariant f => (a -> b) -> f b -> f a infixl 4 Source
This is an infix alias for contramap
(>$$<) :: Contravariant f => f b -> (a -> b) -> f a infixl 4 Source
This is an infix version of contramap
with the arguments flipped.
Predicates
Predicate | |
|
Comparisons
newtype Comparison a Source
Defines a total ordering on a type as per compare
This condition is not checked by the types. You must ensure that the supplied values are valid total orderings yourself.
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
This data type represents an equivalence relation.
Equivalence relations are expected to satisfy three laws:
Reflexivity:
getEquivalence
f a a = True
Symmetry:
getEquivalence
f a b =getEquivalence
f b a
Transitivity:
If
and getEquivalence
f a b
are both getEquivalence
f b cTrue
then so is getEquivalence
f a c
The types alone do not enforce these laws, so you'll have to check them yourself.
Equivalence | |
|
Contravariant Equivalence | Equivalence relations are |
Decidable Equivalence | |
Divisible Equivalence | |
Monoid (Equivalence a) | |
Semigroup (Equivalence a) | |
Typeable (* -> *) Equivalence |
defaultEquivalence :: Eq a => Equivalence a Source
comparisonEquivalence :: Comparison a -> Equivalence a Source
Dual arrows
Dual function arrows.