166b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman(*===-- llvm_scalar_opts.mli - LLVM Ocaml Interface ------------*- OCaml -*-===*
266b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman *
366b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman *                     The LLVM Compiler Infrastructure
466b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman *
566b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman * This file is distributed under the University of Illinois Open Source
666b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman * License. See LICENSE.TXT for details.
766b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman *
866b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman *===----------------------------------------------------------------------===*)
966b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman
1066b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman(** Scalar Transforms.
1166b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman
1266b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman    This interface provides an ocaml API for LLVM scalar transforms, the
1366b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman    classes in the [LLVMScalarOpts] library. *)
1466b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman
1566b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman(** See the [llvm::createConstantPropogationPass] function. *)
1666b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanexternal add_constant_propagation : [<Llvm.PassManager.any] Llvm.PassManager.t
1766b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                                    -> unit
1866b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                                  = "llvm_add_constant_propagation"
1966b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman
2066b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman(** See the [llvm::createSCCPPass] function. *)
2166b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanexternal add_sccp : [<Llvm.PassManager.any] Llvm.PassManager.t -> unit
2266b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                  = "llvm_add_sccp"
2366b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman
2466b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman(** See [llvm::createDeadStoreEliminationPass] function. *)
2566b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanexternal add_dead_store_elimination : [<Llvm.PassManager.any] Llvm.PassManager.t
2666b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                                      -> unit
2766b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                                    = "llvm_add_dead_store_elimination"
2866b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman
2966b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman(** See The [llvm::createAggressiveDCEPass] function. *)
3066b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanexternal add_aggressive_dce : [<Llvm.PassManager.any] Llvm.PassManager.t -> unit
3166b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                            = "llvm_add_aggressive_dce"
3266b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman
3366b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman(** See the [llvm::createScalarReplAggregatesPass] function. *)
3466b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanexternal
3566b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanadd_scalar_repl_aggregation : [<Llvm.PassManager.any] Llvm.PassManager.t -> unit
3666b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                            = "llvm_add_scalar_repl_aggregation"
3766b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman
3866b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman(** See the [llvm::createScalarReplAggregatesPassSSA] function. *)
3966b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanexternal
4066b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanadd_scalar_repl_aggregation_ssa : [<Llvm.PassManager.any] Llvm.PassManager.t -> unit
4166b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                            = "llvm_add_scalar_repl_aggregation_ssa"
4266b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman
4366b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman(** See the [llvm::createScalarReplAggregatesWithThreshold] function. *)
4466b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanexternal
4566b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanadd_scalar_repl_aggregation_with_threshold : int -> [<Llvm.PassManager.any] Llvm.PassManager.t
4666b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                                             -> unit
4766b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                            = "llvm_add_scalar_repl_aggregation_with_threshold"
4866b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman
4966b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman(** See the [llvm::createIndVarSimplifyPass] function. *)
5066b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanexternal add_ind_var_simplification : [<Llvm.PassManager.any] Llvm.PassManager.t
5166b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                                      -> unit
5266b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                                    = "llvm_add_ind_var_simplification"
5366b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman
5466b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman(** See the [llvm::createInstructionCombiningPass] function. *)
5566b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanexternal
5666b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanadd_instruction_combination : [<Llvm.PassManager.any] Llvm.PassManager.t
5766b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                              -> unit
5866b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                            = "llvm_add_instruction_combination"
5966b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman
6066b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman(** See the [llvm::createLICMPass] function. *)
6166b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanexternal add_licm : [<Llvm.PassManager.any] Llvm.PassManager.t
6266b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                                -> unit
6366b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                              = "llvm_add_licm"
6466b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman
6566b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman(** See the [llvm::createLoopUnswitchPass] function. *)
6666b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanexternal add_loop_unswitch : [<Llvm.PassManager.any] Llvm.PassManager.t
6766b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                                -> unit
6866b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                              = "llvm_add_loop_unswitch"
6966b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman
7066b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman(** See the [llvm::createLoopUnrollPass] function. *)
7166b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanexternal add_loop_unroll : [<Llvm.PassManager.any] Llvm.PassManager.t
7266b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                                -> unit
7366b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                              = "llvm_add_loop_unroll"
7466b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman
7566b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman(** See the [llvm::createLoopRotatePass] function. *)
7666b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanexternal add_loop_rotation : [<Llvm.PassManager.any] Llvm.PassManager.t
7766b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                             -> unit
7866b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                           = "llvm_add_loop_rotation"
7966b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman
8066b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman(** See the [llvm::createPromoteMemoryToRegisterPass] function. *)
8166b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanexternal
8266b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanadd_memory_to_register_promotion : [<Llvm.PassManager.any] Llvm.PassManager.t
8366b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                                   -> unit
8466b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                                 = "llvm_add_memory_to_register_promotion"
8566b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman
8666b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman(** See the [llvm::createDemoteMemoryToRegisterPass] function. *)
8766b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanexternal
8866b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanadd_memory_to_register_demotion : [<Llvm.PassManager.any] Llvm.PassManager.t
8966b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                                  -> unit
9066b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                                = "llvm_add_memory_to_register_demotion"
9166b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman
9266b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman(** See the [llvm::createReassociatePass] function. *)
9366b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanexternal add_reassociation : [<Llvm.PassManager.any] Llvm.PassManager.t -> unit
9466b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                           = "llvm_add_reassociation"
9566b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman
9666b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman(** See the [llvm::createJumpThreadingPass] function. *)
9766b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanexternal add_jump_threading : [<Llvm.PassManager.any] Llvm.PassManager.t
9866b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                                -> unit
9966b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                              = "llvm_add_jump_threading"
10066b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman
10166b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman(** See the [llvm::createCFGSimplificationPass] function. *)
10266b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanexternal add_cfg_simplification : [<Llvm.PassManager.any] Llvm.PassManager.t
10366b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                                  -> unit
10466b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                                = "llvm_add_cfg_simplification"
10566b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman
10666b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman(** See the [llvm::createTailCallEliminationPass] function. *)
10766b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanexternal
10866b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanadd_tail_call_elimination : [<Llvm.PassManager.any] Llvm.PassManager.t -> unit
10966b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                          = "llvm_add_tail_call_elimination" 
11066b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman
11166b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman(** See the [llvm::createGVNPass] function. *)
11266b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanexternal add_gvn : [<Llvm.PassManager.any] Llvm.PassManager.t
11366b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                   -> unit
11466b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                 = "llvm_add_gvn"
11566b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman
11666b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman(** See the [llvm::createMemCpyOptPass] function. *)
11766b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanexternal add_memcpy_opt : [<Llvm.PassManager.any] Llvm.PassManager.t
11866b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                                -> unit
11966b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                              = "llvm_add_memcpy_opt"
12066b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman
12166b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman(** See the [llvm::createLoopDeletionPass] function. *)
12266b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanexternal add_loop_deletion : [<Llvm.PassManager.any] Llvm.PassManager.t
12366b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                             -> unit
12466b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                           = "llvm_add_loop_deletion"
12566b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman
12666b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanexternal add_loop_idiom : [<Llvm.PassManager.any] Llvm.PassManager.t
12766b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                             -> unit
12866b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                           = "llvm_add_loop_idiom"
12966b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman
13066b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman(** See the [llvm::createSimplifyLibCallsPass] function. *)
13166b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanexternal
13266b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanadd_lib_call_simplification : [<Llvm.PassManager.any] Llvm.PassManager.t -> unit
13366b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman                            = "llvm_add_lib_call_simplification"
13466b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman
13566b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman(** See the [llvm::createVerifierPass] function. *)
13666b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanexternal
13766b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanadd_verifier : [<Llvm.PassManager.any] Llvm.PassManager.t -> unit
13866b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman        = "llvm_add_verifier"
13966b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman
14066b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman(** See the [llvm::createCorrelatedValuePropagationPass] function. *)
14166b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanexternal
14266b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanadd_correlated_value_propagation : [<Llvm.PassManager.any] Llvm.PassManager.t -> unit
14366b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman        = "llvm_add_correlated_value_propagation"
14466b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman
14566b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman(** See the [llvm::createEarlyCSE] function. *)
14666b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanexternal
14766b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanadd_early_cse : [<Llvm.PassManager.any] Llvm.PassManager.t -> unit
14866b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman        = "llvm_add_early_cse"
14966b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman
15066b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman(** See the [llvm::createLowerExpectIntrinsicPass] function. *)
15166b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanexternal
15266b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanadd_lower_expect_intrinsic : [<Llvm.PassManager.any] Llvm.PassManager.t -> unit
15366b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman        = "llvm_add_lower_expect_intrinsic"
15466b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman
15566b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman(** See the [llvm::createTypeBasedAliasAnalysisPass] function. *)
15666b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanexternal
15766b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanadd_type_based_alias_analysis : [<Llvm.PassManager.any] Llvm.PassManager.t -> unit
15866b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman        = "llvm_add_type_based_alias_analysis"
15966b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman
16066b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman(** See the [llvm::createBasicAliasAnalysisPass] function. *)
16166b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanexternal
16266b8ab22586debccb1f787d4d52b7f042d4ddeb8John Baumanadd_basic_alias_analysis : [<Llvm.PassManager.any] Llvm.PassManager.t -> unit
16366b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman        = "llvm_add_basic_alias_analysis"
16466b8ab22586debccb1f787d4d52b7f042d4ddeb8John Bauman
165