servant-reflex-0.3.3: Servant reflex API generator

Safe HaskellNone
LanguageHaskell2010

Servant.Reflex

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 t m layout tag => Proxy layout -> Proxy m -> Proxy tag -> Dynamic t BaseUrl -> Client t m layout tag 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 :: Event t l -> m (Event t (l, ReqResult [Book]))
postNewBook :: Dynamic t (Maybe Book) -> Event t l
  • > m (Event t (l, ReqResult Book))) > (getAllBooks :| postNewBook) = client myApi host > where host = constDyn $ BaseUrl Http "localhost" 8080

clientWithOpts :: HasClient t m layout tag => Proxy layout -> Proxy m -> Proxy tag -> Dynamic t BaseUrl -> ClientOptions -> Client t m layout tag Source #

clientWithOptsAndResultHandler :: HasClient t m layout tag => Proxy layout -> Proxy m -> Proxy tag -> Dynamic t BaseUrl -> ClientOptions -> (forall a. Event t (ReqResult tag a) -> m (Event t (ReqResult tag a))) -> Client t m layout tag Source #

Like clientWithOpts but allows passing a function which will process the result event in some way. This can be used to handle errors in a uniform way across call sites.

clientWithRoute :: HasClient t m layout tag => Proxy layout -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> Client t m layout tag Source #

clientWithRouteAndResultHandler :: HasClient t m layout tag => Proxy layout -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> (forall a. Event t (ReqResult tag a) -> m (Event t (ReqResult tag a))) -> Client t m layout tag Source #

class BuildHeaderKeysTo hs where Source #

Minimal complete definition

buildHeaderKeysTo

Methods

buildHeaderKeysTo :: Proxy hs -> [Text] Source #

Instances
BuildHeaderKeysTo ([] :: [k]) Source # 
Instance details

Defined in Servant.Reflex

Methods

buildHeaderKeysTo :: Proxy [] -> [Text] Source #

