blob: 166b7bcddca69db5de50da2a703036216351f25e [file] [log] [blame]
Gordon Henriksen2a8cd892007-12-23 16:59:28 +00001(*===-- llvm_executionengine.mli - LLVM Ocaml Interface ---------*- C++ -*-===*
2 *
3 * The LLVM Compiler Infrastructure
4 *
Chris Lattner6787a452007-12-29 22:59:10 +00005 * This file is distributed under the University of Illinois Open Source
6 * License. See LICENSE.TXT for details.
Gordon Henriksen2a8cd892007-12-23 16:59:28 +00007 *
Gordon Henriksen2a8cd892007-12-23 16:59:28 +00008 *===----------------------------------------------------------------------===*)
9
Gordon Henriksen95f4b772008-03-09 07:17:38 +000010(** JIT Interpreter.
11
12 This interface provides an ocaml API for LLVM execution engine (JIT/
13 interpreter), the classes in the ExecutionEngine library. *)
Gordon Henriksen2a8cd892007-12-23 16:59:28 +000014
15exception Error of string
16
Gordon Henriksen2a8cd892007-12-23 16:59:28 +000017module GenericValue: sig
18 (** [GenericValue.t] is a boxed union type used to portably pass arguments to
19 and receive values from the execution engine. It supports only a limited
20 selection of types; for more complex argument types, it is necessary to
21 generate a stub function by hand or to pass parameters by reference.
Gordon Henriksen95f4b772008-03-09 07:17:38 +000022 See the struct [llvm::GenericValue]. *)
Gordon Henriksen2a8cd892007-12-23 16:59:28 +000023 type t
24
25 (** [of_float fpty n] boxes the float [n] in a float-valued generic value
Gordon Henriksen95f4b772008-03-09 07:17:38 +000026 according to the floating point type [fpty]. See the fields
27 [llvm::GenericValue::DoubleVal] and [llvm::GenericValue::FloatVal]. *)
Torok Edwin5abf51b2010-12-23 15:49:26 +000028 val of_float : Llvm.lltype -> float -> t
Gordon Henriksen2a8cd892007-12-23 16:59:28 +000029
30 (** [of_pointer v] boxes the pointer value [v] in a generic value. See the
Gordon Henriksen95f4b772008-03-09 07:17:38 +000031 field [llvm::GenericValue::PointerVal]. *)
Torok Edwin5abf51b2010-12-23 15:49:26 +000032 val of_pointer : 'a -> t
Gordon Henriksen2a8cd892007-12-23 16:59:28 +000033
34 (** [of_int32 n w] boxes the int32 [i] in a generic value with the bitwidth
Gordon Henriksen95f4b772008-03-09 07:17:38 +000035 [w]. See the field [llvm::GenericValue::IntVal]. *)
Torok Edwin5abf51b2010-12-23 15:49:26 +000036 val of_int32 : Llvm.lltype -> int32 -> t
Gordon Henriksen2a8cd892007-12-23 16:59:28 +000037
38 (** [of_int n w] boxes the int [i] in a generic value with the bitwidth
Gordon Henriksen95f4b772008-03-09 07:17:38 +000039 [w]. See the field [llvm::GenericValue::IntVal]. *)
Torok Edwin5abf51b2010-12-23 15:49:26 +000040 val of_int : Llvm.lltype -> int -> t
Gordon Henriksen2a8cd892007-12-23 16:59:28 +000041
42 (** [of_natint n w] boxes the native int [i] in a generic value with the
Gordon Henriksen95f4b772008-03-09 07:17:38 +000043 bitwidth [w]. See the field [llvm::GenericValue::IntVal]. *)
Torok Edwin5abf51b2010-12-23 15:49:26 +000044 val of_nativeint : Llvm.lltype -> nativeint -> t
45
Erick Tryzelaar7dd26152010-03-03 23:51:28 +000046
Gordon Henriksen2a8cd892007-12-23 16:59:28 +000047 (** [of_int64 n w] boxes the int64 [i] in a generic value with the bitwidth
Gordon Henriksen95f4b772008-03-09 07:17:38 +000048 [w]. See the field [llvm::GenericValue::IntVal]. *)
Torok Edwin5abf51b2010-12-23 15:49:26 +000049 val of_int64 : Llvm.lltype -> int64 -> t
Erick Tryzelaar7dd26152010-03-03 23:51:28 +000050
Gordon Henriksen2a8cd892007-12-23 16:59:28 +000051 (** [as_float fpty gv] unboxes the floating point-valued generic value [gv] of
52 floating point type [fpty]. See the fields [llvm::GenericValue::DoubleVal]
Gordon Henriksen95f4b772008-03-09 07:17:38 +000053 and [llvm::GenericValue::FloatVal]. *)
Torok Edwin5abf51b2010-12-23 15:49:26 +000054 val as_float : Llvm.lltype -> t -> float
Gordon Henriksen2a8cd892007-12-23 16:59:28 +000055
56 (** [as_pointer gv] unboxes the pointer-valued generic value [gv]. See the
Gordon Henriksen95f4b772008-03-09 07:17:38 +000057 field [llvm::GenericValue::PointerVal]. *)
Torok Edwin5abf51b2010-12-23 15:49:26 +000058 val as_pointer : t -> 'a
Gordon Henriksen2a8cd892007-12-23 16:59:28 +000059
60 (** [as_int32 gv] unboxes the integer-valued generic value [gv] as an [int32].
61 Is invalid if [gv] has a bitwidth greater than 32 bits. See the field
Gordon Henriksen95f4b772008-03-09 07:17:38 +000062 [llvm::GenericValue::IntVal]. *)
Torok Edwin5abf51b2010-12-23 15:49:26 +000063 val as_int32 : t -> int32
Gordon Henriksen2a8cd892007-12-23 16:59:28 +000064
65 (** [as_int gv] unboxes the integer-valued generic value [gv] as an [int].
66 Is invalid if [gv] has a bitwidth greater than the host bit width (but the
67 most significant bit may be lost). See the field
Gordon Henriksen95f4b772008-03-09 07:17:38 +000068 [llvm::GenericValue::IntVal]. *)
Torok Edwin5abf51b2010-12-23 15:49:26 +000069 val as_int : t -> int
Gordon Henriksen2a8cd892007-12-23 16:59:28 +000070
71 (** [as_natint gv] unboxes the integer-valued generic value [gv] as a
72 [nativeint]. Is invalid if [gv] has a bitwidth greater than
Gordon Henriksen95f4b772008-03-09 07:17:38 +000073 [nativeint]. See the field [llvm::GenericValue::IntVal]. *)
Torok Edwin5abf51b2010-12-23 15:49:26 +000074 val as_nativeint : t -> nativeint
Gordon Henriksen2a8cd892007-12-23 16:59:28 +000075
76 (** [as_int64 gv] returns the integer-valued generic value [gv] as an [int64].
77 Is invalid if [gv] has a bitwidth greater than [int64]. See the field
Gordon Henriksen95f4b772008-03-09 07:17:38 +000078 [llvm::GenericValue::IntVal]. *)
Torok Edwin5abf51b2010-12-23 15:49:26 +000079 val as_int64 : t -> int64
Gordon Henriksen2a8cd892007-12-23 16:59:28 +000080end
81
82
83module ExecutionEngine: sig
84 (** An execution engine is either a JIT compiler or an interpreter, capable of
85 directly loading an LLVM module and executing its functions without first
Gordon Henriksen95f4b772008-03-09 07:17:38 +000086 invoking a static compiler and generating a native executable. *)
Gordon Henriksen2a8cd892007-12-23 16:59:28 +000087 type t
88
Erick Tryzelaar98b05d62010-03-02 23:59:00 +000089 (** [create m] creates a new execution engine, taking ownership of the
90 module [m] if successful. Creates a JIT if possible, else falls back to an
91 interpreter. Raises [Error msg] if an error occurrs. The execution engine
92 is not garbage collected and must be destroyed with [dispose ee].
93 See the function [llvm::EngineBuilder::create]. *)
Torok Edwin5abf51b2010-12-23 15:49:26 +000094 val create : Llvm.llmodule -> t
Erick Tryzelaar98b05d62010-03-02 23:59:00 +000095
96 (** [create_interpreter m] creates a new interpreter, taking ownership of the
97 module [m] if successful. Raises [Error msg] if an error occurrs. The
Gordon Henriksen2a8cd892007-12-23 16:59:28 +000098 execution engine is not garbage collected and must be destroyed with
Erick Tryzelaar98b05d62010-03-02 23:59:00 +000099 [dispose ee].
100 See the function [llvm::EngineBuilder::create]. *)
Torok Edwin5abf51b2010-12-23 15:49:26 +0000101 val create_interpreter : Llvm.llmodule -> t
Gordon Henriksen2a8cd892007-12-23 16:59:28 +0000102
Erick Tryzelaar94feaaf2010-03-02 23:59:03 +0000103 (** [create_jit m optlevel] creates a new JIT (just-in-time compiler), taking
104 ownership of the module [m] if successful with the desired optimization
105 level [optlevel]. Raises [Error msg] if an error occurrs. The execution
106 engine is not garbage collected and must be destroyed with [dispose ee].
Reid Klecknerfc8a2d52009-07-18 00:42:18 +0000107 See the function [llvm::EngineBuilder::create]. *)
Torok Edwin5abf51b2010-12-23 15:49:26 +0000108 val create_jit : Llvm.llmodule -> int -> t
Erick Tryzelaar94feaaf2010-03-02 23:59:03 +0000109
Gordon Henriksen2a8cd892007-12-23 16:59:28 +0000110 (** [dispose ee] releases the memory used by the execution engine and must be
Gordon Henriksen95f4b772008-03-09 07:17:38 +0000111 invoked to avoid memory leaks. *)
Torok Edwin5abf51b2010-12-23 15:49:26 +0000112 val dispose : t -> unit
Gordon Henriksen2a8cd892007-12-23 16:59:28 +0000113
Erick Tryzelaar98b05d62010-03-02 23:59:00 +0000114 (** [add_module m ee] adds the module [m] to the execution engine [ee]. *)
Torok Edwin5abf51b2010-12-23 15:49:26 +0000115 val add_module : Llvm.llmodule -> t -> unit
Gordon Henriksen2a8cd892007-12-23 16:59:28 +0000116
Erick Tryzelaar98b05d62010-03-02 23:59:00 +0000117 (** [remove_module m ee] removes the module [m] from the execution engine
118 [ee], disposing of [m] and the module referenced by [mp]. Raises
119 [Error msg] if an error occurs. *)
Torok Edwin5abf51b2010-12-23 15:49:26 +0000120 val remove_module : Llvm.llmodule -> t -> Llvm.llmodule
121
Gordon Henriksen2a8cd892007-12-23 16:59:28 +0000122
Gordon Henriksen95f4b772008-03-09 07:17:38 +0000123 (** [find_function n ee] finds the function named [n] defined in any of the
Gordon Henriksen2a8cd892007-12-23 16:59:28 +0000124 modules owned by the execution engine [ee]. Returns [None] if the function
Gordon Henriksen95f4b772008-03-09 07:17:38 +0000125 is not found and [Some f] otherwise. *)
Torok Edwin5abf51b2010-12-23 15:49:26 +0000126 val find_function : string -> t -> Llvm.llvalue option
127
Gordon Henriksen2a8cd892007-12-23 16:59:28 +0000128
129 (** [run_function f args ee] synchronously executes the function [f] with the
Gordon Henriksen95f4b772008-03-09 07:17:38 +0000130 arguments [args], which must be compatible with the parameter types. *)
Torok Edwin5abf51b2010-12-23 15:49:26 +0000131 val run_function : Llvm.llvalue -> GenericValue.t array -> t ->
Erick Tryzelaar7dd26152010-03-03 23:51:28 +0000132 GenericValue.t
Torok Edwin5abf51b2010-12-23 15:49:26 +0000133
Gordon Henriksen2a8cd892007-12-23 16:59:28 +0000134
135 (** [run_static_ctors ee] executes the static constructors of each module in
Gordon Henriksen95f4b772008-03-09 07:17:38 +0000136 the execution engine [ee]. *)
Torok Edwin5abf51b2010-12-23 15:49:26 +0000137 val run_static_ctors : t -> unit
Gordon Henriksen2a8cd892007-12-23 16:59:28 +0000138
139 (** [run_static_dtors ee] executes the static destructors of each module in
Gordon Henriksen95f4b772008-03-09 07:17:38 +0000140 the execution engine [ee]. *)
Torok Edwin5abf51b2010-12-23 15:49:26 +0000141 val run_static_dtors : t -> unit
Gordon Henriksen2a8cd892007-12-23 16:59:28 +0000142
Gordon Henriksen95f4b772008-03-09 07:17:38 +0000143 (** [run_function_as_main f args env ee] executes the function [f] as a main
Gordon Henriksen2a8cd892007-12-23 16:59:28 +0000144 function, passing it [argv] and [argc] according to the string array
Gordon Henriksen95f4b772008-03-09 07:17:38 +0000145 [args], and [envp] as specified by the array [env]. Returns the integer
146 return value of the function. *)
Torok Edwin5abf51b2010-12-23 15:49:26 +0000147 val run_function_as_main : Llvm.llvalue -> string array ->
Erick Tryzelaar7dd26152010-03-03 23:51:28 +0000148 (string * string) array -> t -> int
Torok Edwin5abf51b2010-12-23 15:49:26 +0000149
Gordon Henriksen2a8cd892007-12-23 16:59:28 +0000150
151 (** [free_machine_code f ee] releases the memory in the execution engine [ee]
Gordon Henriksen95f4b772008-03-09 07:17:38 +0000152 used to store the machine code for the function [f]. *)
Torok Edwin5abf51b2010-12-23 15:49:26 +0000153 val free_machine_code : Llvm.llvalue -> t -> unit
154
Erick Tryzelaar8ac07c22008-03-27 00:27:14 +0000155
156 (** [target_data ee] is the target data owned by the execution engine
157 [ee]. *)
Torok Edwin5abf51b2010-12-23 15:49:26 +0000158 val target_data : t -> Llvm_target.TargetData.t
159
Gordon Henriksen2a8cd892007-12-23 16:59:28 +0000160end
Erick Tryzelaarb4e19172009-09-14 21:54:32 +0000161
Torok Edwin5abf51b2010-12-23 15:49:26 +0000162val initialize_native_target : unit -> bool
163