@@ -67,7 +67,7 @@ import Control.Exception
67
67
, uninterruptibleMask_
68
68
)
69
69
import qualified Control.Exception as Exception (Handler (.. ), catches , finally )
70
- import Control.Concurrent (forkIO , forkIOWithUnmask , myThreadId )
70
+ import Control.Concurrent (forkIO , forkIOWithUnmask , killThread , myThreadId )
71
71
import Control.Distributed.Process.Internal.StrictMVar
72
72
( newMVar
73
73
, withMVar
@@ -76,7 +76,6 @@ import Control.Distributed.Process.Internal.StrictMVar
76
76
, newEmptyMVar
77
77
, putMVar
78
78
, takeMVar
79
- , readMVar
80
79
)
81
80
import Control.Concurrent.Chan (newChan , writeChan , readChan )
82
81
import qualified Control.Concurrent.MVar as MVar (newEmptyMVar , takeMVar )
@@ -119,6 +118,9 @@ import Control.Distributed.Process.Internal.Types
119
118
, LocalNode (.. )
120
119
, MxEventBus (.. )
121
120
, LocalNodeState (.. )
121
+ , ValidLocalNodeState (.. )
122
+ , withValidLocalState
123
+ , modifyValidLocalState_
122
124
, LocalProcess (.. )
123
125
, LocalProcessState (.. )
124
126
, Process (.. )
@@ -233,7 +235,7 @@ newLocalNode transport rtable = do
233
235
createBareLocalNode :: NT. EndPoint -> RemoteTable -> IO LocalNode
234
236
createBareLocalNode endPoint rtable = do
235
237
unq <- randomIO
236
- state <- newMVar LocalNodeState
238
+ state <- newMVar $ LocalNodeValid $ ValidLocalNodeState
237
239
{ _localProcesses = Map. empty
238
240
, _localPidCounter = firstNonReservedProcessId
239
241
, _localPidUnique = unq
@@ -320,12 +322,21 @@ startServiceProcesses node = do
320
322
sendChan ch ()
321
323
]
322
324
323
- -- | Force-close a local node
324
- --
325
- -- TODO: for now we just close the associated endpoint
325
+ -- | Force-close a local node, killing all processes on that node.
326
326
closeLocalNode :: LocalNode -> IO ()
327
- closeLocalNode node =
328
- -- TODO: close all our processes, surely!?
327
+ closeLocalNode node = do
328
+ modifyMVar_ (localState node) $ \ st -> case st of
329
+ LocalNodeValid vst -> do
330
+ forM_ (vst ^. localProcesses) $ \ lproc ->
331
+ -- Semantics of 'throwTo' guarantee that target thread will get
332
+ -- delivered an exception. Therefore, target thread will be killed
333
+ -- eventually and that's as good as we can do. No need to wait for
334
+ -- thread to actually finish dying.
335
+ killThread (processThread lproc)
336
+ return LocalNodeClosed
337
+ LocalNodeClosed -> return LocalNodeClosed
338
+ -- This call will have the effect of shutting down the NC as well (see
339
+ -- 'createBareLocalNode').
329
340
NT. closeEndPoint (localEndPoint node)
330
341
331
342
-- | Run a process on a local node and wait for it to finish
@@ -344,9 +355,9 @@ forkProcess node proc =
344
355
modifyMVarMasked (localState node) startProcess
345
356
where
346
357
startProcess :: LocalNodeState -> IO (LocalNodeState , ProcessId )
347
- startProcess st = do
348
- let lpid = LocalProcessId { lpidCounter = st ^. localPidCounter
349
- , lpidUnique = st ^. localPidUnique
358
+ startProcess ( LocalNodeValid vst) = do
359
+ let lpid = LocalProcessId { lpidCounter = vst ^. localPidCounter
360
+ , lpidUnique = vst ^. localPidUnique
350
361
}
351
362
let pid = ProcessId { processNodeId = localNodeId node
352
363
, processLocalId = lpid
@@ -378,7 +389,7 @@ forkProcess node proc =
378
389
(return . DiedException . (show :: SomeException -> String )))]
379
390
380
391
-- [Unified: Table 4, rules termination and exiting]
381
- modifyMVar_ (localState node) (cleanupProcess pid)
392
+ modifyValidLocalState_ node (cleanupProcess pid)
382
393
writeChan (localCtrlChan node) NCMsg
383
394
{ ctrlMsgSender = ProcessIdentifier pid
384
395
, ctrlMsgSignal = Died (ProcessIdentifier pid) reason
@@ -393,27 +404,30 @@ forkProcess node proc =
393
404
-- TODO: this doesn't look right at all - how do we know
394
405
-- that newUnique represents a process id that is available!?
395
406
newUnique <- randomIO
396
- return ( (localProcessWithId lpid ^= Just lproc)
407
+ return ( LocalNodeValid
408
+ $ (localProcessWithId lpid ^= Just lproc)
397
409
. (localPidCounter ^= firstNonReservedProcessId)
398
410
. (localPidUnique ^= newUnique)
399
- $ st
411
+ $ vst
400
412
, pid
401
413
)
402
414
else
403
- return ( (localProcessWithId lpid ^= Just lproc)
415
+ return ( LocalNodeValid
416
+ $ (localProcessWithId lpid ^= Just lproc)
404
417
. (localPidCounter ^: (+ 1 ))
405
- $ st
418
+ $ vst
406
419
, pid
407
420
)
421
+ startProcess LocalNodeClosed = throwIO $ userError $ " Node closed " ++ show (localNodeId node)
408
422
409
- cleanupProcess :: ProcessId -> LocalNodeState -> IO LocalNodeState
410
- cleanupProcess pid st = do
423
+ cleanupProcess :: ProcessId -> ValidLocalNodeState -> IO ValidLocalNodeState
424
+ cleanupProcess pid vst = do
411
425
let pid' = ProcessIdentifier pid
412
- let (affected, unaffected) = Map. partitionWithKey (\ (fr, _to) ! _v -> impliesDeathOf pid' fr) (st ^. localConnections)
426
+ let (affected, unaffected) = Map. partitionWithKey (\ (fr, _to) ! _v -> impliesDeathOf pid' fr) (vst ^. localConnections)
413
427
mapM_ (NT. close . fst ) (Map. elems affected)
414
428
return $ (localProcessWithId (processLocalId pid) ^= Nothing )
415
429
. (localConnections ^= unaffected)
416
- $ st
430
+ $ vst
417
431
418
432
-- note [tracer/forkProcess races]
419
433
--
@@ -502,7 +516,7 @@ handleIncomingMessages node = go initConnectionState
502
516
case decode (BSL. fromChunks payload) of
503
517
ProcessIdentifier pid -> do
504
518
let lpid = processLocalId pid
505
- mProc <- withMVar state $ return . (^. localProcessWithId lpid)
519
+ mProc <- withValidLocalState node $ return . (^. localProcessWithId lpid)
506
520
case mProc of
507
521
Just proc ->
508
522
go (incomingAt cid ^= Just (src, ToProc pid (processWeakQ proc )) $ st)
@@ -511,7 +525,7 @@ handleIncomingMessages node = go initConnectionState
511
525
SendPortIdentifier chId -> do
512
526
let lcid = sendPortLocalId chId
513
527
lpid = processLocalId (sendPortProcessId chId)
514
- mProc <- withMVar state $ return . (^. localProcessWithId lpid)
528
+ mProc <- withValidLocalState node $ return . (^. localProcessWithId lpid)
515
529
case mProc of
516
530
Just proc -> do
517
531
mChannel <- withMVar (processState proc ) $ return . (^. typedChannelWithId lcid)
@@ -978,8 +992,8 @@ ncEffectGetInfo from pid =
978
992
them = (ProcessIdentifier pid)
979
993
in do
980
994
node <- ask
981
- mProc <- liftIO $
982
- withMVar (localState node) $ return . (^. localProcessWithId lpid)
995
+ mProc <- liftIO $ withValidLocalState node
996
+ $ return . (^. localProcessWithId lpid)
983
997
case mProc of
984
998
Nothing -> dispatch (isLocal node (ProcessIdentifier from))
985
999
from node (ProcessInfoNone DiedUnknownId )
@@ -1022,17 +1036,17 @@ ncEffectGetNodeStats :: ProcessId -> NodeId -> NC ()
1022
1036
ncEffectGetNodeStats from _nid = do
1023
1037
node <- ask
1024
1038
ncState <- StateT. get
1025
- nodeState <- liftIO $ readMVar (localState node)
1026
- let localProcesses' = nodeState ^. localProcesses
1027
- stats =
1039
+ nodeState <- liftIO $ withValidLocalState node return
1040
+ let stats =
1028
1041
NodeStats {
1029
1042
nodeStatsNode = localNodeId node
1030
1043
, nodeStatsRegisteredNames = Map. size $ ncState ^. registeredHere
1031
1044
, nodeStatsMonitors = Map. size $ ncState ^. monitors
1032
1045
, nodeStatsLinks = Map. size $ ncState ^. links
1033
- , nodeStatsProcesses = Map. size localProcesses'
1046
+ , nodeStatsProcesses = Map. size (nodeState ^. localProcesses)
1034
1047
}
1035
1048
postAsMessage from stats
1049
+
1036
1050
--------------------------------------------------------------------------------
1037
1051
-- Auxiliary --
1038
1052
--------------------------------------------------------------------------------
@@ -1105,7 +1119,7 @@ unClosure closure = do
1105
1119
isValidLocalIdentifier :: Identifier -> NC Bool
1106
1120
isValidLocalIdentifier ident = do
1107
1121
node <- ask
1108
- liftIO . withMVar (localState node) $ \ nSt ->
1122
+ liftIO . withValidLocalState node $ \ nSt ->
1109
1123
case ident of
1110
1124
NodeIdentifier nid ->
1111
1125
return $ nid == localNodeId node
@@ -1145,8 +1159,8 @@ withLocalProc node pid p =
1145
1159
-- By [Unified: table 6, rule missing_process] messages to dead processes
1146
1160
-- can silently be dropped
1147
1161
let lpid = processLocalId pid in do
1148
- mProc <- withMVar (localState node) $ return . ( ^. localProcessWithId lpid)
1149
- forM_ mProc p
1162
+ withValidLocalState node $ \ vst ->
1163
+ forM_ (vst ^. localProcessWithId lpid) p
1150
1164
1151
1165
--------------------------------------------------------------------------------
1152
1166
-- Accessors --
0 commit comments