servant-client-0.9.0.1: automatical derivation of querying functions for servant webservices

Safe HaskellNone
LanguageHaskell2010

Servant.Client

Description

This module provides client which can automatically generate querying functions for each endpoint just from the type representing your API.

Synopsis

Documentation

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

newtype AuthenticateReq 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

Constructors

AuthenticateReq 

client :: HasClient api => Proxy api -> Client api Source #

client allows you to produce operations to query an API from a client.

type MyApi = "books" :> Get '[JSON] [Book] -- GET /books
        :<|> "books" :> ReqBody '[JSON] Book :> Post '[JSON] Book -- POST /books

myApi :: Proxy MyApi
myApi = Proxy

getAllBooks :: ClientM [Book]
postNewBook :: Book -> ClientM Book
(getAllBooks :<|> postNewBook) = client myApi

class HasClient api where Source #

This class lets us define how each API combinator influences the creation of an HTTP request. It's mostly an internal class, you can just use client.

Minimal complete definition

clientWithRoute

Associated Types

type Client api :: * Source #

Methods

clientWithRoute :: Proxy api -> Req -> Client api Source #

Instances

HasClient * Raw Source #

Pick a Method and specify where the server you want to query is. You get back the full Response.

Associated Types

type Client Raw (api :: Raw) :: * Source #

Methods

clientWithRoute :: Proxy Raw api -> Req -> Client Raw api Source #

(HasClient * a, HasClient * b) => HasClient * ((:<|>) a b) Source #

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.

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

Associated Types

type Client ((:<|>) a b) (api :: (:<|>) a b) :: * Source #

Methods

clientWithRoute :: Proxy (a :<|> b) api -> Req -> Client (a :<|> b) api Source #

HasClient * subapi => HasClient * (WithNamedContext name context subapi) Source # 

Associated Types

type Client (WithNamedContext name context subapi) (api :: WithNamedContext name context subapi) :: * Source #

Methods

clientWithRoute :: Proxy (WithNamedContext name context subapi) api -> Req -> Client (WithNamedContext name context subapi) api Source #

HasClient k1 api => HasClient * ((:>) * k1 (BasicAuth realm usr) api) Source # 

Associated Types

type Client ((:>) * k1 (BasicAuth realm usr) api) (api :: (:>) * k1 (BasicAuth realm usr) api) :: * Source #

Methods

clientWithRoute :: Proxy ((* :> k1) (BasicAuth realm usr) api) api -> Req -> Client ((* :> k1) (BasicAuth realm usr) api) api Source #

HasClient k1 api => HasClient * ((:>) * k1 (AuthProtect k tag) api) Source # 

Associated Types

type Client ((:>) * k1 (AuthProtect k tag) api) (api :: (:>) * k1 (AuthProtect k tag) api) :: * Source #

Methods

clientWithRoute :: Proxy ((* :> k1) (AuthProtect k tag) api) api -> Req -> Client ((* :> k1) (AuthProtect k tag) api) api Source #

HasClient k1 api => HasClient * ((:>) * k1 IsSecure api) Source # 

Associated Types

type Client ((:>) * k1 IsSecure api) (api :: (:>) * k1 IsSecure api) :: * Source #

Methods

clientWithRoute :: Proxy ((* :> k1) IsSecure api) api -> Req -> Client ((* :> k1) IsSecure api) api Source #

HasClient k1 api => HasClient * ((:>) * k1 RemoteHost api) Source # 

Associated Types

type Client ((:>) * k1 RemoteHost api) (api :: (:>) * k1 RemoteHost api) :: * Source #

Methods

clientWithRoute :: Proxy ((* :> k1) RemoteHost api) api -> Req -> Client ((* :> k1) RemoteHost api) api Source #

HasClient k1 api => HasClient * ((:>) * k1 Vault api) Source # 

Associated Types

type Client ((:>) * k1 Vault api) (api :: (:>) * k1 Vault api) :: * Source #

Methods

clientWithRoute :: Proxy ((* :> k1) Vault api) api -> Req -> Client ((* :> k1) Vault api) api Source #

(MimeRender * ct a, HasClient k1 api) => HasClient * ((:>) * k1 (ReqBody * ((:) * ct cts) a) api) Source #

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:

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

Associated Types

type Client ((:>) * k1 (ReqBody * ((:) * ct cts) a) api) (api :: (:>) * k1 (ReqBody * ((:) * ct cts) a) api) :: * Source #

