% 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 repair} \begin{code} module Darcs.Commands.Repair ( repair ) where import Workaround ( getCurrentDirectory ) import System.IO import System.Exit ( exitWith, ExitCode(..) ) import Control.Monad ( when, ) import Darcs.Commands import Darcs.Arguments ( DarcsFlag( Verbose, Quiet ), working_repo_dir, umask_option, ) import Darcs.Patch ( RepoPatch, patch2patchinfo ) import Darcs.Patch.Patchy ( applyAndTryToFix ) import Darcs.Patch.Info ( human_friendly ) import Darcs.Patch.Ordered ( FL(..), RL(..), lengthFL, reverseFL, reverseRL, concatRL ) import Darcs.Hopefully ( PatchInfoAnd, info ) import Darcs.Repository ( Repository, withRepoLock, ($-), amInRepository, read_repo, writePatchSet, makePatchLazy, checkPristineAgainstCwd, replacePristine ) import Darcs.Repository.Checkpoint ( get_checkpoint_by_default ) import Darcs.Global ( darcsdir ) import Darcs.Progress ( debugMessage, beginTedious, endTedious, tediousSize, finishedOneIO ) import Darcs.Patch.Depends ( get_patches_beyond_tag ) import Darcs.Lock( withTempDir ) import Darcs.Commands.Check ( check_uniqueness ) import Darcs.Sealed ( Sealed(..), unsafeUnflippedseal ) import Darcs.Utils ( catchall, withCurrentDirectory ) import Printer ( putDocLn, text ) \end{code} \options{repair} \begin{code} repair_description :: String repair_description = "Repair the corrupted repository." \end{code} \haskell{repair_help} \begin{code} repair_help :: String repair_help = "Repair attempts to fix corruption that may have entered your\n"++ "repository.\n" \end{code} \begin{code} repair :: DarcsCommand repair = DarcsCommand {command_name = "repair", command_help = repair_help, command_description = repair_description, command_extra_args = 0, command_extra_arg_help = [], command_command = repair_cmd, command_prereq = amInRepository, command_get_arg_possibilities = return [], command_argdefaults = nodefaults, command_advanced_options = [umask_option], command_basic_options = [working_repo_dir]} \end{code} Repair currently will only repair damage to the pristine tree. Fortunately this is just the sort of corruption that is most likely to happen. \begin{code} repair_cmd :: [DarcsFlag] -> [String] -> IO () repair_cmd opts _ = withRepoLock opts $- \repository -> do let putVerbose s = when (Verbose `elem` opts) $ putDocLn s putInfo s = when (not $ Quiet `elem` opts) $ putDocLn s check_uniqueness putVerbose putInfo repository maybe_chk <- get_checkpoint_by_default repository formerdir <- getCurrentDirectory withTempDir (formerdir++"/"++darcsdir++"/newpristine") $ \newcur -> do putVerbose $ text "Applying patches..." case maybe_chk of Just chk -> do let chtg = patch2patchinfo chk putVerbose $ text "I am repairing from a checkpoint." Sealed patches <- read_repo repository applyAndTryToFix chk applyAndFix repository (reverseRL $ concatRL $ unsafeUnflippedseal $ get_patches_beyond_tag chtg patches) return () Nothing -> do debugMessage "Fixing any broken patches..." Sealed rawpatches <- read_repo repository let psin = reverseRL $ concatRL rawpatches ps <- applyAndFix repository psin withCurrentDirectory formerdir $ writePatchSet (reverseFL ps :<: NilRL) opts debugMessage "Done fixing broken patches..." is_same <- checkPristineAgainstCwd repository `catchall` return False if is_same then do putStrLn "The repository is already consistent, no changes made." exitWith ExitSuccess else do putStrLn "Fixing pristine tree..." replacePristine repository newcur exitWith ExitSuccess applyAndFix :: RepoPatch p => Repository p -> FL (PatchInfoAnd p) -> IO (FL (PatchInfoAnd p)) applyAndFix _ NilFL = return NilFL applyAndFix r psin = do beginTedious k tediousSize k $ lengthFL psin ps <- aaf psin endTedious k return ps where k = "Repairing patch" aaf NilFL = return NilFL aaf (p:>:ps) = do mp' <- applyAndTryToFix p finishedOneIO k $ show $ human_friendly $ info p p' <- case mp' of Nothing -> return p Just (e,pp) -> do putStrLn e return pp p'' <- makePatchLazy r p' ps' <- aaf ps return (p'':>:ps') \end{code}