v7 for all repositories

* Default to v7 for new repositories.
* Automatically upgrade v5 repositories to v7.
This commit is contained in:
Joey Hess 2019-08-30 13:54:57 -04:00
parent 1558e03014
commit 3f0eef4baa
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
29 changed files with 127 additions and 482 deletions

View file

@ -26,7 +26,6 @@ module Annex.AdjustedBranch (
propigateAdjustedCommits, propigateAdjustedCommits,
AdjustedClone(..), AdjustedClone(..),
checkAdjustedClone, checkAdjustedClone,
isSupported,
checkVersionSupported, checkVersionSupported,
isGitVersionSupported, isGitVersionSupported,
) where ) where
@ -50,7 +49,6 @@ import Git.Index
import Git.FilePath import Git.FilePath
import qualified Git.LockFile import qualified Git.LockFile
import qualified Git.Version import qualified Git.Version
import Annex.Version
import Annex.CatFile import Annex.CatFile
import Annex.Link import Annex.Link
import Annex.AutoMerge import Annex.AutoMerge
@ -572,7 +570,7 @@ diffTreeToTreeItem dti = TreeItem
(Git.DiffTree.dstmode dti) (Git.DiffTree.dstmode dti)
(Git.DiffTree.dstsha dti) (Git.DiffTree.dstsha dti)
data AdjustedClone = InAdjustedClone | NotInAdjustedClone | NeedUpgradeForAdjustedClone data AdjustedClone = InAdjustedClone | NotInAdjustedClone
{- Cloning a repository that has an adjusted branch checked out will {- Cloning a repository that has an adjusted branch checked out will
- result in the clone having the same adjusted branch checked out -- but - result in the clone having the same adjusted branch checked out -- but
@ -611,18 +609,10 @@ checkAdjustedClone = ifM isBareRepo
case aps of case aps of
Just [p] -> setBasisBranch basis p Just [p] -> setBasisBranch basis p
_ -> giveup $ "Unable to clean up from clone of adjusted branch; perhaps you should check out " ++ Git.Ref.describe origbranch _ -> giveup $ "Unable to clean up from clone of adjusted branch; perhaps you should check out " ++ Git.Ref.describe origbranch
ifM versionSupportsUnlockedPointers return InAdjustedClone
( return InAdjustedClone
, return NeedUpgradeForAdjustedClone
)
isSupported :: Annex Bool
isSupported = versionSupportsAdjustedBranch <&&> liftIO isGitVersionSupported
checkVersionSupported :: Annex () checkVersionSupported :: Annex ()
checkVersionSupported = do checkVersionSupported =
unlessM versionSupportsAdjustedBranch $
giveup "Adjusted branches are only supported in v6 or newer repositories."
unlessM (liftIO isGitVersionSupported) $ unlessM (liftIO isGitVersionSupported) $
giveup "Your version of git is too old; upgrade it to 2.2.0 or newer to use adjusted branches." giveup "Your version of git is too old; upgrade it to 2.2.0 or newer to use adjusted branches."

View file

@ -31,7 +31,6 @@ import Annex.Perms
import Annex.Link import Annex.Link
import Annex.MetaData import Annex.MetaData
import Annex.CurrentBranch import Annex.CurrentBranch
import Annex.Version
import Logs.Location import Logs.Location
import qualified Annex import qualified Annex
import qualified Annex.Queue import qualified Annex.Queue
@ -308,11 +307,9 @@ forceParams = ifM (Annex.getState Annex.force)
-} -}
addUnlocked :: Annex Bool addUnlocked :: Annex Bool
addUnlocked = addUnlocked =
(versionSupportsUnlockedPointers <&&> ((not . coreSymlinks <$> Annex.getGitConfig) <||>
((not . coreSymlinks <$> Annex.getGitConfig) <||> (annexAddUnlocked <$> Annex.getGitConfig) <||>
(annexAddUnlocked <$> Annex.getGitConfig) <||> (maybe False isadjustedunlocked . snd <$> getCurrentBranch)
(maybe False isadjustedunlocked . snd <$> getCurrentBranch)
)
) )
where where
isadjustedunlocked (LinkAdjustment UnlockAdjustment) = True isadjustedunlocked (LinkAdjustment UnlockAdjustment) = True

View file

