summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--Assistant/Threads/Merger.hs7
-rw-r--r--Assistant/Threads/Watcher.hs37
-rw-r--r--Command/TransferKeys.hs10
-rw-r--r--Database/Keys.hs11
-rw-r--r--Database/Keys/Handle.hs12
-rw-r--r--debian/changelog4
-rw-r--r--doc/bugs/Central_annex_+_assistant_+_v6___61___weirdness__63__.mdwn2
7 files changed, 70 insertions, 13 deletions
diff --git a/Assistant/Threads/Merger.hs b/Assistant/Threads/Merger.hs
index 521e5bda6..0080ef964 100644
--- a/Assistant/Threads/Merger.hs
+++ b/Assistant/Threads/Merger.hs
@@ -19,6 +19,7 @@ import qualified Annex.Branch
import qualified Git
import qualified Git.Branch
import qualified Command.Sync
+import qualified Database.Keys
import Annex.TaggedPush
import Remote (remoteFromUUID)
@@ -89,6 +90,12 @@ onChange file
currbranch mergeConfig
Git.Branch.AutomaticCommit
changedbranch
+ -- Merging can cause new associated files
+ -- to appear and the smudge filter will
+ -- add them to the database. To ensure that
+ -- this process sees those changes, close
+ -- the database if it was open.
+ liftAnnex $ Database.Keys.closeDb
mergecurrent _ = noop
handleDesynced = case fromTaggedBranch changedbranch of
diff --git a/Assistant/Threads/Watcher.hs b/Assistant/Threads/Watcher.hs
index f0a639984..1f50065b9 100644
--- a/Assistant/Threads/Watcher.hs
+++ b/Assistant/Threads/Watcher.hs
@@ -221,7 +221,11 @@ shouldRestage :: DaemonStatus -> Bool
shouldRestage ds = scanComplete ds || forceRestage ds
onAddUnlocked :: Bool -> GetFileMatcher -> Handler
-onAddUnlocked = onAddUnlocked' False contentchanged addassociatedfile samefilestatus
+onAddUnlocked symlinkssupported matcher f fs = do
+ mk <- liftIO $ isPointerFile f
+ case mk of
+ Nothing -> onAddUnlocked' False contentchanged addassociatedfile addlink samefilestatus symlinkssupported matcher f fs
+ Just k -> addlink f k
where
addassociatedfile key file =
Database.Keys.addAssociatedFile key
@@ -238,15 +242,32 @@ onAddUnlocked = onAddUnlocked' False contentchanged addassociatedfile samefilest
=<< inRepo (toTopFilePath file)
unlessM (inAnnex oldkey) $
logStatus oldkey InfoMissing
+ addlink file key = do
+ mode <- liftIO $ catchMaybeIO $ fileMode <$> getFileStatus file
+ liftAnnex $ stagePointerFile file mode =<< hashPointerFile key
+ madeChange file $ LinkChange (Just key)
{- In direct mode, add events are received for both new files, and
- modified existing files.
-}
onAddDirect :: Bool -> GetFileMatcher -> Handler
-onAddDirect = onAddUnlocked' True changedDirect (\k f -> void $ addAssociatedFile k f) sameFileStatus
-
-onAddUnlocked' :: Bool -> (Key -> FilePath -> Annex ()) -> (Key -> FilePath -> Annex ()) -> (Key -> FilePath -> FileStatus -> Annex Bool) -> Bool -> GetFileMatcher -> Handler
-onAddUnlocked' isdirect contentchanged addassociatedfile samefilestatus symlinkssupported matcher file fs = do
+onAddDirect = onAddUnlocked' True changedDirect addassociatedfile addlink sameFileStatus
+ where
+ addassociatedfile key file = void $ addAssociatedFile key file
+ addlink file key = do
+ link <- liftAnnex $ calcRepo $ gitAnnexLink file key
+ addLink file link (Just key)
+
+onAddUnlocked'
+ :: Bool
+ -> (Key -> FilePath -> Annex ())
+ -> (Key -> FilePath -> Annex ())
+ -> (FilePath -> Key -> Assistant (Maybe Change))
+ -> (Key -> FilePath -> FileStatus -> Annex Bool)
+ -> Bool
+ -> GetFileMatcher
+ -> Handler
+onAddUnlocked' isdirect contentchanged addassociatedfile addlink samefilestatus symlinkssupported matcher file fs = do
v <- liftAnnex $ catKeyFile file
case (v, fs) of
(Just key, Just filestatus) ->
@@ -255,11 +276,9 @@ onAddUnlocked' isdirect contentchanged addassociatedfile samefilestatus symlinks
- an existing file that is not
- really modified, but it might have
- just been deleted and been put back,
- - so it symlink is restaged to make sure. -}
+ - so its annex link is restaged to make sure. -}
( ifM (shouldRestage <$> getDaemonStatus)
- ( do
- link <- liftAnnex $ calcRepo $ gitAnnexLink file key
- addLink file link (Just key)
+ ( addlink file key
, noChange
)
, guardSymlinkStandin (Just key) $ do
diff --git a/Command/TransferKeys.hs b/Command/TransferKeys.hs
index 005e491b4..82dc15032 100644
--- a/Command/TransferKeys.hs
+++ b/Command/TransferKeys.hs
@@ -16,6 +16,7 @@ import Annex.Transfer
import qualified Remote
import Utility.SimpleProtocol (dupIoHandles)
import Git.Types (RemoteName)
+import qualified Database.Keys
data TransferRequest = TransferRequest Direction Remote Key AssociatedFile
@@ -41,8 +42,13 @@ start = do
return ok
| otherwise = notifyTransfer direction file $
download (Remote.uuid remote) key file forwardRetry observer $ \p ->
- getViaTmp (RemoteVerify remote) key $ \t ->
- Remote.retrieveKeyFile remote key file t p
+ getViaTmp (RemoteVerify remote) key $ \t -> do
+ r <- Remote.retrieveKeyFile remote key file t p
+ -- Make sure we get the current
+ -- associated files data for the key,
+ -- not old cached data.
+ Database.Keys.closeDb
+ return r
observer False t tinfo = recordFailedTransfer t tinfo
observer True _ _ = noop
diff --git a/Database/Keys.hs b/Database/Keys.hs
index ed3878161..778540137 100644
--- a/Database/Keys.hs
+++ b/Database/Keys.hs
@@ -9,6 +9,7 @@
module Database.Keys (
DbHandle,
+ closeDb,
addAssociatedFile,
getAssociatedFiles,
getAssociatedKey,
@@ -137,6 +138,16 @@ openDb createdb _ = catchPermissionDenied permerr $ withExclusiveLock gitAnnexKe
False -> return DbUnavailable
True -> throwM e
+{- Closes the database if it was open. Any writes will be flushed to it.
+ -
+ - This does not normally need to be called; the database will auto-close
+ - when the handle is garbage collected. However, this can be used to
+ - force a re-read of the database, in case another process has written
+ - data to it.
+ -}
+closeDb :: Annex ()
+closeDb = liftIO . closeDbHandle =<< getDbHandle
+
addAssociatedFile :: Key -> TopFilePath -> Annex ()
addAssociatedFile k f = runWriterIO $ SQL.addAssociatedFile (toIKey k) f
diff --git a/Database/Keys/Handle.hs b/Database/Keys/Handle.hs
index 51de58fa8..1ef16d031 100644
--- a/Database/Keys/Handle.hs
+++ b/Database/Keys/Handle.hs
@@ -11,6 +11,7 @@ module Database.Keys.Handle (
DbState(..),
withDbState,
flushDbQueue,
+ closeDbHandle,
) where
import qualified Database.Queue as H
@@ -38,8 +39,7 @@ newDbHandle = DbHandle <$> newMVar DbClosed
withDbState
:: (MonadIO m, MonadCatch m)
=> DbHandle
- -> (DbState
- -> m (v, DbState))
+ -> (DbState -> m (v, DbState))
-> m v
withDbState (DbHandle mvar) a = do
st <- liftIO $ takeMVar mvar
@@ -55,3 +55,11 @@ flushDbQueue (DbHandle mvar) = go =<< readMVar mvar
where
go (DbOpen qh) = H.flushDbQueue qh
go _ = return ()
+
+closeDbHandle :: DbHandle -> IO ()
+closeDbHandle h = withDbState h go
+ where
+ go (DbOpen qh) = do
+ H.closeDbQueue qh
+ return ((), DbClosed)
+ go st = return ((), st)
diff --git a/debian/changelog b/debian/changelog
index a653efdfd..e9de8bce8 100644
--- a/debian/changelog
+++ b/debian/changelog
@@ -6,6 +6,10 @@ git-annex (6.20160512) UNRELEASED; urgency=medium
* adjust: If the adjusted branch already exists, avoid overwriting it,
since it might contain changes that have not yet been propigated to the
original branch.
+ * assistant: Fix bug that caused v6 pointer files to be annexed by the
+ assistant.
+ * assistant: Fix race in v6 mode that caused downloaded file content to
+ sometimes not replace pointer files.
-- Joey Hess <id@joeyh.name> Wed, 11 May 2016 16:08:38 -0400
diff --git a/doc/bugs/Central_annex_+_assistant_+_v6___61___weirdness__63__.mdwn b/doc/bugs/Central_annex_+_assistant_+_v6___61___weirdness__63__.mdwn
index 5afd3d31a..4acf81e7b 100644
--- a/doc/bugs/Central_annex_+_assistant_+_v6___61___weirdness__63__.mdwn
+++ b/doc/bugs/Central_annex_+_assistant_+_v6___61___weirdness__63__.mdwn
@@ -102,3 +102,5 @@ Everything up-to-date
### Have you had any luck using git-annex before? (Sometimes we get tired of reading bug reports all day and a lil' positive end note does wonders)
It seems to work really well on v5, but the v6 file "corruption" is difficult to recover from.
+
+> [[fixed|done]] --[[Joey]]