symantic-cli-2.3.3.20190711: Symantics for parsing and documenting a CLI

Safe HaskellNone
LanguageHaskell2010

Symantic.CLI.Parser

Contents

Synopsis

Type Parser

newtype Parser e d f k Source #

Constructors

Parser 

Fields

Instances
Ord e => Trans (Router (Parser e d)) Source # 
Instance details

Defined in Symantic.CLI.Parser

Associated Types

type UnTrans (Router (Parser e d)) :: Type -> Type -> Type Source #

Methods

noTrans :: UnTrans (Router (Parser e d)) a b -> Router (Parser e d) a b Source #

unTrans :: Router (Parser e d) a b -> UnTrans (Router (Parser e d)) a b Source #

CLI_Help (Router (Parser e d)) Source # 
Instance details

Defined in Symantic.CLI.Parser

Associated Types

type HelpConstraint (Router (Parser e d)) d :: Constraint Source #

Methods

help :: HelpConstraint (Router (Parser e d)) d0 => d0 -> Router (Parser e d) f k -> Router (Parser e d) f k Source #

program :: Name -> Router (Parser e d) f k -> Router (Parser e d) f k Source #

rule :: Name -> Router (Parser e d) f k -> Router (Parser e d) f k Source #

Ord e => CLI_Response (Router (Parser e d)) Source # 
Instance details

Defined in Symantic.CLI.Parser

Associated Types

type ResponseConstraint (Router (Parser e d)) a :: Constraint Source #

type ResponseArgs (Router (Parser e d)) a :: Type Source #

type Response (Router (Parser e d)) :: Type Source #

Ord e => CLI_Tag (Router (Parser e d)) Source # 
Instance details

Defined in Symantic.CLI.Parser

Associated Types

type TagConstraint (Router (Parser e d)) a :: Constraint Source #

Methods

tagged :: Tag -> Router (Parser e d) f k -> Router (Parser e d) f k Source #

endOpts :: Router (Parser e d) k k Source #

short :: TagConstraint (Router (Parser e d)) a => Char -> Router (Parser e d) (a -> k) k -> Permutation (Router (Parser e d)) k a Source #

long :: TagConstraint (Router (Parser e d)) a => Name -> Router (Parser e d) (a -> k) k -> Permutation (Router (Parser e d)) k a Source #

option :: TagConstraint (Router (Parser e d)) a => a -> Router (Parser e d) (a -> k) k -> Permutation (Router (Parser e d)) k a Source #

flag :: TagConstraint (Router (Parser e d)) Bool => Tag -> Permutation (Router (Parser e d)) k Bool Source #

shortOpt :: TagConstraint (Router (Parser e d)) a => Char -> a -> Router (Parser e d) (a -> k) k -> Permutation (Router (Parser e d)) k a Source #

longOpt :: TagConstraint (Router (Parser e d)) a => Name -> a -> Router (Parser e d) (a -> k) k -> Permutation (Router (Parser e d)) k a Source #

Ord e => CLI_Env (Router (Parser e d)) Source # 
Instance details

Defined in Symantic.CLI.Parser

Associated Types

type EnvConstraint (Router (Parser e d)) a :: Constraint Source #

Methods

env' :: EnvConstraint (Router (Parser e d)) a => Name -> Router (Parser e d) (a -> k) k Source #

Ord e => CLI_Var (Router (Parser e d)) Source # 
Instance details

Defined in Symantic.CLI.Parser

Associated Types

type VarConstraint (Router (Parser e d)) a :: Constraint Source #

Methods

var' :: VarConstraint (Router (Parser e d)) a => Name -> Router (Parser e d) (a -> k) k Source #

just :: a -> Router (Parser e d) (a -> k) k Source #

nothing :: Router (Parser e d) k k Source #

Ord e => Permutable (Router (Parser e d)) Source # 
Instance details

Defined in Symantic.CLI.Parser

Associated Types

type Permutation (Router (Parser e d)) = (r :: Type -> Type -> Type) Source #

