incremental verify for webdav special remote

Sponsored-by: Dartmouth College's DANDI project
This commit is contained in:
Joey Hess 2021-08-16 16:51:58 -04:00
parent b1622eb932
commit 8613770b06
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
3 changed files with 25 additions and 17 deletions

View file

@ -8,10 +8,12 @@ git-annex (8.20210804) UNRELEASED; urgency=medium
* add: When adding a dotfile, avoid treating its name as an extension. * add: When adding a dotfile, avoid treating its name as an extension.
* rsync special remote: Stop displaying rsync progress, and use * rsync special remote: Stop displaying rsync progress, and use
git-annex's own progress display. git-annex's own progress display.
* Special remotes now checksum content while it is being retrieved, * Many special remotes now checksum content while it is being retrieved,
instead of in a separate pass at the end. This is supported for all instead of in a separate pass at the end. This is supported for most
special remotes on Linux (except for web and bittorrent), and for a special remotes on Linux (except for web, bittorrent, gitlfs, and S3),
few on other OSs (directory, bup, ddar, gcrypt, glacier). and for a few on other OSs (directory, webdav, bup, ddar, gcrypt,
glacier). Special remotes using chunking or encryption also support
it. But exporttree/importtree special remotes do not.
-- Joey Hess <id@joeyh.name> Tue, 03 Aug 2021 12:22:45 -0400 -- Joey Hess <id@joeyh.name> Tue, 03 Aug 2021 12:22:45 -0400

View file

@ -1,6 +1,6 @@
{- helpers for remotes using http {- helpers for remotes using http
- -
- Copyright 2014 Joey Hess <id@joeyh.name> - Copyright 2014-2021 Joey Hess <id@joeyh.name>
- -
- Licensed under the GNU AGPL version 3 or higher. - Licensed under the GNU AGPL version 3 or higher.
-} -}
@ -11,6 +11,7 @@ module Remote.Helper.Http where
import Annex.Common import Annex.Common
import Types.StoreRetrieve import Types.StoreRetrieve
import Types.Backend
import Remote.Helper.Special import Remote.Helper.Special
import Utility.Metered import Utility.Metered
@ -67,9 +68,9 @@ handlePopper numchunks chunksize meterupdate h sink = do
target = toBytesProcessed (numchunks * fromIntegral chunksize) target = toBytesProcessed (numchunks * fromIntegral chunksize)
-- Reads the http body and stores it to the specified file, updating the -- Reads the http body and stores it to the specified file, updating the
-- meter as it goes. -- meter and incremental verifier as it goes.
httpBodyRetriever :: FilePath -> MeterUpdate -> Response BodyReader -> IO () httpBodyRetriever :: FilePath -> MeterUpdate -> Maybe IncrementalVerifier -> Response BodyReader -> IO ()
httpBodyRetriever dest meterupdate resp httpBodyRetriever dest meterupdate iv resp
| responseStatus resp /= ok200 = giveup $ show $ responseStatus resp | responseStatus resp /= ok200 = giveup $ show $ responseStatus resp
| otherwise = bracket (openBinaryFile dest WriteMode) hClose (go zeroBytesProcessed) | otherwise = bracket (openBinaryFile dest WriteMode) hClose (go zeroBytesProcessed)
where where
@ -82,4 +83,5 @@ httpBodyRetriever dest meterupdate resp
let sofar' = addBytesProcessed sofar $ S.length b let sofar' = addBytesProcessed sofar $ S.length b
S.hPut h b S.hPut h b
meterupdate sofar' meterupdate sofar'
maybe noop (flip updateIncremental b) iv
go sofar' h go sofar' h

View file

@ -1,6 +1,6 @@
{- WebDAV remotes. {- WebDAV remotes.
- -
- Copyright 2012-2020 Joey Hess <id@joeyh.name> - Copyright 2012-2021 Joey Hess <id@joeyh.name>
- -
- Licensed under the GNU AGPL version 3 or higher. - Licensed under the GNU AGPL version 3 or higher.
-} -}
@ -28,6 +28,7 @@ import Control.Concurrent.STM hiding (check)
import Annex.Common import Annex.Common
import Types.Remote import Types.Remote
import Types.Export import Types.Export
import Types.Backend
import qualified Git import qualified Git
import qualified Annex import qualified Annex
import Config import Config
@ -168,17 +169,20 @@ finalizeStore dav tmp dest = do
moveDAV (baseURL dav) tmp dest moveDAV (baseURL dav) tmp dest
retrieve :: DavHandleVar -> ChunkConfig -> Retriever retrieve :: DavHandleVar -> ChunkConfig -> Retriever
retrieve hv cc = fileRetriever $ \d k p -> retrieve hv cc = fileRetriever' $ \d k p iv ->
withDavHandle hv $ \dav -> case cc of withDavHandle hv $ \dav -> case cc of
LegacyChunks _ -> retrieveLegacyChunked (fromRawFilePath d) k p dav LegacyChunks _ -> do
_ -> liftIO $ -- Not doing incremental verification for chunks.
goDAV dav $ retrieveHelper (keyLocation k) (fromRawFilePath d) p liftIO $ maybe noop failIncremental iv
retrieveLegacyChunked (fromRawFilePath d) k p dav
_ -> liftIO $ goDAV dav $
retrieveHelper (keyLocation k) (fromRawFilePath d) p iv
retrieveHelper :: DavLocation -> FilePath -> MeterUpdate -> DAVT IO () retrieveHelper :: DavLocation -> FilePath -> MeterUpdate -> Maybe IncrementalVerifier -> DAVT IO ()
retrieveHelper loc d p = do retrieveHelper loc d p iv = do
debugDav $ "retrieve " ++ loc debugDav $ "retrieve " ++ loc
inLocation loc $ inLocation loc $
withContentM $ httpBodyRetriever d p withContentM $ httpBodyRetriever d p iv
remove :: DavHandleVar -> Remover remove :: DavHandleVar -> Remover
remove hv k = withDavHandle hv $ \dav -> liftIO $ goDAV dav $ remove hv k = withDavHandle hv $ \dav -> liftIO $ goDAV dav $
@ -217,7 +221,7 @@ storeExportDav hdl f k loc p = case exportLocation loc of
retrieveExportDav :: DavHandleVar -> Key -> ExportLocation -> FilePath -> MeterUpdate -> Annex () retrieveExportDav :: DavHandleVar -> Key -> ExportLocation -> FilePath -> MeterUpdate -> Annex ()
retrieveExportDav hdl _k loc d p = case exportLocation loc of retrieveExportDav hdl _k loc d p = case exportLocation loc of
Right src -> withDavHandle hdl $ \h -> runExport h $ \_dav -> Right src -> withDavHandle hdl $ \h -> runExport h $ \_dav ->
retrieveHelper src d p retrieveHelper src d p Nothing
Left err -> giveup err Left err -> giveup err
checkPresentExportDav :: DavHandleVar -> Remote -> Key -> ExportLocation -> Annex Bool checkPresentExportDav :: DavHandleVar -> Remote -> Key -> ExportLocation -> Annex Bool