W3cubDocs

/Haskell 8

Data.Functor.Contravariant

Copyright (C) 2007-2015 Edward Kmett
License BSD-style (see the file LICENSE)
Maintainer [email protected]
Stability provisional
Portability portable
Safe Haskell Trustworthy
Language Haskell2010

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.

Since: base-4.12.0.0

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

Identity
contramap id = id
Composition
contramap (g . f) = contramap f . contramap g

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.

Minimal complete definition

contramap

Methods

contramap :: (a -> b) -> f b -> f a Source

(>$) :: b -> f b -> f a infixl 4 Source

Replace all locations in the output with the same value. The default definition is contramap . const, but this may be overridden with a more efficient version.

Instances
Instances details
Contravariant Equivalence

Equivalence relations are Contravariant, because you can apply the contramapped function to each input to the equivalence relation.

Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Equivalence b -> Equivalence a Source

(>$) :: b -> Equivalence b -> Equivalence a Source

Contravariant Comparison

A Comparison is a Contravariant Functor, because contramap can apply its function argument to each input of the comparison function.

Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Comparison b -> Comparison a Source

(>$) :: b -> Comparison b -> Comparison a Source

Contravariant Predicate

A Predicate is a Contravariant Functor, because contramap can apply its function argument to the input of the predicate.

Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Predicate b -> Predicate a Source

(>$) :: b -> Predicate b -> Predicate a Source

Contravariant (V1 :: Type -> Type)
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> V1 b -> V1 a Source

(>$) :: b -> V1 b -> V1 a Source

Contravariant (U1 :: Type -> Type)
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> U1 b -> U1 a Source

(>$) :: b -> U1 b -> U1 a Source

Contravariant (Proxy :: Type -> Type)
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Proxy b -> Proxy a Source

(>$) :: b -> Proxy b -> Proxy a Source

Contravariant (Op a)
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a0 -> b) -> Op a b -> Op a a0 Source

(>$) :: b -> Op a b -> Op a a0 Source

Contravariant f => Contravariant (Rec1 f)
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Rec1 f b -> Rec1 f a Source

(>$) :: b -> Rec1 f b -> Rec1 f a Source

Contravariant f => Contravariant (Alt f)
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Alt f b -> Alt f a Source

(>$) :: b -> Alt f b -> Alt f a Source

Contravariant (Const a :: Type -> Type)
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a0 -> b) -> Const a b -> Const a a0 Source

(>$) :: b -> Const a b -> Const a a0 Source

Contravariant (K1 i c :: Type -> Type)
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> K1 i c b -> K1 i c a Source

(>$) :: b -> K1 i c b -> K1 i c a Source

(Contravariant f, Contravariant g) => Contravariant (f :+: g)
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> (f :+: g) b -> (f :+: g) a Source

(>$) :: b -> (f :+: g) b -> (f :+: g) a Source

(Contravariant f, Contravariant g) => Contravariant (f :*: g)
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> (f :*: g) b -> (f :*: g) a Source

(>$) :: b -> (f :*: g) b -> (f :*: g) a Source

(Contravariant f, Contravariant g) => Contravariant (Sum f g)
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Sum f g b -> Sum f g a Source

(>$) :: b -> Sum f g b -> Sum f g a Source

(Contravariant f, Contravariant g) => Contravariant (Product f g)
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Product f g b -> Product f g a Source

(>$) :: b -> Product f g b -> Product f g a Source

Contravariant f => Contravariant (M1 i c f)
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> M1 i c f b -> M1 i c f a Source

(>$) :: b -> M1 i c f b -> M1 i c f a Source

(Functor f, Contravariant g) => Contravariant (f :.: g)
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> (f :.: g) b -> (f :.: g) a Source

(>$) :: b -> (f :.: g) b -> (f :.: g) a Source

(Functor f, Contravariant g) => Contravariant (Compose f g)
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Compose f g b -> Compose f g a Source

(>$) :: b -> Compose f g b -> Compose f g a Source

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

