Safe Haskell | None |
---|---|
Language | Haskell2010 |
A Context
is used to define the capabilities of the Template Haskell code
that handles the inline C code. See the documentation of the data type for
more details.
In practice, a Context
will have to be defined for each library that
defines new C types, to allow the TemplateHaskell code to interpret said
types correctly.
Synopsis
- type TypesTable = Map TypeSpecifier TypeQ
- data Purity
- convertType :: Purity -> TypesTable -> Type CIdentifier -> Q (Maybe Type)
- type CArray = Ptr
- typeNamesFromTypesTable :: TypesTable -> TypeNames
- data AntiQuoter a = AntiQuoter {
- aqParser :: forall m. CParser HaskellIdentifier m => m (CIdentifier, Type CIdentifier, a)
- aqMarshaller :: Purity -> TypesTable -> Type CIdentifier -> a -> Q (Type, Exp)
- type AntiQuoterId = String
- data SomeAntiQuoter = forall a.(Eq a, Typeable a) => SomeAntiQuoter (AntiQuoter a)
- type AntiQuoters = Map AntiQuoterId SomeAntiQuoter
- data Context = Context {}
- baseCtx :: Context
- fptrCtx :: Context
- funCtx :: Context
- vecCtx :: Context
- class VecCtx a where
- type VecCtxScalar a :: *
- vecCtxLength :: a -> Int
- vecCtxUnsafeWith :: a -> (Ptr (VecCtxScalar a) -> IO b) -> IO b
- bsCtx :: Context
TypesTable
type TypesTable = Map TypeSpecifier TypeQ Source #
A mapping from TypeSpecifier
s to Haskell types. Needed both to
parse C types, and to convert them to Haskell types.
A data type to indicate whether the user requested pure or IO function from Haskell
convertType :: Purity -> TypesTable -> Type CIdentifier -> Q (Maybe Type) Source #
Given a Context
, it uses its ctxTypesTable
to convert
arbitrary C types.
AntiQuoter
data AntiQuoter a Source #
AntiQuoter | |
|
type AntiQuoterId = String Source #
An identifier for a AntiQuoter
.
data SomeAntiQuoter Source #
Existential wrapper around AntiQuoter
.
forall a.(Eq a, Typeable a) => SomeAntiQuoter (AntiQuoter a) |
type AntiQuoters = Map AntiQuoterId SomeAntiQuoter Source #
Context
A Context
stores various information needed to produce the files with
the C code derived from the inline C snippets.
Context
s can be composed with their Monoid
instance, where mappend
is
right-biased -- in mappend
x yy
will take precedence over x
.
Context | |
|
Context useful to work with vanilla C. Used by default.
ctxTypesTable
: converts C basic types to their counterparts in
Foreign.C.Types.
No ctxAntiQuoters
.
This Context
adds support for ForeignPtr
arguments. It adds a unique
marshaller called fptr-ptr
. For example, $fptr-ptr:(int *x)
extracts the
bare C pointer out of foreign pointer x
.
This Context
includes a AntiQuoter
that removes the need for
explicitely creating FunPtr
s, named "fun"
along with one which
allocates new memory which must be manually freed named "fun-alloc"
.
For example, we can capture function f
of type CInt -> CInt -> IO
CInt
in C code using $fun:(int (*f)(int, int))
.
When used in a pure
embedding, the Haskell function will have to be
pure too. Continuing the example above we'll have CInt -> CInt ->
IO CInt
.
Does not include the baseCtx
, since most of the time it's going to
be included as part of larger contexts.
IMPORTANT: When using the fun
anti quoter, one must be aware that
the function pointer which is automatically generated is freed when
the code contained in the block containing the anti quoter exits.
Thus, if you need the function pointer to be longer-lived, you must
allocate it and free it manually using freeHaskellFunPtr
.
We provide utilities to easily
allocate them (see mkFunPtr
).
IMPORTANT: When using the fun-alloc
anti quoter, one must free the allocated
function pointer. The GHC runtime provides a function to do this,
hs_free_fun_ptr
available in the h
header.
This Context
includes two AntiQuoter
s that allow to easily use
Haskell vectors in C.
Specifically, the vec-len
and vec-ptr
will get the length and the
pointer underlying mutable (IOVector
) and immutable (Vector
)
storable vectors.
Note that if you use vecCtx
to manipulate immutable vectors you
must make sure that the vector is not modified in the C code.
To use vec-len
, simply write $vec-len:x
, where x
is something
of type
or IOVector
a
, for some Vector
aa
. To use
vec-ptr
you need to specify the type of the pointer,
e.g. $vec-len:(int *x)
will work if x
has type
.IOVector
CInt
Type class used to implement the anti-quoters in vecCtx
.
type VecCtxScalar a :: * Source #
vecCtxLength :: a -> Int Source #
vecCtxUnsafeWith :: a -> (Ptr (VecCtxScalar a) -> IO b) -> IO b Source #
Instances
Storable a => VecCtx (Vector a) Source # | |
Defined in Language.C.Inline.Context type VecCtxScalar (Vector a) Source # vecCtxLength :: Vector a -> Int Source # vecCtxUnsafeWith :: Vector a -> (Ptr (VecCtxScalar (Vector a)) -> IO b) -> IO b Source # | |
Storable a => VecCtx (IOVector a) Source # | |
Defined in Language.C.Inline.Context type VecCtxScalar (IOVector a) Source # vecCtxLength :: IOVector a -> Int Source # vecCtxUnsafeWith :: IOVector a -> (Ptr (VecCtxScalar (IOVector a)) -> IO b) -> IO b Source # |
bsCtx
serves exactly the same purpose as vecCtx
, but only for
ByteString
. vec-ptr
becomes bs-ptr
, and vec-len
becomes
bs-len
. You don't need to specify the type of the pointer in
bs-ptr
, it will always be char*
.
Moreover, bs-cstr
works as bs-ptr
but it provides a null-terminated
copy of the given ByteString
.