summaryrefslogtreecommitdiff
path: root/PingMachine.hs
diff options
context:
space:
mode:
Diffstat (limited to 'PingMachine.hs')
-rw-r--r--PingMachine.hs113
1 files changed, 113 insertions, 0 deletions
diff --git a/PingMachine.hs b/PingMachine.hs
new file mode 100644
index 00000000..b714d71e
--- /dev/null
+++ b/PingMachine.hs
@@ -0,0 +1,113 @@
1{-# LANGUAGE CPP #-}
2module PingMachine where
3
4import Control.Monad
5import Data.Function
6#ifdef THREAD_DEBUG
7import Control.Concurrent.Lifted.Instrument
8#else
9import Control.Concurrent.Lifted
10import GHC.Conc (labelThread)
11#endif
12import Control.Concurrent.STM
13
14import InterruptibleDelay
15
16type Miliseconds = Int
17type TimeOut = Miliseconds
18type PingInterval = Miliseconds
19
20-- | Events that occur as a result of the 'PingMachine' watchdog.
21--
22-- Use 'pingWait' to wait for one of these to occur.
23data PingEvent
24 = PingIdle -- ^ You should send a ping if you observe this event.
25 | PingTimeOut -- ^ You should give up on the connection in case of this event.
26
27data PingMachine = PingMachine
28 { pingFlag :: TVar Bool
29 , pingInterruptible :: InterruptibleDelay
30 , pingEvent :: TMVar PingEvent
31 , pingStarted :: TMVar Bool
32 }
33
34-- | Fork a thread to monitor a connection for a ping timeout.
35--
36-- If 'pingBump' is not invoked after a idle is signaled, a timeout event will
37-- occur. When that happens, even if the caller chooses to ignore this event,
38-- the watchdog thread will be terminated and no more ping events will be
39-- signaled.
40--
41-- An idle connection will be signaled by:
42--
43-- (1) 'pingFlag' is set 'True'
44--
45-- (2) 'pingWait' returns 'PingIdle'
46--
47-- Either may be tested to determine whether a ping should be sent but
48-- 'pingFlag' is difficult to use properly because it is up to the caller to
49-- remember that the ping is already in progress.
50forkPingMachine
51 :: PingInterval -- ^ Milliseconds of idle before a ping is considered necessary.
52 -> TimeOut -- ^ Milliseconds after 'PingIdle' before we signal 'PingTimeOut'.
53 -> IO PingMachine
54forkPingMachine idle timeout = do
55 d <- interruptibleDelay
56 flag <- atomically $ newTVar False
57 canceled <- atomically $ newTVar False
58 event <- atomically newEmptyTMVar
59 started <- atomically $ newEmptyTMVar
60 when (idle/=0) $ void . forkIO $ do
61 myThreadId >>= flip labelThread ("ping.watchdog")
62 (>>=) (atomically (readTMVar started)) $ flip when $ do
63 fix $ \loop -> do
64 atomically $ writeTVar flag False
65 fin <- startDelay d (1000*idle)
66 (>>=) (atomically (readTMVar started)) $ flip when $ do
67 if (not fin) then loop
68 else do
69 -- Idle event
70 atomically $ do
71 tryTakeTMVar event
72 putTMVar event PingIdle
73 writeTVar flag True
74 fin <- startDelay d (1000*timeout)
75 (>>=) (atomically (readTMVar started)) $ flip when $ do
76 me <- myThreadId
77 if (not fin) then loop
78 else do
79 -- Timeout event
80 atomically $ do
81 tryTakeTMVar event
82 writeTVar flag False
83 putTMVar event PingTimeOut
84 return PingMachine
85 { pingFlag = flag
86 , pingInterruptible = d
87 , pingEvent = event
88 , pingStarted = started
89 }
90
91-- | Terminate the watchdog thread. Call this upon connection close.
92--
93-- You should ensure no threads are waiting on 'pingWait' because there is no
94-- 'PingEvent' signaling termination.
95pingCancel :: PingMachine -> IO ()
96pingCancel me = do
97 atomically $ do tryTakeTMVar (pingStarted me)
98 putTMVar (pingStarted me) False
99 interruptDelay (pingInterruptible me)
100
101-- | Reset the ping timer. Call this regularly to prevent 'PingTimeOut'.
102pingBump :: PingMachine -> IO ()
103pingBump me = do
104 atomically $ do
105 b <- tryReadTMVar (pingStarted me)
106 when (b/=Just False) $ do
107 tryTakeTMVar (pingStarted me)
108 putTMVar (pingStarted me) True
109 interruptDelay (pingInterruptible me)
110
111-- | Retries until a 'PingEvent' occurs.
112pingWait :: PingMachine -> STM PingEvent
113pingWait me = takeTMVar (pingEvent me)