Add indirect br support to llvm-c and ocaml.
[oota-llvm.git] / bindings / ocaml / llvm / llvm.mli
index bcdcb2ce1102f8f8117a9416ed7fda300ae25935..c7fa30a96f2dfc8dce1ed860e5cd9224cce2ad14 100644 (file)
@@ -73,6 +73,7 @@ module TypeKind : sig
   | Opaque
   | Vector
   | Metadata
+  | Union
 end
 
 (** The linkage of a global value, accessed with {!linkage} and
@@ -220,6 +221,11 @@ external dispose_context : llcontext -> unit = "llvm_dispose_context"
 (** See the function [llvm::getGlobalContext]. *)
 external global_context : unit -> llcontext = "llvm_global_context"
 
+(** [mdkind_id context name] returns the MDKind ID that corresponds to the
+    name [name] in the context [context].  See the function
+    [llvm::LLVMContext::getMDKindID]. *)
+external mdkind_id : llcontext -> string -> int = "llvm_mdkind_id"
+
 
 (** {6 Modules} *)
 
@@ -381,15 +387,29 @@ external struct_type : llcontext -> lltype array -> lltype
 external packed_struct_type : llcontext -> lltype array -> lltype
                             = "llvm_packed_struct_type"
 
-(** [element_types sty] returns the constituent types of the struct type [sty].
-    See the method [llvm::StructType::getElementType]. *)
-external element_types : lltype -> lltype array = "llvm_element_types"
+(** [struct_element_types sty] returns the constituent types of the struct type
+    [sty]. See the method [llvm::StructType::getElementType]. *)
+external struct_element_types : lltype -> lltype array
+                              = "llvm_struct_element_types"
 
 (** [is_packed sty] returns [true] if the structure type [sty] is packed,
     [false] otherwise. See the method [llvm::StructType::isPacked]. *)
 external is_packed : lltype -> bool = "llvm_is_packed"
 
 
+(** {7 Operations on union types} *)
+
+(** [union_type context tys] returns the union type in the context [context]
+    containing the types in the array [tys]. See the method
+    [llvm::UnionType::get] *)
+external union_type : llcontext -> lltype array -> lltype = "llvm_union_type"
+
+(** [union_element_types uty] returns the constituent types of the union type
+    [uty]. See the method [llvm::UnionType::getElementType]. *)
+external union_element_types : lltype -> lltype array
+                             = "llvm_union_element_types"
+
+
 (** {7 Operations on pointer, vector, and array types} *)
 
 (** [array_type ty n] returns the array type containing [n] elements of type
@@ -510,6 +530,39 @@ external is_null : llvalue -> bool = "llvm_is_null"
 external is_undef : llvalue -> bool = "llvm_is_undef"
 
 
+(** {7 Operations on instructions} *)
+
+(** [has_metadata i] returns whether or not the instruction [i] has any
+    metadata attached to it. See the function
+    [llvm::Instruction::hasMetadata]. *)
+external has_metadata : llvalue -> bool = "llvm_has_metadata"
+
+(** [metadata i kind] optionally returns the metadata associated with the
+    kind [kind] in the instruction [i] See the function
+    [llvm::Instruction::getMetadata]. *)
+external metadata : llvalue -> int -> llvalue option = "llvm_metadata"
+
+(** [set_metadata i kind md] sets the metadata [md] of kind [kind] in the
+    instruction [i]. See the function [llvm::Instruction::setMetadata]. *)
+external set_metadata : llvalue -> int -> llvalue -> unit = "llvm_set_metadata"
+
+(** [clear_metadata i kind] clears the metadata of kind [kind] in the
+    instruction [i]. See the function [llvm::Instruction::setMetadata]. *)
+external clear_metadata : llvalue -> int -> unit = "llvm_clear_metadata"
+
+
+(** {7 Operations on metadata} *)
+
+(** [mdstring c s] returns the MDString of the string [s] in the context [c].
+    See the method [llvm::MDNode::get]. *)
+external mdstring : llcontext -> string -> llvalue = "llvm_mdstring"
+
+(** [mdnode c elts] returns the MDNode containing the values [elts] in the
+    context [c].
+    See the method [llvm::MDNode::get]. *)
+external mdnode : llcontext -> llvalue array -> llvalue = "llvm_mdnode"
+
+
 (** {7 Operations on scalar constants} *)
 
 (** [const_int ty i] returns the integer constant of type [ty] and value [i].
@@ -577,6 +630,10 @@ external const_packed_struct : llcontext -> llvalue array -> llvalue
     values [elts]. See the method [llvm::ConstantVector::get]. *)
 external const_vector : llvalue array -> llvalue = "llvm_const_vector"
 
+(** [const_union ty v] returns the union constant of type [union_type tys] and
+    containing the value [v]. See the method [llvm::ConstantUnion::get]. *)
+external const_union : lltype -> llvalue -> llvalue = "LLVMConstUnion"
+
 
 (** {7 Constant expressions} *)
 
@@ -596,6 +653,16 @@ external size_of : lltype -> llvalue = "LLVMSizeOf"
     See the method [llvm::ConstantExpr::getNeg]. *)
 external const_neg : llvalue -> llvalue = "LLVMConstNeg"
 
+(** [const_nsw_neg c] returns the arithmetic negation of the constant [c] with
+    no signed wrapping. The result is undefined if the negation overflows.
+    See the method [llvm::ConstantExpr::getNSWNeg]. *)
+external const_nsw_neg : llvalue -> llvalue = "LLVMConstNSWNeg"
+
+(** [const_nuw_neg c] returns the arithmetic negation of the constant [c] with
+    no unsigned wrapping. The result is undefined if the negation overflows.
+    See the method [llvm::ConstantExpr::getNUWNeg]. *)
+external const_nuw_neg : llvalue -> llvalue = "LLVMConstNUWNeg"
+
 (** [const_fneg c] returns the arithmetic negation of the constant float [c].
     See the method [llvm::ConstantExpr::getFNeg]. *)
 external const_fneg : llvalue -> llvalue = "LLVMConstFNeg"
@@ -613,6 +680,11 @@ external const_add : llvalue -> llvalue -> llvalue = "LLVMConstAdd"
     See the method [llvm::ConstantExpr::getNSWAdd]. *)
 external const_nsw_add : llvalue -> llvalue -> llvalue = "LLVMConstNSWAdd"
 
