--  Copyright (C) 2002-2004 David Roundy
--
--  This program 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.
--
--  This program is distributed in the hope that it will be useful,
--  but WITHOUT ANY WARRANTY; without even the implied warranty of
--  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
--  GNU General Public License for more details.
--
--  You should have received a copy of the GNU General Public License
--  along with this program; see the file COPYING.  If not, write to
--  the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor,
--  Boston, MA 02110-1301, USA.

{-# 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 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, prefsFilesHelp )

import Darcs.UI.Commands
    ( CommandArgs(..)
    , CommandControl(..)
    , DarcsCommand(..)
    , commandName
    , disambiguateCommands
    , extractCommands
    , getSubcommands
    , nodefaults
    , normalCommand
    )
import Darcs.UI.External ( viewDoc )
import Darcs.UI.Flags ( DarcsFlag, environmentHelpEmail, environmentHelpSendmail )
import Darcs.UI.Options ( defaultFlags, ocheck, 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.Download ( environmentHelpProxy, environmentHelpProxyPassword )
import Darcs.Util.English ( andClauses )
import Darcs.Util.File ( withCurrentDirectory )
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 :: String
helpDescription = String
"Display help about darcs and darcs commands."

helpHelp :: Doc
helpHelp :: Doc
helpHelp = [String] -> Doc
formatWords
  [ String
"Without arguments, `darcs help` prints a categorized list of darcs"
  , String
"commands and a short description of each one.  With an extra argument,"
  , String
"`darcs help foo` prints detailed help about the darcs command foo."
  ]

-- | Starting from a list of 'CommandControl's, unwrap one level
-- to get a list of command names together with their subcommands.
unwrapTree :: [CommandControl] -> [(String, [CommandControl])]
unwrapTree :: [CommandControl] -> [(String, [CommandControl])]
unwrapTree [CommandControl]
cs = [ (DarcsCommand -> String
commandName DarcsCommand
c, DarcsCommand -> [CommandControl]
getSubcommands DarcsCommand
c) | CommandData DarcsCommand
c <- [CommandControl]
cs ]

-- | Given a list of (normal) arguments to the help command, produce a list
-- of possible completions for the next (normal) argument.
completeArgs :: [String] -> [String]
completeArgs :: [String] -> [String]
completeArgs [] = ((String, [CommandControl]) -> String)
-> [(String, [CommandControl])] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String, [CommandControl]) -> String
forall a b. (a, b) -> a
fst ([CommandControl] -> [(String, [CommandControl])]
unwrapTree [CommandControl]
commandControlList) [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
extraArgs where
  extraArgs :: [String]
extraArgs = [ String
"patterns", String
"preferences", String
"environment", String
"manpage", String
"markdown" ]
completeArgs (String
arg:[String]
args) = String -> [String] -> [CommandControl] -> [String]
exploreTree String
arg [String]
args [CommandControl]
commandControlList where
  exploreTree :: String -> [String] -> [CommandControl] -> [String]
exploreTree String
cmd [String]
cmds [CommandControl]
cs =
    case String -> [(String, [CommandControl])] -> Maybe [CommandControl]
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup String
cmd ([CommandControl] -> [(String, [CommandControl])]
unwrapTree [CommandControl]
cs) of
      Maybe [CommandControl]
Nothing -> []
      Just [CommandControl]
cs' -> case [String]
cmds of
        [] -> ((String, [CommandControl]) -> String)
-> [(String, [CommandControl])] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String, [CommandControl]) -> String
forall a b. (a, b) -> a
fst ([CommandControl] -> [(String, [CommandControl])]
unwrapTree [CommandControl]
cs')
        String
sub:[String]
cmds' -> String -> [String] -> [CommandControl] -> [String]
exploreTree String
sub [String]
cmds' [CommandControl]
cs'

help :: DarcsCommand
help :: DarcsCommand
help = DarcsCommand :: String
-> String
-> Doc
-> String
-> Int
-> [String]
-> ((AbsolutePath, AbsolutePath)
    -> [DarcsFlag] -> [String] -> IO ())
-> ([DarcsFlag] -> IO (Either String ()))
-> ((AbsolutePath, AbsolutePath)
    -> [DarcsFlag] -> [String] -> IO [String])
-> ([DarcsFlag] -> AbsolutePath -> [String] -> IO [String])
-> [DarcsOptDescr DarcsFlag]
-> [DarcsOptDescr DarcsFlag]
-> [DarcsFlag]
-> ([DarcsFlag] -> [String])
-> DarcsCommand
DarcsCommand
    { commandProgramName :: String
commandProgramName = String
"darcs"
    , commandName :: String
commandName = String
"help"
    , commandHelp :: Doc
commandHelp = Doc
helpHelp
    , commandDescription :: String
commandDescription = String
helpDescription
    , commandExtraArgs :: Int
commandExtraArgs = -Int
1
    , commandExtraArgHelp :: [String]
commandExtraArgHelp = [String
"[<DARCS_COMMAND> [DARCS_SUBCOMMAND]]  "]
    , commandCommand :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
commandCommand = \ (AbsolutePath, AbsolutePath)
x [DarcsFlag]
y [String]
z -> (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
helpCmd (AbsolutePath, AbsolutePath)
x [DarcsFlag]
y [String]
z IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO ()
forall a. IO a
exitSuccess
    , commandPrereq :: [DarcsFlag] -> IO (Either String ())
commandPrereq = \[DarcsFlag]
_ -> Either String () -> IO (Either String ())
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String () -> IO (Either String ()))
-> Either String () -> IO (Either String ())
forall a b. (a -> b) -> a -> b
$ () -> Either String ()
forall a b. b -> Either a b
Right ()
    , commandCompleteArgs :: (AbsolutePath, AbsolutePath)
-> [DarcsFlag] -> [String] -> IO [String]
commandCompleteArgs = \(AbsolutePath, AbsolutePath)
_ [DarcsFlag]
_ -> [String] -> IO [String]
forall (m :: * -> *) a. Monad m => a -> m a
return ([String] -> IO [String])
-> ([String] -> [String]) -> [String] -> IO [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> [String]
completeArgs
    , commandArgdefaults :: [DarcsFlag] -> AbsolutePath -> [String] -> IO [String]
commandArgdefaults = [DarcsFlag] -> AbsolutePath -> [String] -> IO [String]
nodefaults
    , commandAdvancedOptions :: [DarcsOptDescr DarcsFlag]
commandAdvancedOptions = []
    , commandBasicOptions :: [DarcsOptDescr DarcsFlag]
commandBasicOptions = []
    , commandDefaults :: [DarcsFlag]
commandDefaults = OptSpec Any DarcsFlag [DarcsFlag] [DarcsFlag] -> [DarcsFlag]
forall (d :: * -> *) f b. OptSpec d f [f] b -> [f]
defaultFlags OptSpec Any DarcsFlag [DarcsFlag] [DarcsFlag]
forall (d :: * -> *) f a. OptSpec d f a a
oid
    , commandCheckOptions :: [DarcsFlag] -> [String]
commandCheckOptions = OptSpec Any DarcsFlag Any Any -> [DarcsFlag] -> [String]
forall (d :: * -> *) f a b. OptSpec d f a b -> [f] -> [String]
ocheck OptSpec Any DarcsFlag Any Any
forall (d :: * -> *) f a. OptSpec d f a a
oid
    }

helpCmd :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
helpCmd :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
helpCmd (AbsolutePath, AbsolutePath)
_ [DarcsFlag]
_ [String
"manpage"] = Doc -> IO ()
viewDoc Doc
manpage
helpCmd (AbsolutePath, AbsolutePath)
_ [DarcsFlag]
_ [String
"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
$ (String -> Doc) -> [String] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map String -> Doc
text [String]
markdownLines
helpCmd (AbsolutePath, AbsolutePath)
_ [DarcsFlag]
_ [String
"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
$ (String -> Doc) -> [String] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map String -> Doc
text [String]
helpOnMatchers
helpCmd (AbsolutePath, AbsolutePath)
_ [DarcsFlag]
_ [String
"preferences"] =
    Doc -> IO ()
viewDoc (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$ Doc
header Doc -> Doc -> Doc
$+$ [Doc] -> Doc
vcat (((String, String) -> Doc) -> [(String, String)] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (String, String) -> Doc
render [(String, String)]
prefsFilesHelp)
  where
    header :: Doc
header = Doc
"Preference Files" Doc -> Doc -> Doc
$$
             Doc
"================"
    render :: (String, String) -> Doc
render (String
f, String
h) =
      let item :: String
item = String
"_darcs/prefs/" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
f in
        String -> Doc
text String
item Doc -> Doc -> Doc
$$ String -> Doc
text (Int -> Char -> String
forall a. Int -> a -> [a]
replicate (String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
item) Char
'-') Doc -> Doc -> Doc
$$ String -> Doc
text String
h
helpCmd (AbsolutePath, AbsolutePath)
_ [DarcsFlag]
_ (String
"environment":[String]
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]
: (([String], [String]) -> Doc) -> [([String], [String])] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map ([String], [String]) -> Doc
render [([String], [String])]
known) Doc -> Doc -> Doc
$+$ Doc
footer
  where
    header :: Doc
header | [([String], [String])] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [([String], [String])]
known = Doc
empty
           | Bool
otherwise = Doc
"Environment Variables" Doc -> Doc -> Doc
$$
                         Doc
"====================="

    footer :: Doc
footer | [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
unknown = Doc
empty
           | Bool
otherwise = String -> Doc
text (String
"Unknown environment variables: "
                               String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
", " [String]
unknown)

    render :: ([String], [String]) -> Doc
render ([String]
ks, [String]
ds) = String -> Doc
text ([String] -> String
andClauses [String]
ks String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
":") Doc -> Doc -> Doc
$$
                      [Doc] -> Doc
vcat [ String -> Doc
text (String
"  " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
d) | String
d <- [String]
ds ]

    ([String]
unknown, [([String], [String])]
known) = case (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map ((Char -> Char) -> String -> String
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toUpper) [String]
vs_ of
                           [] -> ([], [([String], [String])]
environmentHelp)
                           [String]
vs -> ([String] -> [String]
forall a. Eq a => [a] -> [a]
nub ([String] -> [String])
-> ([[([String], [String])]] -> [([String], [String])])
-> ([String], [[([String], [String])]])
-> ([String], [([String], [String])])
forall (a :: * -> * -> *) b c b' c'.
Arrow a =>
a b c -> a b' c' -> a (b, b') (c, c')
*** ([([String], [String])] -> [([String], [String])]
forall a. Eq a => [a] -> [a]
nub ([([String], [String])] -> [([String], [String])])
-> ([[([String], [String])]] -> [([String], [String])])
-> [[([String], [String])]]
-> [([String], [String])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[([String], [String])]] -> [([String], [String])]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat)) (([String], [[([String], [String])]])
 -> ([String], [([String], [String])]))
-> ([Either String [([String], [String])]]
    -> ([String], [[([String], [String])]]))
-> [Either String [([String], [String])]]
-> ([String], [([String], [String])])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Either String [([String], [String])]]
-> ([String], [[([String], [String])]])
forall a b. [Either a b] -> ([a], [b])
partitionEithers ([Either String [([String], [String])]]
 -> ([String], [([String], [String])]))
-> [Either String [([String], [String])]]
-> ([String], [([String], [String])])
forall a b. (a -> b) -> a -> b
$
                                     (String -> Either String [([String], [String])])
-> [String] -> [Either String [([String], [String])]]
forall a b. (a -> b) -> [a] -> [b]
map String -> Either String [([String], [String])]
doLookup [String]
vs

    -- v is not known if it doesn't appear in the list of aliases of any
    -- of the environment var help descriptions.
    doLookup :: String -> Either String [([String], [String])]
doLookup String
v = case (([String], [String]) -> Bool)
-> [([String], [String])] -> [([String], [String])]
forall a. (a -> Bool) -> [a] -> [a]
filter ((String
v String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem`) ([String] -> Bool)
-> (([String], [String]) -> [String])
-> ([String], [String])
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([String], [String]) -> [String]
forall a b. (a, b) -> a
fst) [([String], [String])]
environmentHelp of
                     [] -> String -> Either String [([String], [String])]
forall a b. a -> Either a b
Left String
v
                     [([String], [String])]
es -> [([String], [String])] -> Either String [([String], [String])]
forall a b. b -> Either a b
Right [([String], [String])]
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]
_ (String
cmd:[String]
args) =
    case [CommandControl]
-> String -> [String] -> Either String (CommandArgs, [String])
disambiguateCommands [CommandControl]
commandControlList String
cmd [String]
args of
         Left String
err -> String -> IO ()
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
err
         Right (CommandArgs
cmds,[String]
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 [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
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 String
here <- IO String
getCurrentDirectory
       [Either String ()]
is_valid <- (DarcsCommand -> IO (Either String ()))
-> [DarcsCommand] -> IO [Either String ()]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM
                   (\DarcsCommand
c -> String -> IO (Either String ()) -> IO (Either String ())
forall p a. FilePathLike p => p -> IO a -> IO a
withCurrentDirectory String
here (IO (Either String ()) -> IO (Either String ()))
-> IO (Either String ()) -> IO (Either String ())
forall a b. (a -> b) -> a -> b
$ DarcsCommand -> [DarcsFlag] -> IO (Either String ())
commandPrereq DarcsCommand
c [])
                   ([CommandControl] -> [DarcsCommand]
extractCommands [CommandControl]
commandControlList)
       String -> IO ()
putStr (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ [String] -> String
unlines ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ ((DarcsCommand, Either String ()) -> String)
-> [(DarcsCommand, Either String ())] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (DarcsCommand -> String
commandName (DarcsCommand -> String)
-> ((DarcsCommand, Either String ()) -> DarcsCommand)
-> (DarcsCommand, Either String ())
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DarcsCommand, Either String ()) -> DarcsCommand
forall a b. (a, b) -> a
fst) ([(DarcsCommand, Either String ())] -> [String])
-> [(DarcsCommand, Either String ())] -> [String]
forall a b. (a -> b) -> a -> b
$
                ((DarcsCommand, Either String ()) -> Bool)
-> [(DarcsCommand, Either String ())]
-> [(DarcsCommand, Either String ())]
forall a. (a -> Bool) -> [a] -> [a]
filter (Either String () -> Bool
forall a b. Either a b -> Bool
isRight(Either String () -> Bool)
-> ((DarcsCommand, Either String ()) -> Either String ())
-> (DarcsCommand, Either String ())
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(DarcsCommand, Either String ()) -> Either String ()
forall a b. (a, b) -> b
snd) ([(DarcsCommand, Either String ())]
 -> [(DarcsCommand, Either String ())])
-> [(DarcsCommand, Either String ())]
-> [(DarcsCommand, Either String ())]
forall a b. (a -> b) -> a -> b
$
                [DarcsCommand]
-> [Either String ()] -> [(DarcsCommand, Either String ())]
forall a b. [a] -> [b] -> [(a, b)]
zip ([CommandControl] -> [DarcsCommand]
extractCommands [CommandControl]
commandControlList) [Either String ()]
is_valid
       String -> IO ()
putStrLn String
"--help"
       String -> IO ()
putStrLn String
"--version"
       String -> IO ()
putStrLn String
"--exact-version"
    where isRight :: Either a b -> Bool
isRight (Right b
_) = Bool
True
          isRight Either a b
_ = Bool
False

printVersion :: IO ()
printVersion :: IO ()
printVersion = String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"darcs version " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
version

-- avoiding a module import cycle between Help and TheCommands
commandControlList :: [CommandControl]
commandControlList :: [CommandControl]
commandControlList =
  DarcsCommand -> CommandControl
normalCommand DarcsCommand
help CommandControl -> [CommandControl] -> [CommandControl]
forall a. a -> [a] -> [a]
: [CommandControl]
TheCommands.commandControlList

-- FIXME: the "grouping" comments below should made subsections in the
-- manpage, as we already do for DarcsCommand groups. --twb, 2009

-- | Help on each environment variable in which Darcs is interested.
environmentHelp :: [([String], [String])]
environmentHelp :: [([String], [String])]
environmentHelp = [
 -- General-purpose
 ([String], [String])
environmentHelpHome,
 ([String], [String])
environmentHelpEditor,
 ([String], [String])
environmentHelpPager,
 ([String], [String])
environmentHelpColor,
 ([String], [String])
environmentHelpEscapeWhite,
 ([String], [String])
environmentHelpEscape,
 ([String], [String])
environmentHelpTmpdir,
 ([String], [String])
environmentHelpKeepTmpdir,
 ([String], [String])
environmentHelpEmail,
 ([String], [String])
environmentHelpSendmail,
 ([String], [String])
environmentHelpLocks,
 -- Remote Repositories
 ([String], [String])
environmentHelpSsh,
 ([String], [String])
environmentHelpScp,
 ([String], [String])
environmentHelpSshPort,
 ([String], [String])
environmentHelpProxy,
 ([String], [String])
environmentHelpProxyPassword,
 ([String], [String])
environmentHelpTimeout]

-- | This function is responsible for emitting a darcs "man-page", a
-- reference document used widely on Unix-like systems.  Manpages are
-- primarily used as a quick reference, or "memory jogger", so the
-- output should be terser than the user manual.
--
-- Before modifying the output, please be sure to read the man(7) and
-- man-pages(7) manpages, as these respectively describe the relevant
-- syntax and conventions.
manpage :: Doc
manpage :: Doc
manpage = [Doc] -> Doc
vcat [
 Doc
".TH DARCS 1" Doc -> Doc -> Doc
<+> String -> Doc
quoted String
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 ((String -> Doc) -> [String] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map String -> Doc
text [String]
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.",
 -- ".SH EXAMPLE",
 -- FIXME:
 -- new project: init, rec -la;
 -- track upstream project: clone, pull -a;
 -- contribute to project: add, rec, push/send.
 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
      -- | A synopsis line for each command.  Uses 'foldl' because it is
      -- necessary to avoid blank lines from Hidden_commands, as groff
      -- translates them into annoying vertical padding (unlike TeX).
      synopsis :: Doc
      synopsis :: Doc
synopsis = (Doc -> CommandControl -> Doc) -> Doc -> [CommandControl] -> Doc
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 String
_) = 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
                            (String -> DarcsCommand -> Doc
render (DarcsCommand -> String
commandName DarcsCommand
c String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" "))
                            ([CommandControl] -> [DarcsCommand]
extractCommands (DarcsCommand -> [CommandControl]
commandSubCommands DarcsCommand
c)))
                iter Doc
acc (CommandData DarcsCommand
c) = Doc
acc Doc -> Doc -> Doc
$$ String -> DarcsCommand -> Doc
render String
"" DarcsCommand
c
                render :: String -> DarcsCommand -> Doc
                render :: String -> DarcsCommand -> Doc
render String
prefix DarcsCommand
c =
                    Doc
".B darcs " Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> String -> Doc
text String
prefix Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> String -> Doc
text (DarcsCommand -> String
commandName DarcsCommand
c) Doc -> Doc -> Doc
$$
                    [Doc] -> Doc
vcat ((String -> Doc) -> [String] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (String -> Doc
text(String -> Doc) -> (String -> String) -> String -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
.String -> String
mangle_args) (DarcsCommand -> [String]
commandExtraArgHelp DarcsCommand
c)) Doc -> Doc -> Doc
$$
                    -- In the output, we want each command to be on its own
                    -- line, but we don't want blank lines between them.
                    Doc
".br"

      -- | As 'synopsis', but make each group a subsection (.SS), and
      -- include the help text for each command.
      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 String
x) = Doc
".SS" Doc -> Doc -> Doc
<+> String -> Doc
quoted String
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
<> String -> Doc
text (DarcsCommand -> String
commandName DarcsCommand
c)
                  , String -> Doc
text (String -> String
mangle_args String
"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 (String -> DarcsCommand -> Doc
render (DarcsCommand -> String
commandName DarcsCommand
c String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" "))
                    ([CommandControl] -> [DarcsCommand]
extractCommands (DarcsCommand -> [CommandControl]
commandSubCommands DarcsCommand
c)))
                iter (CommandData DarcsCommand
c) = String -> DarcsCommand -> Doc
render String
"" DarcsCommand
c
                render :: String -> DarcsCommand -> Doc
                render :: String -> DarcsCommand -> Doc
render String
prefix DarcsCommand
c =
                  [Doc] -> Doc
vcat
                  [ Doc
".B darcs " Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> String -> Doc
text String
prefix Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> String -> Doc
text (DarcsCommand -> String
commandName DarcsCommand
c)
                  , [Doc] -> Doc
vcat ((String -> Doc) -> [String] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (String -> Doc
text(String -> Doc) -> (String -> String) -> String -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
.String -> String
mangle_args) (DarcsCommand -> [String]
commandExtraArgHelp DarcsCommand
c))
                  , Doc
".RS 4"
                  , DarcsCommand -> Doc
commandHelp DarcsCommand
c
                  , Doc
".RE"
                  ]

      -- | Now I'm showing off: mangle the extra arguments of Darcs commands
      -- so as to use the ideal format for manpages, italic words and roman
      -- punctuation.
      mangle_args :: String -> String
      mangle_args :: String -> String
mangle_args String
s =
          String
".RI " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
unwords ((String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map String -> String
forall a. Show a => a -> String
show ((Char -> Char -> Bool) -> String -> [String]
forall a. (a -> a -> Bool) -> [a] -> [[a]]
groupBy Char -> Char -> Bool
cmp (String -> [String]) -> String -> [String]
forall a b. (a -> b) -> a -> b
$ (Char -> Char) -> String -> String
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String -> String
gank String
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 :: String -> String
gank (Char
' ':Char
'o':Char
'r':Char
' ':String
xs) = Char
'|' Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
gank String
xs
                    gank (Char
x:String
xs) = Char
x Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
gank String
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
<+> String -> Doc
quoted ([String] -> String
andClauses [String]
ks)) Doc -> [Doc] -> [Doc]
forall a. a -> [a] -> [a]
: (String -> Doc) -> [String] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map String -> Doc
text [String]
ds
                     | ([String]
ks, [String]
ds) <- [([String], [String])]
environmentHelp]

      prefFiles :: Doc
      prefFiles :: Doc
prefFiles = [Doc] -> Doc
vcat ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ ((String, String) -> Doc) -> [(String, String)] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (String, String) -> Doc
go [(String, String)]
prefsFilesHelp
        where go :: (String, String) -> Doc
go (String
f,String
h) = Doc
".SS" Doc -> Doc -> Doc
<+> String -> Doc
quoted(String
"_darcs/prefs/" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
f) Doc -> Doc -> Doc
$$ String -> Doc
text String
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 :: [String]
markdownLines =
 [ String
"# Commands", String
""
 , [String] -> String
unlines [String]
commands
 , String
"# Patterns"
 , String
"", [String] -> String
unlines [String]
helpOnMatchers
 , String
"# Configuration"
 , String
"", [String] -> String
unlines [String]
prefFiles
 , String
"# Environment variables"
 , String
"", [String] -> String
unlines [String]
environment ]
   where
      prefFiles :: [String]
prefFiles = ((String, String) -> [String]) -> [(String, String)] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (String, String) -> [String]
go [(String, String)]
prefsFilesHelp
        where go :: (String, String) -> [String]
go (String
f,String
h) = [String
"## `_darcs/prefs/" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
f String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"`", String
"", String
h]

      environment :: [String]
      environment :: [String]
environment = [String] -> [[String]] -> [String]
forall a. [a] -> [[a]] -> [a]
intercalate [String
""]
                     [ [String] -> [String] -> [String]
renderEnv [String]
ks [String]
ds | ([String]
ks, [String]
ds) <- [([String], [String])]
environmentHelp ]
        where
          renderEnv :: [String] -> [String] -> [String]
renderEnv [String]
k [String]
d = (String
"## " String -> String -> String
forall a. [a] -> [a] -> [a]
++ (String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
", " [String]
k)) String -> [String] -> [String]
forall a. a -> [a] -> [a]
: String
"" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
d
      commands :: [String]
      commands :: [String]
commands = ([String] -> CommandControl -> [String])
-> [String] -> [CommandControl] -> [String]
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl [String] -> CommandControl -> [String]
iter [] [CommandControl]
commandControlList
      iter :: [String] -> CommandControl -> [String]
      iter :: [String] -> CommandControl -> [String]
iter [String]
acc (GroupName String
x) = [String]
acc [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
"## " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
x, String
""]
      iter [String]
acc (HiddenCommand DarcsCommand
_) = [String]
acc
      iter [String]
acc (CommandData (c :: DarcsCommand
c@SuperCommand {})) =
          [String]
acc [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ (DarcsCommand -> [String]) -> [DarcsCommand] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap
                  (String -> DarcsCommand -> [String]
render (DarcsCommand -> String
commandName DarcsCommand
c String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" "))
                  ([CommandControl] -> [DarcsCommand]
extractCommands (DarcsCommand -> [CommandControl]
commandSubCommands DarcsCommand
c))
      iter [String]
acc (CommandData DarcsCommand
c) = [String]
acc [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ String -> DarcsCommand -> [String]
render String
"" DarcsCommand
c
      render :: String -> DarcsCommand -> [String]
      render :: String -> DarcsCommand -> [String]
render String
prefix DarcsCommand
c =
          [ String
"### " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
prefix String -> String -> String
forall a. [a] -> [a] -> [a]
++ DarcsCommand -> String
commandName DarcsCommand
c
          , String
"", String
"darcs " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
prefix String -> String -> String
forall a. [a] -> [a] -> [a]
++ DarcsCommand -> String
commandName DarcsCommand
c String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" [OPTION]... " String -> String -> String
forall a. [a] -> [a] -> [a]
++
          [String] -> String
unwords (DarcsCommand -> [String]
commandExtraArgHelp DarcsCommand
c)
          , String
"", DarcsCommand -> String
commandDescription DarcsCommand
c
          , String
"", Doc -> String
renderString (DarcsCommand -> Doc
commandHelp DarcsCommand
c)
          , String
"Options:", [DarcsOptDescr DarcsFlag] -> String
forall f. [DarcsOptDescr f] -> String
optionsMarkdown ([DarcsOptDescr DarcsFlag] -> String)
-> [DarcsOptDescr DarcsFlag] -> String
forall a b. (a -> b) -> a -> b
$ DarcsCommand -> [DarcsOptDescr DarcsFlag]
commandBasicOptions DarcsCommand
c
          , if [DarcsOptDescr DarcsFlag] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [DarcsOptDescr DarcsFlag]
opts2 then String
""
             else [String] -> String
unlines [String
"Advanced Options:", [DarcsOptDescr DarcsFlag] -> String
forall f. [DarcsOptDescr f] -> String
optionsMarkdown [DarcsOptDescr DarcsFlag]
opts2]
          ]
       where opts2 :: [DarcsOptDescr DarcsFlag]
opts2 = DarcsCommand -> [DarcsOptDescr DarcsFlag]
commandAdvancedOptions DarcsCommand
c

environmentHelpEditor :: ([String], [String])
environmentHelpEditor :: ([String], [String])
environmentHelpEditor = ([String
"DARCS_EDITOR", String
"VISUAL", String
"EDITOR"],[
 String
"To edit a patch description of email comment, Darcs will invoke an",
 String
"external editor.  Your preferred editor can be set as any of the",
 String
"environment variables $DARCS_EDITOR, $VISUAL or $EDITOR.",
 String
"If none of these are set, nano is used.  If nano crashes or is not",
 String
"found in your PATH, vi, emacs, emacs -nw and (on Windows) edit are",
 String
"each tried in turn."])

environmentHelpPager :: ([String], [String])
environmentHelpPager :: ([String], [String])
environmentHelpPager = ([String
"DARCS_PAGER", String
"PAGER"],[
 String
"Darcs will invoke a pager if the output of some command is longer",
 String
"than 20 lines. Darcs will use the pager specified by $DARCS_PAGER",
 String
"or $PAGER.  If neither are set, `less` will be used."])

environmentHelpTimeout :: ([String], [String])
environmentHelpTimeout :: ([String], [String])
environmentHelpTimeout = ([String
"DARCS_CONNECTION_TIMEOUT"],[
 String
"Set the maximum time in seconds that darcs allows and connection to",
 String
"take. If the variable is not specified the default are 30 seconds.",
 String
"This option only works with curl."])

-- | There are two environment variables that we do not document:
-- - DARCS_USE_ISPRINT: deprecated, use DARCS_DONT_ESCAPE_ISPRINT.
-- - DARCS_TESTING_PREFS_DIR: used by the test suite to tell darcs
--                            where to find its configuration files.