Add support for inserting inline asm to ocaml.
[oota-llvm.git] / bindings / ocaml / llvm / llvm.mli
index c7fa30a96f2dfc8dce1ed860e5cd9224cce2ad14..c8c48f3c5376dfc42d984babc6eaf938b527ff7d 100644 (file)
@@ -274,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"
@@ -502,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} *)
 
@@ -517,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"
@@ -950,6 +964,12 @@ 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"
@@ -1003,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. *)