Add support for global aliases to ocaml.
[oota-llvm.git] / bindings / ocaml / llvm / llvm.mli
index 98ba05f2081176b99f5c232ea25cbb4461757bdd..3413a646609f2b9c66e2ec77146b7d8cd7ed1f5d 100644 (file)
@@ -221,6 +221,11 @@ external dispose_context : llcontext -> unit = "llvm_dispose_context"
 (** See the function [llvm::getGlobalContext]. *)
 external global_context : unit -> llcontext = "llvm_global_context"
 
+(** [mdkind_id context name] returns the MDKind ID that corresponds to the
+    name [name] in the context [context].  See the function
+    [llvm::LLVMContext::getMDKindID]. *)
+external mdkind_id : llcontext -> string -> int = "llvm_mdkind_id"
+
 
 (** {6 Modules} *)
 
@@ -269,6 +274,11 @@ external define_type_name : string -> lltype -> llmodule -> bool
 external delete_type_name : string -> llmodule -> unit
                           = "llvm_delete_type_name"
 
+(** [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]. *)
+external type_by_name : llmodule -> string -> lltype option
+                      = "llvm_type_by_name"
+
 (** [dump_module m] prints the .ll representation of the module [m] to standard
     error. See the method [llvm::Module::dump]. *)
 external dump_module : llmodule -> unit = "llvm_dump_module"
@@ -497,6 +507,11 @@ external set_value_name : string -> llvalue -> unit = "llvm_set_value_name"
     error. See the method [llvm::Value::dump]. *)
 external dump_value : llvalue -> unit = "llvm_dump_value"
 
+(** [replace_all_uses_with old new] replaces all uses of the value [old]
+ * with the value [new]. See the method [llvm::Value::replaceAllUsesWith]. *)
+external replace_all_uses_with : llvalue -> llvalue -> unit
+                               = "LLVMReplaceAllUsesWith"
+
 
 (** {7 Operations on constants of (mostly) any type} *)
 
@@ -512,6 +527,10 @@ external const_null : lltype -> llvalue = "LLVMConstNull"
     [ty]. See the method [llvm::Constant::getAllOnesValue]. *)
 external const_all_ones : (*int|vec*)lltype -> llvalue = "LLVMConstAllOnes"
 
+(** [const_pointer_null ty] returns the constant null (zero) pointer of the type
+    [ty]. See the method [llvm::ConstantPointerNull::get]. *)
+external const_pointer_null : lltype -> llvalue = "LLVMConstPointerNull"
+
 (** [undef ty] returns the undefined value of the type [ty].
     See the method [llvm::UndefValue::get]. *)
 external undef : lltype -> llvalue = "LLVMGetUndef"
@@ -525,6 +544,39 @@ external is_null : llvalue -> bool = "llvm_is_null"
 external is_undef : llvalue -> bool = "llvm_is_undef"
 
 
+(** {7 Operations on instructions} *)
+
+(** [has_metadata i] returns whether or not the instruction [i] has any
+    metadata attached to it. See the function
+    [llvm::Instruction::hasMetadata]. *)
+external has_metadata : llvalue -> bool = "llvm_has_metadata"
+
+(** [metadata i kind] optionally returns the metadata associated with the
+    kind [kind] in the instruction [i] See the function
+    [llvm::Instruction::getMetadata]. *)
+external metadata : llvalue -> int -> llvalue option = "llvm_metadata"
+
+(** [set_metadata i kind md] sets the metadata [md] of kind [kind] in the
+    instruction [i]. See the function [llvm::Instruction::setMetadata]. *)
+external set_metadata : llvalue -> int -> llvalue -> unit = "llvm_set_metadata"
+
+(** [clear_metadata i kind] clears the metadata of kind [kind] in the
+    instruction [i]. See the function [llvm::Instruction::setMetadata]. *)
+external clear_metadata : llvalue -> int -> unit = "llvm_clear_metadata"
+
+
+(** {7 Operations on metadata} *)
+
+(** [mdstring c s] returns the MDString of the string [s] in the context [c].
+    See the method [llvm::MDNode::get]. *)
+external mdstring : llcontext -> string -> llvalue = "llvm_mdstring"
+
+(** [mdnode c elts] returns the MDNode containing the values [elts] in the
+    context [c].
+    See the method [llvm::MDNode::get]. *)
+external mdnode : llcontext -> llvalue array -> llvalue = "llvm_mdnode"
+
+
 (** {7 Operations on scalar constants} *)
 
 (** [const_int ty i] returns the integer constant of type [ty] and value [i].
@@ -912,6 +964,16 @@ external const_extractvalue : llvalue -> int array -> llvalue
 external const_insertvalue : llvalue -> llvalue -> int array -> llvalue
                            = "llvm_const_insertvalue"
 
+(** [const_inline_asm ty asm con side align] inserts a inline assembly string.
+    See the method [llvm::InlineAsm::get]. *)
+external const_inline_asm : lltype -> string -> string -> bool -> bool ->
+                            llvalue
+                          = "llvm_const_inline_asm"
+
+(** [block_address f bb] returns the address of the basic block [bb] in the
+    function [f]. See the method [llvm::BasicBlock::get]. *)
+external block_address : llvalue -> llbasicblock -> llvalue = "LLVMBlockAddress"
+
 
 (** {7 Operations on global variables, functions, and aliases (globals)} *)
 
@@ -961,19 +1023,35 @@ external set_alignment : int -> llvalue -> unit = "llvm_set_alignment"
 (** {7 Operations on global variables} *)
 
 (** [declare_global ty name m] returns a new global variable of type [ty] and
-    with name [name] in module [m]. If such a global variable already exists,
-    it is returned. If the type of the existing global differs, then a bitcast
-    to [ty] is returned. *)
+    with name [name] in module [m] in the default address space (0). If such a
+    global variable already exists, it is returned. If the type of the existing
+    global differs, then a bitcast to [ty] is returned. *)
 external declare_global : lltype -> string -> llmodule -> llvalue
                         = "llvm_declare_global"
 
