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, JIT, and native target to be linked in. */
28 void llvm_initialize(void) {
29 LLVMLinkInInterpreter();
31 LLVMInitializeNativeTarget();
34 /* Can't use the recommended caml_named_value mechanism for backwards
35 compatibility reasons. This is largely equivalent. */
36 static value llvm_ee_error_exn
;
38 CAMLprim value
llvm_register_ee_exns(value Error
) {
39 llvm_ee_error_exn
= Field(Error
, 0);
40 register_global_root(&llvm_ee_error_exn
);
44 static void llvm_raise(value Prototype
, char *Message
) {
45 CAMLparam1(Prototype
);
46 CAMLlocal1(CamlMessage
);
48 CamlMessage
= copy_string(Message
);
49 LLVMDisposeMessage(Message
);
51 raise_with_arg(Prototype
, CamlMessage
);
52 abort(); /* NOTREACHED */
54 CAMLnoreturn
; /* Silences warnings, but is missing in some versions. */
59 /*--... Operations on generic values .......................................--*/
61 #define Genericvalue_val(v) (*(LLVMGenericValueRef *)(Data_custom_val(v)))
63 static void llvm_finalize_generic_value(value GenVal
) {
64 LLVMDisposeGenericValue(Genericvalue_val(GenVal
));
67 static struct custom_operations generic_value_ops
= {
68 (char *) "LLVMGenericValue",
69 llvm_finalize_generic_value
,
70 custom_compare_default
,
72 custom_serialize_default
,
73 custom_deserialize_default
76 static value
alloc_generic_value(LLVMGenericValueRef Ref
) {
77 value Val
= alloc_custom(&generic_value_ops
, sizeof(LLVMGenericValueRef
), 0, 1);
78 Genericvalue_val(Val
) = Ref
;
82 /* Llvm.lltype -> float -> t */
83 CAMLprim value
llvm_genericvalue_of_float(LLVMTypeRef Ty
, value N
) {
85 CAMLreturn(alloc_generic_value(
86 LLVMCreateGenericValueOfFloat(Ty
, Double_val(N
))));
90 CAMLprim value
llvm_genericvalue_of_value(value V
) {
92 CAMLreturn(alloc_generic_value(LLVMCreateGenericValueOfPointer(Op_val(V
))));
95 /* Llvm.lltype -> int -> t */
96 CAMLprim value
llvm_genericvalue_of_int(LLVMTypeRef Ty
, value Int
) {
97 return alloc_generic_value(LLVMCreateGenericValueOfInt(Ty
, Int_val(Int
), 1));
100 /* Llvm.lltype -> int32 -> t */
101 CAMLprim value
llvm_genericvalue_of_int32(LLVMTypeRef Ty
, value Int32
) {
103 CAMLreturn(alloc_generic_value(
104 LLVMCreateGenericValueOfInt(Ty
, Int32_val(Int32
), 1)));
107 /* Llvm.lltype -> nativeint -> t */
108 CAMLprim value
llvm_genericvalue_of_nativeint(LLVMTypeRef Ty
, value NatInt
) {
110 CAMLreturn(alloc_generic_value(
111 LLVMCreateGenericValueOfInt(Ty
, Nativeint_val(NatInt
), 1)));
114 /* Llvm.lltype -> int64 -> t */
115 CAMLprim value
llvm_genericvalue_of_int64(LLVMTypeRef Ty
, value Int64
) {
117 CAMLreturn(alloc_generic_value(
118 LLVMCreateGenericValueOfInt(Ty
, Int64_val(Int64
), 1)));
121 /* Llvm.lltype -> t -> float */
122 CAMLprim value
llvm_genericvalue_as_float(LLVMTypeRef Ty
, value GenVal
) {
124 CAMLreturn(copy_double(
125 LLVMGenericValueToFloat(Ty
, Genericvalue_val(GenVal
))));
129 CAMLprim value
llvm_genericvalue_as_value(value GenVal
) {
130 return Val_op(LLVMGenericValueToPointer(Genericvalue_val(GenVal
)));
134 CAMLprim value
llvm_genericvalue_as_int(value GenVal
) {
135 assert(LLVMGenericValueIntWidth(Genericvalue_val(GenVal
)) <= 8 * sizeof(value
)
136 && "Generic value too wide to treat as an int!");
137 return Val_int(LLVMGenericValueToInt(Genericvalue_val(GenVal
), 1));
141 CAMLprim value
llvm_genericvalue_as_int32(value GenVal
) {
143 assert(LLVMGenericValueIntWidth(Genericvalue_val(GenVal
)) <= 32
144 && "Generic value too wide to treat as an int32!");
145 CAMLreturn(copy_int32(LLVMGenericValueToInt(Genericvalue_val(GenVal
), 1)));
149 CAMLprim value
llvm_genericvalue_as_int64(value GenVal
) {
151 assert(LLVMGenericValueIntWidth(Genericvalue_val(GenVal
)) <= 64
152 && "Generic value too wide to treat as an int64!");
153 CAMLreturn(copy_int64(LLVMGenericValueToInt(Genericvalue_val(GenVal
), 1)));
157 CAMLprim value
llvm_genericvalue_as_nativeint(value GenVal
) {
159 assert(LLVMGenericValueIntWidth(Genericvalue_val(GenVal
)) <= 8 * sizeof(value
)
160 && "Generic value too wide to treat as a nativeint!");
161 CAMLreturn(copy_nativeint(LLVMGenericValueToInt(Genericvalue_val(GenVal
),1)));
165 /*--... Operations on execution engines ....................................--*/
167 /* llmoduleprovider -> ExecutionEngine.t */
168 CAMLprim LLVMExecutionEngineRef
llvm_ee_create(LLVMModuleProviderRef MP
) {
169 LLVMExecutionEngineRef Interp
;
171 if (LLVMCreateExecutionEngine(&Interp
, MP
, &Error
))
172 llvm_raise(llvm_ee_error_exn
, Error
);
176 /* llmoduleprovider -> ExecutionEngine.t */
177 CAMLprim LLVMExecutionEngineRef
178 llvm_ee_create_interpreter(LLVMModuleProviderRef MP
) {
179 LLVMExecutionEngineRef Interp
;
181 if (LLVMCreateInterpreter(&Interp
, MP
, &Error
))
182 llvm_raise(llvm_ee_error_exn
, Error
);
186 /* llmoduleprovider -> ExecutionEngine.t */
187 CAMLprim LLVMExecutionEngineRef
188 llvm_ee_create_jit(LLVMModuleProviderRef MP
) {
189 LLVMExecutionEngineRef JIT
;
191 if (LLVMCreateJITCompiler(&JIT
, MP
, 3, &Error
))
192 llvm_raise(llvm_ee_error_exn
, Error
);
196 /* llmoduleprovider -> ExecutionEngine.t */
197 CAMLprim LLVMExecutionEngineRef
198 llvm_ee_create_fast_jit(LLVMModuleProviderRef MP
) {
199 LLVMExecutionEngineRef JIT
;
201 if (LLVMCreateJITCompiler(&JIT
, MP
, 0, &Error
))
202 llvm_raise(llvm_ee_error_exn
, Error
);
206 /* ExecutionEngine.t -> unit */
207 CAMLprim value
llvm_ee_dispose(LLVMExecutionEngineRef EE
) {
208 LLVMDisposeExecutionEngine(EE
);
212 /* llmoduleprovider -> ExecutionEngine.t -> unit */
213 CAMLprim value
llvm_ee_add_mp(LLVMModuleProviderRef MP
,
214 LLVMExecutionEngineRef EE
) {
215 LLVMAddModuleProvider(EE
, MP
);
219 /* llmoduleprovider -> ExecutionEngine.t -> llmodule */
220 CAMLprim LLVMModuleRef
llvm_ee_remove_mp(LLVMModuleProviderRef MP
,
221 LLVMExecutionEngineRef EE
) {
222 LLVMModuleRef RemovedModule
;
224 if (LLVMRemoveModuleProvider(EE
, MP
, &RemovedModule
, &Error
))
225 llvm_raise(llvm_ee_error_exn
, Error
);
226 return RemovedModule
;
229 /* string -> ExecutionEngine.t -> llvalue option */
230 CAMLprim value
llvm_ee_find_function(value Name
, LLVMExecutionEngineRef EE
) {
234 if (LLVMFindFunction(EE
, String_val(Name
), &Found
))
235 CAMLreturn(Val_unit
);
236 Option
= alloc(1, 1);
237 Field(Option
, 0) = Val_op(Found
);
241 /* llvalue -> GenericValue.t array -> ExecutionEngine.t -> GenericValue.t */
242 CAMLprim value
llvm_ee_run_function(LLVMValueRef F
, value Args
,
243 LLVMExecutionEngineRef EE
) {
245 LLVMGenericValueRef Result
, *GVArgs
;
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
));
253 Result
= LLVMRunFunction(EE
, F
, NumArgs
, GVArgs
);
256 return alloc_generic_value(Result
);
259 /* ExecutionEngine.t -> unit */
260 CAMLprim value
llvm_ee_run_static_ctors(LLVMExecutionEngineRef EE
) {
261 LLVMRunStaticConstructors(EE
);
265 /* ExecutionEngine.t -> unit */
266 CAMLprim value
llvm_ee_run_static_dtors(LLVMExecutionEngineRef EE
) {
267 LLVMRunStaticDestructors(EE
);
271 /* llvalue -> string array -> (string * string) array -> ExecutionEngine.t ->
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
;
281 NumArgs
= Wosize_val(Args
);
282 NumEnv
= Wosize_val(Env
);
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
));
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;
295 /* Build the environment. */
296 CEnv
= (const char **) malloc((NumEnv
+ 1) * sizeof(char*));
297 CEnvBuf
= (char*) malloc(EnvSize
);
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
);
306 memcpy(Pos
, Name
, NameLen
);
309 memcpy(Pos
, Value
, ValueLen
);
315 Result
= LLVMRunFunctionAsMain(EE
, F
, NumArgs
, CArgs
, CEnv
);
321 CAMLreturn(Val_int(Result
));
324 /* llvalue -> ExecutionEngine.t -> unit */
325 CAMLprim value
llvm_ee_free_machine_code(LLVMValueRef F
,
326 LLVMExecutionEngineRef EE
) {
327 LLVMFreeMachineCodeForFunction(EE
, F
);