servant-client-0.4.4.7: 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

client :: HasClient layout => Proxy layout -> BaseUrl -> 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 Book -- POST /books

myApi :: Proxy MyApi
myApi = Proxy

getAllBooks :: EitherT String IO [Book]
postNewBook :: Book -> EitherT String IO Book
(getAllBooks :<|> postNewBook) = client myApi host
  where host = BaseUrl Http "localhost" 8080

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.

Associated Types

type Client layout :: * Source

Methods

clientWithRoute :: Proxy layout -> Req -> BaseUrl -> Client layout Source

Instances

HasClient Raw Source

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

(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 :: EitherT String IO [Book]
postNewBook :: Book -> EitherT String IO Book
(getAllBooks :<|> postNewBook) = client myApi host
  where host = BaseUrl Http "localhost" 8080
(MimeUnrender * ct a, BuildHeadersTo ls) => HasClient (Get ((:) * ct cts) (Headers ls a)) Source

If you have a 'Get xs (Headers ls x)' endpoint, the client expects the corresponding headers.

HasClient (Get ((:) * ct cts) ()) Source

If you have a 'Get xs ()' endpoint, the client expects a 204 No Content HTTP status.

MimeUnrender * ct result => HasClient (Get ((:) * ct cts) result) Source

If you have a Get endpoint in your API, the client side querying function that is created when calling client will just require an argument that specifies the scheme, host and port to send the request to.

(MimeUnrender * ct a, BuildHeadersTo ls) => HasClient (Post ((:) * ct cts) (Headers ls a)) Source

If you have a 'Post xs (Headers ls x)' endpoint, the client expects the corresponding headers.

HasClient (Post ((:) * ct cts) ()) Source

If you have a 'Post xs ()' endpoint, the client expects a 204 No Content HTTP header.

MimeUnrender * ct a => HasClient (Post ((:) * ct cts) a) Source

If you have a Post endpoint in your API, the client side querying function that is created when calling client will just require an argument that specifies the scheme, host and port to send the request to.

(MimeUnrender * ct a, BuildHeadersTo ls, (~) [*] cts' ((:) * ct cts)) => HasClient (Delete cts' (Headers ls a)) Source

If you have a 'Delete xs (Headers ls x)' endpoint, the client expects the corresponding headers.

HasClient (Delete cts ()) Source

If you have a 'Delete xs ()' endpoint, the client expects a 204 No Content HTTP header.

(MimeUnrender * ct a, (~) [*] cts' ((:) * ct cts)) => HasClient (Delete cts' a) Source

If you have a Delete endpoint in your API, the client side querying function that is created when calling client will just require an argument that specifies the scheme, host and port to send the request to.

(MimeUnrender * ct a, BuildHeadersTo ls) => HasClient (Put ((:) * ct cts) (Headers ls a)) Source

If you have a 'Put xs (Headers ls x)' endpoint, the client expects the corresponding headers.

HasClient (Put ((:) * ct cts) ()) Source

If you have a 'Put xs ()' endpoint, the client expects a 204 No Content HTTP header.

MimeUnrender * ct a => HasClient (Put ((:) * ct cts) a) Source

If you have a Put endpoint in your API, the client side querying function that is created when calling client will just require an argument that specifies the scheme, host and port to send the request to.

(MimeUnrender * ct a, BuildHeadersTo ls) => HasClient (Patch ((:) * ct cts) (Headers ls a)) Source

If you have a 'Patch xs (Headers ls x)' endpoint, the client expects the corresponding headers.

HasClient (Patch ((:) * ct cts) ()) Source

If you have a 'Patch xs ()' endpoint, the client expects a 204 No Content HTTP header.

MimeUnrender * ct a => HasClient (Patch ((:) * ct cts) a) Source

If you have a Patch endpoint in your API, the client side querying function that is created when calling client will just require an argument that specifies the scheme, host and port to send the request to.

(KnownSymbol capture, ToText a, HasClient sublayout) => HasClient ((:>) * * (Capture * capture a) sublayout) 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 ToText instance for your type.

Example:

type MyApi = "books" :> Capture "isbn" Text :> Get '[JSON] Book

myApi :: Proxy MyApi
myApi = Proxy

getBook :: Text -> EitherT String IO Book
getBook = client myApi host
  where host = BaseUrl Http "localhost" 8080
-- then you can just use "getBook" to query that endpoint
(KnownSymbol sym, ToText a, HasClient sublayout) => HasClient ((:>) * * (Header sym a) sublayout) 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 ToText instance.

Example:

newtype Referer = Referer { referrer :: Text }
  deriving (Eq, Show, Generic, FromText, ToText)

           -- GET /view-my-referer
type MyApi = "view-my-referer" :> Header "Referer" Referer :> Get '[JSON] Referer

myApi :: Proxy MyApi
myApi = Proxy

viewReferer :: Maybe Referer -> EitherT String IO Book
viewReferer = client myApi host
  where host = BaseUrl Http "localhost" 8080
-- then you can just use "viewRefer" to query that endpoint
-- specifying Nothing or e.g Just "http://haskell.org/" as arguments
(KnownSymbol sym, ToText a, HasClient sublayout) => HasClient ((:>) * * (QueryParam * sym a) sublayout) 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 ToText instance for your type.

Example:

type MyApi = "books" :> QueryParam "author" Text :> Get '[JSON] [Book]

myApi :: Proxy MyApi
myApi = Proxy

getBooksBy :: Maybe Text -> EitherT String IO [Book]
getBooksBy = client myApi host
  where host = BaseUrl Http "localhost" 8080
-- 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
(KnownSymbol sym, ToText a, HasClient sublayout) => HasClient ((:>) * * (QueryParams * sym a) sublayout) 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 ToText instance for your type.

Example:

type MyApi = "books" :> QueryParams "authors" Text :> Get '[JSON] [Book]

myApi :: Proxy MyApi
myApi = Proxy

getBooksBy :: [Text] -> EitherT String IO [Book]
getBooksBy = client myApi host
  where host = BaseUrl Http "localhost" 8080
-- 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, HasClient sublayout) => HasClient ((:>) * * (QueryFlag sym) sublayout) 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 -> EitherT String IO [Book]
getBooks = client myApi host
  where host = BaseUrl Http "localhost" 8080
