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

Safe HaskellNone
LanguageHaskell2010

Servant.Reflex.Multi

Contents

Synopsis

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

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 :: Type -> Type #

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 :: Type -> Type #

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.5-inplace" False) (C1 (MetaCons "Http" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Https" PrefixI False) (U1 :: Type -> Type))

Build QueryParam arguments

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)

Access response data

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

Access response data

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 #

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

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

Simple filter/accessor for the raw XHR response

class HasClientMulti t m layout f (tag :: *) where Source #

Associated Types

type ClientMulti t m layout f tag :: * Source #

Methods

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 #

Instances
(HasClientMulti t m a f tag, HasClientMulti t m b f tag) => HasClientMulti t (m :: k) (a :<|> b :: Type) f tag Source # 
Instance details

Defined in Servant.Reflex.Multi

Associated Types

type ClientMulti t m (a :<|> b) f tag :: Type Source #

Methods

clientWithRouteMulti :: Proxy (a :<|> b) -> Proxy m -> Proxy f -> Proxy tag -> Dynamic t (f (Req t)) -> Dynamic t BaseUrl -> ClientOptions -> ClientMulti t m (a :<|> b) f tag Source #

(HasClientMulti t m api f tag, Reflex t, Applicative f) => HasClientMulti t (m :: k) (BasicAuth realm usr :> api :: Type) f tag Source # 
Instance details

Defined in Servant.Reflex.Multi

Associated Types

type ClientMulti t m (BasicAuth realm usr :> api) f tag :: Type Source #

Methods

clientWithRouteMulti :: Proxy (BasicAuth realm usr :> api) -> Proxy m -> Proxy f -> Proxy tag -> Dynamic t (f (Req t)) -> Dynamic t BaseUrl -> ClientOptions -> ClientMulti t m (BasicAuth realm usr :> api) f tag Source #

HasClientMulti t m api f tag => HasClientMulti t (m :: k) (IsSecure :> api :: Type) f tag Source # 
Instance details

Defined in Servant.Reflex.Multi

Associated Types

type ClientMulti t m (IsSecure :> api) f tag :: Type Source #

Methods

clientWithRouteMulti :: Proxy (IsSecure :> api) -> Proxy m -> Proxy f -> Proxy tag -> Dynamic t (f (Req t)) -> Dynamic t BaseUrl -> ClientOptions -> ClientMulti t m (IsSecure :> api) f tag Source #

HasClientMulti t m api f tag => HasClientMulti t (m :: k) (RemoteHost :> api :: Type) f tag Source # 
Instance details

Defined in Servant.Reflex.Multi

Associated Types

type ClientMulti t m (RemoteHost :> api) f tag :: Type Source #

Methods

clientWithRouteMulti :: Proxy (RemoteHost :> api) -> Proxy m -> Proxy f -> Proxy tag -> Dynamic t (f (Req t)) -> Dynamic t BaseUrl -> ClientOptions -> ClientMulti t m (RemoteHost :> api) f tag Source #

HasClientMulti t m api f tag => HasClientMulti t (m :: k) (Vault :> api :: Type) f tag Source # 
Instance details

Defined in Servant.Reflex.Multi

Associated Types

type ClientMulti t m (Vault :> api) f tag :: Type Source #

Methods

clientWithRouteMulti :: Proxy (Vault :> api) -> Proxy m -> Proxy f -> Proxy tag -> Dynamic t (f (Req t)) -> Dynamic t BaseUrl -> ClientOptions -> ClientMulti t m (Vault :> api) f tag Source #

(KnownSymbol path, HasClientMulti t m sublayout f tag, Reflex t, Functor f) => HasClientMulti t (m :: k) (path :> sublayout :: Type) f tag Source # 
Instance details

Defined in Servant.Reflex.Multi

Associated Types

type ClientMulti t m (path :> sublayout) f tag :: Type Source #

Methods

clientWithRouteMulti :: Proxy (path :> sublayout) -> Proxy m -> Proxy f -> Proxy tag -> Dynamic t (f (Req t)) -> Dynamic t BaseUrl -> ClientOptions -> ClientMulti t m (path :> sublayout) f tag Source #

