Safe Haskell | None |
---|---|
Language | Haskell2010 |
Example usage of this module:
-- options.hs {-# LANGUAGE OverloadedStrings #-} import Turtle parser :: Parser (Text, Int) parser = (,) <$> optText "name" 'n' "Your first name" <*> optInt "age" 'a' "Your current age" main = do (name, age) <- options "Greeting script" parser echo (repr (format ("Hello there, "%s) name)) echo (repr (format ("You are "%d%" years old") age))
$ ./options --name John --age 42 Hello there, John You are 42 years old
$ ./options --help Greeting script Usage: options (-n|--name NAME) (-a|--age AGE) Available options: -h,--help Show this help text --name NAME Your first name --age AGE Your current age
See the Turtle.Tutorial module which contains more examples on how to use command-line parsing.
Synopsis
- data Parser a
- newtype ArgName = ArgName {
- getArgName :: Text
- newtype CommandName = CommandName {}
- type ShortName = Char
- newtype Description = Description {}
- newtype HelpMessage = HelpMessage {}
- switch :: ArgName -> ShortName -> Optional HelpMessage -> Parser Bool
- optText :: ArgName -> ShortName -> Optional HelpMessage -> Parser Text
- optLine :: ArgName -> ShortName -> Optional HelpMessage -> Parser Line
- optInt :: ArgName -> ShortName -> Optional HelpMessage -> Parser Int
- optInteger :: ArgName -> ShortName -> Optional HelpMessage -> Parser Integer
- optDouble :: ArgName -> ShortName -> Optional HelpMessage -> Parser Double
- optPath :: ArgName -> ShortName -> Optional HelpMessage -> Parser FilePath
- optRead :: Read a => ArgName -> ShortName -> Optional HelpMessage -> Parser a
- opt :: (Text -> Maybe a) -> ArgName -> ShortName -> Optional HelpMessage -> Parser a
- argText :: ArgName -> Optional HelpMessage -> Parser Text
- argLine :: ArgName -> Optional HelpMessage -> Parser Line
- argInt :: ArgName -> Optional HelpMessage -> Parser Int
- argInteger :: ArgName -> Optional HelpMessage -> Parser Integer
- argDouble :: ArgName -> Optional HelpMessage -> Parser Double
- argPath :: ArgName -> Optional HelpMessage -> Parser FilePath
- argRead :: Read a => ArgName -> Optional HelpMessage -> Parser a
- arg :: (Text -> Maybe a) -> ArgName -> Optional HelpMessage -> Parser a
- subcommand :: CommandName -> Description -> Parser a -> Parser a
- subcommandGroup :: forall a. Description -> [(CommandName, Description, Parser a)] -> Parser a
- options :: MonadIO io => Description -> Parser a -> io a
Types
A Parser a
is an option parser returning a value of type a
.
Instances
Functor Parser | |
Applicative Parser | |
Alternative Parser | |
The name of a command-line argument
This is used to infer the long name and metavariable for the command line
flag. For example, an ArgName
of "name"
will create a --name
flag
with a NAME
metavariable
Instances
IsString ArgName Source # | |
Defined in Turtle.Options fromString :: String -> ArgName # |
newtype CommandName Source #
The name of a sub-command
This is lower-cased to create a sub-command. For example, a CommandName
of
"Name"
will parse name
on the command line before parsing the
remaining arguments using the command's subparser.
Instances
IsString CommandName Source # | |
Defined in Turtle.Options fromString :: String -> CommandName # |
newtype Description Source #
A brief description of what your program does
This description will appear in the header of the --help
output
Instances
IsString Description Source # | |
Defined in Turtle.Options fromString :: String -> Description # |
newtype HelpMessage Source #
A helpful message explaining what a flag does
This will appear in the --help
output
Instances
IsString HelpMessage Source # | |
Defined in Turtle.Options fromString :: String -> HelpMessage # |
Flag-based option parsers
optText :: ArgName -> ShortName -> Optional HelpMessage -> Parser Text Source #
Parse a Text
value as a flag-based option
optLine :: ArgName -> ShortName -> Optional HelpMessage -> Parser Line Source #
Parse a Line
value as a flag-based option
optInt :: ArgName -> ShortName -> Optional HelpMessage -> Parser Int Source #
Parse an Int
as a flag-based option
optInteger :: ArgName -> ShortName -> Optional HelpMessage -> Parser Integer Source #
Parse an Integer
as a flag-based option
optDouble :: ArgName -> ShortName -> Optional HelpMessage -> Parser Double Source #
Parse a Double
as a flag-based option
optPath :: ArgName -> ShortName -> Optional HelpMessage -> Parser FilePath Source #
Parse a FilePath
value as a flag-based option
optRead :: Read a => ArgName -> ShortName -> Optional HelpMessage -> Parser a Source #
Parse any type that implements Read
opt :: (Text -> Maybe a) -> ArgName -> ShortName -> Optional HelpMessage -> Parser a Source #
Build a flag-based option parser for any type by providing a Text
-parsing
function
Positional argument parsers
argText :: ArgName -> Optional HelpMessage -> Parser Text Source #
Parse a Text
as a positional argument
argLine :: ArgName -> Optional HelpMessage -> Parser Line Source #
Parse a Line
as a positional argument
argInt :: ArgName -> Optional HelpMessage -> Parser Int Source #
Parse an Int
as a positional argument
argInteger :: ArgName -> Optional HelpMessage -> Parser Integer Source #
Parse an Integer
as a positional argument
argDouble :: ArgName -> Optional HelpMessage -> Parser Double Source #
Parse a Double
as a positional argument
argPath :: ArgName -> Optional HelpMessage -> Parser FilePath Source #
Parse a FilePath
as a positional argument
argRead :: Read a => ArgName -> Optional HelpMessage -> Parser a Source #
Parse any type that implements Read
as a positional argument
arg :: (Text -> Maybe a) -> ArgName -> Optional HelpMessage -> Parser a Source #
Build a positional argument parser for any type by providing a
Text
-parsing function
Consume parsers
subcommand :: CommandName -> Description -> Parser a -> Parser a Source #
Create a sub-command that parses CommandName
and then parses the rest
of the command-line arguments
The sub-command will have its own Description
and help text
subcommandGroup :: forall a. Description -> [(CommandName, Description, Parser a)] -> Parser a Source #
Create a named group of sub-commands