Skip to content

Commit 569a753

Browse files
authored
Merge pull request #24 from Shimuuar/main-deadlovk
Fix deadlock when exception is raised in runInMain
2 parents c11bfe9 + fe21e29 commit 569a753

File tree

4 files changed

+89
-64
lines changed

4 files changed

+89
-64
lines changed

src/Python/Inline/Literal.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -607,7 +607,7 @@ instance (FromPy a1, FromPy a2, ToPy b) => ToPy (a1 -> a2 -> IO b) where
607607

608608
-- | Execute haskell callback function
609609
pyCallback :: Program (Ptr PyObject) (Ptr PyObject) -> IO (Ptr PyObject)
610-
pyCallback io = callbackEnsurePyLock $ unPy $ ensureGIL $ runProgram io `catch` convertHaskell2Py
610+
pyCallback io = callbackEnsurePyLock $ unsafeRunPy $ ensureGIL $ runProgram io `catch` convertHaskell2Py
611611

612612
-- | Load argument from python object for haskell evaluation
613613
loadArg

src/Python/Internal/Eval.hs

Lines changed: 60 additions & 62 deletions
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,7 @@ module Python.Internal.Eval
1515
-- * Evaluator
1616
, runPy
1717
, runPyInMain
18-
, unPy
18+
, unsafeRunPy
1919
-- * GC-related
2020
, newPyObject
2121
-- * C-API wrappers
@@ -41,6 +41,7 @@ import Control.Monad.Catch
4141
import Control.Monad.IO.Class
4242
import Control.Monad.Trans.Cont
4343
import Data.Maybe
44+
import Data.Function
4445
import Foreign.Concurrent qualified as GHC
4546
import Foreign.Ptr
4647
import Foreign.ForeignPtr
@@ -273,13 +274,39 @@ releaseLock tid = readTVar globalPyLock >>= \case
273274
initializePython :: IO ()
274275
-- See NOTE: [Python and threading]
275276
initializePython = [CU.exp| int { Py_IsInitialized() } |] >>= \case
276-
0 | rtsSupportsBoundThreads -> runInBoundThread $ mask_ $ doInializePython
277-
| otherwise -> mask_ $ doInializePython
277+
0 | rtsSupportsBoundThreads -> runInBoundThread $ doInializePython
278+
| otherwise -> doInializePython
278279
_ -> pure ()
279280

280281
-- | Destroy python interpreter.
281282
finalizePython :: IO ()
282-
finalizePython = mask_ doFinalizePython
283+
finalizePython = join $ atomically $ readTVar globalPyState >>= \case
284+
NotInitialized -> throwSTM PythonNotInitialized
285+
InitFailed -> throwSTM PythonIsFinalized
286+
Finalized -> pure $ pure ()
287+
InInitialization -> retry
288+
InFinalization -> retry
289+
-- We can simply call Py_Finalize
290+
Running1 -> checkLock $ [C.block| void {
291+
PyGILState_Ensure();
292+
Py_Finalize();
293+
} |]
294+
-- We need to call Py_Finalize on main thread
295+
RunningN _ eval _ tid_gc -> checkLock $ do
296+
killThread tid_gc
297+
resp <- newEmptyMVar
298+
putMVar eval $ StopReq resp
299+
takeMVar resp
300+
where
301+
checkLock action = readTVar globalPyLock >>= \case
302+
LockUninialized -> throwSTM $ PyInternalError "finalizePython LockUninialized"
303+
LockFinalized -> throwSTM $ PyInternalError "finalizePython LockFinalized"
304+
Locked{} -> retry
305+
LockedByGC -> retry
306+
LockUnlocked -> do
307+
writeTVar globalPyLock LockFinalized
308+
writeTVar globalPyState Finalized
309+
pure action
283310

