hoppy-runtime-0.2.1: C++ FFI generator - Runtime support

Safe HaskellNone
LanguageHaskell2010

Foreign.Hoppy.Runtime

Contents

Description

Runtime support for generated Haskell bindings.

Synopsis

Primitive types

newtype CBool Source #

A numeric type representing a C++ boolean.

Constructors

CBool CUChar 

Instances

Bounded CBool Source # 
Enum CBool Source # 
Eq CBool Source # 

Methods

(==) :: CBool -> CBool -> Bool #

(/=) :: CBool -> CBool -> Bool #

Integral CBool Source # 
Num CBool Source # 
Ord CBool Source # 

Methods

compare :: CBool -> CBool -> Ordering #

(<) :: CBool -> CBool -> Bool #

(<=) :: CBool -> CBool -> Bool #

(>) :: CBool -> CBool -> Bool #

(>=) :: CBool -> CBool -> Bool #

max :: CBool -> CBool -> CBool #

min :: CBool -> CBool -> CBool #

Real CBool Source # 

Methods

toRational :: CBool -> Rational #

Show CBool Source # 

Methods

showsPrec :: Int -> CBool -> ShowS #

show :: CBool -> String #

showList :: [CBool] -> ShowS #

Storable CBool Source # 

Methods

sizeOf :: CBool -> Int #

alignment :: CBool -> Int #

peekElemOff :: Ptr CBool -> Int -> IO CBool #

pokeElemOff :: Ptr CBool -> Int -> CBool -> IO () #

peekByteOff :: Ptr b -> Int -> IO CBool #

pokeByteOff :: Ptr b -> Int -> CBool -> IO () #

peek :: Ptr CBool -> IO CBool #

poke :: Ptr CBool -> CBool -> IO () #

Decodable (Ptr CBool) Bool Source # 

Methods

decode :: Ptr CBool -> IO Bool Source #

Assignable (Ptr CBool) Bool Source # 

Methods

assign :: Ptr CBool -> Bool -> IO () Source #

Decodable (Ptr (Ptr CBool)) (Ptr CBool) Source # 

Methods

decode :: Ptr (Ptr CBool) -> IO (Ptr CBool) Source #

newtype CUChar :: * #

Haskell type representing the C unsigned char type.

Constructors

CUChar Word8 

Instances

Bounded CUChar 
Enum CUChar 
Eq CUChar 

Methods

(==) :: CUChar -> CUChar -> Bool #

(/=) :: CUChar -> CUChar -> Bool #

Integral CUChar 
Num CUChar 
Ord CUChar 
Read CUChar 
Real CUChar 
Show CUChar 
Storable CUChar 
Bits CUChar 
FiniteBits CUChar 
Decodable (Ptr CUChar) CUChar Source # 
Decodable (Ptr (Ptr CUChar)) (Ptr CUChar) Source # 

Methods

decode :: Ptr (Ptr CUChar) -> IO (Ptr CUChar) Source #

coerceIntegral :: (Integral a, Integral b, Typeable a, Typeable b, Show a) => a -> b Source #

Converts between integral types by going from a to b, and also round-tripping the b value back to an a value. If the two a values don't match, then an error is signalled.

Objects

class CppPtr this where Source #

An instance of this class represents a pointer to a C++ object. All C++ classes bound by Hoppy have instances of CppPtr. The lifetime of such an object can optionally be managed by the Haskell garbage collector. Pointers returned from constructors are unmanaged, and toGc converts an unmanaged pointer to a managed one. delete must not be called on managed pointers.

Minimal complete definition

nullptr, withCppPtr, toPtr, touchCppPtr

Methods

nullptr :: this Source #

Polymorphic null pointer.

withCppPtr :: this -> (Ptr this -> IO a) -> IO a Source #

Runs an IO action on the Ptr underlying this pointer. Equivalent to withForeignPtr for managed pointers: the Ptr is only guaranteed to be valid until the action returns. There is no such restriction for unmanaged pointers.

toPtr :: this -> Ptr this Source #

Converts to a regular pointer. For objects managed by the garbage collector, this comes with the warnings associated with unsafeForeignPtrToPtr, namely that the object may be collected immediately after this function returns unless there is a touchCppPtr call later on.

touchCppPtr :: this -> IO () Source #

Equivalent to touchForeignPtr for managed object pointers. Has no effect on unmanaged pointers.

class Deletable this where Source #

C++ values that can be deleted. All C++ classes bound by Hoppy have instances of Deletable.

Minimal complete definition

delete, toGc

Methods

delete :: this -> IO () Source #

Deletes the object with the C++ delete operator.

toGc :: this -> IO this Source #

Converts a pointer to one managed by the garbage collector. A new managed pointer is returned, and existing pointers including the argument remain unmanaged, becoming invalid once all managed pointers are unreachable. Calling this on an already managed pointer has no effect and the argument is simply returned. It is no longer safe to call delete on the given object after calling this function. It is also not safe to call this function on unmanaged pointers for a single object multiple times: the object will get deleted more than once.

class Assignable cppType value where Source #

