summaryrefslogtreecommitdiff
path: root/bindings/ocaml/executionengine
diff options
context:
space:
mode:
Diffstat (limited to 'bindings/ocaml/executionengine')
-rw-r--r--bindings/ocaml/executionengine/executionengine_ocaml.c37
-rw-r--r--bindings/ocaml/executionengine/llvm_executionengine.ml12
-rw-r--r--bindings/ocaml/executionengine/llvm_executionengine.mli57
3 files changed, 52 insertions, 54 deletions
diff --git a/bindings/ocaml/executionengine/executionengine_ocaml.c b/bindings/ocaml/executionengine/executionengine_ocaml.c
index 072d583bf8..bc2b08196b 100644
--- a/bindings/ocaml/executionengine/executionengine_ocaml.c
+++ b/bindings/ocaml/executionengine/executionengine_ocaml.c
@@ -168,41 +168,41 @@ CAMLprim value llvm_genericvalue_as_nativeint(value GenVal) {
/*--... Operations on execution engines ....................................--*/
-/* llmoduleprovider -> ExecutionEngine.t */
-CAMLprim LLVMExecutionEngineRef llvm_ee_create(LLVMModuleProviderRef MP) {
+/* llmodule -> ExecutionEngine.t */
+CAMLprim LLVMExecutionEngineRef llvm_ee_create(LLVMModuleRef M) {
LLVMExecutionEngineRef Interp;
char *Error;
- if (LLVMCreateExecutionEngine(&Interp, MP, &Error))
+ if (LLVMCreateExecutionEngineForModule(&Interp, M, &Error))
llvm_raise(llvm_ee_error_exn, Error);
return Interp;
}
-/* llmoduleprovider -> ExecutionEngine.t */
+/* llmodule -> ExecutionEngine.t */
CAMLprim LLVMExecutionEngineRef
-llvm_ee_create_interpreter(LLVMModuleProviderRef MP) {
+llvm_ee_create_interpreter(LLVMModuleRef M) {
LLVMExecutionEngineRef Interp;
char *Error;
- if (LLVMCreateInterpreter(&Interp, MP, &Error))
+ if (LLVMCreateInterpreterForModule(&Interp, M, &Error))
llvm_raise(llvm_ee_error_exn, Error);
return Interp;
}
-/* llmoduleprovider -> ExecutionEngine.t */
+/* llmodule -> ExecutionEngine.t */
CAMLprim LLVMExecutionEngineRef
-llvm_ee_create_jit(LLVMModuleProviderRef MP) {
+llvm_ee_create_jit(LLVMModuleRef M) {
LLVMExecutionEngineRef JIT;
char *Error;
- if (LLVMCreateJITCompiler(&JIT, MP, 3, &Error))
+ if (LLVMCreateJITCompilerForModule(&JIT, M, 3, &Error))
llvm_raise(llvm_ee_error_exn, Error);
return JIT;
}
-/* llmoduleprovider -> ExecutionEngine.t */
+/* llmodule -> ExecutionEngine.t */
CAMLprim LLVMExecutionEngineRef
-llvm_ee_create_fast_jit(LLVMModuleProviderRef MP) {
+llvm_ee_create_fast_jit(LLVMModuleRef M) {
LLVMExecutionEngineRef JIT;
char *Error;
- if (LLVMCreateJITCompiler(&JIT, MP, 0, &Error))
+ if (LLVMCreateJITCompiler(&JIT, M, 0, &Error))
llvm_raise(llvm_ee_error_exn, Error);
return JIT;
}
@@ -213,19 +213,18 @@ CAMLprim value llvm_ee_dispose(LLVMExecutionEngineRef EE) {
return Val_unit;
}
-/* llmoduleprovider -> ExecutionEngine.t -> unit */
-CAMLprim value llvm_ee_add_mp(LLVMModuleProviderRef MP,
- LLVMExecutionEngineRef EE) {
- LLVMAddModuleProvider(EE, MP);
+/* llmodule -> ExecutionEngine.t -> unit */
+CAMLprim value llvm_ee_add_mp(LLVMModuleRef M, LLVMExecutionEngineRef EE) {
+ LLVMAddModule(EE, M);
return Val_unit;
}
-/* llmoduleprovider -> ExecutionEngine.t -> llmodule */
-CAMLprim LLVMModuleRef llvm_ee_remove_mp(LLVMModuleProviderRef MP,
+/* llmodule -> ExecutionEngine.t -> llmodule */
+CAMLprim LLVMModuleRef llvm_ee_remove_mp(LLVMModuleRef M,
LLVMExecutionEngineRef EE) {
LLVMModuleRef RemovedModule;
char *Error;
- if (LLVMRemoveModuleProvider(EE, MP, &RemovedModule, &Error))
+ if (LLVMRemoveModule(EE, M, &RemovedModule, &Error))
llvm_raise(llvm_ee_error_exn, Error);
return RemovedModule;
}
diff --git a/bindings/ocaml/executionengine/llvm_executionengine.ml b/bindings/ocaml/executionengine/llvm_executionengine.ml
index c9e8f18b22..921d424ad5 100644
--- a/bindings/ocaml/executionengine/llvm_executionengine.ml
+++ b/bindings/ocaml/executionengine/llvm_executionengine.ml
@@ -56,19 +56,19 @@ module ExecutionEngine = struct
call into LLVM. *)
let _ = register_exns (Error "")
- external create: Llvm.llmoduleprovider -> t
+ external create: Llvm.llmodule -> t
= "llvm_ee_create"
- external create_interpreter: Llvm.llmoduleprovider -> t
+ external create_interpreter: Llvm.llmodule -> t
= "llvm_ee_create_interpreter"
- external create_jit: Llvm.llmoduleprovider -> t
+ external create_jit: Llvm.llmodule -> t
= "llvm_ee_create_jit"
- external create_fast_jit: Llvm.llmoduleprovider -> t
+ external create_fast_jit: Llvm.llmodule -> t
= "llvm_ee_create_fast_jit"
external dispose: t -> unit
= "llvm_ee_dispose"
- external add_module_provider: Llvm.llmoduleprovider -> t -> unit
+ external add_module: Llvm.llmodule -> t -> unit
= "llvm_ee_add_mp"
- external remove_module_provider: Llvm.llmoduleprovider -> t -> Llvm.llmodule
+ external remove_module: Llvm.llmodule -> t -> Llvm.llmodule
= "llvm_ee_remove_mp"
external find_function: string -> t -> Llvm.llvalue option
= "llvm_ee_find_function"
diff --git a/bindings/ocaml/executionengine/llvm_executionengine.mli b/bindings/ocaml/executionengine/llvm_executionengine.mli
index 6c2fdfb786..ec469fcf04 100644
--- a/bindings/ocaml/executionengine/llvm_executionengine.mli
+++ b/bindings/ocaml/executionengine/llvm_executionengine.mli
@@ -85,48 +85,47 @@ module ExecutionEngine: sig
invoking a static compiler and generating a native executable. *)
type t
- (** [create mp] creates a new execution engine, taking ownership of the
- module provider [mp] if successful. Creates a JIT if possible, else falls
- back to an interpreter. Raises [Error msg] if an error occurrs. The
- execution engine is not garbage collected and must be destroyed with
- [dispose ee]. See the function [llvm::EngineBuilder::create]. *)
- val create: Llvm.llmoduleprovider -> t
+ (** [create m] creates a new execution engine, taking ownership of the
+ module [m] if successful. Creates a JIT if possible, else falls back to an
+ interpreter. Raises [Error msg] if an error occurrs. The execution engine
+ is not garbage collected and must be destroyed with [dispose ee].
+ See the function [llvm::EngineBuilder::create]. *)
+ val create: Llvm.llmodule -> t
- (** [create_interpreter mp] creates a new interpreter, taking ownership of the
- module provider [mp] if successful. Raises [Error msg] if an error
- occurrs. The execution engine is not garbage collected and must be
- destroyed with [dispose ee].
+ (** [create_interpreter m] creates a new interpreter, taking ownership of the
+ module [m] if successful. Raises [Error msg] if an error occurrs. The
+ execution engine is not garbage collected and must be destroyed with
+ [dispose ee].
See the function [llvm::EngineBuilder::create]. *)
- val create_interpreter: Llvm.llmoduleprovider -> t
+ val create_interpreter: Llvm.llmodule -> t
- (** [create_jit mp] creates a new JIT (just-in-time compiler), taking
- ownership of the module provider [mp] if successful. This function creates
- a JIT which favors code quality over compilation speed. Raises [Error msg]
- if an error occurrs. The execution engine is not garbage collected and
- must be destroyed with [dispose ee].
+ (** [create_jit m] creates a new JIT (just-in-time compiler), taking
+ ownership of the module [m] if successful. This function creates a JIT
+ which favors code quality over compilation speed. Raises [Error msg] if an
+ error occurrs. The execution engine is not garbage collected and must be
+ destroyed with [dispose ee].
See the function [llvm::EngineBuilder::create]. *)
- val create_jit: Llvm.llmoduleprovider -> t
+ val create_jit: Llvm.llmodule -> t
- (** [create_fast_jit mp] creates a new JIT (just-in-time compiler) which
+ (** [create_fast_jit m] creates a new JIT (just-in-time compiler) which
favors compilation speed over code quality. It takes ownership of the
- module provider [mp] if successful. Raises [Error msg] if an error
- occurrs. The execution engine is not garbage collected and must be
- destroyed with [dispose ee].
+ module [m] if successful. Raises [Error msg] if an error occurrs. The
+ execution engine is not garbage collected and must be destroyed with
+ [dispose ee].
See the function [llvm::EngineBuilder::create]. *)
- val create_fast_jit: Llvm.llmoduleprovider -> t
+ val create_fast_jit: Llvm.llmodule -> t
(** [dispose ee] releases the memory used by the execution engine and must be
invoked to avoid memory leaks. *)
val dispose: t -> unit
- (** [add_module_provider mp ee] adds the module provider [mp] to the execution
- engine [ee]. *)
- val add_module_provider: Llvm.llmoduleprovider -> t -> unit
+ (** [add_module m ee] adds the module [m] to the execution engine [ee]. *)
+ val add_module: Llvm.llmodule -> t -> unit
- (** [remove_module_provider mp ee] removes the module provider [mp] from the
- execution engine [ee], disposing of [mp] and the module referenced by
- [mp]. Raises [Error msg] if an error occurs. *)
- val remove_module_provider: Llvm.llmoduleprovider -> t -> Llvm.llmodule
+ (** [remove_module m ee] removes the module [m] from the execution engine
+ [ee], disposing of [m] and the module referenced by [mp]. Raises
+ [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