blob: ce25f9d0ae097d4f36b0746329aee8dbc87cf10a [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]. *)
Erick Tryzelaar7dd26152010-03-03 23:51:28 +000028 external of_float : Llvm.lltype -> float -> t = "llvm_genericvalue_of_float"
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]. *)
Erick Tryzelaar3e64c262010-03-03 23:51:30 +000032 external of_pointer : 'a -> t = "llvm_genericvalue_of_pointer"
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]. *)
Erick Tryzelaar7dd26152010-03-03 23:51:28 +000036 external of_int32 : Llvm.lltype -> int32 -> t = "llvm_genericvalue_of_int32"
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]. *)
Erick Tryzelaar7dd26152010-03-03 23:51:28 +000040 external of_int : Llvm.lltype -> int -> t = "llvm_genericvalue_of_int"
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]. *)
Erick Tryzelaar7dd26152010-03-03 23:51:28 +000044 external of_nativeint : Llvm.lltype -> nativeint -> t
45 = "llvm_genericvalue_of_nativeint"
46
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]. *)
Erick Tryzelaar7dd26152010-03-03 23:51:28 +000049 external of_int64 : Llvm.lltype -> int64 -> t = "llvm_genericvalue_of_int64"
50
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]. *)
Erick Tryzelaar7dd26152010-03-03 23:51:28 +000054 external as_float : Llvm.lltype -> t -> float = "llvm_genericvalue_as_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]. *)
Erick Tryzelaar3e64c262010-03-03 23:51:30 +000058 external as_pointer : t -> 'a = "llvm_genericvalue_as_pointer"
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]. *)
Erick Tryzelaar7dd26152010-03-03 23:51:28 +000063 external as_int32 : t -> int32 = "llvm_genericvalue_as_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]. *)
Erick Tryzelaar7dd26152010-03-03 23:51:28 +000069 external as_int : t -> int = "llvm_genericvalue_as_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]. *)
Erick Tryzelaar3e64c262010-03-03 23:51:30 +000074 external as_nativeint : t -> nativeint = "llvm_genericvalue_as_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]. *)
Erick Tryzelaar7dd26152010-03-03 23:51:28 +000079 external as_int64 : t -> int64 = "llvm_genericvalue_as_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]. *)
Erick Tryzelaar7dd26152010-03-03 23:51:28 +000094 external create : Llvm.llmodule -> t = "llvm_ee_create"
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]. *)
Erick Tryzelaar7dd26152010-03-03 23:51:28 +0000101 external create_interpreter : Llvm.llmodule -> t = "llvm_ee_create_interpreter"
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]. *)
Erick Tryzelaar7dd26152010-03-03 23:51:28 +0000108 external create_jit : Llvm.llmodule -> int -> t = "llvm_ee_create_jit"
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. *)
Erick Tryzelaar7dd26152010-03-03 23:51:28 +0000112 external dispose : t -> unit = "llvm_ee_dispose"
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]. *)
Erick Tryzelaar3e64c262010-03-03 23:51:30 +0000115 external add_module : Llvm.llmodule -> t -> unit = "llvm_ee_add_module"
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. *)
Erick Tryzelaar7dd26152010-03-03 23:51:28 +0000120 external remove_module : Llvm.llmodule -> t -> Llvm.llmodule
121 = "llvm_ee_remove_module"
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. *)
Erick Tryzelaar7dd26152010-03-03 23:51:28 +0000126 external find_function : string -> t -> Llvm.llvalue option
127 = "llvm_ee_find_function"
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. *)
Erick Tryzelaar7dd26152010-03-03 23:51:28 +0000131 external run_function : Llvm.llvalue -> GenericValue.t array -> t ->
132 GenericValue.t
133 = "llvm_ee_run_function"
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]. *)
Erick Tryzelaar7dd26152010-03-03 23:51:28 +0000137 external run_static_ctors : t -> unit = "llvm_ee_run_static_ctors"
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]. *)
Erick Tryzelaar7dd26152010-03-03 23:51:28 +0000141 external run_static_dtors : t -> unit = "llvm_ee_run_static_dtors"
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. *)
Erick Tryzelaar7dd26152010-03-03 23:51:28 +0000147 external run_function_as_main : Llvm.llvalue -> string array ->
148 (string * string) array -> t -> int
149 = "llvm_ee_run_function_as_main"
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]. *)
Erick Tryzelaar7dd26152010-03-03 23:51:28 +0000153 external free_machine_code : Llvm.llvalue -> t -> unit
154 = "llvm_ee_free_machine_code"
Erick Tryzelaar8ac07c22008-03-27 00:27:14 +0000155
156 (** [target_data ee] is the target data owned by the execution engine
157 [ee]. *)
Erick Tryzelaar7dd26152010-03-03 23:51:28 +0000158 external target_data : t -> Llvm_target.TargetData.t
159 = "LLVMGetExecutionEngineTargetData"
Gordon Henriksen2a8cd892007-12-23 16:59:28 +0000160end
Erick Tryzelaarb4e19172009-09-14 21:54:32 +0000161
162external initialize_native_target : unit -> bool
163 = "llvm_initialize_native_target"