contravariant-1.4: Contravariant functors

Copyright(C) 2007-2015 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Data.Functor.Contravariant

Contents

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.

Synopsis

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.

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

Contravariant V1 Source 

Methods

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

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

Contravariant U1 Source 

Methods

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

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

Contravariant SettableStateVar Source 
Contravariant Equivalence Source

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

Methods

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

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

Contravariant Comparison Source

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

Methods

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

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

Contravariant Predicate Source

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

Methods

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

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

Contravariant f => Contravariant (Rec1 f) Source 

Methods

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

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

Contravariant (Const a) Source 

Methods

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

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

Contravariant (Proxy *) Source 

Methods

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

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

Contravariant f => Contravariant (Reverse f) Source 

Methods

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

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

Contravariant f => Contravariant (Backwards f) Source 

Methods

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

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

Contravariant m => Contravariant (MaybeT m) Source 

Methods

contramap :: (a -> b) -> MaybeT m b -> MaybeT m a Source

(>$) :: b -> MaybeT m b -> MaybeT m a Source

Contravariant m => Contravariant (ListT m) Source 

Methods

contramap :: (a -> b) -> ListT m b -> ListT m a Source

(>$) :: b -> ListT m b -> ListT m a Source

Contravariant f => Contravariant (IdentityT f) Source 

Methods

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

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

Contravariant (Constant a) Source 

Methods

contramap :: (b -> c) -> Constant a c -> Constant a b Source

(>$) :: b -> Constant a b -> Constant a c Source

Contravariant (Op a) Source 

Methods

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

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

Contravariant (K1 i c) Source 

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) Source 

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) Source 

Methods

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

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

(Functor f, Contravariant g) => Contravariant ((:.:) f g) Source 

Methods

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

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

Contravariant f => Contravariant (Alt * f) Source 

Methods

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

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

(Contravariant f, Contravariant g) => Contravariant (Sum f g) Source 

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) Source 

Methods

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

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

(Functor f, Contravariant g) => Contravariant (Compose f g) Source 

Methods

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

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

Contravariant m => Contravariant (WriterT w m) Source 

Methods

contramap :: (a -> b) -> WriterT w m b -> WriterT w m a Source

(>$) :: b -> WriterT w m b -> WriterT w m a Source

Contravariant m => Contravariant (WriterT w m) Source 

Methods

contramap :: (a -> b) -> WriterT w m b -> WriterT w m a Source

(>$) :: b -> WriterT w m b -> WriterT w m a Source

Contravariant m => Contravariant (ErrorT e m) Source 

Methods

contramap :: (a -> b) -> ErrorT e m b -> ErrorT e m a Source

(>$) :: b -> ErrorT e m b -> ErrorT e m a Source

Contravariant m => Contravariant (ExceptT e m) Source 

Methods

contramap :: (a -> b) -> ExceptT e m b -> ExceptT e m a Source

(>$) :: b -> ExceptT e m b -> ExceptT e m a Source

Contravariant m => Contravariant (StateT s m) Source 

Methods

contramap :: (a -> b) -> StateT s m b -> StateT s m a Source

(>$) :: b -> StateT s m b -> StateT s m a Source

Contravariant m => Contravariant (StateT s m) Source 

Methods

contramap :: (a -> b) -> StateT s m b -> StateT s m a Source

(>$) :: b -> StateT s m b -> StateT s m a Source

Contravariant m => Contravariant (ReaderT r m) Source 

Methods

contramap :: (a -> b) -> ReaderT r m b -> ReaderT r m a Source

(>$) :: b -> ReaderT r m b -> ReaderT r m a Source

(Contravariant f, Functor g) => Contravariant (ComposeCF f g) Source 

Methods

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

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

(Functor f, Contravariant g) => Contravariant (ComposeFC f g) Source 

Methods

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

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

Contravariant f => Contravariant (M1 i c f) Source 

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

Contravariant m => Contravariant (RWST r w s m) Source 

