servant/servant-client-core/src/Servant/Client/Generic.hs
Gaël Deest fca59556dd Code reorganization
Move `HasServer (NamedRoutes routes)` instance

The instance has been moved to `Servant.Server.Internal`, as the
instances for other combinators. It is necessary so that the instance
can be re-exported from `Servant.Server` without circular imports.

Otherwise, users have to import `Servant.Server.Generic` manually ;
forgetting to do so will produce confusing error messages about the
missing instance.

Move `HasClient (NamedRoutes routes)` instance

Moved so that the instance is made available when importing
`Servant.Client`, avoiding possibly confusing errors when
`Servant.Client.Generic` isn't imported.
2021-11-18 10:09:58 +01:00

49 lines
1.4 KiB
Haskell

{-# 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
= fromServant
$ clientIn (Proxy :: Proxy (ToServantApi routes)) (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 nt
= fromServant
$ hoistClientMonad m api nt
$ clientIn api m
where
m = Proxy :: Proxy m
api = Proxy :: Proxy (ToServantApi routes)