% Copyright (C) 2002-2003,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 mark-conflicts} \begin{code} {-# OPTIONS_GHC -cpp #-} {-# LANGUAGE CPP #-} module Darcs.Commands.MarkConflicts ( markconflicts, resolve ) where import System.Exit ( ExitCode(..), exitWith ) import Darcs.SignalHandler ( withSignalsBlocked ) import Control.Monad ( when ) import Darcs.Commands ( DarcsCommand(..), nodefaults, command_alias ) import Darcs.Arguments ( DarcsFlag, ignoretimes, working_repo_dir, umask_option ) import Darcs.Repository ( withRepoLock, ($-), amInRepository, add_to_pending, applyToWorking, read_repo, sync_repo, get_unrecorded_unsorted, ) import Darcs.Patch ( invert ) import Darcs.Ordered ( FL(..) ) import Darcs.Sealed ( Sealed(Sealed) ) import Darcs.Resolution ( patchset_conflict_resolutions ) import Darcs.Utils ( promptYorn ) #include "impossible.h" markconflicts_description :: String markconflicts_description = "Mark any unresolved conflicts in working copy, for manual resolution." \end{code} \options{mark-conflicts} \haskell{mark-conflicts_help} \begin{code} markconflicts_help :: String markconflicts_help = "Darcs requires human guidance to unify changes to the same part of a\n" ++ "source file. When a conflict first occurs, darcs will add both\n" ++ "choices to the working tree, delimited by markers.\n" ++ -- Removing this part of the sentence for now, because ^ ^ ^ upsets TeX. -- the markers `v v v', `* * *' and `^ ^ ^'.\n" "\n" ++ "However, you might revert or manually delete these markers without\n" ++ "actually resolving the conflict. In this case, `darcs mark-conflicts'\n" ++ "is useful to show where any unresolved conflicts. It is also useful\n" ++ "if `darcs apply' is called with --apply-conflicts, where conflicts\n" ++ "aren't marked initially.\n" ++ "\n" ++ "Any unrecorded changes to the working tree *will* be lost forever when\n" ++ "you run this command! You will be prompted for confirmation before\n" ++ "this takes place.\n" ++ "\n" ++ "This command was historically called `resolve', and this deprecated\n" ++ "alias still exists for backwards-compatibility.\n" markconflicts :: DarcsCommand markconflicts = DarcsCommand {command_name = "mark-conflicts", command_help = markconflicts_help, command_description = markconflicts_description, command_extra_args = 0, command_extra_arg_help = [], command_command = markconflicts_cmd, command_prereq = amInRepository, command_get_arg_possibilities = return [], command_argdefaults = nodefaults, command_advanced_options = [umask_option], command_basic_options = [ignoretimes, working_repo_dir]} markconflicts_cmd :: [DarcsFlag] -> [String] -> IO () markconflicts_cmd opts [] = withRepoLock opts $- \repository -> do pend <- get_unrecorded_unsorted repository r <- read_repo repository Sealed res <- return $ patchset_conflict_resolutions r case res of NilFL -> do putStrLn "No conflicts to mark." exitWith ExitSuccess _ -> return () case pend of NilFL -> return () _ -> do yorn <- promptYorn ("This will trash any unrecorded changes"++ " in the working directory.\nAre you sure? ") when (yorn /= 'y') $ exitWith ExitSuccess applyToWorking repository opts (invert pend) `catch` \e -> bug ("Can't undo pending changes!" ++ show e) sync_repo repository withSignalsBlocked $ do add_to_pending repository res applyToWorking repository opts res `catch` \e -> bug ("Problem marking conflicts in mark-conflicts!" ++ show e) putStrLn "Finished marking conflicts." markconflicts_cmd _ _ = impossible -- |resolve is an alias for mark-conflicts. resolve :: DarcsCommand resolve = command_alias "resolve" markconflicts \end{code}