Home | History | Annotate | Download | only in ipo
      1 /*===-- ipo_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/Transforms/IPO.h"
     19 #include "caml/mlvalues.h"
     20 #include "caml/misc.h"
     21 
     22 /* [`Module] Llvm.PassManager.t -> unit */
     23 CAMLprim value llvm_add_argument_promotion(LLVMPassManagerRef PM) {
     24   LLVMAddArgumentPromotionPass(PM);
     25   return Val_unit;
     26 }
     27 
     28 /* [`Module] Llvm.PassManager.t -> unit */
     29 CAMLprim value llvm_add_constant_merge(LLVMPassManagerRef PM) {
     30   LLVMAddConstantMergePass(PM);
     31   return Val_unit;
     32 }
     33 
     34 /* [`Module] Llvm.PassManager.t -> unit */
     35 CAMLprim value llvm_add_dead_arg_elimination(LLVMPassManagerRef PM) {
     36   LLVMAddDeadArgEliminationPass(PM);
     37   return Val_unit;
     38 }
     39 
     40 /* [`Module] Llvm.PassManager.t -> unit */
     41 CAMLprim value llvm_add_function_attrs(LLVMPassManagerRef PM) {
     42   LLVMAddFunctionAttrsPass(PM);
     43   return Val_unit;
     44 }
     45 
     46 /* [`Module] Llvm.PassManager.t -> unit */
     47 CAMLprim value llvm_add_function_inlining(LLVMPassManagerRef PM) {
     48   LLVMAddFunctionInliningPass(PM);
     49   return Val_unit;
     50 }
     51 
     52 /* [`Module] Llvm.PassManager.t -> unit */
     53 CAMLprim value llvm_add_always_inliner(LLVMPassManagerRef PM) {
     54   LLVMAddAlwaysInlinerPass(PM);
     55   return Val_unit;
     56 }
     57 
     58 /* [`Module] Llvm.PassManager.t -> unit */
     59 CAMLprim value llvm_add_global_dce(LLVMPassManagerRef PM) {
     60   LLVMAddGlobalDCEPass(PM);
     61   return Val_unit;
     62 }
     63 
     64 /* [`Module] Llvm.PassManager.t -> unit */
     65 CAMLprim value llvm_add_global_optimizer(LLVMPassManagerRef PM) {
     66   LLVMAddGlobalOptimizerPass(PM);
     67   return Val_unit;
     68 }
     69 
     70 /* [`Module] Llvm.PassManager.t -> unit */
     71 CAMLprim value llvm_add_ip_constant_propagation(LLVMPassManagerRef PM) {
     72   LLVMAddIPConstantPropagationPass(PM);
     73   return Val_unit;
     74 }
     75 
     76 /* [`Module] Llvm.PassManager.t -> unit */
     77 CAMLprim value llvm_add_prune_eh(LLVMPassManagerRef PM) {
     78   LLVMAddPruneEHPass(PM);
     79   return Val_unit;
     80 }
     81 
     82 /* [`Module] Llvm.PassManager.t -> unit */
     83 CAMLprim value llvm_add_ipsccp(LLVMPassManagerRef PM) {
     84   LLVMAddIPSCCPPass(PM);
     85   return Val_unit;
     86 }
     87 
     88 /* [`Module] Llvm.PassManager.t -> all_but_main:bool -> unit */
     89 CAMLprim value llvm_add_internalize(LLVMPassManagerRef PM, value AllButMain) {
     90   LLVMAddInternalizePass(PM, Bool_val(AllButMain));
     91   return Val_unit;
     92 }
     93 
     94 /* [`Module] Llvm.PassManager.t -> unit */
     95 CAMLprim value llvm_add_strip_dead_prototypes(LLVMPassManagerRef PM) {
     96   LLVMAddStripDeadPrototypesPass(PM);
     97   return Val_unit;
     98 }
     99 
    100 /* [`Module] Llvm.PassManager.t -> unit */
    101 CAMLprim value llvm_add_strip_symbols(LLVMPassManagerRef PM) {
    102   LLVMAddStripSymbolsPass(PM);
    103   return Val_unit;
    104 }
    105