make start button work on queued transfers

When multiple downloads of a key are queued, it starts the first, but leaves the
other downloads in the queue. This ensures that we don't lose a queued
download if the one that got started failed.
This commit is contained in:
Joey Hess 2012-08-29 16:30:40 -04:00
parent c21a9fe04a
commit 8d32d54320
3 changed files with 66 additions and 51 deletions

View file

@ -34,49 +34,26 @@ transfererThread :: ThreadState -> DaemonStatusHandle -> TransferQueue -> Transf
transfererThread st dstatus transferqueue slots = go =<< readProgramFile transfererThread st dstatus transferqueue slots = go =<< readProgramFile
where where
go program = forever $ inTransferSlot dstatus slots $ go program = forever $ inTransferSlot dstatus slots $
getNextTransfer transferqueue dstatus notrunning maybe (return Nothing) (uncurry $ startTransfer st dstatus program)
>>= handle program =<< getNextTransfer transferqueue dstatus notrunning
handle _ Nothing = return Nothing
handle program (Just (t, info)) = ifM (runThreadState st $ shouldTransfer t info)
( do
debug thisThread [ "Transferring:" , show t ]
notifyTransfer dstatus
let a = doTransfer dstatus t info program
return $ Just (t, info, a)
, do
debug thisThread [ "Skipping unnecessary transfer:" , show t ]
-- getNextTransfer added t to the
-- daemonstatus's transfer map.
void $ removeTransfer dstatus t
return Nothing
)
{- Skip transfers that are already running. -} {- Skip transfers that are already running. -}
notrunning i = startedTime i == Nothing notrunning i = startedTime i == Nothing
{- Checks if the file to download is already present, or the remote {- By the time this is called, the daemonstatis's transfer map should
- being uploaded to isn't known to have the file. -} - already have been updated to include the transfer. -}
shouldTransfer :: Transfer -> TransferInfo -> Annex Bool startTransfer :: ThreadState -> DaemonStatusHandle -> FilePath -> Transfer -> TransferInfo -> TransferGenerator
shouldTransfer t info startTransfer st dstatus program t info = case (transferRemote info, associatedFile info) of
| transferDirection t == Download = (Just remote, Just file) -> ifM (runThreadState st $ shouldTransfer t info)
not <$> inAnnex key ( do
| transferDirection t == Upload = debug thisThread [ "Transferring:" , show t ]
{- Trust the location log to check if the notifyTransfer dstatus
- remote already has the key. This avoids return $ Just (t, info, transferprocess remote file)
- a roundtrip to the remote. -} , do
case transferRemote info of debug thisThread [ "Skipping unnecessary transfer:" , show t ]
Nothing -> return False void $ removeTransfer dstatus t
Just remote -> return Nothing
notElem (Remote.uuid remote) )
<$> loggedLocations key _ -> return Nothing
| otherwise = return False
where
key = transferKey t
doTransfer :: DaemonStatusHandle -> Transfer -> TransferInfo -> FilePath -> IO ()
doTransfer dstatus t info program = case (transferRemote info, associatedFile info) of
(Nothing, _) -> noop
(_, Nothing) -> noop
(Just remote, Just file) -> transferprocess remote file
where where
direction = transferDirection t direction = transferDirection t
isdownload = direction == Download isdownload = direction == Download
@ -101,3 +78,22 @@ doTransfer dstatus t info program = case (transferRemote info, associatedFile in
, Param "--file" , Param "--file"
, File file , File file
] ]
{- Checks if the file to download is already present, or the remote
- being uploaded to isn't known to have the file. -}
shouldTransfer :: Transfer -> TransferInfo -> Annex Bool
shouldTransfer t info
| transferDirection t == Download =
not <$> inAnnex key
| transferDirection t == Upload =
{- Trust the location log to check if the
- remote already has the key. This avoids
- a roundtrip to the remote. -}
case transferRemote info of
Nothing -> return False
Just remote ->
notElem (Remote.uuid remote)
<$> loggedLocations key
| otherwise = return False
where
key = transferKey t

View file

@ -15,6 +15,7 @@ module Assistant.TransferQueue (
queueTransferAt, queueTransferAt,
queueTransferWhenSmall, queueTransferWhenSmall,
getNextTransfer, getNextTransfer,
getMatchingTransfers,
dequeueTransfers, dequeueTransfers,
) where ) where
@ -140,20 +141,32 @@ getNextTransfer q dstatus acceptable = atomically $ do
return $ Just r return $ Just r
else return Nothing else return Nothing
{- Moves transfers matching a condition from the queue, to the
- currentTransfers map. -}
getMatchingTransfers :: TransferQueue -> DaemonStatusHandle -> (Transfer -> Bool) -> IO [(Transfer, TransferInfo)]
getMatchingTransfers q dstatus c = atomically $ do
ts <- dequeueTransfersSTM q c
unless (null ts) $
adjustTransfersSTM dstatus $ \m -> M.union m $ M.fromList ts
return ts
{- Removes transfers matching a condition from the queue, and returns the {- Removes transfers matching a condition from the queue, and returns the
- removed transfers. -} - removed transfers. -}
dequeueTransfers :: TransferQueue -> DaemonStatusHandle -> (Transfer -> Bool) -> IO [(Transfer, TransferInfo)] dequeueTransfers :: TransferQueue -> DaemonStatusHandle -> (Transfer -> Bool) -> IO [(Transfer, TransferInfo)]
dequeueTransfers q dstatus c = do dequeueTransfers q dstatus c = do
removed <- atomically $ do removed <- atomically $ dequeueTransfersSTM q c
(removed, ls) <- partition (c . fst)
<$> readTVar (queuelist q)
void $ writeTVar (queuesize q) (length ls)
void $ writeTVar (queuelist q) ls
drain
forM_ ls $ unGetTChan (queue q)
return removed
unless (null removed) $ unless (null removed) $
notifyTransfer dstatus notifyTransfer dstatus
return removed return removed
dequeueTransfersSTM :: TransferQueue -> (Transfer -> Bool) -> STM [(Transfer, TransferInfo)]
dequeueTransfersSTM q c = do
(removed, ts) <- partition (c . fst)
<$> readTVar (queuelist q)
void $ writeTVar (queuesize q) (length ts)
void $ writeTVar (queuelist q) ts
drain
forM_ ts $ unGetTChan (queue q)
return removed
where where
drain = maybe noop (const drain) =<< tryReadTChan (queue q) drain = maybe noop (const drain) =<< tryReadTChan (queue q)

View file

@ -209,8 +209,14 @@ cancelTransfer pause t = do
startTransfer :: Transfer -> Handler () startTransfer :: Transfer -> Handler ()
startTransfer t = do startTransfer t = do
m <- getCurrentTransfers m <- getCurrentTransfers
webapp <- getYesod
let dstatus = daemonStatus webapp
let q = transferQueue webapp
{- resume a paused transfer -}
maybe noop go (M.lookup t m) maybe noop go (M.lookup t m)
-- TODO: handle starting a queued transfer {- start a queued transfer -}
is <- liftIO $ map snd <$> getMatchingTransfers q dstatus (== t)
maybe noop start $ headMaybe is
where where
go info = maybe (start info) (resume info) $ transferTid info go info = maybe (start info) (resume info) $ transferTid info
resume info tid = do resume info tid = do
@ -222,6 +228,7 @@ startTransfer t = do
throwTo tid ResumeTransfer throwTo tid ResumeTransfer
start info = do start info = do
webapp <- getYesod webapp <- getYesod
let st = fromJust $ threadState webapp
let dstatus = daemonStatus webapp let dstatus = daemonStatus webapp
let slots = transferSlots webapp let slots = transferSlots webapp
{- This transfer was being run by another process, {- This transfer was being run by another process,
@ -230,8 +237,7 @@ startTransfer t = do
{ transferPid = Nothing, transferPaused = False } { transferPid = Nothing, transferPaused = False }
liftIO $ inImmediateTransferSlot dstatus slots $ do liftIO $ inImmediateTransferSlot dstatus slots $ do
program <- readProgramFile program <- readProgramFile
let a = Transferrer.doTransfer dstatus t info program Transferrer.startTransfer st dstatus program t info
return $ Just (t, info, a)
getCurrentTransfers :: Handler TransferMap getCurrentTransfers :: Handler TransferMap
getCurrentTransfers = currentTransfers getCurrentTransfers = currentTransfers