newtype Predicate a Source

Constructors

Predicate

Fields

Instances
Instances details
Contravariant Predicate

A Predicate is a Contravariant Functor, because contramap can apply its function argument to the input of the predicate.

Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Predicate b -> Predicate a Source

(>$) :: b -> Predicate b -> Predicate a Source

Semigroup (Predicate a)
Instance details

Defined in Data.Functor.Contravariant

Monoid (Predicate a)
Instance details

Defined in Data.Functor.Contravariant

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.

Constructors

Comparison

Fields

Instances
Instances details
Contravariant Comparison

A Comparison is a Contravariant Functor, because contramap can apply its function argument to each input of the comparison function.

Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Comparison b -> Comparison a Source

(>$) :: b -> Comparison b -> Comparison a Source

Semigroup (Comparison a)
Instance details

Defined in Data.Functor.Contravariant

Monoid (Comparison a)
Instance details

Defined in Data.Functor.Contravariant

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 getEquivalence f a b and getEquivalence f b c are both True 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

Instances
Instances details
Contravariant Equivalence

Equivalence relations are Contravariant, because you can apply the contramapped function to each input to the equivalence relation.

Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Equivalence b -> Equivalence a Source

(>$) :: b -> Equivalence b -> Equivalence a Source

Semigroup (Equivalence a)
Instance details

Defined in Data.Functor.Contravariant

Monoid (Equivalence a)
Instance details

Defined in Data.Functor.Contravariant

defaultEquivalence :: Eq a => Equivalence a Source

Check for equivalence with ==.

Note: The instances for Double and Float violate reflexivity for NaN.

comparisonEquivalence :: Comparison a -> Equivalence a Source

Dual arrows

newtype Op a b Source

Dual function arrows.

Constructors

Op

Fields

Instances
Instances details
Contravariant (Op a)
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a0 -> b) -> Op a b -> Op a a0 Source

(>$) :: b -> Op a b -> Op a a0 Source

Category Op
Instance details

Defined in Data.Functor.Contravariant

Methods

id :: forall (a :: k). Op a a Source

(.) :: forall (b :: k) (c :: k) (a :: k). Op b c -> Op a b -> Op a c Source

Floating a => Floating (Op a b)
Instance details

Defined in Data.Functor.Contravariant

Methods

pi :: Op a b Source

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

log1pexp :: Op a b -> Op a b Source

log1mexp :: Op a b -> Op a b Source

Fractional a => Fractional (Op a b)
Instance details

Defined in Data.Functor.Contravariant

Methods

(/) :: Op a b -> Op a b -> Op a b Source

recip :: Op a b -> Op a b Source

fromRational :: Rational -> Op a b Source

Num a => Num (Op a b)
Instance details

Defined in Data.Functor.Contravariant

Methods

(+) :: Op a b -> Op a b -> Op a b Source

(-) :: Op a b -> Op a b -> Op a b Source

(*) :: Op a b -> Op a b -> Op a b Source

negate :: Op a b -> Op a b Source

abs :: Op a b -> Op a b Source

signum :: Op a b -> Op a b Source

fromInteger :: Integer -> Op a b Source

Semigroup a => Semigroup (Op a b)
Instance details

Defined in Data.Functor.Contravariant

Methods

(<>) :: Op a b -> Op a b -> Op a b Source

sconcat :: NonEmpty (Op a b) -> Op a b Source

stimes :: Integral b0 => b0 -> Op a b -> Op a b Source

Monoid a => Monoid (Op a b)
Instance details

Defined in Data.Functor.Contravariant

Methods

mempty :: Op a b Source

mappend :: Op a b -> Op a b -> Op a b Source

mconcat :: [Op a b] -> Op a b Source

© The University of Glasgow and others
Licensed under a BSD-style license (see top of the page).
https://downloads.haskell.org/~ghc/8.8.3/docs/html/libraries/base-4.13.0.0/Data-Functor-Contravariant.html