284311
-- | Bracket which ensures that action is executed with properly
285312
-- initialized interpreter
@@ -303,7 +330,6 @@ doInializePython = do
303330
let fini st = atomically $ do
304331
writeTVar globalPyState $ st
305332
writeTVar globalPyLock $ LockUnlocked
306-
307333
pure $
308334
(mask_ $ if
309335
-- On multithreaded runtime create bound thread to make
@@ -335,22 +361,18 @@ mainThread lock_init lock_eval = do
335361
putMVar lock_init r_init
336362
case r_init of
337363
False -> pure ()
338-
True -> mask_ $ do
339-
let loop
340-
= handle (\InterruptMain -> pure ())
341-
$ takeMVar lock_eval >>= \case
342-
EvalReq py resp -> do
343-
res <- (Right <$> runPy py) `catch` (pure . Left)
344-
putMVar resp res
345-
loop
346-
StopReq resp -> do
347-
[C.block| void {
348-
PyGILState_Ensure();
349-
Py_Finalize();
350-
} |]
351-
putMVar resp ()
352-
loop
353-
364+
True -> mask_ $ fix $ \loop ->
365+
takeMVar lock_eval >>= \case
366+
EvalReq py resp -> do
367+
res <- (Right <$> runPy py) `catch` (pure . Left)
368+
putMVar resp res
369+
loop
370+
StopReq resp -> do
371+
[C.block| void {
372+
PyGILState_Ensure();
373+
Py_Finalize();
374+
} |]
375+
putMVar resp ()
354376

355377

356378
doInializePythonIO :: IO Bool
@@ -401,35 +423,6 @@ doInializePythonIO = do
401423
} |]
402424
return $! r == 0
403425

404-
doFinalizePython :: IO ()
405-
doFinalizePython = join $ atomically $ readTVar globalPyState >>= \case
406-
NotInitialized -> throwSTM PythonNotInitialized
407-
InitFailed -> throwSTM PythonIsFinalized
408-
Finalized -> pure $ pure ()
409-
InInitialization -> retry
410-
InFinalization -> retry
411-
-- We can simply call Py_Finalize
412-
Running1 -> checkLock $ [C.block| void {
413-
PyGILState_Ensure();
414-
Py_Finalize();
415-
} |]
416-
-- We need to call Py_Finalize on main thread
417-
RunningN _ eval _ tid_gc -> checkLock $ do
418-
killThread tid_gc
419-
resp <- newEmptyMVar
420-
putMVar eval $ StopReq resp
421-
takeMVar resp
422-
where
423-
checkLock action = readTVar globalPyLock >>= \case
424-
LockUninialized -> throwSTM $ PyInternalError "doFinalizePython LockUninialized"
425-
LockFinalized -> throwSTM $ PyInternalError "doFinalizePython LockFinalized"
426-
Locked{} -> retry
427-
LockedByGC -> retry
428-
LockUnlocked -> do
429-
writeTVar globalPyLock LockFinalized
430-
writeTVar globalPyState Finalized
431-
pure action
432-
433426

434427
----------------------------------------------------------------
435428
-- Running Py monad
@@ -454,7 +447,7 @@ runPy py
454447
where
455448
-- We check whether interpreter is initialized. Throw exception if
456449
-- it wasn't. Better than segfault isn't it?
457-
go = ensurePyLock $ unPy (ensureGIL py)
450+
go = ensurePyLock $ mask_ $ unsafeRunPy (ensureGIL py)
458451

