add ChunkMethod type and make Logs.Chunk use it, rather than assuming fixed size chunks (so eg, rolling hash chunks can be supported later)

If a newer git-annex starts logging something else in the chunk log, it
won't be used by this version, but it will be preserved when updating the
log.
This commit is contained in:
Joey Hess 2014-07-28 13:19:08 -04:00
parent a33dafae5a
commit 80cc554c82
3 changed files with 42 additions and 21 deletions

View file

@ -15,7 +15,14 @@
- Licensed under the GNU GPL version 3 or higher. - Licensed under the GNU GPL version 3 or higher.
-} -}
module Logs.Chunk where module Logs.Chunk (
ChunkMethod(..),
ChunkSize,
ChunkCount,
chunksStored,
chunksRemoved,
getCurrentChunks,
) where
import Common.Annex import Common.Annex
import Logs import Logs
@ -26,19 +33,19 @@ import Logs.Chunk.Pure
import qualified Data.Map as M import qualified Data.Map as M
import Data.Time.Clock.POSIX import Data.Time.Clock.POSIX
chunksStored :: UUID -> Key -> ChunkSize -> ChunkCount -> Annex () chunksStored :: UUID -> Key -> ChunkMethod -> ChunkCount -> Annex ()
chunksStored u k chunksize chunkcount = do chunksStored u k chunkmethod chunkcount = do
ts <- liftIO getPOSIXTime ts <- liftIO getPOSIXTime
Annex.Branch.change (chunkLogFile k) $ Annex.Branch.change (chunkLogFile k) $
showLog . changeMapLog ts (u, chunksize) chunkcount . parseLog showLog . changeMapLog ts (u, chunkmethod) chunkcount . parseLog
chunksRemoved :: UUID -> Key -> ChunkSize -> Annex () chunksRemoved :: UUID -> Key -> ChunkMethod -> Annex ()
chunksRemoved u k chunksize = chunksStored u k chunksize 0 chunksRemoved u k chunkmethod = chunksStored u k chunkmethod 0
getCurrentChunks :: UUID -> Key -> Annex [(ChunkSize, ChunkCount)] getCurrentChunks :: UUID -> Key -> Annex [(ChunkMethod, ChunkCount)]
getCurrentChunks u k = select . parseLog <$> Annex.Branch.get (chunkLogFile k) getCurrentChunks u k = select . parseLog <$> Annex.Branch.get (chunkLogFile k)
where where
select = filter (\(_sz, ct) -> ct > 0) select = filter (\(_m, ct) -> ct > 0)
. map (\((_ku, sz), l) -> (sz, value l)) . map (\((_ku, m), l) -> (m, value l))
. M.toList . M.toList
. M.filterWithKey (\(ku, _sz) _ -> ku == u) . M.filterWithKey (\(ku, _m) _ -> ku == u)

View file

@ -6,7 +6,8 @@
-} -}
module Logs.Chunk.Pure module Logs.Chunk.Pure
( ChunkSize ( ChunkMethod(..)
, ChunkSize
, ChunkCount , ChunkCount
, ChunkLog , ChunkLog
, parseLog , parseLog
@ -17,24 +18,37 @@ import Common.Annex
import Logs.MapLog import Logs.MapLog
import Data.Int import Data.Int
-- Currently chunks are all fixed size, but other chunking methods
-- may be added.
data ChunkMethod = FixedSizeChunks ChunkSize | UnknownChunks String
deriving (Ord, Eq)
type ChunkSize = Int64 type ChunkSize = Int64
-- 0 when chunks are no longer present
type ChunkCount = Integer type ChunkCount = Integer
type ChunkLog = MapLog (UUID, ChunkSize) ChunkCount type ChunkLog = MapLog (UUID, ChunkMethod) ChunkCount
parseChunkMethod :: String -> ChunkMethod
parseChunkMethod s = maybe (UnknownChunks s) FixedSizeChunks (readish s)
showChunkMethod :: ChunkMethod -> String
showChunkMethod (FixedSizeChunks sz) = show sz
showChunkMethod (UnknownChunks s) = s
parseLog :: String -> ChunkLog parseLog :: String -> ChunkLog
parseLog = parseMapLog fieldparser valueparser parseLog = parseMapLog fieldparser valueparser
where where
fieldparser s = fieldparser s =
let (u,sz) = separate (== sep) s let (u,m) = separate (== sep) s
in (,) <$> pure (toUUID u) <*> readish sz in Just (toUUID u, parseChunkMethod m)
valueparser = readish valueparser = readish
showLog :: ChunkLog -> String showLog :: ChunkLog -> String
showLog = showMapLog fieldshower valueshower showLog = showMapLog fieldshower valueshower
where where
fieldshower (u, sz) = fromUUID u ++ sep : show sz fieldshower (u, m) = fromUUID u ++ sep : showChunkMethod m
valueshower = show valueshower = show
sep :: Char sep :: Char

View file

@ -19,7 +19,6 @@ import Common.Annex
import Utility.DataUnits import Utility.DataUnits
import Types.Remote import Types.Remote
import Types.Key import Types.Key
import Logs.Chunk.Pure (ChunkSize, ChunkCount)
import Logs.Chunk import Logs.Chunk
import Utility.Metered import Utility.Metered
import Crypto (EncKey) import Crypto (EncKey)
@ -108,7 +107,7 @@ storeChunks u chunkconfig k f p storer = metered (Just p) k $ \meterupdate ->
| L.null chunk && numchunks > 0 = do | L.null chunk && numchunks > 0 = do
-- Once all chunks are successfully -- Once all chunks are successfully
-- stored, update the chunk log. -- stored, update the chunk log.
chunksStored u k chunksize numchunks chunksStored u k (FixedSizeChunks chunksize) numchunks
return True return True
| otherwise = do | otherwise = do
let (chunkkey, chunkkeys') = nextChunkKeyStream chunkkeys let (chunkkey, chunkkeys') = nextChunkKeyStream chunkkeys
@ -140,7 +139,7 @@ removeChunks remover u chunkconfig encryptor k = do
ok <- allM (remover . encryptor) (concat ls) ok <- allM (remover . encryptor) (concat ls)
when ok $ do when ok $ do
let chunksizes = catMaybes $ map (keyChunkSize <=< headMaybe) ls let chunksizes = catMaybes $ map (keyChunkSize <=< headMaybe) ls
forM_ chunksizes $ chunksRemoved u k . fromIntegral forM_ chunksizes $ chunksRemoved u k . FixedSizeChunks . fromIntegral
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
@ -313,6 +312,7 @@ chunkKeys u chunkconfig k = do
chunkKeysOnly :: UUID -> Key -> Annex [[Key]] chunkKeysOnly :: UUID -> Key -> Annex [[Key]]
chunkKeysOnly u k = map (toChunkList k) <$> getCurrentChunks u k chunkKeysOnly u k = map (toChunkList k) <$> getCurrentChunks u k
toChunkList :: Key -> (ChunkSize, ChunkCount) -> [Key] toChunkList :: Key -> (ChunkMethod, ChunkCount) -> [Key]
toChunkList k (chunksize, chunkcount) = takeChunkKeyStream chunkcount $ toChunkList k (FixedSizeChunks chunksize, chunkcount) =
chunkKeyStream k chunksize takeChunkKeyStream chunkcount $ chunkKeyStream k chunksize
toChunkList _ (UnknownChunks _, _) = []