(BuildHeaderKeysTo xs, KnownSymbol h) => BuildHeaderKeysTo (Header h v ': xs :: [*]) Source # 
Instance details

Defined in Servant.Reflex

Methods

buildHeaderKeysTo :: Proxy (Header h v ': xs) -> [Text] Source #

class Monad m => HasClient t m layout (tag :: *) 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

clientWithRouteAndResultHandler

Instances
SupportsServantReflex t m => HasClient t m Raw tag Source #

Send a raw 'XhrRequest ()' directly to baseurl

Instance details

Defined in Servant.Reflex

Associated Types

type Client t m Raw tag :: * Source #

Methods

clientWithRoute :: Proxy Raw -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> Client t m Raw tag Source #

clientWithRouteAndResultHandler :: Proxy Raw -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> (forall a. Event t (ReqResult tag a) -> m (Event t (ReqResult tag a))) -> Client t m Raw tag Source #

(HasClient t m a tag, HasClient t m b tag) => HasClient t m (a :<|> b :: *) tag Source # 
Instance details

Defined in Servant.Reflex

Associated Types

type Client t m (a :<|> b) tag :: * Source #

Methods

clientWithRoute :: Proxy (a :<|> b) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> Client t m (a :<|> b) tag Source #

clientWithRouteAndResultHandler :: Proxy (a :<|> b) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> (forall a0. Event t (ReqResult tag a0) -> m (Event t (ReqResult tag a0))) -> Client t m (a :<|> b) tag Source #

(HasCookieAuth auths, HasClient t m api tag) => HasClient t m (Auth auths a :> api :: *) tag Source # 
Instance details

Defined in Servant.Reflex

Associated Types

type Client t m (Auth auths a :> api) tag :: * Source #

Methods

clientWithRoute :: Proxy (Auth auths a :> api) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> Client t m (Auth auths a :> api) tag Source #

clientWithRouteAndResultHandler :: Proxy (Auth auths a :> api) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> (forall a0. Event t (ReqResult tag a0) -> m (Event t (ReqResult tag a0))) -> Client t m (Auth auths a :> api) tag Source #

(HasClient t m api tag, Reflex t) => HasClient t m (BasicAuth realm usr :> api :: *) tag Source # 
Instance details

Defined in Servant.Reflex

Associated Types

type Client t m (BasicAuth realm usr :> api) tag :: * Source #

Methods

clientWithRoute :: Proxy (BasicAuth realm usr :> api) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> Client t m (BasicAuth realm usr :> api) tag Source #

clientWithRouteAndResultHandler :: Proxy (BasicAuth realm usr :> api) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> (forall a. Event t (ReqResult tag a) -> m (Event t (ReqResult tag a))) -> Client t m (BasicAuth realm usr :> api) tag Source #

HasClient t m api tag => HasClient t m (IsSecure :> api :: *) tag Source # 
Instance details

Defined in Servant.Reflex

Associated Types

type Client t m (IsSecure :> api) tag :: * Source #

Methods

clientWithRoute :: Proxy (IsSecure :> api) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> Client t m (IsSecure :> api) tag Source #

clientWithRouteAndResultHandler :: Proxy (IsSecure :> api) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> (forall a. Event t (ReqResult tag a) -> m (Event t (ReqResult tag a))) -> Client t m (IsSecure :> api) tag Source #

HasClient t m api tag => HasClient t m (RemoteHost :> api :: *) tag Source # 
Instance details

Defined in Servant.Reflex

Associated Types

type Client t m (RemoteHost :> api) tag :: * Source #

Methods

clientWithRoute :: Proxy (RemoteHost :> api) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> Client t m (RemoteHost :> api) tag Source #

clientWithRouteAndResultHandler :: Proxy (RemoteHost :> api) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> (forall a. Event t (ReqResult tag a) -> m (Event t (ReqResult tag a))) -> Client t m (RemoteHost :> api) tag Source #

HasClient t m api tag => HasClient t m (Vault :> api :: *) tag Source # 
Instance details

Defined in Servant.Reflex

Associated Types

type Client t m (Vault :> api) tag :: * Source #

Methods

clientWithRoute :: Proxy (Vault :> api) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> Client t m (Vault :> api) tag Source #

clientWithRouteAndResultHandler :: Proxy (Vault :> api) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> (forall a. Event t (ReqResult tag a) -> m (Event t (ReqResult tag a))) -> Client t m (Vault :> api) tag Source #

(KnownSymbol path, HasClient t m sublayout tag, Reflex t) => HasClient t m (path :> sublayout :: *) tag Source #

Make the querying function append path to the request path.

Instance details

Defined in Servant.Reflex

Associated Types

type Client t m (path :> sublayout) tag :: * Source #

Methods

clientWithRoute :: Proxy (path :> sublayout) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> Client t m (path :> sublayout) tag Source #

clientWithRouteAndResultHandler :: Proxy (path :> sublayout) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> (forall a. Event t (ReqResult tag a) -> m (Event t (ReqResult tag a))) -> Client t m (path :> sublayout) tag Source #

(MimeRender ct a, HasClient t m sublayout tag, Reflex t) => HasClient t m (ReqBody (ct ': cts) a :> sublayout :: *) tag 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 -> ExceptT String IO Book
addBook = client myApi host
  where host = BaseUrl Http "localhost" 8080
-- then you can just use "addBook" to query that endpoint
Instance details

Defined in Servant.Reflex

Associated Types

type Client t m (ReqBody (ct ': cts) a :> sublayout) tag :: * Source #

Methods

clientWithRoute :: Proxy (ReqBody (ct ': cts) a :> sublayout) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> Client t m (ReqBody (ct ': cts) a :> sublayout) tag Source #

clientWithRouteAndResultHandler :: Proxy (ReqBody (ct ': cts) a :> sublayout) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> (forall a0. Event t (ReqResult tag a0) -> m (Event t (ReqResult tag a0))) -> Client t m (ReqBody (ct ': cts) a :> sublayout) tag Source #

(KnownSymbol sym, HasClient t m sublayout tag, Reflex t) => HasClient t m (QueryFlag sym :> sublayout :: *) tag 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 -> ExceptT 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
Instance details

Defined in Servant.Reflex

Associated Types

type Client t m (QueryFlag sym :> sublayout) tag :: * Source #

Methods

clientWithRoute :: Proxy (QueryFlag sym :> sublayout) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> Client t m (QueryFlag sym :> sublayout) tag Source #

clientWithRouteAndResultHandler :: Proxy (QueryFlag sym :> sublayout) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> (forall a. Event t (ReqResult tag a) -> m (Event t (ReqResult tag a))) -> Client t m (QueryFlag sym :> sublayout) tag Source #

(KnownSymbol sym, ToHttpApiData a, HasClient t m sublayout tag, Reflex t) => HasClient t m (QueryParams sym a :> sublayout :: *) tag 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] -> ExceptT 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
Instance details

Defined in Servant.Reflex

Associated Types

type Client t m (QueryParams sym a :> sublayout) tag :: * Source #

Methods

clientWithRoute :: Proxy (QueryParams sym a :> sublayout) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> Client t m (QueryParams sym a :> sublayout) tag Source #

clientWithRouteAndResultHandler :: Proxy (QueryParams sym a :> sublayout) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> (forall a0. Event t (ReqResult tag a0) -> m (Event t (ReqResult tag a0))) -> Client t m (QueryParams sym a :> sublayout) tag Source #

(KnownSymbol sym, ToHttpApiData a, HasClient t m sublayout tag, Reflex t) => HasClient t m (QueryParam sym a :> sublayout :: *) tag 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 -> ExceptT 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
Instance details

Defined in Servant.Reflex

Associated Types

type Client t m (QueryParam sym a :> sublayout) tag :: * Source #

Methods

clientWithRoute :: Proxy (QueryParam sym a :> sublayout) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> Client t m (QueryParam sym a :> sublayout) tag Source #

clientWithRouteAndResultHandler :: Proxy (QueryParam sym a :> sublayout) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> (forall a0. Event t (ReqResult tag a0) -> m (Event t (ReqResult tag a0))) -> Client t m (QueryParam sym a :> sublayout) tag Source #

HasClient t m sublayout tag => HasClient t m (HttpVersion :> sublayout :: *) tag Source #

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

Instance details

Defined in Servant.Reflex

Associated Types

type Client t m (HttpVersion :> sublayout) tag :: * Source #

Methods

clientWithRoute :: Proxy (HttpVersion :> sublayout) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> Client t m (HttpVersion :> sublayout) tag Source #

clientWithRouteAndResultHandler :: Proxy (HttpVersion :> sublayout) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> (forall a. Event t (ReqResult tag a) -> m (Event t (ReqResult tag a))) -> Client t m (HttpVersion :> sublayout) tag Source #

(KnownSymbol sym, ToHttpApiData a, HasClient t m sublayout tag, SupportsServantReflex t m) => HasClient t m (Header sym a :> sublayout :: *) tag Source # 
Instance details

Defined in Servant.Reflex

Associated Types

type Client t m (Header sym a :> sublayout) tag :: * Source #

Methods

clientWithRoute :: Proxy (Header sym a :> sublayout) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> Client t m (Header sym a :> sublayout) tag Source #

clientWithRouteAndResultHandler :: Proxy (Header sym a :> sublayout) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> (forall a0. Event t (ReqResult tag a0) -> m (Event t (ReqResult tag a0))) -> Client t m (Header sym a :> sublayout) tag Source #

(SupportsServantReflex t m, ToHttpApiData a, HasClient t m sublayout tag) => HasClient t m (Capture capture a :> sublayout :: *) tag Source # 
Instance details

Defined in Servant.Reflex

Associated Types

type Client t m (Capture capture a :> sublayout) tag :: * Source #

Methods

clientWithRoute :: Proxy (Capture capture a :> sublayout) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> Client t m (Capture capture a :> sublayout) tag Source #

clientWithRouteAndResultHandler :: Proxy (Capture capture a :> sublayout) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> (forall a0. Event t (ReqResult tag a0) -> m (Event t (ReqResult tag a0))) -> Client t m (Capture capture a :> sublayout) tag Source #

(BuildHeadersTo ls, BuildHeaderKeysTo ls, ReflectMethod method, SupportsServantReflex t m) => HasClient t m (Verb method status cts (Headers ls NoContent) :: *) tag Source # 
Instance details

Defined in Servant.Reflex

Associated Types

type Client t m (Verb method status cts (Headers ls NoContent)) tag :: * Source #

Methods

clientWithRoute :: Proxy (Verb method status cts (Headers ls NoContent)) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> Client t m (Verb method status cts (Headers ls NoContent)) tag Source #

clientWithRouteAndResultHandler :: Proxy (Verb method status cts (Headers ls NoContent)) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> (forall a. Event t (ReqResult tag a) -> m (Event t (ReqResult tag a))) -> Client t m (Verb method status cts (Headers ls NoContent)) tag Source #

(MimeUnrender ct a, BuildHeadersTo ls, BuildHeaderKeysTo ls, ReflectMethod method, cts' ~ (ct ': cts), SupportsServantReflex t m) => HasClient t m (Verb method status cts' (Headers ls a) :: *) tag Source # 
Instance details

Defined in Servant.Reflex

Associated Types

type Client t m (Verb method status cts' (Headers ls a)) tag :: * Source #

Methods

clientWithRoute :: Proxy (Verb method status cts' (Headers ls a)) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> Client t m (Verb method status cts' (Headers ls a)) tag Source #

clientWithRouteAndResultHandler :: Proxy (Verb method status cts' (Headers ls a)) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> (forall a0. Event t (ReqResult tag a0) -> m (Event t (ReqResult tag a0))) -> Client t m (Verb method status cts' (Headers ls a)) tag Source #

(ReflectMethod method, SupportsServantReflex t m) => HasClient t m (Verb method status cts NoContent :: *) tag Source # 
Instance details

Defined in Servant.Reflex

Associated Types

type Client t m (Verb method status cts NoContent) tag :: * Source #

Methods

clientWithRoute :: Proxy (Verb method status cts NoContent) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> Client t m (Verb method status cts NoContent) tag Source #

clientWithRouteAndResultHandler :: Proxy (Verb method status cts NoContent) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> (forall a. Event t (ReqResult tag a) -> m (Event t (ReqResult tag a))) -> Client t m (Verb method status cts NoContent) tag Source #

(MimeUnrender ct a, ReflectMethod method, cts' ~ (ct ': cts), SupportsServantReflex t m) => HasClient t m (Verb method status cts' a :: *) tag Source # 
Instance details

Defined in Servant.Reflex

Associated Types

type Client t m (Verb method status cts' a) tag :: * Source #

Methods

clientWithRoute :: Proxy (Verb method status cts' a) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> Client t m (Verb method status cts' a) tag Source #

clientWithRouteAndResultHandler :: Proxy (Verb method status cts' a) -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> (forall a0. Event t (ReqResult tag a0) -> m (Event t (ReqResult tag a0))) -> Client t m (Verb method status cts' a) tag Source #

type family Client t m layout tag :: * Source #

Instances
type Client t m Raw tag Source # 
Instance details

Defined in Servant.Reflex

type Client t m Raw tag = Dynamic t (Either Text (XhrRequest ())) -> Event t tag -> m (Event t (ReqResult tag ()))
type Client t m (a :<|> b :: *) tag Source # 
Instance details

Defined in Servant.Reflex

type Client t m (a :<|> b :: *) tag = Client t m a tag :<|> Client t m b tag
type Client t m (BasicAuth realm usr :> api :: *) tag Source # 
Instance details

Defined in Servant.Reflex

type Client t m (BasicAuth realm usr :> api :: *) tag = Dynamic t (Maybe BasicAuthData) -> Client t m api tag
type Client t m (IsSecure :> api :: *) tag Source # 
Instance details

Defined in Servant.Reflex

type Client t m (IsSecure :> api :: *) tag = Client t m api tag
type Client t m (RemoteHost :> api :: *) tag Source # 
Instance details

Defined in Servant.Reflex

type Client t m (RemoteHost :> api :: *) tag = Client t m api tag
type Client t m (Vault :> api :: *) tag Source # 
Instance details

Defined in Servant.Reflex

type Client t m (Vault :> api :: *) tag = Client t m api tag
type Client t m (path :> sublayout :: *) tag Source # 
Instance details

Defined in Servant.Reflex

type Client t m (path :> sublayout :: *) tag = Client t m sublayout tag
type Client t m (ReqBody (ct ': cts) a :> sublayout :: *) tag Source # 
Instance details

Defined in Servant.Reflex

type Client t m (ReqBody (ct ': cts) a :> sublayout :: *) tag = Dynamic t (Either Text a) -> Client t m sublayout tag
type Client t m (QueryFlag sym :> sublayout :: *) tag Source # 
Instance details

Defined in Servant.Reflex

type Client t m (QueryFlag sym :> sublayout :: *) tag = Dynamic t Bool -> Client t m sublayout tag
type Client t m (QueryParams sym a :> sublayout :: *) tag Source # 
Instance details

Defined in Servant.Reflex

type Client t m (QueryParams sym a :> sublayout :: *) tag = Dynamic t [a] -> Client t m sublayout tag
type Client t m (QueryParam sym a :> sublayout :: *) tag Source # 
Instance details

Defined in Servant.Reflex

type Client t m (QueryParam sym a :> sublayout :: *) tag = Dynamic t (QParam a) -> Client t m sublayout tag
type Client t m (HttpVersion :> sublayout :: *) tag Source # 
Instance details

Defined in Servant.Reflex

type Client t m (HttpVersion :> sublayout :: *) tag = Client t m sublayout tag
type Client t m (Header sym a :> sublayout :: *) tag Source # 
Instance details

Defined in Servant.Reflex

type Client t m (Header sym a :> sublayout :: *) tag = Dynamic t (Either Text a) -> Client t m sublayout tag
type Client t m (Capture capture a :> sublayout :: *) tag Source # 
Instance details

Defined in Servant.Reflex

type Client t m (Capture capture a :> sublayout :: *) tag = Dynamic t (Either Text a) -> Client t m sublayout tag
type Client t m (Auth auths a :> api :: *) tag Source # 
Instance details

Defined in Servant.Reflex

type Client t m (Auth auths a :> api :: *) tag = Client t m api tag
type Client t m (Verb method status cts NoContent :: *) tag Source # 
Instance details

Defined in Servant.Reflex

type Client t m (Verb method status cts NoContent :: *) tag = Event t tag -> m (Event t (ReqResult tag NoContent))
type Client t m (Verb method status cts' a :: *) tag Source # 
Instance details

Defined in Servant.Reflex

type Client t m (Verb method status cts' a :: *) tag = Event t tag -> m (Event t (ReqResult tag a))
type Client t m (Verb method status cts (Headers ls NoContent) :: *) tag Source # 
Instance details

Defined in Servant.Reflex

type Client t m (Verb method status cts (Headers ls NoContent) :: *) tag = Event t tag -> m (Event t (ReqResult tag (Headers ls NoContent)))
type Client t m (Verb method status cts' (Headers ls a) :: *) tag Source # 
Instance details

Defined in Servant.Reflex

type Client t m (Verb method status cts' (Headers ls a) :: *) tag = Event t tag -> m (Event t (ReqResult tag (Headers ls a)))

data Req t Source #

data QParam a Source #

You must wrap the parameter of a QueryParam endpoint with QParam to indicate whether the parameter is valid and present, validly absent, or invalid

Constructors

QParamSome a

A valid query parameter

QNone

Indication that the parameter is intentionally absent (the request is valid)

QParamInvalid Text

Indication that your validation failed (the request isn't valid)

data ClientOptions Source #

Constructors

ClientOptions 

Fields

  • optsRequestFixup :: forall a. Show a => XhrRequest a -> JSM (XhrRequest a)

    Aribtrarily modify requests just before they are sent. Warning: This escape hatch opens the possibility for your requests to diverge from what the server expects, when the server is also derived from a servant API

data ReqResult tag a Source #

The result of a request event

Constructors

ResponseSuccess tag a XhrResponse

The succesfully decoded response from a request tagged with tag

ResponseFailure tag Text XhrResponse

The failure response, which may have failed decoding or had a non-successful response code

RequestFailure tag Text

A failure to construct the request tagged with tag at trigger time

Instances
Functor (ReqResult tag) Source # 
Instance details

Defined in Servant.Common.Req

Methods

fmap :: (a -> b) -> ReqResult tag a -> ReqResult tag b #

(<$) :: a -> ReqResult tag b -> ReqResult tag a #

withCredentials :: (Show a, Functor f) => (Bool -> f Bool) -> XhrRequest a -> f (XhrRequest a) Source #

reqSuccess :: ReqResult tag a -> Maybe a Source #

Simple filter/accessor for successful responses, when you want to ignore the error case. For example: >> goodResponses fmapMaybe reqSuccess <$ clientFun triggers

reqFailure :: ReqResult tag a -> Maybe Text Source #

Simple filter/accessor for any failure case

response :: ReqResult tag a -> Maybe XhrResponse Source #

Simple filter/accessor for the raw XHR response

reqTag :: ReqResult tag a -> tag Source #

Retrieve response tag

addHeader :: (ToHttpApiData a, Reflex t) => Text -> Dynamic t (Either Text a) -> Req t -> Req t Source #

performSomeRequestsAsync :: (MonadIO (Performable m), MonadJSM (Performable m), HasWebView (Performable m), PerformEvent t m, TriggerEvent t m, Traversable f, IsXhrPayload a, Show a) => ClientOptions -> Event t (f (Either Text (XhrRequest a))) -> m (Event t (f (Either Text XhrResponse))) Source #

Issues a collection of requests when the supplied Event fires. When ALL requests from a given firing complete, the results are collected and returned via the return Event.

performRequestsCT :: (SupportsServantReflex t m, MimeUnrender ct a, Traversable f) => Proxy ct -> Text -> Dynamic t (f (Req t)) -> Dynamic t BaseUrl -> ClientOptions -> Event t tag -> m (Event t (f (ReqResult tag a))) Source #

evalResponse :: (XhrResponse -> Either Text a) -> (tag, XhrResponse) -> ReqResult tag a Source #

data BaseUrl Source #

Simple data type to represent the target of HTTP requests for servant's automatically-generated clients.

Instances
Eq BaseUrl Source # 
Instance details

Defined in Servant.Common.BaseUrl

Methods

(==) :: BaseUrl -> BaseUrl -> Bool #

(/=) :: BaseUrl -> BaseUrl -> Bool #

Ord BaseUrl Source # 
Instance details

Defined in Servant.Common.BaseUrl

Read BaseUrl Source # 
Instance details

Defined in Servant.Common.BaseUrl

Show BaseUrl Source # 
Instance details

Defined in Servant.Common.BaseUrl

Generic BaseUrl Source # 
Instance details

Defined in Servant.Common.BaseUrl

Associated Types

type Rep BaseUrl :: * -> * #

Methods

from :: BaseUrl -> Rep BaseUrl x #

to :: Rep BaseUrl x -> BaseUrl #

type Rep BaseUrl Source # 
Instance details

Defined in Servant.Common.BaseUrl

data Scheme Source #

URI scheme to use

Constructors

Http

http://

Https

https://

Instances
Eq Scheme Source # 
Instance details

Defined in Servant.Common.BaseUrl

Methods

(==) :: Scheme -> Scheme -> Bool #

(/=) :: Scheme -> Scheme -> Bool #

Ord Scheme Source # 
Instance details

Defined in Servant.Common.BaseUrl

Read Scheme Source # 
Instance details

Defined in Servant.Common.BaseUrl

Show Scheme Source # 
Instance details

Defined in Servant.Common.BaseUrl

Generic Scheme Source # 
Instance details

Defined in Servant.Common.BaseUrl

Associated Types

type Rep Scheme :: * -> * #

Methods

from :: Scheme -> Rep Scheme x #

to :: Rep Scheme x -> Scheme #

type Rep Scheme Source # 
Instance details

Defined in Servant.Common.BaseUrl

type Rep Scheme = D1 (MetaData "Scheme" "Servant.Common.BaseUrl" "servant-reflex-0.3.3-HgwVL2SxZXQILb64VgoONt" False) (C1 (MetaCons "Http" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Https" PrefixI False) (U1 :: * -> *))

baseUrlWidget :: forall t m. (SupportsServantReflex t m, DomBuilderSpace m ~ GhcjsDomSpace, MonadFix m, PostBuild t m, MonadHold t m, DomBuilder t m) => m (Dynamic t BaseUrl) Source #