1(**************************************************************************)
2(*                                                                        *)
3(*                                 OCaml                                  *)
4(*                                                                        *)
5(*             Xavier Leroy, projet Cristal, INRIA Rocquencourt           *)
6(*                                                                        *)
7(*   Copyright 2005 Institut National de Recherche en Informatique et     *)
8(*     en Automatique.                                                    *)
9(*                                                                        *)
10(*   All rights reserved.  This file is distributed under the terms of    *)
11(*   the GNU Lesser General Public License version 2.1, with the          *)
12(*   special exception on linking described in the file LICENSE.          *)
13(*                                                                        *)
14(**************************************************************************)
15
16(** Optimization parameters represented as ints indexed by round number. *)
17module Int_arg_helper : sig
18  type parsed
19
20  val parse : string -> string -> parsed ref -> unit
21
22  type parse_result =
23    | Ok
24    | Parse_failed of exn
25  val parse_no_error : string -> parsed ref -> parse_result
26
27  val get : key:int -> parsed -> int
28end
29
30(** Optimization parameters represented as floats indexed by round number. *)
31module Float_arg_helper : sig
32  type parsed
33
34  val parse : string -> string -> parsed ref -> unit
35
36  type parse_result =
37    | Ok
38    | Parse_failed of exn
39  val parse_no_error : string -> parsed ref -> parse_result
40
41  val get : key:int -> parsed -> float
42end
43
44type inlining_arguments = {
45  inline_call_cost : int option;
46  inline_alloc_cost : int option;
47  inline_prim_cost : int option;
48  inline_branch_cost : int option;
49  inline_indirect_cost : int option;
50  inline_lifting_benefit : int option;
51  inline_branch_factor : float option;
52  inline_max_depth : int option;
53  inline_max_unroll : int option;
54  inline_threshold : float option;
55  inline_toplevel_threshold : int option;
56}
57
58val classic_arguments : inlining_arguments
59val o1_arguments : inlining_arguments
60val o2_arguments : inlining_arguments
61val o3_arguments : inlining_arguments
62
63(** Set all the inlining arguments for a round.
64    The default is set if no round is provided. *)
65val use_inlining_arguments_set : ?round:int -> inlining_arguments -> unit
66
67val objfiles : string list ref
68val ccobjs : string list ref
69val dllibs : string list ref
70val compile_only : bool ref
71val output_name : string option ref
72val include_dirs : string list ref
73val no_std_include : bool ref
74val print_types : bool ref
75val make_archive : bool ref
76val debug : bool ref
77val fast : bool ref
78val link_everything : bool ref
79val custom_runtime : bool ref
80val no_check_prims : bool ref
81val bytecode_compatible_32 : bool ref
82val output_c_object : bool ref
83val output_complete_object : bool ref
84val all_ccopts : string list ref
85val classic : bool ref
86val nopervasives : bool ref
87val open_modules : string list ref
88val preprocessor : string option ref
89val all_ppx : string list ref
90val annotations : bool ref
91val binary_annotations : bool ref
92val use_threads : bool ref
93val use_vmthreads : bool ref
94val noassert : bool ref
95val verbose : bool ref
96val noprompt : bool ref
97val nopromptcont : bool ref
98val init_file : string option ref
99val noinit : bool ref
100val noversion : bool ref
101val use_prims : string ref
102val use_runtime : string ref
103val principal : bool ref
104val real_paths : bool ref
105val recursive_types : bool ref
106val strict_sequence : bool ref
107val strict_formats : bool ref
108val applicative_functors : bool ref
109val make_runtime : bool ref
110val gprofile : bool ref
111val c_compiler : string option ref
112val no_auto_link : bool ref
113val dllpaths : string list ref
114val make_package : bool ref
115val for_package : string option ref
116val error_size : int ref
117val float_const_prop : bool ref
118val transparent_modules : bool ref
119val dump_source : bool ref
120val dump_parsetree : bool ref
121val dump_typedtree : bool ref
122val dump_rawlambda : bool ref
123val dump_lambda : bool ref
124val dump_rawclambda : bool ref
125val dump_clambda : bool ref
126val dump_rawflambda : bool ref
127val dump_flambda : bool ref
128val dump_flambda_let : int option ref
129val dump_instr : bool ref
130val keep_asm_file : bool ref
131val optimize_for_speed : bool ref
132val dump_cmm : bool ref
133val dump_selection : bool ref
134val dump_cse : bool ref
135val dump_live : bool ref
136val dump_spill : bool ref
137val dump_split : bool ref
138val dump_interf : bool ref
139val dump_prefer : bool ref
140val dump_regalloc : bool ref
141val dump_reload : bool ref
142val dump_scheduling : bool ref
143val dump_linear : bool ref
144val keep_startup_file : bool ref
145val dump_combine : bool ref
146val native_code : bool ref
147val default_inline_threshold : float
148val inline_threshold : Float_arg_helper.parsed ref
149val inlining_report : bool ref
150val simplify_rounds : int option ref
151val default_simplify_rounds : int ref
152val rounds : unit -> int
153val default_inline_max_unroll : int
154val inline_max_unroll : Int_arg_helper.parsed ref
155val default_inline_toplevel_threshold : int
156val inline_toplevel_threshold : Int_arg_helper.parsed ref
157val default_inline_call_cost : int
158val default_inline_alloc_cost : int
159val default_inline_prim_cost : int
160val default_inline_branch_cost : int
161val default_inline_indirect_cost : int
162val default_inline_lifting_benefit : int
163val inline_call_cost : Int_arg_helper.parsed ref
164val inline_alloc_cost : Int_arg_helper.parsed ref
165val inline_prim_cost : Int_arg_helper.parsed ref
166val inline_branch_cost : Int_arg_helper.parsed ref
167val inline_indirect_cost : Int_arg_helper.parsed ref
168val inline_lifting_benefit : Int_arg_helper.parsed ref
169val default_inline_branch_factor : float
170val inline_branch_factor : Float_arg_helper.parsed ref
171val dont_write_files : bool ref
172val std_include_flag : string -> string
173val std_include_dir : unit -> string list
174val shared : bool ref
175val dlcode : bool ref
176val pic_code : bool ref
177val runtime_variant : string ref
178val force_slash : bool ref
179val keep_docs : bool ref
180val keep_locs : bool ref
181val unsafe_string : bool ref
182val opaque : bool ref
183val print_timings : bool ref
184val flambda_invariant_checks : bool ref
185val unbox_closures : bool ref
186val unbox_closures_factor : int ref
187val default_unbox_closures_factor : int
188val unbox_free_vars_of_closures : bool ref
189val unbox_specialised_args : bool ref
190val clambda_checks : bool ref
191val default_inline_max_depth : int
192val inline_max_depth : Int_arg_helper.parsed ref
193val remove_unused_arguments : bool ref
194val dump_flambda_verbose : bool ref
195val classic_inlining : bool ref
196val afl_instrument : bool ref
197val afl_inst_ratio : int ref
198
199val all_passes : string list ref
200val dumped_pass : string -> bool
201val set_dumped_pass : string -> bool -> unit
202
203val parse_color_setting : string -> Misc.Color.setting option
204val color : Misc.Color.setting option ref
205
206val unboxed_types : bool ref
207
208val arg_spec : (string * Arg.spec * string) list ref
209
210(* [add_arguments __LOC__ args] will add the arguments from [args] at
211   the end of [arg_spec], checking that they have not already been
212   added by [add_arguments] before. A warning is printed showing the
213   locations of the function from which the argument was previously
214   added. *)
215val add_arguments : string -> (string * Arg.spec * string) list -> unit
216
217(* [parse_arguments anon_arg usage] will parse the arguments, using
218  the arguments provided in [Clflags.arg_spec]. It allows plugins to
219  provide their own arguments.
220*)
221val parse_arguments : Arg.anon_fun -> string -> unit
222
223val print_arguments : string -> unit
224