@ -100,26 +100,20 @@ initialize' :: Maybe RepoVersion -> Annex ()
initialize' mversion = checkCanInitialize $ do initialize' mversion = checkCanInitialize $ do
checkLockSupport checkLockSupport
checkFifoSupport checkFifoSupport
checkCrippledFileSystem mversion checkCrippledFileSystem
unlessM isBareRepo $ do unlessM isBareRepo $ do
hookWrite preCommitHook hookWrite preCommitHook
hookWrite postReceiveHook hookWrite postReceiveHook
setDifferences setDifferences
unlessM (isJust <$> getVersion) $ unlessM (isJust <$> getVersion) $
ifM (crippledFileSystem <&&> (not <$> isBareRepo)) setVersion (fromMaybe defaultVersion mversion)
( setVersion (fromMaybe versionForCrippledFilesystem mversion) configureSmudgeFilter
, setVersion (fromMaybe defaultVersion mversion) showSideAction "scanning for unlocked files"
) scanUnlockedFiles True
whenM versionSupportsUnlockedPointers $ do unlessM isBareRepo $ do
configureSmudgeFilter hookWrite postCheckoutHook
showSideAction "scanning for unlocked files" hookWrite postMergeHook
scanUnlockedFiles True
unlessM isBareRepo $ do
hookWrite postCheckoutHook
hookWrite postMergeHook
AdjustedBranch.checkAdjustedClone >>= \case AdjustedBranch.checkAdjustedClone >>= \case
AdjustedBranch.NeedUpgradeForAdjustedClone ->
void $ upgrade True versionForAdjustedClone
AdjustedBranch.InAdjustedClone -> return () AdjustedBranch.InAdjustedClone -> return ()
AdjustedBranch.NotInAdjustedClone -> AdjustedBranch.NotInAdjustedClone ->
ifM (crippledFileSystem <&&> (not <$> isBareRepo)) ifM (crippledFileSystem <&&> (not <$> isBareRepo))
@ -147,12 +141,12 @@ uninitialize = do
- Checks repository version and handles upgrades too. - Checks repository version and handles upgrades too.
-} -}
ensureInitialized :: Annex () ensureInitialized :: Annex ()
ensureInitialized = do ensureInitialized = ifM isDirect
getVersion >>= maybe needsinit checkUpgrade ( unlessM (catchBoolIO $ upgrade True defaultVersion) $ do
whenM isDirect $ g <- Annex.gitRepo
unlessM (catchBoolIO $ upgrade True versionForAdjustedBranch) $ do giveup $ "Upgrading direct mode repository " ++ Git.repoDescribe g ++ " failed, and direct mode is no longer supported."
g <- Annex.gitRepo , getVersion >>= maybe needsinit checkUpgrade
giveup $ "Upgrading direct mode repository " ++ Git.repoDescribe g ++ " failed, and direct mode is no longer supported." )
where where
needsinit = ifM Annex.Branch.hasSibling needsinit = ifM Annex.Branch.hasSibling
( initialize Nothing Nothing ( initialize Nothing Nothing
@ -204,15 +198,9 @@ probeCrippledFileSystem' tmp = do
) )
#endif #endif
checkCrippledFileSystem :: Maybe RepoVersion -> Annex () checkCrippledFileSystem :: Annex ()
checkCrippledFileSystem mversion = whenM probeCrippledFileSystem $ do checkCrippledFileSystem = whenM probeCrippledFileSystem $ do
warning "Detected a crippled filesystem." warning "Detected a crippled filesystem."
unlessM isBareRepo $ case mversion of
Just ver | ver < versionForCrippledFilesystem ->
giveup $ "Cannot use repo version " ++ show (fromRepoVersion ver) ++ " in a crippled filesystem."
_ -> noop
setCrippledFileSystem True setCrippledFileSystem True
{- Normally git disables core.symlinks itself when the {- Normally git disables core.symlinks itself when the

View file

@ -9,7 +9,6 @@ module Annex.UpdateInstead where
import qualified Annex import qualified Annex
import Annex.Common import Annex.Common
import Annex.Version
import Annex.AdjustedBranch import Annex.AdjustedBranch
import Git.Branch import Git.Branch
import Git.ConfigTypes import Git.ConfigTypes
@ -21,5 +20,4 @@ needUpdateInsteadEmulation = updateinsteadset <&&> isadjusted
where where
updateinsteadset = (== UpdateInstead) . receiveDenyCurrentBranch updateinsteadset = (== UpdateInstead) . receiveDenyCurrentBranch
<$> Annex.getGitConfig <$> Annex.getGitConfig
isadjusted = versionSupportsUnlockedPointers isadjusted = (maybe False (isJust . getAdjustment) <$> inRepo Git.Branch.current)
<&&> (maybe False (isJust . getAdjustment) <$> inRepo Git.Branch.current)

View file

@ -17,22 +17,13 @@ import qualified Annex
import qualified Data.Map as M import qualified Data.Map as M
defaultVersion :: RepoVersion defaultVersion :: RepoVersion
defaultVersion = RepoVersion 5 defaultVersion = RepoVersion 7
latestVersion :: RepoVersion latestVersion :: RepoVersion
latestVersion = RepoVersion 7 latestVersion = RepoVersion 7
supportedVersions :: [RepoVersion] supportedVersions :: [RepoVersion]
supportedVersions = map RepoVersion [5, 7] supportedVersions = map RepoVersion [7]
versionForAdjustedClone :: RepoVersion
versionForAdjustedClone = RepoVersion 7
versionForAdjustedBranch :: RepoVersion
versionForAdjustedBranch = RepoVersion 7
versionForCrippledFilesystem :: RepoVersion
versionForCrippledFilesystem = RepoVersion 7
upgradableVersions :: [RepoVersion] upgradableVersions :: [RepoVersion]
#ifndef mingw32_HOST_OS #ifndef mingw32_HOST_OS
@ -54,18 +45,6 @@ versionField = annexConfig "version"
getVersion :: Annex (Maybe RepoVersion) getVersion :: Annex (Maybe RepoVersion)
getVersion = annexVersion <$> Annex.getGitConfig getVersion = annexVersion <$> Annex.getGitConfig
versionSupportsUnlockedPointers :: Annex Bool
versionSupportsUnlockedPointers = go <$> getVersion
where
go (Just v) | v >= RepoVersion 6 = True
go _ = False
versionSupportsAdjustedBranch :: Annex Bool
versionSupportsAdjustedBranch = versionSupportsUnlockedPointers
versionUsesKeysDatabase :: Annex Bool
versionUsesKeysDatabase = versionSupportsUnlockedPointers
setVersion :: RepoVersion -> Annex () setVersion :: RepoVersion -> Annex ()
setVersion (RepoVersion v) = setConfig versionField (show v) setVersion (RepoVersion v) = setConfig versionField (show v)

View file

@ -10,7 +10,6 @@ module Annex.WorkTree where
import Annex.Common import Annex.Common
import Annex.Link import Annex.Link
import Annex.CatFile import Annex.CatFile
import Annex.Version
import Annex.Content import Annex.Content
import Annex.ReplaceFile import Annex.ReplaceFile
import Annex.CurrentBranch import Annex.CurrentBranch
@ -54,10 +53,7 @@ lookupFileNotHidden = lookupFile' catkeyfile
lookupFile' :: (FilePath -> Annex (Maybe Key)) -> FilePath -> Annex (Maybe Key) lookupFile' :: (FilePath -> Annex (Maybe Key)) -> FilePath -> Annex (Maybe Key)
lookupFile' catkeyfile file = isAnnexLink file >>= \case lookupFile' catkeyfile file = isAnnexLink file >>= \case
Just key -> return (Just key) Just key -> return (Just key)
Nothing -> ifM versionSupportsUnlockedPointers Nothing -> catkeyfile file
( catkeyfile file
, return Nothing
)
{- Modifies an action to only act on files that are already annexed, {- Modifies an action to only act on files that are already annexed,
- and passes the key on to it. -} - and passes the key on to it. -}

View file

@ -17,8 +17,6 @@ import qualified Annex
import Annex.UUID import Annex.UUID
import Annex.AdjustedBranch import Annex.AdjustedBranch
import Annex.Action import Annex.Action
import Annex.Version
import Upgrade
import Types.StandardGroups import Types.StandardGroups
import Logs.PreferredContent import Logs.PreferredContent
import qualified Annex.Branch import qualified Annex.Branch
@ -62,14 +60,13 @@ initRepo True primary_assistant_repo dir desc mgroup = inDir dir $ do
, Param "-m" , Param "-m"
, Param "created repository" , Param "created repository"
] ]
{- Repositories directly managed by the assistant use v7 unlocked {- Repositories directly managed by the assistant use
- with annex.thin set. - an adjusted unlocked branch with annex.thin set.
- -
- Automatic gc is disabled, as it can be slow. Insted, gc is done - Automatic gc is disabled, as it can be slow. Insted, gc is done
- once a day. - once a day.
-} -}
when primary_assistant_repo $ do when primary_assistant_repo $ do
void $ upgrade True versionForAdjustedBranch
void $ enterAdjustedBranch (LinkAdjustment UnlockAdjustment) void $ enterAdjustedBranch (LinkAdjustment UnlockAdjustment)
setConfig (annexConfig "thin") (Git.Config.boolConfig True) setConfig (annexConfig "thin") (Git.Config.boolConfig True)
inRepo $ Git.Command.run inRepo $ Git.Command.run

View file

