2014-03-22 14:42:38 +00:00
|
|
|
{- git-annex transfers
|
|
|
|
-
|
use fine-grained WorkerStages when transferring and verifying
This means that Command.Move and Command.Get don't need to
manually set the stage, and is a lot cleaner conceptually.
Also, this makes Command.Sync.syncFile use the worker pool better.
In the scenario where it first downloads content and then uploads it to
some other remotes, it will start in TransferStage, then enter VerifyStage
and then go back to TransferStage for each transfer to the remotes.
Before, it entered CleanupStage after the download, and stayed in it for
the upload, so too many transfer jobs could run at the same time.
Note that, in Remote.Git, it uses runTransfer and also verifyKeyContent
inside onLocal. That has a Annex state for the remote, with no worker pool.
So the resulting calls to enteringStage won't block in there.
While Remote.Git.copyToRemote does do checksum verification, I
realized that should not use a verification slot in the WorkerPool
to do it. Because, it's reading back from eg, a removable disk to checksum.
That will contend with other writes to that disk. It's best to treat
that checksum verification as just part of the transer. So, removed the todo
item about that, as there's nothing needing to be done.
2019-06-19 17:09:26 +00:00
|
|
|
- Copyright 2012-2019 Joey Hess <id@joeyh.name>
|
2014-03-22 14:42:38 +00:00
|
|
|
-
|
2019-03-13 19:48:14 +00:00
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
2014-03-22 14:42:38 +00:00
|
|
|
-}
|
|
|
|
|
2017-11-29 19:49:05 +00:00
|
|
|
{-# LANGUAGE CPP, BangPatterns #-}
|
2014-03-22 14:42:38 +00:00
|
|
|
|
|
|
|
module Annex.Transfer (
|
|
|
|
module X,
|
|
|
|
upload,
|
2018-11-06 17:00:25 +00:00
|
|
|
alwaysUpload,
|
2014-03-22 14:42:38 +00:00
|
|
|
download,
|
|
|
|
runTransfer,
|
2014-08-15 18:17:05 +00:00
|
|
|
alwaysRunTransfer,
|
2014-03-22 14:42:38 +00:00
|
|
|
noRetry,
|
2018-03-29 17:04:07 +00:00
|
|
|
stdRetry,
|
2016-09-06 16:42:50 +00:00
|
|
|
pickRemote,
|
2014-03-22 14:42:38 +00:00
|
|
|
) where
|
|
|
|
|
2016-01-20 20:36:33 +00:00
|
|
|
import Annex.Common
|
2016-09-06 16:42:50 +00:00
|
|
|
import qualified Annex
|
2014-03-22 14:42:38 +00:00
|
|
|
import Logs.Transfer as X
|
2016-08-03 16:37:12 +00:00
|
|
|
import Types.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
|
2018-03-29 17:04:07 +00:00
|
|
|
import Utility.ThreadScheduler
|
2015-11-12 22:05:45 +00:00
|
|
|
import Annex.LockPool
|
2017-02-27 19:21:24 +00:00
|
|
|
import Types.Key
|
2016-09-06 16:42:50 +00:00
|
|
|
import qualified Types.Remote as Remote
|
use fine-grained WorkerStages when transferring and verifying
This means that Command.Move and Command.Get don't need to
manually set the stage, and is a lot cleaner conceptually.
Also, this makes Command.Sync.syncFile use the worker pool better.
In the scenario where it first downloads content and then uploads it to
some other remotes, it will start in TransferStage, then enter VerifyStage
and then go back to TransferStage for each transfer to the remotes.
Before, it entered CleanupStage after the download, and stayed in it for
the upload, so too many transfer jobs could run at the same time.
Note that, in Remote.Git, it uses runTransfer and also verifyKeyContent
inside onLocal. That has a Annex state for the remote, with no worker pool.
So the resulting calls to enteringStage won't block in there.
While Remote.Git.copyToRemote does do checksum verification, I
realized that should not use a verification slot in the WorkerPool
to do it. Because, it's reading back from eg, a removable disk to checksum.
That will contend with other writes to that disk. It's best to treat
that checksum verification as just part of the transer. So, removed the todo
item about that, as there's nothing needing to be done.
2019-06-19 17:09:26 +00:00
|
|
|
import Annex.Concurrent
|
2016-09-09 16:57:42 +00:00
|
|
|
import Types.Concurrency
|
use fine-grained WorkerStages when transferring and verifying
This means that Command.Move and Command.Get don't need to
manually set the stage, and is a lot cleaner conceptually.
Also, this makes Command.Sync.syncFile use the worker pool better.
In the scenario where it first downloads content and then uploads it to
some other remotes, it will start in TransferStage, then enter VerifyStage
and then go back to TransferStage for each transfer to the remotes.
Before, it entered CleanupStage after the download, and stayed in it for
the upload, so too many transfer jobs could run at the same time.
Note that, in Remote.Git, it uses runTransfer and also verifyKeyContent
inside onLocal. That has a Annex state for the remote, with no worker pool.
So the resulting calls to enteringStage won't block in there.
While Remote.Git.copyToRemote does do checksum verification, I
realized that should not use a verification slot in the WorkerPool
to do it. Because, it's reading back from eg, a removable disk to checksum.
That will contend with other writes to that disk. It's best to treat
that checksum verification as just part of the transer. So, removed the todo
item about that, as there's nothing needing to be done.
2019-06-19 17:09:26 +00:00
|
|
|
import Types.WorkerPool
|
2014-03-22 14:42:38 +00:00
|
|
|
|
|
|
|
import Control.Concurrent
|
2017-03-08 18:49:30 +00:00
|
|
|
import qualified Data.Map.Strict as M
|
|
|
|
import Data.Ord
|
2014-03-22 14:42:38 +00:00
|
|
|
|
2016-08-03 17:46:20 +00:00
|
|
|
upload :: Observable v => UUID -> Key -> AssociatedFile -> RetryDecider -> (MeterUpdate -> Annex v) -> NotifyWitness -> Annex v
|
|
|
|
upload u key f d a _witness = guardHaveUUID u $
|
|
|
|
runTransfer (Transfer Upload u key) f d a
|
2015-05-12 19:50:03 +00:00
|
|
|
|
2018-11-06 17:00:25 +00:00
|
|
|
alwaysUpload :: Observable v => UUID -> Key -> AssociatedFile -> RetryDecider -> (MeterUpdate -> Annex v) -> NotifyWitness -> Annex v
|
|
|
|
alwaysUpload u key f d a _witness = guardHaveUUID u $
|
|
|
|
alwaysRunTransfer (Transfer Upload u key) f d a
|
|
|
|
|
2016-08-03 17:46:20 +00:00
|
|
|
download :: Observable v => UUID -> Key -> AssociatedFile -> RetryDecider -> (MeterUpdate -> Annex v) -> NotifyWitness -> Annex v
|
|
|
|
download u key f d a _witness = guardHaveUUID u $
|
|
|
|
runTransfer (Transfer Download u key) f d a
|
2016-06-02 17:50:05 +00:00
|
|
|
|
|
|
|
guardHaveUUID :: Observable v => UUID -> Annex v -> Annex v
|
|
|
|
guardHaveUUID u a
|
|
|
|
| u == NoUUID = return observeFailure
|
|
|
|
| otherwise = 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.
|
|
|
|
-}
|
2017-03-10 17:12:24 +00:00
|
|
|
runTransfer :: Observable v => Transfer -> AssociatedFile -> RetryDecider -> (MeterUpdate -> Annex v) -> Annex v
|
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. -}
|
2017-03-10 17:12:24 +00:00
|
|
|
alwaysRunTransfer :: Observable v => Transfer -> AssociatedFile -> RetryDecider -> (MeterUpdate -> Annex v) -> Annex v
|
2014-08-15 18:17:05 +00:00
|
|
|
alwaysRunTransfer = runTransfer' True
|
|
|
|
|
2017-03-10 17:12:24 +00:00
|
|
|
runTransfer' :: Observable v => Bool -> Transfer -> AssociatedFile -> RetryDecider -> (MeterUpdate -> Annex v) -> Annex v
|
use fine-grained WorkerStages when transferring and verifying
This means that Command.Move and Command.Get don't need to
manually set the stage, and is a lot cleaner conceptually.
Also, this makes Command.Sync.syncFile use the worker pool better.
In the scenario where it first downloads content and then uploads it to
some other remotes, it will start in TransferStage, then enter VerifyStage
and then go back to TransferStage for each transfer to the remotes.
Before, it entered CleanupStage after the download, and stayed in it for
the upload, so too many transfer jobs could run at the same time.
Note that, in Remote.Git, it uses runTransfer and also verifyKeyContent
inside onLocal. That has a Annex state for the remote, with no worker pool.
So the resulting calls to enteringStage won't block in there.
While Remote.Git.copyToRemote does do checksum verification, I
realized that should not use a verification slot in the WorkerPool
to do it. Because, it's reading back from eg, a removable disk to checksum.
That will contend with other writes to that disk. It's best to treat
that checksum verification as just part of the transer. So, removed the todo
item about that, as there's nothing needing to be done.
2019-06-19 17:09:26 +00:00
|
|
|
runTransfer' ignorelock t afile retrydecider transferaction = enteringStage TransferStage $ debugLocks $ checkSecureHashes t $ do
|
2018-03-29 17:04:07 +00:00
|
|
|
shouldretry <- retrydecider
|
2017-10-17 21:54:38 +00:00
|
|
|
info <- liftIO $ startTransferInfo afile
|
2018-03-14 22:55:27 +00:00
|
|
|
(meter, tfile, createtfile, metervar) <- mkProgressUpdater t info
|
2017-10-17 21:54:38 +00:00
|
|
|
mode <- annexFileMode
|
2018-03-14 22:55:27 +00:00
|
|
|
(lck, inprogress) <- prep tfile createtfile mode
|
2017-10-17 21:54:38 +00:00
|
|
|
if inprogress && not ignorelock
|
|
|
|
then do
|
|
|
|
showNote "transfer already in progress, or unable to take transfer lock"
|
|
|
|
return observeFailure
|
|
|
|
else do
|
2018-03-29 17:04:07 +00:00
|
|
|
v <- retry shouldretry info metervar $ transferaction meter
|
2017-10-17 21:54:38 +00:00
|
|
|
liftIO $ cleanup tfile lck
|
|
|
|
if observeBool v
|
|
|
|
then removeFailedTransfer t
|
|
|
|
else recordFailedTransfer t info
|
|
|
|
return v
|
2014-03-22 14:42:38 +00:00
|
|
|
where
|
2018-03-15 17:20:38 +00:00
|
|
|
prep :: FilePath -> Annex () -> FileMode -> Annex (Maybe LockHandle, Bool)
|
2014-03-22 14:42:38 +00:00
|
|
|
#ifndef mingw32_HOST_OS
|
2018-03-14 22:55:27 +00:00
|
|
|
prep tfile createtfile mode = catchPermissionDenied (const prepfailed) $ do
|
2015-05-12 23:36:16 +00:00
|
|
|
let lck = transferLockFile tfile
|
create directory for transfer lock file, and catch perm error
Before, the call to mkProgressUpdater created the directory as a
side-effect, but since that ignored failure to create it, this led to
a "does not exist" exception when the transfer lock file was created,
rather than a permissions error.
So, make sure the directory exists before trying to lock the file in it.
When a PermissionDenied exception is caught, skip making the transfer lock.
This lets downloads from readonly remotes happen.
If an upload is being tried, and the lock file can't be written due to
permissions, then probably the actual transfer will fail for the same
reason, so I think it's ok that it continues w/o taking the lock in that
case.
2016-02-12 18:11:25 +00:00
|
|
|
createAnnexDirectory $ takeDirectory lck
|
2017-12-05 19:00:50 +00:00
|
|
|
tryLockExclusive (Just mode) lck >>= \case
|
2015-05-12 23:36:16 +00:00
|
|
|
Nothing -> return (Nothing, True)
|
2015-11-16 19:35:41 +00:00
|
|
|
Just lockhandle -> ifM (checkSaneLock lck lockhandle)
|
2015-05-12 23:39:28 +00:00
|
|
|
( do
|
2018-03-14 22:55:27 +00:00
|
|
|
createtfile
|
2015-05-12 23:36:16 +00:00
|
|
|
return (Just lockhandle, False)
|
2017-05-25 20:02:17 +00:00
|
|
|
, do
|
|
|
|
liftIO $ dropLock lockhandle
|
|
|
|
return (Nothing, True)
|
2015-05-12 23:39:28 +00:00
|
|
|
)
|
2014-03-22 14:42:38 +00:00
|
|
|
#else
|
2018-03-14 22:55:27 +00:00
|
|
|
prep tfile createtfile _mode = catchPermissionDenied (const prepfailed) $ do
|
2015-05-12 23:36:16 +00:00
|
|
|
let lck = transferLockFile tfile
|
create directory for transfer lock file, and catch perm error
Before, the call to mkProgressUpdater created the directory as a
side-effect, but since that ignored failure to create it, this led to
a "does not exist" exception when the transfer lock file was created,
rather than a permissions error.
So, make sure the directory exists before trying to lock the file in it.
When a PermissionDenied exception is caught, skip making the transfer lock.
This lets downloads from readonly remotes happen.
If an upload is being tried, and the lock file can't be written due to
permissions, then probably the actual transfer will fail for the same
reason, so I think it's ok that it continues w/o taking the lock in that
case.
2016-02-12 18:11:25 +00:00
|
|
|
createAnnexDirectory $ takeDirectory lck
|
2017-12-05 19:00:50 +00:00
|
|
|
catchMaybeIO (liftIO $ lockExclusive lck) >>= \case
|
2014-03-22 14:42:38 +00:00
|
|
|
Nothing -> return (Nothing, False)
|
|
|
|
Just Nothing -> return (Nothing, True)
|
|
|
|
Just (Just lockhandle) -> do
|
2018-03-14 22:55:27 +00:00
|
|
|
createtfile
|
2014-03-22 14:42:38 +00:00
|
|
|
return (Just lockhandle, False)
|
|
|
|
#endif
|
create directory for transfer lock file, and catch perm error
Before, the call to mkProgressUpdater created the directory as a
side-effect, but since that ignored failure to create it, this led to
a "does not exist" exception when the transfer lock file was created,
rather than a permissions error.
So, make sure the directory exists before trying to lock the file in it.
When a PermissionDenied exception is caught, skip making the transfer lock.
This lets downloads from readonly remotes happen.
If an upload is being tried, and the lock file can't be written due to
permissions, then probably the actual transfer will fail for the same
reason, so I think it's ok that it continues w/o taking the lock in that
case.
2016-02-12 18:11:25 +00:00
|
|
|
prepfailed = return (Nothing, False)
|
|
|
|
|
2014-03-22 14:42:38 +00:00
|
|
|
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
|
2018-03-29 17:04:07 +00:00
|
|
|
retry shouldretry oldinfo metervar run = tryNonAsync run >>= \case
|
2018-03-29 17:22:49 +00:00
|
|
|
Right v
|
|
|
|
| observeBool v -> return v
|
|
|
|
| otherwise -> checkretry
|
2017-12-05 19:00:50 +00:00
|
|
|
Left e -> do
|
|
|
|
warning (show e)
|
2018-03-29 17:22:49 +00:00
|
|
|
checkretry
|
|
|
|
where
|
|
|
|
checkretry = do
|
2017-12-05 19:00:50 +00:00
|
|
|
b <- getbytescomplete metervar
|
|
|
|
let newinfo = oldinfo { bytesComplete = Just b }
|
2018-03-29 17:04:07 +00:00
|
|
|
ifM (shouldretry oldinfo newinfo)
|
|
|
|
( retry shouldretry newinfo metervar run
|
|
|
|
, return observeFailure
|
|
|
|
)
|
2014-03-22 14:42:38 +00:00
|
|
|
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
|
|
|
|
2017-02-27 19:21:24 +00:00
|
|
|
{- Avoid download and upload of keys with insecure content when
|
|
|
|
- annex.securehashesonly is configured.
|
|
|
|
-
|
|
|
|
- This is not a security check. Even if this let the content be
|
|
|
|
- downloaded, the actual security checks would prevent the content from
|
|
|
|
- being added to the repository. The only reason this is done here is to
|
|
|
|
- avoid transferring content that's going to be rejected anyway.
|
|
|
|
-
|
|
|
|
- We assume that, if annex.securehashesonly is set and the local repo
|
|
|
|
- still contains content using an insecure hash, remotes will likewise
|
|
|
|
- tend to be configured to reject it, so Upload is also prevented.
|
|
|
|
-}
|
|
|
|
checkSecureHashes :: Observable v => Transfer -> Annex v -> Annex v
|
|
|
|
checkSecureHashes t a
|
|
|
|
| cryptographicallySecure variety = a
|
|
|
|
| otherwise = ifM (annexSecureHashesOnly <$> Annex.getGitConfig)
|
|
|
|
( do
|
2019-01-11 20:34:04 +00:00
|
|
|
warning $ "annex.securehashesonly blocked transfer of " ++ decodeBS (formatKeyVariety variety) ++ " key"
|
2017-02-27 19:21:24 +00:00
|
|
|
return observeFailure
|
|
|
|
, a
|
|
|
|
)
|
|
|
|
where
|
|
|
|
variety = keyVariety (transferKey t)
|
|
|
|
|
2018-03-29 17:04:07 +00:00
|
|
|
type RetryDecider = Annex (TransferInfo -> TransferInfo -> Annex Bool)
|
|
|
|
|
|
|
|
{- The first RetryDecider will be checked first; only if it says not to
|
|
|
|
- retry will the second one be checked. -}
|
|
|
|
combineRetryDeciders :: RetryDecider -> RetryDecider -> RetryDecider
|
|
|
|
combineRetryDeciders a b = do
|
|
|
|
ar <- a
|
|
|
|
br <- b
|
|
|
|
return $ \old new -> ar old new <||> br old new
|
2014-03-22 14:42:38 +00:00
|
|
|
|
|
|
|
noRetry :: RetryDecider
|
2018-03-29 17:04:07 +00:00
|
|
|
noRetry = pure $ \_ _ -> pure False
|
|
|
|
|
|
|
|
stdRetry :: RetryDecider
|
|
|
|
stdRetry = combineRetryDeciders forwardRetry configuredRetry
|
2014-03-22 14:42:38 +00:00
|
|
|
|
|
|
|
{- Retries a transfer when it fails, as long as the failed transfer managed
|
|
|
|
- to send some data. -}
|
|
|
|
forwardRetry :: RetryDecider
|
2018-05-08 20:11:45 +00:00
|
|
|
forwardRetry = pure $ \old new -> pure $
|
|
|
|
fromMaybe 0 (bytesComplete old) < fromMaybe 0 (bytesComplete new)
|
2018-03-29 17:04:07 +00:00
|
|
|
|
|
|
|
{- Retries a number of times with growing delays in between when enabled
|
|
|
|
- by git configuration. -}
|
|
|
|
configuredRetry :: RetryDecider
|
2018-11-19 19:00:24 +00:00
|
|
|
configuredRetry = debugLocks $ do
|
2018-03-29 17:04:07 +00:00
|
|
|
retrycounter <- liftIO $ newMVar 0
|
|
|
|
return $ \_old new -> do
|
|
|
|
(maxretries, Seconds initretrydelay) <- getcfg $
|
|
|
|
Remote.gitconfig <$> transferRemote new
|
|
|
|
retries <- liftIO $ modifyMVar retrycounter $
|
|
|
|
\n -> return (n + 1, n + 1)
|
|
|
|
if retries < maxretries
|
|
|
|
then do
|
|
|
|
let retrydelay = Seconds (initretrydelay * 2^(retries-1))
|
2018-03-29 17:31:53 +00:00
|
|
|
showSideAction $ "Delaying " ++ show (fromSeconds retrydelay) ++ "s before retrying."
|
2018-03-29 17:04:07 +00:00
|
|
|
liftIO $ threadDelaySeconds retrydelay
|
|
|
|
return True
|
|
|
|
else return False
|
|
|
|
where
|
|
|
|
globalretrycfg = fromMaybe 0 . annexRetry
|
|
|
|
<$> Annex.getGitConfig
|
|
|
|
globalretrydelaycfg = fromMaybe (Seconds 1) . annexRetryDelay
|
|
|
|
<$> Annex.getGitConfig
|
|
|
|
getcfg Nothing = (,) <$> globalretrycfg <*> globalretrydelaycfg
|
|
|
|
getcfg (Just gc) = (,)
|
|
|
|
<$> maybe globalretrycfg return (remoteAnnexRetry gc)
|
|
|
|
<*> maybe globalretrydelaycfg return (remoteAnnexRetryDelay gc)
|
2016-09-06 16:42:50 +00:00
|
|
|
|
|
|
|
{- Picks a remote from the list and tries a transfer to it. If the transfer
|
|
|
|
- does not succeed, goes on to try other remotes from the list.
|
|
|
|
-
|
|
|
|
- The list should already be ordered by remote cost, and is normally
|
|
|
|
- tried in order. However, when concurrent jobs are running, they will
|
|
|
|
- be assigned different remotes of the same cost when possible. This can
|
|
|
|
- increase total transfer speed.
|
|
|
|
-}
|
|
|
|
pickRemote :: Observable v => [Remote] -> (Remote -> Annex v) -> Annex v
|
2018-11-19 19:00:24 +00:00
|
|
|
pickRemote l a = debugLocks $ go l =<< Annex.getState Annex.concurrency
|
2016-09-06 16:42:50 +00:00
|
|
|
where
|
|
|
|
go [] _ = return observeFailure
|
|
|
|
go (r:[]) _ = a r
|
2019-05-10 17:24:31 +00:00
|
|
|
go rs NonConcurrent = gononconcurrent rs
|
|
|
|
go rs (Concurrent n)
|
|
|
|
| n <= 1 = gononconcurrent rs
|
|
|
|
| otherwise = goconcurrent rs
|
|
|
|
go rs ConcurrentPerCpu = goconcurrent rs
|
|
|
|
|
|
|
|
gononconcurrent [] = return observeFailure
|
|
|
|
gononconcurrent (r:rs) = do
|
2016-09-06 16:42:50 +00:00
|
|
|
ok <- a r
|
|
|
|
if observeBool ok
|
|
|
|
then return ok
|
2019-05-10 17:24:31 +00:00
|
|
|
else gononconcurrent rs
|
|
|
|
|
|
|
|
goconcurrent rs = do
|
|
|
|
mv <- Annex.getState Annex.activeremotes
|
|
|
|
active <- liftIO $ takeMVar mv
|
|
|
|
let rs' = sortBy (lessActiveFirst active) rs
|
|
|
|
goconcurrent' mv active rs'
|
|
|
|
|
|
|
|
goconcurrent' mv active [] = do
|
2016-09-06 16:42:50 +00:00
|
|
|
liftIO $ putMVar mv active
|
|
|
|
return observeFailure
|
2019-05-10 17:24:31 +00:00
|
|
|
goconcurrent' mv active (r:rs) = do
|
2017-03-08 18:49:30 +00:00
|
|
|
let !active' = M.insertWith (+) r 1 active
|
2016-09-06 16:42:50 +00:00
|
|
|
liftIO $ putMVar mv active'
|
|
|
|
let getnewactive = do
|
|
|
|
active'' <- liftIO $ takeMVar mv
|
2017-03-08 18:49:30 +00:00
|
|
|
let !active''' = M.update (\n -> if n > 1 then Just (n-1) else Nothing) r active''
|
2016-09-06 16:42:50 +00:00
|
|
|
return active'''
|
|
|
|
let removeactive = liftIO . putMVar mv =<< getnewactive
|
|
|
|
ok <- a r `onException` removeactive
|
|
|
|
if observeBool ok
|
|
|
|
then do
|
|
|
|
removeactive
|
|
|
|
return ok
|
|
|
|
else do
|
|
|
|
active'' <- getnewactive
|
|
|
|
-- Re-sort the remaining rs
|
|
|
|
-- because other threads could have
|
|
|
|
-- been assigned them in the meantime.
|
2017-03-08 18:49:30 +00:00
|
|
|
let rs' = sortBy (lessActiveFirst active'') rs
|
2019-05-10 17:24:31 +00:00
|
|
|
goconcurrent' mv active'' rs'
|
2016-09-06 16:42:50 +00:00
|
|
|
|
2017-03-08 18:49:30 +00:00
|
|
|
lessActiveFirst :: M.Map Remote Integer -> Remote -> Remote -> Ordering
|
|
|
|
lessActiveFirst active a b
|
|
|
|
| Remote.cost a == Remote.cost b = comparing (`M.lookup` active) a b
|
2018-08-03 17:06:06 +00:00
|
|
|
| otherwise = comparing Remote.cost a b
|