Methods

runPermutation :: Permutation (Router (Parser e d)) k a -> Router (Parser e d) (a -> k) k Source #

toPermutation :: Router (Parser e d) (a -> k) k -> Permutation (Router (Parser e d)) k a Source #

toPermDefault :: a -> Router (Parser e d) (a -> k) k -> Permutation (Router (Parser e d)) k a Source #

Ord e => Pro (Router (Parser e d)) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

dimap :: (a -> b) -> (b -> a) -> Router (Parser e d) (a -> k) k -> Router (Parser e d) (b -> k) k Source #

Ord e => Alt (Router (Parser e d)) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

(<!>) :: Router (Parser e d) a k -> Router (Parser e d) b k -> Router (Parser e d) (a :!: b) k Source #

alt :: Router (Parser e d) a k -> Router (Parser e d) a k -> Router (Parser e d) a k Source #

opt :: Router (Parser e d) (a -> k) k -> Router (Parser e d) (Maybe a -> k) k Source #

Ord e => App (Router (Parser e d)) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

(<.>) :: Router (Parser e d) a b -> Router (Parser e d) b c -> Router (Parser e d) a c Source #

Ord e => CLI_Routing (Router (Parser e d)) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

commands :: Map Name (Router (Parser e d) a k) -> Map Name (Router (Parser e d) a k) -> Router (Parser e d) a k Source #

Ord e => Functor (Router (Parser e d) f) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

fmap :: (a -> b) -> Router (Parser e d) f a -> Router (Parser e d) f b #

(<$) :: a -> Router (Parser e d) f b -> Router (Parser e d) f a #

Ord e => Applicative (Router (Parser e d) f) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

pure :: a -> Router (Parser e d) f a #

(<*>) :: Router (Parser e d) f (a -> b) -> Router (Parser e d) f a -> Router (Parser e d) f b #

liftA2 :: (a -> b -> c) -> Router (Parser e d) f a -> Router (Parser e d) f b -> Router (Parser e d) f c #

(*>) :: Router (Parser e d) f a -> Router (Parser e d) f b -> Router (Parser e d) f b #

(<*) :: Router (Parser e d) f a -> Router (Parser e d) f b -> Router (Parser e d) f a #

Ord e => Alternative (Router (Parser e d) f) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

empty :: Router (Parser e d) f a #

(<|>) :: Router (Parser e d) f a -> Router (Parser e d) f a -> Router (Parser e d) f a #

some :: Router (Parser e d) f a -> Router (Parser e d) f [a] #

many :: Router (Parser e d) f a -> Router (Parser e d) f [a] #

Ord e => CLI_Help (Parser e d) Source # 
Instance details

Defined in Symantic.CLI.Parser

Associated Types

type HelpConstraint (Parser e d) d :: Constraint Source #

Methods

help :: HelpConstraint (Parser e d) d0 => d0 -> Parser e d f k -> Parser e d f k Source #

program :: Name -> Parser e d f k -> Parser e d f k Source #

rule :: Name -> Parser e d f k -> Parser e d f k Source #

Ord e => CLI_Response (Parser e d) Source # 
Instance details

Defined in Symantic.CLI.Parser

Associated Types

type ResponseConstraint (Parser e d) a :: Constraint Source #

type ResponseArgs (Parser e d) a :: Type Source #

type Response (Parser e d) :: Type Source #

Methods

response' :: ResponseConstraint (Parser e d) a => Parser e d (ResponseArgs (Parser e d) a) (Response (Parser e d)) Source #

Ord e => CLI_Tag (Parser e d) Source # 
Instance details

Defined in Symantic.CLI.Parser

Associated Types

type TagConstraint (Parser e d) a :: Constraint Source #

Methods

tagged :: Tag -> Parser e d f k -> Parser e d f k Source #

endOpts :: Parser e d k k Source #

short :: TagConstraint (Parser e d) a => Char -> Parser e d (a -> k) k -> Permutation (Parser e d) k a Source #

