Safe Haskell | None |
---|---|
Language | Haskell2010 |
Servant.Client.Core
Description
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
Synopsis
- clientIn :: HasClient m api => Proxy api -> Proxy m -> Client m api
- class RunClient m => HasClient m api where
- type Client (m :: * -> *) (api :: *) :: *
- clientWithRoute :: Proxy m -> Proxy api -> Request -> Client m api
- hoistClientMonad :: Proxy m -> Proxy api -> (forall x. mon x -> mon' x) -> Client mon api -> Client mon' api
- type Request = RequestF RequestBody Builder
- data RequestF body path = Request {
- requestPath :: path
- requestQueryString :: Seq QueryItem
- requestBody :: Maybe (body, MediaType)
- requestAccept :: Seq MediaType
- requestHeaders :: Seq Header
- requestHttpVersion :: HttpVersion
- requestMethod :: Method
- defaultRequest :: Request
- data RequestBody
- = RequestBodyLBS ByteString
- | RequestBodyBS ByteString
- | RequestBodySource (SourceIO 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 :: *
- data ClientError
- = FailureResponse (RequestF () (BaseUrl, ByteString)) Response
- | DecodeFailure Text Response
- | UnsupportedContentType MediaType Response
- | InvalidContentTypeHeader Response
- | ConnectionError SomeException
- data EmptyClient = EmptyClient
- type Response = ResponseF ByteString
- data ResponseF a = Response {}
- class Monad m => RunClient m where
- runRequest :: Request -> m Response
- throwClientError :: ClientError -> m a
- data BaseUrl = BaseUrl {
- baseUrlScheme :: Scheme
- baseUrlHost :: String
- baseUrlPort :: Int
- baseUrlPath :: String
- data Scheme
- showBaseUrl :: BaseUrl -> String
- parseBaseUrl :: MonadThrow m => String -> m BaseUrl
- newtype InvalidBaseUrlException = InvalidBaseUrlException String
- class RunClient m => RunStreamingClient m where
- withStreamingRequest :: Request -> (StreamingResponse -> IO a) -> m a
- type StreamingResponse = ResponseF (SourceIO ByteString)
- 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.
Methods
clientWithRoute :: Proxy m -> Proxy api -> Request -> Client m api Source #
hoistClientMonad :: Proxy m -> Proxy api -> (forall x. mon x -> mon' x) -> Client mon api -> Client mon' api Source #
Instances
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 |
Defined in Servant.Client.Core.HasClient | |
(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 |
Defined in Servant.Client.Core.HasClient | |
HasClient m api => HasClient m (BasicAuth realm usr :> api) Source # | |
Defined in Servant.Client.Core.HasClient Methods clientWithRoute :: Proxy m -> Proxy (BasicAuth realm usr :> api) -> Request -> Client m (BasicAuth realm usr :> api) Source # hoistClientMonad :: Proxy m -> Proxy (BasicAuth realm usr :> api) -> (forall x. mon x -> mon' x) -> Client mon (BasicAuth realm usr :> api) -> Client mon' (BasicAuth realm usr :> api) Source # | |
HasClient m api => HasClient m (AuthProtect tag :> api) Source # | |
Defined in Servant.Client.Core.HasClient Associated Types type Client m (AuthProtect tag :> api) Source # Methods clientWithRoute :: Proxy m -> Proxy (AuthProtect tag :> api) -> Request -> Client m (AuthProtect tag :> api) Source # hoistClientMonad :: Proxy m -> Proxy (AuthProtect tag :> api) -> (forall x. mon x -> mon' x) -> Client mon (AuthProtect tag :> api) -> Client mon' (AuthProtect tag :> api) Source # | |
HasClient m subapi => HasClient m (WithNamedContext name context subapi) Source # | |
Defined in Servant.Client.Core.HasClient Associated Types type Client m (WithNamedContext name context subapi) Source # Methods clientWithRoute :: Proxy m -> Proxy (WithNamedContext name context subapi) -> Request -> Client m (WithNamedContext name context subapi) Source # hoistClientMonad :: Proxy m -> Proxy (WithNamedContext name context subapi) -> (forall x. mon x -> mon' x) -> Client mon (WithNamedContext name context subapi) -> Client mon' (WithNamedContext name context subapi) Source # | |
HasClient m api => HasClient m (IsSecure :> api) Source # | |
Defined in Servant.Client.Core.HasClient | |
HasClient m api => HasClient m (RemoteHost :> api) Source # | |
Defined in Servant.Client.Core.HasClient Associated Types type Client m (RemoteHost :> api) Source # Methods clientWithRoute :: Proxy m -> Proxy (RemoteHost :> api) -> Request -> Client m (RemoteHost :> api) Source # hoistClientMonad :: Proxy m -> Proxy (RemoteHost :> api) -> (forall x. mon x -> mon' x) -> Client mon (RemoteHost :> api) -> Client mon' (RemoteHost :> api) Source # | |
HasClient m api => HasClient m (Vault :> api) Source # | |
Defined in Servant.Client.Core.HasClient | |
(KnownSymbol path, HasClient m api) => HasClient m (path :> api) Source # | Make the querying function append |
Defined in Servant.Client.Core.HasClient | |
(HasClient m api, MimeRender ctype chunk, FramingRender framing, ToSourceIO chunk a) => HasClient m (StreamBody' mods framing ctype a :> api) Source # | |
Defined in Servant.Client.Core.HasClient Associated Types type Client m (StreamBody' mods framing ctype a :> api) Source # Methods clientWithRoute :: Proxy m -> Proxy (StreamBody' mods framing ctype a :> api) -> Request -> Client m (StreamBody' mods framing ctype a :> api) Source # hoistClientMonad :: Proxy m -> Proxy (StreamBody' mods framing ctype a :> api) -> (forall x. mon x -> mon' x) -> Client mon (StreamBody' mods framing ctype a :> api) -> Client mon' (StreamBody' mods framing ctype a :> api) Source # | |
(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 |
Defined in Servant.Client.Core.HasClient Methods clientWithRoute :: Proxy m -> Proxy (ReqBody' mods (ct ': cts) a :> api) -> Request -> Client m (ReqBody' mods (ct ': cts) a :> api) Source # hoistClientMonad :: Proxy m -> Proxy (ReqBody' mods (ct ': cts) a :> api) -> (forall x. mon x -> mon' x) -> Client mon (ReqBody' mods (ct ': cts) a :> api) -> Client mon' (ReqBody' mods (ct ': cts) a :> api) Source # | |
(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 |
Defined in Servant.Client.Core.HasClient | |
(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 |
Defined in Servant.Client.Core.HasClient Associated Types type Client m (QueryParams sym a :> api) Source # Methods clientWithRoute :: Proxy m -> Proxy (QueryParams sym a :> api) -> Request -> Client m (QueryParams sym a :> api) Source # hoistClientMonad :: Proxy m -> Proxy (QueryParams sym a :> api) -> (forall x. mon x -> mon' x) -> Client mon (QueryParams sym a :> api) -> Client mon' (QueryParams sym a :> api) Source # | |
(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 |
Defined in Servant.Client.Core.HasClient Associated Types type Client m (QueryParam' mods sym a :> api) Source # Methods clientWithRoute :: Proxy m -> Proxy (QueryParam' mods sym a :> api) -> Request -> Client m (QueryParam' mods sym a :> api) Source # hoistClientMonad :: Proxy m -> Proxy (QueryParam' mods sym a :> api) -> (forall x. mon x -> mon' x) -> Client mon (QueryParam' mods sym a :> api) -> Client mon' (QueryParam' mods sym a :> api) Source # | |
HasClient m api => HasClient m (Description desc :> api) Source # | Ignore |
Defined in Servant.Client.Core.HasClient Associated Types type Client m (Description desc :> api) Source # Methods clientWithRoute :: Proxy m -> Proxy (Description desc :> api) -> Request -> Client m (Description desc :> api) Source # hoistClientMonad :: Proxy m -> Proxy (Description desc :> api) -> (forall x. mon x -> mon' x) -> Client mon (Description desc :> api) -> Client mon' (Description desc :> api) Source # | |
HasClient m api => HasClient m (Summary desc :> api) Source # | Ignore |
Defined in Servant.Client.Core.HasClient | |
HasClient m api => HasClient m (HttpVersion :> api) Source # | Using a |
Defined in Servant.Client.Core.HasClient Associated Types type Client m (HttpVersion :> api) Source # Methods clientWithRoute :: Proxy m -> Proxy (HttpVersion :> api) -> Request -> Client m (HttpVersion :> api) Source # hoistClientMonad :: Proxy m -> Proxy (HttpVersion :> api) -> (forall x. mon x -> mon' x) -> Client mon (HttpVersion :> api) -> Client mon' (HttpVersion :> api) Source # | |
(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 |
Defined in Servant.Client.Core.HasClient Methods clientWithRoute :: Proxy m -> Proxy (Header' mods sym a :> api) -> Request -> Client m (Header' mods sym a :> api) Source # hoistClientMonad :: Proxy m -> Proxy (Header' mods sym a :> api) -> (forall x. mon x -> mon' x) -> Client mon (Header' mods sym a :> api) -> Client mon' (Header' mods sym a :> api) Source # | |
(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 |
Defined in Servant.Client.Core.HasClient Associated Types type Client m (CaptureAll capture a :> sublayout) Source # Methods clientWithRoute :: Proxy m -> Proxy (CaptureAll capture a :> sublayout) -> Request -> Client m (CaptureAll capture a :> sublayout) Source # hoistClientMonad :: Proxy m -> Proxy (CaptureAll capture a :> sublayout) -> (forall x. mon x -> mon' x) -> Client mon (CaptureAll capture a :> sublayout) -> Client mon' (CaptureAll capture a :> sublayout) Source # | |
(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 |
Defined in Servant.Client.Core.HasClient Methods clientWithRoute :: Proxy m -> Proxy (Capture' mods capture a :> api) -> Request -> Client m (Capture' mods capture a :> api) Source # hoistClientMonad :: Proxy m -> Proxy (Capture' mods capture a :> api) -> (forall x. mon x -> mon' x) -> Client mon (Capture' mods capture a :> api) -> Client mon' (Capture' mods capture a :> api) Source # | |
(RunClient m, BuildHeadersTo ls, ReflectMethod method) => HasClient m (Verb method status cts (Headers ls NoContent)) Source # | |
Defined in Servant.Client.Core.HasClient Methods clientWithRoute :: Proxy m -> Proxy (Verb method status cts (Headers ls NoContent)) -> Request -> Client m (Verb method status cts (Headers ls NoContent)) Source # hoistClientMonad :: Proxy m -> Proxy (Verb method status cts (Headers ls NoContent)) -> (forall x. mon x -> mon' x) -> Client mon (Verb method status cts (Headers ls NoContent)) -> Client mon' (Verb method status cts (Headers ls NoContent)) Source # | |
(RunClient m, MimeUnrender ct a, BuildHeadersTo ls, ReflectMethod method, cts' ~ (ct ': cts)) => HasClient m (Verb method status cts' (Headers ls a)) Source # | |
Defined in Servant.Client.Core.HasClient Methods clientWithRoute :: Proxy m -> Proxy (Verb method status cts' (Headers ls a)) -> Request -> Client m (Verb method status cts' (Headers ls a)) Source # hoistClientMonad :: Proxy m -> Proxy (Verb method status cts' (Headers ls a)) -> (forall x. mon x -> mon' x) -> Client mon (Verb method status cts' (Headers ls a)) -> Client mon' (Verb method status cts' (Headers ls a)) Source # | |
(RunClient m, ReflectMethod method) => HasClient m (Verb method status cts NoContent) Source # | |
Defined in Servant.Client.Core.HasClient Methods clientWithRoute :: Proxy m -> Proxy (Verb method status cts NoContent) -> Request -> Client m (Verb method status cts NoContent) Source # hoistClientMonad :: Proxy m -> Proxy (Verb method status cts NoContent) -> (forall x. mon x -> mon' x) -> Client mon (Verb method status cts NoContent) -> Client mon' (Verb method status cts NoContent) Source # | |
(RunClient m, MimeUnrender ct a, ReflectMethod method, cts' ~ (ct ': cts)) => HasClient m (Verb method status cts' a) Source # | |
Defined in Servant.Client.Core.HasClient Methods clientWithRoute :: Proxy m -> Proxy (Verb method status cts' a) -> Request -> Client m (Verb method status cts' a) Source # hoistClientMonad :: Proxy m -> Proxy (Verb method status cts' a) -> (forall x. mon x -> mon' x) -> Client mon (Verb method status cts' a) -> Client mon' (Verb method status cts' a) Source # | |
(RunStreamingClient m, MimeUnrender ct chunk, ReflectMethod method, FramingUnrender framing, FromSourceIO chunk a) => HasClient m (Stream method status framing ct a) Source # | |
Defined in Servant.Client.Core.HasClient Methods clientWithRoute :: Proxy m -> Proxy (Stream method status framing ct a) -> Request -> Client m (Stream method status framing ct a) Source # hoistClientMonad :: Proxy m -> Proxy (Stream method status framing ct a) -> (forall x. mon x -> mon' x) -> Client mon (Stream method status framing ct a) -> Client mon' (Stream method status framing ct a) Source # |
Request
type Request = RequestF RequestBody Builder Source #
data RequestF body path Source #
Constructors
Request | |
Fields
|
Instances
Bitraversable RequestF Source # | |
Defined in Servant.Client.Core.Request Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> RequestF a b -> f (RequestF c d) | |
Bifunctor RequestF Source # | |
Bifoldable RequestF Source # | |
Functor (RequestF body) Source # | |
Foldable (RequestF body) Source # | |
Defined in Servant.Client.Core.Request Methods fold :: Monoid m => RequestF body m -> m foldMap :: Monoid m => (a -> m) -> RequestF body a -> m foldMap' :: Monoid m => (a -> m) -> RequestF body a -> m foldr :: (a -> b -> b) -> b -> RequestF body a -> b foldr' :: (a -> b -> b) -> b -> RequestF body a -> b foldl :: (b -> a -> b) -> b -> RequestF body a -> b foldl' :: (b -> a -> b) -> b -> RequestF body a -> b foldr1 :: (a -> a -> a) -> RequestF body a -> a foldl1 :: (a -> a -> a) -> RequestF body a -> a toList :: RequestF body a -> [a] null :: RequestF body a -> Bool length :: RequestF body a -> Int elem :: Eq a => a -> RequestF body a -> Bool maximum :: Ord a => RequestF body a -> a minimum :: Ord a => RequestF body a -> a | |
Traversable (RequestF body) Source # | |
Defined in Servant.Client.Core.Request Methods traverse :: Applicative f => (a -> f b) -> RequestF body a -> f (RequestF body b) sequenceA :: Applicative f => RequestF body (f a) -> f (RequestF body a) mapM :: Monad m => (a -> m b) -> RequestF body a -> m (RequestF body b) # sequence :: Monad m => RequestF body (m a) -> m (RequestF body a) # | |
(Eq path, Eq body) => Eq (RequestF body path) Source # | |
(Show path, Show body) => Show (RequestF body path) Source # | |
Generic (RequestF body path) Source # | |
(NFData path, NFData body) => NFData (RequestF body path) Source # | |
Defined in Servant.Client.Core.Request | |
type Rep (RequestF body path) Source # | |
Defined in Servant.Client.Core.Request type Rep (RequestF body path) = D1 ('MetaData "RequestF" "Servant.Client.Core.Request" "servant-client-core-0.16-IPyRddtWkj09XxrnWzUYh0" 'False) (C1 ('MetaCons "Request" 'PrefixI 'True) ((S1 ('MetaSel ('Just "requestPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 path) :*: (S1 ('MetaSel ('Just "requestQueryString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq QueryItem)) :*: S1 ('MetaSel ('Just "requestBody") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (body, MediaType))))) :*: ((S1 ('MetaSel ('Just "requestAccept") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq MediaType)) :*: S1 ('MetaSel ('Just "requestHeaders") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq Header))) :*: (S1 ('MetaSel ('Just "requestHttpVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HttpVersion) :*: S1 ('MetaSel ('Just "requestMethod") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Method))))) |
data RequestBody Source #
The request body. R replica of the http-client
RequestBody
.
Constructors
RequestBodyLBS ByteString | |
RequestBodyBS ByteString | |
RequestBodySource (SourceIO ByteString) |
Instances
Show RequestBody Source # | |
Defined in Servant.Client.Core.Request Methods showsPrec :: Int -> RequestBody -> ShowS show :: RequestBody -> String showList :: [RequestBody] -> ShowS | |
Generic RequestBody Source # | |
Defined in Servant.Client.Core.Request Associated Types type Rep RequestBody :: Type -> Type # | |
type Rep RequestBody Source # | |
Defined in Servant.Client.Core.Request type Rep RequestBody = D1 ('MetaData "RequestBody" "Servant.Client.Core.Request" "servant-client-core-0.16-IPyRddtWkj09XxrnWzUYh0" 'False) (C1 ('MetaCons "RequestBodyLBS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)) :+: (C1 ('MetaCons "RequestBodyBS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)) :+: C1 ('MetaCons "RequestBodySource" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SourceIO ByteString))))) |
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
Constructors
AuthenticatedRequest | |
Fields
|
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
data ClientError Source #
A type representing possible errors in a request
Note that this type substantially changed in 0.12.
Constructors
FailureResponse (RequestF () (BaseUrl, ByteString)) Response | The server returned an error response including the
failing request. |
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 SomeException | There was a connection error, and no response was received |
Instances
Eq ClientError Source # | |
Defined in Servant.Client.Core.ClientError | |
Show ClientError Source # | |
Defined in Servant.Client.Core.ClientError Methods showsPrec :: Int -> ClientError -> ShowS show :: ClientError -> String showList :: [ClientError] -> ShowS | |
Generic ClientError Source # | |
Defined in Servant.Client.Core.ClientError Associated Types type Rep ClientError :: Type -> Type # | |
Exception ClientError Source # | |
Defined in Servant.Client.Core.ClientError Methods toException :: ClientError -> SomeException # fromException :: SomeException -> Maybe ClientError # displayException :: ClientError -> String # | |
NFData ClientError Source # | Note: an exception in |
Defined in Servant.Client.Core.ClientError Methods rnf :: ClientError -> () | |
type Rep ClientError Source # | |
Defined in Servant.Client.Core.ClientError type Rep ClientError = D1 ('MetaData "ClientError" "Servant.Client.Core.ClientError" "servant-client-core-0.16-IPyRddtWkj09XxrnWzUYh0" 'False) ((C1 ('MetaCons "FailureResponse" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (RequestF () (BaseUrl, ByteString))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Response)) :+: C1 ('MetaCons "DecodeFailure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Response))) :+: (C1 ('MetaCons "UnsupportedContentType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MediaType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Response)) :+: (C1 ('MetaCons "InvalidContentTypeHeader" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Response)) :+: C1 ('MetaCons "ConnectionError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SomeException))))) |
data EmptyClient Source #
Singleton type representing a client for an empty API.
Constructors
EmptyClient |
Instances
Bounded EmptyClient Source # | |
Defined in Servant.Client.Core.HasClient | |
Enum EmptyClient Source # | |
Defined in Servant.Client.Core.HasClient Methods succ :: EmptyClient -> EmptyClient pred :: EmptyClient -> EmptyClient toEnum :: Int -> EmptyClient fromEnum :: EmptyClient -> Int enumFrom :: EmptyClient -> [EmptyClient] enumFromThen :: EmptyClient -> EmptyClient -> [EmptyClient] enumFromTo :: EmptyClient -> EmptyClient -> [EmptyClient] enumFromThenTo :: EmptyClient -> EmptyClient -> EmptyClient -> [EmptyClient] | |
Eq EmptyClient Source # | |
Defined in Servant.Client.Core.HasClient | |
Show EmptyClient Source # | |
Defined in Servant.Client.Core.HasClient Methods showsPrec :: Int -> EmptyClient -> ShowS show :: EmptyClient -> String showList :: [EmptyClient] -> ShowS |
Response
Constructors
Response | |
Fields
|
Instances
Functor ResponseF Source # | |
Foldable ResponseF Source # | |
Defined in Servant.Client.Core.Response Methods fold :: Monoid m => ResponseF m -> m foldMap :: Monoid m => (a -> m) -> ResponseF a -> m foldMap' :: Monoid m => (a -> m) -> ResponseF a -> m foldr :: (a -> b -> b) -> b -> ResponseF a -> b foldr' :: (a -> b -> b) -> b -> ResponseF a -> b foldl :: (b -> a -> b) -> b -> ResponseF a -> b foldl' :: (b -> a -> b) -> b -> ResponseF a -> b foldr1 :: (a -> a -> a) -> ResponseF a -> a foldl1 :: (a -> a -> a) -> ResponseF a -> a elem :: Eq a => a -> ResponseF a -> Bool maximum :: Ord a => ResponseF a -> a minimum :: Ord a => ResponseF a -> a | |
Traversable ResponseF Source # | |
Defined in Servant.Client.Core.Response | |
Eq a => Eq (ResponseF a) Source # | |
Show a => Show (ResponseF a) Source # | |
Generic (ResponseF a) Source # | |
NFData a => NFData (ResponseF a) Source # | |
Defined in Servant.Client.Core.Response | |
type Rep (ResponseF a) Source # | |
Defined in Servant.Client.Core.Response type Rep (ResponseF a) = D1 ('MetaData "ResponseF" "Servant.Client.Core.Response" "servant-client-core-0.16-IPyRddtWkj09XxrnWzUYh0" 'False) (C1 ('MetaCons "Response" 'PrefixI 'True) ((S1 ('MetaSel ('Just "responseStatusCode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Status) :*: S1 ('MetaSel ('Just "responseHeaders") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq Header))) :*: (S1 ('MetaSel ('Just "responseHttpVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HttpVersion) :*: S1 ('MetaSel ('Just "responseBody") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))) |
class Monad m => RunClient m where Source #
Methods
runRequest :: Request -> m Response Source #
How to make a request.
throwClientError :: ClientError -> m a Source #
Instances
ClientF ~ f => RunClient (Free f) Source # | |
Defined in Servant.Client.Core.RunClient Methods runRequest :: Request -> Free f Response Source # throwClientError :: ClientError -> Free f a Source # |
BaseUrl
Simple data type to represent the target of HTTP requests for servant's automatically-generated clients.
Constructors
BaseUrl | |
Fields
|
Instances
Eq BaseUrl Source # | |
Data BaseUrl Source # | |
Defined in Servant.Client.Core.BaseUrl Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BaseUrl -> c BaseUrl gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BaseUrl dataTypeOf :: BaseUrl -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BaseUrl) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BaseUrl) gmapT :: (forall b. Data b => b -> b) -> BaseUrl -> BaseUrl gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BaseUrl -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BaseUrl -> r gmapQ :: (forall d. Data d => d -> u) -> BaseUrl -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> BaseUrl -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> BaseUrl -> m BaseUrl gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BaseUrl -> m BaseUrl gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BaseUrl -> m BaseUrl | |
Ord BaseUrl Source # | |
Show BaseUrl Source # | |
Generic BaseUrl Source # | |
Lift BaseUrl Source # | |
Defined in Servant.Client.Core.BaseUrl | |
ToJSON BaseUrl Source # |
|
ToJSONKey BaseUrl Source # |
|
Defined in Servant.Client.Core.BaseUrl Methods | |
FromJSON BaseUrl Source # |
|
FromJSONKey BaseUrl Source # | |
Defined in Servant.Client.Core.BaseUrl Methods | |
NFData BaseUrl Source # | |
Defined in Servant.Client.Core.BaseUrl | |
type Rep BaseUrl Source # | |
Defined in Servant.Client.Core.BaseUrl type Rep BaseUrl = D1 ('MetaData "BaseUrl" "Servant.Client.Core.BaseUrl" "servant-client-core-0.16-IPyRddtWkj09XxrnWzUYh0" 'False) (C1 ('MetaCons "BaseUrl" 'PrefixI 'True) ((S1 ('MetaSel ('Just "baseUrlScheme") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Scheme) :*: S1 ('MetaSel ('Just "baseUrlHost") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :*: (S1 ('MetaSel ('Just "baseUrlPort") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "baseUrlPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))) |
URI scheme to use
Instances
Eq Scheme Source # | |
Data Scheme Source # | |
Defined in Servant.Client.Core.BaseUrl Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Scheme -> c Scheme gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Scheme dataTypeOf :: Scheme -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Scheme) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Scheme) gmapT :: (forall b. Data b => b -> b) -> Scheme -> Scheme gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Scheme -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Scheme -> r gmapQ :: (forall d. Data d => d -> u) -> Scheme -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> Scheme -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> Scheme -> m Scheme gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Scheme -> m Scheme gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Scheme -> m Scheme | |
Ord Scheme Source # | |
Show Scheme Source # | |
Generic Scheme Source # | |
Lift Scheme Source # | |
Defined in Servant.Client.Core.BaseUrl | |
type Rep Scheme Source # | |
Defined in Servant.Client.Core.BaseUrl |
showBaseUrl :: BaseUrl -> String Source #
>>>
showBaseUrl <$> parseBaseUrl "api.example.com"
"http://api.example.com"
parseBaseUrl :: MonadThrow m => String -> m BaseUrl Source #
>>>
parseBaseUrl "api.example.com"
BaseUrl {baseUrlScheme = Http, baseUrlHost = "api.example.com", baseUrlPort = 80, baseUrlPath = ""}
Note: trailing slash is removed
>>>
parseBaseUrl "api.example.com/"
BaseUrl {baseUrlScheme = Http, baseUrlHost = "api.example.com", baseUrlPort = 80, baseUrlPath = ""}
>>>
parseBaseUrl "api.example.com/dir/"
BaseUrl {baseUrlScheme = Http, baseUrlHost = "api.example.com", baseUrlPort = 80, baseUrlPath = "/dir"}
newtype InvalidBaseUrlException Source #
Constructors
InvalidBaseUrlException String |
Instances
Show InvalidBaseUrlException Source # | |
Defined in Servant.Client.Core.BaseUrl Methods showsPrec :: Int -> InvalidBaseUrlException -> ShowS show :: InvalidBaseUrlException -> String showList :: [InvalidBaseUrlException] -> ShowS | |
Exception InvalidBaseUrlException Source # | |
Defined in Servant.Client.Core.BaseUrl Methods toException :: InvalidBaseUrlException -> SomeException # fromException :: SomeException -> Maybe InvalidBaseUrlException # |
Streaming
class RunClient m => RunStreamingClient m where Source #
Methods
withStreamingRequest :: Request -> (StreamingResponse -> IO a) -> m a Source #
type StreamingResponse = ResponseF (SourceIO ByteString) Source #
Writing HasClient instances
These functions need not be re-exported by backend libraries.
addHeader :: ToHttpApiData a => HeaderName -> a -> Request -> Request Source #
appendToPath :: Text -> 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