module Generics.SOP.BasicFunctors
  ( K(..)
  , unK
  , I(..)
  , unI
  , (:.:)(..)
  , unComp
  ) where
#if MIN_VERSION_base(4,8,0)
import Data.Monoid ((<>))
#else
import Control.Applicative
import Data.Foldable (Foldable(..))
import Data.Monoid (Monoid, mempty, (<>))
import Data.Traversable (Traversable(..))
#endif
import qualified GHC.Generics as GHC
newtype K (a :: *) (b :: k) = K a
#if MIN_VERSION_base(4,7,0)
  deriving (Show, Functor, Foldable, Traversable, GHC.Generic)
#else
  deriving (Show, GHC.Generic)
instance Functor (K a) where
  fmap _ (K x) = K x
instance Foldable (K a) where
  foldr _ z (K _) = z
  foldMap _ (K _) = mempty
instance Traversable (K a) where
  traverse _ (K x) = pure (K x)
#endif
instance Monoid a => Applicative (K a) where
  pure _      = K mempty
  K x <*> K y = K (x <> y)
unK :: K a b -> a
unK (K x) = x
newtype I (a :: *) = I a
#if MIN_VERSION_base(4,7,0)
  deriving (Show, Functor, Foldable, Traversable, GHC.Generic)
#else
  deriving (Show, GHC.Generic)
instance Functor I where
  fmap f (I x) = I (f x)
instance Foldable I where
  foldr f z (I x) = f x z
  foldMap f (I x) = f x
instance Traversable I where
  traverse f (I x) = fmap I (f x)
#endif
instance Applicative I where
  pure = I
  I f <*> I x = I (f x)
instance Monad I where
  return = I
  I x >>= f = f x
unI :: I a -> a
unI (I x) = x
newtype (:.:) (f :: l -> *) (g :: k -> l) (p :: k) = Comp (f (g p))
  deriving (Show, GHC.Generic)
infixr 7 :.:
instance (Functor f, Functor g) => Functor (f :.: g) where
  fmap f (Comp x) = Comp (fmap (fmap f) x)
unComp :: (f :.: g) p -> f (g p)
unComp (Comp x) = x