diff options
author | Joey Hess <joeyh@joeyh.name> | 2015-12-22 15:23:27 -0400 |
---|---|---|
committer | Joey Hess <joeyh@joeyh.name> | 2015-12-22 15:23:27 -0400 |
commit | 56d1ad16c61d9e5abe1c123b3f791c9e5f641bd8 (patch) | |
tree | 1c6b88f7e44b18551cc6090ba465e0375df03e44 /Annex | |
parent | 00e240f3803384ae8761f2d5bc95319351f4e0fa (diff) |
finish v6 support for assistant
Seems to basically work now!
Diffstat (limited to 'Annex')
-rw-r--r-- | Annex/Ingest.hs | 104 |
1 files changed, 58 insertions, 46 deletions
diff --git a/Annex/Ingest.hs b/Annex/Ingest.hs index 0fd32a042..707f71eff 100644 --- a/Annex/Ingest.hs +++ b/Annex/Ingest.hs @@ -8,6 +8,7 @@ {-# LANGUAGE CPP #-} module Annex.Ingest ( + LockedDown(..), lockDown, ingest, finishIngestDirect, @@ -33,7 +34,6 @@ import Annex.ReplaceFile import Utility.Tmp import Utility.CopyFile import Annex.InodeSentinal -import Annex.Version #ifdef WITH_CLIBS #ifndef __ANDROID__ import Utility.Touch @@ -42,46 +42,42 @@ import Utility.Touch import Control.Exception (IOException) +data LockedDown = LockedDown + { lockingFile :: Bool + , keySource :: KeySource + } + deriving (Show) + {- The file that's being ingested is locked down before a key is generated, - to prevent it from being modified in between. This lock down is not - perfect at best (and pretty weak at worst). For example, it does not - guard against files that are already opened for write by another process. - - So a KeySource is returned. Its inodeCache can be used to detect any - - changes that might be made to the file after it was locked down. + - So, the InodeCache can be used to detect any changes that might be made + - to the file after it was locked down. - - When possible, the file is hard linked to a temp directory. This guards - against some changes, like deletion or overwrite of the file, and - allows lsof checks to be done more efficiently when adding a lot of files. - + - If the file is to be locked, lockingfile is True. Then the write + - bit is removed from the file as part of lock down to guard against + - further writes. + - - Lockdown can fail if a file gets deleted, and Nothing will be returned. -} -lockDown :: FilePath -> Annex (Maybe KeySource) -lockDown = either +lockDown :: Bool -> FilePath -> Annex (Maybe LockedDown) +lockDown lockingfile file = either (\e -> warning (show e) >> return Nothing) (return . Just) - <=< lockDown' + =<< lockDown' lockingfile file -lockDown' :: FilePath -> Annex (Either IOException KeySource) -lockDown' file = ifM crippledFileSystem +lockDown' :: Bool -> FilePath -> Annex (Either IOException LockedDown) +lockDown' lockingfile file = ifM crippledFileSystem ( withTSDelta $ liftIO . tryIO . nohardlink , tryIO $ do tmp <- fromRepo gitAnnexTmpMiscDir createAnnexDirectory tmp - go tmp - ) - where - {- In indirect mode, the write bit is removed from the file as part - - of lock down to guard against further writes, and because objects - - in the annex have their write bit disabled anyway. - - - - Freezing the content early also lets us fail early when - - someone else owns the file. - - - - This is not done in direct mode, because files there need to - - remain writable at all times. - -} - go tmp = do - unlessM isDirect $ + when lockingfile $ freezeContent file withTSDelta $ \delta -> liftIO $ do (tmpfile, h) <- openTempFile tmp $ @@ -89,9 +85,11 @@ lockDown' file = ifM crippledFileSystem hClose h nukeFile tmpfile withhardlink delta tmpfile `catchIO` const (nohardlink delta) + ) + where nohardlink delta = do cache <- genInodeCache file delta - return KeySource + return $ LockedDown lockingfile $ KeySource { keyFilename = file , contentLocation = file , inodeCache = cache @@ -99,7 +97,7 @@ lockDown' file = ifM crippledFileSystem withhardlink delta tmpfile = do createLink file tmpfile cache <- genInodeCache tmpfile delta - return KeySource + return $ LockedDown lockingfile $ KeySource { keyFilename = file , contentLocation = tmpfile , inodeCache = cache @@ -107,12 +105,13 @@ lockDown' file = ifM crippledFileSystem {- Ingests a locked down file into the annex. - - - In direct mode, leaves the file alone, and just updates bookkeeping - - information. + - The file may be added to the git repository as a locked or an unlocked + - file. When unlocked, the work tree file is left alone. When locked, + - the work tree file is deleted, in preparation for adding the symlink. -} -ingest :: Maybe KeySource -> Annex (Maybe Key, Maybe InodeCache) +ingest :: Maybe LockedDown -> Annex (Maybe Key, Maybe InodeCache) ingest Nothing = return (Nothing, Nothing) -ingest (Just source) = withTSDelta $ \delta -> do +ingest (Just (LockedDown lockingfile source)) = withTSDelta $ \delta -> do backend <- chooseBackend $ keyFilename source k <- genKey source backend let src = contentLocation source @@ -123,43 +122,56 @@ ingest (Just source) = withTSDelta $ \delta -> do (Just newc, Just c) | compareStrong c newc -> go k mcache ms _ -> failure "changed while it was being added" where - go k mcache ms = ifM isDirect - ( godirect k mcache ms - , goindirect k mcache ms - ) - - goindirect (Just (key, _)) mcache ms = do + go (Just (key, _)) mcache (Just s) + | lockingfile = golocked key mcache s + | otherwise = ifM isDirect + ( godirect key mcache s + , gounlocked key mcache s + ) + go _ _ _ = failure "failed to generate a key" + + golocked key mcache s = do catchNonAsync (moveAnnex key $ contentLocation source) (restoreFile (keyFilename source) key) - maybe noop (genMetaData key (keyFilename source)) ms liftIO $ nukeFile $ keyFilename source - return (Just key, mcache) - goindirect _ _ _ = failure "failed to generate a key" + success key mcache s + + gounlocked key (Just cache) s = do + r <- linkAnnex key (keyFilename source) (Just cache) + case r of + LinkAnnexFailed -> failure "failed to link to annex" + _ -> success key (Just cache) s + gounlocked _ _ _ = failure "failed statting file" - godirect (Just (key, _)) (Just cache) ms = do + godirect key (Just cache) s = do addInodeCache key cache - maybe noop (genMetaData key (keyFilename source)) ms finishIngestDirect key source - return (Just key, Just cache) - godirect _ _ _ = failure "failed to generate a key" + success key (Just cache) s + godirect _ _ _ = failure "failed statting file" + + success k mcache s = do + genMetaData k (keyFilename source) s + return (Just k, mcache) failure msg = do warning $ keyFilename source ++ " " ++ msg - when (contentLocation source /= keyFilename source) $ - liftIO $ nukeFile $ contentLocation source + cleanCruft source return (Nothing, Nothing) finishIngestDirect :: Key -> KeySource -> Annex () finishIngestDirect key source = do void $ addAssociatedFile key $ keyFilename source - when (contentLocation source /= keyFilename source) $ - liftIO $ nukeFile $ contentLocation source + cleanCruft source {- Copy to any other locations using the same key. -} otherfs <- filter (/= keyFilename source) <$> associatedFiles key forM_ otherfs $ addContentWhenNotPresent key (keyFilename source) +cleanCruft :: KeySource -> Annex () +cleanCruft source = when (contentLocation source /= keyFilename source) $ + liftIO $ nukeFile $ contentLocation source + {- On error, put the file back so it doesn't seem to have vanished. - This can be called before or after the symlink is in place. -} restoreFile :: FilePath -> Key -> SomeException -> Annex a |