summaryrefslogtreecommitdiff
path: root/bindings/ocaml/llvm/llvm.mli
diff options
context:
space:
mode:
Diffstat (limited to 'bindings/ocaml/llvm/llvm.mli')
-rw-r--r--bindings/ocaml/llvm/llvm.mli137
1 files changed, 74 insertions, 63 deletions
diff --git a/bindings/ocaml/llvm/llvm.mli b/bindings/ocaml/llvm/llvm.mli
index 0f973000f754..4068126e2cbf 100644
--- a/bindings/ocaml/llvm/llvm.mli
+++ b/bindings/ocaml/llvm/llvm.mli
@@ -44,6 +44,12 @@ type llbasicblock
class. *)
type llbuilder
+(** Used to represent attribute kinds. *)
+type llattrkind
+
+(** An attribute in LLVM IR. See the [llvm::Attribute] class. *)
+type llattribute
+
(** Used to efficiently handle large buffers of read-only binary data.
See the [llvm::MemoryBuffer] class. *)
type llmemorybuffer
@@ -130,36 +136,19 @@ module CallConv : sig
convention from C. *)
end
-(** The attribute kind of a function parameter, result or the function itself.
- See [llvm::Attribute::AttrKind]. *)
-module Attribute : sig
+(** The logical representation of an attribute. *)
+module AttrRepr : sig
+ type t =
+ | Enum of llattrkind * int64
+ | String of string * string
+end
+
+(** The position of an attribute. See [LLVMAttributeIndex]. *)
+module AttrIndex : sig
type t =
- | Zext
- | Sext
- | Noreturn
- | Inreg
- | Structret
- | Nounwind
- | Noalias
- | Byval
- | Nest
- | Readnone
- | Readonly
- | Noinline
- | Alwaysinline
- | Optsize
- | Ssp
- | Sspreq
- | Alignment of int
- | Nocapture
- | Noredzone
- | Noimplicitfloat
- | Naked
- | Inlinehint
- | Stackalignment of int
- | ReturnsTwice
- | UWTable
- | NonLazyBind
+ | Function
+ | Return
+ | Param of int
end
(** The predicate for an integer comparison ([icmp]) instruction.
@@ -443,6 +432,36 @@ val global_context : unit -> llcontext
val mdkind_id : llcontext -> string -> llmdkind
+(** {6 Attributes} *)
+
+(** [UnknownAttribute attr] is raised when a enum attribute name [name]
+ is not recognized by LLVM. *)
+exception UnknownAttribute of string
+
+(** [enum_attr_kind name] returns the kind of enum attributes named [name].
+ May raise [UnknownAttribute]. *)
+val enum_attr_kind : string -> llattrkind
+
+(** [create_enum_attr context value kind] creates an enum attribute
+ with the supplied [kind] and [value] in [context]; if the value
+ is not required (as for the majority of attributes), use [0L].
+ May raise [UnknownAttribute].
+ See the constructor [llvm::Attribute::get]. *)
+val create_enum_attr : llcontext -> string -> int64 -> llattribute
+
+(** [create_string_attr context kind value] creates a string attribute
+ with the supplied [kind] and [value] in [context].
+ See the constructor [llvm::Attribute::get]. *)
+val create_string_attr : llcontext -> string -> string -> llattribute
+
+(** [attr_of_repr context repr] creates an attribute with the supplied
+ representation [repr] in [context]. *)
+val attr_of_repr : llcontext -> AttrRepr.t -> llattribute
+
+(** [repr_of_attr attr] describes the representation of attribute [attr]. *)
+val repr_of_attr : llattribute -> AttrRepr.t
+
+
(** {6 Modules} *)
(** [create_module context id] creates a module with the supplied module ID in
@@ -1547,21 +1566,21 @@ val gc : llvalue -> string option
[gc]. See the method [llvm::Function::setGC]. *)
val set_gc : string option -> llvalue -> unit
-(** [add_function_attr f a] adds attribute [a] to the return type of function
- [f]. *)
-val add_function_attr : llvalue -> Attribute.t -> unit
+(** [add_function_attr f a i] adds attribute [a] to the function [f]
+ at position [i]. *)
+val add_function_attr : llvalue -> llattribute -> AttrIndex.t -> unit
-(** [add_target_dependent_function_attr f a] adds target-dependent attribute
- [a] to function [f]. *)
-val add_target_dependent_function_attr : llvalue -> string -> string -> unit
+(** [function_attrs f i] returns the attributes for the function [f]
+ at position [i]. *)
+val function_attrs : llvalue -> AttrIndex.t -> llattribute array
-(** [function_attr f] returns the function attribute for the function [f].
- See the method [llvm::Function::getAttributes] *)
-val function_attr : llvalue -> Attribute.t list
+(** [remove_enum_function_attr f k i] removes enum attribute with kind [k]
+ from the function [f] at position [i]. *)
+val remove_enum_function_attr : llvalue -> llattrkind -> AttrIndex.t -> unit
-(** [remove_function_attr f a] removes attribute [a] from the return type of
- function [f]. *)
-val remove_function_attr : llvalue -> Attribute.t -> unit
+(** [remove_string_function_attr f k i] removes string attribute with kind [k]
+ from the function [f] at position [i]. *)
+val remove_string_function_attr : llvalue -> string -> AttrIndex.t -> unit
(** {7 Operations on params} *)
@@ -1574,11 +1593,6 @@ val params : llvalue -> llvalue array
See the method [llvm::Function::getArgumentList]. *)
val param : llvalue -> int -> llvalue
-(** [param_attr p] returns the attributes of parameter [p].
- See the methods [llvm::Function::getAttributes] and
- [llvm::Attributes::getParamAttributes] *)
-val param_attr : llvalue -> Attribute.t list
-
(** [param_parent p] returns the parent function that owns the parameter.
See the method [llvm::Argument::getParent]. *)
val param_parent : llvalue -> llvalue
@@ -1620,15 +1634,6 @@ 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]. *)
-val add_param_attr : llvalue -> Attribute.t -> unit
-
-(** [remove_param_attr p a] removes attribute [a] from parameter [p]. *)
-val remove_param_attr : llvalue -> Attribute.t -> unit
-
-(** [set_param_alignment p a] set the alignment of parameter [p] to [a]. *)
-val set_param_alignment : llvalue -> int -> unit
-
(** {7 Operations on basic blocks} *)
@@ -1797,15 +1802,21 @@ val instruction_call_conv: llvalue -> int
and [llvm::InvokeInst::setCallingConv]. *)
val set_instruction_call_conv: int -> llvalue -> unit
-(** [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. *)
-val add_instruction_param_attr : llvalue -> int -> Attribute.t -> unit
+(** [add_call_site_attr f a i] adds attribute [a] to the call instruction [ci]
+ at position [i]. *)
+val add_call_site_attr : llvalue -> llattribute -> AttrIndex.t -> unit
+
+(** [call_site_attr f i] returns the attributes for the call instruction [ci]
+ at position [i]. *)
+val call_site_attrs : llvalue -> AttrIndex.t -> llattribute array
+
+(** [remove_enum_call_site_attr f k i] removes enum attribute with kind [k]
+ from the call instruction [ci] at position [i]. *)
+val remove_enum_call_site_attr : llvalue -> llattrkind -> AttrIndex.t -> unit
-(** [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. *)
-val remove_instruction_param_attr : llvalue -> int -> Attribute.t -> unit
+(** [remove_string_call_site_attr f k i] removes string attribute with kind [k]
+ from the call instruction [ci] at position [i]. *)
+val remove_string_call_site_attr : llvalue -> string -> AttrIndex.t -> unit
(** {7 Operations on call instructions (only)} *)