+(** [const_nuw_add c1 c2] returns the constant sum of two constants with no
+    unsigned wrapping. The result is undefined if the sum overflows.
+    See the method [llvm::ConstantExpr::getNSWAdd]. *)
+external const_nuw_add : llvalue -> llvalue -> llvalue = "LLVMConstNUWAdd"
+
 (** [const_fadd c1 c2] returns the constant sum of two constant floats.
     See the method [llvm::ConstantExpr::getFAdd]. *)
 external const_fadd : llvalue -> llvalue -> llvalue = "LLVMConstFAdd"
@@ -621,6 +693,16 @@ external const_fadd : llvalue -> llvalue -> llvalue = "LLVMConstFAdd"
     constants. See the method [llvm::ConstantExpr::getSub]. *)
 external const_sub : llvalue -> llvalue -> llvalue = "LLVMConstSub"
 
+(** [const_nsw_sub c1 c2] returns the constant difference of two constants with
+    no signed wrapping. The result is undefined if the sum overflows.
+    See the method [llvm::ConstantExpr::getNSWSub]. *)
+external const_nsw_sub : llvalue -> llvalue -> llvalue = "LLVMConstNSWSub"
+
+(** [const_nuw_sub c1 c2] returns the constant difference of two constants with
+    no unsigned wrapping. The result is undefined if the sum overflows.
+    See the method [llvm::ConstantExpr::getNSWSub]. *)
+external const_nuw_sub : llvalue -> llvalue -> llvalue = "LLVMConstNUWSub"
+
 (** [const_fsub c1 c2] returns the constant difference, [c1 - c2], of two
     constant floats. See the method [llvm::ConstantExpr::getFSub]. *)
 external const_fsub : llvalue -> llvalue -> llvalue = "LLVMConstFSub"
