{-# OPTIONS_GHC -fno-warn-orphans  #-}
{-# LANGUAGE FlexibleContexts      #-}
{-# LANGUAGE KindSignatures        #-}
{-# LANGUAGE RankNTypes            #-}
{-# LANGUAGE ScopedTypeVariables   #-}
{-# LANGUAGE TypeFamilies          #-}

module  Servant.Client.Generic (
    AsClientT,
    genericClient,
    genericClientHoist,
    ) where

import           Data.Proxy
                 (Proxy (..))

import           Servant.API.Generic
import           Servant.Client.Core
import           Servant.Client.Core.HasClient (AsClientT)

-- | Generate a record of client functions.
genericClient
    :: forall routes m.
       ( HasClient m (ToServantApi routes)
       , GenericServant routes (AsClientT m)
       , Client m (ToServantApi routes) ~ ToServant routes (AsClientT m)
       )
    => routes (AsClientT m)
genericClient :: forall (routes :: * -> *) (m :: * -> *).
(HasClient m (ToServantApi routes),
 GenericServant routes (AsClientT m),
 Client m (ToServantApi routes) ~ ToServant routes (AsClientT m)) =>
routes (AsClientT m)
genericClient
    = forall (routes :: * -> *) mode.
GenericServant routes mode =>
ToServant routes mode -> routes mode
fromServant
    forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) api.
HasClient m api =>
Proxy api -> Proxy m -> Client m api
clientIn (forall {k} (t :: k). Proxy t
Proxy :: Proxy (ToServantApi routes)) (forall {k} (t :: k). Proxy t
Proxy :: Proxy m)

-- | 'genericClient' but with 'hoistClientMonad' in between.
genericClientHoist
    :: forall routes m n.
       ( HasClient m (ToServantApi routes)
       , GenericServant routes (AsClientT n)
       , Client n (ToServantApi routes) ~ ToServant routes (AsClientT n)
       )
    => (forall x. m x -> n x)  -- ^ natural transformation
    -> routes (AsClientT n)
genericClientHoist :: forall (routes :: * -> *) (m :: * -> *) (n :: * -> *).
(HasClient m (ToServantApi routes),
 GenericServant routes (AsClientT n),
 Client n (ToServantApi routes) ~ ToServant routes (AsClientT n)) =>
(forall x. m x -> n x) -> routes (AsClientT n)
genericClientHoist forall x. m x -> n x
nt
    = forall (routes :: * -> *) mode.
GenericServant routes mode =>
ToServant routes mode -> routes mode
fromServant
    forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) api (mon :: * -> *) (mon' :: * -> *).
HasClient m api =>
Proxy m
-> Proxy api
-> (forall x. mon x -> mon' x)
-> Client mon api
-> Client mon' api
hoistClientMonad Proxy m
m Proxy (ToServantApi routes)
api forall x. m x -> n x
nt
    forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) api.
HasClient m api =>
Proxy api -> Proxy m -> Client m api
clientIn Proxy (ToServantApi routes)
api Proxy m
m
  where
    m :: Proxy m
m = forall {k} (t :: k). Proxy t
Proxy :: Proxy m
    api :: Proxy (ToServantApi routes)
api = forall {k} (t :: k). Proxy t
Proxy :: Proxy (ToServantApi routes)