Skip to content

Commit b2af3fa

Browse files
authored
Merge pull request #33 from Shimuuar/prepare-release
From/ToPy instancer maybe and release 0.2
2 parents 1b66c72 + d89d118 commit b2af3fa

File tree

10 files changed

+115
-32
lines changed

10 files changed

+115
-32
lines changed

ChangeLog.md

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,10 @@
1-
NEXT_VERSION [..]
1+
0.2 [2025.05.04]
22
----------------
3-
* `FromPy`/`ToPy` instances for text and bytestrings data types.
3+
* `FromPy`/`ToPy` instances added for: `Complex`, both strict and lazy `Text` &
4+
`ByteString`, `ShortByteString`, `Maybe a`
5+
* Module `Python.Inline.Eval` added which support for eval/exec with user
6+
supplied global and local variables.
7+
* QuasiQuotes `Python.Inline.QQ.pycode` added for creating `PyQuote` data type.
48

59
0.1.1.1 [2025.03.10]
610
--------------------

inline-python.cabal

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,7 @@ Cabal-Version: 3.0
22
Build-Type: Simple
33

44
Name: inline-python
5-
Version: 0.1.1.1
5+
Version: 0.2
66
Synopsis: Python interpreter embedded into haskell.
77
Description:
88
This package embeds python interpreter into haskell program and

src/Python/Inline/Eval.hs