long :: TagConstraint (Parser e d) a => Name -> Parser e d (a -> k) k -> Permutation (Parser e d) k a Source #

option :: TagConstraint (Parser e d) a => a -> Parser e d (a -> k) k -> Permutation (Parser e d) k a Source #

flag :: TagConstraint (Parser e d) Bool => Tag -> Permutation (Parser e d) k Bool Source #

shortOpt :: TagConstraint (Parser e d) a => Char -> a -> Parser e d (a -> k) k -> Permutation (Parser e d) k a Source #

longOpt :: TagConstraint (Parser e d) a => Name -> a -> Parser e d (a -> k) k -> Permutation (Parser e d) k a Source #

Ord e => CLI_Env (Parser e d) Source # 
Instance details

Defined in Symantic.CLI.Parser

Associated Types

type EnvConstraint (Parser e d) a :: Constraint Source #

Methods

env' :: EnvConstraint (Parser e d) a => Name -> Parser e d (a -> k) k Source #

Ord e => CLI_Var (Parser e d) Source # 
Instance details

Defined in Symantic.CLI.Parser

Associated Types

type VarConstraint (Parser e d) a :: Constraint Source #

Methods

var' :: VarConstraint (Parser e d) a => Name -> Parser e d (a -> k) k Source #

just :: a -> Parser e d (a -> k) k Source #

nothing :: Parser e d k k Source #

Ord e => CLI_Command (Parser e d) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

command :: Name -> Parser e d a k -> Parser e d a k Source #

Ord e => Permutable (Parser e d) Source # 
Instance details

Defined in Symantic.CLI.Parser

Associated Types

type Permutation (Parser e d) = (r :: Type -> Type -> Type) Source #

Methods

runPermutation :: Permutation (Parser e d) k a -> Parser e d (a -> k) k Source #

toPermutation :: Parser e d (a -> k) k -> Permutation (Parser e d) k a Source #

toPermDefault :: a -> Parser e d (a -> k) k -> Permutation (Parser e d) k a Source #

Ord e => AltApp (Parser e d) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

many0 :: Parser e d (a -> k) k -> Parser e d ([a] -> k) k Source #

many1 :: Parser e d (a -> k) k -> Parser e d ([a] -> k) k Source #

Pro (Parser e d) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

dimap :: (a -> b) -> (b -> a) -> Parser e d (a -> k) k -> Parser e d (b -> k) k Source #

Ord e => Alt (Parser e d) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

(<!>) :: Parser e d a k -> Parser e d b k -> Parser e d (a :!: b) k Source #

alt :: Parser e d a k -> Parser e d a k -> Parser e d a k Source #

opt :: Parser e d (a -> k) k -> Parser e d (Maybe a -> k) k Source #

App (Parser e d) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

(<.>) :: Parser e d a b -> Parser e d b c -> Parser e d a c Source #

Ord e => CLI_Routing (Parser e d) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

commands :: Map Name (Parser e d a k) -> Map Name (Parser e d a k) -> Parser e d a k Source #

Functor (Parser e d f) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

fmap :: (a -> b) -> Parser e d f a -> Parser e d f b #

(<$) :: a -> Parser e d f b -> Parser e d f a #

Applicative (Parser e d f) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

pure :: a -> Parser e d f a #

(<*>) :: Parser e d f (a -> b) -> Parser e d f a -> Parser e d f b #

liftA2 :: (a -> b -> c) -> Parser e d f a -> Parser e d f b -> Parser e d f c #

(*>) :: Parser e d f a -> Parser e d f b -> Parser e d f b #

(<*) :: Parser e d f a -> Parser e d f b -> Parser e d f a #

Ord e => Alternative (Parser e d f) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

empty :: Parser e d f a #

(<|>) :: Parser e d f a -> Parser e d f a -> Parser e d f a #

some :: Parser e d f a -> Parser e d f [a] #

many :: Parser e d f a -> Parser e d f [a] #

type UnTrans (Router (Parser e d)) Source # 
Instance details