+(** [declare_qualified_global ty name as m] returns a new global variable of
+    type [ty] and with name [name] in module [m] in the address space [as]. If
+    such a global variable already exists, it is returned. If the type of the
+    existing global differs, then a bitcast to [ty] is returned. *)
+external declare_qualified_global : lltype -> string -> int -> llmodule ->
+                                    llvalue
+                                  = "llvm_declare_qualified_global"
+
 (** [define_global name init m] returns a new global with name [name] and
-    initializer [init] in module [m]. If the named global already exists, it is
-    renamed.
+    initializer [init] in module [m] in the default address space (0). If the
+    named global already exists, it is renamed.
     See the constructor of [llvm::GlobalVariable]. *)
 external define_global : string -> llvalue -> llmodule -> llvalue
                        = "llvm_define_global"
 
+(** [define_qualified_global name init as m] returns a new global with name
+    [name] and initializer [init] in module [m] in the address space [as]. If
+    the named global already exists, it is renamed.
+    See the constructor of [llvm::GlobalVariable]. *)
+external define_qualified_global : string -> llvalue -> int -> llmodule ->
+                                   llvalue
+                                 = "llvm_define_qualified_global"
+
 (** [lookup_global name m] returns [Some g] if a global variable with name
     [name] exists in module [m]. If no such global exists, returns [None].
     See the [llvm::GlobalVariable] constructor. *)
@@ -1062,6 +1140,15 @@ external is_thread_local : llvalue -> bool = "llvm_is_thread_local"
 external set_thread_local : bool -> llvalue -> unit = "llvm_set_thread_local"
 
 
+(** {7 Operations on aliases} *)
+
+(** [add_alias m t a n] inserts an alias in the module [m] with the type [t] and
+    the aliasee [a] with the name [n].
+    See the constructor for [llvm::GlobalAlias]. *)
+external add_alias : llmodule -> lltype -> llvalue -> string -> llvalue
+                   = "llvm_add_alias"
+
+
 (** {7 Operations on functions} *)
 
 (** [declare_function name ty m] returns a new function of type [ty] and
@@ -1451,6 +1538,30 @@ external insertion_block : llbuilder -> llbasicblock = "llvm_insertion_block"
 external insert_into_builder : llvalue -> string -> llbuilder -> unit
                              = "llvm_insert_into_builder"
 
+(** {7 Metadata} *)
+
+(** [set_current_debug_location b md] sets the current debug location [md] in
+    the builder [b].
+    See the method [llvm::IRBuilder::SetDebugLocation]. *)
+external set_current_debug_location : llbuilder -> llvalue -> unit
+                                    = "llvm_set_current_debug_location"
+
+(** [clear_current_debug_location b] clears the current debug location in the
+    builder [b]. *)
+external clear_current_debug_location : llbuilder -> unit
+                                      = "llvm_clear_current_debug_location"
+
+(** [current_debug_location b] returns the current debug location, or None
+    if none is currently set.
+    See the method [llvm::IRBuilder::GetDebugLocation]. *)
+external current_debug_location : llbuilder -> llvalue option
+                                = "llvm_current_debug_location"
+
+(** [set_inst_debug_location b i] sets the current debug location of the builder
+    [b] to the instruction [i].
+    See the method [llvm::IRBuilder::SetInstDebugLocation]. *)
+external set_inst_debug_location : llbuilder -> llvalue -> unit
+                                 = "llvm_set_inst_debug_location"
 
 (** {7 Terminators} *)
 
@@ -1500,6 +1611,20 @@ external build_switch : llvalue -> llbasicblock -> int -> llbuilder -> llvalue
 external add_case : llvalue -> llvalue -> llbasicblock -> unit
                   = "llvm_add_case"
 
+(** [build_indirect_br addr count b] creates a
+    [indirectbr %addr]
+    instruction at the position specified by the instruction builder [b] with
+    space reserved for [count] destinations.
+    See the method [llvm::LLVMBuilder::CreateIndirectBr]. *)
+external build_indirect_br : llvalue -> int -> llbuilder -> llvalue
+                           = "llvm_build_indirect_br"
+
+(** [add_destination br bb] adds the basic block [bb] as a possible branch
+    location for the indirectbr instruction [br].
+    See the method [llvm::IndirectBrInst::addDestination]. **)
+external add_destination : llvalue -> llbasicblock -> unit
+                         = "llvm_add_destination"
+
 (** [build_invoke fn args tobb unwindbb name b] creates an
     [%name = invoke %fn(args) to %tobb unwind %unwindbb]
     instruction at the position specified by the instruction builder [b].