Remove unions from the ocaml bindings.
[oota-llvm.git] / bindings / ocaml / llvm / llvm.mli
index c8c48f3c5376dfc42d984babc6eaf938b527ff7d..ba3bbe248b716ae4630503ce5eb885d0fceb9599 100644 (file)
@@ -39,6 +39,9 @@ type lltypehandle
     This type covers a wide range of subclasses. *)
 type llvalue
 
+(** Used to store users and usees of values. See the [llvm::Use] class. *)
+type lluse
+
 (** A basic block in LLVM IR. See the [llvm::BasicBlock] class. *)
 type llbasicblock
 
@@ -46,10 +49,6 @@ type llbasicblock
     class. *)
 type llbuilder
 
-(** Used to provide a module to JIT or interpreter.
-    See the [llvm::ModuleProvider] class. *)
-type llmoduleprovider
-
 (** Used to efficiently handle large buffers of read-only binary data.
     See the [llvm::MemoryBuffer] class. *)
 type llmemorybuffer
@@ -73,7 +72,6 @@ module TypeKind : sig
   | Opaque
   | Vector
   | Metadata
-  | Union
 end
 
 (** The linkage of a global value, accessed with {!linkage} and
@@ -140,11 +138,13 @@ module Attribute : sig
   | Optsize
   | Ssp
   | Sspreq
+  | Alignment of int
   | Nocapture
   | Noredzone
   | Noimplicitfloat
   | Naked
   | Inlinehint
+  | Stackalignment of int
 end
 
 (** The predicate for an integer comparison ([icmp]) instruction.
@@ -283,6 +283,11 @@ external type_by_name : llmodule -> string -> lltype option
     error. See the method [llvm::Module::dump]. *)
 external dump_module : llmodule -> unit = "llvm_dump_module"
 
+(** [set_module_inline_asm m asm] sets the inline assembler for the module. See
+    the method [llvm::Module::setModuleInlineAsm]. *)
+external set_module_inline_asm : llmodule -> string -> unit
+                               = "llvm_set_module_inline_asm"
+
 
 (** {6 Types} *)
 
@@ -402,19 +407,6 @@ external struct_element_types : lltype -> lltype array
 external is_packed : lltype -> bool = "llvm_is_packed"
 
 
-(** {7 Operations on union types} *)
-
-(** [union_type context tys] returns the union type in the context [context]
-    containing the types in the array [tys]. See the method
-    [llvm::UnionType::get] *)
-external union_type : llcontext -> lltype array -> lltype = "llvm_union_type"
-
-(** [union_element_types uty] returns the constituent types of the union type
-    [uty]. See the method [llvm::UnionType::getElementType]. *)
-external union_element_types : lltype -> lltype array
-                             = "llvm_union_element_types"
-
-
 (** {7 Operations on pointer, vector, and array types} *)
 
 (** [array_type ty n] returns the array type containing [n] elements of type
@@ -513,6 +505,53 @@ external replace_all_uses_with : llvalue -> llvalue -> unit
                                = "LLVMReplaceAllUsesWith"
 
 
+(* {6 Uses} *)
+
+(** [use_begin v] returns the first position in the use list for the value [v].
+    [use_begin] and [use_succ] can e used to iterate over the use list in order.
+    See the method [llvm::Value::use_begin]. *)
+external use_begin : llvalue -> lluse option = "llvm_use_begin"
+
+(** [use_succ u] returns the use list position succeeding [u].
+    See the method [llvm::use_value_iterator::operator++]. *)
+external use_succ : lluse -> lluse option = "llvm_use_succ"
+
+(** [user u] returns the user of the use [u].
+    See the method [llvm::Use::getUser]. *)
+external user : lluse -> llvalue = "llvm_user"
+
+(** [used_value u] returns the usee of the use [u].
+    See the method [llvm::Use::getUsedValue]. *)
+external used_value : lluse -> llvalue = "llvm_used_value"
+
+(** [iter_uses f v] applies function [f] to each of the users of the value [v]
+    in order. Tail recursive. *)
+val iter_uses : (lluse -> unit) -> llvalue -> unit
+
+(** [fold_left_uses f init v] is [f (... (f init u1) ...) uN] where
+    [u1,...,uN] are the users of the value [v]. Tail recursive. *)
+val fold_left_uses : ('a -> lluse -> 'a) -> 'a -> llvalue -> 'a
+
+(** [fold_right_uses f v init] is [f u1 (... (f uN init) ...)] where
+    [u1,...,uN] are the users of the value [v]. Not tail recursive. *)
+val fold_right_uses : (lluse -> 'a -> 'a) -> llvalue -> 'a -> 'a
+
+
+(* {6 Users} *)
+
+(** [operand v i] returns the operand at index [i] for the value [v]. See the
+    method [llvm::User::getOperand]. *)
+external operand : llvalue -> int -> llvalue = "llvm_operand"
+
+(** [set_operand v i o] sets the operand of the value [v] at the index [i] to
+    the value [o].
+    See the method [llvm::User::setOperand]. *)
+external set_operand : llvalue -> int -> llvalue -> unit = "llvm_set_operand"
+
+(** [num_operands v] returns the number of operands for the value [v].
+    See the method [llvm::User::getNumOperands]. *)
+external num_operands : llvalue -> int = "llvm_num_operands"
+
 (** {7 Operations on constants of (mostly) any type} *)
 
 (** [is_constant v] returns [true] if the value [v] is a constant, [false]
@@ -644,10 +683,6 @@ external const_packed_struct : llcontext -> llvalue array -> llvalue
     values [elts]. See the method [llvm::ConstantVector::get]. *)
 external const_vector : llvalue array -> llvalue = "llvm_const_vector"
 
-(** [const_union ty v] returns the union constant of type [union_type tys] and
-    containing the value [v]. See the method [llvm::ConstantUnion::get]. *)
-external const_union : lltype -> llvalue -> llvalue = "LLVMConstUnion"
-
 
 (** {7 Constant expressions} *)
 
@@ -946,7 +981,7 @@ external const_insertelement : llvalue -> llvalue -> llvalue -> llvalue
                              = "LLVMConstInsertElement"
 
 (** [const_shufflevector a b mask] returns a constant [shufflevector].
-    See the LLVM Language Reference for details on the [sufflevector]
+    See the LLVM Language Reference for details on the [shufflevector]
     instruction.
     See the method [llvm::ConstantExpr::getShuffleVector]. *)
 external const_shufflevector : llvalue -> llvalue -> llvalue -> llvalue
@@ -1029,10 +1064,11 @@ external set_alignment : int -> llvalue -> unit = "llvm_set_alignment"
 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. *)
+(** [declare_qualified_global ty name addrspace m] returns a new global variable
+    of type [ty] and with name [name] in module [m] in the address space
+    [addrspace]. 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"
@@ -1044,9 +1080,9 @@ external declare_qualified_global : lltype -> string -> int -> llmodule ->
 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.
+(** [define_qualified_global name init addrspace m] returns a new global with
+    name [name] and initializer [init] in module [m] in the address space
+    [addrspace]. If the named global already exists, it is renamed.
     See the constructor of [llvm::GlobalVariable]. *)
 external define_qualified_global : string -> llvalue -> int -> llmodule ->
                                    llvalue
@@ -1140,6 +1176,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
@@ -1232,13 +1277,11 @@ external set_gc : string option -> llvalue -> unit = "llvm_set_gc"
 
 (** [add_function_attr f a] adds attribute [a] to the return type of function
     [f]. *)
-external add_function_attr : llvalue -> Attribute.t -> unit
-                           = "llvm_add_function_attr"
+val add_function_attr : llvalue -> Attribute.t -> unit
 
 (** [remove_function_attr f a] removes attribute [a] from the return type of
     function [f]. *)
-external remove_function_attr : llvalue -> Attribute.t -> unit
-                              = "llvm_remove_function_attr"
+val remove_function_attr : llvalue -> Attribute.t -> unit
 
 (** {7 Operations on params} *)
 
@@ -1293,11 +1336,10 @@ val rev_iter_params : (llvalue -> unit) -> llvalue -> unit
 val fold_right_params : (llvalue -> 'a -> 'a) -> llvalue -> 'a -> 'a
 
 (** [add_param p a] adds attribute [a] to parameter [p]. *)
-external add_param_attr : llvalue -> Attribute.t -> unit = "llvm_add_param_attr"
+val add_param_attr : llvalue -> Attribute.t -> unit
 
 (** [remove_param_attr p a] removes attribute [a] from parameter [p]. *)
-external remove_param_attr : llvalue -> Attribute.t -> unit
-                           = "llvm_remove_param_attr"
+val remove_param_attr : llvalue -> Attribute.t -> unit
 
 (** [set_param_alignment p a] set the alignment of parameter [p] to [a]. *)
 external set_param_alignment : llvalue -> int -> unit
@@ -1449,14 +1491,12 @@ external set_instruction_call_conv: int -> llvalue -> unit
 (** [add_instruction_param_attr ci i a] adds attribute [a] to the [i]th
     parameter of the call or invoke instruction [ci]. [i]=0 denotes the return
     value. *)
-external add_instruction_param_attr : llvalue -> int -> Attribute.t -> unit
-  = "llvm_add_instruction_param_attr"
+val add_instruction_param_attr : llvalue -> int -> Attribute.t -> unit
 
 (** [remove_instruction_param_attr ci i a] removes attribute [a] from the
     [i]th parameter of the call or invoke instruction [ci]. [i]=0 denotes the
     return value. *)
-external remove_instruction_param_attr : llvalue -> int -> Attribute.t -> unit
-  = "llvm_remove_instruction_param_attr"
+val remove_instruction_param_attr : llvalue -> int -> Attribute.t -> unit
 
 (** {Operations on call instructions (only)} *)
 
@@ -2147,20 +2187,6 @@ external build_is_not_null : llvalue -> string -> llbuilder -> llvalue
 external build_ptrdiff : llvalue -> llvalue -> string -> llbuilder -> llvalue
                        = "llvm_build_ptrdiff"
 
-(** {6 Module providers} *)
-
-module ModuleProvider : sig
-  (** [create_module_provider m] encapsulates [m] in a module provider and takes
-      ownership of the module. See the constructor
-      [llvm::ExistingModuleProvider::ExistingModuleProvider]. *)
-  external create : llmodule -> llmoduleprovider
-                  = "LLVMCreateModuleProviderForExistingModule"
-  
-  (** [dispose_module_provider mp] destroys the module provider [mp] as well as
-      the contained module. *)
-  external dispose : llmoduleprovider -> unit = "llvm_dispose_module_provider"
-end
-
 
 (** {6 Memory buffers} *)
 
@@ -2192,12 +2218,12 @@ module PassManager : sig
       See the constructor of [llvm::PassManager]. *)
   external create : unit -> [ `Module ] t = "llvm_passmanager_create"
   
-  (** [PassManager.create_function mp] constructs a new function-by-function
-      pass pipeline over the module provider [mp]. It does not take ownership of
-      [mp]. This type of pipeline is suitable for code generation and JIT
-      compilation tasks.
+  (** [PassManager.create_function m] constructs a new function-by-function
+      pass pipeline over the module [m]. It does not take ownership of [m].
+      This type of pipeline is suitable for code generation and JIT compilation
+      tasks.
       See the constructor of [llvm::FunctionPassManager]. *)
-  external create_function : llmoduleprovider -> [ `Function ] t
+  external create_function : llmodule -> [ `Function ] t
                            = "LLVMCreateFunctionPassManager"
   
   (** [run_module m pm] initializes, executes on the module [m], and finalizes
@@ -2227,7 +2253,7 @@ module PassManager : sig
   external finalize : [ `Function ] t -> bool = "llvm_passmanager_finalize"
   
   (** Frees the memory of a pass pipeline. For function pipelines, does not free
-      the module provider.
+      the module.
       See the destructor of [llvm::BasePassManager]. *)
   external dispose : [< any ] t -> unit = "llvm_passmanager_dispose"
 end