blob: 97167055f70e616f578dfb59d4369884763d6488 [file] [log] [blame]
Gordon Henriksen3ed72362007-10-06 21:00:36 +00001/*===-- analysis_ocaml.c - LLVM Ocaml Glue ----------------------*- C++ -*-===*\
2|* *|
3|* The LLVM Compiler Infrastructure *|
4|* *|
Chris Lattner3023be42007-12-29 22:59:10 +00005|* This file is distributed under the University of Illinois Open Source *|
6|* License. See LICENSE.TXT for details. *|
Gordon Henriksen3ed72362007-10-06 21:00:36 +00007|* *|
8|*===----------------------------------------------------------------------===*|
9|* *|
10|* This file glues LLVM's ocaml interface to its C interface. These functions *|
11|* are by and large transparent wrappers to the corresponding C functions. *|
12|* *|
13|* Note that these functions intentionally take liberties with the CAMLparamX *|
14|* macros, since most of the parameters are not GC heap objects. *|
15|* *|
16\*===----------------------------------------------------------------------===*/
17
18#include "llvm-c/Analysis.h"
19#include "caml/alloc.h"
20#include "caml/mlvalues.h"
21#include "caml/memory.h"
22
23
24/* Llvm.llmodule -> string option */
25CAMLprim value llvm_verify_module(LLVMModuleRef M) {
26 CAMLparam0();
27 CAMLlocal2(String, Option);
28
29 char *Message;
30 int Result = LLVMVerifyModule(M, LLVMReturnStatusAction, &Message);
31
32 if (0 == Result) {
33 Option = Val_int(0);
34 } else {
Gordon Henriksen282d1772007-12-08 16:55:43 +000035 Option = alloc(1, 0);
Gordon Henriksen3ed72362007-10-06 21:00:36 +000036 String = copy_string(Message);
37 Store_field(Option, 0, String);
38 }
39
Gordon Henriksen91ab68b2007-12-19 22:30:40 +000040 LLVMDisposeMessage(Message);
Gordon Henriksen3ed72362007-10-06 21:00:36 +000041
42 CAMLreturn(Option);
43}
44
45/* Llvm.llvalue -> bool */
46CAMLprim value llvm_verify_function(LLVMValueRef Fn) {
47 return Val_bool(LLVMVerifyFunction(Fn, LLVMReturnStatusAction) == 0);
48}
49
50/* Llvm.llmodule -> unit */
51CAMLprim value llvm_assert_valid_module(LLVMModuleRef M) {
52 LLVMVerifyModule(M, LLVMAbortProcessAction, 0);
53 return Val_unit;
54}
55
56/* Llvm.llvalue -> unit */
57CAMLprim value llvm_assert_valid_function(LLVMValueRef Fn) {
58 LLVMVerifyFunction(Fn, LLVMAbortProcessAction);
59 return Val_unit;
60}
Erick Tryzelaara268e322008-03-31 16:22:09 +000061
62/* Llvm.llvalue -> unit */
63CAMLprim value llvm_view_function_cfg(LLVMValueRef Fn) {
64 LLVMViewFunctionCFG(Fn);
65 return Val_unit;
66}
67
68/* Llvm.llvalue -> unit */
69CAMLprim value llvm_view_function_cfg_only(LLVMValueRef Fn) {
70 LLVMViewFunctionCFGOnly(Fn);
71 return Val_unit;
72}