toward SafeDropProof expiry checking

Added Maybe POSIXTime to SafeDropProof, which gets set when the proof is
based on a LockedCopy. If there are several LockedCopies, it uses the
closest expiry time. That is not optimal, it may be that the proof
expires based on one LockedCopy but another one has not expired. But
that seems unlikely to really happen, and anyway the user can just
re-run a drop if it fails due to expiry.

Pass the SafeDropProof to removeKey, which is responsible for checking
it for expiry in situations where that could be a problem. Which really
only means in Remote.Git.

Made Remote.Git check expiry when dropping from a local remote.

Checking expiry when dropping from a P2P remote is not yet implemented.
P2P.Protocol.remove has SafeDropProof plumbed through to it for that
purpose.

Fixing the remaining 2 build warnings should complete this work.

Note that the use of a POSIXTime here means that if the clock gets set
forward while git-annex is in the middle of a drop, it may say that
dropping took too long. That seems ok. Less ok is that if the clock gets
turned back a sufficient amount (eg 5 minutes), proof expiry won't be
noticed. It might be better to use the Monotonic clock, but that doesn't
advance when a laptop is suspended, and while there is the linux
Boottime clock, that is not available on other systems. Perhaps a
combination of POSIXTime and the Monotonic clock could detect laptop
suspension and also detect clock being turned back?

There is a potential future flag day where
p2pDefaultLockContentRetentionDuration is not assumed, but is probed
using the P2P protocol, and peers that don't support it can no longer
produce a LockedCopy. Until that happens, when git-annex is
communicating with older peers there is a risk of data loss when
a ssh connection closes during LOCKCONTENT.
This commit is contained in:
Joey Hess 2024-07-04 12:23:46 -04:00
parent 98dbfb6bbd
commit 1243af4a18
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
39 changed files with 274 additions and 123 deletions

View file

@ -226,10 +226,10 @@ seekResume h encryptor chunkkeys checker = do
-
- This action may be called on a chunked key. It will simply remove it.
-}
removeChunks :: Remover -> UUID -> ChunkConfig -> EncKey -> Key -> Annex ()
removeChunks remover u chunkconfig encryptor k = do
removeChunks :: Remover -> UUID -> ChunkConfig -> EncKey -> Maybe SafeDropProof -> Key -> Annex ()
removeChunks remover u chunkconfig encryptor proof k = do
ls <- map chunkKeyList <$> chunkKeys u chunkconfig k
mapM_ (remover . encryptor) (concat ls)
mapM_ (remover proof . encryptor) (concat ls)
let chunksizes = catMaybes $ map (fromKey keyChunkSize <=< headMaybe) ls
forM_ chunksizes $ chunksRemoved u k . FixedSizeChunks . fromIntegral

View file

@ -41,7 +41,8 @@ addHooks' r starthook stophook = r'
, retrieveKeyFileCheap = case retrieveKeyFileCheap r of
Just a -> Just $ \k af f -> wrapper $ a k af f
Nothing -> Nothing
, removeKey = wrapper . removeKey r
, removeKey = \proof k ->
wrapper $ removeKey r proof k
, checkPresent = wrapper . checkPresent r
}
where

View file

