{-# LANGUAGE CPP        #-}
{-# LANGUAGE RankNTypes #-}
module Data.Functor.Confusing (
    confusing, LensLike,
    iconfusing, IxLensLike,
    fconfusing, FLensLike,
    liftCurriedYoneda, yap,
    Curried (..), liftCurried, lowerCurried,
    Yoneda (..), liftYoneda, lowerYoneda,
  ) where
#ifndef MIN_VERSION_base
#define MIN_VERSION_base(x,y,z) 0
#endif
#if !(MIN_VERSION_base(4,8,0))
import Control.Applicative
#endif
type LensLike f s t a b = (a -> f b) -> s -> f t
confusing :: Applicative f => LensLike (Curried (Yoneda f)) s t a b -> LensLike f s t a b
confusing t = \f -> lowerYoneda . lowerCurried . t (liftCurriedYoneda . f)
{-# INLINE confusing #-}
liftCurriedYoneda :: Applicative f => f a -> Curried (Yoneda f) a
liftCurriedYoneda fa = Curried (`yap` fa)
{-# INLINE liftCurriedYoneda #-}
yap :: Applicative f => Yoneda f (a -> b) -> f a -> Yoneda f b
yap (Yoneda k) fa = Yoneda (\ab_r -> k (ab_r .) <*> fa)
{-# INLINE yap #-}
type IxLensLike f i s t a b = (i -> a -> f b) -> s -> f t
iconfusing :: Applicative f => IxLensLike (Curried (Yoneda f)) i s t a b -> IxLensLike f i s t a b
iconfusing t = \f -> lowerYoneda . lowerCurried . t (\i a -> liftCurriedYoneda (f i a))
{-# INLINE iconfusing #-}
type FLensLike f s t a b = (forall x. a x -> f (b x)) -> s -> f t
fconfusing :: Applicative f => FLensLike (Curried (Yoneda f)) s t a b -> FLensLike f s t a b
fconfusing t = \f -> lowerYoneda . lowerCurried . t (liftCurriedYoneda . f)
{-# INLINE fconfusing #-}
newtype Curried f a = Curried { runCurried :: forall r. f (a -> r) -> f r }
instance Functor f => Functor (Curried f) where
    fmap f (Curried g) = Curried (g . fmap (.f))
    {-# INLINE fmap #-}
instance Functor f => Applicative (Curried f) where
    pure a = Curried (fmap ($ a))
    {-# INLINE pure #-}
    Curried mf <*> Curried ma = Curried (ma . mf . fmap (.))
    {-# INLINE (<*>) #-}
liftCurried :: Applicative f => f a -> Curried f a
liftCurried fa = Curried (<*> fa)
lowerCurried :: Applicative f => Curried f a -> f a
lowerCurried (Curried f) = f (pure id)
newtype Yoneda f a = Yoneda { runYoneda :: forall b. (a -> b) -> f b }
liftYoneda :: Functor f => f a -> Yoneda f a
liftYoneda a = Yoneda (\f -> fmap f a)
lowerYoneda :: Yoneda f a -> f a
lowerYoneda (Yoneda f) = f id
instance Functor (Yoneda f) where
    fmap f m = Yoneda (\k -> runYoneda m (k . f))
instance Applicative f => Applicative (Yoneda f) where
    pure a = Yoneda (\f -> pure (f a))
    Yoneda m <*> Yoneda n = Yoneda (\f -> m (f .) <*> n id)