convert glacier to new ChunkedEncryptable API (but do not support chunking)

Chunking would complicate the assistant's code that checks when a pending
retrieval of a key from glacier is done. It would perhaps be nice to
support it to allow resuming, but not right now.

Converting to the new API still simplifies the code.
This commit is contained in:
Joey Hess 2014-08-02 16:47:21 -04:00
parent 32e4368377
commit 0eb1f057c4
2 changed files with 50 additions and 54 deletions

View file

@ -9,6 +9,7 @@ module Remote.Glacier (remote, jobList) where
import qualified Data.Map as M import qualified Data.Map as M
import qualified Data.Text as T import qualified Data.Text as T
import qualified Data.ByteString.Lazy as L
import Common.Annex import Common.Annex
import Types.Remote import Types.Remote
@ -17,13 +18,12 @@ import qualified Git
import Config import Config
import Config.Cost import Config.Cost
import Remote.Helper.Special import Remote.Helper.Special
import Remote.Helper.Encryptable import Remote.Helper.ChunkedEncryptable
import qualified Remote.Helper.AWS as AWS import qualified Remote.Helper.AWS as AWS
import Crypto import Crypto
import Creds import Creds
import Utility.Metered import Utility.Metered
import qualified Annex import qualified Annex
import Annex.Content
import Annex.UUID import Annex.UUID
import Utility.Env import Utility.Env
@ -42,16 +42,16 @@ gen :: Git.Repo -> UUID -> RemoteConfig -> RemoteGitConfig -> Annex (Maybe Remot
gen r u c gc = new <$> remoteCost gc veryExpensiveRemoteCost gen r u c gc = new <$> remoteCost gc veryExpensiveRemoteCost
where where
new cst = Just $ encryptableRemote c new cst = Just $ encryptableRemote c
(storeEncrypted this) (prepareStore this)
(retrieveEncrypted this) (prepareRetrieve this)
this this
where where
this = Remote { this = Remote {
uuid = u, uuid = u,
cost = cst, cost = cst,
name = Git.repoDescribe r, name = Git.repoDescribe r,
storeKey = store this, storeKey = storeKeyDummy,
retrieveKeyFile = retrieve this, retrieveKeyFile = retreiveKeyFileDummy,
retrieveKeyFileCheap = retrieveCheap this, retrieveKeyFileCheap = retrieveCheap this,
removeKey = remove this, removeKey = remove this,
hasKey = checkPresent this, hasKey = checkPresent this,
@ -89,38 +89,18 @@ glacierSetup' enabling u c = do
, ("vault", defvault) , ("vault", defvault)
] ]
store :: Remote -> Key -> AssociatedFile -> MeterUpdate -> Annex Bool prepareStore :: Remote -> Preparer Storer
store r k _f p prepareStore r = checkPrepare nonEmpty (byteStorer $ store r)
nonEmpty :: Key -> Annex Bool
nonEmpty k
| keySize k == Just 0 = do | keySize k == Just 0 = do
warning "Cannot store empty files in Glacier." warning "Cannot store empty files in Glacier."
return False return False
| otherwise = sendAnnex k (void $ remove r k) $ \src -> | otherwise = return True
metered (Just p) k $ \meterupdate ->
storeHelper r k $ streamMeteredFile src meterupdate
storeEncrypted :: Remote -> (Cipher, Key) -> Key -> MeterUpdate -> Annex Bool store :: Remote -> Key -> L.ByteString -> MeterUpdate -> Annex Bool
storeEncrypted r (cipher, enck) k p = sendAnnex k (void $ remove r enck) $ \src -> store r k b p = go =<< glacierEnv c u
metered (Just p) k $ \meterupdate ->
storeHelper r enck $ \h ->
encrypt (getGpgEncParams r) cipher (feedFile src)
(readBytes $ meteredWrite meterupdate h)
retrieve :: Remote -> Key -> AssociatedFile -> FilePath -> MeterUpdate -> Annex Bool
retrieve r k _f d p = metered (Just p) k $ \meterupdate ->
retrieveHelper r k $
readBytes $ meteredWriteFile meterupdate d
retrieveCheap :: Remote -> Key -> FilePath -> Annex Bool
retrieveCheap _ _ _ = return False
retrieveEncrypted :: Remote -> (Cipher, Key) -> Key -> FilePath -> MeterUpdate -> Annex Bool
retrieveEncrypted r (cipher, enck) k d p = metered (Just p) k $ \meterupdate ->
retrieveHelper r enck $ readBytes $ \b ->
decrypt cipher (feedBytes b) $
readBytes $ meteredWriteFile meterupdate d
storeHelper :: Remote -> Key -> (Handle -> IO ()) -> Annex Bool
storeHelper r k feeder = go =<< glacierEnv c u
where where
c = config r c = config r
u = uuid r u = uuid r
@ -133,14 +113,18 @@ storeHelper r k feeder = go =<< glacierEnv c u
] ]
go Nothing = return False go Nothing = return False
go (Just e) = do go (Just e) = do
let p = (proc "glacier" (toCommand params)) { env = Just e } let cmd = (proc "glacier" (toCommand params)) { env = Just e }
liftIO $ catchBoolIO $ liftIO $ catchBoolIO $
withHandle StdinHandle createProcessSuccess p $ \h -> do withHandle StdinHandle createProcessSuccess cmd $ \h -> do
feeder h meteredWrite p h b
return True return True
retrieveHelper :: Remote -> Key -> (Handle -> IO ()) -> Annex Bool prepareRetrieve :: Remote -> Preparer Retriever
retrieveHelper r k reader = go =<< glacierEnv c u prepareRetrieve r = simplyPrepare $ fileRetriever $ \d k p ->
retrieve r k (readBytes (meteredWriteFile p d))
retrieve :: Remote -> Key -> (Handle -> IO ()) -> Annex ()
retrieve r k reader = go =<< glacierEnv c u
where where
c = config r c = config r
u = uuid r u = uuid r
@ -151,29 +135,33 @@ retrieveHelper r k reader = go =<< glacierEnv c u
, Param $ getVault $ config r , Param $ getVault $ config r
, Param $ archive r k , Param $ archive r k
] ]
go Nothing = return False go Nothing = error "cannot retrieve from glacier"
go (Just e) = do go (Just e) = do
let p = (proc "glacier" (toCommand params)) { env = Just e } let cmd = (proc "glacier" (toCommand params)) { env = Just e }
ok <- liftIO $ catchBoolIO $ ok <- liftIO $ catchBoolIO $
withHandle StdoutHandle createProcessSuccess p $ \h -> withHandle StdoutHandle createProcessSuccess cmd $ \h ->
ifM (hIsEOF h) ifM (hIsEOF h)
( return False ( return False
, do , do
reader h reader h
return True return True
) )
unless ok later unless ok $ do
return ok showLongNote "Recommend you wait up to 4 hours, and then run this command again."
later = showLongNote "Recommend you wait up to 4 hours, and then run this command again." error "not yet available"
remove :: Remote -> Key -> Annex Bool remove :: Remote -> Key -> Annex Bool
remove r k = glacierAction r remove r k = glacierAction r
[ Param "archive" [ Param "archive"
, Param "delete" , Param "delete"
, Param $ getVault $ config r , Param $ getVault $ config r
, Param $ archive r k , Param $ archive r k
] ]
retrieveCheap :: Remote -> Key -> FilePath -> Annex Bool
retrieveCheap _ _ _ = return False
checkPresent :: Remote -> Key -> Annex (Either String Bool) checkPresent :: Remote -> Key -> Annex (Either String Bool)
checkPresent r k = do checkPresent r k = do
showAction $ "checking " ++ name r showAction $ "checking " ++ name r
@ -261,6 +249,10 @@ genVault c u = unlessM (runGlacier c u params) $
- -
- A complication is that `glacier job list` will display the encrypted - A complication is that `glacier job list` will display the encrypted
- keys when the remote is encrypted. - keys when the remote is encrypted.
-
- Dealing with encrypted chunked keys would be tricky. However, there
- seems to be no benefit to using chunking with glacier, so chunking is
- not supported.
-} -}
jobList :: Remote -> [Key] -> Annex ([Key], [Key]) jobList :: Remote -> [Key] -> Annex ([Key], [Key])
jobList r keys = go =<< glacierEnv (config r) (uuid r) jobList r keys = go =<< glacierEnv (config r) (uuid r)

