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