on second thought, InodeCache should use getFileSize

This is necessary for interop between inode caches created on unix and
windows. Which is more important than supporting inodecaches for large keys
with the wrong size, which are broken anyway.

There should be no slowdown from this change, except on Windows.
This commit is contained in:
Joey Hess 2015-01-20 19:35:50 -04:00
parent 467b77fd3b
commit 068aaf943b
6 changed files with 15 additions and 16 deletions

View file

@ -174,10 +174,10 @@ sameInodeCache file old = go =<< withTSDelta (liftIO . genInodeCache file)
go (Just curr) = elemInodeCaches curr old go (Just curr) = elemInodeCaches curr old
{- Checks if a FileStatus matches the recorded InodeCache of a file. -} {- Checks if a FileStatus matches the recorded InodeCache of a file. -}
sameFileStatus :: Key -> FileStatus -> Annex Bool sameFileStatus :: Key -> FilePath -> FileStatus -> Annex Bool
sameFileStatus key status = do sameFileStatus key f status = do
old <- recordedInodeCache key old <- recordedInodeCache key
curr <- withTSDelta $ \delta -> liftIO $ toInodeCache delta status curr <- withTSDelta $ \delta -> liftIO $ toInodeCache delta f status
case (old, curr) of case (old, curr) of
(_, Just c) -> elemInodeCaches c old (_, Just c) -> elemInodeCaches c old
([], Nothing) -> return True ([], Nothing) -> return True

View file

@ -56,7 +56,7 @@ stageDirect = do
go (file, Just sha, Just mode) = withTSDelta $ \delta -> do go (file, Just sha, Just mode) = withTSDelta $ \delta -> do
shakey <- catKey sha mode shakey <- catKey sha mode
mstat <- liftIO $ catchMaybeIO $ getSymbolicLinkStatus file mstat <- liftIO $ catchMaybeIO $ getSymbolicLinkStatus file
mcache <- liftIO $ maybe (pure Nothing) (toInodeCache delta) mstat mcache <- liftIO $ maybe (pure Nothing) (toInodeCache delta file) mstat
filekey <- isAnnexLink file filekey <- isAnnexLink file
case (shakey, filekey, mstat, mcache) of case (shakey, filekey, mstat, mcache) of
(_, Just key, _, _) (_, Just key, _, _)

View file

@ -224,7 +224,7 @@ onAddDirect symlinkssupported matcher file fs = do
v <- liftAnnex $ catKeyFile file v <- liftAnnex $ catKeyFile file
case (v, fs) of case (v, fs) of
(Just key, Just filestatus) -> (Just key, Just filestatus) ->
ifM (liftAnnex $ sameFileStatus key filestatus) ifM (liftAnnex $ sameFileStatus key file filestatus)
{- It's possible to get an add event for {- It's possible to get an add event for
- an existing file that is not - an existing file that is not
- really modified, but it might have - really modified, but it might have

View file

@ -160,8 +160,9 @@ ingest Nothing = return (Nothing, Nothing)
ingest (Just source) = withTSDelta $ \delta -> do ingest (Just source) = withTSDelta $ \delta -> do
backend <- chooseBackend $ keyFilename source backend <- chooseBackend $ keyFilename source
k <- genKey source backend k <- genKey source backend
ms <- liftIO $ catchMaybeIO $ getFileStatus $ contentLocation source let src = contentLocation source
mcache <- maybe (pure Nothing) (liftIO . toInodeCache delta) ms ms <- liftIO $ catchMaybeIO $ getFileStatus src
mcache <- maybe (pure Nothing) (liftIO . toInodeCache delta src) ms
case (mcache, inodeCache source) of case (mcache, inodeCache source) of
(_, Nothing) -> go k mcache ms (_, Nothing) -> go k mcache ms
(Just newc, Just c) | compareStrong c newc -> go k mcache ms (Just newc, Just c) | compareStrong c newc -> go k mcache ms

View file

@ -70,7 +70,7 @@ statusDirect f = checkstatus =<< liftIO (catchMaybeIO $ getFileStatus f)
| not (isSymbolicLink s) = checkkey s =<< catKeyFile f | not (isSymbolicLink s) = checkkey s =<< catKeyFile f
| otherwise = Just <$> checkNew f | otherwise = Just <$> checkNew f
checkkey s (Just k) = ifM (sameFileStatus k s) checkkey s (Just k) = ifM (sameFileStatus k f s)
( return Nothing ( return Nothing
, return $ Just ModifiedFile , return $ Just ModifiedFile
) )

View file

@ -40,15 +40,12 @@ module Utility.InodeCache (
import Common import Common
import System.PosixCompat.Types import System.PosixCompat.Types
import Utility.QuickCheck import Utility.QuickCheck
-- While fileSize overflows and wraps at 2gb on Windows,
-- it's ok for purposes of comparison.
import System.PosixCompat.Files (fileSize)
#ifdef mingw32_HOST_OS #ifdef mingw32_HOST_OS
import Data.Word (Word64) import Data.Word (Word64)
#endif #endif
data InodeCachePrim = InodeCachePrim FileID FileOffset EpochTime data InodeCachePrim = InodeCachePrim FileID Integer EpochTime
deriving (Show, Eq, Ord) deriving (Show, Eq, Ord)
newtype InodeCache = InodeCache InodeCachePrim newtype InodeCache = InodeCache InodeCachePrim
@ -115,15 +112,16 @@ readInodeCache s = case words s of
genInodeCache :: FilePath -> TSDelta -> IO (Maybe InodeCache) genInodeCache :: FilePath -> TSDelta -> IO (Maybe InodeCache)
genInodeCache f delta = catchDefaultIO Nothing $ genInodeCache f delta = catchDefaultIO Nothing $
toInodeCache delta =<< getFileStatus f toInodeCache delta f =<< getFileStatus f
toInodeCache :: TSDelta -> FileStatus -> IO (Maybe InodeCache) toInodeCache :: TSDelta -> FilePath -> FileStatus -> IO (Maybe InodeCache)
toInodeCache (TSDelta getdelta) s toInodeCache (TSDelta getdelta) f s
| isRegularFile s = do | isRegularFile s = do
delta <- getdelta delta <- getdelta
sz <- getFileSize' f s
return $ Just $ InodeCache $ InodeCachePrim return $ Just $ InodeCache $ InodeCachePrim
(fileID s) (fileID s)
(fileSize s) sz
(modificationTime s + delta) (modificationTime s + delta)
| otherwise = pure Nothing | otherwise = pure Nothing