Skip to content

Commit b054b01

Browse files
Merge pull request #156 from kazu-yamamoto/improve-manager
Improve manager
2 parents f7c0701 + 3af78ae commit b054b01

File tree

2 files changed

+78
-56
lines changed

2 files changed

+78
-56
lines changed

Network/HTTP2/H2/Manager.hs

+57-32
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,7 @@ module Network.HTTP2.H2.Manager (
99
stopAfter,
1010
forkManaged,
1111
forkManagedUnmask,
12-
withTimeout,
12+
forkManagedTimeout,
1313
KilledByHttp2ThreadManager (..),
1414
waitCounter0,
1515
) where
@@ -19,8 +19,10 @@ import Control.Concurrent.STM
1919
import Control.Exception
2020
import qualified Control.Exception as E
2121
import Data.Foldable
22-
import Data.Map (Map)
23-
import qualified Data.Map.Strict as Map
22+
import Data.IORef
23+
import Data.IntMap (IntMap)
24+
import qualified Data.IntMap.Strict as Map
25+
import System.Mem.Weak (Weak, deRefWeak)
2426
import qualified System.TimeManager as T
2527

2628
import Imports
@@ -30,17 +32,15 @@ import Imports
3032
-- | Manager to manage the thread and the timer.
3133
data Manager = Manager T.Manager (TVar ManagedThreads)
3234

33-
type ManagedThreads = Map ThreadId TimeoutHandle
35+
type ManagedThreads = IntMap ManagedThread
3436

3537
----------------------------------------------------------------
3638

37-
data TimeoutHandle
38-
= ThreadWithTimeout T.Handle
39-
| ThreadWithoutTimeout
40-
41-
cancelTimeout :: TimeoutHandle -> IO ()
42-
cancelTimeout (ThreadWithTimeout th) = T.cancel th
43-
cancelTimeout ThreadWithoutTimeout = return ()
39+
-- 'IORef' prevents race between WAI TimeManager (TimeoutThread)
40+
-- and stopAfter (KilledByHttp2ThreadManager).
41+
-- It is initialized with 'False' and turned into 'True' when locked.
42+
-- The winner can throw an asynchronous exception.
43+
data ManagedThread = ManagedThread (Weak ThreadId) (IORef Bool)
4444

4545
----------------------------------------------------------------
4646

@@ -74,10 +74,10 @@ stopAfter (Manager _timmgr var) action cleanup = do
7474
m0 <- readTVar var
7575
writeTVar var Map.empty
7676
return m0
77-
forM_ (Map.elems m) cancelTimeout
78-
let er = either Just (const Nothing) ma
79-
forM_ (Map.keys m) $ \tid ->
80-
E.throwTo tid $ KilledByHttp2ThreadManager er
77+
let ths = Map.elems m
78+
er = either Just (const Nothing) ma
79+
ex = KilledByHttp2ThreadManager er
80+
forM_ ths $ \(ManagedThread wtid ref) -> lockAndKill wtid ref ex
8181
case ma of
8282
Left err -> cleanup (Just err) >> throwIO err
8383
Right a -> cleanup Nothing >> return a
@@ -97,18 +97,44 @@ forkManaged mgr label io =
9797
forkManagedUnmask
9898
:: Manager -> String -> ((forall x. IO x -> IO x) -> IO ()) -> IO ()
9999
forkManagedUnmask (Manager _timmgr var) label io =
100-
-- This is the top level of thread.
101-
-- So, SomeException should be reasonable.
102100
void $ mask_ $ forkIOWithUnmask $ \unmask -> E.handle ignore $ do
103101
labelMe label
104-
tid <- myThreadId
105-
atomically $ modifyTVar var $ Map.insert tid ThreadWithoutTimeout
106-
-- We catch the exception and do not rethrow it: we don't want the
107-
-- exception printed to stderr.
108-
io unmask `catch` ignore
109-
atomically $ modifyTVar var $ Map.delete tid
110-
where
111-
ignore (E.SomeException _) = return ()
102+
E.bracket (setup var) (clear var) $ \_ -> io unmask
103+
104+
forkManagedTimeout :: Manager -> String -> (T.Handle -> IO ()) -> IO ()
105+
forkManagedTimeout (Manager timmgr var) label io =
106+
void $ forkIO $ E.handle ignore $ do
107+
labelMe label
108+
E.bracket (setup var) (clear var) $ \(_n, wtid, ref) ->
109+
-- 'TimeoutThread' is ignored by 'withHandle'.
110+
T.withHandle timmgr (lockAndKill wtid ref T.TimeoutThread) io
111+
112+
setup :: TVar (IntMap ManagedThread) -> IO (Int, Weak ThreadId, IORef Bool)
113+
setup var = do
114+
(wtid, n) <- myWeakThradId
115+
ref <- newIORef False
116+
let ent = ManagedThread wtid ref
117+
-- asking to throw KilledByHttp2ThreadManager to me
118+
atomically $ modifyTVar' var $ Map.insert n ent
119+
return (n, wtid, ref)
120+
121+
lockAndKill :: Exception e => Weak ThreadId -> IORef Bool -> e -> IO ()
122+
lockAndKill wtid ref e = do
123+
alreadyLocked <- atomicModifyIORef' ref (\b -> (True, b)) -- try to lock
124+
unless alreadyLocked $ do
125+
mtid <- deRefWeak wtid
126+
case mtid of
127+
Nothing -> return ()
128+
Just tid -> E.throwTo tid e
129+
130+
clear
131+
:: TVar (IntMap ManagedThread)
132+
-> (Map.Key, Weak ThreadId, IORef Bool)
133+
-> IO ()
134+
clear var (n, _, _) = atomically $ modifyTVar' var $ Map.delete n
135+
136+
ignore :: KilledByHttp2ThreadManager -> IO ()
137+
ignore (KilledByHttp2ThreadManager _) = return ()
112138

