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 "caml/alloc.h"
20 #include "caml/custom.h"
21 #include "caml/fail.h"
22 #include "caml/memory.h"
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
;
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
);
37 static void llvm_raise(value Prototype
, char *Message
) {
38 CAMLparam1(Prototype
);
39 CAMLlocal1(CamlMessage
);
41 CamlMessage
= copy_string(Message
);
42 LLVMDisposeMessage(Message
);
44 raise_with_arg(Prototype
, CamlMessage
);
45 abort(); /* NOTREACHED */
47 CAMLnoreturn
; /* Silences warnings, but is missing in some versions. */
52 /*--... Operations on generic values .......................................--*/
54 #define Genericvalue_val(v) (*(LLVMGenericValueRef *)(Data_custom_val(v)))
56 static void llvm_finalize_generic_value(value GenVal
) {
57 LLVMDisposeGenericValue(Genericvalue_val(GenVal
));
60 static struct custom_operations generic_value_ops
= {
61 (char *) "LLVMGenericValue",
62 llvm_finalize_generic_value
,
63 custom_compare_default
,
65 custom_serialize_default
,
66 custom_deserialize_default
69 static value
alloc_generic_value(LLVMGenericValueRef Ref
) {
70 value Val
= alloc_custom(&generic_value_ops
, sizeof(LLVMGenericValueRef
), 0, 1);
71 Genericvalue_val(Val
) = Ref
;
75 /* Llvm.lltype -> float -> t */
76 CAMLprim value
llvm_genericvalue_of_float(LLVMTypeRef Ty
, value N
) {
78 CAMLreturn(alloc_generic_value(
79 LLVMCreateGenericValueOfFloat(Ty
, Double_val(N
))));
83 CAMLprim value
llvm_genericvalue_of_value(value V
) {
85 CAMLreturn(alloc_generic_value(LLVMCreateGenericValueOfPointer(Op_val(V
))));
88 /* Llvm.lltype -> int -> t */
89 CAMLprim value
llvm_genericvalue_of_int(LLVMTypeRef Ty
, value Int
) {
90 return alloc_generic_value(LLVMCreateGenericValueOfInt(Ty
, Int_val(Int
), 1));
93 /* Llvm.lltype -> int32 -> t */
94 CAMLprim value
llvm_genericvalue_of_int32(LLVMTypeRef Ty
, value Int32
) {
96 CAMLreturn(alloc_generic_value(
97 LLVMCreateGenericValueOfInt(Ty
, Int32_val(Int32
), 1)));
100 /* Llvm.lltype -> nativeint -> t */
101 CAMLprim value
llvm_genericvalue_of_nativeint(LLVMTypeRef Ty
, value NatInt
) {
103 CAMLreturn(alloc_generic_value(
104 LLVMCreateGenericValueOfInt(Ty
, Nativeint_val(NatInt
), 1)));
107 /* Llvm.lltype -> int64 -> t */
108 CAMLprim value
llvm_genericvalue_of_int64(LLVMTypeRef Ty
, value Int64
) {
110 CAMLreturn(alloc_generic_value(
111 LLVMCreateGenericValueOfInt(Ty
, Int64_val(Int64
), 1)));
114 /* Llvm.lltype -> t -> float */
115 CAMLprim value
llvm_genericvalue_as_float(LLVMTypeRef Ty
, value GenVal
) {
117 CAMLreturn(copy_double(
118 LLVMGenericValueToFloat(Ty
, Genericvalue_val(GenVal
))));
122 CAMLprim value
llvm_genericvalue_as_value(value GenVal
) {
123 return Val_op(LLVMGenericValueToPointer(Genericvalue_val(GenVal
)));
127 CAMLprim value
llvm_genericvalue_as_int(value GenVal
) {
128 assert(LLVMGenericValueIntWidth(Genericvalue_val(GenVal
)) <= 8 * sizeof(value
)
129 && "Generic value too wide to treat as an int!");
130 return Val_int(LLVMGenericValueToInt(Genericvalue_val(GenVal
), 1));
134 CAMLprim value
llvm_genericvalue_as_int32(value GenVal
) {
136 assert(LLVMGenericValueIntWidth(Genericvalue_val(GenVal
)) <= 32
137 && "Generic value too wide to treat as an int32!");
138 CAMLreturn(copy_int32(LLVMGenericValueToInt(Genericvalue_val(GenVal
), 1)));
142 CAMLprim value
llvm_genericvalue_as_int64(value GenVal
) {
144 assert(LLVMGenericValueIntWidth(Genericvalue_val(GenVal
)) <= 64
145 && "Generic value too wide to treat as an int64!");
146 CAMLreturn(copy_int64(LLVMGenericValueToInt(Genericvalue_val(GenVal
), 1)));
150 CAMLprim value
llvm_genericvalue_as_nativeint(value GenVal
) {
152 assert(LLVMGenericValueIntWidth(Genericvalue_val(GenVal
)) <= 8 * sizeof(value
)
153 && "Generic value too wide to treat as a nativeint!");
154 CAMLreturn(copy_nativeint(LLVMGenericValueToInt(Genericvalue_val(GenVal
),1)));
158 /*--... Operations on execution engines ....................................--*/
160 /* llmoduleprovider -> ExecutionEngine.t */
161 CAMLprim LLVMExecutionEngineRef
llvm_ee_create(LLVMModuleProviderRef MP
) {
162 LLVMExecutionEngineRef Interp
;
164 if (LLVMCreateExecutionEngine(&Interp
, MP
, &Error
))
165 llvm_raise(llvm_ee_error_exn
, Error
);
169 /* llmoduleprovider -> ExecutionEngine.t */
170 CAMLprim LLVMExecutionEngineRef
171 llvm_ee_create_interpreter(LLVMModuleProviderRef MP
) {
172 LLVMExecutionEngineRef Interp
;
174 if (LLVMCreateInterpreter(&Interp
, MP
, &Error
))
175 llvm_raise(llvm_ee_error_exn
, Error
);
179 /* llmoduleprovider -> ExecutionEngine.t */
180 CAMLprim LLVMExecutionEngineRef
181 llvm_ee_create_jit(LLVMModuleProviderRef MP
) {
182 LLVMExecutionEngineRef JIT
;
184 if (LLVMCreateJITCompiler(&JIT
, MP
, 0, &Error
))
185 llvm_raise(llvm_ee_error_exn
, Error
);
189 /* llmoduleprovider -> ExecutionEngine.t */
190 CAMLprim LLVMExecutionEngineRef
191 llvm_ee_create_fast_jit(LLVMModuleProviderRef MP
) {
192 LLVMExecutionEngineRef JIT
;
194 if (LLVMCreateJITCompiler(&JIT
, MP
, 1, &Error
))
195 llvm_raise(llvm_ee_error_exn
, Error
);
199 /* ExecutionEngine.t -> unit */
200 CAMLprim value
llvm_ee_dispose(LLVMExecutionEngineRef EE
) {
201 LLVMDisposeExecutionEngine(EE
);
205 /* llmoduleprovider -> ExecutionEngine.t -> unit */
206 CAMLprim value
llvm_ee_add_mp(LLVMModuleProviderRef MP
,
207 LLVMExecutionEngineRef EE
) {
208 LLVMAddModuleProvider(EE
, MP
);
212 /* llmoduleprovider -> ExecutionEngine.t -> llmodule */
213 CAMLprim LLVMModuleRef
llvm_ee_remove_mp(LLVMModuleProviderRef MP
,
214 LLVMExecutionEngineRef EE
) {
215 LLVMModuleRef RemovedModule
;
217 if (LLVMRemoveModuleProvider(EE
, MP
, &RemovedModule
, &Error
))
218 llvm_raise(llvm_ee_error_exn
, Error
);
219 return RemovedModule
;
222 /* string -> ExecutionEngine.t -> llvalue option */
223 CAMLprim value
llvm_ee_find_function(value Name
, LLVMExecutionEngineRef EE
) {
227 if (LLVMFindFunction(EE
, String_val(Name
), &Found
))
228 CAMLreturn(Val_unit
);
229 Option
= alloc(1, 1);
230 Field(Option
, 0) = Val_op(Found
);
234 /* llvalue -> GenericValue.t array -> ExecutionEngine.t -> GenericValue.t */
235 CAMLprim value
llvm_ee_run_function(LLVMValueRef F
, value Args
,
236 LLVMExecutionEngineRef EE
) {
238 LLVMGenericValueRef Result
, *GVArgs
;
241 NumArgs
= Wosize_val(Args
);
242 GVArgs
= (LLVMGenericValueRef
*) malloc(NumArgs
* sizeof(LLVMGenericValueRef
));
243 for (I
= 0; I
!= NumArgs
; ++I
)
244 GVArgs
[I
] = Genericvalue_val(Field(Args
, I
));
246 Result
= LLVMRunFunction(EE
, F
, NumArgs
, GVArgs
);
249 return alloc_generic_value(Result
);
252 /* ExecutionEngine.t -> unit */
253 CAMLprim value
llvm_ee_run_static_ctors(LLVMExecutionEngineRef EE
) {
254 LLVMRunStaticConstructors(EE
);
258 /* ExecutionEngine.t -> unit */
259 CAMLprim value
llvm_ee_run_static_dtors(LLVMExecutionEngineRef EE
) {
260 LLVMRunStaticDestructors(EE
);
264 /* llvalue -> string array -> (string * string) array -> ExecutionEngine.t ->
266 CAMLprim value
llvm_ee_run_function_as_main(LLVMValueRef F
,
267 value Args
, value Env
,
268 LLVMExecutionEngineRef EE
) {
269 CAMLparam2(Args
, Env
);
270 int I
, NumArgs
, NumEnv
, EnvSize
, Result
;
271 const char **CArgs
, **CEnv
;
274 NumArgs
= Wosize_val(Args
);
275 NumEnv
= Wosize_val(Env
);
277 /* Build the environment. */
278 CArgs
= (const char **) malloc(NumArgs
* sizeof(char*));
279 for (I
= 0; I
!= NumArgs
; ++I
)
280 CArgs
[I
] = String_val(Field(Args
, I
));
282 /* Compute the size of the environment string buffer. */
283 for (I
= 0, EnvSize
= 0; I
!= NumEnv
; ++I
) {
284 EnvSize
+= strlen(String_val(Field(Field(Env
, I
), 0))) + 1;
285 EnvSize
+= strlen(String_val(Field(Field(Env
, I
), 1))) + 1;
288 /* Build the environment. */
289 CEnv
= (const char **) malloc((NumEnv
+ 1) * sizeof(char*));
290 CEnvBuf
= (char*) malloc(EnvSize
);
292 for (I
= 0; I
!= NumEnv
; ++I
) {
293 char *Name
= String_val(Field(Field(Env
, I
), 0)),
294 *Value
= String_val(Field(Field(Env
, I
), 1));
295 int NameLen
= strlen(Name
),
296 ValueLen
= strlen(Value
);
299 memcpy(Pos
, Name
, NameLen
);
302 memcpy(Pos
, Value
, ValueLen
);
308 Result
= LLVMRunFunctionAsMain(EE
, F
, NumArgs
, CArgs
, CEnv
);
314 CAMLreturn(Val_int(Result
));
317 /* llvalue -> ExecutionEngine.t -> unit */
318 CAMLprim value
llvm_ee_free_machine_code(LLVMValueRef F
,
319 LLVMExecutionEngineRef EE
) {
320 LLVMFreeMachineCodeForFunction(EE
, F
);