module System.Console.ArgParser.BaseType where
import Control.Applicative ((<*>), Applicative, pure)
import qualified Data.Map as M (Map)
type Arg = String
type Args = [Arg]
type Flags = M.Map Arg Args
type NiceArgs = (Args, Flags)
type ParseResult a = Either String a
data ParamDescr = ParamDescr
{ argUsageFmt :: String -> String
, argCategory :: String
, argFormat :: String -> String
, argDescr :: String
, argMetaVar :: String
}
argUsage :: ParamDescr -> String
argUsage d = argUsageFmt d $ argMetaVar d
getArgFormat :: ParamDescr -> String
getArgFormat d = argFormat d $ argMetaVar d
data Parser a = Parser (NiceArgs -> (ParseResult a, NiceArgs))
data ParserSpec a = ParserSpec
{ getParserParams :: [ParamDescr]
, getParserFun :: Parser a
}
instance Functor ParserSpec where
fmap f p = p {getParserFun = fmap f $ getParserFun p}
instance Applicative ParserSpec where
pure val = ParserSpec [] $ pure val
ParserSpec d1 p1 <*> ParserSpec d2 p2 =
ParserSpec (d1 ++ d2) (p1 <*> p2)
type SpecialAction a =
CmdLnInterface a
-> NiceArgs
-> ParseResult a
type SpecialFlag a = (ParserSpec Bool, SpecialAction a)
data CmdLnInterface a = CmdLnInterface
{ cmdArgParser :: ParserSpec a
, specialFlags :: [SpecialFlag a]
, getAppName :: String
, getAppVersion :: Maybe String
, getAppDescr :: Maybe String
, getAppEpilog :: Maybe String
}
instance Functor Parser where
fmap f (Parser g) = Parser (\args ->
let (res, newargs) = g args
in (fmap f res, newargs))
instance Applicative Parser where
pure val = Parser parser where
parser args = (Right val, args)
(Parser f) <*> (Parser g) = Parser (\args ->
let (h, newargs) = f args
(res, lastargs) = g newargs
in (h <*> res, lastargs))