{-# LANGUAGE OverloadedStrings #-}
module Darcs.UI.Commands.Help
( helpCmd
, commandControlList
, printVersion
, listAvailableCommands
) where
import Darcs.Prelude
import Control.Arrow ( (***) )
import Data.Char ( isAlphaNum, toLower, toUpper )
import System.Directory ( withCurrentDirectory )
import System.FilePath.Posix ( (</>) )
import Data.Either ( partitionEithers )
import Data.List ( groupBy, intercalate, lookup, nub )
import System.Exit ( exitSuccess )
import Version ( version )
import Darcs.Patch.Match ( helpOnMatchers )
import Darcs.Repository.Prefs ( environmentHelpHome, prefsDirPath, prefsFilesHelp )
import Darcs.UI.Commands
( CommandArgs(..)
, CommandControl(..)
, DarcsCommand(..)
, commandAlloptions
, commandName
, disambiguateCommands
, extractCommands
, getSubcommands
, nodefaults
, normalCommand
, withStdOpts
)
import Darcs.UI.External ( viewDoc )
import Darcs.UI.Flags ( DarcsFlag, environmentHelpEmail, environmentHelpSendmail )
import Darcs.UI.Options ( oid )
import Darcs.UI.Options.Markdown ( optionsMarkdown )
import qualified Darcs.UI.TheCommands as TheCommands
import Darcs.UI.Usage ( getCommandHelp, getSuperCommandHelp, subusage, usage )
import Darcs.Util.English ( andClauses )
import Darcs.Util.Lock
( environmentHelpKeepTmpdir
, environmentHelpLocks
, environmentHelpTmpdir
)
import Darcs.Util.Path ( AbsolutePath )
import Darcs.Util.Printer
( Doc
, empty
, formatWords
, quoted
, renderString
, text
, vcat
, vsep
, ($$)
, ($+$)
, (<+>)
)
import Darcs.Util.Printer.Color
( environmentHelpColor
, environmentHelpEscape
, environmentHelpEscapeWhite
)
import Darcs.Util.Ssh
( environmentHelpScp
, environmentHelpSsh
, environmentHelpSshPort
)
import Darcs.Util.Workaround ( getCurrentDirectory )
helpDescription :: String
helpDescription :: [Char]
helpDescription = [Char]
"Display help about darcs and darcs commands."
helpHelp :: Doc
helpHelp :: Doc
helpHelp = [[Char]] -> Doc
formatWords
[ [Char]
"Without arguments, `darcs help` prints a categorized list of darcs"
, [Char]
"commands and a short description of each one. With an extra argument,"
, [Char]
"`darcs help foo` prints detailed help about the darcs command foo."
]
unwrapTree :: [CommandControl] -> [(String, [CommandControl])]
unwrapTree :: [CommandControl] -> [([Char], [CommandControl])]
unwrapTree [CommandControl]
cs = [ (DarcsCommand -> [Char]
commandName DarcsCommand
c, DarcsCommand -> [CommandControl]
getSubcommands DarcsCommand
c) | CommandData DarcsCommand
c <- [CommandControl]
cs ]
completeArgs :: [String] -> [String]
completeArgs :: [[Char]] -> [[Char]]
completeArgs [] = (([Char], [CommandControl]) -> [Char])
-> [([Char], [CommandControl])] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map ([Char], [CommandControl]) -> [Char]
forall a b. (a, b) -> a
fst ([CommandControl] -> [([Char], [CommandControl])]
unwrapTree [CommandControl]
commandControlList) [[Char]] -> [[Char]] -> [[Char]]
forall a. [a] -> [a] -> [a]
++ [[Char]]
extraArgs where
extraArgs :: [[Char]]
extraArgs = [ [Char]
"patterns", [Char]
"preferences", [Char]
"environment", [Char]
"manpage", [Char]
"markdown" ]
completeArgs ([Char]
arg:[[Char]]
args) = [Char] -> [[Char]] -> [CommandControl] -> [[Char]]
exploreTree [Char]
arg [[Char]]
args [CommandControl]
commandControlList where
exploreTree :: [Char] -> [[Char]] -> [CommandControl] -> [[Char]]
exploreTree [Char]
cmd [[Char]]
cmds [CommandControl]
cs =
case [Char] -> [([Char], [CommandControl])] -> Maybe [CommandControl]
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup [Char]
cmd ([CommandControl] -> [([Char], [CommandControl])]
unwrapTree [CommandControl]
cs) of
Maybe [CommandControl]
Nothing -> []
Just [CommandControl]
cs' -> case [[Char]]
cmds of
[] -> (([Char], [CommandControl]) -> [Char])
-> [([Char], [CommandControl])] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map ([Char], [CommandControl]) -> [Char]
forall a b. (a, b) -> a
fst ([CommandControl] -> [([Char], [CommandControl])]
unwrapTree [CommandControl]
cs')
[Char]
sub:[[Char]]
cmds' -> [Char] -> [[Char]] -> [CommandControl] -> [[Char]]
exploreTree [Char]
sub [[Char]]
cmds' [CommandControl]
cs'
help :: DarcsCommand
help :: DarcsCommand
help = DarcsCommand
{ commandProgramName :: [Char]
commandProgramName = [Char]
"darcs"
, commandName :: [Char]
commandName = [Char]
"help"
, commandHelp :: Doc
commandHelp = Doc
helpHelp
, commandDescription :: [Char]
commandDescription = [Char]
helpDescription
, commandExtraArgs :: Int
commandExtraArgs = -Int
1
, commandExtraArgHelp :: [[Char]]
commandExtraArgHelp = [[Char]
"[<DARCS_COMMAND> [DARCS_SUBCOMMAND]] "]
, commandCommand :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [[Char]] -> IO ()
commandCommand = \ (AbsolutePath, AbsolutePath)
x [DarcsFlag]
y [[Char]]
z -> (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [[Char]] -> IO ()
helpCmd (AbsolutePath, AbsolutePath)
x [DarcsFlag]
y [[Char]]
z IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO ()
forall a. IO a
exitSuccess
, commandPrereq :: [DarcsFlag] -> IO (Either [Char] ())
commandPrereq = \[DarcsFlag]
_ -> Either [Char] () -> IO (Either [Char] ())
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either [Char] () -> IO (Either [Char] ()))
-> Either [Char] () -> IO (Either [Char] ())
forall a b. (a -> b) -> a -> b
$ () -> Either [Char] ()
forall a b. b -> Either a b
Right ()
, commandCompleteArgs :: (AbsolutePath, AbsolutePath)
-> [DarcsFlag] -> [[Char]] -> IO [[Char]]
commandCompleteArgs = \(AbsolutePath, AbsolutePath)
_ [DarcsFlag]
_ -> [[Char]] -> IO [[Char]]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([[Char]] -> IO [[Char]])
-> ([[Char]] -> [[Char]]) -> [[Char]] -> IO [[Char]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Char]] -> [[Char]]
completeArgs
, commandArgdefaults :: [DarcsFlag] -> AbsolutePath -> [[Char]] -> IO [[Char]]
commandArgdefaults = [DarcsFlag] -> AbsolutePath -> [[Char]] -> IO [[Char]]
nodefaults
, commandOptions :: CommandOptions
commandOptions = DarcsOption
(Maybe StdCmdAction
-> Verbosity
-> UseCache
-> UseIndex
-> HooksConfig
-> Bool
-> Bool
-> [DarcsFlag])
(Maybe StdCmdAction
-> Verbosity
-> UseCache
-> UseIndex
-> HooksConfig
-> Bool
-> Bool
-> [DarcsFlag])
-> DarcsOption
(UseCache
-> UseIndex -> HooksConfig -> Bool -> Bool -> [DarcsFlag])
(UseCache
-> UseIndex -> HooksConfig -> Bool -> Bool -> [DarcsFlag])
-> CommandOptions
forall b c.
DarcsOption (Maybe StdCmdAction -> Verbosity -> b) c
-> DarcsOption
(UseCache
-> UseIndex -> HooksConfig -> Bool -> Bool -> [DarcsFlag])
b
-> CommandOptions
withStdOpts DarcsOption
(Maybe StdCmdAction
-> Verbosity
-> UseCache
-> UseIndex
-> HooksConfig
-> Bool
-> Bool
-> [DarcsFlag])
(Maybe StdCmdAction
-> Verbosity
-> UseCache
-> UseIndex
-> HooksConfig
-> Bool
-> Bool
-> [DarcsFlag])
forall (d :: * -> *) f a. OptSpec d f a a
oid DarcsOption
(UseCache
-> UseIndex -> HooksConfig -> Bool -> Bool -> [DarcsFlag])
(UseCache
-> UseIndex -> HooksConfig -> Bool -> Bool -> [DarcsFlag])
forall (d :: * -> *) f a. OptSpec d f a a
oid
}
helpCmd :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
helpCmd :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [[Char]] -> IO ()
helpCmd (AbsolutePath, AbsolutePath)
_ [DarcsFlag]
_ [[Char]
"manpage"] = Doc -> IO ()
viewDoc Doc
manpage
helpCmd (AbsolutePath, AbsolutePath)
_ [DarcsFlag]
_ [[Char]
"markdown"] = Doc -> IO ()
viewDoc (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$ [Doc] -> Doc
vcat ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ ([Char] -> Doc) -> [[Char]] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map [Char] -> Doc
text [[Char]]
markdownLines
helpCmd (AbsolutePath, AbsolutePath)
_ [DarcsFlag]
_ [[Char]
"patterns"] = Doc -> IO ()
viewDoc (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$ [Doc] -> Doc
vcat ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ ([Char] -> Doc) -> [[Char]] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map [Char] -> Doc
text [[Char]]
helpOnMatchers
helpCmd (AbsolutePath, AbsolutePath)
_ [DarcsFlag]
_ [[Char]
"preferences"] =
Doc -> IO ()
viewDoc (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$ Doc
header Doc -> Doc -> Doc
$+$ [Doc] -> Doc
vcat ((([Char], [Char]) -> Doc) -> [([Char], [Char])] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map ([Char], [Char]) -> Doc
render [([Char], [Char])]
prefsFilesHelp)
where
header :: Doc
header = Doc
"Preference Files" Doc -> Doc -> Doc
$$
Doc
"================"
render :: ([Char], [Char]) -> Doc
render ([Char]
f, [Char]
h) =
let item :: [Char]
item = [Char]
prefsDirPath [Char] -> [Char] -> [Char]
</> [Char]
f in
[Char] -> Doc
text [Char]
item Doc -> Doc -> Doc
$$ [Char] -> Doc
text (Int -> Char -> [Char]
forall a. Int -> a -> [a]
replicate ([Char] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Char]
item) Char
'-') Doc -> Doc -> Doc
$$ [Char] -> Doc
text [Char]
h
helpCmd (AbsolutePath, AbsolutePath)
_ [DarcsFlag]
_ ([Char]
"environment":[[Char]]
vs_) =
Doc -> IO ()
viewDoc (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$ [Doc] -> Doc
vsep (Doc
header Doc -> [Doc] -> [Doc]
forall a. a -> [a] -> [a]
: (([[Char]], [[Char]]) -> Doc) -> [([[Char]], [[Char]])] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map ([[Char]], [[Char]]) -> Doc
render [([[Char]], [[Char]])]
known) Doc -> Doc -> Doc
$+$ Doc
footer
where
header :: Doc
header | [([[Char]], [[Char]])] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [([[Char]], [[Char]])]
known = Doc
empty
| Bool
otherwise = Doc
"Environment Variables" Doc -> Doc -> Doc
$$
Doc
"====================="
footer :: Doc
footer | [[Char]] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [[Char]]
unknown = Doc
empty
| Bool
otherwise = [Char] -> Doc
text ([Char]
"Unknown environment variables: "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [[Char]] -> [Char]
forall a. [a] -> [[a]] -> [a]
intercalate [Char]
", " [[Char]]
unknown)
render :: ([[Char]], [[Char]]) -> Doc
render ([[Char]]
ks, [[Char]]
ds) = [Char] -> Doc
text ([[Char]] -> [Char]
andClauses [[Char]]
ks [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
":") Doc -> Doc -> Doc
$$
[Doc] -> Doc
vcat [ [Char] -> Doc
text ([Char]
" " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
d) | [Char]
d <- [[Char]]
ds ]
([[Char]]
unknown, [([[Char]], [[Char]])]
known) = case ([Char] -> [Char]) -> [[Char]] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map ((Char -> Char) -> [Char] -> [Char]
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toUpper) [[Char]]
vs_ of
[] -> ([], [([[Char]], [[Char]])]
environmentHelp)
[[Char]]
vs -> ([[Char]] -> [[Char]]
forall a. Eq a => [a] -> [a]
nub ([[Char]] -> [[Char]])
-> ([[([[Char]], [[Char]])]] -> [([[Char]], [[Char]])])
-> ([[Char]], [[([[Char]], [[Char]])]])
-> ([[Char]], [([[Char]], [[Char]])])
forall b c b' c'. (b -> c) -> (b' -> c') -> (b, b') -> (c, c')
forall (a :: * -> * -> *) b c b' c'.
Arrow a =>
a b c -> a b' c' -> a (b, b') (c, c')
*** ([([[Char]], [[Char]])] -> [([[Char]], [[Char]])]
forall a. Eq a => [a] -> [a]
nub ([([[Char]], [[Char]])] -> [([[Char]], [[Char]])])
-> ([[([[Char]], [[Char]])]] -> [([[Char]], [[Char]])])
-> [[([[Char]], [[Char]])]]
-> [([[Char]], [[Char]])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[([[Char]], [[Char]])]] -> [([[Char]], [[Char]])]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat)) (([[Char]], [[([[Char]], [[Char]])]])
-> ([[Char]], [([[Char]], [[Char]])]))
-> ([Either [Char] [([[Char]], [[Char]])]]
-> ([[Char]], [[([[Char]], [[Char]])]]))
-> [Either [Char] [([[Char]], [[Char]])]]
-> ([[Char]], [([[Char]], [[Char]])])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Either [Char] [([[Char]], [[Char]])]]
-> ([[Char]], [[([[Char]], [[Char]])]])
forall a b. [Either a b] -> ([a], [b])
partitionEithers ([Either [Char] [([[Char]], [[Char]])]]
-> ([[Char]], [([[Char]], [[Char]])]))
-> [Either [Char] [([[Char]], [[Char]])]]
-> ([[Char]], [([[Char]], [[Char]])])
forall a b. (a -> b) -> a -> b
$
([Char] -> Either [Char] [([[Char]], [[Char]])])
-> [[Char]] -> [Either [Char] [([[Char]], [[Char]])]]
forall a b. (a -> b) -> [a] -> [b]
map [Char] -> Either [Char] [([[Char]], [[Char]])]
doLookup [[Char]]
vs
doLookup :: [Char] -> Either [Char] [([[Char]], [[Char]])]
doLookup [Char]
v = case (([[Char]], [[Char]]) -> Bool)
-> [([[Char]], [[Char]])] -> [([[Char]], [[Char]])]
forall a. (a -> Bool) -> [a] -> [a]
filter (([Char]
v [Char] -> [[Char]] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem`) ([[Char]] -> Bool)
-> (([[Char]], [[Char]]) -> [[Char]])
-> ([[Char]], [[Char]])
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([[Char]], [[Char]]) -> [[Char]]
forall a b. (a, b) -> a
fst) [([[Char]], [[Char]])]
environmentHelp of
[] -> [Char] -> Either [Char] [([[Char]], [[Char]])]
forall a b. a -> Either a b
Left [Char]
v
[([[Char]], [[Char]])]
es -> [([[Char]], [[Char]])] -> Either [Char] [([[Char]], [[Char]])]
forall a b. b -> Either a b
Right [([[Char]], [[Char]])]
es
helpCmd (AbsolutePath, AbsolutePath)
_ [DarcsFlag]
_ [] = Doc -> IO ()
viewDoc (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$ [CommandControl] -> Doc
usage [CommandControl]
commandControlList
helpCmd (AbsolutePath, AbsolutePath)
_ [DarcsFlag]
_ ([Char]
cmd:[[Char]]
args) =
case [CommandControl]
-> [Char] -> [[Char]] -> Either [Char] (CommandArgs, [[Char]])
disambiguateCommands [CommandControl]
commandControlList [Char]
cmd [[Char]]
args of
Left [Char]
err -> [Char] -> IO ()
forall a. [Char] -> IO a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
err
Right (CommandArgs
cmds,[[Char]]
as) ->
let msg :: Doc
msg = case CommandArgs
cmds of
CommandOnly DarcsCommand
c -> Maybe DarcsCommand -> DarcsCommand -> Doc
getCommandHelp Maybe DarcsCommand
forall a. Maybe a
Nothing DarcsCommand
c
SuperCommandOnly DarcsCommand
c ->
if [[Char]] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [[Char]]
as then
DarcsCommand -> Doc
getSuperCommandHelp DarcsCommand
c
else
Doc
"Invalid subcommand!" Doc -> Doc -> Doc
$+$ DarcsCommand -> Doc
subusage DarcsCommand
c
SuperCommandSub DarcsCommand
c DarcsCommand
s -> Maybe DarcsCommand -> DarcsCommand -> Doc
getCommandHelp (DarcsCommand -> Maybe DarcsCommand
forall a. a -> Maybe a
Just DarcsCommand
c) DarcsCommand
s
in Doc -> IO ()
viewDoc (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$ Doc
msg
listAvailableCommands :: IO ()
listAvailableCommands :: IO ()
listAvailableCommands =
do [Char]
here <- IO [Char]
getCurrentDirectory
[Either [Char] ()]
is_valid <- (DarcsCommand -> IO (Either [Char] ()))
-> [DarcsCommand] -> IO [Either [Char] ()]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM
(\DarcsCommand
c -> [Char] -> IO (Either [Char] ()) -> IO (Either [Char] ())
forall a. [Char] -> IO a -> IO a
withCurrentDirectory [Char]
here (IO (Either [Char] ()) -> IO (Either [Char] ()))
-> IO (Either [Char] ()) -> IO (Either [Char] ())
forall a b. (a -> b) -> a -> b
$ DarcsCommand -> [DarcsFlag] -> IO (Either [Char] ())
commandPrereq DarcsCommand
c [])
([CommandControl] -> [DarcsCommand]
extractCommands [CommandControl]
commandControlList)
[Char] -> IO ()
putStr ([Char] -> IO ()) -> [Char] -> IO ()
forall a b. (a -> b) -> a -> b
$ [[Char]] -> [Char]
unlines ([[Char]] -> [Char]) -> [[Char]] -> [Char]
forall a b. (a -> b) -> a -> b
$ ((DarcsCommand, Either [Char] ()) -> [Char])
-> [(DarcsCommand, Either [Char] ())] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map (DarcsCommand -> [Char]
commandName (DarcsCommand -> [Char])
-> ((DarcsCommand, Either [Char] ()) -> DarcsCommand)
-> (DarcsCommand, Either [Char] ())
-> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DarcsCommand, Either [Char] ()) -> DarcsCommand
forall a b. (a, b) -> a
fst) ([(DarcsCommand, Either [Char] ())] -> [[Char]])
-> [(DarcsCommand, Either [Char] ())] -> [[Char]]
forall a b. (a -> b) -> a -> b
$
((DarcsCommand, Either [Char] ()) -> Bool)
-> [(DarcsCommand, Either [Char] ())]
-> [(DarcsCommand, Either [Char] ())]
forall a. (a -> Bool) -> [a] -> [a]
filter (Either [Char] () -> Bool
forall {a} {b}. Either a b -> Bool
isRight(Either [Char] () -> Bool)
-> ((DarcsCommand, Either [Char] ()) -> Either [Char] ())
-> (DarcsCommand, Either [Char] ())
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(DarcsCommand, Either [Char] ()) -> Either [Char] ()
forall a b. (a, b) -> b
snd) ([(DarcsCommand, Either [Char] ())]
-> [(DarcsCommand, Either [Char] ())])
-> [(DarcsCommand, Either [Char] ())]
-> [(DarcsCommand, Either [Char] ())]
forall a b. (a -> b) -> a -> b
$
[DarcsCommand]
-> [Either [Char] ()] -> [(DarcsCommand, Either [Char] ())]
forall a b. [a] -> [b] -> [(a, b)]
zip ([CommandControl] -> [DarcsCommand]
extractCommands [CommandControl]
commandControlList) [Either [Char] ()]
is_valid
[Char] -> IO ()
putStrLn [Char]
"--help"
[Char] -> IO ()
putStrLn [Char]
"--version"
[Char] -> IO ()
putStrLn [Char]
"--exact-version"
where isRight :: Either a b -> Bool
isRight (Right b
_) = Bool
True
isRight Either a b
_ = Bool
False
printVersion :: IO ()
printVersion :: IO ()
printVersion = [Char] -> IO ()
putStrLn ([Char] -> IO ()) -> [Char] -> IO ()
forall a b. (a -> b) -> a -> b
$ [Char]
"darcs version " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
version
commandControlList :: [CommandControl]
commandControlList :: [CommandControl]
commandControlList =
DarcsCommand -> CommandControl
normalCommand DarcsCommand
help CommandControl -> [CommandControl] -> [CommandControl]
forall a. a -> [a] -> [a]
: [CommandControl]
TheCommands.commandControlList
environmentHelp :: [([String], [String])]
environmentHelp :: [([[Char]], [[Char]])]
environmentHelp = [
([[Char]], [[Char]])
environmentHelpHome,
([[Char]], [[Char]])
environmentHelpEditor,
([[Char]], [[Char]])
environmentHelpPager,
([[Char]], [[Char]])
environmentHelpColor,
([[Char]], [[Char]])
environmentHelpEscapeWhite,
([[Char]], [[Char]])
environmentHelpEscape,
([[Char]], [[Char]])
environmentHelpTmpdir,
([[Char]], [[Char]])
environmentHelpKeepTmpdir,
([[Char]], [[Char]])
environmentHelpEmail,
([[Char]], [[Char]])
environmentHelpSendmail,
([[Char]], [[Char]])
environmentHelpLocks,
([[Char]], [[Char]])
environmentHelpSsh,
([[Char]], [[Char]])
environmentHelpScp,
([[Char]], [[Char]])
environmentHelpSshPort,
([[Char]], [[Char]])
environmentHelpTimeout]
manpage :: Doc
manpage :: Doc
manpage = [Doc] -> Doc
vcat [
Doc
".TH DARCS 1" Doc -> Doc -> Doc
<+> [Char] -> Doc
quoted [Char]
version,
Doc
".SH NAME",
Doc
"darcs \\- an advanced revision control system",
Doc
".SH SYNOPSIS",
Doc
".B darcs", Doc
".I command", Doc
".RI < arguments |[ options ]>...",
Doc
"",
Doc
"Where the", Doc
".I commands", Doc
"and their respective", Doc
".I arguments", Doc
"are",
Doc
"",
Doc
synopsis,
Doc
".SH DESCRIPTION",
Doc
description,
Doc
".SH OPTIONS",
Doc
"Different options are accepted by different Darcs commands.",
Doc
"Each command's most important options are listed in the",
Doc
".B COMMANDS",
Doc
"section. For a full list of all options accepted by",
Doc
"a particular command, run `darcs", Doc
".I command", Doc
"\\-\\-help'.",
Doc
".SS " Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> [Doc] -> Doc
vcat (([Char] -> Doc) -> [[Char]] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map [Char] -> Doc
text [[Char]]
helpOnMatchers),
Doc
".SH COMMANDS",
Doc
commands,
Doc
".SH ENVIRONMENT",
Doc
environment,
Doc
".SH FILES",
Doc
prefFiles,
Doc
".SH BUGS",
Doc
"At http://bugs.darcs.net/ you can find a list of known",
Doc
"bugs in Darcs. Unknown bugs can be reported at that",
Doc
"site (after creating an account) or by emailing the",
Doc
"report to bugs@darcs.net.",
Doc
".SH SEE ALSO",
Doc
"The Darcs website provides a lot of additional information.",
Doc
"It can be found at http://darcs.net/",
Doc
".SH LICENSE",
Doc
"Darcs is free software; you can redistribute it and/or modify",
Doc
"it under the terms of the GNU General Public License as published by",
Doc
"the Free Software Foundation; either version 2, or (at your option)",
Doc
"any later version." ]
where
synopsis :: Doc
synopsis :: Doc
synopsis = (Doc -> CommandControl -> Doc) -> Doc -> [CommandControl] -> Doc
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl Doc -> CommandControl -> Doc
iter Doc
forall a. Monoid a => a
mempty [CommandControl]
commandControlList
where iter :: Doc -> CommandControl -> Doc
iter :: Doc -> CommandControl -> Doc
iter Doc
acc (GroupName [Char]
_) = Doc
acc
iter Doc
acc (HiddenCommand DarcsCommand
_) = Doc
acc
iter Doc
acc (CommandData (c :: DarcsCommand
c@SuperCommand {})) =
Doc
acc Doc -> Doc -> Doc
$$ [Doc] -> Doc
vcat ((DarcsCommand -> Doc) -> [DarcsCommand] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map
([Char] -> DarcsCommand -> Doc
render (DarcsCommand -> [Char]
commandName DarcsCommand
c [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" "))
([CommandControl] -> [DarcsCommand]
extractCommands (DarcsCommand -> [CommandControl]
commandSubCommands DarcsCommand
c)))
iter Doc
acc (CommandData DarcsCommand
c) = Doc
acc Doc -> Doc -> Doc
$$ [Char] -> DarcsCommand -> Doc
render [Char]
"" DarcsCommand
c
render :: String -> DarcsCommand -> Doc
render :: [Char] -> DarcsCommand -> Doc
render [Char]
prefix DarcsCommand
c =
Doc
".B darcs " Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> [Char] -> Doc
text [Char]
prefix Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> [Char] -> Doc
text (DarcsCommand -> [Char]
commandName DarcsCommand
c) Doc -> Doc -> Doc
$$
[Doc] -> Doc
vcat (([Char] -> Doc) -> [[Char]] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map ([Char] -> Doc
text([Char] -> Doc) -> ([Char] -> [Char]) -> [Char] -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
.[Char] -> [Char]
mangle_args) (DarcsCommand -> [[Char]]
commandExtraArgHelp DarcsCommand
c)) Doc -> Doc -> Doc
$$
Doc
".br"
commands :: Doc
commands :: Doc
commands = [Doc] -> Doc
vsep ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ (CommandControl -> Doc) -> [CommandControl] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map CommandControl -> Doc
iter [CommandControl]
commandControlList
where iter :: CommandControl -> Doc
iter :: CommandControl -> Doc
iter (GroupName [Char]
x) = Doc
".SS" Doc -> Doc -> Doc
<+> [Char] -> Doc
quoted [Char]
x
iter (HiddenCommand DarcsCommand
_) = Doc
forall a. Monoid a => a
mempty
iter (CommandData (c :: DarcsCommand
c@SuperCommand {})) =
[Doc] -> Doc
vcat
[ Doc
".B darcs " Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> [Char] -> Doc
text (DarcsCommand -> [Char]
commandName DarcsCommand
c)
, [Char] -> Doc
text ([Char] -> [Char]
mangle_args [Char]
"subcommand")
, Doc
".RS 4"
, DarcsCommand -> Doc
commandHelp DarcsCommand
c
, Doc
".RE"
]
Doc -> Doc -> Doc
$+$
[Doc] -> Doc
vsep ((DarcsCommand -> Doc) -> [DarcsCommand] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map ([Char] -> DarcsCommand -> Doc
render (DarcsCommand -> [Char]
commandName DarcsCommand
c [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" "))
([CommandControl] -> [DarcsCommand]
extractCommands (DarcsCommand -> [CommandControl]
commandSubCommands DarcsCommand
c)))
iter (CommandData DarcsCommand
c) = [Char] -> DarcsCommand -> Doc
render [Char]
"" DarcsCommand
c
render :: String -> DarcsCommand -> Doc
render :: [Char] -> DarcsCommand -> Doc
render [Char]
prefix DarcsCommand
c =
[Doc] -> Doc
vcat
[ Doc
".B darcs " Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> [Char] -> Doc
text [Char]
prefix Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> [Char] -> Doc
text (DarcsCommand -> [Char]
commandName DarcsCommand
c)
, [Doc] -> Doc
vcat (([Char] -> Doc) -> [[Char]] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map ([Char] -> Doc
text([Char] -> Doc) -> ([Char] -> [Char]) -> [Char] -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
.[Char] -> [Char]
mangle_args) (DarcsCommand -> [[Char]]
commandExtraArgHelp DarcsCommand
c))
, Doc
".RS 4"
, DarcsCommand -> Doc
commandHelp DarcsCommand
c
, Doc
".RE"
]
mangle_args :: String -> String
mangle_args :: [Char] -> [Char]
mangle_args [Char]
s =
[Char]
".RI " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
unwords (([Char] -> [Char]) -> [[Char]] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map [Char] -> [Char]
forall a. Show a => a -> [Char]
show ((Char -> Char -> Bool) -> [Char] -> [[Char]]
forall a. (a -> a -> Bool) -> [a] -> [[a]]
groupBy Char -> Char -> Bool
cmp ([Char] -> [[Char]]) -> [Char] -> [[Char]]
forall a b. (a -> b) -> a -> b
$ (Char -> Char) -> [Char] -> [Char]
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower ([Char] -> [Char]) -> [Char] -> [Char]
forall a b. (a -> b) -> a -> b
$ [Char] -> [Char]
gank [Char]
s))
where cmp :: Char -> Char -> Bool
cmp Char
x Char
y = Char -> Bool
isAlphaNum Char
x Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Char -> Bool
isAlphaNum Char
y
gank :: [Char] -> [Char]
gank (Char
' ':Char
'o':Char
'r':Char
' ':[Char]
xs) = Char
'|' Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: [Char] -> [Char]
gank [Char]
xs
gank (Char
x:[Char]
xs) = Char
x Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: [Char] -> [Char]
gank [Char]
xs
gank [] = []
environment :: Doc
environment :: Doc
environment = [Doc] -> Doc
vcat ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ [[Doc]] -> [Doc]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[(Doc
".SS" Doc -> Doc -> Doc
<+> [Char] -> Doc
quoted ([[Char]] -> [Char]
andClauses [[Char]]
ks)) Doc -> [Doc] -> [Doc]
forall a. a -> [a] -> [a]
: ([Char] -> Doc) -> [[Char]] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map [Char] -> Doc
text [[Char]]
ds
| ([[Char]]
ks, [[Char]]
ds) <- [([[Char]], [[Char]])]
environmentHelp]
prefFiles :: Doc
prefFiles :: Doc
prefFiles = [Doc] -> Doc
vcat ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ (([Char], [Char]) -> Doc) -> [([Char], [Char])] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map ([Char], [Char]) -> Doc
go [([Char], [Char])]
prefsFilesHelp
where go :: ([Char], [Char]) -> Doc
go ([Char]
f,[Char]
h) = Doc
".SS" Doc -> Doc -> Doc
<+> [Char] -> Doc
quoted([Char]
prefsDirPath [Char] -> [Char] -> [Char]
</> [Char]
f) Doc -> Doc -> Doc
$$ [Char] -> Doc
text [Char]
h
description :: Doc
description = [Doc] -> Doc
vcat
[ Doc
"Unlike conventional revision control systems, Darcs is based on tracking"
, Doc
"changes, rather than versions: it can and does automatically re-order"
, Doc
"independent changes when needed. This means that in Darcs the state of"
, Doc
"a repository should be regarded as a"
, Doc
".I set of patches"
, Doc
"rather than a"
, Doc
".I sequence of versions."
, Doc
""
, Doc
"Another distinguishing feature of darcs is that most commands are"
, Doc
"interactive by default. For instance, `darcs record' (the equivalent of"
, Doc
"what is usually called `commit') presents you with"
, Doc
"each unrecorded change and asks you whether it should be included in"
, Doc
"the patch to be recorded. Similarly, `darcs push' and `darcs pull'"
, Doc
"present you with each patch, allowing you to select which patches to"
, Doc
"push or pull."
]
markdownLines :: [String]
markdownLines :: [[Char]]
markdownLines =
[ [Char]
"# Commands", [Char]
""
, [[Char]] -> [Char]
unlines [[Char]]
commands
, [Char]
"# Patterns"
, [Char]
"", [[Char]] -> [Char]
unlines [[Char]]
helpOnMatchers
, [Char]
"# Configuration"
, [Char]
"", [[Char]] -> [Char]
unlines [[Char]]
prefFiles
, [Char]
"# Environment variables"
, [Char]
"", [[Char]] -> [Char]
unlines [[Char]]
environment ]
where
prefFiles :: [[Char]]
prefFiles = (([Char], [Char]) -> [[Char]]) -> [([Char], [Char])] -> [[Char]]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ([Char], [Char]) -> [[Char]]
go [([Char], [Char])]
prefsFilesHelp
where go :: ([Char], [Char]) -> [[Char]]
go ([Char]
f,[Char]
h) = [[Char]
"## `" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
prefsDirPath [Char] -> [Char] -> [Char]
</> [Char]
f [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"`", [Char]
"", [Char]
h]
environment :: [String]
environment :: [[Char]]
environment = [[Char]] -> [[[Char]]] -> [[Char]]
forall a. [a] -> [[a]] -> [a]
intercalate [[Char]
""]
[ [[Char]] -> [[Char]] -> [[Char]]
renderEnv [[Char]]
ks [[Char]]
ds | ([[Char]]
ks, [[Char]]
ds) <- [([[Char]], [[Char]])]
environmentHelp ]
where
renderEnv :: [[Char]] -> [[Char]] -> [[Char]]
renderEnv [[Char]]
k [[Char]]
d = ([Char]
"## " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ ([Char] -> [[Char]] -> [Char]
forall a. [a] -> [[a]] -> [a]
intercalate [Char]
", " [[Char]]
k)) [Char] -> [[Char]] -> [[Char]]
forall a. a -> [a] -> [a]
: [Char]
"" [Char] -> [[Char]] -> [[Char]]
forall a. a -> [a] -> [a]
: [[Char]]
d
commands :: [String]
commands :: [[Char]]
commands = ([[Char]] -> CommandControl -> [[Char]])
-> [[Char]] -> [CommandControl] -> [[Char]]
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl [[Char]] -> CommandControl -> [[Char]]
iter [] [CommandControl]
commandControlList
iter :: [String] -> CommandControl -> [String]
iter :: [[Char]] -> CommandControl -> [[Char]]
iter [[Char]]
acc (GroupName [Char]
x) = [[Char]]
acc [[Char]] -> [[Char]] -> [[Char]]
forall a. [a] -> [a] -> [a]
++ [[Char]
"## " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
x, [Char]
""]
iter [[Char]]
acc (HiddenCommand DarcsCommand
_) = [[Char]]
acc
iter [[Char]]
acc (CommandData (c :: DarcsCommand
c@SuperCommand {})) =
[[Char]]
acc [[Char]] -> [[Char]] -> [[Char]]
forall a. [a] -> [a] -> [a]
++ (DarcsCommand -> [[Char]]) -> [DarcsCommand] -> [[Char]]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap
([Char] -> DarcsCommand -> [[Char]]
render (DarcsCommand -> [Char]
commandName DarcsCommand
c [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" "))
([CommandControl] -> [DarcsCommand]
extractCommands (DarcsCommand -> [CommandControl]
commandSubCommands DarcsCommand
c))
iter [[Char]]
acc (CommandData DarcsCommand
c) = [[Char]]
acc [[Char]] -> [[Char]] -> [[Char]]
forall a. [a] -> [a] -> [a]
++ [Char] -> DarcsCommand -> [[Char]]
render [Char]
"" DarcsCommand
c
render :: String -> DarcsCommand -> [String]
render :: [Char] -> DarcsCommand -> [[Char]]
render [Char]
prefix DarcsCommand
c =
[ [Char]
"### " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
prefix [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ DarcsCommand -> [Char]
commandName DarcsCommand
c
, [Char]
"", [Char]
"darcs " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
prefix [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ DarcsCommand -> [Char]
commandName DarcsCommand
c [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" [OPTION]... " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++
[[Char]] -> [Char]
unwords (DarcsCommand -> [[Char]]
commandExtraArgHelp DarcsCommand
c)
, [Char]
"", DarcsCommand -> [Char]
commandDescription DarcsCommand
c
, [Char]
"", Doc -> [Char]
renderString (DarcsCommand -> Doc
commandHelp DarcsCommand
c)
, [Char]
"Options:", [DarcsOptDescr DarcsFlag] -> [Char]
forall f. [DarcsOptDescr f] -> [Char]
optionsMarkdown [DarcsOptDescr DarcsFlag]
bopts
, if [DarcsOptDescr DarcsFlag] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [DarcsOptDescr DarcsFlag]
aopts then [Char]
""
else [[Char]] -> [Char]
unlines [[Char]
"Advanced Options:", [DarcsOptDescr DarcsFlag] -> [Char]
forall f. [DarcsOptDescr f] -> [Char]
optionsMarkdown [DarcsOptDescr DarcsFlag]
aopts]
]
where ([DarcsOptDescr DarcsFlag]
bopts, [DarcsOptDescr DarcsFlag]
aopts) = DarcsCommand
-> ([DarcsOptDescr DarcsFlag], [DarcsOptDescr DarcsFlag])
commandAlloptions DarcsCommand
c
environmentHelpEditor :: ([String], [String])
environmentHelpEditor :: ([[Char]], [[Char]])
environmentHelpEditor = ([[Char]
"DARCS_EDITOR", [Char]
"VISUAL", [Char]
"EDITOR"],[
[Char]
"To edit a patch description of email comment, Darcs will invoke an",
[Char]
"external editor. Your preferred editor can be set as any of the",
[Char]
"environment variables $DARCS_EDITOR, $VISUAL or $EDITOR.",
[Char]
"If none of these are set, nano is used. If nano crashes or is not",
[Char]
"found in your PATH, vi, emacs, emacs -nw and (on Windows) edit are",
[Char]
"each tried in turn."])
environmentHelpPager :: ([String], [String])
= ([[Char]
"DARCS_PAGER", [Char]
"PAGER"],[
[Char]
"Darcs will invoke a pager if the output of some command is longer",
[Char]
"than 20 lines. Darcs will use the pager specified by $DARCS_PAGER",
[Char]
"or $PAGER. If neither are set, `less` will be used. Set $DARCS_PAGER",
[Char]
"- or $PAGER if the former is not set - to the empty string in order not",
[Char]
"to use a pager."])
environmentHelpTimeout :: ([String], [String])
environmentHelpTimeout :: ([[Char]], [[Char]])
environmentHelpTimeout = ([[Char]
"DARCS_CONNECTION_TIMEOUT"],[
[Char]
"Set the maximum time in seconds that darcs allows and connection to",
[Char]
"take. If the variable is not specified the default are 30 seconds.",
[Char]
"This option only works with curl."])