v7 for all repositories
* Default to v7 for new repositories. * Automatically upgrade v5 repositories to v7.
This commit is contained in:
parent
1558e03014
commit
3f0eef4baa
29 changed files with 127 additions and 482 deletions
|
@ -17,8 +17,6 @@ import qualified Annex
|
|||
import Annex.UUID
|
||||
import Annex.AdjustedBranch
|
||||
import Annex.Action
|
||||
import Annex.Version
|
||||
import Upgrade
|
||||
import Types.StandardGroups
|
||||
import Logs.PreferredContent
|
||||
import qualified Annex.Branch
|
||||
|
@ -62,14 +60,13 @@ initRepo True primary_assistant_repo dir desc mgroup = inDir dir $ do
|
|||
, Param "-m"
|
||||
, Param "created repository"
|
||||
]
|
||||
{- Repositories directly managed by the assistant use v7 unlocked
|
||||
- with annex.thin set.
|
||||
{- Repositories directly managed by the assistant use
|
||||
- an adjusted unlocked branch with annex.thin set.
|
||||
-
|
||||
- Automatic gc is disabled, as it can be slow. Insted, gc is done
|
||||
- once a day.
|
||||
-}
|
||||
when primary_assistant_repo $ do
|
||||
void $ upgrade True versionForAdjustedBranch
|
||||
void $ enterAdjustedBranch (LinkAdjustment UnlockAdjustment)
|
||||
setConfig (annexConfig "thin") (Git.Config.boolConfig True)
|
||||
inRepo $ Git.Command.run
|
||||
|
|
|
@ -20,7 +20,6 @@ import Assistant.Drop
|
|||
import Types.Transfer
|
||||
import Logs.Location
|
||||
import qualified Annex.Queue
|
||||
import qualified Git.LsFiles
|
||||
import Utility.ThreadScheduler
|
||||
import qualified Utility.Lsof as Lsof
|
||||
import qualified Utility.DirWatcher as DirWatcher
|
||||
|
@ -32,7 +31,6 @@ import Annex.Link
|
|||
import Annex.Perms
|
||||
import Annex.CatFile
|
||||
import Annex.InodeSentinal
|
||||
import Annex.Version
|
||||
import Annex.CurrentBranch
|
||||
import qualified Annex
|
||||
import Utility.InodeCache
|
||||
|
@ -53,8 +51,7 @@ commitThread :: NamedThread
|
|||
commitThread = namedThread "Committer" $ do
|
||||
havelsof <- liftIO $ inPath "lsof"
|
||||
delayadd <- liftAnnex $
|
||||
maybe delayaddDefault (return . Just . Seconds)
|
||||
=<< annexDelayAdd <$> Annex.getGitConfig
|
||||
fmap Seconds . annexDelayAdd <$> Annex.getGitConfig
|
||||
msg <- liftAnnex Command.Sync.commitMsg
|
||||
lockdowndir <- liftAnnex $ fromRepo gitAnnexTmpWatcherDir
|
||||
liftAnnex $ do
|
||||
|
@ -239,19 +236,6 @@ commitStaged msg = do
|
|||
Command.Sync.updateBranches =<< getCurrentBranch
|
||||
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
|
||||
- have not yet actually been added to the annex, and that has to be done
|
||||
- now, before committing.
|
||||
|
@ -274,49 +258,22 @@ delayaddDefault = return Nothing
|
|||
handleAdds :: FilePath -> Bool -> Maybe Seconds -> [Change] -> Assistant [Change]
|
||||
handleAdds lockdowndir havelsof delayadd cs = returnWhen (null incomplete) $ do
|
||||
let (pending, inprocess) = partition isPendingAddChange incomplete
|
||||
unlocked <- liftAnnex versionSupportsUnlockedPointers
|
||||
let lockingfiles = not unlocked
|
||||
let lockdownconfig = LockDownConfig
|
||||
{ lockingFile = lockingfiles
|
||||
{ lockingFile = False
|
||||
, hardlinkFileTmpDir = Just lockdowndir
|
||||
}
|
||||
(pending', cleanup) <- if unlocked
|
||||
then return (pending, noop)
|
||||
else findnew pending
|
||||
(postponed, toadd) <- partitionEithers
|
||||
<$> safeToAdd lockdowndir lockdownconfig havelsof delayadd pending' inprocess
|
||||
cleanup
|
||||
<$> safeToAdd lockdowndir lockdownconfig havelsof delayadd pending inprocess
|
||||
|
||||
unless (null postponed) $
|
||||
refillChanges postponed
|
||||
|
||||
returnWhen (null toadd) $ do
|
||||
added <- addaction toadd $
|
||||
catMaybes <$>
|
||||
if not lockingfiles
|
||||
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
|
||||
catMaybes <$> addunlocked toadd
|
||||
return $ added ++ otherchanges
|
||||
where
|
||||
(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
|
||||
| c = return otherchanges
|
||||
|
@ -328,10 +285,10 @@ handleAdds lockdowndir havelsof delayadd cs = returnWhen (null incomplete) $ do
|
|||
where
|
||||
ks = keySource ld
|
||||
doadd = sanitycheck ks $ do
|
||||
(mkey, mcache) <- liftAnnex $ do
|
||||
(mkey, _mcache) <- liftAnnex $ do
|
||||
showStart "add" $ keyFilename ks
|
||||
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
|
||||
|
||||
{- 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
|
||||
let source = keySource $ lockedDown change
|
||||
liftAnnex $ finishIngestUnlocked key source
|
||||
done change Nothing (keyFilename source) key
|
||||
done change (keyFilename source) key
|
||||
|
||||
removedKeysMap :: InodeComparisonType -> [Change] -> Annex (M.Map InodeCacheKey Key)
|
||||
removedKeysMap ct l = do
|
||||
|
@ -379,17 +336,10 @@ handleAdds lockdowndir havelsof delayadd cs = returnWhen (null incomplete) $ do
|
|||
liftAnnex showEndFail
|
||||
return Nothing
|
||||
|
||||
done change mcache file key = liftAnnex $ do
|
||||
done change file key = liftAnnex $ do
|
||||
logStatus key InfoPresent
|
||||
ifM versionSupportsUnlockedPointers
|
||||
( do
|
||||
mode <- liftIO $ catchMaybeIO $ fileMode <$> getFileStatus file
|
||||
stagePointerFile file mode =<< hashPointerFile key
|
||||
, do
|
||||
link <- makeLink file key mcache
|
||||
when DirWatcher.eventsCoalesce $
|
||||
stageSymlink file =<< hashSymlink link
|
||||
)
|
||||
mode <- liftIO $ catchMaybeIO $ fileMode <$> getFileStatus file
|
||||
stagePointerFile file mode =<< hashPointerFile key
|
||||
showEndOk
|
||||
return $ Just $ finishedChange change key
|
||||
|
||||
|
|
|
@ -36,7 +36,6 @@ import Annex.Link
|
|||
import Annex.FileMatcher
|
||||
import Annex.Content
|
||||
import Annex.ReplaceFile
|
||||
import Annex.Version
|
||||
import Annex.InodeSentinal
|
||||
import Git.Types
|
||||
import Git.FilePath
|
||||
|
@ -90,11 +89,8 @@ runWatcher :: Assistant ()
|
|||
runWatcher = do
|
||||
startup <- asIO1 startupScan
|
||||
matcher <- liftAnnex largeFilesMatcher
|
||||
unlocked <- liftAnnex versionSupportsUnlockedPointers
|
||||
symlinkssupported <- liftAnnex $ coreSymlinks <$> Annex.getGitConfig
|
||||
addhook <- hook $ if unlocked
|
||||
then onAddUnlocked symlinkssupported matcher
|
||||
else onAdd matcher
|
||||
addhook <- hook $ onAddUnlocked symlinkssupported matcher
|
||||
delhook <- hook onDel
|
||||
addsymlinkhook <- hook onAddSymlink
|
||||
deldirhook <- hook onDelDir
|
||||
|
@ -205,13 +201,6 @@ add largefilematcher file = ifM (liftAnnex $ checkFileMatcher largefilematcher f
|
|||
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 ds = scanComplete ds || forceRestage ds
|
||||
|
||||
|
@ -356,8 +345,7 @@ onDel file _ = do
|
|||
onDel' :: FilePath -> Annex ()
|
||||
onDel' file = do
|
||||
topfile <- inRepo (toTopFilePath file)
|
||||
whenM versionSupportsUnlockedPointers $
|
||||
withkey $ flip Database.Keys.removeAssociatedFile topfile
|
||||
withkey $ flip Database.Keys.removeAssociatedFile topfile
|
||||
Annex.Queue.addUpdateIndex =<<
|
||||
inRepo (Git.UpdateIndex.unstageFile file)
|
||||
where
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue