#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 702
#endif
module Data.Functor.Contravariant.Adjunction
( Adjunction(..)
, adjuncted
, contrarepAdjunction
, coindexAdjunction
) where
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ < 707
import Control.Monad.Instances ()
#endif
import Data.Functor.Contravariant
import Data.Functor.Contravariant.Rep
import Data.Profunctor
class (Contravariant f, Representable g) => Adjunction f g | f -> g, g -> f where
#if __GLASGOW_HASKELL__ >= 708
#endif
unit :: a -> g (f a)
counit :: a -> f (g a)
leftAdjunct :: (b -> f a) -> a -> g b
rightAdjunct :: (a -> g b) -> b -> f a
unit = leftAdjunct id
counit = rightAdjunct id
leftAdjunct f = contramap f . unit
rightAdjunct f = contramap f . counit
adjuncted :: (Adjunction f g, Profunctor p, Functor h)
=> p (a -> g b) (h (c -> g d)) -> p (b -> f a) (h (d -> f c))
adjuncted = dimap leftAdjunct (fmap rightAdjunct)
instance Adjunction (Op r) (Op r) where
unit a = Op (\k -> getOp k a)
counit = unit
instance Adjunction Predicate Predicate where
unit a = Predicate (\k -> getPredicate k a)
counit = unit
contrarepAdjunction :: Adjunction f g => (a -> f ()) -> g a
contrarepAdjunction = flip leftAdjunct ()
coindexAdjunction :: Adjunction f g => g a -> a -> f ()
coindexAdjunction = rightAdjunct . const