aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--Annex/Content.hs6
-rw-r--r--Annex/Content/Direct.hs60
-rw-r--r--Annex/Direct.hs4
-rw-r--r--Annex/Init.hs4
-rw-r--r--Annex/InodeSentinal.hs67
-rw-r--r--Assistant/Threads/Committer.hs1
-rw-r--r--Command/Add.hs1
-rw-r--r--Upgrade/V5.hs7
-rw-r--r--doc/todo/smudge.mdwn4
9 files changed, 93 insertions, 61 deletions
diff --git a/Annex/Content.hs b/Annex/Content.hs
index d3bf4f94f..564bc2dca 100644
--- a/Annex/Content.hs
+++ b/Annex/Content.hs
@@ -1,6 +1,6 @@
{- git-annex file content managing
-
- - Copyright 2010-2014 Joey Hess <id@joeyh.name>
+ - Copyright 2010-2015 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU GPL version 3 or higher.
-}
@@ -72,6 +72,7 @@ import qualified Types.Backend
import qualified Backend
import Types.NumCopies
import Annex.UUID
+import Annex.InodeSentinal
import qualified Database.AssociatedFiles as AssociatedFiles
{- Checks if a given key's content is currently present. -}
@@ -584,6 +585,9 @@ cleanObjectLoc key cleaner = do
{- Removes a key's file from .git/annex/objects/
-
+ - When a key has associated pointer files, they are checked for
+ - modifications, and if unmodified, are reset.
+ -
- In direct mode, deletes the associated files or files, and replaces
- them with symlinks.
-}
diff --git a/Annex/Content/Direct.hs b/Annex/Content/Direct.hs
index 86e053d7f..1edcbaed5 100644
--- a/Annex/Content/Direct.hs
+++ b/Annex/Content/Direct.hs
@@ -1,12 +1,13 @@
{- git-annex file content managing for direct mode
-
+ - This is deprecated, and will be removed when direct mode gets removed
+ - from git-annex.
+ -
- Copyright 2012-2014 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU GPL version 3 or higher.
-}
-{-# LANGUAGE CPP #-}
-
module Annex.Content.Direct (
associatedFiles,
associatedFilesRelative,
@@ -26,15 +27,10 @@ module Annex.Content.Direct (
sameFileStatus,
removeInodeCache,
toInodeCache,
- inodesChanged,
- createInodeSentinalFile,
addContentWhenNotPresent,
- withTSDelta,
- getTSDelta,
) where
import Common.Annex
-import qualified Annex
import Annex.Perms
import qualified Git
import Utility.Tmp
@@ -43,6 +39,7 @@ import Utility.InodeCache
import Utility.CopyFile
import Annex.ReplaceFile
import Annex.Link
+import Annex.InodeSentinal
{- Absolute FilePaths of Files in the tree that are associated with a key. -}
associatedFiles :: Key -> Annex [FilePath]
@@ -212,52 +209,3 @@ addContentWhenNotPresent key contentfile associatedfile = do
replaceFile associatedfile $
liftIO . void . copyFileExternal CopyAllMetaData contentfile
updateInodeCache key associatedfile
-
-{- 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 :: Annex ()
-createInodeSentinalFile = unlessM (alreadyexists <||> hasobjects) $ do
- s <- annexSentinalFile
- createAnnexDirectory (parentDir (sentinalFile s))
- liftIO $ writeSentinalFile s
- where
- alreadyexists = liftIO. sentinalFileExists =<< annexSentinalFile
- hasobjects = liftIO . doesDirectoryExist =<< fromRepo gitAnnexObjectDir
-
-annexSentinalFile :: Annex SentinalFile
-annexSentinalFile = do
- sentinalfile <- fromRepo gitAnnexInodeSentinal
- sentinalcachefile <- fromRepo gitAnnexInodeSentinalCache
- return SentinalFile
- { sentinalFile = sentinalfile
- , sentinalCacheFile = sentinalcachefile
- }
diff --git a/Annex/Direct.hs b/Annex/Direct.hs
index 803f020ca..8fced2d44 100644
--- a/Annex/Direct.hs
+++ b/Annex/Direct.hs
@@ -1,5 +1,8 @@
{- git-annex direct mode
-
+ - This is deprecated, and will be removed when direct mode gets removed
+ - from git-annex.
+ -
- Copyright 2012-2014 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU GPL version 3 or higher.
@@ -36,6 +39,7 @@ import Annex.VariantFile
import Git.Index
import Annex.Index
import Annex.LockFile
+import Annex.InodeSentinal
{- Uses git ls-files to find files that need to be committed, and stages
- them into the index. Returns True if some changes were staged. -}
diff --git a/Annex/Init.hs b/Annex/Init.hs
index 7eea0dfa1..997312c31 100644
--- a/Annex/Init.hs
+++ b/Annex/Init.hs
@@ -32,9 +32,9 @@ import Annex.UUID
import Annex.Link
import Config
import Annex.Direct
-import Annex.Content.Direct
import Annex.Environment
import Annex.Hook
+import Annex.InodeSentinal
import Upgrade
#ifndef mingw32_HOST_OS
import Utility.UserInfo
@@ -96,7 +96,7 @@ initialize' = do
, unlessM isBare
switchHEADBack
)
- createInodeSentinalFile
+ createInodeSentinalFile False
uninitialize :: Annex ()
uninitialize = do
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
+ }
diff --git a/Assistant/Threads/Committer.hs b/Assistant/Threads/Committer.hs
index 59ca69e88..745047d9d 100644
--- a/Assistant/Threads/Committer.hs
+++ b/Assistant/Threads/Committer.hs
@@ -30,6 +30,7 @@ import Config
import Annex.Content
import Annex.Link
import Annex.CatFile
+import Annex.InodeSentinal
import qualified Annex
import Utility.InodeCache
import Annex.Content.Direct
diff --git a/Command/Add.hs b/Command/Add.hs
index 27c11eab4..f4bdc70c9 100644
--- a/Command/Add.hs
+++ b/Command/Add.hs
@@ -32,6 +32,7 @@ import Annex.FileMatcher
import Annex.ReplaceFile
import Utility.Tmp
import Utility.CopyFile
+import Annex.InodeSentinal
import Control.Exception (IOException)
diff --git a/Upgrade/V5.hs b/Upgrade/V5.hs
index cf273bb16..e4501302d 100644
--- a/Upgrade/V5.hs
+++ b/Upgrade/V5.hs
@@ -9,10 +9,17 @@ module Upgrade.V5 where
import Common.Annex
import Config
+import Annex.InodeSentinal
upgrade :: Bool -> Annex Bool
upgrade automatic = do
unless automatic $
showAction "v5 to v6"
configureSmudgeFilter
+ -- Inode sentinal file was only used in direct mode and when
+ -- locking down files as they were added. In v6, it's used more
+ -- extensively, so make sure it exists, since old repos that didn't
+ -- use direct mode may not have created it.
+ unlessM (isDirect) $
+ createInodeSentinalFile True
return True
diff --git a/doc/todo/smudge.mdwn b/doc/todo/smudge.mdwn
index 373c65561..60cc65f3f 100644
--- a/doc/todo/smudge.mdwn
+++ b/doc/todo/smudge.mdwn
@@ -325,12 +325,12 @@ files to be unlocked, while the indirect upgrades don't touch the files.
#### implementation todo list
-* inAnnex check should fail in the case where an annexed objects is unlocked
+* inAnnex check should fail in the case where an annexed object is unlocked
and has had its content changed. Could use an InodeCache for
such objects. This parallels how inAnnex checks work for direct mode.
* Reconcile staged changes into the associated files database, whenever
the database is queried.
-* See if the case where the associated files database is not used can be
+* See if the cases where the associated files database is not used can be
optimised. Eg, if the associated files database doesn't exist at all,
we know smudge/clean are not used, so queries for associated files don't
need to open the database or do reconciliation, but can simply return none.