Fix transferring files to special remotes in direct mode.
This commit is contained in:
parent
e457be7631
commit
909f67443f
10 changed files with 33 additions and 38 deletions
|
@ -309,7 +309,6 @@ withObjectLoc key indirect direct = ifM isDirect
|
|||
where
|
||||
goindirect = indirect =<< inRepo (gitAnnexLocation key)
|
||||
|
||||
|
||||
cleanObjectLoc :: Key -> Annex ()
|
||||
cleanObjectLoc key = do
|
||||
file <- inRepo $ gitAnnexLocation key
|
||||
|
|
|
@ -93,6 +93,9 @@ annexLocation key hasher = objectDir </> keyPath key hasher
|
|||
-
|
||||
- When the file is not present, returns the location where the file should
|
||||
- be stored.
|
||||
-
|
||||
- This does not take direct mode into account, so in direct mode it is not
|
||||
- the actual location of the file's content.
|
||||
-}
|
||||
gitAnnexLocation :: Key -> Git.Repo -> IO FilePath
|
||||
gitAnnexLocation key r
|
||||
|
|
|
@ -27,6 +27,7 @@ import Crypto
|
|||
import Data.ByteString.Lazy.UTF8 (fromString)
|
||||
import Data.Digest.Pure.SHA
|
||||
import Utility.UserInfo
|
||||
import Annex.Content
|
||||
|
||||
type BupRepo = String
|
||||
|
||||
|
@ -120,14 +121,12 @@ bupSplitParams r buprepo k src = do
|
|||
(os ++ [Param "-n", Param (bupRef k)] ++ src)
|
||||
|
||||
store :: Remote -> BupRepo -> Key -> AssociatedFile -> MeterUpdate -> Annex Bool
|
||||
store r buprepo k _f _p = do
|
||||
src <- inRepo $ gitAnnexLocation k
|
||||
store r buprepo k _f _p = sendAnnex k $ \src -> do
|
||||
params <- bupSplitParams r buprepo k [File src]
|
||||
liftIO $ boolSystem "bup" params
|
||||
|
||||
storeEncrypted :: Remote -> BupRepo -> (Cipher, Key) -> Key -> MeterUpdate -> Annex Bool
|
||||
storeEncrypted r buprepo (cipher, enck) k _p = do
|
||||
src <- inRepo $ gitAnnexLocation k
|
||||
storeEncrypted r buprepo (cipher, enck) k _p = sendAnnex k $ \src -> do
|
||||
params <- bupSplitParams r buprepo enck []
|
||||
liftIO $ catchBoolIO $
|
||||
encrypt cipher (feedFile src) $ \h ->
|
||||
|
|
|
@ -111,8 +111,7 @@ withStoredFiles :: ChunkSize -> FilePath -> Key -> ([FilePath] -> IO Bool) -> IO
|
|||
withStoredFiles = withCheckedFiles doesFileExist
|
||||
|
||||
store :: FilePath -> ChunkSize -> Key -> AssociatedFile -> MeterUpdate -> Annex Bool
|
||||
store d chunksize k _f p = do
|
||||
src <- inRepo $ gitAnnexLocation k
|
||||
store d chunksize k _f p = sendAnnex k $ \src ->
|
||||
metered (Just p) k $ \meterupdate ->
|
||||
storeHelper d chunksize k $ \dests ->
|
||||
case chunksize of
|
||||
|
@ -126,8 +125,7 @@ store d chunksize k _f p = do
|
|||
=<< L.readFile src
|
||||
|
||||
storeEncrypted :: FilePath -> ChunkSize -> (Cipher, Key) -> Key -> MeterUpdate -> Annex Bool
|
||||
storeEncrypted d chunksize (cipher, enck) k p = do
|
||||
src <- inRepo $ gitAnnexLocation k
|
||||
storeEncrypted d chunksize (cipher, enck) k p = sendAnnex k $ \src ->
|
||||
metered (Just p) k $ \meterupdate ->
|
||||
storeHelper d chunksize enck $ \dests ->
|
||||
encrypt cipher (feedFile src) $ readBytes $ \b ->
|
||||
|
|
|
@ -23,6 +23,7 @@ import Crypto
|
|||
import Creds
|
||||
import Meters
|
||||
import qualified Annex
|
||||
import Annex.Content
|
||||
|
||||
import System.Process
|
||||
|
||||
|
@ -84,17 +85,15 @@ store r k _f m
|
|||
| keySize k == Just 0 = do
|
||||
warning "Cannot store empty files in Glacier."
|
||||
return False
|
||||
| otherwise = do
|
||||
src <- inRepo $ gitAnnexLocation k
|
||||
| otherwise = sendAnnex k $ \src ->
|
||||
metered (Just m) k $ \meterupdate ->
|
||||
storeHelper r k $ streamMeteredFile src meterupdate
|
||||
|
||||
storeEncrypted :: Remote -> (Cipher, Key) -> Key -> MeterUpdate -> Annex Bool
|
||||
storeEncrypted r (cipher, enck) k m = do
|
||||
f <- inRepo $ gitAnnexLocation k
|
||||
storeEncrypted r (cipher, enck) k m = sendAnnex k $ \src -> do
|
||||
metered (Just m) k $ \meterupdate ->
|
||||
storeHelper r enck $ \h ->
|
||||
encrypt cipher (feedFile f)
|
||||
encrypt cipher (feedFile src)
|
||||
(readBytes $ meteredWrite meterupdate h)
|
||||
|
||||
retrieve :: Remote -> Key -> AssociatedFile -> FilePath -> Annex Bool
|
||||
|
|
|
@ -103,16 +103,15 @@ runHook hooktype hook k f a = maybe (return False) run =<< lookupHook hooktype h
|
|||
)
|
||||
|
||||
store :: String -> Key -> AssociatedFile -> MeterUpdate -> Annex Bool
|
||||
store h k _f _p = do
|
||||
src <- inRepo $ gitAnnexLocation k
|
||||
store h k _f _p = sendAnnex k $ \src ->
|
||||
runHook h "store" k (Just src) $ return True
|
||||
|
||||
storeEncrypted :: String -> (Cipher, Key) -> Key -> MeterUpdate -> Annex Bool
|
||||
storeEncrypted h (cipher, enck) k _p = withTmp enck $ \tmp -> do
|
||||
src <- inRepo $ gitAnnexLocation k
|
||||
liftIO $ encrypt cipher (feedFile src) $
|
||||
readBytes $ L.writeFile tmp
|
||||
runHook h "store" enck (Just tmp) $ return True
|
||||
storeEncrypted h (cipher, enck) k _p = withTmp enck $ \tmp ->
|
||||
sendAnnex k $ \src -> do
|
||||
liftIO $ encrypt cipher (feedFile src) $
|
||||
readBytes $ L.writeFile tmp
|
||||
runHook h "store" enck (Just tmp) $ return True
|
||||
|
||||
retrieve :: String -> Key -> AssociatedFile -> FilePath -> Annex Bool
|
||||
retrieve h k _f d = runHook h "retrieve" k (Just d) $ return True
|
||||
|
|
|
@ -101,14 +101,14 @@ rsyncUrls o k = map use annexHashes
|
|||
f = keyFile k
|
||||
|
||||
store :: RsyncOpts -> Key -> AssociatedFile -> MeterUpdate -> Annex Bool
|
||||
store o k _f p = rsyncSend o p k <=< inRepo $ gitAnnexLocation k
|
||||
store o k _f p = sendAnnex k $ rsyncSend o p k
|
||||
|
||||
storeEncrypted :: RsyncOpts -> (Cipher, Key) -> Key -> MeterUpdate -> Annex Bool
|
||||
storeEncrypted o (cipher, enck) k p = withTmp enck $ \tmp -> do
|
||||
src <- inRepo $ gitAnnexLocation k
|
||||
liftIO $ encrypt cipher (feedFile src) $
|
||||
readBytes $ L.writeFile tmp
|
||||
rsyncSend o p enck tmp
|
||||
storeEncrypted o (cipher, enck) k p = withTmp enck $ \tmp ->
|
||||
sendAnnex k $ \src -> do
|
||||
liftIO $ encrypt cipher (feedFile src) $
|
||||
readBytes $ L.writeFile tmp
|
||||
rsyncSend o p enck tmp
|
||||
|
||||
retrieve :: RsyncOpts -> Key -> AssociatedFile -> FilePath -> Annex Bool
|
||||
retrieve o k _ f = untilTrue (rsyncUrls o k) $ \u -> rsyncRemote o Nothing
|
||||
|
|
|
@ -112,8 +112,7 @@ s3Setup u c = handlehost $ M.lookup "host" c
|
|||
M.delete "bucket" defaults
|
||||
|
||||
store :: Remote -> Key -> AssociatedFile -> MeterUpdate -> Annex Bool
|
||||
store r k _f p = s3Action r False $ \(conn, bucket) -> do
|
||||
src <- inRepo $ gitAnnexLocation k
|
||||
store r k _f p = s3Action r False $ \(conn, bucket) -> sendAnnex k $ \src -> do
|
||||
res <- storeHelper (conn, bucket) r k p src
|
||||
s3Bool res
|
||||
|
||||
|
@ -121,9 +120,8 @@ storeEncrypted :: Remote -> (Cipher, Key) -> Key -> MeterUpdate -> Annex Bool
|
|||
storeEncrypted r (cipher, enck) k p = s3Action r False $ \(conn, bucket) ->
|
||||
-- To get file size of the encrypted content, have to use a temp file.
|
||||
-- (An alternative would be chunking to to a constant size.)
|
||||
withTmp enck $ \tmp -> do
|
||||
f <- inRepo $ gitAnnexLocation k
|
||||
liftIO $ encrypt cipher (feedFile f) $
|
||||
withTmp enck $ \tmp -> sendAnnex k $ \src -> do
|
||||
liftIO $ encrypt cipher (feedFile src) $
|
||||
readBytes $ L.writeFile tmp
|
||||
res <- storeHelper (conn, bucket) r enck p tmp
|
||||
s3Bool res
|
||||
|
|
|
@ -30,6 +30,7 @@ import Remote.Helper.Chunked
|
|||
import Crypto
|
||||
import Creds
|
||||
import Meters
|
||||
import Annex.Content
|
||||
|
||||
type DavUrl = String
|
||||
type DavUser = B8.ByteString
|
||||
|
@ -82,16 +83,14 @@ webdavSetup u c = do
|
|||
|
||||
store :: Remote -> Key -> AssociatedFile -> MeterUpdate -> Annex Bool
|
||||
store r k _f p = metered (Just p) k $ \meterupdate ->
|
||||
davAction r False $ \(baseurl, user, pass) -> do
|
||||
f <- inRepo $ gitAnnexLocation k
|
||||
liftIO $ withMeteredFile f meterupdate $
|
||||
davAction r False $ \(baseurl, user, pass) -> sendAnnex k $ \src ->
|
||||
liftIO $ withMeteredFile src meterupdate $
|
||||
storeHelper r k baseurl user pass
|
||||
|
||||
storeEncrypted :: Remote -> (Cipher, Key) -> Key -> MeterUpdate -> Annex Bool
|
||||
storeEncrypted r (cipher, enck) k p = metered (Just p) k $ \meterupdate ->
|
||||
davAction r False $ \(baseurl, user, pass) -> do
|
||||
f <- inRepo $ gitAnnexLocation k
|
||||
liftIO $ encrypt cipher (streamMeteredFile f meterupdate) $
|
||||
davAction r False $ \(baseurl, user, pass) -> sendAnnex k $ \src ->
|
||||
liftIO $ encrypt cipher (streamMeteredFile src meterupdate) $
|
||||
readBytes $ storeHelper r enck baseurl user pass
|
||||
|
||||
storeHelper :: Remote -> Key -> DavUrl -> DavUser -> DavPass -> L.ByteString -> IO Bool
|
||||
|
|
1
debian/changelog
vendored
1
debian/changelog
vendored
|
@ -9,6 +9,7 @@ git-annex (3.20130105) UNRELEASED; urgency=low
|
|||
and set environment to prevent git from failing.
|
||||
* direct: Avoid hardlinking symlinks that point to the same content
|
||||
when the content is not present.
|
||||
* Fix transferring files to special remotes in direct mode.
|
||||
|
||||
-- Joey Hess <joeyh@debian.org> Thu, 03 Jan 2013 14:58:45 -0400
|
||||
|
||||
|
|
Loading…
Reference in a new issue