add ContentSource type, for remotes that act on files rather than ByteStrings
Note that currently nothing cleans up a ContentSource's file, when eg, retrieving chunks.
This commit is contained in:
parent
216fdbd6bd
commit
f5af470875
5 changed files with 102 additions and 49 deletions
|
@ -110,9 +110,9 @@ tmpDir d k = addTrailingPathSeparator $ d </> "tmp" </> keyFile k
|
||||||
prepareStore :: FilePath -> ChunkConfig -> Preparer Storer
|
prepareStore :: FilePath -> ChunkConfig -> Preparer Storer
|
||||||
prepareStore d chunkconfig = checkPrepare
|
prepareStore d chunkconfig = checkPrepare
|
||||||
(\k -> checkDiskSpace (Just d) k 0)
|
(\k -> checkDiskSpace (Just d) k 0)
|
||||||
(store d chunkconfig)
|
(byteStorer $ store d chunkconfig)
|
||||||
|
|
||||||
store :: FilePath -> ChunkConfig -> Storer
|
store :: FilePath -> ChunkConfig -> Key -> L.ByteString -> MeterUpdate -> IO Bool
|
||||||
store d chunkconfig k b p = do
|
store d chunkconfig k b p = do
|
||||||
void $ tryIO $ createDirectoryIfMissing True tmpdir
|
void $ tryIO $ createDirectoryIfMissing True tmpdir
|
||||||
case chunkconfig of
|
case chunkconfig of
|
||||||
|
@ -137,7 +137,8 @@ store d chunkconfig k b p = do
|
||||||
|
|
||||||
retrieve :: FilePath -> ChunkConfig -> Preparer Retriever
|
retrieve :: FilePath -> ChunkConfig -> Preparer Retriever
|
||||||
retrieve d (LegacyChunks _) = Legacy.retrieve locations d
|
retrieve d (LegacyChunks _) = Legacy.retrieve locations d
|
||||||
retrieve d _ = simplyPrepare $ \k -> L.readFile =<< getLocation d k
|
retrieve d _ = simplyPrepare $ byteRetriever $
|
||||||
|
\k -> L.readFile =<< getLocation d k
|
||||||
|
|
||||||
retrieveCheap :: FilePath -> ChunkConfig -> Key -> FilePath -> Annex Bool
|
retrieveCheap :: FilePath -> ChunkConfig -> Key -> FilePath -> Annex Bool
|
||||||
-- no cheap retrieval possible for chunks
|
-- no cheap retrieval possible for chunks
|
||||||
|
|
|
@ -96,7 +96,7 @@ retrieve locations d basek a = do
|
||||||
tmpdir <- fromRepo $ gitAnnexTmpMiscDir
|
tmpdir <- fromRepo $ gitAnnexTmpMiscDir
|
||||||
createAnnexDirectory tmpdir
|
createAnnexDirectory tmpdir
|
||||||
let tmp = tmpdir </> keyFile basek ++ ".directorylegacy.tmp"
|
let tmp = tmpdir </> keyFile basek ++ ".directorylegacy.tmp"
|
||||||
a $ Just $ \k -> do
|
a $ Just $ byteRetriever $ \k -> do
|
||||||
void $ withStoredFiles d locations k $ \fs -> do
|
void $ withStoredFiles d locations k $ \fs -> do
|
||||||
forM_ fs $
|
forM_ fs $
|
||||||
S.appendFile tmp <=< S.readFile
|
S.appendFile tmp <=< S.readFile
|
||||||
|
|
|
@ -17,6 +17,7 @@ module Remote.Helper.Chunked (
|
||||||
|
|
||||||
import Common.Annex
|
import Common.Annex
|
||||||
import Utility.DataUnits
|
import Utility.DataUnits
|
||||||
|
import Types.StoreRetrieve
|
||||||
import Types.Remote
|
import Types.Remote
|
||||||
import Types.Key
|
import Types.Key
|
||||||
import Logs.Chunk
|
import Logs.Chunk
|
||||||
|
@ -90,29 +91,31 @@ storeChunks
|
||||||
-> Key
|
-> Key
|
||||||
-> FilePath
|
-> FilePath
|
||||||
-> MeterUpdate
|
-> MeterUpdate
|
||||||
-> (Key -> L.ByteString -> MeterUpdate -> IO Bool)
|
-> (Key -> ContentSource -> MeterUpdate -> IO Bool)
|
||||||
-> (Key -> Annex (Either String Bool))
|
-> (Key -> Annex (Either String Bool))
|
||||||
-> Annex Bool
|
-> Annex Bool
|
||||||
storeChunks u chunkconfig k f p storer checker = bracketIO open close go
|
storeChunks u chunkconfig k f p storer checker =
|
||||||
|
case chunkconfig of
|
||||||
|
(UnpaddedChunks chunksize) ->
|
||||||
|
bracketIO open close (go chunksize)
|
||||||
|
_ -> showprogress $
|
||||||
|
liftIO . storer k (FileContent f)
|
||||||
where
|
where
|
||||||
|
showprogress = metered (Just p) k
|
||||||
|
|
||||||
open = tryIO $ openBinaryFile f ReadMode
|
open = tryIO $ openBinaryFile f ReadMode
|
||||||
|
|
||||||
close (Right h) = hClose h
|
close (Right h) = hClose h
|
||||||
close (Left _) = noop
|
close (Left _) = noop
|
||||||
|
|
||||||
go (Left e) = do
|
go _ (Left e) = do
|
||||||
warning (show e)
|
warning (show e)
|
||||||
return False
|
return False
|
||||||
go (Right h) = metered (Just p) k $ \meterupdate ->
|
go chunksize (Right h) = showprogress $ \meterupdate -> do
|
||||||
case chunkconfig of
|
let chunkkeys = chunkKeyStream k chunksize
|
||||||
(UnpaddedChunks chunksize) -> do
|
(chunkkeys', startpos) <- seekResume h chunkkeys checker
|
||||||
let chunkkeys = chunkKeyStream k chunksize
|
b <- liftIO $ L.hGetContents h
|
||||||
(chunkkeys', startpos) <- seekResume h chunkkeys checker
|
gochunks meterupdate startpos chunksize b chunkkeys'
|
||||||
b <- liftIO $ L.hGetContents h
|
|
||||||
gochunks meterupdate startpos chunksize b chunkkeys'
|
|
||||||
_ -> liftIO $ do
|
|
||||||
b <- L.hGetContents h
|
|
||||||
storer k b meterupdate
|
|
||||||
|
|
||||||
gochunks :: MeterUpdate -> BytesProcessed -> ChunkSize -> L.ByteString -> ChunkKeyStream -> Annex Bool
|
gochunks :: MeterUpdate -> BytesProcessed -> ChunkSize -> L.ByteString -> ChunkKeyStream -> Annex Bool
|
||||||
gochunks meterupdate startpos chunksize = loop startpos . splitchunk
|
gochunks meterupdate startpos chunksize = loop startpos . splitchunk
|
||||||
|
@ -127,7 +130,7 @@ storeChunks u chunkconfig k f p storer checker = bracketIO open close go
|
||||||
return True
|
return True
|
||||||
| otherwise = do
|
| otherwise = do
|
||||||
let (chunkkey, chunkkeys') = nextChunkKeyStream chunkkeys
|
let (chunkkey, chunkkeys') = nextChunkKeyStream chunkkeys
|
||||||
ifM (liftIO $ storer chunkkey chunk meterupdate')
|
ifM (liftIO $ storer chunkkey (ByteContent chunk) meterupdate')
|
||||||
( do
|
( do
|
||||||
let bytesprocessed' = addBytesProcessed bytesprocessed (L.length chunk)
|
let bytesprocessed' = addBytesProcessed bytesprocessed (L.length chunk)
|
||||||
loop bytesprocessed' (splitchunk bs) chunkkeys'
|
loop bytesprocessed' (splitchunk bs) chunkkeys'
|
||||||
|
@ -197,8 +200,7 @@ removeChunks remover u chunkconfig encryptor k = do
|
||||||
forM_ chunksizes $ chunksRemoved u k . FixedSizeChunks . 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.
|
||||||
- streams it to a ByteString.
|
|
||||||
-
|
-
|
||||||
- When the remote is chunked, tries each of the options returned by
|
- When the remote is chunked, tries each of the options returned by
|
||||||
- chunkKeys until it finds one where the retriever successfully
|
- chunkKeys until it finds one where the retriever successfully
|
||||||
|
@ -214,7 +216,7 @@ removeChunks remover u chunkconfig encryptor k = do
|
||||||
- to resume.
|
- to resume.
|
||||||
-}
|
-}
|
||||||
retrieveChunks
|
retrieveChunks
|
||||||
:: (Key -> IO L.ByteString)
|
:: Retriever
|
||||||
-> UUID
|
-> UUID
|
||||||
-> ChunkConfig
|
-> ChunkConfig
|
||||||
-> EncKey
|
-> EncKey
|
||||||
|
@ -250,13 +252,13 @@ retrieveChunks retriever u chunkconfig encryptor basek dest basep sink
|
||||||
Left e
|
Left e
|
||||||
| null ls -> giveup e
|
| null ls -> giveup e
|
||||||
| otherwise -> firstavail currsize ls
|
| otherwise -> firstavail currsize ls
|
||||||
Right b -> do
|
Right content -> do
|
||||||
let offset = resumeOffset currsize k
|
let offset = resumeOffset currsize k
|
||||||
let p = maybe basep
|
let p = maybe basep
|
||||||
(offsetMeterUpdate basep . toBytesProcessed)
|
(offsetMeterUpdate basep . toBytesProcessed)
|
||||||
offset
|
offset
|
||||||
bracket (maybe opennew openresume offset) hClose $ \h -> do
|
bracket (maybe opennew openresume offset) hClose $ \h -> do
|
||||||
sink h p b
|
withBytes content $ sink h p
|
||||||
let sz = toBytesProcessed $
|
let sz = toBytesProcessed $
|
||||||
fromMaybe 0 $ keyChunkSize k
|
fromMaybe 0 $ keyChunkSize k
|
||||||
getrest p h sz sz ks
|
getrest p h sz sz ks
|
||||||
|
@ -264,11 +266,13 @@ retrieveChunks retriever u chunkconfig encryptor basek dest basep sink
|
||||||
getrest _ _ _ _ [] = return True
|
getrest _ _ _ _ [] = return True
|
||||||
getrest p h sz bytesprocessed (k:ks) = do
|
getrest p h sz bytesprocessed (k:ks) = do
|
||||||
let p' = offsetMeterUpdate p bytesprocessed
|
let p' = offsetMeterUpdate p bytesprocessed
|
||||||
sink h p' =<< retriever (encryptor k)
|
content <- retriever (encryptor k)
|
||||||
|
withBytes content $ sink h p'
|
||||||
getrest p h sz (addBytesProcessed bytesprocessed sz) ks
|
getrest p h sz (addBytesProcessed bytesprocessed sz) ks
|
||||||
|
|
||||||
getunchunked = liftIO $ bracket opennew hClose $ \h -> do
|
getunchunked = liftIO $ bracket opennew hClose $ \h -> do
|
||||||
retriever (encryptor basek) >>= sink h basep
|
content <- retriever (encryptor basek)
|
||||||
|
withBytes content $ sink h basep
|
||||||
return True
|
return True
|
||||||
|
|
||||||
opennew = openBinaryFile dest WriteMode
|
opennew = openBinaryFile dest WriteMode
|
||||||
|
|
|
@ -5,23 +5,28 @@
|
||||||
- Licensed under the GNU GPL version 3 or higher.
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
{-# LANGUAGE Rank2Types #-}
|
{-# LANGUAGE RankNTypes #-}
|
||||||
|
{-# LANGUAGE ImpredicativeTypes #-}
|
||||||
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
|
|
||||||
module Remote.Helper.ChunkedEncryptable (
|
module Remote.Helper.ChunkedEncryptable (
|
||||||
Preparer,
|
Preparer,
|
||||||
simplyPrepare,
|
|
||||||
checkPrepare,
|
|
||||||
Storer,
|
Storer,
|
||||||
Retriever,
|
Retriever,
|
||||||
|
simplyPrepare,
|
||||||
|
checkPrepare,
|
||||||
|
fileStorer,
|
||||||
|
byteStorer,
|
||||||
|
fileRetriever,
|
||||||
|
byteRetriever,
|
||||||
chunkedEncryptableRemote,
|
chunkedEncryptableRemote,
|
||||||
storeKeyDummy,
|
storeKeyDummy,
|
||||||
retreiveKeyFileDummy,
|
retreiveKeyFileDummy,
|
||||||
module X
|
module X
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import qualified Data.ByteString.Lazy as L
|
|
||||||
|
|
||||||
import Common.Annex
|
import Common.Annex
|
||||||
|
import Types.StoreRetrieve
|
||||||
import Types.Remote
|
import Types.Remote
|
||||||
import Crypto
|
import Crypto
|
||||||
import Config.Cost
|
import Config.Cost
|
||||||
|
@ -31,10 +36,6 @@ import Remote.Helper.Encryptable as X
|
||||||
import Annex.Content
|
import Annex.Content
|
||||||
import Annex.Exception
|
import Annex.Exception
|
||||||
|
|
||||||
-- Prepares for and then runs an action that will act on a Key,
|
|
||||||
-- passing it a helper when the preparation is successful.
|
|
||||||
type Preparer helper = forall a. Key -> (Maybe helper -> Annex a) -> Annex a
|
|
||||||
|
|
||||||
simplyPrepare :: helper -> Preparer helper
|
simplyPrepare :: helper -> Preparer helper
|
||||||
simplyPrepare helper _ a = a $ Just helper
|
simplyPrepare helper _ a = a $ Just helper
|
||||||
|
|
||||||
|
@ -44,14 +45,6 @@ checkPrepare checker helper k a = ifM (checker k)
|
||||||
, a Nothing
|
, a Nothing
|
||||||
)
|
)
|
||||||
|
|
||||||
-- Stores a Key, which may be encrypted and/or a chunk key.
|
|
||||||
-- May throw exceptions.
|
|
||||||
type Storer = Key -> L.ByteString -> MeterUpdate -> IO Bool
|
|
||||||
|
|
||||||
-- Retrieves a Key, which may be encrypted and/or a chunk key.
|
|
||||||
-- Throws exception if key is not present, or remote is not accessible.
|
|
||||||
type Retriever = Key -> IO L.ByteString
|
|
||||||
|
|
||||||
{- Modifies a base Remote to support both chunking and encryption.
|
{- Modifies a base Remote to support both chunking and encryption.
|
||||||
-}
|
-}
|
||||||
chunkedEncryptableRemote
|
chunkedEncryptableRemote
|
||||||
|
@ -88,16 +81,17 @@ chunkedEncryptableRemote c preparestorer prepareretriever baser = encr
|
||||||
go (Just storer) = sendAnnex k rollback $ \src ->
|
go (Just storer) = sendAnnex k rollback $ \src ->
|
||||||
metered (Just p) k $ \p' ->
|
metered (Just p) k $ \p' ->
|
||||||
storeChunks (uuid baser) chunkconfig k src p'
|
storeChunks (uuid baser) chunkconfig k src p'
|
||||||
(storechunk storer)
|
(storechunk enc storer)
|
||||||
(hasKey baser)
|
(hasKey baser)
|
||||||
go Nothing = return False
|
go Nothing = return False
|
||||||
rollback = void $ removeKey encr k
|
rollback = void $ removeKey encr k
|
||||||
storechunk storer k' b p' = case enc of
|
|
||||||
Nothing -> storer k' b p'
|
storechunk Nothing storer k content p = storer k content p
|
||||||
Just (cipher, enck) ->
|
storechunk (Just (cipher, enck)) storer k content p =
|
||||||
encrypt gpgopts cipher (feedBytes b) $
|
withBytes content $ \b ->
|
||||||
readBytes $ \encb ->
|
encrypt gpgopts cipher (feedBytes b) $
|
||||||
storer (enck k') encb p'
|
readBytes $ \encb ->
|
||||||
|
storer (enck k) (ByteContent encb) p
|
||||||
|
|
||||||
-- call retriever to get chunks; decrypt them; stream to dest file
|
-- call retriever to get chunks; decrypt them; stream to dest file
|
||||||
retrieveKeyFileGen k dest p enc =
|
retrieveKeyFileGen k dest p enc =
|
||||||
|
|
54
Types/StoreRetrieve.hs
Normal file
54
Types/StoreRetrieve.hs
Normal file
|
@ -0,0 +1,54 @@
|
||||||
|
{- Types for Storer and Retriever
|
||||||
|
-
|
||||||
|
- Copyright 2014 Joey Hess <joey@kitenet.net>
|
||||||
|
-
|
||||||
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
|
-}
|
||||||
|
|
||||||
|
{-# LANGUAGE Rank2Types #-}
|
||||||
|
|
||||||
|
module Types.StoreRetrieve where
|
||||||
|
|
||||||
|
import Common.Annex
|
||||||
|
import Utility.Metered
|
||||||
|
import Utility.Tmp
|
||||||
|
|
||||||
|
import qualified Data.ByteString.Lazy as L
|
||||||
|
|
||||||
|
-- Prepares for and then runs an action that will act on a Key's
|
||||||
|
-- content, passing it a helper when the preparation is successful.
|
||||||
|
type Preparer helper = forall a. Key -> (Maybe helper -> Annex a) -> Annex a
|
||||||
|
|
||||||
|
-- A source of a Key's content.
|
||||||
|
data ContentSource
|
||||||
|
= FileContent FilePath
|
||||||
|
| ByteContent L.ByteString
|
||||||
|
|
||||||
|
-- Action that stores a Key's content on a remote.
|
||||||
|
-- Can throw exceptions.
|
||||||
|
type Storer = Key -> ContentSource -> MeterUpdate -> IO Bool
|
||||||
|
|
||||||
|
-- Action that retrieves a Key's content from a remote.
|
||||||
|
-- Throws exception if key is not present, or remote is not accessible.
|
||||||
|
type Retriever = Key -> IO ContentSource
|
||||||
|
|
||||||
|
fileStorer :: (Key -> FilePath -> MeterUpdate -> IO Bool) -> Storer
|
||||||
|
fileStorer a k (FileContent f) m = a k f m
|
||||||
|
fileStorer a k (ByteContent b) m = do
|
||||||
|
withTmpFile "tmpXXXXXX" $ \f h -> do
|
||||||
|
L.hPut h b
|
||||||
|
hClose h
|
||||||
|
a k f m
|
||||||
|
|
||||||
|
byteStorer :: (Key -> L.ByteString -> MeterUpdate -> IO Bool) -> Storer
|
||||||
|
byteStorer a k c m = withBytes c $ \b -> a k b m
|
||||||
|
|
||||||
|
withBytes :: ContentSource -> (L.ByteString -> IO a) -> IO a
|
||||||
|
withBytes (ByteContent b) a = a b
|
||||||
|
withBytes (FileContent f) a = a =<< L.readFile f
|
||||||
|
|
||||||
|
fileRetriever :: (Key -> IO FilePath) -> Retriever
|
||||||
|
fileRetriever a k = FileContent <$> a k
|
||||||
|
|
||||||
|
byteRetriever :: (Key -> IO L.ByteString) -> Retriever
|
||||||
|
byteRetriever a k = ByteContent <$> a k
|
Loading…
Add table
Add a link
Reference in a new issue