Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- clientA :: (HasClientMulti t m layout f tag, Applicative f, Reflex t) => Proxy layout -> Proxy m -> Proxy f -> Proxy tag -> Dynamic t BaseUrl -> ClientMulti t m layout f tag
- clientWithOptsA :: (HasClientMulti t m layout f tag, Applicative f, Reflex t) => Proxy layout -> Proxy m -> Proxy f -> Proxy tag -> Dynamic t BaseUrl -> ClientOptions -> ClientMulti t m layout f tag
- data BaseUrl
- data Scheme
- data QParam a
- = QParamSome a
- | QNone
- | QParamInvalid Text
- withCredentials :: (Show a, Functor f) => (Bool -> f Bool) -> XhrRequest a -> f (XhrRequest a)
- data ReqResult tag a
- = ResponseSuccess tag a XhrResponse
- | ResponseFailure tag Text XhrResponse
- | RequestFailure tag Text
- reqSuccess :: ReqResult tag a -> Maybe a
- reqSuccess' :: ReqResult tag a -> Maybe (tag, a)
- reqFailure :: ReqResult tag a -> Maybe Text
- response :: ReqResult tag a -> Maybe XhrResponse
- class HasClientMulti t m layout f (tag :: *) where
- type ClientMulti t m layout f tag :: *
Compute servant client functions
clientA :: (HasClientMulti t m layout f tag, Applicative f, Reflex t) => Proxy layout -> Proxy m -> Proxy f -> Proxy tag -> Dynamic t BaseUrl -> ClientMulti t m layout f tag Source #
clientWithOptsA :: (HasClientMulti t m layout f tag, Applicative f, Reflex t) => Proxy layout -> Proxy m -> Proxy f -> Proxy tag -> Dynamic t BaseUrl -> ClientOptions -> ClientMulti t m layout f tag Source #
A version of client
that sets the withCredentials flag
on requests. Use this function for clients of CORS API's
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
Build QueryParam arguments
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) |
Access response data
withCredentials :: (Show a, Functor f) => (Bool -> f Bool) -> XhrRequest a -> f (XhrRequest a) Source #
Access response data
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 |
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
reqSuccess' :: ReqResult tag a -> Maybe (tag, a) Source #
Simple filter/accessor like reqSuccess
, but keeping the request tag
response :: ReqResult tag a -> Maybe XhrResponse Source #
Simple filter/accessor for the raw XHR response
class HasClientMulti t m layout f (tag :: *) where Source #
type ClientMulti t m layout f tag :: * Source #
clientWithRouteMulti :: Proxy layout -> Proxy m -> Proxy f -> Proxy tag -> Dynamic t (f (Req t)) -> Dynamic t BaseUrl -> ClientOptions -> ClientMulti t m layout f tag Source #