cpython-3.5.0: Bindings for libpython
Safe HaskellNone
LanguageHaskell2010

CPython.Protocols.Object

Synopsis

Documentation

class Object a Source #

Minimal complete definition

toObject, fromForeignPtr

Instances

Instances details
Object SomeIterator Source # 
Instance details

Defined in CPython.Internal

Object SomeSequence Source # 
Instance details

Defined in CPython.Internal

Object SomeMapping Source # 
Instance details

Defined in CPython.Internal

Object Tuple Source # 
Instance details

Defined in CPython.Internal

Object List Source # 
Instance details

Defined in CPython.Internal

Object Dictionary Source # 
Instance details

Defined in CPython.Internal

Object Type Source # 
Instance details

Defined in CPython.Internal

Object SomeObject Source # 
Instance details

Defined in CPython.Internal

Object ByteArray Source # 
Instance details

Defined in CPython.Types.ByteArray

Object Bytes Source # 
Instance details

Defined in CPython.Types.Bytes

Object Capsule Source # 
Instance details

Defined in CPython.Types.Capsule

Object Cell Source # 
Instance details

Defined in CPython.Types.Cell

Object Code Source # 
Instance details

Defined in CPython.Types.Code

Object Complex Source # 
Instance details

Defined in CPython.Types.Complex

Object Float Source # 
Instance details

Defined in CPython.Types.Float

Object Function Source # 
Instance details

Defined in CPython.Types.Function

Object InstanceMethod Source # 
Instance details

Defined in CPython.Types.InstanceMethod

Object CallableIterator Source # 
Instance details

Defined in CPython.Types.Iterator

Object SequenceIterator Source # 
Instance details

Defined in CPython.Types.Iterator

Object Method Source # 
Instance details

Defined in CPython.Types.Method

Object Slice Source # 
Instance details

Defined in CPython.Types.Slice

Object FrozenSet Source # 
Instance details

Defined in CPython.Types.Set

Object Set Source # 
Instance details

Defined in CPython.Types.Set

Object Unicode Source # 
Instance details

Defined in CPython.Types.Unicode

Object Integer Source # 
Instance details

Defined in CPython.Types.Integer

Object Module Source # 
Instance details

Defined in CPython.Types.Module

Object SomeNumber Source # 
Instance details

Defined in CPython.Protocols.Number

Object Proxy Source # 
Instance details

Defined in CPython.Types.WeakReference

Object Reference Source # 
Instance details

Defined in CPython.Types.WeakReference

class Object a => Concrete a Source #

Minimal complete definition

concreteType

Instances

Instances details
Concrete Tuple Source # 
Instance details

Defined in CPython.Types.Tuple

Methods

concreteType :: Tuple -> Type

Concrete List Source # 
Instance details

Defined in CPython.Types.List

Methods

concreteType :: List -> Type

Concrete Dictionary Source # 
Instance details

Defined in CPython.Types.Dictionary

Concrete Type Source #

Returns True if the first parameter is a subtype of the second parameter.

Instance details

Defined in CPython.Types.Type

Methods

concreteType :: Type -> Type

Concrete ByteArray Source # 
Instance details

Defined in CPython.Types.ByteArray

Concrete Bytes Source # 
Instance details

Defined in CPython.Types.Bytes

Methods

concreteType :: Bytes -> Type

Concrete Capsule Source # 
Instance details

Defined in CPython.Types.Capsule

Concrete Cell Source # 
Instance details

Defined in CPython.Types.Cell

Methods

concreteType :: Cell -> Type

Concrete Code Source # 
Instance details

Defined in CPython.Types.Code

Methods

concreteType :: Code -> Type

Concrete Complex Source # 
Instance details

Defined in CPython.Types.Complex

Concrete Float Source # 
Instance details

Defined in CPython.Types.Float

Methods

concreteType :: Float -> Type

Concrete Function Source # 
Instance details

Defined in CPython.Types.Function

Concrete InstanceMethod Source # 
Instance details

Defined in CPython.Types.InstanceMethod

Concrete CallableIterator Source # 
Instance details

Defined in CPython.Types.Iterator

Concrete SequenceIterator Source # 
Instance details

Defined in CPython.Types.Iterator

Concrete Method Source # 
Instance details

Defined in CPython.Types.Method

Methods

concreteType :: Method -> Type

Concrete Slice Source # 
Instance details

Defined in CPython.Types.Slice

Methods

concreteType :: Slice -> Type

Concrete FrozenSet Source # 
Instance details

Defined in CPython.Types.Set

Concrete Set Source # 
Instance details

Defined in CPython.Types.Set

Methods

concreteType :: Set -> Type

Concrete Unicode Source # 
Instance details

Defined in CPython.Types.Unicode

Concrete Integer Source # 
Instance details

Defined in CPython.Types.Integer

Concrete Module Source # 
Instance details

Defined in CPython.Types.Module

Methods

concreteType :: Module -> Type

data SomeObject Source #

Instances

Instances details
Object SomeObject Source # 
Instance details

Defined in CPython.Internal

Types and casting

getType :: Object self => self -> IO Type Source #

