% 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 replace} \begin{code} {-# OPTIONS_GHC -cpp #-} module Darcs.Commands.Replace ( replace ) where import Data.Maybe ( isJust ) import Control.Monad (unless, liftM) import Darcs.Commands import Darcs.Arguments import Darcs.Repository ( withRepoLock, ($-), add_to_pending, amInRepository, slurp_recorded_and_unrecorded, applyToWorking, ) import Darcs.Patch ( Prim, apply_to_slurpy, tokreplace, force_replace_slurpy ) import Darcs.Patch.Ordered ( FL(..), unsafeFL, (+>+), concatFL ) import Darcs.SlurpDirectory ( slurp_hasfile, Slurpy ) import RegChars ( regChars ) import Data.Char ( isSpace ) import Darcs.Diff ( smart_diff ) import Darcs.RepoPath ( SubPath, sp2fn, toFilePath ) import Darcs.Repository.Prefs ( FileType(TextFile) ) #include "impossible.h" \end{code} \begin{code} replace_description :: String replace_description = "Replace a token with a new value for that token." \end{code} \options{replace} \haskell{replace_help} The default regexp is \verb![A-Za-z_0-9]!), and if one of your tokens contains a `\verb|-|' or `\verb|.|', you will then (by default) get the ``filename'' regexp, which is \verb![A-Za-z_0-9\-\.]!. \begin{options} --token-chars \end{options} If you prefer to choose a different set of characters to define your token (perhaps because you are programming in some other language), you may do so with the \verb!--token-chars! option. You may prefer to define tokens in terms of delimiting characters instead of allowed characters using a flag such as \verb!--token-chars '[^ \n\t]'!, which would define a token as being white-space delimited. If you do choose a non-default token definition, I recommend using \verb!_darcs/prefs/defaults! to always specify the same \verb!--token-chars!, since your replace patches will be better behaved (in terms of commutation and merges) if they have tokens defined in the same way. When using darcs replace, the ``new'' token may not already appear in the file---if that is the case, the replace change would not be invertible. This limitation holds only on the already-recorded version of the file. There is a potentially confusing difference, however, when a replace is used to make another replace possible: \begin{verbatim} % darcs replace newtoken aaack ./foo.c % darcs replace oldtoken newtoken ./foo.c % darcs record \end{verbatim} will be valid, even if \verb!newtoken! and \verb!oldtoken! are both present in the recorded version of foo.c, while the sequence \begin{verbatim} % [manually edit foo.c replacing newtoken with aaack] % darcs replace oldtoken newtoken ./foo.c \end{verbatim} will fail because ``newtoken'' still exists in the recorded version of \verb!foo.c!. The reason for the difference is that when recording, a ``replace'' patch always is recorded \emph{before} any manual changes, which is usually what you want, since often you will introduce new occurrences of the ``newtoken'' in your manual changes. In contrast, multiple ``replace'' changes are recorded in the order in which they were made. \begin{code} replace_help :: String replace_help = "Replace allows you to change a specified token wherever it\n"++ "occurs in the specified files. The replace is encoded in a\n"++ "special patch and will merge as expected with other patches.\n"++ "Tokens here are defined by a regexp specifying the characters\n"++ "which are allowed. By default a token corresponds to a C identifier.\n" \end{code} \begin{code} replace :: DarcsCommand replace = DarcsCommand {command_name = "replace", command_help = replace_help, command_description = replace_description, command_extra_args = -1, command_extra_arg_help = ["","", " ..."], command_command = replace_cmd, command_prereq = amInRepository, command_get_arg_possibilities = list_registered_files, command_argdefaults = nodefaults, command_advanced_options = [ignoretimes, umask_option], command_basic_options = [tokens, force_replace, working_repo_dir]} \end{code} \begin{code} replace_cmd :: [DarcsFlag] -> [String] -> IO () replace_cmd opts (old:new:relfs) = withRepoLock opts $- \repository -> do fs <- getRepoPaths opts relfs toks <- choose_toks opts old new let checkToken tok = unless (is_tok toks tok) $ fail $ "'"++tok++"' is not a valid token!" checkToken old checkToken new (cur, work) <- slurp_recorded_and_unrecorded repository pswork <- (concatFL . unsafeFL) `liftM` sequence (map (repl toks cur work) fs) add_to_pending repository pswork applyToWorking repository opts pswork `catch` \e -> fail $ "Can't do replace on working!\n" ++ "Perhaps one of the files already contains '"++ new++"'?\n" ++ show e where ftf _ = TextFile repl :: String -> Slurpy -> Slurpy -> SubPath -> IO (FL Prim) repl toks cur work f = if not $ slurp_hasfile (sp2fn f) work then do putStrLn $ "Skipping file '"++f_fp++"' which isn't in the repository." return NilFL else if ForceReplace `elem` opts || isJust (apply_to_slurpy (tokreplace f_fp toks old new) work) || isJust (apply_to_slurpy (tokreplace f_fp toks old new) cur) then return (get_force_replace f toks work) else do putStrLn $ "Skipping file '"++f_fp++"'" putStrLn $ "Perhaps the recorded version of this " ++ "file already contains '" ++new++"'?" return NilFL where f_fp = toFilePath f get_force_replace :: SubPath -> String -> Slurpy -> FL Prim get_force_replace f toks s = case force_replace_slurpy (tokreplace f_fp toks new old) s of Nothing -> bug "weird forcing bug in replace." Just s' -> case smart_diff [] ftf s s' of pfix -> pfix +>+ (tokreplace f_fp toks old new :>: NilFL) where f_fp = toFilePath f replace_cmd _ _ = fail "Usage: darcs replace OLD NEW [FILES]" \end{code} \begin{code} default_toks :: String default_toks = "A-Za-z_0-9" filename_toks :: String filename_toks = "A-Za-z_0-9\\-\\." is_tok :: String -> String -> Bool is_tok _ "" = False is_tok toks s = and $ map (regChars toks) s choose_toks :: [DarcsFlag] -> String -> String -> IO String choose_toks (Toks t:_) a b | any isSpace t = fail $ bad_token_spec $ "Space is not allowed in the spec" | length t <= 2 = fail $ bad_token_spec $ "It must contain more than 2 characters, because " ++ "it should be enclosed in square brackets" | head t /= '[' || last t /= ']' = fail $ bad_token_spec $ "It should be enclosed in square brackets" | not (is_tok tok a) = fail $ bad_token_spec $ not_a_token a | not (is_tok tok b) = fail $ bad_token_spec $ not_a_token b | otherwise = return tok where tok = init $ tail t :: String bad_token_spec msg = "Bad token spec: '"++ t ++"' ("++ msg ++")" not_a_token x = x ++ " is not a token, according to your spec" choose_toks (_:fs) a b = choose_toks fs a b choose_toks [] a b = if is_tok default_toks a && is_tok default_toks b then return default_toks else return filename_toks \end{code}