| 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 |
Data.Functor.Contravariant
Description
Contravariant functors, sometimes referred to colloquially asCofunctor, even though the dual of aFunctor is just aFunctor. As withFunctor the definition ofContravariant for a given ADT is unambiguous.
Since: 4.12.0.0
classContravariant fwhereSource#
The class of contravariant functors.
Whereas in Haskell, one can think of aFunctor as containing or producing values, a contravariant functor is a functor that can be thought of asconsuming values.
As an example, consider the type of predicate functionsa -> Bool. One such predicate might benegative 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 valuesto integers. For instance, we can use thenegative 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 f (Predicate p) = Predicate (p . f) | `- First, map the input... `----- then apply the predicate.overdrawn :: Predicate Personoverdrawn = contramap personBankBalance negativeAny instance should be subject to the following laws:
contramap id = idcontramap f . contramap g = contramap (g . f)
Note, that the second law follows from the free theorem of the type ofcontramap and the first law, so you need only check that the former condition holds.
Minimal complete definition
phantom :: (Functor f,Contravariant f) => f a -> f bSource#
Iff is bothFunctor andContravariant 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:
fmapf ≡phantomcontramapf ≡phantom
(>$<) ::Contravariant f => (a -> b) -> f b -> f ainfixl 4Source#
This is an infix alias forcontramap.
(>$$<) ::Contravariant f => f b -> (a -> b) -> f ainfixl 4Source#
This is an infix version ofcontramap with the arguments flipped.
($<) ::Contravariant f => f b -> b -> f ainfixl 4Source#
This is>$ with its arguments flipped.
Constructors
| Predicate | |
Fields
| |
newtypeComparison aSource#
Defines a total ordering on a type as percompare.
This condition is not checked by the types. You must ensure that the supplied values are valid total orderings yourself.
Constructors
| Comparison | |
Fields
| |
| ContravariantComparisonSource# | A |
Instance detailsDefined inData.Functor.Contravariant Methods contramap :: (a -> b) ->Comparison b ->Comparison aSource# (>$) :: b ->Comparison b ->Comparison aSource# | |
| Semigroup (Comparison a)Source# | |
Instance detailsDefined inData.Functor.Contravariant Methods (<>) ::Comparison a ->Comparison a ->Comparison aSource# sconcat ::NonEmpty (Comparison a) ->Comparison aSource# stimes ::Integral b => b ->Comparison a ->Comparison aSource# | |
| Monoid (Comparison a)Source# | |
Instance detailsDefined inData.Functor.Contravariant Methods mappend ::Comparison a ->Comparison a ->Comparison aSource# mconcat :: [Comparison a] ->Comparison aSource# | |
defaultComparison ::Ord a =>Comparison aSource#
Compare usingcompare.
newtypeEquivalence aSource#
This data type represents an equivalence relation.
Equivalence relations are expected to satisfy three laws:
Reflexivity:
getEquivalence f a a = TrueSymmetry:
getEquivalencef a b =getEquivalencef 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.
Constructors
| Equivalence | |
Fields
| |
| ContravariantEquivalenceSource# | Equivalence relations are |
Instance detailsDefined inData.Functor.Contravariant Methods contramap :: (a -> b) ->Equivalence b ->Equivalence aSource# (>$) :: b ->Equivalence b ->Equivalence aSource# | |
| Semigroup (Equivalence a)Source# | |
Instance detailsDefined inData.Functor.Contravariant Methods (<>) ::Equivalence a ->Equivalence a ->Equivalence aSource# sconcat ::NonEmpty (Equivalence a) ->Equivalence aSource# stimes ::Integral b => b ->Equivalence a ->Equivalence aSource# | |
| Monoid (Equivalence a)Source# | |
Instance detailsDefined inData.Functor.Contravariant Methods mappend ::Equivalence a ->Equivalence a ->Equivalence aSource# mconcat :: [Equivalence a] ->Equivalence aSource# | |
defaultEquivalence ::Eq a =>Equivalence aSource#
Dual function arrows.
| Contravariant (Op a)Source# | |
| CategoryOpSource# | |
| Floating a =>Floating (Op a b)Source# | |
Instance detailsDefined inData.Functor.Contravariant | |
| Fractional a =>Fractional (Op a b)Source# | |
| Num a =>Num (Op a b)Source# | |
| Semigroup a =>Semigroup (Op a b)Source# | |
| Monoid a =>Monoid (Op a b)Source# | |
Produced byHaddock version 2.20.0