#if __GLASGOW_HASKELL__ >= 706
#endif
#if __GLASGOW_HASKELL__ >= 702 && __GLASGOW_HASKELL__ < 710
#endif
module Data.Functor.Kan.Lan
(
Lan(..)
, toLan, fromLan
, glan
, composeLan, decomposeLan
, adjointToLan, lanToAdjoint
, composedAdjointToLan, lanToComposedAdjoint
) where
import Control.Applicative
import Data.Functor.Adjunction
import Data.Functor.Apply
import Data.Functor.Composition
import Data.Functor.Identity
data Lan g h a where
Lan :: (g b -> a) -> h b -> Lan g h a
instance Functor (Lan f g) where
fmap f (Lan g h) = Lan (f . g) h
instance (Functor g, Apply h) => Apply (Lan g h) where
Lan kxf x <.> Lan kya y =
Lan (\k -> kxf (fmap fst k) (kya (fmap snd k))) ((,) <$> x <.> y)
instance (Functor g, Applicative h) => Applicative (Lan g h) where
pure a = Lan (const a) (pure ())
Lan kxf x <*> Lan kya y =
Lan (\k -> kxf (fmap fst k) (kya (fmap snd k))) (liftA2 (,) x y)
toLan :: Functor f => (forall a. h a -> f (g a)) -> Lan g h b -> f b
toLan s (Lan f v) = fmap f (s v)
fromLan :: (forall a. Lan g h a -> f a) -> h b -> f (g b)
fromLan s = s . glan
adjointToLan :: Adjunction f g => g a -> Lan f Identity a
adjointToLan = Lan counit . Identity
lanToAdjoint :: Adjunction f g => Lan f Identity a -> g a
lanToAdjoint (Lan f v) = leftAdjunct f (runIdentity v)
lanToComposedAdjoint :: (Functor h, Adjunction f g) => Lan f h a -> h (g a)
lanToComposedAdjoint (Lan f v) = fmap (leftAdjunct f) v
composedAdjointToLan :: Adjunction f g => h (g a) -> Lan f h a
composedAdjointToLan = Lan counit
composeLan :: (Composition compose, Functor f) => Lan f (Lan g h) a -> Lan (compose f g) h a
composeLan (Lan f (Lan g h)) = Lan (f . fmap g . decompose) h
decomposeLan :: Composition compose => Lan (compose f g) h a -> Lan f (Lan g h) a
decomposeLan (Lan f h) = Lan (f . compose) (Lan id h)
glan :: h a -> Lan g h (g a)
glan = Lan id