summaryrefslogtreecommitdiff
path: root/bindings/ocaml/llvm/llvm_ocaml.c
diff options
context:
space:
mode:
Diffstat (limited to 'bindings/ocaml/llvm/llvm_ocaml.c')
-rw-r--r--bindings/ocaml/llvm/llvm_ocaml.c25
1 files changed, 25 insertions, 0 deletions
diff --git a/bindings/ocaml/llvm/llvm_ocaml.c b/bindings/ocaml/llvm/llvm_ocaml.c
index 21519d474d..cbc05448fa 100644
--- a/bindings/ocaml/llvm/llvm_ocaml.c
+++ b/bindings/ocaml/llvm/llvm_ocaml.c
@@ -427,6 +427,12 @@ CAMLprim value llvm_is_undef(LLVMValueRef Val) {
return Val_bool(LLVMIsUndef(Val));
}
+/* llvalue -> Opcode.t */
+CAMLprim value llvm_constexpr_get_opcode(LLVMValueRef Val) {
+ return LLVMIsAConstantExpr(Val) ?
+ Val_int(LLVMGetConstOpcode(Val)) : Val_int(0);
+}
+
/*--... Operations on instructions .........................................--*/
/* llvalue -> bool */
@@ -512,6 +518,19 @@ CAMLprim LLVMValueRef llvm_const_of_int64(LLVMTypeRef IntTy, value N,
return LLVMConstInt(IntTy, Int64_val(N), Bool_val(SExt));
}
+/* llvalue -> Int64.t */
+CAMLprim value llvm_int64_of_const(LLVMValueRef Const)
+{
+ CAMLparam0();
+ if (LLVMIsAConstantInt(Const) &&
+ LLVMGetIntTypeWidth(LLVMTypeOf(Const)) <= 64) {
+ value Option = alloc(1, 0);
+ Field(Option, 0) = caml_copy_int64(LLVMConstIntGetSExtValue(Const));
+ CAMLreturn(Option);
+ }
+ CAMLreturn(Val_int(0));
+}
+
/* lltype -> string -> int -> llvalue */
CAMLprim LLVMValueRef llvm_const_int_of_string(LLVMTypeRef IntTy, value S,
value Radix) {
@@ -1013,6 +1032,12 @@ CAMLprim value llvm_value_is_block(LLVMValueRef Val) {
DEFINE_ITERATORS(instr, Instruction, LLVMBasicBlockRef, LLVMValueRef,
LLVMGetInstructionParent)
+/* llvalue -> Opcode.t */
+CAMLprim value llvm_instr_get_opcode(LLVMValueRef Inst) {
+ LLVMOpcode o = LLVMGetInstructionOpcode(Inst);
+ assert (o <= LLVMUnwind );
+ return Val_int(o);
+}
/* llvalue -> ICmp.t */
CAMLprim value llvm_instr_icmp_predicate(LLVMValueRef Val) {