459452
-- | Same as 'runPy' but will make sure that code is run in python's
460453
-- main thread. It's thread in which python's interpreter was
@@ -464,7 +457,11 @@ runPyInMain :: Py a -> IO a
464457
-- See NOTE: [Python and threading]
465458
runPyInMain py
466459
-- Multithreaded RTS
467-
| rtsSupportsBoundThreads = join $ atomically $ readTVar globalPyState >>= \case
460+
| rtsSupportsBoundThreads = bracket acquireMain releaseMain evalMain
461+
-- Single-threaded RTS
462+
| otherwise = runPy py
463+
where
464+
acquireMain = atomically $ readTVar globalPyState >>= \case
468465
NotInitialized -> throwSTM PythonNotInitialized
469466
InitFailed -> throwSTM PyInitializationFailed
470467
Finalized -> throwSTM PythonIsFinalized
@@ -473,19 +470,20 @@ runPyInMain py
473470
Running1 -> throwSTM $ PyInternalError "runPyInMain: Running1"
474471
RunningN _ eval tid_main _ -> do
475472
acquireLock tid_main
476-
pure
477-
$ flip finally (atomically (releaseLock tid_main))
478-
$ flip onException (throwTo tid_main InterruptMain)
479-
$ do resp <- newEmptyMVar
480-
putMVar eval $ EvalReq py resp
481-
either throwM pure =<< takeMVar resp
482-
-- Single-threaded RTS
483-
| otherwise = runPy py
473+
pure (tid_main, eval)
474+
--
475+
releaseMain (tid_main, _ ) = atomically (releaseLock tid_main)
476+
evalMain (tid_main, eval) = do
477+
r <- mask_ $ do resp <- newEmptyMVar
478+
putMVar eval $ EvalReq py resp
479+
takeMVar resp `onException` throwTo tid_main InterruptMain
480+
either throwM pure r
481+
484482

485483
-- | Execute python action. This function is unsafe and should be only
486484
-- called in thread of interpreter.
487-
unPy :: Py a -> IO a
488-
unPy (Py io) = io
485+
unsafeRunPy :: Py a -> IO a
486+
unsafeRunPy (Py io) = io
489487

490488

491489

test/TST/Run.hs

Lines changed: 24 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,8 @@
22
-- Tests for variable scope and names
33
module TST.Run(tests) where
44

5+
import Control.Concurrent
6+
import Control.Exception
57
import Control.Monad
68
import Control.Monad.IO.Class
79
import Test.Tasty
@@ -19,7 +21,24 @@ tests = testGroup "Run python"
1921
import threading
2022
assert threading.main_thread() == threading.current_thread()
2123
|]
22-
, testCase "Python exceptions are converted" $ runPy $ throwsPy [py_| 1 / 0 |]
24+
, testCase "Python exceptions are converted (py)" $ runPy $ throwsPy [py_| 1 / 0 |]
25+
, testCase "Python exceptions are converted (std)" $ throwsPyIO $ runPy [py_| 1 / 0 |]
26+
, testCase "Python exceptions are converted (main)" $ throwsPyIO $ runPyInMain [py_| 1 / 0 |]
27+
, testCase "Main doesn't deadlock after exception" $ do
28+
throwsPyIO $ runPyInMain [py_| 1 / 0 |]
29+
runPyInMain [py_| assert True |]
30+
-- Here we test that exceptions are really passed to python's thread without running python
31+
, testCase "Exception in runPyInMain works" $ do
32+
lock <- newEmptyMVar
33+
tid <- myThreadId
34+
_ <- forkIO $ takeMVar lock >> throwTo tid Stop
35+
handle (\Stop -> pure ())
36+
$ runPyInMain
37+
$ do liftIO $ putMVar lock ()
38+
liftIO $ threadDelay 10_000_000
39+
error "Should be interrupted"
40+
runPyInMain $ pure ()
41+
--
2342
, testCase "Scope pymain->any" $ runPy $ do
2443
[pymain|
2544
x = 12
@@ -112,3 +131,7 @@ tests = testGroup "Run python"
112131
pass
113132
|]
114133
]
134+
135+
data Stop = Stop
136+
deriving stock Show
137+
deriving anyclass Exception

test/TST/Util.hs

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -12,3 +12,7 @@ throwsPy :: Py () -> Py ()
1212
throwsPy io = (io >> liftIO (assertFailure "Evaluation should raise python exception"))
1313
`catch` (\(_::PyError) -> pure ())
1414

15+
throwsPyIO :: IO () -> IO ()
16+
throwsPyIO io = (io >> assertFailure "Evaluation should raise python exception")
17+
`catch` (\(_::PyError) -> pure ())
18+

0 commit comments

Comments
 (0)