Methods

contramap :: (a -> b) -> RWST r w s m b -> RWST r w s m a Source

(>$) :: b -> RWST r w s m b -> RWST r w s m a Source

Contravariant m => Contravariant (RWST r w s m) Source 

Methods

contramap :: (a -> b) -> RWST r w s m b -> RWST r w s m a Source

(>$) :: b -> RWST r w s m b -> RWST r w s m 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 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.

($<) :: 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

Contravariant Predicate Source

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

Methods

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

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

Decidable Predicate Source 

Methods

lose :: (a -> Void) -> Predicate a Source

choose :: (a -> Either b c) -> Predicate b -> Predicate c -> Predicate a Source

Divisible Predicate Source 

Methods

divide :: (a -> (b, c)) -> Predicate b -> Predicate c -> Predicate a Source

conquer :: Predicate a Source

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

Contravariant Comparison Source

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

Methods

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

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

Decidable Comparison Source 

Methods

lose :: (a -> Void) -> Comparison a Source

choose :: (a -> Either b c) -> Comparison b -> Comparison c -> Comparison a Source

Divisible Comparison Source 

Methods

divide :: (a -> (b, c)) -> Comparison b -> Comparison c -> Comparison a Source

conquer :: Comparison a Source

Monoid (Comparison a) Source 
Semigroup (Comparison a) Source 

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

Contravariant Equivalence Source

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

Methods

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

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

Decidable Equivalence Source 

Methods

lose :: (a -> Void) -> Equivalence a Source

choose :: (a -> Either b c) -> Equivalence b -> Equivalence c -> Equivalence a Source

Divisible Equivalence Source 

Methods

divide :: (a -> (b, c)) -> Equivalence b -> Equivalence c -> Equivalence a Source

conquer :: Equivalence a Source

Monoid (Equivalence a) Source 
Semigroup (Equivalence a) Source 

defaultEquivalence :: Eq a => Equivalence a Source

Check for equivalence with ==

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

Dual arrows

newtype Op a b Source

Dual function arrows.

Constructors

Op 

Fields

Instances

Category * Op Source 

Methods

id :: Op a a

(.) :: Op b c -> Op a b -> Op a c

Contravariant (Op a) Source 

Methods

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

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

Monoid r => Decidable (Op r) Source 

Methods

lose :: (a -> Void) -> Op r a Source

choose :: (a -> Either b c) -> Op r b -> Op r c -> Op r a Source

Monoid r => Divisible (Op r) Source 

Methods

divide :: (a -> (b, c)) -> Op r b -> Op r c -> Op r a Source

conquer :: Op r a Source

Floating a => Floating (Op a b) Source 

Methods

pi :: Op a b

exp :: Op a b -> Op a b

log :: Op a b -> Op a b

sqrt :: Op a b -> Op a b

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

logBase :: Op a b -> Op a b -> Op a b

sin :: Op a b -> Op a b

cos :: Op a b -> Op a b

tan :: Op a b -> Op a b

asin :: Op a b -> Op a b

acos :: Op a b -> Op a b

atan :: Op a b -> Op a b

sinh :: Op a b -> Op a b

cosh :: Op a b -> Op a b

tanh :: Op a b -> Op a b

asinh :: Op a b -> Op a b

acosh :: Op a b -> Op a b

atanh :: Op a b -> Op a b

Fractional a => Fractional (Op a b) Source 

Methods

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

recip :: Op a b -> Op a b

fromRational :: Rational -> Op a b

Num a => Num (Op a b) Source 

Methods

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

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

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

negate :: Op a b -> Op a b

abs :: Op a b -> Op a b

signum :: Op a b -> Op a b

fromInteger :: Integer -> Op a b

Monoid a => Monoid (Op a b) Source 

Methods

mempty :: Op a b

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

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

Semigroup a => Semigroup (Op a b) Source 

Methods

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

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

stimes :: Integral c => c -> Op a b -> Op a b