servant-cli-0.1.0.2: Command line interface for Servant API clients

Copyright(c) Justin Le 2019
LicenseBSD3
Maintainerjustin@jle.im
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Servant.CLI.Internal.PStruct

Contents

Description

Internal module providing a data structure for representing structure of command line parsers that can be manipulated as an ADT, as well as functionality to interpret it as a Parser command line argument parser.

Synopsis

Documentation

data OptRead :: Type -> Type where Source #

How to "read" an option.

Constructors

ORRequired :: ReadM a -> OptRead a 
OROptional :: ReadM a -> OptRead (Maybe a) 
ORSwitch :: OptRead Bool 

data Opt a Source #

Query parameters are interpreted as options

Instances
Functor Opt Source # 
Instance details

Defined in Servant.CLI.Internal.PStruct

Methods

fmap :: (a -> b) -> Opt a -> Opt b #

(<$) :: a -> Opt b -> Opt a #

data Arg a Source #

Captures are interpreted as arguments

Constructors

Arg 
Instances
Functor Arg Source # 
Instance details

Defined in Servant.CLI.Internal.PStruct

Methods

fmap :: (a -> b) -> Arg a -> Arg b #

(<$) :: a -> Arg b -> Arg a #

data MultiArg :: Type -> Type where Source #

Interpret an Arg as something that can be given repeatedly an arbitrary number of times.

Constructors

MultiArg :: Arg a -> MultiArg [a] 

type Captures = Day Arg PStruct :+: Day MultiArg EndpointMap Source #

Captures can be a single capture leading to the next level, or a multi-capture leading to an endpoint action.

newtype Endpoint a Source #

Endpoint arguments and body.

Constructors

Endpoint 

Fields

Instances
Functor Endpoint Source # 
Instance details

Defined in Servant.CLI.Internal.PStruct

Methods

fmap :: (a -> b) -> Endpoint a -> Endpoint b #

(<$) :: a -> Endpoint b -> Endpoint a #

data EndpointMap a Source #

A map of endpoints associated with methods, paired with an optional "raw" endpoint.

Constructors

EPM 

Fields

Instances
Functor EndpointMap Source # 
Instance details

Defined in Servant.CLI.Internal.PStruct

Methods

fmap :: (a -> b) -> EndpointMap a -> EndpointMap b #

(<$) :: a -> EndpointMap b -> EndpointMap a #

Semigroup (EndpointMap a) Source #

Combine two EndpointMaps, preferring the left hand side for conflicts. If the left hand has a raw endpoint, the right hand's endpoints are ignored.

Instance details

Defined in Servant.CLI.Internal.PStruct

Monoid (EndpointMap a) Source # 
Instance details

Defined in Servant.CLI.Internal.PStruct

data PStruct a Source #

Structure for a parser of a given value that may use items from captures and arguments.

Constructors

PStruct 

Fields

Instances
Functor PStruct Source # 
Instance details

Defined in Servant.CLI.Internal.PStruct

Methods

fmap :: (a -> b) -> PStruct a -> PStruct b #

(<$) :: a -> PStruct b -> PStruct a #

Semigroup (PStruct a) Source #

Combine two PStructs, preferring the left hand side for conflicts. If the left hand has a capture, the right hand's components are ignored. If the left hand has a raw endpoint, the right hand's endpoints are ignored.

Instance details

Defined in Servant.CLI.Internal.PStruct

Methods

(<>) :: PStruct a -> PStruct a -> PStruct a #

sconcat :: NonEmpty (PStruct a) -> PStruct a #

stimes :: Integral b => b -> PStruct a -> PStruct a #

Monoid (PStruct a) Source # 
Instance details

Defined in Servant.CLI.Internal.PStruct

Methods

mempty :: PStruct a #

mappend :: PStruct a -> PStruct a -> PStruct a #

mconcat :: [PStruct a] -> PStruct a #

Recursive (PStruct a) Source # 
Instance details

Defined in Servant.CLI.Internal.PStruct

Methods

project :: PStruct a -> Base (PStruct a) (PStruct a) #

cata :: (Base (PStruct a) a0 -> a0) -> PStruct a -> a0 #

para :: (Base (PStruct a) (PStruct a, a0) -> a0) -> PStruct a -> a0 #

gpara :: (Corecursive (PStruct a), Comonad w) => (forall b. Base (PStruct a) (w b) -> w (Base (PStruct a) b)) -> (Base (PStruct a) (EnvT (PStruct a) w a0) -> a0) -> PStruct a -> a0 #

prepro :: Corecursive (PStruct a) => (forall b. Base (PStruct a) b -> Base (PStruct a) b) -> (Base (PStruct a) a0 -> a0) -> PStruct a -> a0 #

gprepro :: (Corecursive (PStruct a), Comonad w) => (forall b. Base (PStruct a) (w b) -> w (Base (PStruct a) b)) -> (forall c. Base (PStruct a) c -> Base (PStruct a) c) -> (Base (PStruct a) (w a0) -> a0) -> PStruct a -> a0 #

