Expose Function::viewCFG and Function::viewCFGOnly to bindings.
[oota-llvm.git] / bindings / ocaml / analysis / analysis_ocaml.c
index cc1098a374913623552bf9e764615abf1ce9a188..97167055f70e616f578dfb59d4369884763d6488 100644 (file)
@@ -2,8 +2,8 @@
 |*                                                                            *|
 |*                     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.                                      *|
 |*                                                                            *|
 |*===----------------------------------------------------------------------===*|
 |*                                                                            *|
@@ -32,12 +32,12 @@ CAMLprim value llvm_verify_module(LLVMModuleRef M) {
   if (0 == Result) {
     Option = Val_int(0);
   } else {
-    Option = alloc(1, 1);
+    Option = alloc(1, 0);
     String = copy_string(Message);
     Store_field(Option, 0, String);
   }
   
-  LLVMDisposeVerifierMessage(Message);
+  LLVMDisposeMessage(Message);
   
   CAMLreturn(Option);
 }
@@ -58,3 +58,15 @@ CAMLprim value llvm_assert_valid_function(LLVMValueRef Fn) {
   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;
+}