Defined in Symantic.CLI.Parser

type UnTrans (Router (Parser e d)) = Parser e d
type Response (Router (Parser e d)) Source # 
Instance details

Defined in Symantic.CLI.Parser

type Permutation (Router (Parser e d)) Source # 
Instance details

Defined in Symantic.CLI.Parser

type Permutation (Router (Parser e d)) = ParserPerm e d (Router (Parser e d))
type HelpConstraint (Router (Parser e d1)) d2 Source # 
Instance details

Defined in Symantic.CLI.Parser

type ResponseConstraint (Router (Parser e d)) a Source # 
Instance details

Defined in Symantic.CLI.Parser

type ResponseArgs (Router (Parser e d)) a Source # 
Instance details

Defined in Symantic.CLI.Parser

type TagConstraint (Router (Parser e d)) a Source # 
Instance details

Defined in Symantic.CLI.Parser

type EnvConstraint (Router (Parser e d)) a Source # 
Instance details

Defined in Symantic.CLI.Parser

type VarConstraint (Router (Parser e d)) a Source # 
Instance details

Defined in Symantic.CLI.Parser

type Response (Parser e d) Source # 
Instance details

Defined in Symantic.CLI.Parser

type Permutation (Parser e d) Source # 
Instance details

Defined in Symantic.CLI.Parser

type Permutation (Parser e d) = ParserPerm e d (Parser e d)
type HelpConstraint (Parser e d) d' Source # 
Instance details

Defined in Symantic.CLI.Parser

type HelpConstraint (Parser e d) d' = d ~ d'
type ResponseConstraint (Parser e d) a Source # 
Instance details

Defined in Symantic.CLI.Parser

type ResponseArgs (Parser e d) a Source # 
Instance details

Defined in Symantic.CLI.Parser

type TagConstraint (Parser e d) a Source # 
Instance details

Defined in Symantic.CLI.Parser

type TagConstraint (Parser e d) a = ()
type EnvConstraint (Parser e d) a Source # 
Instance details

Defined in Symantic.CLI.Parser

type EnvConstraint (Parser e d) a = (IOType a, FromSegment a)
type VarConstraint (Parser e d) a Source # 
Instance details

Defined in Symantic.CLI.Parser

type VarConstraint (Parser e d) a = (IOType a, FromSegment a)

parser :: ShowErrorComponent e => Router (Parser e d) handlers (Response (Router (Parser e d))) -> handlers -> [Arg] -> IO () Source #

concatCont :: [(a -> k) -> k] -> ([a] -> k) -> k Source #

consCont :: (a -> b -> c) -> ((a -> k) -> k) -> ((b -> k) -> k) -> (c -> k) -> k Source #

mapCont :: (a -> b) -> ((a -> k) -> k) -> (b -> k) -> k Source #

Type ParserResponse

newtype ParserResponse Source #

Constructors

ParserResponse 

Fields

Type ParserResponseArgs

Class Outputable

class IOType a => Outputable a where Source #

Output of a CLI.

Minimal complete definition

Nothing

Methods

output :: a -> IO () Source #

output :: Show a => a -> IO () Source #

Instances
Outputable Bool Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

output :: Bool -> IO () Source #

Outputable Char Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

output :: Char -> IO () Source #

Outputable Int Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

output :: Int -> IO () Source #

Outputable Integer Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

output :: Integer -> IO () Source #

Outputable Natural Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

output :: Natural -> IO () Source #

Outputable () Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

output :: () -> IO () Source #

Outputable String Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

output :: String -> IO () Source #

Outputable Text Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

output :: Text -> IO () Source #

Outputable Text Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

output :: Text -> IO () Source #

Outputable (Plain Builder) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

output :: Plain Builder -> IO () Source #

Outputable (OnHandle Bool) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

output :: OnHandle Bool -> IO () Source #

Outputable (OnHandle Char) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

output :: OnHandle Char -> IO () Source #

Outputable (OnHandle Int) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

output :: OnHandle Int -> IO () Source #

