module SimpleGetOpt
(
getOpts
, getOptsX
, OptSpec(..)
, OptDescr(..)
, OptSetter
, ArgDescr(..)
, GetOptException(..)
, dumpUsage
, reportUsageError
, usageString
) where
import qualified System.Console.GetOpt as GetOpt
import System.IO(stderr,hPutStrLn)
import System.Exit(exitFailure)
import System.Environment(getArgs)
import Control.Monad(unless)
import Control.Exception(Exception,throwIO,catch)
data OptSpec a = OptSpec
{ progDefaults :: a
, progOptions :: [OptDescr a]
, progParamDocs :: [(String,String)]
, progParams :: String -> OptSetter a
}
data OptDescr a = Option
{ optShortFlags :: [Char]
, optLongFlags :: [String]
, optDescription :: String
, optArgument :: ArgDescr a
}
type OptSetter a = a -> Either String a
data ArgDescr a =
NoArg (OptSetter a)
| ReqArg String (String -> OptSetter a)
| OptArg String (Maybe String -> OptSetter a)
opts :: OptSpec a -> [ GetOpt.OptDescr (OptSetter a) ]
opts = map convertOpt . progOptions
convertArg :: ArgDescr a -> GetOpt.ArgDescr (OptSetter a)
convertArg arg =
case arg of
NoArg a -> GetOpt.NoArg a
ReqArg s a -> GetOpt.ReqArg a s
OptArg s a -> GetOpt.OptArg a s
convertOpt :: OptDescr a -> GetOpt.OptDescr (OptSetter a)
convertOpt (Option a b c d) = GetOpt.Option a b (convertArg d) c
addOpt :: (a, [String]) -> (a -> Either String a) -> (a, [String])
addOpt (a,es) f = case f a of
Left e -> (a,e:es)
Right a1 -> (a1,es)
addFile :: (String -> OptSetter a) -> (a, [String]) -> String -> (a,[String])
addFile add (a,es) file = case add file a of
Left e -> (a,e:es)
Right a1 -> (a1,es)
getOptsX :: OptSpec a -> IO a
getOptsX os =
do as <- getArgs
let (funs,files,errs) = GetOpt.getOpt GetOpt.Permute (opts os) as
unless (null errs) $ throwIO (GetOptException errs)
let (a, errs1) = foldl addOpt (progDefaults os,[]) funs
unless (null errs1) $ throwIO (GetOptException errs1)
let (b, errs2) = foldl (addFile (progParams os)) (a,[]) files
unless (null errs2) $ throwIO (GetOptException errs2)
return b
getOpts :: OptSpec a -> IO a
getOpts os =
getOptsX os `catch` \(GetOptException errs) -> reportUsageError os errs
reportUsageError :: OptSpec a -> [String] -> IO b
reportUsageError os es =
do hPutStrLn stderr "Invalid command line options:"
hPutStrLn stderr $ unlines $ map (" " ++) es
dumpUsage os
exitFailure
dumpUsage :: OptSpec a -> IO ()
dumpUsage os = hPutStrLn stderr (usageString os)
usageString :: OptSpec a -> String
usageString os = GetOpt.usageInfo (params ++ "Flags:") (opts os)
where
params = case concatMap ppParam (progParamDocs os) of
"" -> ""
ps -> "Parameters:\n" ++ ps ++ "\n"
ppParam (x,y) = " " ++ x ++ " " ++ y ++ "\n"
data GetOptException = GetOptException [String] deriving Show
instance Exception GetOptException