use existing chunks even when chunk=0
When chunk=0, always try the unchunked key first. This avoids the overhead of needing to read the git-annex branch to find the chunkcount. However, if the unchunked key is not present, go on and try the chunks. Also, when removing a chunked key, update the chunkcounts even when chunk=0.
This commit is contained in:
parent
7afb057d60
commit
2996f0eb05
1 changed files with 45 additions and 24 deletions
|
@ -23,6 +23,7 @@ import Logs.Chunk.Pure (ChunkSize, ChunkCount)
|
||||||
import Logs.Chunk
|
import Logs.Chunk
|
||||||
import Utility.Metered
|
import Utility.Metered
|
||||||
import Crypto (EncKey)
|
import Crypto (EncKey)
|
||||||
|
import Annex.Exception
|
||||||
|
|
||||||
import qualified Data.ByteString.Lazy as L
|
import qualified Data.ByteString.Lazy as L
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
|
@ -32,6 +33,10 @@ data ChunkConfig
|
||||||
| UnpaddedChunks ChunkSize
|
| UnpaddedChunks ChunkSize
|
||||||
| LegacyChunks ChunkSize
|
| LegacyChunks ChunkSize
|
||||||
|
|
||||||
|
noChunks :: ChunkConfig -> Bool
|
||||||
|
noChunks NoChunks = True
|
||||||
|
noChunks _ = False
|
||||||
|
|
||||||
chunkConfig :: RemoteConfig -> ChunkConfig
|
chunkConfig :: RemoteConfig -> ChunkConfig
|
||||||
chunkConfig m =
|
chunkConfig m =
|
||||||
case M.lookup "chunksize" m of
|
case M.lookup "chunksize" m of
|
||||||
|
@ -75,8 +80,6 @@ numChunks = pred . fromJust . keyChunkNum . fst . nextChunkKeyStream
|
||||||
- smaller than the ChunkSize), and eg, write those chunks to a Handle.
|
- smaller than the ChunkSize), and eg, write those chunks to a Handle.
|
||||||
- But this is the best that can be done with the storer interface that
|
- But this is the best that can be done with the storer interface that
|
||||||
- writes a whole L.ByteString at a time.
|
- writes a whole L.ByteString at a time.
|
||||||
-
|
|
||||||
- This action may be called on a chunked key. It will simply store it.
|
|
||||||
-}
|
-}
|
||||||
storeChunks
|
storeChunks
|
||||||
:: UUID
|
:: UUID
|
||||||
|
@ -91,7 +94,7 @@ storeChunks u chunkconfig k f p storer = metered (Just p) k $ \meterupdate ->
|
||||||
=<< (liftIO $ tryIO $ L.readFile f)
|
=<< (liftIO $ tryIO $ L.readFile f)
|
||||||
where
|
where
|
||||||
go meterupdate b = case chunkconfig of
|
go meterupdate b = case chunkconfig of
|
||||||
(UnpaddedChunks chunksize) | not (isChunkKey k) ->
|
(UnpaddedChunks chunksize) ->
|
||||||
gochunks meterupdate chunksize b (chunkKeyStream k chunksize)
|
gochunks meterupdate chunksize b (chunkKeyStream k chunksize)
|
||||||
_ -> liftIO $ storer k b meterupdate
|
_ -> liftIO $ storer k b meterupdate
|
||||||
|
|
||||||
|
@ -134,12 +137,9 @@ removeChunks :: (Key -> Annex Bool) -> UUID -> ChunkConfig -> EncKey -> Key -> A
|
||||||
removeChunks remover u chunkconfig encryptor k = do
|
removeChunks remover u chunkconfig encryptor k = do
|
||||||
ls <- chunkKeys u chunkconfig k
|
ls <- chunkKeys u chunkconfig k
|
||||||
ok <- allM (remover . encryptor) (concat ls)
|
ok <- allM (remover . encryptor) (concat ls)
|
||||||
when ok $
|
when ok $ do
|
||||||
case chunkconfig of
|
let chunksizes = catMaybes $ map (keyChunkSize <=< headMaybe) ls
|
||||||
(UnpaddedChunks _) | not (isChunkKey k) -> do
|
forM_ chunksizes $ chunksRemoved u k . fromIntegral
|
||||||
let chunksizes = catMaybes $ map (keyChunkSize <=< headMaybe) ls
|
|
||||||
forM_ chunksizes $ chunksRemoved u k . fromIntegral
|
|
||||||
_ -> noop
|
|
||||||
return ok
|
return ok
|
||||||
|
|
||||||
{- Retrieves a key from a remote, using a retriever action that
|
{- Retrieves a key from a remote, using a retriever action that
|
||||||
|
@ -163,10 +163,17 @@ retrieveChunks
|
||||||
-> MeterUpdate
|
-> MeterUpdate
|
||||||
-> (MeterUpdate -> L.ByteString -> IO ())
|
-> (MeterUpdate -> L.ByteString -> IO ())
|
||||||
-> Annex Bool
|
-> Annex Bool
|
||||||
retrieveChunks retriever u chunkconfig encryptor basek basep sink = do
|
retrieveChunks retriever u chunkconfig encryptor basek basep sink
|
||||||
ls <- chunkKeys u chunkconfig basek
|
| noChunks chunkconfig =
|
||||||
liftIO $ firstavail ls `catchNonAsync` giveup
|
-- Optimisation: Try the unchunked key first, to avoid
|
||||||
|
-- looking in the git-annex branch for chunk counts.
|
||||||
|
liftIO (retriever (encryptor basek) >>= sink basep >> return True)
|
||||||
|
`catchNonAsyncAnnex`
|
||||||
|
const (go =<< chunkKeysOnly u basek)
|
||||||
|
| otherwise = go =<< chunkKeys u chunkconfig basek
|
||||||
where
|
where
|
||||||
|
go ls = liftIO $ firstavail ls `catchNonAsync` giveup
|
||||||
|
|
||||||
giveup e = do
|
giveup e = do
|
||||||
warningIO (show e)
|
warningIO (show e)
|
||||||
return False
|
return False
|
||||||
|
@ -202,8 +209,15 @@ hasKeyChunks
|
||||||
-> EncKey
|
-> EncKey
|
||||||
-> Key
|
-> Key
|
||||||
-> Annex (Either String Bool)
|
-> Annex (Either String Bool)
|
||||||
hasKeyChunks checker u chunkconfig encryptor basek = do
|
hasKeyChunks checker u chunkconfig encryptor basek
|
||||||
checklists impossible =<< chunkKeys u chunkconfig basek
|
| noChunks chunkconfig =
|
||||||
|
-- Optimisation: Try the unchunked key first, to avoid
|
||||||
|
-- looking in the git-annex branch for chunk counts.
|
||||||
|
ifM ((Right True ==) <$> checker (encryptor basek))
|
||||||
|
( return (Right True)
|
||||||
|
, checklists impossible =<< chunkKeysOnly u basek
|
||||||
|
)
|
||||||
|
| otherwise = checklists impossible =<< chunkKeys u chunkconfig basek
|
||||||
where
|
where
|
||||||
checklists lastfailmsg [] = return $ Left lastfailmsg
|
checklists lastfailmsg [] = return $ Left lastfailmsg
|
||||||
checklists _ (l:ls)
|
checklists _ (l:ls)
|
||||||
|
@ -228,18 +242,25 @@ hasKeyChunks checker u chunkconfig encryptor basek = do
|
||||||
impossible = "no recorded chunks"
|
impossible = "no recorded chunks"
|
||||||
|
|
||||||
{- A key can be stored in a remote unchunked, or as a list of chunked keys.
|
{- A key can be stored in a remote unchunked, or as a list of chunked keys.
|
||||||
- It's even possible for a remote to have the same key stored multiple
|
- This can be the case whether or not the remote is currently configured
|
||||||
- times with different chunk sizes. This finds all possible lists of keys
|
- to use chunking.
|
||||||
- that might be on the remote that can be combined to get back the
|
-
|
||||||
- requested key.
|
- It's even possible for a remote to have the same key stored multiple
|
||||||
|
- times with different chunk sizes!
|
||||||
|
-
|
||||||
|
- This finds all possible lists of keys that might be on the remote that
|
||||||
|
- can be combined to get back the requested key, in order from most to
|
||||||
|
- least likely to exist.
|
||||||
-}
|
-}
|
||||||
chunkKeys :: UUID -> ChunkConfig -> Key -> Annex [[Key]]
|
chunkKeys :: UUID -> ChunkConfig -> Key -> Annex [[Key]]
|
||||||
chunkKeys u (UnpaddedChunks _) k | not (isChunkKey k) = do
|
chunkKeys u chunkconfig k = do
|
||||||
chunklists <- map (toChunkList k) <$> getCurrentChunks u k
|
l <- chunkKeysOnly u k
|
||||||
-- Probably using the chunklists, but the unchunked
|
return $ if noChunks chunkconfig
|
||||||
-- key could be present.
|
then [k] : l
|
||||||
return (chunklists ++ [[k]])
|
else l ++ [[k]]
|
||||||
chunkKeys _ _ k = pure [[k]]
|
|
||||||
|
chunkKeysOnly :: UUID -> Key -> Annex [[Key]]
|
||||||
|
chunkKeysOnly u k = map (toChunkList k) <$> getCurrentChunks u k
|
||||||
|
|
||||||
toChunkList :: Key -> (ChunkSize, ChunkCount) -> [Key]
|
toChunkList :: Key -> (ChunkSize, ChunkCount) -> [Key]
|
||||||
toChunkList k (chunksize, chunkcount) = takeChunkKeyStream chunkcount $
|
toChunkList k (chunksize, chunkcount) = takeChunkKeyStream chunkcount $
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue