Cleanup some comments in the OCaml bindings.
[oota-llvm.git] / bindings / ocaml / llvm / llvm_ocaml.c
index 506b5294dea03310cceaad6077d399c71d233a6d..f4e958d966ccfe1f82eef559f6c6734b3f05272f 100644 (file)
@@ -1,9 +1,9 @@
-/*===-- llvm_ocaml.h - LLVM Ocaml Glue --------------------------*- C++ -*-===*\
+/*===-- llvm_ocaml.c - LLVM Ocaml Glue --------------------------*- C++ -*-===*\
 |*                                                                            *|
 |*                     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.                                      *|
 |*                                                                            *|
 |*===----------------------------------------------------------------------===*|
 |*                                                                            *|
@@ -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,7 +44,10 @@ void llvm_raise(value Prototype, char *Message) {
   LLVMDisposeMessage(Message);
   
   raise_with_arg(Prototype, CamlMessage);
-  CAMLnoreturn;
+  abort(); /* NOTREACHED */
+#ifdef CAMLnoreturn
+  CAMLnoreturn; /* Silences warnings, but is missing in some versions. */
+#endif
 }
 
 
@@ -62,6 +64,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);
@@ -234,7 +258,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));
 }
 
@@ -630,6 +654,19 @@ CAMLprim value llvm_value_is_block(LLVMValueRef Val) {
   return Val_bool(LLVMValueIsBasicBlock(Val));
 }
 
+/*--... Operations on call sites ...........................................--*/
+
+/* llvalue -> int */
+CAMLprim value llvm_instruction_call_conv(LLVMValueRef Inst) {
+  return Val_int(LLVMGetInstructionCallConv(Inst));
+}
+
+/* int -> llvalue -> unit */
+CAMLprim value llvm_set_instruction_call_conv(value CC, LLVMValueRef Inst) {
+  LLVMSetInstructionCallConv(Inst, Int_val(CC));
+  return Val_unit;
+}
+
 /*--... Operations on phi nodes ............................................--*/
 
 /* (llvalue * llbasicblock) -> llvalue -> unit */
@@ -668,7 +705,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 +718,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 */