View file

@ -22,6 +22,7 @@ module Remote.Helper.ChunkedEncryptable (
storeKeyDummy, storeKeyDummy,
retreiveKeyFileDummy, retreiveKeyFileDummy,
chunkedEncryptableRemote, chunkedEncryptableRemote,
encryptableRemote,
module X module X
) where ) where
@ -32,7 +33,7 @@ import Crypto
import Config.Cost import Config.Cost
import Utility.Metered import Utility.Metered
import Remote.Helper.Chunked as X import Remote.Helper.Chunked as X
import Remote.Helper.Encryptable as X import Remote.Helper.Encryptable as X hiding (encryptableRemote)
import Annex.Content import Annex.Content
import Annex.Exception import Annex.Exception
@ -90,14 +91,18 @@ storeKeyDummy _ _ _ = return False
retreiveKeyFileDummy :: Key -> AssociatedFile -> FilePath -> MeterUpdate -> Annex Bool retreiveKeyFileDummy :: Key -> AssociatedFile -> FilePath -> MeterUpdate -> Annex Bool
retreiveKeyFileDummy _ _ _ _ = return False retreiveKeyFileDummy _ _ _ _ = return False
type RemoteModifier = RemoteConfig -> Preparer Storer -> Preparer Retriever -> Remote -> Remote
-- Modifies a base Remote to support both chunking and encryption. -- Modifies a base Remote to support both chunking and encryption.
chunkedEncryptableRemote chunkedEncryptableRemote :: RemoteModifier
:: RemoteConfig chunkedEncryptableRemote c = chunkedEncryptableRemote' (chunkConfig c) c
-> Preparer Storer
-> Preparer Retriever -- Modifies a base Remote to support encryption, but not chunking.
-> Remote encryptableRemote :: RemoteModifier
-> Remote encryptableRemote = chunkedEncryptableRemote' NoChunks
chunkedEncryptableRemote c preparestorer prepareretriever baser = encr
chunkedEncryptableRemote' :: ChunkConfig -> RemoteModifier
chunkedEncryptableRemote' chunkconfig c preparestorer prepareretriever baser = encr
where where
encr = baser encr = baser
{ storeKey = \k _f p -> cip >>= storeKeyGen k p { storeKey = \k _f p -> cip >>= storeKeyGen k p
@ -113,7 +118,6 @@ chunkedEncryptableRemote c preparestorer prepareretriever baser = encr
(extractCipher c) (extractCipher c)
} }
cip = cipherKey c cip = cipherKey c
chunkconfig = chunkConfig c
gpgopts = getGpgEncParams encr gpgopts = getGpgEncParams encr
safely a = catchNonAsyncAnnex a (\e -> warning (show e) >> return False) safely a = catchNonAsyncAnnex a (\e -> warning (show e) >> return False)