#ifdef __GLASGOW_HASKELL__
#if __GLASGOW_HASKELL__ >= 702
#if MIN_VERSION_transformers(0,3,0)
#if MIN_VERSION_tagged(0,6,1)
#else
#endif
#else
#endif
#endif
#endif
module Data.Functor.Contravariant (
Contravariant(..)
, (>$<), (>$$<)
, Predicate(..)
, Comparison(..)
, defaultComparison
, Equivalence(..)
, defaultEquivalence
, Op(..)
) where
import Control.Applicative
import Control.Applicative.Backwards
import Control.Category
import Data.Functor.Product
import Data.Functor.Constant
import Data.Functor.Compose
import Data.Functor.Reverse
import Data.Proxy
import Prelude hiding ((.),id)
#ifdef __GLASGOW_HASKELL__
import Data.Typeable
#endif
class Contravariant f where
contramap :: (a -> b) -> f b -> f a
infixl 4 >$<, >$$<
(>$<) :: Contravariant f => (a -> b) -> f b -> f a
(>$<) = contramap
(>$$<) :: Contravariant f => f b -> (a -> b) -> f a
(>$$<) = flip contramap
instance (Contravariant f, Contravariant g) => Contravariant (Product f g) where
contramap f (Pair a b) = Pair (contramap f a) (contramap f b)
instance Contravariant (Constant a) where
contramap _ (Constant a) = Constant a
instance Contravariant (Const a) where
contramap _ (Const a) = Const a
instance (Functor f, Contravariant g) => Contravariant (Compose f g) where
contramap f (Compose fga) = Compose (fmap (contramap f) fga)
instance Contravariant f => Contravariant (Backwards f) where
contramap f = Backwards . contramap f . forwards
instance Contravariant f => Contravariant (Reverse f) where
contramap f = Reverse . contramap f . getReverse
instance Contravariant Proxy where
contramap _ Proxy = Proxy
newtype Predicate a = Predicate { getPredicate :: a -> Bool }
#ifdef __GLASGOW_HASKELL__
deriving Typeable
#endif
instance Contravariant Predicate where
contramap f g = Predicate $ getPredicate g . f
newtype Comparison a = Comparison { getComparison :: a -> a -> Ordering }
#ifdef __GLASGOW_HASKELL__
deriving Typeable
#endif
instance Contravariant Comparison where
contramap f g = Comparison $ \a b -> getComparison g (f a) (f b)
defaultComparison :: Ord a => Comparison a
defaultComparison = Comparison compare
newtype Equivalence a = Equivalence { getEquivalence :: a -> a -> Bool }
#ifdef __GLASGOW_HASKELL__
deriving Typeable
#endif
instance Contravariant Equivalence where
contramap f g = Equivalence $ \a b -> getEquivalence g (f a) (f b)
defaultEquivalence :: Eq a => Equivalence a
defaultEquivalence = Equivalence (==)
newtype Op a b = Op { getOp :: b -> a }
#ifdef __GLASGOW_HASKELL__
deriving Typeable
#endif
instance Category Op where
id = Op id
Op f . Op g = Op (g . f)
instance Contravariant (Op a) where
contramap f g = Op (getOp g . f)