@@ -629,6 +711,16 @@ external const_fsub : llvalue -> llvalue -> llvalue = "LLVMConstFSub"
     See the method [llvm::ConstantExpr::getMul]. *)
 external const_mul : llvalue -> llvalue -> llvalue = "LLVMConstMul"
 
+(** [const_nsw_mul c1 c2] returns the constant product of two constants with
+    no signed wrapping. The result is undefined if the sum overflows.
+    See the method [llvm::ConstantExpr::getNSWMul]. *)
+external const_nsw_mul : llvalue -> llvalue -> llvalue = "LLVMConstNSWMul"
+
+(** [const_nuw_mul c1 c2] returns the constant product of two constants with
+    no unsigned wrapping. The result is undefined if the sum overflows.
+    See the method [llvm::ConstantExpr::getNSWMul]. *)
+external const_nuw_mul : llvalue -> llvalue -> llvalue = "LLVMConstNUWMul"
+
 (** [const_fmul c1 c2] returns the constant product of two constants floats.
     See the method [llvm::ConstantExpr::getFMul]. *)
 external const_fmul : llvalue -> llvalue -> llvalue = "LLVMConstFMul"
@@ -858,6 +950,10 @@ external const_extractvalue : llvalue -> int array -> llvalue
 external const_insertvalue : llvalue -> llvalue -> int array -> llvalue
                            = "llvm_const_insertvalue"
 
+(** [block_address f bb] returns the address of the basic block [bb] in the
+    function [f]. See the method [llvm::BasicBlock::get]. *)
+external block_address : llvalue -> llbasicblock -> llvalue = "LLVMBlockAddress"
+
 
 (** {7 Operations on global variables, functions, and aliases (globals)} *)
 
@@ -1397,6 +1493,30 @@ external insertion_block : llbuilder -> llbasicblock = "llvm_insertion_block"
 external insert_into_builder : llvalue -> string -> llbuilder -> unit
                              = "llvm_insert_into_builder"
 
+(** {7 Metadata} *)
+
+(** [set_current_debug_location b md] sets the current debug location [md] in
+    the builder [b].
+    See the method [llvm::IRBuilder::SetDebugLocation]. *)
+external set_current_debug_location : llbuilder -> llvalue -> unit
+                                    = "llvm_set_current_debug_location"
+
+(** [clear_current_debug_location b] clears the current debug location in the
+    builder [b]. *)
+external clear_current_debug_location : llbuilder -> unit
+                                      = "llvm_clear_current_debug_location"
+
+(** [current_debug_location b] returns the current debug location, or None
+    if none is currently set.
+    See the method [llvm::IRBuilder::GetDebugLocation]. *)
+external current_debug_location : llbuilder -> llvalue option
+                                = "llvm_current_debug_location"
+
+(** [set_inst_debug_location b i] sets the current debug location of the builder
+    [b] to the instruction [i].
+    See the method [llvm::IRBuilder::SetInstDebugLocation]. *)
+external set_inst_debug_location : llbuilder -> llvalue -> unit
+                                 = "llvm_set_inst_debug_location"
 
 (** {7 Terminators} *)
 
@@ -1420,13 +1540,13 @@ external build_aggregate_ret : llvalue array -> llbuilder -> llvalue
                              = "llvm_build_aggregate_ret"
 
 (** [build_br bb b] creates a
-    [b %bb]
+    [br %bb]
     instruction at the position specified by the instruction builder [b].
     See the method [llvm::LLVMBuilder::CreateBr]. *)
 external build_br : llbasicblock -> llbuilder -> llvalue = "llvm_build_br"
 
 (** [build_cond_br cond tbb fbb b] creates a
-    [b %cond, %tbb, %fbb]
+    [br %cond, %tbb, %fbb]
     instruction at the position specified by the instruction builder [b].
     See the method [llvm::LLVMBuilder::CreateCondBr]. *)
 external build_cond_br : llvalue -> llbasicblock -> llbasicblock -> llbuilder ->
