Copyright | (C) 2007-2015 Edward Kmett |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | libraries@haskell.org |
Stability | provisional |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
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.
Since: base-4.12.0.0
Synopsis
- 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
- ($<) :: Contravariant f => f b -> 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 #
The class of contravariant functors.
Whereas in Haskell, one can think of a Functor
as containing or producing
values, a contravariant functor is a functor that can be thought of as
consuming values.
As an example, consider the type of predicate functions a -> Bool
. One
such predicate might be negative x = x < 0
, which
classifies integers as to whether they are negative. However, given this
predicate, we can re-use it in other situations, providing we have a way to
map values to integers. For instance, we can use the negative
predicate
on a person's bank balance to work out if they are currently overdrawn:
newtype Predicate a = Predicate { getPredicate :: a -> Bool } instance Contravariant Predicate where contramap :: (a' -> a) -> (Predicate a -> Predicate a') contramap f (Predicate p) = Predicate (p . f) | `- First, map the input... `----- then apply the predicate. overdrawn :: Predicate Person overdrawn = contramap personBankBalance negative
Any instance should be subject to the following laws:
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.
Instances
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 its 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.
($<) :: Contravariant f => f b -> b -> f a infixl 4 Source #
This is >$
with its arguments flipped.
Predicates
Predicate | |
|
Instances
Contravariant Predicate Source # | A Without newtypes contramap :: (a' -> a) -> (Predicate a -> Predicate a') contramap f (Predicate g) = Predicate (g . f) |
Monoid (Predicate a) Source # |
mempty :: Predicate a mempty = _ -> True |
Semigroup (Predicate a) Source # |
(<>) :: Predicate a -> Predicate a -> Predicate a Predicate pred <> Predicate pred' = Predicate a -> pred a && pred' a |
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 | |
|
Instances
Contravariant Comparison Source # | A |
Defined in Data.Functor.Contravariant contramap :: (a' -> a) -> Comparison a -> Comparison a' Source # (>$) :: b -> Comparison b -> Comparison a Source # | |
Monoid (Comparison a) Source # |
mempty :: Comparison a mempty = Comparison _ _ -> EQ |
Defined in Data.Functor.Contravariant mempty :: Comparison a Source # mappend :: Comparison a -> Comparison a -> Comparison a Source # mconcat :: [Comparison a] -> Comparison a Source # | |
Semigroup (Comparison a) Source # |
(<>) :: Comparison a -> Comparison a -> Comparison a Comparison cmp <> Comparison cmp' = Comparison a a' -> cmp a a' <> cmp a a' |
Defined in Data.Functor.Contravariant (<>) :: Comparison a -> Comparison a -> Comparison a Source # sconcat :: NonEmpty (Comparison a) -> Comparison a Source # stimes :: Integral b => b -> Comparison a -> Comparison a Source # |
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
andgetEquivalence
f a b
are bothgetEquivalence
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 | |
|
Instances
Contravariant Equivalence Source # | Equivalence relations are |
Defined in Data.Functor.Contravariant contramap :: (a' -> a) -> Equivalence a -> Equivalence a' Source # (>$) :: b -> Equivalence b -> Equivalence a Source # | |
Monoid (Equivalence a) Source # |
mempty :: Equivalence a mempty = Equivalence _ _ -> True |
Defined in Data.Functor.Contravariant mempty :: Equivalence a Source # mappend :: Equivalence a -> Equivalence a -> Equivalence a Source # mconcat :: [Equivalence a] -> Equivalence a Source # | |
Semigroup (Equivalence a) Source # |
(<>) :: Equivalence a -> Equivalence a -> Equivalence a Equivalence equiv <> Equivalence equiv' = Equivalence a b -> equiv a b && equiv' a b |
Defined in Data.Functor.Contravariant (<>) :: Equivalence a -> Equivalence a -> Equivalence a Source # sconcat :: NonEmpty (Equivalence a) -> Equivalence a Source # stimes :: Integral b => b -> Equivalence a -> Equivalence a Source # |
defaultEquivalence :: Eq a => Equivalence a Source #
comparisonEquivalence :: Comparison a -> Equivalence a Source #
Dual arrows
Dual function arrows.
Instances
Category Op Source # | |
Contravariant (Op a) Source # | |
Monoid a => Monoid (Op a b) Source # |
mempty :: Op a b mempty = Op _ -> mempty |
Semigroup a => Semigroup (Op a b) Source # |
(<>) :: Op a b -> Op a b -> Op a b Op f <> Op g = Op a -> f a <> g a |
Floating a => Floating (Op a b) Source # | |
Defined in Data.Functor.Contravariant exp :: Op a b -> Op a b Source # log :: Op a b -> Op a b Source # sqrt :: Op a b -> Op a b Source # (**) :: Op a b -> Op a b -> Op a b Source # logBase :: Op a b -> Op a b -> Op a b Source # sin :: Op a b -> Op a b Source # cos :: Op a b -> Op a b Source # tan :: Op a b -> Op a b Source # asin :: Op a b -> Op a b Source # acos :: Op a b -> Op a b Source # atan :: Op a b -> Op a b Source # sinh :: Op a b -> Op a b Source # cosh :: Op a b -> Op a b Source # tanh :: Op a b -> Op a b Source # asinh :: Op a b -> Op a b Source # acosh :: Op a b -> Op a b Source # atanh :: Op a b -> Op a b Source # log1p :: Op a b -> Op a b Source # expm1 :: Op a b -> Op a b Source # | |
Num a => Num (Op a b) Source # | |
Defined in Data.Functor.Contravariant | |
Fractional a => Fractional (Op a b) Source # | |