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.mli79
1 files changed, 78 insertions, 1 deletions
diff --git a/bindings/ocaml/llvm/llvm.mli b/bindings/ocaml/llvm/llvm.mli
index 0f1e9a9017..2e2db6e531 100644
--- a/bindings/ocaml/llvm/llvm.mli
+++ b/bindings/ocaml/llvm/llvm.mli
@@ -179,6 +179,78 @@ module Fcmp : sig
| True
end
+(** The opcodes for LLVM instructions and constant expressions. *)
+module Opcode : sig
+ type t =
+ | Invalid (* not an instruction *)
+ (* Terminator Instructions *)
+ | Ret
+ | Br
+ | Switch
+ | IndirectBr
+ | Invoke
+ | Invalid2
+ | Unreachable
+ (* Standard Binary Operators *)
+ | Add
+ | FAdd
+ | Sub
+ | FSub
+ | Mul
+ | FMul
+ | UDiv
+ | SDiv
+ | FDiv
+ | URem
+ | SRem
+ | FRem
+ (* Logical Operators *)
+ | Shl
+ | LShr
+ | AShr
+ | And
+ | Or
+ | Xor
+ (* Memory Operators *)
+ | Alloca
+ | Load
+ | Store
+ | GetElementPtr
+ (* Cast Operators *)
+ | Trunc
+ | ZExt
+ | SExt
+ | FPToUI
+ | FPToSI
+ | UIToFP
+ | SIToFP
+ | FPTrunc
+ | FPExt
+ | PtrToInt
+ | IntToPtr
+ | BitCast
+ (* Other Operators *)
+ | ICmp
+ | FCmp
+ | PHI
+ | Call
+ | Select
+ | UserOp1
+ | UserOp2
+ | VAArg
+ | ExtractElement
+ | InsertElement
+ | ShuffleVector
+ | ExtractValue
+ | InsertValue
+ | Fence
+ | AtomicCmpXchg
+ | AtomicRMW
+ | Resume
+ | LandingPad
+ | Unwind
+end
+
(** {6 Iteration} *)
@@ -543,7 +615,7 @@ val is_null : llvalue -> bool
otherwise. Similar to [llvm::isa<UndefValue>]. *)
val is_undef : llvalue -> bool
-
+val constexpr_opcode : llvalue -> Opcode.t
(** {7 Operations on instructions} *)
(** [has_metadata i] returns whether or not the instruction [i] has any
@@ -595,6 +667,10 @@ val const_int : lltype -> int -> llvalue
[i]. See the method [llvm::ConstantInt::get]. *)
val const_of_int64 : lltype -> Int64.t -> bool -> llvalue
+(** [int64_of_const c] returns the int64 value of the [c] constant integer.
+ * None is returned if this is not an integer constant, or bitwidth exceeds 64.
+ * See the method [llvm::ConstantInt::getSExtValue].*)
+val int64_of_const : llvalue -> Int64.t option
(** [const_int_of_string ty s r] returns the integer constant of type [ty] and
* value [s], with the radix [r]. See the method [llvm::ConstantInt::get]. *)
@@ -1439,6 +1515,7 @@ val instr_pred : llvalue -> (llbasicblock, llvalue) llrev_pos
[f1,...,fN] are the instructions of basic block [bb]. Tail recursive. *)
val fold_right_instrs: (llvalue -> 'a -> 'a) -> llbasicblock -> 'a -> 'a
+val instr_opcode : llvalue -> Opcode.t
val icmp_predicate : llvalue -> Icmp.t option