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