cpython-3.8.0: Bindings for libpython
Safe HaskellSafe-Inferred
LanguageHaskell2010

CPython.Simple

Synopsis

Documentation

arg :: ToPy a => a -> Arg Source #

Builds a Python argument from any Haskell type with a ToPy instance

class FromPy a where Source #

FromPy instances indicate that a type can be marshalled from Python to Haskell automatically

For example, FromPy Integer indicates that we know how to take some Python object and convert it into a Haskell Integer. If the Python object is int, then we can cast properly. Failed casts throw a PyCastException

Methods

fromPy :: SomeObject -> IO a Source #

Takes some Python object, and converts it to the corresponding Haskell type by going over FFI. Might throw a PyCastException

Generally you'll only need to call fromPy manually on some type when writing your own FromPy instances for another type

Instances

Instances details
FromPy Text Source # 
Instance details

Defined in CPython.Simple.Instances

FromPy String Source # 
Instance details

Defined in CPython.Simple.Instances

FromPy Integer Source # 
Instance details

Defined in CPython.Simple.Instances

FromPy () Source # 
Instance details

Defined in CPython.Simple.Instances

Methods

fromPy :: SomeObject -> IO () Source #

FromPy Bool Source # 
Instance details

Defined in CPython.Simple.Instances

FromPy Char Source # 
Instance details

Defined in CPython.Simple.Instances

FromPy Double Source # 
Instance details

Defined in CPython.Simple.Instances

FromPy a => FromPy (Maybe a) Source # 
Instance details

Defined in CPython.Simple.Instances

Methods

fromPy :: SomeObject -> IO (Maybe a) Source #

FromPy a => FromPy [a] Source # 
Instance details

Defined in CPython.Simple.Instances

Methods

fromPy :: SomeObject -> IO [a] Source #

(FromPy a, FromPy b) => FromPy (a, b) Source # 
Instance details

Defined in CPython.Simple.Instances

Methods

fromPy :: SomeObject -> IO (a, b) Source #

(FromPy a, FromPy b, FromPy c) => FromPy (a, b, c) Source # 
Instance details

Defined in CPython.Simple.Instances

Methods

fromPy :: SomeObject -> IO (a, b, c) Source #

(FromPy a, FromPy b, FromPy c, FromPy d) => FromPy (a, b, c, d) Source # 
Instance details

Defined in CPython.Simple.Instances

Methods

fromPy :: SomeObject -> IO (a, b, c, d) Source #

data PyCastException Source #

An exception representing a failed cast from a Python object to Haskell value, usually because the expected type of the Python object was not correct.

Carries a String which represents the name of the expected Haskell type which caused a failed cast. If using easyFromPy, this String is found with typeRep

Constructors

PyCastException String 

class ToPy a where Source #

ToPy instances indicate that a type can be marshalled from Haskell to Python automatically

For example, ToPy Integer indicates that we know how to take a Haskell Integer and convert it into a Python int object

Methods

toPy :: a -> IO SomeObject Source #

Takes some Haskell type, and converts it to a Python object by going over FFI

Generally you'll only need to call toPy manually on some type when writing your own ToPy instances for another type

Instances

Instances details
ToPy Text Source # 
Instance details

Defined in CPython.Simple.Instances

Methods

toPy :: Text -> IO SomeObject Source #

ToPy String Source # 
Instance details

Defined in CPython.Simple.Instances

ToPy Integer Source # 
Instance details

Defined in CPython.Simple.Instances

ToPy Bool Source # 
Instance details

Defined in CPython.Simple.Instances

Methods

toPy :: Bool -> IO SomeObject Source #

ToPy Char Source # 
Instance details

Defined in CPython.Simple.Instances

Methods

toPy :: Char -> IO SomeObject Source #

ToPy Double Source # 
Instance details

Defined in CPython.Simple.Instances

ToPy a => ToPy (Maybe a) Source # 
Instance details

Defined in CPython.Simple.Instances

Methods

