optparse-declarative-0.4.2: Declarative command line option parser
Safe HaskellNone
LanguageHaskell2010

Options.Declarative

Description

Declarative options parser

Synopsis

Command type

class IsCmd c Source #

Command class

Minimal complete definition

runCmd

Instances

Instances details
IsCmd Group Source # 
Instance details

Defined in Options.Declarative

(KnownSymbol placeholder, ArgRead a, IsCmd c) => IsCmd (Arg placeholder [a] -> c) Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

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

Instances details
Monad (Cmd help) Source # 
Instance details

Defined in Options.Declarative

Methods

(>>=) :: Cmd help a -> (a -> Cmd help b) -> Cmd help b #

(>>) :: Cmd help a -> Cmd help b -> Cmd help b #

return :: a -> Cmd help a #

Functor (Cmd help) Source # 
Instance details

Defined in Options.Declarative

Methods

fmap :: (a -> b) -> Cmd help a -> Cmd help b #

(<$) :: a -> Cmd help b -> Cmd help a #

MonadFix (Cmd help) Source # 
Instance details

Defined in Options.Declarative

Methods

mfix :: (a -> Cmd help a) -> Cmd help a #

MonadFail (Cmd help) Source # 
Instance details

Defined in Options.Declarative

Methods

fail :: String -> Cmd help a #

Applicative (Cmd help) Source # 
Instance details

Defined in Options.Declarative

Methods

pure :: a -> Cmd help a #

(<*>) :: Cmd help (a -> b) -> Cmd help a -> Cmd help b #

liftA2 :: (a -> b -> c) -> Cmd help a -> Cmd help b -> Cmd help c #

(*>) :: Cmd help a -> Cmd help b -> Cmd help b #

(<*) :: Cmd help a -> Cmd help b -> Cmd help a #

MonadIO (Cmd help) Source # 
Instance details

Defined in Options.Declarative

Methods

liftIO :: IO a -> Cmd help a #

Alternative (Cmd help) Source # 
Instance details

Defined in Options.Declarative

Methods

empty :: Cmd help a #

(<|>) :: Cmd help a -> Cmd help a -> Cmd help a #

some :: Cmd help a -> Cmd help [a] #

many :: Cmd help a -> Cmd help [a] #

MonadPlus (Cmd help) Source # 
Instance details

Defined in Options.Declarative

Methods

mzero :: Cmd help a #

mplus :: Cmd help a -> Cmd help a -> Cmd help a #

MonadThrow (Cmd help) Source # 
Instance details

Defined in Options.Declarative

Methods

throwM :: Exception e => e -> Cmd help a #

MonadCatch (Cmd help) Source # 
Instance details

Defined in Options.Declarative

Methods

catch :: Exception e => Cmd help a -> (e -> Cmd help a) -> Cmd help a #

KnownSymbol help => IsCmd (Cmd help ()) Source # 
Instance details

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

logStr Source #

Arguments

:: Int

Verbosity Level

-> String

Message

-> Cmd help () 

Output string when the verbosity level is greater than or equal to logLevel

getVerbosity :: Cmd help Int Source #

Return the verbosity level ('--verbosity=n')

getLogger :: MonadIO m => Cmd a (Int -> String -> m ()) Source #

Retrieve the logger function

Argument definition tools

class Option a where Source #

Command line option

Associated Types

type Value a :: * Source #

Type of the argument' value

Methods

get :: a -> Value a Source #

Get the argument' value

Instances

Instances details
Option (Arg _a a) Source # 
Instance details

Defined in Options.Declarative

Associated Types

type Value (Arg _a a) Source #

Methods

get :: Arg _a a -> Value (Arg _a a) Source #

ArgRead a => Option (Flag _a _b _c _d a) Source # 
Instance details

Defined in Options.Declarative

Associated Types

type Value (Flag _a _b _c _d a) Source #

Methods

get :: Flag _a _b _c _d a -> Value (Flag _a _b _c _d a) Source #

data Flag (shortNames :: Symbol) (longNames :: [Symbol]) (placeholder :: Symbol) (help :: Symbol) a Source #

Named argument

Instances

Instances details
(KnownSymbol shortNames, KnownSymbols longNames, KnownSymbol placeholder, KnownSymbol help, ArgRead a, IsCmd c) => IsCmd (Flag shortNames longNames placeholder help a -> c) Source # 
Instance details

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 # 
Instance details

