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

Safe HaskellNone
LanguageHaskell2010

Symantic.CLI.Layout

Contents

Synopsis

Type Layout

data Layout d f k Source #

Constructors

Layout 

Fields

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

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 #

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

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 #

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

Defined in Symantic.CLI.Layout

Methods

constant :: Segment -> a -> Layout d (a -> k) k Source #

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

nothing :: Layout 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 #

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

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

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

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 #

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 #

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 #

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 #

Semigroup d => Semigroup (Layout d f k) Source # 
Instance details

Defined in Symantic.CLI.Layout

Methods

(<>) :: Layout d f k -> Layout d f k -> Layout d f k #

sconcat :: NonEmpty (Layout d f k) -> Layout d f k #

stimes :: Integral b => b -> Layout d f k -> Layout d f k #

type Response (Layout d) Source # 
Instance details

Defined in Symantic.CLI.Layout

type Sequence (Layout d) Source # 
Instance details

Defined in Symantic.CLI.Layout

type Permutation (Layout d) Source # 
Instance details

Defined in Symantic.CLI.Layout

type HelpConstraint (Layout d) d' Source # 
Instance details

Defined in Symantic.CLI.Layout

type ResponseConstraint (Layout d) a Source # 
Instance details

Defined in Symantic.CLI.Layout

type ResponseArgs (Layout d) a Source # 
Instance details

Defined in Symantic.CLI.Layout

type TagConstraint (Layout d) a Source # 
Instance details

Defined in Symantic.CLI.Layout

type EnvConstraint (Layout d) a Source # 
Instance details

Defined in Symantic.CLI.Layout

type VarConstraint (Layout d) a Source # 
Instance details

Defined in Symantic.CLI.Layout

runLayout :: LayoutDoc d => Bool -> Layout d f k -> d Source #

coerceLayout :: Layout d f k -> Layout d f' k' Source #

Type LayoutInh

newtype LayoutInh d Source #

Constructors

LayoutInh 

Fields

Type LayoutState

Type Diff

type Diff a = Maybe a -> Maybe a Source #

A continuation-passing-style constructor, (each constructor prepending something), augmented with Maybe to change the prepending according to what the following parts are. Used in <!> and alt to know if branches lead to at least one route (ie. contain at least one response).

Type LayoutDoc

Type LayoutSeq

data LayoutSeq d k a Source #

Constructors

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

Functor (LayoutSeq d k) Source # 
Instance details

Defined in Symantic.CLI.Layout

Methods

fmap :: (a -> b) -> LayoutSeq d k a -> LayoutSeq d k b #

(<$) :: a -> LayoutSeq d k b -> LayoutSeq d k a #

Applicative (LayoutSeq d k) Source # 
Instance details

Defined in Symantic.CLI.Layout

Methods

pure :: a -> LayoutSeq d k a #

(<*>) :: LayoutSeq d k (a -> b) -> LayoutSeq d k a -> LayoutSeq d k b #

liftA2 :: (a -> b -> c) -> LayoutSeq d k a -> LayoutSeq d k b -> LayoutSeq d k c #

(*>) :: LayoutSeq d k a -> LayoutSeq d k b -> LayoutSeq d k b #

(<*) :: LayoutSeq d k a -> LayoutSeq d k b -> LayoutSeq d k a #

type HelpConstraint (LayoutSeq d) d' Source # 
Instance details

Defined in Symantic.CLI.Layout

Type LayoutPerm

data LayoutPerm d k a Source #

Constructors

LayoutPerm 

Fields

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

Functor (LayoutPerm d k) Source # 
Instance details

Defined in Symantic.CLI.Layout

Methods

fmap :: (a -> b) -> LayoutPerm d k a -> LayoutPerm d k b #

(<$) :: a -> LayoutPerm d k b -> LayoutPerm d k a #

Applicative (LayoutPerm d k) Source # 
Instance details

Defined in Symantic.CLI.Layout

Methods

pure :: a -> LayoutPerm d k a #

(<*>) :: LayoutPerm d k (a -> b) -> LayoutPerm d k a -> LayoutPerm d k b #

liftA2 :: (a -> b -> c) -> LayoutPerm d k a -> LayoutPerm d k b -> LayoutPerm d k c #

(*>) :: LayoutPerm d k a -> LayoutPerm d k b -> LayoutPerm d k b #

(<*) :: LayoutPerm d k a -> LayoutPerm d k b -> LayoutPerm d k a #

type HelpConstraint (LayoutPerm d) d' Source # 
Instance details

Defined in Symantic.CLI.Layout

Type LayoutNode

data LayoutNode d Source #

Constructors

LayoutNode_Single d [d] 
LayoutNode_List [d] [(d, [d])] 
LayoutNode_Forest d [d] (Forest (LayoutNode d)) 
Instances
Show d => Show (LayoutNode d) Source # 
Instance details

Defined in Symantic.CLI.Layout