----------------------------------------------------------------------------- -- | -- Module : UI.Menu -- Copyright : (c) 2011 University of Minho -- License : BSD3 -- -- Maintainer : hpacheco@di.uminho.pt -- Stability : experimental -- Portability : non-portable -- -- Multifocal: -- Bidirectional Two-level Transformation of XML Schemas -- -- General ui menu configuration functions. -- ----------------------------------------------------------------------------- module UI.Menu where import System.IO import System.Environment import System.Console.GetOpt import System.Exit type Opts a = [OptDescr (a -> IO a)] parseOptions :: a -> Opts a -> [String] -> IO a parseOptions start opts argv = case getOpt RequireOrder opts argv of (optsActions,rest,[]) -> foldl (>>=) (return start) optsActions (_,_,errs) -> do prg <- getProgName ioError (userError (concat errs ++ usageInfo ("Usage: "++prg++" [OPTION...] files...") opts)) run :: String -> Maybe a -> IO a run err = maybe (error err) return -- | Function that prints the help usage and returns with a success code (used -- when the help program option is specified. exitHelp :: Opts a -> IO a exitHelp opts = do showHelp opts exitWith ExitSuccess -- | Function that prints the program usage to the sdtderr using the standard -- 'usageInfo' function. showHelp :: Opts a -> IO () showHelp opts = do prg <- getProgName hPutStrLn stderr (usageInfo ("Usage: "++prg++" [OPTION...]") opts) hFlush stderr