bindings: named struct support
[oota-llvm.git] / bindings / ocaml / llvm / llvm.ml
index 031bd7cd471973fc0c7838bc418209af29f9a1e6..19ad672b547c7fb24a15cf1dfab7364d159d2aab 100644 (file)
@@ -201,6 +201,30 @@ module Opcode  = struct
   | Unwind
 end
 
   | Unwind
 end
 
+module ValueKind = struct
+  type t =
+  | NullValue
+  | Argument
+  | BasicBlock
+  | InlineAsm
+  | MDNode
+  | MDString
+  | BlockAddress
+  | ConstantAggregateZero
+  | ConstantArray
+  | ConstantExpr
+  | ConstantFP
+  | ConstantInt
+  | ConstantPointerNull
+  | ConstantStruct
+  | ConstantVector
+  | Function
+  | GlobalAlias
+  | GlobalVariable
+  | UndefValue
+  | Instruction of Opcode.t
+end
+
 exception IoError of string
 
 external register_exns : exn -> unit = "llvm_register_core_exns"
 exception IoError of string
 
 external register_exns : exn -> unit = "llvm_register_core_exns"
@@ -270,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 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 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"
 
 (*--... Operations on pointer, vector, and array types .....................--*)
 external array_type : lltype -> int -> lltype = "llvm_array_type"
@@ -290,6 +319,7 @@ external vector_size : lltype -> int = "llvm_vector_size"
 external void_type : llcontext -> lltype = "llvm_void_type"
 external label_type : llcontext -> lltype = "llvm_label_type"
 
 external void_type : llcontext -> lltype = "llvm_void_type"
 external label_type : llcontext -> lltype = "llvm_label_type"
 
+external classify_value : llvalue -> ValueKind.t = "llvm_classify_value"
 (*===-- Values ------------------------------------------------------------===*)
 external type_of : llvalue -> lltype = "llvm_type_of"
 external value_name : llvalue -> string = "llvm_value_name"
 (*===-- Values ------------------------------------------------------------===*)
 external type_of : llvalue -> lltype = "llvm_type_of"
 external value_name : llvalue -> string = "llvm_value_name"
@@ -375,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_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"
 external const_packed_struct : llcontext -> llvalue array -> llvalue
                              = "llvm_const_packed_struct"
 external const_vector : llvalue array -> llvalue = "llvm_const_vector"