| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Options.Declarative
Description
Declarative options parser
Synopsis
- class IsCmd c
- data Cmd (help :: Symbol) a
- logStr :: Int -> String -> Cmd help ()
- getVerbosity :: Cmd help Int
- getLogger :: MonadIO m => Cmd a (Int -> String -> m ())
- class Option a where
- data Flag (shortNames :: Symbol) (longNames :: [Symbol]) (placeholder :: Symbol) (help :: Symbol) a
- data Arg (placeholder :: Symbol) a
- class ArgRead a where
- data Def (defaultValue :: Symbol) a
- data Group = Group {}
- data SubCmd
- subCmd :: IsCmd c => String -> c -> SubCmd
- run :: IsCmd c => String -> Maybe String -> c -> IO ()
- run_ :: IsCmd c => c -> IO ()
Command type
Command class
Minimal complete definition
runCmd
Instances
| IsCmd Group Source # | |
| Defined in Options.Declarative | |
| (KnownSymbol placeholder, ArgRead a, IsCmd c) => IsCmd (Arg placeholder [a] -> c) Source # | |
| Defined in Options.Declarative Methods getCmdHelp :: (Arg placeholder [a] -> c) -> String getOptDescr :: (Arg placeholder [a] -> c) -> [OptDescr (String, String)] getUsageHeader :: (Arg placeholder [a] -> c) -> String -> String getUsageFooter :: (Arg placeholder [a] -> c) -> String -> String runCmd :: (Arg placeholder [a] -> c) -> [String] -> Maybe String -> [(String, String)] -> [String] -> [String] -> IO () | |
| (KnownSymbol placeholder, IsCmd c) => IsCmd (Arg placeholder String -> c) Source # | |
| Defined in Options.Declarative Methods getCmdHelp :: (Arg placeholder String -> c) -> String getOptDescr :: (Arg placeholder String -> c) -> [OptDescr (String, String)] getUsageHeader :: (Arg placeholder String -> c) -> String -> String getUsageFooter :: (Arg placeholder String -> c) -> String -> String runCmd :: (Arg placeholder String -> c) -> [String] -> Maybe String -> [(String, String)] -> [String] -> [String] -> IO () | |
| (KnownSymbol placeholder, ArgRead a, IsCmd c) => IsCmd (Arg placeholder a -> c) Source # | |
| Defined in Options.Declarative Methods getCmdHelp :: (Arg placeholder a -> c) -> String getOptDescr :: (Arg placeholder a -> c) -> [OptDescr (String, String)] getUsageHeader :: (Arg placeholder a -> c) -> String -> String getUsageFooter :: (Arg placeholder a -> c) -> String -> String runCmd :: (Arg placeholder a -> c) -> [String] -> Maybe String -> [(String, String)] -> [String] -> [String] -> IO () | |
| (KnownSymbol shortNames, KnownSymbols longNames, KnownSymbol placeholder, KnownSymbol help, ArgRead a, IsCmd c) => IsCmd (Flag shortNames longNames placeholder help a -> c) Source # | |
| Defined in Options.Declarative Methods getCmdHelp :: (Flag shortNames longNames placeholder help a -> c) -> String getOptDescr :: (Flag shortNames longNames placeholder help a -> c) -> [OptDescr (String, String)] getUsageHeader :: (Flag shortNames longNames placeholder help a -> c) -> String -> String getUsageFooter :: (Flag shortNames longNames placeholder help a -> c) -> String -> String runCmd :: (Flag shortNames longNames placeholder help a -> c) -> [String] -> Maybe String -> [(String, String)] -> [String] -> [String] -> IO () | |
| KnownSymbol help => IsCmd (Cmd help ()) Source # | |
| Defined in Options.Declarative Methods getCmdHelp :: Cmd help () -> String getOptDescr :: Cmd help () -> [OptDescr (String, String)] getUsageHeader :: Cmd help () -> String -> String getUsageFooter :: Cmd help () -> String -> String runCmd :: Cmd help () -> [String] -> Maybe String -> [(String, String)] -> [String] -> [String] -> IO () | |
data Cmd (help :: Symbol) a Source #
Command
Instances
| Monad (Cmd help) Source # | |
| Functor (Cmd help) Source # | |
| Applicative (Cmd help) Source # | |
| MonadIO (Cmd help) Source # | |
| Defined in Options.Declarative | |
| KnownSymbol help => IsCmd (Cmd help ()) Source # | |
| Defined in Options.Declarative Methods getCmdHelp :: Cmd help () -> String getOptDescr :: Cmd help () -> [OptDescr (String, String)] getUsageHeader :: Cmd help () -> String -> String getUsageFooter :: Cmd help () -> String -> String runCmd :: Cmd help () -> [String] -> Maybe String -> [(String, String)] -> [String] -> [String] -> IO () | |
Output string when the verbosity level is greater than or equal to logLevel
getVerbosity :: Cmd help Int Source #
Return the verbosity level ('--verbosity=n')
Argument definition tools
Command line option
data Flag (shortNames :: Symbol) (longNames :: [Symbol]) (placeholder :: Symbol) (help :: Symbol) a Source #
Named argument
Instances
| (KnownSymbol shortNames, KnownSymbols longNames, KnownSymbol placeholder, KnownSymbol help, ArgRead a, IsCmd c) => IsCmd (Flag shortNames longNames placeholder help a -> c) Source # | |
| Defined in Options.Declarative Methods getCmdHelp :: (Flag shortNames longNames placeholder help a -> c) -> String getOptDescr :: (Flag shortNames longNames placeholder help a -> c) -> [OptDescr (String, String)] getUsageHeader :: (Flag shortNames longNames placeholder help a -> c) -> String -> String getUsageFooter :: (Flag shortNames longNames placeholder help a -> c) -> String -> String runCmd :: (Flag shortNames longNames placeholder help a -> c) -> [String] -> Maybe String -> [(String, String)] -> [String] -> [String] -> IO () | |
| ArgRead a => Option (Flag _a _b _c _d a) Source # | |
| type Value (Flag _a _b _c _d a) Source # | |
| Defined in Options.Declarative | |
data Arg (placeholder :: Symbol) a Source #
Unnamed argument
Instances
| (KnownSymbol placeholder, ArgRead a, IsCmd c) => IsCmd (Arg placeholder [a] -> c) Source # | |
| Defined in Options.Declarative Methods getCmdHelp :: (Arg placeholder [a] -> c) -> String getOptDescr :: (Arg placeholder [a] -> c) -> [OptDescr (String, String)] getUsageHeader :: (Arg placeholder [a] -> c) -> String -> String getUsageFooter :: (Arg placeholder [a] -> c) -> String -> String runCmd :: (Arg placeholder [a] -> c) -> [String] -> Maybe String -> [(String, String)] -> [String] -> [String] -> IO () | |
| (KnownSymbol placeholder, IsCmd c) => IsCmd (Arg placeholder String -> c) Source # | |
| Defined in Options.Declarative Methods getCmdHelp :: (Arg placeholder String -> c) -> String getOptDescr :: (Arg placeholder String -> c) -> [OptDescr (String, String)] getUsageHeader :: (Arg placeholder String -> c) -> String -> String getUsageFooter :: (Arg placeholder String -> c) -> String -> String runCmd :: (Arg placeholder String -> c) -> [String] -> Maybe String -> [(String, String)] -> [String] -> [String] -> IO () | |
| (KnownSymbol placeholder, ArgRead a, IsCmd c) => IsCmd (Arg placeholder a -> c) Source # | |
| Defined in Options.Declarative Methods getCmdHelp :: (Arg placeholder a -> c) -> String getOptDescr :: (Arg placeholder a -> c) -> [OptDescr (String, String)] getUsageHeader :: (Arg placeholder a -> c) -> String -> String getUsageFooter :: (Arg placeholder a -> c) -> String -> String runCmd :: (Arg placeholder a -> c) -> [String] -> Maybe String -> [(String, String)] -> [String] -> [String] -> IO () | |
| Option (Arg _a a) Source # | |
| type Value (Arg _a a) Source # | |
| Defined in Options.Declarative | |
Defining argment types
class ArgRead a where Source #
Command line option's annotated types
Minimal complete definition
Nothing
Methods
unwrap :: a -> Unwrap a Source #
Get the argument's value
unwrap :: a ~ Unwrap a => a -> Unwrap a Source #
Get the argument's value
argRead :: Maybe String -> Maybe a Source #
Argument parser
argRead :: Read a => Maybe String -> Maybe a Source #
Argument parser
needArg :: Proxy a -> Bool Source #
Indicate this argument is mandatory
data Def (defaultValue :: Symbol) a Source #
The argument which has defalut value
Subcommands support
Command group
Instances
| IsCmd Group Source # | |
| Defined in Options.Declarative | |