1d0b692198
When a page is loaded, the javascript requests an notification url, and does long polling on the url to be informed of changes. But if a change occured before the notification url was requested, it would not be notified of that change, and so the page display would not update. I fixed this by *always* updating the page display after it gets the notification url. This is extra work, but the overhead is not noticable in the other overhead of loading a page. (A nicer way would be to somehow record the version of a page initially loaded, and then compare it with the current version when getting the notification url, and only force an update if it's changed. But getting the "version" of the different parts of the page that use long polling is difficult.)
56 lines
1.8 KiB
Haskell
56 lines
1.8 KiB
Haskell
{- git-annex assistant transfer polling thread
|
|
-
|
|
- Copyright 2012 Joey Hess <joey@kitenet.net>
|
|
-
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
-}
|
|
|
|
module Assistant.Threads.TransferPoller where
|
|
|
|
import Assistant.Common
|
|
import Assistant.DaemonStatus
|
|
import Logs.Transfer
|
|
import Utility.NotificationBroadcaster
|
|
import qualified Assistant.Threads.TransferWatcher as TransferWatcher
|
|
|
|
import Control.Concurrent
|
|
import qualified Data.Map as M
|
|
|
|
{- This thread polls the status of ongoing transfers, determining how much
|
|
- of each transfer is complete. -}
|
|
transferPollerThread :: NamedThread
|
|
transferPollerThread = namedThread "TransferPoller" $ do
|
|
g <- liftAnnex gitRepo
|
|
tn <- liftIO . newNotificationHandle True =<<
|
|
transferNotifier <$> getDaemonStatus
|
|
forever $ do
|
|
liftIO $ threadDelay 500000 -- 0.5 seconds
|
|
ts <- currentTransfers <$> getDaemonStatus
|
|
if M.null ts
|
|
-- block until transfers running
|
|
then liftIO $ waitNotification tn
|
|
else mapM_ (poll g) $ M.toList ts
|
|
where
|
|
poll g (t, info)
|
|
{- Downloads are polled by checking the size of the
|
|
- temp file being used for the transfer. -}
|
|
| transferDirection t == Download = do
|
|
let f = gitAnnexTmpLocation (transferKey t) g
|
|
sz <- liftIO $ catchMaybeIO $
|
|
fromIntegral . fileSize <$> getFileStatus f
|
|
newsize t info sz
|
|
{- Uploads don't need to be polled for when the TransferWatcher
|
|
- thread can track file modifications. -}
|
|
| TransferWatcher.watchesTransferSize = noop
|
|
{- Otherwise, this code polls the upload progress
|
|
- by reading the transfer info file. -}
|
|
| otherwise = do
|
|
let f = transferFile t g
|
|
mi <- liftIO $ catchDefaultIO Nothing $
|
|
readTransferInfoFile Nothing f
|
|
maybe noop (newsize t info . bytesComplete) mi
|
|
|
|
newsize t info sz
|
|
| bytesComplete info /= sz && isJust sz =
|
|
alterTransferInfo t $ \i -> i { bytesComplete = sz }
|
|
| otherwise = noop
|