summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorGravatar Joey Hess <joey@kitenet.net>2013-02-14 16:17:40 -0400
committerGravatar Joey Hess <joey@kitenet.net>2013-02-14 16:17:40 -0400
commit5fc9ccdaa5c73ec424de175962f98cc8fd63eca0 (patch)
tree1030a6fe9d351709bcdada518d4a24fa4986ed18
parent177245deb6ee3271eb44d77c2b0cd722755b2c3f (diff)
split out Utility.InodeCache
-rw-r--r--Annex/Content.hs12
-rw-r--r--Annex/Content/Direct.hs90
-rw-r--r--Annex/Direct.hs13
-rw-r--r--Command/Add.hs6
-rw-r--r--Command/Indirect.hs2
-rw-r--r--Locations.hs6
-rw-r--r--Utility/InodeCache.hs50
-rw-r--r--test.hs4
8 files changed, 95 insertions, 88 deletions
diff --git a/Annex/Content.hs b/Annex/Content.hs
index 0a66d9912..e488de274 100644
--- a/Annex/Content.hs
+++ b/Annex/Content.hs
@@ -260,7 +260,7 @@ moveAnnex key src = withObjectLoc key storeobject storedirect
storedirect' [] = storeobject =<< inRepo (gitAnnexLocation key)
storedirect' (dest:fs) = do
- updateCache key src
+ updateInodeCache key src
thawContent src
liftIO $ replaceFile dest $ moveFile src
liftIO $ forM_ fs $ \f -> replaceFile f $
@@ -308,10 +308,10 @@ prepSendAnnex key = withObjectLoc key indirect direct
indirect f = return $ Just (f, return True)
direct [] = return Nothing
direct (f:fs) = do
- cache <- recordedCache key
+ cache <- recordedInodeCache key
-- check that we have a good file
- ifM (compareCache f cache)
- ( return $ Just (f, compareCache f cache)
+ ifM (liftIO $ compareInodeCache f cache)
+ ( return $ Just (f, liftIO $ compareInodeCache f cache)
, direct fs
)
@@ -361,10 +361,10 @@ removeAnnex key = withObjectLoc key remove removedirect
liftIO $ removeFile file
cleanObjectLoc key
removedirect fs = do
- cache <- recordedCache key
+ cache <- recordedInodeCache key
mapM_ (resetfile cache) fs
cleanObjectLoc key
- resetfile cache f = whenM (compareCache f cache) $ do
+ resetfile cache f = whenM (liftIO $ compareInodeCache f cache) $ do
l <- calcGitLink f key
top <- fromRepo Git.repoPath
cwd <- liftIO getCurrentDirectory
diff --git a/Annex/Content/Direct.hs b/Annex/Content/Direct.hs
index 9e917cf68..07edb4dd9 100644
--- a/Annex/Content/Direct.hs
+++ b/Annex/Content/Direct.hs
@@ -11,14 +11,11 @@ module Annex.Content.Direct (
addAssociatedFile,
goodContent,
changedFileStatus,
- updateCache,
- recordedCache,
- compareCache,
- writeCache,
- genCache,
- toCache,
- Cache(..),
- prop_read_show_direct
+ recordedInodeCache,
+ updateInodeCache,
+ writeInodeCache,
+ compareInodeCache,
+ toInodeCache,
) where
import Common.Annex
@@ -26,8 +23,7 @@ import Annex.Perms
import qualified Git
import Utility.TempFile
import Logs.Location
-
-import System.Posix.Types
+import Utility.InodeCache
{- Absolute FilePaths of Files in the tree that are associated with a key. -}
associatedFiles :: Key -> Annex [FilePath]
@@ -98,70 +94,30 @@ normaliseAssociatedFile file = do
-}
goodContent :: Key -> FilePath -> Annex Bool
goodContent key file = do
- old <- recordedCache key
- compareCache file old
+ old <- recordedInodeCache key
+ liftIO $ compareInodeCache file old
changedFileStatus :: Key -> FileStatus -> Annex Bool
changedFileStatus key status = do
- old <- recordedCache key
- let curr = toCache status
+ old <- recordedInodeCache key
+ let curr = toInodeCache status
return $ curr /= old
-{- Gets the recorded cache for a key. -}
-recordedCache :: Key -> Annex (Maybe Cache)
-recordedCache key = withCacheFile key $ \cachefile ->
- liftIO $ catchDefaultIO Nothing $ readCache <$> readFile cachefile
-
-{- Compares a cache with the current cache for a file. -}
-compareCache :: FilePath -> Maybe Cache -> Annex Bool
-compareCache file old = do
- curr <- liftIO $ genCache file
- return $ isJust curr && curr == old
+{- Gets the recorded inode cache for a key. -}
+recordedInodeCache :: Key -> Annex (Maybe InodeCache)
+recordedInodeCache key = withInodeCacheFile key $ \f ->
+ liftIO $ catchDefaultIO Nothing $ readInodeCache <$> readFile f
{- Stores a cache of attributes for a file that is associated with a key. -}
-updateCache :: Key -> FilePath -> Annex ()
-updateCache key file = maybe noop (writeCache key) =<< liftIO (genCache file)
+updateInodeCache :: Key -> FilePath -> Annex ()
+updateInodeCache key file = maybe noop (writeInodeCache key)
+ =<< liftIO (genInodeCache file)
{- Writes a cache for a key. -}
-writeCache :: Key -> Cache -> Annex ()
-writeCache key cache = withCacheFile key $ \cachefile -> do
- createContentDir cachefile
- liftIO $ writeFile cachefile $ showCache cache
-
-{- Cache a file's inode, size, and modification time to determine if it's
- - been changed. -}
-data Cache = Cache FileID FileOffset EpochTime
- deriving (Eq, Show)
-
-showCache :: Cache -> String
-showCache (Cache inode size mtime) = unwords
- [ show inode
- , show size
- , show mtime
- ]
-
-readCache :: String -> Maybe Cache
-readCache s = case words s of
- (inode:size:mtime:_) -> Cache
- <$> readish inode
- <*> readish size
- <*> readish mtime
- _ -> Nothing
-
--- for quickcheck
-prop_read_show_direct :: Cache -> Bool
-prop_read_show_direct c = readCache (showCache c) == Just c
-
-genCache :: FilePath -> IO (Maybe Cache)
-genCache f = catchDefaultIO Nothing $ toCache <$> getFileStatus f
-
-toCache :: FileStatus -> Maybe Cache
-toCache s
- | isRegularFile s = Just $ Cache
- (fileID s)
- (fileSize s)
- (modificationTime s)
- | otherwise = Nothing
+writeInodeCache :: Key -> InodeCache -> Annex ()
+writeInodeCache key cache = withInodeCacheFile key $ \f -> do
+ createContentDir f
+ liftIO $ writeFile f $ showInodeCache cache
-withCacheFile :: Key -> (FilePath -> Annex a) -> Annex a
-withCacheFile key a = a =<< inRepo (gitAnnexCache key)
+withInodeCacheFile :: Key -> (FilePath -> Annex a) -> Annex a
+withInodeCacheFile key a = a =<< inRepo (gitAnnexInodeCache key)
diff --git a/Annex/Direct.hs b/Annex/Direct.hs
index b33fef8bc..55bff785c 100644
--- a/Annex/Direct.hs
+++ b/Annex/Direct.hs
@@ -24,6 +24,7 @@ import Backend
import Types.KeySource
import Annex.Content
import Annex.Content.Direct
+import Utility.InodeCache
import Utility.CopyFile
{- Uses git ls-files to find files that need to be committed, and stages
@@ -45,12 +46,12 @@ stageDirect = do
go (file, Just sha) = do
mkey <- catKey sha
mstat <- liftIO $ catchMaybeIO $ getSymbolicLinkStatus file
- case (mkey, mstat, toCache =<< mstat) of
+ case (mkey, mstat, toInodeCache =<< mstat) of
(Just key, _, Just cache) -> do
{- All direct mode files will show as
- modified, so compare the cache to see if
- it really was. -}
- oldcache <- recordedCache key
+ oldcache <- recordedInodeCache key
when (oldcache /= Just cache) $
modifiedannexed file key cache
(Just key, Nothing, _) -> deletedannexed file key
@@ -72,7 +73,7 @@ stageDirect = do
{- Adds a file to the annex in direct mode. Can fail, if the file is
- modified or deleted while it's being added. -}
-addDirect :: FilePath -> Cache -> Annex Bool
+addDirect :: FilePath -> InodeCache -> Annex Bool
addDirect file cache = do
showStart "add" file
let source = KeySource
@@ -84,13 +85,13 @@ addDirect file cache = do
got Nothing = do
showEndFail
return False
- got (Just (key, _)) = ifM (compareCache file $ Just cache)
+ got (Just (key, _)) = ifM (liftIO $ compareInodeCache file $ Just cache)
( do
link <- calcGitLink file key
sha <- inRepo $ Git.HashObject.hashObject BlobObject link
Annex.Queue.addUpdateIndex =<<
inRepo (Git.UpdateIndex.stageSymlink file sha)
- writeCache key cache
+ writeInodeCache key cache
void $ addAssociatedFile key file
logStatus key InfoPresent
showEndOk
@@ -177,7 +178,7 @@ toDirectGen k f = do
[] -> ifM (liftIO $ doesFileExist loc)
( return $ Just $ do
{- Move content from annex to direct file. -}
- updateCache k loc
+ updateInodeCache k loc
thawContent loc
liftIO $ replaceFile f $ moveFile loc
, return Nothing
diff --git a/Command/Add.hs b/Command/Add.hs
index f6b43034c..7fff5e778 100644
--- a/Command/Add.hs
+++ b/Command/Add.hs
@@ -95,7 +95,7 @@ ingest (Just source) = do
( do
mstat <- liftIO $ catchMaybeIO $ getSymbolicLinkStatus $ keyFilename source
k <- genKey source backend
- godirect k (toCache =<< mstat)
+ godirect k (toInodeCache =<< mstat)
, go =<< genKey source backend
)
where
@@ -107,9 +107,9 @@ ingest (Just source) = do
go Nothing = failure
godirect (Just (key, _)) (Just cache) =
- ifM (compareCache (keyFilename source) $ Just cache)
+ ifM (liftIO $ compareInodeCache (keyFilename source) $ Just cache)
( do
- writeCache key cache
+ writeInodeCache key cache
void $ addAssociatedFile key $ keyFilename source
unlessM crippledFileSystem $
liftIO $ allowWrite $ keyFilename source
diff --git a/Command/Indirect.hs b/Command/Indirect.hs
index 168d837ff..e09e3c9be 100644
--- a/Command/Indirect.hs
+++ b/Command/Indirect.hs
@@ -73,7 +73,7 @@ perform = do
showEndOk
cleandirect k = do
- liftIO . nukeFile =<< inRepo (gitAnnexCache k)
+ liftIO . nukeFile =<< inRepo (gitAnnexInodeCache k)
liftIO . nukeFile =<< inRepo (gitAnnexMapping k)
cleanup :: CommandCleanup
diff --git a/Locations.hs b/Locations.hs
index 9713a8ec2..49ccb350c 100644
--- a/Locations.hs
+++ b/Locations.hs
@@ -12,7 +12,7 @@ module Locations (
keyPath,
gitAnnexLocation,
gitAnnexMapping,
- gitAnnexCache,
+ gitAnnexInodeCache,
annexLocations,
annexLocation,
gitAnnexDir,
@@ -123,8 +123,8 @@ gitAnnexMapping key r = do
{- File that caches information about a key's content, used to determine
- if a file has changed.
- Used in direct mode. -}
-gitAnnexCache :: Key -> Git.Repo -> IO FilePath
-gitAnnexCache key r = do
+gitAnnexInodeCache :: Key -> Git.Repo -> IO FilePath
+gitAnnexInodeCache key r = do
loc <- gitAnnexLocation key r
return $ loc ++ ".cache"
diff --git a/Utility/InodeCache.hs b/Utility/InodeCache.hs
new file mode 100644
index 000000000..023a203f8
--- /dev/null
+++ b/Utility/InodeCache.hs
@@ -0,0 +1,50 @@
+{- Caching a file's inode, size, and modification time to see when it's changed.
+ -
+ - Copyright 2013 Joey Hess <joey@kitenet.net>
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+module Utility.InodeCache where
+
+import Common
+import System.Posix.Types
+
+data InodeCache = InodeCache FileID FileOffset EpochTime
+ deriving (Eq, Show)
+
+showInodeCache :: InodeCache -> String
+showInodeCache (InodeCache inode size mtime) = unwords
+ [ show inode
+ , show size
+ , show mtime
+ ]
+
+readInodeCache :: String -> Maybe InodeCache
+readInodeCache s = case words s of
+ (inode:size:mtime:_) -> InodeCache
+ <$> readish inode
+ <*> readish size
+ <*> readish mtime
+ _ -> Nothing
+
+-- for quickcheck
+prop_read_show_inodecache :: InodeCache -> Bool
+prop_read_show_inodecache c = readInodeCache (showInodeCache c) == Just c
+
+genInodeCache :: FilePath -> IO (Maybe InodeCache)
+genInodeCache f = catchDefaultIO Nothing $ toInodeCache <$> getFileStatus f
+
+toInodeCache :: FileStatus -> Maybe InodeCache
+toInodeCache s
+ | isRegularFile s = Just $ InodeCache
+ (fileID s)
+ (fileSize s)
+ (modificationTime s)
+ | 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
diff --git a/test.hs b/test.hs
index 3394eea43..6270c5978 100644
--- a/test.hs
+++ b/test.hs
@@ -54,7 +54,7 @@ import qualified Utility.Format
import qualified Utility.Verifiable
import qualified Utility.Process
import qualified Utility.Misc
-import qualified Annex.Content.Direct
+import qualified Utility.InodeCache
-- instances for quickcheck
instance Arbitrary Types.Key.Key where
@@ -119,7 +119,7 @@ quickcheck = TestLabel "quickcheck" $ TestList
, qctest "prop_verifiable_sane" Utility.Verifiable.prop_verifiable_sane
, qctest "prop_segment_regressionTest" Utility.Misc.prop_segment_regressionTest
, qctest "prop_read_write_transferinfo" Logs.Transfer.prop_read_write_transferinfo
- , qctest "prop_read_show_direct" Annex.Content.Direct.prop_read_show_direct
+ , qctest "prop_read_show_inodecache" Utility.InodeCache.prop_read_show_inodecache
, qctest "prop_parse_show_log" Logs.Presence.prop_parse_show_log
, qctest "prop_read_show_TrustLevel" Types.TrustLevel.prop_read_show_TrustLevel
, qctest "prop_parse_show_TrustLog" Logs.Trust.prop_parse_show_TrustLog