@ -20,7 +20,6 @@ import Assistant.Drop
import Types.Transfer import Types.Transfer
import Logs.Location import Logs.Location
import qualified Annex.Queue import qualified Annex.Queue
import qualified Git.LsFiles
import Utility.ThreadScheduler import Utility.ThreadScheduler
import qualified Utility.Lsof as Lsof import qualified Utility.Lsof as Lsof
import qualified Utility.DirWatcher as DirWatcher import qualified Utility.DirWatcher as DirWatcher
@ -32,7 +31,6 @@ import Annex.Link
import Annex.Perms import Annex.Perms
import Annex.CatFile import Annex.CatFile
import Annex.InodeSentinal import Annex.InodeSentinal
import Annex.Version
import Annex.CurrentBranch import Annex.CurrentBranch
import qualified Annex import qualified Annex
import Utility.InodeCache import Utility.InodeCache
@ -53,8 +51,7 @@ commitThread :: NamedThread
commitThread = namedThread "Committer" $ do commitThread = namedThread "Committer" $ do
havelsof <- liftIO $ inPath "lsof" havelsof <- liftIO $ inPath "lsof"
delayadd <- liftAnnex $ delayadd <- liftAnnex $
maybe delayaddDefault (return . Just . Seconds) fmap Seconds . annexDelayAdd <$> Annex.getGitConfig
=<< annexDelayAdd <$> Annex.getGitConfig
msg <- liftAnnex Command.Sync.commitMsg msg <- liftAnnex Command.Sync.commitMsg
lockdowndir <- liftAnnex $ fromRepo gitAnnexTmpWatcherDir lockdowndir <- liftAnnex $ fromRepo gitAnnexTmpWatcherDir
liftAnnex $ do liftAnnex $ do
@ -239,19 +236,6 @@ commitStaged msg = do
Command.Sync.updateBranches =<< getCurrentBranch Command.Sync.updateBranches =<< getCurrentBranch
return ok return ok
{- OSX needs a short delay after a file is added before locking it down,
- as pasting a file seems to try to set file permissions or otherwise
- access the file after closing it. -}
delayaddDefault :: Annex (Maybe Seconds)
#ifdef darwin_HOST_OS
delayaddDefault = ifM versionSupportsUnlockedPointers
( return Nothing
, return $ Just $ Seconds 1
)
#else
delayaddDefault = return Nothing
#endif
{- If there are PendingAddChanges, or InProcessAddChanges, the files {- If there are PendingAddChanges, or InProcessAddChanges, the files
- have not yet actually been added to the annex, and that has to be done - have not yet actually been added to the annex, and that has to be done
- now, before committing. - now, before committing.
@ -274,49 +258,22 @@ delayaddDefault = return Nothing
handleAdds :: FilePath -> Bool -> Maybe Seconds -> [Change] -> Assistant [Change] handleAdds :: FilePath -> Bool -> Maybe Seconds -> [Change] -> Assistant [Change]
handleAdds lockdowndir havelsof delayadd cs = returnWhen (null incomplete) $ do handleAdds lockdowndir havelsof delayadd cs = returnWhen (null incomplete) $ do
let (pending, inprocess) = partition isPendingAddChange incomplete let (pending, inprocess) = partition isPendingAddChange incomplete
unlocked <- liftAnnex versionSupportsUnlockedPointers
let lockingfiles = not unlocked
let lockdownconfig = LockDownConfig let lockdownconfig = LockDownConfig
{ lockingFile = lockingfiles { lockingFile = False
, hardlinkFileTmpDir = Just lockdowndir , hardlinkFileTmpDir = Just lockdowndir
} }
(pending', cleanup) <- if unlocked
then return (pending, noop)
else findnew pending
(postponed, toadd) <- partitionEithers (postponed, toadd) <- partitionEithers
<$> safeToAdd lockdowndir lockdownconfig havelsof delayadd pending' inprocess <$> safeToAdd lockdowndir lockdownconfig havelsof delayadd pending inprocess
cleanup
unless (null postponed) $ unless (null postponed) $
refillChanges postponed refillChanges postponed
returnWhen (null toadd) $ do returnWhen (null toadd) $ do
added <- addaction toadd $ added <- addaction toadd $
catMaybes <$> catMaybes <$> addunlocked toadd
if not lockingfiles return $ added ++ otherchanges
then addunlocked toadd
else forM toadd (add lockdownconfig)
if DirWatcher.eventsCoalesce || null added || unlocked
then return $ added ++ otherchanges
else do
r <- handleAdds lockdowndir havelsof delayadd =<< getChanges
return $ r ++ added ++ otherchanges
where where
(incomplete, otherchanges) = partition (\c -> isPendingAddChange c || isInProcessAddChange c) cs (incomplete, otherchanges) = partition (\c -> isPendingAddChange c || isInProcessAddChange c) cs
-- Find files that are actually new, and not unlocked annexed
-- files. The ls-files is run on a batch of files.
findnew [] = return ([], noop)
findnew pending@(exemplar:_) = do
let segments = segmentXargsUnordered $ map changeFile pending
rs <- liftAnnex $ forM segments $ \fs ->
inRepo (Git.LsFiles.notInRepo False fs)
let (newfiles, cleanup) = foldl'
(\(l1, a1) (l2, a2) -> (l1 ++ l2, a1 >> a2))
([], return True) rs
-- note: timestamp info is lost here
let ts = changeTime exemplar
return (map (PendingAddChange ts) newfiles, void $ liftIO cleanup)
returnWhen c a returnWhen c a
| c = return otherchanges | c = return otherchanges
@ -328,10 +285,10 @@ handleAdds lockdowndir havelsof delayadd cs = returnWhen (null incomplete) $ do
where where
ks = keySource ld ks = keySource ld
doadd = sanitycheck ks $ do doadd = sanitycheck ks $ do
(mkey, mcache) <- liftAnnex $ do (mkey, _mcache) <- liftAnnex $ do
showStart "add" $ keyFilename ks showStart "add" $ keyFilename ks
ingest nullMeterUpdate (Just $ LockedDown lockdownconfig ks) Nothing ingest nullMeterUpdate (Just $ LockedDown lockdownconfig ks) Nothing
maybe (failedingest change) (done change mcache $ keyFilename ks) mkey maybe (failedingest change) (done change $ keyFilename ks) mkey
add _ _ = return Nothing add _ _ = return Nothing
{- Avoid overhead of re-injesting a renamed unlocked file, by {- Avoid overhead of re-injesting a renamed unlocked file, by
@ -363,7 +320,7 @@ handleAdds lockdowndir havelsof delayadd cs = returnWhen (null incomplete) $ do
fastadd change key = do fastadd change key = do
let source = keySource $ lockedDown change let source = keySource $ lockedDown change
liftAnnex $ finishIngestUnlocked key source liftAnnex $ finishIngestUnlocked key source
done change Nothing (keyFilename source) key done change (keyFilename source) key
removedKeysMap :: InodeComparisonType -> [Change] -> Annex (M.Map InodeCacheKey Key) removedKeysMap :: InodeComparisonType -> [Change] -> Annex (M.Map InodeCacheKey Key)
removedKeysMap ct l = do removedKeysMap ct l = do
@ -379,17 +336,10 @@ handleAdds lockdowndir havelsof delayadd cs = returnWhen (null incomplete) $ do
liftAnnex showEndFail liftAnnex showEndFail
return Nothing return Nothing
done change mcache file key = liftAnnex $ do done change file key = liftAnnex $ do
logStatus key InfoPresent logStatus key InfoPresent
ifM versionSupportsUnlockedPointers mode <- liftIO $ catchMaybeIO $ fileMode <$> getFileStatus file
( do stagePointerFile file mode =<< hashPointerFile key
mode <- liftIO $ catchMaybeIO $ fileMode <$> getFileStatus file
stagePointerFile file mode =<< hashPointerFile key
, do
link <- makeLink file key mcache
when DirWatcher.eventsCoalesce $
stageSymlink file =<< hashSymlink link
)
showEndOk showEndOk
return $ Just $ finishedChange change key return $ Just $ finishedChange change key

View file

@ -36,7 +36,6 @@ import Annex.Link
import Annex.FileMatcher import Annex.FileMatcher
import Annex.Content import Annex.Content
import Annex.ReplaceFile import Annex.ReplaceFile
import Annex.Version
import Annex.InodeSentinal import Annex.InodeSentinal
import Git.Types import Git.Types
import Git.FilePath import Git.FilePath
@ -90,11 +89,8 @@ runWatcher :: Assistant ()
runWatcher = do runWatcher = do
startup <- asIO1 startupScan startup <- asIO1 startupScan
matcher <- liftAnnex largeFilesMatcher matcher <- liftAnnex largeFilesMatcher
unlocked <- liftAnnex versionSupportsUnlockedPointers
symlinkssupported <- liftAnnex $ coreSymlinks <$> Annex.getGitConfig symlinkssupported <- liftAnnex $ coreSymlinks <$> Annex.getGitConfig
addhook <- hook $ if unlocked addhook <- hook $ onAddUnlocked symlinkssupported matcher
then onAddUnlocked symlinkssupported matcher
else onAdd matcher
delhook <- hook onDel delhook <- hook onDel
addsymlinkhook <- hook onAddSymlink addsymlinkhook <- hook onAddSymlink
deldirhook <- hook onDelDir deldirhook <- hook onDelDir
@ -205,13 +201,6 @@ add largefilematcher file = ifM (liftAnnex $ checkFileMatcher largefilematcher f
madeChange file AddFileChange madeChange file AddFileChange
) )
onAdd :: GetFileMatcher -> Handler
onAdd matcher file filestatus
| maybe False isRegularFile filestatus =
unlessIgnored file $
add matcher file
| otherwise = noChange
shouldRestage :: DaemonStatus -> Bool shouldRestage :: DaemonStatus -> Bool
shouldRestage ds = scanComplete ds || forceRestage ds shouldRestage ds = scanComplete ds || forceRestage ds
@ -356,8 +345,7 @@ onDel file _ = do
onDel' :: FilePath -> Annex () onDel' :: FilePath -> Annex ()
onDel' file = do onDel' file = do
topfile <- inRepo (toTopFilePath file) topfile <- inRepo (toTopFilePath file)
whenM versionSupportsUnlockedPointers $ withkey $ flip Database.Keys.removeAssociatedFile topfile
withkey $ flip Database.Keys.removeAssociatedFile topfile
Annex.Queue.addUpdateIndex =<< Annex.Queue.addUpdateIndex =<<
inRepo (Git.UpdateIndex.unstageFile file) inRepo (Git.UpdateIndex.unstageFile file)
where where

View file

@ -1,5 +1,7 @@
git-annex (7.20190826) UNRELEASED; urgency=medium git-annex (7.20190826) UNRELEASED; urgency=medium
* Default to v7 for new repositories.
* Automatically upgrade v5 repositories to v7.
* Automatically convert direct mode repositories to v7 with adjusted * Automatically convert direct mode repositories to v7 with adjusted
unlocked branches and set annex.thin. unlocked branches and set annex.thin.
* Refuse to upgrade direct mode repositories when git is older than 2.22, * Refuse to upgrade direct mode repositories when git is older than 2.22,

View file

@ -114,38 +114,21 @@ withFilesToBeCommitted :: (FilePath -> CommandSeek) -> [WorkTreeItem] -> Command
withFilesToBeCommitted a l = seekActions $ prepFiltered a $ withFilesToBeCommitted a l = seekActions $ prepFiltered a $
seekHelper LsFiles.stagedNotDeleted l seekHelper LsFiles.stagedNotDeleted l
withFilesOldUnlocked :: (FilePath -> CommandSeek) -> [WorkTreeItem] -> CommandSeek
withFilesOldUnlocked = withFilesOldUnlocked' LsFiles.typeChanged
{- Unlocked files before v6 have changed type from a symlink to a regular file.
-
- Furthermore, unlocked files used to be a git-annex symlink,
- not some other sort of symlink.
-}
withFilesOldUnlocked' :: ([FilePath] -> Git.Repo -> IO ([FilePath], IO Bool)) -> (FilePath -> CommandSeek) -> [WorkTreeItem] -> CommandSeek
withFilesOldUnlocked' typechanged a l = seekActions $
prepFiltered a unlockedfiles
where
unlockedfiles = filterM isOldUnlocked =<< seekHelper typechanged l
isOldUnlocked :: FilePath -> Annex Bool isOldUnlocked :: FilePath -> Annex Bool
isOldUnlocked f = liftIO (notSymlink f) <&&> isOldUnlocked f = liftIO (notSymlink f) <&&>
(isJust <$> catKeyFile f <||> isJust <$> catKeyFileHEAD f) (isJust <$> catKeyFile f <||> isJust <$> catKeyFileHEAD f)
withFilesOldUnlockedToBeCommitted :: (FilePath -> CommandSeek) -> [WorkTreeItem] -> CommandSeek {- unlocked pointer files that are staged, and whose content has not been
withFilesOldUnlockedToBeCommitted = withFilesOldUnlocked' LsFiles.typeChangedStaged
{- v6 unlocked pointer files that are staged, and whose content has not been
- modified-} - modified-}
withUnmodifiedUnlockedPointers :: (FilePath -> CommandSeek) -> [WorkTreeItem] -> CommandSeek withUnmodifiedUnlockedPointers :: (FilePath -> CommandSeek) -> [WorkTreeItem] -> CommandSeek
withUnmodifiedUnlockedPointers a l = seekActions $ withUnmodifiedUnlockedPointers a l = seekActions $
prepFiltered a unlockedfiles prepFiltered a unlockedfiles
where where
unlockedfiles = filterM isV6UnmodifiedUnlocked unlockedfiles = filterM isUnmodifiedUnlocked
=<< seekHelper LsFiles.typeChangedStaged l =<< seekHelper LsFiles.typeChangedStaged l
isV6UnmodifiedUnlocked :: FilePath -> Annex Bool isUnmodifiedUnlocked :: FilePath -> Annex Bool
isV6UnmodifiedUnlocked f = catKeyFile f >>= \case isUnmodifiedUnlocked f = catKeyFile f >>= \case
Nothing -> return False Nothing -> return False
Just k -> sameInodeCache f =<< Database.Keys.getInodeCaches k Just k -> sameInodeCache f =<< Database.Keys.getInodeCaches k

View file

@ -16,7 +16,6 @@ import qualified Annex.Queue
import qualified Database.Keys import qualified Database.Keys
import Annex.FileMatcher import Annex.FileMatcher
import Annex.Link import Annex.Link
import Annex.Version
import Annex.Tmp import Annex.Tmp
import Messages.Progress import Messages.Progress
import Git.FilePath import Git.FilePath
@ -69,10 +68,7 @@ seek o = startConcurrency commandStages $ do
unless (updateOnly o) $ unless (updateOnly o) $
go (withFilesNotInGit (not $ includeDotFiles o)) go (withFilesNotInGit (not $ includeDotFiles o))
go withFilesMaybeModified go withFilesMaybeModified
ifM versionSupportsUnlockedPointers go withUnmodifiedUnlockedPointers
( go withUnmodifiedUnlockedPointers
, go withFilesOldUnlocked
)
{- Pass file off to git-add. -} {- Pass file off to git-add. -}
startSmall :: FilePath -> CommandStart startSmall :: FilePath -> CommandStart
@ -92,12 +88,8 @@ addFile file = do
start :: FilePath -> CommandStart start :: FilePath -> CommandStart
start file = do start file = do
ifM versionSupportsUnlockedPointers mk <- liftIO $ isPointerFile file
( do maybe go fixuppointer mk
mk <- liftIO $ isPointerFile file
maybe go fixuppointer mk
, go
)
where where
go = ifAnnexed file addpresent add go = ifAnnexed file addpresent add
add = liftIO (catchMaybeIO $ getSymbolicLinkStatus file) >>= \case add = liftIO (catchMaybeIO $ getSymbolicLinkStatus file) >>= \case
@ -109,12 +101,10 @@ start file = do
if isSymbolicLink s if isSymbolicLink s
then next $ addFile file then next $ addFile file
else perform file else perform file
addpresent key = ifM versionSupportsUnlockedPointers addpresent key =
( liftIO (catchMaybeIO $ getSymbolicLinkStatus file) >>= \case liftIO (catchMaybeIO $ getSymbolicLinkStatus file) >>= \case
Just s | isSymbolicLink s -> fixuplink key Just s | isSymbolicLink s -> fixuplink key
_ -> add _ -> add
, fixuplink key
)
fixuplink key = starting "add" (ActionItemWorkTreeFile file) $ do fixuplink key = starting "add" (ActionItemWorkTreeFile file) $ do
-- the annexed symlink is present but not yet added to git -- the annexed symlink is present but not yet added to git
liftIO $ removeFile file liftIO $ removeFile file

View file

@ -12,7 +12,6 @@ module Command.Fix where
import Command import Command
import Config import Config
import qualified Annex import qualified Annex
import Annex.Version
import Annex.ReplaceFile import Annex.ReplaceFile
import Annex.Content import Annex.Content
import Annex.Perms import Annex.Perms
@ -32,12 +31,8 @@ cmd = noCommit $ withGlobalOptions [annexedMatchingOptions] $
seek :: CmdParams -> CommandSeek seek :: CmdParams -> CommandSeek
seek ps = unlessM crippledFileSystem $ do seek ps = unlessM crippledFileSystem $ do
fixwhat <- ifM versionSupportsUnlockedPointers
( return FixAll
, return FixSymlinks
)
withFilesInGit withFilesInGit
(commandAction . (whenAnnexed $ start fixwhat)) (commandAction . (whenAnnexed $ start FixAll))
=<< workTreeItems ps =<< workTreeItems ps
data FixWhat = FixSymlinks | FixAll data FixWhat = FixSymlinks | FixAll

View file

@ -10,7 +10,6 @@ module Command.Lock where
import Command import Command
import qualified Annex.Queue import qualified Annex.Queue
import qualified Annex import qualified Annex
import Annex.Version
import Annex.Content import Annex.Content
import Annex.Link import Annex.Link
import Annex.InodeSentinal import Annex.InodeSentinal
@ -31,12 +30,7 @@ cmd = withGlobalOptions [jsonOptions, annexedMatchingOptions] $
seek :: CmdParams -> CommandSeek seek :: CmdParams -> CommandSeek
seek ps = do seek ps = do
l <- workTreeItems ps l <- workTreeItems ps
ifM versionSupportsUnlockedPointers withFilesInGit (commandAction . (whenAnnexed startNew)) l
( withFilesInGit (commandAction . (whenAnnexed startNew)) l
, do
withFilesOldUnlocked (commandAction . startOld) l
withFilesOldUnlockedToBeCommitted (commandAction . startOld) l
)
startNew :: FilePath -> Key -> CommandStart startNew :: FilePath -> Key -> CommandStart
startNew file key = ifM (isJust <$> isAnnexLink file) startNew file key = ifM (isJust <$> isAnnexLink file)

View file

@ -10,21 +10,17 @@
module Command.PreCommit where module Command.PreCommit where
import Command import Command
import qualified Command.Add
import qualified Command.Fix import qualified Command.Fix
import qualified Command.Smudge import qualified Command.Smudge
import Annex.Hook import Annex.Hook
import Annex.Link import Annex.Link
import Annex.View import Annex.View
import Annex.Version
import Annex.View.ViewedFile import Annex.View.ViewedFile
import Annex.LockFile import Annex.LockFile
import Logs.View import Logs.View
import Logs.MetaData import Logs.MetaData
import Types.View import Types.View
import Types.MetaData import Types.MetaData
import qualified Git.Index as Git
import qualified Git.LsFiles as Git
import qualified Data.Set as S import qualified Data.Set as S
import qualified Data.Text as T import qualified Data.Text as T
@ -37,31 +33,14 @@ cmd = command "pre-commit" SectionPlumbing
seek :: CmdParams -> CommandSeek seek :: CmdParams -> CommandSeek
seek ps = lockPreCommitHook $ do seek ps = lockPreCommitHook $ do
ifM (not <$> versionSupportsUnlockedPointers <&&> liftIO Git.haveFalseIndex) l <- workTreeItems ps
( do -- fix symlinks to files being committed
(fs, cleanup) <- inRepo $ Git.typeChangedStaged ps flip withFilesToBeCommitted l $ \f -> commandAction $
whenM (anyM isOldUnlocked fs) $ maybe stop (Command.Fix.start Command.Fix.FixSymlinks f)
giveup "Cannot make a partial commit with unlocked annexed files. You should `git annex add` the files you want to commit, and then run git commit." =<< isAnnexLink f
void $ liftIO cleanup -- after a merge conflict or git cherry-pick or stash, pointer
, do -- files in the worktree won't be populated, so populate them here
l <- workTreeItems ps Command.Smudge.updateSmudged (Restage False)
-- fix symlinks to files being committed
flip withFilesToBeCommitted l $ \f -> commandAction $
maybe stop (Command.Fix.start Command.Fix.FixSymlinks f)
=<< isAnnexLink f
ifM versionSupportsUnlockedPointers
-- after a merge conflict or git
-- cherry-pick or stash, pointer
-- files in the worktree won't
-- be populated, so populate them
-- here
( Command.Smudge.updateSmudged (Restage False)
-- inject unlocked files into the annex
-- (not needed when repo version uses
-- unlocked pointer files)
, withFilesOldUnlockedToBeCommitted (commandAction . startInjectUnlocked) l
)
)
runAnnexHook preCommitAnnexHook runAnnexHook preCommitAnnexHook
@ -73,12 +52,6 @@ seek ps = lockPreCommitHook $ do
(addViewMetaData v) (addViewMetaData v)
(removeViewMetaData v) (removeViewMetaData v)
startInjectUnlocked :: FilePath -> CommandStart
startInjectUnlocked f = startingCustomOutput (ActionItemOther Nothing) $ do
unlessM (callCommandAction $ Command.Add.start f) $
error $ "failed to add " ++ f ++ "; canceling commit"
next $ return True
addViewMetaData :: View -> ViewedFile -> Key -> CommandStart addViewMetaData :: View -> ViewedFile -> Key -> CommandStart
addViewMetaData v f k = starting "metadata" (mkActionItem (k, f)) $ addViewMetaData v f k = starting "metadata" (mkActionItem (k, f)) $
next $ changeMetaData k $ fromView v f next $ changeMetaData k $ fromView v f

View file

@ -11,13 +11,8 @@ import Command
import qualified Annex import qualified Annex
import Annex.Content import Annex.Content
import Annex.Perms import Annex.Perms
import Annex.Version
import qualified Git.Command import qualified Git.Command
import qualified Git.Branch
import qualified Git.Ref
import qualified Git.DiffTree as DiffTree
import Utility.CopyFile import Utility.CopyFile
import Command.PreCommit (lockPreCommitHook)
import qualified Database.Keys import qualified Database.Keys
import Git.FilePath import Git.FilePath
@ -28,40 +23,7 @@ cmd = withGlobalOptions [annexedMatchingOptions] $
paramPaths (withParams seek) paramPaths (withParams seek)
seek :: CmdParams -> CommandSeek seek :: CmdParams -> CommandSeek
seek ps = wrapUnannex $ seek ps = (withFilesInGit $ commandAction . whenAnnexed start) =<< workTreeItems ps
(withFilesInGit $ commandAction . whenAnnexed start) =<< workTreeItems ps
wrapUnannex :: Annex a -> Annex a
wrapUnannex a = ifM versionSupportsUnlockedPointers
( a
{- Run with the pre-commit hook disabled, to avoid confusing
- behavior if an unannexed file is added back to git as
- a normal, non-annexed file and then committed.
- Otherwise, the pre-commit hook would think that the file
- has been unlocked and needs to be re-annexed.
-
- At the end, make a commit removing the unannexed files.
-}
, ifM cleanindex
( lockPreCommitHook $ commit `after` a
, giveup "Cannot proceed with uncommitted changes staged in the index. Recommend you: git commit"
)
)
where
commit = inRepo $ Git.Branch.commitCommand Git.Branch.ManualCommit
[ Param "-q"
, Param "--allow-empty"
, Param "--no-verify"
, Param "-m", Param "content removed from git annex"
]
cleanindex = ifM (inRepo Git.Ref.headExists)
( do
(diff, reap) <- inRepo $ DiffTree.diffIndex Git.Ref.headRef
if null diff
then void (liftIO reap) >> return True
else void (liftIO reap) >> return False
, return False
)
start :: FilePath -> Key -> CommandStart start :: FilePath -> Key -> CommandStart
start file key = stopUnless (inAnnex key) $ start file key = stopUnless (inAnnex key) $

View file

@ -10,11 +10,8 @@ module Command.Unlock where
import Command import Command
import Annex.Content import Annex.Content
import Annex.Perms import Annex.Perms
import Annex.CatFile
import Annex.Version
import Annex.Link import Annex.Link
import Annex.ReplaceFile import Annex.ReplaceFile
import Utility.CopyFile
import Git.FilePath import Git.FilePath
import qualified Database.Keys import qualified Database.Keys
@ -37,15 +34,12 @@ seek ps = withFilesInGit (commandAction . whenAnnexed start) =<< workTreeItems p
start :: FilePath -> Key -> CommandStart start :: FilePath -> Key -> CommandStart
start file key = ifM (isJust <$> isAnnexLink file) start file key = ifM (isJust <$> isAnnexLink file)
( starting "unlock" (mkActionItem (key, AssociatedFile (Just file))) $ ( starting "unlock" (mkActionItem (key, AssociatedFile (Just file))) $
ifM versionSupportsUnlockedPointers perform file key
( performNew file key
, performOld file key
)
, stop , stop
) )
performNew :: FilePath -> Key -> CommandPerform perform :: FilePath -> Key -> CommandPerform
performNew dest key = do perform dest key = do
destmode <- liftIO $ catchMaybeIO $ fileMode <$> getFileStatus dest destmode <- liftIO $ catchMaybeIO $ fileMode <$> getFileStatus dest
replaceFile dest $ \tmp -> replaceFile dest $ \tmp ->
ifM (inAnnex key) ifM (inAnnex key)
@ -57,47 +51,10 @@ performNew dest key = do
LinkAnnexFailed -> error "unlock failed" LinkAnnexFailed -> error "unlock failed"
, liftIO $ writePointerFile tmp key destmode , liftIO $ writePointerFile tmp key destmode
) )
next $ cleanupNew dest key destmode next $ cleanup dest key destmode
cleanupNew :: FilePath -> Key -> Maybe FileMode -> CommandCleanup cleanup :: FilePath -> Key -> Maybe FileMode -> CommandCleanup
cleanupNew dest key destmode = do cleanup dest key destmode = do
stagePointerFile dest destmode =<< hashPointerFile key stagePointerFile dest destmode =<< hashPointerFile key
Database.Keys.addAssociatedFile key =<< inRepo (toTopFilePath dest) Database.Keys.addAssociatedFile key =<< inRepo (toTopFilePath dest)
return True return True
performOld :: FilePath -> Key -> CommandPerform
performOld file key =
ifM (inAnnex key)
( ifM (isJust <$> catKeyFileHEAD file)
( performOld' file key
, do
warning "this has not yet been committed to git; cannot unlock it"
next $ return False
)
, do
warning "content not present; cannot unlock"
next $ return False
)
performOld' :: FilePath -> Key -> CommandPerform
performOld' dest key = ifM (checkDiskSpace Nothing key 0 True)
( do
src <- calcRepo $ gitAnnexLocation key
tmpdest <- fromRepo $ gitAnnexTmpObjectLocation key
liftIO $ createDirectoryIfMissing True (parentDir tmpdest)
showAction "copying"
ifM (liftIO $ copyFileExternal CopyAllMetaData src tmpdest)
( do
liftIO $ do
removeFile dest
moveFile tmpdest dest
thawContent dest
next $ return True
, do
warning "copy failed!"
next $ return False
)
, do
warning "not enough disk space to copy file"
next $ return False
)

View file

@ -29,7 +29,6 @@ import qualified Database.Queue as H
import Database.Init import Database.Init
import Annex.Locations import Annex.Locations
import Annex.Common hiding (delete) import Annex.Common hiding (delete)
import Annex.Version (versionUsesKeysDatabase)
import qualified Annex import qualified Annex
import Annex.LockFile import Annex.LockFile
import Annex.CatFile import Annex.CatFile
@ -103,10 +102,7 @@ getDbHandle = go =<< Annex.getState Annex.keysdbhandle
where where
go (Just h) = pure h go (Just h) = pure h
go Nothing = do go Nothing = do
h <- ifM versionUsesKeysDatabase h <- liftIO newDbHandle
( liftIO newDbHandle
, liftIO unavailableDbHandle
)
Annex.changeState $ \s -> s { Annex.keysdbhandle = Just h } Annex.changeState $ \s -> s { Annex.keysdbhandle = Just h }
return h return h
@ -220,7 +216,7 @@ removeInodeCaches = runWriterIO . SQL.removeInodeCaches . toIKey
- file. - file.
-} -}
reconcileStaged :: H.DbQueue -> Annex () reconcileStaged :: H.DbQueue -> Annex ()
reconcileStaged qh = whenM versionUsesKeysDatabase $ do reconcileStaged qh = do
gitindex <- inRepo currentIndexFile gitindex <- inRepo currentIndexFile
indexcache <- fromRepo gitAnnexKeysDbIndexCache indexcache <- fromRepo gitAnnexKeysDbIndexCache
withTSDelta (liftIO . genInodeCache gitindex) >>= \case withTSDelta (liftIO . genInodeCache gitindex) >>= \case

