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