Add support for global variables in an address space for llvm-c and ocaml.
[oota-llvm.git] / bindings / ocaml / llvm / llvm.ml
index 74fd1f1e170aeb7e8badac8e4ea5680c89ce88ca..16674274057f20ee58cbe886cec908efc020b409 100644 (file)
@@ -35,6 +35,7 @@ module TypeKind = struct
   | Opaque
   | Vector
   | Metadata
+  | Union
 end
 
 module Linkage = struct
@@ -42,13 +43,18 @@ module Linkage = struct
   | External
   | Available_externally
   | Link_once
+  | Link_once_odr
   | Weak
+  | Weak_odr
   | Appending
   | Internal
+  | Private
   | Dllimport
   | Dllexport
   | External_weak
   | Ghost
+  | Common
+  | Linker_private
 end
 
 module Visibility = struct
@@ -79,6 +85,16 @@ module Attribute = struct
   | Nest
   | Readnone
   | Readonly
+  | Noinline
+  | Alwaysinline
+  | Optsize
+  | Ssp
+  | Sspreq
+  | Nocapture
+  | Noredzone
+  | Noimplicitfloat
+  | Naked
+  | Inlinehint
 end
 
 module Icmp = struct
@@ -130,8 +146,9 @@ type ('a, 'b) llrev_pos =
 
 (*===-- Contexts ----------------------------------------------------------===*)
 external create_context : unit -> llcontext = "llvm_create_context"
-external dispose_context : unit -> llcontext = "llvm_dispose_context"
+external dispose_context : llcontext -> unit = "llvm_dispose_context"
 external global_context : unit -> llcontext = "llvm_global_context"
+external mdkind_id : llcontext -> string -> int = "llvm_mdkind_id"
 
 (*===-- Modules -----------------------------------------------------------===*)
 external create_module : llcontext -> string -> llmodule = "llvm_create_module"
@@ -155,33 +172,21 @@ external classify_type : lltype -> TypeKind.t = "llvm_classify_type"
 external type_context : lltype -> llcontext = "llvm_type_context"
 
 (*--... Operations on integer types ........................................--*)
-external _i1_type : unit -> lltype = "llvm_i1_type"
-external _i8_type : unit -> lltype = "llvm_i8_type"
-external _i16_type : unit -> lltype = "llvm_i16_type"
-external _i32_type : unit -> lltype = "llvm_i32_type"
-external _i64_type : unit -> lltype = "llvm_i64_type"
-
-let i1_type = _i1_type ()
-let i8_type = _i8_type ()
-let i16_type = _i16_type ()
-let i32_type = _i32_type ()
-let i64_type = _i64_type ()
-
-external integer_type : int -> lltype = "llvm_integer_type"
+external i1_type : llcontext -> lltype = "llvm_i1_type"
+external i8_type : llcontext -> lltype = "llvm_i8_type"
+external i16_type : llcontext -> lltype = "llvm_i16_type"
+external i32_type : llcontext -> lltype = "llvm_i32_type"
+external i64_type : llcontext -> lltype = "llvm_i64_type"
+
+external integer_type : llcontext -> int -> lltype = "llvm_integer_type"
 external integer_bitwidth : lltype -> int = "llvm_integer_bitwidth"
 
 (*--... Operations on real types ...........................................--*)
-external _float_type : unit -> lltype = "llvm_float_type"
-external _double_type : unit -> lltype = "llvm_double_type"
-external _x86fp80_type : unit -> lltype = "llvm_x86fp80_type"
-external _fp128_type : unit -> lltype = "llvm_fp128_type"
-external _ppc_fp128_type : unit -> lltype = "llvm_ppc_fp128_type"
-
-let float_type = _float_type ()
-let double_type = _double_type ()
-let x86fp80_type = _x86fp80_type ()
-let fp128_type = _fp128_type ()
-let ppc_fp128_type = _ppc_fp128_type ()
+external float_type : llcontext -> lltype = "llvm_float_type"
+external double_type : llcontext -> lltype = "llvm_double_type"
+external x86fp80_type : llcontext -> lltype = "llvm_x86fp80_type"
+external fp128_type : llcontext -> lltype = "llvm_fp128_type"
+external ppc_fp128_type : llcontext -> lltype = "llvm_ppc_fp128_type"
 
 (*--... Operations on function types .......................................--*)
 external function_type : lltype -> lltype array -> lltype = "llvm_function_type"
@@ -195,9 +200,15 @@ external param_types : lltype -> lltype array = "llvm_param_types"
 external struct_type : llcontext -> lltype array -> lltype = "llvm_struct_type"
 external packed_struct_type : llcontext -> lltype array -> lltype
                             = "llvm_packed_struct_type"
