webdav: reuse http connection when operating on the chunks of a file
For both new and legacy chunks. Massive speed up! This commit was sponsored by Dominik Wagenknecht.
This commit is contained in:
parent
0b1b85d9ea
commit
fc4b3cdcce
2 changed files with 101 additions and 88 deletions
187
Remote/WebDAV.hs
187
Remote/WebDAV.hs
|
@ -30,11 +30,9 @@ import Creds
|
||||||
import Utility.Metered
|
import Utility.Metered
|
||||||
import Utility.Url (URLString)
|
import Utility.Url (URLString)
|
||||||
import Annex.UUID
|
import Annex.UUID
|
||||||
|
import Annex.Exception
|
||||||
import Remote.WebDAV.DavLocation
|
import Remote.WebDAV.DavLocation
|
||||||
|
|
||||||
type DavUser = B8.ByteString
|
|
||||||
type DavPass = B8.ByteString
|
|
||||||
|
|
||||||
remote :: RemoteType
|
remote :: RemoteType
|
||||||
remote = RemoteType {
|
remote = RemoteType {
|
||||||
typename = "webdav",
|
typename = "webdav",
|
||||||
|
@ -47,10 +45,10 @@ gen :: Git.Repo -> UUID -> RemoteConfig -> RemoteGitConfig -> Annex (Maybe Remot
|
||||||
gen r u c gc = new <$> remoteCost gc expensiveRemoteCost
|
gen r u c gc = new <$> remoteCost gc expensiveRemoteCost
|
||||||
where
|
where
|
||||||
new cst = Just $ specialRemote c
|
new cst = Just $ specialRemote c
|
||||||
(prepareStore this chunkconfig)
|
(prepareDAV this $ store chunkconfig)
|
||||||
(prepareRetrieve this chunkconfig)
|
(prepareDAV this $ retrieve chunkconfig)
|
||||||
(prepareRemove this)
|
(prepareDAV this $ remove)
|
||||||
(prepareCheckPresent this chunkconfig)
|
(prepareDAV this $ checkKey this chunkconfig)
|
||||||
this
|
this
|
||||||
where
|
where
|
||||||
this = Remote {
|
this = Remote {
|
||||||
|
@ -88,30 +86,34 @@ webdavSetup mu mcreds c = do
|
||||||
c'' <- setRemoteCredPair c' (davCreds u) creds
|
c'' <- setRemoteCredPair c' (davCreds u) creds
|
||||||
return (c'', u)
|
return (c'', u)
|
||||||
|
|
||||||
prepareStore :: Remote -> ChunkConfig -> Preparer Storer
|
-- Opens a http connection to the DAV server, which will be reused
|
||||||
prepareStore r chunkconfig = simplyPrepare $ fileStorer $ \k f p ->
|
-- each time the helper is called.
|
||||||
davAction r False $ \(baseurl, user, pass) -> liftIO $
|
prepareDAV :: Remote -> (Maybe DavHandle -> helper) -> Preparer helper
|
||||||
withMeteredFile f p $
|
prepareDAV = resourcePrepare . const . withDAVHandle
|
||||||
storeHelper chunkconfig k baseurl user pass
|
|
||||||
|
|
||||||
storeHelper :: ChunkConfig -> Key -> URLString -> DavUser -> DavPass -> L.ByteString -> IO Bool
|
store :: ChunkConfig -> Maybe DavHandle -> Storer
|
||||||
storeHelper chunkconfig k baseurl user pass b = do
|
store _ Nothing = byteStorer $ \_k _b _p -> return False
|
||||||
|
store chunkconfig (Just dav) = fileStorer $ \k f p -> liftIO $
|
||||||
|
withMeteredFile f p $ storeHelper chunkconfig k dav
|
||||||
|
|
||||||
|
storeHelper :: ChunkConfig -> Key -> DavHandle -> L.ByteString -> IO Bool
|
||||||
|
storeHelper chunkconfig k dav b = do
|
||||||
case chunkconfig of
|
case chunkconfig of
|
||||||
LegacyChunks chunksize -> do
|
LegacyChunks chunksize -> do
|
||||||
let storehttp l b' = do
|
let storehttp l b' = do
|
||||||
void $ goDAV baseurl user pass $ do
|
void $ goDAV dav $ do
|
||||||
maybe noop (void . mkColRecursive) (locationParent l)
|
maybe noop (void . mkColRecursive) (locationParent l)
|
||||||
inLocation l $ putContentM (contentType, b')
|
inLocation l $ putContentM (contentType, b')
|
||||||
let storer locs = Legacy.storeChunked chunksize locs storehttp b
|
let storer locs = Legacy.storeChunked chunksize locs storehttp b
|
||||||
let recorder l s = storehttp l (L8.fromString s)
|
let recorder l s = storehttp l (L8.fromString s)
|
||||||
let finalizer tmp' dest' = goDAV baseurl user pass $
|
let finalizer tmp' dest' = goDAV dav $
|
||||||
finalizeStore baseurl tmp' (fromJust $ locationParent dest')
|
finalizeStore (baseURL dav) tmp' (fromJust $ locationParent dest')
|
||||||
Legacy.storeChunks k tmp dest storer recorder finalizer
|
Legacy.storeChunks k tmp dest storer recorder finalizer
|
||||||
_ -> goDAV baseurl user pass $ do
|
_ -> goDAV dav $ do
|
||||||
void $ mkColRecursive tmpDir
|
void $ mkColRecursive tmpDir
|
||||||
inLocation tmp $
|
inLocation tmp $
|
||||||
putContentM (contentType, b)
|
putContentM (contentType, b)
|
||||||
finalizeStore baseurl tmp dest
|
finalizeStore (baseURL dav) tmp dest
|
||||||
return True
|
return True
|
||||||
where
|
where
|
||||||
tmp = keyTmpLocation k
|
tmp = keyTmpLocation k
|
||||||
|
@ -126,77 +128,71 @@ finalizeStore baseurl tmp dest = do
|
||||||
retrieveCheap :: Key -> FilePath -> Annex Bool
|
retrieveCheap :: Key -> FilePath -> Annex Bool
|
||||||
retrieveCheap _ _ = return False
|
retrieveCheap _ _ = return False
|
||||||
|
|
||||||
prepareRetrieve :: Remote -> ChunkConfig -> Preparer Retriever
|
retrieve :: ChunkConfig -> Maybe DavHandle -> Retriever
|
||||||
prepareRetrieve r chunkconfig = simplyPrepare $ fileRetriever $ \d k p ->
|
retrieve _ Nothing = error "unable to connect"
|
||||||
davAction r onerr $ \(baseurl, user, pass) -> liftIO $
|
retrieve chunkconfig (Just dav) = fileRetriever $ \d k p -> liftIO $
|
||||||
withStoredFiles chunkconfig k baseurl user pass onerr $ \locs -> do
|
withStoredFiles chunkconfig k dav onerr $ \locs -> do
|
||||||
Legacy.meteredWriteFileChunks p d locs $ \l -> do
|
Legacy.meteredWriteFileChunks p d locs $ \l -> do
|
||||||
mb <- goDAV baseurl user pass $ safely $
|
mb <- goDAV dav $ safely $
|
||||||
inLocation l $
|
inLocation l $
|
||||||
snd <$> getContentM
|
snd <$> getContentM
|
||||||
case mb of
|
case mb of
|
||||||
Nothing -> onerr
|
Nothing -> onerr
|
||||||
Just b -> return b
|
Just b -> return b
|
||||||
where
|
where
|
||||||
onerr = error "download failed"
|
onerr = error "download failed"
|
||||||
|
|
||||||
prepareRemove :: Remote -> Preparer Remover
|
remove :: Maybe DavHandle -> Remover
|
||||||
prepareRemove r = simplyPrepare $ \k ->
|
remove Nothing _ = return False
|
||||||
davAction r False $ \(baseurl, user, pass) -> liftIO $ do
|
remove (Just dav) k = liftIO $ do
|
||||||
-- Delete the key's whole directory, including any
|
-- Delete the key's whole directory, including any
|
||||||
-- legacy chunked files, etc, in a single action.
|
-- legacy chunked files, etc, in a single action.
|
||||||
ret <- goDAV baseurl user pass $ safely $
|
ret <- goDAV dav $ safely $
|
||||||
inLocation (keyLocation k) delContentM
|
inLocation (keyLocation k) delContentM
|
||||||
return (isJust ret)
|
return (isJust ret)
|
||||||
|
|
||||||
prepareCheckPresent :: Remote -> ChunkConfig -> Preparer CheckPresent
|
checkKey :: Remote -> ChunkConfig -> Maybe DavHandle -> CheckPresent
|
||||||
prepareCheckPresent r chunkconfig = simplyPrepare $ checkKey r chunkconfig
|
checkKey r _ Nothing _ = error $ name r ++ " not configured"
|
||||||
|
checkKey r chunkconfig (Just dav) k = either error id <$> go
|
||||||
checkKey :: Remote -> ChunkConfig -> Key -> Annex Bool
|
|
||||||
checkKey r chunkconfig k = davAction r noconn (either error id <$$> go)
|
|
||||||
where
|
where
|
||||||
noconn = error $ name r ++ " not configured"
|
go = do
|
||||||
|
|
||||||
go (baseurl, user, pass) = do
|
|
||||||
showAction $ "checking " ++ name r
|
showAction $ "checking " ++ name r
|
||||||
liftIO $ withStoredFiles chunkconfig k baseurl user pass onerr check
|
liftIO $ withStoredFiles chunkconfig k dav onerr check
|
||||||
where
|
|
||||||
check [] = return $ Right True
|
|
||||||
check (l:ls) = do
|
|
||||||
v <- goDAV baseurl user pass $ existsDAV l
|
|
||||||
if v == Right True
|
|
||||||
then check ls
|
|
||||||
else return v
|
|
||||||
|
|
||||||
{- Failed to read the chunkcount file; see if it's missing,
|
check [] = return $ Right True
|
||||||
- or if there's a problem accessing it,
|
check (l:ls) = do
|
||||||
- or perhaps this was an intermittent error. -}
|
v <- goDAV dav $ existsDAV l
|
||||||
onerr f = do
|
if v == Right True
|
||||||
v <- goDAV baseurl user pass $ existsDAV f
|
then check ls
|
||||||
return $ if v == Right True
|
else return v
|
||||||
then Left $ "failed to read " ++ f
|
|
||||||
else v
|
{- Failed to read the chunkcount file; see if it's missing,
|
||||||
|
- or if there's a problem accessing it,
|
||||||
|
- or perhaps this was an intermittent error. -}
|
||||||
|
onerr f = do
|
||||||
|
v <- goDAV dav $ existsDAV f
|
||||||
|
return $ if v == Right True
|
||||||
|
then Left $ "failed to read " ++ f
|
||||||
|
else v
|
||||||
|
|
||||||
withStoredFiles
|
withStoredFiles
|
||||||
:: ChunkConfig
|
:: ChunkConfig
|
||||||
-> Key
|
-> Key
|
||||||
-> URLString
|
-> DavHandle
|
||||||
-> DavUser
|
|
||||||
-> DavPass
|
|
||||||
-> (DavLocation -> IO a)
|
-> (DavLocation -> IO a)
|
||||||
-> ([DavLocation] -> IO a)
|
-> ([DavLocation] -> IO a)
|
||||||
-> IO a
|
-> IO a
|
||||||
withStoredFiles chunkconfig k baseurl user pass onerr a = case chunkconfig of
|
withStoredFiles chunkconfig k dav onerr a = case chunkconfig of
|
||||||
LegacyChunks _ -> do
|
LegacyChunks _ -> do
|
||||||
let chunkcount = keyloc ++ Legacy.chunkCount
|
let chunkcount = keyloc ++ Legacy.chunkCount
|
||||||
v <- goDAV baseurl user pass $ safely $
|
v <- goDAV dav $ safely $
|
||||||
inLocation chunkcount $
|
inLocation chunkcount $
|
||||||
snd <$> getContentM
|
snd <$> getContentM
|
||||||
case v of
|
case v of
|
||||||
Just s -> a $ Legacy.listChunks keyloc $ L8.toString s
|
Just s -> a $ Legacy.listChunks keyloc $ L8.toString s
|
||||||
Nothing -> do
|
Nothing -> do
|
||||||
chunks <- Legacy.probeChunks keyloc $ \f ->
|
chunks <- Legacy.probeChunks keyloc $ \f ->
|
||||||
(== Right True) <$> goDAV baseurl user pass (existsDAV f)
|
(== Right True) <$> goDAV dav (existsDAV f)
|
||||||
if null chunks
|
if null chunks
|
||||||
then onerr chunkcount
|
then onerr chunkcount
|
||||||
else a chunks
|
else a chunks
|
||||||
|
@ -204,20 +200,19 @@ withStoredFiles chunkconfig k baseurl user pass onerr a = case chunkconfig of
|
||||||
where
|
where
|
||||||
keyloc = keyLocation k ++ keyFile k
|
keyloc = keyLocation k ++ keyFile k
|
||||||
|
|
||||||
davAction :: Remote -> a -> ((DavLocation, DavUser, DavPass) -> Annex a) -> Annex a
|
|
||||||
davAction r unconfigured action = do
|
|
||||||
mcreds <- getCreds (config r) (uuid r)
|
|
||||||
case (mcreds, configUrl r) of
|
|
||||||
(Just (user, pass), Just url) ->
|
|
||||||
action (url, toDavUser user, toDavPass pass)
|
|
||||||
_ -> return unconfigured
|
|
||||||
|
|
||||||
configUrl :: Remote -> Maybe URLString
|
configUrl :: Remote -> Maybe URLString
|
||||||
configUrl r = fixup <$> M.lookup "url" (config r)
|
configUrl r = fixup <$> M.lookup "url" (config r)
|
||||||
where
|
where
|
||||||
-- box.com DAV url changed
|
-- box.com DAV url changed
|
||||||
fixup = replace "https://www.box.com/dav/" "https://dav.box.com/dav/"
|
fixup = replace "https://www.box.com/dav/" "https://dav.box.com/dav/"
|
||||||
|
|
||||||
|
type DavUser = B8.ByteString
|
||||||
|
type DavPass = B8.ByteString
|
||||||
|
|
||||||
|
baseURL :: DavHandle -> URLString
|
||||||
|
baseURL (DavHandle _ _ _ u) = u
|
||||||
|
|
||||||
|
|
||||||
toDavUser :: String -> DavUser
|
toDavUser :: String -> DavUser
|
||||||
toDavUser = B8.fromString
|
toDavUser = B8.fromString
|
||||||
|
|
||||||
|
@ -234,7 +229,8 @@ toDavPass = B8.fromString
|
||||||
testDav :: URLString -> Maybe CredPair -> Annex ()
|
testDav :: URLString -> Maybe CredPair -> Annex ()
|
||||||
testDav url (Just (u, p)) = do
|
testDav url (Just (u, p)) = do
|
||||||
showSideAction "testing WebDAV server"
|
showSideAction "testing WebDAV server"
|
||||||
test $ liftIO $ goDAV url user pass $ do
|
test $ liftIO $ evalDAVT url $ do
|
||||||
|
prepDAV user pass
|
||||||
makeParentDirs
|
makeParentDirs
|
||||||
inLocation tmpDir $ void mkCol
|
inLocation tmpDir $ void mkCol
|
||||||
inLocation (tmpLocation "git-annex-test") $ do
|
inLocation (tmpLocation "git-annex-test") $ do
|
||||||
|
@ -325,15 +321,32 @@ safely :: DAVT IO a -> DAVT IO (Maybe a)
|
||||||
safely a = (Just <$> a)
|
safely a = (Just <$> a)
|
||||||
`EL.catch` (\(_ :: EL.SomeException) -> return Nothing)
|
`EL.catch` (\(_ :: EL.SomeException) -> return Nothing)
|
||||||
|
|
||||||
goDAV :: URLString -> DavUser -> DavPass -> DAVT IO a -> IO a
|
choke :: IO (Either String a) -> IO a
|
||||||
goDAV url user pass a = choke $ evalDAVT url $ do
|
choke f = do
|
||||||
setResponseTimeout Nothing -- disable default (5 second!) timeout
|
x <- f
|
||||||
setCreds user pass
|
case x of
|
||||||
|
Left e -> error e
|
||||||
|
Right r -> return r
|
||||||
|
|
||||||
|
data DavHandle = DavHandle DAVContext DavUser DavPass URLString
|
||||||
|
|
||||||
|
withDAVHandle :: Remote -> (Maybe DavHandle -> Annex a) -> Annex a
|
||||||
|
withDAVHandle r a = do
|
||||||
|
mcreds <- getCreds (config r) (uuid r)
|
||||||
|
case (mcreds, configUrl r) of
|
||||||
|
(Just (user, pass), Just baseurl) ->
|
||||||
|
bracketIO (mkDAVContext baseurl) closeDAVContext $ \ctx ->
|
||||||
|
a (Just (DavHandle ctx (toDavUser user) (toDavPass pass) baseurl))
|
||||||
|
_ -> a Nothing
|
||||||
|
|
||||||
|
goDAV :: DavHandle -> DAVT IO a -> IO a
|
||||||
|
goDAV (DavHandle ctx user pass _) a = choke $ run $ do
|
||||||
|
prepDAV user pass
|
||||||
a
|
a
|
||||||
where
|
where
|
||||||
choke :: IO (Either String a) -> IO a
|
run = fst <$$> runDAVContext ctx
|
||||||
choke f = do
|
|
||||||
x <- f
|
prepDAV :: DavUser -> DavPass -> DAVT IO ()
|
||||||
case x of
|
prepDAV user pass = do
|
||||||
Left e -> error e
|
setResponseTimeout Nothing -- disable default (5 second!) timeout
|
||||||
Right r -> return r
|
setCreds user pass
|
||||||
|
|
|
@ -142,7 +142,7 @@ Executable git-annex
|
||||||
CPP-Options: -DWITH_S3
|
CPP-Options: -DWITH_S3
|
||||||
|
|
||||||
if flag(WebDAV)
|
if flag(WebDAV)
|
||||||
Build-Depends: DAV (> 0.8),
|
Build-Depends: DAV (>= 0.8),
|
||||||
http-client, http-conduit, http-types, lifted-base, transformers
|
http-client, http-conduit, http-types, lifted-base, transformers
|
||||||
CPP-Options: -DWITH_WEBDAV
|
CPP-Options: -DWITH_WEBDAV
|
||||||
|
|
||||||
|
|
Loading…
Reference in a new issue