{-# LANGUAGE Safe #-}
module System.Console.GetOpt.Utils (parseCmdLine,
validateCmdLine,
StdOption,
stdRequired,
stdOptional
)
where
import safe System.Console.GetOpt
( getOpt, usageInfo, ArgOrder, OptDescr )
import safe System.Environment ( getArgs )
parseCmdLine :: ArgOrder a -> [OptDescr a] -> String -> IO ([a], [String])
parseCmdLine :: ArgOrder a -> [OptDescr a] -> String -> IO ([a], [String])
parseCmdLine ArgOrder a
order [OptDescr a]
options String
header =
do [String]
argv <- IO [String]
getArgs
case ArgOrder a -> [OptDescr a] -> [String] -> ([a], [String], [String])
forall a.
ArgOrder a -> [OptDescr a] -> [String] -> ([a], [String], [String])
getOpt ArgOrder a
order [OptDescr a]
options [String]
argv of
([a]
o, [String]
n, []) -> ([a], [String]) -> IO ([a], [String])
forall (m :: * -> *) a. Monad m => a -> m a
return ([a]
o, [String]
n)
([a]
_, [String]
_, [String]
errors) -> IOError -> IO ([a], [String])
forall a. IOError -> IO a
ioError (String -> IOError
userError ([String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String]
errors String -> String -> String
forall a. [a] -> [a] -> [a]
++
String -> [OptDescr a] -> String
forall a. String -> [OptDescr a] -> String
usageInfo String
header [OptDescr a]
options))
validateCmdLine :: ArgOrder a -> [OptDescr a] -> String ->
(([a],[String]) -> Maybe String) -> IO ([a], [String])
validateCmdLine :: ArgOrder a
-> [OptDescr a]
-> String
-> (([a], [String]) -> Maybe String)
-> IO ([a], [String])
validateCmdLine ArgOrder a
order [OptDescr a]
options String
header ([a], [String]) -> Maybe String
func =
do ([a], [String])
res <- ArgOrder a -> [OptDescr a] -> String -> IO ([a], [String])
forall a.
ArgOrder a -> [OptDescr a] -> String -> IO ([a], [String])
parseCmdLine ArgOrder a
order [OptDescr a]
options String
header
case ([a], [String]) -> Maybe String
func ([a], [String])
res of
Maybe String
Nothing -> ([a], [String]) -> IO ([a], [String])
forall (m :: * -> *) a. Monad m => a -> m a
return ([a], [String])
res
Just String
errormsg -> IOError -> IO ([a], [String])
forall a. IOError -> IO a
ioError (String -> IOError
userError (String
errormsg String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\n" String -> String -> String
forall a. [a] -> [a] -> [a]
++
String -> [OptDescr a] -> String
forall a. String -> [OptDescr a] -> String
usageInfo String
header [OptDescr a]
options))
type StdOption = (String, String)
stdRequired :: String
-> String -> StdOption
stdRequired :: String -> String -> StdOption
stdRequired String
name String
value = (String
name, String
value)
stdOptional :: String
-> Maybe String -> StdOption
stdOptional :: String -> Maybe String -> StdOption
stdOptional String
name Maybe String
Nothing = (String
name, String
"")
stdOptional String
name (Just String
x) = (String
name, String
x)