% 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 whatsnew} \label{whatsnew} \begin{code} {-# OPTIONS_GHC -cpp #-} module Darcs.Commands.WhatsNew ( whatsnew ) where import System.Exit ( ExitCode(..), exitWith ) import Data.List ( sort ) import Control.Monad ( when ) import Darcs.Commands ( DarcsCommand(..), nodefaults ) import Darcs.Arguments ( DarcsFlag(..), working_repo_dir, lookforadds, ignoretimes, noskip_boring, unified, areFileArgs, getRepoPaths, list_registered_files, ) import Darcs.Arguments ( summary ) import Darcs.Patch.TouchesFiles ( choose_touching ) import Darcs.RepoPath ( toFilePath ) import Darcs.Repository ( withRepository, ($-), slurp_recorded, get_unrecorded, get_unrecorded_no_look_for_adds, amInRepository ) import Darcs.Repository.Prefs ( filetype_function ) import Darcs.Diff ( smart_diff ) import Darcs.Patch ( summarize, apply_to_slurpy, is_hunk, invert, apply_to_filepaths ) import Darcs.Patch.Permutations ( partitionRL ) import Darcs.Patch.Real ( prim2real ) import Darcs.PrintPatch ( printPatch, contextualPrintPatch ) import Darcs.Patch.Ordered ( FL(..), mapFL_FL, reverseRL, reverseFL, (:>)(..) ) import Printer ( putDocLn, renderString, vcat, text ) #include "impossible.h" \end{code} \options{whatsnew} \haskell{whatsnew_description} \begin{code} whatsnew_description :: String whatsnew_description = "Display unrecorded changes in the working copy." \end{code} \haskell{whatsnew_help} \verb!darcs whatsnew! will return a non-zero value if there are no changes, which can be useful if you just want to see in a script if anything has been modified. If you want to see some context around your changes, you can use the \verb!-u! option, to get output similar to the unidiff format. \begin{code} whatsnew_help :: String whatsnew_help = "whatsnew gives you a view of what changes you've made in your working\n"++ "copy that haven't yet been recorded. The changes are displayed in\n"++ "darcs patch format. Note that --look-for-adds implies --summary usage.\n" \end{code} \begin{code} whatsnew :: DarcsCommand whatsnew = DarcsCommand {command_name = "whatsnew", command_help = whatsnew_help, command_description = whatsnew_description, command_extra_args = -1, command_extra_arg_help = ["[FILE or DIRECTORY]..."], command_command = whatsnew_cmd, command_prereq = amInRepository, command_get_arg_possibilities = list_registered_files, command_argdefaults = nodefaults, command_advanced_options = [ignoretimes, noskip_boring], command_basic_options = [summary, unified, lookforadds, working_repo_dir]} \end{code} \begin{code} whatsnew_cmd :: [DarcsFlag] -> [String] -> IO () whatsnew_cmd opts' args | LookForAdds `elem` opts' && NoSummary `notElem` opts' = -- add Summary to the opts since 'darcs whatsnew --look-for-adds' -- implies summary withRepository (Summary:opts') $- \repository -> do files <- getRepoPaths opts' args when (areFileArgs files) $ putStrLn $ "What's new in "++unwords (map show files)++":\n" all_changes <- get_unrecorded repository chold <- get_unrecorded_no_look_for_adds repository s <- slurp_recorded repository ftf <- filetype_function let pre_changed_files = apply_to_filepaths (invert chold) $ map toFilePath files select_files = choose_touching pre_changed_files cho = select_files chold cho_adds :> _ <- return $ partitionRL is_hunk $ reverseFL cho cha :> _ <- return $ partitionRL is_hunk $ reverseFL $ select_files all_changes let chn = smart_diff [LookForAdds,Summary] ftf (fromJust $ apply_to_slurpy (reverseRL cho_adds) s) (fromJust $ apply_to_slurpy (reverseRL cha) s) case (chn, cho) of (NilFL, NilFL) -> do putStrLn "No changes!" exitWith $ ExitFailure 1 _ -> return () putDocLn $ summarize cho case chn of NilFL -> return () _ -> putDocLn $ lower_as $ renderString $ summarize chn where lower_as x = vcat $ map (text . l_as) $ lines x l_as ('A':x) = 'a':x l_as x = x whatsnew_cmd opts args = withRepository opts $- \repository -> do files <- sort `fmap` getRepoPaths opts args when (areFileArgs files) $ putStrLn $ "What's new in "++unwords (map show files)++":\n" changes <- get_unrecorded repository case changes of NilFL -> do putStrLn "No changes!" exitWith $ ExitFailure 1 _ -> let pre_changed_files = apply_to_filepaths (invert changes) $ map toFilePath files in case mapFL_FL prim2real $ choose_touching pre_changed_files changes of NilFL -> do putStrLn "No changes!" exitWith $ ExitFailure 1 ch -> if Summary `elem` opts then putDocLn $ summarize ch else if Unified `elem` opts then do s <- slurp_recorded repository contextualPrintPatch s ch else printPatch ch \end{code} If you give one or more file or directory names as an argument to \verb!whatsnew!, darcs will output only changes to those files or to files in those directories.