A typeclass for references to C++ values that can be assigned to. This includes raw pointers (Ptr), as well as pointers to object types that have an assignment operator (see Assignable).

Minimal complete definition

assign

Methods

assign :: cppType -> value -> IO () Source #

assign x v assigns the value v at the location pointed to by x.

Instances

class Encodable cppPtrType hsType | cppPtrType -> hsType where Source #

For a C++ class that also has a native Haskell representation (e.g. value types such as std::string), this typeclass allows converting a Haskell value into a C++ object on the heap. Encoding to both the non-const and const objects is supported.

Because the functional dependency points in the direction it does, calls of the form encode value are ambiguously typed, so encodeAs is provided to resolve the ambiguity.

Prefer withCppObj over calling encode directly, to manage the lifetime of the object.

See also Decodable.

Minimal complete definition

encode

Methods

encode :: hsType -> IO cppPtrType Source #

encodeAs :: Encodable cppPtrType hsType => cppPtrType -> hsType -> IO cppPtrType Source #

Takes a dummy argument to help with type resolution of encode, a la asTypeOf. For example, for a C++ pointer type StdString that gets converted to a regular haskell String, the expected usage is:

str :: String
encodeAs (undefined :: StdString) str

class Decodable cppPtrType hsType | cppPtrType -> hsType where Source #

A typeclass for converting references to C++ values into Haskell values. What this means depends on the type of C++ value. Pointers to numeric types and to other pointers (i.e. Ptr (Ptr ...)) are decodable by peeking at the value.

For a C++ class that also has a native Haskell representation (e.g. value types such as std::string), this typeclass allows converting a C++ heap object into a Haskell value based on the defined conversion. Decoding from both the non-const and const objects is supported.

See also Encodable.

Minimal complete definition

decode

Methods

decode :: cppPtrType -> IO hsType Source #

Instances

Decodable (Ptr Int8) Int8 Source # 

Methods

decode :: Ptr Int8 -> IO Int8 Source #

Decodable (Ptr Int16) Int16 Source # 

Methods

decode :: Ptr Int16 -> IO Int16 Source #

Decodable (Ptr Int32) Int32 Source # 

Methods

decode :: Ptr Int32 -> IO Int32 Source #

Decodable (Ptr Int64) Int64 Source # 

Methods

decode :: Ptr Int64 -> IO Int64 Source #

Decodable (Ptr Word8) Word8 Source # 

Methods

decode :: Ptr Word8 -> IO Word8 Source #

Decodable (Ptr Word16) Word16 Source # 
Decodable (Ptr Word32) Word32 Source # 
Decodable (Ptr Word64) Word64 Source # 
Decodable (Ptr CSsize) CSsize Source # 
Decodable (Ptr CChar) CChar Source # 

Methods

decode :: Ptr CChar -> IO CChar Source #

Decodable (Ptr CUChar) CUChar Source # 
Decodable (Ptr CShort) CShort Source # 
Decodable (Ptr CUShort) CUShort Source # 
Decodable (Ptr CInt) Int Source # 

Methods

decode :: Ptr CInt -> IO Int Source #

Decodable (Ptr CUInt) CUInt Source # 

Methods

decode :: Ptr CUInt -> IO CUInt Source #

Decodable (Ptr CLong) CLong Source # 

Methods

decode :: Ptr CLong -> IO CLong Source #

Decodable (Ptr CULong) CULong Source # 
Decodable (Ptr CLLong) CLLong Source # 
Decodable (Ptr CULLong) CULLong Source # 
Decodable (Ptr CFloat) Float Source # 
Decodable (Ptr CDouble) Double Source # 
Decodable (Ptr CPtrdiff) CPtrdiff Source # 
Decodable (Ptr CSize) CSize Source # 

Methods

decode :: Ptr CSize -> IO CSize Source #

Decodable (Ptr CBool) Bool Source # 

Methods

decode :: Ptr CBool -> IO Bool Source #

Decodable (Ptr (Ptr Int8)) (Ptr Int8) Source # 

Methods

decode :: Ptr (Ptr Int8) -> IO (Ptr Int8) Source #

Decodable (Ptr (Ptr Int16)) (Ptr Int16) Source # 

Methods

decode :: Ptr (Ptr Int16) -> IO (Ptr Int16) Source #

Decodable (Ptr (Ptr Int32)) (Ptr Int32) Source # 

Methods

decode :: Ptr (Ptr Int32) -> IO (Ptr Int32) Source #

Decodable (Ptr (Ptr Int64)) (Ptr Int64) Source # 

Methods

decode :: Ptr (Ptr Int64) -> IO (Ptr Int64) Source #

Decodable (Ptr (Ptr Word8)) (Ptr Word8) Source # 

Methods

decode :: Ptr (Ptr Word8) -> IO (Ptr Word8) Source #

Decodable (Ptr (Ptr Word16)) (Ptr Word16) Source # 

Methods

decode :: Ptr (Ptr Word16) -> IO (Ptr Word16) Source #

Decodable (Ptr (Ptr Word32)) (Ptr Word32) Source # 

Methods

decode :: Ptr (Ptr Word32) -> IO (Ptr Word32) Source #

