Fix the ocaml bindings.
[oota-llvm.git] / bindings / ocaml / executionengine / executionengine_ocaml.c
index d12a9f7acdeb7f623305bc37d6bcb76285d8254c..4896c74121bb5b660447f4580510cfe51251d067 100644 (file)
@@ -1,4 +1,4 @@
-/*===-- executionengine_ocaml.c - LLVM Ocaml Glue ---------------*- C++ -*-===*\
+/*===-- executionengine_ocaml.c - LLVM OCaml Glue ---------------*- C++ -*-===*\
 |*                                                                            *|
 |*                     The LLVM Compiler Infrastructure                       *|
 |*                                                                            *|
@@ -7,7 +7,7 @@
 |*                                                                            *|
 |*===----------------------------------------------------------------------===*|
 |*                                                                            *|
-|* This file glues LLVM's ocaml interface to its C interface. These functions *|
+|* This file glues LLVM's OCaml interface to its C interface. These functions *|
 |* are by and large transparent wrappers to the corresponding C functions.    *|
 |*                                                                            *|
 |* Note that these functions intentionally take liberties with the CAMLparamX *|
@@ -27,7 +27,7 @@
 /* Force the LLVM interpreter and JIT to be linked in. */
 void llvm_initialize(void) {
   LLVMLinkInInterpreter();
-  LLVMLinkInJIT();
+  LLVMLinkInMCJIT();
 }
 
 /* unit -> bool */
@@ -75,6 +75,9 @@ static struct custom_operations generic_value_ops = {
   custom_hash_default,
   custom_serialize_default,
   custom_deserialize_default
+#ifdef custom_compare_ext_default
+  , custom_compare_ext_default
+#endif
 };
 
 static value alloc_generic_value(LLVMGenericValueRef Ref) {
@@ -91,7 +94,7 @@ CAMLprim value llvm_genericvalue_of_float(LLVMTypeRef Ty, value N) {
 }
 
 /* 'a -> t */
-CAMLprim value llvm_genericvalue_of_value(value V) {
+CAMLprim value llvm_genericvalue_of_pointer(value V) {
   CAMLparam1(V);
   CAMLreturn(alloc_generic_value(LLVMCreateGenericValueOfPointer(Op_val(V))));
 }
@@ -130,7 +133,7 @@ CAMLprim value llvm_genericvalue_as_float(LLVMTypeRef Ty, value GenVal) {
 }
 
 /* t -> 'a */
-CAMLprim value llvm_genericvalue_as_value(value GenVal) {
+CAMLprim value llvm_genericvalue_as_pointer(value GenVal) {
   return Val_op(LLVMGenericValueToPointer(Genericvalue_val(GenVal)));
 }
 
@@ -204,14 +207,14 @@ CAMLprim value llvm_ee_dispose(LLVMExecutionEngineRef EE) {
 }
 
 /* llmodule -> ExecutionEngine.t -> unit */
-CAMLprim value llvm_ee_add_mp(LLVMModuleRef M, LLVMExecutionEngineRef EE) {
+CAMLprim value llvm_ee_add_module(LLVMModuleRef M, LLVMExecutionEngineRef EE) {
   LLVMAddModule(EE, M);
   return Val_unit;
 }
 
 /* llmodule -> ExecutionEngine.t -> llmodule */
-CAMLprim LLVMModuleRef llvm_ee_remove_mp(LLVMModuleRef M,
-                                         LLVMExecutionEngineRef EE) {
+CAMLprim LLVMModuleRef llvm_ee_remove_module(LLVMModuleRef M,
+                                             LLVMExecutionEngineRef EE) {
   LLVMModuleRef RemovedModule;
   char *Error;
   if (LLVMRemoveModule(EE, M, &RemovedModule, &Error))
@@ -226,7 +229,7 @@ CAMLprim value llvm_ee_find_function(value Name, LLVMExecutionEngineRef EE) {
   LLVMValueRef Found;
   if (LLVMFindFunction(EE, String_val(Name), &Found))
     CAMLreturn(Val_unit);
-  Option = alloc(1, 1);
+  Option = alloc(1, 0);
   Field(Option, 0) = Val_op(Found);
   CAMLreturn(Option);
 }
@@ -321,3 +324,18 @@ CAMLprim value llvm_ee_free_machine_code(LLVMValueRef F,
   return Val_unit;
 }
 
+extern value llvm_alloc_data_layout(LLVMTargetDataRef TargetData);
+
+/* ExecutionEngine.t -> Llvm_target.DataLayout.t */
+CAMLprim value llvm_ee_get_data_layout(LLVMExecutionEngineRef EE) {
+  value DataLayout;
+  LLVMTargetDataRef OrigDataLayout;
+  OrigDataLayout = LLVMGetExecutionEngineTargetData(EE);
+
+  char* TargetDataCStr;
+  TargetDataCStr = LLVMCopyStringRepOfTargetData(OrigDataLayout);
+  DataLayout = llvm_alloc_data_layout(LLVMCreateTargetData(TargetDataCStr));
+  LLVMDisposeMessage(TargetDataCStr);
+
+  return DataLayout;
+}