servant-to-elm-0.4.3.0: Automatically generate Elm clients for Servant APIs
Safe HaskellNone
LanguageHaskell2010

Servant.To.Elm

Synopsis

Documentation

elmEndpointDefinition Source #

Arguments

:: Expression Void

The URL base of the endpoint

-> Module

The module that the function should be generated into

-> Endpoint

A description of the endpoint

-> Definition 

Generate an Elm function for making a request to a Servant endpoint.

See elmEndpointRequestInfo if you need more flexibility, such as setting timeouts.

elmEndpointRequestInfo Source #

Arguments

:: Module

The module that the function should be generated into

-> Endpoint

A description of the endpoint

-> Definition 

Generate an Elm function for creating information needed to make an HTTP request. This gives the user flexibility in how to actually make the request.

For example, they can use the https://package.elm-lang.org/packages/elm/http/latest/Http#request function and provide it with their own timeout and tracker arguments.

It also leaves building the final URL to the Elm user. This gives them the flexibility to do things like vary the domain used at runtime based on whether the app's in staging or production. Note that they must remember to use BOTH urlPath and urlQueryParams.

class HasElmEndpoints api where Source #

HasElmEndpoints api means that the Servant API api can be converted to a list of Endpoints, which contains the information we need to generate an Elm client library for the API.

Instances

Instances details
HasElmEndpoints EmptyAPI Source # 
Instance details

Defined in Servant.To.Elm

ReflectMethod method => HasElmEndpoints (NoContentVerb method :: Type) Source # 
Instance details

Defined in Servant.To.Elm

(HasElmEndpoints a, HasElmEndpoints b) => HasElmEndpoints (a :<|> b :: Type) Source # 
Instance details

Defined in Servant.To.Elm

HasElmEndpoints api => HasElmEndpoints (WithNamedContext name context api :: Type) Source # 
Instance details

Defined in Servant.To.Elm

HasElmEndpoints api => HasElmEndpoints (HttpVersion :> api :: Type) Source # 
Instance details

Defined in Servant.To.Elm

(HasElmEncoder Value a, HasElmEndpoints api, list ~ '[JSON]) => HasElmEndpoints (ReqBody' mods list a :> api :: Type) Source # 
Instance details

Defined in Servant.To.Elm

HasElmEndpoints api => HasElmEndpoints (RemoteHost :> api :: Type) Source # 
Instance details

Defined in Servant.To.Elm

(SBoolI (FoldRequired mods), KnownSymbol symbol, HasElmEncoder (RequiredArgument mods Text) (RequiredArgument mods a), HasElmEndpoints api) => HasElmEndpoints (QueryParam' mods symbol a :> api :: Type) Source # 
Instance details

Defined in Servant.To.Elm

(KnownSymbol symbol, HasElmEncoder Text a, HasElmEndpoints api) => HasElmEndpoints (QueryParams symbol a :> api :: Type) Source # 
Instance details

Defined in Servant.To.Elm

(KnownSymbol symbol, HasElmEndpoints api) => HasElmEndpoints (QueryFlag symbol :> api :: Type) Source # 
Instance details

Defined in Servant.To.Elm

(SBoolI (FoldRequired mods), KnownSymbol symbol, HasElmEncoder (RequiredArgument mods Text) (RequiredArgument mods a), HasElmEndpoints api) => HasElmEndpoints (Header' mods symbol a :> api :: Type) Source # 
Instance details

Defined in Servant.To.Elm

HasElmEndpoints api => HasElmEndpoints (IsSecure :> api :: Type) Source # 
Instance details

Defined in Servant.To.Elm

HasElmEndpoints api => HasElmEndpoints (Summary summary :> api :: Type) Source # 
Instance details

Defined in Servant.To.Elm

HasElmEndpoints api => HasElmEndpoints (Description description :> api :: Type) Source # 
Instance details

Defined in Servant.To.Elm

(KnownSymbol symbol, HasElmEncoder Text a, HasElmEndpoints api) => HasElmEndpoints (Capture' mods symbol a :> api :: Type) Source # 
Instance details

Defined in Servant.To.Elm

(KnownSymbol symbol, HasElmEncoder Text a, HasElmEndpoints api) => HasElmEndpoints (CaptureAll symbol a :> api :: Type) Source # 
Instance details

Defined in Servant.To.Elm

HasElmEndpoints api => HasElmEndpoints (Vault :> api :: Type) Source # 
Instance details

Defined in Servant.To.Elm

(HasElmEncoder (MultipartData tag) a, HasElmEndpoints api) => HasElmEndpoints (MultipartForm tag a :> api :: Type) Source # 
Instance details

Defined in Servant.To.Elm

(KnownSymbol path, HasElmEndpoints api) => HasElmEndpoints (path :> api :: Type) Source # 
Instance details

Defined in Servant.To.Elm

ReflectMethod method => HasElmEndpoints (Verb method 204 list a :: Type) Source # 
Instance details

Defined in Servant.To.Elm

(ReflectMethod method, HasElmDecoder Value a, list ~ '[JSON]) => HasElmEndpoints (Verb method 200 list a :: Type) Source # 
Instance details

Defined in Servant.To.Elm

elmEndpoints :: forall api. HasElmEndpoints api => [Endpoint] Source #

Convert an API to a list of Elm endpoint descriptors, Endpoint.

Usage: elmEndpoints @MyAPI

data Endpoint Source #

Contains the information we need about an endpoint to generate an Elm definition that calls it.

data PathSegment e Source #

Constructors

Static Text 
Capture Text e 

Instances

Instances details
Show e => Show (PathSegment e) Source # 
Instance details

Defined in Servant.To.Elm

data QueryParamType Source #

Constructors

Required 
Optional 
Flag 
List 

Instances

Instances details
Show QueryParamType Source # 
Instance details

Defined in Servant.To.Elm

data URL Source #

Constructors

URL 

Instances

Instances details
Show URL Source # 
Instance details

Defined in Servant.To.Elm

Methods

showsPrec :: Int -> URL -> ShowS #

show :: URL -> String #

showList :: [URL] -> ShowS #

data Encoder Source #

Constructors

Encoder 

Instances

Instances details
Show Encoder Source # 
Instance details

Defined in Servant.To.Elm

data Decoder Source #

Constructors

Decoder 

Instances

Instances details
Show Decoder Source # 
Instance details

Defined in Servant.To.Elm

makeEncoder :: forall value a. HasElmEncoder value a => Encoder Source #

makeDecoder :: forall value a. HasElmDecoder value a => Decoder Source #

Orphan instances