| Safe Haskell | None | 
|---|---|
| Language | Haskell98 | 
Data.GI.CodeGen.Callable
Synopsis
- genCCallableWrapper :: Name -> Text -> Callable -> ExcCodeGen ()
- genDynamicCallableWrapper :: Name -> Text -> Callable -> ExcCodeGen Text
- data ForeignSymbol- = KnownForeignSymbol Text
- | DynamicForeignSymbol DynamicWrapper
 
- data ExposeClosures
- hOutType :: Callable -> [Arg] -> ExcCodeGen TypeRep
- skipRetVal :: Callable -> Bool
- arrayLengths :: Callable -> [Arg]
- arrayLengthsMap :: Callable -> [(Arg, Arg)]
- callableSignature :: Callable -> ForeignSymbol -> ExcCodeGen Signature
- data Signature = Signature {}
- fixupCallerAllocates :: Callable -> Callable
- callableHInArgs :: Callable -> ExposeClosures -> ([Arg], [Arg])
- callableHOutArgs :: Callable -> [Arg]
- wrapMaybe :: Arg -> CodeGen Bool
- inArgInterfaces :: [Arg] -> ExcCodeGen ([Text], [Text])
Documentation
genCCallableWrapper :: Name -> Text -> Callable -> ExcCodeGen () Source #
Generate a wrapper for a known C symbol.
genDynamicCallableWrapper :: Name -> Text -> Callable -> ExcCodeGen Text Source #
Generate a wrapper for a dynamic C symbol (i.e. a Haskell
 function that will invoke its first argument, which should be a
 FunPtr of the appropriate type). The caller should have created a
 type synonym with the right type for the foreign symbol.
data ForeignSymbol Source #
The foreign symbol to wrap. It is either a foreign symbol wrapped in a foreign import, in which case we are given the name of the Haskell wrapper, or alternatively the information about a "dynamic" wrapper in scope.
Constructors
| KnownForeignSymbol Text | Haskell symbol in scope. | 
| DynamicForeignSymbol DynamicWrapper | Info about the dynamic wrapper. | 
data ExposeClosures Source #
Whether to expose closures and the associated destroy notify handlers in the Haskell wrapper.
Constructors
| WithClosures | |
| WithoutClosures | 
skipRetVal :: Callable -> Bool Source #
Whether to skip the return value in the generated bindings. The C convention is that functions throwing an error and returning a gboolean set the boolean to TRUE iff there is no error, so the information is always implicit in whether we emit an exception or not, so the return value can be omitted from the generated bindings without loss of information (and omitting it gives rise to a nicer API). See https://bugzilla.gnome.org/show_bug.cgi?id=649657
arrayLengths :: Callable -> [Arg] Source #
callableSignature :: Callable -> ForeignSymbol -> ExcCodeGen Signature Source #
The Haskell signature for the given callable. It returns a tuple ([constraints], [(type, argname)]).
Signature for a callable.
Constructors
| Signature | |
| Fields 
 | |
fixupCallerAllocates :: Callable -> Callable Source #
caller-allocates arguments are arguments that the caller
 allocates, and the called function modifies. They are marked as
 out argumens in the introspection data, we sometimes treat them
 as inout arguments instead. The semantics are somewhat tricky:
 for memory management purposes they should be treated as "in"
 arguments, but from the point of view of the exposed API they
 should be treated as "out" or "inout". Unfortunately we cannot
 always just assume that they are purely "out", so in many cases the
 generated API is somewhat suboptimal (since the initial values are
 not important): for example for g_io_channel_read_chars the size of
 the buffer to read is determined by the caller-allocates
 argument. As a compromise, we assume that we can allocate anything
 that is not a TCArray of length determined by an argument.
callableHInArgs :: Callable -> ExposeClosures -> ([Arg], [Arg]) Source #
In arguments for the given callable on the Haskell side, together with the omitted arguments.
callableHOutArgs :: Callable -> [Arg] Source #
Out arguments for the given callable on the Haskell side.
wrapMaybe :: Arg -> CodeGen Bool Source #
Given an argument to a function, return whether it should be wrapped in a maybe type (useful for nullable types). We do some sanity checking to make sure that the argument is actually nullable (a relatively common annotation mistake is to mix up (optional) with (nullable)).
inArgInterfaces :: [Arg] -> ExcCodeGen ([Text], [Text]) Source #