-- then you can just use "getBooks" to query that endpoint.
-- 'getBooksBy False' for all books
-- 'getBooksBy True' to only get _already published_ books
(MimeRender * ct a, HasClient sublayout) => HasClient ((:>) * * (ReqBody * ((:) * ct cts) a) sublayout) 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 -> EitherT String IO Book
addBook = client myApi host
  where host = BaseUrl Http "localhost" 8080
-- then you can just use "addBook" to query that endpoint
(KnownSymbol sym, ToText a, HasClient sublayout) => HasClient ((:>) * * (MatrixParam * sym a) sublayout) Source

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

Example:

type MyApi = "books" :> MatrixParam "author" Text :> Get '[JSON] [Book]

myApi :: Proxy MyApi
myApi = Proxy

getBooksBy :: Maybe Text -> EitherT String IO [Book]
getBooksBy = client myApi host
  where host = BaseUrl Http "localhost" 8080
-- 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
(KnownSymbol sym, ToText a, HasClient sublayout) => HasClient ((:>) * * (MatrixParams * sym a) sublayout) Source

If you use a MatrixParams 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 MatrixParams.

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 path segment string, under the same matrix string parameter name.

You can control how values for your type are turned into text by specifying a ToText instance for your type.

Example:

type MyApi = "books" :> MatrixParams "authors" Text :> Get '[JSON] [Book]

myApi :: Proxy MyApi
myApi = Proxy

getBooksBy :: [Text] -> EitherT String IO [Book]
getBooksBy = client myApi host
  where host = BaseUrl Http "localhost" 8080
-- 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, HasClient sublayout) => HasClient ((:>) * * (MatrixFlag sym) sublayout) Source

If you use a MatrixFlag 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 path segment.

Otherwise, this function will insert a value-less matrix parameter under the name associated to your MatrixFlag.

Example:

type MyApi = "books" :> MatrixFlag "published" :> Get '[JSON] [Book]

myApi :: Proxy MyApi
myApi = Proxy

getBooks :: Bool -> EitherT String IO [Book]
getBooks = client myApi host
  where host = BaseUrl Http "localhost" 8080
-- then you can just use "getBooks" to query that endpoint.
-- 'getBooksBy False' for all books
-- 'getBooksBy True' to only get _already published_ books
(KnownSymbol path, HasClient sublayout) => HasClient ((:>) Symbol * path sublayout) Source

Make the querying function append path to the request path.