blob: 9794f358fff14161419e61e31fdcaf98fa9d4742 [file] [log] [blame]
Gordon Henriksen2e855e62007-12-23 16:59:28 +00001(*===-- llvm_executionengine.mli - LLVM Ocaml Interface ---------*- C++ -*-===*
2 *
3 * The LLVM Compiler Infrastructure
4 *
Chris Lattner234d5292007-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 Henriksen2e855e62007-12-23 16:59:28 +00007 *
Gordon Henriksen2e855e62007-12-23 16:59:28 +00008 *===----------------------------------------------------------------------===*)
9
Gordon Henriksen3b646de2008-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 Henriksen2e855e62007-12-23 16:59:28 +000014
15exception Error of string
16
Gordon Henriksen2e855e62007-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 Henriksen3b646de2008-03-09 07:17:38 +000022 See the struct [llvm::GenericValue]. *)
Gordon Henriksen2e855e62007-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 Henriksen3b646de2008-03-09 07:17:38 +000026 according to the floating point type [fpty]. See the fields
27 [llvm::GenericValue::DoubleVal] and [llvm::GenericValue::FloatVal]. *)
Gordon Henriksen2e855e62007-12-23 16:59:28 +000028 val of_float: Llvm.lltype -> float -> t
29
30 (** [of_pointer v] boxes the pointer value [v] in a generic value. See the
Gordon Henriksen3b646de2008-03-09 07:17:38 +000031 field [llvm::GenericValue::PointerVal]. *)
Gordon Henriksen2e855e62007-12-23 16:59:28 +000032 val of_pointer: 'a -> t
33
34 (** [of_int32 n w] boxes the int32 [i] in a generic value with the bitwidth
Gordon Henriksen3b646de2008-03-09 07:17:38 +000035 [w]. See the field [llvm::GenericValue::IntVal]. *)
Gordon Henriksen2e855e62007-12-23 16:59:28 +000036 val of_int32: Llvm.lltype -> int32 -> t
37
38 (** [of_int n w] boxes the int [i] in a generic value with the bitwidth
Gordon Henriksen3b646de2008-03-09 07:17:38 +000039 [w]. See the field [llvm::GenericValue::IntVal]. *)
Gordon Henriksen2e855e62007-12-23 16:59:28 +000040 val of_int: Llvm.lltype -> int -> t
41
42 (** [of_natint n w] boxes the native int [i] in a generic value with the
Gordon Henriksen3b646de2008-03-09 07:17:38 +000043 bitwidth [w]. See the field [llvm::GenericValue::IntVal]. *)
Gordon Henriksen2e855e62007-12-23 16:59:28 +000044 val of_nativeint: Llvm.lltype -> nativeint -> t
45
46 (** [of_int64 n w] boxes the int64 [i] in a generic value with the bitwidth
Gordon Henriksen3b646de2008-03-09 07:17:38 +000047 [w]. See the field [llvm::GenericValue::IntVal]. *)
Gordon Henriksen2e855e62007-12-23 16:59:28 +000048 val of_int64: Llvm.lltype -> int64 -> t
49
50 (** [as_float fpty gv] unboxes the floating point-valued generic value [gv] of
51 floating point type [fpty]. See the fields [llvm::GenericValue::DoubleVal]
Gordon Henriksen3b646de2008-03-09 07:17:38 +000052 and [llvm::GenericValue::FloatVal]. *)
Gordon Henriksen2e855e62007-12-23 16:59:28 +000053 val as_float: Llvm.lltype -> t -> float
54
55 (** [as_pointer gv] unboxes the pointer-valued generic value [gv]. See the
Gordon Henriksen3b646de2008-03-09 07:17:38 +000056 field [llvm::GenericValue::PointerVal]. *)
Gordon Henriksen2e855e62007-12-23 16:59:28 +000057 val as_pointer: t -> 'a
58
59 (** [as_int32 gv] unboxes the integer-valued generic value [gv] as an [int32].
60 Is invalid if [gv] has a bitwidth greater than 32 bits. See the field
Gordon Henriksen3b646de2008-03-09 07:17:38 +000061 [llvm::GenericValue::IntVal]. *)
Gordon Henriksen2e855e62007-12-23 16:59:28 +000062 val as_int32: t -> int32
63
64 (** [as_int gv] unboxes the integer-valued generic value [gv] as an [int].
65 Is invalid if [gv] has a bitwidth greater than the host bit width (but the
66 most significant bit may be lost). See the field
Gordon Henriksen3b646de2008-03-09 07:17:38 +000067 [llvm::GenericValue::IntVal]. *)
Gordon Henriksen2e855e62007-12-23 16:59:28 +000068 val as_int: t -> int
69
70 (** [as_natint gv] unboxes the integer-valued generic value [gv] as a
71 [nativeint]. Is invalid if [gv] has a bitwidth greater than
Gordon Henriksen3b646de2008-03-09 07:17:38 +000072 [nativeint]. See the field [llvm::GenericValue::IntVal]. *)
Gordon Henriksen2e855e62007-12-23 16:59:28 +000073 val as_nativeint: t -> nativeint
74
75 (** [as_int64 gv] returns the integer-valued generic value [gv] as an [int64].
76 Is invalid if [gv] has a bitwidth greater than [int64]. See the field
Gordon Henriksen3b646de2008-03-09 07:17:38 +000077 [llvm::GenericValue::IntVal]. *)
Gordon Henriksen2e855e62007-12-23 16:59:28 +000078 val as_int64: t -> int64
79end
80
81
82module ExecutionEngine: sig
83 (** An execution engine is either a JIT compiler or an interpreter, capable of
84 directly loading an LLVM module and executing its functions without first
Gordon Henriksen3b646de2008-03-09 07:17:38 +000085 invoking a static compiler and generating a native executable. *)
Gordon Henriksen2e855e62007-12-23 16:59:28 +000086 type t
87
88 (** [create mp] creates a new execution engine, taking ownership of the
89 module provider [mp] if successful. Creates a JIT if possible, else falls
90 back to an interpreter. Raises [Error msg] if an error occurrs. The
91 execution engine is not garbage collected and must be destroyed with
Gordon Henriksen3b646de2008-03-09 07:17:38 +000092 [dispose ee]. See the function [llvm::ExecutionEngine::create]. *)
Gordon Henriksen2e855e62007-12-23 16:59:28 +000093 val create: Llvm.llmoduleprovider -> t
94
95 (** [create_interpreter mp] creates a new interpreter, taking ownership of the
96 module provider [mp] if successful. Raises [Error msg] if an error
97 occurrs. The execution engine is not garbage collected and must be
98 destroyed with [dispose ee].
Gordon Henriksen3b646de2008-03-09 07:17:38 +000099 See the function [llvm::ExecutionEngine::create]. *)
Gordon Henriksen2e855e62007-12-23 16:59:28 +0000100 val create_interpreter: Llvm.llmoduleprovider -> t
101
102 (** [create_jit mp] creates a new JIT (just-in-time compiler), taking
103 ownership of the module provider [mp] if successful. Raises [Error msg] if
104 an error occurrs. The execution engine is not garbage collected and must
105 be destroyed with [dispose ee].
Gordon Henriksen3b646de2008-03-09 07:17:38 +0000106 See the function [llvm::ExecutionEngine::create]. *)
Gordon Henriksen2e855e62007-12-23 16:59:28 +0000107 val create_jit: Llvm.llmoduleprovider -> t
108
109 (** [dispose ee] releases the memory used by the execution engine and must be
Gordon Henriksen3b646de2008-03-09 07:17:38 +0000110 invoked to avoid memory leaks. *)
Gordon Henriksen2e855e62007-12-23 16:59:28 +0000111 val dispose: t -> unit
112
113 (** [add_module_provider mp ee] adds the module provider [mp] to the execution
Gordon Henriksen3b646de2008-03-09 07:17:38 +0000114 engine [ee]. *)
Gordon Henriksen2e855e62007-12-23 16:59:28 +0000115 val add_module_provider: Llvm.llmoduleprovider -> t -> unit
116
117 (** [remove_module_provider mp ee] removes the module provider [mp] from the
118 execution engine [ee], disposing of [mp] and the module referenced by
Gordon Henriksen3b646de2008-03-09 07:17:38 +0000119 [mp]. Raises [Error msg] if an error occurs. *)
Gordon Henriksen2e855e62007-12-23 16:59:28 +0000120 val remove_module_provider: Llvm.llmoduleprovider -> t -> Llvm.llmodule
121
Gordon Henriksen3b646de2008-03-09 07:17:38 +0000122 (** [find_function n ee] finds the function named [n] defined in any of the
Gordon Henriksen2e855e62007-12-23 16:59:28 +0000123 modules owned by the execution engine [ee]. Returns [None] if the function
Gordon Henriksen3b646de2008-03-09 07:17:38 +0000124 is not found and [Some f] otherwise. *)
Gordon Henriksen2e855e62007-12-23 16:59:28 +0000125 val find_function: string -> t -> Llvm.llvalue option
126
127 (** [run_function f args ee] synchronously executes the function [f] with the
Gordon Henriksen3b646de2008-03-09 07:17:38 +0000128 arguments [args], which must be compatible with the parameter types. *)
Gordon Henriksen2e855e62007-12-23 16:59:28 +0000129 val run_function: Llvm.llvalue -> GenericValue.t array -> t ->
130 GenericValue.t
131
132 (** [run_static_ctors ee] executes the static constructors of each module in
Gordon Henriksen3b646de2008-03-09 07:17:38 +0000133 the execution engine [ee]. *)
Gordon Henriksen2e855e62007-12-23 16:59:28 +0000134 val run_static_ctors: t -> unit
135
136 (** [run_static_dtors ee] executes the static destructors of each module in
Gordon Henriksen3b646de2008-03-09 07:17:38 +0000137 the execution engine [ee]. *)
Gordon Henriksen2e855e62007-12-23 16:59:28 +0000138 val run_static_dtors: t -> unit
139
Gordon Henriksen3b646de2008-03-09 07:17:38 +0000140 (** [run_function_as_main f args env ee] executes the function [f] as a main
Gordon Henriksen2e855e62007-12-23 16:59:28 +0000141 function, passing it [argv] and [argc] according to the string array
Gordon Henriksen3b646de2008-03-09 07:17:38 +0000142 [args], and [envp] as specified by the array [env]. Returns the integer
143 return value of the function. *)
Gordon Henriksen2e855e62007-12-23 16:59:28 +0000144 val run_function_as_main: Llvm.llvalue -> string array ->
145 (string * string) array -> t -> int
146
147 (** [free_machine_code f ee] releases the memory in the execution engine [ee]
Gordon Henriksen3b646de2008-03-09 07:17:38 +0000148 used to store the machine code for the function [f]. *)
Gordon Henriksen2e855e62007-12-23 16:59:28 +0000149 val free_machine_code: Llvm.llvalue -> t -> unit
Erick Tryzelaar7c1483b2008-03-27 00:27:14 +0000150
151 (** [target_data ee] is the target data owned by the execution engine
152 [ee]. *)
153 val target_data: t -> Llvm_target.TargetData.t
Gordon Henriksen2e855e62007-12-23 16:59:28 +0000154end