Add (very basic) bindings for ModuleProvider.
[oota-llvm.git] / bindings / ocaml / llvm / llvm.ml
index 0361001b6eba3d57ece76512800136eb0f8dfaae..6ede17978bff2a418ca51334cf3bb986fbd42883 100644 (file)
@@ -5,22 +5,16 @@
  * This file was developed by Gordon Henriksen and is distributed under the
  * University of Illinois Open Source License. See LICENSE.TXT for details.
  *
- *===----------------------------------------------------------------------===
- *
- * This interface provides an ocaml API for the LLVM intermediate
- * representation, the classes in the VMCore library.
- *
  *===----------------------------------------------------------------------===*)
 
 
-(* These abstract types correlate directly to the LLVM VMCore classes. *)
 type llmodule
 type lltype
 type lltypehandle
 type llvalue
-type llbasicblock (* These are actually values, but
-                     benefit from type checking. *)
+type llbasicblock
 type llbuilder
+type llmoduleprovider
 
 type type_kind =
   Void_type
@@ -93,19 +87,10 @@ type real_predicate =
 
 (*===-- Modules -----------------------------------------------------------===*)
 
-(* Creates a module with the supplied module ID. Modules are not garbage
-   collected; it is mandatory to call dispose_module to free memory. *)
 external create_module : string -> llmodule = "llvm_create_module"
-
-(* Disposes a module. All references to subordinate objects are invalidated;
-   referencing them will invoke undefined behavior. *)
 external dispose_module : llmodule -> unit = "llvm_dispose_module"
-
-(* 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 returns false. *)
 external define_type_name : string -> lltype -> llmodule -> bool
                           = "llvm_add_type_name"
-
 external delete_type_name : string -> llmodule -> unit
                           = "llvm_delete_type_name"
 
@@ -113,8 +98,6 @@ external delete_type_name : string -> llmodule -> unit
 (*===-- Types -------------------------------------------------------------===*)
 
 external classify_type : lltype -> type_kind = "llvm_classify_type"
-external refine_abstract_type : lltype -> lltype -> unit
-                              = "llvm_refine_abstract_type"
 
 (*--... Operations on integer types ........................................--*)
 external _i1_type : unit -> lltype = "llvm_i1_type"
@@ -146,7 +129,6 @@ let fp128_type = _fp128_type ()
 let ppc_fp128_type = _ppc_fp128_type ()
 
 (*--... Operations on function types .......................................--*)
-(* FIXME: handle parameter attributes *)
 external function_type : lltype -> lltype array -> lltype = "llvm_function_type"
 external var_arg_function_type : lltype -> lltype array -> lltype
                                = "llvm_var_arg_function_type"
@@ -268,13 +250,19 @@ external visibility : llvalue -> visibility = "llvm_visibility"
 external set_visibility : visibility -> llvalue -> unit = "llvm_set_visibility"
 external alignment : llvalue -> int = "llvm_alignment"
 external set_alignment : int -> llvalue -> unit = "llvm_set_alignment"
+external is_global_constant : llvalue -> bool = "llvm_is_global_constant"
+external set_global_constant : bool -> llvalue -> unit
+                             = "llvm_set_global_constant"
 
 (*--... Operations on global variables .....................................--*)
 external declare_global : lltype -> string -> llmodule -> llvalue
                         = "llvm_declare_global"
 external define_global : string -> llvalue -> llmodule -> llvalue
                        = "llvm_define_global"
+external lookup_global : string -> llmodule -> llvalue option
+                       = "llvm_lookup_global"
 external delete_global : llvalue -> unit = "llvm_delete_global"
+external has_initializer : llvalue -> bool = "llvm_has_initializer"
 external global_initializer : llvalue -> llvalue = "LLVMGetInitializer"
 external set_initializer : llvalue -> llvalue -> unit = "llvm_set_initializer"
 external remove_initializer : llvalue -> unit = "llvm_remove_initializer"
@@ -286,6 +274,8 @@ external declare_function : string -> lltype -> llmodule -> llvalue
                           = "llvm_declare_function"
 external define_function : string -> lltype -> llmodule -> llvalue
                          = "llvm_define_function"
+external lookup_function : string -> llmodule -> llvalue option
+                         = "llvm_lookup_function"
 external delete_function : llvalue -> unit = "llvm_delete_function"
 external params : llvalue -> llvalue array = "llvm_params"
 external param : llvalue -> int -> llvalue = "llvm_param"
@@ -293,6 +283,8 @@ external is_intrinsic : llvalue -> bool = "llvm_is_intrinsic"
 external function_call_conv : llvalue -> int = "llvm_function_call_conv"
 external set_function_call_conv : int -> llvalue -> unit
                                 = "llvm_set_function_call_conv"
+external collector : llvalue -> string option = "llvm_collector"
+external set_collector : string option -> llvalue -> unit = "llvm_set_collector"
 
 (* TODO: param attrs *)
 
@@ -307,6 +299,11 @@ external value_of_block : llbasicblock -> llvalue = "LLVMBasicBlockAsValue"
 external value_is_block : llvalue -> bool = "llvm_value_is_block"
 external block_of_value : llvalue -> llbasicblock = "LLVMValueAsBasicBlock"
 
+(*--... Operations on phi nodes ............................................--*)
+external add_incoming : (llvalue * llbasicblock) -> llvalue -> unit
+                      = "llvm_add_incoming"
+external incoming : llvalue -> (llvalue * llbasicblock) list = "llvm_incoming"
+
 
 (*===-- Instruction builders ----------------------------------------------===*)
 external builder_before : llvalue -> llbuilder = "llvm_builder_before"
@@ -415,7 +412,8 @@ external build_fcmp : real_predicate -> llvalue -> llvalue -> string ->
                       llbuilder -> llvalue = "llvm_build_fcmp"
 
 (*--... Miscellaneous instructions .........................................--*)
-external build_phi : lltype -> string -> llbuilder -> llvalue = "llvm_build_phi"
+external build_phi : (llvalue * llbasicblock) list -> string -> llbuilder ->
+                     llvalue = "llvm_build_phi"
 external build_call : llvalue -> llvalue array -> string -> llbuilder -> llvalue
                     = "llvm_build_call"
 external build_select : llvalue -> llvalue -> llvalue -> string -> llbuilder ->
@@ -430,6 +428,13 @@ external build_shufflevector : llvalue -> llvalue -> llvalue -> string ->
                                llbuilder -> llvalue = "llvm_build_shufflevector"
 
 
+(*===-- Module providers --------------------------------------------------===*)
+external create_module_provider : llmodule -> llmoduleprovider
+                                = "LLVMCreateModuleProviderForExistingModule"
+external dispose_module_provider : llmoduleprovider -> unit
+                                 = "llvm_dispose_module_provider"
+
+
 (*===-- Non-Externs -------------------------------------------------------===*)
 (* These functions are built using the externals, so must be declared late.   *)
 
@@ -444,6 +449,7 @@ let concat2 sep arr =
   !s
 
 let rec string_of_lltype ty =
+  (* FIXME: stop infinite recursion! :) *)
   match classify_type ty with
     Integer_type -> "i" ^ string_of_int (integer_bitwidth ty)
   | Pointer_type -> (string_of_lltype (element_type ty)) ^ "*"