add tmp flag parameter to retrieveKeyFile
This commit is contained in:
parent
94aa6b42b5
commit
06b0cb6224
12 changed files with 29 additions and 27 deletions
|
@ -65,7 +65,7 @@ performRemote key file backend numcopies remote = withTmp key $ \tmpfile -> do
|
||||||
showNote err
|
showNote err
|
||||||
stop
|
stop
|
||||||
Right True -> do
|
Right True -> do
|
||||||
copied <- Remote.retrieveKeyFile remote key tmpfile
|
copied <- Remote.retrieveKeyFile remote key True tmpfile
|
||||||
if copied then go True (Just tmpfile) else go False Nothing
|
if copied then go True (Just tmpfile) else go False Nothing
|
||||||
Right False -> go False Nothing
|
Right False -> go False Nothing
|
||||||
where
|
where
|
||||||
|
|
|
@ -72,7 +72,7 @@ getKeyFile key file = do
|
||||||
else return True
|
else return True
|
||||||
docopy r continue = do
|
docopy r continue = do
|
||||||
showAction $ "from " ++ Remote.name r
|
showAction $ "from " ++ Remote.name r
|
||||||
copied <- Remote.retrieveKeyFile r key file
|
copied <- Remote.retrieveKeyFile r key False file
|
||||||
if copied
|
if copied
|
||||||
then return True
|
then return True
|
||||||
else continue
|
else continue
|
||||||
|
|
|
@ -131,7 +131,7 @@ fromPerform src move key = moveLock move key $ do
|
||||||
then handle move True
|
then handle move True
|
||||||
else do
|
else do
|
||||||
showAction $ "from " ++ Remote.name src
|
showAction $ "from " ++ Remote.name src
|
||||||
ok <- getViaTmp key $ Remote.retrieveKeyFile src key
|
ok <- getViaTmp key $ Remote.retrieveKeyFile src key False
|
||||||
handle move ok
|
handle move ok
|
||||||
where
|
where
|
||||||
handle _ False = stop -- failed
|
handle _ False = stop -- failed
|
||||||
|
|
|
@ -118,8 +118,8 @@ storeEncrypted r buprepo (cipher, enck) k = do
|
||||||
withEncryptedHandle cipher (L.readFile src) $ \h ->
|
withEncryptedHandle cipher (L.readFile src) $ \h ->
|
||||||
pipeBup params (Just h) Nothing
|
pipeBup params (Just h) Nothing
|
||||||
|
|
||||||
retrieve :: BupRepo -> Key -> FilePath -> Annex Bool
|
retrieve :: BupRepo -> Key -> Bool -> FilePath -> Annex Bool
|
||||||
retrieve buprepo k f = do
|
retrieve buprepo k _ f = do
|
||||||
let params = bupParams "join" buprepo [Param $ show k]
|
let params = bupParams "join" buprepo [Param $ show k]
|
||||||
liftIO $ catchBoolIO $ do
|
liftIO $ catchBoolIO $ do
|
||||||
tofile <- openFile f WriteMode
|
tofile <- openFile f WriteMode
|
||||||
|
|
|
@ -109,8 +109,9 @@ storeHelper d key a = do
|
||||||
preventWrite dir
|
preventWrite dir
|
||||||
return ok
|
return ok
|
||||||
|
|
||||||
retrieve :: FilePath -> Key -> FilePath -> Annex Bool
|
retrieve :: FilePath -> Key -> Bool -> FilePath -> Annex Bool
|
||||||
retrieve d k f = liftIO $ withStoredFile d k $ \file -> copyFileExternal file f
|
retrieve d k _ f = do
|
||||||
|
liftIO $ withStoredFile d k $ \file -> copyFileExternal file f
|
||||||
|
|
||||||
retrieveEncrypted :: FilePath -> (Cipher, Key) -> FilePath -> Annex Bool
|
retrieveEncrypted :: FilePath -> (Cipher, Key) -> FilePath -> Annex Bool
|
||||||
retrieveEncrypted d (cipher, enck) f =
|
retrieveEncrypted d (cipher, enck) f =
|
||||||
|
|
|
@ -198,8 +198,8 @@ dropKey r key
|
||||||
]
|
]
|
||||||
|
|
||||||
{- Tries to copy a key's content from a remote's annex to a file. -}
|
{- Tries to copy a key's content from a remote's annex to a file. -}
|
||||||
copyFromRemote :: Git.Repo -> Key -> FilePath -> Annex Bool
|
copyFromRemote :: Git.Repo -> Key -> Bool -> FilePath -> Annex Bool
|
||||||
copyFromRemote r key file
|
copyFromRemote r key _ file
|
||||||
| not $ Git.repoIsUrl r = do
|
| not $ Git.repoIsUrl r = do
|
||||||
params <- rsyncParams r
|
params <- rsyncParams r
|
||||||
loc <- liftIO $ gitAnnexLocation key r
|
loc <- liftIO $ gitAnnexLocation key r
|
||||||
|
|
|
@ -55,8 +55,8 @@ encryptableRemote c storeKeyEncrypted retrieveKeyFileEncrypted r =
|
||||||
store k = cip k >>= maybe
|
store k = cip k >>= maybe
|
||||||
(storeKey r k)
|
(storeKey r k)
|
||||||
(`storeKeyEncrypted` k)
|
(`storeKeyEncrypted` k)
|
||||||
retrieve k f = cip k >>= maybe
|
retrieve k t f = cip k >>= maybe
|
||||||
(retrieveKeyFile r k f)
|
(retrieveKeyFile r k t f)
|
||||||
(`retrieveKeyFileEncrypted` f)
|
(`retrieveKeyFileEncrypted` f)
|
||||||
withkey a k = cip k >>= maybe (a k) (a . snd)
|
withkey a k = cip k >>= maybe (a k) (a . snd)
|
||||||
cip = cipherKey c
|
cip = cipherKey c
|
||||||
|
|
|
@ -106,8 +106,8 @@ storeEncrypted h (cipher, enck) k = withTmp enck $ \tmp -> do
|
||||||
liftIO $ withEncryptedContent cipher (L.readFile src) $ L.writeFile tmp
|
liftIO $ withEncryptedContent cipher (L.readFile src) $ L.writeFile tmp
|
||||||
runHook h "store" enck (Just tmp) $ return True
|
runHook h "store" enck (Just tmp) $ return True
|
||||||
|
|
||||||
retrieve :: String -> Key -> FilePath -> Annex Bool
|
retrieve :: String -> Key -> Bool -> FilePath -> Annex Bool
|
||||||
retrieve h k f = runHook h "retrieve" k (Just f) $ return True
|
retrieve h k _ f = runHook h "retrieve" k (Just f) $ return True
|
||||||
|
|
||||||
retrieveEncrypted :: String -> (Cipher, Key) -> FilePath -> Annex Bool
|
retrieveEncrypted :: String -> (Cipher, Key) -> FilePath -> Annex Bool
|
||||||
retrieveEncrypted h (cipher, enck) f = withTmp enck $ \tmp ->
|
retrieveEncrypted h (cipher, enck) f = withTmp enck $ \tmp ->
|
||||||
|
|
|
@ -104,9 +104,9 @@ storeEncrypted o (cipher, enck) k = withTmp enck $ \tmp -> do
|
||||||
liftIO $ withEncryptedContent cipher (L.readFile src) $ L.writeFile tmp
|
liftIO $ withEncryptedContent cipher (L.readFile src) $ L.writeFile tmp
|
||||||
rsyncSend o enck tmp
|
rsyncSend o enck tmp
|
||||||
|
|
||||||
retrieve :: RsyncOpts -> Key -> FilePath -> Annex Bool
|
retrieve :: RsyncOpts -> Key -> Bool -> FilePath -> Annex Bool
|
||||||
retrieve o k f = untilTrue (rsyncUrls o k) $ \u -> do
|
retrieve o k tmp f = untilTrue (rsyncUrls o k) $ \u -> do
|
||||||
unlessM (liftIO $ doesFileExist f) $ whenM (inAnnex k) $ preseed
|
when tmp $ preseed
|
||||||
rsyncRemote o
|
rsyncRemote o
|
||||||
-- use inplace when retrieving to support resuming
|
-- use inplace when retrieving to support resuming
|
||||||
[ Param "--inplace"
|
[ Param "--inplace"
|
||||||
|
@ -115,14 +115,15 @@ retrieve o k f = untilTrue (rsyncUrls o k) $ \u -> do
|
||||||
]
|
]
|
||||||
where
|
where
|
||||||
-- this speeds up fsck --from
|
-- this speeds up fsck --from
|
||||||
preseed = do
|
preseed = unlessM (liftIO $ doesFileExist f) $
|
||||||
|
whenM (inAnnex k) $ do
|
||||||
s <- inRepo $ gitAnnexLocation k
|
s <- inRepo $ gitAnnexLocation k
|
||||||
liftIO $ whenM (copyFileExternal s f) $
|
liftIO $ whenM (copyFileExternal s f) $
|
||||||
allowWrite f
|
allowWrite f
|
||||||
|
|
||||||
retrieveEncrypted :: RsyncOpts -> (Cipher, Key) -> FilePath -> Annex Bool
|
retrieveEncrypted :: RsyncOpts -> (Cipher, Key) -> FilePath -> Annex Bool
|
||||||
retrieveEncrypted o (cipher, enck) f = withTmp enck $ \tmp -> do
|
retrieveEncrypted o (cipher, enck) f = withTmp enck $ \tmp -> do
|
||||||
res <- retrieve o enck tmp
|
res <- retrieve o enck False tmp
|
||||||
if res
|
if res
|
||||||
then liftIO $ catchBoolIO $ do
|
then liftIO $ catchBoolIO $ do
|
||||||
withDecryptedContent cipher (L.readFile tmp) $ L.writeFile f
|
withDecryptedContent cipher (L.readFile tmp) $ L.writeFile f
|
||||||
|
|
|
@ -149,8 +149,8 @@ storeHelper (conn, bucket) r k file = do
|
||||||
xheaders = filter isxheader $ M.assocs $ fromJust $ config r
|
xheaders = filter isxheader $ M.assocs $ fromJust $ config r
|
||||||
isxheader (h, _) = "x-amz-" `isPrefixOf` h
|
isxheader (h, _) = "x-amz-" `isPrefixOf` h
|
||||||
|
|
||||||
retrieve :: Remote -> Key -> FilePath -> Annex Bool
|
retrieve :: Remote -> Key -> Bool -> FilePath -> Annex Bool
|
||||||
retrieve r k f = s3Action r False $ \(conn, bucket) -> do
|
retrieve r k _ f = s3Action r False $ \(conn, bucket) -> do
|
||||||
res <- liftIO $ getObject conn $ bucketKey r bucket k
|
res <- liftIO $ getObject conn $ bucketKey r bucket k
|
||||||
case res of
|
case res of
|
||||||
Right o -> do
|
Right o -> do
|
||||||
|
|
|
@ -48,8 +48,8 @@ gen r _ _ =
|
||||||
remotetype = remote
|
remotetype = remote
|
||||||
}
|
}
|
||||||
|
|
||||||
downloadKey :: Key -> FilePath -> Annex Bool
|
downloadKey :: Key -> Bool -> FilePath -> Annex Bool
|
||||||
downloadKey key file = get =<< getUrls key
|
downloadKey key _ file = get =<< getUrls key
|
||||||
where
|
where
|
||||||
get [] = do
|
get [] = do
|
||||||
warning "no known url"
|
warning "no known url"
|
||||||
|
|
|
@ -43,8 +43,8 @@ data RemoteA a = Remote {
|
||||||
cost :: Int,
|
cost :: Int,
|
||||||
-- Transfers a key to the remote.
|
-- Transfers a key to the remote.
|
||||||
storeKey :: Key -> a Bool,
|
storeKey :: Key -> a Bool,
|
||||||
-- retrieves a key's contents to a file
|
-- retrieves a key's contents to a file (possibly a tmp file)
|
||||||
retrieveKeyFile :: Key -> FilePath -> a Bool,
|
retrieveKeyFile :: Key -> Bool -> FilePath -> a Bool,
|
||||||
-- removes a key's contents
|
-- removes a key's contents
|
||||||
removeKey :: Key -> a Bool,
|
removeKey :: Key -> a Bool,
|
||||||
-- Checks if a key is present in the remote; if the remote
|
-- Checks if a key is present in the remote; if the remote
|
||||||
|
|
Loading…
Reference in a new issue