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