-external element_types : lltype -> lltype array = "llvm_element_types"
+external struct_element_types : lltype -> lltype array
+                              = "llvm_struct_element_types"
 external is_packed : lltype -> bool = "llvm_is_packed"
 
+(*--... Operations on union types ..........................................--*)
+external union_type : llcontext -> lltype array -> lltype = "llvm_union_type"
+external union_element_types : lltype -> lltype array
+                             = "llvm_union_element_types"
+
 (*--... Operations on pointer, vector, and array types .....................--*)
 external array_type : lltype -> int -> lltype = "llvm_array_type"
 external pointer_type : lltype -> lltype = "llvm_pointer_type"
@@ -211,12 +222,9 @@ external address_space : lltype -> int = "llvm_address_space"
 external vector_size : lltype -> int = "llvm_vector_size"
 
 (*--... Operations on other types ..........................................--*)
-external opaque_type : unit -> lltype = "llvm_opaque_type"
-external _void_type : unit -> lltype = "llvm_void_type"
-external _label_type : unit -> lltype = "llvm_label_type"
-
-let void_type = _void_type ()
-let label_type = _label_type ()
+external opaque_type : llcontext -> lltype = "llvm_opaque_type"
+external void_type : llcontext -> lltype = "llvm_void_type"
+external label_type : llcontext -> lltype = "llvm_label_type"
 
 (*--... Operations on type handles .........................................--*)
 external handle_to_type : lltype -> lltypehandle = "llvm_handle_to_type"
@@ -238,6 +246,16 @@ external undef : lltype -> llvalue = "LLVMGetUndef"
 external is_null : llvalue -> bool = "llvm_is_null"
 external is_undef : llvalue -> bool = "llvm_is_undef"
 
+(*--... Operations on instructions .........................................--*)
+external has_metadata : llvalue -> bool = "llvm_has_metadata"
+external metadata : llvalue -> int -> llvalue option = "llvm_metadata"
+external set_metadata : llvalue -> int -> llvalue -> unit = "llvm_set_metadata"
+external clear_metadata : llvalue -> int -> unit = "llvm_clear_metadata"
+
+(*--... Operations on metadata .......,.....................................--*)
+external mdstring : llcontext -> string -> llvalue = "llvm_mdstring"
+external mdnode : llcontext -> llvalue array -> llvalue = "llvm_mdnode"
+
 (*--... Operations on scalar constants .....................................--*)
 external const_int : lltype -> int -> llvalue = "llvm_const_int"
 external const_of_int64 : lltype -> Int64.t -> bool -> llvalue
@@ -249,27 +267,35 @@ external const_float_of_string : lltype -> string -> llvalue
                                = "llvm_const_float_of_string"
 
 (*--... Operations on composite constants ..................................--*)
-external const_string : string -> llvalue = "llvm_const_string"
-external const_stringz : string -> llvalue = "llvm_const_stringz"
+external const_string : llcontext -> string -> llvalue = "llvm_const_string"
+external const_stringz : llcontext -> string -> llvalue = "llvm_const_stringz"
 external const_array : lltype -> llvalue array -> llvalue = "llvm_const_array"
 external const_struct : llcontext -> llvalue array -> llvalue
                       = "llvm_const_struct"
 external const_packed_struct : llcontext -> llvalue array -> llvalue
                              = "llvm_const_packed_struct"
 external const_vector : llvalue array -> llvalue = "llvm_const_vector"
+external const_union : lltype -> llvalue -> llvalue = "LLVMConstUnion"
 
 (*--... Constant expressions ...............................................--*)
 external align_of : lltype -> llvalue = "LLVMAlignOf"
 external size_of : lltype -> llvalue = "LLVMSizeOf"
 external const_neg : llvalue -> llvalue = "LLVMConstNeg"
+external const_nsw_neg : llvalue -> llvalue = "LLVMConstNSWNeg"
+external const_nuw_neg : llvalue -> llvalue = "LLVMConstNUWNeg"
 external const_fneg : llvalue -> llvalue = "LLVMConstFNeg"
 external const_not : llvalue -> llvalue = "LLVMConstNot"
 external const_add : llvalue -> llvalue -> llvalue = "LLVMConstAdd"
 external const_nsw_add : llvalue -> llvalue -> llvalue = "LLVMConstNSWAdd"
+external const_nuw_add : llvalue -> llvalue -> llvalue = "LLVMConstNUWAdd"
 external const_fadd : llvalue -> llvalue -> llvalue = "LLVMConstFAdd"
 external const_sub : llvalue -> llvalue -> llvalue = "LLVMConstSub"
