Safe Haskell | None |
---|---|
Language | Haskell2010 |
This library provides a thin layer on optparse-applicative
argument and option parsing, using Parser (IO ())
,
applying commands directly to their argument parsing.
A few option Mod functions are also provided.
Synopsis
- simpleCmdArgs :: Maybe Version -> String -> String -> Parser (IO ()) -> IO ()
- simpleCmdArgs' :: Maybe Version -> String -> String -> Parser (IO ()) -> IO ()
- simpleCmdArgsWithMods :: Maybe Version -> InfoMod (IO ()) -> Parser (IO ()) -> IO ()
- data Subcommand = Subcommand String String (Parser (IO ()))
- subcommands :: [Subcommand] -> Parser (IO ())
- strArg :: String -> Parser String
- switchWith :: Char -> String -> String -> Parser Bool
- flagWith :: a -> a -> Char -> String -> String -> Parser a
- flagWith' :: a -> Char -> String -> String -> Parser a
- switchMods :: HasName f => Char -> String -> String -> Mod f a
- strOptionWith :: Char -> String -> String -> String -> Parser String
- optionWith :: ReadM a -> Char -> String -> String -> String -> Parser a
- optionMods :: (HasMetavar f, HasName f) => Char -> String -> String -> String -> Mod f a
- strOptionalWith :: Char -> String -> String -> String -> String -> Parser String
- optionalWith :: ReadM a -> Char -> String -> String -> String -> a -> Parser a
- optionalMods :: (HasMetavar f, HasName f, HasValue f) => Char -> String -> String -> String -> a -> Mod f a
- argumentWith :: ReadM a -> String -> Parser a
- data Parser a
- data ReadM a
- auto :: Read a => ReadM a
- many :: Alternative f => f a -> f [a]
- eitherReader :: (String -> Either String a) -> ReadM a
- maybeReader :: (String -> Maybe a) -> ReadM a
- optional :: Alternative f => f a -> f (Maybe a)
- some :: Alternative f => f a -> f [a]
- str :: IsString s => ReadM s
- (<|>) :: Alternative f => f a -> f a -> f a
Documentation
:: Maybe Version | version string |
-> String | header |
-> String | program description |
-> Parser (IO ()) | commands |
-> IO () |
Parser executor (allows interspersed args and options)
simpleCmdArgs (Just version) "summary" "program description" $ myCommand <$> myOptParser <*> myargsParser
:: Maybe Version | version string |
-> String | header |
-> String | program description |
-> Parser (IO ()) | commands |
-> IO () |
Parser executor without interspersing options and args
simpleCmdArgs' Nothing "summary" "program description" $ myCommand <$> myOptParser <*> myargsParser
simpleCmdArgsWithMods Source #
Generic parser executor with explicit info modifiers
Since: 0.1.1
Subcommands
data Subcommand Source #
Subcommand "command" "help description text" $ myCommand <$> optParser
Subcommand String String (Parser (IO ())) |
Instances
Eq Subcommand Source # | equality by command name Since: 0.1.5 |
Defined in SimpleCmdArgs (==) :: Subcommand -> Subcommand -> Bool # (/=) :: Subcommand -> Subcommand -> Bool # | |
Ord Subcommand Source # | comparison by command name Since: 0.1.5 |
Defined in SimpleCmdArgs compare :: Subcommand -> Subcommand -> Ordering # (<) :: Subcommand -> Subcommand -> Bool # (<=) :: Subcommand -> Subcommand -> Bool # (>) :: Subcommand -> Subcommand -> Bool # (>=) :: Subcommand -> Subcommand -> Bool # max :: Subcommand -> Subcommand -> Subcommand # min :: Subcommand -> Subcommand -> Subcommand # |
subcommands :: [Subcommand] -> Parser (IO ()) Source #
Create a list of Subcommand
that can be run by simpleCmdArgs
Option and arg helpers
switchWith :: Char -> String -> String -> Parser Bool Source #
switch with Mods
switchWith 'o' "option" "help description"
Since: 0.1.1
flagWith :: a -> a -> Char -> String -> String -> Parser a Source #
flag with Mods
flagWith offVal onVal 'f' "flag" "help description"
Since: 0.1.2
flagWith' :: a -> Char -> String -> String -> Parser a Source #
flag' with Mods
flagWith' val 'f' "flag" "help description"
Since: 0.1.2
switchMods :: HasName f => Char -> String -> String -> Mod f a Source #
Mod
s for a switch.
switchMods 'o' "option" "help description"
strOptionWith :: Char -> String -> String -> String -> Parser String Source #
strOption with Mods
strOptionWith 'o' "option" "METAVAR" "help description"
Since: 0.1.1
optionWith :: ReadM a -> Char -> String -> String -> String -> Parser a Source #
option with Mods
optionWith auto 'o' "option" "METAVAR" "help description"
Since: 0.1.1
optionMods :: (HasMetavar f, HasName f) => Char -> String -> String -> String -> Mod f a Source #
Mod
s for a mandatory option.
optionMods 'o' "option" "METAVAR" "help description"
strOptionalWith :: Char -> String -> String -> String -> String -> Parser String Source #
strOptional with Mods
strOptionalWith 'o' "option" "METAVAR" "help description" default
Since: 0.1.1
optionalWith :: ReadM a -> Char -> String -> String -> String -> a -> Parser a Source #
optional option with Mods, includes a default value.
optionalWith auto 'o' "option" "METAVAR" "help description" default
Since: 0.1.1
optionalMods :: (HasMetavar f, HasName f, HasValue f) => Char -> String -> String -> String -> a -> Mod f a Source #
Mod
s for an optional option: includes a default value.
optionalMods 'o' "option" "METAVAR" "help description" default
argumentWith :: ReadM a -> String -> Parser a Source #
argument with METAVAR
argumentWith auto "METAVAR"
Since: 0.1.1
Re-exports from optparse-applicative
A Parser a
is an option parser returning a value of type a
.
Instances
A newtype over 'ReaderT String Except', used by option readers.
Instances
many :: Alternative f => f a -> f [a] #
Zero or more.
eitherReader :: (String -> Either String a) -> ReadM a #
Convert a function producing an Either
into a reader.
As an example, one can create a ReadM from an attoparsec Parser easily with
import qualified Data.Attoparsec.Text as A import qualified Data.Text as T attoparsecReader :: A.Parser a -> ReadM a attoparsecReader p = eitherReader (A.parseOnly p . T.pack)
optional :: Alternative f => f a -> f (Maybe a) #
One or none.
some :: Alternative f => f a -> f [a] #
One or more.
(<|>) :: Alternative f => f a -> f a -> f a infixl 3 #
An associative binary operation