| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Language.C.Inline.Internal
Contents
- setContext :: Context -> Q ()
- getContext :: Q Context
- emitVerbatim :: String -> DecsQ
- data Code = Code {
- codeCallSafety :: Safety
- codeType :: TypeQ
- codeFunName :: String
- codeDefs :: String
- inlineCode :: Code -> ExpQ
- inlineExp :: Safety -> TypeQ -> Type -> [(Identifier, Type)] -> String -> ExpQ
- inlineItems :: Safety -> TypeQ -> Type -> [(Identifier, Type)] -> String -> ExpQ
- data SomeEq
- toSomeEq :: (Eq a, Typeable a) => a -> SomeEq
- fromSomeEq :: (Eq a, Typeable a) => SomeEq -> Maybe a
- data ParameterType
- data ParseTypedC = ParseTypedC {
- ptcReturnType :: Type
- ptcParameters :: [(Identifier, Type, ParameterType)]
- ptcBody :: String
- parseTypedC :: forall m. CParser m => AntiQuoters -> m ParseTypedC
- runParserInQ :: String -> IsTypeName -> (forall m. CParser m => m a) -> Q a
- genericQuote :: Purity -> (TypeQ -> Type -> [(Identifier, Type)] -> String -> ExpQ) -> QuasiQuoter
Context handling
setContext :: Context -> Q () 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.
getContext :: Q Context Source
Gets the current Context. Also makes sure that the current
module is initialised.
Emitting and invoking C code
The functions in this section let us access more the C file
associated with the current module. They can be used to build
additional features on top of the basic machinery. All of
inline-c is based upon the functions defined here.
Emitting C code
emitVerbatim :: String -> DecsQ Source
Simply appends some string to the module's C file. Use with care.
Inlining C code
We use the Code data structure to represent some C code that we
want to emit to the module's C file and immediately generate a
foreign call to. For this reason, Code includes both some C
definition, and enough information to be able to generate a foreign
call -- specifically the name of the function to call and the Haskell
type.
All the quasi-quoters work by constructing a Code and calling
inlineCode.
Data type representing a list of C definitions with a typed and named entry function.
We use it as a basis to inline and call C code.
Constructors
| Code | |
Fields
| |
inlineCode :: Code -> ExpQ Source
Inlines a piece of code inline. The resulting Exp will have
the type specified in the codeType.
In practice, this function outputs the C code to the module's C file,
and then inserts a foreign call of type codeType calling the
provided codeFunName.
Example:
c_add :: Int -> Int -> Int
c_add = $(inlineCode $ Code
TH.Unsafe -- Call safety
[t| Int -> Int -> Int |] -- Call type
"francescos_add" -- Call name
-- C Code
"int francescos_add(int x, int y) { int z = x + y; return z; }")
Arguments
| :: Safety | Safety of the foreign call |
| -> TypeQ | Type of the foreign call |
| -> Type | Return type of the C expr |
| -> [(Identifier, Type)] | Parameters of the C expr |
| -> String | The C expression |
| -> ExpQ |
Same as inlineCItems, but with a single expression.
c_cos :: Double -> Double
c_cos = $(inlineExp
TH.Unsafe
[t| Double -> Double |]
(quickCParser_ "double" parseType)
[("x", quickCParser_ "double") parseType]
"cos(x)")
Arguments
| :: Safety | Safety of the foreign call |
| -> TypeQ | Type of the foreign call |
| -> Type | Return type of the C expr |
| -> [(Identifier, Type)] | Parameters of the C expr |
| -> String | The C items |
| -> ExpQ |
Same as inlineCode, but accepts a string containing a list of C
statements instead instead than a full-blown Code. A function
containing the provided statement will be automatically generated.
c_cos :: Double -> Double
c_cos = $(inlineItems
TH.Unsafe
[t| Double -> Double |]
(quickCParser_ "double" parseType)
[("x", quickCParser_ "double" parseType)]
"return cos(x);")
Parsing
These functions are used to parse the anti-quotations. They're exposed for testing purposes, you really should not use them.
data ParseTypedC Source
Constructors
| ParseTypedC | |
Fields
| |
Arguments
| :: CParser m | |
| => AntiQuoters | |
| -> m ParseTypedC | Returns the return type, the captured variables, and the body. |
runParserInQ :: String -> IsTypeName -> (forall m. CParser m => m a) -> Q a Source
Utility functions for writing quasiquoters
Arguments
| :: Purity | |
| -> (TypeQ -> Type -> [(Identifier, Type)] -> String -> ExpQ) | Function taking that something and building an expression, see
|
| -> QuasiQuoter |