% Copyright (C) 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 apply} \begin{code} module Apply ( apply ) where import System ( ExitCode(..), exitWith ) import Prelude hiding ( catch ) import IO ( hClose, stdin, stdout, stderr ) import Control.Exception ( catch, throw, Exception( ExitException ) ) import Monad ( when, liftM ) import DarcsUtils ( nubsort ) import Maybe ( catMaybes ) import SignalHandler ( withSignalsBlocked ) import DarcsCommands ( DarcsCommand(..) ) import DarcsCommandsAux ( check_paths ) import DarcsArguments ( DarcsFlag( Reply, Test, NoTest, AnyOrder, Gui, Interactive, All, MarkConflicts, AllowConflicts, Verbose, HappyForwarding ), get_cc, want_external_merge, working_repo_dir, notest, nocompress, apply_conflict_options, ignoretimes, verbose, get_sendmail_cmd, reply, verify, list_files, fix_filepath, umask_option, all_gui_interactive, sendmail_cmd, leave_test_dir, happy_forwarding, set_scripts_executable ) import qualified DarcsArguments ( cc ) import Repository ( PatchSet, withRepoLock, amInRepository, get_unrecorded, slurp_pending, slurp_recorded, with_new_pending, sync_repo, read_repo, updateInventory, applyToWorking, applyToPristine, ) import Patch ( Patch, patch2patchinfo, invert, list_touched_files, join_patches, unjoin_patches, null_patch, ) import PatchInfo ( human_friendly ) import SlurpDirectory ( wait_a_moment, co_slurp, ) import FastPackedString ( readFilePS, packString, unpackPS, hGetContentsPS, linesPS, takePS, dropPS, PackedString, lastPS, initPS, nullPS, unlinesPS ) import External ( sendEmail, sendEmailDoc, resendEmail, verifyPS ) import Email ( read_email ) import Lock ( withStdoutTemp, readBinFile ) import Pull ( merge_with_us_and_pending, save_patches, check_unrecorded_conflicts ) import Depends ( get_common_and_uncommon_or_missing ) import Resolution ( standard_resolution, no_resolution, external_resolution ) import SelectChanges ( with_selected_changes ) import Test ( test_patch ) import PatchBundle ( scan_bundle ) import DarcsUtils ( putStrLnError ) import Printer ( packedString, putDocLn, vcat, text, ($$), errorDoc, empty ) #include "impossible.h" \end{code} \begin{code} apply_description :: String apply_description = "Apply patches (from an email bundle) to the repository." \end{code} \options{apply} \haskell{apply_help} \begin{code} apply_help :: String apply_help = "Apply is used to apply a bundle of patches to this repository.\n"++ "Such a bundle may be created using send.\n" \end{code} \begin{code} stdin_magic :: String stdin_magic = "magic darcs standard input" stdindefault :: FilePath -> [String] -> IO [String] stdindefault _ [] = return [stdin_magic] stdindefault _ x = return x apply :: DarcsCommand apply = DarcsCommand {command_name = "apply", command_help = apply_help, command_description = apply_description, command_extra_args = 1, command_extra_arg_help = [""], command_command = apply_cmd, command_prereq = amInRepository, command_get_arg_possibilities = list_files, command_argdefaults = stdindefault, command_darcsoptions = [verify, reply, DarcsArguments.cc, verbose, ignoretimes, nocompress, all_gui_interactive, apply_conflict_options, notest, happy_forwarding, leave_test_dir, working_repo_dir, sendmail_cmd, set_scripts_executable, umask_option]} \end{code} \begin{code} apply_cmd :: [DarcsFlag] -> [String] -> IO () apply_cmd opts [patchesfile] = withRepoLock opts $ \repository -> do with_patches_file (fix_filepath "" opts patchesfile) $ \ps -> do am_verbose <- return $ Verbose `elem` opts let from_whom = get_from ps us <- read_repo repository either_them <- get_patch_bundle opts ps them <- case either_them of Right t -> return t Left er -> do forwarded <- consider_forwarding opts ps if forwarded then exitWith ExitSuccess else fail er (_, us', them') <- case get_common_and_uncommon_or_missing (us, them) of Left pinfo -> if pinfo `elem` map fst (concat us) then cannotApplyPartialRepo pinfo else cannotApplyMissing pinfo Right x -> return x when (null $ head them') $ do putStr $ "All these patches have already been applied. " ++ "Nothing to do.\n" exitWith ExitSuccess s <- slurp_recorded repository let their_ps = map fromJustTheirPatch $ reverse $ head them' with_selected_changes "apply" fixed_opts s their_ps (Just $ length their_ps) $ \ (_,to_be_applied) -> do when (null to_be_applied) $ do putStrLn "You don't want to apply any patches, so I'm exiting!" exitWith ExitSuccess check_paths opts to_be_applied redirect_output opts from_whom $ do when am_verbose $ putStrLn "We have the following extra patches:" when am_verbose $ putDocLn $ vcat $ map (human_friendly.fst) $ head us' when am_verbose $ putStrLn "Will apply the following patches:" when am_verbose $ putDocLn $ vcat $ map (human_friendly.fromJust.patch2patchinfo) $ to_be_applied (us_patch, work_patch) <- merge_with_us_and_pending opts (map fromJustOurPatch $ reverse $ head us', to_be_applied) recorded_with_pending <- slurp_pending repository working <- co_slurp recorded_with_pending "." standard_resolved_pw <- standard_resolution work_patch announce_merge_conflicts opts standard_resolved_pw check_unrecorded_conflicts us_patch pw_resolved <- if AllowConflicts `elem` opts then join_patches `liftM` no_resolution work_patch else case want_external_merge opts of Nothing -> return $ join_patches standard_resolved_pw Just c -> do pend <- get_unrecorded repository (AnyOrder:opts) join_patches `liftM` external_resolution c working (join_patches $ (++catMaybes [pend]) $ map (fromJust.snd) $ reverse $ head us') (join_patches $ map (fromJust.snd) $ reverse $ head them') work_patch when am_verbose $ putStrLn "Applying patches to the local directories..." when (not (NoTest `elem` opts) && Test `elem` opts) $ do testproblem <- test_patch opts us_patch when (testproblem /= ExitSuccess) $ do putStrLnError "Error in test..." exitWith $ ExitFailure 1 tokens <- save_patches repository opts $ unjoin_patches us_patch mp <- get_unrecorded repository (AnyOrder:opts) let npend = join_patches [invert us_patch, fromMaybePatch mp, pw_resolved] withSignalsBlocked $ with_new_pending repository npend $ do applyToPristine repository us_patch `catch` \e -> fail ("Error applying patch to recorded!\nRunning 'darcs repair' on the target repository may help.\n" ++ show e) wait_a_moment -- so work will be more recent than rec updateInventory repository tokens applyToWorking repository opts pw_resolved `catch` \e -> fail ("Error applying patch to working dir:\n" ++ show e) sync_repo repository putStrLn "Finished applying..." exitWith ExitSuccess where fixed_opts = if Gui `elem` opts || Interactive `elem` opts then opts else All : opts cannotApplyMissing pinfo = errorDoc $ text "Cannot apply this patch bundle, since we're missing:" $$ human_friendly pinfo fromJustTheirPatch (pinfo, Nothing) = cannotApplyMissing pinfo fromJustTheirPatch (_, Just p) = p cannotApplyPartialRepo pinfo = errorDoc $ text ("Cannot apply this patch bundle, " ++ "this is a \"--partial repository") $$ text "We don't have the following patch:" $$ human_friendly pinfo fromJustOurPatch (pinfo, Nothing) = cannotApplyPartialRepo pinfo fromJustOurPatch (_, Just p) = p fromMaybePatch Nothing = null_patch fromMaybePatch (Just p) = p apply_cmd _ _ = impossible \end{code} Darcs apply accepts a single argument, which is the name of the patch file to be applied. If you omit this argument, the patch is read from standard input.\footnote{One caveat: don't name your patch file ``magic darcs standard input'', or darcs will read from standard input instead!} This allows you to use apply with a pipe from your email program, for example. \begin{code} with_patches_file :: FilePath -> (PackedString -> IO a) -> IO a with_patches_file fn c | fn == stdin_magic = do ps <- hGetContentsPS stdin c ps | otherwise = do ps <- readFilePS fn c ps \end{code} \begin{options} --verify \end{options} If you specify the \verb!--verify PUBRING! option, darcs will check that the patch was GPG-signed by a key which is in \verb!PUBRING! and will refuse to apply the patch otherwise. \begin{code} get_patch_bundle :: [DarcsFlag] -> PackedString -> IO (Either String PatchSet) get_patch_bundle opts fps = do mps <- verifyPS opts $ read_email fps mops <- verifyPS opts fps case (mps, mops) of (Nothing, Nothing) -> return $ Left "Patch bundle not properly signed, or gpg failed." (Just ps, Nothing) -> return $ scan_bundle ps (Nothing, Just ps) -> return $ scan_bundle ps -- We use careful_scan_bundle only below because in either of the two -- above case we know the patch was signed, so it really shouldn't -- need stripping of CRs. (Just ps1, Just ps2) -> case careful_scan_bundle ps1 of Left _ -> return $ careful_scan_bundle ps2 Right x -> return $ Right x where careful_scan_bundle ps = case scan_bundle ps of Left e -> case scan_bundle $ stripCrPS ps of Right x -> Right x _ -> Left e x -> x stripCrPS :: PackedString -> PackedString stripCrPS ps = unlinesPS $ map stripline $ linesPS ps stripline p | nullPS p = p | lastPS p == '\r' = initPS p | otherwise = p \end{code} \begin{options} --cc, --reply \end{options} If you give the \verb!--reply FROM! option to \verb!darcs apply!, it will send the results of the application to the sender of the patch. This only works if the patch is in the form of email with its headers intact, so that darcs can actually know the origin of the patch. The reply email will indicate whether or not the patch was successfully applied. The \verb!FROM! flag is the email address that will be used as the ``from'' address when replying. If the darcs apply is being done automatically, it is important that this address not be the same as the address at which the patch was received, in order to avoid automatic email loops. If you want to also send the apply email to another address (for example, to create something like a ``commits'' mailing list), you can use the \verb!--cc! option to specify additional recipients. Note that the \verb!--cc! option \emph{requires} the \verb!--reply! option, which provides the ``From'' address. The \verb!--reply! feature of apply is intended primarily for two uses. When used by itself, it is handy for when you want to apply patches sent to you by other developers so that they will know when their patch has been applied. For example, in my \verb!.muttrc! (the config file for my mailer) I have: \begin{verbatim} macro pager A "darcs apply --verbose \ --reply droundy@abridgegame.org --repodir ~/darcs \end{verbatim} which allows me to apply a patch to darcs directly from my mailer, with the originator of that patch being sent a confirmation when the patch is successfully applied. NOTE: In an attempt to make sure no one else can read your email, mutt seems to set the umask such that patches created with the above macro are not world-readable, so use it with care. When used in combination with the \verb!--verify! option, the \verb!--reply! option allows for a nice pushable repository. When these two options are used together, any patches that don't pass the verify will be forwarded to the \verb!FROM! address of the \verb!--reply! option. This allows you to set up a repository so that anyone who is authorized can push to it and have it automatically applied, but if a stranger pushes to it, the patch will be forwarded to you. Please (for your own sake!)\ be certain that the \verb!--reply FROM! address is different from the one used to send patches to a pushable repository, since otherwise an unsigned patch will be forwarded to the repository in an infinite loop. If you use \verb!darcs apply --verify PUBRING --reply! to create a pushable repository by applying patches automatically as they are received by email, you will also want to use the \verb!--dont-allow-conflicts! option. \begin{options} --dont-allow-conflicts \end{options} The \verb!--dont-allow-conflicts! flag causes apply to fail when applying a patch would cause conflicts. This flag is recommended on repositories which will be pushed to or sent to. \begin{options} --allow-conflicts \end{options} \verb!--allow-conflicts! will allow conflicts, but will keep the local and recorded versions in sync on the repository. This means the conflict will exist in both locations until it is resolved. \begin{options} --mark-conflicts \end{options} \verb!--mark-conflicts! will add conflict markers to illustrate the the conflict. \begin{code} announce_merge_conflicts :: [DarcsFlag] -> [Patch] -> IO () announce_merge_conflicts opts resolved_pw = case nubsort $ list_touched_files $ join_patches $ tail resolved_pw of [] -> return () cfs -> if MarkConflicts `elem` opts || AllowConflicts `elem` opts || want_external_merge opts /= Nothing then do putStrLn "We have conflicts in the following files:" putStrLn $ unwords cfs else do putStrLn "There are conflicts in the following files:" putStrLn $ unwords cfs fail $ "Refusing to apply patches leading to conflicts.\n"++ "If you would rather apply the patch and mark the conflicts,\n"++ "use the --mark-conflicts option to apply." \end{code} \begin{options} --external-merge \end{options} You can use an external interactive merge tool to resolve conflicts with the flag \verb!--external-merge!. For more details see subsection~\ref{resolution}. \begin{options} --all, --gui, --interactive \end{options} If you provide the \verb!--interactive! or \verb!--gui! flag, darcs will ask you for each change in the patch bundle whether or not you wish to apply that change. The opposite is the \verb!--all! flag, which can be used to override an \verb!interactive! or \verb!gui! which might be set in your ``defaults'' file. NOTE: The GUI is not currently functional, but is expected to re-appear in a future release. \begin{options} --sendmail-command \end{options} If you want to use a command different from the default one for sending mail, you need to specify a command line with the \verb!--sendmail-command! option. The command line can contain the format specifier \verb!%t! for to and you can add \verb!% String get_from ps = readFrom $ linesPS ps where readFrom [] = "" readFrom (x:xs) | takePS 5 x == from_start = unpackPS $ dropPS 5 x | otherwise = readFrom xs redirect_output :: [DarcsFlag] -> String -> IO a -> IO a redirect_output opts to doit = ro opts where cc = get_cc opts scmd = get_sendmail_cmd opts ro [] = doit ro (Reply f:_) = withStdoutTemp $ \tempf-> do {a <- doit; hClose stdout; hClose stderr; return a; } `catch` (sendit tempf) where sendit tempf e@(ExitException ExitSuccess) = do body <- sanitizeFile tempf sendEmail f to "Patch applied" cc scmd body throwIO e sendit tempf (ExitException _) = do body <- sanitizeFile tempf sendEmail f to "Patch failed!" cc scmd body throwIO $ ExitException ExitSuccess sendit tempf e = do body <- sanitizeFile tempf sendEmail f to "Darcs error applying patch!" cc scmd $ body ++ "\n\nCaught exception:\n"++ show e++"\n" throwIO $ ExitException ExitSuccess ro (_:fs) = ro fs -- sanitizeFile is used to clean up the stdout/stderr before sticking it in -- an email. sanitizeFile :: FilePath -> IO String sanitizeFile f = sanitize `liftM` readBinFile f where sanitize s = wash $ remove_backspaces "" s wash ('\000':s) = "\\NUL" ++ wash s wash ('\026':s) = "\\EOF" ++ wash s wash (c:cs) = c : wash cs wash [] = [] remove_backspaces rev_sofar "" = reverse rev_sofar remove_backspaces (_:rs) ('\008':s) = remove_backspaces rs s remove_backspaces "" ('\008':s) = remove_backspaces "" s remove_backspaces rs (s:ss) = remove_backspaces (s:rs) ss throwIO :: Exception -> IO a throwIO e = return $ throw e \end{code} \begin{code} forwarding_message :: PackedString forwarding_message = packString $ "The following patch was either unsigned, or signed by a non-allowed\n"++ "key, or there was a GPG failure.\n" consider_forwarding :: [DarcsFlag] -> PackedString -> IO Bool consider_forwarding opts m = cf opts (get_cc opts) where cf [] _ = return False cf (Reply t:_) cc = case break is_from (linesPS m) of (m1, f:m2) -> let m_lines = forwarding_message:m1 ++ m2 m' = unlinesPS m_lines f' = unpackPS (dropPS 5 f) in if t == f' || t == init f' then return False -- Refuse possible email loop. else do let scmd = get_sendmail_cmd opts if HappyForwarding `elem` opts then resendEmail t scmd m else sendEmailDoc f' t "A forwarded darcs patch" cc scmd (Just (empty,empty)) (packedString m') return True _ -> return False -- Don't forward emails lacking headers! cf (_:fs) cc = cf fs cc is_from l = takePS 5 l == from_start from_start :: PackedString from_start = packString "From:" \end{code} \begin{options} --no-test, --test \end{options} If you specify the \verb!--test! option, apply will run the test (if a test exists) prior to applying the patch. If the test fails, the patch is not applied. In this case, if the \verb!--reply! option was used, the results of the test are sent in the reply email. You can also specify the \verb!--no-test! option, which will override the \verb!--test! option, and prevent the test from being run. This is helpful when setting up a pushable repository, to keep users from running code.