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

Safe HaskellSafe
LanguageHaskell2010

Symantic.CLI.API

Contents

Synopsis

Class App

class App repr where Source #

Minimal complete definition

Nothing

Methods

(<.>) :: repr a b -> repr b c -> repr a c infixr 4 Source #

(<.>) :: Trans repr => App (UnTrans repr) => repr a b -> repr b c -> repr a c infixr 4 Source #

Instances
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 #

SchemaDoc d => App (Schema d) Source # 
Instance details

Defined in Symantic.CLI.Schema

Methods

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

LayoutDoc d => App (Layout d) Source # 
Instance details

Defined in Symantic.CLI.Layout

Methods

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

SchemaDoc d => App (Help d) Source # 
Instance details

Defined in Symantic.CLI.Help

Methods

(<.>) :: Help d a b -> Help d b c -> Help d a c 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 #

Class Alt

class Alt repr where Source #

Minimal complete definition

Nothing

Methods

(<!>) :: repr a k -> repr b k -> repr (a :!: b) k infixr 3 Source #

alt :: repr a k -> repr a k -> repr a k infixr 3 Source #

opt :: repr (a -> k) k -> repr (Maybe a -> k) k Source #

(<!>) :: Trans repr => Alt (UnTrans repr) => repr a k -> repr b k -> repr (a :!: b) k infixr 3 Source #

alt :: Trans repr => Alt (UnTrans repr) => repr a k -> repr a k -> repr a k infixr 3 Source #

opt :: Trans repr => Alt (UnTrans repr) => repr (a -> k) k -> repr (Maybe a -> k) k Source #

Instances
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 #

SchemaDoc d => Alt (Schema d) Source # 
Instance details

Defined in Symantic.CLI.Schema

Methods

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

alt :: Schema d a k -> Schema d a k -> Schema d a k Source #

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

LayoutDoc d => Alt (Layout d) Source # 
Instance details

Defined in Symantic.CLI.Layout

Methods

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

alt :: Layout d a k -> Layout d a k -> Layout d a k Source #

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

SchemaDoc d => Alt (Help d) Source # 
Instance details

Defined in Symantic.CLI.Help

Methods

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

alt :: Help d a k -> Help d a k -> Help d a k Source #

