simple-cmd-args-0.1.8: Simple command args parsing and execution
Safe HaskellNone
LanguageHaskell2010

SimpleCmdArgs

Description

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

Documentation

simpleCmdArgs Source #

Arguments

:: 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

simpleCmdArgs' Source #

Arguments

:: 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 #

Arguments

:: Maybe Version

version string

-> InfoMod (IO ())

modifiers

-> Parser (IO ())

commands

-> IO () 

Generic parser executor with explicit info modifiers

Since: 0.1.1

Subcommands

data Subcommand Source #

Subcommand "command" "help description text" $ myCommand <$> optParser

Constructors

Subcommand String String (Parser (IO ())) 

Instances

Instances details
Eq Subcommand Source #

equality by command name

Since: 0.1.5

Instance details

Defined in SimpleCmdArgs

Methods

(==) :: Subcommand -> Subcommand -> Bool

(/=) :: Subcommand -> Subcommand -> Bool

Ord Subcommand Source #

comparison by command name

Since: 0.1.5

Instance details

Defined in SimpleCmdArgs

subcommands :: [Subcommand] -> Parser (IO ()) Source #

Create a list of Subcommand that can be run by simpleCmdArgs

Option and arg helpers

strArg :: String -> Parser String Source #

A string arg parser with a METAVAR for help

switchWith :: Char -> String -> String -> Parser Bool Source #

switch with Mods

switchWith 'o' "option" "help description"

Since: 0.1.1

switchLongWith :: String -> String -> Parser Bool Source #

switchWith without short option

switchLongWith "option" "help description"

Since: 0.1.8

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

flagLongWith :: a -> a -> String -> String -> Parser a Source #

flagWith without short option

flagLongWith offVal onVal "flag" "help description"

Since: 0.1.8

flagLongWith' :: a -> String -> String -> Parser a Source #

flagWith' without short option

flagLongWith' val "flag" "help description"

Since: 0.1.8

switchMods :: HasName f => Char -> String -> String -> Mod f a Source #

Mods for a switch.

switchMods 'o' "option" "help description"

switchLongMods :: HasName f => String -> String -> Mod f a Source #

Mods for a switch.

switchLongMods "option" "help description"

strOptionWith :: Char -> String -> String -> String -> Parser String Source #

strOption with Mods

strOptionWith 'o' "option" "METAVAR" "help description"

Since: 0.1.1

strOptionLongWith :: String -> String -> String -> Parser String Source #

strOptionWith without short option

strOptionLongWith "option" "METAVAR" "help description"

Since: 0.1.8

optionWith :: ReadM a -> Char -> String -> String -> String -> Parser a Source #

option with Mods

optionWith auto 'o' "option" "METAVAR" "help description"

Since: 0.1.1

optionLongWith :: ReadM a -> String -> String -> String -> Parser a Source #

optionWith without short option

optionLongWith auto "option" "METAVAR" "help description"

Since: 0.1.8

optionMods :: (HasMetavar f, HasName f) => Char -> String -> String -> String -> Mod f a Source #

Mods for a mandatory option.

optionMods 'o' "option" "METAVAR" "help description"

optionLongMods :: (HasMetavar f, HasName f) => String -> String -> String -> Mod f a Source #

optionMods without short option

optionLongMods "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

strOptionalLongWith :: String -> String -> String -> String -> Parser String Source #

strOptionalWith without short option

strOptionalLongWith "option" "METAVAR" "help description" default

Since: 0.1.8

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

optionalLongWith :: ReadM a -> String -> String -> String -> a -> Parser a Source #

optionalWith without short option

optionalLongWith auto "option" "METAVAR" "help description" default

Since: 0.1.8

optionalMods :: (HasMetavar f, HasName f, HasValue f) => Char -> String -> String -> String -> a -> Mod f a Source #

Mods for an optional option: includes a default value.

optionalMods 'o' "option" "METAVAR" "help description" default

optionalLongMods :: (HasMetavar f, HasName f, HasValue f) => String -> String -> String -> a -> Mod f a Source #

optionalMods without short option

optionalLongMods "option" "METAVAR" "help description" default

Since: 0.1.8

argumentWith :: ReadM a -> String -> Parser a Source #

argument with METAVAR

argumentWith auto "METAVAR"

Since: 0.1.1

Re-exports from optparse-applicative

data Parser a #

Instances

Instances details
Functor Parser 
Instance details

Defined in Options.Applicative.Types

Methods

fmap :: (a -> b) -> Parser a -> Parser b

(<$) :: a -> Parser b -> Parser a

Applicative Parser 
Instance details

Defined in Options.Applicative.Types

Methods

pure :: a -> Parser a

(<*>) :: Parser (a -> b) -> Parser a -> Parser b

liftA2 :: (a -> b -> c) -> Parser a -> Parser b -> Parser c

(*>) :: Parser a -> Parser b -> Parser b

(<*) :: Parser a -> Parser b -> Parser a

Alternative Parser 
Instance details

Defined in Options.Applicative.Types

Methods

empty :: Parser a

(<|>) :: Parser a -> Parser a -> Parser a #

some :: Parser a -> Parser [a] #

many :: Parser a -> Parser [a] #

data ReadM a #

Instances

Instances details
Monad ReadM 
Instance details

Defined in Options.Applicative.Types

Methods

(>>=) :: ReadM a -> (a -> ReadM b) -> ReadM b

(>>) :: ReadM a -> ReadM b -> ReadM b

return :: a -> ReadM a

Functor ReadM 
Instance details

Defined in Options.Applicative.Types

Methods

fmap :: (a -> b) -> ReadM a -> ReadM b

(<$) :: a -> ReadM b -> ReadM a

MonadFail ReadM 
Instance details

Defined in Options.Applicative.Types

Methods

fail :: String -> ReadM a

Applicative ReadM 
Instance details

Defined in Options.Applicative.Types

Methods

pure :: a -> ReadM a

(<*>) :: ReadM (a -> b) -> ReadM a -> ReadM b

liftA2 :: (a -> b -> c) -> ReadM a -> ReadM b -> ReadM c

(*>) :: ReadM a -> ReadM b -> ReadM b

(<*) :: ReadM a -> ReadM b -> ReadM a

MonadPlus ReadM 
Instance details

Defined in Options.Applicative.Types

Methods

mzero :: ReadM a

mplus :: ReadM a -> ReadM a -> ReadM a

Alternative ReadM 
Instance details

Defined in Options.Applicative.Types

Methods

empty :: ReadM a

(<|>) :: ReadM a -> ReadM a -> ReadM a #

some :: ReadM a -> ReadM [a] #

many :: ReadM a -> 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 #