summaryrefslogtreecommitdiff
path: root/bindings/ocaml/executionengine
diff options
context:
space:
mode:
authorDimitry Andric <dim@FreeBSD.org>2013-12-22 00:04:03 +0000
committerDimitry Andric <dim@FreeBSD.org>2013-12-22 00:04:03 +0000
commitf8af5cf600354830d4ccf59732403f0f073eccb9 (patch)
tree2ba0398b4c42ad4f55561327538044fd2c925a8b /bindings/ocaml/executionengine
parent59d6cff90eecf31cb3dd860c4e786674cfdd42eb (diff)
Diffstat (limited to 'bindings/ocaml/executionengine')
-rw-r--r--bindings/ocaml/executionengine/executionengine_ocaml.c19
-rw-r--r--bindings/ocaml/executionengine/llvm_executionengine.ml7
-rw-r--r--bindings/ocaml/executionengine/llvm_executionengine.mli19
3 files changed, 25 insertions, 20 deletions
diff --git a/bindings/ocaml/executionengine/executionengine_ocaml.c b/bindings/ocaml/executionengine/executionengine_ocaml.c
index 02e030605720e..4b44a91066fe6 100644
--- a/bindings/ocaml/executionengine/executionengine_ocaml.c
+++ b/bindings/ocaml/executionengine/executionengine_ocaml.c
@@ -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 *|
@@ -324,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;
+}
diff --git a/bindings/ocaml/executionengine/llvm_executionengine.ml b/bindings/ocaml/executionengine/llvm_executionengine.ml
index ddb53bbb5afd3..a738df765dce4 100644
--- a/bindings/ocaml/executionengine/llvm_executionengine.ml
+++ b/bindings/ocaml/executionengine/llvm_executionengine.ml
@@ -1,4 +1,4 @@
-(*===-- llvm_executionengine.ml - LLVM Ocaml Interface ----------*- C++ -*-===*
+(*===-- llvm_executionengine.ml - LLVM OCaml Interface ----------*- C++ -*-===*
*
* The LLVM Compiler Infrastructure
*
@@ -83,12 +83,11 @@ module ExecutionEngine = struct
external free_machine_code: Llvm.llvalue -> t -> unit
= "llvm_ee_free_machine_code"
- external target_data: t -> Llvm_target.DataLayout.t
- = "LLVMGetExecutionEngineTargetData"
+ external data_layout : t -> Llvm_target.DataLayout.t
+ = "llvm_ee_get_data_layout"
(* The following are not bound. Patches are welcome.
- get_target_data: t -> lltargetdata
add_global_mapping: llvalue -> llgenericvalue -> t -> unit
clear_all_global_mappings: t -> unit
update_global_mapping: llvalue -> llgenericvalue -> t -> unit
diff --git a/bindings/ocaml/executionengine/llvm_executionengine.mli b/bindings/ocaml/executionengine/llvm_executionengine.mli
index 0b06078bad860..16f08930a75b9 100644
--- a/bindings/ocaml/executionengine/llvm_executionengine.mli
+++ b/bindings/ocaml/executionengine/llvm_executionengine.mli
@@ -1,4 +1,4 @@
-(*===-- llvm_executionengine.mli - LLVM Ocaml Interface ---------*- C++ -*-===*
+(*===-- llvm_executionengine.mli - LLVM OCaml Interface ---------*- C++ -*-===*
*
* The LLVM Compiler Infrastructure
*
@@ -9,7 +9,7 @@
(** JIT Interpreter.
- This interface provides an ocaml API for LLVM execution engine (JIT/
+ This interface provides an OCaml API for LLVM execution engine (JIT/
interpreter), the classes in the ExecutionEngine library. *)
exception Error of string
@@ -43,7 +43,6 @@ module GenericValue: sig
bitwidth [w]. See the field [llvm::GenericValue::IntVal]. *)
val of_nativeint : Llvm.lltype -> nativeint -> t
-
(** [of_int64 n w] boxes the int64 [i] in a generic value with the bitwidth
[w]. See the field [llvm::GenericValue::IntVal]. *)
val of_int64 : Llvm.lltype -> int64 -> t
@@ -110,7 +109,7 @@ module ExecutionEngine: sig
(** [dispose ee] releases the memory used by the execution engine and must be
invoked to avoid memory leaks. *)
val dispose : t -> unit
-
+
(** [add_module m ee] adds the module [m] to the execution engine [ee]. *)
val add_module : Llvm.llmodule -> t -> unit
@@ -119,19 +118,16 @@ module ExecutionEngine: sig
[Error msg] if an error occurs. *)
val remove_module : Llvm.llmodule -> t -> Llvm.llmodule
-
(** [find_function n ee] finds the function named [n] defined in any of the
modules owned by the execution engine [ee]. Returns [None] if the function
is not found and [Some f] otherwise. *)
val find_function : string -> t -> Llvm.llvalue option
-
(** [run_function f args ee] synchronously executes the function [f] with the
arguments [args], which must be compatible with the parameter types. *)
val run_function : Llvm.llvalue -> GenericValue.t array -> t ->
GenericValue.t
-
(** [run_static_ctors ee] executes the static constructors of each module in
the execution engine [ee]. *)
val run_static_ctors : t -> unit
@@ -147,17 +143,12 @@ module ExecutionEngine: sig
val run_function_as_main : Llvm.llvalue -> string array ->
(string * string) array -> t -> int
-
(** [free_machine_code f ee] releases the memory in the execution engine [ee]
used to store the machine code for the function [f]. *)
val free_machine_code : Llvm.llvalue -> t -> unit
-
- (** [target_data ee] is the target data owned by the execution engine
- [ee]. *)
- val target_data : t -> Llvm_target.DataLayout.t
-
+ (** [data_layout ee] is the data layout of the execution engine [ee]. *)
+ val data_layout : t -> Llvm_target.DataLayout.t
end
val initialize_native_target : unit -> bool
-