module System.Console.ArgParser.Run (
withParseResult
, runApp
, parseArgs
, parseNiceArgs
, mkApp
, mkDefaultApp
, defaultSpecialFlags
, setAppDescr
, setAppEpilog
, setAppName
) where
import Control.Monad
import Data.Maybe
import System.Console.ArgParser.ArgsProcess
import System.Console.ArgParser.BaseType
import System.Console.ArgParser.Format
import System.Console.ArgParser.Params
import System.Console.ArgParser.Parser
import System.Environment
runParser :: Parser a -> NiceArgs -> ParseResult a
runParser (Parser parse) args = fst $ parse args
runApp
:: CmdLnInterface a
-> (a -> IO ())
-> IO ()
runApp appspec appfun = do
args <- getArgs
either putStrLn appfun $ parseArgs args appspec
withParseResult
:: ParserSpec a
-> (a -> IO ())
-> IO ()
withParseResult parser app = do
interface <- mkApp parser
runApp interface app
parseArgs
:: Args
-> CmdLnInterface a
-> ParseResult a
parseArgs args = parseNiceArgs niceargs
where
niceargs = preprocess args
parseNiceArgs
:: NiceArgs
-> CmdLnInterface a
-> ParseResult a
parseNiceArgs niceargs appspec = fromMaybe normalprocess specialprocess
where
parser = getParserFun $ cmdArgParser appspec
normalprocess = runParser parser niceargs
specialprocess = runSpecialFlags appspec niceargs
runSpecialFlags :: CmdLnInterface a -> NiceArgs -> Maybe (ParseResult a)
runSpecialFlags app args = loop $ specialFlags app where
loop flags = case flags of
[] -> Nothing
(parse, action):rest -> runSpecialAction parse action rest
runSpecialAction parse action other = case specialParseResult of
Right True -> Just $ action app args
_ -> loop other
where
specialParseResult = runParser (getParserFun parse) args
defaultSpecialFlags :: [SpecialFlag a]
defaultSpecialFlags =
[ ( flagparser Short "help" "show this help message and exit"
, showParser $ showCmdLineAppUsage defaultFormat
)
, ( flagparser Long "version" "print the program version and exit"
, showParser showCmdLineVersion
)
] where
flagparser fmt key descr = liftParam $ FlagParam fmt key id `Descr` descr
showParser action = const . Left . action
mkApp
:: ParserSpec a
-> IO (CmdLnInterface a)
mkApp spec = liftM (mkDefaultApp spec) getProgName
mkDefaultApp :: ParserSpec a -> String -> CmdLnInterface a
mkDefaultApp spec progName = CmdLnInterface
spec defaultSpecialFlags progName Nothing Nothing Nothing
setAppDescr :: CmdLnInterface a -> String -> CmdLnInterface a
setAppDescr app descr = app {getAppDescr = Just descr }
setAppEpilog :: CmdLnInterface a -> String -> CmdLnInterface a
setAppEpilog app descr = app {getAppEpilog = Just descr }
setAppName :: CmdLnInterface a -> String -> CmdLnInterface a
setAppName app descr = app {getAppName = descr }