lambda-options-0.9.1.0: Declarative command line parser using type-driven pattern matching.
Text.LambdaOptions.Keyword
Synopsis
data Keyword Source #
An option keyword, such as "--help"
"--help"
Constructors
Fields
All the aliases for this keyword.
Text to describe the arguments to the option given by this keyword.
Text to describe the function of the option given by this keyword.
Instances
Methods
(==) :: Keyword -> Keyword -> Bool #
(/=) :: Keyword -> Keyword -> Bool #
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Keyword -> c Keyword #
gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Keyword #
toConstr :: Keyword -> Constr #
dataTypeOf :: Keyword -> DataType #
dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Keyword) #
dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Keyword) #
gmapT :: (forall b. Data b => b -> b) -> Keyword -> Keyword #
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Keyword -> r #
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Keyword -> r #
gmapQ :: (forall d. Data d => d -> u) -> Keyword -> [u] #
gmapQi :: Int -> (forall d. Data d => d -> u) -> Keyword -> u #
gmapM :: Monad m => (forall d. Data d => d -> m d) -> Keyword -> m Keyword #
gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Keyword -> m Keyword #
gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Keyword -> m Keyword #
compare :: Keyword -> Keyword -> Ordering #
(<) :: Keyword -> Keyword -> Bool #
(<=) :: Keyword -> Keyword -> Bool #
(>) :: Keyword -> Keyword -> Bool #
(>=) :: Keyword -> Keyword -> Bool #
max :: Keyword -> Keyword -> Keyword #
min :: Keyword -> Keyword -> Keyword #
showsPrec :: Int -> Keyword -> ShowS #
show :: Keyword -> String #
showList :: [Keyword] -> ShowS #
fromString :: String -> Keyword #
Identiy mapping.
toKeyword :: Keyword -> Keyword Source #
class ToKeyword a where Source #
Convenience Keyword creation class.
Keyword
Minimal complete definition
toKeyword
toKeyword :: a -> Keyword Source #
Used to create a Keyword with a single alias.
toKeyword :: String -> Keyword Source #
Used to create a Keyword with many (or no) aliases
toKeyword :: [String] -> Keyword Source #
kw :: ToKeyword a => a -> Keyword Source #
Shorthand for toKeyword.
argText :: Keyword -> String -> Keyword Source #
Sets the kwArgText field in the keyword. Intended to be used infix:
kwArgText
kw "--directory" `argText` "DIR" `text` "Write files to DIR."
text :: Keyword -> String -> Keyword Source #
Sets the kwText field in the keyword. Intended to be used infix.
kwText
kw "--quiet" `text` "Suppress message display."