Reputation: 103
I am calling a Third Party API in which the number of variables I send as Query Params will be dynamic and will depend on an array of values.
For example, if my array=[value1]
, my API call would be
https://clientapi.com/test?userId=myuser&var1=value1
When my array=[value1,value2,value3]
, the API call should be as below
https://clientapi.com/test?userId=myuser&var1=value1&var2=value2&var3=value3
.
One way I can think of doing this is to define a lot of vars in the API definition like
type ClientAPI =
QueryParam "userId" Text
:> QueryParam "var1" Text
:> QueryParam "var2" Text
:> QueryParam "var3" Text
:> QueryParam "var4" Text
:> QueryParam "var5" Text
:> Get '[JSON] MyType
and pass in my array values in the call as required.
Is there a better way to do this?
Upvotes: 4
Views: 98
Reputation: 51169
Note that Servant does provide a QueryParams
endpoint where a single key with multiple values is allowed:
clientapi.com/test?var=value1&var=value2&var=value3
^^^ ^^^ ^^^
So, if your third-party API had been designed this way, you'd could have just used:
type API = QueryParams "var" Double :> Get '[JSON] Int
getVar :: [Double] -> ClientM Int
getVar = client (Proxy @API)
Since you need to generate different key values, there's no built-in endpoint for this, but you can write one.
Writing an endpoint involves defining a (constructor-less) data type to represent the new endpoint:
data QueryParamSeq (prefix :: Symbol) (a :: Type) deriving Typeable
and defining instances for its implementation on the server side (HasServer
) and/or the client side (HasClient
).
You only need the HasClient
instance, and the HasClient
instances for existing endpoints are located in the Servant.Client.Core.HasClient
module of servant-client-core
. I adapted the QueryParams
instance from version 0.19 to your problem. It involves some internals, so it may or may not work with earlier or later versions:
import GHC.TypeLits
import Data.Kind
import Data.Typeable
import Data.List (foldl')
import Servant.Client.Core.Request
import qualified Data.ByteString.Lazy as BL
import Data.ByteString.Builder (toLazyByteString)
data QueryParamSeq (prefix :: Symbol) (a :: Type) deriving Typeable
instance (KnownSymbol sym, ToHttpApiData a, HasClient m api)
=> HasClient m (QueryParamSeq sym a :> api) where
type Client m (QueryParamSeq sym a :> api) = [a] -> Client m api
clientWithRoute pm Proxy req paramlist =
clientWithRoute pm (Proxy @api) $
foldl' add req $ zip [(1::Int)..] paramlist
where add req' (i, v) = appendToQueryString (key i) (encodeQueryParam v) req'
key i = pack $ symbolVal (Proxy @sym) <> show i
encodeQueryParam = Just . BL.toStrict . toLazyByteString . toEncodedUrlPiece
hoistClientMonad pm Proxy f cl as = hoistClientMonad pm (Proxy @api) f (cl as)
The idea with this instance is that the Client
type family defines the parameter(s) needed by the endpoint. When you define a client using the endpoint:
type API = QueryParam "userId" Text :> QueryParamSeq "var" Double :> Get '[JSON] Int
getIt :: Maybe Text -> [Double] -> ClientM Int
getIt = client (Proxy @API)
it's this type family instance that ensures the a ~ Double
in the API's QueryParamSeq
component gets translated into an [a] ~ [Double]
parameter in the query function getIt
.
The clientWithRoute
method implements the client-side behavior for the endpoint. It's passed a couple of proxies (respectively for the base monad and the portion of the API from the current endpoint onwards), the request being constructed, and the [a]
parameter. It should typically dispatch to clientWithRoute
on the rest of the API, passing along a modified request as appropriate. This implementation just runs a bunch of add
calls to add pairs of indexed keys (e.g., var1
, var2
) and associated values from the supplied list.
The hoistClientMonad
is just boilerplate to support the hoistClient
function.
Anyway, the resulting full example which appears to work fine with the 0.19 versions of the servant packages follows:
{-# LANGUAGE GHC2021 #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeFamilies #-}
module Main (main) where
import Servant.API
import Servant.Client
import Data.Proxy
import Data.Text (Text, pack)
import Network.HTTP.Client (newManager, defaultManagerSettings)
import GHC.TypeLits
import Data.Kind
import Data.Typeable
import Data.List (foldl')
import Servant.Client.Core.Request
import qualified Data.ByteString.Lazy as BL
import Data.ByteString.Builder (toLazyByteString)
data QueryParamSeq (prefix :: Symbol) (a :: Type) deriving Typeable
instance (KnownSymbol sym, ToHttpApiData a, HasClient m api)
=> HasClient m (QueryParamSeq sym a :> api) where
type Client m (QueryParamSeq sym a :> api) = [a] -> Client m api
clientWithRoute pm Proxy req paramlist =
clientWithRoute pm (Proxy @api) $
foldl' add req $ zip [(1::Int)..] paramlist
where add req' (i, v) = appendToQueryString (key i) (encodeQueryParam v) req'
key i = pack $ symbolVal (Proxy @sym) <> show i
encodeQueryParam = Just . BL.toStrict . toLazyByteString . toEncodedUrlPiece
hoistClientMonad pm Proxy f cl as = hoistClientMonad pm (Proxy @api) f (cl as)
type API = QueryParam "userId" Text :> QueryParamSeq "var" Double :> Get '[JSON] Int
getIt :: Maybe Text -> [Double] -> ClientM Int
getIt = client (Proxy @API)
main :: IO ()
main = do
manager' <- newManager defaultManagerSettings
res <- runClientM (getIt (Just "user") [1.0, 2.0]) (mkClientEnv manager' (BaseUrl Http "localhost" 80 ""))
print res
Upvotes: 1