% 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. \subsection{darcs help} \label{help} \begin{code} module Darcs.Commands.Help ( help_cmd, command_control_list, print_version, list_available_commands ) where import System.Exit ( ExitCode(..), exitWith ) import Autoconf( darcs_version ) import Darcs.Commands ( CommandControl(Command_data), DarcsCommand(..), disambiguate_commands, CommandArgs(..), get_command_help, extract_commands, nodefaults, usage ) import Darcs.Arguments ( DarcsFlag(..), help_on_match ) import Darcs.External ( viewDoc ) import Darcs.Patch.Match ( helpOnMatchers ) import Darcs.Utils ( withCurrentDirectory ) import Printer ( text ) import Workaround ( getCurrentDirectory ) import qualified Darcs.TheCommands as TheCommands \end{code} \options{help} \haskell{help_description} \begin{code} help_description :: String help_description = "Display help about darcs and darcs commands." \end{code} \haskell{help_help} \begin{code} help_help :: String help_help = "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" help :: DarcsCommand help = DarcsCommand {command_name = "help", command_help = help_help, command_description = help_description, command_extra_args = -1, command_extra_arg_help = ["[ [DARCS_SUBCOMMAND]] "], command_command = help_cmd, command_prereq = \_ -> return $ Right (), command_get_arg_possibilities = return [], command_argdefaults = nodefaults, command_advanced_options = [], command_basic_options = [help_on_match]} help_cmd :: [DarcsFlag] -> [String] -> IO () help_cmd opts [] = do viewDoc $ text $ case () of _ | HelpOnMatch `elem` opts -> helpOnMatchers | otherwise -> usage command_control_list exitWith $ ExitSuccess help_cmd _ (cmd:args) = do let disambiguated = disambiguate_commands command_control_list cmd args case disambiguated of Left err -> fail err Right (cmds,_) -> let msg = case cmds of CommandOnly c -> get_command_help Nothing c SuperCommandOnly c -> get_command_help Nothing c SuperCommandSub c s -> get_command_help (Just c) s in viewDoc $ text msg exitWith $ ExitSuccess list_available_commands :: IO () list_available_commands = do here <- getCurrentDirectory is_valid <- sequence $ map (\c-> withCurrentDirectory here $ (command_prereq c) []) (extract_commands command_control_list) putStr $ unlines $ map (command_name . fst) $ filter (isRight.snd) $ zip (extract_commands command_control_list) is_valid putStrLn "--help" putStrLn "--version" putStrLn "--exact-version" putStrLn "--overview" where isRight (Right _) = True isRight _ = False print_version :: IO () print_version = putStrLn $ "darcs version " ++ darcs_version -- avoiding a module import cycle between Help and TheCommands command_control_list :: [CommandControl] command_control_list = Command_data help : TheCommands.command_control_list \end{code}