OCaml bindings: add icmp_predicate
[oota-llvm.git] / bindings / ocaml / llvm / llvm.ml
index 4ae2eb602d2865925d9db059320598795795b73e..0b24fd5e4249b848d088f184159c82187af8d0b0 100644 (file)
@@ -294,9 +294,14 @@ external struct_type : llcontext -> lltype array -> lltype = "llvm_struct_type"
 external packed_struct_type : llcontext -> lltype array -> lltype
                             = "llvm_packed_struct_type"
 external struct_name : lltype -> string option = "llvm_struct_name"
+external named_struct_type : llcontext -> string -> lltype =
+    "llvm_named_struct_type"
+external struct_set_body : lltype -> lltype array -> bool -> unit =
+    "llvm_struct_set_body"
 external struct_element_types : lltype -> lltype array
                               = "llvm_struct_element_types"
 external is_packed : lltype -> bool = "llvm_is_packed"
+external is_opaque : lltype -> bool = "llvm_is_opaque"
 
 (*--... Operations on pointer, vector, and array types .....................--*)
 external array_type : lltype -> int -> lltype = "llvm_array_type"
@@ -400,6 +405,8 @@ external const_stringz : llcontext -> string -> llvalue = "llvm_const_stringz"
 external const_array : lltype -> llvalue array -> llvalue = "llvm_const_array"
 external const_struct : llcontext -> llvalue array -> llvalue
                       = "llvm_const_struct"
+external const_named_struct : lltype -> llvalue array -> llvalue
+                      = "llvm_const_named_struct"
 external const_packed_struct : llcontext -> llvalue array -> llvalue
                              = "llvm_const_packed_struct"
 external const_vector : llvalue array -> llvalue = "llvm_const_vector"
@@ -808,6 +815,8 @@ external instr_pred : llvalue -> (llbasicblock, llvalue) llrev_pos
 external instr_opcode : llvalue -> Opcode.t = "llvm_instr_get_opcode"
 external icmp_predicate : llvalue -> Icmp.t option = "llvm_instr_icmp_predicate"
 
+external icmp_predicate : llvalue -> Icmp.t option = "llvm_instr_icmp_predicate"
+
 let rec iter_instrs_range f i e =
   if i = e then () else
   match i with
@@ -1130,7 +1139,14 @@ let rec string_of_lltype ty =
   (* FIXME: stop infinite recursion! :) *)
   match classify_type ty with
     TypeKind.Integer -> "i" ^ string_of_int (integer_bitwidth ty)
-  | TypeKind.Pointer -> (string_of_lltype (element_type ty)) ^ "*"
+  | TypeKind.Pointer ->
+      (let ety = element_type ty in
+      match classify_type ety with
+      | TypeKind.Struct ->
+          (match struct_name ety with
+          | None -> (string_of_lltype ety)
+          | Some s -> s) ^ "*"
+      | _ -> (string_of_lltype (element_type ty)) ^ "*")
   | TypeKind.Struct ->
       let s = "{ " ^ (concat2 ", " (
                 Array.map string_of_lltype (struct_element_types ty)