inline-c-0.9.1.3: Write Haskell source files including C code inline. No FFI required.

Safe HaskellNone
LanguageHaskell2010

Language.C.Inline.Context

Contents

Description

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

TypesTable

type TypesTable = Map TypeSpecifier TypeQ Source #

A mapping from TypeSpecifiers to Haskell types. Needed both to parse C types, and to convert them to Haskell types.

data Purity Source #

A data type to indicate whether the user requested pure or IO function from Haskell

Constructors

Pure 
IO 
Instances
Eq Purity Source # 
Instance details

Defined in Language.C.Inline.Context

Methods

(==) :: Purity -> Purity -> Bool #

(/=) :: Purity -> Purity -> Bool #

Show Purity Source # 
Instance details

Defined in Language.C.Inline.Context

convertType :: Purity -> TypesTable -> Type CIdentifier -> Q (Maybe Type) Source #

Given a Context, it uses its ctxTypesTable to convert arbitrary C types.

type CArray = Ptr Source #

An alias for Ptr.

AntiQuoter

data AntiQuoter a Source #

Constructors

AntiQuoter 

Fields

  • aqParser :: forall m. CParser HaskellIdentifier m => m (CIdentifier, Type CIdentifier, a)

    Parses the body of the antiquotation, returning a hint for the name to assign to the variable that will replace the anti-quotation, the type of said variable, and some arbitrary data which will then be fed to aqMarshaller.

    The Type has Void as an identifier type to make sure that no names appear in it.

  • aqMarshaller :: Purity -> TypesTable -> Type CIdentifier -> a -> Q (Type, Exp)

    Takes the requested purity, the current TypesTable, and the type and the body returned by aqParser.

    Returns the Haskell type for the parameter, and the Haskell expression that will be passed in as the parameter.

    If the the type returned is ty, the Exp must have type forall a. (ty -> IO a) -> IO a. This allows to do resource handling when preparing C values.

    Care must be taken regarding Purity. Specifically, the generated IO computation must be idempotent to guarantee its safety when used in pure code. We cannot prevent the IO computation from being inlined, hence potentially duplicated. If non-idempotent marshallers are required (e.g. if an update to some global state is needed), it is best to throw an error when Purity is Pure (for example "you cannot use context X with pure"), which will show up at compile time.

type AntiQuoterId = String Source #

An identifier for a AntiQuoter.

data SomeAntiQuoter Source #

Existential wrapper around AntiQuoter.

Constructors

(Eq a, Typeable a) => SomeAntiQuoter (AntiQuoter a) 

Context

data Context Source #

A Context stores various information needed to produce the files with the C code derived from the inline C snippets.

Contexts can be composed with their Monoid instance, where mappend is right-biased -- in mappend x y y will take precedence over x.

Constructors

Context 

Fields

Instances
Semigroup Context Source # 
Instance details

Defined in Language.C.Inline.Context

Monoid Context Source # 
Instance details

Defined in Language.C.Inline.Context

baseCtx :: Context Source #

Context useful to work with vanilla C. Used by default.

ctxTypesTable: converts C basic types to their counterparts in Foreign.C.Types.

No ctxAntiQuoters.

fptrCtx :: Context Source #

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.

funCtx :: Context Source #

This Context includes a AntiQuoter that removes the need for explicitely creating FunPtrs, 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.

vecCtx :: Context Source #

This Context includes two AntiQuoters 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 IOVector a or Vector a, for some a. 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.

class VecCtx a where Source #

Type class used to implement the anti-quoters in vecCtx.

Associated Types

type VecCtxScalar a :: * Source #

Methods

vecCtxLength :: a -> Int Source #

vecCtxUnsafeWith :: a -> (Ptr (VecCtxScalar a) -> IO b) -> IO b Source #

Instances
Storable a => VecCtx (Vector a) Source # 
Instance details

Defined in Language.C.Inline.Context

Associated Types

type VecCtxScalar (Vector a) :: Type Source #

Storable a => VecCtx (IOVector a) Source # 
Instance details

Defined in Language.C.Inline.Context

Associated Types

type VecCtxScalar (IOVector a) :: Type Source #

bsCtx :: Context 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.