Home | History | Annotate | Download | only in passmgr_builder
      1 (*===-- llvm_passmgr_builder.mli - LLVM OCaml Interface -------*- OCaml -*-===*
      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 (** Pass Manager Builder.
     11 
     12     This interface provides an OCaml API for LLVM pass manager builder
     13     from the [LLVMCore] library. *)
     14 
     15 type t
     16 
     17 (** See the [llvm::PassManagerBuilder] function. *)
     18 external create : unit -> t
     19   = "llvm_pmbuilder_create"
     20 
     21 (** See the [llvm::PassManagerBuilder::OptLevel] function. *)
     22 external set_opt_level : int -> t -> unit
     23   = "llvm_pmbuilder_set_opt_level"
     24 
     25 (** See the [llvm::PassManagerBuilder::SizeLevel] function. *)
     26 external set_size_level : int -> t -> unit
     27   = "llvm_pmbuilder_set_size_level"
     28 
     29 (** See the [llvm::PassManagerBuilder::DisableUnitAtATime] function. *)
     30 external set_disable_unit_at_a_time : bool -> t -> unit
     31   = "llvm_pmbuilder_set_disable_unit_at_a_time"
     32 
     33 (** See the [llvm::PassManagerBuilder::DisableUnrollLoops] function. *)
     34 external set_disable_unroll_loops : bool -> t -> unit
     35   = "llvm_pmbuilder_set_disable_unroll_loops"
     36 
     37 (** See the [llvm::PassManagerBuilder::Inliner] function. *)
     38 external use_inliner_with_threshold : int -> t -> unit
     39   = "llvm_pmbuilder_use_inliner_with_threshold"
     40 
     41 (** See the [llvm::PassManagerBuilder::populateFunctionPassManager] function. *)
     42 external populate_function_pass_manager
     43   : [ `Function ] Llvm.PassManager.t -> t -> unit
     44   = "llvm_pmbuilder_populate_function_pass_manager"
     45 
     46 (** See the [llvm::PassManagerBuilder::populateModulePassManager] function. *)
     47 external populate_module_pass_manager
     48   : [ `Module ] Llvm.PassManager.t -> t -> unit
     49   = "llvm_pmbuilder_populate_module_pass_manager"
     50 
     51 (** See the [llvm::PassManagerBuilder::populateLTOPassManager] function. *)
     52 external populate_lto_pass_manager
     53   : [ `Module ] Llvm.PassManager.t -> internalize:bool -> run_inliner:bool -> t -> unit
     54   = "llvm_pmbuilder_populate_lto_pass_manager"
     55