console-program-0.4.2.0: Interpret the command line and a config file as commands and options

Safe HaskellSafe
LanguageHaskell98

System.Console.Command

Description

A Command provides a mode of operation of your program. This allows a single program to provide many different pieces of functionality. The first argument to the program (or the first few, if it has subcommands) determines which command should be executed. (darcs and cabal are examples of programs with this behaviour.)

An Action represents an IO action, together with information about applicable options and non-option arguments.

Synopsis

Documentation

type Commands m = Tree (Command m) Source #

Commands m is a tree of commands (with action in the monad m). It represents the whole set of possible commands of a program.

data Tree a :: * -> * #

Multi-way trees, also known as rose trees.

Constructors

Node a (Forest a) 

Instances

Monad Tree 

Methods

(>>=) :: Tree a -> (a -> Tree b) -> Tree b #

(>>) :: Tree a -> Tree b -> Tree b #

return :: a -> Tree a #

fail :: String -> Tree a #

Functor Tree 

Methods

fmap :: (a -> b) -> Tree a -> Tree b #

(<$) :: a -> Tree b -> Tree a #

Applicative Tree 

Methods

pure :: a -> Tree a #

(<*>) :: Tree (a -> b) -> Tree a -> Tree b #

(*>) :: Tree a -> Tree b -> Tree b #

(<*) :: Tree a -> Tree b -> Tree a #

Foldable Tree 

Methods

fold :: Monoid m => Tree m -> m #

foldMap :: Monoid m => (a -> m) -> Tree a -> m #

foldr :: (a -> b -> b) -> b -> Tree a -> b #

foldr' :: (a -> b -> b) -> b -> Tree a -> b #

foldl :: (b -> a -> b) -> b -> Tree a -> b #

foldl' :: (b -> a -> b) -> b -> Tree a -> b #

foldr1 :: (a -> a -> a) -> Tree a -> a #

foldl1 :: (a -> a -> a) -> Tree a -> a #

toList :: Tree a -> [a] #

null :: Tree a -> Bool #

length :: Tree a -> Int #

elem :: Eq a => a -> Tree a -> Bool #

maximum :: Ord a => Tree a -> a #

minimum :: Ord a => Tree a -> a #

sum :: Num a => Tree a -> a #

product :: Num a => Tree a -> a #

Traversable Tree 

Methods

traverse :: Applicative f => (a -> f b) -> Tree a -> f (Tree b) #

sequenceA :: Applicative f => Tree (f a) -> f (Tree a) #

mapM :: Monad m => (a -> m b) -> Tree a -> m (Tree b) #

sequence :: Monad m => Tree (m a) -> m (Tree a) #

Eq a => Eq (Tree a) 

Methods

(==) :: Tree a -> Tree a -> Bool #

(/=) :: Tree a -> Tree a -> Bool #

Data a => Data (Tree a) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Tree a -> c (Tree a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Tree a) #

toConstr :: Tree a -> Constr #

dataTypeOf :: Tree a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Tree a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Tree a)) #

gmapT :: (forall b. Data b => b -> b) -> Tree a -> Tree a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tree a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tree a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Tree a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Tree a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tree a -> m (Tree a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tree a -> m (Tree a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tree a -> m (Tree a) #

Read a => Read (Tree a) 
Show a => Show (Tree a) 

Methods

showsPrec :: Int -> Tree a -> ShowS #

show :: Tree a -> String #

showList :: [Tree a] -> ShowS #

NFData a => NFData (Tree a) 

Methods

rnf :: Tree a -> () #

data Command m Source #

A Command m is an action (in the monad m), together with some descriptive information.

Constructors

Command 

Fields

command :: String -> String -> Action m -> Command m Source #

Create a new command having a given name and action.

data Action m Source #

An Action m is an action (in the monad m), which may take arguments ("non-options") and options from the command line.

io :: MonadIO m => m () -> Action m Source #

A simple action, taking no argument, and having no options.

withNonOption :: MonadIO m => Type x -> (x -> Action m) -> Action m Source #

Create an action that takes an argument (non-option).

The type of argument is specified by the first parameter; such values can be obtained from the module System.Console.Argument.

withNonOptions :: MonadIO m => Type x -> ([x] -> Action m) -> Action m Source #

Create an action that takes all remaining non-option arguments.

The type of arguments is specified by the first parameter; such values can be obtained from the module System.Console.Argument.

withOption :: MonadIO m => Option a -> (a -> Action m) -> Action m Source #

Create an action that takes an option.

The first parameter is a description of the option; such a value can be constructed using option.

ignoreOption :: Option a -> Action m -> Action m Source #

Create an action that allows, but ignores, the given option.

This is especially useful if this option is given in the configuration file, but is meant for other commands; then this action will not give an error message about an unrecognised option.