servant-reflex-0.3.5: servant API generator for reflex apps

Safe HaskellNone
LanguageHaskell2010

Servant.Common.Req

Contents

Synopsis

Documentation

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 #

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

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

reqSuccess' :: ReqResult tag a -> Maybe (tag, a) Source #

Simple filter/accessor like reqSuccess, but keeping the request tag

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

Simple filter/accessor for any failure case

reqFailure' :: ReqResult tag a -> Maybe (tag, Text) Source #

Simple filter/accessor like reqFailure, but keeping the request tag

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

Simple filter/accessor for the raw XHR response

reqTag :: ReqResult tag a -> tag Source #

Retrieve response tag

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)

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

performing requests

performRequests :: forall t m f tag. (SupportsServantReflex t m, Traversable f) => Text -> Dynamic t (f (Req t)) -> Dynamic t BaseUrl -> ClientOptions -> Event t tag -> m (Event t (tag, f (Either Text XhrResponse))) Source #

This function performs the request

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.

performSomeRequestsAsync' :: (MonadJSM (Performable m), PerformEvent t m, TriggerEvent t m, Traversable f, Show b) => ClientOptions -> (XhrRequest b -> (a -> JSM ()) -> Performable m XMLHttpRequest) -> Event t (Performable m (f (Either Text (XhrRequest b)))) -> m (Event t (f (Either Text a))) Source #

A modified version or Reflex.Dom.Xhr.performRequestsAsync that accepts 'f (Either e (XhrRequestb))' events

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 #

fanReqResult :: Reflex t => Event t (ReqResult tag a) -> (Event t Text, Event t a) Source #

Utility for simultaneously accessing/filtering Success and Failure response Events,

fanReqResult' :: Reflex t => Event t (ReqResult tag a) -> (Event t (tag, Text), Event t (tag, a)) Source #

Utility for simultaneously accessing/filtering Success and Failure response Events, but keeping the request tag

note :: e -> Maybe a -> Either e a Source #

fmapL :: (e -> e') -> Either e a -> Either e' a Source #