% Copyright (C) 2005 Florian Weimer % % 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. \darcsCommand{show files} \begin{code} {-# OPTIONS_GHC -cpp #-} {-# LANGUAGE CPP #-} #include "gadts.h" module Darcs.Commands.ShowFiles ( show_files, show_manifest ) where import Darcs.Arguments ( DarcsFlag(..), working_repo_dir, files, directories, pending, nullFlag ) import Darcs.Commands ( DarcsCommand(..), nodefaults, command_alias ) import Darcs.Repository ( Repository, amInRepository, slurp_pending, slurp_recorded, withRepository ) import Darcs.Patch ( RepoPatch ) import Darcs.SlurpDirectory ( Slurpy, list_slurpy, list_slurpy_files, list_slurpy_dirs ) show_files_description :: String show_files_description = "Show version-controlled files in the working copy." show_files_help :: String show_files_help = "The `darcs show files' command lists those files and directories in\n" ++ "the working tree that are under version control. This command is\n" ++ "primarily for scripting purposes; end users will probably want `darcs\n" ++ "whatsnew --summary'.\n" ++ "\n" ++ "A file is `pending' if it has been added but not recorded. By\n" ++ "default, pending files (and directories) are listed; the --no-pending\n" ++ "option prevents this.\n" ++ "\n" ++ "By default `darcs show files' lists both files and directories, but\n" ++ "the alias `darcs show manifest' only lists files. The --files,\n" ++ "--directories, --no-files and --no-directories modify this behaviour.\n" ++ "\n" ++ "By default entries are one-per-line (i.e. newline separated). This\n" ++ "can cause problems if the files themselves contain newlines or other\n" ++ "control characters. To get aroudn this, the --null option uses the\n" ++ "null character instead. The script interpreting output from this\n" ++ "command needs to understand this idiom; `xargs -0' is such a command.\n" ++ "\n" ++ "For example, to list version-controlled files by size:\n" ++ "\n" ++ " darcs show files -0 | xargs -0 ls -ldS\n" show_files :: DarcsCommand show_files = DarcsCommand { command_name = "files", command_help = show_files_help, command_description = show_files_description, command_extra_args = 0, command_extra_arg_help = [], command_command = manifest_cmd to_list_files, command_prereq = amInRepository, command_get_arg_possibilities = return [], command_argdefaults = nodefaults, command_advanced_options = [], command_basic_options = [files, directories, pending, nullFlag, working_repo_dir] } show_manifest :: DarcsCommand show_manifest = command_alias "manifest" show_files { command_command = manifest_cmd to_list_manifest } to_list_files, to_list_manifest :: [DarcsFlag] -> Slurpy -> [FilePath] to_list_files opts = files_dirs (NoFiles `notElem` opts) (NoDirectories `notElem` opts) to_list_manifest opts = files_dirs (NoFiles `notElem` opts) (Directories `elem` opts) files_dirs :: Bool -> Bool -> Slurpy -> [FilePath] files_dirs False False = \_ -> [] files_dirs False True = list_slurpy_dirs files_dirs True False = list_slurpy_files files_dirs True True = list_slurpy manifest_cmd :: ([DarcsFlag] -> Slurpy -> [FilePath]) -> [DarcsFlag] -> [String] -> IO () manifest_cmd to_list opts _ = do list <- (to_list opts) `fmap` withRepository opts slurp mapM_ output list where slurp :: RepoPatch p => Repository p C(r u r) -> IO Slurpy slurp = if NoPending `notElem` opts then slurp_pending else slurp_recorded output_null name = do { putStr name ; putChar '\0' } output = if NullFlag `elem` opts then output_null else putStrLn \end{code}