1 /*===-- executionengine_ocaml.c - LLVM Ocaml Glue ---------------*- C++ -*-===*\
3 |* The LLVM Compiler Infrastructure *|
5 |* This file is distributed under the University of Illinois Open Source *|
6 |* License. See LICENSE.TXT for details. *|
8 |*===----------------------------------------------------------------------===*|
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. *|
13 |* Note that these functions intentionally take liberties with the CAMLparamX *|
14 |* macros, since most of the parameters are not GC heap objects. *|
16 \*===----------------------------------------------------------------------===*/
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"
27 /* Force the LLVM interpreter and JIT to be linked in. */
28 void llvm_initialize(void) {
29 LLVMLinkInInterpreter();
34 CAMLprim value
llvm_initialize_native_target(value Unit
) {
35 return Val_bool(LLVMInitializeNativeTarget());
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
;
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
);
48 static void llvm_raise(value Prototype
, char *Message
) {
49 CAMLparam1(Prototype
);
50 CAMLlocal1(CamlMessage
);
52 CamlMessage
= copy_string(Message
);
53 LLVMDisposeMessage(Message
);
55 raise_with_arg(Prototype
, CamlMessage
);
56 abort(); /* NOTREACHED */
58 CAMLnoreturn
; /* Silences warnings, but is missing in some versions. */
63 /*--... Operations on generic values .......................................--*/
65 #define Genericvalue_val(v) (*(LLVMGenericValueRef *)(Data_custom_val(v)))
67 static void llvm_finalize_generic_value(value GenVal
) {
68 LLVMDisposeGenericValue(Genericvalue_val(GenVal
));
71 static struct custom_operations generic_value_ops
= {
72 (char *) "LLVMGenericValue",
73 llvm_finalize_generic_value
,
74 custom_compare_default
,
76 custom_serialize_default
,
77 custom_deserialize_default
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
;
86 /* Llvm.lltype -> float -> t */
87 CAMLprim value
llvm_genericvalue_of_float(LLVMTypeRef Ty
, value N
) {
89 CAMLreturn(alloc_generic_value(
90 LLVMCreateGenericValueOfFloat(Ty
, Double_val(N
))));
94 CAMLprim value
llvm_genericvalue_of_value(value V
) {
96 CAMLreturn(alloc_generic_value(LLVMCreateGenericValueOfPointer(Op_val(V
))));
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));
104 /* Llvm.lltype -> int32 -> t */
105 CAMLprim value
llvm_genericvalue_of_int32(LLVMTypeRef Ty
, value Int32
) {
107 CAMLreturn(alloc_generic_value(
108 LLVMCreateGenericValueOfInt(Ty
, Int32_val(Int32
), 1)));
111 /* Llvm.lltype -> nativeint -> t */
112 CAMLprim value
llvm_genericvalue_of_nativeint(LLVMTypeRef Ty
, value NatInt
) {
114 CAMLreturn(alloc_generic_value(
115 LLVMCreateGenericValueOfInt(Ty
, Nativeint_val(NatInt
), 1)));
118 /* Llvm.lltype -> int64 -> t */
119 CAMLprim value
llvm_genericvalue_of_int64(LLVMTypeRef Ty
, value Int64
) {
121 CAMLreturn(alloc_generic_value(
122 LLVMCreateGenericValueOfInt(Ty
, Int64_val(Int64
), 1)));
125 /* Llvm.lltype -> t -> float */
126 CAMLprim value
llvm_genericvalue_as_float(LLVMTypeRef Ty
, value GenVal
) {
128 CAMLreturn(copy_double(
129 LLVMGenericValueToFloat(Ty
, Genericvalue_val(GenVal
))));
133 CAMLprim value
llvm_genericvalue_as_value(value GenVal
) {
134 return Val_op(LLVMGenericValueToPointer(Genericvalue_val(GenVal
)));
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));
145 CAMLprim value
llvm_genericvalue_as_int32(value 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)));
153 CAMLprim value
llvm_genericvalue_as_int64(value 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)));
161 CAMLprim value
llvm_genericvalue_as_nativeint(value 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)));
169 /*--... Operations on execution engines ....................................--*/
171 /* llmoduleprovider -> ExecutionEngine.t */
172 CAMLprim LLVMExecutionEngineRef
llvm_ee_create(LLVMModuleProviderRef MP
) {
173 LLVMExecutionEngineRef Interp
;
175 if (LLVMCreateExecutionEngine(&Interp
, MP
, &Error
))
176 llvm_raise(llvm_ee_error_exn
, Error
);
180 /* llmoduleprovider -> ExecutionEngine.t */
181 CAMLprim LLVMExecutionEngineRef
182 llvm_ee_create_interpreter(LLVMModuleProviderRef MP
) {
183 LLVMExecutionEngineRef Interp
;
185 if (LLVMCreateInterpreter(&Interp
, MP
, &Error
))
186 llvm_raise(llvm_ee_error_exn
, Error
);
190 /* llmoduleprovider -> ExecutionEngine.t */
191 CAMLprim LLVMExecutionEngineRef
192 llvm_ee_create_jit(LLVMModuleProviderRef MP
) {
193 LLVMExecutionEngineRef JIT
;
195 if (LLVMCreateJITCompiler(&JIT
, MP
, 3, &Error
))
196 llvm_raise(llvm_ee_error_exn
, Error
);
200 /* llmoduleprovider -> ExecutionEngine.t */
201 CAMLprim LLVMExecutionEngineRef
202 llvm_ee_create_fast_jit(LLVMModuleProviderRef MP
) {
203 LLVMExecutionEngineRef JIT
;
205 if (LLVMCreateJITCompiler(&JIT
, MP
, 0, &Error
))
206 llvm_raise(llvm_ee_error_exn
, Error
);
210 /* ExecutionEngine.t -> unit */
211 CAMLprim value
llvm_ee_dispose(LLVMExecutionEngineRef EE
) {
212 LLVMDisposeExecutionEngine(EE
);
216 /* llmoduleprovider -> ExecutionEngine.t -> unit */
217 CAMLprim value
llvm_ee_add_mp(LLVMModuleProviderRef MP
,
218 LLVMExecutionEngineRef EE
) {
219 LLVMAddModuleProvider(EE
, MP
);
223 /* llmoduleprovider -> ExecutionEngine.t -> llmodule */
224 CAMLprim LLVMModuleRef
llvm_ee_remove_mp(LLVMModuleProviderRef MP
,
225 LLVMExecutionEngineRef EE
) {
226 LLVMModuleRef RemovedModule
;
228 if (LLVMRemoveModuleProvider(EE
, MP
, &RemovedModule
, &Error
))
229 llvm_raise(llvm_ee_error_exn
, Error
);
230 return RemovedModule
;
233 /* string -> ExecutionEngine.t -> llvalue option */
234 CAMLprim value
llvm_ee_find_function(value Name
, LLVMExecutionEngineRef EE
) {
238 if (LLVMFindFunction(EE
, String_val(Name
), &Found
))
239 CAMLreturn(Val_unit
);
240 Option
= alloc(1, 1);
241 Field(Option
, 0) = Val_op(Found
);
245 /* llvalue -> GenericValue.t array -> ExecutionEngine.t -> GenericValue.t */
246 CAMLprim value
llvm_ee_run_function(LLVMValueRef F
, value Args
,
247 LLVMExecutionEngineRef EE
) {
249 LLVMGenericValueRef Result
, *GVArgs
;
252 NumArgs
= Wosize_val(Args
);
253 GVArgs
= (LLVMGenericValueRef
*) malloc(NumArgs
* sizeof(LLVMGenericValueRef
));
254 for (I
= 0; I
!= NumArgs
; ++I
)
255 GVArgs
[I
] = Genericvalue_val(Field(Args
, I
));
257 Result
= LLVMRunFunction(EE
, F
, NumArgs
, GVArgs
);
260 return alloc_generic_value(Result
);
263 /* ExecutionEngine.t -> unit */
264 CAMLprim value
llvm_ee_run_static_ctors(LLVMExecutionEngineRef EE
) {
265 LLVMRunStaticConstructors(EE
);
269 /* ExecutionEngine.t -> unit */
270 CAMLprim value
llvm_ee_run_static_dtors(LLVMExecutionEngineRef EE
) {
271 LLVMRunStaticDestructors(EE
);
275 /* llvalue -> string array -> (string * string) array -> ExecutionEngine.t ->
277 CAMLprim value
llvm_ee_run_function_as_main(LLVMValueRef F
,
278 value Args
, value Env
,
279 LLVMExecutionEngineRef EE
) {
280 CAMLparam2(Args
, Env
);
281 int I
, NumArgs
, NumEnv
, EnvSize
, Result
;
282 const char **CArgs
, **CEnv
;
285 NumArgs
= Wosize_val(Args
);
286 NumEnv
= Wosize_val(Env
);
288 /* Build the environment. */
289 CArgs
= (const char **) malloc(NumArgs
* sizeof(char*));
290 for (I
= 0; I
!= NumArgs
; ++I
)
291 CArgs
[I
] = String_val(Field(Args
, I
));
293 /* Compute the size of the environment string buffer. */
294 for (I
= 0, EnvSize
= 0; I
!= NumEnv
; ++I
) {
295 EnvSize
+= strlen(String_val(Field(Field(Env
, I
), 0))) + 1;
296 EnvSize
+= strlen(String_val(Field(Field(Env
, I
), 1))) + 1;
299 /* Build the environment. */
300 CEnv
= (const char **) malloc((NumEnv
+ 1) * sizeof(char*));
301 CEnvBuf
= (char*) malloc(EnvSize
);
303 for (I
= 0; I
!= NumEnv
; ++I
) {
304 char *Name
= String_val(Field(Field(Env
, I
), 0)),
305 *Value
= String_val(Field(Field(Env
, I
), 1));
306 int NameLen
= strlen(Name
),
307 ValueLen
= strlen(Value
);
310 memcpy(Pos
, Name
, NameLen
);
313 memcpy(Pos
, Value
, ValueLen
);
319 Result
= LLVMRunFunctionAsMain(EE
, F
, NumArgs
, CArgs
, CEnv
);
325 CAMLreturn(Val_int(Result
));
328 /* llvalue -> ExecutionEngine.t -> unit */
329 CAMLprim value
llvm_ee_free_machine_code(LLVMValueRef F
,
330 LLVMExecutionEngineRef EE
) {
331 LLVMFreeMachineCodeForFunction(EE
, F
);