Outputable (OnHandle Integer) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

output :: OnHandle Integer -> IO () Source #

Outputable (OnHandle Natural) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

output :: OnHandle Natural -> IO () Source #

Outputable (OnHandle ()) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

output :: OnHandle () -> IO () Source #

Outputable (OnHandle String) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

output :: OnHandle String -> IO () Source #

Outputable (OnHandle Text) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

output :: OnHandle Text -> IO () Source #

Outputable (OnHandle (Plain Builder)) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

output :: OnHandle (Plain Builder) -> IO () Source #

Outputable (OnHandle Text) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

output :: OnHandle Text -> IO () Source #

Type OnHandle

data OnHandle a Source #

Constructors

OnHandle Handle a 
Instances
IOType a => IOType (OnHandle a) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

ioType :: String Source #

Outputable (OnHandle Bool) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

output :: OnHandle Bool -> IO () Source #

Outputable (OnHandle Char) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

output :: OnHandle Char -> IO () Source #

Outputable (OnHandle Int) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

output :: OnHandle Int -> IO () Source #

Outputable (OnHandle Integer) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

output :: OnHandle Integer -> IO () Source #

Outputable (OnHandle Natural) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

output :: OnHandle Natural -> IO () Source #

Outputable (OnHandle ()) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

output :: OnHandle () -> IO () Source #

Outputable (OnHandle String) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

output :: OnHandle String -> IO () Source #

Outputable (OnHandle Text) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

output :: OnHandle Text -> IO () Source #

Outputable (OnHandle (Plain Builder)) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

output :: OnHandle (Plain Builder) -> IO () Source #

Outputable (OnHandle Text) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

output :: OnHandle Text -> IO () Source #

Class IOType

class IOType a where Source #

Like a MIME type but for input/output of a CLI.

Minimal complete definition

Nothing

Instances
IOType Bool Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

ioType :: String Source #

IOType Char Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

ioType :: String Source #

IOType Int Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

ioType :: String Source #

IOType Integer Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

ioType :: String Source #

IOType Natural Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

ioType :: String Source #

IOType () Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

ioType :: String Source #

IOType String Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

ioType :: String Source #

IOType Text Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

ioType :: String Source #

IOType Text Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

ioType :: String Source #

IOType (Plain Builder) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

ioType :: String Source #

IOType a => IOType (OnHandle a) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

ioType :: String Source #

IOType (Handle, Plain Builder) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

ioType :: String Source #

Class FromSegment

class FromSegment a where Source #

Minimal complete definition

Nothing

Type ParserPerm

data ParserPerm e d repr k a Source #

Constructors

ParserPerm 

Fields

Instances
CLI_Help repr => CLI_Help (ParserPerm e d repr) Source # 
Instance details

Defined in Symantic.CLI.Parser

Associated Types

type HelpConstraint (ParserPerm e d repr) d :: Constraint Source #

Methods

help :: HelpConstraint (ParserPerm e d repr) d0 => d0 -> ParserPerm e d repr f k -> ParserPerm e d repr f k Source #

program :: Name -> ParserPerm e d repr f k -> ParserPerm e d repr f k Source #

rule :: Name -> ParserPerm e d repr f k -> ParserPerm e d repr f k Source #

(App repr, Functor (repr ())) => Functor (ParserPerm e d repr k) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

fmap :: (a -> b) -> ParserPerm e d repr k a -> ParserPerm e d repr k b #

(<$) :: a -> ParserPerm e d repr k b -> ParserPerm e d repr k a #

(App repr, Functor (repr ()), Alternative (repr ())) => Applicative (ParserPerm e d repr k) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

pure :: a -> ParserPerm e d repr k a #

(<*>) :: ParserPerm e d repr k (a -> b) -> ParserPerm e d repr k a -> ParserPerm e d repr k b #

liftA2 :: (a -> b -> c) -> ParserPerm e d repr k a -> ParserPerm e d repr k b -> ParserPerm e d repr k c #

