2015-12-09 19:42:16 +00:00
|
|
|
{- git-annex inode sentinal file
|
|
|
|
-
|
|
|
|
- Copyright 2012-2015 Joey Hess <id@joeyh.name>
|
|
|
|
-
|
2019-03-13 19:48:14 +00:00
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
2015-12-09 19:42:16 +00:00
|
|
|
-}
|
|
|
|
|
|
|
|
{-# LANGUAGE CPP #-}
|
|
|
|
|
|
|
|
module Annex.InodeSentinal where
|
|
|
|
|
2016-01-20 20:36:33 +00:00
|
|
|
import Annex.Common
|
2015-12-09 19:42:16 +00:00
|
|
|
import qualified Annex
|
|
|
|
import Utility.InodeCache
|
|
|
|
import Annex.Perms
|
|
|
|
|
2015-12-10 18:20:38 +00:00
|
|
|
{- If the sendinal shows the inodes have changed, only the size and mtime
|
|
|
|
- are compared. -}
|
2015-12-09 21:00:37 +00:00
|
|
|
compareInodeCaches :: InodeCache -> InodeCache -> Annex Bool
|
|
|
|
compareInodeCaches x y
|
|
|
|
| compareStrong x y = return True
|
|
|
|
| otherwise = ifM inodesChanged
|
|
|
|
( return $ compareWeak x y
|
|
|
|
, return False
|
|
|
|
)
|
|
|
|
|
2015-12-21 22:41:15 +00:00
|
|
|
compareInodeCachesWith :: Annex InodeComparisonType
|
|
|
|
compareInodeCachesWith = ifM inodesChanged ( return Weakly, return Strongly )
|
|
|
|
|
2015-12-10 18:20:38 +00:00
|
|
|
{- Checks if one of the provided old InodeCache matches the current
|
|
|
|
- version of a file. -}
|
2019-12-11 18:12:22 +00:00
|
|
|
sameInodeCache :: RawFilePath -> [InodeCache] -> Annex Bool
|
2015-12-10 18:20:38 +00:00
|
|
|
sameInodeCache _ [] = return False
|
|
|
|
sameInodeCache file old = go =<< withTSDelta (liftIO . genInodeCache file)
|
|
|
|
where
|
|
|
|
go Nothing = return False
|
|
|
|
go (Just curr) = elemInodeCaches curr old
|
|
|
|
|
|
|
|
elemInodeCaches :: InodeCache -> [InodeCache] -> Annex Bool
|
|
|
|
elemInodeCaches _ [] = return False
|
|
|
|
elemInodeCaches c (l:ls) = ifM (compareInodeCaches c l)
|
|
|
|
( return True
|
|
|
|
, elemInodeCaches c ls
|
|
|
|
)
|
|
|
|
|
2015-12-09 19:42:16 +00:00
|
|
|
{- 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
|
2020-10-28 21:25:59 +00:00
|
|
|
createAnnexDirectory (parentDir (sentinalFile s))
|
2015-12-09 19:42:16 +00:00
|
|
|
liftIO $ writeSentinalFile s
|
|
|
|
where
|
|
|
|
alreadyexists = liftIO. sentinalFileExists =<< annexSentinalFile
|
|
|
|
hasobjects
|
|
|
|
| evenwithobjects = pure False
|
2020-11-06 18:10:58 +00:00
|
|
|
| otherwise = liftIO . doesDirectoryExist . fromRawFilePath
|
|
|
|
=<< fromRepo gitAnnexObjectDir
|
2015-12-09 19:42:16 +00:00
|
|
|
|
|
|
|
annexSentinalFile :: Annex SentinalFile
|
|
|
|
annexSentinalFile = do
|
|
|
|
sentinalfile <- fromRepo gitAnnexInodeSentinal
|
|
|
|
sentinalcachefile <- fromRepo gitAnnexInodeSentinalCache
|
|
|
|
return SentinalFile
|
|
|
|
{ sentinalFile = sentinalfile
|
|
|
|
, sentinalCacheFile = sentinalcachefile
|
|
|
|
}
|