2014-03-22 14:42:38 +00:00
|
|
|
{- git-annex transfers
|
|
|
|
-
|
2015-01-21 16:50:09 +00:00
|
|
|
- Copyright 2012-2014 Joey Hess <id@joeyh.name>
|
2014-03-22 14:42:38 +00:00
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
|
|
|
{-# LANGUAGE CPP #-}
|
|
|
|
|
|
|
|
module Annex.Transfer (
|
|
|
|
module X,
|
2015-05-12 19:50:03 +00:00
|
|
|
noObserver,
|
2014-03-22 14:42:38 +00:00
|
|
|
upload,
|
|
|
|
download,
|
|
|
|
runTransfer,
|
2014-08-15 18:17:05 +00:00
|
|
|
alwaysRunTransfer,
|
2014-03-22 14:42:38 +00:00
|
|
|
noRetry,
|
|
|
|
forwardRetry,
|
|
|
|
) where
|
|
|
|
|
2014-03-22 19:01:48 +00:00
|
|
|
import Common.Annex
|
2014-03-22 14:42:38 +00:00
|
|
|
import Logs.Transfer as X
|
2014-03-22 19:01:48 +00:00
|
|
|
import Annex.Notification as X
|
2014-03-22 14:42:38 +00:00
|
|
|
import Annex.Perms
|
|
|
|
import Utility.Metered
|
2014-08-23 23:27:24 +00:00
|
|
|
import Utility.LockFile
|
2014-03-22 14:42:38 +00:00
|
|
|
|
|
|
|
import Control.Concurrent
|
|
|
|
|
2015-05-12 19:50:03 +00:00
|
|
|
type TransferAction = MeterUpdate -> Annex Bool
|
2014-03-22 14:42:38 +00:00
|
|
|
|
2015-05-12 19:50:03 +00:00
|
|
|
type TransferObserver = Bool -> Transfer -> TransferInfo -> Annex ()
|
|
|
|
|
|
|
|
noObserver :: TransferObserver
|
|
|
|
noObserver _ _ _ = noop
|
|
|
|
|
|
|
|
upload :: UUID -> Key -> AssociatedFile -> RetryDecider -> TransferObserver -> TransferAction -> NotifyWitness -> Annex Bool
|
|
|
|
upload u key f d o a _witness = runTransfer (Transfer Upload u key) f d o a
|
|
|
|
|
|
|
|
download :: UUID -> Key -> AssociatedFile -> RetryDecider -> TransferObserver -> TransferAction -> NotifyWitness -> Annex Bool
|
|
|
|
download u key f d o a _witness = runTransfer (Transfer Download u key) f d o a
|
2014-03-22 14:42:38 +00:00
|
|
|
|
|
|
|
{- Runs a transfer action. Creates and locks the lock file while the
|
|
|
|
- action is running, and stores info in the transfer information
|
|
|
|
- file.
|
|
|
|
-
|
|
|
|
- If the transfer action returns False, the transfer info is
|
|
|
|
- left in the failedTransferDir.
|
|
|
|
-
|
|
|
|
- If the transfer is already in progress, returns False.
|
|
|
|
-
|
|
|
|
- An upload can be run from a read-only filesystem, and in this case
|
|
|
|
- no transfer information or lock file is used.
|
|
|
|
-}
|
2015-05-12 19:50:03 +00:00
|
|
|
runTransfer :: Transfer -> Maybe FilePath -> RetryDecider -> TransferObserver -> TransferAction -> Annex Bool
|
2014-08-15 18:17:05 +00:00
|
|
|
runTransfer = runTransfer' False
|
|
|
|
|
|
|
|
{- Like runTransfer, but ignores any existing transfer lock file for the
|
|
|
|
- transfer, allowing re-running a transfer that is already in progress.
|
|
|
|
-
|
|
|
|
- Note that this may result in confusing progress meter display in the
|
|
|
|
- webapp, if multiple processes are writing to the transfer info file. -}
|
2015-05-12 19:50:03 +00:00
|
|
|
alwaysRunTransfer :: Transfer -> Maybe FilePath -> RetryDecider -> TransferObserver -> TransferAction -> Annex Bool
|
2014-08-15 18:17:05 +00:00
|
|
|
alwaysRunTransfer = runTransfer' True
|
|
|
|
|
2015-05-12 19:50:03 +00:00
|
|
|
runTransfer' :: Bool -> Transfer -> Maybe FilePath -> RetryDecider -> TransferObserver -> TransferAction -> Annex Bool
|
|
|
|
runTransfer' ignorelock t file shouldretry transferobserver transferaction = do
|
2014-03-22 14:42:38 +00:00
|
|
|
info <- liftIO $ startTransferInfo file
|
|
|
|
(meter, tfile, metervar) <- mkProgressUpdater t info
|
|
|
|
mode <- annexFileMode
|
2015-05-12 23:36:16 +00:00
|
|
|
(lck, inprogress) <- liftIO $ prep tfile mode info
|
2014-08-15 18:17:05 +00:00
|
|
|
if inprogress && not ignorelock
|
2014-03-22 14:42:38 +00:00
|
|
|
then do
|
|
|
|
showNote "transfer already in progress"
|
|
|
|
return False
|
|
|
|
else do
|
2015-05-12 19:50:03 +00:00
|
|
|
ok <- retry info metervar $ bracketIO
|
2015-05-12 23:36:16 +00:00
|
|
|
(return lck)
|
2015-05-12 19:50:03 +00:00
|
|
|
(cleanup tfile)
|
|
|
|
(const $ transferaction meter)
|
|
|
|
transferobserver ok t info
|
2014-03-22 14:42:38 +00:00
|
|
|
return ok
|
|
|
|
where
|
|
|
|
#ifndef mingw32_HOST_OS
|
|
|
|
prep tfile mode info = do
|
2015-05-12 23:36:16 +00:00
|
|
|
let lck = transferLockFile tfile
|
|
|
|
r <- tryLockExclusive (Just mode) lck
|
|
|
|
case r of
|
|
|
|
Nothing -> return (Nothing, True)
|
|
|
|
Just lockhandle -> do
|
|
|
|
void $ tryIO $ writeTransferInfoFile info tfile
|
|
|
|
return (Just lockhandle, False)
|
2014-03-22 14:42:38 +00:00
|
|
|
#else
|
|
|
|
prep tfile _mode info = do
|
2015-05-12 23:36:16 +00:00
|
|
|
let lck = transferLockFile tfile
|
|
|
|
v <- catchMaybeIO $ lockExclusive lck
|
2014-03-22 14:42:38 +00:00
|
|
|
case v of
|
|
|
|
Nothing -> return (Nothing, False)
|
|
|
|
Just Nothing -> return (Nothing, True)
|
|
|
|
Just (Just lockhandle) -> do
|
|
|
|
void $ tryIO $ writeTransferInfoFile info tfile
|
|
|
|
return (Just lockhandle, False)
|
|
|
|
#endif
|
|
|
|
cleanup _ Nothing = noop
|
|
|
|
cleanup tfile (Just lockhandle) = do
|
2015-05-12 23:36:16 +00:00
|
|
|
let lck = transferLockFile tfile
|
2014-03-22 14:42:38 +00:00
|
|
|
void $ tryIO $ removeFile tfile
|
|
|
|
#ifndef mingw32_HOST_OS
|
2015-05-12 23:36:16 +00:00
|
|
|
void $ tryIO $ removeFile lck
|
|
|
|
dropLock lockhandle
|
2014-03-22 14:42:38 +00:00
|
|
|
#else
|
|
|
|
{- Windows cannot delete the lockfile until the lock
|
|
|
|
- is closed. So it's possible to race with another
|
|
|
|
- process that takes the lock before it's removed,
|
|
|
|
- so ignore failure to remove.
|
|
|
|
-}
|
|
|
|
dropLock lockhandle
|
2015-05-12 23:36:16 +00:00
|
|
|
void $ tryIO $ removeFile lck
|
2014-03-22 14:42:38 +00:00
|
|
|
#endif
|
|
|
|
retry oldinfo metervar run = do
|
unify exception handling into Utility.Exception
Removed old extensible-exceptions, only needed for very old ghc.
Made webdav use Utility.Exception, to work after some changes in DAV's
exception handling.
Removed Annex.Exception. Mostly this was trivial, but note that
tryAnnex is replaced with tryNonAsync and catchAnnex replaced with
catchNonAsync. In theory that could be a behavior change, since the former
caught all exceptions, and the latter don't catch async exceptions.
However, in practice, nothing in the Annex monad uses async exceptions.
Grepping for throwTo and killThread only find stuff in the assistant,
which does not seem related.
Command.Add.undo is changed to accept a SomeException, and things
that use it for rollback now catch non-async exceptions, rather than
only IOExceptions.
2014-08-08 01:55:44 +00:00
|
|
|
v <- tryNonAsync run
|
2014-03-22 14:42:38 +00:00
|
|
|
case v of
|
|
|
|
Right b -> return b
|
2014-07-30 19:57:19 +00:00
|
|
|
Left e -> do
|
|
|
|
warning (show e)
|
2014-03-22 14:42:38 +00:00
|
|
|
b <- getbytescomplete metervar
|
|
|
|
let newinfo = oldinfo { bytesComplete = Just b }
|
|
|
|
if shouldretry oldinfo newinfo
|
|
|
|
then retry newinfo metervar run
|
|
|
|
else return False
|
|
|
|
getbytescomplete metervar
|
|
|
|
| transferDirection t == Upload =
|
|
|
|
liftIO $ readMVar metervar
|
|
|
|
| otherwise = do
|
|
|
|
f <- fromRepo $ gitAnnexTmpObjectLocation (transferKey t)
|
2015-01-20 20:58:48 +00:00
|
|
|
liftIO $ catchDefaultIO 0 $ getFileSize f
|
2014-03-22 14:42:38 +00:00
|
|
|
|
|
|
|
type RetryDecider = TransferInfo -> TransferInfo -> Bool
|
|
|
|
|
|
|
|
noRetry :: RetryDecider
|
|
|
|
noRetry _ _ = False
|
|
|
|
|
|
|
|
{- Retries a transfer when it fails, as long as the failed transfer managed
|
|
|
|
- to send some data. -}
|
|
|
|
forwardRetry :: RetryDecider
|
|
|
|
forwardRetry old new = bytesComplete old < bytesComplete new
|