diff options
-rw-r--r-- | Annex/Init.hs | 6 | ||||
-rw-r--r-- | Database/Keys.hs | 34 | ||||
-rw-r--r-- | Test.hs | 4 | ||||
-rw-r--r-- | Upgrade/V5.hs | 1 | ||||
-rw-r--r-- | doc/todo/smudge.mdwn | 8 |
5 files changed, 38 insertions, 15 deletions
diff --git a/Annex/Init.hs b/Annex/Init.hs index 99bb03e92..9cb876284 100644 --- a/Annex/Init.hs +++ b/Annex/Init.hs @@ -1,6 +1,6 @@ {- git-annex repository initialization - - - Copyright 2011 Joey Hess <id@joeyh.name> + - Copyright 2011-2016 Joey Hess <id@joeyh.name> - - Licensed under the GNU GPL version 3 or higher. -} @@ -36,6 +36,7 @@ import Annex.Environment import Annex.Hook import Annex.InodeSentinal import Upgrade +import qualified Database.Keys #ifndef mingw32_HOST_OS import Utility.UserInfo import Utility.FileMode @@ -87,8 +88,9 @@ initialize' mversion = do setDifferences unlessM (isJust <$> getVersion) $ setVersion (fromMaybe defaultVersion mversion) - whenM versionSupportsUnlockedPointers + whenM versionSupportsUnlockedPointers $ do configureSmudgeFilter + Database.Keys.scanAssociatedFiles ifM (crippledFileSystem <&&> not <$> isBare) ( do enableDirectMode diff --git a/Database/Keys.hs b/Database/Keys.hs index f5a28c704..30e6ff921 100644 --- a/Database/Keys.hs +++ b/Database/Keys.hs @@ -1,14 +1,14 @@ {- Sqlite database of information about Keys - - - Copyright 2015 Joey Hess <id@joeyh.name> - -: + - Copyright 2015-2016 Joey Hess <id@joeyh.name> + - - Licensed under the GNU GPL version 3 or higher. -} {-# LANGUAGE QuasiQuotes, TypeFamilies, TemplateHaskell #-} {-# LANGUAGE OverloadedStrings, GADTs, FlexibleContexts #-} {-# LANGUAGE MultiParamTypeClasses, GeneralizedNewtypeDeriving #-} -{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE RankNTypes, ScopedTypeVariables #-} module Database.Keys ( DbHandle, @@ -16,6 +16,7 @@ module Database.Keys ( getAssociatedFiles, getAssociatedKey, removeAssociatedFile, + scanAssociatedFiles, storeInodeCaches, addInodeCaches, getInodeCaches, @@ -35,6 +36,12 @@ import Annex.Perms import Annex.LockFile import Utility.InodeCache import Annex.InodeSentinal +import qualified Git.Types +import qualified Git.LsTree +import Git.Ref +import Git.FilePath +import Annex.CatFile +import Messages import Database.Persist.TH import Database.Esqueleto hiding (Key) @@ -203,6 +210,27 @@ removeAssociatedFile' :: SKey -> FilePath -> Writer removeAssociatedFile' sk f = queueDb $ delete $ from $ \r -> do where_ (r ^. AssociatedKey ==. val sk &&. r ^. AssociatedFile ==. val f) + +{- Find all unlocked associated files. This is expensive, and so normally + - the associated files are updated incrementally when changes are noticed. -} +scanAssociatedFiles :: Annex () +scanAssociatedFiles = runWriter $ \h -> do + showSideAction "scanning for unlocked files" + dropallassociated h + l <- inRepo $ Git.LsTree.lsTree headRef + forM_ l $ \i -> + when (isregfile i) $ + maybe noop (add h i) + =<< catKey (Git.Types.Ref $ Git.LsTree.sha i) + where + dropallassociated = queueDb $ + delete $ from $ \(_r :: SqlExpr (Entity Associated)) -> + return () + isregfile i = Git.Types.toBlobType (Git.LsTree.mode i) == Just Git.Types.FileBlob + add h i k = flip queueDb h $ + void $ insertUnique $ Associated + (toSKey k) + (getTopFilePath $ Git.LsTree.file i) {- Stats the files, and stores their InodeCaches. -} storeInodeCaches :: Key -> [FilePath] -> Annex () @@ -124,8 +124,8 @@ tests = testGroup "Tests" $ properties : map (\(d, te) -> withTestMode te (unitTests d)) testmodes where testmodes = - -- ("v6 unlocked", (testMode "6") { unlockedFiles = True }) - [ ("v6 locked", testMode "6") + [ ("v6 unlocked", (testMode "6") { unlockedFiles = True }) + , ("v6 locked", testMode "6") , ("v5", testMode "5") #ifndef mingw32_HOST_OS -- Windows will only use direct mode, so don't test twice. diff --git a/Upgrade/V5.hs b/Upgrade/V5.hs index 69518f63b..83a68ed4e 100644 --- a/Upgrade/V5.hs +++ b/Upgrade/V5.hs @@ -49,6 +49,7 @@ upgrade automatic = do showLongNote "Changes have been staged for all annexed files in this repository; you should run `git commit` to commit these changes." showLongNote "Any other clones of this repository that use direct mode need to be upgraded now, too." configureSmudgeFilter + Database.Keys.scanAssociatedFiles -- 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 diff --git a/doc/todo/smudge.mdwn b/doc/todo/smudge.mdwn index f7835c563..4a9878335 100644 --- a/doc/todo/smudge.mdwn +++ b/doc/todo/smudge.mdwn @@ -4,14 +4,6 @@ git-annex should use smudge/clean filters. * Test suite has a currently disabled pass that tests v6 unlocked files. That pass has many failures. -* Associated files database is not populated when a repository is cloned, - because the smudge filters are not set up when git checks out the work - tree. So, git annex get etc won't work immediately after cloning. - Need to make init run through the whole work index and populate the - associated files database. - (Or could update it incrementally, so git-annex get foo updates the - database for foo's key. But, then if bar has the same content as foo, bar - wouldn't be populated by get foo.) * Reconcile staged changes into the associated files database, whenever the database is queried. This is needed to handle eg: git add largefile |