2017-09-03 08:49:24 +02:00
|
|
|
{-# LANGUAGE AllowAmbiguousTypes #-}
|
|
|
|
{-# LANGUAGE CPP #-}
|
|
|
|
{-# LANGUAGE DataKinds #-}
|
|
|
|
{-# LANGUAGE FlexibleContexts #-}
|
|
|
|
{-# LANGUAGE FlexibleInstances #-}
|
|
|
|
{-# LANGUAGE InstanceSigs #-}
|
|
|
|
{-# LANGUAGE MultiParamTypeClasses #-}
|
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
{-# LANGUAGE PolyKinds #-}
|
|
|
|
{-# LANGUAGE ScopedTypeVariables #-}
|
|
|
|
{-# LANGUAGE TypeFamilies #-}
|
|
|
|
{-# LANGUAGE TypeOperators #-}
|
|
|
|
{-# LANGUAGE UndecidableInstances #-}
|
2015-12-27 17:54:29 +01:00
|
|
|
|
|
|
|
#include "overlapping-compat.h"
|
2014-11-27 18:28:01 +01:00
|
|
|
-- | This module provides 'client' which can automatically generate
|
|
|
|
-- querying functions for each endpoint just from the type representing your
|
|
|
|
-- API.
|
2017-09-07 19:05:12 +02:00
|
|
|
module Servant.Client.Core
|
2016-02-17 21:45:08 +01:00
|
|
|
( AuthClientData
|
|
|
|
, AuthenticateReq(..)
|
2017-09-12 18:38:52 +02:00
|
|
|
, clientIn
|
2014-11-27 18:28:01 +01:00
|
|
|
, HasClient(..)
|
2016-02-17 21:45:08 +01:00
|
|
|
, mkAuthenticateReq
|
2015-03-05 02:46:35 +01:00
|
|
|
, ServantError(..)
|
2017-05-16 18:00:15 +02:00
|
|
|
, EmptyClient(..)
|
2017-09-08 01:07:18 +02:00
|
|
|
, RunClient(..)
|
|
|
|
, Request(..)
|
2017-09-12 20:43:16 +02:00
|
|
|
, defaultRequest
|
2017-09-08 01:07:18 +02:00
|
|
|
, Response(..)
|
|
|
|
, RequestBody(..)
|
2017-09-07 22:38:31 +02:00
|
|
|
, module Servant.Client.Core.Internal.BaseUrl
|
2017-09-12 18:38:52 +02:00
|
|
|
, ClientLike(..)
|
|
|
|
, genericMkClientL
|
|
|
|
, genericMkClientP
|
|
|
|
-- * Writing instances
|
|
|
|
, addHeader
|
|
|
|
, appendToQueryString
|
|
|
|
, appendToPath
|
|
|
|
, setRequestBodyLBS
|
|
|
|
, setRequestBody
|
2014-11-27 18:28:01 +01:00
|
|
|
) where
|
|
|
|
|
2017-09-07 22:38:31 +02:00
|
|
|
import Control.Monad.Error.Class (throwError)
|
|
|
|
import Data.List (foldl')
|
|
|
|
import Data.Proxy (Proxy (Proxy))
|
|
|
|
import Data.String (fromString)
|
|
|
|
import Data.Text (pack)
|
|
|
|
import GHC.Exts (fromList, toList)
|
|
|
|
import GHC.TypeLits (KnownSymbol, symbolVal)
|
|
|
|
import qualified Network.HTTP.Types as H
|
|
|
|
import Prelude ()
|
2016-10-15 23:43:21 +02:00
|
|
|
import Prelude.Compat
|
2017-09-07 22:38:31 +02:00
|
|
|
import Servant.API ((:<|>) ((:<|>)), (:>),
|
|
|
|
AuthProtect, BasicAuth,
|
|
|
|
BasicAuthData,
|
|
|
|
BuildHeadersTo (..),
|
|
|
|
Capture, CaptureAll,
|
|
|
|
Description, EmptyAPI,
|
|
|
|
Header, Headers (..),
|
|
|
|
HttpVersion, IsSecure,
|
|
|
|
MimeRender (mimeRender),
|
|
|
|
MimeUnrender (mimeUnrender),
|
|
|
|
NoContent (NoContent),
|
|
|
|
QueryFlag, QueryParam,
|
|
|
|
QueryParams, Raw,
|
|
|
|
ReflectMethod (..),
|
|
|
|
RemoteHost, ReqBody,
|
|
|
|
Summary, ToHttpApiData,
|
|
|
|
Vault, Verb,
|
|
|
|
WithNamedContext,
|
|
|
|
contentType,
|
|
|
|
getHeadersHList,
|
|
|
|
getResponse,
|
|
|
|
toQueryParam,
|
|
|
|
toUrlPiece)
|
|
|
|
import Servant.API.ContentTypes (contentTypes)
|
|
|
|
|
|
|
|
import Servant.Client.Core.Internal.Auth
|
2017-09-12 18:38:52 +02:00
|
|
|
import Servant.Client.Core.Internal.BaseUrl (BaseUrl (..),
|
|
|
|
InvalidBaseUrlException,
|
|
|
|
Scheme (..),
|
|
|
|
parseBaseUrl,
|
|
|
|
showBaseUrl)
|
2017-09-07 22:38:31 +02:00
|
|
|
import Servant.Client.Core.Internal.BasicAuth
|
|
|
|
import Servant.Client.Core.Internal.Class
|
|
|
|
import Servant.Client.Core.Internal.Request
|
2017-09-12 18:38:52 +02:00
|
|
|
import Servant.Client.Core.Internal.Generic
|
2014-11-27 18:28:01 +01:00
|
|
|
|
|
|
|
-- * Accessing APIs as a Client
|
|
|
|
|
2017-09-04 09:19:08 +02:00
|
|
|
-- | 'client' allows you to produce operations to query an API from a client within
|
|
|
|
-- a given monadic context `m`
|
2014-11-27 18:28:01 +01:00
|
|
|
--
|
2015-05-14 00:52:37 +02:00
|
|
|
-- > type MyApi = "books" :> Get '[JSON] [Book] -- GET /books
|
2015-11-27 02:05:34 +01:00
|
|
|
-- > :<|> "books" :> ReqBody '[JSON] Book :> Post '[JSON] Book -- POST /books
|
2014-11-27 18:28:01 +01:00
|
|
|
-- >
|
|
|
|
-- > myApi :: Proxy MyApi
|
|
|
|
-- > myApi = Proxy
|
|
|
|
-- >
|
2017-09-04 09:19:08 +02:00
|
|
|
-- > clientM :: Proxy ClientM
|
|
|
|
-- > clientM = Proxy
|
|
|
|
-- >
|
2016-10-09 21:34:16 +02:00
|
|
|
-- > getAllBooks :: ClientM [Book]
|
|
|
|
-- > postNewBook :: Book -> ClientM Book
|
2017-09-12 18:38:52 +02:00
|
|
|
-- > (getAllBooks :<|> postNewBook) = myApi `clientIn` clientM
|
|
|
|
clientIn :: HasClient m api => Proxy api -> Proxy m -> Client m api
|
|
|
|
clientIn p pm = clientWithRoute pm p defaultRequest
|
2017-09-04 09:19:08 +02:00
|
|
|
|
|
|
|
|
2014-11-27 18:28:01 +01:00
|
|
|
-- | This class lets us define how each API combinator
|
2014-12-01 13:41:12 +01:00
|
|
|
-- influences the creation of an HTTP request. It's mostly
|
|
|
|
-- an internal class, you can just use 'client'.
|
2017-09-07 22:38:31 +02:00
|
|
|
class RunClient m => HasClient m api where
|
2017-08-28 19:27:05 +02:00
|
|
|
type Client (m :: * -> *) (api :: *) :: *
|
2017-09-07 22:38:31 +02:00
|
|
|
clientWithRoute :: Proxy m -> Proxy api -> Request -> Client m api
|
2015-03-09 21:50:30 +01:00
|
|
|
|
2014-11-27 18:28:01 +01:00
|
|
|
|
|
|
|
-- | A client querying function for @a ':<|>' b@ will actually hand you
|
|
|
|
-- one function for querying @a@ and another one for querying @b@,
|
|
|
|
-- stitching them together with ':<|>', which really is just like a pair.
|
|
|
|
--
|
2015-05-14 00:52:37 +02:00
|
|
|
-- > type MyApi = "books" :> Get '[JSON] [Book] -- GET /books
|
|
|
|
-- > :<|> "books" :> ReqBody '[JSON] Book :> Post Book -- POST /books
|
2014-11-27 18:28:01 +01:00
|
|
|
-- >
|
|
|
|
-- > myApi :: Proxy MyApi
|
|
|
|
-- > myApi = Proxy
|
|
|
|
-- >
|
2016-10-09 21:34:16 +02:00
|
|
|
-- > getAllBooks :: ClientM [Book]
|
|
|
|
-- > postNewBook :: Book -> ClientM Book
|
2016-03-28 15:56:50 +02:00
|
|
|
-- > (getAllBooks :<|> postNewBook) = client myApi
|
2017-09-03 08:49:24 +02:00
|
|
|
instance (HasClient m a, HasClient m b) => HasClient m (a :<|> b) where
|
2017-08-28 19:27:05 +02:00
|
|
|
type Client m (a :<|> b) = Client m a :<|> Client m b
|
2017-09-03 08:49:24 +02:00
|
|
|
clientWithRoute pm Proxy req =
|
|
|
|
clientWithRoute pm (Proxy :: Proxy a) req :<|>
|
|
|
|
clientWithRoute pm (Proxy :: Proxy b) req
|
2014-11-27 18:28:01 +01:00
|
|
|
|
2017-05-16 13:06:37 +02:00
|
|
|
-- | Singleton type representing a client for an empty API.
|
2017-05-16 18:00:15 +02:00
|
|
|
data EmptyClient = EmptyClient deriving (Eq, Show, Bounded, Enum)
|
2017-05-16 11:42:06 +02:00
|
|
|
|
2017-05-16 18:00:15 +02:00
|
|
|
-- | The client for 'EmptyAPI' is simply 'EmptyClient'.
|
2017-05-16 13:06:37 +02:00
|
|
|
--
|
|
|
|
-- > type MyAPI = "books" :> Get '[JSON] [Book] -- GET /books
|
|
|
|
-- > :<|> "nothing" :> EmptyAPI
|
|
|
|
-- >
|
|
|
|
-- > myApi :: Proxy MyApi
|
|
|
|
-- > myApi = Proxy
|
|
|
|
-- >
|
|
|
|
-- > getAllBooks :: ClientM [Book]
|
2017-05-16 18:00:15 +02:00
|
|
|
-- > (getAllBooks :<|> EmptyClient) = client myApi
|
2017-09-07 22:38:31 +02:00
|
|
|
instance RunClient m => HasClient m EmptyAPI where
|
2017-08-28 19:27:05 +02:00
|
|
|
type Client m EmptyAPI = EmptyClient
|
2017-09-04 08:22:38 +02:00
|
|
|
clientWithRoute _pm Proxy _ = EmptyClient
|
2017-05-16 11:42:06 +02:00
|
|
|
|
2014-11-27 18:28:01 +01:00
|
|
|
-- | If you use a 'Capture' in one of your endpoints in your API,
|
|
|
|
-- the corresponding querying function will automatically take
|
|
|
|
-- an additional argument of the type specified by your 'Capture'.
|
|
|
|
-- That function will take care of inserting a textual representation
|
|
|
|
-- of this value at the right place in the request path.
|
|
|
|
--
|
|
|
|
-- You can control how values for this type are turned into
|
2015-10-07 23:38:47 +02:00
|
|
|
-- text by specifying a 'ToHttpApiData' instance for your type.
|
2014-11-27 18:28:01 +01:00
|
|
|
--
|
|
|
|
-- Example:
|
|
|
|
--
|
2015-05-14 00:52:37 +02:00
|
|
|
-- > type MyApi = "books" :> Capture "isbn" Text :> Get '[JSON] Book
|
2014-11-27 18:28:01 +01:00
|
|
|
-- >
|
|
|
|
-- > myApi :: Proxy MyApi
|
|
|
|
-- > myApi = Proxy
|
|
|
|
-- >
|
2016-10-09 21:34:16 +02:00
|
|
|
-- > getBook :: Text -> ClientM Book
|
2016-03-28 15:56:50 +02:00
|
|
|
-- > getBook = client myApi
|
2014-11-27 18:28:01 +01:00
|
|
|
-- > -- then you can just use "getBook" to query that endpoint
|
2017-09-03 08:49:24 +02:00
|
|
|
instance (KnownSymbol capture, ToHttpApiData a, HasClient m api)
|
|
|
|
=> HasClient m (Capture capture a :> api) where
|
2014-11-27 18:28:01 +01:00
|
|
|
|
2017-08-28 19:27:05 +02:00
|
|
|
type Client m (Capture capture a :> api) =
|
|
|
|
a -> Client m api
|
2014-11-27 18:28:01 +01:00
|
|
|
|
2017-09-03 08:49:24 +02:00
|
|
|
clientWithRoute pm Proxy req val =
|
|
|
|
clientWithRoute pm (Proxy :: Proxy api)
|
2015-04-24 17:51:30 +02:00
|
|
|
(appendToPath p req)
|
2014-11-27 18:28:01 +01:00
|
|
|
|
2017-09-07 22:38:31 +02:00
|
|
|
where p = (toUrlPiece val)
|
2014-11-27 18:28:01 +01:00
|
|
|
|
2016-05-26 18:10:33 +02:00
|
|
|
-- | If you use a 'CaptureAll' in one of your endpoints in your API,
|
|
|
|
-- the corresponding querying function will automatically take an
|
|
|
|
-- additional argument of a list of the type specified by your
|
|
|
|
-- 'CaptureAll'. That function will take care of inserting a textual
|
|
|
|
-- representation of this value at the right place in the request
|
|
|
|
-- path.
|
|
|
|
--
|
|
|
|
-- You can control how these values are turned into text by specifying
|
|
|
|
-- a 'ToHttpApiData' instance of your type.
|
|
|
|
--
|
|
|
|
-- Example:
|
|
|
|
--
|
|
|
|
-- > type MyAPI = "src" :> CaptureAll Text -> Get '[JSON] SourceFile
|
|
|
|
-- >
|
|
|
|
-- > myApi :: Proxy
|
|
|
|
-- > myApi = Proxy
|
|
|
|
--
|
2016-10-09 21:34:16 +02:00
|
|
|
-- > getSourceFile :: [Text] -> ClientM SourceFile
|
2016-05-26 18:10:33 +02:00
|
|
|
-- > getSourceFile = client myApi
|
|
|
|
-- > -- then you can use "getSourceFile" to query that endpoint
|
2017-09-03 08:49:24 +02:00
|
|
|
instance (KnownSymbol capture, ToHttpApiData a, HasClient m sublayout)
|
|
|
|
=> HasClient m (CaptureAll capture a :> sublayout) where
|
2016-05-26 18:10:33 +02:00
|
|
|
|
2017-08-28 19:27:05 +02:00
|
|
|
type Client m (CaptureAll capture a :> sublayout) =
|
|
|
|
[a] -> Client m sublayout
|
2016-05-26 18:10:33 +02:00
|
|
|
|
2017-09-03 08:49:24 +02:00
|
|
|
clientWithRoute pm Proxy req vals =
|
|
|
|
clientWithRoute pm (Proxy :: Proxy sublayout)
|
2016-05-26 18:10:33 +02:00
|
|
|
(foldl' (flip appendToPath) req ps)
|
|
|
|
|
2017-09-07 22:38:31 +02:00
|
|
|
where ps = map (toUrlPiece) vals
|
2016-05-26 18:10:33 +02:00
|
|
|
|
2015-12-27 17:54:29 +01:00
|
|
|
instance OVERLAPPABLE_
|
2015-11-27 02:05:34 +01:00
|
|
|
-- Note [Non-Empty Content Types]
|
2017-09-07 22:38:31 +02:00
|
|
|
( RunClient m, MimeUnrender ct a, ReflectMethod method, cts' ~ (ct ': cts)
|
2017-09-03 08:49:24 +02:00
|
|
|
) => HasClient m (Verb method status cts' a) where
|
2017-08-28 19:27:05 +02:00
|
|
|
type Client m (Verb method status cts' a) = m a
|
2017-09-04 08:22:38 +02:00
|
|
|
clientWithRoute _pm Proxy req = do
|
2017-09-07 22:38:31 +02:00
|
|
|
response <- runRequest req
|
|
|
|
{ requestAccept = fromList $ toList accept
|
|
|
|
, requestMethod = method
|
|
|
|
}
|
2017-09-13 01:49:55 +02:00
|
|
|
response `decodedAs` (Proxy :: Proxy ct)
|
|
|
|
where
|
|
|
|
accept = contentTypes (Proxy :: Proxy ct)
|
|
|
|
method = reflectMethod (Proxy :: Proxy method)
|
2014-11-27 18:28:01 +01:00
|
|
|
|
2015-12-27 17:54:29 +01:00
|
|
|
instance OVERLAPPING_
|
2017-09-07 22:38:31 +02:00
|
|
|
( RunClient m, ReflectMethod method
|
|
|
|
) => HasClient m (Verb method status cts NoContent) where
|
2017-08-28 19:27:05 +02:00
|
|
|
type Client m (Verb method status cts NoContent)
|
|
|
|
= m NoContent
|
2017-09-04 08:22:38 +02:00
|
|
|
clientWithRoute _pm Proxy req = do
|
2017-09-07 22:38:31 +02:00
|
|
|
_response <- runRequest req { requestMethod = method }
|
2017-09-03 08:49:24 +02:00
|
|
|
return NoContent
|
2015-11-27 02:05:34 +01:00
|
|
|
where method = reflectMethod (Proxy :: Proxy method)
|
2015-05-06 21:21:35 +02:00
|
|
|
|
2015-12-27 17:54:29 +01:00
|
|
|
instance OVERLAPPING_
|
2015-11-27 02:05:34 +01:00
|
|
|
-- Note [Non-Empty Content Types]
|
2017-09-07 22:38:31 +02:00
|
|
|
( RunClient m, MimeUnrender ct a, BuildHeadersTo ls
|
|
|
|
, ReflectMethod method, cts' ~ (ct ': cts)
|
2017-09-03 08:49:24 +02:00
|
|
|
) => HasClient m (Verb method status cts' (Headers ls a)) where
|
2017-08-28 19:27:05 +02:00
|
|
|
type Client m (Verb method status cts' (Headers ls a))
|
|
|
|
= m (Headers ls a)
|
2017-09-04 08:22:38 +02:00
|
|
|
clientWithRoute _pm Proxy req = do
|
2017-09-07 22:38:31 +02:00
|
|
|
response <- runRequest req
|
|
|
|
{ requestMethod = method
|
|
|
|
, requestAccept = fromList $ toList accept
|
|
|
|
}
|
|
|
|
case mimeUnrender (Proxy :: Proxy ct) $ responseBody response of
|
|
|
|
Left err -> throwError $ DecodeFailure (pack err) response
|
|
|
|
Right val -> return $ Headers
|
|
|
|
{ getResponse = val
|
|
|
|
, getHeadersHList = buildHeadersTo . toList $ responseHeaders response
|
|
|
|
}
|
|
|
|
where method = reflectMethod (Proxy :: Proxy method)
|
|
|
|
accept = contentTypes (Proxy :: Proxy ct)
|
2015-05-06 21:21:35 +02:00
|
|
|
|
2015-12-27 17:54:29 +01:00
|
|
|
instance OVERLAPPING_
|
2017-09-07 22:38:31 +02:00
|
|
|
( RunClient m, BuildHeadersTo ls, ReflectMethod method
|
2017-09-03 08:49:24 +02:00
|
|
|
) => HasClient m (Verb method status cts (Headers ls NoContent)) where
|
2017-08-28 19:27:05 +02:00
|
|
|
type Client m (Verb method status cts (Headers ls NoContent))
|
|
|
|
= m (Headers ls NoContent)
|
2017-09-04 08:22:38 +02:00
|
|
|
clientWithRoute _pm Proxy req = do
|
2015-11-27 02:05:34 +01:00
|
|
|
let method = reflectMethod (Proxy :: Proxy method)
|
2017-09-07 22:38:31 +02:00
|
|
|
response <- runRequest req { requestMethod = method }
|
2016-01-07 14:30:08 +01:00
|
|
|
return $ Headers { getResponse = NoContent
|
2017-09-07 22:38:31 +02:00
|
|
|
, getHeadersHList = buildHeadersTo . toList $ responseHeaders response
|
2015-05-02 03:21:03 +02:00
|
|
|
}
|
|
|
|
|
2015-11-27 02:05:34 +01:00
|
|
|
|
2014-12-08 12:52:30 +01:00
|
|
|
-- | If you use a 'Header' in one of your endpoints in your API,
|
|
|
|
-- the corresponding querying function will automatically take
|
|
|
|
-- an additional argument of the type specified by your 'Header',
|
|
|
|
-- wrapped in Maybe.
|
|
|
|
--
|
|
|
|
-- That function will take care of encoding this argument as Text
|
|
|
|
-- in the request headers.
|
|
|
|
--
|
2015-10-07 23:38:47 +02:00
|
|
|
-- All you need is for your type to have a 'ToHttpApiData' instance.
|
2014-12-08 12:52:30 +01:00
|
|
|
--
|
|
|
|
-- Example:
|
|
|
|
--
|
2015-05-14 00:52:37 +02:00
|
|
|
-- > newtype Referer = Referer { referrer :: Text }
|
2016-04-01 22:56:19 +02:00
|
|
|
-- > deriving (Eq, Show, Generic, ToHttpApiData)
|
2014-12-08 12:52:30 +01:00
|
|
|
-- >
|
|
|
|
-- > -- GET /view-my-referer
|
2015-05-14 00:52:37 +02:00
|
|
|
-- > type MyApi = "view-my-referer" :> Header "Referer" Referer :> Get '[JSON] Referer
|
2014-12-08 12:52:30 +01:00
|
|
|
-- >
|
|
|
|
-- > myApi :: Proxy MyApi
|
|
|
|
-- > myApi = Proxy
|
|
|
|
-- >
|
2016-10-09 21:34:16 +02:00
|
|
|
-- > viewReferer :: Maybe Referer -> ClientM Book
|
2016-03-28 15:56:50 +02:00
|
|
|
-- > viewReferer = client myApi
|
2014-12-08 12:52:30 +01:00
|
|
|
-- > -- then you can just use "viewRefer" to query that endpoint
|
2015-05-14 00:52:37 +02:00
|
|
|
-- > -- specifying Nothing or e.g Just "http://haskell.org/" as arguments
|
2017-09-03 08:49:24 +02:00
|
|
|
instance (KnownSymbol sym, ToHttpApiData a, HasClient m api)
|
|
|
|
=> HasClient m (Header sym a :> api) where
|
2014-12-08 12:52:30 +01:00
|
|
|
|
2017-08-28 19:27:05 +02:00
|
|
|
type Client m (Header sym a :> api) =
|
|
|
|
Maybe a -> Client m api
|
2014-12-08 12:52:30 +01:00
|
|
|
|
2017-09-03 08:49:24 +02:00
|
|
|
clientWithRoute pm Proxy req mval =
|
|
|
|
clientWithRoute pm (Proxy :: Proxy api)
|
2015-04-24 17:51:30 +02:00
|
|
|
(maybe req
|
2017-09-07 22:38:31 +02:00
|
|
|
(\value -> addHeader hname value req)
|
2015-04-24 17:51:30 +02:00
|
|
|
mval
|
|
|
|
)
|
2014-12-08 12:52:30 +01:00
|
|
|
|
2017-09-07 22:38:31 +02:00
|
|
|
where hname = fromString $ symbolVal (Proxy :: Proxy sym)
|
2014-11-27 18:28:01 +01:00
|
|
|
|
2016-01-16 19:34:44 +01:00
|
|
|
-- | Using a 'HttpVersion' combinator in your API doesn't affect the client
|
|
|
|
-- functions.
|
2017-09-03 08:49:24 +02:00
|
|
|
instance HasClient m api
|
|
|
|
=> HasClient m (HttpVersion :> api) where
|
2016-01-16 19:34:44 +01:00
|
|
|
|
2017-08-28 19:27:05 +02:00
|
|
|
type Client m (HttpVersion :> api) =
|
|
|
|
Client m api
|
2016-01-16 19:34:44 +01:00
|
|
|
|
2017-09-03 08:49:24 +02:00
|
|
|
clientWithRoute pm Proxy =
|
|
|
|
clientWithRoute pm (Proxy :: Proxy api)
|
2017-06-08 17:27:36 +02:00
|
|
|
|
|
|
|
-- | Ignore @'Summary'@ in client functions.
|
2017-09-03 08:49:24 +02:00
|
|
|
instance HasClient m api => HasClient m (Summary desc :> api) where
|
2017-08-28 19:27:05 +02:00
|
|
|
type Client m (Summary desc :> api) = Client m api
|
2017-06-08 17:27:36 +02:00
|
|
|
|
2017-09-03 08:49:24 +02:00
|
|
|
clientWithRoute pm _ = clientWithRoute pm (Proxy :: Proxy api)
|
2017-06-08 17:27:36 +02:00
|
|
|
|
|
|
|
-- | Ignore @'Description'@ in client functions.
|
2017-09-03 08:49:24 +02:00
|
|
|
instance HasClient m api => HasClient m (Description desc :> api) where
|
2017-08-28 19:27:05 +02:00
|
|
|
type Client m (Description desc :> api) = Client m api
|
2017-06-08 17:27:36 +02:00
|
|
|
|
2017-09-03 08:49:24 +02:00
|
|
|
clientWithRoute pm _ = clientWithRoute pm (Proxy :: Proxy api)
|
2016-01-16 19:34:44 +01:00
|
|
|
|
2014-11-27 18:28:01 +01:00
|
|
|
-- | If you use a 'QueryParam' in one of your endpoints in your API,
|
|
|
|
-- the corresponding querying function will automatically take
|
|
|
|
-- an additional argument of the type specified by your 'QueryParam',
|
|
|
|
-- enclosed in Maybe.
|
|
|
|
--
|
|
|
|
-- If you give Nothing, nothing will be added to the query string.
|
|
|
|
--
|
|
|
|
-- If you give a non-'Nothing' value, this function will take care
|
|
|
|
-- of inserting a textual representation of this value in the query string.
|
|
|
|
--
|
|
|
|
-- You can control how values for your type are turned into
|
2015-10-07 23:38:47 +02:00
|
|
|
-- text by specifying a 'ToHttpApiData' instance for your type.
|
2014-11-27 18:28:01 +01:00
|
|
|
--
|
|
|
|
-- Example:
|
|
|
|
--
|
2015-05-14 00:52:37 +02:00
|
|
|
-- > type MyApi = "books" :> QueryParam "author" Text :> Get '[JSON] [Book]
|
2014-11-27 18:28:01 +01:00
|
|
|
-- >
|
|
|
|
-- > myApi :: Proxy MyApi
|
|
|
|
-- > myApi = Proxy
|
|
|
|
-- >
|
2016-10-09 21:34:16 +02:00
|
|
|
-- > getBooksBy :: Maybe Text -> ClientM [Book]
|
2016-03-28 15:56:50 +02:00
|
|
|
-- > getBooksBy = client myApi
|
2014-11-27 18:28:01 +01:00
|
|
|
-- > -- then you can just use "getBooksBy" to query that endpoint.
|
|
|
|
-- > -- 'getBooksBy Nothing' for all books
|
|
|
|
-- > -- 'getBooksBy (Just "Isaac Asimov")' to get all books by Isaac Asimov
|
2017-09-03 08:49:24 +02:00
|
|
|
instance (KnownSymbol sym, ToHttpApiData a, HasClient m api)
|
|
|
|
=> HasClient m (QueryParam sym a :> api) where
|
2014-11-27 18:28:01 +01:00
|
|
|
|
2017-08-28 19:27:05 +02:00
|
|
|
type Client m (QueryParam sym a :> api) =
|
|
|
|
Maybe a -> Client m api
|
2014-11-27 18:28:01 +01:00
|
|
|
|
|
|
|
-- if mparam = Nothing, we don't add it to the query string
|
2017-09-03 08:49:24 +02:00
|
|
|
clientWithRoute pm Proxy req mparam =
|
|
|
|
clientWithRoute pm (Proxy :: Proxy api)
|
2015-04-24 17:51:30 +02:00
|
|
|
(maybe req
|
|
|
|
(flip (appendToQueryString pname) req . Just)
|
|
|
|
mparamText
|
|
|
|
)
|
2014-11-27 18:28:01 +01:00
|
|
|
|
2017-09-07 22:38:31 +02:00
|
|
|
where pname = pack $ symbolVal (Proxy :: Proxy sym)
|
2015-10-07 23:38:47 +02:00
|
|
|
mparamText = fmap toQueryParam mparam
|
2014-11-27 18:28:01 +01:00
|
|
|
|
|
|
|
-- | If you use a 'QueryParams' in one of your endpoints in your API,
|
|
|
|
-- the corresponding querying function will automatically take
|
2015-03-26 14:34:38 +01:00
|
|
|
-- an additional argument, a list of values of the type specified
|
2014-11-27 18:28:01 +01:00
|
|
|
-- by your 'QueryParams'.
|
|
|
|
--
|
|
|
|
-- If you give an empty list, nothing will be added to the query string.
|
|
|
|
--
|
|
|
|
-- Otherwise, this function will take care
|
|
|
|
-- of inserting a textual representation of your values in the query string,
|
|
|
|
-- under the same query string parameter name.
|
|
|
|
--
|
|
|
|
-- You can control how values for your type are turned into
|
2015-10-07 23:38:47 +02:00
|
|
|
-- text by specifying a 'ToHttpApiData' instance for your type.
|
2014-11-27 18:28:01 +01:00
|
|
|
--
|
|
|
|
-- Example:
|
|
|
|
--
|
2015-05-14 00:52:37 +02:00
|
|
|
-- > type MyApi = "books" :> QueryParams "authors" Text :> Get '[JSON] [Book]
|
2014-11-27 18:28:01 +01:00
|
|
|
-- >
|
|
|
|
-- > myApi :: Proxy MyApi
|
|
|
|
-- > myApi = Proxy
|
|
|
|
-- >
|
2016-10-09 21:34:16 +02:00
|
|
|
-- > getBooksBy :: [Text] -> ClientM [Book]
|
2016-03-28 15:56:50 +02:00
|
|
|
-- > getBooksBy = client myApi
|
2014-11-27 18:28:01 +01:00
|
|
|
-- > -- then you can just use "getBooksBy" to query that endpoint.
|
|
|
|
-- > -- 'getBooksBy []' for all books
|
|
|
|
-- > -- 'getBooksBy ["Isaac Asimov", "Robert A. Heinlein"]'
|
|
|
|
-- > -- to get all books by Asimov and Heinlein
|
2017-09-03 08:49:24 +02:00
|
|
|
instance (KnownSymbol sym, ToHttpApiData a, HasClient m api)
|
|
|
|
=> HasClient m (QueryParams sym a :> api) where
|
2014-11-27 18:28:01 +01:00
|
|
|
|
2017-08-28 19:27:05 +02:00
|
|
|
type Client m (QueryParams sym a :> api) =
|
|
|
|
[a] -> Client m api
|
2014-11-27 18:28:01 +01:00
|
|
|
|
2017-09-03 08:49:24 +02:00
|
|
|
clientWithRoute pm Proxy req paramlist =
|
|
|
|
clientWithRoute pm (Proxy :: Proxy api)
|
2015-04-24 17:51:30 +02:00
|
|
|
(foldl' (\ req' -> maybe req' (flip (appendToQueryString pname) req' . Just))
|
|
|
|
req
|
|
|
|
paramlist'
|
|
|
|
)
|
2014-11-27 18:28:01 +01:00
|
|
|
|
2017-09-07 22:38:31 +02:00
|
|
|
where pname = pack $ symbolVal (Proxy :: Proxy sym)
|
2015-10-07 23:38:47 +02:00
|
|
|
paramlist' = map (Just . toQueryParam) paramlist
|
2014-11-27 18:28:01 +01:00
|
|
|
|
|
|
|
-- | If you use a 'QueryFlag' in one of your endpoints in your API,
|
|
|
|
-- the corresponding querying function will automatically take
|
|
|
|
-- an additional 'Bool' argument.
|
|
|
|
--
|
|
|
|
-- If you give 'False', nothing will be added to the query string.
|
|
|
|
--
|
|
|
|
-- Otherwise, this function will insert a value-less query string
|
|
|
|
-- parameter under the name associated to your 'QueryFlag'.
|
|
|
|
--
|
|
|
|
-- Example:
|
|
|
|
--
|
2015-05-14 00:52:37 +02:00
|
|
|
-- > type MyApi = "books" :> QueryFlag "published" :> Get '[JSON] [Book]
|
2014-11-27 18:28:01 +01:00
|
|
|
-- >
|
|
|
|
-- > myApi :: Proxy MyApi
|
|
|
|
-- > myApi = Proxy
|
|
|
|
-- >
|
2016-10-09 21:34:16 +02:00
|
|
|
-- > getBooks :: Bool -> ClientM [Book]
|
2016-03-28 15:56:50 +02:00
|
|
|
-- > getBooks = client myApi
|
2014-11-27 18:28:01 +01:00
|
|
|
-- > -- then you can just use "getBooks" to query that endpoint.
|
|
|
|
-- > -- 'getBooksBy False' for all books
|
|
|
|
-- > -- 'getBooksBy True' to only get _already published_ books
|
2017-09-03 08:49:24 +02:00
|
|
|
instance (KnownSymbol sym, HasClient m api)
|
|
|
|
=> HasClient m (QueryFlag sym :> api) where
|
2014-11-27 18:28:01 +01:00
|
|
|
|
2017-08-28 19:27:05 +02:00
|
|
|
type Client m (QueryFlag sym :> api) =
|
|
|
|
Bool -> Client m api
|
2014-11-27 18:28:01 +01:00
|
|
|
|
2017-09-03 08:49:24 +02:00
|
|
|
clientWithRoute pm Proxy req flag =
|
|
|
|
clientWithRoute pm (Proxy :: Proxy api)
|
2015-04-24 17:51:30 +02:00
|
|
|
(if flag
|
|
|
|
then appendToQueryString paramname Nothing req
|
|
|
|
else req
|
|
|
|
)
|
2014-11-27 18:28:01 +01:00
|
|
|
|
2017-09-07 22:38:31 +02:00
|
|
|
where paramname = pack $ symbolVal (Proxy :: Proxy sym)
|
2014-11-27 18:28:01 +01:00
|
|
|
|
2015-01-01 23:43:29 +01:00
|
|
|
|
2014-11-27 18:28:01 +01:00
|
|
|
-- | Pick a 'Method' and specify where the server you want to query is. You get
|
2015-03-16 01:12:11 +01:00
|
|
|
-- back the full `Response`.
|
2017-09-07 22:38:31 +02:00
|
|
|
instance RunClient m => HasClient m Raw where
|
2017-08-28 19:27:05 +02:00
|
|
|
type Client m Raw
|
2017-09-07 22:38:31 +02:00
|
|
|
= H.Method -> m Response
|
2014-11-27 18:28:01 +01:00
|
|
|
|
2017-09-07 22:38:31 +02:00
|
|
|
clientWithRoute :: Proxy m -> Proxy Raw -> Request -> Client m Raw
|
2017-09-04 08:22:38 +02:00
|
|
|
clientWithRoute _pm Proxy req httpMethod = do
|
2017-09-07 22:38:31 +02:00
|
|
|
runRequest req { requestMethod = httpMethod }
|
2014-11-27 18:28:01 +01:00
|
|
|
|
|
|
|
-- | If you use a 'ReqBody' in one of your endpoints in your API,
|
|
|
|
-- the corresponding querying function will automatically take
|
|
|
|
-- an additional argument of the type specified by your 'ReqBody'.
|
|
|
|
-- That function will take care of encoding this argument as JSON and
|
|
|
|
-- of using it as the request body.
|
|
|
|
--
|
|
|
|
-- All you need is for your type to have a 'ToJSON' instance.
|
|
|
|
--
|
|
|
|
-- Example:
|
|
|
|
--
|
2015-05-14 00:52:37 +02:00
|
|
|
-- > type MyApi = "books" :> ReqBody '[JSON] Book :> Post '[JSON] Book
|
2014-11-27 18:28:01 +01:00
|
|
|
-- >
|
|
|
|
-- > myApi :: Proxy MyApi
|
|
|
|
-- > myApi = Proxy
|
|
|
|
-- >
|
2016-10-09 21:34:16 +02:00
|
|
|
-- > addBook :: Book -> ClientM Book
|
2016-03-28 15:56:50 +02:00
|
|
|
-- > addBook = client myApi
|
2014-11-27 18:28:01 +01:00
|
|
|
-- > -- then you can just use "addBook" to query that endpoint
|
2017-09-03 08:49:24 +02:00
|
|
|
instance (MimeRender ct a, HasClient m api)
|
|
|
|
=> HasClient m (ReqBody (ct ': cts) a :> api) where
|
2014-11-27 18:28:01 +01:00
|
|
|
|
2017-08-28 19:27:05 +02:00
|
|
|
type Client m (ReqBody (ct ': cts) a :> api) =
|
|
|
|
a -> Client m api
|
2014-11-27 18:28:01 +01:00
|
|
|
|
2017-09-03 08:49:24 +02:00
|
|
|
clientWithRoute pm Proxy req body =
|
|
|
|
clientWithRoute pm (Proxy :: Proxy api)
|
2015-04-24 17:51:30 +02:00
|
|
|
(let ctProxy = Proxy :: Proxy ct
|
2017-09-07 22:38:31 +02:00
|
|
|
in setRequestBodyLBS (mimeRender ctProxy body)
|
|
|
|
-- We use first contentType from the Accept list
|
|
|
|
(contentType ctProxy)
|
|
|
|
req
|
2015-04-24 17:51:30 +02:00
|
|
|
)
|
2014-11-27 18:28:01 +01:00
|
|
|
|
|
|
|
-- | Make the querying function append @path@ to the request path.
|
2017-09-03 08:49:24 +02:00
|
|
|
instance (KnownSymbol path, HasClient m api) => HasClient m (path :> api) where
|
2017-08-28 19:27:05 +02:00
|
|
|
type Client m (path :> api) = Client m api
|
2014-11-27 18:28:01 +01:00
|
|
|
|
2017-09-03 08:49:24 +02:00
|
|
|
clientWithRoute pm Proxy req =
|
|
|
|
clientWithRoute pm (Proxy :: Proxy api)
|
2015-04-24 17:51:30 +02:00
|
|
|
(appendToPath p req)
|
2014-11-27 18:28:01 +01:00
|
|
|
|
2017-09-07 22:38:31 +02:00
|
|
|
where p = pack $ symbolVal (Proxy :: Proxy path)
|
2014-11-27 18:28:01 +01:00
|
|
|
|
2017-09-03 08:49:24 +02:00
|
|
|
instance HasClient m api => HasClient m (Vault :> api) where
|
2017-08-28 19:27:05 +02:00
|
|
|
type Client m (Vault :> api) = Client m api
|
2015-06-23 10:34:20 +02:00
|
|
|
|
2017-09-03 08:49:24 +02:00
|
|
|
clientWithRoute pm Proxy req =
|
|
|
|
clientWithRoute pm (Proxy :: Proxy api) req
|
2015-06-23 10:34:20 +02:00
|
|
|
|
2017-09-03 08:49:24 +02:00
|
|
|
instance HasClient m api => HasClient m (RemoteHost :> api) where
|
2017-08-28 19:27:05 +02:00
|
|
|
type Client m (RemoteHost :> api) = Client m api
|
2015-06-23 10:34:20 +02:00
|
|
|
|
2017-09-03 08:49:24 +02:00
|
|
|
clientWithRoute pm Proxy req =
|
|
|
|
clientWithRoute pm (Proxy :: Proxy api) req
|
2015-06-23 10:34:20 +02:00
|
|
|
|
2017-09-03 08:49:24 +02:00
|
|
|
instance HasClient m api => HasClient m (IsSecure :> api) where
|
2017-08-28 19:27:05 +02:00
|
|
|
type Client m (IsSecure :> api) = Client m api
|
2015-06-23 10:34:20 +02:00
|
|
|
|
2017-09-03 08:49:24 +02:00
|
|
|
clientWithRoute pm Proxy req =
|
|
|
|
clientWithRoute pm (Proxy :: Proxy api) req
|
2015-11-27 02:05:34 +01:00
|
|
|
|
2017-09-03 08:49:24 +02:00
|
|
|
instance HasClient m subapi =>
|
|
|
|
HasClient m (WithNamedContext name context subapi) where
|
2016-01-18 21:27:19 +01:00
|
|
|
|
2017-08-28 19:27:05 +02:00
|
|
|
type Client m (WithNamedContext name context subapi) = Client m subapi
|
2017-09-03 08:49:24 +02:00
|
|
|
clientWithRoute pm Proxy = clientWithRoute pm (Proxy :: Proxy subapi)
|
2016-01-18 21:27:19 +01:00
|
|
|
|
2017-09-03 08:49:24 +02:00
|
|
|
instance ( HasClient m api
|
|
|
|
) => HasClient m (AuthProtect tag :> api) where
|
2017-08-28 19:27:05 +02:00
|
|
|
type Client m (AuthProtect tag :> api)
|
|
|
|
= AuthenticateReq (AuthProtect tag) -> Client m api
|
2016-02-17 21:45:08 +01:00
|
|
|
|
2017-09-03 08:49:24 +02:00
|
|
|
clientWithRoute pm Proxy req (AuthenticateReq (val,func)) =
|
|
|
|
clientWithRoute pm (Proxy :: Proxy api) (func val req)
|
2015-11-27 02:05:34 +01:00
|
|
|
|
2016-02-17 20:12:47 +01:00
|
|
|
-- * Basic Authentication
|
|
|
|
|
2017-09-03 08:49:24 +02:00
|
|
|
instance HasClient m api => HasClient m (BasicAuth realm usr :> api) where
|
2017-08-28 19:27:05 +02:00
|
|
|
type Client m (BasicAuth realm usr :> api) = BasicAuthData -> Client m api
|
2016-02-17 20:12:47 +01:00
|
|
|
|
2017-09-03 08:49:24 +02:00
|
|
|
clientWithRoute pm Proxy req val =
|
|
|
|
clientWithRoute pm (Proxy :: Proxy api) (basicAuthReq val req)
|
2016-02-17 20:12:47 +01:00
|
|
|
|
|
|
|
|
2015-11-27 02:05:34 +01:00
|
|
|
{- Note [Non-Empty Content Types]
|
|
|
|
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|
|
|
|
Rather than have
|
|
|
|
|
|
|
|
instance (..., cts' ~ (ct ': cts)) => ... cts' ...
|
|
|
|
|
|
|
|
It may seem to make more sense to have:
|
|
|
|
|
|
|
|
instance (...) => ... (ct ': cts) ...
|
|
|
|
|
|
|
|
But this means that if another instance exists that does *not* require
|
|
|
|
non-empty lists, but is otherwise more specific, no instance will be overall
|
2016-01-08 17:43:10 +01:00
|
|
|
more specific. This in turn generally means adding yet another instance (one
|
2015-11-27 02:05:34 +01:00
|
|
|
for empty and one for non-empty lists).
|
|
|
|
-}
|