1 (*===-- llvm_executionengine.mli - LLVM OCaml Interface -------*- OCaml -*-===*
3 * Part of the LLVM Project, under the Apache License v2.0 with LLVM Exceptions.
4 * See https://llvm.org/LICENSE.txt for license information.
5 * SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception
7 *===----------------------------------------------------------------------===*)
11 This interface provides an OCaml API for LLVM execution engine (JIT/
12 interpreter), the classes in the [ExecutionEngine] library. *)
14 exception Error
of string
16 (** [initialize ()] initializes the backend corresponding to the host.
17 Returns [true] if initialization is successful; [false] indicates
18 that there is no such backend or it is unable to emit object code
20 val initialize
: unit -> bool
22 (** An execution engine is either a JIT compiler or an interpreter, capable of
23 directly loading an LLVM module and executing its functions without first
24 invoking a static compiler and generating a native executable. *)
25 type llexecutionengine
27 (** MCJIT compiler options. See [llvm::TargetOptions]. *)
28 type llcompileroptions
= {
30 code_model
: Llvm_target.CodeModel.t
;
31 no_framepointer_elim
: bool;
32 enable_fast_isel
: bool;
35 (** Default MCJIT compiler options:
36 [{ opt_level = 0; code_model = CodeModel.JIT_default;
37 no_framepointer_elim = false; enable_fast_isel = false }] *)
38 val default_compiler_options
: llcompileroptions
40 (** [create m optlevel] creates a new MCJIT just-in-time compiler, taking
41 ownership of the module [m] if successful with the desired optimization
42 level [optlevel]. Raises [Error msg] if an error occurrs. The execution
43 engine is not garbage collected and must be destroyed with [dispose ee].
45 Run {!initialize} before using this function.
47 See the function [llvm::EngineBuilder::create]. *)
48 val create
: ?options
:llcompileroptions
-> Llvm.llmodule
-> llexecutionengine
50 (** [dispose ee] releases the memory used by the execution engine and must be
51 invoked to avoid memory leaks. *)
52 val dispose
: llexecutionengine
-> unit
54 (** [add_module m ee] adds the module [m] to the execution engine [ee]. *)
55 val add_module
: Llvm.llmodule
-> llexecutionengine
-> unit
57 (** [remove_module m ee] removes the module [m] from the execution engine
58 [ee]. Raises [Error msg] if an error occurs. *)
59 val remove_module
: Llvm.llmodule
-> llexecutionengine
-> unit
61 (** [run_static_ctors ee] executes the static constructors of each module in
62 the execution engine [ee]. *)
63 val run_static_ctors
: llexecutionengine
-> unit
65 (** [run_static_dtors ee] executes the static destructors of each module in
66 the execution engine [ee]. *)
67 val run_static_dtors
: llexecutionengine
-> unit
69 (** [data_layout ee] is the data layout of the execution engine [ee]. *)
70 val data_layout
: llexecutionengine
-> Llvm_target.DataLayout.t
72 (** [add_global_mapping gv ptr ee] tells the execution engine [ee] that
73 the global [gv] is at the specified location [ptr], which must outlive
75 All uses of [gv] in the compiled code will refer to [ptr]. *)
76 val add_global_mapping
: Llvm.llvalue
-> 'a
Ctypes.ptr
-> llexecutionengine
-> unit
78 (** [get_global_value_address id typ ee] returns a pointer to the
79 identifier [id] as type [typ], which will be a pointer type for a
80 value, and which will be live as long as [id] and [ee]
81 are. Caution: this function finalizes, i.e. forces code
82 generation, all loaded modules. Further modifications to the
83 modules will not have any effect. *)
84 val get_global_value_address
: string -> 'a
Ctypes.typ
-> llexecutionengine
-> 'a
86 (** [get_function_address fn typ ee] returns a pointer to the function
87 [fn] as type [typ], which will be a pointer type for a function
88 (e.g. [(int -> int) typ]), and which will be live as long as [fn]
89 and [ee] are. Caution: this function finalizes, i.e. forces code
90 generation, all loaded modules. Further modifications to the
91 modules will not have any effect. *)
92 val get_function_address
: string -> 'a
Ctypes.typ
-> llexecutionengine
-> 'a