+external const_nsw_sub : llvalue -> llvalue -> llvalue = "LLVMConstNSWSub"
+external const_nuw_sub : llvalue -> llvalue -> llvalue = "LLVMConstNUWSub"
 external const_fsub : llvalue -> llvalue -> llvalue = "LLVMConstFSub"
 external const_mul : llvalue -> llvalue -> llvalue = "LLVMConstMul"
+external const_nsw_mul : llvalue -> llvalue -> llvalue = "LLVMConstNSWMul"
+external const_nuw_mul : llvalue -> llvalue -> llvalue = "LLVMConstNUWMul"
 external const_fmul : llvalue -> llvalue -> llvalue = "LLVMConstFMul"
 external const_udiv : llvalue -> llvalue -> llvalue = "LLVMConstUDiv"
 external const_sdiv : llvalue -> llvalue -> llvalue = "LLVMConstSDiv"
@@ -325,6 +351,7 @@ external const_extractvalue : llvalue -> int array -> llvalue
                             = "llvm_const_extractvalue"
 external const_insertvalue : llvalue -> llvalue -> int array -> llvalue
                            = "llvm_const_insertvalue"
+external block_address : llvalue -> llbasicblock -> llvalue = "LLVMBlockAddress"
 
 (*--... Operations on global variables, functions, and aliases (globals) ...--*)
 external global_parent : llvalue -> llmodule = "LLVMGetGlobalParent"
@@ -344,8 +371,14 @@ external set_global_constant : bool -> llvalue -> unit
 (*--... Operations on global variables .....................................--*)
 external declare_global : lltype -> string -> llmodule -> llvalue
                         = "llvm_declare_global"
+external declare_qualified_global : lltype -> string -> int -> llmodule ->
+                                    llvalue
+                                  = "llvm_declare_qualified_global"
 external define_global : string -> llvalue -> llmodule -> llvalue
                        = "llvm_define_global"
+external define_qualified_global : string -> llvalue -> int -> llmodule ->
+                                   llvalue
+                                 = "llvm_define_qualified_global"
 external lookup_global : string -> llmodule -> llvalue option
                        = "llvm_lookup_global"
 external delete_global : llvalue -> unit = "llvm_delete_global"
@@ -535,8 +568,9 @@ external block_parent : llbasicblock -> llvalue = "LLVMGetBasicBlockParent"
 external basic_blocks : llvalue -> llbasicblock array = "llvm_basic_blocks"
 external entry_block : llvalue -> llbasicblock = "LLVMGetEntryBasicBlock"
 external delete_block : llbasicblock -> unit = "llvm_delete_block"
-external append_block : string -> llvalue -> llbasicblock = "llvm_append_block"
-external insert_block : string -> llbasicblock -> llbasicblock
+external append_block : llcontext -> string -> llvalue -> llbasicblock
+                      = "llvm_append_block"
+external insert_block : llcontext -> string -> llbasicblock -> llbasicblock
                       = "llvm_insert_block"
 external block_begin : llvalue -> (llvalue, llbasicblock) llpos
                      = "llvm_block_begin"
@@ -679,6 +713,17 @@ let position_before i = position_builder (Before i)
 let position_at_end bb = position_builder (At_end bb)
 
 
+(*--... Metadata ...........................................................--*)
+external set_current_debug_location : llbuilder -> llvalue -> unit
+                                    = "llvm_set_current_debug_location"
+external clear_current_debug_location : llbuilder -> unit
+                                      = "llvm_clear_current_debug_location"
+external current_debug_location : llbuilder -> llvalue option
+                                    = "llvm_current_debug_location"
+external set_inst_debug_location : llbuilder -> llvalue -> unit
+                                 = "llvm_set_inst_debug_location"
+
+
 (*--... Terminators ........................................................--*)
 external build_ret_void : llbuilder -> llvalue = "llvm_build_ret_void"
 external build_ret : llvalue -> llbuilder -> llvalue = "llvm_build_ret"
@@ -691,6 +736,10 @@ external build_switch : llvalue -> llbasicblock -> int -> llbuilder -> llvalue
                       = "llvm_build_switch"
 external add_case : llvalue -> llvalue -> llbasicblock -> unit
                   = "llvm_add_case"
+external build_indirect_br : llvalue -> int -> llbuilder -> llvalue
+                           = "llvm_build_indirect_br"
+external add_destination : llvalue -> llbasicblock -> unit
+                         = "llvm_add_destination"
 external build_invoke : llvalue -> llvalue array -> llbasicblock ->
                         llbasicblock -> string -> llbuilder -> llvalue
                       = "llvm_build_invoke_bc" "llvm_build_invoke_nat"
