2013-03-19 22:46:29 +00:00
|
|
|
{- A pool of "git-annex transferkeys" processes
|
|
|
|
-
|
2020-12-07 16:50:48 +00:00
|
|
|
- Copyright 2013-2020 Joey Hess <id@joeyh.name>
|
2013-03-19 22:46:29 +00:00
|
|
|
-
|
2019-03-13 19:48:14 +00:00
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
2013-03-19 22:46:29 +00:00
|
|
|
-}
|
|
|
|
|
2020-12-07 16:50:48 +00:00
|
|
|
{-# LANGUAGE RankNTypes #-}
|
2013-03-19 22:46:29 +00:00
|
|
|
|
2020-12-07 16:50:48 +00:00
|
|
|
module Annex.TransferrerPool where
|
|
|
|
|
|
|
|
import Annex.Common
|
|
|
|
import Types.TransferrerPool
|
2016-08-03 16:37:12 +00:00
|
|
|
import Types.Transfer
|
2013-12-01 18:56:37 +00:00
|
|
|
import Utility.Batch
|
2020-12-04 17:50:03 +00:00
|
|
|
import Messages.Serialized
|
2013-03-19 22:46:29 +00:00
|
|
|
import qualified Command.TransferKeys as T
|
|
|
|
|
assistant: Start a new git-annex transferkeys process after a network connection change
So that remotes that use a persistent network connection are restarted.
A remote might keep open a long duration network connection, and could
fail to deal well with losing the connection. This is particularly a
concern now that we have external special reotes. An external
special remote that is implemented naively might open the connection only
when PREPARE is sent, and if it loses connection, throw errors on each
request that is made.
(Note that the ssh connection caching should not have this problem; if the
long-duration ssh process loses connection, the named pipe is disconnected
and the next ssh attempt will reconnect. Also, XMPP already deals with
disconnection robustly in its own way.)
There's no way for git-annex to know if a lost network connection actually
affects a given remote, which might have a transfer in process. It does not
make sense to force kill the transferkeys process every time the NetWatcher
detects a change. (Especially because the NetWatcher sometimes polls 1
change per hour.)
In any case, the NetWatcher only detects connection to a network, not
disconnection. So if a transfer is in progress over the network, and the
network goes down, that will need to time out on its own.
An alternate approch that was considered is to use a separate transferkeys
process for each remote, and detect when a request fails, and assume that
means that process is in a failing state and restart it. The problem with
that approach is that if a resource is not available and a remote fails
every time, it degrades to starting a new transferkeys process for every
file transfer, which is too expensive.
Instead, this commit only handles the network reconnection case, and restarts
transferkeys only once the network has reconnected and another transfer needs
to be made. So, a transferkeys process will be reused for 1 hour, or until the
next network connection.
----
The NotificationBroadcaster was rewritten to use TMVars rather than MSampleVars,
to allow checking without blocking if a notification has been received.
----
This commit was sponsored by Tobias Brunner.
2014-01-06 20:03:39 +00:00
|
|
|
import Control.Concurrent.STM hiding (check)
|
2013-03-19 22:46:29 +00:00
|
|
|
import Control.Concurrent
|
2020-12-07 16:50:48 +00:00
|
|
|
import Control.Monad.IO.Class (MonadIO)
|
2013-03-19 22:46:29 +00:00
|
|
|
|
assistant: Start a new git-annex transferkeys process after a network connection change
So that remotes that use a persistent network connection are restarted.
A remote might keep open a long duration network connection, and could
fail to deal well with losing the connection. This is particularly a
concern now that we have external special reotes. An external
special remote that is implemented naively might open the connection only
when PREPARE is sent, and if it loses connection, throw errors on each
request that is made.
(Note that the ssh connection caching should not have this problem; if the
long-duration ssh process loses connection, the named pipe is disconnected
and the next ssh attempt will reconnect. Also, XMPP already deals with
disconnection robustly in its own way.)
There's no way for git-annex to know if a lost network connection actually
affects a given remote, which might have a transfer in process. It does not
make sense to force kill the transferkeys process every time the NetWatcher
detects a change. (Especially because the NetWatcher sometimes polls 1
change per hour.)
In any case, the NetWatcher only detects connection to a network, not
disconnection. So if a transfer is in progress over the network, and the
network goes down, that will need to time out on its own.
An alternate approch that was considered is to use a separate transferkeys
process for each remote, and detect when a request fails, and assume that
means that process is in a failing state and restart it. The problem with
that approach is that if a resource is not available and a remote fails
every time, it degrades to starting a new transferkeys process for every
file transfer, which is too expensive.
Instead, this commit only handles the network reconnection case, and restarts
transferkeys only once the network has reconnected and another transfer needs
to be made. So, a transferkeys process will be reused for 1 hour, or until the
next network connection.
----
The NotificationBroadcaster was rewritten to use TMVars rather than MSampleVars,
to allow checking without blocking if a notification has been received.
----
This commit was sponsored by Tobias Brunner.
2014-01-06 20:03:39 +00:00
|
|
|
{- Runs an action with a Transferrer from the pool.
|
|
|
|
-
|
2020-12-07 16:50:48 +00:00
|
|
|
- When minimizeprocesses is True, only one Transferrer is left running
|
|
|
|
- in the pool at a time. So if this needed to start a new Transferrer,
|
|
|
|
- it's stopped when done. Otherwise, idle processes are left in the pool
|
|
|
|
- for use later.
|
assistant: Start a new git-annex transferkeys process after a network connection change
So that remotes that use a persistent network connection are restarted.
A remote might keep open a long duration network connection, and could
fail to deal well with losing the connection. This is particularly a
concern now that we have external special reotes. An external
special remote that is implemented naively might open the connection only
when PREPARE is sent, and if it loses connection, throw errors on each
request that is made.
(Note that the ssh connection caching should not have this problem; if the
long-duration ssh process loses connection, the named pipe is disconnected
and the next ssh attempt will reconnect. Also, XMPP already deals with
disconnection robustly in its own way.)
There's no way for git-annex to know if a lost network connection actually
affects a given remote, which might have a transfer in process. It does not
make sense to force kill the transferkeys process every time the NetWatcher
detects a change. (Especially because the NetWatcher sometimes polls 1
change per hour.)
In any case, the NetWatcher only detects connection to a network, not
disconnection. So if a transfer is in progress over the network, and the
network goes down, that will need to time out on its own.
An alternate approch that was considered is to use a separate transferkeys
process for each remote, and detect when a request fails, and assume that
means that process is in a failing state and restart it. The problem with
that approach is that if a resource is not available and a remote fails
every time, it degrades to starting a new transferkeys process for every
file transfer, which is too expensive.
Instead, this commit only handles the network reconnection case, and restarts
transferkeys only once the network has reconnected and another transfer needs
to be made. So, a transferkeys process will be reused for 1 hour, or until the
next network connection.
----
The NotificationBroadcaster was rewritten to use TMVars rather than MSampleVars,
to allow checking without blocking if a notification has been received.
----
This commit was sponsored by Tobias Brunner.
2014-01-06 20:03:39 +00:00
|
|
|
-}
|
2020-12-07 17:08:59 +00:00
|
|
|
withTransferrer :: Bool -> MkCheckTransferrer -> FilePath -> BatchCommandMaker -> TransferrerPool -> (Transferrer -> IO a) -> IO a
|
|
|
|
withTransferrer minimizeprocesses mkcheck program batchmaker pool a = do
|
2014-01-06 21:07:08 +00:00
|
|
|
(mi, leftinpool) <- atomically (popTransferrerPool pool)
|
|
|
|
i@(TransferrerPoolItem (Just t) check) <- case mi of
|
2020-12-07 17:08:59 +00:00
|
|
|
Nothing -> mkTransferrerPoolItem mkcheck =<< mkTransferrer program batchmaker
|
2014-01-06 21:07:08 +00:00
|
|
|
Just i -> checkTransferrerPoolItem program batchmaker i
|
2020-12-07 16:50:48 +00:00
|
|
|
a t `finally` returntopool leftinpool check t i
|
|
|
|
where
|
|
|
|
returntopool leftinpool check t i
|
|
|
|
| not minimizeprocesses || leftinpool == 0 =
|
|
|
|
atomically $ pushTransferrerPool pool i
|
|
|
|
| otherwise = do
|
2014-01-06 21:07:08 +00:00
|
|
|
void $ forkIO $ stopTransferrer t
|
|
|
|
atomically $ pushTransferrerPool pool $ TransferrerPoolItem Nothing check
|
assistant: Start a new git-annex transferkeys process after a network connection change
So that remotes that use a persistent network connection are restarted.
A remote might keep open a long duration network connection, and could
fail to deal well with losing the connection. This is particularly a
concern now that we have external special reotes. An external
special remote that is implemented naively might open the connection only
when PREPARE is sent, and if it loses connection, throw errors on each
request that is made.
(Note that the ssh connection caching should not have this problem; if the
long-duration ssh process loses connection, the named pipe is disconnected
and the next ssh attempt will reconnect. Also, XMPP already deals with
disconnection robustly in its own way.)
There's no way for git-annex to know if a lost network connection actually
affects a given remote, which might have a transfer in process. It does not
make sense to force kill the transferkeys process every time the NetWatcher
detects a change. (Especially because the NetWatcher sometimes polls 1
change per hour.)
In any case, the NetWatcher only detects connection to a network, not
disconnection. So if a transfer is in progress over the network, and the
network goes down, that will need to time out on its own.
An alternate approch that was considered is to use a separate transferkeys
process for each remote, and detect when a request fails, and assume that
means that process is in a failing state and restart it. The problem with
that approach is that if a resource is not available and a remote fails
every time, it degrades to starting a new transferkeys process for every
file transfer, which is too expensive.
Instead, this commit only handles the network reconnection case, and restarts
transferkeys only once the network has reconnected and another transfer needs
to be made. So, a transferkeys process will be reused for 1 hour, or until the
next network connection.
----
The NotificationBroadcaster was rewritten to use TMVars rather than MSampleVars,
to allow checking without blocking if a notification has been received.
----
This commit was sponsored by Tobias Brunner.
2014-01-06 20:03:39 +00:00
|
|
|
|
|
|
|
{- Check if a Transferrer from the pool is still ok to be used.
|
|
|
|
- If not, stop it and start a new one. -}
|
|
|
|
checkTransferrerPoolItem :: FilePath -> BatchCommandMaker -> TransferrerPoolItem -> IO TransferrerPoolItem
|
|
|
|
checkTransferrerPoolItem program batchmaker i = case i of
|
|
|
|
TransferrerPoolItem (Just t) check -> ifM check
|
|
|
|
( return i
|
|
|
|
, do
|
|
|
|
stopTransferrer t
|
|
|
|
new check
|
2013-03-19 22:46:29 +00:00
|
|
|
)
|
assistant: Start a new git-annex transferkeys process after a network connection change
So that remotes that use a persistent network connection are restarted.
A remote might keep open a long duration network connection, and could
fail to deal well with losing the connection. This is particularly a
concern now that we have external special reotes. An external
special remote that is implemented naively might open the connection only
when PREPARE is sent, and if it loses connection, throw errors on each
request that is made.
(Note that the ssh connection caching should not have this problem; if the
long-duration ssh process loses connection, the named pipe is disconnected
and the next ssh attempt will reconnect. Also, XMPP already deals with
disconnection robustly in its own way.)
There's no way for git-annex to know if a lost network connection actually
affects a given remote, which might have a transfer in process. It does not
make sense to force kill the transferkeys process every time the NetWatcher
detects a change. (Especially because the NetWatcher sometimes polls 1
change per hour.)
In any case, the NetWatcher only detects connection to a network, not
disconnection. So if a transfer is in progress over the network, and the
network goes down, that will need to time out on its own.
An alternate approch that was considered is to use a separate transferkeys
process for each remote, and detect when a request fails, and assume that
means that process is in a failing state and restart it. The problem with
that approach is that if a resource is not available and a remote fails
every time, it degrades to starting a new transferkeys process for every
file transfer, which is too expensive.
Instead, this commit only handles the network reconnection case, and restarts
transferkeys only once the network has reconnected and another transfer needs
to be made. So, a transferkeys process will be reused for 1 hour, or until the
next network connection.
----
The NotificationBroadcaster was rewritten to use TMVars rather than MSampleVars,
to allow checking without blocking if a notification has been received.
----
This commit was sponsored by Tobias Brunner.
2014-01-06 20:03:39 +00:00
|
|
|
TransferrerPoolItem Nothing check -> new check
|
|
|
|
where
|
|
|
|
new check = do
|
|
|
|
t <- mkTransferrer program batchmaker
|
|
|
|
return $ TransferrerPoolItem (Just t) check
|
2013-03-19 22:46:29 +00:00
|
|
|
|
|
|
|
{- Requests that a Transferrer perform a Transfer, and waits for it to
|
|
|
|
- finish. -}
|
2020-12-07 16:50:48 +00:00
|
|
|
performTransfer
|
|
|
|
:: (Monad m, MonadIO m, MonadMask m)
|
|
|
|
=> Transferrer
|
|
|
|
-> Transfer
|
|
|
|
-> TransferInfo
|
|
|
|
-> (forall a. Annex a -> m a)
|
|
|
|
-- ^ Run an annex action in the monad. Will not be used with
|
|
|
|
-- actions that block for a long time.
|
|
|
|
-> m Bool
|
|
|
|
performTransfer transferrer t info runannex = catchBoolIO $ do
|
new protocol for transferkeys, with message serialization
Necessarily threw out the old protocol, so if an old git-annex assistant
is running, and starts a transferkeys from the new git-annex, it would
fail. But, that seems unlikely; the assistant starts up transferkeys
processes and then keeps them running. Still, may need to test that
scenario.
The new protocol is simple read/show and looks like this:
TransferRequest Download (Right "origin") (Key {keyName = "f8f8766a836fb6120abf4d5328ce8761404e437529e997aaa0363bdd4fecd7bb", keyVariety = SHA2Key (HashSize 256) (HasExt True), keySize = Just 30, keyMtime = Nothing, keyChunkSize = Nothing, keyChunkNum = Nothing}) (AssociatedFile (Just "foo"))
TransferOutput (ProgressMeter (Just 30) (MeterState {meterBytesProcessed = BytesProcessed 0, meterTimeStamp = 1.6070268727892535e9}) (MeterState {meterBytesProcessed = BytesProcessed 30, meterTimeStamp = 1.6070268728043e9}))
TransferOutput (OutputMessage "(checksum...) ")
TransferResult True
Granted, this is not optimally fast, but it seems good enough, and is
probably nearly as fast as the old protocol anyhow.
emitSerializedOutput for ProgressMeter is not yet implemented. It needs
to somehow start or update a progress meter. There may need to be a new
message that allocates a progress meter, and then have ProgressMeter
update it.
This commit was sponsored by Ethan Aubin
2020-12-03 20:21:20 +00:00
|
|
|
(liftIO $ T.sendRequest t info (transferrerWrite transferrer))
|
2020-12-04 17:50:03 +00:00
|
|
|
relaySerializedOutput
|
2020-12-04 18:54:09 +00:00
|
|
|
(liftIO $ T.readResponse (transferrerRead transferrer))
|
|
|
|
(liftIO . T.sendSerializedOutputResponse (transferrerWrite transferrer))
|
2020-12-07 16:50:48 +00:00
|
|
|
runannex
|
2013-03-19 22:46:29 +00:00
|
|
|
|
2013-12-11 03:19:18 +00:00
|
|
|
{- Starts a new git-annex transferkeys process, setting up handles
|
2013-03-19 22:46:29 +00:00
|
|
|
- that will be used to communicate with it. -}
|
2013-12-01 19:37:51 +00:00
|
|
|
mkTransferrer :: FilePath -> BatchCommandMaker -> IO Transferrer
|
|
|
|
mkTransferrer program batchmaker = do
|
2013-12-01 18:56:37 +00:00
|
|
|
{- It runs as a batch job. -}
|
2013-12-11 03:19:18 +00:00
|
|
|
let (program', params') = batchmaker (program, [Param "transferkeys"])
|
2013-03-19 22:46:29 +00:00
|
|
|
{- It's put into its own group so that the whole group can be
|
|
|
|
- killed to stop a transfer. -}
|
2013-12-11 03:19:18 +00:00
|
|
|
(Just writeh, Just readh, _, pid) <- createProcess
|
|
|
|
(proc program' $ toCommand params')
|
|
|
|
{ create_group = True
|
|
|
|
, std_in = CreatePipe
|
|
|
|
, std_out = CreatePipe
|
|
|
|
}
|
2013-03-19 22:46:29 +00:00
|
|
|
return $ Transferrer
|
2013-12-11 03:19:18 +00:00
|
|
|
{ transferrerRead = readh
|
|
|
|
, transferrerWrite = writeh
|
2013-03-19 22:46:29 +00:00
|
|
|
, transferrerHandle = pid
|
|
|
|
}
|
|
|
|
|
2020-12-07 16:50:48 +00:00
|
|
|
{- Closing the fds will stop the transferrer, but only when it's in between
|
|
|
|
- transfers. -}
|
2013-03-19 22:46:29 +00:00
|
|
|
stopTransferrer :: Transferrer -> IO ()
|
|
|
|
stopTransferrer t = do
|
|
|
|
hClose $ transferrerRead t
|
|
|
|
hClose $ transferrerWrite t
|
|
|
|
void $ waitForProcess $ transferrerHandle t
|