Tests of the ocaml (and thus C) bindings for constants.
[oota-llvm.git] / bindings / ocaml / llvm / llvm.ml
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
72 external classify_type : lltype -> type_kind = "llvm_classify_type"
73 external refine_abstract_type : lltype -> lltype -> unit
74                               = "llvm_refine_abstract_type"
75
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"
82
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 ()
88
89 external make_integer_type : int -> lltype = "llvm_make_integer_type"
90 external integer_bitwidth : lltype -> int = "llvm_integer_bitwidth"
91
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"
98
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 ()
104
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"
112
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"
118
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"
123
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"
127
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"
132
133 let void_type = _void_type ()
134 let label_type = _label_type ()
135
136
137 (*===-- Values ------------------------------------------------------------===*)
138
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"
142
143 (*--... Operations on constants of (mostly) any type .......................--*)
144 external is_constant : llvalue -> bool = "llvm_is_constant"
145 external make_null : lltype -> llvalue = "llvm_make_null"
146 external make_all_ones : (*int|vec*)lltype -> llvalue = "llvm_make_all_ones"
147 external make_undef : lltype -> llvalue = "llvm_make_undef"
148 external is_null : llvalue -> bool = "llvm_is_null"
149 external is_undef : llvalue -> bool = "llvm_is_undef"
150
151 (*--... Operations on scalar constants .....................................--*)
152 external make_int_constant : lltype -> int -> bool -> llvalue
153                            = "llvm_make_int_constant"
154 external make_int64_constant : lltype -> Int64.t -> bool -> llvalue
155                              = "llvm_make_int64_constant"
156 external make_real_constant : lltype -> float -> llvalue
157                             = "llvm_make_real_constant"
158
159 (*--... Operations on composite constants ..................................--*)
160 external make_string_constant : string -> bool -> llvalue
161                               = "llvm_make_string_constant"
162 external make_array_constant : lltype -> llvalue array -> llvalue
163                              = "llvm_make_array_constant"
164 external make_struct_constant : llvalue array -> bool -> llvalue
165                               = "llvm_make_struct_constant"
166 external make_vector_constant : llvalue array -> llvalue
167                               = "llvm_make_vector_constant"
168
169 (*--... Operations on global variables, functions, and aliases (globals) ...--*)
170 external is_declaration : llvalue -> bool = "llvm_is_declaration"
171 external linkage : llvalue -> linkage = "llvm_linkage"
172 external set_linkage : linkage -> llvalue -> unit = "llvm_set_linkage"
173 external section : llvalue -> string = "llvm_section"
174 external set_section : string -> llvalue -> unit = "llvm_set_section"
175 external visibility : llvalue -> visibility = "llvm_visibility"
176 external set_visibility : visibility -> llvalue -> unit = "llvm_set_visibility"
177 external alignment : llvalue -> int = "llvm_alignment"
178 external set_alignment : int -> llvalue -> unit = "llvm_set_alignment"
179
180 (*--... Operations on global variables .....................................--*)
181 external declare_global : lltype -> string -> llmodule -> llvalue
182                         = "llvm_declare_global"
183 external define_global : string -> llvalue -> llmodule -> llvalue
184                        = "llvm_define_global"
185 external delete_global : llvalue -> unit = "llvm_delete_global"
186 external global_initializer : llvalue -> llvalue = "llvm_global_initializer"
187 external set_initializer : llvalue -> llvalue -> unit = "llvm_set_initializer"
188 external remove_initializer : llvalue -> unit = "llvm_remove_initializer"
189 external is_thread_local : llvalue -> bool = "llvm_is_thread_local"
190 external set_thread_local : bool -> llvalue -> unit = "llvm_set_thread_local"
191
192
193 (*===-- Non-Externs -------------------------------------------------------===*)
194 (* These functions are built using the externals, so must be declared late.   *)
195
196 let concat2 sep arr =
197   let s = ref "" in
198   if 0 < Array.length arr then begin
199     s := !s ^ arr.(0);
200     for i = 1 to (Array.length arr) - 1 do
201       s := !s ^ sep ^ arr.(i)
202     done
203   end;
204   !s
205
206 let rec string_of_lltype ty =
207   match classify_type ty with
208     Integer_type -> "i" ^ string_of_int (integer_bitwidth ty)
209   | Pointer_type -> (string_of_lltype (element_type ty)) ^ "*"
210   | Struct_type ->
211       let s = "{ " ^ (concat2 ", " (
212                 Array.map string_of_lltype (element_types ty)
213               )) ^ " }" in
214       if is_packed ty
215         then "<" ^ s ^ ">"
216         else s
217   | Array_type -> "["   ^ (string_of_int (array_length ty)) ^
218                   " x " ^ (string_of_lltype (element_type ty)) ^ "]"
219   | Vector_type -> "<"   ^ (string_of_int (vector_size ty)) ^
220                    " x " ^ (string_of_lltype (element_type ty)) ^ ">"
221   | Opaque_type -> "opaque"
222   | Function_type -> string_of_lltype (return_type ty) ^
223                      " (" ^ (concat2 ", " (
224                        Array.map string_of_lltype (param_types ty)
225                      )) ^ ")"
226   | Label_type -> "label"
227   | Ppc_fp128_type -> "ppc_fp128"
228   | Fp128_type -> "fp128"
229   | X86fp80_type -> "x86_fp80"
230   | Double_type -> "double"
231   | Float_type -> "float"
232   | Void_type -> "void"