{-# LANGUAGE OverloadedStrings #-}
module Darcs.UI.RunCommand
( runTheCommand
, runWithHooks
) where
import Darcs.Prelude
import Control.Monad ( unless, when )
import System.Console.GetOpt( ArgOrder( Permute, RequireOrder ),
OptDescr( Option ),
getOpt )
import System.Exit ( ExitCode ( ExitSuccess ), exitWith )
import Darcs.UI.Options ( (^), odesc, oparse, parseFlags, optDescr, (?) )
import Darcs.UI.Options.All
( stdCmdActions, StdCmdAction(..)
, debugging, verbosity, Verbosity(..), network, NetworkOptions(..)
, HooksConfig(..), hooks )
import Darcs.UI.Defaults ( applyDefaults )
import Darcs.UI.External ( viewDoc )
import Darcs.UI.Flags ( DarcsFlag, matchAny, fixRemoteRepos, withNewRepo )
import Darcs.UI.Commands
( CommandArgs( CommandOnly, SuperCommandOnly, SuperCommandSub )
, CommandControl
, DarcsCommand
, commandName
, commandCommand
, commandPrereq
, commandExtraArgHelp
, commandExtraArgs
, commandArgdefaults
, commandCompleteArgs
, commandOptions
, commandName
, disambiguateCommands
, getSubcommands
, extractCommands
, superName
)
import Darcs.UI.Commands.GZCRCs ( doCRCWarnings )
import Darcs.UI.Commands.Clone ( makeRepoName, cloneToSSH )
import Darcs.UI.Usage
( getCommandHelp
, getCommandMiniHelp
, subusage
)
import Darcs.Patch.Match ( checkMatchSyntax )
import Darcs.Repository.Prefs ( getGlobal, getPreflist )
import Darcs.Repository.Test ( runPosthook, runPrehook )
import Darcs.Util.AtExit ( atexit )
import Darcs.Util.Download ( setDebugHTTP, disableHTTPPipelining )
import Darcs.Util.Exception ( die )
import Darcs.Util.Global ( setDebugMode, setTimingsMode )
import Darcs.Util.Path ( AbsolutePath, getCurrentDirectory, toPath, ioAbsoluteOrRemote, makeAbsolute )
import Darcs.Util.Printer ( (<+>), ($+$), renderString, text, vcat )
import Darcs.Util.Printer.Color ( ePutDocLn )
import Darcs.Util.Progress ( setProgressMode )
runTheCommand :: [CommandControl] -> String -> [String] -> IO ()
runTheCommand commandControlList cmd args =
either die rtc $ disambiguateCommands commandControlList cmd args
where
rtc (CommandOnly c, as) = runCommand Nothing c as
rtc (SuperCommandOnly c, as) = runRawSupercommand c as
rtc (SuperCommandSub c s, as) = runCommand (Just c) s as
runCommand :: Maybe DarcsCommand -> DarcsCommand -> [String] -> IO ()
runCommand _ _ args
| "-all" `elem` args =
die "Are you sure you didn't mean --all rather than -all?"
runCommand msuper cmd args = do
old_wd <- getCurrentDirectory
let options = commandOptions old_wd cmd
case fixupMsgs $ getOpt Permute options args of
(cmdline_flags,orig_extra,getopt_errs) -> do
prereq_errors <- commandPrereq cmd cmdline_flags
new_wd <- getCurrentDirectory
user_defs <- getGlobal "defaults"
repo_defs <- getPreflist "defaults"
let (flags,flag_errors) =
applyDefaults (fmap commandName msuper) cmd old_wd user_defs repo_defs cmdline_flags
case parseFlags stdCmdActions flags of
Just Help -> viewDoc $ getCommandHelp msuper cmd
Just ListOptions -> do
setProgressMode False
possible_args <- commandCompleteArgs cmd (new_wd, old_wd) flags orig_extra
mapM_ putStrLn $ optionList options ++ possible_args
Just Disable ->
die $ "Command "++commandName cmd++" disabled with --disable option!"
Nothing -> case prereq_errors of
Left complaint -> die $
"Unable to '" ++ "darcs " ++ superName msuper ++ commandName cmd ++
"' here:\n" ++ complaint
Right () -> do
ePutDocLn $ vcat $ map text $ getopt_errs ++ flag_errors
extra <- commandArgdefaults cmd flags old_wd orig_extra
case extraArgumentsError extra cmd msuper of
Nothing -> runWithHooks cmd (new_wd, old_wd) flags extra
Just msg -> die msg
fixupMsgs :: (a, b, [String]) -> (a, b, [String])
fixupMsgs (fs,as,es) = (fs,as,map (("command line: "++).chompTrailingNewline) es)
where
chompTrailingNewline "" = ""
chompTrailingNewline s = if last s == '\n' then init s else s
runWithHooks :: DarcsCommand
-> (AbsolutePath, AbsolutePath)
-> [DarcsFlag] -> [String] -> IO ()
runWithHooks cmd (new_wd, old_wd) flags extra = do
checkMatchSyntax $ matchAny ? flags
oparse (verbosity ^ debugging ^ network) setGlobalVariables flags
let hooksCfg = parseFlags hooks flags
let verb = parseFlags verbosity flags
preHookExitCode <- runPrehook (pre hooksCfg) verb new_wd
if preHookExitCode /= ExitSuccess
then exitWith preHookExitCode
else do fixedFlags <- fixRemoteRepos old_wd flags
phDir <- getPosthookDir new_wd cmd fixedFlags extra
commandCommand cmd (new_wd, old_wd) fixedFlags extra
postHookExitCode <- runPosthook (post hooksCfg) verb phDir
exitWith postHookExitCode
setGlobalVariables :: Verbosity -> Bool -> Bool -> Bool -> NetworkOptions -> IO ()
setGlobalVariables verb debug debugHttp timings net = do
when timings setTimingsMode
when debug setDebugMode
when debugHttp setDebugHTTP
when (verb == Quiet) $ setProgressMode False
when (noHttpPipelining net) disableHTTPPipelining
unless (verb == Quiet) $ atexit $ doCRCWarnings (verb == Verbose)
getPosthookDir :: AbsolutePath -> DarcsCommand -> [DarcsFlag] -> [String] -> IO AbsolutePath
getPosthookDir new_wd cmd flags extra | commandName cmd `elem` ["get","clone"] = do
case extra of
[inrepodir, outname] -> getPosthookDir new_wd cmd (withNewRepo outname flags) [inrepodir]
[inrepodir] ->
case cloneToSSH flags of
Nothing -> do
repodir <- toPath <$> ioAbsoluteOrRemote inrepodir
newRepo <- makeRepoName False flags repodir
return $ makeAbsolute new_wd newRepo
_ -> return new_wd
_ -> die "You must provide 'clone' with either one or two arguments."
getPosthookDir new_wd _ _ _ = return new_wd
extraArgumentsError :: [String]
-> DarcsCommand
-> Maybe DarcsCommand
-> Maybe String
extraArgumentsError extra cmd msuper
| extraArgsCmd < 0 = Nothing
| extraArgsInput > extraArgsCmd = Just badArg
| extraArgsInput < extraArgsCmd = Just missingArg
| otherwise = Nothing
where
extraArgsInput = length extra
extraArgsCmd = commandExtraArgs cmd
badArg = "Bad argument: `" ++ unwords extra ++
"'\n" ++ getCommandMiniHelp msuper cmd
missingArg = "Missing argument: " ++ nthArg (length extra + 1) ++
"\n" ++ getCommandMiniHelp msuper cmd
nthArg n = nthOf n (commandExtraArgHelp cmd)
nthOf 1 (h:_) = h
nthOf n (_:hs) = nthOf (n-1) hs
nthOf _ [] = "UNDOCUMENTED"
optionList :: [OptDescr DarcsFlag] -> [String]
optionList = concatMap names
where
names (Option sos los _ desc) =
map (short desc) sos ++ map (long desc) los
short d o = '-' : o : ";" ++ d
long d o = "--" ++ o ++ ";" ++ d
runRawSupercommand :: DarcsCommand -> [String] -> IO ()
runRawSupercommand super [] =
die $ renderString $
"Command '" <> text (commandName super) <> "' requires a subcommand!"
$+$
subusage super
runRawSupercommand super args = do
cwd <- getCurrentDirectory
case fixupMsgs $ getOpt RequireOrder (map (optDescr cwd) (odesc stdCmdActions)) args of
(flags,_,getopt_errs) -> case parseFlags stdCmdActions flags of
Just Help ->
viewDoc $ getCommandHelp Nothing super
Just ListOptions -> do
putStrLn "--help"
mapM_ (putStrLn . commandName) (extractCommands $ getSubcommands super)
Just Disable -> do
die $ renderString $
"Command" <+> text (commandName super) <+> "disabled with --disable option!"
Nothing ->
die $ renderString $
case getopt_errs of
[] -> text "Invalid subcommand!" $+$ subusage super
_ -> vcat (map text getopt_errs)