{-# LANGUAGE ScopedTypeVariables, CPP #-}
module System.Console.CmdArgs.Explicit(
process, processArgs, processValue, processValueIO,
module System.Console.CmdArgs.Explicit.Type,
flagHelpSimple, flagHelpFormat, flagVersion, flagNumericVersion, flagsVerbosity,
module System.Console.CmdArgs.Explicit.Help,
module System.Console.CmdArgs.Explicit.ExpandArgsAt,
module System.Console.CmdArgs.Explicit.SplitJoin,
Complete(..), complete
) where
import System.Console.CmdArgs.Explicit.Type
import System.Console.CmdArgs.Explicit.Process
import System.Console.CmdArgs.Explicit.Help
import System.Console.CmdArgs.Explicit.ExpandArgsAt
import System.Console.CmdArgs.Explicit.SplitJoin
import System.Console.CmdArgs.Explicit.Complete
import System.Console.CmdArgs.Default
import System.Console.CmdArgs.Helper
import System.Console.CmdArgs.Text
import System.Console.CmdArgs.Verbosity
import Control.Monad
import Data.Char
import Data.Maybe
import System.Environment
import System.Exit
import System.IO
processArgs :: Mode a -> IO a
processArgs :: forall a. Mode a -> IO a
processArgs Mode a
m = do
[(String, String)]
env <- IO [(String, String)]
getEnvironment
case forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup String
"CMDARGS_COMPLETE" [(String, String)]
env of
Just String
x -> do
[String]
args <- IO [String]
getArgs
let argInd :: Int
argInd = forall a. a -> Maybe a -> a
fromMaybe (forall (t :: * -> *) a. Foldable t => t a -> Int
length [String]
args forall a. Num a => a -> a -> a
- Int
1) forall a b. (a -> b) -> a -> b
$ forall a. Read a => String -> Maybe a
readMay String
x
argPos :: Int
argPos = forall a. a -> Maybe a -> a
fromMaybe (if Int
argInd forall a. Ord a => a -> a -> Bool
>= Int
0 Bool -> Bool -> Bool
&& Int
argInd forall a. Ord a => a -> a -> Bool
< forall (t :: * -> *) a. Foldable t => t a -> Int
length [String]
args then forall (t :: * -> *) a. Foldable t => t a -> Int
length ([String]
args forall a. [a] -> Int -> a
!! Int
argInd) else Int
0) forall a b. (a -> b) -> a -> b
$
forall a. Read a => String -> Maybe a
readMay forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup String
"CMDARGS_COMPLETE_POS" [(String, String)]
env
forall a. Show a => a -> IO ()
print forall a b. (a -> b) -> a -> b
$ forall a. Mode a -> [String] -> (Int, Int) -> [Complete]
complete Mode a
m (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap String -> [String]
words [String]
args) (Int
argInd,Int
argPos)
forall a. ExitCode -> IO a
exitWith ExitCode
ExitSuccess
Maybe String
Nothing -> do
String
nam <- IO String
getProgName
let var :: Maybe String
var = forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
mplus (forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup (String
"CMDARGS_HELPER_" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toUpper forall a b. (a -> b) -> a -> b
$ forall a. [a] -> a
head forall a b. (a -> b) -> a -> b
$ forall a. Mode a -> [String]
modeNames Mode a
m forall a. [a] -> [a] -> [a]
++ [String
nam])) [(String, String)]
env)
(forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup String
"CMDARGS_HELPER" [(String, String)]
env)
case Maybe String
var of
Maybe String
Nothing -> forall a. Mode a -> [String] -> IO a
processValueIO Mode a
m forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (if forall a. Mode a -> Bool
modeExpandAt Mode a
m then [String] -> IO [String]
expandArgsAt else forall (m :: * -> *) a. Monad m => a -> m a
return) forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO [String]
getArgs
Just String
cmd -> do
Either String [String]
res <- forall a.
String -> Mode a -> [String] -> IO (Either String [String])
execute String
cmd Mode a
m []
case Either String [String]
res of
Left String
err -> do
Handle -> String -> IO ()
hPutStrLn Handle
stderr forall a b. (a -> b) -> a -> b
$ String
"Error when running helper " forall a. [a] -> [a] -> [a]
++ String
cmd
Handle -> String -> IO ()
hPutStrLn Handle
stderr String
err
forall a. IO a
exitFailure
Right [String]
args -> forall a. Mode a -> [String] -> IO a
processValueIO Mode a
m [String]
args
readMay :: Read a => String -> Maybe a
readMay :: forall a. Read a => String -> Maybe a
readMay String
s = case [a
x | (a
x,String
t) <- forall a. Read a => ReadS a
reads String
s, (String
"",String
"") <- ReadS String
lex String
t] of
[a
x] -> forall a. a -> Maybe a
Just a
x
[a]
_ -> forall a. Maybe a
Nothing
#if __GLASGOW_HASKELL__ < 800
errorWithoutStackTrace :: String -> a
errorWithoutStackTrace = error
#endif
processValue :: Mode a -> [String] -> a
processValue :: forall a. Mode a -> [String] -> a
processValue Mode a
m [String]
xs = case forall a. Mode a -> [String] -> Either String a
process Mode a
m [String]
xs of
Left String
x -> forall a. String -> a
errorWithoutStackTrace String
x
Right a
x -> a
x
processValueIO :: Mode a -> [String] -> IO a
processValueIO :: forall a. Mode a -> [String] -> IO a
processValueIO Mode a
m [String]
xs = case forall a. Mode a -> [String] -> Either String a
process Mode a
m [String]
xs of
Left String
x -> do Handle -> String -> IO ()
hPutStrLn Handle
stderr String
x; forall a. IO a
exitFailure
Right a
x -> forall (m :: * -> *) a. Monad m => a -> m a
return a
x
flagHelpSimple :: (a -> a) -> Flag a
flagHelpSimple :: forall a. (a -> a) -> Flag a
flagHelpSimple a -> a
f = forall a. [String] -> (a -> a) -> String -> Flag a
flagNone [String
"help",String
"?"] a -> a
f String
"Display help message"
flagHelpFormat :: (HelpFormat -> TextFormat -> a -> a) -> Flag a
flagHelpFormat :: forall a. (HelpFormat -> TextFormat -> a -> a) -> Flag a
flagHelpFormat HelpFormat -> TextFormat -> a -> a
f = (forall a.
String -> [String] -> Update a -> String -> String -> Flag a
flagOpt String
"" [String
"help",String
"?"] String -> a -> Either String a
upd String
"" String
"Display help message"){flagInfo :: FlagInfo
flagInfo = String -> FlagInfo
FlagOptRare String
""}
where
upd :: String -> a -> Either String a
upd String
s a
v = case String -> Either String (HelpFormat, TextFormat)
format String
s of
Left String
e -> forall a b. a -> Either a b
Left String
e
Right (HelpFormat
a,TextFormat
b) -> forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ HelpFormat -> TextFormat -> a -> a
f HelpFormat
a TextFormat
b a
v
format :: String -> Either String (HelpFormat,TextFormat)
format :: String -> Either String (HelpFormat, TextFormat)
format String
xs = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl (\Either String (HelpFormat, TextFormat)
acc String
x -> String
-> (HelpFormat, TextFormat)
-> Either String (HelpFormat, TextFormat)
f String
x forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Either String (HelpFormat, TextFormat)
acc) (forall a b. b -> Either a b
Right forall a. Default a => a
def) (String -> [String]
sep String
xs)
where
sep :: String -> [String]
sep = String -> [String]
words forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map (\Char
x -> if Char
x forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` String
":," then Char
' ' else Char -> Char
toLower Char
x)
f :: String
-> (HelpFormat, TextFormat)
-> Either String (HelpFormat, TextFormat)
f String
x (HelpFormat
a,TextFormat
b) = case String
x of
String
"all" -> forall a b. b -> Either a b
Right (HelpFormat
HelpFormatAll,TextFormat
b)
String
"one" -> forall a b. b -> Either a b
Right (HelpFormat
HelpFormatOne,TextFormat
b)
String
"def" -> forall a b. b -> Either a b
Right (HelpFormat
HelpFormatDefault,TextFormat
b)
String
"html" -> forall a b. b -> Either a b
Right (HelpFormat
a,TextFormat
HTML)
String
"text" -> forall a b. b -> Either a b
Right (HelpFormat
a,TextFormat
defaultWrap)
String
"bash" -> forall a b. b -> Either a b
Right (HelpFormat
HelpFormatBash,Int -> TextFormat
Wrap Int
1000000)
String
"zsh" -> forall a b. b -> Either a b
Right (HelpFormat
HelpFormatZsh ,Int -> TextFormat
Wrap Int
1000000)
String
_ | forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Char -> Bool
isDigit String
x -> forall a b. b -> Either a b
Right (HelpFormat
a,Int -> TextFormat
Wrap forall a b. (a -> b) -> a -> b
$ forall a. Read a => String -> a
read String
x)
String
_ -> forall a b. a -> Either a b
Left String
"unrecognised help format, expected one of: all one def html text <NUMBER>"
flagVersion :: (a -> a) -> Flag a
flagVersion :: forall a. (a -> a) -> Flag a
flagVersion a -> a
f = forall a. [String] -> (a -> a) -> String -> Flag a
flagNone [String
"version",String
"V"] a -> a
f String
"Print version information"
flagNumericVersion :: (a -> a) -> Flag a
flagNumericVersion :: forall a. (a -> a) -> Flag a
flagNumericVersion a -> a
f = forall a. [String] -> (a -> a) -> String -> Flag a
flagNone [String
"numeric-version"] a -> a
f String
"Print just the version number"
flagsVerbosity :: (Verbosity -> a -> a) -> [Flag a]
flagsVerbosity :: forall a. (Verbosity -> a -> a) -> [Flag a]
flagsVerbosity Verbosity -> a -> a
f =
[forall a. [String] -> (a -> a) -> String -> Flag a
flagNone [String
"verbose",String
"v"] (Verbosity -> a -> a
f Verbosity
Loud) String
"Loud verbosity"
,forall a. [String] -> (a -> a) -> String -> Flag a
flagNone [String
"quiet",String
"q"] (Verbosity -> a -> a
f Verbosity
Quiet) String
"Quiet verbosity"]