xref: /minix3/external/bsd/llvm/dist/llvm/bindings/ocaml/analysis/analysis_ocaml.c (revision 0a6a1f1d05b60e214de2f05a7310ddd1f0e590e7)
1  /*===-- analysis_ocaml.c - LLVM OCaml Glue ----------------------*- C++ -*-===*\
2  |*                                                                            *|
3  |*                     The LLVM Compiler Infrastructure                       *|
4  |*                                                                            *|
5  |* This file is distributed under the University of Illinois Open Source      *|
6  |* License. See LICENSE.TXT for details.                                      *|
7  |*                                                                            *|
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  /* Llvm.llmodule -> string option */
llvm_verify_module(LLVMModuleRef M)24  CAMLprim value llvm_verify_module(LLVMModuleRef M) {
25    CAMLparam0();
26    CAMLlocal2(String, Option);
27  
28    char *Message;
29    int Result = LLVMVerifyModule(M, LLVMReturnStatusAction, &Message);
30  
31    if (0 == Result) {
32      Option = Val_int(0);
33    } else {
34      Option = alloc(1, 0);
35      String = copy_string(Message);
36      Store_field(Option, 0, String);
37    }
38  
39    LLVMDisposeMessage(Message);
40  
41    CAMLreturn(Option);
42  }
43  
44  /* Llvm.llvalue -> bool */
llvm_verify_function(LLVMValueRef Fn)45  CAMLprim value llvm_verify_function(LLVMValueRef Fn) {
46    return Val_bool(LLVMVerifyFunction(Fn, LLVMReturnStatusAction) == 0);
47  }
48  
49  /* Llvm.llmodule -> unit */
llvm_assert_valid_module(LLVMModuleRef M)50  CAMLprim value llvm_assert_valid_module(LLVMModuleRef M) {
51    LLVMVerifyModule(M, LLVMAbortProcessAction, 0);
52    return Val_unit;
53  }
54  
55  /* Llvm.llvalue -> unit */
llvm_assert_valid_function(LLVMValueRef Fn)56  CAMLprim value llvm_assert_valid_function(LLVMValueRef Fn) {
57    LLVMVerifyFunction(Fn, LLVMAbortProcessAction);
58    return Val_unit;
59  }
60  
61  /* Llvm.llvalue -> unit */
llvm_view_function_cfg(LLVMValueRef Fn)62  CAMLprim value llvm_view_function_cfg(LLVMValueRef Fn) {
63    LLVMViewFunctionCFG(Fn);
64    return Val_unit;
65  }
66  
67  /* Llvm.llvalue -> unit */
llvm_view_function_cfg_only(LLVMValueRef Fn)68  CAMLprim value llvm_view_function_cfg_only(LLVMValueRef Fn) {
69    LLVMViewFunctionCFGOnly(Fn);
70    return Val_unit;
71  }
72