1/*===-- analysis_ocaml.c - LLVM OCaml Glue ----------------------*- C++ -*-===*\
2|*                                                                            *|
3|* Part of the LLVM Project, under the Apache License v2.0 with LLVM          *|
4|* Exceptions.                                                                *|
5|* See https://llvm.org/LICENSE.txt for license information.                  *|
6|* SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception                    *|
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 "llvm-c/Core.h"
20#include "caml/alloc.h"
21#include "caml/mlvalues.h"
22#include "caml/memory.h"
23#include "llvm_ocaml.h"
24
25/* Llvm.llmodule -> string option */
26value llvm_verify_module(LLVMModuleRef M) {
27  CAMLparam0();
28  CAMLlocal2(String, Option);
29
30  char *Message;
31  int Result = LLVMVerifyModule(M, LLVMReturnStatusAction, &Message);
32
33  if (0 == Result) {
34    Option = Val_none;
35  } else {
36    String = copy_string(Message);
37    Option = caml_alloc_some(String);
38  }
39
40  LLVMDisposeMessage(Message);
41
42  CAMLreturn(Option);
43}
44
45/* Llvm.llvalue -> bool */
46value llvm_verify_function(LLVMValueRef Fn) {
47  return Val_bool(LLVMVerifyFunction(Fn, LLVMReturnStatusAction) == 0);
48}
49
50/* Llvm.llmodule -> unit */
51value llvm_assert_valid_module(LLVMModuleRef M) {
52  LLVMVerifyModule(M, LLVMAbortProcessAction, 0);
53  return Val_unit;
54}
55
56/* Llvm.llvalue -> unit */
57value llvm_assert_valid_function(LLVMValueRef Fn) {
58  LLVMVerifyFunction(Fn, LLVMAbortProcessAction);
59  return Val_unit;
60}
61
62/* Llvm.llvalue -> unit */
63value llvm_view_function_cfg(LLVMValueRef Fn) {
64  LLVMViewFunctionCFG(Fn);
65  return Val_unit;
66}
67
68/* Llvm.llvalue -> unit */
69value llvm_view_function_cfg_only(LLVMValueRef Fn) {
70  LLVMViewFunctionCFGOnly(Fn);
71  return Val_unit;
72}
73