summaryrefslogtreecommitdiff
path: root/Assistant/Threads/TransferWatcher.hs
diff options
context:
space:
mode:
authorGravatar Joey Hess <joey@kitenet.net>2012-07-06 21:45:08 -0600
committerGravatar Joey Hess <joey@kitenet.net>2012-07-06 21:59:45 -0600
commitcc6f660752d4eef1e667f1ac859c6140f4da87ca (patch)
tree8605cbd31e97154794cd9998faee58cea6ff83e7 /Assistant/Threads/TransferWatcher.hs
parentd954a0ce5934a877f8df0c683eaccaf8c2b1938e (diff)
fix transfer slots blocking and refilling when transfers are stopped
There's a bug, if a transfer process notices it needs to do nothing, it never starts the transfer, so the slot is never freed.
Diffstat (limited to 'Assistant/Threads/TransferWatcher.hs')
-rw-r--r--Assistant/Threads/TransferWatcher.hs25
1 files changed, 14 insertions, 11 deletions
diff --git a/Assistant/Threads/TransferWatcher.hs b/Assistant/Threads/TransferWatcher.hs
index 4e468a416..aa8b3f6e6 100644
--- a/Assistant/Threads/TransferWatcher.hs
+++ b/Assistant/Threads/TransferWatcher.hs
@@ -10,6 +10,7 @@ module Assistant.Threads.TransferWatcher where
import Common.Annex
import Assistant.ThreadedMonad
import Assistant.DaemonStatus
+import Assistant.TransferSlots
import Logs.Transfer
import Utility.DirWatcher
import Utility.Types.DirWatcher
@@ -19,12 +20,12 @@ import Data.Map as M
{- This thread watches for changes to the gitAnnexTransferDir,
- and updates the DaemonStatus's map of ongoing transfers. -}
-transferWatcherThread :: ThreadState -> DaemonStatusHandle -> IO ()
-transferWatcherThread st dstatus = do
+transferWatcherThread :: ThreadState -> DaemonStatusHandle -> TransferSlots -> IO ()
+transferWatcherThread st dstatus transferslots = do
g <- runThreadState st $ fromRepo id
let dir = gitAnnexTransferDir g
createDirectoryIfMissing True dir
- let hook a = Just $ runHandler st dstatus a
+ let hook a = Just $ runHandler st dstatus transferslots a
let hooks = mkWatchHooks
{ addHook = hook onAdd
, delHook = hook onDel
@@ -32,25 +33,25 @@ transferWatcherThread st dstatus = do
}
void $ watchDir dir (const False) hooks id
-type Handler = ThreadState -> DaemonStatusHandle -> FilePath -> Maybe FileStatus -> IO ()
+type Handler = ThreadState -> DaemonStatusHandle -> TransferSlots -> FilePath -> Maybe FileStatus -> IO ()
{- Runs an action handler.
-
- Exceptions are ignored, otherwise a whole thread could be crashed.
-}
-runHandler :: ThreadState -> DaemonStatusHandle -> Handler -> FilePath -> Maybe FileStatus -> IO ()
-runHandler st dstatus handler file filestatus = void $ do
+runHandler :: ThreadState -> DaemonStatusHandle -> TransferSlots -> Handler -> FilePath -> Maybe FileStatus -> IO ()
+runHandler st dstatus transferslots handler file filestatus = void $ do
either print (const noop) =<< tryIO go
where
- go = handler st dstatus file filestatus
+ go = handler st dstatus transferslots file filestatus
{- Called when there's an error with inotify. -}
onErr :: Handler
-onErr _ _ msg _ = error msg
+onErr _ _ _ msg _ = error msg
{- Called when a new transfer information file is written. -}
onAdd :: Handler
-onAdd st dstatus file _ = case parseTransferFile file of
+onAdd st dstatus _ file _ = case parseTransferFile file of
Nothing -> noop
Just t -> runThreadState st $ go t =<< checkTransfer t
where
@@ -64,7 +65,7 @@ onAdd st dstatus file _ = case parseTransferFile file of
- to avoid zombies.
-}
onDel :: Handler
-onDel st dstatus file _ = case parseTransferFile file of
+onDel st dstatus transferslots file _ = case parseTransferFile file of
Nothing -> noop
Just t -> maybe noop waitchild
=<< runThreadState st (removeTransfer dstatus t)
@@ -73,6 +74,8 @@ onDel st dstatus file _ = case parseTransferFile file of
| shouldWait info = case transferPid info of
Nothing -> noop
Just pid -> do
- void $ getProcessStatus True False pid
+ void $ tryIO $
+ getProcessStatus True False pid
runThreadState st invalidateCache
+ transferComplete transferslots
| otherwise = noop