repair: Remove damaged git-annex sync branches.

This commit is contained in:
Joey Hess 2013-12-10 16:17:49 -04:00
parent b37323d857
commit e6c4f550d8
4 changed files with 31 additions and 21 deletions

View file

@ -10,7 +10,7 @@
module Assistant.Repair where
import Assistant.Common
import Command.Repair (repairAnnexBranch)
import Command.Repair (repairAnnexBranch, trackingOrSyncBranch)
import Git.Fsck (FsckResults, foundBroken)
import Git.Repair (runRepairOf)
import qualified Git
@ -99,7 +99,7 @@ runRepair u mrmt destructiverepair = do
repair fsckresults referencerepo = do
(ok, modifiedbranches) <- inRepo $
runRepairOf fsckresults destructiverepair referencerepo
runRepairOf fsckresults trackingOrSyncBranch destructiverepair referencerepo
when destructiverepair $
repairAnnexBranch modifiedbranches
return ok

View file

@ -28,7 +28,7 @@ start = next $ next $ runRepair =<< Annex.getState Annex.force
runRepair :: Bool -> Annex Bool
runRepair forced = do
(ok, modifiedbranches) <- inRepo $
Git.Repair.runRepair forced
Git.Repair.runRepair isAnnexSyncBranch forced
-- This command can be run in git repos not using git-annex,
-- so avoid git annex branch stuff in that case.
whenM (isJust <$> getVersion) $
@ -67,3 +67,9 @@ repairAnnexBranch modifiedbranches
Annex.Branch.forceCommit "committing index after git repository repair"
liftIO $ putStrLn "Successfully recovered the git-annex branch using .git/annex/index"
nukeindex = inRepo $ nukeFile . gitAnnexIndex
trackingOrSyncBranch :: Ref -> Bool
trackingOrSyncBranch b = Git.Repair.isTrackingBranch b || isAnnexSyncBranch b
isAnnexSyncBranch :: Ref -> Bool
isAnnexSyncBranch b = "refs/synced/" `isPrefixOf` show b

View file

@ -13,11 +13,11 @@ module Git.Repair (
cleanCorruptObjects,
retrieveMissingObjects,
resetLocalBranches,
removeTrackingBranches,
checkIndex,
checkIndexFast,
missingIndex,
emptyGoodCommits,
isTrackingBranch,
) where
import Common
@ -189,15 +189,17 @@ resetLocalBranches missing goodcommits r =
, Param (show c)
] r
isTrackingBranch :: Ref -> Bool
isTrackingBranch b = "refs/remotes/" `isPrefixOf` show b
{- To deal with missing objects that cannot be recovered, removes
- any remote tracking branches that reference them. Returns a list of
- all removed branches.
- any branches (filtered by a predicate) that reference them
- Returns a list of all removed branches.
-}
removeTrackingBranches :: MissingObjects -> GoodCommits -> Repo -> IO ([Branch], GoodCommits)
removeTrackingBranches missing goodcommits r =
go [] goodcommits =<< filter istrackingbranch <$> getAllRefs r
removeBadBranches :: (Ref -> Bool) -> MissingObjects -> GoodCommits -> Repo -> IO ([Branch], GoodCommits)
removeBadBranches removablebranch missing goodcommits r =
go [] goodcommits =<< filter removablebranch <$> getAllRefs r
where
istrackingbranch b = "refs/remotes/" `isPrefixOf` show b
go removed gcs [] = return (removed, gcs)
go removed gcs (b:bs) = do
(ok, gcs') <- verifyCommit missing gcs b r
@ -434,24 +436,24 @@ preRepair g = do
validhead s = "ref: refs/" `isPrefixOf` s || isJust (extractSha s)
{- Put it all together. -}
runRepair :: Bool -> Repo -> IO (Bool, [Branch])
runRepair forced g = do
runRepair :: (Ref -> Bool) -> Bool -> Repo -> IO (Bool, [Branch])
runRepair removablebranch forced g = do
preRepair g
putStrLn "Running git fsck ..."
fsckresult <- findBroken False g
if foundBroken fsckresult
then runRepair' fsckresult forced Nothing g
then runRepair' removablebranch fsckresult forced Nothing g
else do
putStrLn "No problems found."
return (True, [])
runRepairOf :: FsckResults -> Bool -> Maybe FilePath -> Repo -> IO (Bool, [Branch])
runRepairOf fsckresult forced referencerepo g = do
runRepairOf :: FsckResults -> (Ref -> Bool) -> Bool -> Maybe FilePath -> Repo -> IO (Bool, [Branch])
runRepairOf fsckresult removablebranch forced referencerepo g = do
preRepair g
runRepair' fsckresult forced referencerepo g
runRepair' removablebranch fsckresult forced referencerepo g
runRepair' :: FsckResults -> Bool -> Maybe FilePath -> Repo -> IO (Bool, [Branch])
runRepair' fsckresult forced referencerepo g = do
runRepair' :: (Ref -> Bool) -> FsckResults -> Bool -> Maybe FilePath -> Repo -> IO (Bool, [Branch])
runRepair' removablebranch fsckresult forced referencerepo g = do
missing <- cleanCorruptObjects fsckresult g
stillmissing <- retrieveMissingObjects missing referencerepo g
case stillmissing of
@ -490,7 +492,8 @@ runRepair' fsckresult forced referencerepo g = do
| otherwise -> unsuccessfulfinish
where
continuerepairs stillmissing = do
(remotebranches, goodcommits) <- removeTrackingBranches stillmissing emptyGoodCommits g
(removedbranches, goodcommits) <- removeBadBranches removablebranch stillmissing emptyGoodCommits g
let remotebranches = filter isTrackingBranch removedbranches
unless (null remotebranches) $
putStrLn $ unwords
[ "Removed"
@ -528,7 +531,7 @@ runRepair' fsckresult forced referencerepo g = do
-- The corrupted index can prevent fsck from finding other
-- problems, so re-run repair.
fsckresult' <- findBroken False g
result <- runRepairOf fsckresult' forced referencerepo g
result <- runRepairOf fsckresult' removablebranch forced referencerepo g
putStrLn "Removed the corrupted index file. You should look at what files are present in your working tree and git add them back to the index when appropriate."
return result

3
debian/changelog vendored
View file

@ -22,7 +22,8 @@ git-annex (5.20131131) UNRELEASED; urgency=low
* Windows: Support annex.diskreserve.
* Fix bad behavior in Firefox, which was caused by an earlier fix to
bad behavior in Chromium.
* Improve repair of git-annex index file.
* repair: Improve repair of git-annex index file.
* repair: Remove damaged git-annex sync branches.
-- Joey Hess <joeyh@debian.org> Sun, 01 Dec 2013 13:57:58 -0400