Corecursive (PStruct a) Source # 
Instance details

Defined in Servant.CLI.Internal.PStruct

Methods

embed :: Base (PStruct a) (PStruct a) -> PStruct a #

ana :: (a0 -> Base (PStruct a) a0) -> a0 -> PStruct a #

apo :: (a0 -> Base (PStruct a) (Either (PStruct a) a0)) -> a0 -> PStruct a #

postpro :: Recursive (PStruct a) => (forall b. Base (PStruct a) b -> Base (PStruct a) b) -> (a0 -> Base (PStruct a) a0) -> a0 -> PStruct a #

gpostpro :: (Recursive (PStruct a), Monad m) => (forall b. m (Base (PStruct a) b) -> Base (PStruct a) (m b)) -> (forall c. Base (PStruct a) c -> Base (PStruct a) c) -> (a0 -> Base (PStruct a) (m a0)) -> a0 -> PStruct a #

type Base (PStruct a) Source # 
Instance details

Defined in Servant.CLI.Internal.PStruct

type Base (PStruct a) = PStructF a

data PStructF (a :: Type) r Source #

Instances
Functor (PStructF a) Source # 
Instance details

Defined in Servant.CLI.Internal.PStruct

Methods

fmap :: (a0 -> b) -> PStructF a a0 -> PStructF a b #

(<$) :: a0 -> PStructF a b -> PStructF a a0 #

Foldable (PStructF a) Source # 
Instance details

Defined in Servant.CLI.Internal.PStruct

Methods

fold :: Monoid m => PStructF a m -> m #

foldMap :: Monoid m => (a0 -> m) -> PStructF a a0 -> m #

foldr :: (a0 -> b -> b) -> b -> PStructF a a0 -> b #

foldr' :: (a0 -> b -> b) -> b -> PStructF a a0 -> b #

foldl :: (b -> a0 -> b) -> b -> PStructF a a0 -> b #

foldl' :: (b -> a0 -> b) -> b -> PStructF a a0 -> b #

foldr1 :: (a0 -> a0 -> a0) -> PStructF a a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> PStructF a a0 -> a0 #

toList :: PStructF a a0 -> [a0] #

null :: PStructF a a0 -> Bool #

length :: PStructF a a0 -> Int #

elem :: Eq a0 => a0 -> PStructF a a0 -> Bool #

maximum :: Ord a0 => PStructF a a0 -> a0 #

minimum :: Ord a0 => PStructF a a0 -> a0 #

sum :: Num a0 => PStructF a a0 -> a0 #

product :: Num a0 => PStructF a a0 -> a0 #

Traversable (PStructF a) Source # 
Instance details

Defined in Servant.CLI.Internal.PStruct

Methods

traverse :: Applicative f => (a0 -> f b) -> PStructF a a0 -> f (PStructF a b) #

sequenceA :: Applicative f => PStructF a (f a0) -> f (PStructF a a0) #

mapM :: Monad m => (a0 -> m b) -> PStructF a a0 -> m (PStructF a b) #

sequence :: Monad m => PStructF a (m a0) -> m (PStructF a a0) #

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.

structParser_ Source #

Arguments

:: PStruct a 
-> Bool

add helper

-> [String]

root path

-> InfoMod a

modify top level

-> ParserInfo a 

Low-level implementation of structParser.

Creating

branch :: PStruct a -> PStruct b -> PStruct (Either a b) infixr 3 Source #

Combine two PStructs in an either-or fashion, favoring the left hand side.

($:>) :: String -> PStruct a -> PStruct a infixr 4 Source #

Shift by a path component.

(%:>) :: Parser a -> PStruct (a -> b) -> PStruct b infixr 4 Source #

Add a request body to all endpoints.

If done more than once per endpoint, it runs *both* parsers; however, we can only send one request body, so this is undefined behavior as a client.

(?:>) :: Opt a -> PStruct (a -> b) -> PStruct b infixr 4 Source #

Add a command-line option to all endpoints.

(#:>) :: Arg a -> PStruct (a -> b) -> PStruct b infixr 4 Source #

Add a single argument praser.

(##:>) :: Arg a -> PStruct ([a] -> b) -> PStruct b infixr 4 Source #

Add a repeating argument parser.

note :: [String] -> PStruct a -> PStruct a infixr 4 Source #

Add notes to the beginning of a documentation level.

endpoint :: Method -> a -> PStruct a Source #

Create an endpoint action.

rawEndpoint :: (Method -> a) -> PStruct a Source #

Create a raw endpoint.

Readers

orRequired :: ReadM a -> Coyoneda OptRead a Source #

Helper to lift a ReadM into something that can be used with optRead.

orOptional :: ReadM a -> Coyoneda OptRead (Maybe a) Source #

Helper to lift an optional ReadM into something that can be used with optRead.

orSwitch :: Coyoneda OptRead Bool Source #

An optRead that is on-or-off.