View file

@ -58,19 +58,3 @@ currentIndexFile r = fromMaybe (indexFile r) <$> getEnv indexEnv
{- Git locks the index by creating this file. -} {- Git locks the index by creating this file. -}
indexFileLock :: FilePath -> FilePath indexFileLock :: FilePath -> FilePath
indexFileLock f = f ++ ".lock" indexFileLock f = f ++ ".lock"
{- When the pre-commit hook is run, and git commit has been run with
- a file or files specified to commit, rather than committing the staged
- index, git provides the pre-commit hook with a "false index file".
-
- Changes made to this index will influence the commit, but won't
- affect the real index file.
-
- This detects when we're in this situation, using a heuristic, which
- might be broken by changes to git. Any use of this should have a test
- case to make sure it works.
-}
haveFalseIndex :: IO Bool
haveFalseIndex = maybe (False) check <$> getEnv indexEnv
where
check f = "next-index" `isPrefixOf` takeFileName f

View file

@ -37,7 +37,6 @@ import Config
import Config.Cost import Config.Cost
import Config.DynamicConfig import Config.DynamicConfig
import Annex.Init import Annex.Init
import Annex.Version
import Types.CleanupActions import Types.CleanupActions
import qualified CmdLine.GitAnnexShell.Fields as Fields import qualified CmdLine.GitAnnexShell.Fields as Fields
import Logs.Location import Logs.Location
@ -642,7 +641,7 @@ copyToRemote' repo r st@(State connpool duc _ _) key file meterupdate
-- This is too broad really, but recvkey normally -- This is too broad really, but recvkey normally
-- verifies content anyway, so avoid complicating -- verifies content anyway, so avoid complicating
-- it with a local sendAnnex check and rollback. -- it with a local sendAnnex check and rollback.
unlocked <- versionSupportsUnlockedPointers let unlocked = True
oh <- mkOutputHandlerQuiet oh <- mkOutputHandlerQuiet
Ssh.rsyncHelper oh (Just p) Ssh.rsyncHelper oh (Just p)
=<< Ssh.rsyncParamsRemote unlocked r Upload key object file =<< Ssh.rsyncParamsRemote unlocked r Upload key object file

