Adding bindings for memory buffers and module providers. Switching
[oota-llvm.git] / bindings / ocaml / llvm / llvm.mli
index ac83e428098ea9f4463691cdbe65d394b909b45e..546ab4579feecfe2d5459bf43e6988cbe5c48fc9 100644 (file)
@@ -40,6 +40,14 @@ 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
+
 (** The kind of an [lltype], the result of [classify_type ty]. See the 
     [llvm::Type::TypeID] enumeration. **)
 type type_kind =
@@ -126,6 +134,8 @@ type real_predicate =
 | Fcmp_une
 | Fcmp_true
 
+exception IoError of string
+
 
 (*===-- Modules -----------------------------------------------------------===*)
 
@@ -255,8 +265,15 @@ external is_packed : lltype -> bool = "llvm_is_packed"
 external array_type : lltype -> int -> lltype = "llvm_array_type"
 
 (** [pointer_type ty] returns the pointer type referencing objects of type
-    [ty]. See the method [llvm::PointerType::get]. **)
-external pointer_type : lltype -> lltype = "LLVMPointerType"
+    [ty] in the default address space (0).
+    See the method [llvm::PointerType::getUnqual]. **)
+external pointer_type : lltype -> lltype = "llvm_pointer_type"
+
+(** [qualified_pointer_type ty as] returns the pointer type referencing objects
+    of type [ty] in address space [as].
+    See the method [llvm::PointerType::get]. **)
+external qualified_pointer_type : lltype -> int -> lltype
+                                = "llvm_qualified_pointer_type"
 
 (** [vector_type ty n] returns the array type containing [n] elements of the
     primitive type [ty]. See the method [llvm::ArrayType::get]. **)
@@ -270,6 +287,10 @@ external element_type : lltype -> lltype = "LLVMGetElementType"
     See the method [llvm::ArrayType::getNumElements]. **)
 external array_length : lltype -> int = "llvm_array_length"
 
+(** [address_space pty] returns the address space qualifier of the pointer type
+    [pty]. See the method [llvm::PointerType::getAddressSpace]. **)
+external address_space : lltype -> int = "llvm_address_space"
+
 (** [element_type ty] returns the element count of the vector type [ty].
     See the method [llvm::VectorType::getNumElements]. **)
 external vector_size : lltype -> int = "llvm_vector_size"
@@ -754,6 +775,15 @@ external function_call_conv : llvalue -> int = "llvm_function_call_conv"
 external set_function_call_conv : int -> llvalue -> unit
                                 = "llvm_set_function_call_conv"
 
+(** [collector f] returns [Some name] if the function [f] has a garbage
+    collection algorithm specified and [None] otherwise.
+    See the method [llvm::Function::getCollector]. **)
+external collector : llvalue -> string option = "llvm_collector"
+
+(** [set_collector gc f] sets the collection algorithm for the function [f] to
+    [gc]. See the method [llvm::Function::setCollector]. **)
+external set_collector : string option -> llvalue -> unit = "llvm_set_collector"
+
 (*--... Operations on basic blocks .........................................--*)
 
 (** [basic_blocks fn] returns the basic blocks of the function [f].
@@ -1208,3 +1238,34 @@ external build_insertelement : llvalue -> llvalue -> llvalue -> string ->
     See the method [llvm::LLVMBuilder::CreateShuffleVector]. **)
 external build_shufflevector : llvalue -> llvalue -> llvalue -> string ->
                                llbuilder -> llvalue = "llvm_build_shufflevector"
+
+
+(*===-- 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
+  
+
+(*===-- Memory buffers ----------------------------------------------------===*)
+
+module MemoryBuffer : sig
+  (** [of_file p] is the memory buffer containing the contents of the file at 
+      path [p]. If the file could not be read, then [IoError msg] is raised. **)
+  external of_file : string -> llmemorybuffer = "llvm_memorybuffer_of_file"
+  
+  (** [stdin ()] is the memory buffer containing the contents of standard input.
+      If standard input is empty, then [IoError msg] is raised. **)
+  external of_stdin : unit -> llmemorybuffer = "llvm_memorybuffer_of_stdin"
+  
+  (** Disposes of a memory buffer. **)
+  external dispose : llmemorybuffer -> unit = "llvm_memorybuffer_dispose"
+end