Returns True if inst is an instance of the class cls or a subclass of cls, or False if not. On error, throws an exception. If cls is a type object rather than a class object, isInstance returns True if inst is of type cls. If cls is a tuple, the check will be done against every entry in cls. The result will be True when at least one of the checks returns True, otherwise it will be False. If inst is not a class instance and cls is neither a type object, nor a class object, nor a tuple, inst must have a class attribute ߞ the class relationship of the value of that attribute with cls will be used to determine the result of this function.

Subclass determination is done in a fairly straightforward way, but includes a wrinkle that implementors of extensions to the class system may want to be aware of. If A and B are class objects, B is a subclass of A if it inherits from A either directly or indirectly. If either is not a class object, a more general mechanism is used to determine the class relationship of the two objects. When testing if B is a subclass of A, if A is B, isSubclass returns True. If A and B are different objects, Bߢs bases attribute is searched in a depth-first fashion for A ߞ the presence of the bases attribute is considered sufficient for this determination.

Returns a Type object corresponding to the object type of self. On failure, throws SystemError. This is equivalent to the Python expression type(o).

isInstance :: (Object self, Object cls) => self -> cls -> IO Bool Source #

isSubclass :: (Object derived, Object cls) => derived -> cls -> IO Bool Source #

Returns True if the class derived is identical to or derived from the class cls, otherwise returns False. In case of an error, throws an exception. If cls is a tuple, the check will be done against every entry in cls. The result will be True when at least one of the checks returns True, otherwise it will be False. If either derived or cls is not an actual class object (or tuple), this function uses the generic algorithm described above.

cast :: (Object a, Concrete b) => a -> IO (Maybe b) Source #

Attempt to cast an object to some concrete class. If the object isn't an instance of the class or subclass, returns Nothing.

Attributes

hasAttribute :: Object self => self -> Unicode -> IO Bool Source #

Returns True if self has an attribute with the given name, and False otherwise. This is equivalent to the Python expression hasattr(self, name)

getAttribute :: Object self => self -> Unicode -> IO SomeObject Source #

Retrieve an attribute with the given name from object self. Returns the attribute value on success, and throws an exception on failure. This is the equivalent of the Python expression self.name.

setAttribute :: (Object self, Object v) => self -> Unicode -> v -> IO () Source #

Set the value of the attribute with the given name, for object self, to the value v. THrows an exception on failure. This is the equivalent of the Python statement self.name = v.

deleteAttribute :: Object self => self -> Unicode -> IO () Source #

Delete an attribute with the given name, for object self. Throws an exception on failure. This is the equivalent of the Python statement del self.name.

Display and debugging

print :: Object self => self -> Handle -> IO () Source #

Print repr(self) to a handle.

repr :: Object self => self -> IO Unicode Source #

Compute a string representation of object self, or throw an exception on failure. This is the equivalent of the Python expression repr(self).

ascii :: Object self => self -> IO Unicode Source #

string :: Object self => self -> IO Unicode Source #

Compute a string representation of object self, or throw an exception on failure. This is the equivalent of the Python expression str(self).

bytes :: Object self => self -> IO Bytes Source #

Compute a bytes representation of object self, or throw an exception on failure. This is equivalent to the Python expression bytes(self).

Callables

callable :: Object self => self -> IO Bool Source #

Determine if the object self is callable.

call :: Object self => self -> Tuple -> Dictionary -> IO SomeObject Source #

Call a callable Python object self, with arguments given by the tuple and named arguments given by the dictionary. Returns the result of the call on success, or throws an exception on failure. This is the equivalent of the Python expression self(*args, **kw).

callArgs :: Object self => self -> [SomeObject] -> IO SomeObject Source #

Call a callable Python object self, with arguments given by the list.

callMethod :: Object self => self -> Text -> Tuple -> Dictionary -> IO SomeObject Source #

Call the named method of object self, with arguments given by the tuple and named arguments given by the dictionary. Returns the result of the call on success, or throws an exception on failure. This is the equivalent of the Python expression self.method(args).

callMethodArgs :: Object self => self -> Text -> [SomeObject] -> IO SomeObject Source #

Call the named method of object self, with arguments given by the list. Returns the result of the call on success, or throws an exception on failure. This is the equivalent of the Python expression self.method(args).

Misc

data Comparison Source #

Constructors

LT 
LE 
EQ 
NE 
GT 
GE 

Instances

Instances details
Show Comparison Source # 
Instance details

Defined in CPython.Protocols.Object

richCompare :: (Object a, Object b) => a -> b -> Comparison -> IO Bool Source #

Compare the values of a and b using the specified comparison. If an exception is raised, throws an exception.

toBool :: Object self => self -> IO Bool Source #

Returns True if the object self is considered to be true, and False otherwise. This is equivalent to the Python expression not not self. On failure, throws an exception.

hash :: Object self => self -> IO Integer Source #

Compute and return the hash value of an object self. On failure, throws an exception. This is the equivalent of the Python expression hash(self).

dir :: Object self => self -> IO List Source #

This is equivalent to the Python expression dir(self), returning a (possibly empty) list of strings appropriate for the object argument, or throws an exception if there was an error.

getIterator :: Object self => self -> IO SomeObject Source #

This is equivalent to the Python expression iter(self). It returns a new iterator for the object argument, or the object itself if the object is already an iterator. Throws TypeError if the object cannot be iterated.