git-annex/Command/Repair.hs
Joey Hess 40ecf58d4b
update licenses from GPL to AGPL
This does not change the overall license of the git-annex program, which
was already AGPL due to a number of sources files being AGPL already.

Legally speaking, I'm adding a new license under which these files are
now available; I already released their current contents under the GPL
license. Now they're dual licensed GPL and AGPL. However, I intend
for all my future changes to these files to only be released under the
AGPL license, and I won't be tracking the dual licensing status, so I'm
simply changing the license statement to say it's AGPL.

(In some cases, others wrote parts of the code of a file and released it
under the GPL; but in all cases I have contributed a significant portion
of the code in each file and it's that code that is getting the AGPL
license; the GPL license of other contributors allows combining with
AGPL code.)
2019-03-13 15:48:14 -04:00

85 lines
2.8 KiB
Haskell

{- git-annex command
-
- Copyright 2013 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
module Command.Repair where
import Command
import qualified Annex
import qualified Git.Repair
import qualified Annex.Branch
import qualified Git.Ref
import Git.Types
import Annex.Version
cmd :: Command
cmd = noCommit $ dontCheck repoExists $
command "repair" SectionMaintenance
"recover broken git repository"
paramNothing (withParams seek)
seek :: CmdParams -> CommandSeek
seek = withNothing (commandAction start)
start :: CommandStart
start = next $ next $ runRepair =<< Annex.getState Annex.force
runRepair :: Bool -> Annex Bool
runRepair forced = do
(ok, modifiedbranches) <- inRepo $
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) $
repairAnnexBranch modifiedbranches
return ok
{- After git repository repair, the .git/annex/index file could
- still be broken, by pointing to bad objects, or might just be corrupt on
- its own. Since this index file is not used to stage things
- for long durations of time, it can safely be deleted if it is broken.
-
- Otherwise, if the git-annex branch was modified by the repair,
- commit the index file to the git-annex branch.
- This way, if the git-annex branch got rewound to an old version by
- the repository repair, or was completely deleted, this will get it back
- to a good state. Note that in the unlikely case where the git-annex
- branch was rewound to a state that, had new changes from elsewhere not
- yet reflected in the index, this does properly merge those into the
- index before committing.
-}
repairAnnexBranch :: [Branch] -> Annex ()
repairAnnexBranch modifiedbranches
| Annex.Branch.fullname `elem` modifiedbranches = ifM okindex
( commitindex
, do
nukeindex
missingbranch
)
| otherwise = ifM okindex
( noop
, do
nukeindex
ifM (null <$> inRepo (Git.Ref.matching [Annex.Branch.fullname]))
( missingbranch
, liftIO $ putStrLn "No data was lost."
)
)
where
okindex = Annex.Branch.withIndex $ inRepo Git.Repair.checkIndex
commitindex = do
Annex.Branch.forceCommit "committing index after git repository repair"
liftIO $ putStrLn "Successfully recovered the git-annex branch using .git/annex/index"
nukeindex = do
inRepo $ nukeFile . gitAnnexIndex
liftIO $ putStrLn "Had to delete the .git/annex/index file as it was corrupt."
missingbranch = liftIO $ putStrLn "Since the git-annex branch is not up-to-date anymore. It would be a very good idea to run: git annex fsck --fast"
trackingOrSyncBranch :: Ref -> Bool
trackingOrSyncBranch b = Git.Repair.isTrackingBranch b || isAnnexSyncBranch b
isAnnexSyncBranch :: Ref -> Bool
isAnnexSyncBranch b = "refs/synced/" `isPrefixOf` fromRef b