Implementation of HasClient

Follows the same design as `HasServer` in the previous commit.

A test has been added (which incidentally acts as a test for the
HasServer instance).
This commit is contained in:
Gaël Deest 2021-10-01 02:24:21 +02:00
parent 49c7dd2e8d
commit 7e8a1b240d
4 changed files with 77 additions and 7 deletions

View file

@ -52,6 +52,7 @@ library
build-depends: build-depends:
base >= 4.9 && < 4.16 base >= 4.9 && < 4.16
, bytestring >= 0.10.8.1 && < 0.12 , bytestring >= 0.10.8.1 && < 0.12
, constraints
, containers >= 0.5.7.1 && < 0.7 , containers >= 0.5.7.1 && < 0.7
, deepseq >= 1.4.2.0 && < 1.5 , deepseq >= 1.4.2.0 && < 1.5
, text >= 1.2.3.0 && < 1.3 , text >= 1.2.3.0 && < 1.3

View file

@ -1,15 +1,23 @@
{-# LANGUAGE ConstraintKinds #-} {-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE KindSignatures #-} {-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-} {-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
module Servant.Client.Generic ( module Servant.Client.Generic (
AsClientT, AsClientT,
genericClient, genericClient,
genericClientHoist, genericClientHoist,
) where ) where
import Data.Constraint (Dict(..))
import Data.Proxy import Data.Proxy
(Proxy (..)) (Proxy (..))
@ -49,3 +57,41 @@ genericClientHoist nt
where where
m = Proxy :: Proxy m m = Proxy :: Proxy m
api = Proxy :: Proxy (ToServantApi routes) api = Proxy :: Proxy (ToServantApi routes)
type GClientConstraints api m =
( GenericServant api (AsClientT m)
, Client m (ToServantApi api) ~ ToServant api (AsClientT m)
)
class GClient (api :: * -> *) m where
proof :: Dict (GClientConstraints api m)
instance GClientConstraints api m => GClient api m where
proof = Dict
instance
( forall n. GClient api n
, HasClient m (ToServantApi api)
, RunClient m
)
=> HasClient m (NamedRoutes api) where
type Client m (NamedRoutes api) = api (AsClientT m)
clientWithRoute :: Proxy m -> Proxy (NamedRoutes api) -> Request -> Client m (NamedRoutes api)
clientWithRoute pm _ request =
case proof @api @m of
Dict -> fromServant $ clientWithRoute pm (Proxy @(ToServantApi api)) request
hoistClientMonad
:: forall ma mb.
Proxy m
-> Proxy (NamedRoutes api)
-> (forall x. ma x -> mb x)
-> Client ma (NamedRoutes api)
-> Client mb (NamedRoutes api)
hoistClientMonad _ _ nat clientA =
case (proof @api @ma, proof @api @mb) of
(Dict, Dict) ->
fromServant @api @(AsClientT mb) $
hoistClientMonad @m @(ToServantApi api) @ma @mb Proxy Proxy nat $
toServant @api @(AsClientT ma) clientA

View file

@ -90,6 +90,7 @@ test-suite spec
Servant.ConnectionErrorSpec Servant.ConnectionErrorSpec
Servant.FailSpec Servant.FailSpec
Servant.GenAuthSpec Servant.GenAuthSpec
Servant.GenericSpec
Servant.HoistClientSpec Servant.HoistClientSpec
Servant.StreamSpec Servant.StreamSpec
Servant.SuccessSpec Servant.SuccessSpec

View file

@ -59,9 +59,12 @@ import Servant.API
NoContent (NoContent), PlainText, Post, QueryFlag, QueryParam, NoContent (NoContent), PlainText, Post, QueryFlag, QueryParam,
QueryParams, Raw, ReqBody, StdMethod (GET), UVerb, Union, QueryParams, Raw, ReqBody, StdMethod (GET), UVerb, Union,
WithStatus (WithStatus), addHeader) WithStatus (WithStatus), addHeader)
import Servant.API.Generic
import Servant.Client import Servant.Client
import Servant.Client.Generic
import qualified Servant.Client.Core.Auth as Auth import qualified Servant.Client.Core.Auth as Auth
import Servant.Server import Servant.Server
import Servant.Server.Generic
import Servant.Server.Experimental.Auth import Servant.Server.Experimental.Auth
import Servant.Test.ComprehensiveAPI import Servant.Test.ComprehensiveAPI
@ -101,6 +104,16 @@ carol = Person "Carol" 17
type TestHeaders = '[Header "X-Example1" Int, Header "X-Example2" String] type TestHeaders = '[Header "X-Example1" Int, Header "X-Example2" String]
data RecordRoutes mode = RecordRoutes
{ version :: mode :- "version" :> Get '[JSON] Int
, echo :: mode :- "echo" :> Capture "string" String :> Get '[JSON] String
, otherRoutes :: mode :- "other" :> NamedRoutes OtherRoutes
} deriving Generic
data OtherRoutes mode = OtherRoutes
{ something :: mode :- "something" :> Get '[JSON] [String]
} deriving Generic
type Api = type Api =
Get '[JSON] Person Get '[JSON] Person
:<|> "get" :> Get '[JSON] Person :<|> "get" :> Get '[JSON] Person
@ -131,6 +144,7 @@ type Api =
UVerb 'GET '[PlainText] '[WithStatus 200 Person, UVerb 'GET '[PlainText] '[WithStatus 200 Person,
WithStatus 301 Text] WithStatus 301 Text]
:<|> "uverb-get-created" :> UVerb 'GET '[PlainText] '[WithStatus 201 Person] :<|> "uverb-get-created" :> UVerb 'GET '[PlainText] '[WithStatus 201 Person]
:<|> NamedRoutes RecordRoutes
api :: Proxy Api api :: Proxy Api
@ -180,7 +194,8 @@ getRoot
:<|> getRedirectWithCookie :<|> getRedirectWithCookie
:<|> EmptyClient :<|> EmptyClient
:<|> uverbGetSuccessOrRedirect :<|> uverbGetSuccessOrRedirect
:<|> uverbGetCreated = client api :<|> uverbGetCreated
:<|> recordRoutes = client api
server :: Application server :: Application
server = serve api ( server = serve api (
@ -210,6 +225,13 @@ server = serve api (
then respond (WithStatus @301 ("redirecting" :: Text)) then respond (WithStatus @301 ("redirecting" :: Text))
else respond (WithStatus @200 alice )) else respond (WithStatus @200 alice ))
:<|> respond (WithStatus @201 carol) :<|> respond (WithStatus @201 carol)
:<|> RecordRoutes
{ version = pure 42
, echo = pure
, otherRoutes = OtherRoutes
{ something = pure ["foo", "bar", "pweet"]
}
}
) )
type FailApi = type FailApi =