cli-0.2.0: CLI

LicenseBSD-style
MaintainerVincent Hanquez <vincent@snarc.org>
Stabilityexperimental
PortabilityGood
Safe HaskellNone
LanguageHaskell2010

Console.Options

Contents

Description

Options parsing using a simple DSL approach.

Using this API, your program should have the following shape:

defaultMain $ do
    f1 <- flag ..
    f2 <- argument ..
    action $ \toParam ->
        something (toParam f1) (toParam f2) ..

You can also define subcommand using:

defaultMain $ do
    subcommand "foo" $ do
       <..flags & parameters definitions...>
       action $ \toParam -> <..IO-action..>
    subcommand "bar" $ do
       <..flags & parameters definitions...>
       action $ \toParam -> <..IO-action..>

Example:

main = defaultMain $ do
    programName "test-cli"
    programDescription "test CLI program"
    flagA    <- flag $ FlagShort 'a' <> FlagLong "aaa"
    allArgs  <- remainingArguments "FILE"
    action $ \toParam -> do
        putStrLn $ "using flag A : " ++ show (toParam flagA)
        putStrLn $ "args: " ++ show (toParam allArgs)
Synopsis

Running

defaultMain :: OptionDesc (IO ()) () -> IO () Source #

run parse options description on the action

to be able to specify the arguments manually (e.g. pre-handling), you can use defaultMainWith. >defaultMain dsl = getArgs >>= defaultMainWith dsl

defaultMainWith :: OptionDesc (IO ()) () -> [String] -> IO () Source #

same as defaultMain, but with the argument

parseOptions :: OptionDesc r () -> [String] -> (ProgramDesc r, OptionRes r) Source #

This is only useful when you want to handle all the description parsing manually and need to not automatically execute any action or help/error handling.

Used for testing the parser.

data OptionRes r Source #

return value of the option parser. only needed when using parseOptions directly

data OptionDesc r a Source #

Option description Monad

Instances
Monad (OptionDesc r) Source # 
Instance details

Defined in Console.Options.Monad

Methods

(>>=) :: OptionDesc r a -> (a -> OptionDesc r b) -> OptionDesc r b #

(>>) :: OptionDesc r a -> OptionDesc r b -> OptionDesc r b #

return :: a -> OptionDesc r a #

fail :: String -> OptionDesc r a #

Functor (OptionDesc r) Source # 
Instance details

Defined in Console.Options.Monad

Methods

fmap :: (a -> b) -> OptionDesc r a -> OptionDesc r b #

(<$) :: a -> OptionDesc r b -> OptionDesc r a #

Applicative (OptionDesc r) Source # 
Instance details

Defined in Console.Options.Monad

Methods

pure :: a -> OptionDesc r a #

(<*>) :: OptionDesc r (a -> b) -> OptionDesc r a -> OptionDesc r b #

liftA2 :: (a -> b -> c) -> OptionDesc r a -> OptionDesc r b -> OptionDesc r c #

(*>) :: OptionDesc r a -> OptionDesc r b -> OptionDesc r b #

(<*) :: OptionDesc r a -> OptionDesc r b -> OptionDesc r a #

MonadState (OptionDesc r) Source # 
Instance details

Defined in Console.Options.Monad

Associated Types

type State (OptionDesc r) :: Type #

Methods

withState :: (State (OptionDesc r) -> (a, State (OptionDesc r))) -> OptionDesc r a #

type State (OptionDesc r) Source # 
Instance details

Defined in Console.Options.Monad

type State (OptionDesc r)

Description

programName :: String -> OptionDesc r () Source #

Set the program name

default is the result of base's getProgName

programVersion :: Version -> OptionDesc r () Source #

Set the program version

programDescription :: String -> OptionDesc r () Source #

Set the program description

command :: String -> OptionDesc r () -> OptionDesc r () Source #

Create a new sub command

data FlagFrag Source #

Fragment of flag definition.

Use the monoid approach to concat flags together e.g. > FlagShort o <> FlagLong "option"

Constructors

FlagShort Char

short option e.g. '-a'

FlagLong String

long option e.g. "--aaaa"

FlagDescription String

description of this flag. | FlagDefault String

Instances
Eq FlagFrag Source # 
Instance details

Defined in Console.Options.Flags

Show FlagFrag Source # 
Instance details

Defined in Console.Options.Flags

Semigroup FlagFrag Source # 
Instance details

Defined in Console.Options.Flags

Monoid FlagFrag Source # 
Instance details

Defined in Console.Options.Flags

flag :: FlagFrag -> OptionDesc r (Flag Bool) Source #

Flag option either of the form -short or --long

for flag that expect a value (optional or mandatory), uses flagArg

flagParam :: FlagFrag -> FlagParser a -> OptionDesc r (FlagParam a) Source #

Flag option either of the form -short or --long

for flag that doesn't have parameter, use flag

flagMany :: OptionDesc r (FlagParam a) -> OptionDesc r (FlagMany a) Source #

Apply on a flagParam to turn into a flag that can be invoked multiples, creating a list of values in the action.

argument :: String -> ValueParser a -> OptionDesc r (Arg a) Source #

An unnamed positional argument

For now, argument in a point of tree that contains sub trees will be ignored. TODO: record a warning or add a strict mode (for developping the CLI) and error.

remainingArguments :: String -> OptionDesc r (ArgRemaining [String]) Source #

All the remaining position arguments

This is useful for example for a program that takes an unbounded list of files as parameters.

action :: Action r -> OptionDesc r () Source #

Set the action to run in this command

description :: String -> OptionDesc r () Source #

Set the description for a command

type Action r = (forall a p. Param p => p a -> Ret p a) -> r Source #

Represent a program to run

Arguments

type ValueParser a = String -> Either String a Source #

A parser for a value. In case parsing failed Left should be returned.

data FlagParser a Source #

A parser for a flag's value, either optional or required.

Constructors

FlagRequired (ValueParser a)

flag value parser with a required parameter.

FlagOptional a (ValueParser a)

Optional flag value parser: Default value if not present to a

data Flag a Source #

Represent a boolean flag (present / not present)

data FlagLevel a Source #

Represent a Flag that can be called multiples times and will increase a counter.

data FlagParam a Source #

Represent a Flag with an optional or required value associated

data FlagMany a Source #

Represent a Flag with optional or required value that can be added multiple times

data Arg a Source #

A positional argument

data ArgRemaining a Source #

All the remaining positional arguments

data Params Source #

A dictionary of parsed flags and arguments

paramsFlags :: Params -> [(Nid, Maybe String)] Source #

return all the flags and their unique identifier. internal only

getParams :: Param p => Params -> forall a. p a -> Ret p a Source #

get the value associated with a specific Param (either a Flag, FlagParam, or an Arg)