xref: /llvm-project/llvm/bindings/ocaml/executionengine/llvm_executionengine.mli (revision 2946cd701067404b99c39fb29dc9c74bd7193eb3)
1(*===-- llvm_executionengine.mli - LLVM OCaml Interface -------*- OCaml -*-===*
2 *
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
6 *
7 *===----------------------------------------------------------------------===*)
8
9(** JIT Interpreter.
10
11    This interface provides an OCaml API for LLVM execution engine (JIT/
12    interpreter), the classes in the [ExecutionEngine] library. *)
13
14exception Error of string
15
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
19    via MCJIT. *)
20val initialize : unit -> bool
21
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. *)
25type llexecutionengine
26
27(** MCJIT compiler options. See [llvm::TargetOptions]. *)
28type llcompileroptions = {
29  opt_level: int;
30  code_model: Llvm_target.CodeModel.t;
31  no_framepointer_elim: bool;
32  enable_fast_isel: bool;
33}
34
35(** Default MCJIT compiler options:
36    [{ opt_level = 0; code_model = CodeModel.JIT_default;
37       no_framepointer_elim = false; enable_fast_isel = false }] *)
38val default_compiler_options : llcompileroptions
39
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].
44
45    Run {!initialize} before using this function.
46
47    See the function [llvm::EngineBuilder::create]. *)
48val create : ?options:llcompileroptions -> Llvm.llmodule -> llexecutionengine
49
50(** [dispose ee] releases the memory used by the execution engine and must be
51    invoked to avoid memory leaks. *)
52val dispose : llexecutionengine -> unit
53
54(** [add_module m ee] adds the module [m] to the execution engine [ee]. *)
55val add_module : Llvm.llmodule -> llexecutionengine -> unit
56
57(** [remove_module m ee] removes the module [m] from the execution engine
58    [ee]. Raises [Error msg] if an error occurs. *)
59val remove_module : Llvm.llmodule -> llexecutionengine -> unit
60
61(** [run_static_ctors ee] executes the static constructors of each module in
62    the execution engine [ee]. *)
63val run_static_ctors : llexecutionengine -> unit
64
65(** [run_static_dtors ee] executes the static destructors of each module in
66    the execution engine [ee]. *)
67val run_static_dtors : llexecutionengine -> unit
68
69(** [data_layout ee] is the data layout of the execution engine [ee]. *)
70val data_layout : llexecutionengine -> Llvm_target.DataLayout.t
71
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
74    [gv] and [ee].
75    All uses of [gv] in the compiled code will refer to [ptr]. *)
76val add_global_mapping : Llvm.llvalue -> 'a Ctypes.ptr -> llexecutionengine -> unit
77
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. *)
84val get_global_value_address : string -> 'a Ctypes.typ -> llexecutionengine -> 'a
85
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. *)
92val get_function_address : string -> 'a Ctypes.typ -> llexecutionengine -> 'a
93