summaryrefslogtreecommitdiffstats
path: root/llvm/bindings/ocaml/executionengine/llvm_executionengine.ml
blob: f61195337ca1fb691fa8adf5b02e67a1b9890d18 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
(*===-- llvm_executionengine.ml - LLVM OCaml Interface --------*- OCaml -*-===*
 *
 *                     The LLVM Compiler Infrastructure
 *
 * This file is distributed under the University of Illinois Open Source
 * License. See LICENSE.TXT for details.
 *
 *===----------------------------------------------------------------------===*)

exception Error of string

let () = Callback.register_exception "Llvm_executionengine.Error" (Error "")

module CodeModel = struct
  type t =
  | Default
  | JIT_default
  | Small
  | Kernel
  | Medium
  | Large
end

module GenericValue = struct
  type t

  external of_float: Llvm.lltype -> float -> t
    = "llvm_genericvalue_of_float"
  external of_pointer: 'a -> t
    = "llvm_genericvalue_of_pointer"
  external of_int32: Llvm.lltype -> int32 -> t
    = "llvm_genericvalue_of_int32"
  external of_int: Llvm.lltype -> int -> t
    = "llvm_genericvalue_of_int"
  external of_nativeint: Llvm.lltype -> nativeint -> t
    = "llvm_genericvalue_of_nativeint"
  external of_int64: Llvm.lltype -> int64 -> t
    = "llvm_genericvalue_of_int64"

  external as_float: Llvm.lltype -> t -> float
    = "llvm_genericvalue_as_float"
  external as_pointer: t -> 'a
    = "llvm_genericvalue_as_pointer"
  external as_int32: t -> int32
    = "llvm_genericvalue_as_int32"
  external as_int: t -> int
    = "llvm_genericvalue_as_int"
  external as_nativeint: t -> nativeint
    = "llvm_genericvalue_as_nativeint"
  external as_int64: t -> int64
    = "llvm_genericvalue_as_int64"
end


module ExecutionEngine = struct
  type t

  type compileroptions = {
    opt_level: int;
    code_model: CodeModel.t;
    no_framepointer_elim: bool;
    enable_fast_isel: bool;
  }

  let default_compiler_options = {
    opt_level = 0;
    code_model = CodeModel.JIT_default;
    no_framepointer_elim = false;
    enable_fast_isel = false }

  external create: Llvm.llmodule -> t
    = "llvm_ee_create"
  external create_interpreter: Llvm.llmodule -> t
    = "llvm_ee_create_interpreter"
  external create_jit: Llvm.llmodule -> int -> t
    = "llvm_ee_create_jit"
  external create_mcjit: Llvm.llmodule -> compileroptions -> t
    = "llvm_ee_create_mcjit"
  external dispose: t -> unit
    = "llvm_ee_dispose"
  external add_module: Llvm.llmodule -> t -> unit
    = "llvm_ee_add_module"
  external remove_module: Llvm.llmodule -> t -> Llvm.llmodule
    = "llvm_ee_remove_module"
  external find_function: string -> t -> Llvm.llvalue option
    = "llvm_ee_find_function"
  external run_function: Llvm.llvalue -> GenericValue.t array -> t ->
                         GenericValue.t
    = "llvm_ee_run_function"
  external run_static_ctors: t -> unit
    = "llvm_ee_run_static_ctors"
  external run_static_dtors: t -> unit
    = "llvm_ee_run_static_dtors"
  external run_function_as_main: Llvm.llvalue -> string array ->
                                 (string * string) array -> t -> int
    = "llvm_ee_run_function_as_main"
  external free_machine_code: Llvm.llvalue -> t -> unit
    = "llvm_ee_free_machine_code"

  external data_layout : t -> Llvm_target.DataLayout.t
    = "llvm_ee_get_data_layout"

  (* The following are not bound. Patches are welcome.

  add_global_mapping: llvalue -> llgenericvalue -> t -> unit
  clear_all_global_mappings: t -> unit
  update_global_mapping: llvalue -> llgenericvalue -> t -> unit
  get_pointer_to_global_if_available: llvalue -> t -> llgenericvalue
  get_pointer_to_global: llvalue -> t -> llgenericvalue
  get_pointer_to_function: llvalue -> t -> llgenericvalue
  get_pointer_to_function_or_stub: llvalue -> t -> llgenericvalue
  get_global_value_at_address: llgenericvalue -> t -> llvalue option
  store_value_to_memory: llgenericvalue -> llgenericvalue -> lltype -> unit
  initialize_memory: llvalue -> llgenericvalue -> t -> unit
  recompile_and_relink_function: llvalue -> t -> llgenericvalue
  get_or_emit_global_variable: llvalue -> t -> llgenericvalue
  disable_lazy_compilation: t -> unit
  lazy_compilation_enabled: t -> bool
  install_lazy_function_creator: (string -> llgenericvalue) -> t -> unit

   *)
end

external initialize_native_target : unit -> bool
                                  = "llvm_initialize_native_target"
OpenPOWER on IntegriCloud