Lines changed: 40 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1,25 +1,59 @@
11
{-# LANGUAGE QuasiQuotes #-}
22
{-# LANGUAGE TemplateHaskell #-}
33
-- |
4-
-- Interface to python's @eval@ and @exec@
4+
-- Interface to python's @eval@ and @exec@ which gives programmer
5+
-- control over local and global variables.
56
module Python.Inline.Eval
67
( -- * Python execution
78
eval
89
, exec
910
-- * Source code
1011
, PyQuote(..)
12+
, Code
13+
, codeFromText
14+
, codeFromString
15+
, DictBinder
16+
, bindVar
17+
-- * Variable namespaces
1118
, Namespace(..)
1219
, Main(..)
1320
, Temp(..)
1421
, Dict(..)
1522
, Module(..)
16-
-- ** Data types
17-
, Code
18-
, codeFromText
19-
, codeFromString
20-
, DictBinder
2123
) where
2224

25+
import Data.ByteString.Unsafe qualified as BS
26+
import Data.Text (Text)
27+
import Data.Text.Encoding qualified as T
28+
import Language.C.Inline qualified as C
29+
import Language.C.Inline.Unsafe qualified as CU
30+
2331
import Python.Internal.Types
2432
import Python.Internal.Eval
33+
import Python.Internal.Program
34+
import Python.Inline.Literal
35+
36+
37+
----------------------------------------------------------------
38+
C.context (C.baseCtx <> pyCtx)
39+
C.include "<inline-python.h>"
40+
----------------------------------------------------------------
41+
42+
-- | Bind variable in dictionary
43+
bindVar
44+
:: (ToPy a)
45+
=> Text -- ^ Variable name
46+
-> a -- ^ Variable value
47+
-> DictBinder
48+
bindVar name a = DictBinder $ \p_dict -> runProgram $ do
49+
p_key <- progIOBracket $ BS.unsafeUseAsCString (T.encodeUtf8 name)
50+
p_obj <- takeOwnership =<< progPy (throwOnNULL =<< basicToPy a)
51+
progPy $ do
52+
r <- Py [CU.block| int {
53+
PyObject* p_obj = $(PyObject* p_obj);
54+
return PyDict_SetItemString($(PyObject* p_dict), $(char* p_key), p_obj);
55+
} |]
56+
case r of
57+
0 -> pure ()
58+
_ -> mustThrowPyError
2559

src/Python/Inline/Literal.hs

Lines changed: 44 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -208,17 +208,21 @@ deriving via CDouble instance FromPy Double
208208
instance ToPy Float where basicToPy = basicToPy . float2Double
209209
instance FromPy Float where basicFromPy = fmap double2Float . basicFromPy
210210

211+
-- | @since 0.2
211212
instance ToPy (Complex Float) where
212213
basicToPy (x:+y) = basicToPy $ float2Double x :+ float2Double y
214+
-- | @since 0.2
213215
instance FromPy (Complex Float) where
214216
basicFromPy xy_py = do
215217
x :+ y <- basicFromPy xy_py
216218
return $ double2Float x :+ double2Float y
217219

220+
-- | @since 0.2
218221
instance ToPy (Complex Double) where
219222
basicToPy (x:+y) = Py [CU.exp| PyObject* { PyComplex_FromDoubles($(double x'), $(double y')) } |]
220223
where x' = CDouble x
221224
y' = CDouble y
225+
-- | @since 0.2
222226
instance FromPy (Complex Double) where
223227
basicFromPy xy_py = do
224228
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
412416
d <- basicFromPy p_d
413417
pure (a,b,c,d)
414418

419+
420+
-- | @Nothing@ is encoded as @None@. @Just a@ same as @a@.
421+
--
422+
-- @since 0.2
423+
instance (ToPy a) => ToPy (Maybe a) where
424+
basicToPy Nothing = Py [CU.exp| PyObject* { Py_None } |]
425+
basicToPy (Just a) = basicToPy a
426+
427+
-- | @None@ is decoded as @Nothing@ rest is attempted to be decoded as @a@
428+
--
429+
-- @since 0.2
430+
instance (FromPy a) => FromPy (Maybe a) where
431+
basicFromPy p =
432+
Py [CU.exp| bool { Py_None == $(PyObject *p) } |] >>= \case
433+
0 -> Just <$> basicFromPy p
434+
_ -> pure Nothing
435+
436+
415437
instance (ToPy a) => ToPy [a] where
416438
basicToPy = basicListToPy
417439

@@ -566,7 +588,9 @@ vectorToPy vec = runProgram $ do
566588
n_c = fromIntegral n :: CLLong
567589

568590

569-
-- | @since NEXT_VERSION@. Converted to @bytes@
591+
-- | Converted to @bytes@
592+
--
593+
-- @since 0.2
570594
instance ToPy BS.ByteString where
571595
basicToPy bs = pyIO $ BS.unsafeUseAsCStringLen bs $ \(ptr,len) -> do
572596
let c_len = fromIntegral len :: CLLong
@@ -575,7 +599,9 @@ instance ToPy BS.ByteString where
575599
NULL -> unsafeRunPy mustThrowPyError
576600
_ -> return py
577601

578-
-- | @since NEXT_VERSION@. Accepts @bytes@ and @bytearray@
602+
-- | Accepts @bytes@ and @bytearray@
603+
--
604+
-- @since 0.2
579605
instance FromPy BS.ByteString where
580606
basicFromPy py = pyIO $ do
581607
[CU.exp| int { PyBytes_Check($(PyObject* py)) } |] >>= \case
@@ -595,16 +621,22 @@ instance FromPy BS.ByteString where
595621
copyBytes hs_buf py_buf sz
596622
BS.unsafePackMallocCStringLen (hs_buf, sz)
597623

598-
-- | @since NEXT_VERSION@. Converted to @bytes@
624+
-- | Converted to @bytes@
625+
--
626+
-- @since 0.2
599627
instance ToPy BL.ByteString where
600628
basicToPy = basicToPy . BL.toStrict
601629

602-
-- | @since NEXT_VERSION@. Accepts @bytes@ and @bytearray@
630+
-- | Accepts @bytes@ and @bytearray@
631+
--
632+
-- @since 0.2
603633
instance FromPy BL.ByteString where
604634
basicFromPy = fmap BL.fromStrict . basicFromPy
605635

606636

607-
-- | @since NEXT_VERSION@. Accepts @bytes@ and @bytearray@
637+
-- | Accepts @bytes@ and @bytearray@
638+
--
639+
-- @since 0.2
608640
instance FromPy SBS.ShortByteString where
609641
basicFromPy py = pyIO $ do
610642
[CU.exp| int { PyBytes_Check($(PyObject* py)) } |] >>= \case
@@ -623,7 +655,9 @@ instance FromPy SBS.ShortByteString where
623655
bs <- BS.unsafePackCStringLen (buf, sz)
624656
evaluate $ SBS.toShort bs
625657

626-
-- | @since NEXT_VERSION@. Converted to @bytes@
658+
-- | Converted to @bytes@
659+
--
660+
-- @since 0.2
627661
instance ToPy SBS.ShortByteString where
628662
basicToPy bs = pyIO $ SBS.useAsCStringLen bs $ \(ptr,len) -> do
629663
let c_len = fromIntegral len :: CLLong
@@ -633,7 +667,7 @@ instance ToPy SBS.ShortByteString where
633667
_ -> return py
634668

635669

636-
-- | @since NEXT_VERSION@.
670+
-- | @since 0.2@.
637671
instance ToPy T.Text where
638672
-- NOTE: Is there ore efficient way to access
639673
basicToPy str = pyIO $ BS.unsafeUseAsCStringLen bs $ \(ptr,len) -> do
@@ -645,11 +679,11 @@ instance ToPy T.Text where
645679
where
646680
bs = T.encodeUtf8 str
647681

648-
-- | @since NEXT_VERSION@.
682+
-- | @since 0.2@.
649683
instance ToPy TL.Text where
650684
basicToPy = basicToPy . TL.toStrict
651685

652-
-- | @since NEXT_VERSION@.
686+
-- | @since 0.2@.
653687
instance FromPy T.Text where
654688
basicFromPy py = pyIO $ do
655689
[CU.exp| int { PyUnicode_Check($(PyObject* py)) } |] >>= \case
@@ -660,7 +694,7 @@ instance FromPy T.Text where
660694
return $! T.decodeUtf8Lenient bs
661695
_ -> throwM BadPyType
662696

663-
-- | @since NEXT_VERSION@.
697+
-- | @since 0.2@.
664698
instance FromPy TL.Text where
665699
basicFromPy = fmap TL.fromStrict . basicFromPy
666700

src/Python/Inline/QQ.hs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -29,6 +29,9 @@
2929
-- > do_this()
3030
-- > do_that()
3131
-- > |]
32+
--
33+
-- If control over python's global and local variables is
34+
-- required. APIs from "Python.Inline.Eval" should be used instead.
3235
module Python.Inline.QQ
3336
( pymain
3437
, py_

src/Python/Internal/Eval.hs

Lines changed: 8 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -683,12 +683,13 @@ checkThrowBadPyType = do
683683
--
684684
-- @since 0.2@
685685
class Namespace a where
686-
-- | Returns dictionary object. Caller takes ownership of returned
687-
-- object.
686+
-- | Returns dictionary object. Caller should take ownership of
687+
-- returned object.
688688
basicNamespaceDict :: a -> Py (Ptr PyObject)
689689

690690

691-
-- | Namespace for the top level code execution.
691+
-- | Namespace for the top level code execution. It corresponds to
692+
-- @\__dict\__@ field of a @\__main\__@ module.
692693
--
693694
-- @since 0.2@
694695
data Main = Main
@@ -724,8 +725,8 @@ instance Namespace DictPtr where
724725
basicNamespaceDict (DictPtr p) = p <$ incref p
725726

726727

727-
-- | Newtype wrapper for bare python object. It's assumed to be a
728-
-- dictionary. This is not checked.
728+
-- | Newtype wrapper for python dictionary. It's not checked whether
729+
-- object is actually dictionary.
729730
--
730731
-- @since 0.2@
731732
newtype Dict = Dict PyObject
@@ -757,7 +758,7 @@ instance Namespace Module where
757758
= unsafeWithPyObject d (basicNamespaceDict . ModulePtr)
758759

759760

760-
-- | Evaluate python expression
761+
-- | Evaluate python expression. This is wrapper over python's @eval@.
761762
--
762763
-- @since 0.2@
763764
eval :: (Namespace global, Namespace local)
@@ -788,7 +789,7 @@ eval globals locals q = runProgram $ do
788789
newPyObject p_res
789790
{-# SPECIALIZE eval :: Main -> Temp -> PyQuote -> Py PyObject #-}
790791

791-
-- | Evaluate sequence of python statements
792+
-- | Evaluate sequence of python statements This is wrapper over python's @exec@.
792793
--
793794
-- @since 0.2@
794795
exec :: (Namespace global, Namespace local)

src/Python/Internal/EvalQQ.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -50,8 +50,8 @@ varName :: String -> PyVarName
5050
varName = PyVarName . T.encodeUtf8 . T.pack
5151

5252
unsafeWithPyVarName :: PyVarName -> Program r (Ptr CChar)
53-
unsafeWithPyVarName (PyVarName bs) = Program $ ContT $ \fun ->
54-
Py (BS.unsafeUseAsCString bs $ unsafeRunPy . fun)
53+
unsafeWithPyVarName (PyVarName bs)
54+
= progIOBracket (BS.unsafeUseAsCString bs)
5555

5656

5757
bindVar :: ToPy a => PyVarName -> a -> DictBinder

src/Python/Internal/Program.hs

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,7 @@ module Python.Internal.Program
66
, runProgram
77
, progPy
88
, progIO
9+
, progIOBracket
910
-- * Control flow
1011
, abort
1112
, abortM
@@ -64,6 +65,9 @@ progIO = Program . lift . pyIO
6465
progPy :: Py a -> Program r a
6566
progPy = Program . lift
6667

68+
progIOBracket :: ((a -> IO r) -> IO r) -> Program r a
69+
progIOBracket = coerce
70+
6771
-- | Early exit from continuation monad.
6872
abort :: r -> Program r a
6973
abort r = Program $ ContT $ \_ -> pure r

src/Python/Internal/Types.hs

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -135,7 +135,9 @@ instance PrimMonad Py where
135135
----------------------------------------------------------------
136136

137137
-- | Quasiquoted python code. It contains source code and closure
138-
-- which populates dictionary with local variables.
138+
-- which populates dictionary with local variables. @PyQuote@ value
139+
-- which captures local variables could be created using
140+
-- 'Python.Inline.QQ.pycode' quasiquoter.
139141
--
140142
-- @since 0.2@
141143
data PyQuote = PyQuote
@@ -144,8 +146,7 @@ data PyQuote = PyQuote
144146
}
145147

146148

147-
-- | UTF-8 encoded python source code. Usually it's produced by
148-
-- Template Haskell's 'TH.lift' function.
149+
-- | UTF-8 encoded python source code.
149150
--
150151
-- @since 0.2@
151152
newtype Code = Code BS.ByteString
@@ -165,7 +166,7 @@ codeFromText = Code . T.encodeUtf8
165166
codeFromString :: String -> Code
166167
codeFromString = codeFromText . T.pack
167168

168-
-- | Closure which stores values in provided dictionary
169+
-- | Closure which stores values in provided python dictionary.
169170
--
170171
-- @since 0.2@
171172
newtype DictBinder = DictBinder { bind :: Ptr PyObject -> Py () }

test/TST/Roundtrip.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -73,6 +73,8 @@ tests = testGroup "Roundtrip"
7373
, testRoundtrip @(Int,(Int,Int))
7474
, testRoundtrip @(Int,Int,Int)
7575
, testRoundtrip @(Int,Int,Int,Char)
76+
, testRoundtrip @(Maybe Int)
77+
, testRoundtrip @(Maybe T.Text)
7678
, testRoundtrip @[Int]
7779
, testRoundtrip @[[Int]]
7880
, testRoundtrip @[Complex Double]

0 commit comments

Comments
 (0)