Skip to content

Commit 9efdb83

Browse files
authored
Merge pull request #20 from Shimuuar/exceptions
Rework exceptions
2 parents 81cfcc4 + 7715eac commit 9efdb83

File tree

10 files changed

+115
-73
lines changed

10 files changed

+115
-73
lines changed

inline-python.cabal

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -66,10 +66,10 @@ Library
6666
pkgconfig-depends: python3-embed
6767
--
6868
Exposed-modules:
69+
Python.Inline
6970
Python.Inline.Literal
7071
Python.Inline.QQ
71-
Python.Inline
72-
Python.Types
72+
Python.Inline.Types
7373
Other-modules:
7474
Python.Internal.CAPI
7575
Python.Internal.Eval

src/Python/Inline.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -55,8 +55,8 @@ module Python.Inline
5555
, FromPy
5656
) where
5757

58-
import Python.Types
5958
import Python.Inline.Literal
59+
import Python.Internal.Types
6060
import Python.Internal.Eval
6161

6262

src/Python/Inline/Literal.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,6 @@ import GHC.Float (float2Double, double2Float)
2828
import Language.C.Inline qualified as C
2929
import Language.C.Inline.Unsafe qualified as CU
3030

31-
import Python.Types
3231
import Python.Internal.Types
3332
import Python.Internal.Eval
3433
import Python.Internal.CAPI
@@ -104,7 +103,7 @@ fromPy' py = unsafeWithPyObject py basicFromPy
104103
-- | Convert haskell value to a python object.
105104
toPy :: ToPy a => a -> Py PyObject
106105
toPy a = basicToPy a >>= \case
107-
NULL -> throwM =<< convertPy2Haskell
106+
NULL -> mustThrowPyError
108107
p -> newPyObject p
109108

110109

