Copyright | (c) Simon Bergot |
---|---|
License | BSD3 |
Maintainer | simon.bergot@gmail.com |
Stability | unstable |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell98 |
Simple command line parsing library. This library provides a small combinator dsl to specify a parser for a datatype. Running the parser will automatically consume and convert command line arguments. Default special action such as help/usage are automatically built from the parser specification.
Here is a quick example.
data MyTest = -- First, we need a datatype MyTest Int Int deriving (Show) -- we will print the values myTestParser -- Then, we define a parser :: ParserSpec MyTest myTestParser = MyTest `parsedBy` reqPos "pos1" `andBy` optPos 0 "pos2" main = withParseResult myTestParser print
Building this app will produce an executable foo
which will behave like this:
$ foo 1 2 MyTest 1 2 $ foo 3 MyTest 3 0 $ foo -h foo usage : foo pos1 [pos2] [-h] [--version] mandatory arguments: pos1 optional arguments: pos2 -h, --help show this help message and exit --version print the program version and exit
- parsedBy :: ParamSpec spec => (a -> b) -> spec a -> ParserSpec b
- andBy :: ParamSpec spec => ParserSpec (a -> b) -> spec a -> ParserSpec b
- mkApp :: ParserSpec a -> IO (CmdLnInterface a)
- mkDefaultApp :: ParserSpec a -> String -> CmdLnInterface a
- data Descr spec a = Descr (spec a) String
- setAppDescr :: CmdLnInterface a -> String -> CmdLnInterface a
- setAppEpilog :: CmdLnInterface a -> String -> CmdLnInterface a
- mkSubParser :: [(Arg, CmdLnInterface a)] -> IO (CmdLnInterface a)
- withParseResult :: ParserSpec a -> (a -> IO ()) -> IO ()
- runApp :: CmdLnInterface a -> (a -> IO ()) -> IO ()
- parseArgs :: Args -> CmdLnInterface a -> ParseResult a
- boolFlag :: Key -> FlagParam Bool
- reqFlag :: RawRead a => Key -> StdArgParam a
- optFlag :: RawRead a => a -> Key -> StdArgParam a
- reqPos :: RawRead a => Key -> StdArgParam a
- optPos :: RawRead a => a -> Key -> StdArgParam a
- reqFlagArgs :: RawRead a => Key -> b -> (b -> a -> b) -> StdArgParam b
- optFlagArgs :: RawRead a => b -> Key -> b -> (b -> a -> b) -> StdArgParam b
- posArgs :: RawRead a => Key -> b -> (b -> a -> b) -> StdArgParam b
- module System.Console.ArgParser.BaseType
Creating a parser
Basics
parsedBy :: ParamSpec spec => (a -> b) -> spec a -> ParserSpec b infixl 1 Source
Build a parser from a type constructor and a ParamSpec
MyApp `parsedBy` myparamspec
andBy :: ParamSpec spec => ParserSpec (a -> b) -> spec a -> ParserSpec b infixl 1 Source
Build a parser from a parser and a ParamSpec
MyApp `parsedBy` myparamspec `andBy` myotherparamspec
mkApp :: ParserSpec a -> IO (CmdLnInterface a) Source
Build an application with no version/description and with a name equal to the file name.
mkDefaultApp :: ParserSpec a -> String -> CmdLnInterface a Source
Build an application with no version/description and with a name equal to the provided String.
Adding descriptions
You can add descriptions for individual arguments and for the application:
import System.Console.ArgParser import Control.Applicative data MyTest = MyTest Int Int deriving (Show) -- we will print the values myTestParser :: ParserSpec MyTest myTestParser = MyTest `parsedBy` reqPos "pos1" `Descr` "description for the first argument" `andBy` optPos 0 "pos2" `Descr` "description for the second argument" myTestInterface :: IO (CmdLnInterface MyTest) myTestInterface = (`setAppDescr` "top description") <$> (`setAppEpilog` "bottom description") <$> mkApp myTestParser main = do interface <- myTestInterface runApp interface print
The new help will look like:
foo usage : foo pos1 [pos2] [-h] [--version] top description mandatory arguments: pos1 description for the first argument optional arguments: pos2 description for the second argument -h, --help show this help message and exit --version print the program version and exit bottom description
data Descr spec a infixl 2 Source
Allows the user to provide a description for a particular parameter. Can be used as an infix operator:
myparam `Descr` "this is my description"
setAppDescr :: CmdLnInterface a -> String -> CmdLnInterface a Source
Set the description of an interface
setAppEpilog :: CmdLnInterface a -> String -> CmdLnInterface a Source
Set the bottom text of an interface
Sub commands
You can also split different parsers of the same type into sub-commands with mkSubParser
:
data MyTest = MyCons1 Int Int | MyCons2 Int deriving (Eq, Show) myTestParser :: IO (CmdLnInterface MyTest) myTestParser = mkSubParser [ ("A", mkDefaultApp (MyCons1 `parsedBy` reqPos "pos1" `andBy` reqPos "pos2") "A") , ("B", mkDefaultApp (MyCons2 `parsedBy` reqPos "pos1") "B") ] main = do interface <- myTestParser runApp interface print
Running this script will yield:
$ hscmd A 1 2 MyCons1 1 2 $ hscmd B 3 MyCons2 3 $ hscmd -h hscmd usage : hscmd {A,B} [-h] [--version] commands arguments: {A,B} A B optional arguments: -h, --help show this help message and exit --version print the program version and exit $ hscmd A -h hscmd A usage : hscmd A pos1 pos2 [-h] [--version] mandatory arguments: pos1 pos2 optional arguments: -h, --help show this help message and exit --version print the program version and exit
mkSubParser :: [(Arg, CmdLnInterface a)] -> IO (CmdLnInterface a) Source
Create a parser composed of a list of subparsers.
Each subparser is associated with a command which the user must type to activate.
Running a parser
withParseResult :: ParserSpec a -> (a -> IO ()) -> IO () Source
:: CmdLnInterface a | Command line spec |
-> (a -> IO ()) | Process to run if the parsing success |
-> IO () |
Runs a command line application with the user provided arguments. If the parsing succeeds, run the application. Print the returned message otherwise
:: Args | Arguments to parse |
-> CmdLnInterface a | Command line spec |
-> ParseResult a |
Parse the arguments with the parser provided to the function.
Creating parameters
Values provided to parsedBy
and andBy
should be created with
the following functions. Those are shortcuts based on data types defined in
System.Console.ArgParser.Params. The types are inferred. argparser will use
read
to convert the arguments to haskell values, except for strings
which will be passed unmodified.
Flags can be passed in long form (--foo
) or short form (-f
)
You may also provide a prefix form such as --fo
.
Mandatory parameters will fail if the argument is absent or invalid.
Optional parameters only fail if the argument is invalid (ie foo
passed
as Int
)
Note that single arg parameters need exactly one arg, and that multiple args parameters can have any number of args (0 included).
Those functions are all defined in System.Console.ArgParser.QuickParams.
A simple command line flag.
The parsing function will return True
if the flag is present, if the flag is provided to
the command line, and False otherwise.
For a key foo
, the flag can either be --foo
or -f
Parameters with one arg
Flags
:: RawRead a | |
=> a | Default value |
-> Key | Flag name |
-> StdArgParam a |
An optional flag argument parameter
Positional
:: RawRead a | |
=> Key | Param name |
-> StdArgParam a |
A mandatory positional argument parameter
:: RawRead a | |
=> a | Default value |
-> Key | Param name |
-> StdArgParam a |
An optional positional argument parameter
Parameters with multiple args
Flags
:: RawRead a | |
=> Key | Flag name |
-> b | Initial value |
-> (b -> a -> b) | Accumulation function |
-> StdArgParam b |
A mandatory flag argument parameter taking multiple arguments
:: RawRead a | |
=> b | Default value |
-> Key | Flag name |
-> b | Initial value |
-> (b -> a -> b) | Accumulation function |
-> StdArgParam b |
An optional flag argument parameter taking multiple arguments
Positionnal
:: RawRead a | |
=> Key | Param name |
-> b | Initial value |
-> (b -> a -> b) | Accumulation function |
-> StdArgParam b |
A parameter consuming all the remaining positional parameters