Home | History | Annotate | Download | only in ipo
      1 (*===-- llvm_ipo.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 (** IPO Transforms.
     11 
     12     This interface provides an OCaml API for LLVM interprocedural optimizations, the
     13     classes in the [LLVMIPO] library. *)
     14 
     15 (** See the [llvm::createAddArgumentPromotionPass] function. *)
     16 external add_argument_promotion
     17   : [ `Module ] Llvm.PassManager.t -> unit
     18   = "llvm_add_argument_promotion"
     19 
     20 (** See the [llvm::createConstantMergePass] function. *)
     21 external add_constant_merge
     22   : [ `Module ] Llvm.PassManager.t -> unit
     23   = "llvm_add_constant_merge"
     24 
     25 (** See the [llvm::createDeadArgEliminationPass] function. *)
     26 external add_dead_arg_elimination
     27   : [ `Module ] Llvm.PassManager.t -> unit
     28   = "llvm_add_dead_arg_elimination"
     29 
     30 (** See the [llvm::createFunctionAttrsPass] function. *)
     31 external add_function_attrs
     32   : [ `Module ] Llvm.PassManager.t -> unit
     33   = "llvm_add_function_attrs"
     34 
     35 (** See the [llvm::createFunctionInliningPass] function. *)
     36 external add_function_inlining
     37   : [ `Module ] Llvm.PassManager.t -> unit
     38   = "llvm_add_function_inlining"
     39 
     40 (** See the [llvm::createAlwaysInlinerPass] function. *)
     41 external add_always_inliner
     42   : [ `Module ] Llvm.PassManager.t -> unit
     43   = "llvm_add_always_inliner"
     44 
     45 (** See the [llvm::createGlobalDCEPass] function. *)
     46 external add_global_dce
     47   : [ `Module ] Llvm.PassManager.t -> unit
     48   = "llvm_add_global_dce"
     49 
     50 (** See the [llvm::createGlobalOptimizerPass] function. *)
     51 external add_global_optimizer
     52   : [ `Module ] Llvm.PassManager.t -> unit
     53   = "llvm_add_global_optimizer"
     54 
     55 (** See the [llvm::createIPConstantPropagationPass] function. *)
     56 external add_ipc_propagation
     57   : [ `Module ] Llvm.PassManager.t -> unit
     58   = "llvm_add_ip_constant_propagation"
     59 
     60 (** See the [llvm::createPruneEHPass] function. *)
     61 external add_prune_eh
     62   : [ `Module ] Llvm.PassManager.t -> unit
     63   = "llvm_add_prune_eh"
     64 
     65 (** See the [llvm::createIPSCCPPass] function. *)
     66 external add_ipsccp
     67   : [ `Module ] Llvm.PassManager.t -> unit
     68   = "llvm_add_ipsccp"
     69 
     70 (** See the [llvm::createInternalizePass] function. *)
     71 external add_internalize
     72   : [ `Module ] Llvm.PassManager.t -> all_but_main:bool -> unit
     73   = "llvm_add_internalize"
     74 
     75 (** See the [llvm::createStripDeadPrototypesPass] function. *)
     76 external add_strip_dead_prototypes
     77   : [ `Module ] Llvm.PassManager.t -> unit
     78   = "llvm_add_strip_dead_prototypes"
     79 
     80 (** See the [llvm::createStripSymbolsPass] function. *)
     81 external add_strip_symbols
     82   : [ `Module ] Llvm.PassManager.t -> unit
     83   = "llvm_add_strip_symbols"
     84