src/Python/Types.hs renamed to src/Python/Inline/Types.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
-- |
22
-- Data types and utilities.
3-
module Python.Types
3+
module Python.Inline.Types
44
( -- * @Py@ monad
55
Py
66
, runPy

src/Python/Internal/Eval.hs

Lines changed: 35 additions & 50 deletions
Original file line numberDiff line numberDiff line change
@@ -40,6 +40,7 @@ import Control.Monad
4040
import Control.Monad.Catch
4141
import Control.Monad.IO.Class
4242
import Control.Monad.Trans.Cont
43+
import Data.Maybe
4344
import Foreign.Concurrent qualified as GHC
4445
import Foreign.Ptr
4546
import Foreign.ForeignPtr
@@ -53,6 +54,7 @@ import System.IO.Unsafe
5354
import Language.C.Inline qualified as C
5455
import Language.C.Inline.Unsafe qualified as CU
5556

57+
import Python.Internal.CAPI
5658
import Python.Internal.Types
5759
import Python.Internal.Util
5860
import Python.Internal.Program
@@ -231,8 +233,8 @@ callbackEnsurePyLock action = do
231233

232234
acquireLock :: ThreadId -> STM ()
233235
acquireLock tid = readTVar globalPyLock >>= \case
234-
LockUninialized -> error "Python is not started"
235-
LockFinalized -> error "Python is already stopped"
236+
LockUninialized -> throwSTM PythonNotInitialized
237+
LockFinalized -> throwSTM PythonIsFinalized
236238
LockedByGC -> retry
237239
LockUnlocked -> writeTVar globalPyLock $ Locked tid []
238240
Locked t xs
@@ -241,20 +243,20 @@ acquireLock tid = readTVar globalPyLock >>= \case
241243

242244
grabLock :: ThreadId -> STM ()
243245
grabLock tid = readTVar globalPyLock >>= \case
244-
LockUninialized -> error "Python is not started"
245-
LockFinalized -> error "Python is already stopped"
246+
LockUninialized -> throwSTM PythonNotInitialized
247+
LockFinalized -> throwSTM PythonIsFinalized
246248
LockedByGC -> retry
247249
LockUnlocked -> writeTVar globalPyLock $ Locked tid []
248250
Locked t xs -> writeTVar globalPyLock $ Locked tid (t : xs)
249251

250252
releaseLock :: ThreadId -> STM ()
251253
releaseLock tid = readTVar globalPyLock >>= \case
252-
LockUninialized -> error "Python is not started"
253-
LockFinalized -> error "Python is already stopped"
254-
LockUnlocked -> error "INTERNAL ERROR releasing unlocked"
255-
LockedByGC -> error "INTERNAL ERROR lock held by GC"
254+
LockUninialized -> throwSTM PythonNotInitialized
255+
LockFinalized -> throwSTM PythonIsFinalized
256+
LockUnlocked -> throwSTM $ PyInternalError "releaseLock: releasing LockUnlocked"
257+
LockedByGC -> throwSTM $ PyInternalError "releaseLock: releasing LockedByGC"
256258
Locked t xs
257-
| t /= tid -> error "INTERNAL ERROR releasing wrong lock"
259+
| t /= tid -> throwSTM $ PyInternalError "releaseLock: releasing wrong lock"
258260
| otherwise -> writeTVar globalPyLock $! case xs of
259261
[] -> LockUnlocked
260262
t':ts -> Locked t' ts
@@ -290,8 +292,8 @@ doInializePython = do
290292
-- First we need to grab global python lock on haskell side
291293
join $ atomically $ do
292294
readTVar globalPyState >>= \case
293-
Finalized -> error "Python was already finalized"
294-
InitFailed -> error "Python was unable to initialize"
295+
Finalized -> throwSTM PythonNotInitialized
296+
InitFailed -> throwSTM PythonIsFinalized
295297
InInitialization -> retry
296298
InFinalization -> retry
297299
Running1{} -> pure $ pure ()
@@ -401,8 +403,8 @@ doInializePythonIO = do
401403

402404
doFinalizePython :: IO ()
403405
doFinalizePython = join $ atomically $ readTVar globalPyState >>= \case
404-
NotInitialized -> error "Python is not initialized"
405-
InitFailed -> error "Python failed to initialize"
406+
NotInitialized -> throwSTM PythonNotInitialized
407+
InitFailed -> throwSTM PythonIsFinalized
406408
Finalized -> pure $ pure ()
407409
InInitialization -> retry
408410
InFinalization -> retry
@@ -419,8 +421,8 @@ doFinalizePython = join $ atomically $ readTVar globalPyState >>= \case
419421
takeMVar resp
420422
where
421423
checkLock action = readTVar globalPyLock >>= \case
422-
LockUninialized -> error "Internal error: Lock not initialized"
423-
LockFinalized -> error "Internal error: Lock is already finalized"
424+
LockUninialized -> throwSTM $ PyInternalError "doFinalizePython LockUninialized"
425+
LockFinalized -> throwSTM $ PyInternalError "doFinalizePython LockFinalized"
424426
Locked{} -> retry
425427
LockedByGC -> retry
426428
LockUnlocked -> do
@@ -459,12 +461,12 @@ runPyInMain :: Py a -> IO a
459461
runPyInMain py
460462
-- Multithreaded RTS
461463
| rtsSupportsBoundThreads = join $ atomically $ readTVar globalPyState >>= \case
462-
NotInitialized -> error "Python is not initialized"
463-
InitFailed -> error "Python failed to initialize"
464-
Finalized -> error "Python is already finalized"
464+
NotInitialized -> throwSTM PythonNotInitialized
465+
InitFailed -> throwSTM PyInitializationFailed
466+
Finalized -> throwSTM PythonIsFinalized
465467
InInitialization -> retry
466468
InFinalization -> retry
467-
Running1 -> error "INTERNAL ERROR"
469+
Running1 -> throwSTM $ PyInternalError "runPyInMain: Running1"
468470
RunningN _ eval tid_main _ -> do
469471
acquireLock tid_main
470472
pure
@@ -572,10 +574,9 @@ convertHaskell2Py err = Py $ do
572574

573575
-- | Convert python exception to haskell exception. Should only be
574576
-- called if there's unhandled python exception. Clears exception.
575-
convertPy2Haskell :: Py PyError
577+
convertPy2Haskell :: Py PyException
576578
convertPy2Haskell = runProgram $ do
577579
p_errors <- withPyAllocaArray @(Ptr PyObject) 3
578-
p_len <- withPyAlloca @CLong
579580
-- Fetch error indicator
580581
(p_type, p_value) <- progIO $ do
581582
[CU.block| void {
@@ -587,48 +588,32 @@ convertPy2Haskell = runProgram $ do
587588
-- Traceback is not used ATM
588589
pure (p_type,p_value)
589590
-- Convert exception type and value to strings.
590-
let pythonStr p = do
591-
p_str <- progIO [CU.block| PyObject* {
592-
PyObject *s = PyObject_Str($(PyObject *p));
593-
if( PyErr_Occurred() ) {
594-
PyErr_Clear();
595-
}
596-
return s;
597-
} |]
598-
case p_str of
599-
NULL -> abort UncovertablePyError
600-
_ -> pure p_str
601-
s_type <- takeOwnership =<< pythonStr p_type
602-
s_value <- takeOwnership =<< pythonStr p_value
603-
-- Convert to haskell strings
604-
let toString p = do
605-
c_str <- [CU.block| const char* {
606-
const char* s = PyUnicode_AsUTF8AndSize($(PyObject *p), $(long *p_len));
607-
if( PyErr_Occurred() ) {
608-
PyErr_Clear();
609-
}
610-
return s;
611-
} |]
612-
case c_str of
613-
NULL -> pure ""
614-
_ -> peekCString c_str
615-
progIO $ PyError <$> toString s_type <*> toString s_value
616-
591+
progPy $ do
592+
s_type <- pyobjectStrAsHask p_type
593+
s_value <- pyobjectStrAsHask p_value
594+
incref p_value
595+
exc <- newPyObject p_value
596+
let bad_str = "__str__ call failed"
597+
pure $ PyException
598+
{ ty = fromMaybe bad_str s_type
599+
, str = fromMaybe bad_str s_value
600+
, exception = exc
601+
}
617602

618603
-- | Throw python error as haskell exception if it's raised.
619604
checkThrowPyError :: Py ()
620605
checkThrowPyError =
621606
Py [CU.exp| PyObject* { PyErr_Occurred() } |] >>= \case
622607
NULL -> pure ()
623-
_ -> throwM =<< convertPy2Haskell
608+
_ -> throwM . PyError =<< convertPy2Haskell
624609

625610
-- | Throw python error as haskell exception if it's raised. If it's
626611
-- not that internal error. Another exception will be raised
627612
mustThrowPyError :: Py a
628613
mustThrowPyError =
629614
Py [CU.exp| PyObject* { PyErr_Occurred() } |] >>= \case
630615
NULL -> error $ "mustThrowPyError: no python exception raised."
631-
_ -> throwM =<< convertPy2Haskell
616+
_ -> throwM . PyError =<< convertPy2Haskell
632617

633618
-- | Calls mustThrowPyError if pointer is null or returns it unchanged
634619
throwOnNULL :: Ptr PyObject -> Py (Ptr PyObject)

src/Python/Internal/EvalQQ.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,7 @@ module Python.Internal.EvalQQ
1313
) where
1414

1515
import Control.Monad.IO.Class
16+
import Control.Monad.Catch
1617
import Data.Bits
1718
import Data.Char
1819
import Data.List (intercalate)
@@ -29,7 +30,6 @@ import Language.C.Inline.Unsafe qualified as CU
2930
import Language.Haskell.TH.Lib qualified as TH
3031
import Language.Haskell.TH.Syntax qualified as TH
3132

32-
import Python.Types
3333
import Python.Internal.Types
3434
import Python.Internal.Program
3535
import Python.Internal.Eval
@@ -125,7 +125,7 @@ evaluatorPyf getSource = runProgram $ do
125125
pyExecExpr p_globals p_locals =<< getSource p_kwargs
126126
-- Look up function
127127
p_fun <- getFunctionObject p_locals >>= \case
128-
NULL -> error "INTERNAL ERROR: _inline_python_ must be present"
128+
NULL -> throwM $ PyInternalError "_inline_python_ must be present"
129129
p -> pure p
130130
-- Call python function we just constructed
131131
newPyObject =<< throwOnNULL =<< basicCallKwdOnly p_fun p_kwargs
@@ -204,7 +204,7 @@ expQQ mode qq_src = do
204204
]
205205
case code of
206206
ExitSuccess -> pure $ words stdout
207-
ExitFailure{} -> error stderr
207+
ExitFailure{} -> fail stderr
208208
let args = [ [| basicBindInDict $(TH.lift nm) $(TH.dyn (chop nm)) |]
209209
| nm <- antis
210210
]

src/Python/Internal/Program.hs

Lines changed: 46 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE QuasiQuotes #-}
2+
{-# LANGUAGE TemplateHaskell #-}
13
-- |
24
module Python.Internal.Program
35
( Program(..)
@@ -7,6 +9,7 @@ module Python.Internal.Program
79
-- * Control flow
810
, abort
911
, abortM
12+
, abortOnNull
1013
, checkNull
1114
, finallyProg
1215
, onExceptionProg
@@ -17,8 +20,11 @@ module Python.Internal.Program
1720
, withPyCString
1821
, withPyCStringLen
1922
, withPyWCString
23+
-- * Helpers
24+
, pyobjectStrAsHask
2025
) where
2126

27+
import Control.Monad
2228
import Control.Monad.Trans.Cont
2329
import Control.Monad.Trans.Class
2430
import Control.Monad.Catch
@@ -30,10 +36,18 @@ import Foreign.C.String
3036
import Foreign.C.Types
3137
import Foreign.Storable
3238

39+
import Language.C.Inline qualified as C
40+
import Language.C.Inline.Unsafe qualified as CU
41+
3342
import Python.Internal.Types
3443
import Python.Internal.Util
3544
import Python.Internal.CAPI
3645

46+
----------------------------------------------------------------
47+
C.context (C.baseCtx <> pyCtx)
48+
C.include "<inline-python.h>"
49+
----------------------------------------------------------------
50+
3751

3852
-- | This monad wraps 'Py' into 'ContT' in order get early exit,
3953
-- applying @finally@ while avoiding building huge ladders.
@@ -58,11 +72,15 @@ abort r = Program $ ContT $ \_ -> pure r
5872
abortM :: Py r -> Program r a
5973
abortM m = Program $ ContT $ \_ -> m
6074

75+
-- | Perform early exit if pointer is null
76+
abortOnNull :: r -> Py (Ptr a) -> Program r (Ptr a)
77+
abortOnNull r action = Program $ ContT $ \cnt -> action >>= \case
78+
NULL -> pure r
79+
p -> cnt p
80+
6181
-- | If result of computation is NULL return NULL immediately.
6282
checkNull :: Py (Ptr a) -> Program (Ptr a) (Ptr a)
63-
checkNull action = Program $ ContT $ \cnt -> action >>= \case
64-
NULL -> pure nullPtr
65-
p -> cnt p
83+
checkNull = abortOnNull nullPtr
6684

6785
-- | Evaluate finalizer even if exception is thrown.
6886
finallyProg
@@ -99,3 +117,28 @@ withPyWCString = coerce (withWCString @r)
99117

100118
withPyCStringLen :: forall r. String -> Program r CStringLen
101119
withPyCStringLen = coerce (withCStringLen @r)
120+
121+
122+
----------------------------------------------------------------
123+
-- More complicated helpers
124+
----------------------------------------------------------------
125+
126+
-- | Call @__str__@ method of object and return haskell
127+
-- string. Returns Nothing if exception was raisede
128+
pyobjectStrAsHask :: Ptr PyObject -> Py (Maybe String)
129+
pyobjectStrAsHask p_obj = runProgram $ do
130+
p_str <- takeOwnership <=< abortOnNull Nothing $ Py [CU.block| PyObject* {
131+
PyObject *s = PyObject_Str($(PyObject *p_obj));
132+
if( PyErr_Occurred() ) {
133+
PyErr_Clear();
134+
}
135+
return s;
136+
} |]
137+
c_str <- abortOnNull Nothing $ Py [CU.block| const char* {
138+
const char* s = PyUnicode_AsUTF8($(PyObject *p_str));
139+
if( PyErr_Occurred() ) {
140+
PyErr_Clear();
141+
}
142+
return s;
143+
} |]
144+
progIO $ Just <$> peekCString c_str

0 commit comments

Comments
 (0)