servant-cli-0.1.1.0: Command line interface for Servant API clients
Copyright(c) Justin Le 2019
LicenseBSD3
Maintainerjustin@jle.im
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Servant.CLI

Description

Parse command line arguments into a servant client, from a servant API.

Mainly used through parseClient and parseHandleClient. parseClient returns a servant client action that returns nested Eithers for every endpoint, but parseHandleClient allows you to conveniently specify how you want to sort each endpoint entry into a single result.

See README for a tutorial.

Synopsis

Parse Client

parseClient Source #

Arguments

:: HasCLI m api '[] 
=> Proxy api

API

-> Proxy m

Client monad

-> InfoMod (m (CLIResult m api))

Options for top-level display

-> IO (m (CLIResult m api)) 

Parse a servant client; the result can be run. The choice of m gives the backend you are using; for example, the default GHC servant-client backend is ClientM.

Returns the request response, which is usually a layer of Either for every endpoint branch. You can find the response type directly by using typed holes or asking ghci with :t or :kind! forall m. CLIResult m MyAPI. Because it might be tedious handling nested Eithers, see parseHandleClient for a way to handle each potential branch in a convenient way.

Takes options on how the top-level prompt is displayed when given "--help"; it can be useful for adding a header or program description. Otherwise, just use mempty.

parseHandleClient Source #

Arguments