@ -21,8 +21,10 @@ import Types.NumCopies
import Annex.Verify
import Logs.Location
import Utility.SafeOutput
import Utility.HumanTime
import Control.Concurrent
import Data.Time.Clock.POSIX
-- Runs a Proto action using a connection it sets up.
type ProtoRunner a = P2P.Proto a -> Annex (Maybe a)
@ -60,8 +62,8 @@ retrieve gc runner k af dest p verifyconfig = do
Just (False, _) -> giveup "Transfer failed"
Nothing -> remoteUnavail
remove :: UUID -> ProtoRunner (Either String Bool, Maybe [UUID]) -> Key -> Annex ()
remove remoteuuid runner k = runner (P2P.remove k) >>= \case
remove :: UUID -> ProtoRunner (Either String Bool, Maybe [UUID]) -> Maybe SafeDropProof -> Key -> Annex ()
remove remoteuuid runner proof k = runner (P2P.remove proof k) >>= \case
Just (Right True, alsoremoveduuids) -> note alsoremoveduuids
Just (Right False, alsoremoveduuids) -> do
note alsoremoveduuids
@ -94,18 +96,23 @@ checkpresent runner k =
-}
lock :: WithConn a c -> ProtoConnRunner c -> UUID -> Key -> (VerifiedCopy -> Annex a) -> Annex a
lock withconn connrunner u k callback = withconn $ \conn -> do
starttime <- liftIO getPOSIXTime
connv <- liftIO $ newMVar conn
let runproto d p = do
c <- liftIO $ takeMVar connv
(c', mr) <- connrunner p c
liftIO $ putMVar connv c'
return (fromMaybe d mr)
r <- P2P.lockContentWhile runproto k go
r <- P2P.lockContentWhile runproto k (go starttime)
conn' <- liftIO $ takeMVar connv
return (conn', r)
where
go False = giveup "can't lock content"
go True = withVerifiedCopy LockedCopy u (return True) callback
go _ False = giveup "can't lock content"
go starttime True = do
let check = return $ Left $ starttime + retentionduration
withVerifiedCopy LockedCopy u check callback
retentionduration = fromIntegral $
durationSeconds p2pDefaultLockContentRetentionDuration
remoteUnavail :: a
remoteUnavail = giveup "can't connect to remote"

View file

@ -47,8 +47,8 @@ adjustReadOnly r
readonlyStoreKey :: Key -> AssociatedFile -> Maybe FilePath -> MeterUpdate -> Annex ()
readonlyStoreKey _ _ _ _ = readonlyFail
readonlyRemoveKey :: Key -> Annex ()
readonlyRemoveKey _ = readonlyFail
readonlyRemoveKey :: Maybe SafeDropProof -> Key -> Annex ()
readonlyRemoveKey _ _ = readonlyFail
readonlyStorer :: Storer
readonlyStorer _ _ _ = readonlyFail

View file

@ -138,8 +138,8 @@ storeKeyDummy :: Key -> AssociatedFile -> Maybe FilePath -> MeterUpdate -> Annex
storeKeyDummy _ _ _ _ = error "missing storeKey implementation"
retrieveKeyFileDummy :: Key -> AssociatedFile -> FilePath -> MeterUpdate -> VerifyConfig -> Annex Verification
retrieveKeyFileDummy _ _ _ _ _ = error "missing retrieveKeyFile implementation"
removeKeyDummy :: Key -> Annex ()
removeKeyDummy _ = error "missing removeKey implementation"
removeKeyDummy :: Maybe SafeDropProof -> Key -> Annex ()
removeKeyDummy _ _ = error "missing removeKey implementation"
checkPresentDummy :: Key -> Annex Bool
checkPresentDummy _ = error "missing checkPresent implementation"
@ -197,7 +197,7 @@ specialRemote' cfg c storer retriever remover checkpresent baser = encr
, retrievalSecurityPolicy = if isencrypted
then mkRetrievalVerifiableKeysSecure (gitconfig baser)
else retrievalSecurityPolicy baser
, removeKey = \k -> cip >>= removeKeyGen k
, removeKey = \k proof -> cip >>= removeKeyGen k proof
, checkPresent = \k -> cip >>= checkPresentGen k
, cost = if isencrypted
then cost baser + encryptedRemoteCostAdj
@ -227,7 +227,7 @@ specialRemote' cfg c storer retriever remover checkpresent baser = encr
storeChunks (uuid baser) chunkconfig enck k src p'
enc encr storer checkpresent
where
rollback = void $ removeKey encr k
rollback = void $ removeKey encr Nothing k
enck = maybe id snd enc
-- call retriever to get chunks; decrypt them; stream to dest file
@ -238,8 +238,8 @@ specialRemote' cfg c storer retriever remover checkpresent baser = encr
where
enck = maybe id snd enc
removeKeyGen k enc =
removeChunks remover (uuid baser) chunkconfig enck k
removeKeyGen proof k enc =
removeChunks remover (uuid baser) chunkconfig enck proof k
where
enck = maybe id snd enc

View file

@ -105,13 +105,17 @@ inAnnex r k = onRemote NoConsumeStdin r (runcheck, cantCheck r) "inannex"
dispatch (ExitFailure 1) = return False
dispatch _ = cantCheck r
{- Removes a key from a remote. -}
dropKey :: Git.Repo -> Key -> Annex ()
dropKey r key = unlessM (dropKey' r key) $
{- Removes a key from a remote using the legacy git-annex-shell dropkey,
- rather than the P2P protocol.
-
- The proof is not checked for expire on the remote, so this should only
- be used by remotes that do not have lockContent return a LockedCopy. -}
dropKey :: Git.Repo -> Maybe SafeDropProof -> Key -> Annex ()
dropKey r proof key = unlessM (dropKey' r proof key) $
giveup "unable to remove key from remote"
dropKey' :: Git.Repo -> Key -> Annex Bool
dropKey' r key = onRemote NoConsumeStdin r (\f p -> liftIO (boolSystem f p), return False) "dropkey"
dropKey' :: Git.Repo -> Maybe SafeDropProof -> Key -> Annex Bool
dropKey' r _proof key = onRemote NoConsumeStdin r (\f p -> liftIO (boolSystem f p), return False) "dropkey"
[ Param "--quiet", Param "--force"
, Param $ serializeKey key
]