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.
Synopsis
- client :: HasClient t m layout tag => Proxy layout -> Proxy m -> Proxy tag -> Dynamic t BaseUrl -> Client t m layout tag
- clientWithOpts :: HasClient t m layout tag => Proxy layout -> Proxy m -> Proxy tag -> Dynamic t BaseUrl -> ClientOptions -> Client t m layout tag
- 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
- clientWithRoute :: HasClient t m layout tag => Proxy layout -> Proxy m -> Proxy tag -> Req t -> Dynamic t BaseUrl -> ClientOptions -> Client t m layout tag
- 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
- class BuildHeaderKeysTo hs where
- toHeaders :: BuildHeadersTo ls => ReqResult tag a -> ReqResult tag (Headers ls a)
- class Monad m => HasClient t m layout (tag :: *)
- type family Client t m layout tag :: *
- data Req t
- data QueryPart t
- = QueryPartParam (Dynamic t (Either Text (Maybe Text)))
- | QueryPartParams (Dynamic t [Text])
- | QueryPartFlag (Dynamic t Bool)
- data QParam a
- = QParamSome a
- | QNone
- | QParamInvalid Text
- data ClientOptions = ClientOptions {
- optsRequestFixup :: forall a. Show a => XhrRequest a -> JSM (XhrRequest a)
- data ReqResult tag a
- = ResponseSuccess tag a XhrResponse
- | ResponseFailure tag Text XhrResponse
- | RequestFailure tag Text
- defaultClientOptions :: ClientOptions
- withCredentials :: (Show a, Functor f) => (Bool -> f Bool) -> XhrRequest a -> f (XhrRequest a)
- reqSuccess :: ReqResult tag a -> Maybe a
- reqFailure :: ReqResult tag a -> Maybe Text
- response :: ReqResult tag a -> Maybe XhrResponse
- reqTag :: ReqResult tag a -> tag
- qParamToQueryPart :: ToHttpApiData a => QParam a -> Either Text (Maybe Text)
- defReq :: Req t
- prependToPathParts :: Dynamic t (Either Text Text) -> Req t -> Req t
- addHeader :: (ToHttpApiData a, Reflex t) => Text -> Dynamic t (Either Text a) -> Req t -> Req t
- 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)))
- 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)))
- performRequestsNoBody :: (SupportsServantReflex t m, Traversable f) => Text -> Dynamic t (f (Req t)) -> Dynamic t BaseUrl -> ClientOptions -> Event t tag -> m (Event t (f (ReqResult tag NoContent)))
- evalResponse :: (XhrResponse -> Either Text a) -> (tag, XhrResponse) -> ReqResult tag a
- data BaseUrl
- data Scheme
- type SupportsServantReflex t m = (Reflex t, TriggerEvent t m, PerformEvent t m, HasWebView (Performable m), MonadJSM (Performable m))
- showBaseUrl :: BaseUrl -> Text
- 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)
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 #
buildHeaderKeysTo :: Proxy hs -> [Text] Source #
Instances
BuildHeaderKeysTo ([] :: [k]) Source # | |
Defined in Servant.Reflex buildHeaderKeysTo :: Proxy [] -> [Text] Source # | |
(BuildHeaderKeysTo xs, KnownSymbol h) => BuildHeaderKeysTo (Header h v ': xs :: [*]) Source # | |
Defined in Servant.Reflex |
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
.
Instances
SupportsServantReflex t m => HasClient t m Raw tag Source # | Send a raw 'XhrRequest ()' directly to |
Defined in Servant.Reflex 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 # | |
Defined in Servant.Reflex 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 # | |
Defined in Servant.Reflex 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 # | |
Defined in Servant.Reflex 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 # | |
Defined in Servant.Reflex 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 # | |
Defined in Servant.Reflex 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 # | |
Defined in Servant.Reflex 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 |
Defined in Servant.Reflex 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 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 -> ExceptT String IO Book addBook = client myApi host where host = BaseUrl Http "localhost" 8080 -- then you can just use "addBook" to query that endpoint |
Defined in Servant.Reflex 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 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 -> 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 |
Defined in Servant.Reflex 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 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] -> 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 |
Defined in Servant.Reflex 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 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 -> 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 |
Defined in Servant.Reflex 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 |
Defined in Servant.Reflex 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 # | |
Defined in Servant.Reflex 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 # | |
Defined in Servant.Reflex 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 # | |
Defined in Servant.Reflex 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 # | |
Defined in Servant.Reflex 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 # | |
Defined in Servant.Reflex 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 # | |
Defined in Servant.Reflex 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 # | |
type Client t m (a :<|> b :: *) tag Source # | |
type Client t m (BasicAuth realm usr :> api :: *) tag Source # | |
Defined in Servant.Reflex | |
type Client t m (IsSecure :> api :: *) tag Source # | |
type Client t m (RemoteHost :> api :: *) tag Source # | |
Defined in Servant.Reflex | |
type Client t m (Vault :> api :: *) tag Source # | |
type Client t m (path :> sublayout :: *) tag Source # | |
Defined in Servant.Reflex | |
type Client t m (ReqBody (ct ': cts) a :> sublayout :: *) tag Source # | |
type Client t m (QueryFlag sym :> sublayout :: *) tag Source # | |
type Client t m (QueryParams sym a :> sublayout :: *) tag Source # | |
Defined in Servant.Reflex | |
type Client t m (QueryParam sym a :> sublayout :: *) tag Source # | |
Defined in Servant.Reflex | |
type Client t m (HttpVersion :> sublayout :: *) tag Source # | |
Defined in Servant.Reflex | |
type Client t m (Header sym a :> sublayout :: *) tag Source # | |
type Client t m (Capture capture a :> sublayout :: *) tag Source # | |
type Client t m (Auth auths a :> api :: *) tag Source # | |
type Client t m (Verb method status cts NoContent :: *) tag Source # | |
type Client t m (Verb method status cts' a :: *) tag Source # | |
type Client t m (Verb method status cts (Headers ls NoContent) :: *) tag Source # | |
type Client t m (Verb method status cts' (Headers ls a) :: *) tag Source # | |
QueryPartParam (Dynamic t (Either Text (Maybe Text))) | |
QueryPartParams (Dynamic t [Text]) | |
QueryPartFlag (Dynamic t Bool) |
You must wrap the parameter of a QueryParam endpoint with QParam
to
indicate whether the parameter is valid and present, validly absent, or
invalid
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 #
ClientOptions | |
|
The result of a request event
ResponseSuccess tag a XhrResponse | The succesfully decoded response from a request tagged with |
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 |
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
response :: ReqResult tag a -> Maybe XhrResponse Source #
Simple filter/accessor for the raw XHR response
qParamToQueryPart :: ToHttpApiData a => QParam a -> Either Text (Maybe Text) Source #
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 #
performRequestsNoBody :: (SupportsServantReflex t m, Traversable f) => Text -> Dynamic t (f (Req t)) -> Dynamic t BaseUrl -> ClientOptions -> Event t tag -> m (Event t (f (ReqResult tag NoContent))) Source #
Simple data type to represent the target of HTTP requests for servant's automatically-generated clients.
Instances
Eq BaseUrl Source # | |
Ord BaseUrl Source # | |
Read BaseUrl Source # | |
Show BaseUrl Source # | |
Generic BaseUrl Source # | |
type Rep BaseUrl Source # | |
Defined in Servant.Common.BaseUrl type Rep BaseUrl = D1 (MetaData "BaseUrl" "Servant.Common.BaseUrl" "servant-reflex-0.3.3-HgwVL2SxZXQILb64VgoONt" False) (C1 (MetaCons "BaseFullUrl" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Scheme) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) :+: C1 (MetaCons "BasePath" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) |
URI scheme to use
type SupportsServantReflex t m = (Reflex t, TriggerEvent t m, PerformEvent t m, HasWebView (Performable m), MonadJSM (Performable m)) Source #
showBaseUrl :: BaseUrl -> Text Source #
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 #