:: (HasCLI m api '[], Functor m) 
=> Proxy api

API

-> Proxy m

Client monad

-> InfoMod (m (CLIResult m api))

Options for top-level display

-> CLIHandler m api r

Handler

-> IO (m r) 

Parse a server client, like parseClient. However, instead of that client action returning the request response, instead use a CLIHandler to handle every potential request response. It essentially lets you specify how to sort each potential endpoint's response into a single output value.

The handler is usually a :<|> for every endpoint branch. You can find it by using typed holes or asking ghci with :t or :kind! forall m r. CLIHandler m MyAPI r.

Takes options on how the top-level prompt is displayed when given "--help"; it can be useful for adding a header or program description. Otherwise, just use mempty.

With context

parseClientWithContext Source #

Arguments

:: HasCLI m api context 
=> Proxy api

API

-> Proxy m

Client monad

-> Rec (ContextFor m) context

Extra context

-> InfoMod (m (CLIResult m api))

Options for top-level display

-> IO (m (CLIResult m api)) 

A version of parseClient that can be used if the API requires any external context to generate runtime data.

parseHandleClientWithContext Source #

Arguments

:: forall m api context r. (HasCLI m api context, Functor m) 
=> Proxy api

API

-> Proxy m

Client monad

-> Rec (ContextFor m) context

Extra context

-> InfoMod (m (CLIResult m api))

Options for top-level display

-> CLIHandler m api r

Handler

-> IO (m r) 

A version of parseHandleClient that can be used if the API requires any external context to generate runtime data.

Typeclasses

class HasCLI m api ctx where Source #

Typeclass defining how each API combinator influences how a server can be interacted with using command line options.

Note that query parameters and captures all require servant-docs annotation instances, to allow for proper help messages.

Unless you are adding new combinators to be used with APIs, you can ignore this class.

Minimal complete definition

cliPStructWithContext_, cliHandler

Associated Types

type CLIResult (m :: Type -> Type) (api :: Type) :: Type Source #

The parsed type of the client request response. Usually this will be a bunch of nested Eithers for every API endpoint, nested according to the :<|>s in the API.

type CLIHandler (m :: Type -> Type) (api :: Type) (r :: Type) :: Type Source #

The type of a data structure to conveniently handle the results of all pontential endpoints. This is useful because it is often tedious to handle the bunch of nested Eithers that CLIResult has.

It essentially lets you specify how to sort each potential endpoint's response into a single output value.

Usually this will be a bunch of nested :<|>s which handle each endpoint, according to the :<|>s in the API. It mirrors the structure of Client and ServerT.

Used with functions like parseHandleClient.

Methods

cliHandler :: Proxy m -> Proxy api -> Proxy ctx -> CLIHandler m api r -> CLIResult m api -> r Source #

Handle all the possibilities in a CLIResult, by giving the appropriate CLIHandler.

Instances

Instances details
HasCLI m EmptyAPI ctx Source #

EmptyAPI will always fail to parse.

The branch ending in EmptyAPI will never be return, so if this is combined using :<|>, the branch will never end up on the side of EmptyAPI.

One can use absurd to handle this branch as a part of CLIHandler.

Instance details

Defined in Servant.CLI.HasCLI

Associated Types

type CLIResult m EmptyAPI Source #

type CLIHandler m EmptyAPI r Source #

RunClient m => HasCLI m Raw ctx Source #

Asks for method as a command line argument. If any Verb exists at the same endpoint, it can only be accessed as an extra RAW subcommand (as if it had an extra path component labeled RAW).

Instance details

Defined in Servant.CLI.HasCLI

Associated Types

type CLIResult m Raw Source #

type CLIHandler m Raw r Source #

(HasCLI m a ctx, HasCLI m b ctx, Functor m) => HasCLI m (a :<|> b) ctx Source #

Using alternation with :<|> provides an Either between the two results.

Instance details

Defined in Servant.CLI.HasCLI

Associated Types

type CLIResult m (a :<|> b) Source #

type CLIHandler m (a :<|> b) r Source #

Methods

cliPStructWithContext_ :: Proxy m -> Proxy (a :<|> b) -> Rec (ContextFor m) ctx -> PStruct (Request -> m (CLIResult m (a :<|> b))) Source #

cliHandler :: Proxy m -> Proxy (a :<|> b) -> Proxy ctx -> CLIHandler m (a :<|> b) r -> CLIResult m (a :<|> b) -> r Source #

(RunClient m, ReflectMethod method) => HasCLI m (NoContentVerb method) ctx Source #

Final actions are the result of specifying all necessary command line positional arguments.

All command line options are associated with the final action at the end of their endpoint/path. They cannot be entered in "before" you arrive at your final endpoint.

If more than one action (under a different method) exists under the same endpoint/path, the method (GET, POST, etc.) will be treated as an extra final command. After that, you may begin entering in options.

Instance details

Defined in Servant.CLI.HasCLI

Associated Types

type CLIResult m (NoContentVerb method) Source #

type CLIHandler m (NoContentVerb method) r Source #

Methods

cliPStructWithContext_ :: Proxy m -> Proxy (NoContentVerb method) -> Rec (ContextFor m) ctx -> PStruct (Request -> m (CLIResult m (NoContentVerb method))) Source #

cliHandler :: Proxy m -> Proxy (NoContentVerb method) -> Proxy ctx -> CLIHandler m (NoContentVerb method) r -> CLIResult m (NoContentVerb method) -> r Source #

(KnownSymbol path, HasCLI m api ctx) => HasCLI m (path :> api) ctx Source #

A path component is interpreted as a "subcommand".

Instance details

Defined in Servant.CLI.HasCLI

Associated Types

type CLIResult m (path :> api) Source #

type CLIHandler m (path :> api) r Source #

Methods

cliPStructWithContext_ :: Proxy m -> Proxy (path :> api) -> Rec (ContextFor m) ctx -> PStruct (Request -> m (CLIResult m (path :> api))) Source #

cliHandler :: Proxy m -> Proxy (path :> api) -> Proxy ctx -> CLIHandler m (path :> api) r -> CLIResult m (path :> api) -> r Source #

HasCLI m api ctx => HasCLI m (HttpVersion :> api) ctx Source #

Using HttpVersion has no affect on CLI operations.

Instance details

Defined in Servant.CLI.HasCLI

Associated Types

type CLIResult m (HttpVersion :> api) Source #

type CLIHandler m (HttpVersion :> api) r Source #

Methods

cliPStructWithContext_ :: Proxy m -> Proxy (HttpVersion :> api) -> Rec (ContextFor m) ctx -> PStruct (Request -> m (CLIResult m (HttpVersion :> api))) Source #

cliHandler :: Proxy m -> Proxy (HttpVersion :> api) -> Proxy ctx -> CLIHandler m (HttpVersion :> api) r -> CLIResult m (HttpVersion :> api) -> r Source #

(ToAuthInfo (BasicAuth realm usr), HasCLI m api ctx, BasicAuth realm usr ctx, Monad m) => HasCLI m (BasicAuth realm usr :> api) ctx Source #

Add GenBasicAuthData to the required context, meaning it must be provided to allow the client to generate authentication data. The action will only be run if the user selects this endpoint via command line arguments.

Please use a secure connection!

Instance details

Defined in Servant.CLI.HasCLI

Associated Types

type CLIResult m (BasicAuth realm usr :> api) Source #

type CLIHandler m (BasicAuth realm usr :> api) r Source #

Methods

cliPStructWithContext_ :: Proxy m -> Proxy (BasicAuth realm usr :> api) -> Rec (ContextFor m) ctx -> PStruct (Request -> m (CLIResult m (BasicAuth realm usr :> api))) Source #

cliHandler :: Proxy m -> Proxy (BasicAuth realm usr :> api) -> Proxy ctx -> CLIHandler m (BasicAuth realm usr :> api) r -> CLIResult m (BasicAuth realm usr :> api) -> r Source #

(FromHttpApiData a, ToHttpApiData a, Typeable a, ToCapture (Capture sym a), HasCLI m api ctx) => HasCLI m (Capture' mods sym a :> api) ctx Source #

A Capture is interpreted as a positional required command line argument.

Note that these require ToCapture instances from servant-docs, to provide appropriate help messages.

Instance details

Defined in Servant.CLI.HasCLI

Associated Types

type CLIResult m (Capture' mods sym a :> api) Source #

type CLIHandler m (Capture' mods sym a :> api) r Source #

Methods

cliPStructWithContext_ :: Proxy m -> Proxy (Capture' mods sym a :> api) -> Rec (ContextFor m) ctx -> PStruct (Request -> m (CLIResult m (Capture' mods sym a :> api))) Source #

cliHandler :: Proxy m -> Proxy (Capture' mods sym a :> api) -> Proxy ctx -> CLIHandler m (Capture' mods sym a :> api) r -> CLIResult m (Capture' mods sym a :> api) -> r Source #

(FromHttpApiData a, ToHttpApiData a, Typeable a, ToCapture (CaptureAll sym a), HasCLI m api ctx) => HasCLI m (CaptureAll sym a :> api) ctx Source #

A CaptureAll is interpreted as arbitrarily many command line arguments. If there is more than one final endpoint method, the method must be given as a command line option before beginning the arguments.

Instance details

Defined in Servant.CLI.HasCLI

Associated Types

type CLIResult m (CaptureAll sym a :> api) Source #

type CLIHandler m (CaptureAll sym a :> api) r Source #

Methods

cliPStructWithContext_ :: Proxy m -> Proxy (CaptureAll sym a :> api) -> Rec (ContextFor m) ctx -> PStruct (Request -> m (CLIResult m (CaptureAll sym a :> api))) Source #

cliHandler :: Proxy m -> Proxy (CaptureAll sym a :> api) -> Proxy ctx -> CLIHandler m (CaptureAll sym a :> api) r -> CLIResult m (CaptureAll sym a :> api) -> r Source #

(KnownSymbol desc, HasCLI m api ctx) => HasCLI m (Description desc :> api) ctx Source #

Description is displayed during --help when it is reached while navigating down subcommands.

Instance details

Defined in Servant.CLI.HasCLI

Associated Types

type CLIResult m (Description desc :> api) Source #

type CLIHandler m (Description desc :> api) r Source #

Methods

cliPStructWithContext_ :: Proxy m -> Proxy (Description desc :> api) -> Rec (ContextFor m) ctx -> PStruct (Request -> m (CLIResult m (Description desc :> api))) Source #

cliHandler :: Proxy m -> Proxy (Description desc :> api) -> Proxy ctx -> CLIHandler m (Description desc :> api) r -> CLIResult m (Description desc :> api) -> r Source #

(KnownSymbol desc, HasCLI m api ctx) => HasCLI m (Summary desc :> api) ctx Source #

Summary is displayed during --help when it is reached while navigating down subcommands.

Instance details

Defined in Servant.CLI.HasCLI

Associated Types

type CLIResult m (Summary desc :> api) Source #

type CLIHandler m (Summary desc :> api) r Source #

Methods

cliPStructWithContext_ :: Proxy m -> Proxy (Summary desc :> api) -> Rec (ContextFor m) ctx -> PStruct (Request -> m (CLIResult m (Summary desc :> api))) Source #

cliHandler :: Proxy m -> Proxy (Summary desc :> api) -> Proxy ctx -> CLIHandler m (Summary desc :> api) r -> CLIResult m (Summary desc :> api) -> r Source #

(HasCLI m api ctx, AuthProtect tag ctx, Monad m) => HasCLI m (AuthProtect tag :> api) ctx Source #

Add GenAuthReq to the required context, meaning it must be provided to allow the client to generate authentication data. The action will only be run if the user selects this endpoint via command line arguments.

Please use a secure connection!

Instance details

Defined in Servant.CLI.HasCLI

Associated Types

type CLIResult m (AuthProtect tag :> api) Source #

type CLIHandler m (AuthProtect tag :> api) r Source #

Methods

cliPStructWithContext_ :: Proxy m -> Proxy (AuthProtect tag :> api) -> Rec (ContextFor m) ctx -> PStruct (Request -> m (CLIResult m (AuthProtect tag :> api))) Source #

cliHandler :: Proxy m -> Proxy (AuthProtect tag :> api) -> Proxy ctx -> CLIHandler m (AuthProtect tag :> api) r -> CLIResult m (AuthProtect tag :> api) -> r Source #

(KnownSymbol sym, FromHttpApiData a, ToHttpApiData a, SBoolI (FoldRequired' 'False mods), Typeable a, HasCLI m api ctx) => HasCLI m (Header' mods sym a :> api) ctx Source #

A Header' in the middle of a path is interpreted as a command line argument, prefixed with "header". For example, Header "foo" Int is an option for --header-foo.

Like for QueryParam', arguments are associated with the action at their endpoint. After entering all path components and positional arguments, the parser library will begin asking for arguments.

Instance details

Defined in Servant.CLI.HasCLI

Associated Types

type CLIResult m (Header' mods sym a :> api) Source #

type CLIHandler m (Header' mods sym a :> api) r Source #

Methods

cliPStructWithContext_ :: Proxy m -> Proxy (Header' mods sym a :> api) -> Rec (ContextFor m) ctx -> PStruct (Request -> m (CLIResult m (Header' mods sym a :> api))) Source #

cliHandler :: Proxy m -> Proxy (Header' mods sym a :> api) -> Proxy ctx -> CLIHandler m (Header' mods sym a :> api) r -> CLIResult m (Header' mods sym a :> api) -> r Source #

HasCLI m api ctx => HasCLI m (IsSecure :> api) ctx Source # 
Instance details

Defined in Servant.CLI.HasCLI

Associated Types

type CLIResult m (IsSecure :> api) Source #

type CLIHandler m (IsSecure :> api) r Source #

Methods

cliPStructWithContext_ :: Proxy m -> Proxy (IsSecure :> api) -> Rec (ContextFor m) ctx -> PStruct (Request -> m (CLIResult m (IsSecure :> api))) Source #

cliHandler :: Proxy m -> Proxy (IsSecure :> api) -> Proxy ctx -> CLIHandler m (IsSecure :> api) r -> CLIResult m (IsSecure :> api) -> r Source #

(KnownSymbol sym, ToParam (QueryFlag sym), HasCLI m api ctx) => HasCLI m (QueryFlag sym :> api) ctx Source #

Query flags are interpreted as command line flags/switches.

QueryFlag arguments are associated with the action at their endpoint. After entering all path components and positional arguments, the parser library will begin asking for arguments.

Note that these require ToParam instances from servant-docs, to provide appropriate help messages.

Instance details

Defined in Servant.CLI.HasCLI

Associated Types

type CLIResult m (QueryFlag sym :> api) Source #

type CLIHandler m (QueryFlag sym :> api) r Source #

Methods

cliPStructWithContext_ :: Proxy m -> Proxy (QueryFlag sym :> api) -> Rec (ContextFor m) ctx -> PStruct (Request -> m (CLIResult m (QueryFlag sym :> api))) Source #

cliHandler :: Proxy m -> Proxy (QueryFlag sym :> api) -> Proxy ctx -> CLIHandler m (QueryFlag sym :> api) r -> CLIResult m (QueryFlag sym :> api) -> r Source #

(KnownSymbol sym, FromHttpApiData a, ToHttpApiData a, SBoolI (FoldRequired' 'False mods), Typeable a, ToParam (QueryParam' mods sym a), HasCLI m api ctx) => HasCLI m (QueryParam' mods sym a :> api) ctx Source #

Query parameters are interpreted as command line options.

QueryParam' arguments are associated with the action at their endpoint. After entering all path components and positional arguments, the parser library will begin asking for arguments.

Note that these require ToParam instances from servant-docs, to provide appropriate help messages.

Instance details

Defined in Servant.CLI.HasCLI

Associated Types

type CLIResult m (QueryParam' mods sym a :> api) Source #

type CLIHandler m (QueryParam' mods sym a :> api) r Source #

Methods

cliPStructWithContext_ :: Proxy m -> Proxy (QueryParam' mods sym a :> api) -> Rec (ContextFor m) ctx -> PStruct (Request -> m (CLIResult m (QueryParam' mods sym a :> api))) Source #

cliHandler :: Proxy m -> Proxy (QueryParam' mods sym a :> api) -> Proxy ctx -> CLIHandler m (QueryParam' mods sym a :> api) r -> CLIResult m (QueryParam' mods sym a :> api) -> r Source #

(ToHttpApiData a, ToParam (QueryParams sym a), KnownSymbol sym, Typeable a, FromHttpApiData a, HasCLI m api ctx) => HasCLI m (QueryParams sym a :> api) ctx Source #

Query parameters are interpreted as command line options, and so repeated query parameters are repeated command line options.

QueryParams are associated with the action at their endpoint. After entering all path components and positional arguments, the parser library will begin asking for arguments.

Note that these require ToParam instances from servant-docs, to provide appropriate help messages.

Instance details

Defined in Servant.CLI.HasCLI

Associated Types

type CLIResult m (QueryParams sym a :> api) Source #

type CLIHandler m (QueryParams sym a :> api) r Source #

Methods

cliPStructWithContext_ :: Proxy m -> Proxy (QueryParams sym a :> api) -> Rec (ContextFor m) ctx -> PStruct (Request -> m (CLIResult m (QueryParams sym a :> api))) Source #

cliHandler :: Proxy m -> Proxy (QueryParams sym a :> api) -> Proxy ctx -> CLIHandler m (QueryParams sym a :> api) r -> CLIResult m (QueryParams sym a :> api) -> r Source #

HasCLI m api ctx => HasCLI m (RemoteHost :> api) ctx Source # 
Instance details

Defined in Servant.CLI.HasCLI

Associated Types

type CLIResult m (RemoteHost :> api) Source #

type CLIHandler m (RemoteHost :> api) r Source #

Methods

cliPStructWithContext_ :: Proxy m -> Proxy (RemoteHost :> api) -> Rec (ContextFor m) ctx -> PStruct (Request -> m (CLIResult m (RemoteHost :> api))) Source #

cliHandler :: Proxy m -> Proxy (RemoteHost :> api) -> Proxy ctx -> CLIHandler m (RemoteHost :> api) r -> CLIResult m (RemoteHost :> api) -> r Source #

(MimeRender ct a, ParseBody a, HasCLI m api ctx) => HasCLI m (ReqBody' mods (ct ': cts) a :> api) ctx Source #

Request body requirements are interpreted using ParseBody.

Note if more than one ReqBody is in an API endpoint, both parsers will be "run", but only the final one will be used. This shouldn't be an issue, since multiple ReqBodys in a single endpoint should be undefined behavior.

Instance details

Defined in Servant.CLI.HasCLI

Associated Types

type CLIResult m (ReqBody' mods (ct ': cts) a :> api) Source #

type CLIHandler m (ReqBody' mods (ct ': cts) a :> api) r Source #

Methods

cliPStructWithContext_ :: Proxy m -> Proxy (ReqBody' mods (ct ': cts) a :> api) -> Rec (ContextFor m) ctx -> PStruct (Request -> m (CLIResult m (ReqBody' mods (ct ': cts) a :> api))) Source #

cliHandler :: Proxy m -> Proxy (ReqBody' mods (ct ': cts) a :> api) -> Proxy ctx -> CLIHandler m (ReqBody' mods (ct ': cts) a :> api) r -> CLIResult m (ReqBody' mods (ct ': cts) a :> api) -> r Source #

