implemented upgrade of direct mode repo to v6

This commit is contained in:
Joey Hess 2015-12-15 15:56:37 -04:00
parent cdd27b8920
commit f9d077186a
Failed to extract signature
4 changed files with 101 additions and 15 deletions

View file

@ -753,13 +753,14 @@ moveBad key = do
logStatus key InfoMissing
return dest
data KeyLocation = InAnnex | InRepository
data KeyLocation = InAnnex | InRepository | InAnywhere
{- List of keys whose content exists in the specified location.
- InAnnex only lists keys with content in .git/annex/objects,
- while InRepository, in direct mode, also finds keys with content
- in the work tree.
- in the work tree. InAnywhere lists all keys that have directories
- in .git/annex/objects, whether or not the content is present.
-
- Note that InRepository has to check whether direct mode files
- have goodContent.
@ -788,6 +789,11 @@ getKeysPresent keyloc = do
morekeys <- unsafeInterleaveIO a
continue (morekeys++keys) as
inanywhere = case keyloc of
InAnywhere -> True
_ -> False
present _ _ _ | inanywhere = pure True
present _ False d = presentInAnnex d
present s True d = presentDirect s d <||> presentInAnnex d
@ -800,6 +806,7 @@ getKeysPresent keyloc = do
Nothing -> return False
Just k -> Annex.eval s $
anyM (Direct.goodContent k) =<< Direct.associatedFiles k
InAnywhere -> return True
{- In order to run Annex monad actions within unsafeInterleaveIO,
- the current state is taken and reused. No changes made to this

View file

@ -1,4 +1,4 @@
{- git-annex v5 -> v6 uppgrade support
{- git-annex v5 -> v6 upgrade support
-
- Copyright 2015 Joey Hess <id@joeyh.name>
-
@ -10,11 +10,36 @@ module Upgrade.V5 where
import Common.Annex
import Config
import Annex.InodeSentinal
import Annex.Link
import Annex.Direct
import Annex.Content
import Annex.WorkTree
import qualified Database.Keys
import qualified Annex.Content.Direct as Direct
import qualified Git
import qualified Git.LsFiles
import qualified Git.Branch
import Git.FileMode
upgrade :: Bool -> Annex Bool
upgrade automatic = do
unless automatic $
showAction "v5 to v6"
whenM isDirect $ do
{- Since upgrade from direct mode changes how files
- are represented in git, commit any changes in the
- work tree first. -}
whenM stageDirect $ do
unless automatic $
showAction "committing first"
upgradeDirectCommit automatic
"commit before upgrade to annex.version 6"
setDirect False
upgradeDirectWorkTree
removeDirectCruft
showLongNote "Upgraded repository out of direct mode."
showLongNote "Changes have been staged for all annexed files in this repository; you should run `git commit` to commit these changes."
showLongNote "Any other clones of this repository that use direct mode need to be upgraded now, too."
configureSmudgeFilter
-- Inode sentinal file was only used in direct mode and when
-- locking down files as they were added. In v6, it's used more
@ -23,3 +48,55 @@ upgrade automatic = do
unlessM (isDirect) $
createInodeSentinalFile True
return True
upgradeDirectCommit :: Bool -> String -> Annex ()
upgradeDirectCommit automatic msg =
void $ inRepo $ Git.Branch.commitCommand commitmode
[ Param "-m"
, Param msg
]
where
commitmode = if automatic then Git.Branch.AutomaticCommit else Git.Branch.ManualCommit
{- Walk work tree from top and convert all annex symlinks to pointer files,
- staging them in the index, and updating the work tree files with
- either the content of the object, or the pointer file content. -}
upgradeDirectWorkTree :: Annex ()
upgradeDirectWorkTree = do
top <- fromRepo Git.repoPath
(l, clean) <- inRepo $ Git.LsFiles.stagedDetails [top]
forM_ l go
void $ liftIO clean
where
go (f, Just _sha, Just mode) | isSymLink mode = do
mk <- lookupFile f
case mk of
Nothing -> noop
Just k -> do
ifM (isJust <$> getAnnexLinkTarget f)
( writepointer f k
, fromdirect f k
)
stagePointerFile f =<< hashPointerFile k
Database.Keys.addAssociatedFile k f
return ()
go _ = noop
fromdirect f k = do
-- If linkAnnex fails for some reason, the work tree file
-- still has the content; the annex object file is just
-- not populated with it. Since the work tree file
-- is recorded as an associated file, things will still
-- work that way, it's just not ideal.
void $ linkAnnex k f
writepointer f k = liftIO $ do
nukeFile f
writeFile f (formatPointer k)
{- Remove all direct mode bookkeeping files. -}
removeDirectCruft :: Annex ()
removeDirectCruft = mapM_ go =<< getKeysPresent InAnywhere
where
go k = do
Direct.removeInodeCache k
Direct.removeAssociatedFiles k

View file

@ -323,8 +323,12 @@ files to be unlocked, while the indirect upgrades don't touch the files.
* Dropping a smudged file causes git status to show it as modified,
because the timestamp has changed. Getting a smudged file can also
cause this. Avoid this by preserving timestamp of smudged files
when manipulating.
cause this. Upgrading a direct mode repo also leaves files in this state.
User can use `git add` to clear it up, but better to avoid this,
by updating stat info in the index.
(May need to use libgit2 to do this, cannot find
any plumbing except git-update-index, which is very inneficient for
smudged files.)
* Reconcile staged changes into the associated files database, whenever
the database is queried.
* See if the cases where the Keys database is not used can be
@ -335,8 +339,6 @@ files to be unlocked, while the indirect upgrades don't touch the files.
(when not in direct mode).
However, beware over-optimisation breaking the assistant or perhaps other
long-lived processes.
* Make v6 upgrade convert direct mode repo to repo with all unlocked
files.
* Make automatic merge conflict resolution work for pointer files.
- Should probably automatically handle merge conflicts between annex
symlinks and pointer files too. Maybe by always resulting in a pointer

View file

@ -48,6 +48,12 @@ The upgrade events, so far:
The upgrade from v5 to v6 is handled manually. Run `git-annex upgrade`
perform the upgrade.
Warning: All places that a direct mode repository is cloned to should be
running git-annex version 6.x before you upgrade the repository.
This is necessary because the contents of the repository are changed
in the upgrade, and the old version of git-annex won't be able to
access files after the repo is upgraded.
This upgrade does away with the direct mode/indirect mode distinction.
A v6 git-annex repository can have some files locked and other files
unlocked, and all git and git-annex commands can be used on both locked and
@ -65,19 +71,13 @@ The behavior of some commands changes in an upgraded repository:
* `git annex unlock` and `git annex lock` change how the pointer to
the annexed content is stored in git.
All places that a direct mode repository is cloned to should be
running git-annex version 6.x before you upgrade the repository.
This is necessary because the contents of the repository are changed
in the upgrade, and the old version of git-annex won't be able to
access files after the repo is upgraded.
If a repository is only used in indirect mode, you can use git-annex
v5 and v6 in different clones of the same indirect mode repository without
problems.
On upgrade, all files in a direct mode repository will be converted to
unlocked files. The upgrade will need to stage changes to all files in
the git repository.
unlocked files. The upgrade will stage changes to all annexed files in
the git repository, which you can then commit.
If a repository has some clones using direct mode and some using indirect
mode, all the files will end up unlocked in all clones after the upgrade.