2012-07-02 20:07:39 +00:00
|
|
|
{- git-annex assistant pending transfer queue
|
|
|
|
-
|
|
|
|
- Copyright 2012 Joey Hess <joey@kitenet.net>
|
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
2012-07-25 18:54:09 +00:00
|
|
|
module Assistant.TransferQueue (
|
|
|
|
TransferQueue,
|
|
|
|
Schedule(..),
|
|
|
|
newTransferQueue,
|
2012-07-27 15:47:34 +00:00
|
|
|
getTransferQueue,
|
2012-07-25 18:54:09 +00:00
|
|
|
queueTransfers,
|
|
|
|
queueTransfer,
|
|
|
|
queueTransferAt,
|
|
|
|
getNextTransfer
|
|
|
|
) where
|
2012-07-02 20:07:39 +00:00
|
|
|
|
|
|
|
import Common.Annex
|
2012-07-05 16:21:22 +00:00
|
|
|
import Assistant.DaemonStatus
|
2012-07-02 20:07:39 +00:00
|
|
|
import Logs.Transfer
|
|
|
|
import Types.Remote
|
2012-07-05 16:21:22 +00:00
|
|
|
import qualified Remote
|
2012-07-02 20:07:39 +00:00
|
|
|
|
|
|
|
import Control.Concurrent.STM
|
2012-07-28 22:47:24 +00:00
|
|
|
import qualified Data.Map as M
|
2012-07-02 20:07:39 +00:00
|
|
|
|
2012-07-25 17:12:34 +00:00
|
|
|
{- The transfer queue consists of a channel listing the transfers to make;
|
2012-07-27 15:47:34 +00:00
|
|
|
- the size of the queue is also tracked, and a list is maintained
|
|
|
|
- in parallel to allow for reading. -}
|
2012-07-25 17:12:34 +00:00
|
|
|
data TransferQueue = TransferQueue
|
|
|
|
{ queue :: TChan (Transfer, TransferInfo)
|
|
|
|
, queuesize :: TVar Integer
|
2012-07-27 15:47:34 +00:00
|
|
|
, queuelist :: TVar [(Transfer, TransferInfo)]
|
2012-07-25 17:12:34 +00:00
|
|
|
}
|
|
|
|
|
|
|
|
data Schedule = Next | Later
|
|
|
|
deriving (Eq)
|
2012-07-02 20:07:39 +00:00
|
|
|
|
|
|
|
newTransferQueue :: IO TransferQueue
|
2012-07-27 15:47:34 +00:00
|
|
|
newTransferQueue = atomically $ TransferQueue
|
|
|
|
<$> newTChan
|
|
|
|
<*> newTVar 0
|
|
|
|
<*> newTVar []
|
|
|
|
|
|
|
|
{- Reads the queue's content without blocking or changing it. -}
|
|
|
|
getTransferQueue :: TransferQueue -> IO [(Transfer, TransferInfo)]
|
|
|
|
getTransferQueue q = atomically $ readTVar $ queuelist q
|
2012-07-02 20:07:39 +00:00
|
|
|
|
2012-07-25 18:02:50 +00:00
|
|
|
stubInfo :: AssociatedFile -> Remote -> TransferInfo
|
|
|
|
stubInfo f r = TransferInfo
|
2012-07-02 20:07:39 +00:00
|
|
|
{ startedTime = Nothing
|
|
|
|
, transferPid = Nothing
|
2012-07-18 22:42:41 +00:00
|
|
|
, transferTid = Nothing
|
2012-07-25 18:02:50 +00:00
|
|
|
, transferRemote = Just r
|
2012-07-02 20:07:39 +00:00
|
|
|
, bytesComplete = Nothing
|
|
|
|
, associatedFile = f
|
|
|
|
}
|
|
|
|
|
2012-07-25 18:02:50 +00:00
|
|
|
{- Adds transfers to queue for some of the known remotes. -}
|
2012-07-25 17:12:34 +00:00
|
|
|
queueTransfers :: Schedule -> TransferQueue -> DaemonStatusHandle -> Key -> AssociatedFile -> Direction -> Annex ()
|
2012-07-28 22:47:24 +00:00
|
|
|
queueTransfers schedule q dstatus k f direction = do
|
|
|
|
rs <- knownRemotes <$> liftIO (getDaemonStatus dstatus)
|
2012-07-25 17:12:34 +00:00
|
|
|
mapM_ go =<< sufficientremotes rs
|
2012-07-05 16:21:22 +00:00
|
|
|
where
|
2012-07-23 03:16:56 +00:00
|
|
|
sufficientremotes rs
|
2012-07-17 16:17:01 +00:00
|
|
|
-- Queue downloads from all remotes that
|
|
|
|
-- have the key, with the cheapest ones first.
|
|
|
|
-- More expensive ones will only be tried if
|
|
|
|
-- downloading from a cheap one fails.
|
|
|
|
| direction == Download = do
|
|
|
|
uuids <- Remote.keyLocations k
|
2012-07-23 03:16:56 +00:00
|
|
|
return $ filter (\r -> uuid r `elem` uuids) rs
|
2012-07-05 16:44:03 +00:00
|
|
|
-- TODO: Determine a smaller set of remotes that
|
|
|
|
-- can be uploaded to, in order to ensure all
|
|
|
|
-- remotes can access the content. Currently,
|
|
|
|
-- send to every remote we can.
|
2012-07-23 03:16:56 +00:00
|
|
|
| otherwise = return rs
|
2012-07-05 16:21:22 +00:00
|
|
|
gentransfer r = Transfer
|
|
|
|
{ transferDirection = direction
|
|
|
|
, transferKey = k
|
2012-07-05 20:34:20 +00:00
|
|
|
, transferUUID = Remote.uuid r
|
2012-07-05 16:21:22 +00:00
|
|
|
}
|
2012-07-28 22:47:24 +00:00
|
|
|
go r = liftIO $
|
|
|
|
enqueue schedule q dstatus (gentransfer r) (stubInfo f r)
|
2012-07-25 17:12:34 +00:00
|
|
|
|
2012-07-28 22:47:24 +00:00
|
|
|
enqueue :: Schedule -> TransferQueue -> DaemonStatusHandle -> Transfer -> TransferInfo -> IO ()
|
|
|
|
enqueue schedule q dstatus t info
|
2012-07-27 15:47:34 +00:00
|
|
|
| schedule == Next = go unGetTChan (new:)
|
|
|
|
| otherwise = go writeTChan (\l -> l++[new])
|
2012-07-25 17:12:34 +00:00
|
|
|
where
|
2012-07-27 15:47:34 +00:00
|
|
|
new = (t, info)
|
|
|
|
go modqueue modlist = do
|
2012-07-28 22:47:24 +00:00
|
|
|
atomically $ do
|
|
|
|
void $ modqueue (queue q) new
|
|
|
|
void $ modifyTVar' (queuesize q) succ
|
|
|
|
void $ modifyTVar' (queuelist q) modlist
|
2012-07-29 12:52:57 +00:00
|
|
|
void $ notifyTransfer dstatus
|
2012-07-05 16:21:22 +00:00
|
|
|
|
2012-07-25 17:12:34 +00:00
|
|
|
{- Adds a transfer to the queue. -}
|
2012-07-28 22:47:24 +00:00
|
|
|
queueTransfer :: Schedule -> TransferQueue -> DaemonStatusHandle -> AssociatedFile -> Transfer -> Remote -> IO ()
|
|
|
|
queueTransfer schedule q dstatus f t remote =
|
|
|
|
enqueue schedule q dstatus t (stubInfo f remote)
|
2012-07-02 20:07:39 +00:00
|
|
|
|
2012-07-25 17:12:34 +00:00
|
|
|
{- Blocks until the queue is no larger than a given size, and then adds a
|
|
|
|
- transfer to the queue. -}
|
2012-07-28 22:47:24 +00:00
|
|
|
queueTransferAt :: Integer -> Schedule -> TransferQueue -> DaemonStatusHandle -> AssociatedFile -> Transfer -> Remote -> IO ()
|
|
|
|
queueTransferAt wantsz schedule q dstatus f t remote = do
|
|
|
|
atomically $ do
|
|
|
|
sz <- readTVar (queuesize q)
|
|
|
|
if sz <= wantsz
|
|
|
|
then return ()
|
|
|
|
else retry -- blocks until queuesize changes
|
|
|
|
enqueue schedule q dstatus t (stubInfo f remote)
|
2012-07-02 20:07:39 +00:00
|
|
|
|
2012-07-29 17:37:26 +00:00
|
|
|
{- Blocks until a pending transfer is available from the queue,
|
|
|
|
- and removes it.
|
|
|
|
-
|
|
|
|
- Checks that it's acceptable, before adding it to the
|
|
|
|
- the currentTransfers map. If it's not acceptable, it's discarded.
|
|
|
|
-
|
|
|
|
- This is done in a single STM transaction, so there is no window
|
|
|
|
- where an observer sees an inconsistent status. -}
|
|
|
|
getNextTransfer :: TransferQueue -> DaemonStatusHandle -> (TransferInfo -> Bool) -> IO (Maybe (Transfer, TransferInfo))
|
|
|
|
getNextTransfer q dstatus acceptable = atomically $ do
|
2012-07-25 17:12:34 +00:00
|
|
|
void $ modifyTVar' (queuesize q) pred
|
2012-07-27 15:47:34 +00:00
|
|
|
void $ modifyTVar' (queuelist q) (drop 1)
|
2012-07-28 22:47:24 +00:00
|
|
|
r@(t, info) <- readTChan (queue q)
|
2012-07-29 17:37:26 +00:00
|
|
|
if acceptable info
|
|
|
|
then do
|
|
|
|
adjustTransfersSTM dstatus $
|
|
|
|
M.insertWith' const t info
|
|
|
|
return $ Just r
|
|
|
|
else return Nothing
|