(*>) :: ParserPerm e d repr k a -> ParserPerm e d repr k b -> ParserPerm e d repr k b #

(<*) :: ParserPerm e d repr k a -> ParserPerm e d repr k b -> ParserPerm e d repr k a #

type HelpConstraint (ParserPerm e d repr) d' Source # 
Instance details

Defined in Symantic.CLI.Parser

type HelpConstraint (ParserPerm e d repr) d' = HelpConstraint (Parser e d) d'

noTransParserPerm :: Trans repr => Functor (UnTrans repr ()) => ParserPerm e d (UnTrans repr) k a -> ParserPerm e d repr k a Source #

unTransParserPerm :: Trans repr => Functor (UnTrans repr ()) => ParserPerm e d repr k a -> ParserPerm e d (UnTrans repr) k a Source #

hoistParserPerm :: Functor (repr ()) => (forall a b. repr a b -> repr a b) -> ParserPerm e d repr k c -> ParserPerm e d repr k c Source #

Class CLI_Routing

class CLI_Routing repr where Source #

Methods

commands :: Map Name (repr a k) -> Map Name (repr a k) -> repr a k Source #

Instances
Ord e => CLI_Routing (Router (Parser e d)) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

commands :: Map Name (Router (Parser e d) a k) -> Map Name (Router (Parser e d) a k) -> Router (Parser e d) a k Source #

Ord e => CLI_Routing (Parser e d) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

commands :: Map Name (Parser e d a k) -> Map Name (Parser e d a k) -> Parser e d a k Source #

Type Router

data Router repr a b where Source #

Constructors

Router_Any :: repr a b -> Router repr a b

Lift any (repr) into Router, those not useful to segregate wrt. the Transformation performed, aka. noTrans.

Router_Commands :: Map Name (Router repr a k) -> Map Name (Router repr a k) -> Router repr a k

Represent commands.

Router_Tagged :: Tag -> Router repr f k -> Router repr f k

Represent tagged.

Router_App :: Router repr a b -> Router repr b c -> Router repr a c

Represent (<.>).

Router_Alt :: Router repr a k -> Router repr b k -> Router repr (a :!: b) k

Represent (<!>).

Router_Union :: (b -> a) -> Router repr a k -> Router repr b k

Unify Routers which have different handlers. Useful to put alternative Routers in a Map as in Router_Commands.

Instances
Ord e => Trans (Router (Parser e d)) Source # 
Instance details

Defined in Symantic.CLI.Parser

Associated Types

type UnTrans (Router (Parser e d)) :: Type -> Type -> Type Source #

Methods

noTrans :: UnTrans (Router (Parser e d)) a b -> Router (Parser e d) a b Source #

unTrans :: Router (Parser e d) a b -> UnTrans (Router (Parser e d)) a b Source #

CLI_Help (Router (Parser e d)) Source # 
Instance details

Defined in Symantic.CLI.Parser

Associated Types

type HelpConstraint (Router (Parser e d)) d :: Constraint Source #

Methods

help :: HelpConstraint (Router (Parser e d)) d0 => d0 -> Router (Parser e d) f k -> Router (Parser e d) f k Source #

program :: Name -> Router (Parser e d) f k -> Router (Parser e d) f k Source #

rule :: Name -> Router (Parser e d) f k -> Router (Parser e d) f k Source #

Ord e => CLI_Response (Router (Parser e d)) Source # 
Instance details

Defined in Symantic.CLI.Parser

Associated Types

type ResponseConstraint (Router (Parser e d)) a :: Constraint Source #

type ResponseArgs (Router (Parser e d)) a :: Type Source #

type Response (Router (Parser e d)) :: Type Source #

Ord e => CLI_Tag (Router (Parser e d)) Source # 
Instance details

Defined in Symantic.CLI.Parser

Associated Types

type TagConstraint (Router (Parser e d)) a :: Constraint Source #

Methods

tagged :: Tag -> Router (Parser e d) f k -> Router (Parser e d) f k Source #

endOpts :: Router (Parser e d) k k Source #

