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