[OCaml] Add Llvm.instr_clone.
[oota-llvm.git] / bindings / ocaml / llvm / llvm.mli
index 59a89db5f489bb40b0908958338c53b0d286b068..54d070fb04316fe076c1c4fd5e37c4d8700c517b 100644 (file)
@@ -157,38 +157,40 @@ end
     See the [llvm::ICmpInst::Predicate] enumeration. *)
 module Icmp : sig
   type t =
-  | Eq
-  | Ne
-  | Ugt
-  | Uge
-  | Ult
-  | Ule
-  | Sgt
-  | Sge
-  | Slt
-  | Sle
+  | Eq  (* Equal *)
+  | Ne  (* Not equal *)
+  | Ugt (* Unsigned greater than *)
+  | Uge (* Unsigned greater or equal *)
+  | Ult (* Unsigned less than *)
+  | Ule (* Unsigned less or equal *)
+  | Sgt (* Signed greater than *)
+  | Sge (* Signed greater or equal *)
+  | Slt (* Signed less than *)
+  | Sle (* Signed less or equal *)
 end
 
 (** The predicate for a floating-point comparison ([fcmp]) instruction.
+    Ordered means that neither operand is a QNAN while unordered means
+    that either operand may be a QNAN.
     See the [llvm::FCmpInst::Predicate] enumeration. *)
 module Fcmp : sig
   type t =
-  | False
-  | Oeq
-  | Ogt
-  | Oge
-  | Olt
-  | Ole
-  | One
-  | Ord
-  | Uno
-  | Ueq
-  | Ugt
-  | Uge
-  | Ult
-  | Ule
-  | Une
-  | True
+  | False (* Always false *)
+  | Oeq   (* Ordered and equal *)
+  | Ogt   (* Ordered and greater than *)
+  | Oge   (* Ordered and greater or equal *)
+  | Olt   (* Ordered and less than *)
+  | Ole   (* Ordered and less or equal *)
+  | One   (* Ordered and not equal *)
+  | Ord   (* Ordered (no operand is NaN) *)
+  | Uno   (* Unordered (one operand at least is NaN) *)
+  | Ueq   (* Unordered and equal *)
+  | Ugt   (* Unordered and greater than *)
+  | Uge   (* Unordered and greater or equal *)
+  | Ult   (* Unordered and less than *)
+  | Ule   (* Unordered and less or equal *)
+  | Une   (* Unordered and not equal *)
+  | True  (* Always true *)
 end
 
 (** The opcodes for LLVM instructions and constant expressions. *)
@@ -718,6 +720,11 @@ val fold_right_uses : (lluse -> 'a -> 'a) -> llvalue -> 'a -> 'a
     method [llvm::User::getOperand]. *)
 val operand : llvalue -> int -> llvalue
 
+(** [operand_use v i] returns the use of the operand at index [i] for the value [v]. See the
+    method [llvm::User::getOperandUse]. *)
+val operand_use : llvalue -> int -> lluse
+
+
 (** [set_operand v i o] sets the operand of the value [v] at the index [i] to
     the value [o].
     See the method [llvm::User::setOperand]. *)
@@ -839,7 +846,6 @@ val const_float : lltype -> float -> llvalue
     [ty] and value [n]. See the method [llvm::ConstantFP::get]. *)
 val const_float_of_string : lltype -> string -> llvalue
 
-
 (** {7 Operations on composite constants} *)
 
 (** [const_string c s] returns the constant [i8] array with the values of the
@@ -885,6 +891,14 @@ val const_packed_struct : llcontext -> llvalue array -> llvalue
     values [elts]. See the method [llvm::ConstantVector::get]. *)
 val const_vector : llvalue array -> llvalue
 
+(** [string_of_const c] returns [Some str] if [c] is a string constant,
+    or [None] if this is not a string constant. *)
+val string_of_const : llvalue -> string option
+
+(** [const_element c] returns a constant for a specified index's element.
+    See the method ConstantDataSequential::getElementAsConstant. *)
+val const_element : llvalue -> int -> llvalue
+
 
 (** {7 Constant expressions} *)
 
@@ -1051,12 +1065,12 @@ val const_lshr : llvalue -> llvalue -> llvalue
     See the method [llvm::ConstantExpr::getAShr]. *)
 val const_ashr : llvalue -> llvalue -> llvalue
 
-(** [const_gep pc indices] returns the constant [getElementPtr] of [p1] with the
+(** [const_gep pc indices] returns the constant [getElementPtr] of [pc] with the
     constant integers indices from the array [indices].
     See the method [llvm::ConstantExpr::getGetElementPtr]. *)
 val const_gep : llvalue -> llvalue array -> llvalue
 
-(** [const_in_bounds_gep pc indices] returns the constant [getElementPtr] of [p1]
+(** [const_in_bounds_gep pc indices] returns the constant [getElementPtr] of [pc]
     with the constant integers indices from the array [indices].
     See the method [llvm::ConstantExpr::getInBoundsGetElementPtr]. *)
 val const_in_bounds_gep : llvalue -> llvalue array -> llvalue
@@ -1685,6 +1699,11 @@ val instr_opcode : llvalue -> Opcode.t
     instruction [i]. *)
 val icmp_predicate : llvalue -> Icmp.t option
 
+(** [inst_clone i] returns a copy of instruction [i],
+    The instruction has no parent, and no name.
+    See the method [llvm::Instruction::clone]. *)
+val instr_clone : llvalue -> llvalue
+
 
 (** {7 Operations on call sites} *)
 
@@ -2360,7 +2379,7 @@ val build_insertelement : llvalue -> llvalue -> llvalue -> string ->
 val build_shufflevector : llvalue -> llvalue -> llvalue -> string ->
                                llbuilder -> llvalue
 
-(** [build_insertvalue agg idx name b] creates a
+(** [build_extractvalue agg idx name b] creates a
     [%name = extractvalue %agg, %idx]
     instruction at the position specified by the instruction builder [b].
     See the method [llvm::LLVMBuilder::CreateExtractValue]. *)