OCaml parameter attribute bindings from PR2752.
[oota-llvm.git] / bindings / ocaml / llvm / llvm.mli
index 06d4b21c8d15c26f55c8511fd5ba9bb5d34995a4..421c20cba96187fe7a82c019cd895ab81436a675 100644 (file)
@@ -111,6 +111,21 @@ module CallConv : sig
                               convention from C. *)
 end
 
+module Attribute : sig
+  type t =
+  | Zext
+  | Sext
+  | Noreturn
+  | Inreg
+  | Structret
+  | Nounwind
+  | Noalias
+  | Byval
+  | Nest
+  | Readnone
+  | Readonly
+end
+
 (** The predicate for an integer comparison ([icmp]) instruction.
     See the [llvm::ICmpInst::Predicate] enumeration. *)
 module Icmp : sig
@@ -931,6 +946,15 @@ external gc : llvalue -> string option = "llvm_gc"
     [gc]. See the method [llvm::Function::setGC]. *)
 external set_gc : string option -> llvalue -> unit = "llvm_set_gc"
 
+(** [add_function_attr f a] adds attribute [a] to the return type of function
+    [f]. *)
+external add_function_attr : llvalue -> Attribute.t -> unit
+                           = "llvm_add_function_attr"
+
+(** [remove_function_attr f a] removes attribute [a] from the return type of
+    function [f]. *)
+external remove_function_attr : llvalue -> Attribute.t -> unit
+                              = "llvm_remove_function_attr"
 
 (** {7 Operations on params} *)
 
@@ -984,6 +1008,16 @@ val rev_iter_params : (llvalue -> unit) -> llvalue -> unit
     [b1,...,bN] are the parameters of function [fn]. Tail recursive. *)
 val fold_right_params : (llvalue -> 'a -> 'a) -> llvalue -> 'a -> 'a
 
+(** [add_param p a] adds attribute [a] to parameter [p]. *)
+external add_param_attr : llvalue -> Attribute.t -> unit = "llvm_add_param_attr"
+
+(** [remove_param_attr p a] removes attribute [a] from parameter [p]. *)
+external remove_param_attr : llvalue -> Attribute.t -> unit
+                           = "llvm_remove_param_attr"
+
+(** [set_param_alignment p a] set the alignment of parameter [p] to [a]. *)
+external set_param_alignment : llvalue -> int -> unit
+                             = "llvm_set_param_alignment"
 
 (** {7 Operations on basic blocks} *)
 
@@ -1127,6 +1161,18 @@ external instruction_call_conv: llvalue -> int
 external set_instruction_call_conv: int -> llvalue -> unit
                                   = "llvm_set_instruction_call_conv"
 
+(** [add_instruction_param_attr ci i a] adds attribute [a] to the [i]th
+    parameter of the call or invoke instruction [ci]. [i]=0 denotes the return
+    value. *)
+external add_instruction_param_attr : llvalue -> int -> Attribute.t -> unit
+  = "llvm_add_instruction_param_attr"
+
+(** [remove_instruction_param_attr ci i a] removes attribute [a] from the
+    [i]th parameter of the call or invoke instruction [ci]. [i]=0 denotes the
+    return value. *)
+external remove_instruction_param_attr : llvalue -> int -> Attribute.t -> unit
+  = "llvm_remove_instruction_param_attr"
+
 (** {Operations on call instructions (only)} *)
 
 (** [is_tail_call ci] is [true] if the call instruction [ci] is flagged as