[OCaml] Expose Llvm.{set_,}unnamed_addr.
[oota-llvm.git] / bindings / ocaml / llvm / llvm.mli
index e5e90c33f4aa28ad978bf2996c277e6aeab44012..541c35a2a229d24f0a34ff6497f77a0cc95a5612 100644 (file)
@@ -431,9 +431,6 @@ val create_module : llcontext -> string -> llmodule
     [llvm::Module::~Module]. *)
 val dispose_module : llmodule -> unit
 
-(** [clone_module m] returns an exact copy of module [m]. *)
-val clone_module : llmodule -> llmodule
-
 (** [target_triple m] is the target specifier for the module [m], something like
     [i686-apple-darwin8]. See the method [llvm::Module::getTargetTriple]. *)
 val target_triple: llmodule -> string
@@ -822,6 +819,9 @@ val mdstring : llcontext -> string -> llvalue
     See the method [llvm::MDNode::get]. *)
 val mdnode : llcontext -> llvalue array -> llvalue
 
+(** [mdnull c ] returns a null MDNode in context [c].  *)
+val mdnull : llcontext -> llvalue
+
 (** [get_mdstring v] returns the MDString.
     See the method [llvm::MDString::getString] *)
 val get_mdstring : llvalue -> string option
@@ -1255,6 +1255,16 @@ val linkage : llvalue -> Linkage.t
     See the method [llvm::GlobalValue::setLinkage]. *)
 val set_linkage : Linkage.t -> llvalue -> unit
 
+(** [unnamed_addr g] returns [true] if the global value [g] has the unnamed_addr
+    attribute. Returns [false] otherwise.
+    See the method [llvm::GlobalValue::getUnnamedAddr]. *)
+val unnamed_addr : llvalue -> bool
+
+(** [set_unnamed_addr b g] if [b] is [true], sets the unnamed_addr attribute of
+    the global value [g]. Unset it otherwise.
+    See the method [llvm::GlobalValue::setUnnamedAddr]. *)
+val set_unnamed_addr : bool -> llvalue -> unit
+
 (** [section g] returns the linker section of the global value [g].
     See the method [llvm::GlobalValue::getSection]. *)
 val section : llvalue -> string
@@ -2422,6 +2432,12 @@ val build_fcmp : Fcmp.t -> llvalue -> llvalue -> string ->
 val build_phi : (llvalue * llbasicblock) list -> string -> llbuilder ->
                      llvalue
 
+(** [build_empty_phi ty name b] creates a
+    [%name = phi %ty] instruction at the position specified by
+    the instruction builder [b]. [ty] is the type of the instruction.
+    See the method [llvm::LLVMBuilder::CreatePHI]. *)
+val build_empty_phi : lltype -> string -> llbuilder -> llvalue
+
 (** [build_call fn args name b] creates a
     [%name = call %fn(args...)]
     instruction at the position specified by the instruction builder [b].