@@ -1446,6 +1566,20 @@ external build_switch : llvalue -> llbasicblock -> int -> llbuilder -> llvalue
 external add_case : llvalue -> llvalue -> llbasicblock -> unit
                   = "llvm_add_case"
 
+(** [build_indirect_br addr count b] creates a
+    [indirectbr %addr]
+    instruction at the position specified by the instruction builder [b] with
+    space reserved for [count] destinations.
+    See the method [llvm::LLVMBuilder::CreateIndirectBr]. *)
+external build_indirect_br : llvalue -> int -> llbuilder -> llvalue
+                           = "llvm_build_indirect_br"
+
+(** [add_destination br bb] adds the basic block [bb] as a possible branch
+    location for the indirectbr instruction [br].
+    See the method [llvm::IndirectBrInst::addDestination]. **)
+external add_destination : llvalue -> llbasicblock -> unit
+                         = "llvm_add_destination"
+
 (** [build_invoke fn args tobb unwindbb name b] creates an
     [%name = invoke %fn(args) to %tobb unwind %unwindbb]
     instruction at the position specified by the instruction builder [b].
@@ -1476,13 +1610,20 @@ external build_unreachable : llbuilder -> llvalue = "llvm_build_unreachable"
 external build_add : llvalue -> llvalue -> string -> llbuilder -> llvalue
                    = "llvm_build_add"
 
-(** [build_nswadd x y name b] creates a
+(** [build_nsw_add x y name b] creates a
     [%name = nsw add %x, %y]
     instruction at the position specified by the instruction builder [b].
     See the method [llvm::LLVMBuilder::CreateNSWAdd]. *)
 external build_nsw_add : llvalue -> llvalue -> string -> llbuilder -> llvalue
                       = "llvm_build_nsw_add"
 
+(** [build_nuw_add x y name b] creates a
+    [%name = nuw add %x, %y]
+    instruction at the position specified by the instruction builder [b].
+    See the method [llvm::LLVMBuilder::CreateNUWAdd]. *)
+external build_nuw_add : llvalue -> llvalue -> string -> llbuilder -> llvalue
+                      = "llvm_build_nuw_add"
+
 (** [build_fadd x y name b] creates a
     [%name = fadd %x, %y]
     instruction at the position specified by the instruction builder [b].
@@ -1497,6 +1638,20 @@ external build_fadd : llvalue -> llvalue -> string -> llbuilder -> llvalue
 external build_sub : llvalue -> llvalue -> string -> llbuilder -> llvalue
                    = "llvm_build_sub"
 
+(** [build_nsw_sub x y name b] creates a
+    [%name = nsw sub %x, %y]
+    instruction at the position specified by the instruction builder [b].
+    See the method [llvm::LLVMBuilder::CreateNSWSub]. *)
+external build_nsw_sub : llvalue -> llvalue -> string -> llbuilder -> llvalue
+                       = "llvm_build_nsw_sub"
+
+(** [build_nuw_sub x y name b] creates a
+    [%name = nuw sub %x, %y]
+    instruction at the position specified by the instruction builder [b].
+    See the method [llvm::LLVMBuilder::CreateNUWSub]. *)
+external build_nuw_sub : llvalue -> llvalue -> string -> llbuilder -> llvalue
+                       = "llvm_build_nuw_sub"
+
 (** [build_fsub x y name b] creates a
     [%name = fsub %x, %y]
     instruction at the position specified by the instruction builder [b].
@@ -1511,6 +1666,20 @@ external build_fsub : llvalue -> llvalue -> string -> llbuilder -> llvalue
 external build_mul : llvalue -> llvalue -> string -> llbuilder -> llvalue
                    = "llvm_build_mul"
 
+(** [build_nsw_mul x y name b] creates a
+    [%name = nsw mul %x, %y]
+    instruction at the position specified by the instruction builder [b].
+    See the method [llvm::LLVMBuilder::CreateNSWMul]. *)
+external build_nsw_mul : llvalue -> llvalue -> string -> llbuilder -> llvalue
+                       = "llvm_build_nsw_mul"
+
+(** [build_nuw_mul x y name b] creates a
+    [%name = nuw mul %x, %y]
+    instruction at the position specified by the instruction builder [b].
+    See the method [llvm::LLVMBuilder::CreateNUWMul]. *)
+external build_nuw_mul : llvalue -> llvalue -> string -> llbuilder -> llvalue
+                       = "llvm_build_nuw_mul"
+
 (** [build_fmul x y name b] creates a
     [%name = fmul %x, %y]
     instruction at the position specified by the instruction builder [b].
@@ -1617,6 +1786,30 @@ external build_xor : llvalue -> llvalue -> string -> llbuilder -> llvalue
 external build_neg : llvalue -> string -> llbuilder -> llvalue
                    = "llvm_build_neg"
 
+(** [build_nsw_neg x name b] creates a
+    [%name = nsw sub 0, %x]
+    instruction at the position specified by the instruction builder [b].
+    [-0.0] is used for floating point types to compute the correct sign.
+    See the method [llvm::LLVMBuilder::CreateNeg]. *)
+external build_nsw_neg : llvalue -> string -> llbuilder -> llvalue
+                       = "llvm_build_nsw_neg"
+
+(** [build_nuw_neg x name b] creates a
+    [%name = nuw sub 0, %x]
+    instruction at the position specified by the instruction builder [b].
+    [-0.0] is used for floating point types to compute the correct sign.
+    See the method [llvm::LLVMBuilder::CreateNeg]. *)
+external build_nuw_neg : llvalue -> string -> llbuilder -> llvalue
+                       = "llvm_build_nuw_neg"
+
+(** [build_fneg x name b] creates a
+    [%name = fsub 0, %x]
+    instruction at the position specified by the instruction builder [b].
+    [-0.0] is used for floating point types to compute the correct sign.
+    See the method [llvm::LLVMBuilder::CreateFNeg]. *)
+external build_fneg : llvalue -> string -> llbuilder -> llvalue
+                    = "llvm_build_fneg"
+
 (** [build_xor x name b] creates a
     [%name = xor %x, -1]
     instruction at the position specified by the instruction builder [b].
@@ -1628,20 +1821,6 @@ external build_not : llvalue -> string -> llbuilder -> llvalue
 
 (** {7 Memory} *)
 
-(** [build_malloc ty name b] creates a
-    [%name = malloc %ty]
-    instruction at the position specified by the instruction builder [b].
-    See the method [llvm::LLVMBuilder::CreateAlloca]. *)
-external build_malloc : lltype -> string -> llbuilder -> llvalue
-                      = "llvm_build_malloc"
-
-(** [build_array_malloc ty n name b] creates a
-    [%name = malloc %ty, %n]
-    instruction at the position specified by the instruction builder [b].
-    See the method [llvm::LLVMBuilder::CreateMalloc]. *)
-external build_array_malloc : lltype -> llvalue -> string -> llbuilder ->
-                              llvalue = "llvm_build_array_malloc"
-
 (** [build_alloca ty name b] creates a
     [%name = alloca %ty]
     instruction at the position specified by the instruction builder [b].
@@ -1656,12 +1835,6 @@ external build_alloca : lltype -> string -> llbuilder -> llvalue
 external build_array_alloca : lltype -> llvalue -> string -> llbuilder ->
                               llvalue = "llvm_build_array_alloca"
 
-(** [build_free v b] creates a
-    [free %v]
-    instruction at the position specified by the instruction builder [b].
-    See the method [llvm::LLVMBuilder::CreateFree]. *)
-external build_free : llvalue -> llbuilder -> llvalue = "llvm_build_free"
-
 (** [build_load v name b] creates a
     [%name = load %v]
     instruction at the position specified by the instruction builder [b].