repair: Remove damaged git-annex sync branches.
This commit is contained in:
parent
b37323d857
commit
e6c4f550d8
4 changed files with 31 additions and 21 deletions
|
@ -10,7 +10,7 @@
|
||||||
module Assistant.Repair where
|
module Assistant.Repair where
|
||||||
|
|
||||||
import Assistant.Common
|
import Assistant.Common
|
||||||
import Command.Repair (repairAnnexBranch)
|
import Command.Repair (repairAnnexBranch, trackingOrSyncBranch)
|
||||||
import Git.Fsck (FsckResults, foundBroken)
|
import Git.Fsck (FsckResults, foundBroken)
|
||||||
import Git.Repair (runRepairOf)
|
import Git.Repair (runRepairOf)
|
||||||
import qualified Git
|
import qualified Git
|
||||||
|
@ -99,7 +99,7 @@ runRepair u mrmt destructiverepair = do
|
||||||
|
|
||||||
repair fsckresults referencerepo = do
|
repair fsckresults referencerepo = do
|
||||||
(ok, modifiedbranches) <- inRepo $
|
(ok, modifiedbranches) <- inRepo $
|
||||||
runRepairOf fsckresults destructiverepair referencerepo
|
runRepairOf fsckresults trackingOrSyncBranch destructiverepair referencerepo
|
||||||
when destructiverepair $
|
when destructiverepair $
|
||||||
repairAnnexBranch modifiedbranches
|
repairAnnexBranch modifiedbranches
|
||||||
return ok
|
return ok
|
||||||
|
|
|
@ -28,7 +28,7 @@ start = next $ next $ runRepair =<< Annex.getState Annex.force
|
||||||
runRepair :: Bool -> Annex Bool
|
runRepair :: Bool -> Annex Bool
|
||||||
runRepair forced = do
|
runRepair forced = do
|
||||||
(ok, modifiedbranches) <- inRepo $
|
(ok, modifiedbranches) <- inRepo $
|
||||||
Git.Repair.runRepair forced
|
Git.Repair.runRepair isAnnexSyncBranch forced
|
||||||
-- This command can be run in git repos not using git-annex,
|
-- This command can be run in git repos not using git-annex,
|
||||||
-- so avoid git annex branch stuff in that case.
|
-- so avoid git annex branch stuff in that case.
|
||||||
whenM (isJust <$> getVersion) $
|
whenM (isJust <$> getVersion) $
|
||||||
|
@ -67,3 +67,9 @@ repairAnnexBranch modifiedbranches
|
||||||
Annex.Branch.forceCommit "committing index after git repository repair"
|
Annex.Branch.forceCommit "committing index after git repository repair"
|
||||||
liftIO $ putStrLn "Successfully recovered the git-annex branch using .git/annex/index"
|
liftIO $ putStrLn "Successfully recovered the git-annex branch using .git/annex/index"
|
||||||
nukeindex = inRepo $ nukeFile . gitAnnexIndex
|
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
|
||||||
|
|
|
@ -13,11 +13,11 @@ module Git.Repair (
|
||||||
cleanCorruptObjects,
|
cleanCorruptObjects,
|
||||||
retrieveMissingObjects,
|
retrieveMissingObjects,
|
||||||
resetLocalBranches,
|
resetLocalBranches,
|
||||||
removeTrackingBranches,
|
|
||||||
checkIndex,
|
checkIndex,
|
||||||
checkIndexFast,
|
checkIndexFast,
|
||||||
missingIndex,
|
missingIndex,
|
||||||
emptyGoodCommits,
|
emptyGoodCommits,
|
||||||
|
isTrackingBranch,
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Common
|
import Common
|
||||||
|
@ -189,15 +189,17 @@ resetLocalBranches missing goodcommits r =
|
||||||
, Param (show c)
|
, Param (show c)
|
||||||
] r
|
] r
|
||||||
|
|
||||||
|
isTrackingBranch :: Ref -> Bool
|
||||||
|
isTrackingBranch b = "refs/remotes/" `isPrefixOf` show b
|
||||||
|
|
||||||
{- To deal with missing objects that cannot be recovered, removes
|
{- To deal with missing objects that cannot be recovered, removes
|
||||||
- any remote tracking branches that reference them. Returns a list of
|
- any branches (filtered by a predicate) that reference them
|
||||||
- all removed branches.
|
- Returns a list of all removed branches.
|
||||||
-}
|
-}
|
||||||
removeTrackingBranches :: MissingObjects -> GoodCommits -> Repo -> IO ([Branch], GoodCommits)
|
removeBadBranches :: (Ref -> Bool) -> MissingObjects -> GoodCommits -> Repo -> IO ([Branch], GoodCommits)
|
||||||
removeTrackingBranches missing goodcommits r =
|
removeBadBranches removablebranch missing goodcommits r =
|
||||||
go [] goodcommits =<< filter istrackingbranch <$> getAllRefs r
|
go [] goodcommits =<< filter removablebranch <$> getAllRefs r
|
||||||
where
|
where
|
||||||
istrackingbranch b = "refs/remotes/" `isPrefixOf` show b
|
|
||||||
go removed gcs [] = return (removed, gcs)
|
go removed gcs [] = return (removed, gcs)
|
||||||
go removed gcs (b:bs) = do
|
go removed gcs (b:bs) = do
|
||||||
(ok, gcs') <- verifyCommit missing gcs b r
|
(ok, gcs') <- verifyCommit missing gcs b r
|
||||||
|
@ -434,24 +436,24 @@ preRepair g = do
|
||||||
validhead s = "ref: refs/" `isPrefixOf` s || isJust (extractSha s)
|
validhead s = "ref: refs/" `isPrefixOf` s || isJust (extractSha s)
|
||||||
|
|
||||||
{- Put it all together. -}
|
{- Put it all together. -}
|
||||||
runRepair :: Bool -> Repo -> IO (Bool, [Branch])
|
runRepair :: (Ref -> Bool) -> Bool -> Repo -> IO (Bool, [Branch])
|
||||||
runRepair forced g = do
|
runRepair removablebranch forced g = do
|
||||||
preRepair g
|
preRepair g
|
||||||
putStrLn "Running git fsck ..."
|
putStrLn "Running git fsck ..."
|
||||||
fsckresult <- findBroken False g
|
fsckresult <- findBroken False g
|
||||||
if foundBroken fsckresult
|
if foundBroken fsckresult
|
||||||
then runRepair' fsckresult forced Nothing g
|
then runRepair' removablebranch fsckresult forced Nothing g
|
||||||
else do
|
else do
|
||||||
putStrLn "No problems found."
|
putStrLn "No problems found."
|
||||||
return (True, [])
|
return (True, [])
|
||||||
|
|
||||||
runRepairOf :: FsckResults -> Bool -> Maybe FilePath -> Repo -> IO (Bool, [Branch])
|
runRepairOf :: FsckResults -> (Ref -> Bool) -> Bool -> Maybe FilePath -> Repo -> IO (Bool, [Branch])
|
||||||
runRepairOf fsckresult forced referencerepo g = do
|
runRepairOf fsckresult removablebranch forced referencerepo g = do
|
||||||
preRepair g
|
preRepair g
|
||||||
runRepair' fsckresult forced referencerepo g
|
runRepair' removablebranch fsckresult forced referencerepo g
|
||||||
|
|
||||||
runRepair' :: FsckResults -> Bool -> Maybe FilePath -> Repo -> IO (Bool, [Branch])
|
runRepair' :: (Ref -> Bool) -> FsckResults -> Bool -> Maybe FilePath -> Repo -> IO (Bool, [Branch])
|
||||||
runRepair' fsckresult forced referencerepo g = do
|
runRepair' removablebranch fsckresult forced referencerepo g = do
|
||||||
missing <- cleanCorruptObjects fsckresult g
|
missing <- cleanCorruptObjects fsckresult g
|
||||||
stillmissing <- retrieveMissingObjects missing referencerepo g
|
stillmissing <- retrieveMissingObjects missing referencerepo g
|
||||||
case stillmissing of
|
case stillmissing of
|
||||||
|
@ -490,7 +492,8 @@ runRepair' fsckresult forced referencerepo g = do
|
||||||
| otherwise -> unsuccessfulfinish
|
| otherwise -> unsuccessfulfinish
|
||||||
where
|
where
|
||||||
continuerepairs stillmissing = do
|
continuerepairs stillmissing = do
|
||||||
(remotebranches, goodcommits) <- removeTrackingBranches stillmissing emptyGoodCommits g
|
(removedbranches, goodcommits) <- removeBadBranches removablebranch stillmissing emptyGoodCommits g
|
||||||
|
let remotebranches = filter isTrackingBranch removedbranches
|
||||||
unless (null remotebranches) $
|
unless (null remotebranches) $
|
||||||
putStrLn $ unwords
|
putStrLn $ unwords
|
||||||
[ "Removed"
|
[ "Removed"
|
||||||
|
@ -528,7 +531,7 @@ runRepair' fsckresult forced referencerepo g = do
|
||||||
-- The corrupted index can prevent fsck from finding other
|
-- The corrupted index can prevent fsck from finding other
|
||||||
-- problems, so re-run repair.
|
-- problems, so re-run repair.
|
||||||
fsckresult' <- findBroken False g
|
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."
|
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
|
return result
|
||||||
|
|
||||||
|
|
3
debian/changelog
vendored
3
debian/changelog
vendored
|
@ -22,7 +22,8 @@ git-annex (5.20131131) UNRELEASED; urgency=low
|
||||||
* Windows: Support annex.diskreserve.
|
* Windows: Support annex.diskreserve.
|
||||||
* Fix bad behavior in Firefox, which was caused by an earlier fix to
|
* Fix bad behavior in Firefox, which was caused by an earlier fix to
|
||||||
bad behavior in Chromium.
|
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
|
-- Joey Hess <joeyh@debian.org> Sun, 01 Dec 2013 13:57:58 -0400
|
||||||
|
|
||||||
|
|
Loading…
Reference in a new issue