make getViaTmpFrom no longer update location log
All callers adjusted to update it themselves. In Command.ReKey, and Command.SetKey, the cleanup action already did, so it was updating the log twice before. This fixes a bug when annex.stalldetection is set, as now Command.Transferrer can skip updating the location log, and let it be updated by the calling process.
This commit is contained in:
parent
a6ed23b82f
commit
a422a056f2
12 changed files with 33 additions and 20 deletions
|
@ -227,12 +227,7 @@ getViaTmpFromDisk rsp v key af action = checkallowed $ do
|
||||||
else verification
|
else verification
|
||||||
if ok
|
if ok
|
||||||
then ifM (verifyKeyContent rsp v verification' key tmpfile)
|
then ifM (verifyKeyContent rsp v verification' key tmpfile)
|
||||||
( ifM (pruneTmpWorkDirBefore tmpfile (moveAnnex key af))
|
( pruneTmpWorkDirBefore tmpfile (moveAnnex key af)
|
||||||
( do
|
|
||||||
logStatus key InfoPresent
|
|
||||||
return True
|
|
||||||
, return False
|
|
||||||
)
|
|
||||||
, do
|
, do
|
||||||
warning "verification of content failed"
|
warning "verification of content failed"
|
||||||
-- The bad content is not retained, because
|
-- The bad content is not retained, because
|
||||||
|
|
|
@ -30,6 +30,7 @@ import Annex.Notification as X
|
||||||
import Annex.Content
|
import Annex.Content
|
||||||
import Annex.Perms
|
import Annex.Perms
|
||||||
import Annex.Action
|
import Annex.Action
|
||||||
|
import Logs.Location
|
||||||
import Utility.Metered
|
import Utility.Metered
|
||||||
import Utility.ThreadScheduler
|
import Utility.ThreadScheduler
|
||||||
import Annex.LockPool
|
import Annex.LockPool
|
||||||
|
@ -68,7 +69,7 @@ alwaysUpload u key f d a _witness = guardHaveUUID u $
|
||||||
|
|
||||||
-- Download, supporting stall detection.
|
-- Download, supporting stall detection.
|
||||||
download :: Remote -> Key -> AssociatedFile -> RetryDecider -> NotifyWitness -> Annex Bool
|
download :: Remote -> Key -> AssociatedFile -> RetryDecider -> NotifyWitness -> Annex Bool
|
||||||
download r key f d witness = stallDetection r >>= \case
|
download r key f d witness = logStatusAfter key $ stallDetection r >>= \case
|
||||||
Nothing -> getViaTmp (Remote.retrievalSecurityPolicy r) (RemoteVerify r) key f $ \dest ->
|
Nothing -> getViaTmp (Remote.retrievalSecurityPolicy r) (RemoteVerify r) key f $ \dest ->
|
||||||
download' (Remote.uuid r) key f d (go dest) witness
|
download' (Remote.uuid r) key f d (go dest) witness
|
||||||
Just sd -> runTransferrer sd r key f d Download witness
|
Just sd -> runTransferrer sd r key f d Download witness
|
||||||
|
|
|
@ -16,6 +16,7 @@ import Annex.WorkTree
|
||||||
import Annex.Content
|
import Annex.Content
|
||||||
import Annex.UUID
|
import Annex.UUID
|
||||||
import Annex.Perms
|
import Annex.Perms
|
||||||
|
import Logs.Location
|
||||||
import Utility.FileMode
|
import Utility.FileMode
|
||||||
#ifndef mingw32_HOST_OS
|
#ifndef mingw32_HOST_OS
|
||||||
import Creds
|
import Creds
|
||||||
|
@ -212,7 +213,7 @@ storeReceived f = do
|
||||||
Nothing -> do
|
Nothing -> do
|
||||||
warning $ "Received a file " ++ f ++ " that is not a git-annex key. Deleting this file."
|
warning $ "Received a file " ++ f ++ " that is not a git-annex key. Deleting this file."
|
||||||
liftIO $ removeWhenExistsWith R.removeLink (toRawFilePath f)
|
liftIO $ removeWhenExistsWith R.removeLink (toRawFilePath f)
|
||||||
Just k -> void $
|
Just k -> void $ logStatusAfter k $
|
||||||
getViaTmpFromDisk RetrievalVerifiableKeysSecure AlwaysVerify k (AssociatedFile Nothing) $ \dest -> unVerified $
|
getViaTmpFromDisk RetrievalVerifiableKeysSecure AlwaysVerify k (AssociatedFile Nothing) $ \dest -> unVerified $
|
||||||
liftIO $ catchBoolIO $ do
|
liftIO $ catchBoolIO $ do
|
||||||
rename f (fromRawFilePath dest)
|
rename f (fromRawFilePath dest)
|
||||||
|
|
|
@ -13,6 +13,7 @@ import Annex.Action
|
||||||
import Annex
|
import Annex
|
||||||
import Utility.Rsync
|
import Utility.Rsync
|
||||||
import Types.Transfer
|
import Types.Transfer
|
||||||
|
import Logs.Location
|
||||||
import Command.SendKey (fieldTransfer)
|
import Command.SendKey (fieldTransfer)
|
||||||
import qualified CmdLine.GitAnnexShell.Fields as Fields
|
import qualified CmdLine.GitAnnexShell.Fields as Fields
|
||||||
|
|
||||||
|
@ -35,6 +36,7 @@ start (_, key) = fieldTransfer Download key $ \_p -> do
|
||||||
let rsp = RetrievalAllKeysSecure
|
let rsp = RetrievalAllKeysSecure
|
||||||
ifM (getViaTmp rsp verify key (AssociatedFile Nothing) go)
|
ifM (getViaTmp rsp verify key (AssociatedFile Nothing) go)
|
||||||
( do
|
( do
|
||||||
|
logStatus key InfoPresent
|
||||||
-- forcibly quit after receiving one key,
|
-- forcibly quit after receiving one key,
|
||||||
-- and shutdown cleanly
|
-- and shutdown cleanly
|
||||||
_ <- shutdown True
|
_ <- shutdown True
|
||||||
|
|
|
@ -294,7 +294,7 @@ test runannex mkr mkk =
|
||||||
Just b -> case Types.Backend.verifyKeyContent b of
|
Just b -> case Types.Backend.verifyKeyContent b of
|
||||||
Nothing -> return True
|
Nothing -> return True
|
||||||
Just verifier -> verifier k (serializeKey' k)
|
Just verifier -> verifier k (serializeKey' k)
|
||||||
get r k = getViaTmp (Remote.retrievalSecurityPolicy r) (RemoteVerify r) k (AssociatedFile Nothing) $ \dest ->
|
get r k = logStatusAfter k $ getViaTmp (Remote.retrievalSecurityPolicy r) (RemoteVerify r) k (AssociatedFile Nothing) $ \dest ->
|
||||||
tryNonAsync (Remote.retrieveKeyFile r k (AssociatedFile Nothing) (fromRawFilePath dest) nullMeterUpdate) >>= \case
|
tryNonAsync (Remote.retrieveKeyFile r k (AssociatedFile Nothing) (fromRawFilePath dest) nullMeterUpdate) >>= \case
|
||||||
Right v -> return (True, v)
|
Right v -> return (True, v)
|
||||||
Left _ -> return (False, UnVerified)
|
Left _ -> return (False, UnVerified)
|
||||||
|
@ -368,13 +368,13 @@ testUnavailable runannex mkr mkk =
|
||||||
, check (`notElem` [Right True, Right False]) "checkPresent" $ \r k ->
|
, check (`notElem` [Right True, Right False]) "checkPresent" $ \r k ->
|
||||||
Remote.checkPresent r k
|
Remote.checkPresent r k
|
||||||
, check (== Right False) "retrieveKeyFile" $ \r k ->
|
, check (== Right False) "retrieveKeyFile" $ \r k ->
|
||||||
getViaTmp (Remote.retrievalSecurityPolicy r) (RemoteVerify r) k (AssociatedFile Nothing) $ \dest ->
|
logStatusAfter k $ getViaTmp (Remote.retrievalSecurityPolicy r) (RemoteVerify r) k (AssociatedFile Nothing) $ \dest ->
|
||||||
tryNonAsync (Remote.retrieveKeyFile r k (AssociatedFile Nothing) (fromRawFilePath dest) nullMeterUpdate) >>= \case
|
tryNonAsync (Remote.retrieveKeyFile r k (AssociatedFile Nothing) (fromRawFilePath dest) nullMeterUpdate) >>= \case
|
||||||
Right v -> return (True, v)
|
Right v -> return (True, v)
|
||||||
Left _ -> return (False, UnVerified)
|
Left _ -> return (False, UnVerified)
|
||||||
, check (== Right False) "retrieveKeyFileCheap" $ \r k -> case Remote.retrieveKeyFileCheap r of
|
, check (== Right False) "retrieveKeyFileCheap" $ \r k -> case Remote.retrieveKeyFileCheap r of
|
||||||
Nothing -> return False
|
Nothing -> return False
|
||||||
Just a -> getViaTmp (Remote.retrievalSecurityPolicy r) (RemoteVerify r) k (AssociatedFile Nothing) $ \dest ->
|
Just a -> logStatusAfter k $ getViaTmp (Remote.retrievalSecurityPolicy r) (RemoteVerify r) k (AssociatedFile Nothing) $ \dest ->
|
||||||
unVerified $ isRight
|
unVerified $ isRight
|
||||||
<$> tryNonAsync (a k (AssociatedFile Nothing) (fromRawFilePath dest))
|
<$> tryNonAsync (a k (AssociatedFile Nothing) (fromRawFilePath dest))
|
||||||
]
|
]
|
||||||
|
|
|
@ -63,7 +63,7 @@ toPerform key file remote = go Upload file $
|
||||||
fromPerform :: Key -> AssociatedFile -> Remote -> CommandPerform
|
fromPerform :: Key -> AssociatedFile -> Remote -> CommandPerform
|
||||||
fromPerform key file remote = go Upload file $
|
fromPerform key file remote = go Upload file $
|
||||||
download' (uuid remote) key file stdRetry $ \p ->
|
download' (uuid remote) key file stdRetry $ \p ->
|
||||||
getViaTmp (retrievalSecurityPolicy remote) (RemoteVerify remote) key file $ \t ->
|
logStatusAfter key $ getViaTmp (retrievalSecurityPolicy remote) (RemoteVerify remote) key file $ \t ->
|
||||||
tryNonAsync (Remote.retrieveKeyFile remote key file (fromRawFilePath t) p) >>= \case
|
tryNonAsync (Remote.retrieveKeyFile remote key file (fromRawFilePath t) p) >>= \case
|
||||||
Right v -> return (True, v)
|
Right v -> return (True, v)
|
||||||
Left e -> do
|
Left e -> do
|
||||||
|
|
|
@ -50,7 +50,7 @@ start = do
|
||||||
return True
|
return True
|
||||||
| otherwise = notifyTransfer direction file $
|
| otherwise = notifyTransfer direction file $
|
||||||
download' (Remote.uuid remote) key file stdRetry $ \p ->
|
download' (Remote.uuid remote) key file stdRetry $ \p ->
|
||||||
getViaTmp (Remote.retrievalSecurityPolicy remote) (RemoteVerify remote) key file $ \t -> do
|
logStatusAfter key $ getViaTmp (Remote.retrievalSecurityPolicy remote) (RemoteVerify remote) key file $ \t -> do
|
||||||
r <- tryNonAsync (Remote.retrieveKeyFile remote key file (fromRawFilePath t) p) >>= \case
|
r <- tryNonAsync (Remote.retrieveKeyFile remote key file (fromRawFilePath t) p) >>= \case
|
||||||
Left e -> do
|
Left e -> do
|
||||||
warning (show e)
|
warning (show e)
|
||||||
|
|
|
@ -45,14 +45,14 @@ start = do
|
||||||
runner (UploadRequest _ key (TransferAssociatedFile file)) remote =
|
runner (UploadRequest _ key (TransferAssociatedFile file)) remote =
|
||||||
-- This is called by eg, Annex.Transfer.upload,
|
-- This is called by eg, Annex.Transfer.upload,
|
||||||
-- so caller is responsible for doing notification,
|
-- so caller is responsible for doing notification,
|
||||||
-- and for retrying.
|
-- and for retrying, and updating location log.
|
||||||
upload' (Remote.uuid remote) key file noRetry
|
upload' (Remote.uuid remote) key file noRetry
|
||||||
(Remote.action . Remote.storeKey remote key file)
|
(Remote.action . Remote.storeKey remote key file)
|
||||||
noNotification
|
noNotification
|
||||||
runner (DownloadRequest _ key (TransferAssociatedFile file)) remote =
|
runner (DownloadRequest _ key (TransferAssociatedFile file)) remote =
|
||||||
-- This is called by eg, Annex.Transfer.download
|
-- This is called by eg, Annex.Transfer.download
|
||||||
-- so caller is responsible for doing notification
|
-- so caller is responsible for doing notification
|
||||||
-- and for retrying.
|
-- and for retrying, and updating location log.
|
||||||
let go p = getViaTmp (Remote.retrievalSecurityPolicy remote) (RemoteVerify remote) key file $ \t -> do
|
let go p = getViaTmp (Remote.retrievalSecurityPolicy remote) (RemoteVerify remote) key file $ \t -> do
|
||||||
Remote.verifiedAction (Remote.retrieveKeyFile remote key file (fromRawFilePath t) p)
|
Remote.verifiedAction (Remote.retrieveKeyFile remote key file (fromRawFilePath t) p)
|
||||||
in download' (Remote.uuid remote) key file noRetry go
|
in download' (Remote.uuid remote) key file noRetry go
|
||||||
|
@ -70,7 +70,7 @@ start = do
|
||||||
runner (AssistantDownloadRequest _ key (TransferAssociatedFile file)) remote =
|
runner (AssistantDownloadRequest _ key (TransferAssociatedFile file)) remote =
|
||||||
notifyTransfer Download file $
|
notifyTransfer Download file $
|
||||||
download' (Remote.uuid remote) key file stdRetry $ \p ->
|
download' (Remote.uuid remote) key file stdRetry $ \p ->
|
||||||
getViaTmp (Remote.retrievalSecurityPolicy remote) (RemoteVerify remote) key file $ \t -> do
|
logStatusAfter key $ getViaTmp (Remote.retrievalSecurityPolicy remote) (RemoteVerify remote) key file $ \t -> do
|
||||||
r <- tryNonAsync (Remote.retrieveKeyFile remote key file (fromRawFilePath t) p) >>= \case
|
r <- tryNonAsync (Remote.retrieveKeyFile remote key file (fromRawFilePath t) p) >>= \case
|
||||||
Left e -> do
|
Left e -> do
|
||||||
warning (show e)
|
warning (show e)
|
||||||
|
|
|
@ -16,6 +16,7 @@
|
||||||
module Logs.Location (
|
module Logs.Location (
|
||||||
LogStatus(..),
|
LogStatus(..),
|
||||||
logStatus,
|
logStatus,
|
||||||
|
logStatusAfter,
|
||||||
logChange,
|
logChange,
|
||||||
loggedLocations,
|
loggedLocations,
|
||||||
loggedLocationsHistorical,
|
loggedLocationsHistorical,
|
||||||
|
@ -48,6 +49,16 @@ logStatus key s = do
|
||||||
u <- getUUID
|
u <- getUUID
|
||||||
logChange key u s
|
logChange key u s
|
||||||
|
|
||||||
|
{- Run an action that gets the content of a key, and update the log
|
||||||
|
- when it succeeds. -}
|
||||||
|
logStatusAfter :: Key -> Annex Bool -> Annex Bool
|
||||||
|
logStatusAfter key a = ifM a
|
||||||
|
( do
|
||||||
|
logStatus key InfoPresent
|
||||||
|
return True
|
||||||
|
, return False
|
||||||
|
)
|
||||||
|
|
||||||
{- Log a change in the presence of a key's value in a repository. -}
|
{- Log a change in the presence of a key's value in a repository. -}
|
||||||
logChange :: Key -> UUID -> LogStatus -> Annex ()
|
logChange :: Key -> UUID -> LogStatus -> Annex ()
|
||||||
logChange = logChange' logNow
|
logChange = logChange' logNow
|
||||||
|
|
|
@ -76,7 +76,7 @@ runLocal runst runner a = case a of
|
||||||
v <- tryNonAsync $ do
|
v <- tryNonAsync $ do
|
||||||
let runtransfer ti =
|
let runtransfer ti =
|
||||||
Right <$> transfer download' k af (\p ->
|
Right <$> transfer download' k af (\p ->
|
||||||
getViaTmp rsp DefaultVerify k af $ \tmp ->
|
logStatusAfter k $ getViaTmp rsp DefaultVerify k af $ \tmp ->
|
||||||
storefile (fromRawFilePath tmp) o l getb validitycheck p ti)
|
storefile (fromRawFilePath tmp) o l getb validitycheck p ti)
|
||||||
let fallback = return $ Left $
|
let fallback = return $ Left $
|
||||||
ProtoFailureMessage "transfer already in progress, or unable to take transfer lock"
|
ProtoFailureMessage "transfer already in progress, or unable to take transfer lock"
|
||||||
|
|
|
@ -690,7 +690,7 @@ copyToRemote' repo r st@(State connpool duc _ _ _) key file meterupdate
|
||||||
copier <- mkCopier hardlink st params
|
copier <- mkCopier hardlink st params
|
||||||
let verify = Annex.Content.RemoteVerify r
|
let verify = Annex.Content.RemoteVerify r
|
||||||
let rsp = RetrievalAllKeysSecure
|
let rsp = RetrievalAllKeysSecure
|
||||||
res <- Annex.Content.getViaTmp rsp verify key file $ \dest ->
|
res <- logStatusAfter key $ Annex.Content.getViaTmp rsp verify key file $ \dest ->
|
||||||
metered (Just (combineMeterUpdate meterupdate p)) key $ \_ p' ->
|
metered (Just (combineMeterUpdate meterupdate p)) key $ \_ p' ->
|
||||||
copier object (fromRawFilePath dest) p' (liftIO checksuccessio)
|
copier object (fromRawFilePath dest) p' (liftIO checksuccessio)
|
||||||
Annex.Content.saveState True
|
Annex.Content.saveState True
|
||||||
|
|
|
@ -1,6 +1,9 @@
|
||||||
Setting annex.stalldetection can break move, which complains it cannot find
|
Setting annex.stalldetection can break sync when it does a move,
|
||||||
enough copies to drop.
|
which complains it cannot find enough copies to drop.
|
||||||
|
(Seems that git-annex move does work ok.)
|
||||||
|
|
||||||
The problem is that the transferrer process updates the location log, but
|
The problem is that the transferrer process updates the location log, but
|
||||||
the parent process doesn't see the update in time. So, the location log
|
the parent process doesn't see the update in time. So, the location log
|
||||||
update needs to move to the parent process. --[[Joey]]
|
update needs to move to the parent process. --[[Joey]]
|
||||||
|
|
||||||
|
> [[fixed|done]] --[[Joey]]
|
||||||
|
|
Loading…
Add table
Reference in a new issue