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