aboutsummaryrefslogtreecommitdiff
path: root/Annex/InodeSentinal.hs
diff options
context:
space:
mode:
authorGravatar Joey Hess <joeyh@joeyh.name>2015-12-09 15:42:16 -0400
committerGravatar Joey Hess <joeyh@joeyh.name>2015-12-09 15:52:11 -0400
commitb5c8ba7db3ea2eb4f1cd28e49cadb5fd348ca738 (patch)
tree81d2f8bca341e56bb20d01d68e0a60812e285aa2 /Annex/InodeSentinal.hs
parent7f00b7eaf0877e791194e7dfed5abefbb091ee86 (diff)
move InodeSentinal from direct mode code to its own module
Will be used outside of direct mode for v6 unlocked files, and is already used outside of direct mode when adding files to annex.
Diffstat (limited to 'Annex/InodeSentinal.hs')
-rw-r--r--Annex/InodeSentinal.hs67
1 files changed, 67 insertions, 0 deletions
diff --git a/Annex/InodeSentinal.hs b/Annex/InodeSentinal.hs
new file mode 100644
index 000000000..7047a405c
--- /dev/null
+++ b/Annex/InodeSentinal.hs
@@ -0,0 +1,67 @@
+{- git-annex inode sentinal file
+ -
+ - Copyright 2012-2015 Joey Hess <id@joeyh.name>
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+{-# LANGUAGE CPP #-}
+
+module Annex.InodeSentinal where
+
+import Common.Annex
+import qualified Annex
+import Utility.InodeCache
+import Annex.Perms
+
+{- 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.
+ -
+ - If the sentinal file does not exist, we have to assume that the
+ - inodes have changed.
+ -}
+inodesChanged :: Annex Bool
+inodesChanged = sentinalInodesChanged <$> sentinalStatus
+
+withTSDelta :: (TSDelta -> Annex a) -> Annex a
+withTSDelta a = a =<< getTSDelta
+
+getTSDelta :: Annex TSDelta
+#ifdef mingw32_HOST_OS
+getTSDelta = sentinalTSDelta <$> sentinalStatus
+#else
+getTSDelta = pure noTSDelta -- optimisation
+#endif
+
+sentinalStatus :: Annex SentinalStatus
+sentinalStatus = maybe check return =<< Annex.getState Annex.sentinalstatus
+ where
+ check = do
+ sc <- liftIO . checkSentinalFile =<< annexSentinalFile
+ Annex.changeState $ \s -> s { Annex.sentinalstatus = Just sc }
+ return sc
+
+{- The sentinal file is only created when first initializing a repository.
+ - If there are any annexed objects in the repository already, creating
+ - the file would invalidate their inode caches. -}
+createInodeSentinalFile :: Bool -> Annex ()
+createInodeSentinalFile evenwithobjects =
+ unlessM (alreadyexists <||> hasobjects) $ do
+ s <- annexSentinalFile
+ createAnnexDirectory (parentDir (sentinalFile s))
+ liftIO $ writeSentinalFile s
+ where
+ alreadyexists = liftIO. sentinalFileExists =<< annexSentinalFile
+ hasobjects
+ | evenwithobjects = pure False
+ | otherwise = liftIO . doesDirectoryExist =<< fromRepo gitAnnexObjectDir
+
+annexSentinalFile :: Annex SentinalFile
+annexSentinalFile = do
+ sentinalfile <- fromRepo gitAnnexInodeSentinal
+ sentinalcachefile <- fromRepo gitAnnexInodeSentinalCache
+ return SentinalFile
+ { sentinalFile = sentinalfile
+ , sentinalCacheFile = sentinalcachefile
+ }