0e38ca0ef2f2bc72d940c0b0ca2fff7676f7454f
[oota-llvm.git] / bindings / ocaml / llvm / llvm.mli
1 (*===-- tools/ml/llvm.ml - LLVM Ocaml Interface ---------------------------===*
2  *
3  *                     The LLVM Compiler Infrastructure
4  *
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.
7  *
8  *===----------------------------------------------------------------------===
9  *
10  * This interface provides an ocaml API for the LLVM intermediate
11  * representation, the classes in the VMCore library.
12  *
13  *===----------------------------------------------------------------------===*)
14
15
16 (* These abstract types correlate directly to the LLVM VMCore classes. *)
17 type llmodule
18 type lltype
19 type llvalue
20
21 type type_kind =
22   Void_type
23 | Float_type
24 | Double_type
25 | X86fp80_type
26 | Fp128_type
27 | Ppc_fp128_type
28 | Label_type
29 | Integer_type
30 | Function_type
31 | Struct_type
32 | Array_type
33 | Pointer_type 
34 | Opaque_type
35 | Vector_type
36
37 type linkage =
38   External_linkage
39 | Link_once_linkage
40 | Weak_linkage
41 | Appending_linkage
42 | Internal_linkage
43 | Dllimport_linkage
44 | Dllexport_linkage
45 | External_weak_linkage
46 | Ghost_linkage
47
48 type visibility =
49   Default_visibility
50 | Hidden_visibility
51 | Protected_visibility
52
53
54 (*===-- Modules -----------------------------------------------------------===*)
55
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"
59
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"
63
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"
68
69
70 (*===-- Types -------------------------------------------------------------===*)
71 external classify_type : lltype -> type_kind = "llvm_classify_type"
72 external refine_abstract_type : lltype -> lltype -> unit
73                               = "llvm_refine_abstract_type"
74 val string_of_lltype : lltype -> string
75
76 (*--... Operations on integer types ........................................--*)
77 val i1_type : lltype
78 val i8_type : lltype
79 val i16_type : lltype
80 val i32_type : lltype
81 val i64_type : lltype
82 external make_integer_type : int -> lltype = "llvm_make_integer_type"
83 external integer_bitwidth : lltype -> int = "llvm_integer_bitwidth"
84
85 (*--... Operations on real types ...........................................--*)
86 val float_type : lltype
87 val double_type : lltype
88 val x86fp80_type : lltype
89 val fp128_type : lltype
90 val ppc_fp128_type : lltype
91
92 (*--... Operations on function types .......................................--*)
93 (* FIXME: handle parameter attributes                                         *)
94 external make_function_type : lltype -> lltype array -> bool -> lltype
95                             = "llvm_make_function_type"
96 external is_var_arg : lltype -> bool = "llvm_is_var_arg"
97 external return_type : lltype -> lltype = "llvm_return_type"
98 external param_types : lltype -> lltype array = "llvm_param_types"
99
100 (*--... Operations on struct types .........................................--*)
101 external make_struct_type : lltype array -> bool -> lltype
102                           = "llvm_make_struct_type"
103 external element_types : lltype -> lltype array = "llvm_element_types"
104 external is_packed : lltype -> bool = "llvm_is_packed"
105
106 (*--... Operations on pointer, vector, and array types .....................--*)
107 external make_array_type : lltype -> int -> lltype = "llvm_make_array_type"
108 external make_pointer_type : lltype -> lltype = "llvm_make_pointer_type"
109 external make_vector_type : lltype -> int -> lltype = "llvm_make_vector_type"
110
111 external element_type : lltype -> lltype = "llvm_element_type"
112 external array_length : lltype -> int = "llvm_array_length"
113 external vector_size : lltype -> int = "llvm_vector_size"
114
115 (*--... Operations on other types ..........................................--*)
116 external make_opaque_type : unit -> lltype = "llvm_make_opaque_type"
117 val void_type : lltype
118 val label_type : lltype
119
120
121 (*===-- Values ------------------------------------------------------------===*)
122 external type_of : llvalue -> lltype = "llvm_type_of"
123 external value_name : llvalue -> string = "llvm_value_name"
124 external set_value_name : string -> llvalue -> unit = "llvm_set_value_name"
125
126 (*--... Operations on constants of (mostly) any type .......................--*)
127 external is_constant : llvalue -> bool = "llvm_is_constant"
128 external make_null : lltype -> llvalue = "llvm_make_null"
129 external make_all_ones : (*int|vec*)lltype -> llvalue = "llvm_make_all_ones"
130 external make_undef : lltype -> llvalue = "llvm_make_undef"
131 external is_null : llvalue -> bool = "llvm_is_null"
132 external is_undef : llvalue -> bool = "llvm_is_undef"
133
134 (*--... Operations on scalar constants .....................................--*)
135 external make_int_constant : lltype -> int -> bool -> llvalue
136                            = "llvm_make_int_constant"
137 external make_int64_constant : lltype -> Int64.t -> bool -> llvalue
138                              = "llvm_make_int64_constant"
139 external make_real_constant : lltype -> float -> llvalue
140                             = "llvm_make_real_constant"
141
142 (*--... Operations on composite constants ..................................--*)
143 external make_string_constant : string -> bool -> llvalue
144                               = "llvm_make_string_constant"
145 external make_array_constant : lltype -> llvalue array -> llvalue
146                              = "llvm_make_array_constant"
147 external make_struct_constant : llvalue array -> bool -> llvalue
148                               = "llvm_make_struct_constant"
149 external make_vector_constant : llvalue array -> llvalue
150                               = "llvm_make_vector_constant"
151
152 (*--... Operations on global variables, functions, and aliases (globals) ...--*)
153 external is_declaration : llvalue -> bool = "llvm_is_declaration"
154 external linkage : llvalue -> linkage = "llvm_linkage"
155 external set_linkage : linkage -> llvalue -> unit = "llvm_set_linkage"
156 external section : llvalue -> string = "llvm_section"
157 external set_section : string -> llvalue -> unit = "llvm_set_section"
158 external visibility : llvalue -> visibility = "llvm_visibility"
159 external set_visibility : visibility -> llvalue -> unit = "llvm_set_visibility"
160 external alignment : llvalue -> int = "llvm_alignment"
161 external set_alignment : int -> llvalue -> unit = "llvm_set_alignment"
162
163 (*--... Operations on global variables .....................................--*)
164 external declare_global : lltype -> string -> llmodule -> llvalue
165                         = "llvm_declare_global"
166 external define_global : string -> llvalue -> llmodule -> llvalue
167                        = "llvm_define_global"
168 external delete_global : llvalue -> unit = "llvm_delete_global"
169 external global_initializer : llvalue -> llvalue = "llvm_global_initializer"
170 external set_initializer : llvalue -> llvalue -> unit = "llvm_set_initializer"
171 external remove_initializer : llvalue -> unit = "llvm_remove_initializer"
172 external is_thread_local : llvalue -> bool = "llvm_is_thread_local"
173 external set_thread_local : bool -> llvalue -> unit = "llvm_set_thread_local"
174