(ToSourceIO chunk a, MimeRender ctype chunk, FramingRender framing, StreamBody' mods framing ctype a ctx, HasCLI m api ctx, Monad m) => HasCLI m (StreamBody' mods framing ctype a :> api) ctx Source #

As a part of ctx, asks for a streaming source a.

Instance details

Defined in Servant.CLI.HasCLI

Associated Types

type CLIResult m (StreamBody' mods framing ctype a :> api) Source #

type CLIHandler m (StreamBody' mods framing ctype a :> api) r Source #

Methods

cliPStructWithContext_ :: Proxy m -> Proxy (StreamBody' mods framing ctype a :> api) -> Rec (ContextFor m) ctx -> PStruct (Request -> m (CLIResult m (StreamBody' mods framing ctype a :> api))) Source #

cliHandler :: Proxy m -> Proxy (StreamBody' mods framing ctype a :> api) -> Proxy ctx -> CLIHandler m (StreamBody' mods framing ctype a :> api) r -> CLIResult m (StreamBody' mods framing ctype a :> api) -> r Source #

HasCLI m api ctx => HasCLI m (Vault :> api) ctx Source # 
Instance details

Defined in Servant.CLI.HasCLI

Associated Types

type CLIResult m (Vault :> api) Source #

type CLIHandler m (Vault :> api) r Source #

Methods

cliPStructWithContext_ :: Proxy m -> Proxy (Vault :> api) -> Rec (ContextFor m) ctx -> PStruct (Request -> m (CLIResult m (Vault :> api))) Source #

cliHandler :: Proxy m -> Proxy (Vault :> api) -> Proxy ctx -> CLIHandler m (Vault :> api) r -> CLIResult m (Vault :> api) -> r Source #

(NamedContext m name subctx ctx, HasCLI m subapi subctx) => HasCLI m (WithNamedContext name subctx subapi) ctx Source #

Descend down a subcontext indexed by a given name. Must be provided when parsing within the context.

Useful for when you have multiple items with the same name within a context; this essentially creates a namespace for context items.

Instance details

Defined in Servant.CLI.HasCLI

Associated Types

type CLIResult m (WithNamedContext name subctx subapi) Source #

type CLIHandler m (WithNamedContext name subctx subapi) r Source #

Methods

cliPStructWithContext_ :: Proxy m -> Proxy (WithNamedContext name subctx subapi) -> Rec (ContextFor m) ctx -> PStruct (Request -> m (CLIResult m (WithNamedContext name subctx subapi))) Source #

cliHandler :: Proxy m -> Proxy (WithNamedContext name subctx subapi) -> Proxy ctx -> CLIHandler m (WithNamedContext name subctx subapi) r -> CLIResult m (WithNamedContext name subctx subapi) -> r Source #

(HasClient m (Verb method status cts' a), ReflectMethod method) => HasCLI m (Verb method status cts' a) ctx Source #

Final actions are the result of specifying all necessary command line positional arguments.

All command line options are associated with the final action at the end of their endpoint/path. They cannot be entered in "before" you arrive at your final endpoint.

If more than one action (under a different method) exists under the same endpoint/path, the method (GET, POST, etc.) will be treated as an extra final command. After that, you may begin entering in options.

Instance details

Defined in Servant.CLI.HasCLI

Associated Types

type CLIResult m (Verb method status cts' a) Source #

type CLIHandler m (Verb method status cts' a) r Source #

Methods

cliPStructWithContext_ :: Proxy m -> Proxy (Verb method status cts' a) -> Rec (ContextFor m) ctx -> PStruct (Request -> m (CLIResult m (Verb method status cts' a))) Source #

cliHandler :: Proxy m -> Proxy (Verb method status cts' a) -> Proxy ctx -> CLIHandler m (Verb method status cts' a) r -> CLIResult m (Verb method status cts' a) -> r Source #

(RunStreamingClient m, MimeUnrender ct chunk, ReflectMethod method, FramingUnrender framing, FromSourceIO chunk a) => HasCLI m (Stream method status framing ct a) ctx Source #

Same semantics in parsing command line options as Verb.

Instance details

Defined in Servant.CLI.HasCLI

Associated Types

type CLIResult m (Stream method status framing ct a) Source #

type CLIHandler m (Stream method status framing ct a) r Source #

Methods

cliPStructWithContext_ :: Proxy m -> Proxy (Stream method status framing ct a) -> Rec (ContextFor m) ctx -> PStruct (Request -> m (CLIResult m (Stream method status framing ct a))) Source #

cliHandler :: Proxy m -> Proxy (Stream method status framing ct a) -> Proxy ctx -> CLIHandler m (Stream method status framing ct a) r -> CLIResult m (Stream method status framing ct a) -> r Source #

Context

data family ContextFor (m :: Type -> Type) :: Type -> Type Source #

Data family associating API combinators with contexts required to run them. These typically will be actions in m that fetch/generate the required data, and will only be "run" if the user selects an endpoint that requires it through the command line interface.

Instances

Instances details
newtype ContextFor m (BasicAuth realm usr) Source # 
Instance details

Defined in Servant.CLI.HasCLI

newtype ContextFor m (AuthProtect tag) Source # 
Instance details

Defined in Servant.CLI.HasCLI

newtype ContextFor m (NamedContext m name subContext) Source # 
Instance details

Defined in Servant.CLI.HasCLI

newtype ContextFor m (NamedContext m name subContext) = NC (NamedContext m name subContext)
newtype ContextFor m (StreamBody' mods framing ctype a) Source # 
Instance details

Defined in Servant.CLI.HasCLI

newtype ContextFor m (StreamBody' mods framing ctype a) = GenStreamBody {}

newtype NamedContext m (name :: Symbol) (subContext :: [Type]) Source #

Contains a subcontext that can be descended down into using NamedContext. Mirrors NamedContext.

Useful for when you have multiple items with the same name within a context; this essentially creates a namespace for context items.

Constructors

NamedContext (Rec (ContextFor m) subContext) 

Instances

Instances details
newtype ContextFor m (NamedContext m name subContext) Source # 
Instance details

Defined in Servant.CLI.HasCLI

newtype ContextFor m (NamedContext m name subContext) = NC (NamedContext m name subContext)

descendIntoNamedContext :: forall (name :: Symbol) context subContext m. NamedContext m name subContext context => Proxy name -> Rec (ContextFor m) context -> Rec (ContextFor m) subContext Source #

Allows you to access NamedContexts inside a context.

Lower-level

cliPStruct Source #

Arguments

:: HasCLI m api '[] 
=> Proxy m

Client monad

-> Proxy api

API

-> PStruct (m (CLIResult m api)) 

Create a structure for a command line parser.

This can be useful if you are combining functionality with existing optparse-applicative parsers. You can convert a PStruct to a Parser using structParser.

cliPStructWithContext Source #

Arguments

:: HasCLI m api context 
=> Proxy m

Client monad

-> Proxy api

API

-> Rec (ContextFor m) context

Extra context

-> PStruct (m (CLIResult m api)) 

A version of cliPStruct that can be used if the API requires any external context to generate runtime data.

structParser Source #

Arguments

:: PStruct a

The PStruct to convert.

-> InfoMod a

Modify how the top-level prompt is displayed.

-> ParserInfo a 

Convert a PStruct into a command line argument parser, from the optparse-applicative library. It can be run with execParser.

It takes options on how the top-level prompt is displayed when given "--help"; it can be useful for adding a header or program description. Otherwise, just use mempty.

With context

cliHandlePStruct Source #

Arguments

:: (HasCLI m api '[], Functor m) 
=> Proxy m

Client monad

-> Proxy api

API

-> CLIHandler m api r

Handler

-> PStruct (m r) 

Create a structure for a command line parser, producing results according to a CLIHandler. See parseHandleClient for more information.

This can be useful if you are combining functionality with existing optparse-applicative parsers. You can convert a PStruct to a Parser using structParser.

cliHandlePStructWithContext Source #

Arguments

:: forall m api context r. (HasCLI m api context, Functor m) 
=> Proxy m

Client monad

-> Proxy api

API

-> Rec (ContextFor m) context

Extra context

-> CLIHandler m api r

Handler

-> PStruct (m r) 

A version of cliHandlePStruct that can be used if the API requires any external context to generate runtime data.

Re-export

class ParseBody a where Source #

A helper class for defining directly how to parse request bodies. This allows more complex parsing of bodies.

You need an instance of this for every type you use with ReqBody.

Minimal complete definition

Nothing

Methods

parseBody :: Parser a Source #

default parseBody :: (Typeable a, Read a) => Parser a Source #

Instances

Instances details
ParseBody Text Source # 
Instance details

Defined in Servant.CLI.ParseBody

ParseBody Text Source # 
Instance details

Defined in Servant.CLI.ParseBody

ParseBody Integer Source # 
Instance details

Defined in Servant.CLI.ParseBody

ParseBody Double Source # 
Instance details

Defined in Servant.CLI.ParseBody

ParseBody Float Source # 
Instance details

Defined in Servant.CLI.ParseBody

ParseBody Int Source # 
Instance details

Defined in Servant.CLI.ParseBody

defaultParseBody Source #

Arguments

:: String

type specification

-> ReadM a

parser

-> Parser a 

Default implementation that expects a --data option.

class ToCapture (c :: k) where #

The class that helps us automatically get documentation for URL captures.

Example of an instance:

instance ToCapture (Capture "name" Text) where
  toCapture _ = DocCapture "name" "name of the person to greet"

Methods

toCapture :: Proxy c -> DocCapture #

data DocCapture #

A type to represent captures. Holds the name of the capture and a description.

Write a ToCapture instance for your captured types.

Constructors

DocCapture 

class ToParam (t :: k) where #

The class that helps us automatically get documentation for GET (or other Method) parameters.

Example of an instance:

instance ToParam (QueryParam' mods "capital" Bool) where
  toParam _ =
    DocQueryParam "capital"
                  ["true", "false"]
                  "Get the greeting message in uppercase (true) or not (false). Default is false."

Methods

toParam :: Proxy t -> DocQueryParam #

data DocQueryParam #

A type to represent a GET (or other possible Method) parameter from the Query String. Holds its name, the possible values (leave empty if there isn't a finite number of them), and a description of how it influences the output or behavior.

Write a ToParam instance for your GET parameter types

data ParamKind #

Type of GET (or other Method) parameter:

  • Normal corresponds to QueryParam, i.e your usual GET parameter
  • List corresponds to QueryParams, i.e GET parameters with multiple values
  • Flag corresponds to QueryFlag, i.e a value-less GET parameter

Constructors

Normal 
List 
Flag 

Instances

Instances details
Show ParamKind 
Instance details

Defined in Servant.Docs.Internal

Eq ParamKind 
Instance details

Defined in Servant.Docs.Internal

Ord ParamKind 
Instance details

Defined in Servant.Docs.Internal

class ToAuthInfo (a :: k) where #

The class that helps us get documentation for authenticated endpoints