Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Runtime support for generated Haskell bindings.
Synopsis
- coerceIntegral :: (Integral a, Integral b, Typeable a, Typeable b, Show a) => a -> b
- class CppEnum n e | e -> n where
- toCppEnum :: HasCallStack => n -> e
- fromCppEnum :: e -> n
- class CppPtr this where
- nullptr :: this
- withCppPtr :: this -> (Ptr this -> IO a) -> IO a
- toPtr :: this -> Ptr this
- touchCppPtr :: this -> IO ()
- class Deletable this where
- class Assignable cppType value where
- class Copyable from to | from -> to where
- class Encodable cppPtrType hsType | cppPtrType -> hsType where
- encodeAs :: Encodable cppPtrType hsType => cppPtrType -> hsType -> IO cppPtrType
- class Decodable cppPtrType hsType | cppPtrType -> hsType where
- decodeAndDelete :: (Deletable cppPtrType, Decodable cppPtrType hsType) => cppPtrType -> IO hsType
- withCppObj :: (Deletable cppPtrType, Encodable cppPtrType hsType) => hsType -> (cppPtrType -> IO a) -> IO a
- withScopedPtr :: Deletable cppPtrType => IO cppPtrType -> (cppPtrType -> IO a) -> IO a
- withScopedFunPtr :: IO (FunPtr a) -> (FunPtr a -> IO b) -> IO b
- class CppException e where
- cppExceptionInfo :: e -> ExceptionClassInfo
- cppExceptionBuild :: ForeignPtr () -> Ptr () -> e
- cppExceptionBuildToGc :: Ptr () -> IO e
- class CppException e => CppThrowable e where
- toSomeCppException :: e -> SomeCppException
- catchCpp :: forall a e. CppException e => IO a -> (e -> IO a) -> IO a
- throwCpp :: CppThrowable e => e -> IO a
- data UnknownCppException
- class HasContents c e | c -> e where
- toContents :: c -> IO [e]
- class FromContents c e | c -> e where
- fromContents :: [e] -> IO c
- fromContentsToGc :: (Deletable c, FromContents c e) => [e] -> IO c
- newtype CCallback fnHsCType = CCallback (Ptr ())
- freeHaskellFunPtrFunPtr :: FunPtr (FunPtr (IO ()) -> IO ())
- newtype ExceptionId = ExceptionId CInt
- data SomeCppException
- = SomeCppException ExceptionClassInfo (Maybe (ForeignPtr ())) (Ptr ())
- | SomeUnknownCppException
- internalHandleExceptions :: ExceptionDb -> (Ptr CInt -> Ptr (Ptr ()) -> IO a) -> IO a
- internalHandleCallbackExceptions :: CppDefault a => Ptr CInt -> Ptr (Ptr ()) -> IO a -> IO a
- newtype ExceptionDb = ExceptionDb (Map ExceptionId ExceptionClassInfo)
- data ExceptionClassInfo = ExceptionClassInfo {
- exceptionClassId :: ExceptionId
- exceptionClassName :: String
- exceptionClassUpcasts :: Map ExceptionId (Ptr () -> Ptr ())
- exceptionClassDelete :: Ptr () -> IO ()
- exceptionClassCopy :: Ptr () -> IO (Ptr ())
- exceptionClassToGc :: Ptr () -> IO (ForeignPtr ())
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
.
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.
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
.
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
).
assign :: cppType -> value -> IO () Source #
assign x v
assigns the value v
at the location pointed to by x
.
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
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
are ambiguously typed, so encode
valueencodeAs
is provided to
resolve the ambiguity.
Prefer withCppObj
over calling encode
directly, to manage the lifetime of
the object.
See also Decodable
.
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.
) are decodable by peeking at
the value.Ptr
(Ptr
...)
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
.
Instances
decodeAndDelete :: (Deletable cppPtrType, Decodable cppPtrType hsType) => cppPtrType -> IO hsType Source #
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.
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.
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.
Instances
CppException UnknownCppException Source # | |
Defined in Foreign.Hoppy.Runtime cppExceptionInfo :: UnknownCppException -> ExceptionClassInfo Source # cppExceptionBuild :: ForeignPtr () -> Ptr () -> UnknownCppException Source # cppExceptionBuildToGc :: Ptr () -> IO UnknownCppException Source # |
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.
toSomeCppException :: e -> SomeCppException Source #
Internal. Creates a throw
able 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.)
Instances
CppException UnknownCppException Source # | |
Defined in Foreign.Hoppy.Runtime cppExceptionInfo :: UnknownCppException -> ExceptionClassInfo Source # cppExceptionBuild :: ForeignPtr () -> Ptr () -> UnknownCppException Source # cppExceptionBuildToGc :: Ptr () -> IO UnknownCppException Source # |
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 Foreign.Hoppy.Generator.Std.ConvertPtr
then the following instances are recommended:
instance HasContents ContConst FooConst instance HasContents Cont Foo
If the container uses Foreign.Hoppy.Generator.Std.ConvertValue
then the
following instances are recommended:
instance HasContents ContConst Bar instance HasContents Cont Bar
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.
fromContents :: [e] -> IO c Source #
Creates and returns a new container holding the given elements.
The new container is not managed by the garbage collector. If this is
desired, use fromContentsToGc
.
fromContentsToGc :: (Deletable c, FromContents c e) => [e] -> IO c Source #
Creates and returns a new container holding the given elements, like
fromContents
, and additionally assigns ownership to the garbage collector.
This function is useful if the object being created is only needed as a temporary for passing into another function, for example:
processBlobs $ fromContentsToGc [Blob 1, Blob 2] :: IO BlobContainer
In this example, processBlobs
inspects all of the blobs but does not take
ownership of the container, so the Haskell code has to release the container
itself. This is done via the garbage collector.
In a simple case like this, we can also write it a bit more efficiently like below, since we don't truly need the garbage collector:
withScopedPtr (fromContents [Blob 1, Blob 2] :: IO BlobContainer) processBlobs
In this second example, the container is freed immediately when
processBlobs
returns.
Internal
newtype CCallback fnHsCType Source #
Internal type that represents a pointer to a C++ callback object (callback impl object, specifically).
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.
Instances
Show ExceptionId Source # | |
Defined in Foreign.Hoppy.Runtime showsPrec :: Int -> ExceptionId -> ShowS # show :: ExceptionId -> String # showList :: [ExceptionId] -> ShowS # | |
Eq ExceptionId Source # | |
Defined in Foreign.Hoppy.Runtime (==) :: ExceptionId -> ExceptionId -> Bool # (/=) :: ExceptionId -> ExceptionId -> Bool # | |
Ord ExceptionId Source # | |
Defined in Foreign.Hoppy.Runtime compare :: ExceptionId -> ExceptionId -> Ordering # (<) :: ExceptionId -> ExceptionId -> Bool # (<=) :: ExceptionId -> ExceptionId -> Bool # (>) :: ExceptionId -> ExceptionId -> Bool # (>=) :: ExceptionId -> ExceptionId -> Bool # max :: ExceptionId -> ExceptionId -> ExceptionId # min :: ExceptionId -> ExceptionId -> ExceptionId # |
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.
Instances
Exception SomeCppException Source # | |
Defined in Foreign.Hoppy.Runtime | |
Show SomeCppException Source # | |
Defined in Foreign.Hoppy.Runtime showsPrec :: Int -> SomeCppException -> ShowS # show :: SomeCppException -> String # showList :: [SomeCppException] -> ShowS # |
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.
ExceptionClassInfo | |
|