Defined in Options.Declarative

Associated Types

type Value (Flag _a _b _c _d a) Source #

Methods

get :: Flag _a _b _c _d a -> Value (Flag _a _b _c _d a) Source #

type Value (Flag _a _b _c _d a) Source # 
Instance details

Defined in Options.Declarative

type Value (Flag _a _b _c _d a) = Unwrap a

data Arg (placeholder :: Symbol) a Source #

Unnamed argument

Instances

Instances details
(KnownSymbol placeholder, ArgRead a, IsCmd c) => IsCmd (Arg placeholder [a] -> c) Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in Options.Declarative

Associated Types

type Value (Arg _a a) Source #

Methods

get :: Arg _a a -> Value (Arg _a a) Source #

type Value (Arg _a a) Source # 
Instance details

Defined in Options.Declarative

type Value (Arg _a a) = a

Defining argument types

class ArgRead a where Source #

Command line option's annotated types

Minimal complete definition

Nothing

Associated Types

type Unwrap a :: * Source #

Type of the argument

type Unwrap a = a

Methods

unwrap :: a -> Unwrap a Source #

Get the argument's value

default unwrap :: a ~ Unwrap a => a -> Unwrap a Source #

argRead :: [String] -> Maybe a Source #

Argument parser

default argRead :: Read a => [String] -> Maybe a Source #

needArg :: Proxy a -> Bool Source #

Indicate this argument is mandatory

Instances

Instances details
ArgRead Bool Source # 
Instance details

Defined in Options.Declarative

Associated Types

type Unwrap Bool Source #

ArgRead Double Source # 
Instance details

Defined in Options.Declarative

Associated Types

type Unwrap Double Source #

ArgRead Int Source # 
Instance details

Defined in Options.Declarative

Associated Types

type Unwrap Int Source #

ArgRead Integer Source # 
Instance details

Defined in Options.Declarative

Associated Types

type Unwrap Integer Source #

ArgRead String Source # 
Instance details

Defined in Options.Declarative

Associated Types

type Unwrap String Source #

ArgRead a => ArgRead [a] Source # 
Instance details

Defined in Options.Declarative

Associated Types

type Unwrap [a] Source #

Methods

unwrap :: [a] -> Unwrap [a] Source #

argRead :: [String] -> Maybe [a] Source #

needArg :: Proxy [a] -> Bool Source #

ArgRead a => ArgRead (Maybe a) Source # 
Instance details

Defined in Options.Declarative

Associated Types

type Unwrap (Maybe a) Source #

(KnownSymbol defaultValue, ArgRead a) => ArgRead (Def defaultValue a) Source # 
Instance details

Defined in Options.Declarative

Associated Types

type Unwrap (Def defaultValue a) Source #

Methods

unwrap :: Def defaultValue a -> Unwrap (Def defaultValue a) Source #

argRead :: [String] -> Maybe (Def defaultValue a) Source #

needArg :: Proxy (Def defaultValue a) -> Bool Source #

data Def (defaultValue :: Symbol) a Source #

The argument which has default value

Instances

Instances details
(KnownSymbol defaultValue, ArgRead a) => ArgRead (Def defaultValue a) Source # 
Instance details

Defined in Options.Declarative

Associated Types

type Unwrap (Def defaultValue a) Source #

Methods

unwrap :: Def defaultValue a -> Unwrap (Def defaultValue a) Source #

argRead :: [String] -> Maybe (Def defaultValue a) Source #

needArg :: Proxy (Def defaultValue a) -> Bool Source #

type Unwrap (Def defaultValue a) Source # 
Instance details

Defined in Options.Declarative

type Unwrap (Def defaultValue a) = Unwrap a

Subcommands support

data Group Source #

Command group

Constructors

Group 

Fields

Instances

Instances details
IsCmd Group Source # 
Instance details

Defined in Options.Declarative

data SubCmd Source #

Sub command

subCmd :: IsCmd c => String -> c -> SubCmd Source #

Make a sub command

Run a command

run :: IsCmd c => String -> Maybe String -> c -> IO () Source #

Run a command with specifying program name and version

run_ :: IsCmd c => c -> IO () Source #

Run a command