Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- convert :: Text -> CodeGen e Converter -> CodeGen e Text
- genConversion :: Text -> Converter -> CodeGen e Text
- unpackCArray :: Text -> Type -> Transfer -> ExcCodeGen Converter
- computeArrayLength :: Text -> Type -> ExcCodeGen Text
- callableHasClosures :: Callable -> Bool
- hToF :: Type -> Transfer -> ExcCodeGen Converter
- fToH :: Type -> Transfer -> ExcCodeGen Converter
- transientToH :: Type -> Transfer -> ExcCodeGen Converter
- haskellType :: Type -> CodeGen e TypeRep
- isoHaskellType :: Type -> CodeGen e TypeRep
- foreignType :: Type -> CodeGen e TypeRep
- argumentType :: Type -> ExposeClosures -> CodeGen e (Text, [Text])
- data ExposeClosures
- elementType :: Type -> Maybe Type
- elementMap :: Type -> Text -> Maybe Text
- elementTypeAndMap :: Type -> Text -> Maybe (Type, Text)
- isManaged :: Type -> CodeGen e Bool
- typeIsNullable :: Type -> CodeGen e Bool
- typeIsPtr :: Type -> CodeGen e Bool
- typeIsCallback :: Type -> CodeGen e Bool
- maybeNullConvert :: Type -> CodeGen e (Maybe Text)
- nullPtrForType :: Type -> CodeGen e (Maybe Text)
- typeAllocInfo :: Type -> CodeGen e (Maybe TypeAllocInfo)
- data TypeAllocInfo = TypeAlloc Text Int
- apply :: Constructor -> Converter
- mapC :: Constructor -> Converter
- literal :: Constructor -> Converter
- data Constructor
Documentation
unpackCArray :: Text -> Type -> Transfer -> ExcCodeGen Converter Source #
computeArrayLength :: Text -> Type -> ExcCodeGen Text Source #
Given an array, together with its type, return the code for reading its length.
callableHasClosures :: Callable -> Bool Source #
Whether the callable has closure arguments (i.e. "user_data" style arguments).
transientToH :: Type -> Transfer -> ExcCodeGen Converter Source #
Somewhat like fToH
, but with slightly different borrowing
semantics: in the case of TransferNothing
we wrap incoming
pointers to boxed structs into transient ManagedPtr
s (every other
case behaves as fToH
). These are ManagedPtr
s for which we do
not make a copy, and which will be disowned when the function
exists, instead of making a copy that the GC will collect
eventually.
This is necessary in order to get the semantics of callbacks and signals right: in some cases making a copy of the object does not simply increase the refcount, but rather makes a full copy. In this cases modification of the original object is not possible, but this is sometimes useful, see for example
https://github.com/haskell-gi/haskell-gi/issues/97
Another situation where making a copy of incoming arguments is problematic is when the underlying library is not thread-safe. When running under the threaded GHC runtime it can happen that the GC runs on a different OS thread than the thread where the object was created, and this leads to rather mysterious bugs, see for example
https://github.com/haskell-gi/haskell-gi/issues/96
This case is particularly nasty, since it affects onWidgetDraw
,
which is very common.
haskellType :: Type -> CodeGen e TypeRep Source #
This translates GI types to the types used for generated Haskell code.
isoHaskellType :: Type -> CodeGen e TypeRep Source #
Basically like haskellType
, but for types which admit a
"isomorphic" version of the Haskell type distinct from the usual
Haskell type. Generally the Haskell type we expose is isomorphic
to the foreign type, but in some cases, such as callbacks with
closure arguments, this does not hold, as we omit the closure
arguments. This function returns a type which is actually
isomorphic. There is another case this function deals with: for
convenience untyped TGClosure
types have a type variable on the
Haskell side when they are arguments to functions, but we do not
want this when they appear as arguments to callbacks/signals, or
return types of properties, as it would force the type synonym/type
family to depend on the type variable.
argumentType :: Type -> ExposeClosures -> CodeGen e (Text, [Text]) Source #
Given a type find the typeclasses the type belongs to, and return the representation of the type in the function signature and the list of typeclass constraints for the type.
data ExposeClosures Source #
Whether to expose closures and the associated destroy notify handlers in the Haskell wrapper.
Instances
Eq ExposeClosures Source # | |
Defined in Data.GI.CodeGen.Conversions (==) :: ExposeClosures -> ExposeClosures -> Bool # (/=) :: ExposeClosures -> ExposeClosures -> Bool # |
elementTypeAndMap :: Type -> Text -> Maybe (Type, Text) Source #
If the given type maps to a list in Haskell, return the type of the elements, and the function that maps over them.
isManaged :: Type -> CodeGen e Bool Source #
Returns whether the given type corresponds to a ManagedPtr
instance (a thin wrapper over a ForeignPtr
).
typeIsNullable :: Type -> CodeGen e Bool Source #
Returns whether the given type should be represented by a
Maybe
type on the Haskell side. This applies to all properties
which have a C representation in terms of pointers, except for
G(S)Lists, for which NULL is a valid G(S)List, and raw pointers,
which we just pass through to the Haskell side. Notice that
introspection annotations can override this.
typeIsPtr :: Type -> CodeGen e Bool Source #
Returns whether the given type is represented by a pointer on the C side.
typeIsCallback :: Type -> CodeGen e Bool Source #
Check whether the given type corresponds to a callback.
maybeNullConvert :: Type -> CodeGen e (Maybe Text) Source #
If the passed in type is nullable, return the conversion function
between the FFI pointer type (may be a Ptr
or a FunPtr
) and the
corresponding Maybe
type.
nullPtrForType :: Type -> CodeGen e (Maybe Text) Source #
An appropriate NULL value for the given type, for types which are represented by pointers on the C side.
typeAllocInfo :: Type -> CodeGen e (Maybe TypeAllocInfo) Source #
Information on how to allocate the given type, if known.
data TypeAllocInfo Source #
Information on how to allocate a type: allocator function and size of the struct.
apply :: Constructor -> Converter Source #
mapC :: Constructor -> Converter Source #
literal :: Constructor -> Converter Source #
data Constructor Source #
Instances
IsString Constructor Source # | |
Defined in Data.GI.CodeGen.Conversions fromString :: String -> Constructor # | |
Show Constructor Source # | |
Defined in Data.GI.CodeGen.Conversions showsPrec :: Int -> Constructor -> ShowS # show :: Constructor -> String # showList :: [Constructor] -> ShowS # | |
Eq Constructor Source # | |
Defined in Data.GI.CodeGen.Conversions (==) :: Constructor -> Constructor -> Bool # (/=) :: Constructor -> Constructor -> Bool # |