@@ -702,14 +751,24 @@ external build_add : llvalue -> llvalue -> string -> llbuilder -> llvalue
                    = "llvm_build_add"
 external build_nsw_add : llvalue -> llvalue -> string -> llbuilder -> llvalue
                        = "llvm_build_nsw_add"
+external build_nuw_add : llvalue -> llvalue -> string -> llbuilder -> llvalue
+                       = "llvm_build_nuw_add"
 external build_fadd : llvalue -> llvalue -> string -> llbuilder -> llvalue
                     = "llvm_build_fadd"
 external build_sub : llvalue -> llvalue -> string -> llbuilder -> llvalue
                    = "llvm_build_sub"
+external build_nsw_sub : llvalue -> llvalue -> string -> llbuilder -> llvalue
+                       = "llvm_build_nsw_sub"
+external build_nuw_sub : llvalue -> llvalue -> string -> llbuilder -> llvalue
+                       = "llvm_build_nuw_sub"
 external build_fsub : llvalue -> llvalue -> string -> llbuilder -> llvalue
                     = "llvm_build_fsub"
 external build_mul : llvalue -> llvalue -> string -> llbuilder -> llvalue
                    = "llvm_build_mul"
+external build_nsw_mul : llvalue -> llvalue -> string -> llbuilder -> llvalue
+                       = "llvm_build_nsw_mul"
+external build_nuw_mul : llvalue -> llvalue -> string -> llbuilder -> llvalue
+                       = "llvm_build_nuw_mul"
 external build_fmul : llvalue -> llvalue -> string -> llbuilder -> llvalue
                     = "llvm_build_fmul"
 external build_udiv : llvalue -> llvalue -> string -> llbuilder -> llvalue
@@ -740,19 +799,20 @@ external build_xor : llvalue -> llvalue -> string -> llbuilder -> llvalue
                    = "llvm_build_xor"
 external build_neg : llvalue -> string -> llbuilder -> llvalue
                    = "llvm_build_neg"
+external build_nsw_neg : llvalue -> string -> llbuilder -> llvalue
+                       = "llvm_build_nsw_neg"
+external build_nuw_neg : llvalue -> string -> llbuilder -> llvalue
+                       = "llvm_build_nuw_neg"
+external build_fneg : llvalue -> string -> llbuilder -> llvalue
+                    = "llvm_build_fneg"
 external build_not : llvalue -> string -> llbuilder -> llvalue
                    = "llvm_build_not"
 
 (*--... Memory .............................................................--*)
-external build_malloc : lltype -> string -> llbuilder -> llvalue
-                      = "llvm_build_malloc"
-external build_array_malloc : lltype -> llvalue -> string -> llbuilder ->
-                              llvalue = "llvm_build_array_malloc"
 external build_alloca : lltype -> string -> llbuilder -> llvalue
                       = "llvm_build_alloca"
 external build_array_alloca : lltype -> llvalue -> string -> llbuilder ->
                               llvalue = "llvm_build_array_alloca"
-external build_free : llvalue -> llbuilder -> llvalue = "llvm_build_free"
 external build_load : llvalue -> string -> llbuilder -> llvalue
                     = "llvm_build_load"
 external build_store : llvalue -> llvalue -> llbuilder -> llvalue
@@ -847,7 +907,7 @@ module ModuleProvider = struct
                   = "LLVMCreateModuleProviderForExistingModule"
   external dispose : llmoduleprovider -> unit = "llvm_dispose_module_provider"
 end
-  
+
 
 (*===-- Memory buffers ----------------------------------------------------===*)
 
@@ -896,11 +956,14 @@ let rec string_of_lltype ty =
   | TypeKind.Pointer -> (string_of_lltype (element_type ty)) ^ "*"
   | TypeKind.Struct ->
       let s = "{ " ^ (concat2 ", " (
-                Array.map string_of_lltype (element_types ty)
+                Array.map string_of_lltype (struct_element_types ty)
               )) ^ " }" in
       if is_packed ty
         then "<" ^ s ^ ">"
         else s
+  | TypeKind.Union -> "union { " ^ (concat2 ", " (
+                        Array.map string_of_lltype (union_element_types ty)
+                      )) ^ " }"
   | TypeKind.Array -> "["   ^ (string_of_int (array_length ty)) ^
                       " x " ^ (string_of_lltype (element_type ty)) ^ "]"
   | TypeKind.Vector -> "<"   ^ (string_of_int (vector_size ty)) ^