Safe Haskell | None |
---|---|
Language | Haskell2010 |
CPython.Types
Synopsis
- data ByteArray
- data Bytes
- data Capsule
- data Cell
- data Code
- data Complex
- data Dictionary
- data Exception
- data Float
- data Function
- data InstanceMethod
- data Integer
- data SequenceIterator
- data CallableIterator
- data List
- data Method
- data Module
- class Object a => AnySet a
- data Set
- data FrozenSet
- data Slice
- data Tuple
- data Type
- data Unicode
- data Reference
- data Proxy
- byteArrayType :: Type
- bytesType :: Type
- capsuleType :: Type
- cellType :: Type
- codeType :: Type
- complexType :: Type
- dictionaryType :: Type
- floatType :: Type
- functionType :: Type
- instanceMethodType :: Type
- integerType :: Type
- sequenceIteratorType :: Type
- callableIteratorType :: Type
- listType :: Type
- methodType :: Type
- moduleType :: Type
- setType :: Type
- frozenSetType :: Type
- sliceType :: Type
- tupleType :: Type
- typeType :: Type
- unicodeType :: Type
- toByteArray :: ByteString -> IO ByteArray
- fromByteArray :: ByteArray -> IO ByteString
- toBytes :: ByteString -> IO Bytes
- fromBytes :: Bytes -> IO ByteString
- toComplex :: Complex Double -> IO Complex
- fromComplex :: Complex -> IO (Complex Double)
- toFloat :: Double -> IO Float
- fromFloat :: Float -> IO Double
- toInteger :: Integer -> IO Integer
- fromInteger :: Integer -> IO Integer
- toList :: [SomeObject] -> IO List
- iterableToList :: Object iter => iter -> IO List
- fromList :: List -> IO [SomeObject]
- toSet :: [SomeObject] -> IO Set
- toFrozenSet :: [SomeObject] -> IO FrozenSet
- iterableToSet :: Object obj => obj -> IO Set
- iterableToFrozenSet :: Object obj => obj -> IO FrozenSet
- fromSet :: AnySet set => set -> IO [SomeObject]
- toTuple :: [SomeObject] -> IO Tuple
- iterableToTuple :: Object iter => iter -> IO Tuple
- fromTuple :: Tuple -> IO [SomeObject]
- toUnicode :: Text -> IO Unicode
- fromUnicode :: Unicode -> IO Text
Types and classes
Instances
Sequence ByteArray Source # | |
Defined in CPython.Protocols.Sequence Methods toSequence :: ByteArray -> SomeSequence Source # | |
Concrete ByteArray Source # | |
Defined in CPython.Types.ByteArray Methods concreteType :: ByteArray -> Type | |
Object ByteArray Source # | |
Defined in CPython.Types.ByteArray Methods toObject :: ByteArray -> SomeObject Source # |
Instances
Sequence Bytes Source # | |
Defined in CPython.Protocols.Sequence Methods toSequence :: Bytes -> SomeSequence Source # | |
Concrete Bytes Source # | |
Defined in CPython.Types.Bytes Methods concreteType :: Bytes -> Type | |
Object Bytes Source # | |
Defined in CPython.Types.Bytes |
Instances
Concrete Capsule Source # | |
Defined in CPython.Types.Capsule Methods concreteType :: Capsule -> Type | |
Object Capsule Source # | |
Defined in CPython.Types.Capsule |
Instances
Concrete Cell Source # | |
Defined in CPython.Types.Cell Methods concreteType :: Cell -> Type | |
Object Cell Source # | |
Defined in CPython.Types.Cell |
Instances
Concrete Code Source # | |
Defined in CPython.Types.Code Methods concreteType :: Code -> Type | |
Object Code Source # | |
Defined in CPython.Types.Code |
Instances
Concrete Complex Source # | |
Defined in CPython.Types.Complex Methods concreteType :: Complex -> Type | |
Object Complex Source # | |
Defined in CPython.Types.Complex | |
Number Complex Source # | |
Defined in CPython.Protocols.Number Methods toNumber :: Complex -> SomeNumber Source # |
data Dictionary Source #
Instances
Mapping Dictionary Source # | |
Defined in CPython.Protocols.Mapping Methods toMapping :: Dictionary -> SomeMapping Source # | |
Concrete Dictionary Source # | |
Defined in CPython.Types.Dictionary Methods concreteType :: Dictionary -> Type | |
Object Dictionary Source # | |
Defined in CPython.Internal Methods toObject :: Dictionary -> SomeObject Source # |
Instances
Show Exception Source # | |
Exception Exception Source # | |
Defined in CPython.Internal Methods toException :: Exception -> SomeException # fromException :: SomeException -> Maybe Exception # displayException :: Exception -> String # |
Instances
Concrete Float Source # | |
Defined in CPython.Types.Float Methods concreteType :: Float -> Type | |
Object Float Source # | |
Defined in CPython.Types.Float | |
Number Float Source # | |
Defined in CPython.Protocols.Number Methods toNumber :: Float -> SomeNumber Source # |
Instances
Concrete Function Source # | |
Defined in CPython.Types.Function Methods concreteType :: Function -> Type | |
Object Function Source # | |
Defined in CPython.Types.Function |
data InstanceMethod Source #
Instances
Concrete InstanceMethod Source # | |
Defined in CPython.Types.InstanceMethod Methods concreteType :: InstanceMethod -> Type | |
Object InstanceMethod Source # | |
Defined in CPython.Types.InstanceMethod Methods toObject :: InstanceMethod -> SomeObject Source # fromForeignPtr :: ForeignPtr InstanceMethod -> InstanceMethod |
Instances
Concrete Integer Source # | |
Defined in CPython.Types.Integer Methods concreteType :: Integer -> Type | |
Object Integer Source # | |
Defined in CPython.Types.Integer | |
Number Integer Source # | |
Defined in CPython.Protocols.Number Methods toNumber :: Integer -> SomeNumber Source # |
data SequenceIterator Source #
Instances
Iterator SequenceIterator Source # | |
Defined in CPython.Types.Iterator Methods | |
Concrete SequenceIterator Source # | |
Defined in CPython.Types.Iterator Methods concreteType :: SequenceIterator -> Type | |
Object SequenceIterator Source # | |
Defined in CPython.Types.Iterator Methods toObject :: SequenceIterator -> SomeObject Source # fromForeignPtr :: ForeignPtr SequenceIterator -> SequenceIterator |
data CallableIterator Source #
Instances
Iterator CallableIterator Source # | |
Defined in CPython.Types.Iterator Methods | |
Concrete CallableIterator Source # | |
Defined in CPython.Types.Iterator Methods concreteType :: CallableIterator -> Type | |
Object CallableIterator Source # | |
Defined in CPython.Types.Iterator Methods toObject :: CallableIterator -> SomeObject Source # fromForeignPtr :: ForeignPtr CallableIterator -> CallableIterator |
Instances
Sequence List Source # | |
Defined in CPython.Protocols.Sequence Methods toSequence :: List -> SomeSequence Source # | |
Concrete List Source # | |
Defined in CPython.Types.List Methods concreteType :: List -> Type | |
Object List Source # | |
Defined in CPython.Internal |
Instances
Concrete Method Source # | |
Defined in CPython.Types.Method Methods concreteType :: Method -> Type | |
Object Method Source # | |
Defined in CPython.Types.Method |
Instances
Concrete Module Source # | |
Defined in CPython.Types.Module Methods concreteType :: Module -> Type | |
Object Module Source # | |
Defined in CPython.Types.Module |
class Object a => AnySet a Source #
Instances
AnySet FrozenSet Source # | |
Defined in CPython.Types.Set | |
AnySet Set Source # | |
Defined in CPython.Types.Set |
Instances
Concrete Set Source # | |
Defined in CPython.Types.Set Methods concreteType :: Set -> Type | |
Object Set Source # | |
Defined in CPython.Types.Set | |
AnySet Set Source # | |
Defined in CPython.Types.Set | |
Number Set Source # | |
Defined in CPython.Protocols.Number Methods toNumber :: Set -> SomeNumber Source # |
Instances
Concrete FrozenSet Source # | |
Defined in CPython.Types.Set Methods concreteType :: FrozenSet -> Type | |
Object FrozenSet Source # | |
Defined in CPython.Types.Set Methods toObject :: FrozenSet -> SomeObject Source # | |
AnySet FrozenSet Source # | |
Defined in CPython.Types.Set | |
Number FrozenSet Source # | |
Defined in CPython.Protocols.Number Methods toNumber :: FrozenSet -> SomeNumber Source # |
Instances
Concrete Slice Source # | |
Defined in CPython.Types.Slice Methods concreteType :: Slice -> Type | |
Object Slice Source # | |
Defined in CPython.Types.Slice |
Instances
Sequence Tuple Source # | |
Defined in CPython.Protocols.Sequence Methods toSequence :: Tuple -> SomeSequence Source # | |
Concrete Tuple Source # | |
Defined in CPython.Types.Tuple Methods concreteType :: Tuple -> Type | |
Object Tuple Source # | |
Defined in CPython.Internal |
Instances
Concrete Type Source # | Returns |
Defined in CPython.Types.Type Methods concreteType :: Type -> Type | |
Object Type Source # | |
Defined in CPython.Internal |
Instances
Sequence Unicode Source # | |
Defined in CPython.Protocols.Sequence Methods toSequence :: Unicode -> SomeSequence Source # | |
Concrete Unicode Source # | |
Defined in CPython.Types.Unicode Methods concreteType :: Unicode -> Type | |
Object Unicode Source # | |
Defined in CPython.Types.Unicode |
Instances
Object Reference Source # | |
Defined in CPython.Types.WeakReference Methods toObject :: Reference -> SomeObject Source # |
Instances
Object Proxy Source # | |
Defined in CPython.Types.WeakReference |
Python Type
values
byteArrayType :: Type Source #
capsuleType :: Type Source #
complexType :: Type Source #
functionType :: Type Source #
Return a new function associated with the given code object. The second parameter will be used as the globals accessible to the function.
The function's docstring, name, and module
are retrieved from the
code object. The parameter defaults and closure are set to Nothing
.
integerType :: Type Source #
methodType :: Type Source #
moduleType :: Type Source #
Return a new module object with the name
attribute set. Only the
module’s doc
and name
attributes are filled in; the
caller is responsible for providing a file
attribute.
frozenSetType :: Type Source #
Return a new slice object with the given values. The start, stop,
and step parameters are used as the values of the slice object
attributes of the same names. Any of the values may be Nothing
, in which
case None
will be used for the corresponding attribute.
unicodeType :: Type Source #
Building and parsing values
toByteArray :: ByteString -> IO ByteArray Source #
fromByteArray :: ByteArray -> IO ByteString Source #
iterableToList :: Object iter => iter -> IO List Source #
Convert any object implementing the iterator protocol to a List
.
toFrozenSet :: [SomeObject] -> IO FrozenSet Source #