[OCaml] De-duplicate llvm_raise and llvm_string_of_message.
[oota-llvm.git] / bindings / ocaml / executionengine / executionengine_ocaml.c
1 /*===-- executionengine_ocaml.c - LLVM OCaml Glue ---------------*- C++ -*-===*\
2 |*                                                                            *|
3 |*                     The LLVM Compiler Infrastructure                       *|
4 |*                                                                            *|
5 |* This file is distributed under the University of Illinois Open Source      *|
6 |* License. See LICENSE.TXT for details.                                      *|
7 |*                                                                            *|
8 |*===----------------------------------------------------------------------===*|
9 |*                                                                            *|
10 |* This file glues LLVM's OCaml interface to its C interface. These functions *|
11 |* are by and large transparent wrappers to the corresponding C functions.    *|
12 |*                                                                            *|
13 |* Note that these functions intentionally take liberties with the CAMLparamX *|
14 |* macros, since most of the parameters are not GC heap objects.              *|
15 |*                                                                            *|
16 \*===----------------------------------------------------------------------===*/
17
18 #include <string.h>
19 #include <assert.h>
20 #include "llvm-c/ExecutionEngine.h"
21 #include "llvm-c/Target.h"
22 #include "caml/alloc.h"
23 #include "caml/custom.h"
24 #include "caml/fail.h"
25 #include "caml/memory.h"
26 #include "caml/callback.h"
27
28 void llvm_raise(value Prototype, char *Message);
29
30 /*--... Operations on generic values .......................................--*/
31
32 #define Genericvalue_val(v)  (*(LLVMGenericValueRef *)(Data_custom_val(v)))
33
34 static void llvm_finalize_generic_value(value GenVal) {
35   LLVMDisposeGenericValue(Genericvalue_val(GenVal));
36 }
37
38 static struct custom_operations generic_value_ops = {
39   (char *) "Llvm_executionengine.GenericValue.t",
40   llvm_finalize_generic_value,
41   custom_compare_default,
42   custom_hash_default,
43   custom_serialize_default,
44   custom_deserialize_default,
45   custom_compare_ext_default
46 };
47
48 static value alloc_generic_value(LLVMGenericValueRef Ref) {
49   value Val = alloc_custom(&generic_value_ops, sizeof(LLVMGenericValueRef), 0, 1);
50   Genericvalue_val(Val) = Ref;
51   return Val;
52 }
53
54 /* Llvm.lltype -> float -> t */
55 CAMLprim value llvm_genericvalue_of_float(LLVMTypeRef Ty, value N) {
56   CAMLparam1(N);
57   CAMLreturn(alloc_generic_value(
58     LLVMCreateGenericValueOfFloat(Ty, Double_val(N))));
59 }
60
61 /* 'a -> t */
62 CAMLprim value llvm_genericvalue_of_pointer(value V) {
63   CAMLparam1(V);
64   CAMLreturn(alloc_generic_value(LLVMCreateGenericValueOfPointer(Op_val(V))));
65 }
66
67 /* Llvm.lltype -> int -> t */
68 CAMLprim value llvm_genericvalue_of_int(LLVMTypeRef Ty, value Int) {
69   return alloc_generic_value(LLVMCreateGenericValueOfInt(Ty, Int_val(Int), 1));
70 }
71
72 /* Llvm.lltype -> int32 -> t */
73 CAMLprim value llvm_genericvalue_of_int32(LLVMTypeRef Ty, value Int32) {
74   CAMLparam1(Int32);
75   CAMLreturn(alloc_generic_value(
76     LLVMCreateGenericValueOfInt(Ty, Int32_val(Int32), 1)));
77 }
78
79 /* Llvm.lltype -> nativeint -> t */
80 CAMLprim value llvm_genericvalue_of_nativeint(LLVMTypeRef Ty, value NatInt) {
81   CAMLparam1(NatInt);
82   CAMLreturn(alloc_generic_value(
83     LLVMCreateGenericValueOfInt(Ty, Nativeint_val(NatInt), 1)));
84 }
85
86 /* Llvm.lltype -> int64 -> t */
87 CAMLprim value llvm_genericvalue_of_int64(LLVMTypeRef Ty, value Int64) {
88   CAMLparam1(Int64);
89   CAMLreturn(alloc_generic_value(
90     LLVMCreateGenericValueOfInt(Ty, Int64_val(Int64), 1)));
91 }
92
93 /* Llvm.lltype -> t -> float */
94 CAMLprim value llvm_genericvalue_as_float(LLVMTypeRef Ty, value GenVal) {
95   CAMLparam1(GenVal);
96   CAMLreturn(copy_double(
97     LLVMGenericValueToFloat(Ty, Genericvalue_val(GenVal))));
98 }
99
100 /* t -> 'a */
101 CAMLprim value llvm_genericvalue_as_pointer(value GenVal) {
102   return Val_op(LLVMGenericValueToPointer(Genericvalue_val(GenVal)));
103 }
104
105 /* t -> int */
106 CAMLprim value llvm_genericvalue_as_int(value GenVal) {
107   assert(LLVMGenericValueIntWidth(Genericvalue_val(GenVal)) <= 8 * sizeof(value)
108          && "Generic value too wide to treat as an int!");
109   return Val_int(LLVMGenericValueToInt(Genericvalue_val(GenVal), 1));
110 }
111
112 /* t -> int32 */
113 CAMLprim value llvm_genericvalue_as_int32(value GenVal) {
114   CAMLparam1(GenVal);
115   assert(LLVMGenericValueIntWidth(Genericvalue_val(GenVal)) <= 32
116          && "Generic value too wide to treat as an int32!");
117   CAMLreturn(copy_int32(LLVMGenericValueToInt(Genericvalue_val(GenVal), 1)));
118 }
119
120 /* t -> int64 */
121 CAMLprim value llvm_genericvalue_as_int64(value GenVal) {
122   CAMLparam1(GenVal);
123   assert(LLVMGenericValueIntWidth(Genericvalue_val(GenVal)) <= 64
124          && "Generic value too wide to treat as an int64!");
125   CAMLreturn(copy_int64(LLVMGenericValueToInt(Genericvalue_val(GenVal), 1)));
126 }
127
128 /* t -> nativeint */
129 CAMLprim value llvm_genericvalue_as_nativeint(value GenVal) {
130   CAMLparam1(GenVal);
131   assert(LLVMGenericValueIntWidth(Genericvalue_val(GenVal)) <= 8 * sizeof(value)
132          && "Generic value too wide to treat as a nativeint!");
133   CAMLreturn(copy_nativeint(LLVMGenericValueToInt(Genericvalue_val(GenVal),1)));
134 }
135
136
137 /*--... Operations on execution engines ....................................--*/
138
139 /* unit -> bool */
140 CAMLprim value llvm_initialize_native_target(value Unit) {
141   LLVMLinkInInterpreter();
142   LLVMLinkInMCJIT();
143
144   return Val_bool(!LLVMInitializeNativeTarget() &&
145                   !LLVMInitializeNativeAsmParser() &&
146                   !LLVMInitializeNativeAsmPrinter());
147 }
148
149 /* llmodule -> ExecutionEngine.t */
150 CAMLprim LLVMExecutionEngineRef llvm_ee_create(LLVMModuleRef M) {
151   LLVMExecutionEngineRef Interp;
152   char *Error;
153   if (LLVMCreateExecutionEngineForModule(&Interp, M, &Error))
154     llvm_raise(*caml_named_value("Llvm_executionengine.Error"), Error);
155   return Interp;
156 }
157
158 /* llmodule -> ExecutionEngine.t */
159 CAMLprim LLVMExecutionEngineRef
160 llvm_ee_create_interpreter(LLVMModuleRef M) {
161   LLVMExecutionEngineRef Interp;
162   char *Error;
163   if (LLVMCreateInterpreterForModule(&Interp, M, &Error))
164     llvm_raise(*caml_named_value("Llvm_executionengine.Error"), Error);
165   return Interp;
166 }
167
168 /* llmodule -> int -> ExecutionEngine.t */
169 CAMLprim LLVMExecutionEngineRef
170 llvm_ee_create_jit(LLVMModuleRef M, value OptLevel) {
171   LLVMExecutionEngineRef JIT;
172   char *Error;
173   if (LLVMCreateJITCompilerForModule(&JIT, M, Int_val(OptLevel), &Error))
174     llvm_raise(*caml_named_value("Llvm_executionengine.Error"), Error);
175   return JIT;
176 }
177
178 /* llmodule -> llcompileroption -> ExecutionEngine.t */
179 CAMLprim LLVMExecutionEngineRef
180 llvm_ee_create_mcjit(LLVMModuleRef M, value OptRecord) {
181   LLVMExecutionEngineRef MCJIT;
182   char *Error;
183   struct LLVMMCJITCompilerOptions Options;
184
185   LLVMInitializeMCJITCompilerOptions(&Options, sizeof(Options));
186   Options.OptLevel = Int_val(Field(OptRecord, 0));
187   Options.CodeModel = Int_val(Field(OptRecord, 1));
188   Options.NoFramePointerElim = Int_val(Field(OptRecord, 2));
189   Options.EnableFastISel = Int_val(Field(OptRecord, 3));
190   Options.MCJMM = NULL;
191
192   if (LLVMCreateMCJITCompilerForModule(&MCJIT, M, &Options,
193                                       sizeof(Options), &Error))
194     llvm_raise(*caml_named_value("Llvm_executionengine.Error"), Error);
195   return MCJIT;
196 }
197
198 /* ExecutionEngine.t -> unit */
199 CAMLprim value llvm_ee_dispose(LLVMExecutionEngineRef EE) {
200   LLVMDisposeExecutionEngine(EE);
201   return Val_unit;
202 }
203
204 /* llmodule -> ExecutionEngine.t -> unit */
205 CAMLprim value llvm_ee_add_module(LLVMModuleRef M, LLVMExecutionEngineRef EE) {
206   LLVMAddModule(EE, M);
207   return Val_unit;
208 }
209
210 /* llmodule -> ExecutionEngine.t -> llmodule */
211 CAMLprim LLVMModuleRef llvm_ee_remove_module(LLVMModuleRef M,
212                                              LLVMExecutionEngineRef EE) {
213   LLVMModuleRef RemovedModule;
214   char *Error;
215   if (LLVMRemoveModule(EE, M, &RemovedModule, &Error))
216     llvm_raise(*caml_named_value("Llvm_executionengine.Error"), Error);
217   return RemovedModule;
218 }
219
220 /* string -> ExecutionEngine.t -> llvalue option */
221 CAMLprim value llvm_ee_find_function(value Name, LLVMExecutionEngineRef EE) {
222   CAMLparam1(Name);
223   CAMLlocal1(Option);
224   LLVMValueRef Found;
225   if (LLVMFindFunction(EE, String_val(Name), &Found))
226     CAMLreturn(Val_unit);
227   Option = alloc(1, 0);
228   Field(Option, 0) = Val_op(Found);
229   CAMLreturn(Option);
230 }
231
232 /* llvalue -> GenericValue.t array -> ExecutionEngine.t -> GenericValue.t */
233 CAMLprim value llvm_ee_run_function(LLVMValueRef F, value Args,
234                                     LLVMExecutionEngineRef EE) {
235   unsigned NumArgs;
236   LLVMGenericValueRef Result, *GVArgs;
237   unsigned I;
238
239   NumArgs = Wosize_val(Args);
240   GVArgs = (LLVMGenericValueRef*) malloc(NumArgs * sizeof(LLVMGenericValueRef));
241   for (I = 0; I != NumArgs; ++I)
242     GVArgs[I] = Genericvalue_val(Field(Args, I));
243
244   Result = LLVMRunFunction(EE, F, NumArgs, GVArgs);
245
246   free(GVArgs);
247   return alloc_generic_value(Result);
248 }
249
250 /* ExecutionEngine.t -> unit */
251 CAMLprim value llvm_ee_run_static_ctors(LLVMExecutionEngineRef EE) {
252   LLVMRunStaticConstructors(EE);
253   return Val_unit;
254 }
255
256 /* ExecutionEngine.t -> unit */
257 CAMLprim value llvm_ee_run_static_dtors(LLVMExecutionEngineRef EE) {
258   LLVMRunStaticDestructors(EE);
259   return Val_unit;
260 }
261
262 /* llvalue -> string array -> (string * string) array -> ExecutionEngine.t ->
263    int */
264 CAMLprim value llvm_ee_run_function_as_main(LLVMValueRef F,
265                                             value Args, value Env,
266                                             LLVMExecutionEngineRef EE) {
267   CAMLparam2(Args, Env);
268   int I, NumArgs, NumEnv, EnvSize, Result;
269   const char **CArgs, **CEnv;
270   char *CEnvBuf, *Pos;
271
272   NumArgs = Wosize_val(Args);
273   NumEnv = Wosize_val(Env);
274
275   /* Build the environment. */
276   CArgs = (const char **) malloc(NumArgs * sizeof(char*));
277   for (I = 0; I != NumArgs; ++I)
278     CArgs[I] = String_val(Field(Args, I));
279
280   /* Compute the size of the environment string buffer. */
281   for (I = 0, EnvSize = 0; I != NumEnv; ++I) {
282     EnvSize += strlen(String_val(Field(Field(Env, I), 0))) + 1;
283     EnvSize += strlen(String_val(Field(Field(Env, I), 1))) + 1;
284   }
285
286   /* Build the environment. */
287   CEnv = (const char **) malloc((NumEnv + 1) * sizeof(char*));
288   CEnvBuf = (char*) malloc(EnvSize);
289   Pos = CEnvBuf;
290   for (I = 0; I != NumEnv; ++I) {
291     char *Name  = String_val(Field(Field(Env, I), 0)),
292          *Value = String_val(Field(Field(Env, I), 1));
293     int NameLen  = strlen(Name),
294         ValueLen = strlen(Value);
295
296     CEnv[I] = Pos;
297     memcpy(Pos, Name, NameLen);
298     Pos += NameLen;
299     *Pos++ = '=';
300     memcpy(Pos, Value, ValueLen);
301     Pos += ValueLen;
302     *Pos++ = '\0';
303   }
304   CEnv[NumEnv] = NULL;
305
306   Result = LLVMRunFunctionAsMain(EE, F, NumArgs, CArgs, CEnv);
307
308   free(CArgs);
309   free(CEnv);
310   free(CEnvBuf);
311
312   CAMLreturn(Val_int(Result));
313 }
314
315 /* llvalue -> ExecutionEngine.t -> unit */
316 CAMLprim value llvm_ee_free_machine_code(LLVMValueRef F,
317                                          LLVMExecutionEngineRef EE) {
318   LLVMFreeMachineCodeForFunction(EE, F);
319   return Val_unit;
320 }
321
322 extern value llvm_alloc_data_layout(LLVMTargetDataRef TargetData);
323
324 /* ExecutionEngine.t -> Llvm_target.DataLayout.t */
325 CAMLprim value llvm_ee_get_data_layout(LLVMExecutionEngineRef EE) {
326   value DataLayout;
327   LLVMTargetDataRef OrigDataLayout;
328   char* TargetDataCStr;
329
330   OrigDataLayout = LLVMGetExecutionEngineTargetData(EE);
331   TargetDataCStr = LLVMCopyStringRepOfTargetData(OrigDataLayout);
332   DataLayout = llvm_alloc_data_layout(LLVMCreateTargetData(TargetDataCStr));
333   LLVMDisposeMessage(TargetDataCStr);
334
335   return DataLayout;
336 }