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

Safe HaskellNone
LanguageHaskell2010

Foreign.Hoppy.Runtime

Contents

Description

Runtime support for generated Haskell bindings.

Synopsis

Primitive types

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.

Enumerations

class CppEnum n e | e -> n where Source #

An instance e of this class represents a value belonging to a C++ enumeration with numeric type n.

Methods

toCppEnum :: HasCallStack => n -> e Source #

Converts a number into an enum value.

If the Hoppy binding didn't request that the enum support arbitrary unknown values, then given an entry not explicitly supported by the enum, this throws an exception.

fromCppEnum :: e -> n Source #

Extracts the number that an enum value represents.

Objects

class CppPtr this where Source #

An instance of this class represents a handle (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. Handles returned from constructors are unmanaged, and toGc converts an unmanaged handle to a managed one. delete must not be called on managed handles.

Methods

nullptr :: this Source #

Polymorphic null pointer handle.

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

Runs an IO action on the Ptr underlying this handle. Equivalent to withForeignPtr for managed handles: the Ptr is only guaranteed to be valid until the action returns. There is no such restriction for unmanaged handles, but of course the object must still be alive to be used.

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 handles. Has no effect on unmanaged handles.

class Deletable this where Source #

C++ values that can be deleted. By default, C++ classes bound by Hoppy are assumed to be deletable, so they get instances of Deletable.

Methods

delete :: this -> IO () Source #

Deletes the object with the C++ delete operator.

toGc :: this -> IO this Source #

Converts a handle to one managed by the garbage collector. A new managed handle is returned, and existing handles including the argument remain unmanaged, becoming invalid once all managed handles are unreachable. Calling this on an already managed handle 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 handles for a single object multiple times: the object will get deleted more than once.

Up- and downcasting managed handles keeps the object alive correctly.

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 handles for object types that have an assignment operator (see Assignable).

Methods

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

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

Instances
Storable a => Assignable (Ptr a) a Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

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

Assignable (Ptr CInt) Int Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

assign :: Ptr CInt -> Int -> IO () Source #

Assignable (Ptr CBool) Bool Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

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

Assignable (Ptr CFloat) Float Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

assign :: Ptr CFloat -> Float -> IO () Source #

Assignable (Ptr CDouble) Double Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

assign :: Ptr CDouble -> Double -> IO () Source #

class Copyable from to | from -> to where Source #

A typeclass for creating copies of C++ objects. Every C++ class with a copy constructor will have two instances:

instance Copyable Foo Foo
instance Copyable FooConst Foo

Methods

copy :: from -> IO to Source #

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.

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 handle 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.

Methods

decode :: cppPtrType -> IO hsType Source #

Instances
Decodable (Ptr Int8) Int8 Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

decode :: Ptr Int8 -> IO Int8 Source #

Decodable (Ptr Int16) Int16 Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

decode :: Ptr Int16 -> IO Int16 Source #

Decodable (Ptr Int32) Int32 Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

decode :: Ptr Int32 -> IO Int32 Source #

Decodable (Ptr Int64) Int64 Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

decode :: Ptr Int64 -> IO Int64 Source #

Decodable (Ptr Word8) Word8 Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

decode :: Ptr Word8 -> IO Word8 Source #

Decodable (Ptr Word16) Word16 Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Decodable (Ptr Word32) Word32 Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Decodable (Ptr Word64) Word64 Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Decodable (Ptr CSsize) CSsize Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Decodable (Ptr CChar) CChar Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

decode :: Ptr CChar -> IO CChar Source #

Decodable (Ptr CUChar) CUChar Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Decodable (Ptr CShort) CShort Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Decodable (Ptr CUShort) CUShort Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Decodable (Ptr CInt) Int Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

decode :: Ptr CInt -> IO Int Source #

Decodable (Ptr CUInt) CUInt Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

decode :: Ptr CUInt -> IO CUInt Source #

Decodable (Ptr CLong) CLong Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

decode :: Ptr CLong -> IO CLong Source #

Decodable (Ptr CULong) CULong Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Decodable (Ptr CLLong) CLLong Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Decodable (Ptr CULLong) CULLong Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Decodable (Ptr CBool) Bool Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

decode :: Ptr CBool -> IO Bool Source #

Decodable (Ptr CFloat) Float Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Decodable (Ptr CDouble) Double Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Decodable (Ptr CPtrdiff) CPtrdiff Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Decodable (Ptr CSize) CSize Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

decode :: Ptr CSize -> IO CSize Source #

Decodable (Ptr (Ptr Int8)) (Ptr Int8) Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

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

Decodable (Ptr (Ptr Int16)) (Ptr Int16) Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

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

Decodable (Ptr (Ptr Int32)) (Ptr Int32) Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

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

Decodable (Ptr (Ptr Int64)) (Ptr Int64) Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

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

Decodable (Ptr (Ptr Word8)) (Ptr Word8) Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

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

Decodable (Ptr (Ptr Word16)) (Ptr Word16) Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

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

Decodable (Ptr (Ptr Word32)) (Ptr Word32) Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

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

Decodable (Ptr (Ptr Word64)) (Ptr Word64) Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

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

Decodable (Ptr (Ptr (Ptr a))) (Ptr (Ptr a)) Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

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

Decodable (Ptr (Ptr CSsize)) (Ptr CSsize) Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

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

Decodable (Ptr (Ptr CChar)) (Ptr CChar) Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

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

Decodable (Ptr (Ptr CUChar)) (Ptr CUChar) Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

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

Decodable (Ptr (Ptr CShort)) (Ptr CShort) Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

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

Decodable (Ptr (Ptr CUShort)) (Ptr CUShort) Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Decodable (Ptr (Ptr CInt)) (Ptr CInt) Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

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

Decodable (Ptr (Ptr CUInt)) (Ptr CUInt) Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

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

Decodable (Ptr (Ptr CLong)) (Ptr CLong) Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

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

Decodable (Ptr (Ptr CULong)) (Ptr CULong) Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

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

Decodable (Ptr (Ptr CLLong)) (Ptr CLLong) Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

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

Decodable (Ptr (Ptr CULLong)) (Ptr CULLong) Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Decodable (Ptr (Ptr CBool)) (Ptr CBool) Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

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

Decodable (Ptr (Ptr CFloat)) (Ptr CFloat) Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

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

Decodable (Ptr (Ptr CDouble)) (Ptr CDouble) Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Decodable (Ptr (Ptr CPtrdiff)) (Ptr CPtrdiff) Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Decodable (Ptr (Ptr CSize)) (Ptr CSize) Source # 
Instance details

Defined in Foreign.Hoppy.Runtime

Methods

decode :: Ptr (Ptr CSize) -> IO (Ptr CSize) 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 handle, which is given to f to execute. When f finishes, the handle is deleted (via bracket and delete).

withScopedFunPtr :: IO (FunPtr a) -> (FunPtr a -> IO b) -> IO b Source #

withScopedFunPtr m f runs m to get a FunPtr, which is given to f to execute. When f finishes, the FunPtr is deleted (via bracket and freeHaskellFunPtr). This is useful in conjunction with function pointers created via generated callback functions.

Exceptions

class CppException e where Source #

A typeclass for C++ values that are catchable as exceptions. C++ classes that have been declared to be used as exceptions have instances of this class. Unlike CppThrowable, UnknownCppException is also an instance of this typeclass.

Methods

cppExceptionInfo :: e -> ExceptionClassInfo Source #

Internal. Returns metadata about the exception.

cppExceptionBuild :: ForeignPtr () -> Ptr () -> e Source #

Internal. Constructs a handle from a GC-managed object's raw pointers.

cppExceptionBuildToGc :: Ptr () -> IO e Source #

Internal. Constructs a GC-managed handle from an unmanaged raw pointer.

class CppException e => CppThrowable e where Source #

A typeclass for C++ values that are throwable as exceptions. C++ classes that have been declared to be used as exceptions have instances of this class.

Methods

toSomeCppException :: e -> SomeCppException Source #

Internal. Creates a throwable exception from a C++ handle.

catchCpp :: forall a e. CppException e => IO a -> (e -> IO a) -> IO a Source #

Catches a C++ exception, similar to catch. Catching an exception class will also catch subtypes of the class, per normal C++ exception semantics. Catching UnknownCppException will catch all C++ exceptions, but will provide no information about the caught exception. Exceptions caught with this function are GC-managed heap objects; you do not need to manually delete them.

throwCpp :: CppThrowable e => e -> IO a Source #

Takes ownership of a C++ object, and throws it as a Haskell exception. This can be caught in Haskell with catchCpp, or propagated to C++ when within a callback that is marked as handling exceptions.

data UnknownCppException Source #

A top type for C++ exceptions. Catching this type with catchCpp will catch all C++ exceptions. (You still have to declare what exceptions can be thrown from each function, to make exceptions pass through the gateway properly.)

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

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.

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.

newtype ExceptionId Source #

A unique identifier for a C++ class. The representation is internal to Hoppy.

Constructors

ExceptionId CInt 

data SomeCppException Source #

Internal. Holds an arbitrary CppException.

Do not catch this with catch; this can leak exception objects. Always use catchCpp to catch C++ exceptions.

internalHandleExceptions :: ExceptionDb -> (Ptr CInt -> Ptr (Ptr ()) -> IO a) -> IO a Source #

Internal. Wraps a call to a C++ gateway function, and provides propagation of C++ exceptions to Haskell.

internalHandleCallbackExceptions :: CppDefault a => Ptr CInt -> Ptr (Ptr ()) -> IO a -> IO a Source #

Internal. Wraps a call to a Haskell function while invoking a callback, and provides propagation of C++ exceptions back into C++.

newtype ExceptionDb Source #

Internal. A database of information about exceptions an interface uses.

data ExceptionClassInfo Source #

Internal. Information about a C++ exception class.

Constructors

ExceptionClassInfo 

Fields