module Darcs.UI.Commands.Help (
helpCmd,
commandControlList, environmentHelp,
printVersion,
listAvailableCommands ) where
import Prelude ()
import Darcs.Prelude
import Darcs.UI.Flags
( DarcsFlag
, environmentHelpEmail
, environmentHelpSendmail
)
import Darcs.UI.Options.Markdown ( optionsMarkdown )
import Darcs.UI.Commands
( CommandArgs(..)
, CommandControl(..)
, normalCommand
, DarcsCommand(..)
, WrappedCommand(..)
, wrappedCommandName
, disambiguateCommands
, extractCommands
, getSubcommands
, nodefaults
)
import Darcs.UI.External ( viewDoc )
import Darcs.UI.Usage
( getCommandHelp
, usage
, subusage
)
import Darcs.Util.Lock ( environmentHelpTmpdir, environmentHelpKeepTmpdir
, environmentHelpLocks )
import Darcs.Patch.Match ( helpOnMatchers )
import Darcs.Repository.Prefs ( environmentHelpHome, prefsFilesHelp )
import Darcs.Util.Ssh ( environmentHelpSsh, environmentHelpScp, environmentHelpSshPort )
import Darcs.Util.File ( withCurrentDirectory )
import Darcs.Util.Path ( AbsolutePath )
import Control.Arrow ( (***) )
import Data.Char ( isAlphaNum, toLower, toUpper )
import Data.Either ( partitionEithers )
import Data.List ( groupBy, isPrefixOf, intercalate, nub, lookup )
import Darcs.Util.English ( andClauses )
import Darcs.Util.Printer (text, vcat, vsep, ($$), empty)
import Darcs.Util.Printer.Color ( environmentHelpColor, environmentHelpEscape, environmentHelpEscapeWhite )
import System.Exit ( exitSuccess )
import Version ( version )
import Darcs.Util.Download ( environmentHelpProxy, environmentHelpProxyPassword )
import Darcs.Util.Workaround ( getCurrentDirectory )
import Darcs.UI.Options ( defaultFlags, ocheck, onormalise, oid )
import qualified Darcs.UI.TheCommands as TheCommands
helpDescription :: String
helpDescription = "Display help about darcs and darcs commands."
helpHelp :: String
helpHelp =
"Without arguments, `darcs help` prints a categorized list of darcs\n" ++
"commands and a short description of each one. With an extra argument,\n" ++
"`darcs help foo` prints detailed help about the darcs command foo.\n"
unwrapTree :: [CommandControl] -> [(String, [CommandControl])]
unwrapTree cs = [ (wrappedCommandName c, subcmds c) | CommandData c <- cs ]
where
subcmds (WrappedCommand sc) = getSubcommands sc
completeArgs :: [String] -> [String]
completeArgs [] = map fst (unwrapTree commandControlList) ++ extraArgs where
extraArgs = [ "manpage", "markdown", "patterns", "environment" ]
completeArgs (arg:args) = exploreTree arg args commandControlList where
exploreTree cmd cmds cs =
case lookup cmd (unwrapTree cs) of
Nothing -> []
Just cs' -> case cmds of
[] -> map fst (unwrapTree cs')
sub:cmds' -> exploreTree sub cmds' cs'
help :: DarcsCommand [DarcsFlag]
help = DarcsCommand
{ commandProgramName = "darcs"
, commandName = "help"
, commandHelp = helpHelp
, commandDescription = helpDescription
, commandExtraArgs = 1
, commandExtraArgHelp = ["[<DARCS_COMMAND> [DARCS_SUBCOMMAND]] "]
, commandCommand = \ x y z -> helpCmd x y z >> exitSuccess
, commandPrereq = \_ -> return $ Right ()
, commandCompleteArgs = \_ _ -> return . completeArgs
, commandArgdefaults = nodefaults
, commandAdvancedOptions = []
, commandBasicOptions = []
, commandDefaults = defaultFlags oid
, commandCheckOptions = ocheck oid
, commandParseOptions = onormalise oid
}
helpCmd :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
helpCmd _ _ ["manpage"] = putStr $ unlines manpageLines
helpCmd _ _ ["markdown"] = putStr $ unlines markdownLines
helpCmd _ _ ["patterns"] = viewDoc $ text $ unlines helpOnMatchers
helpCmd _ _ ("environment":vs_) =
viewDoc $ header $$
vsep (map render known) $$
footer
where
header | null known = empty
| otherwise = text "Environment Variables" $$
text "====================="
footer | null unknown = empty
| otherwise = text "" $$
text ("Unknown environment variables: "
++ intercalate ", " unknown)
render (ks, ds) = text (andClauses ks ++ ":") $$
vcat [ text (" " ++ d) | d <- ds ]
(unknown, known) = case map (map toUpper) vs_ of
[] -> ([], environmentHelp)
vs -> (nub *** (nub . concat)) . partitionEithers $
map doLookup vs
doLookup v = case filter ((v `elem`) . fst) environmentHelp of
[] -> Left v
es -> Right es
helpCmd _ _ [] = viewDoc $ usage commandControlList
helpCmd _ _ (cmd:args) =
case disambiguateCommands commandControlList cmd args of
Left err -> fail err
Right (cmds,as) ->
let msg = case cmds of
CommandOnly c -> getCommandHelp Nothing c
SuperCommandOnly c ->
if null as then
getCommandHelp Nothing c
else
text $ "Invalid subcommand!\n\n" ++ subusage c
SuperCommandSub c s -> getCommandHelp (Just c) s
in viewDoc $ msg
listAvailableCommands :: IO ()
listAvailableCommands =
do here <- getCurrentDirectory
is_valid <- mapM
(\(WrappedCommand c)-> withCurrentDirectory here $ commandPrereq c [])
(extractCommands commandControlList)
putStr $ unlines $ map (wrappedCommandName . fst) $
filter (isRight.snd) $
zip (extractCommands commandControlList) is_valid
putStrLn "--help"
putStrLn "--version"
putStrLn "--exact-version"
where isRight (Right _) = True
isRight _ = False
printVersion :: IO ()
printVersion = putStrLn $ "darcs version " ++ version
commandControlList :: [CommandControl]
commandControlList =
normalCommand help : TheCommands.commandControlList
environmentHelp :: [([String], [String])]
environmentHelp = [
environmentHelpHome,
environmentHelpEditor,
environmentHelpPager,
environmentHelpColor,
environmentHelpEscapeWhite,
environmentHelpEscape,
environmentHelpTmpdir,
environmentHelpKeepTmpdir,
environmentHelpEmail,
environmentHelpSendmail,
environmentHelpLocks,
environmentHelpSsh,
environmentHelpScp,
environmentHelpSshPort,
environmentHelpProxy,
environmentHelpProxyPassword,
environmentHelpTimeout]
manpageLines :: [String]
manpageLines = [
".TH DARCS 1 \"" ++ version ++ "\"",
".SH NAME",
"darcs \\- an advanced revision control system",
".SH SYNOPSIS",
".B darcs", ".I command", ".RI < arguments |[ options ]>...",
"",
"Where the", ".I commands", "and their respective", ".I arguments", "are",
"",
unlines synopsis,
".SH DESCRIPTION",
"Darcs is a free, open source revision control",
"system. It is:",
".TP 3", "\\(bu",
"Distributed: Every user has access to the full",
"command set, removing boundaries between server and",
"client or committer and non\\(hycommitters.",
".TP", "\\(bu",
"Interactive: Darcs is easy to learn and efficient to",
"use because it asks you questions in response to",
"simple commands, giving you choices in your work",
"flow. You can choose to record one change in a file,",
"while ignoring another. As you update from upstream,",
"you can review each patch name, even the full `diff'",
"for interesting patches.",
".TP", "\\(bu",
"Smart: Originally developed by physicist David",
"Roundy, darcs is based on a unique algebra of",
"patches.",
"This smartness lets you respond to changing demands",
"in ways that would otherwise not be possible. Learn",
"more about spontaneous branches with darcs.",
".SH OPTIONS",
"Different options are accepted by different Darcs commands.",
"Each command's most important options are listed in the",
".B COMMANDS",
"section. For a full list of all options accepted by",
"a particular command, run `darcs", ".I command", "\\-\\-help'.",
".SS " ++ escape (unlines helpOnMatchers),
".SH COMMANDS",
unlines commands,
unlines environment,
".SH FILES",
unlines prefFiles,
".SH BUGS",
"At http://bugs.darcs.net/ you can find a list of known",
"bugs in Darcs. Unknown bugs can be reported at that",
"site (after creating an account) or by emailing the",
"report to bugs@darcs.net.",
".SH SEE ALSO",
"The Darcs website provides a lot of additional information.",
"It can be found at http://darcs.net/",
".SH LICENSE",
"Darcs is free software; you can redistribute it and/or modify",
"it under the terms of the GNU General Public License as published by",
"the Free Software Foundation; either version 2, or (at your option)",
"any later version." ]
where
synopsis :: [String]
synopsis = foldl iter [] commandControlList
where iter :: [String] -> CommandControl -> [String]
iter acc (GroupName _) = acc
iter acc (HiddenCommand _) = acc
iter acc (CommandData (WrappedCommand c@SuperCommand {})) =
acc ++ concatMap
(render (commandName c ++ " "))
(extractCommands (commandSubCommands c))
iter acc (CommandData c) = acc ++ render "" c
render :: String -> WrappedCommand -> [String]
render prefix (WrappedCommand c) =
[".B darcs " ++ prefix ++ commandName c] ++
map mangle_args (commandExtraArgHelp c) ++
[".br"]
commands :: [String]
commands = foldl iter [] commandControlList
where iter :: [String] -> CommandControl -> [String]
iter acc (GroupName x) = acc ++ [".SS \"" ++ x ++ "\""]
iter acc (HiddenCommand _) = acc
iter acc (CommandData (WrappedCommand c@SuperCommand {})) =
acc ++ concatMap
(render (commandName c ++ " "))
(extractCommands (commandSubCommands c))
iter acc (CommandData c) = acc ++ render "" c
render :: String -> WrappedCommand -> [String]
render prefix (WrappedCommand c) =
[".B darcs " ++ prefix ++ commandName c] ++
map mangle_args (commandExtraArgHelp c) ++
[".RS 4", escape $ commandHelp c, ".RE"]
mangle_args :: String -> String
mangle_args s =
".RI " ++ unwords (map show (groupBy cmp $ map toLower $ gank s))
where cmp x y = not $ xor (isAlphaNum x) (isAlphaNum y)
xor x y = (x && not y) || (y && not x)
gank (' ':'o':'r':' ':xs) = '|' : gank xs
gank (x:xs) = x : gank xs
gank [] = []
environment :: [String]
environment = ".SH ENVIRONMENT" : concat
[(".SS \"" ++ andClauses ks ++ "\"") : map escape ds
| (ks, ds) <- environmentHelp]
escape :: String -> String
escape = minus . bs
where
minus = replace "-" "\\-"
bs = replace "\\" "\\\\"
replace :: Eq a => [a] -> [a] -> [a] -> [a]
replace _ _ [] = []
replace find repl s =
if find `isPrefixOf` s
then repl ++ replace find repl (drop (length find) s)
else head s : replace find repl (tail s)
prefFiles = concatMap go prefsFilesHelp
where go (f,h) = [".SS \"_darcs/prefs/" ++ f ++ "\"", escape h]
markdownLines :: [String]
markdownLines =
[ "# Commands", ""
, unlines commands
, "# Patterns"
, "", unlines helpOnMatchers
, "# Configuration"
, "", unlines prefFiles
, "# Environment variables"
, "", unlines environment ]
where
prefFiles = concatMap go prefsFilesHelp
where go (f,h) = ["## `_darcs/prefs/" ++ f ++ "`", "", h]
environment :: [String]
environment = intercalate [""]
[ renderEnv ks ds | (ks, ds) <- environmentHelp ]
where
renderEnv k d = ("## " ++ (intercalate ", " k)) : "" : d
commands :: [String]
commands = foldl iter [] commandControlList
iter :: [String] -> CommandControl -> [String]
iter acc (GroupName x) = acc ++ ["## " ++ x, ""]
iter acc (HiddenCommand _) = acc
iter acc (CommandData (WrappedCommand c@SuperCommand {})) =
acc ++ concatMap
(render (commandName c ++ " "))
(extractCommands (commandSubCommands c))
iter acc (CommandData c) = acc ++ render "" c
render :: String -> WrappedCommand -> [String]
render prefix (WrappedCommand c) =
[ "### " ++ prefix ++ commandName c
, "", "darcs " ++ prefix ++ commandName c ++ " [OPTION]... " ++
unwords (commandExtraArgHelp c)
, "", commandDescription c
, "", commandHelp c
, "Options:", optionsMarkdown $ commandBasicOptions c
, if null opts2 then ""
else unlines ["Advanced Options:", optionsMarkdown opts2]
]
where opts2 = commandAdvancedOptions c
environmentHelpEditor :: ([String], [String])
environmentHelpEditor = (["DARCS_EDITOR", "VISUAL", "EDITOR"],[
"To edit a patch description of email comment, Darcs will invoke an",
"external editor. Your preferred editor can be set as any of the",
"environment variables $DARCS_EDITOR, $VISUAL or $EDITOR.",
"If none of these are set, nano is used. If nano crashes or is not",
"found in your PATH, vi, emacs, emacs -nw and (on Windows) edit are",
"each tried in turn."])
environmentHelpPager :: ([String], [String])
environmentHelpPager = (["DARCS_PAGER", "PAGER"],[
"Darcs will invoke a pager if the output of some command is longer",
"than 20 lines. Darcs will use the pager specified by $DARCS_PAGER",
"or $PAGER. If neither are set, `less` will be used."])
environmentHelpTimeout :: ([String], [String])
environmentHelpTimeout = (["DARCS_CONNECTION_TIMEOUT"],[
"Set the maximum time in seconds that darcs allows and connection to",
"take. If the variable is not specified the default are 30 seconds.",
"This option only works with curl."])