short :: TagConstraint (Router (Parser e d)) a => Char -> Router (Parser e d) (a -> k) k -> Permutation (Router (Parser e d)) k a Source #

long :: TagConstraint (Router (Parser e d)) a => Name -> Router (Parser e d) (a -> k) k -> Permutation (Router (Parser e d)) k a Source #

option :: TagConstraint (Router (Parser e d)) a => a -> Router (Parser e d) (a -> k) k -> Permutation (Router (Parser e d)) k a Source #

flag :: TagConstraint (Router (Parser e d)) Bool => Tag -> Permutation (Router (Parser e d)) k Bool Source #

shortOpt :: TagConstraint (Router (Parser e d)) a => Char -> a -> Router (Parser e d) (a -> k) k -> Permutation (Router (Parser e d)) k a Source #

longOpt :: TagConstraint (Router (Parser e d)) a => Name -> a -> Router (Parser e d) (a -> k) k -> Permutation (Router (Parser e d)) k a Source #

Ord e => CLI_Env (Router (Parser e d)) Source # 
Instance details

Defined in Symantic.CLI.Parser

Associated Types

type EnvConstraint (Router (Parser e d)) a :: Constraint Source #

Methods

env' :: EnvConstraint (Router (Parser e d)) a => Name -> Router (Parser e d) (a -> k) k Source #

Ord e => CLI_Var (Router (Parser e d)) Source # 
Instance details

Defined in Symantic.CLI.Parser

Associated Types

type VarConstraint (Router (Parser e d)) a :: Constraint Source #

Methods

var' :: VarConstraint (Router (Parser e d)) a => Name -> Router (Parser e d) (a -> k) k Source #

just :: a -> Router (Parser e d) (a -> k) k Source #

nothing :: Router (Parser e d) k k Source #

repr ~ Parser e d => CLI_Command (Router repr) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

command :: Name -> Router repr a k -> Router repr a k Source #

Ord e => Permutable (Router (Parser e d)) Source # 
Instance details

Defined in Symantic.CLI.Parser

Associated Types

type Permutation (Router (Parser e d)) = (r :: Type -> Type -> Type) Source #

Methods

runPermutation :: Permutation (Router (Parser e d)) k a -> Router (Parser e d) (a -> k) k Source #

toPermutation :: Router (Parser e d) (a -> k) k -> Permutation (Router (Parser e d)) k a Source #

toPermDefault :: a -> Router (Parser e d) (a -> k) k -> Permutation (Router (Parser e d)) k a Source #

Ord e => Pro (Router (Parser e d)) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

dimap :: (a -> b) -> (b -> a) -> Router (Parser e d) (a -> k) k -> Router (Parser e d) (b -> k) k Source #

Ord e => Alt (Router (Parser e d)) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

(<!>) :: Router (Parser e d) a k -> Router (Parser e d) b k -> Router (Parser e d) (a :!: b) k Source #

alt :: Router (Parser e d) a k -> Router (Parser e d) a k -> Router (Parser e d) a k Source #

opt :: Router (Parser e d) (a -> k) k -> Router (Parser e d) (Maybe a -> k) k Source #

Ord e => App (Router (Parser e d)) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

(<.>) :: Router (Parser e d) a b -> Router (Parser e d) b c -> Router (Parser e d) a c Source #

Ord e => CLI_Routing (Router (Parser e d)) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

commands :: Map Name (Router (Parser e d) a k) -> Map Name (Router (Parser e d) a k) -> Router (Parser e d) a k Source #

Ord e => Functor (Router (Parser e d) f) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

fmap :: (a -> b) -> Router (Parser e d) f a -> Router (Parser e d) f b #

(<$) :: a -> Router (Parser e d) f b -> Router (Parser e d) f a #

Ord e => Applicative (Router (Parser e d) f) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

pure :: a -> Router (Parser e d) f a #

(<*>) :: Router (Parser e d) f (a -> b) -> Router (Parser e d) f a -> Router (Parser e d) f b #