toPy :: Maybe a -> IO SomeObject Source #

ToPy a => ToPy [a] Source # 
Instance details

Defined in CPython.Simple.Instances

Methods

toPy :: [a] -> IO SomeObject Source #

(ToPy a, ToPy b) => ToPy (a, b) Source # 
Instance details

Defined in CPython.Simple.Instances

Methods

toPy :: (a, b) -> IO SomeObject Source #

(ToPy a, ToPy b, ToPy c) => ToPy (a, b, c) Source # 
Instance details

Defined in CPython.Simple.Instances

Methods

toPy :: (a, b, c) -> IO SomeObject Source #

(ToPy a, ToPy b, ToPy c, ToPy d) => ToPy (a, b, c, d) Source # 
Instance details

Defined in CPython.Simple.Instances

Methods

toPy :: (a, b, c, d) -> IO SomeObject Source #

call Source #

Arguments

:: FromPy a 
=> Text

Python module name

-> Text

Python function name

-> [Arg]

Python function's arguments

-> [(Text, Arg)]

Python function's keyword arguments (kwargs) as (name, value) pairs

-> IO a 

The most common use case of Simple is calling some Python function

For example, if we wanted to wrap Python's random.randint(low, high), we could write this:

randint :: Integer -> Integer -> IO Integer
randint low high =
  call "random" "randint" [arg low, arg high] []

Because of the FromPy instance in call's type signature, we can infer what to do to convert a Python value back into Haskell, if given the type. In this example using random.uniform, although we use a similar definition as for randint, we correct cast to Double instead of Integer

uniform :: Integer -> Integer -> IO Double
uniform low high =
  call "random" "uniform" [arg low, arg high] []

We can also use the TypeApplications language extension to tell call what type to use, if needed

call @Double "random" "uniform" [arg low, arg high] []

Calling a function with mixed positional and keyword arguments is also fairly straightforward.

The example is equivalent to calling pyautogui.moveTo(x, y, duration=seconds)

moveToDuration :: Integer -> Integer -> Double -> IO ()
moveToDuration x y seconds =
  call "pyautogui" "moveTo" [arg x, arg y] [("duration", arg seconds)]

easyFromPy Source #

Arguments

:: (Concrete p, Typeable h) 
=> (p -> IO h)

python from- conversion, e.g. Py.fromFloat

-> Proxy h

proxy for the type being converted to

-> SomeObject

python object to cast from

-> IO h

Haskell value

Helper that takes a conversion function and a Python object, and casts the Python object into a Haskell value.

Lets you define fromPy with just a Python conversion function

We use Proxy to infer the type name for use in case of a failed cast. In the context of defining an instance, this type will be inferrable, so you can just provide a Proxy value

easyToPy Source #

Arguments

:: Object p 
=> (h -> IO p)

python to- conversion, e.g. Py.toFloat

-> h

haskell type being converted

-> IO SomeObject

Python object

Helper that lets you convert a Haskell value to a Python object by providing both a Python conversion function (from the Haskell type, over FFI, to some Python Object) as well as the Haskell value

Lets you define toPy with just a Python conversion function

getAttribute Source #

Arguments

:: FromPy a 
=> Text

module name

-> Text

attribute name

-> IO a 

Get the value of an attribute of some Python module

This example is equivalent to getting random.BPF in Python

getBpf :: IO Integer
getBpf = getAttribute "random" "BPF"

importModule :: Text -> IO Module Source #

Given a Python module name as text, imports it as a Module

Throws an exception if e.g. the module name was misspelled, or isn't installed

initialize :: IO () Source #

Kicks off talking to Python, and will need to be called before using other functions

setAttribute Source #

Arguments

:: ToPy a 
=> Text

module name

-> Text

attribute name

-> a

value to set attribute to

-> IO () 

Set the value of an attribute of some Python module

This example is equivalent to setting random.BPF = n in Python

setBpf :: Integer -> IO ()
setBpf n = setAttribute "random" "BPF" n