Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides client
which can automatically generate
querying functions for each endpoint just from the type representing your
API.
- type family AuthClientData a :: *
- newtype AuthenticateReq a = AuthenticateReq {
- unAuthReq :: (AuthClientData a, AuthClientData a -> Req -> Req)
- client :: HasClient layout => Proxy layout -> Client layout
- class HasClient layout where
- type Client layout :: *
- clientWithRoute :: Proxy layout -> Req -> Client layout
- type ClientM = ExceptT ServantError IO
- mkAuthenticateReq :: AuthClientData a -> (AuthClientData a -> Req -> Req) -> AuthenticateReq a
- data ServantError
- = FailureResponse { }
- | DecodeFailure { }
- | UnsupportedContentType { }
- | InvalidContentTypeHeader { }
- | ConnectionError { }
- module Servant.Common.BaseUrl
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
AuthenticateReq | |
|
client :: HasClient layout => Proxy layout -> Client layout 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 :: Manager -> BaseUrl -> ClientM [Book] postNewBook :: Book -> Manager -> BaseUrl -> ClientM Book (getAllBooks :<|> postNewBook) = client myApi
class HasClient layout 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
.
clientWithRoute :: Proxy layout -> Req -> Client layout Source
HasClient * Raw Source | Pick a |
(HasClient * a, HasClient * b) => HasClient * ((:<|>) 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 :: Manager -> BaseUrl -> ClientM [Book] postNewBook :: Book -> Manager -> BaseUrl -> ClientM Book (getAllBooks :<|> postNewBook) = client myApi |
HasClient * subapi => HasClient * (WithNamedContext name context subapi) Source | |
HasClient k api => HasClient * ((:>) * k (BasicAuth realm usr) api) Source | |
HasClient k api => HasClient * ((:>) * k (AuthProtect k tag) api) Source | |
HasClient k api => HasClient * ((:>) * k IsSecure api) Source | |
HasClient k api => HasClient * ((:>) * k RemoteHost api) Source | |
HasClient k api => HasClient * ((:>) * k Vault api) Source | |
(MimeRender * ct a, HasClient k sublayout) => HasClient * ((:>) * k (ReqBody * ((:) * ct cts) a) sublayout) 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 -> Manager -> BaseUrl -> ClientM Book addBook = client myApi -- then you can just use "addBook" to query that endpoint |
(KnownSymbol sym, HasClient k sublayout) => HasClient * ((:>) * k (QueryFlag sym) sublayout) 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 -> Manager -> BaseUrl -> 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 k sublayout) => HasClient * ((:>) * k (QueryParams * sym a) sublayout) 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] -> Manager -> BaseUrl -> 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 k sublayout) => HasClient * ((:>) * k (QueryParam * sym a) sublayout) 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 -> Manager -> BaseUrl -> 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 k sublayout => HasClient * ((:>) * k HttpVersion sublayout) Source | Using a |
(KnownSymbol sym, ToHttpApiData a, HasClient k sublayout) => HasClient * ((:>) * k (Header sym a) sublayout) 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 -> Manager -> BaseUrl -> 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 k sublayout) => HasClient * ((:>) * k (Capture * capture a) sublayout) 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 -> Manager -> BaseUrl -> ClientM Book getBook = client myApi -- then you can just use "getBook" to query that endpoint |
(KnownSymbol path, HasClient k sublayout) => HasClient * ((:>) Symbol k path sublayout) Source | Make the querying function append |
(BuildHeadersTo ls, ReflectMethod k method) => HasClient * (Verb k * method status cts (Headers ls NoContent)) Source | |
(MimeUnrender * ct a, BuildHeadersTo ls, ReflectMethod k method, (~) [*] cts' ((:) * ct cts)) => HasClient * (Verb k * method status cts' (Headers ls a)) Source | |
ReflectMethod k method => HasClient * (Verb k * method status cts NoContent) Source | |
(MimeUnrender * ct a, ReflectMethod k method, (~) [*] cts' ((:) * ct cts)) => HasClient * (Verb k * method status cts' a) Source |
type ClientM = ExceptT ServantError IO Source
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
data ServantError Source
module Servant.Common.BaseUrl