1 (*===-- tools/ml/llvm.ml - LLVM Ocaml Interface ---------------------------===*
3 * The LLVM Compiler Infrastructure
5 * This file was developed by Gordon Henriksen and is distributed under the
6 * University of Illinois Open Source License. See LICENSE.TXT for details.
8 *===----------------------------------------------------------------------===
10 * This interface provides an ocaml API for the LLVM intermediate
11 * representation, the classes in the VMCore library.
13 *===----------------------------------------------------------------------===*)
16 (* These abstract types correlate directly to the LLVM VMCore classes. *)
45 | External_weak_linkage
51 | Protected_visibility
54 (*===-- Modules -----------------------------------------------------------===*)
56 (* Creates a module with the supplied module ID. Modules are not garbage
57 collected; it is mandatory to call dispose_module to free memory. *)
58 external create_module : string -> llmodule = "llvm_create_module"
60 (* Disposes a module. All references to subordinate objects are invalidated;
61 referencing them will invoke undefined behavior. *)
62 external dispose_module : llmodule -> unit = "llvm_dispose_module"
64 (* Adds a named type to the module's symbol table. Returns true if successful.
65 If such a name already exists, then no entry is added and returns false. *)
66 external add_type_name : string -> lltype -> llmodule -> bool
67 = "llvm_add_type_name"
70 (*===-- Types -------------------------------------------------------------===*)
72 external classify_type : lltype -> type_kind = "llvm_classify_type"
73 external refine_abstract_type : lltype -> lltype -> unit
74 = "llvm_refine_abstract_type"
76 (*--... Operations on integer types ........................................--*)
77 external _i1_type : unit -> lltype = "llvm_i1_type"
78 external _i8_type : unit -> lltype = "llvm_i8_type"
79 external _i16_type : unit -> lltype = "llvm_i16_type"
80 external _i32_type : unit -> lltype = "llvm_i32_type"
81 external _i64_type : unit -> lltype = "llvm_i64_type"
83 let i1_type = _i1_type ()
84 let i8_type = _i8_type ()
85 let i16_type = _i16_type ()
86 let i32_type = _i32_type ()
87 let i64_type = _i64_type ()
89 external make_integer_type : int -> lltype = "llvm_make_integer_type"
90 external integer_bitwidth : lltype -> int = "llvm_integer_bitwidth"
92 (*--... Operations on real types ...........................................--*)
93 external _float_type : unit -> lltype = "llvm_float_type"
94 external _double_type : unit -> lltype = "llvm_double_type"
95 external _x86fp80_type : unit -> lltype = "llvm_x86fp80_type"
96 external _fp128_type : unit -> lltype = "llvm_fp128_type"
97 external _ppc_fp128_type : unit -> lltype = "llvm_ppc_fp128_type"
99 let float_type = _float_type ()
100 let double_type = _double_type ()
101 let x86fp80_type = _x86fp80_type ()
102 let fp128_type = _fp128_type ()
103 let ppc_fp128_type = _ppc_fp128_type ()
105 (*--... Operations on function types .......................................--*)
106 (* FIXME: handle parameter attributes *)
107 external make_function_type : lltype -> lltype array -> bool -> lltype
108 = "llvm_make_function_type"
109 external is_var_arg : lltype -> bool = "llvm_is_var_arg"
110 external return_type : lltype -> lltype = "llvm_return_type"
111 external param_types : lltype -> lltype array = "llvm_param_types"
113 (*--... Operations on struct types .........................................--*)
114 external make_struct_type : lltype array -> bool -> lltype
115 = "llvm_make_struct_type"
116 external element_types : lltype -> lltype array = "llvm_element_types"
117 external is_packed : lltype -> bool = "llvm_is_packed"
119 (*--... Operations on pointer, vector, and array types .....................--*)
120 external make_array_type : lltype -> int -> lltype = "llvm_make_array_type"
121 external make_pointer_type : lltype -> lltype = "llvm_make_pointer_type"
122 external make_vector_type : lltype -> int -> lltype = "llvm_make_vector_type"
124 external element_type : lltype -> lltype = "llvm_element_type"
125 external array_length : lltype -> int = "llvm_array_length"
126 external vector_size : lltype -> int = "llvm_vector_size"
128 (*--... Operations on other types ..........................................--*)
129 external make_opaque_type : unit -> lltype = "llvm_make_opaque_type"
130 external _void_type : unit -> lltype = "llvm_void_type"
131 external _label_type : unit -> lltype = "llvm_label_type"
133 let void_type = _void_type ()
134 let label_type = _label_type ()
137 (*===-- Values ------------------------------------------------------------===*)
139 external type_of : llvalue -> lltype = "llvm_type_of"
140 external value_name : llvalue -> string = "llvm_value_name"
141 external set_value_name : string -> llvalue -> unit = "llvm_set_value_name"
143 (*--... Operations on constants of (mostly) any type .......................--*)
144 external make_null : lltype -> llvalue = "llvm_make_null"
145 external make_all_ones : lltype -> llvalue = "llvm_make_all_ones"
146 external make_undef : lltype -> llvalue = "llvm_make_undef"
147 external is_null : llvalue -> bool = "llvm_is_null"
149 (*--... Operations on scalar constants .....................................--*)
150 external make_int_constant : lltype -> int -> bool -> llvalue
151 = "llvm_make_int_constant"
152 external make_real_constant : lltype -> float -> llvalue
153 = "llvm_make_real_constant"
155 (*--... Operations on composite constants ..................................--*)
156 external make_string_constant : string -> bool -> llvalue
157 = "llvm_make_string_constant"
158 external make_array_constant : lltype -> llvalue array -> llvalue
159 = "llvm_make_array_constant"
160 external make_struct_constant : llvalue array -> bool -> llvalue
161 = "llvm_make_struct_constant"
162 external make_vector_constant : llvalue array -> llvalue
163 = "llvm_make_vector_constant"
165 (*--... Operations on global variables, functions, and aliases (globals) ...--*)
166 external is_declaration : llvalue -> bool = "llvm_is_declaration"
167 external linkage : llvalue -> linkage = "llvm_linkage"
168 external set_linkage : linkage -> llvalue -> unit = "llvm_set_linkage"
169 external section : llvalue -> string = "llvm_section"
170 external set_section : string -> llvalue -> unit = "llvm_set_section"
171 external visibility : llvalue -> visibility = "llvm_visibility"
172 external set_visibility : visibility -> llvalue -> unit = "llvm_set_visibility"
173 external alignment : llvalue -> int = "llvm_alignment"
174 external set_alignment : int -> llvalue -> unit = "llvm_set_alignment"
176 (*--... Operations on global variables .....................................--*)
177 external declare_global : lltype -> string -> llmodule -> llvalue
178 = "llvm_declare_global"
179 external define_global : string -> llvalue -> llmodule -> llvalue
180 = "llvm_define_global"
181 external delete_global : llvalue -> unit = "llvm_delete_global"
182 external global_initializer : llvalue -> llvalue = "llvm_global_initializer"
183 external set_initializer : llvalue -> llvalue -> unit = "llvm_set_initializer"
184 external remove_initializer : llvalue -> unit = "llvm_remove_initializer"
185 external is_thread_local : llvalue -> bool = "llvm_is_thread_local"
186 external set_thread_local : bool -> llvalue -> unit = "llvm_set_thread_local"
189 (*===-- Non-Externs -------------------------------------------------------===*)
190 (* These functions are built using the externals, so must be declared late. *)
192 let concat2 sep arr =
194 if 0 < Array.length arr then begin
196 for i = 1 to (Array.length arr) - 1 do
197 s := !s ^ sep ^ arr.(i)
202 let rec string_of_lltype ty =
203 match classify_type ty with
204 Integer_type -> "i" ^ string_of_int (integer_bitwidth ty)
205 | Pointer_type -> (string_of_lltype (element_type ty)) ^ "*"
207 let s = "{ " ^ (concat2 ", " (
208 Array.map string_of_lltype (element_types ty)
213 | Array_type -> "[" ^ (string_of_int (array_length ty)) ^
214 " x " ^ (string_of_lltype (element_type ty)) ^ "]"
215 | Vector_type -> "<" ^ (string_of_int (vector_size ty)) ^
216 " x " ^ (string_of_lltype (element_type ty)) ^ ">"
217 | Opaque_type -> "opaque"
218 | Function_type -> string_of_lltype (return_type ty) ^
219 " (" ^ (concat2 ", " (
220 Array.map string_of_lltype (param_types ty)
222 | Label_type -> "label"
223 | Ppc_fp128_type -> "ppc_fp128"
224 | Fp128_type -> "fp128"
225 | X86fp80_type -> "x86_fp80"
226 | Double_type -> "double"
227 | Float_type -> "float"
228 | Void_type -> "void"