opt :: Help d (a -> k) k -> Help d (Maybe a -> 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 #

Type (:!:)

data a :!: b infixr 3 Source #

Like (,) but infixr.

Constructors

a :!: b infixr 3 

Class Pro

class Pro repr where Source #

Minimal complete definition

Nothing

Methods

dimap :: (a -> b) -> (b -> a) -> repr (a -> k) k -> repr (b -> k) k Source #

dimap :: Trans repr => Pro (UnTrans repr) => (a -> b) -> (b -> a) -> repr (a -> k) k -> repr (b -> k) k Source #

Instances
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 #

Pro (Schema d) Source # 
Instance details

Defined in Symantic.CLI.Schema

Methods

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

Pro (Layout d) Source # 
Instance details

Defined in Symantic.CLI.Layout

Methods

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

Pro (Help d) Source # 
Instance details

Defined in Symantic.CLI.Help

Methods

dimap :: (a -> b) -> (b -> a) -> Help d (a -> k) k -> Help d (b -> 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 #

Class AltApp

class AltApp repr where Source #

Minimal complete definition

Nothing

Methods

many0 :: repr (a -> k) k -> repr ([a] -> k) k Source #

many1 :: repr (a -> k) k -> repr ([a] -> k) k Source #

many0 :: Trans repr => AltApp (UnTrans repr) => repr (a -> k) k -> repr ([a] -> k) k Source #

many1 :: Trans repr => AltApp (UnTrans repr) => repr (a -> k) k -> repr ([a] -> k) k Source #

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

Defined in Symantic.CLI.Parser

Methods

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

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

SchemaDoc d => AltApp (Schema d) Source # 
Instance details

Defined in Symantic.CLI.Schema

Methods

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

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

LayoutDoc d => AltApp (Layout d) Source # 
Instance details

Defined in Symantic.CLI.Layout

Methods

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

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

SchemaDoc d => AltApp (Help d) Source # 
Instance details

Defined in Symantic.CLI.Help

Methods

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

many1 :: Help d (a -> k) k -> Help d ([a] -> k) k 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 #

Class Permutable

class Permutable repr where Source #

Associated Types

type Permutation (repr :: * -> * -> *) = (r :: * -> * -> *) | r -> repr Source #

Methods

runPermutation :: Permutation repr k a -> repr (a -> k) k Source #

toPermutation :: repr (a -> k) k -> Permutation repr k a Source #

toPermDefault :: a -> repr (a -> k) k -> Permutation repr k a Source #

Instances
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 #

SchemaDoc d => Permutable (Schema d) Source # 
Instance details

Defined in Symantic.CLI.Schema

Associated Types

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

Methods

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

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

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

(LayoutDoc d, Justifiable d) => Permutable (Layout d) Source # 
Instance details

Defined in Symantic.CLI.Layout

Associated Types

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

Methods

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

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

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

SchemaDoc d => Permutable (Help d) Source # 
Instance details

Defined in Symantic.CLI.Help

Associated Types

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

Methods

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

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

toPermDefault :: a -> Help d (a -> k) k -> Permutation (Help d) k a 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 #

(<?>) :: App repr => Permutable repr => Permutation repr b a -> repr b c -> repr (a -> b) c infixr 4 Source #

Convenient wrapper to omit a runPermutation.

opts <?> next = runPermutation opts <.> next

Class Sequenceable

class Sequenceable repr where Source #

Associated Types

type Sequence (repr :: * -> * -> *) = (r :: * -> * -> *) | r -> repr Source #

Methods

runSequence :: Sequence repr k a -> repr (a -> k) k Source #

toSequence :: repr (a -> k) k -> Sequence repr k a Source #

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

Defined in Symantic.CLI.Parser

Associated Types

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

Methods

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

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

SchemaDoc d => Sequenceable (Schema d) Source # 
Instance details

Defined in Symantic.CLI.Schema

Associated Types

type Sequence (Schema d) = (r :: Type -> Type -> Type) Source #

Methods

runSequence :: Sequence (Schema d) k a -> Schema d (a -> k) k Source #

toSequence :: Schema d (a -> k) k -> Sequence (Schema d) k a Source #

(LayoutDoc d, Justifiable d) => Sequenceable (Layout d) Source # 
Instance details

Defined in Symantic.CLI.Layout

Associated Types

type Sequence (Layout d) = (r :: Type -> Type -> Type) Source #

Methods

runSequence :: Sequence (Layout d) k a -> Layout d (a -> k) k Source #

toSequence :: Layout d (a -> k) k -> Sequence (Layout d) k a Source #

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

Defined in Symantic.CLI.Parser

Associated Types

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

Methods

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

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

Type Name

Type Segment

Class CLI_Command

class CLI_Command repr where Source #

Methods

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

Instances
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 #

SchemaDoc d => CLI_Command (Schema d) Source # 
Instance details

Defined in Symantic.CLI.Schema

Methods

command :: Name -> Schema d a k -> Schema d a k Source #

(LayoutDoc d, From Name d) => CLI_Command (Layout d) Source # 
Instance details

Defined in Symantic.CLI.Layout

Methods

command :: Name -> Layout d a k -> Layout d a k Source #

SchemaDoc d => CLI_Command (Help d) Source # 
Instance details

Defined in Symantic.CLI.Help

Methods

command :: Name -> Help d a k -> Help d a 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 #

Class CLI_Var

class CLI_Var repr where Source #

Minimal complete definition

Nothing

Associated Types

type VarConstraint repr a :: Constraint Source #

Methods

var' :: VarConstraint repr a => Name -> repr (a -> k) k Source #

just :: a -> repr (a -> k) k Source #

nothing :: repr k k Source #

var' :: Trans repr => CLI_Var (UnTrans repr) => VarConstraint (UnTrans repr) a => Name -> repr (a -> k) k Source #

just :: Trans repr => CLI_Var (UnTrans repr) => a -> repr (a -> k) k Source #

nothing :: Trans repr => CLI_Var (UnTrans repr) => repr k k Source #

Instances
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 #

SchemaDoc d => CLI_Var (Schema d) Source # 
Instance details

Defined in Symantic.CLI.Schema

Associated Types

type VarConstraint (Schema d) a :: Constraint Source #

Methods

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

just :: a -> Schema d (a -> k) k Source #

nothing :: Schema d k k Source #

LayoutDoc d => CLI_Var (Layout d) Source # 
Instance details

Defined in Symantic.CLI.Layout

Associated Types

type VarConstraint (Layout d) a :: Constraint Source #

Methods

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

just :: a -> Layout d (a -> k) k Source #

nothing :: Layout d k k Source #

SchemaDoc d => CLI_Var (Help d) Source # 
Instance details

Defined in Symantic.CLI.Help

Associated Types

type VarConstraint (Help d) a :: Constraint Source #

Methods

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

just :: a -> Help d (a -> k) k Source #

nothing :: Help d 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 #

var :: forall a k repr. CLI_Var repr => VarConstraint repr a => Name -> repr (a -> k) k Source #

Like var' but with the type variable (a) first instead or (repr) so it can be passed using TypeApplications without adding a |@_| for (repr).

Class CLI_Env

class CLI_Env repr where Source #

Minimal complete definition

Nothing

Associated Types

type EnvConstraint repr a :: Constraint Source #

Methods

env' :: EnvConstraint repr a => Name -> repr (a -> k) k Source #

env' :: Trans repr => CLI_Env (UnTrans repr) => EnvConstraint (UnTrans repr) a => Name -> repr (a -> k) k Source #

Instances
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 #

SchemaDoc d => CLI_Env (Schema d) Source # 
Instance details

Defined in Symantic.CLI.Schema

Associated Types

type EnvConstraint (Schema d) a :: Constraint Source #

Methods

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

LayoutDoc d => CLI_Env (Layout d) Source # 
Instance details

Defined in Symantic.CLI.Layout

Associated Types

type EnvConstraint (Layout d) a :: Constraint Source #

Methods

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

SchemaDoc d => CLI_Env (Help d) Source # 
Instance details

Defined in Symantic.CLI.Help

Associated Types

type EnvConstraint (Help d) a :: Constraint Source #

Methods

env' :: EnvConstraint (Help d) a => Name -> Help d (a -> k) k 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 #

env :: forall a k repr. CLI_Env repr => EnvConstraint repr a => Name -> repr (a -> k) k Source #

Like env' but with the type enviable (a) first instead or (repr) so it can be passed using TypeApplications without adding a |@_| for (repr).

Type Tag

data Tag Source #

Instances
Eq Tag Source # 
Instance details

Defined in Symantic.CLI.API

Methods

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

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

Show Tag Source # 
Instance details

Defined in Symantic.CLI.API

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

IsString Tag Source # 
Instance details

Defined in Symantic.CLI.API

Methods

fromString :: String -> Tag #

Class CLI_Tag

class (App repr, Permutable repr, CLI_Var repr) => CLI_Tag repr where Source #

Minimal complete definition

Nothing

Associated Types

type TagConstraint repr a :: Constraint Source #

Methods

tag :: Tag -> repr f k -> repr f k Source #

endOpts :: repr k k Source #

flag :: TagConstraint repr Bool => Tag -> Permutation repr k Bool Source #

optionalTag :: TagConstraint repr a => AltApp repr => Alt repr => Pro repr => Tag -> repr (a -> k) k -> Permutation repr k (Maybe a) Source #

defaultTag :: TagConstraint repr a => Tag -> a -> repr (a -> k) k -> Permutation repr k a Source #

requiredTag :: TagConstraint repr a => Tag -> repr (a -> k) k -> Permutation repr k a Source #

many0Tag :: TagConstraint repr a => AltApp repr => Tag -> repr (a -> k) k -> Permutation repr k [a] Source #

many1Tag :: TagConstraint repr a => AltApp repr => Tag -> repr (a -> k) k -> Permutation repr k [a] Source #

tag :: Trans repr => CLI_Tag (UnTrans repr) => Tag -> repr f k -> repr f k Source #

endOpts :: Trans repr => CLI_Tag (UnTrans repr) => repr k k Source #

Instances
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

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

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

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

optionalTag :: (TagConstraint (Router (Parser e d)) a, AltApp (Router (Parser e d)), Alt (Router (Parser e d)), Pro (Router (Parser e d))) => Tag -> Router (Parser e d) (a -> k) k -> Permutation (Router (Parser e d)) k (Maybe a) Source #

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

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

many0Tag :: (TagConstraint (Router (Parser e d)) a, AltApp (Router (Parser e d))) => Tag -> Router (Parser e d) (a -> k) k -> Permutation (Router (Parser e d)) k [a] Source #

many1Tag :: (TagConstraint (Router (Parser e d)) a, AltApp (Router (Parser e d))) => Tag -> Router (Parser e d) (a -> k) k -> Permutation (Router (Parser e d)) k [a] Source #

SchemaDoc d => CLI_Tag (Schema d) Source # 
Instance details

Defined in Symantic.CLI.Schema

Associated Types

type TagConstraint (Schema d) a :: Constraint Source #

Methods

tag :: Tag -> Schema d f k -> Schema d f k Source #

endOpts :: Schema d k k Source #

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

optionalTag :: (TagConstraint (Schema d) a, AltApp (Schema d), Alt (Schema d), Pro (Schema d)) => Tag -> Schema d (a -> k) k -> Permutation (Schema d) k (Maybe a) Source #

defaultTag :: TagConstraint (Schema d) a => Tag -> a -> Schema d (a -> k) k -> Permutation (Schema d) k a Source #

requiredTag :: TagConstraint (Schema d) a => Tag -> Schema d (a -> k) k -> Permutation (Schema d) k a Source #

many0Tag :: (TagConstraint (Schema d) a, AltApp (Schema d)) => Tag -> Schema d (a -> k) k -> Permutation (Schema d) k [a] Source #

many1Tag :: (TagConstraint (Schema d) a, AltApp (Schema d)) => Tag -> Schema d (a -> k) k -> Permutation (Schema d) k [a] Source #

(LayoutDoc d, Justifiable d) => CLI_Tag (Layout d) Source # 
Instance details

Defined in Symantic.CLI.Layout

Associated Types

type TagConstraint (Layout d) a :: Constraint Source #

Methods

tag :: Tag -> Layout d f k -> Layout d f k Source #

endOpts :: Layout d k k Source #

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

optionalTag :: (TagConstraint (Layout d) a, AltApp (Layout d), Alt (Layout d), Pro (Layout d)) => Tag -> Layout d (a -> k) k -> Permutation (Layout d) k (Maybe a) Source #

defaultTag :: TagConstraint (Layout d) a => Tag -> a -> Layout d (a -> k) k -> Permutation (Layout d) k a Source #

requiredTag :: TagConstraint (Layout d) a => Tag -> Layout d (a -> k) k -> Permutation (Layout d) k a Source #

many0Tag :: (TagConstraint (Layout d) a, AltApp (Layout d)) => Tag -> Layout d (a -> k) k -> Permutation (Layout d) k [a] Source #

many1Tag :: (TagConstraint (Layout d) a, AltApp (Layout d)) => Tag -> Layout d (a -> k) k -> Permutation (Layout d) k [a] Source #

SchemaDoc d => CLI_Tag (Help d) Source # 
Instance details

Defined in Symantic.CLI.Help

Associated Types

type TagConstraint (Help d) a :: Constraint Source #

Methods

tag :: Tag -> Help d f k -> Help d f k Source #

endOpts :: Help d k k Source #

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

optionalTag :: (TagConstraint (Help d) a, AltApp (Help d), Alt (Help d), Pro (Help d)) => Tag -> Help d (a -> k) k -> Permutation (Help d) k (Maybe a) Source #

defaultTag :: TagConstraint (Help d) a => Tag -> a -> Help d (a -> k) k -> Permutation (Help d) k a Source #

requiredTag :: TagConstraint (Help d) a => Tag -> Help d (a -> k) k -> Permutation (Help d) k a Source #

many0Tag :: (TagConstraint (Help d) a, AltApp (Help d)) => Tag -> Help d (a -> k) k -> Permutation (Help d) k [a] Source #

many1Tag :: (TagConstraint (Help d) a, AltApp (Help d)) => Tag -> Help d (a -> k) k -> Permutation (Help d) k [a] 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

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

endOpts :: Parser e d k k Source #

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

optionalTag :: (TagConstraint (Parser e d) a, AltApp (Parser e d), Alt (Parser e d), Pro (Parser e d)) => Tag -> Parser e d (a -> k) k -> Permutation (Parser e d) k (Maybe a) Source #

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

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

many0Tag :: (TagConstraint (Parser e d) a, AltApp (Parser e d)) => Tag -> Parser e d (a -> k) k -> Permutation (Parser e d) k [a] Source #

many1Tag :: (TagConstraint (Parser e d) a, AltApp (Parser e d)) => Tag -> Parser e d (a -> k) k -> Permutation (Parser e d) k [a] Source #

Class CLI_Response

class CLI_Response repr where Source #

Minimal complete definition

Nothing

Associated Types

type ResponseConstraint repr a :: Constraint Source #

type ResponseArgs repr a :: * Source #

type Response repr :: * Source #

Methods

response' :: ResponseConstraint repr a => repr (ResponseArgs repr a) (Response repr) Source #

response' :: forall a. Trans repr => CLI_Response (UnTrans repr) => ResponseConstraint (UnTrans repr) a => ResponseArgs repr a ~ ResponseArgs (UnTrans repr) a => Response repr ~ Response (UnTrans repr) => repr (ResponseArgs repr a) (Response repr) Source #

Instances
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 #

SchemaDoc d => CLI_Response (Schema d) Source # 
Instance details

Defined in Symantic.CLI.Schema

Associated Types

type ResponseConstraint (Schema d) a :: Constraint Source #

type ResponseArgs (Schema d) a :: Type Source #

type Response (Schema d) :: Type Source #

LayoutDoc d => CLI_Response (Layout d) Source # 
Instance details

Defined in Symantic.CLI.Layout

Associated Types

type ResponseConstraint (Layout d) a :: Constraint Source #

type ResponseArgs (Layout d) a :: Type Source #

type Response (Layout d) :: Type Source #

SchemaDoc d => CLI_Response (Help d) Source # 
Instance details

Defined in Symantic.CLI.Help

Associated Types

type ResponseConstraint (Help d) a :: Constraint Source #

type ResponseArgs (Help d) a :: Type Source #

type Response (Help d) :: Type 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 #

response :: forall a repr. CLI_Response repr => ResponseConstraint repr a => repr (ResponseArgs repr a) (Response repr) Source #

Class CLI_Help

class CLI_Help repr where Source #

Minimal complete definition

Nothing

Associated Types

type HelpConstraint repr d :: Constraint Source #

Methods

help :: HelpConstraint repr d => d -> repr f k -> repr f k infixr 0 Source #

program :: Name -> repr f k -> repr f k Source #

rule :: Name -> repr f k -> repr f k Source #

program :: Trans repr => CLI_Help (UnTrans repr) => Name -> repr f k -> repr f k Source #

rule :: Trans repr => CLI_Help (UnTrans repr) => Name -> repr f k -> repr f k Source #

Instances
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 #

SchemaDoc d => CLI_Help (SchemaPerm d) Source # 
Instance details

Defined in Symantic.CLI.Schema

Associated Types

type HelpConstraint (SchemaPerm d) d :: Constraint Source #

Methods

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

program :: Name -> SchemaPerm d f k -> SchemaPerm d f k Source #

rule :: Name -> SchemaPerm d f k -> SchemaPerm d f k Source #

SchemaDoc d => CLI_Help (SchemaSeq d) Source # 
Instance details

Defined in Symantic.CLI.Schema

Associated Types

type HelpConstraint (SchemaSeq d) d :: Constraint Source #

Methods

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

program :: Name -> SchemaSeq d f k -> SchemaSeq d f k Source #

rule :: Name -> SchemaSeq d f k -> SchemaSeq d f k Source #

SchemaDoc d => CLI_Help (Schema d) Source # 
Instance details

Defined in Symantic.CLI.Schema

Associated Types

type HelpConstraint (Schema d) d :: Constraint Source #

Methods

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

program :: Name -> Schema d f k -> Schema d f k Source #

rule :: Name -> Schema d f k -> Schema d f k Source #

LayoutDoc d => CLI_Help (LayoutPerm d) Source # 
Instance details

Defined in Symantic.CLI.Layout

Associated Types

type HelpConstraint (LayoutPerm d) d :: Constraint Source #

Methods

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

program :: Name -> LayoutPerm d f k -> LayoutPerm d f k Source #

rule :: Name -> LayoutPerm d f k -> LayoutPerm d f k Source #

LayoutDoc d => CLI_Help (LayoutSeq d) Source # 
Instance details

Defined in Symantic.CLI.Layout

Associated Types

type HelpConstraint (LayoutSeq d) d :: Constraint Source #

Methods

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

program :: Name -> LayoutSeq d f k -> LayoutSeq d f k Source #

rule :: Name -> LayoutSeq d f k -> LayoutSeq d f k Source #

LayoutDoc d => CLI_Help (Layout d) Source # 
Instance details

Defined in Symantic.CLI.Layout

Associated Types

type HelpConstraint (Layout d) d :: Constraint Source #

Methods

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

program :: Name -> Layout d f k -> Layout d f k Source #

rule :: Name -> Layout d f k -> Layout d f k Source #

SchemaDoc d => CLI_Help (HelpPerm d) Source # 
Instance details

Defined in Symantic.CLI.Help

Associated Types

type HelpConstraint (HelpPerm d) d :: Constraint Source #

Methods

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

program :: Name -> HelpPerm d f k -> HelpPerm d f k Source #

rule :: Name -> HelpPerm d f k -> HelpPerm d f k Source #

SchemaDoc d => CLI_Help (Help d) Source # 
Instance details

Defined in Symantic.CLI.Help

Associated Types

type HelpConstraint (Help d) d :: Constraint Source #

Methods

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

program :: Name -> Help d f k -> Help d f k Source #

rule :: Name -> Help d f k -> Help d f k Source #

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 #

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 #

Type Trans

class Trans repr where Source #

Associated Types

type UnTrans repr :: * -> * -> * Source #

The (repr)esentation that (repr) Transforms.

Methods

noTrans :: UnTrans repr a b -> repr a b Source #

Lift the underlying (repr)esentation to (repr). Useful to define a combinator that does nothing in a Transformation.

unTrans :: repr a b -> UnTrans repr a b Source #

Unlift a (repr)esentation. Useful when a Transformation combinator needs to access the UnTransformed (repr)esentation, or at the end to get the underlying UnTransformed (repr)esentation from the inferred (repr) value (eg. in server).

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 #