Decodable (Ptr (Ptr Word64)) (Ptr Word64) Source # 

Methods

decode :: Ptr (Ptr Word64) -> IO (Ptr Word64) Source #

Decodable (Ptr (Ptr (Ptr a))) (Ptr (Ptr a)) Source # 

Methods

decode :: Ptr (Ptr (Ptr a)) -> IO (Ptr (Ptr a)) Source #

Decodable (Ptr (Ptr CSsize)) (Ptr CSsize) Source # 

Methods

decode :: Ptr (Ptr CSsize) -> IO (Ptr CSsize) Source #

Decodable (Ptr (Ptr CChar)) (Ptr CChar) Source # 

Methods

decode :: Ptr (Ptr CChar) -> IO (Ptr CChar) Source #

Decodable (Ptr (Ptr CUChar)) (Ptr CUChar) Source # 

Methods

decode :: Ptr (Ptr CUChar) -> IO (Ptr CUChar) Source #

Decodable (Ptr (Ptr CShort)) (Ptr CShort) Source # 

Methods

decode :: Ptr (Ptr CShort) -> IO (Ptr CShort) Source #

Decodable (Ptr (Ptr CUShort)) (Ptr CUShort) Source # 
Decodable (Ptr (Ptr CInt)) (Ptr CInt) Source # 

Methods

decode :: Ptr (Ptr CInt) -> IO (Ptr CInt) Source #

Decodable (Ptr (Ptr CUInt)) (Ptr CUInt) Source # 

Methods

decode :: Ptr (Ptr CUInt) -> IO (Ptr CUInt) Source #

Decodable (Ptr (Ptr CLong)) (Ptr CLong) Source # 

Methods

decode :: Ptr (Ptr CLong) -> IO (Ptr CLong) Source #

Decodable (Ptr (Ptr CULong)) (Ptr CULong) Source # 

Methods

decode :: Ptr (Ptr CULong) -> IO (Ptr CULong) Source #

Decodable (Ptr (Ptr CLLong)) (Ptr CLLong) Source # 

Methods

decode :: Ptr (Ptr CLLong) -> IO (Ptr CLLong) Source #

Decodable (Ptr (Ptr CULLong)) (Ptr CULLong) Source # 
Decodable (Ptr (Ptr CFloat)) (Ptr CFloat) Source # 

Methods

decode :: Ptr (Ptr CFloat) -> IO (Ptr CFloat) Source #

Decodable (Ptr (Ptr CDouble)) (Ptr CDouble) Source # 
Decodable (Ptr (Ptr CPtrdiff)) (Ptr CPtrdiff) Source # 
Decodable (Ptr (Ptr CSize)) (Ptr CSize) Source # 

Methods

decode :: Ptr (Ptr CSize) -> IO (Ptr CSize) Source #

Decodable (Ptr (Ptr CBool)) (Ptr CBool) Source # 

Methods

decode :: Ptr (Ptr CBool) -> IO (Ptr CBool) Source #

decodeAndDelete :: (Deletable cppPtrType, Decodable cppPtrType hsType) => cppPtrType -> IO hsType Source #

Decodes a C++ object to a Haskell value with decode, releases the original object with delete, then returns the Haskell value.

withCppObj :: (Deletable cppPtrType, Encodable cppPtrType hsType) => hsType -> (cppPtrType -> IO a) -> IO a Source #

Temporarily encodes the Haskell value into a C++ object and passes it to the given function. When the function finishes, the C++ object is deleted.

withScopedPtr :: Deletable cppPtrType => IO cppPtrType -> (cppPtrType -> IO a) -> IO a Source #

withScopedPtr m f runs m to get a pointer, which is given to f to execute. When f finishes, the pointer is deleted.

Containers

class HasContents c e | c -> e where Source #

Containers whose contents can be convered to a list.

For a container Cont holding values with C-side type Foo and Haskell-side type Bar, if the container uses ConvertPtr then the following instances are recommended:

instance HasContents ContConst FooConst
instance HasContents Cont Foo

If the container uses ConvertValue then the following instances are recommended:

instance HasContents ContConst Bar
instance HasContents Cont Bar

Minimal complete definition

toContents

Methods

toContents :: c -> IO [e] Source #

Extracts the contents of a container, returning the elements in a list.

class FromContents c e | c -> e where Source #

Containers that can be created from a list.

For a container Cont holding values with C-side type Foo and Haskell-side type Bar, if the container uses ConvertPtr then the following instance is recommended:

instance FromContents Cont Foo

If the container uses ConvertValue then the following instance is recommended:

instance HasContents Cont Bar

No instances for ContConst are needed because it is easy enough to cast the resulting collection to a const pointer.

Minimal complete definition

fromContents

Methods

fromContents :: [e] -> IO c Source #

Creates and returns a new container holding the given elements.

Internal

newtype CCallback fnHsCType Source #

Internal type that represents a pointer to a C++ callback object (callback impl object, specifically).

Constructors

CCallback (Ptr ()) 

freeHaskellFunPtrFunPtr :: FunPtr (FunPtr (IO ()) -> IO ()) Source #

A global constant function pointer that points to freeHaskellFunPtr.