liftA2 :: (a -> b -> c) -> Router (Parser e d) f a -> Router (Parser e d) f b -> Router (Parser e d) f c #

(*>) :: Router (Parser e d) f a -> Router (Parser e d) f b -> Router (Parser e d) f b #

(<*) :: Router (Parser e d) f a -> Router (Parser e d) f b -> Router (Parser e d) f a #

Ord e => Alternative (Router (Parser e d) f) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

empty :: Router (Parser e d) f a #

(<|>) :: Router (Parser e d) f a -> Router (Parser e d) f a -> Router (Parser e d) f a #

some :: Router (Parser e d) f a -> Router (Parser e d) f [a] #

many :: Router (Parser e d) f a -> Router (Parser e d) f [a] #

repr ~ Parser e d => Show (Router repr a b) Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

showsPrec :: Int -> Router repr a b -> ShowS #

show :: Router repr a b -> String #

showList :: [Router repr a b] -> ShowS #

type UnTrans (Router (Parser e d)) Source # 
Instance details

Defined in Symantic.CLI.Parser

type UnTrans (Router (Parser e d)) = Parser e d
type Response (Router (Parser e d)) Source # 
Instance details

Defined in Symantic.CLI.Parser

type Permutation (Router (Parser e d)) Source # 
Instance details

Defined in Symantic.CLI.Parser

type Permutation (Router (Parser e d)) = ParserPerm e d (Router (Parser e d))
type HelpConstraint (Router (Parser e d1)) d2 Source # 
Instance details

Defined in Symantic.CLI.Parser

type ResponseConstraint (Router (Parser e d)) a Source # 
Instance details

Defined in Symantic.CLI.Parser

type ResponseArgs (Router (Parser e d)) a Source # 
Instance details

Defined in Symantic.CLI.Parser

type TagConstraint (Router (Parser e d)) a Source # 
Instance details

Defined in Symantic.CLI.Parser

type EnvConstraint (Router (Parser e d)) a Source # 
Instance details

Defined in Symantic.CLI.Parser

type VarConstraint (Router (Parser e d)) a Source # 
Instance details

Defined in Symantic.CLI.Parser

router :: repr ~ Parser e d => Router repr a b -> Router repr a b Source #

router_Alt :: repr ~ Parser e d => Router repr a k -> Router repr b k -> Router repr (a :!: b) k Source #

Merge/reorder alternatives if possible or default to a Router_Alt.

router_Commands :: repr ~ Parser e d => Bool -> Map Segment (Router repr a k) -> Map Segment (Router repr b k) -> Map Segment (Router repr (a :!: b) k) Source #

Type Arg

data Arg Source #

Constructors

ArgSegment Segment 
ArgTagLong Name 
ArgTagShort Char 
ArgEnv Name String

Here only for error reporting.

Instances
Eq Arg Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

(==) :: Arg -> Arg -> Bool #

(/=) :: Arg -> Arg -> Bool #

Ord Arg Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

compare :: Arg -> Arg -> Ordering #

(<) :: Arg -> Arg -> Bool #

(<=) :: Arg -> Arg -> Bool #

(>) :: Arg -> Arg -> Bool #

(>=) :: Arg -> Arg -> Bool #

max :: Arg -> Arg -> Arg #

min :: Arg -> Arg -> Arg #

Show Arg Source # 
Instance details

Defined in Symantic.CLI.Parser

Methods

showsPrec :: Int -> Arg -> ShowS #

show :: Arg -> String #

showList :: [Arg] -> ShowS #

Stream [Arg] Source # 
Instance details

Defined in Symantic.CLI.Parser

Associated Types

type Token [Arg] :: Type #

type Tokens [Arg] :: Type #

type Tokens [Arg] Source # 
Instance details

Defined in Symantic.CLI.Parser

type Tokens [Arg] = [Arg]
type Token [Arg] Source # 
Instance details

Defined in Symantic.CLI.Parser

type Token [Arg] = Arg

lexer :: [String] -> [Arg] Source #