1*06f32e7eSjoerg(*===-- llvm_scalar_opts.mli - LLVM OCaml Interface -----------*- OCaml -*-===*
2*06f32e7eSjoerg *
3*06f32e7eSjoerg * Part of the LLVM Project, under the Apache License v2.0 with LLVM Exceptions.
4*06f32e7eSjoerg * See https://llvm.org/LICENSE.txt for license information.
5*06f32e7eSjoerg * SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception
6*06f32e7eSjoerg *
7*06f32e7eSjoerg *===----------------------------------------------------------------------===*)
8*06f32e7eSjoerg
9*06f32e7eSjoerg(** Scalar Transforms.
10*06f32e7eSjoerg
11*06f32e7eSjoerg    This interface provides an OCaml API for LLVM scalar transforms, the
12*06f32e7eSjoerg    classes in the [LLVMScalarOpts] library. *)
13*06f32e7eSjoerg
14*06f32e7eSjoerg(** See the [llvm::createAggressiveDCEPass] function. *)
15*06f32e7eSjoergexternal add_aggressive_dce
16*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
17*06f32e7eSjoerg  = "llvm_add_aggressive_dce"
18*06f32e7eSjoerg
19*06f32e7eSjoerg(** See the [llvm::createDCEPass] function. *)
20*06f32e7eSjoergexternal add_dce
21*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
22*06f32e7eSjoerg  = "llvm_add_dce"
23*06f32e7eSjoerg
24*06f32e7eSjoerg(** See the [llvm::createAlignmentFromAssumptionsPass] function. *)
25*06f32e7eSjoergexternal add_alignment_from_assumptions
26*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
27*06f32e7eSjoerg  = "llvm_add_alignment_from_assumptions"
28*06f32e7eSjoerg
29*06f32e7eSjoerg(** See the [llvm::createCFGSimplificationPass] function. *)
30*06f32e7eSjoergexternal add_cfg_simplification
31*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
32*06f32e7eSjoerg  = "llvm_add_cfg_simplification"
33*06f32e7eSjoerg
34*06f32e7eSjoerg(** See [llvm::createDeadStoreEliminationPass] function. *)
35*06f32e7eSjoergexternal add_dead_store_elimination
36*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
37*06f32e7eSjoerg  = "llvm_add_dead_store_elimination"
38*06f32e7eSjoerg
39*06f32e7eSjoerg(** See [llvm::createScalarizerPass] function. *)
40*06f32e7eSjoergexternal add_scalarizer
41*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
42*06f32e7eSjoerg  = "llvm_add_scalarizer"
43*06f32e7eSjoerg
44*06f32e7eSjoerg(** See [llvm::createMergedLoadStoreMotionPass] function. *)
45*06f32e7eSjoergexternal add_merged_load_store_motion
46*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
47*06f32e7eSjoerg  = "llvm_add_merged_load_store_motion"
48*06f32e7eSjoerg
49*06f32e7eSjoerg(** See the [llvm::createGVNPass] function. *)
50*06f32e7eSjoergexternal add_gvn
51*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
52*06f32e7eSjoerg  = "llvm_add_gvn"
53*06f32e7eSjoerg
54*06f32e7eSjoerg(** See the [llvm::createIndVarSimplifyPass] function. *)
55*06f32e7eSjoergexternal add_ind_var_simplification
56*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
57*06f32e7eSjoerg  = "llvm_add_ind_var_simplify"
58*06f32e7eSjoerg
59*06f32e7eSjoerg(** See the [llvm::createInstructionCombiningPass] function. *)
60*06f32e7eSjoergexternal add_instruction_combination
61*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
62*06f32e7eSjoerg  = "llvm_add_instruction_combining"
63*06f32e7eSjoerg
64*06f32e7eSjoerg(** See the [llvm::createJumpThreadingPass] function. *)
65*06f32e7eSjoergexternal add_jump_threading
66*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
67*06f32e7eSjoerg  = "llvm_add_jump_threading"
68*06f32e7eSjoerg
69*06f32e7eSjoerg(** See the [llvm::createLICMPass] function. *)
70*06f32e7eSjoergexternal add_licm
71*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
72*06f32e7eSjoerg  = "llvm_add_licm"
73*06f32e7eSjoerg
74*06f32e7eSjoerg(** See the [llvm::createLoopDeletionPass] function. *)
75*06f32e7eSjoergexternal add_loop_deletion
76*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
77*06f32e7eSjoerg  = "llvm_add_loop_deletion"
78*06f32e7eSjoerg
79*06f32e7eSjoerg(** See the [llvm::createLoopIdiomPass] function. *)
80*06f32e7eSjoergexternal add_loop_idiom
81*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
82*06f32e7eSjoerg  = "llvm_add_loop_idiom"
83*06f32e7eSjoerg
84*06f32e7eSjoerg(** See the [llvm::createLoopRotatePass] function. *)
85*06f32e7eSjoergexternal add_loop_rotation
86*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
87*06f32e7eSjoerg  = "llvm_add_loop_rotate"
88*06f32e7eSjoerg
89*06f32e7eSjoerg(** See the [llvm::createLoopRerollPass] function. *)
90*06f32e7eSjoergexternal add_loop_reroll
91*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
92*06f32e7eSjoerg  = "llvm_add_loop_reroll"
93*06f32e7eSjoerg
94*06f32e7eSjoerg(** See the [llvm::createLoopUnrollPass] function. *)
95*06f32e7eSjoergexternal add_loop_unroll
96*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
97*06f32e7eSjoerg  = "llvm_add_loop_unroll"
98*06f32e7eSjoerg
99*06f32e7eSjoerg(** See the [llvm::createLoopUnswitchPass] function. *)
100*06f32e7eSjoergexternal add_loop_unswitch
101*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
102*06f32e7eSjoerg  = "llvm_add_loop_unswitch"
103*06f32e7eSjoerg
104*06f32e7eSjoerg(** See the [llvm::createMemCpyOptPass] function. *)
105*06f32e7eSjoergexternal add_memcpy_opt
106*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
107*06f32e7eSjoerg  = "llvm_add_memcpy_opt"
108*06f32e7eSjoerg
109*06f32e7eSjoerg(** See the [llvm::createPartiallyInlineLibCallsPass] function. *)
110*06f32e7eSjoergexternal add_partially_inline_lib_calls
111*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
112*06f32e7eSjoerg  = "llvm_add_partially_inline_lib_calls"
113*06f32e7eSjoerg
114*06f32e7eSjoerg(** See the [llvm::createLowerAtomicPass] function. *)
115*06f32e7eSjoergexternal add_lower_atomic
116*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
117*06f32e7eSjoerg  = "llvm_add_lower_atomic"
118*06f32e7eSjoerg
119*06f32e7eSjoerg(** See the [llvm::createLowerSwitchPass] function. *)
120*06f32e7eSjoergexternal add_lower_switch
121*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
122*06f32e7eSjoerg  = "llvm_add_lower_switch"
123*06f32e7eSjoerg
124*06f32e7eSjoerg(** See the [llvm::createPromoteMemoryToRegisterPass] function. *)
125*06f32e7eSjoergexternal add_memory_to_register_promotion
126*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
127*06f32e7eSjoerg  = "llvm_add_promote_memory_to_register"
128*06f32e7eSjoerg
129*06f32e7eSjoerg(** See the [llvm::createReassociatePass] function. *)
130*06f32e7eSjoergexternal add_reassociation
131*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
132*06f32e7eSjoerg  = "llvm_add_reassociation"
133*06f32e7eSjoerg
134*06f32e7eSjoerg(** See the [llvm::createSCCPPass] function. *)
135*06f32e7eSjoergexternal add_sccp
136*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
137*06f32e7eSjoerg  = "llvm_add_sccp"
138*06f32e7eSjoerg
139*06f32e7eSjoerg(** See the [llvm::createSROAPass] function. *)
140*06f32e7eSjoergexternal add_scalar_repl_aggregation
141*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
142*06f32e7eSjoerg  = "llvm_add_scalar_repl_aggregates"
143*06f32e7eSjoerg
144*06f32e7eSjoerg(** See the [llvm::createSROAPass] function. *)
145*06f32e7eSjoergexternal add_scalar_repl_aggregation_ssa
146*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
147*06f32e7eSjoerg  = "llvm_add_scalar_repl_aggregates_ssa"
148*06f32e7eSjoerg
149*06f32e7eSjoerg(** See the [llvm::createSROAPass] function. *)
150*06f32e7eSjoergexternal add_scalar_repl_aggregation_with_threshold
151*06f32e7eSjoerg  : int -> [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
152*06f32e7eSjoerg  = "llvm_add_scalar_repl_aggregates_with_threshold"
153*06f32e7eSjoerg
154*06f32e7eSjoerg(** See the [llvm::createSimplifyLibCallsPass] function. *)
155*06f32e7eSjoergexternal add_lib_call_simplification
156*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
157*06f32e7eSjoerg  = "llvm_add_simplify_lib_calls"
158*06f32e7eSjoerg
159*06f32e7eSjoerg(** See the [llvm::createTailCallEliminationPass] function. *)
160*06f32e7eSjoergexternal add_tail_call_elimination
161*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
162*06f32e7eSjoerg  = "llvm_add_tail_call_elimination"
163*06f32e7eSjoerg
164*06f32e7eSjoerg(** See the [llvm::createDemoteMemoryToRegisterPass] function. *)
165*06f32e7eSjoergexternal add_memory_to_register_demotion
166*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
167*06f32e7eSjoerg  = "llvm_add_demote_memory_to_register"
168*06f32e7eSjoerg
169*06f32e7eSjoerg(** See the [llvm::createVerifierPass] function. *)
170*06f32e7eSjoergexternal add_verifier
171*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
172*06f32e7eSjoerg  = "llvm_add_verifier"
173*06f32e7eSjoerg
174*06f32e7eSjoerg(** See the [llvm::createCorrelatedValuePropagationPass] function. *)
175*06f32e7eSjoergexternal add_correlated_value_propagation
176*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
177*06f32e7eSjoerg  = "llvm_add_correlated_value_propagation"
178*06f32e7eSjoerg
179*06f32e7eSjoerg(** See the [llvm::createEarlyCSE] function. *)
180*06f32e7eSjoergexternal add_early_cse
181*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
182*06f32e7eSjoerg  = "llvm_add_early_cse"
183*06f32e7eSjoerg
184*06f32e7eSjoerg(** See the [llvm::createLowerExpectIntrinsicPass] function. *)
185*06f32e7eSjoergexternal add_lower_expect_intrinsic
186*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
187*06f32e7eSjoerg  = "llvm_add_lower_expect_intrinsic"
188*06f32e7eSjoerg
189*06f32e7eSjoerg(** See the [llvm::createLowerConstantIntrinsicsPass] function. *)
190*06f32e7eSjoergexternal add_lower_constant_intrinsics
191*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
192*06f32e7eSjoerg  = "llvm_add_lower_constant_intrinsics"
193*06f32e7eSjoerg
194*06f32e7eSjoerg(** See the [llvm::createTypeBasedAliasAnalysisPass] function. *)
195*06f32e7eSjoergexternal add_type_based_alias_analysis
196*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
197*06f32e7eSjoerg  = "llvm_add_type_based_alias_analysis"
198*06f32e7eSjoerg
199*06f32e7eSjoerg(** See the [llvm::createScopedNoAliasAAPass] function. *)
200*06f32e7eSjoergexternal add_scoped_no_alias_alias_analysis
201*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
202*06f32e7eSjoerg  = "llvm_add_scoped_no_alias_aa"
203*06f32e7eSjoerg
204*06f32e7eSjoerg(** See the [llvm::createBasicAliasAnalysisPass] function. *)
205*06f32e7eSjoergexternal add_basic_alias_analysis
206*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
207*06f32e7eSjoerg  = "llvm_add_basic_alias_analysis"
208*06f32e7eSjoerg
209*06f32e7eSjoerg(** See the [llvm::createUnifyFunctionExitNodesPass] function. *)
210*06f32e7eSjoergexternal add_unify_function_exit_nodes
211*06f32e7eSjoerg  : [< Llvm.PassManager.any ] Llvm.PassManager.t -> unit
212*06f32e7eSjoerg  = "llvm_add_unify_function_exit_nodes"
213