IR: Give 'DI' prefix to debug info metadata
[oota-llvm.git] / bindings / ocaml / analysis / analysis_ocaml.c
index e57c5a56d73b2b43048c6dba62d0aca2389f31ac..44e31970a4b7484de1b3e8eeaf28fcc3f55de828 100644 (file)
@@ -1,4 +1,4 @@
-/*===-- analysis_ocaml.c - LLVM Ocaml Glue ----------------------*- C++ -*-===*\
+/*===-- analysis_ocaml.c - LLVM OCaml Glue ----------------------*- C++ -*-===*\
 |*                                                                            *|
 |*                     The LLVM Compiler Infrastructure                       *|
 |*                                                                            *|
 |*                                                                            *|
 |*                     The LLVM Compiler Infrastructure                       *|
 |*                                                                            *|
@@ -7,7 +7,7 @@
 |*                                                                            *|
 |*===----------------------------------------------------------------------===*|
 |*                                                                            *|
 |*                                                                            *|
 |*===----------------------------------------------------------------------===*|
 |*                                                                            *|
-|* This file glues LLVM's ocaml interface to its C interface. These functions *|
+|* This file glues LLVM's OCaml interface to its C interface. These functions *|
 |* are by and large transparent wrappers to the corresponding C functions.    *|
 |*                                                                            *|
 |* Note that these functions intentionally take liberties with the CAMLparamX *|
 |* are by and large transparent wrappers to the corresponding C functions.    *|
 |*                                                                            *|
 |* Note that these functions intentionally take liberties with the CAMLparamX *|
 #include "caml/mlvalues.h"
 #include "caml/memory.h"
 
 #include "caml/mlvalues.h"
 #include "caml/memory.h"
 
-
 /* Llvm.llmodule -> string option */
 CAMLprim value llvm_verify_module(LLVMModuleRef M) {
   CAMLparam0();
   CAMLlocal2(String, Option);
 /* Llvm.llmodule -> string option */
 CAMLprim value llvm_verify_module(LLVMModuleRef M) {
   CAMLparam0();
   CAMLlocal2(String, Option);
-  
+
   char *Message;
   int Result = LLVMVerifyModule(M, LLVMReturnStatusAction, &Message);
   char *Message;
   int Result = LLVMVerifyModule(M, LLVMReturnStatusAction, &Message);
-  
+
   if (0 == Result) {
     Option = Val_int(0);
   } else {
   if (0 == Result) {
     Option = Val_int(0);
   } else {
@@ -36,9 +35,9 @@ CAMLprim value llvm_verify_module(LLVMModuleRef M) {
     String = copy_string(Message);
     Store_field(Option, 0, String);
   }
     String = copy_string(Message);
     Store_field(Option, 0, String);
   }
-  
+
   LLVMDisposeMessage(Message);
   LLVMDisposeMessage(Message);
-  
+
   CAMLreturn(Option);
 }
 
   CAMLreturn(Option);
 }
 
@@ -58,3 +57,15 @@ CAMLprim value llvm_assert_valid_function(LLVMValueRef Fn) {
   LLVMVerifyFunction(Fn, LLVMAbortProcessAction);
   return Val_unit;
 }
   LLVMVerifyFunction(Fn, LLVMAbortProcessAction);
   return Val_unit;
 }
+
+/* Llvm.llvalue -> unit */
+CAMLprim value llvm_view_function_cfg(LLVMValueRef Fn) {
+  LLVMViewFunctionCFG(Fn);
+  return Val_unit;
+}
+
+/* Llvm.llvalue -> unit */
+CAMLprim value llvm_view_function_cfg_only(LLVMValueRef Fn) {
+  LLVMViewFunctionCFGOnly(Fn);
+  return Val_unit;
+}