Methods

clientWithRoute :: Proxy ((* :> k1) (ReqBody * ((* ': ct) cts) a) api) api -> Req -> Client ((* :> k1) (ReqBody * ((* ': ct) cts) a) api) api Source #

(KnownSymbol sym, HasClient k1 api) => HasClient * ((:>) * k1 (QueryFlag sym) api) Source #

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:

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

Associated Types

type Client ((:>) * k1 (QueryFlag sym) api) (api :: (:>) * k1 (QueryFlag sym) api) :: * Source #

Methods

clientWithRoute :: Proxy ((* :> k1) (QueryFlag sym) api) api -> Req -> Client ((* :> k1) (QueryFlag sym) api) api Source #

(KnownSymbol sym, ToHttpApiData a, HasClient k1 api) => HasClient * ((:>) * k1 (QueryParams * sym a) api) Source #

If you use a QueryParams in one of your endpoints in your API, the corresponding querying function will automatically take an additional argument, a list of values of the type specified 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 text by specifying a ToHttpApiData instance for your type.

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

Associated Types

type Client ((:>) * k1 (QueryParams * sym a) api) (api :: (:>) * k1 (QueryParams * sym a) api) :: * Source #

Methods

clientWithRoute :: Proxy ((* :> k1) (QueryParams * sym a) api) api -> Req -> Client ((* :> k1) (QueryParams * sym a) api) api Source #

(KnownSymbol sym, ToHttpApiData a, HasClient k1 api) => HasClient * ((:>) * k1 (QueryParam * sym a) api) Source #

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 text by specifying a ToHttpApiData instance for your type.

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

Associated Types

type Client ((:>) * k1 (QueryParam * sym a) api) (api :: (:>) * k1 (QueryParam * sym a) api) :: * Source #

Methods

clientWithRoute :: Proxy ((* :> k1) (QueryParam * sym a) api) api -> Req -> Client ((* :> k1) (QueryParam * sym a) api) api Source #

HasClient k1 api => HasClient * ((:>) * k1 HttpVersion api) Source #

Using a HttpVersion combinator in your API doesn't affect the client functions.

Associated Types

type Client ((:>) * k1 HttpVersion api) (api :: (:>) * k1 HttpVersion api) :: * Source #

Methods

clientWithRoute :: Proxy ((* :> k1) HttpVersion api) api -> Req -> Client ((* :> k1) HttpVersion api) api Source #

(KnownSymbol sym, ToHttpApiData a, HasClient k1 api) => HasClient * ((:>) * k1 (Header sym a) api) Source #

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.

All you need is for your type to have a ToHttpApiData instance.

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

Associated Types

type Client ((:>) * k1 (Header sym a) api) (api :: (:>) * k1 (Header sym a) api) :: * Source #

Methods

clientWithRoute :: Proxy ((* :> k1) (Header sym a) api) api -> Req -> Client ((* :> k1) (Header sym a) api) api Source #

(KnownSymbol capture, ToHttpApiData a, HasClient k1 sublayout) => HasClient * ((:>) * k1 (CaptureAll * capture a) sublayout) Source #

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
getSourceFile :: [Text] -> ClientM SourceFile
getSourceFile = client myApi
-- then you can use "getSourceFile" to query that endpoint

Associated Types

type Client ((:>) * k1 (CaptureAll * capture a) sublayout) (api :: (:>) * k1 (CaptureAll * capture a) sublayout) :: * Source #

Methods

clientWithRoute :: Proxy ((* :> k1) (CaptureAll * capture a) sublayout) api -> Req -> Client ((* :> k1) (CaptureAll * capture a) sublayout) api Source #

(KnownSymbol capture, ToHttpApiData a, HasClient k1 api) => HasClient * ((:>) * k1 (Capture * capture a) api) Source #

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 text by specifying a ToHttpApiData instance for your type.

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

Associated Types

type Client ((:>) * k1 (Capture * capture a) api) (api :: (:>) * k1 (Capture * capture a) api) :: * Source #

Methods

clientWithRoute :: Proxy ((* :> k1) (Capture * capture a) api) api -> Req -> Client ((* :> k1) (Capture * capture a) api) api Source #

(KnownSymbol path, HasClient k1 api) => HasClient * ((:>) Symbol k1 path api) Source #

Make the querying function append path to the request path.

Associated Types

