Skip to content

Commit 166bfe2

Browse files
authored
Merge pull request #32 from Shimuuar/explicit-code
Finer grained control over eval/exec
2 parents cbee13b + 51d4e28 commit 166bfe2

File tree

9 files changed

+346
-111
lines changed

9 files changed

+346
-111
lines changed

inline-python.cabal

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -57,7 +57,7 @@ Library
5757
, stm >=2.4
5858
, template-haskell -any
5959
, text >=2
60-
, bytestring
60+
, bytestring >=0.11.2
6161
, exceptions >=0.10
6262
, vector >=0.13
6363
hs-source-dirs: src
@@ -70,6 +70,7 @@ Library
7070
Python.Inline
7171
Python.Inline.Literal
7272
Python.Inline.QQ
73+
Python.Inline.Eval
7374
Python.Inline.Types
7475
Other-modules:
7576
Python.Internal.CAPI

src/Python/Inline/Eval.hs

Lines changed: 25 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,25 @@
1+
{-# LANGUAGE QuasiQuotes #-}
2+
{-# LANGUAGE TemplateHaskell #-}
3+
-- |
4+
-- Interface to python's @eval@ and @exec@
5+
module Python.Inline.Eval
6+
( -- * Python execution
7+
eval
8+
, exec
9+
-- * Source code
10+
, PyQuote(..)
11+
, Namespace(..)
12+
, Main(..)
13+
, Temp(..)
14+
, Dict(..)
15+
, Module(..)
16+
-- ** Data types
17+
, Code
18+
, codeFromText
19+
, codeFromString
20+
, DictBinder
21+
) where
22+
23+
import Python.Internal.Types
24+
import Python.Internal.Eval
25+

src/Python/Inline/QQ.hs

Lines changed: 19 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -34,11 +34,13 @@ module Python.Inline.QQ
3434
, py_
3535
, pye
3636
, pyf
37+
, pycode
3738
) where
3839

3940
import Language.Haskell.TH.Quote
4041

4142
import Python.Internal.EvalQQ
43+
import Python.Internal.Eval
4244

4345

4446
-- | Evaluate sequence of python statements. It works in the same way
@@ -48,7 +50,7 @@ import Python.Internal.EvalQQ
4850
-- It creates value of type @Py ()@
4951
pymain :: QuasiQuoter
5052
pymain = QuasiQuoter
51-
{ quoteExp = \txt -> [| evaluatorPymain $(expQQ Exec txt) |]
53+
{ quoteExp = \txt -> [| exec Main Main $(expQQ Exec txt) |]
5254
, quotePat = error "quotePat"
5355
, quoteType = error "quoteType"
5456
, quoteDec = error "quoteDec"
@@ -61,7 +63,7 @@ pymain = QuasiQuoter
6163
-- It creates value of type @Py ()@
6264
py_ :: QuasiQuoter
6365
py_ = QuasiQuoter
64-
{ quoteExp = \txt -> [| evaluatorPy_ $(expQQ Exec txt) |]
66+
{ quoteExp = \txt -> [| exec Main Temp $(expQQ Exec txt) |]
6567
, quotePat = error "quotePat"
6668
, quoteType = error "quoteType"
6769
, quoteDec = error "quoteDec"
@@ -73,7 +75,7 @@ py_ = QuasiQuoter
7375
-- This quote creates object of type @Py PyObject@
7476
pye :: QuasiQuoter
7577
pye = QuasiQuoter
76-
{ quoteExp = \txt -> [| evaluatorPye $(expQQ Eval txt) |]
78+
{ quoteExp = \txt -> [| eval Main Temp $(expQQ Eval txt) |]
7779
, quotePat = error "quotePat"
7880
, quoteType = error "quoteType"
7981
, quoteDec = error "quoteDec"
@@ -90,3 +92,17 @@ pyf = QuasiQuoter
9092
, quoteType = error "quoteType"
9193
, quoteDec = error "quoteDec"
9294
}
95+
96+
-- | Create quote of python code suitable for use with
97+
-- 'Python.Inline.Eval.exec'
98+
--
99+
-- It creates value of type @PyQuote@
100+
--
101+
-- @since 0.2@
102+
pycode :: QuasiQuoter
103+
pycode = QuasiQuoter
104+
{ quoteExp = \txt -> expQQ Exec txt
105+
, quotePat = error "quotePat"
106+
, quoteType = error "quoteType"
107+
, quoteDec = error "quoteDec"
108+
}

src/Python/Internal/Eval.hs

Lines changed: 164 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -29,6 +29,17 @@ module Python.Internal.Eval
2929
, mustThrowPyError
3030
, checkThrowBadPyType
3131
, throwOnNULL
32+
-- * Exec & eval
33+
, Namespace(..)
34+
, Main(..)
35+
, Temp(..)
36+
, Dict(..)
37+
, DictPtr(..)
38+
, Module(..)
39+
, ModulePtr(..)
40+
, unsafeWithCode
41+
, eval
42+
, exec
3243
-- * Debugging
3344
, debugPrintPy
3445
) where
@@ -42,6 +53,8 @@ import Control.Monad.IO.Class
4253
import Control.Monad.Trans.Cont
4354
import Data.Maybe
4455
import Data.Function
56+
import Data.ByteString qualified as BS
57+
import Data.ByteString.Unsafe qualified as BS
4558
import Foreign.Concurrent qualified as GHC
4659
import Foreign.Ptr
4760
import Foreign.ForeignPtr
@@ -662,6 +675,157 @@ checkThrowBadPyType = do
662675
_ -> throwM BadPyType
663676

664677

678+
----------------------------------------------------------------
679+
-- Eval/exec
680+
----------------------------------------------------------------
681+
682+
-- | Type class for values representing python dictionaries containing
683+
-- global or local variables.
684+
--
685+
-- @since 0.2@
686+
class Namespace a where
687+
-- | Returns dictionary object. Caller takes ownership of returned
688+
-- object.
689+
basicNamespaceDict :: a -> Py (Ptr PyObject)
690+
691+
692+
-- | Namespace for the top level code execution.
693+
--
694+
-- @since 0.2@
695+
data Main = Main
696+
697+
instance Namespace Main where
698+
basicNamespaceDict _ =
699+
throwOnNULL =<< Py [CU.block| PyObject* {
700+
PyObject* main_module = PyImport_AddModule("__main__");
701+
if( PyErr_Occurred() )
702+
return NULL;
703+
PyObject* dict = PyModule_GetDict(main_module);
704+
Py_XINCREF(dict);
705+
return dict;
706+
}|]
707+
708+
709+
-- | Temporary namespace which get destroyed after execution
710+
--
711+
-- @since 0.2@
712+
data Temp = Temp
713+
714+
instance Namespace Temp where
715+
basicNamespaceDict _ = basicNewDict
716+
717+
718+
-- | Newtype wrapper for bare python object. It's assumed to be a
719+
-- dictionary. This is not checked.
720+
--
721+
-- @since 0.2@
722+
newtype DictPtr = DictPtr (Ptr PyObject)
723+
724+
instance Namespace DictPtr where
725+
basicNamespaceDict (DictPtr p) = p <$ incref p
726+
727+
728+
-- | Newtype wrapper for bare python object. It's assumed to be a
729+
-- dictionary. This is not checked.
730+
--
731+
-- @since 0.2@
732+
newtype Dict = Dict PyObject
733+
734+
instance Namespace Dict where
735+
basicNamespaceDict (Dict d)
736+
-- NOTE: We're incrementing counter inside bracket so we're safe.
737+
= unsafeWithPyObject d (basicNamespaceDict . DictPtr)
738+
739+
-- | Newtype wrapper over module object.
740+
--
741+
-- @since 0.2@
742+
newtype ModulePtr = ModulePtr (Ptr PyObject)
743+
744+
instance Namespace ModulePtr where
745+
basicNamespaceDict (ModulePtr p) = do
746+
throwOnNULL =<< Py [CU.block| PyObject* {
747+
PyObject* dict = PyModule_GetDict($(PyObject* p));
748+
Py_XINCREF(dict);
749+
return dict;
750+
}|]
751+
752+
-- | Newtype wrapper over module object.
753+
newtype Module = Module PyObject
754+
755+
instance Namespace Module where
756+
basicNamespaceDict (Module d)
757+
-- NOTE: We're incrementing counter inside bracket so we're safe.
758+
= unsafeWithPyObject d (basicNamespaceDict . ModulePtr)
759+
760+
761+
-- | Evaluate python expression
762+
--
763+
-- @since 0.2@
764+
eval :: (Namespace global, Namespace local)
765+
=> global -- ^ Data type providing global variables dictionary
766+
-> local -- ^ Data type providing local variables dictionary
767+
-> PyQuote -- ^ Source code
768+
-> Py PyObject
769+
eval globals locals q = runProgram $ do
770+
p_py <- unsafeWithCode q.code
771+
p_globals <- takeOwnership =<< progPy (basicNamespaceDict globals)
772+
p_locals <- takeOwnership =<< progPy (basicNamespaceDict locals)
773+
progPy $ do
774+
q.binder.bind p_locals
775+
p_res <- Py [C.block| PyObject* {
776+
PyObject* globals = $(PyObject* p_globals);
777+
PyObject* locals = $(PyObject* p_locals);
778+
// Compile code
779+
PyObject *code = Py_CompileString($(char* p_py), "<interactive>", Py_eval_input);
780+
if( PyErr_Occurred() ) {
781+
return NULL;
782+
}
783+
// Evaluate expression
784+
PyObject* r = PyEval_EvalCode(code, globals, locals);
785+
Py_DECREF(code);
786+
return r;
787+
}|]
788+
checkThrowPyError
789+
newPyObject p_res
790+
{-# SPECIALIZE eval :: Main -> Temp -> PyQuote -> Py PyObject #-}
791+
792+
-- | Evaluate sequence of python statements
793+
--
794+
-- @since 0.2@
795+
exec :: (Namespace global, Namespace local)
796+
=> global -- ^ Data type providing global variables dictionary
797+
-> local -- ^ Data type providing local variables dictionary
798+
-> PyQuote -- ^ Source code
799+
-> Py ()
800+
exec globals locals q = runProgram $ do
801+
p_py <- unsafeWithCode q.code
802+
p_globals <- takeOwnership =<< progPy (basicNamespaceDict globals)
803+
p_locals <- takeOwnership =<< progPy (basicNamespaceDict locals)
804+
progPy $ do
805+
q.binder.bind p_locals
806+
Py[C.block| void {
807+
PyObject* globals = $(PyObject* p_globals);
808+
PyObject* locals = $(PyObject* p_locals);
809+
// Compile code
810+
PyObject *code = Py_CompileString($(char* p_py), "<interactive>", Py_file_input);
811+
if( PyErr_Occurred() ){
812+
return;
813+
}
814+
// Execute statements
815+
PyObject* res = PyEval_EvalCode(code, globals, locals);
816+
Py_XDECREF(res);
817+
Py_DECREF(code);
818+
} |]
819+
checkThrowPyError
820+
{-# SPECIALIZE exec :: Main -> Main -> PyQuote -> Py () #-}
821+
{-# SPECIALIZE exec :: Main -> Temp -> PyQuote -> Py () #-}
822+
823+
-- | Obtain pointer to code
824+
unsafeWithCode :: Code -> Program r (Ptr CChar)
825+
unsafeWithCode (Code bs) = Program $ ContT $ \fun ->
826+
Py (BS.unsafeUseAsCString bs $ unsafeRunPy . fun)
827+
828+
665829
----------------------------------------------------------------
666830
-- Debugging
667831
----------------------------------------------------------------

0 commit comments

Comments
 (0)