Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides backend-agnostic functionality for generating clients
from servant
APIs. By "backend," we mean something that concretely
executes the request, such as:
- The
http-client
library - The
haxl
library - GHCJS via FFI
etc.
Each backend is encapsulated in a monad that is an instance of the
RunClient
class.
This library is primarily of interest to backend-writers and combinator-writers. For more information, see the README.md
- clientIn :: HasClient m api => Proxy api -> Proxy m -> Client m api
- class RunClient m => HasClient m api where
- type Request = RequestF Builder
- data RequestF a = Request {}
- defaultRequest :: Request
- newtype RequestBody = RequestBodyLBS ByteString
- mkAuthenticatedRequest :: AuthClientData a -> (AuthClientData a -> Request -> Request) -> AuthenticatedRequest a
- basicAuthReq :: BasicAuthData -> Request -> Request
- newtype AuthenticatedRequest a = AuthenticatedRequest {
- unAuthReq :: (AuthClientData a, AuthClientData a -> Request -> Request)
- type family AuthClientData a :: *
- class ClientLike client custom where
- genericMkClientL :: (Generic custom, Code custom ~ '[xs], GClientList client '[], GClientLikeL (ClientList client '[]) xs) => client -> custom
- genericMkClientP :: (Generic custom, Code custom ~ '[xs], GClientLikeP client xs) => client -> custom
- data ServantError
- data EmptyClient = EmptyClient
- type Response = GenResponse ByteString
- data GenResponse a = Response {}
- class Monad m => RunClient m where
- module Servant.Client.Core.Internal.BaseUrl
- newtype StreamingResponse = StreamingResponse {
- runStreamingResponse :: forall a. (GenResponse (IO ByteString) -> IO a) -> IO a
- addHeader :: ToHttpApiData a => HeaderName -> a -> Request -> Request
- appendToQueryString :: Text -> Maybe Text -> Request -> Request
- appendToPath :: Text -> Request -> Request
- setRequestBodyLBS :: ByteString -> MediaType -> Request -> Request
- setRequestBody :: RequestBody -> MediaType -> Request -> Request
Client generation
clientIn :: HasClient m api => Proxy api -> Proxy m -> Client m api Source #
clientIn
allows you to produce operations to query an API from a client
within a RunClient
monad.
type MyApi = "books" :> Get '[JSON] [Book] -- GET /books :<|> "books" :> ReqBody '[JSON] Book :> Post '[JSON] Book -- POST /books myApi :: Proxy MyApi myApi = Proxy clientM :: Proxy ClientM clientM = Proxy getAllBooks :: ClientM [Book] postNewBook :: Book -> ClientM Book (getAllBooks :<|> postNewBook) = myApi `clientIn` clientM
class RunClient m => HasClient m api where Source #
This class lets us define how each API combinator influences the creation of an HTTP request.
Unless you are writing a new backend for servant-client-core
or new
combinators that you want to support client-generation, you can ignore this
class.
RunClient m => HasClient m Raw Source # | Pick a |
RunClient m => HasClient m EmptyAPI Source # | The client for type MyAPI = "books" :> Get '[JSON] [Book] -- GET /books :<|> "nothing" :> EmptyAPI myApi :: Proxy MyApi myApi = Proxy getAllBooks :: ClientM [Book] (getAllBooks :<|> EmptyClient) = client myApi |
(HasClient m a, HasClient m b) => HasClient m ((:<|>) a b) Source # | A client querying function for type MyApi = "books" :> Get '[JSON] [Book] -- GET /books :<|> "books" :> ReqBody '[JSON] Book :> Post Book -- POST /books myApi :: Proxy MyApi myApi = Proxy getAllBooks :: ClientM [Book] postNewBook :: Book -> ClientM Book (getAllBooks :<|> postNewBook) = client myApi |
HasClient m api => HasClient m ((:>) * (BasicAuth realm usr) api) Source # | |
HasClient m api => HasClient m ((:>) * (AuthProtect k tag) api) Source # | |
HasClient m subapi => HasClient m (WithNamedContext name context subapi) Source # | |
HasClient m api => HasClient m ((:>) * IsSecure api) Source # | |
HasClient m api => HasClient m ((:>) * RemoteHost api) Source # | |
HasClient m api => HasClient m ((:>) * Vault api) Source # | |
(KnownSymbol path, HasClient m api) => HasClient m ((:>) Symbol path api) Source # | Make the querying function append |
(MimeRender * ct a, HasClient m api) => HasClient m ((:>) * (ReqBody' mods ((:) * ct cts) a) api) Source # | If you use a All you need is for your type to have a Example: type MyApi = "books" :> ReqBody '[JSON] Book :> Post '[JSON] Book myApi :: Proxy MyApi myApi = Proxy addBook :: Book -> ClientM Book addBook = client myApi -- then you can just use "addBook" to query that endpoint |
(KnownSymbol sym, HasClient m api) => HasClient m ((:>) * (QueryFlag sym) api) Source # | If you use a If you give Otherwise, this function will insert a value-less query string
parameter under the name associated to your Example: type MyApi = "books" :> QueryFlag "published" :> Get '[JSON] [Book] myApi :: Proxy MyApi myApi = Proxy getBooks :: Bool -> ClientM [Book] getBooks = client myApi -- then you can just use "getBooks" to query that endpoint. -- 'getBooksBy False' for all books -- 'getBooksBy True' to only get _already published_ books |
(KnownSymbol sym, ToHttpApiData a, HasClient m api) => HasClient m ((:>) * (QueryParams sym a) api) Source # | If you use a 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
text by specifying a Example: type MyApi = "books" :> QueryParams "authors" Text :> Get '[JSON] [Book] myApi :: Proxy MyApi myApi = Proxy getBooksBy :: [Text] -> ClientM [Book] getBooksBy = client myApi -- 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 |
(KnownSymbol sym, ToHttpApiData a, HasClient m api, SBoolI (FoldRequired mods)) => HasClient m ((:>) * (QueryParam' mods sym a) api) Source # | If you use a If you give Nothing, nothing will be added to the query string. If you give a non- You can control how values for your type are turned into
text by specifying a Example: type MyApi = "books" :> QueryParam "author" Text :> Get '[JSON] [Book] myApi :: Proxy MyApi myApi = Proxy getBooksBy :: Maybe Text -> ClientM [Book] getBooksBy = client myApi -- 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 |
HasClient m api => HasClient m ((:>) * (Description desc) api) Source # | Ignore |
HasClient m api => HasClient m ((:>) * (Summary desc) api) Source # | Ignore |
HasClient m api => HasClient m ((:>) * HttpVersion api) Source # | Using a |
(KnownSymbol sym, ToHttpApiData a, HasClient m api, SBoolI (FoldRequired mods)) => HasClient m ((:>) * (Header' * mods sym a) api) Source # | If you use a That function will take care of encoding this argument as Text in the request headers. All you need is for your type to have a Example: newtype Referer = Referer { referrer :: Text } deriving (Eq, Show, Generic, ToHttpApiData) -- GET /view-my-referer type MyApi = "view-my-referer" :> Header "Referer" Referer :> Get '[JSON] Referer myApi :: Proxy MyApi myApi = Proxy viewReferer :: Maybe Referer -> ClientM Book viewReferer = client myApi -- then you can just use "viewRefer" to query that endpoint -- specifying Nothing or e.g Just "http://haskell.org/" as arguments |
(KnownSymbol capture, ToHttpApiData a, HasClient m sublayout) => HasClient m ((:>) * (CaptureAll capture a) sublayout) Source # | If you use a You can control how these values are turned into text by specifying
a Example: type MyAPI = "src" :> CaptureAll Text -> Get '[JSON] SourceFile myApi :: Proxy myApi = Proxy getSourceFile :: [Text] -> ClientM SourceFile getSourceFile = client myApi -- then you can use "getSourceFile" to query that endpoint |
(KnownSymbol capture, ToHttpApiData a, HasClient m api) => HasClient m ((:>) * (Capture' mods capture a) api) Source # | If you use a You can control how values for this type are turned into
text by specifying a Example: type MyApi = "books" :> Capture "isbn" Text :> Get '[JSON] Book myApi :: Proxy MyApi myApi = Proxy getBook :: Text -> ClientM Book getBook = client myApi -- then you can just use "getBook" to query that endpoint |
(RunClient m, MimeUnrender * ct a, ReflectMethod k1 method, FramingUnrender * * framing a, BuildFromStream a (f a)) => HasClient m (Stream k1 method framing ct (f a)) Source # | |
(RunClient m, BuildHeadersTo ls, ReflectMethod k1 method) => HasClient m (Verb k1 method status cts (Headers ls NoContent)) Source # | |
(RunClient m, MimeUnrender * ct a, BuildHeadersTo ls, ReflectMethod k1 method, (~) [*] cts' ((:) * ct cts)) => HasClient m (Verb k1 method status cts' (Headers ls a)) Source # | |
(RunClient m, ReflectMethod k1 method) => HasClient m (Verb k1 method status cts NoContent) Source # | |
(RunClient m, MimeUnrender * ct a, ReflectMethod k1 method, (~) [*] cts' ((:) * ct cts)) => HasClient m (Verb k1 method status cts' a) Source # | |
Request
newtype RequestBody Source #
The request body. Currently only lazy ByteStrings are supported.
Authentication
mkAuthenticatedRequest :: AuthClientData a -> (AuthClientData a -> Request -> Request) -> AuthenticatedRequest a Source #
Handy helper to avoid wrapping datatypes in tuples everywhere.
NOTE: THIS API IS EXPERIMENTAL AND SUBJECT TO CHANGE
basicAuthReq :: BasicAuthData -> Request -> Request Source #
Authenticate a request using Basic Authentication
newtype AuthenticatedRequest a Source #
For better type inference and to avoid usage of a data family, we newtype
wrap the combination of some AuthClientData
and a function to add authentication
data to a request
NOTE: THIS API IS EXPERIMENTAL AND SUBJECT TO CHANGE
AuthenticatedRequest | |
|
type family AuthClientData a :: * Source #
For a resource protected by authentication (e.g. AuthProtect), we need to provide the client with some data used to add authentication data to a request
NOTE: THIS API IS EXPERIMENTAL AND SUBJECT TO CHANGE
Generic Client
class ClientLike client custom where Source #
This class allows us to match client structure with client functions
produced with client
without explicit pattern-matching.
The client structure needs a Generic
instance.
Example:
type API = "foo" :> Capture "x" Int :> Get '[JSON] Int :<|> "bar" :> QueryParam "a" Char :> QueryParam "b" String :> Post '[JSON] [Int] :<|> Capture "nested" Int :> NestedAPI type NestedAPI = Get '[JSON] String :<|> "baz" :> QueryParam "c" Char :> Post '[JSON] () data APIClient = APIClient { getFoo :: Int -> ClientM Int , postBar :: Maybe Char -> Maybe String -> ClientM [Int] , mkNestedClient :: Int -> NestedClient } deriving GHC.Generic instance Generics.SOP.Generic APIClient instance (Client API ~ client) => ClientLike client APIClient data NestedClient = NestedClient { getString :: ClientM String , postBaz :: Maybe Char -> ClientM () } deriving GHC.Generic instance Generics.SOP.Generic NestedClient instance (Client NestedAPI ~ client) => ClientLike client NestedClient mkAPIClient :: APIClient mkAPIClient = mkClient (client (Proxy :: Proxy API))
By default, left-nested alternatives are expanded:
type API1 = "foo" :> Capture "x" Int :> Get '[JSON] Int :<|> "bar" :> QueryParam "a" Char :> Post '[JSON] String type API2 = "baz" :> QueryParam "c" Char :> Post '[JSON] () type API = API1 :<|> API2 data APIClient = APIClient { getFoo :: Int -> ClientM Int , postBar :: Maybe Char -> ClientM String , postBaz :: Maybe Char -> ClientM () } deriving GHC.Generic instance Generics.SOP.Generic APIClient instance (Client API ~ client) => ClientLike client APIClient mkAPIClient :: APIClient mkAPIClient = mkClient (client (Proxy :: Proxy API))
If you want to define client for API1
as a separate data structure,
you can use genericMkClientP
:
data APIClient1 = APIClient1 { getFoo :: Int -> ClientM Int , postBar :: Maybe Char -> ClientM String } deriving GHC.Generic instance Generics.SOP.Generic APIClient1 instance (Client API1 ~ client) => ClientLike client APIClient1 data APIClient = APIClient { mkAPIClient1 :: APIClient1 , postBaz :: Maybe Char -> ClientM () } deriving GHC.Generic instance Generics.SOP.Generic APIClient instance (Client API ~ client) => ClientLike client APIClient where mkClient = genericMkClientP mkAPIClient :: APIClient mkAPIClient = mkClient (client (Proxy :: Proxy API))
mkClient :: client -> custom Source #
mkClient :: (Generic custom, Code custom ~ '[xs], GClientList client '[], GClientLikeL (ClientList client '[]) xs) => client -> custom Source #
ClientLike client custom => ClientLike (a -> client) (a -> custom) Source # | |
genericMkClientL :: (Generic custom, Code custom ~ '[xs], GClientList client '[], GClientLikeL (ClientList client '[]) xs) => client -> custom Source #
Generate client structure from client type, expanding left-nested API (done by default).
genericMkClientP :: (Generic custom, Code custom ~ '[xs], GClientLikeP client xs) => client -> custom Source #
Generate client structure from client type, regarding left-nested API clients as separate data structures.
data ServantError Source #
A type representing possible errors in a request
Note that this type substantially changed in 0.12.
FailureResponse Response | The server returned an error response |
DecodeFailure Text Response | The body could not be decoded at the expected type |
UnsupportedContentType MediaType Response | The content-type of the response is not supported |
InvalidContentTypeHeader Response | The content-type header is invalid |
ConnectionError Text | There was a connection error, and no response was received |
data EmptyClient Source #
Singleton type representing a client for an empty API.
Response
type Response = GenResponse ByteString Source #
data GenResponse a Source #
Functor GenResponse Source # | |
Foldable GenResponse Source # | |
Traversable GenResponse Source # | |
Eq a => Eq (GenResponse a) Source # | |
Show a => Show (GenResponse a) Source # | |
Generic (GenResponse a) Source # | |
type Rep (GenResponse a) Source # | |
class Monad m => RunClient m where Source #
runRequest :: Request -> m Response Source #
How to make a request.
streamingRequest :: Request -> m StreamingResponse Source #
throwServantError :: ServantError -> m a Source #
catchServantError :: m a -> (ServantError -> m a) -> m a Source #
newtype StreamingResponse Source #
StreamingResponse | |
|
Writing HasClient instances
These functions need not be re-exported by backend libraries.
addHeader :: ToHttpApiData a => HeaderName -> a -> Request -> Request Source #
setRequestBodyLBS :: ByteString -> MediaType -> Request -> Request Source #
Set body and media type of the request being constructed.
The body is set to the given bytestring using the RequestBodyLBS
constructor.
Since: 0.12
setRequestBody :: RequestBody -> MediaType -> Request -> Request Source #
Set body and media type of the request being constructed.
Since: 0.12