type Client ((:>) Symbol k1 path api) (api :: (:>) Symbol k1 path api) :: * Source #

Methods

clientWithRoute :: Proxy ((Symbol :> k1) path api) api -> Req -> Client ((Symbol :> k1) path api) api Source #

(BuildHeadersTo ls, ReflectMethod k1 method) => HasClient * (Verb k1 * method status cts (Headers ls NoContent)) Source # 

Associated Types

type Client (Verb k1 * method status cts (Headers ls NoContent)) (api :: Verb k1 * method status cts (Headers ls NoContent)) :: * Source #

Methods

clientWithRoute :: Proxy (Verb k1 * method status cts (Headers ls NoContent)) api -> Req -> Client (Verb k1 * method status cts (Headers ls NoContent)) api Source #

(MimeUnrender * ct a, BuildHeadersTo ls, ReflectMethod k1 method, (~) [*] cts' ((:) * ct cts)) => HasClient * (Verb k1 * method status cts' (Headers ls a)) Source # 

Associated Types

type Client (Verb k1 * method status cts' (Headers ls a)) (api :: Verb k1 * method status cts' (Headers ls a)) :: * Source #

Methods

clientWithRoute :: Proxy (Verb k1 * method status cts' (Headers ls a)) api -> Req -> Client (Verb k1 * method status cts' (Headers ls a)) api Source #

ReflectMethod k1 method => HasClient * (Verb k1 * method status cts NoContent) Source # 

Associated Types

type Client (Verb k1 * method status cts NoContent) (api :: Verb k1 * method status cts NoContent) :: * Source #

Methods

clientWithRoute :: Proxy (Verb k1 * method status cts NoContent) api -> Req -> Client (Verb k1 * method status cts NoContent) api Source #

(MimeUnrender * ct a, ReflectMethod k1 method, (~) [*] cts' ((:) * ct cts)) => HasClient * (Verb k1 * method status cts' a) Source # 

Associated Types

type Client (Verb k1 * method status cts' a) (api :: Verb k1 * method status cts' a) :: * Source #

Methods

clientWithRoute :: Proxy (Verb k1 * method status cts' a) api -> Req -> Client (Verb k1 * method status cts' a) api Source #

data ClientM a Source #

ClientM is the monad in which client functions run. Contains the Manager and BaseUrl used for requests in the reader environment.

Instances

Monad ClientM Source # 

Methods

(>>=) :: ClientM a -> (a -> ClientM b) -> ClientM b #

(>>) :: ClientM a -> ClientM b -> ClientM b #

return :: a -> ClientM a #

fail :: String -> ClientM a #

Functor ClientM Source # 

Methods

fmap :: (a -> b) -> ClientM a -> ClientM b #

(<$) :: a -> ClientM b -> ClientM a #

Applicative ClientM Source # 

Methods

pure :: a -> ClientM a #

(<*>) :: ClientM (a -> b) -> ClientM a -> ClientM b #

(*>) :: ClientM a -> ClientM b -> ClientM b #

(<*) :: ClientM a -> ClientM b -> ClientM a #

MonadIO ClientM Source # 

Methods

liftIO :: IO a -> ClientM a #

MonadError ServantError ClientM Source # 
MonadReader ClientEnv ClientM Source # 

Methods

ask :: ClientM ClientEnv #

local :: (ClientEnv -> ClientEnv) -> ClientM a -> ClientM a #

reader :: (ClientEnv -> a) -> ClientM a #

Generic (ClientM a) Source # 

Associated Types

type Rep (ClientM a) :: * -> * #

Methods

from :: ClientM a -> Rep (ClientM a) x #

to :: Rep (ClientM a) x -> ClientM a #

type Rep (ClientM a) Source # 
type Rep (ClientM a) = D1 (MetaData "ClientM" "Servant.Common.Req" "servant-client-0.9.0.1-9klWedFNr0JLJqInwW9G1B" True) (C1 (MetaCons "ClientM" PrefixI True) (S1 (MetaSel (Just Symbol "runClientM'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ReaderT * ClientEnv (ExceptT ServantError IO) a))))

mkAuthenticateReq :: AuthClientData a -> (AuthClientData a -> Req -> Req) -> AuthenticateReq a Source #

Handy helper to avoid wrapping datatypes in tuples everywhere.

NOTE: THIS API IS EXPERIMENTAL AND SUBJECT TO CHANGE