Adding bindings for target triple and data layout.
[oota-llvm.git] / bindings / ocaml / llvm / llvm_ocaml.c
index 5cd9526f560468f7973147b2dc65af76bc0e7ee5..d095550962297737f29e6fa720bd8d92f4f4d028 100644 (file)
@@ -18,7 +18,6 @@
 #include "llvm-c/Core.h"
 #include "caml/alloc.h"
 #include "caml/custom.h"
-#include "caml/mlvalues.h"
 #include "caml/memory.h"
 #include "caml/fail.h"
 #include "caml/callback.h"
@@ -37,7 +36,7 @@ CAMLprim value llvm_register_core_exns(value IoError) {
   return Val_unit;
 }
 
-void llvm_raise(value Prototype, char *Message) {
+static void llvm_raise(value Prototype, char *Message) {
   CAMLparam1(Prototype);
   CAMLlocal1(CamlMessage);
   
@@ -45,6 +44,7 @@ void llvm_raise(value Prototype, char *Message) {
   LLVMDisposeMessage(Message);
   
   raise_with_arg(Prototype, CamlMessage);
+  abort(); /* NOTREACHED */
   CAMLnoreturn;
 }
 
@@ -62,6 +62,28 @@ CAMLprim value llvm_dispose_module(LLVMModuleRef M) {
   return Val_unit;
 }
 
+/* llmodule -> string */
+CAMLprim value llvm_target_triple(LLVMModuleRef M) {
+  return copy_string(LLVMGetTarget(M));
+}
+
+/* string -> llmodule -> unit */
+CAMLprim value llvm_set_target_triple(value Trip, LLVMModuleRef M) {
+  LLVMSetTarget(M, String_val(Trip));
+  return Val_unit;
+}
+
+/* llmodule -> string */
+CAMLprim value llvm_data_layout(LLVMModuleRef M) {
+  return copy_string(LLVMGetDataLayout(M));
+}
+
+/* string -> llmodule -> unit */
+CAMLprim value llvm_set_data_layout(value Layout, LLVMModuleRef M) {
+  LLVMSetDataLayout(M, String_val(Layout));
+  return Val_unit;
+}
+
 /* string -> lltype -> llmodule -> bool */
 CAMLprim value llvm_add_type_name(value Name, LLVMTypeRef Ty, LLVMModuleRef M) {
   int res = LLVMAddTypeName(M, String_val(Name), Ty);
@@ -77,7 +99,7 @@ CAMLprim value llvm_delete_type_name(value Name, LLVMModuleRef M) {
 
 /*===-- Types -------------------------------------------------------------===*/
 
-/* lltype -> type_kind */
+/* lltype -> TypeKind.t */
 CAMLprim value llvm_classify_type(LLVMTypeRef Ty) {
   return Val_int(LLVMGetTypeKind(Ty));
 }
@@ -234,7 +256,7 @@ CAMLprim LLVMTypeRef llvm_opaque_type(value Unit) {
 
 #define Typehandle_val(v)  (*(LLVMTypeHandleRef *)(Data_custom_val(v)))
 
-void llvm_finalize_handle(value TH) {
+static void llvm_finalize_handle(value TH) {
   LLVMDisposeTypeHandle(Typehandle_val(TH));
 }
 
@@ -361,14 +383,14 @@ CAMLprim LLVMValueRef llvm_const_vector(value ElementVals) {
 
 /*--... Constant expressions ...............................................--*/
 
-/* int_predicate -> llvalue -> llvalue -> llvalue */
+/* Icmp.t -> llvalue -> llvalue -> llvalue */
 CAMLprim LLVMValueRef llvm_const_icmp(value Pred,
                                       LLVMValueRef LHSConstant,
                                       LLVMValueRef RHSConstant) {
   return LLVMConstICmp(Int_val(Pred) + LLVMIntEQ, LHSConstant, RHSConstant);
 }
 
-/* real_predicate -> llvalue -> llvalue -> llvalue */
+/* Fcmp.t -> llvalue -> llvalue -> llvalue */
 CAMLprim LLVMValueRef llvm_const_fcmp(value Pred,
                                       LLVMValueRef LHSConstant,
                                       LLVMValueRef RHSConstant) {
@@ -388,12 +410,12 @@ CAMLprim value llvm_is_declaration(LLVMValueRef Global) {
   return Val_bool(LLVMIsDeclaration(Global));
 }
 
-/* llvalue -> linkage */
+/* llvalue -> Linkage.t */
 CAMLprim value llvm_linkage(LLVMValueRef Global) {
   return Val_int(LLVMGetLinkage(Global));
 }
 
-/* linkage -> llvalue -> unit */
+/* Linkage.t -> llvalue -> unit */
 CAMLprim value llvm_set_linkage(value Linkage, LLVMValueRef Global) {
   LLVMSetLinkage(Global, Int_val(Linkage));
   return Val_unit;
@@ -410,12 +432,12 @@ CAMLprim value llvm_set_section(value Section, LLVMValueRef Global) {
   return Val_unit;
 }
 
-/* llvalue -> visibility */
+/* llvalue -> Visibility.t */
 CAMLprim value llvm_visibility(LLVMValueRef Global) {
   return Val_int(LLVMGetVisibility(Global));
 }
 
-/* visibility -> llvalue -> unit */
+/* Visibility.t -> llvalue -> unit */
 CAMLprim value llvm_set_visibility(value Viz, LLVMValueRef Global) {
   LLVMSetVisibility(Global, Int_val(Viz));
   return Val_unit;
@@ -668,7 +690,7 @@ CAMLprim value llvm_incoming(LLVMValueRef PhiNode) {
 
 #define Builder_val(v)  (*(LLVMBuilderRef *)(Data_custom_val(v)))
 
-void llvm_finalize_builder(value B) {
+static void llvm_finalize_builder(value B) {
   LLVMDisposeBuilder(Builder_val(B));
 }
 
@@ -681,24 +703,29 @@ static struct custom_operations builder_ops = {
   custom_deserialize_default
 };
 
+static value alloc_builder(LLVMBuilderRef B) {
+  value V = alloc_custom(&builder_ops, sizeof(LLVMBuilderRef), 0, 1);
+  Builder_val(V) = B;
+  return V;
+}
+
+/* unit-> llbuilder */
+CAMLprim value llvm_builder(value Unit) {
+  return alloc_builder(LLVMCreateBuilder());
+}
+
 /* llvalue -> llbuilder */
 CAMLprim value llvm_builder_before(LLVMValueRef Inst) {
-  value V;
   LLVMBuilderRef B = LLVMCreateBuilder();
   LLVMPositionBuilderBefore(B, Inst);
-  V = alloc_custom(&builder_ops, sizeof(LLVMBuilderRef), 0, 1);
-  Builder_val(V) = B;
-  return V;
+  return alloc_builder(B);
 }
 
 /* llbasicblock -> llbuilder */
 CAMLprim value llvm_builder_at_end(LLVMBasicBlockRef BB) {
-  value V;
   LLVMBuilderRef B = LLVMCreateBuilder();
   LLVMPositionBuilderAtEnd(B, BB);
-  V = alloc_custom(&builder_ops, sizeof(LLVMBuilderRef), 0, 1);
-  Builder_val(V) = B;
-  return V;
+  return alloc_builder(B);
 }
 
 /* llvalue -> llbuilder -> unit */
@@ -1006,7 +1033,7 @@ CAMLprim LLVMValueRef llvm_build_bitcast(LLVMValueRef X, LLVMTypeRef Ty,
 
 /*--... Comparisons ........................................................--*/
 
-/* int_predicate -> llvalue -> llvalue -> string -> llbuilder -> llvalue */
+/* Icmp.t -> llvalue -> llvalue -> string -> llbuilder -> llvalue */
 CAMLprim LLVMValueRef llvm_build_icmp(value Pred,
                                       LLVMValueRef LHS, LLVMValueRef RHS,
                                       value Name, value B) {
@@ -1014,7 +1041,7 @@ CAMLprim LLVMValueRef llvm_build_icmp(value Pred,
                        String_val(Name));
 }
 
-/* real_predicate -> llvalue -> llvalue -> string -> llbuilder -> llvalue */
+/* Fcmp.t -> llvalue -> llvalue -> string -> llbuilder -> llvalue */
 CAMLprim LLVMValueRef llvm_build_fcmp(value Pred,
                                       LLVMValueRef LHS, LLVMValueRef RHS,
                                       value Name, value B) {