module Options
(
Options(..)
, defaultOptions
, simpleOption
, DefineOptions
, SimpleOptionType(..)
, Subcommand
, subcommand
, runCommand
, runSubcommand
, Parsed
, parsedError
, parsedHelp
, ParsedOptions
, parsedOptions
, parsedArguments
, parseOptions
, ParsedSubcommand
, parsedSubcommand
, parseSubcommand
, OptionType
, defineOption
, Option
, optionShortFlags
, optionLongFlags
, optionDefault
, optionDescription
, optionGroup
, Group
, groupName
, groupTitle
, groupDescription
, optionType_bool
, optionType_string
, optionType_int
, optionType_int8
, optionType_int16
, optionType_int32
, optionType_int64
, optionType_word
, optionType_word8
, optionType_word16
, optionType_word32
, optionType_word64
, optionType_integer
, optionType_float
, optionType_double
, optionType_maybe
, optionType_list
, optionType_set
, optionType_map
, optionType_enum
, optionType
, optionTypeName
, optionTypeDefault
, optionTypeParse
, optionTypeShow
, optionTypeUnary
) where
import Control.Applicative
import Control.Monad.IO.Class (liftIO, MonadIO)
import Data.Int
import Data.List (intercalate)
import qualified Data.Map as Map
import Data.Maybe (isJust)
import qualified Data.Set as Set
import Data.Word
import qualified System.Environment
import System.Exit (exitFailure, exitSuccess)
import System.IO (hPutStr, hPutStrLn, stderr, stdout)
import Options.Help
import Options.Tokenize
import Options.Types
class Options opts where
defineOptions :: DefineOptions opts
data DefineOptions a = DefineOptions a (Integer -> (Integer, [OptionInfo])) (Integer -> Map.Map OptionKey Token -> Either String (Integer, a))
instance Functor DefineOptions where
fmap fn (DefineOptions defaultValue getInfo parse) = DefineOptions (fn defaultValue) getInfo (\key tokens -> case parse key tokens of
Left err -> Left err
Right (key', a) -> Right (key', fn a))
instance Applicative DefineOptions where
pure a = DefineOptions a (\key -> (key, [])) (\key _ -> Right (key, a))
(DefineOptions acc_default acc_getInfo acc_parse) <*> (DefineOptions defaultValue getInfo parse) = DefineOptions
(acc_default defaultValue)
(\key -> case acc_getInfo key of
(key', infos) -> case getInfo key' of
(key'', infos') -> (key'', infos ++ infos'))
(\key tokens -> case acc_parse key tokens of
Left err -> Left err
Right (key', fn) -> case parse key' tokens of
Left err -> Left err
Right (key'', a) -> Right (key'', fn a))
defaultOptions :: Options opts => opts
defaultOptions = case defineOptions of
(DefineOptions def _ _) -> def
data OptionType val = OptionType
{
optionTypeName :: String
, optionTypeDefault :: val
, optionTypeParse :: String -> Either String val
, optionTypeShow :: val -> String
, optionTypeUnary :: Maybe val
}
optionType :: String
-> val
-> (String -> Either String val)
-> (val -> String)
-> OptionType val
optionType name def parse show' = OptionType name def parse show' Nothing
class SimpleOptionType a where
simpleOptionType :: OptionType a
instance SimpleOptionType Bool where
simpleOptionType = optionType_bool
optionType_bool :: OptionType Bool
optionType_bool = (optionType "bool" False parseBool (\x -> if x then "true" else "false"))
{ optionTypeUnary = Just True
}
parseBool :: String -> Either String Bool
parseBool s = case s of
"true" -> Right True
"false" -> Right False
_ -> Left (show s ++ " is not in {\"true\", \"false\"}.")
instance SimpleOptionType String where
simpleOptionType = optionType_string
optionType_string :: OptionType String
optionType_string = optionType "text" "" Right show
instance SimpleOptionType Integer where
simpleOptionType = optionType_integer
optionType_integer :: OptionType Integer
optionType_integer = optionType "integer" 0 parseInteger show
parseInteger :: String -> Either String Integer
parseInteger s = parsed where
parsed = if valid
then Right (read s)
else Left (show s ++ " is not an integer.")
valid = case s of
[] -> False
'-':s' -> allDigits s'
_ -> allDigits s
allDigits = all (\c -> c >= '0' && c <= '9')
parseBoundedIntegral :: (Bounded a, Integral a) => String -> String -> Either String a
parseBoundedIntegral label = parse where
getBounds :: (Bounded a, Integral a) => (String -> Either String a) -> a -> a -> (Integer, Integer)
getBounds _ min' max' = (toInteger min', toInteger max')
(minInt, maxInt) = getBounds parse minBound maxBound
parse s = case parseInteger s of
Left err -> Left err
Right int -> if int < minInt || int > maxInt
then Left (show int ++ " is not within bounds [" ++ show minInt ++ ":" ++ show maxInt ++ "] of type " ++ label ++ ".")
else Right (fromInteger int)
optionTypeBoundedInt :: (Bounded a, Integral a, Show a) => String -> OptionType a
optionTypeBoundedInt tName = optionType tName 0 (parseBoundedIntegral tName) show
instance SimpleOptionType Int where
simpleOptionType = optionType_int
optionType_int :: OptionType Int
optionType_int = optionTypeBoundedInt "int"
instance SimpleOptionType Int8 where
simpleOptionType = optionType_int8
optionType_int8 :: OptionType Int8
optionType_int8 = optionTypeBoundedInt "int8"
instance SimpleOptionType Int16 where
simpleOptionType = optionType_int16
optionType_int16 :: OptionType Int16
optionType_int16 = optionTypeBoundedInt "int16"
instance SimpleOptionType Int32 where
simpleOptionType = optionType_int32
optionType_int32 :: OptionType Int32
optionType_int32 = optionTypeBoundedInt "int32"
instance SimpleOptionType Int64 where
simpleOptionType = optionType_int64
optionType_int64 :: OptionType Int64
optionType_int64 = optionTypeBoundedInt "int64"
instance SimpleOptionType Word where
simpleOptionType = optionType_word
optionType_word :: OptionType Word
optionType_word = optionTypeBoundedInt "uint"
instance SimpleOptionType Word8 where
simpleOptionType = optionType_word8
optionType_word8 :: OptionType Word8
optionType_word8 = optionTypeBoundedInt "uint8"
instance SimpleOptionType Word16 where
simpleOptionType = optionType_word16
optionType_word16 :: OptionType Word16
optionType_word16 = optionTypeBoundedInt "uint16"
instance SimpleOptionType Word32 where
simpleOptionType = optionType_word32
optionType_word32 :: OptionType Word32
optionType_word32 = optionTypeBoundedInt "uint32"
instance SimpleOptionType Word64 where
simpleOptionType = optionType_word64
optionType_word64 :: OptionType Word64
optionType_word64 = optionTypeBoundedInt "uint64"
instance SimpleOptionType Float where
simpleOptionType = optionType_float
optionType_float :: OptionType Float
optionType_float = optionType "float32" 0 parseFloat show
instance SimpleOptionType Double where
simpleOptionType = optionType_double
optionType_double :: OptionType Double
optionType_double = optionType "float64" 0 parseFloat show
parseFloat :: Read a => String -> Either String a
parseFloat s = case reads s of
[(x, "")] -> Right x
_ -> Left (show s ++ " is not a number.")
instance SimpleOptionType a => SimpleOptionType (Maybe a) where
simpleOptionType = optionType_maybe simpleOptionType
optionType_maybe :: OptionType a -> OptionType (Maybe a)
optionType_maybe t = maybeT { optionTypeUnary = unary } where
maybeT = optionType name Nothing (parseMaybe t) (showMaybe t)
name = "maybe<" ++ optionTypeName t ++ ">"
unary = case optionTypeUnary t of
Nothing -> Nothing
Just val -> Just (Just val)
parseMaybe :: OptionType val -> String -> Either String (Maybe val)
parseMaybe t s = case s of
"" -> Right Nothing
_ -> case optionTypeParse t s of
Left err -> Left err
Right a -> Right (Just a)
showMaybe :: OptionType val -> Maybe val -> String
showMaybe _ Nothing = ""
showMaybe t (Just x) = optionTypeShow t x
optionType_set :: Ord a
=> Char
-> OptionType a
-> OptionType (Set.Set a)
optionType_set sep t = optionType name Set.empty parseSet showSet where
name = "set<" ++ optionTypeName t ++ ">"
parseSet s = case parseList (optionTypeParse t) (split sep s) of
Left err -> Left err
Right xs -> Right (Set.fromList xs)
showSet xs = intercalate [sep] (map (optionTypeShow t) (Set.toList xs))
optionType_map :: Ord k
=> Char
-> Char
-> OptionType k
-> OptionType v
-> OptionType (Map.Map k v)
optionType_map itemSep keySep kt vt = optionType name Map.empty parser showMap where
name = "map<" ++ optionTypeName kt ++ "," ++ optionTypeName vt ++ ">"
parser s = parseMap keySep (optionTypeParse kt) (optionTypeParse vt) (split itemSep s)
showMap m = intercalate [itemSep] (map showItem (Map.toList m))
showItem (k, v) = optionTypeShow kt k ++ [keySep] ++ optionTypeShow vt v
parseList :: (String -> Either String a) -> [String] -> Either String [a]
parseList p = loop where
loop [] = Right []
loop (x:xs) = case p x of
Left err -> Left err
Right v -> case loop xs of
Left err -> Left err
Right vs -> Right (v:vs)
parseMap :: Ord k => Char -> (String -> Either String k) -> (String -> Either String v) -> [String] -> Either String (Map.Map k v)
parseMap keySep pKey pVal = parsed where
parsed strs = case parseList pItem strs of
Left err -> Left err
Right xs -> Right (Map.fromList xs)
pItem s = case break (== keySep) s of
(sKey, valAndSep) -> case valAndSep of
[] -> Left ("Map item " ++ show s ++ " has no value.")
_ : sVal -> case pKey sKey of
Left err -> Left err
Right key -> case pVal sVal of
Left err -> Left err
Right val -> Right (key, val)
split :: Char -> String -> [String]
split _ [] = []
split sep s0 = loop s0 where
loop s = let
(chunk, rest) = break (== sep) s
cont = chunk : loop (tail rest)
in if null rest then [chunk] else cont
optionType_list :: Char
-> OptionType a
-> OptionType [a]
optionType_list sep t = optionType name [] parser shower where
name = "list<" ++ optionTypeName t ++ ">"
parser s = parseList (optionTypeParse t) (split sep s)
shower xs = intercalate [sep] (map (optionTypeShow t) xs)
optionType_enum :: (Bounded a, Enum a, Show a)
=> String
-> OptionType a
optionType_enum tName = optionType tName minBound parseEnum show where
values = Map.fromList [(show x, x) | x <- enumFrom minBound]
setString = "{" ++ intercalate ", " (map show (Map.keys values)) ++ "}"
parseEnum s = case Map.lookup s values of
Nothing -> Left (show s ++ " is not in " ++ setString ++ ".")
Just x -> Right x
simpleOption :: SimpleOptionType a
=> String
-> a
-> String
-> DefineOptions a
simpleOption flag def desc = defineOption simpleOptionType (\o -> o
{ optionLongFlags = [flag]
, optionDefault = def
, optionDescription = desc
})
defineOption :: OptionType a -> (Option a -> Option a) -> DefineOptions a
defineOption t fn = DefineOptions (optionDefault opt) getInfo parser where
opt = fn (Option
{ optionShortFlags = []
, optionLongFlags = []
, optionDefault = optionTypeDefault t
, optionDescription = ""
, optionGroup = Nothing
, optionLocation = Nothing
})
getInfo key = (key+1, [OptionInfo
{ optionInfoKey = OptionKeyGenerated key
, optionInfoShortFlags = optionShortFlags opt
, optionInfoLongFlags = optionLongFlags opt
, optionInfoDefault = optionTypeShow t (optionDefault opt)
, optionInfoDescription = optionDescription opt
, optionInfoGroup = optionGroup opt
, optionInfoLocation = optionLocation opt
, optionInfoTypeName = optionTypeName t
, optionInfoUnary = isJust (optionTypeUnary t)
, optionInfoUnaryOnly = False
}])
parser key tokens = case Map.lookup (OptionKeyGenerated key) tokens of
Nothing -> Right (key+1, optionDefault opt)
Just tok -> case tok of
TokenUnary flagName -> case optionTypeUnary t of
Nothing -> Left ("The flag " ++ flagName ++ " requires an argument.")
Just val -> Right (key+1, val)
Token flagName rawValue -> case optionTypeParse t rawValue of
Left err -> Left ("Value for flag " ++ flagName ++ " is invalid: " ++ err)
Right val -> Right (key+1, val)
data Option a = Option
{
optionShortFlags :: [Char]
, optionLongFlags :: [String]
, optionDefault :: a
, optionDescription :: String
, optionGroup :: Maybe Group
, optionLocation :: Maybe Location
}
validateOptionDefs :: [OptionInfo] -> [(String, [OptionInfo])] -> Either String OptionDefinitions
validateOptionDefs cmdInfos subInfos = Right (addHelpFlags (OptionDefinitions cmdInfos subInfos))
class Parsed a where
parsedError_ :: a -> Maybe String
parsedHelp_ :: a -> String
data ParsedOptions opts = ParsedOptions (Maybe opts) (Maybe String) String [String]
data ParsedSubcommand action = ParsedSubcommand (Maybe action) (Maybe String) String
instance Parsed (ParsedOptions a) where
parsedError_ (ParsedOptions _ x _ _) = x
parsedHelp_ (ParsedOptions _ _ x _) = x
instance Parsed (ParsedSubcommand a) where
parsedError_ (ParsedSubcommand _ x _) = x
parsedHelp_ (ParsedSubcommand _ _ x) = x
parsedOptions :: ParsedOptions opts -> Maybe opts
parsedOptions (ParsedOptions x _ _ _) = x
parsedArguments :: ParsedOptions opts -> [String]
parsedArguments (ParsedOptions _ _ _ x) = x
parsedSubcommand :: ParsedSubcommand action -> Maybe action
parsedSubcommand (ParsedSubcommand x _ _) = x
parsedError :: Parsed a => a -> Maybe String
parsedError = parsedError_
parsedHelp :: Parsed a => a -> String
parsedHelp = parsedHelp_
parseOptions :: Options opts => [String] -> ParsedOptions opts
parseOptions argv = parsed where
(DefineOptions _ getInfos parser) = defineOptions
(_, optionInfos) = getInfos 0
parseTokens = parser 0
parsed = case validateOptionDefs optionInfos [] of
Left err -> ParsedOptions Nothing (Just err) "" []
Right optionDefs -> case tokenize (addHelpFlags optionDefs) argv of
(_, Left err) -> ParsedOptions Nothing (Just err) (helpFor HelpSummary optionDefs Nothing) []
(_, Right tokens) -> case checkHelpFlag tokens of
Just helpFlag -> ParsedOptions Nothing Nothing (helpFor helpFlag optionDefs Nothing) []
Nothing -> case parseTokens (tokensMap tokens) of
Left err -> ParsedOptions Nothing (Just err) (helpFor HelpSummary optionDefs Nothing) []
Right (_, opts) -> ParsedOptions (Just opts) Nothing (helpFor HelpSummary optionDefs Nothing) (tokensArgv tokens)
runCommand :: (MonadIO m, Options opts) => (opts -> [String] -> m a) -> m a
runCommand io = do
argv <- liftIO System.Environment.getArgs
let parsed = parseOptions argv
case parsedOptions parsed of
Just opts -> io opts (parsedArguments parsed)
Nothing -> liftIO $ case parsedError parsed of
Just err -> do
hPutStrLn stderr (parsedHelp parsed)
hPutStrLn stderr err
exitFailure
Nothing -> do
hPutStr stdout (parsedHelp parsed)
exitSuccess
data Subcommand cmdOpts action = Subcommand String (Integer -> ([OptionInfo], (cmdOpts -> Tokens -> Either String action), Integer))
subcommand :: (Options cmdOpts, Options subcmdOpts)
=> String
-> (cmdOpts -> subcmdOpts -> [String] -> action)
-> Subcommand cmdOpts action
subcommand name fn = Subcommand name (\initialKey -> let
(DefineOptions _ getInfos parser) = defineOptions
(nextKey, optionInfos) = getInfos initialKey
parseTokens = parser initialKey
runAction cmdOpts tokens = case parseTokens (tokensMap tokens) of
Left err -> Left err
Right (_, subOpts) -> Right (fn cmdOpts subOpts (tokensArgv tokens))
in (optionInfos, runAction, nextKey))
parseSubcommand :: Options cmdOpts => [Subcommand cmdOpts action] -> [String] -> ParsedSubcommand action
parseSubcommand subcommands argv = parsed where
(DefineOptions _ getInfos parser) = defineOptions
(cmdNextKey, cmdInfos) = getInfos 0
cmdParseTokens = parser 0
subcmdInfos = do
Subcommand name fn <- subcommands
let (infos, _, _) = fn cmdNextKey
return (name, infos)
subcmdRunners = Map.fromList $ do
Subcommand name fn <- subcommands
let (_, runner, _) = fn cmdNextKey
return (name, runner)
parsed = case validateOptionDefs cmdInfos subcmdInfos of
Left err -> ParsedSubcommand Nothing (Just err) ""
Right optionDefs -> case tokenize (addHelpFlags optionDefs) argv of
(subcmd, Left err) -> ParsedSubcommand Nothing (Just err) (helpFor HelpSummary optionDefs subcmd)
(subcmd, Right tokens) -> case checkHelpFlag tokens of
Just helpFlag -> ParsedSubcommand Nothing Nothing (helpFor helpFlag optionDefs subcmd)
Nothing -> case findAction tokens subcmd of
Left err -> ParsedSubcommand Nothing (Just err) (helpFor HelpSummary optionDefs subcmd)
Right action -> ParsedSubcommand (Just action) Nothing (helpFor HelpSummary optionDefs subcmd)
findAction _ Nothing = Left "No subcommand specified"
findAction tokens (Just subcmdName) = case cmdParseTokens (tokensMap tokens) of
Left err -> Left err
Right (_, cmdOpts) -> case Map.lookup subcmdName subcmdRunners of
Nothing -> Left ("Unknown subcommand " ++ show subcmdName ++ ".")
Just getRunner -> case getRunner cmdOpts tokens of
Left err -> Left err
Right action -> Right action
runSubcommand :: (Options opts, MonadIO m) => [Subcommand opts (m a)] -> m a
runSubcommand subcommands = do
argv <- liftIO System.Environment.getArgs
let parsed = parseSubcommand subcommands argv
case parsedSubcommand parsed of
Just cmd -> cmd
Nothing -> liftIO $ case parsedError parsed of
Just err -> do
hPutStrLn stderr (parsedHelp parsed)
hPutStrLn stderr err
exitFailure
Nothing -> do
hPutStr stdout (parsedHelp parsed)
exitSuccess