Direct mode: Support filesystems like FAT which can change their inodes each time they are mounted.
This commit is contained in:
parent
0f4cc559a7
commit
624e34649f
7 changed files with 69 additions and 15 deletions
2
Annex.hs
2
Annex.hs
|
@ -116,6 +116,7 @@ data AnnexState = AnnexState
|
||||||
, flags :: M.Map String Bool
|
, flags :: M.Map String Bool
|
||||||
, fields :: M.Map String String
|
, fields :: M.Map String String
|
||||||
, cleanup :: M.Map String (Annex ())
|
, cleanup :: M.Map String (Annex ())
|
||||||
|
, inodeschanged :: Maybe Bool
|
||||||
}
|
}
|
||||||
|
|
||||||
newState :: Git.Repo -> AnnexState
|
newState :: Git.Repo -> AnnexState
|
||||||
|
@ -145,6 +146,7 @@ newState gitrepo = AnnexState
|
||||||
, flags = M.empty
|
, flags = M.empty
|
||||||
, fields = M.empty
|
, fields = M.empty
|
||||||
, cleanup = M.empty
|
, cleanup = M.empty
|
||||||
|
, inodeschanged = Nothing
|
||||||
}
|
}
|
||||||
|
|
||||||
{- Makes an Annex state object for the specified git repo.
|
{- Makes an Annex state object for the specified git repo.
|
||||||
|
|
|
@ -304,8 +304,8 @@ prepSendAnnex key = withObjectLoc key indirect direct
|
||||||
direct (f:fs) = do
|
direct (f:fs) = do
|
||||||
cache <- recordedInodeCache key
|
cache <- recordedInodeCache key
|
||||||
-- check that we have a good file
|
-- check that we have a good file
|
||||||
ifM (liftIO $ compareInodeCache f cache)
|
ifM (sameInodeCache f cache)
|
||||||
( return $ Just (f, liftIO $ compareInodeCache f cache)
|
( return $ Just (f, sameInodeCache f cache)
|
||||||
, direct fs
|
, direct fs
|
||||||
)
|
)
|
||||||
|
|
||||||
|
@ -356,7 +356,7 @@ removeAnnex key = withObjectLoc key remove removedirect
|
||||||
cache <- recordedInodeCache key
|
cache <- recordedInodeCache key
|
||||||
removeInodeCache key
|
removeInodeCache key
|
||||||
mapM_ (resetfile cache) fs
|
mapM_ (resetfile cache) fs
|
||||||
resetfile cache f = whenM (liftIO $ compareInodeCache f cache) $ do
|
resetfile cache f = whenM (sameInodeCache f cache) $ do
|
||||||
l <- calcGitLink f key
|
l <- calcGitLink f key
|
||||||
top <- fromRepo Git.repoPath
|
top <- fromRepo Git.repoPath
|
||||||
cwd <- liftIO getCurrentDirectory
|
cwd <- liftIO getCurrentDirectory
|
||||||
|
|
|
@ -1,6 +1,6 @@
|
||||||
{- git-annex file content managing for direct mode
|
{- git-annex file content managing for direct mode
|
||||||
-
|
-
|
||||||
- Copyright 2010,2012 Joey Hess <joey@kitenet.net>
|
- Copyright 2012-2013 Joey Hess <joey@kitenet.net>
|
||||||
-
|
-
|
||||||
- Licensed under the GNU GPL version 3 or higher.
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
@ -14,12 +14,13 @@ module Annex.Content.Direct (
|
||||||
recordedInodeCache,
|
recordedInodeCache,
|
||||||
updateInodeCache,
|
updateInodeCache,
|
||||||
writeInodeCache,
|
writeInodeCache,
|
||||||
compareInodeCache,
|
sameInodeCache,
|
||||||
removeInodeCache,
|
removeInodeCache,
|
||||||
toInodeCache,
|
toInodeCache,
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Common.Annex
|
import Common.Annex
|
||||||
|
import qualified Annex
|
||||||
import Annex.Perms
|
import Annex.Perms
|
||||||
import qualified Git
|
import qualified Git
|
||||||
import Utility.TempFile
|
import Utility.TempFile
|
||||||
|
@ -94,9 +95,7 @@ normaliseAssociatedFile file = do
|
||||||
- expected mtime and inode.
|
- expected mtime and inode.
|
||||||
-}
|
-}
|
||||||
goodContent :: Key -> FilePath -> Annex Bool
|
goodContent :: Key -> FilePath -> Annex Bool
|
||||||
goodContent key file = do
|
goodContent key file = sameInodeCache file =<< recordedInodeCache key
|
||||||
old <- recordedInodeCache key
|
|
||||||
liftIO $ compareInodeCache file old
|
|
||||||
|
|
||||||
changedFileStatus :: Key -> FileStatus -> Annex Bool
|
changedFileStatus :: Key -> FileStatus -> Annex Bool
|
||||||
changedFileStatus key status = do
|
changedFileStatus key status = do
|
||||||
|
@ -128,3 +127,45 @@ removeInodeCache key = withInodeCacheFile key $ \f -> do
|
||||||
|
|
||||||
withInodeCacheFile :: Key -> (FilePath -> Annex a) -> Annex a
|
withInodeCacheFile :: Key -> (FilePath -> Annex a) -> Annex a
|
||||||
withInodeCacheFile key a = a =<< inRepo (gitAnnexInodeCache key)
|
withInodeCacheFile key a = a =<< inRepo (gitAnnexInodeCache key)
|
||||||
|
|
||||||
|
{- Checks if a file's InodeCache matches its current info.
|
||||||
|
-
|
||||||
|
- If the inodes have changed, only the size and mtime are compared.
|
||||||
|
-}
|
||||||
|
sameInodeCache :: FilePath -> Maybe InodeCache -> Annex Bool
|
||||||
|
sameInodeCache _ Nothing = return False
|
||||||
|
sameInodeCache file (Just old) = go =<< liftIO (genInodeCache file)
|
||||||
|
where
|
||||||
|
go Nothing = return False
|
||||||
|
go (Just curr)
|
||||||
|
| curr == old = return True
|
||||||
|
| otherwise = ifM inodesChanged
|
||||||
|
( return $ compareWeak curr old
|
||||||
|
, return False
|
||||||
|
)
|
||||||
|
|
||||||
|
{- Some filesystems get new inodes each time they are mounted.
|
||||||
|
- In order to work on such a filesystem, a sentinal file is used to detect
|
||||||
|
- when the inodes have changed. -}
|
||||||
|
inodesChanged :: Annex Bool
|
||||||
|
inodesChanged = maybe calc return =<< Annex.getState Annex.inodeschanged
|
||||||
|
where
|
||||||
|
calc = do
|
||||||
|
sentinalfile <- fromRepo gitAnnexInodeSentinal
|
||||||
|
sentinalcachefile <- fromRepo gitAnnexInodeSentinalCache
|
||||||
|
scache <- liftIO $ genInodeCache sentinalfile
|
||||||
|
scached <- liftIO $ catchMaybeIO $ readInodeCache <$> readFile sentinalcachefile
|
||||||
|
case (scache, scached) of
|
||||||
|
(Just c1, Just (Just c2)) -> changed $ c1 /= c2
|
||||||
|
_ -> do
|
||||||
|
writesentinal
|
||||||
|
changed True
|
||||||
|
changed v = do
|
||||||
|
Annex.changeState $ \s -> s { Annex.inodeschanged = Just v }
|
||||||
|
return v
|
||||||
|
writesentinal = do
|
||||||
|
sentinalfile <- fromRepo gitAnnexInodeSentinal
|
||||||
|
sentinalcachefile <- fromRepo gitAnnexInodeSentinalCache
|
||||||
|
liftIO $ writeFile sentinalfile ""
|
||||||
|
liftIO $ maybe noop (writeFile sentinalcachefile . showInodeCache)
|
||||||
|
=<< genInodeCache sentinalfile
|
||||||
|
|
|
@ -85,7 +85,7 @@ addDirect file cache = do
|
||||||
got Nothing = do
|
got Nothing = do
|
||||||
showEndFail
|
showEndFail
|
||||||
return False
|
return False
|
||||||
got (Just (key, _)) = ifM (liftIO $ compareInodeCache file $ Just cache)
|
got (Just (key, _)) = ifM (sameInodeCache file $ Just cache)
|
||||||
( do
|
( do
|
||||||
stageSymlink file =<< hashSymlink =<< calcGitLink file key
|
stageSymlink file =<< hashSymlink =<< calcGitLink file key
|
||||||
writeInodeCache key cache
|
writeInodeCache key cache
|
||||||
|
|
|
@ -13,6 +13,8 @@ module Locations (
|
||||||
gitAnnexLocation,
|
gitAnnexLocation,
|
||||||
gitAnnexMapping,
|
gitAnnexMapping,
|
||||||
gitAnnexInodeCache,
|
gitAnnexInodeCache,
|
||||||
|
gitAnnexInodeSentinal,
|
||||||
|
gitAnnexInodeSentinalCache,
|
||||||
annexLocations,
|
annexLocations,
|
||||||
annexLocation,
|
annexLocation,
|
||||||
gitAnnexDir,
|
gitAnnexDir,
|
||||||
|
@ -128,6 +130,12 @@ gitAnnexInodeCache key r = do
|
||||||
loc <- gitAnnexLocation key r
|
loc <- gitAnnexLocation key r
|
||||||
return $ loc ++ ".cache"
|
return $ loc ++ ".cache"
|
||||||
|
|
||||||
|
gitAnnexInodeSentinal :: Git.Repo -> FilePath
|
||||||
|
gitAnnexInodeSentinal r = gitAnnexDir r </> "sentinal"
|
||||||
|
|
||||||
|
gitAnnexInodeSentinalCache :: Git.Repo -> FilePath
|
||||||
|
gitAnnexInodeSentinalCache r = gitAnnexInodeSentinal r ++ ".cache"
|
||||||
|
|
||||||
{- The annex directory of a repository. -}
|
{- The annex directory of a repository. -}
|
||||||
gitAnnexDir :: Git.Repo -> FilePath
|
gitAnnexDir :: Git.Repo -> FilePath
|
||||||
gitAnnexDir r = addTrailingPathSeparator $ Git.localGitDir r </> annexDir
|
gitAnnexDir r = addTrailingPathSeparator $ Git.localGitDir r </> annexDir
|
||||||
|
|
|
@ -13,6 +13,13 @@ import System.Posix.Types
|
||||||
data InodeCache = InodeCache FileID FileOffset EpochTime
|
data InodeCache = InodeCache FileID FileOffset EpochTime
|
||||||
deriving (Eq, Show)
|
deriving (Eq, Show)
|
||||||
|
|
||||||
|
{- Weak comparison of the inode caches, comparing the size and mtime, but
|
||||||
|
- not the actual inode. Useful when inodes have changed, perhaps
|
||||||
|
- due to some filesystems being remounted. -}
|
||||||
|
compareWeak :: InodeCache -> InodeCache -> Bool
|
||||||
|
compareWeak (InodeCache _ size1 mtime1) (InodeCache _ size2 mtime2) =
|
||||||
|
size1 == size2 && mtime1 == mtime2
|
||||||
|
|
||||||
showInodeCache :: InodeCache -> String
|
showInodeCache :: InodeCache -> String
|
||||||
showInodeCache (InodeCache inode size mtime) = unwords
|
showInodeCache (InodeCache inode size mtime) = unwords
|
||||||
[ show inode
|
[ show inode
|
||||||
|
@ -42,9 +49,3 @@ toInodeCache s
|
||||||
(fileSize s)
|
(fileSize s)
|
||||||
(modificationTime s)
|
(modificationTime s)
|
||||||
| otherwise = Nothing
|
| otherwise = Nothing
|
||||||
|
|
||||||
{- Compares an inode cache with the current inode of file. -}
|
|
||||||
compareInodeCache :: FilePath -> Maybe InodeCache -> IO Bool
|
|
||||||
compareInodeCache file old = do
|
|
||||||
curr <- genInodeCache file
|
|
||||||
return $ isJust curr && curr == old
|
|
||||||
|
|
2
debian/changelog
vendored
2
debian/changelog
vendored
|
@ -8,6 +8,8 @@ git-annex (3.20130217) UNRELEASED; urgency=low
|
||||||
the main local repository.
|
the main local repository.
|
||||||
* Android: Bundle now includes openssh.
|
* Android: Bundle now includes openssh.
|
||||||
* Android: Support ssh connection caching.
|
* Android: Support ssh connection caching.
|
||||||
|
* Direct mode: Support filesystems like FAT which can change their inodes
|
||||||
|
each time they are mounted.
|
||||||
|
|
||||||
-- Joey Hess <joeyh@debian.org> Sun, 17 Feb 2013 16:42:16 -0400
|
-- Joey Hess <joeyh@debian.org> Sun, 17 Feb 2013 16:42:16 -0400
|
||||||
|
|
||||||
|
|
Loading…
Reference in a new issue