80
Test.hs
View file

@ -30,7 +30,6 @@ import CmdLine.GitAnnex.Options
import qualified Utility.SafeCommand import qualified Utility.SafeCommand
import qualified Annex import qualified Annex
import qualified Annex.Version
import qualified Git.Filename import qualified Git.Filename
import qualified Git.Types import qualified Git.Types
import qualified Git.Ref import qualified Git.Ref
@ -151,7 +150,6 @@ tests crippledfilesystem adjustedbranchok opts =
testmodes = catMaybes testmodes = catMaybes
[ canadjust ("v7 adjusted unlocked branch", (testMode opts (RepoVersion 7)) { adjustedUnlockedBranch = True }) [ canadjust ("v7 adjusted unlocked branch", (testMode opts (RepoVersion 7)) { adjustedUnlockedBranch = True })
, unlesscrippled ("v7 unlocked", (testMode opts (RepoVersion 7)) { unlockedFiles = True }) , unlesscrippled ("v7 unlocked", (testMode opts (RepoVersion 7)) { unlockedFiles = True })
, unlesscrippled ("v5", testMode opts (RepoVersion 5))
, unlesscrippled ("v7 locked", testMode opts (RepoVersion 7)) , unlesscrippled ("v7 locked", testMode opts (RepoVersion 7))
] ]
unlesscrippled v unlesscrippled v
@ -230,7 +228,7 @@ unitTests note = testGroup ("Unit Tests " ++ note)
, testCase "move (ssh remote)" test_move_ssh_remote , testCase "move (ssh remote)" test_move_ssh_remote
, testCase "copy" test_copy , testCase "copy" test_copy
, testCase "lock" test_lock , testCase "lock" test_lock
, testCase "lock (v7 --force)" test_lock_v7_force , testCase "lock --force" test_lock_force
, testCase "edit (no pre-commit)" test_edit , testCase "edit (no pre-commit)" test_edit
, testCase "edit (pre-commit)" test_edit_precommit , testCase "edit (pre-commit)" test_edit_precommit
, testCase "partial commit" test_partial_commit , testCase "partial commit" test_partial_commit
@ -584,21 +582,12 @@ test_preferred_content = intmpclonerepo $ do
test_lock :: Assertion test_lock :: Assertion
test_lock = intmpclonerepo $ do test_lock = intmpclonerepo $ do
annexed_notpresent annexedfile annexed_notpresent annexedfile
unlessM (annexeval Annex.Version.versionSupportsUnlockedPointers) $
ifM (hasUnlockedFiles <$> getTestMode)
( git_annex_shouldfail "lock" [annexedfile] @? "lock failed to fail with not present file"
, git_annex_shouldfail "unlock" [annexedfile] @? "unlock failed to fail with not present file"
)
annexed_notpresent annexedfile
-- regression test: unlock of newly added, not committed file -- regression test: unlock of newly added, not committed file
-- should fail in v5 mode. In v7 mode, this is allowed. -- should not fail.
writecontent "newfile" "foo" writecontent "newfile" "foo"
git_annex "add" ["newfile"] @? "add new file failed" git_annex "add" ["newfile"] @? "add new file failed"
ifM (annexeval Annex.Version.versionSupportsUnlockedPointers) git_annex "unlock" ["newfile"] @? "unlock failed on newly added, never committed file"
( git_annex "unlock" ["newfile"] @? "unlock failed on newly added, never committed file in v7 repository"
, git_annex_shouldfail "unlock" ["newfile"] @? "unlock failed to fail on newly added, never committed file in v5 repository"
)
git_annex "get" [annexedfile] @? "get of file failed" git_annex "get" [annexedfile] @? "get of file failed"
annexed_present annexedfile annexed_present annexedfile
@ -610,21 +599,15 @@ test_lock = intmpclonerepo $ do
writecontent annexedfile $ content annexedfile ++ "foo" writecontent annexedfile $ content annexedfile ++ "foo"
git_annex_shouldfail "lock" [annexedfile] @? "lock failed to fail without --force" git_annex_shouldfail "lock" [annexedfile] @? "lock failed to fail without --force"
git_annex "lock" ["--force", annexedfile] @? "lock --force failed" git_annex "lock" ["--force", annexedfile] @? "lock --force failed"
-- In v7 mode, the original content of the file is not always -- The original content of an unlocked file is not always
-- preserved after modification, so re-get it. -- preserved after modification, so re-get it.
git_annex "get" [annexedfile] @? "get of file failed after lock --force" git_annex "get" [annexedfile] @? "get of file failed after lock --force"
annexed_present_locked annexedfile annexed_present_locked annexedfile
git_annex "unlock" [annexedfile] @? "unlock failed" git_annex "unlock" [annexedfile] @? "unlock failed"
unannexed annexedfile unannexed annexedfile
changecontent annexedfile changecontent annexedfile
ifM (annexeval Annex.Version.versionSupportsUnlockedPointers) boolSystem "git" [Param "add", Param annexedfile] @? "add of modified file failed"
( do runchecks [checkregularfile, checkwritable] annexedfile
boolSystem "git" [Param "add", Param annexedfile] @? "add of modified file failed"
runchecks [checkregularfile, checkwritable] annexedfile
, do
git_annex "add" [annexedfile] @? "add of modified file failed"
runchecks [checklink, checkunwritable] annexedfile
)
c <- readFile annexedfile c <- readFile annexedfile
assertEqual "content of modified file" c (changedcontent annexedfile) assertEqual "content of modified file" c (changedcontent annexedfile)
r' <- git_annex "drop" [annexedfile] r' <- git_annex "drop" [annexedfile]
@ -633,21 +616,20 @@ test_lock = intmpclonerepo $ do
-- Regression test: lock --force when work tree file -- Regression test: lock --force when work tree file
-- was modified lost the (unmodified) annex object. -- was modified lost the (unmodified) annex object.
-- (Only occurred when the keys database was out of sync.) -- (Only occurred when the keys database was out of sync.)
test_lock_v7_force :: Assertion test_lock_force :: Assertion
test_lock_v7_force = intmpclonerepo $ do test_lock_force = intmpclonerepo $ do
git_annex "upgrade" [] @? "upgrade failed" git_annex "upgrade" [] @? "upgrade failed"
whenM (annexeval Annex.Version.versionSupportsUnlockedPointers) $ do git_annex "get" [annexedfile] @? "get of file failed"
git_annex "get" [annexedfile] @? "get of file failed" git_annex "unlock" [annexedfile] @? "unlock failed"
git_annex "unlock" [annexedfile] @? "unlock failed in v7 mode" annexeval $ do
annexeval $ do Just k <- Annex.WorkTree.lookupFile annexedfile
Just k <- Annex.WorkTree.lookupFile annexedfile Database.Keys.removeInodeCaches k
Database.Keys.removeInodeCaches k Database.Keys.closeDb
Database.Keys.closeDb liftIO . nukeFile =<< Annex.fromRepo Annex.Locations.gitAnnexKeysDbIndexCache
liftIO . nukeFile =<< Annex.fromRepo Annex.Locations.gitAnnexKeysDbIndexCache writecontent annexedfile "test_lock_force content"
writecontent annexedfile "test_lock_v7_force content" git_annex_shouldfail "lock" [annexedfile] @? "lock of modified file failed to fail"
git_annex_shouldfail "lock" [annexedfile] @? "lock of modified file failed to fail in v7 mode" git_annex "lock" ["--force", annexedfile] @? "lock --force of modified file failed"
git_annex "lock" ["--force", annexedfile] @? "lock --force of modified file failed in v7 mode" annexed_present_locked annexedfile
annexed_present_locked annexedfile
test_edit :: Assertion test_edit :: Assertion
test_edit = test_edit' False test_edit = test_edit' False
@ -669,10 +651,7 @@ test_edit' precommit = intmpclonerepo $ do
@? "pre-commit failed" @? "pre-commit failed"
else boolSystem "git" [Param "commit", Param "-q", Param "-m", Param "contentchanged"] else boolSystem "git" [Param "commit", Param "-q", Param "-m", Param "contentchanged"]
@? "git commit of edited file failed" @? "git commit of edited file failed"
ifM (annexeval Annex.Version.versionSupportsUnlockedPointers) runchecks [checkregularfile, checkwritable] annexedfile
( runchecks [checkregularfile, checkwritable] annexedfile
, runchecks [checklink, checkunwritable] annexedfile
)
c <- readFile annexedfile c <- readFile annexedfile
assertEqual "content of modified file" c (changedcontent annexedfile) assertEqual "content of modified file" c (changedcontent annexedfile)
git_annex_shouldfail "drop" [annexedfile] @? "drop wrongly succeeded with no known copy of modified file" git_annex_shouldfail "drop" [annexedfile] @? "drop wrongly succeeded with no known copy of modified file"
@ -683,12 +662,8 @@ test_partial_commit = intmpclonerepo $ do
annexed_present annexedfile annexed_present annexedfile
git_annex "unlock" [annexedfile] @? "unlock failed" git_annex "unlock" [annexedfile] @? "unlock failed"
changecontent annexedfile changecontent annexedfile
ifM (annexeval Annex.Version.versionSupportsUnlockedPointers) boolSystem "git" [Param "commit", Param "-q", Param "-m", Param "test", File annexedfile]
( boolSystem "git" [Param "commit", Param "-q", Param "-m", Param "test", File annexedfile] @? "partial commit of unlocked file should be allowed"
@? "partial commit of unlocked file should be allowed in v7 repository"
, not <$> boolSystem "git" [Param "commit", Param "-q", Param "-m", Param "test", File annexedfile]
@? "partial commit of unlocked file not blocked by pre-commit hook"
)
test_fix :: Assertion test_fix :: Assertion
test_fix = intmpclonerepo $ unlessM (hasUnlockedFiles <$> getTestMode) $ do test_fix = intmpclonerepo $ unlessM (hasUnlockedFiles <$> getTestMode) $ do
@ -1083,8 +1058,6 @@ test_conflict_resolution_adjusted_branch =
writecontent conflictor "conflictor2" writecontent conflictor "conflictor2"
add_annex conflictor @? "add conflicter failed" add_annex conflictor @? "add conflicter failed"
git_annex "sync" [] @? "sync failed in r2" git_annex "sync" [] @? "sync failed in r2"
-- need v7 to use adjust
git_annex "upgrade" [] @? "upgrade failed"
-- We might be in an adjusted branch -- We might be in an adjusted branch
-- already, when eg on a crippled -- already, when eg on a crippled
-- filesystem. So, --force it. -- filesystem. So, --force it.
@ -1348,19 +1321,19 @@ test_conflict_resolution_symlink_bit = unlessM (hasUnlockedFiles <$> getTestMode
all (\i -> Git.Types.toTreeItemType (Git.LsTree.mode i) == Just Git.Types.TreeSymlink) l all (\i -> Git.Types.toTreeItemType (Git.LsTree.mode i) == Just Git.Types.TreeSymlink) l
@? (what ++ " " ++ f ++ " lost symlink bit after merge: " ++ show l) @? (what ++ " " ++ f ++ " lost symlink bit after merge: " ++ show l)
{- A v7 unlocked file that conflicts with a locked file should be resolved {- An unlocked file that conflicts with a locked file should be resolved
- in favor of the unlocked file, with no variant files, as long as they - in favor of the unlocked file, with no variant files, as long as they
- both point to the same key. -} - both point to the same key. -}
test_mixed_lock_conflict_resolution :: Assertion test_mixed_lock_conflict_resolution :: Assertion
test_mixed_lock_conflict_resolution = test_mixed_lock_conflict_resolution =
withtmpclonerepo $ \r1 -> withtmpclonerepo $ \r1 ->
withtmpclonerepo $ \r2 -> do withtmpclonerepo $ \r2 -> do
indir r1 $ whenM shouldtest $ do indir r1 $ do
disconnectOrigin disconnectOrigin
writecontent conflictor "conflictor" writecontent conflictor "conflictor"
git_annex "add" [conflictor] @? "add conflicter failed" git_annex "add" [conflictor] @? "add conflicter failed"
git_annex "sync" [] @? "sync failed in r1" git_annex "sync" [] @? "sync failed in r1"
indir r2 $ whenM shouldtest $ do indir r2 $ do
disconnectOrigin disconnectOrigin
writecontent conflictor "conflictor" writecontent conflictor "conflictor"
git_annex "add" [conflictor] @? "add conflicter failed" git_annex "add" [conflictor] @? "add conflicter failed"
@ -1372,10 +1345,9 @@ test_mixed_lock_conflict_resolution =
checkmerge "r1" r1 checkmerge "r1" r1
checkmerge "r2" r2 checkmerge "r2" r2
where where
shouldtest = annexeval Annex.Version.versionSupportsUnlockedPointers
conflictor = "conflictor" conflictor = "conflictor"
variantprefix = conflictor ++ ".variant" variantprefix = conflictor ++ ".variant"
checkmerge what d = indir d $ whenM shouldtest $ do checkmerge what d = indir d $ do
l <- getDirectoryContents "." l <- getDirectoryContents "."
let v = filter (variantprefix `isPrefixOf`) l let v = filter (variantprefix `isPrefixOf`) l
length v == 0 length v == 0

View file

@ -150,7 +150,7 @@ indir dir a = do
Left e -> throwM e Left e -> throwM e
adjustedbranchsupported :: FilePath -> IO Bool adjustedbranchsupported :: FilePath -> IO Bool
adjustedbranchsupported repo = indir repo $ annexeval Annex.AdjustedBranch.isSupported adjustedbranchsupported repo = indir repo $ Annex.AdjustedBranch.isGitVersionSupported
setuprepo :: FilePath -> IO FilePath setuprepo :: FilePath -> IO FilePath
setuprepo dir = do setuprepo dir = do

View file

@ -23,8 +23,7 @@ Large files are added to the annex in locked form, which prevents further
modification of their content unless unlocked by [[git-annex-unlock]](1). modification of their content unless unlocked by [[git-annex-unlock]](1).
(This is not the case however when a repository is in a filesystem not (This is not the case however when a repository is in a filesystem not
supporting symlinks.) supporting symlinks.)
To add a file to the annex in unlocked form, `git add` can be used instead To add a file to the annex in unlocked form, `git add` can be used instead.
(that only works in repository v7 or higher).
This command can also be used to add symbolic links, both symlinks to This command can also be used to add symbolic links, both symlinks to
annexed content, and other symlinks. annexed content, and other symlinks.

View file

@ -34,8 +34,6 @@ while inside the adjusted branch will update the adjusted branch
as necessary (eg for `--hide-missing`), and will also propagate commits as necessary (eg for `--hide-missing`), and will also propagate commits
back to the original branch. back to the original branch.
This command can only be used in a v7 git-annex repository.
# OPTIONS # OPTIONS
* `--unlock` * `--unlock`

View file

@ -17,9 +17,6 @@ point to annexed content.
When in a view, updates metadata to reflect changes When in a view, updates metadata to reflect changes
made to files in the view. made to files in the view.
When in a repository that has not been upgraded to v7,
also handles injecting changes to unlocked files into the annex.
# SEE ALSO # SEE ALSO
[[git-annex]](1) [[git-annex]](1)

View file

@ -14,21 +14,21 @@ symlink for each specified file with the file's content.
You can then modify it and `git annex add` (or `git commit`) to save your You can then modify it and `git annex add` (or `git commit`) to save your
changes. changes.
In v5 repositories, unlocking a file is local Unlocking a file changes how it is stored in the git repository (from a
to the repository, and is temporary. In v7 repositories, unlocking a file symlink to a pointer file), so this command will make a change that you
changes how it is stored in the git repository (from a symlink to a pointer can commit.
file), so you can commit it like any other change. Also in v7, you
can use `git add` to add a file to the annex in unlocked form. This allows
workflows where a file starts out unlocked, is modified as necessary, and
is locked once it reaches its final version.
Normally, unlocking a file requires a copy to be made of its content, If you use `git add` to add a file, it will be added in unlocked form from
so that its original content is preserved, while the copy can be modified. the beginning. This allows workflows where a file starts out unlocked, is
To use less space, annex.thin can be set to true; this makes a hard link modified as necessary, and is locked once it reaches its final version.
to the content be made instead of a copy. (Only when supported by the file
system, and only in v7 and higher.) While this can save considerable Normally, unlocking a file requires a copy to be made of its content, so
disk space, any modification made to a file will cause the old version of the that its original content is preserved, while the copy can be modified. To
file to be lost from the local repository. So, enable annex.thin with care. use less space, annex.thin can be set to true; this makes a hard link to
the content be made instead of a copy. (Only when supported by the file
system.) While this can save considerable disk space, any modification made
to a file will cause the old version of the file to be lost from the local
repository. So, enable annex.thin with care.
# OPTIONS # OPTIONS

View file

@ -908,7 +908,7 @@ Here are all the supported configuration settings.
Set to true to make commands like `git-annex add` that add files to the Set to true to make commands like `git-annex add` that add files to the
repository add them in unlocked form. The default is to add files in repository add them in unlocked form. The default is to add files in
locked form. This only has effect in v7 repositories. locked form.
When a repository has core.symlinks set to false, it implicitly When a repository has core.symlinks set to false, it implicitly
sets annex.addunlocked to true. sets annex.addunlocked to true.
@ -1049,8 +1049,7 @@ Here are all the supported configuration settings.
Makes the watch and assistant commands delay for the specified number of Makes the watch and assistant commands delay for the specified number of
seconds before adding a newly created file to the annex. Normally this seconds before adding a newly created file to the annex. Normally this
is not needed, because they already wait for all writers of the file is not needed, because they already wait for all writers of the file
to close it. On Mac OSX, this defaults to to close it.
1 second, to work around a bad interaction with software there.
* `annex.expireunused` * `annex.expireunused`

View file

@ -9,50 +9,15 @@ want to lose it in a fumblefingered mistake.
bash: some_file: Permission denied bash: some_file: Permission denied
Sometimes though you want to modify a file. Maybe once, or maybe Sometimes though you want to modify a file. Maybe once, or maybe
repeatedly. To modify a locked file, you have to first unlock it, repeatedly. To support this, git-annex also supports unlocked files.
by running `git annex unlock`. They are stored in the git repository differently, and they appear as
regular files in the working tree, instead of the symbolic links used for
locked files.
# git annex unlock some_file ## adding unlocked files
# echo "new content" > some_file
Back before git-annex version 7, and its v7 repository mode, unlocking a file Instead of using `git annex add`, use `git add`, and the file will be
like this was a transient thing. You'd modify it and then `git annex add` the stored in git-annex, but left unlocked.
modified version to the annex, and finally `git commit`. The new version of
the file was then back to being locked.
# git annex add some_file
add some_file
# git commit
But, that had some problems. The main one is that some users want to be able
to edit files repeatedly, without manually having to unlock them every time.
The [[direct_mode]] made all files be unlocked all the time, but it
had many problems of its own.
## enter v7 mode
This led to the v7 repository mode, which makes unlocked files remain
unlocked after they're committed, so you can keep changing them and
committing the changes whenever you'd like. It also lets you use more
normal git commands (or even interfaces on top of git) for handling
annexed files.
To get a repository into v7 mode, you can [[upgrade|upgrades]] it.
This will eventually happen automatically, but for now it's a manual process
(be sure to read [[upgrades]] before doing this):
# git annex upgrade
Or, you can init a new repository in v7 mode.
# git init
# git annex init --version=7
## using it
Using a v7 repository is easy! Simply use regular git commands to add
and commit files. In a git-annex repository, git will use git-annex
to store the file contents, and the files will be left unlocked.
[[!template id=note text=""" [[!template id=note text="""
Want `git add` to add some file contents to the annex, but store the contents of Want `git add` to add some file contents to the annex, but store the contents of
@ -94,7 +59,7 @@ mode is used. To make them always use unlocked mode, run:
## mixing locked and unlocked files ## mixing locked and unlocked files
A v7 repository can contain both locked and unlocked files. You can switch A repository can contain both locked and unlocked files. You can switch
a file back and forth using the `git annex lock` and `git annex unlock` a file back and forth using the `git annex lock` and `git annex unlock`
commands. This changes what's stored in git between a git-annex symlink commands. This changes what's stored in git between a git-annex symlink
(locked) and a git-annex pointer file (unlocked). To add a file to (locked) and a git-annex pointer file (unlocked). To add a file to
@ -110,7 +75,7 @@ automatically sets up a repository to use all unlocked files.
## imperfections ## imperfections
Unlocked files in v7 repositories mostly work very well, but there are a Unlocked files mostly work very well, but there are a
few imperfections which you should be aware of when using them. few imperfections which you should be aware of when using them.
1. `git stash`, `git cherry-pick` and `git reset --hard` don't update 1. `git stash`, `git cherry-pick` and `git reset --hard` don't update

View file

@ -55,6 +55,8 @@ were added in v7. See below for details about what's new in v6/v7.
## v5 -> v6 (git-annex version 6.x) ## v5 -> v6 (git-annex version 6.x)
v5 repositories are automatically upgraded to v6.
A v6 git-annex repository can have some files locked while other files are A v6 git-annex repository can have some files locked while other files are
unlocked, and all git and git-annex commands can be used on both locked and unlocked, and all git and git-annex commands can be used on both locked and
unlocked files. It's a good idea to make sure that all users of the unlocked files. It's a good idea to make sure that all users of the
@ -89,11 +91,6 @@ same tradeoff.
See [[tips/unlocked_files/]] for more details about locked files and thin See [[tips/unlocked_files/]] for more details about locked files and thin
mode. mode.
Normally you will need to run git-annex upgrade to perform this upgrade.
But, when a new enough git-annex is used in a direct mode repository,
it will be automatically upgraded and configured to use unlocked files
instead of direct mode.
## v4 -> v5 (git-annex version 5.x) ## v4 -> v5 (git-annex version 5.x)
The upgrade from v4 to v5 is handled The upgrade from v4 to v5 is handled