Home | History | Annotate | Download | only in passmgr_builder
      1 /*===-- passmgr_builder_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/PassManagerBuilder.h"
     19 #include "caml/mlvalues.h"
     20 #include "caml/custom.h"
     21 #include "caml/misc.h"
     22 
     23 #define PMBuilder_val(v)  (*(LLVMPassManagerBuilderRef *)(Data_custom_val(v)))
     24 
     25 static void llvm_finalize_pmbuilder(value PMB) {
     26   LLVMPassManagerBuilderDispose(PMBuilder_val(PMB));
     27 }
     28 
     29 static struct custom_operations pmbuilder_ops = {
     30   (char *) "Llvm_passmgr_builder.t",
     31   llvm_finalize_pmbuilder,
     32   custom_compare_default,
     33   custom_hash_default,
     34   custom_serialize_default,
     35   custom_deserialize_default,
     36   custom_compare_ext_default
     37 };
     38 
     39 static value alloc_pmbuilder(LLVMPassManagerBuilderRef Ref) {
     40   value Val = alloc_custom(&pmbuilder_ops,
     41                            sizeof(LLVMPassManagerBuilderRef), 0, 1);
     42   PMBuilder_val(Val) = Ref;
     43   return Val;
     44 }
     45 
     46 /* t -> unit */
     47 CAMLprim value llvm_pmbuilder_create(value Unit) {
     48   return alloc_pmbuilder(LLVMPassManagerBuilderCreate());
     49 }
     50 
     51 /* int -> t -> unit */
     52 CAMLprim value llvm_pmbuilder_set_opt_level(value OptLevel, value PMB) {
     53   LLVMPassManagerBuilderSetOptLevel(PMBuilder_val(PMB), Int_val(OptLevel));
     54   return Val_unit;
     55 }
     56 
     57 /* int -> t -> unit */
     58 CAMLprim value llvm_pmbuilder_set_size_level(value SizeLevel, value PMB) {
     59   LLVMPassManagerBuilderSetSizeLevel(PMBuilder_val(PMB), Int_val(SizeLevel));
     60   return Val_unit;
     61 }
     62 
     63 /* int -> t -> unit */
     64 CAMLprim value llvm_pmbuilder_use_inliner_with_threshold(
     65                       value Threshold, value PMB) {
     66   LLVMPassManagerBuilderSetOptLevel(PMBuilder_val(PMB), Int_val(Threshold));
     67   return Val_unit;
     68 }
     69 
     70 /* bool -> t -> unit */
     71 CAMLprim value llvm_pmbuilder_set_disable_unit_at_a_time(
     72                       value DisableUnitAtATime, value PMB) {
     73   LLVMPassManagerBuilderSetDisableUnitAtATime(
     74                       PMBuilder_val(PMB), Bool_val(DisableUnitAtATime));
     75   return Val_unit;
     76 }
     77 
     78 /* bool -> t -> unit */
     79 CAMLprim value llvm_pmbuilder_set_disable_unroll_loops(
     80                       value DisableUnroll, value PMB) {
     81   LLVMPassManagerBuilderSetDisableUnrollLoops(
     82                       PMBuilder_val(PMB), Bool_val(DisableUnroll));
     83   return Val_unit;
     84 }
     85 
     86 /* [ `Function ] Llvm.PassManager.t -> t -> unit */
     87 CAMLprim value llvm_pmbuilder_populate_function_pass_manager(
     88                       LLVMPassManagerRef PM, value PMB) {
     89   LLVMPassManagerBuilderPopulateFunctionPassManager(
     90                       PMBuilder_val(PMB), PM);
     91   return Val_unit;
     92 }
     93 
     94 /* [ `Module ] Llvm.PassManager.t -> t -> unit */
     95 CAMLprim value llvm_pmbuilder_populate_module_pass_manager(
     96                       LLVMPassManagerRef PM, value PMB) {
     97   LLVMPassManagerBuilderPopulateModulePassManager(
     98                       PMBuilder_val(PMB), PM);
     99   return Val_unit;
    100 }
    101 
    102 /* [ `Module ] Llvm.PassManager.t ->
    103    internalize:bool -> run_inliner:bool -> t -> unit */
    104 CAMLprim value llvm_pmbuilder_populate_lto_pass_manager(
    105                       LLVMPassManagerRef PM, value Internalize, value RunInliner,
    106                       value PMB) {
    107   LLVMPassManagerBuilderPopulateLTOPassManager(
    108                       PMBuilder_val(PMB), PM,
    109                       Bool_val(Internalize), Bool_val(RunInliner));
    110   return Val_unit;
    111 }
    112