(MimeRender ct a, HasClientMulti t m sublayout f tag, Reflex t, Applicative f) => HasClientMulti t (m :: k) (ReqBody (ct ': cts) a :> sublayout :: Type) f tag Source # 
Instance details

Defined in Servant.Reflex.Multi

Associated Types

type ClientMulti t m (ReqBody (ct ': cts) a :> sublayout) f tag :: Type Source #

Methods

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

(KnownSymbol sym, HasClientMulti t m sublayout f tag, Reflex t, Applicative f) => HasClientMulti t (m :: k) (QueryFlag sym :> sublayout :: Type) f tag Source # 
Instance details

Defined in Servant.Reflex.Multi

Associated Types

type ClientMulti t m (QueryFlag sym :> sublayout) f tag :: Type Source #

Methods

clientWithRouteMulti :: Proxy (QueryFlag sym :> sublayout) -> Proxy m -> Proxy f -> Proxy tag -> Dynamic t (f (Req t)) -> Dynamic t BaseUrl -> ClientOptions -> ClientMulti t m (QueryFlag sym :> sublayout) f tag Source #

(KnownSymbol sym, ToHttpApiData a, HasClientMulti t m sublayout f tag, Reflex t, Applicative f) => HasClientMulti t (m :: k) (QueryParams sym a :> sublayout :: Type) f tag Source # 
Instance details

Defined in Servant.Reflex.Multi

Associated Types

type ClientMulti t m (QueryParams sym a :> sublayout) f tag :: Type Source #

Methods

clientWithRouteMulti :: Proxy (QueryParams sym a :> sublayout) -> Proxy m -> Proxy f -> Proxy tag -> Dynamic t (f (Req t)) -> Dynamic t BaseUrl -> ClientOptions -> ClientMulti t m (QueryParams sym a :> sublayout) f tag Source #

(KnownSymbol sym, ToHttpApiData a, HasClientMulti t m sublayout f tag, Reflex t, Applicative f) => HasClientMulti t (m :: k) (QueryParam sym a :> sublayout :: Type) f tag Source # 
Instance details

Defined in Servant.Reflex.Multi

Associated Types

type ClientMulti t m (QueryParam sym a :> sublayout) f tag :: Type Source #

Methods

clientWithRouteMulti :: Proxy (QueryParam sym a :> sublayout) -> Proxy m -> Proxy f -> Proxy tag -> Dynamic t (f (Req t)) -> Dynamic t BaseUrl -> ClientOptions -> ClientMulti t m (QueryParam sym a :> sublayout) f tag Source #

HasClientMulti t m sublayout f tag => HasClientMulti t (m :: k) (HttpVersion :> sublayout :: Type) f tag Source # 
Instance details

Defined in Servant.Reflex.Multi

Associated Types

type ClientMulti t m (HttpVersion :> sublayout) f tag :: Type Source #

Methods

clientWithRouteMulti :: Proxy (HttpVersion :> sublayout) -> Proxy m -> Proxy f -> Proxy tag -> Dynamic t (f (Req t)) -> Dynamic t BaseUrl -> ClientOptions -> ClientMulti t m (HttpVersion :> sublayout) f tag Source #

(SupportsServantReflex t m, Traversable f, Applicative f) => HasClientMulti t (m :: Type -> Type) Raw f tag Source # 
Instance details

Defined in Servant.Reflex.Multi

Associated Types

type ClientMulti t m Raw f tag :: Type Source #

Methods

clientWithRouteMulti :: Proxy Raw -> Proxy m -> Proxy f -> Proxy tag -> Dynamic t (f (Req t)) -> Dynamic t BaseUrl -> ClientOptions -> ClientMulti t m Raw f tag Source #

(KnownSymbol sym, ToHttpApiData a, HasClientMulti t m sublayout f tag, SupportsServantReflex t m, Traversable f, Applicative f) => HasClientMulti t (m :: Type -> Type) (Header sym a :> sublayout :: Type) f tag Source # 
Instance details

Defined in Servant.Reflex.Multi

Associated Types

type ClientMulti t m (Header sym a :> sublayout) f tag :: Type Source #

Methods

clientWithRouteMulti :: Proxy (Header sym a :> sublayout) -> Proxy m -> Proxy f -> Proxy tag -> Dynamic t (f (Req t)) -> Dynamic t BaseUrl -> ClientOptions -> ClientMulti t m (Header sym a :> sublayout) f tag Source #

(SupportsServantReflex t m, ToHttpApiData a, HasClientMulti t m sublayout f tag, Applicative f) => HasClientMulti t (m :: Type -> Type) (Capture capture a :> sublayout :: Type) f tag Source # 
Instance details

Defined in Servant.Reflex.Multi

Associated Types

type ClientMulti t m (Capture capture a :> sublayout) f tag :: Type Source #

Methods

clientWithRouteMulti :: Proxy (Capture capture a :> sublayout) -> Proxy m -> Proxy f -> Proxy tag -> Dynamic t (f (Req t)) -> Dynamic t BaseUrl -> ClientOptions -> ClientMulti t m (Capture capture a :> sublayout) f tag Source #

(BuildHeadersTo ls, BuildHeaderKeysTo ls, ReflectMethod method, SupportsServantReflex t m, Traversable f) => HasClientMulti t (m :: Type -> Type) (Verb method status cts (Headers ls NoContent) :: Type) f tag Source # 
Instance details

Defined in Servant.Reflex.Multi

Associated Types

type ClientMulti t m (Verb method status cts (Headers ls NoContent)) f tag :: Type Source #

Methods

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

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

Defined in Servant.Reflex.Multi

Associated Types

type ClientMulti t m (Verb method status cts' (Headers ls a)) f tag :: Type Source #

Methods

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

(ReflectMethod method, SupportsServantReflex t m, Traversable f) => HasClientMulti t (m :: Type -> Type) (Verb method status cts NoContent :: Type) f tag Source # 
Instance details

Defined in Servant.Reflex.Multi

Associated Types

type ClientMulti t m (Verb method status cts NoContent) f tag :: Type Source #

Methods

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

(MimeUnrender ct a, ReflectMethod method, cts' ~ (ct ': cts), SupportsServantReflex t m, Applicative f, Traversable f) => HasClientMulti t (m :: Type -> Type) (Verb method status cts' a :: Type) f tag Source # 
Instance details

Defined in Servant.Reflex.Multi

Associated Types

type ClientMulti t m (Verb method status cts' a) f tag :: Type Source #

Methods

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