1*9880d681SAndroid Build Coastguard Worker(*===-- llvm_executionengine.ml - 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 Workerexception Error of string 11*9880d681SAndroid Build Coastguard Worker 12*9880d681SAndroid Build Coastguard Workerlet () = Callback.register_exception "Llvm_executionengine.Error" (Error "") 13*9880d681SAndroid Build Coastguard Worker 14*9880d681SAndroid Build Coastguard Workerexternal initialize : unit -> bool 15*9880d681SAndroid Build Coastguard Worker = "llvm_ee_initialize" 16*9880d681SAndroid Build Coastguard Worker 17*9880d681SAndroid Build Coastguard Workertype llexecutionengine 18*9880d681SAndroid Build Coastguard Worker 19*9880d681SAndroid Build Coastguard Workertype llcompileroptions = { 20*9880d681SAndroid Build Coastguard Worker opt_level: int; 21*9880d681SAndroid Build Coastguard Worker code_model: Llvm_target.CodeModel.t; 22*9880d681SAndroid Build Coastguard Worker no_framepointer_elim: bool; 23*9880d681SAndroid Build Coastguard Worker enable_fast_isel: bool; 24*9880d681SAndroid Build Coastguard Worker} 25*9880d681SAndroid Build Coastguard Worker 26*9880d681SAndroid Build Coastguard Workerlet default_compiler_options = { 27*9880d681SAndroid Build Coastguard Worker opt_level = 0; 28*9880d681SAndroid Build Coastguard Worker code_model = Llvm_target.CodeModel.JITDefault; 29*9880d681SAndroid Build Coastguard Worker no_framepointer_elim = false; 30*9880d681SAndroid Build Coastguard Worker enable_fast_isel = false } 31*9880d681SAndroid Build Coastguard Worker 32*9880d681SAndroid Build Coastguard Workerexternal create : ?options:llcompileroptions -> Llvm.llmodule -> llexecutionengine 33*9880d681SAndroid Build Coastguard Worker = "llvm_ee_create" 34*9880d681SAndroid Build Coastguard Workerexternal dispose : llexecutionengine -> unit 35*9880d681SAndroid Build Coastguard Worker = "llvm_ee_dispose" 36*9880d681SAndroid Build Coastguard Workerexternal add_module : Llvm.llmodule -> llexecutionengine -> unit 37*9880d681SAndroid Build Coastguard Worker = "llvm_ee_add_module" 38*9880d681SAndroid Build Coastguard Workerexternal remove_module : Llvm.llmodule -> llexecutionengine -> unit 39*9880d681SAndroid Build Coastguard Worker = "llvm_ee_remove_module" 40*9880d681SAndroid Build Coastguard Workerexternal run_static_ctors : llexecutionengine -> unit 41*9880d681SAndroid Build Coastguard Worker = "llvm_ee_run_static_ctors" 42*9880d681SAndroid Build Coastguard Workerexternal run_static_dtors : llexecutionengine -> unit 43*9880d681SAndroid Build Coastguard Worker = "llvm_ee_run_static_dtors" 44*9880d681SAndroid Build Coastguard Workerexternal data_layout : llexecutionengine -> Llvm_target.DataLayout.t 45*9880d681SAndroid Build Coastguard Worker = "llvm_ee_get_data_layout" 46*9880d681SAndroid Build Coastguard Workerexternal add_global_mapping_ : Llvm.llvalue -> nativeint -> llexecutionengine -> unit 47*9880d681SAndroid Build Coastguard Worker = "llvm_ee_add_global_mapping" 48*9880d681SAndroid Build Coastguard Workerexternal get_global_value_address_ : string -> llexecutionengine -> nativeint 49*9880d681SAndroid Build Coastguard Worker = "llvm_ee_get_global_value_address" 50*9880d681SAndroid Build Coastguard Workerexternal get_function_address_ : string -> llexecutionengine -> nativeint 51*9880d681SAndroid Build Coastguard Worker = "llvm_ee_get_function_address" 52*9880d681SAndroid Build Coastguard Worker 53*9880d681SAndroid Build Coastguard Workerlet add_global_mapping llval ptr ee = 54*9880d681SAndroid Build Coastguard Worker add_global_mapping_ llval (Ctypes.raw_address_of_ptr (Ctypes.to_voidp ptr)) ee 55*9880d681SAndroid Build Coastguard Worker 56*9880d681SAndroid Build Coastguard Workerlet get_global_value_address name typ ee = 57*9880d681SAndroid Build Coastguard Worker let vptr = get_global_value_address_ name ee in 58*9880d681SAndroid Build Coastguard Worker if Nativeint.to_int vptr <> 0 then 59*9880d681SAndroid Build Coastguard Worker let open Ctypes in !@ (coerce (ptr void) (ptr typ) (ptr_of_raw_address vptr)) 60*9880d681SAndroid Build Coastguard Worker else 61*9880d681SAndroid Build Coastguard Worker raise (Error ("Value " ^ name ^ " not found")) 62*9880d681SAndroid Build Coastguard Worker 63*9880d681SAndroid Build Coastguard Workerlet get_function_address name typ ee = 64*9880d681SAndroid Build Coastguard Worker let fptr = get_function_address_ name ee in 65*9880d681SAndroid Build Coastguard Worker if Nativeint.to_int fptr <> 0 then 66*9880d681SAndroid Build Coastguard Worker let open Ctypes in coerce (ptr void) typ (ptr_of_raw_address fptr) 67*9880d681SAndroid Build Coastguard Worker else 68*9880d681SAndroid Build Coastguard Worker raise (Error ("Function " ^ name ^ " not found")) 69*9880d681SAndroid Build Coastguard Worker 70*9880d681SAndroid Build Coastguard Worker(* The following are not bound. Patches are welcome. 71*9880d681SAndroid Build Coastguard Workertarget_machine : llexecutionengine -> Llvm_target.TargetMachine.t 72*9880d681SAndroid Build Coastguard Worker *) 73