% Copyright (C) 2002-2005 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 revert} \begin{code} module Darcs.Commands.Revert ( revert ) where import System.Exit ( ExitCode(..), exitWith ) import Control.Monad ( when ) import Data.List ( sort ) import English (englishNum, This(..), Noun(..)) import Darcs.Commands ( DarcsCommand(..), nodefaults ) import Darcs.Arguments ( DarcsFlag( All, Debug ), ignoretimes, working_repo_dir, all_interactive, getRepoPaths, areFileArgs, list_registered_files, umask_option, ) import Darcs.Utils ( askUser ) import Darcs.RepoPath ( toFilePath ) import Darcs.Repository ( withRepoLock, ($-), withGutsOf, get_unrecorded, get_unrecorded_unsorted, add_to_pending, sync_repo, applyToWorking, amInRepository, slurp_recorded_and_unrecorded, ) import Darcs.Patch ( invert, apply_to_filepaths, commute ) import Darcs.Patch.Ordered ( FL(..), (:>)(..), lengthFL, nullFL, (+>+) ) import Darcs.SelectChanges ( with_selected_last_changes_to_files' ) import Darcs.Patch.TouchesFiles ( choose_touching ) import Darcs.Commands.Unrevert ( write_unrevert ) \end{code} \begin{code} revert_description :: String revert_description = "Revert to the recorded version (not always reversible)." \end{code} \options{revert} \haskell{revert_help} The actions of a revert may be reversed using the unrevert command (see subsection~\ref{unrevert}). However, if you've made changes since the revert your mileage may vary, so please be careful. \begin{code} revert_help :: String revert_help = "Revert is used to undo changes made to the working copy which have\n"++ "not yet been recorded. You will be prompted for which changes you\n"++ "wish to undo. The last revert can be undone safely using the unrevert\n"++ "command if the working copy was not modified in the meantime.\n" \end{code} \begin{code} revert :: DarcsCommand revert = DarcsCommand {command_name = "revert", command_help = revert_help, command_description = revert_description, command_extra_args = -1, command_extra_arg_help = ["[FILE or DIRECTORY]..."], command_command = revert_cmd, command_prereq = amInRepository, command_get_arg_possibilities = list_registered_files, command_argdefaults = nodefaults, command_advanced_options = [ignoretimes, umask_option], command_basic_options = [all_interactive, working_repo_dir]} \end{code} You can give revert optional arguments indicating files or directories. If you do so it will only prompt you to revert changes in those files or in files in those directories. \begin{code} revert_cmd :: [DarcsFlag] -> [String] -> IO () revert_cmd opts args = withRepoLock opts $- \repository -> do files <- sort `fmap` getRepoPaths opts args when (areFileArgs files) $ putStrLn $ "Reverting changes in "++unwords (map show files)++"..\n" changes <- if All `elem` opts then get_unrecorded_unsorted repository else get_unrecorded repository let pre_changed_files = apply_to_filepaths (invert changes) (map toFilePath files) (rec, working_dir) <- slurp_recorded_and_unrecorded repository case choose_touching pre_changed_files changes of NilFL -> putStrLn "There are no changes to revert!" _ -> with_selected_last_changes_to_files' "revert" opts working_dir pre_changed_files changes $ \ (norevert:>p) -> if nullFL p then putStrLn $ "If you don't want to revert after all," ++ " that's fine with me!" else do let theseChanges = englishNum (lengthFL p) . This . Noun $ "change" yorn <- if All `elem` opts then return "y" else askUser $ "Do you really want to revert " ++ theseChanges "? " case yorn of ('y':_) -> return () _ -> exitWith $ ExitSuccess withGutsOf repository $ do add_to_pending repository $ invert p when (Debug `elem` opts) $ putStrLn "About to write the unrevert file." case commute (norevert:>p) of Just (p':>_) -> write_unrevert repository p' rec NilFL Nothing -> write_unrevert repository (norevert+>+p) rec NilFL when (Debug `elem` opts) $ putStrLn "About to apply to the working directory." applyToWorking repository opts (invert p) `catch` \e -> fail ("Unable to apply inverse patch!" ++ show e) sync_repo repository putStrLn "Finished reverting." \end{code}