Safe Haskell | None |
---|---|
Language | Haskell2010 |
Enable painless embedding of C code in Haskell code. If you're interested in how to use the library, skip to the "Inline C" section. To build, read the first two sections.
This module is intended to be imported qualified:
import qualified Language.C.Inline as C
Synopsis
- data Context
- baseCtx :: Context
- fptrCtx :: Context
- funCtx :: Context
- vecCtx :: Context
- bsCtx :: Context
- context :: Context -> DecsQ
- substitute :: [(String, String -> String)] -> Q a -> Q a
- getHaskellType :: Bool -> String -> TypeQ
- exp :: QuasiQuoter
- pure :: QuasiQuoter
- block :: QuasiQuoter
- include :: String -> DecsQ
- verbatim :: String -> DecsQ
- withPtr :: Storable a => (Ptr a -> IO b) -> IO (a, b)
- withPtr_ :: Storable a => (Ptr a -> IO ()) -> IO a
- class WithPtrs a where
- type WithPtrsPtrs a :: *
- withPtrs :: (WithPtrsPtrs a -> IO b) -> IO (a, b)
- withPtrs_ :: (WithPtrsPtrs a -> IO ()) -> IO a
- funPtr :: QuasiQuoter
- mkFunPtr :: TypeQ -> ExpQ
- mkFunPtrFromName :: Name -> ExpQ
- peekFunPtr :: TypeQ -> ExpQ
- module Foreign.C.Types
GHCi
Currently inline-c
does not work in interpreted mode. However, GHCi
can still be used using the -fobject-code
flag. For speed, we
reccomend passing -fobject-code -O0
, for example
stack ghci --ghci-options='-fobject-code -O0'
or
cabal repl --ghc-options='-fobject-code -O0'
Contexts
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 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
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
.
context :: Context -> DecsQ Source #
Sets the Context
for the current module. This function, if
called, must be called before any of the other TH functions in this
module. Fails if that's not the case.
Substitution
substitute :: [(String, String -> String)] -> Q a -> Q a Source #
Define macros that can be used in the nested Template Haskell expression.
Macros can be used as @MACRO_NAME(input)
in inline-c quotes, and will transform their input with the given function.
They can be useful for passing in types when defining Haskell instances for C++ template types.
getHaskellType :: Bool -> String -> TypeQ Source #
Given a C type name, return the Haskell type in Template Haskell. The first parameter controls whether function pointers should be mapped as pure or IO functions.
Inline C
The quasiquoters below are the main interface to this library, for inlining C code into Haskell source files.
In general, quasiquoters are used like so:
[C.XXX| int { <C code> } |]
Where C.XXX
is one of the quasi-quoters defined in this section.
This syntax stands for a piece of typed C, decorated with a type:
- The first type to appear (
int
in the example) is the type of said C code. - The syntax of the
<C code>
depends on on the quasi-quoter used, and the anti-quoters available. Theexp
quasi-quoter expects a C expression. Theblock
quasi-quoter expects a list of statements, like the body of a function. Just like a C function, a block has a return type, matching the type of any values in anyreturn
statements appearing in the block.
See also the README.md
file for more documentation.
Anti-quoters
Haskell variables can be captured using anti-quoters. inline-c
provides a basic anti-quoting mechanism extensible with user-defined
anti-quoters (see Language.C.Inline.Context). The basic
anti-quoter lets you capture Haskell variables, for
example we might say
let x = pi / 3 in [exp
| double { cos($(double x)) } |]
Which would capture the Haskell variable x
of type
.CDouble
In C expressions the $
character is denoted using $$
.
Variable capture and the typing relation
The Haskell type of the inlined expression is determined by the specified
C return type. The relation between the C type and the Haskell type is
defined in the current Context
-- see convertCType
. C pointers and
arrays are both converted to Haskell
s, and function pointers are
converted to Ptr
s. Sized arrays are not supported.FunPtr
Similarly, when capturing Haskell variables using anti-quoting, their
type is assumed to be of the Haskell type corresponding to the C type
provided. For example, if we capture variable x
using double x
in the parameter list, the code will expect a variable x
of type
CDouble
in Haskell (when using baseCtx
).
Purity
The exp
and block
quasi-quotes denote computations in the Purity
monad.
pure
denotes a pure value, expressed as a C expression.
Safe and unsafe
calls
unsafe
variants of the quasi-quoters are provided in
Language.C.Inline.Unsafe to call the C code unsafely, in the sense that the
C code will block the RTS, but with the advantage of a faster call to the
foreign code. See
https://www.haskell.org/onlinereport/haskell2010/haskellch8.html#x15-1590008.4.3.
Examples
Inline C expression
{-# LANGUAGE QuasiQuotes #-} import qualified Language.C.Inline as C import qualified Language.C.Inline.Unsafe as CU import Foreign.C.Types C.include
"<math.h>" c_cos ::CDouble
-> IOCDouble
c_cos x = [C.exp| double { cos($(double x)) } |] faster_c_cos ::CDouble
-> IOCDouble
faster_c_cos x = [CU.exp| double { cos($(double x)) } |]
Inline C statements
{-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE TemplateHaskell #-} import qualified Data.Vector.Storable.Mutable as V import qualified Language.C.Inline as C import Foreign.C.Types C.include
"<stdio.h>" parseVector ::CInt
->Purity
(V.IOVectorCDouble
) parseVector len = do vec <- V.new $fromIntegral
len0 V.unsafeWith vec $ \ptr -> [C.block
| void { int i; for (i = 0; i < $(int len); i++) { scanf("%lf ", &$(double *ptr)[i]); } } |]return
vec
How it works
For each quasi-quotation of C code, a C function is generated in a C file
corresponding to the current Haskell file. Every inline C expression will result
in a corresponding C function.
For example, if we define c_cos
as in the example above in CCos.hs
, we will get a file containing
#include math.h double inline_c_Main_0_a03fba228a6d8e36ea7d69381f87bade594c949d(double x_inline_c_0) { return cos(x_inline_c_0); }
Every anti-quotation will correspond to an argument in the C function. If the same Haskell variable is anti-quoted twice, this will result in two arguments.
The C function is then automatically compiled and invoked from Haskell with the correct arguments passed in.
exp :: QuasiQuoter Source #
C expressions.
pure :: QuasiQuoter Source #
Variant of exp
, for use with expressions known to have no side effects.
BEWARE: Use this function with caution, only when you know what you are
doing. If an expression does in fact have side-effects, then indiscriminate
use of pure
may endanger referential transparency, and in principle even
type safety. Also note that the function might be called multiple times,
given that unsafeDupablePerformIO
is used to call the
provided C code. Please refer to the documentation for
unsafePerformIO
for more details.
unsafeDupablePerformIO is used to ensure good performance using the
threaded runtime.
block :: QuasiQuoter Source #
C code blocks (i.e. statements).
include :: String -> DecsQ Source #
Emits a CPP include directive for C code associated with the current module. To avoid having to escape quotes, the function itself adds them when appropriate, so that
include "foo.h" ==> #include "foo.h"
but
include "<foo>" ==> #include <foo>
verbatim :: String -> DecsQ Source #
Emits an arbitrary C string to the C code associated with the current module. Use with care.
Ptr
utils
class WithPtrs a where Source #
Type class with methods useful to allocate and peek multiple pointers at once:
withPtrs_ :: (Storable a, Storable b) => ((Ptr a, Ptr b) -> IO ()) -> IO (a, b) withPtrs_ :: (Storable a, Storable b, Storable c) => ((Ptr a, Ptr b, Ptr c) -> IO ()) -> IO (a, b, c) ...
type WithPtrsPtrs a :: * Source #
Instances
FunPtr
utils
funPtr :: QuasiQuoter Source #
Easily get a FunPtr
:
let fp :: FunPtr (Ptr CInt -> IO ()) = [C.funPtr| void poke42(int *ptr) { *ptr = 42; } |]
Especially useful to generate finalizers that require C code.
Most importantly, this allows you to write newForeignPtr
invocations conveniently:
do let c_finalizer_funPtr = [C.funPtr| void myfree(char * ptr) { free(ptr); } |] fp <- newForeignPtr c_finalizer_funPtr objPtr
Using where possible newForeignPtr
is superior to
resorting to its delayed-by-a-thread alternative newForeignPtr
from Foreign.Concurrent which takes an IO ()
Haskell finaliser action:
With the non-concurrent newForeignPtr
you can guarantee that the finaliser
will actually be run
- when a GC is executed under memory pressure, because it can point directly to a C function that doesn't have to run any Haskell code (which is problematic when you're out of memory)
- when the program terminates (
newForeignPtr
's finaliser will likely NOT be called if your main thread exits, making your program e.g. not Valgrind-clean if your finaliser isfree
or C++'sdelete
).
funPtr
makes the normal newForeignPtr
as convenient as its concurrent
counterpart.
FunPtr
conversion
mkFunPtrFromName :: Name -> ExpQ Source #
$(
, if mkFunPtrFromName
'foo)foo ::
, splices in an expression of type CDouble
-> IO
CDouble
.IO
(FunPtr
(CDouble
-> IO
CDouble
))
peekFunPtr :: TypeQ -> ExpQ Source #
$(
generates a foreign import
dynamic of typepeekFunPtr
[t| CDouble
-> IO
CDouble
|])
FunPtr
(CDouble
->IO
CDouble
) -> (CDouble
->IO
CDouble
)
And invokes it.
C types re-exports
module Foreign.C.Types