C and Objective Caml bindings for PassManagers.
[oota-llvm.git] / bindings / ocaml / llvm / llvm_ocaml.c
index d095550962297737f29e6fa720bd8d92f4f4d028..01e83e8819c67f348342a8f5ca7042c760e245dc 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.                                      *|
 |*                                                                            *|
 |*===----------------------------------------------------------------------===*|
 |*                                                                            *|
@@ -45,7 +45,9 @@ static void llvm_raise(value Prototype, char *Message) {
   
   raise_with_arg(Prototype, CamlMessage);
   abort(); /* NOTREACHED */
-  CAMLnoreturn;
+#ifdef CAMLnoreturn
+  CAMLnoreturn; /* Silences warnings, but is missing in some versions. */
+#endif
 }
 
 
@@ -96,6 +98,12 @@ CAMLprim value llvm_delete_type_name(value Name, LLVMModuleRef M) {
   return Val_unit;
 }
 
+/* llmodule -> unit */
+CAMLprim value llvm_dump_module(LLVMModuleRef M) {
+  LLVMDumpModule(M);
+  return Val_unit;
+}
+
 
 /*===-- Types -------------------------------------------------------------===*/
 
@@ -652,6 +660,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 */
@@ -1159,3 +1180,37 @@ CAMLprim value llvm_memorybuffer_dispose(LLVMMemoryBufferRef MemBuf) {
   return Val_unit;
 }
 
+/*===-- Pass Managers -----------------------------------------------------===*/
+
+/* unit -> [ `Module ] PassManager.t */
+CAMLprim LLVMPassManagerRef llvm_passmanager_create(value Unit) {
+  return LLVMCreatePassManager();
+}
+
+/* llmodule -> [ `Function ] PassManager.t -> bool */
+CAMLprim value llvm_passmanager_run_module(LLVMModuleRef M,
+                                           LLVMPassManagerRef PM) {
+  return Val_bool(LLVMRunPassManager(PM, M));
+}
+
+/* [ `Function ] PassManager.t -> bool */
+CAMLprim value llvm_passmanager_initialize(LLVMPassManagerRef FPM) {
+  return Val_bool(LLVMInitializeFunctionPassManager(FPM));
+}
+
+/* llvalue -> [ `Function ] PassManager.t -> bool */
+CAMLprim value llvm_passmanager_run_function(LLVMValueRef F,
+                                             LLVMPassManagerRef FPM) {
+  return Val_bool(LLVMRunFunctionPassManager(FPM, F));
+}
+
+/* [ `Function ] PassManager.t -> bool */
+CAMLprim value llvm_passmanager_finalize(LLVMPassManagerRef FPM) {
+  return Val_bool(LLVMFinalizeFunctionPassManager(FPM));
+}
+
+/* PassManager.any PassManager.t -> unit */
+CAMLprim value llvm_passmanager_dispose(LLVMPassManagerRef PM) {
+  LLVMDisposePassManager(PM);
+  return Val_unit;
+}