Automatically convert direct mode repositories to v7 with adjusted unlocked branches
* Automatically convert direct mode repositories to v7 with adjusted unlocked branches and set annex.thin. * init: When run on a crippled filesystem with --version=5, will error out, since version 7 is needed for adjusted unlocked branch. * direct: This command always errors out as direct mode is no longer supported. * indirect: This command has become a deprecated noop. * proxy: This command is deprecated because it was only needed in direct mode. (But it continues to work.) Also removed mentions of direct mode throughough the documentation. I have not removed all the direct mode code yet.
This commit is contained in:
parent
f6fb4b8cdb
commit
20741b1eb4
27 changed files with 98 additions and 484 deletions
|
@ -8,60 +8,14 @@
|
|||
module Command.Direct where
|
||||
|
||||
import Command
|
||||
import qualified Git
|
||||
import qualified Git.LsFiles
|
||||
import qualified Git.Branch
|
||||
import Config
|
||||
import Annex.Direct
|
||||
import Annex.Version
|
||||
|
||||
cmd :: Command
|
||||
cmd = notBareRepo $ noDaemonRunning $
|
||||
command "direct" SectionSetup "switch repository to direct mode"
|
||||
command "direct" SectionSetup "switch repository to direct mode (deprecated)"
|
||||
paramNothing (withParams seek)
|
||||
|
||||
seek :: CmdParams -> CommandSeek
|
||||
seek = withNothing (commandAction start)
|
||||
|
||||
start :: CommandStart
|
||||
start = ifM versionSupportsDirectMode
|
||||
( ifM isDirect
|
||||
( stop
|
||||
, starting "direct" (ActionItemOther Nothing)
|
||||
perform
|
||||
)
|
||||
, giveup "Direct mode is not supported by this repository version. Use git-annex unlock instead."
|
||||
)
|
||||
|
||||
perform :: CommandPerform
|
||||
perform = do
|
||||
showOutput
|
||||
_ <- inRepo $ Git.Branch.commitCommand Git.Branch.ManualCommit
|
||||
[ Param "-a"
|
||||
, Param "-m"
|
||||
, Param "commit before switching to direct mode"
|
||||
]
|
||||
|
||||
top <- fromRepo Git.repoPath
|
||||
(l, clean) <- inRepo $ Git.LsFiles.inRepo [top]
|
||||
forM_ l go
|
||||
void $ liftIO clean
|
||||
next cleanup
|
||||
where
|
||||
go = whenAnnexed $ \f k -> do
|
||||
toDirectGen k f >>= \case
|
||||
Nothing -> noop
|
||||
Just a -> tryNonAsync a >>= \case
|
||||
Left e -> warnlocked f e
|
||||
Right _ -> return ()
|
||||
return Nothing
|
||||
|
||||
warnlocked :: FilePath -> SomeException -> Annex ()
|
||||
warnlocked f e = do
|
||||
warning $ f ++ ": " ++ show e
|
||||
warning "leaving this file as-is; correct this problem and run git annex fsck on it"
|
||||
|
||||
cleanup :: CommandCleanup
|
||||
cleanup = do
|
||||
setDirect True
|
||||
return True
|
||||
start = giveup "Direct mode is not supported by this repository version. Use git-annex unlock instead."
|
||||
|
|
|
@ -8,89 +8,14 @@
|
|||
module Command.Indirect where
|
||||
|
||||
import Command
|
||||
import qualified Git
|
||||
import qualified Git.Branch
|
||||
import qualified Git.LsFiles
|
||||
import Git.FileMode
|
||||
import Config
|
||||
import qualified Annex
|
||||
import Annex.Direct
|
||||
import Annex.Content
|
||||
import Annex.Content.Direct
|
||||
import Annex.CatFile
|
||||
import Annex.Init
|
||||
import Annex.Ingest
|
||||
|
||||
cmd :: Command
|
||||
cmd = notBareRepo $ noDaemonRunning $
|
||||
command "indirect" SectionSetup "switch repository to indirect mode"
|
||||
command "indirect" SectionSetup "switch repository to indirect mode (deprecated)"
|
||||
paramNothing (withParams seek)
|
||||
|
||||
seek :: CmdParams -> CommandSeek
|
||||
seek = withNothing (commandAction start)
|
||||
|
||||
start :: CommandStart
|
||||
start = ifM isDirect
|
||||
( do
|
||||
unlessM (coreSymlinks <$> Annex.getGitConfig) $
|
||||
giveup "Git is configured to not use symlinks, so you must use direct mode."
|
||||
whenM probeCrippledFileSystem $
|
||||
giveup "This repository seems to be on a crippled filesystem, you must use direct mode."
|
||||
starting "indirect" (ActionItemOther Nothing)
|
||||
perform
|
||||
, stop
|
||||
)
|
||||
|
||||
perform :: CommandPerform
|
||||
perform = do
|
||||
whenM stageDirect $ do
|
||||
showOutput
|
||||
void $ inRepo $ Git.Branch.commitCommand Git.Branch.ManualCommit
|
||||
[ Param "-m"
|
||||
, Param "commit before switching to indirect mode"
|
||||
]
|
||||
|
||||
-- Note that we set indirect mode early, so that we can use
|
||||
-- moveAnnex in indirect mode.
|
||||
setDirect False
|
||||
|
||||
top <- fromRepo Git.repoPath
|
||||
(l, clean) <- inRepo $ Git.LsFiles.stagedOthersDetails [top]
|
||||
forM_ l go
|
||||
void $ liftIO clean
|
||||
next $ return True
|
||||
where
|
||||
{- Walk tree from top and move all present direct mode files into
|
||||
- the annex, replacing with symlinks. Also delete direct mode
|
||||
- caches and mappings. -}
|
||||
go (f, Just sha, Just mode) | isSymLink mode = do
|
||||
r <- liftIO $ catchMaybeIO $ getSymbolicLinkStatus f
|
||||
case r of
|
||||
Just s
|
||||
| isSymbolicLink s -> void $ flip whenAnnexed f $
|
||||
\_ k -> do
|
||||
removeInodeCache k
|
||||
removeAssociatedFiles k
|
||||
return Nothing
|
||||
| otherwise ->
|
||||
maybe noop (fromdirect f)
|
||||
=<< catKey sha
|
||||
_ -> noop
|
||||
go _ = noop
|
||||
|
||||
fromdirect f k = do
|
||||
removeInodeCache k
|
||||
removeAssociatedFiles k
|
||||
whenM (liftIO $ not . isSymbolicLink <$> getSymbolicLinkStatus f) $ do
|
||||
v <- tryNonAsync (moveAnnex k f)
|
||||
case v of
|
||||
Right True -> do
|
||||
l <- calcRepo $ gitAnnexLink f k
|
||||
liftIO $ createSymbolicLink l f
|
||||
Right False -> warnlocked "Failed to move file to annex"
|
||||
Left e -> catchNonAsync (restoreFile f k e) $
|
||||
warnlocked . show
|
||||
|
||||
warnlocked msg = do
|
||||
warning msg
|
||||
warning "leaving this file as-is; correct this problem and run git annex add on it"
|
||||
start = stop
|
||||
|
|
|
@ -8,23 +8,11 @@
|
|||
module Command.Proxy where
|
||||
|
||||
import Command
|
||||
import Config
|
||||
import Utility.Tmp.Dir
|
||||
import Utility.Env
|
||||
import Annex.Direct
|
||||
import Annex.Tmp
|
||||
import qualified Git
|
||||
import qualified Git.Sha
|
||||
import qualified Git.Ref
|
||||
import qualified Git.Branch
|
||||
import qualified Git.LsFiles
|
||||
import Git.FilePath
|
||||
import Utility.CopyFile
|
||||
|
||||
cmd :: Command
|
||||
cmd = notBareRepo $
|
||||
command "proxy" SectionPlumbing
|
||||
"safely bypass direct mode guard"
|
||||
"safely bypass direct mode guard (deprecated)"
|
||||
("-- git command") (withParams seek)
|
||||
|
||||
seek :: CmdParams -> CommandSeek
|
||||
|
@ -32,48 +20,4 @@ seek = withWords (commandAction . start)
|
|||
|
||||
start :: [String] -> CommandStart
|
||||
start [] = giveup "Did not specify command to run."
|
||||
start (c:ps) = liftIO . exitWith =<< ifM isDirect
|
||||
( withOtherTmp $ \tmp -> withTmpDirIn tmp "proxy" go
|
||||
, liftIO $ safeSystem c (map Param ps)
|
||||
)
|
||||
where
|
||||
go tmp = do
|
||||
oldref <- fromMaybe Git.Sha.emptyTree
|
||||
<$> (inRepo . maybe Git.Ref.headSha Git.Ref.sha
|
||||
=<< inRepo Git.Branch.currentUnsafe)
|
||||
|
||||
exitcode <- proxy tmp
|
||||
|
||||
cleanupproxy tmp oldref
|
||||
|
||||
return exitcode
|
||||
|
||||
proxy tmp = do
|
||||
usetmp <- liftIO $ Just . addEntry "GIT_WORK_TREE" tmp <$> getEnvironment
|
||||
|
||||
-- Set up the tmp work tree, to contain both a checkout of all
|
||||
-- staged files as well as hard links (or copies) of any
|
||||
-- unstaged files.
|
||||
unlessM (isNothing <$> inRepo Git.Branch.current) $
|
||||
unlessM (liftIO $ boolSystemEnv "git" [Param "checkout", Param "--", Param "."] usetmp) $
|
||||
error "Failed to set up proxy work tree."
|
||||
top <- fromRepo Git.repoPath
|
||||
(fs, cleanup) <- inRepo $ Git.LsFiles.notInRepo True [top]
|
||||
forM_ fs $ \f -> do
|
||||
tf <- inRepo $ toTopFilePath f
|
||||
let tmpf = tmp </> getTopFilePath tf
|
||||
liftIO $ do
|
||||
createDirectoryIfMissing True (takeDirectory tmpf)
|
||||
createLinkOrCopy f tmpf
|
||||
liftIO $ void cleanup
|
||||
|
||||
liftIO $ safeSystemEnv c (map Param ps) usetmp
|
||||
|
||||
-- To merge the changes made by the proxied command into
|
||||
-- the work tree is similar to cleaning up after a
|
||||
-- direct mode merge. But, here we force updates of any
|
||||
-- non-annxed files that were changed by the proxied
|
||||
-- command.
|
||||
cleanupproxy tmp oldref = do
|
||||
updateWorkTree tmp oldref True
|
||||
liftIO $ removeDirectoryRecursive tmp
|
||||
start (c:ps) = liftIO $ exitWith =<< safeSystem c (map Param ps)
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue