module SimpleCmdArgs
(simpleCmdArgs,
simpleCmdArgs',
simpleCmdArgsWithMods,
Subcommand(..),
subcommands,
strArg,
switchWith,
flagWith,
flagWith',
switchMods,
strOptionWith,
optionWith,
optionMods,
strOptionalWith,
optionalWith,
optionalMods,
argumentWith,
Parser,
auto,
many,
optional,
some,
str,
(<|>),
#if (defined(MIN_VERSION_base) && MIN_VERSION_base(4,8,0))
#else
(<$>), (<*>)
#endif
)
where
import Control.Applicative ((<|>),
#if (defined(MIN_VERSION_base) && MIN_VERSION_base(4,8,0))
#else
(<$>), (<*>)
#endif
)
import Control.Monad (join)
#if (defined(MIN_VERSION_base) && MIN_VERSION_base(4,8,0))
#else
import Data.Monoid (mconcat)
#endif
import Data.Semigroup ((<>))
import Data.Version
import Options.Applicative
simpleCmdArgs ::
Maybe Version
-> String
-> String
-> Parser (IO ())
-> IO ()
simpleCmdArgs mversion h pd =
simpleCmdArgsWithMods mversion mods
where
mods = fullDesc <> header h <> progDesc pd
simpleCmdArgs'
:: Maybe Version
-> String
-> String
-> Parser (IO ())
-> IO ()
simpleCmdArgs' mversion h pd =
simpleCmdArgsWithMods mversion mods
where
mods = fullDesc <> header h <> progDesc pd <> noIntersperse
simpleCmdArgsWithMods ::
Maybe Version
-> InfoMod (IO ())
-> Parser (IO ())
-> IO ()
simpleCmdArgsWithMods mversion mods cmdsParser = join $
customExecParser (prefs showHelpOnEmpty)
(case mversion of
(Just version) -> info (helper <*> versionOption version <*> cmdsParser) mods
Nothing -> info (helper <*> cmdsParser) mods)
where
versionOption ver =
infoOption (showVersion ver) (long "version" <> help "Show version")
data Subcommand =
Subcommand String String (Parser (IO ()))
subcommands :: [Subcommand] -> Parser (IO ())
subcommands = subparser . mconcat . map cmdToParse
where
cmdToParse (Subcommand name cmddesc cmdparse) =
command name (info cmdparse (progDesc cmddesc))
strArg :: String -> Parser String
strArg var = strArgument (metavar var)
switchWith :: Char -> String -> String -> Parser Bool
switchWith s l h =
switch (switchMods s l h)
flagWith :: a -> a -> Char -> String -> String -> Parser a
flagWith off on s l h =
flag off on (switchMods s l h)
flagWith' :: a -> Char -> String -> String -> Parser a
flagWith' val s l h =
flag' val (switchMods s l h)
switchMods :: HasName f =>
Char -> String -> String -> Mod f a
switchMods s l h =
short s <> long l <> help h
strOptionWith :: Char -> String -> String -> String -> Parser String
strOptionWith s l meta h =
strOption (optionMods s l meta h)
optionWith :: ReadM a -> Char -> String -> String -> String -> Parser a
optionWith r s l meta h =
option r (optionMods s l meta h)
optionMods :: (HasMetavar f, HasName f) =>
Char -> String -> String -> String -> Mod f a
optionMods s l meta h =
short s <> long l <> metavar meta <> help h
strOptionalWith :: Char -> String -> String -> String -> String -> Parser String
strOptionalWith s l meta h d =
strOption (optionalMods s l meta h d)
optionalWith :: ReadM a -> Char -> String -> String -> String -> a -> Parser a
optionalWith r s l meta h d =
option r (optionalMods s l meta h d)
optionalMods :: (HasMetavar f, HasName f, HasValue f) =>
Char -> String -> String -> String -> a -> Mod f a
optionalMods s l meta h d =
short s <> long l <> metavar meta <> help h <> value d
argumentWith :: ReadM a -> String -> Parser a
argumentWith r meta =
argument r (metavar meta)