ocaml/C bindings: getmdstring, add num_op, get_op should work on metadata too
[oota-llvm.git] / bindings / ocaml / llvm / llvm.mli
index 9b037aae7a46c65c6a36213c002e605c8333b3ab..b4b9622b630bb10ea8fb8bb1c4c73e8c9e9ea8fa 100644 (file)
@@ -29,11 +29,6 @@ type llmodule
     [llvm::Type] class. *)
 type lltype
 
-(** When building recursive types using {!refine_type}, [lltype] values may
-    become invalid; use [lltypehandle] to resolve this problem. See the
-    [llvm::AbstractTypeHolder] class. *)
-type lltypehandle
-
 (** Any value in the LLVM IR. Functions, instructions, global variables,
     constants, and much more are all [llvalues]. See the [llvm::Value] class.
     This type covers a wide range of subclasses. *)
@@ -69,7 +64,6 @@ module TypeKind : sig
   | Struct
   | Array
   | Pointer
-  | Opaque
   | Vector
   | Metadata
 end
@@ -261,24 +255,6 @@ val data_layout: llmodule -> string
     to the string [s]. See the method [llvm::Module::setDataLayout]. *)
 val set_data_layout: string -> llmodule -> unit
 
-
-(** [define_type_name name ty m] adds a named type to the module's symbol table.
-    Returns [true] if successful. If such a name already exists, then no entry
-    is added and [false] is returned. See the [llvm::Module::addTypeName]
-    method. *)
-val define_type_name : string -> lltype -> llmodule -> bool
-
-
-(** [delete_type_name name] removes a type name from the module's symbol
-    table. *)
-val delete_type_name : string -> llmodule -> unit
-
-
-(** [type_by_name m n] returns the type in the module [m] named [n], or [None]
-    if it does not exist. See the method [llvm::Module::getTypeByName]. *)
-val type_by_name : llmodule -> string -> lltype option
-
-
 (** [dump_module m] prints the .ll representation of the module [m] to standard
     error. See the method [llvm::Module::dump]. *)
 val dump_module : llmodule -> unit
@@ -363,7 +339,7 @@ val ppc_fp128_type : llcontext -> lltype
     See the method [llvm::FunctionType::get]. *)
 val function_type : lltype -> lltype array -> lltype
 
-(** [va_arg_function_type ret_ty param_tys] is just like
+(** [var_arg_function_type ret_ty param_tys] is just like
     [function_type ret_ty param_tys] except that it returns the function type
     which also takes a variable number of arguments.
     See the method [llvm::FunctionType::get]. *)
@@ -396,6 +372,10 @@ val struct_type : llcontext -> lltype array -> lltype
     [llvm::StructType::get]. *)
 val packed_struct_type : llcontext -> lltype array -> lltype
 
+(** [struct_name ty] returns the name of the named structure type [ty],
+ * or None if the structure type is not named *)
+val struct_name : lltype -> string option
+
 
 (** [struct_element_types sty] returns the constituent types of the struct type
     [sty]. See the method [llvm::StructType::getElementType]. *)
@@ -447,11 +427,6 @@ val vector_size : lltype -> int
 
 (** {7 Operations on other types} *)
 
-(** [opaque_type c] creates a new opaque type distinct from any other in the
-    context [c]. Opaque types are useful for building recursive types in
-    combination with {!refine_type}. See [llvm::OpaqueType::get]. *)
-val opaque_type : llcontext -> lltype
-
 (** [void_type c] creates a type of a function which does not return any
     value in the context [c]. See [llvm::Type::VoidTy]. *)
 val void_type : llcontext -> lltype
@@ -460,25 +435,6 @@ val void_type : llcontext -> lltype
     [llvm::Type::LabelTy]. *)
 val label_type : llcontext -> lltype
 
-(** {7 Operations on type handles} *)
-
-(** [handle_to_type ty] creates a handle to the type [ty]. If [ty] is later
-    refined as a result of a call to {!refine_type}, the handle will be updated;
-    any bare [lltype] references will become invalid.
-    See the class [llvm::PATypeHolder]. *)
-val handle_to_type : lltype -> lltypehandle
-
-(** [type_of_handle tyh] resolves the type handle [tyh].
-    See the method [llvm::PATypeHolder::get()]. *)
-val type_of_handle : lltypehandle -> lltype
-
-(** [refine_type opaque_ty ty] replaces the abstract type [opaque_ty] with the
-    concrete type [ty] in all users. Warning: This may invalidate {!lltype}
-    values! Use {!lltypehandle} to manipulate potentially abstract types. See
-    the method [llvm::Type::refineAbstractType]. *)
-val refine_type : lltype -> lltype -> unit
-
-
 (* {6 Values} *)
 
 (** [type_of v] returns the type of the value [v].
@@ -615,6 +571,14 @@ val mdstring : llcontext -> string -> llvalue
     See the method [llvm::MDNode::get]. *)
 val mdnode : llcontext -> llvalue array -> llvalue
 
+(** [get_mdstring v] returns the MDString.
+ * See the method [llvm::MDString::getString] *)
+val get_mdstring : llvalue -> string option
+
+(** [get_named_metadata m name] return all the MDNodes belonging to the named
+ * metadata (if any).
+ * See the method [llvm::NamedMDNode::getOperand]. *)
+val get_named_metadata : llmodule -> string -> llvalue array
 
 (** {7 Operations on scalar constants} *)
 
@@ -1663,12 +1627,16 @@ val add_destination : llvalue -> llbasicblock -> unit
 val build_invoke : llvalue -> llvalue array -> llbasicblock ->
                         llbasicblock -> string -> llbuilder -> llvalue
 
-
-(** [build_unwind b] creates an
-    [unwind]
+(** [build_landingpad ty persfn numclauses name b] creates an
+    [landingpad]
     instruction at the position specified by the instruction builder [b].
-    See the method [llvm::LLVMBuilder::CreateUnwind]. *)
-val build_unwind : llbuilder -> llvalue
+    See the method [llvm::LLVMBuilder::CreateLandingPad]. *)
+val build_landingpad : lltype -> llvalue -> int -> string -> llbuilder ->
+                         llvalue
+
+(** [set_cleanup lp] sets the cleanup flag in the [landingpad]instruction.
+    See the method [llvm::LandingPadInst::setCleanup]. *)
+val set_cleanup : llvalue -> bool -> unit
 
 (** [build_unreachable b] creates an
     [unreachable]