executionengine_ocaml.c
4.74 KB
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
/*===-- executionengine_ocaml.c - LLVM OCaml Glue ---------------*- C++ -*-===*\
|* *|
|* Part of the LLVM Project, under the Apache License v2.0 with LLVM *|
|* Exceptions. *|
|* See https://llvm.org/LICENSE.txt for license information. *|
|* SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception *|
|* *|
|*===----------------------------------------------------------------------===*|
|* *|
|* This file glues LLVM's OCaml interface to its C interface. These functions *|
|* are by and large transparent wrappers to the corresponding C functions. *|
|* *|
|* Note that these functions intentionally take liberties with the CAMLparamX *|
|* macros, since most of the parameters are not GC heap objects. *|
|* *|
\*===----------------------------------------------------------------------===*/
#include <string.h>
#include <assert.h>
#include "llvm-c/Core.h"
#include "llvm-c/ExecutionEngine.h"
#include "llvm-c/Target.h"
#include "caml/alloc.h"
#include "caml/custom.h"
#include "caml/fail.h"
#include "caml/memory.h"
#include "caml/callback.h"
void llvm_raise(value Prototype, char *Message);
/* unit -> bool */
CAMLprim value llvm_ee_initialize(value Unit) {
LLVMLinkInMCJIT();
return Val_bool(!LLVMInitializeNativeTarget() &&
!LLVMInitializeNativeAsmParser() &&
!LLVMInitializeNativeAsmPrinter());
}
/* llmodule -> llcompileroption -> ExecutionEngine.t */
CAMLprim LLVMExecutionEngineRef llvm_ee_create(value OptRecordOpt, LLVMModuleRef M) {
value OptRecord;
LLVMExecutionEngineRef MCJIT;
char *Error;
struct LLVMMCJITCompilerOptions Options;
LLVMInitializeMCJITCompilerOptions(&Options, sizeof(Options));
if (OptRecordOpt != Val_int(0)) {
OptRecord = Field(OptRecordOpt, 0);
Options.OptLevel = Int_val(Field(OptRecord, 0));
Options.CodeModel = Int_val(Field(OptRecord, 1));
Options.NoFramePointerElim = Int_val(Field(OptRecord, 2));
Options.EnableFastISel = Int_val(Field(OptRecord, 3));
Options.MCJMM = NULL;
}
if (LLVMCreateMCJITCompilerForModule(&MCJIT, M, &Options,
sizeof(Options), &Error))
llvm_raise(*caml_named_value("Llvm_executionengine.Error"), Error);
return MCJIT;
}
/* ExecutionEngine.t -> unit */
CAMLprim value llvm_ee_dispose(LLVMExecutionEngineRef EE) {
LLVMDisposeExecutionEngine(EE);
return Val_unit;
}
/* llmodule -> ExecutionEngine.t -> unit */
CAMLprim value llvm_ee_add_module(LLVMModuleRef M, LLVMExecutionEngineRef EE) {
LLVMAddModule(EE, M);
return Val_unit;
}
/* llmodule -> ExecutionEngine.t -> llmodule */
CAMLprim value llvm_ee_remove_module(LLVMModuleRef M, LLVMExecutionEngineRef EE) {
LLVMModuleRef RemovedModule;
char *Error;
if (LLVMRemoveModule(EE, M, &RemovedModule, &Error))
llvm_raise(*caml_named_value("Llvm_executionengine.Error"), Error);
return Val_unit;
}
/* ExecutionEngine.t -> unit */
CAMLprim value llvm_ee_run_static_ctors(LLVMExecutionEngineRef EE) {
LLVMRunStaticConstructors(EE);
return Val_unit;
}
/* ExecutionEngine.t -> unit */
CAMLprim value llvm_ee_run_static_dtors(LLVMExecutionEngineRef EE) {
LLVMRunStaticDestructors(EE);
return Val_unit;
}
extern value llvm_alloc_data_layout(LLVMTargetDataRef TargetData);
/* ExecutionEngine.t -> Llvm_target.DataLayout.t */
CAMLprim value llvm_ee_get_data_layout(LLVMExecutionEngineRef EE) {
value DataLayout;
LLVMTargetDataRef OrigDataLayout;
char* TargetDataCStr;
OrigDataLayout = LLVMGetExecutionEngineTargetData(EE);
TargetDataCStr = LLVMCopyStringRepOfTargetData(OrigDataLayout);
DataLayout = llvm_alloc_data_layout(LLVMCreateTargetData(TargetDataCStr));
LLVMDisposeMessage(TargetDataCStr);
return DataLayout;
}
/* Llvm.llvalue -> int64 -> llexecutionengine -> unit */
CAMLprim value llvm_ee_add_global_mapping(LLVMValueRef Global, value Ptr,
LLVMExecutionEngineRef EE) {
LLVMAddGlobalMapping(EE, Global, (void*) (Int64_val(Ptr)));
return Val_unit;
}
CAMLprim value llvm_ee_get_global_value_address(value Name,
LLVMExecutionEngineRef EE) {
return caml_copy_int64((int64_t) LLVMGetGlobalValueAddress(EE, String_val(Name)));
}
CAMLprim value llvm_ee_get_function_address(value Name,
LLVMExecutionEngineRef EE) {
return caml_copy_int64((int64_t) LLVMGetFunctionAddress(EE, String_val(Name)));
}