diff --git a/ChangeLog.md b/ChangeLog.md index b23d0c2..9f542c3 100644 --- a/ChangeLog.md +++ b/ChangeLog.md @@ -1,6 +1,10 @@ -NEXT_VERSION [..] +0.2 [2025.05.04] ---------------- -* `FromPy`/`ToPy` instances for text and bytestrings data types. +* `FromPy`/`ToPy` instances added for: `Complex`, both strict and lazy `Text` & + `ByteString`, `ShortByteString`, `Maybe a` +* Module `Python.Inline.Eval` added which support for eval/exec with user + supplied global and local variables. +* QuasiQuotes `Python.Inline.QQ.pycode` added for creating `PyQuote` data type. 0.1.1.1 [2025.03.10] -------------------- diff --git a/inline-python.cabal b/inline-python.cabal index c987d45..c3f6148 100644 --- a/inline-python.cabal +++ b/inline-python.cabal @@ -2,7 +2,7 @@ Cabal-Version: 3.0 Build-Type: Simple Name: inline-python -Version: 0.1.1.1 +Version: 0.2 Synopsis: Python interpreter embedded into haskell. Description: This package embeds python interpreter into haskell program and diff --git a/src/Python/Inline/Eval.hs b/src/Python/Inline/Eval.hs index 6bd02af..c05ad02 100644 --- a/src/Python/Inline/Eval.hs +++ b/src/Python/Inline/Eval.hs @@ -1,25 +1,59 @@ {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE TemplateHaskell #-} -- | --- Interface to python's @eval@ and @exec@ +-- Interface to python's @eval@ and @exec@ which gives programmer +-- control over local and global variables. module Python.Inline.Eval ( -- * Python execution eval , exec -- * Source code , PyQuote(..) + , Code + , codeFromText + , codeFromString + , DictBinder + , bindVar + -- * Variable namespaces , Namespace(..) , Main(..) , Temp(..) , Dict(..) , Module(..) - -- ** Data types - , Code - , codeFromText - , codeFromString - , DictBinder ) where +import Data.ByteString.Unsafe qualified as BS +import Data.Text (Text) +import Data.Text.Encoding qualified as T +import Language.C.Inline qualified as C +import Language.C.Inline.Unsafe qualified as CU + import Python.Internal.Types import Python.Internal.Eval +import Python.Internal.Program +import Python.Inline.Literal + + +---------------------------------------------------------------- +C.context (C.baseCtx <> pyCtx) +C.include "" +---------------------------------------------------------------- + +-- | Bind variable in dictionary +bindVar + :: (ToPy a) + => Text -- ^ Variable name + -> a -- ^ Variable value + -> DictBinder +bindVar name a = DictBinder $ \p_dict -> runProgram $ do + p_key <- progIOBracket $ BS.unsafeUseAsCString (T.encodeUtf8 name) + p_obj <- takeOwnership =<< progPy (throwOnNULL =<< basicToPy a) + progPy $ do + r <- Py [CU.block| int { + PyObject* p_obj = $(PyObject* p_obj); + return PyDict_SetItemString($(PyObject* p_dict), $(char* p_key), p_obj); + } |] + case r of + 0 -> pure () + _ -> mustThrowPyError diff --git a/src/Python/Inline/Literal.hs b/src/Python/Inline/Literal.hs index 5338bdf..39d7a34 100644 --- a/src/Python/Inline/Literal.hs +++ b/src/Python/Inline/Literal.hs @@ -208,17 +208,21 @@ deriving via CDouble instance FromPy Double instance ToPy Float where basicToPy = basicToPy . float2Double instance FromPy Float where basicFromPy = fmap double2Float . basicFromPy +-- | @since 0.2 instance ToPy (Complex Float) where basicToPy (x:+y) = basicToPy $ float2Double x :+ float2Double y +-- | @since 0.2 instance FromPy (Complex Float) where basicFromPy xy_py = do x :+ y <- basicFromPy xy_py return $ double2Float x :+ double2Float y +-- | @since 0.2 instance ToPy (Complex Double) where basicToPy (x:+y) = Py [CU.exp| PyObject* { PyComplex_FromDoubles($(double x'), $(double y')) } |] where x' = CDouble x y' = CDouble y +-- | @since 0.2 instance FromPy (Complex Double) where basicFromPy xy_py = do CDouble x <- Py [CU.exp| double { PyComplex_RealAsDouble($(PyObject *xy_py)) } |] @@ -412,6 +416,24 @@ instance (FromPy a, FromPy b, FromPy c, FromPy d) => FromPy (a,b,c,d) where d <- basicFromPy p_d pure (a,b,c,d) + +-- | @Nothing@ is encoded as @None@. @Just a@ same as @a@. +-- +-- @since 0.2 +instance (ToPy a) => ToPy (Maybe a) where + basicToPy Nothing = Py [CU.exp| PyObject* { Py_None } |] + basicToPy (Just a) = basicToPy a + +-- | @None@ is decoded as @Nothing@ rest is attempted to be decoded as @a@ +-- +-- @since 0.2 +instance (FromPy a) => FromPy (Maybe a) where + basicFromPy p = + Py [CU.exp| bool { Py_None == $(PyObject *p) } |] >>= \case + 0 -> Just <$> basicFromPy p + _ -> pure Nothing + + instance (ToPy a) => ToPy [a] where basicToPy = basicListToPy @@ -566,7 +588,9 @@ vectorToPy vec = runProgram $ do n_c = fromIntegral n :: CLLong --- | @since NEXT_VERSION@. Converted to @bytes@ +-- | Converted to @bytes@ +-- +-- @since 0.2 instance ToPy BS.ByteString where basicToPy bs = pyIO $ BS.unsafeUseAsCStringLen bs $ \(ptr,len) -> do let c_len = fromIntegral len :: CLLong @@ -575,7 +599,9 @@ instance ToPy BS.ByteString where NULL -> unsafeRunPy mustThrowPyError _ -> return py --- | @since NEXT_VERSION@. Accepts @bytes@ and @bytearray@ +-- | Accepts @bytes@ and @bytearray@ +-- +-- @since 0.2 instance FromPy BS.ByteString where basicFromPy py = pyIO $ do [CU.exp| int { PyBytes_Check($(PyObject* py)) } |] >>= \case @@ -595,16 +621,22 @@ instance FromPy BS.ByteString where copyBytes hs_buf py_buf sz BS.unsafePackMallocCStringLen (hs_buf, sz) --- | @since NEXT_VERSION@. Converted to @bytes@ +-- | Converted to @bytes@ +-- +-- @since 0.2 instance ToPy BL.ByteString where basicToPy = basicToPy . BL.toStrict --- | @since NEXT_VERSION@. Accepts @bytes@ and @bytearray@ +-- | Accepts @bytes@ and @bytearray@ +-- +-- @since 0.2 instance FromPy BL.ByteString where basicFromPy = fmap BL.fromStrict . basicFromPy --- | @since NEXT_VERSION@. Accepts @bytes@ and @bytearray@ +-- | Accepts @bytes@ and @bytearray@ +-- +-- @since 0.2 instance FromPy SBS.ShortByteString where basicFromPy py = pyIO $ do [CU.exp| int { PyBytes_Check($(PyObject* py)) } |] >>= \case @@ -623,7 +655,9 @@ instance FromPy SBS.ShortByteString where bs <- BS.unsafePackCStringLen (buf, sz) evaluate $ SBS.toShort bs --- | @since NEXT_VERSION@. Converted to @bytes@ +-- | Converted to @bytes@ +-- +-- @since 0.2 instance ToPy SBS.ShortByteString where basicToPy bs = pyIO $ SBS.useAsCStringLen bs $ \(ptr,len) -> do let c_len = fromIntegral len :: CLLong @@ -633,7 +667,7 @@ instance ToPy SBS.ShortByteString where _ -> return py --- | @since NEXT_VERSION@. +-- | @since 0.2@. instance ToPy T.Text where -- NOTE: Is there ore efficient way to access basicToPy str = pyIO $ BS.unsafeUseAsCStringLen bs $ \(ptr,len) -> do @@ -645,11 +679,11 @@ instance ToPy T.Text where where bs = T.encodeUtf8 str --- | @since NEXT_VERSION@. +-- | @since 0.2@. instance ToPy TL.Text where basicToPy = basicToPy . TL.toStrict --- | @since NEXT_VERSION@. +-- | @since 0.2@. instance FromPy T.Text where basicFromPy py = pyIO $ do [CU.exp| int { PyUnicode_Check($(PyObject* py)) } |] >>= \case @@ -660,7 +694,7 @@ instance FromPy T.Text where return $! T.decodeUtf8Lenient bs _ -> throwM BadPyType --- | @since NEXT_VERSION@. +-- | @since 0.2@. instance FromPy TL.Text where basicFromPy = fmap TL.fromStrict . basicFromPy diff --git a/src/Python/Inline/QQ.hs b/src/Python/Inline/QQ.hs index 7cb61d4..adce6bf 100644 --- a/src/Python/Inline/QQ.hs +++ b/src/Python/Inline/QQ.hs @@ -29,6 +29,9 @@ -- > do_this() -- > do_that() -- > |] +-- +-- If control over python's global and local variables is +-- required. APIs from "Python.Inline.Eval" should be used instead. module Python.Inline.QQ ( pymain , py_ diff --git a/src/Python/Internal/Eval.hs b/src/Python/Internal/Eval.hs index 2982833..6b4d182 100644 --- a/src/Python/Internal/Eval.hs +++ b/src/Python/Internal/Eval.hs @@ -683,12 +683,13 @@ checkThrowBadPyType = do -- -- @since 0.2@ class Namespace a where - -- | Returns dictionary object. Caller takes ownership of returned - -- object. + -- | Returns dictionary object. Caller should take ownership of + -- returned object. basicNamespaceDict :: a -> Py (Ptr PyObject) --- | Namespace for the top level code execution. +-- | Namespace for the top level code execution. It corresponds to +-- @\__dict\__@ field of a @\__main\__@ module. -- -- @since 0.2@ data Main = Main @@ -724,8 +725,8 @@ instance Namespace DictPtr where basicNamespaceDict (DictPtr p) = p <$ incref p --- | Newtype wrapper for bare python object. It's assumed to be a --- dictionary. This is not checked. +-- | Newtype wrapper for python dictionary. It's not checked whether +-- object is actually dictionary. -- -- @since 0.2@ newtype Dict = Dict PyObject @@ -757,7 +758,7 @@ instance Namespace Module where = unsafeWithPyObject d (basicNamespaceDict . ModulePtr) --- | Evaluate python expression +-- | Evaluate python expression. This is wrapper over python's @eval@. -- -- @since 0.2@ eval :: (Namespace global, Namespace local) @@ -788,7 +789,7 @@ eval globals locals q = runProgram $ do newPyObject p_res {-# SPECIALIZE eval :: Main -> Temp -> PyQuote -> Py PyObject #-} --- | Evaluate sequence of python statements +-- | Evaluate sequence of python statements This is wrapper over python's @exec@. -- -- @since 0.2@ exec :: (Namespace global, Namespace local) diff --git a/src/Python/Internal/EvalQQ.hs b/src/Python/Internal/EvalQQ.hs index ee475a6..3a1948b 100644 --- a/src/Python/Internal/EvalQQ.hs +++ b/src/Python/Internal/EvalQQ.hs @@ -50,8 +50,8 @@ varName :: String -> PyVarName varName = PyVarName . T.encodeUtf8 . T.pack unsafeWithPyVarName :: PyVarName -> Program r (Ptr CChar) -unsafeWithPyVarName (PyVarName bs) = Program $ ContT $ \fun -> - Py (BS.unsafeUseAsCString bs $ unsafeRunPy . fun) +unsafeWithPyVarName (PyVarName bs) + = progIOBracket (BS.unsafeUseAsCString bs) bindVar :: ToPy a => PyVarName -> a -> DictBinder diff --git a/src/Python/Internal/Program.hs b/src/Python/Internal/Program.hs index 1152285..305d3f9 100644 --- a/src/Python/Internal/Program.hs +++ b/src/Python/Internal/Program.hs @@ -6,6 +6,7 @@ module Python.Internal.Program , runProgram , progPy , progIO + , progIOBracket -- * Control flow , abort , abortM @@ -64,6 +65,9 @@ progIO = Program . lift . pyIO progPy :: Py a -> Program r a progPy = Program . lift +progIOBracket :: ((a -> IO r) -> IO r) -> Program r a +progIOBracket = coerce + -- | Early exit from continuation monad. abort :: r -> Program r a abort r = Program $ ContT $ \_ -> pure r diff --git a/src/Python/Internal/Types.hs b/src/Python/Internal/Types.hs index d3db0f6..f617602 100644 --- a/src/Python/Internal/Types.hs +++ b/src/Python/Internal/Types.hs @@ -135,7 +135,9 @@ instance PrimMonad Py where ---------------------------------------------------------------- -- | Quasiquoted python code. It contains source code and closure --- which populates dictionary with local variables. +-- which populates dictionary with local variables. @PyQuote@ value +-- which captures local variables could be created using +-- 'Python.Inline.QQ.pycode' quasiquoter. -- -- @since 0.2@ data PyQuote = PyQuote @@ -144,8 +146,7 @@ data PyQuote = PyQuote } --- | UTF-8 encoded python source code. Usually it's produced by --- Template Haskell's 'TH.lift' function. +-- | UTF-8 encoded python source code. -- -- @since 0.2@ newtype Code = Code BS.ByteString @@ -165,7 +166,7 @@ codeFromText = Code . T.encodeUtf8 codeFromString :: String -> Code codeFromString = codeFromText . T.pack --- | Closure which stores values in provided dictionary +-- | Closure which stores values in provided python dictionary. -- -- @since 0.2@ newtype DictBinder = DictBinder { bind :: Ptr PyObject -> Py () } diff --git a/test/TST/Roundtrip.hs b/test/TST/Roundtrip.hs index 4bdc29a..2079e26 100644 --- a/test/TST/Roundtrip.hs +++ b/test/TST/Roundtrip.hs @@ -73,6 +73,8 @@ tests = testGroup "Roundtrip" , testRoundtrip @(Int,(Int,Int)) , testRoundtrip @(Int,Int,Int) , testRoundtrip @(Int,Int,Int,Char) + , testRoundtrip @(Maybe Int) + , testRoundtrip @(Maybe T.Text) , testRoundtrip @[Int] , testRoundtrip @[[Int]] , testRoundtrip @[Complex Double]