-- This file is part of Diohsc -- Copyright (C) 2020 Martin Bays -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of version 3 of the GNU General Public License as -- published by the Free Software Foundation, or any later version. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see http://www.gnu.org/licenses/. {-# LANGUAGE Safe #-} module Opts (usage, parseArgs, Opt(..)) where import System.Console.GetOpt import Version data Opt = Restricted | Interactive | Batch | Prompt | ScriptFile FilePath | OptCommand String | DataDir FilePath | SocksHost String | SocksPort String | Ghost | Ansi | NoAnsi | Help | Version deriving (Eq, Ord, Show) options :: [OptDescr Opt] options = [ Option ['d'] ["datadir"] (ReqArg DataDir "PATH") "data and config directory (default: ~/.diohsc)" , Option ['e'] ["command"] (ReqArg OptCommand "COMMAND") "execute command" , Option ['f'] ["file"] (ReqArg ScriptFile "PATH") "execute commands from file (\"-\" for stdin)" , Option ['p'] ["prompt"] (NoArg Prompt) "prompt for further commands after -e/-f" , Option ['i'] ["interact"] (NoArg Interactive) "interactive mode (assumed unless -e/-f used)" , Option ['b'] ["batch"] (NoArg Batch) "non-interactive mode (assumed if -e/-f used)" , Option ['c'] ["colour"] (NoArg Ansi) "use ANSI colour (assumed if stdout is term)" , Option ['C'] ["no-colour"] (NoArg NoAnsi) "do not use ANSI colour" , Option ['g'] ["ghost"] (NoArg Ghost) "write nothing to filesystem (unless commanded)" , Option ['r'] ["restricted"] (NoArg Restricted) "disallow shell and filesystem access" , Option ['S'] ["socks-host"] (ReqArg SocksHost "HOST") "use SOCKS5 proxy" , Option ['P'] ["socks-port"] (ReqArg SocksPort "PORT") "port for SOCKS5 proxy (default 1080)" , Option ['v'] ["version"] (NoArg Version) "show version information" , Option ['h'] ["help"] (NoArg Help) "show usage information" ] usage :: String usage = usageInfo header options where header = "Usage: " ++ programName ++ " [OPTION...] [URI|PATH]" parseArgs :: [String] -> IO ([Opt],[String]) parseArgs argv = case getOpt Permute options argv of (o,n,[]) -> return (o,n) (_,_,errs) -> ioError (userError (concat errs ++ usage))