113139
waitCounter0 :: Manager -> IO ()
114140
waitCounter0 (Manager _timmgr var) = atomically $ do
@@ -117,10 +143,9 @@ waitCounter0 (Manager _timmgr var) = atomically $ do
117143

118144
----------------------------------------------------------------
119145

120-
withTimeout :: Manager -> (T.Handle -> IO ()) -> IO ()
121-
withTimeout (Manager timmgr var) action =
122-
T.withHandleKillThread timmgr (return ()) $ \th -> do
123-
tid <- myThreadId
124-
-- overriding ThreadWithoutTimeout
125-
atomically $ modifyTVar var $ Map.insert tid $ ThreadWithTimeout th
126-
action th
146+
myWeakThradId :: IO (Weak ThreadId, Int)
147+
myWeakThradId = do
148+
tid <- myThreadId
149+
wtid <- mkWeakThreadId tid
150+
let n = read (drop 9 $ show tid) -- drop "ThreadId "
151+
return (wtid, n)

Network/HTTP2/Server/Worker.hs

+21-24
Original file line numberDiff line numberDiff line change
@@ -23,15 +23,13 @@ import Network.HTTP2.H2
2323

2424
runServer :: Config -> Server -> Launch
2525
runServer conf server ctx@Context{..} strm req =
26-
forkManaged threadManager label $
27-
withTimeout threadManager $ \th -> do
28-
-- FIXME: exception
29-
let req' = pauseRequestBody th
30-
aux = Aux th mySockAddr peerSockAddr
31-
request = Request req'
32-
lc <- newLoopCheck strm Nothing
33-
server request aux $ sendResponse conf ctx lc strm request
34-
adjustRxWindow ctx strm
26+
forkManagedTimeout threadManager label $ \th -> do
27+
let req' = pauseRequestBody th
28+
aux = Aux th mySockAddr peerSockAddr
29+
request = Request req'
30+
lc <- newLoopCheck strm Nothing
31+
server request aux $ sendResponse conf ctx lc strm request
32+
adjustRxWindow ctx strm
3533
where
3634
label = "H2 response sender for stream " ++ show (streamNumber strm)
3735
pauseRequestBody th = req{inpObjBody = readBody'}
@@ -169,21 +167,20 @@ sendStreaming
169167
-> IO (TBQueue StreamingChunk)
170168
sendStreaming Context{..} strm strmbdy = do
171169
tbq <- newTBQueueIO 10 -- fixme: hard coding: 10
172-
forkManaged threadManager label $
173-
withTimeout threadManager $ \th ->
174-
withOutBodyIface tbq id $ \iface -> do
175-
let iface' =
176-
iface
177-
{ outBodyPush = \b -> do
178-
T.pause th
179-
outBodyPush iface b
180-
T.resume th
181-
, outBodyPushFinal = \b -> do
182-
T.pause th
183-
outBodyPushFinal iface b
184-
T.resume th
185-
}
186-
strmbdy iface'
170+
forkManagedTimeout threadManager label $ \th ->
171+
withOutBodyIface tbq id $ \iface -> do
172+
let iface' =
173+
iface
174+
{ outBodyPush = \b -> do
175+
T.pause th
176+
outBodyPush iface b
177+
T.resume th
178+
, outBodyPushFinal = \b -> do
179+
T.pause th
180+
outBodyPushFinal iface b
181+
T.resume th
182+
}
183+
strmbdy iface'
187184
return tbq
188185
where
189186
label = "H2 response streaming sender for " ++ show (streamNumber strm)

0 commit comments

Comments
 (0)