#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 702
#endif
module Data.Functor.Kan.Lift
  (
  
    Lift(..)
  , toLift, fromLift, glift
  , composeLift, decomposeLift
  , adjointToLift, liftToAdjoint
  , liftToComposedAdjoint, composedAdjointToLift
  , repToLift, liftToRep
  , liftToComposedRep, composedRepToLift
  ) where
import Data.Functor.Adjunction
import Data.Functor.Composition
import Data.Functor.Compose
import Data.Functor.Identity
import Data.Functor.Rep
newtype Lift g f a = Lift { runLift :: forall z. Functor z => (forall x. f x -> g (z x)) -> z a }
instance Functor (Lift g h) where
  fmap f (Lift g) = Lift (\x -> fmap f (g x))
  
glift :: Adjunction l g => k a -> g (Lift g k a)
glift = leftAdjunct (\lka -> Lift (\k2gz -> rightAdjunct k2gz lka))
toLift :: Functor z => (forall a. f a -> g (z a)) -> Lift g f b -> z b
toLift f l =  runLift l f
fromLift :: Adjunction l u => (forall a. Lift u f a -> z a) -> f b -> u (z b)
fromLift f = fmap f . glift
composeLift :: (Composition compose, Functor f, Functor g) => Lift f (Lift g h) a -> Lift (compose g f) h a
composeLift (Lift m) = Lift $ \h -> m $ decompose . toLift (fmap Compose . decompose . h)
decomposeLift :: (Composition compose, Adjunction l g) => Lift (compose g f) h a -> Lift f (Lift g h) a
decomposeLift (Lift m) = Lift $ \h -> m (compose . fmap h . glift)
adjointToLift :: Adjunction f u => f a -> Lift u Identity a
adjointToLift fa = Lift $ \k -> rightAdjunct (k . Identity) fa
liftToAdjoint :: Adjunction f u => Lift u Identity a -> f a
liftToAdjoint = toLift (unit . runIdentity)
repToLift :: Representable u => Rep u -> a -> Lift u Identity a
repToLift e a = Lift $ \k -> index (k (Identity a)) e
liftToRep :: Representable u => Lift u Identity a -> (Rep u, a)
liftToRep (Lift m) = m $ \(Identity a) -> tabulate $ \e -> (e, a)
liftToComposedAdjoint :: (Adjunction f u, Functor h) => Lift u h a -> f (h a)
liftToComposedAdjoint (Lift m) = decompose $ m (leftAdjunct Compose)
composedAdjointToLift :: Adjunction f u => f (h a) -> Lift u h a
composedAdjointToLift = rightAdjunct glift
liftToComposedRep :: (Functor h, Representable u) => Lift u h a -> (Rep u, h a)
liftToComposedRep (Lift m) = decompose $ m $ \h -> tabulate $ \e -> Compose (e, h)
composedRepToLift :: Representable u => Rep u -> h a -> Lift u h a
composedRepToLift e ha = Lift $ \h2uz -> index (h2uz ha) e