@@ -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
4141import Control.Monad.IO.Class
4242import Control.Monad.Trans.Cont
4343import Data.Maybe
44+ import Data.Function
4445import Foreign.Concurrent qualified as GHC
4546import Foreign.Ptr
4647import Foreign.ForeignPtr
@@ -273,13 +274,39 @@ releaseLock tid = readTVar globalPyLock >>= \case
273274initializePython :: IO ()
274275-- See NOTE: [Python and threading]
275276initializePython = [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.
281282finalizePython :: 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
356378doInializePythonIO :: 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]
465458runPyInMain 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
0 commit comments