Cleanup some comments in the OCaml bindings.
[oota-llvm.git] / bindings / ocaml / llvm / llvm.mli
index 4f3bee7fabeb6151dd35e095e216413bc42059fb..3ed9d273293c4fbb5f071bed375d1161bdb0986f 100644 (file)
@@ -1,9 +1,9 @@
-(*===-- tools/ml/llvm.ml - LLVM Ocaml Interface ---------------------------===*
+(*===-- llvm/llvm.mli - LLVM Ocaml Interface -------------------------------===*
  *
  *                     The LLVM Compiler Infrastructure
  *
- * This file was developed by Gordon Henriksen and is distributed under the
- * University of Illinois Open Source License. See LICENSE.TXT for details.
+ * This file is distributed under the University of Illinois Open Source
+ * License. See LICENSE.TXT for details.
  *
  *===----------------------------------------------------------------------===
  *
@@ -95,16 +95,18 @@ end
 (* The following calling convention values may be accessed with
    [function_call_conv f] and [set_function_call_conv conv f]. Calling
    conventions are open-ended. *)
-val ccc : int             (** [ccc] is the C calling convention. **)
-val fastcc : int          (** [fastcc] is the calling convention to allow LLVM
+module CallConv : sig
+  val c : int             (** [c] is the C calling convention. **)
+  val fast : int          (** [fast] is the calling convention to allow LLVM
                               maximum optimization opportunities. Use only with
                               internal linkage. **)
-val coldcc : int          (** [coldcc] is the calling convention for
+  val cold : int          (** [cold] is the calling convention for
                               callee-save. **)
-val x86_stdcallcc : int   (** [x86_stdcallcc] is the familiar stdcall calling
+  val x86_stdcall : int   (** [x86_stdcall] is the familiar stdcall calling
                               convention from C. **)
-val x86_fastcallcc : int  (** [x86_fastcallcc] is the familiar fastcall calling
+  val x86_fastcall : int  (** [x86_fastcall] is the familiar fastcall calling
                               convention from C. **)
+end
 
 (** The predicate for an integer comparison ([icmp]) instruction.
     See the [llvm::ICmpInst::Predicate] enumeration. **)
@@ -160,6 +162,27 @@ external create_module : string -> llmodule = "llvm_create_module"
     [llvm::Module::~Module]. **)
 external dispose_module : llmodule -> unit = "llvm_dispose_module"
 
+(** [target_triple m] is the target specifier for the module [m], something like
+    [i686-apple-darwin8]. See the method [llvm::Module::getTargetTriple]. **)
+external target_triple: llmodule -> string
+                      = "llvm_target_triple"
+
+(** [target_triple triple m] changes the target specifier for the module [m] to
+    the string [triple]. See the method [llvm::Module::setTargetTriple]. **)
+external set_target_triple: string -> llmodule -> unit
+                          = "llvm_set_target_triple"
+
+(** [data_layout m] is the data layout specifier for the module [m], something
+    like [e-p:32:32:32-i1:8:8-i8:8:8-i16:16:16-...-a0:0:64-f80:128:128]. See the
+    method [llvm::Module::getDataLayout]. **)
+external data_layout: llmodule -> string
+                    = "llvm_data_layout"
+
+(** [set_data_layout s m] changes the data layout specifier for the module [m]
+    to the string [s]. See the method [llvm::Module::setDataLayout]. **)
+external set_data_layout: string -> llmodule -> unit
+                        = "llvm_set_data_layout"
+
 (** [define_type_name name ty m] 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 [false] is returned. See the [llvm::Module::addTypeName]
@@ -831,6 +854,20 @@ external value_is_block : llvalue -> bool = "llvm_value_is_block"
 (** [block_of_value v] losslessly casts [v] to an [llbasicblock]. **)
 external block_of_value : llvalue -> llbasicblock = "LLVMValueAsBasicBlock"
 
+(*--... Operations on call sites ...........................................--*)
+
+(** [inst_call_conv ci] is the calling convention for the call or invoke
+    instruction [ci], which may be one of the values from the module [CallConv].
+    See the method [CallSite:: **)
+external instruction_call_conv: llvalue -> int
+                              = "llvm_instruction_call_conv"
+
+(** [set_inst_call_conv cc ci] sets the calling convention for the call or
+    invoke instruction [ci] to the integer [cc], which can be one of the values
+    from the module [CallConv]. See the method [CallSite::]. **)
+external set_instruction_call_conv: int -> llvalue -> unit
+                                  = "llvm_set_instruction_call_conv"
+
 (*--... Operations on phi nodes ............................................--*)
 
 (** [add_incoming (v, bb) pn] adds the value [v] to the phi node [pn] for use
@@ -845,6 +882,12 @@ external incoming : llvalue -> (llvalue * llbasicblock) list = "llvm_incoming"
 
 (*===-- Instruction builders ----------------------------------------------===*)
 
+(** [builder] creates an instruction builder with no position. It is invalid to
+    use this builder until its position is set with [position_before] or
+    [position_at_end]. See the constructor for [llvm::LLVMBuilder]. **)
+external builder: unit-> llbuilder
+                = "llvm_builder"
+
 (** [builder_before ins] creates an instruction builder positioned before the
     instruction [isn]. See the constructor for [llvm::LLVMBuilder]. **)
 external builder_before : llvalue -> llbuilder = "llvm_builder_before"
@@ -1089,7 +1132,7 @@ external build_load : llvalue -> string -> llbuilder -> llvalue
 external build_store : llvalue -> llvalue -> llbuilder -> llvalue
                      = "llvm_build_store"
 
-(** [build_store p indices name b] creates a
+(** [build_gep p indices name b] creates a
     [%name = gep %p, indices...]
     instruction at the position specified by the instruction builder [b].
     See the method [llvm::LLVMBuilder::CreateGetElementPtr]. **)