2016-02-18 07:11:59 -08:00
|
|
|
(**************************************************************************)
|
|
|
|
(* *)
|
|
|
|
(* OCaml *)
|
|
|
|
(* *)
|
|
|
|
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
|
|
|
(* *)
|
|
|
|
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
|
|
|
(* en Automatique. *)
|
|
|
|
(* *)
|
|
|
|
(* All rights reserved. This file is distributed under the terms of *)
|
|
|
|
(* the GNU Lesser General Public License version 2.1, with the *)
|
|
|
|
(* special exception on linking described in the file LICENSE. *)
|
|
|
|
(* *)
|
|
|
|
(**************************************************************************)
|
1995-08-09 08:06:35 -07:00
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
(* Command-line parameters *)
|
|
|
|
|
2016-01-14 03:27:30 -08:00
|
|
|
module Int_arg_helper = Arg_helper.Make (struct
|
|
|
|
module Key = struct
|
|
|
|
include Numbers.Int
|
|
|
|
let of_string = int_of_string
|
|
|
|
end
|
|
|
|
|
|
|
|
module Value = struct
|
|
|
|
include Numbers.Int
|
|
|
|
let of_string = int_of_string
|
|
|
|
end
|
|
|
|
end)
|
|
|
|
module Float_arg_helper = Arg_helper.Make (struct
|
|
|
|
module Key = struct
|
|
|
|
include Numbers.Int
|
|
|
|
let of_string = int_of_string
|
|
|
|
end
|
|
|
|
|
|
|
|
module Value = struct
|
|
|
|
include Numbers.Float
|
|
|
|
let of_string = float_of_string
|
|
|
|
end
|
|
|
|
end)
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
let objfiles = ref ([] : string list) (* .cmo and .cma files *)
|
2001-10-30 01:32:32 -08:00
|
|
|
and ccobjs = ref ([] : string list) (* .o, .a, .so and -cclib -lxxx *)
|
|
|
|
and dllibs = ref ([] : string list) (* .so and -dllib -lxxx *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
let compile_only = ref false (* -c *)
|
2002-06-11 07:15:12 -07:00
|
|
|
and output_name = ref (None : string option) (* -o *)
|
1996-04-29 06:24:35 -07:00
|
|
|
and include_dirs = ref ([] : string list)(* -I *)
|
2002-02-14 07:17:11 -08:00
|
|
|
and no_std_include = ref false (* -nostdlib *)
|
1995-05-04 03:15:53 -07:00
|
|
|
and print_types = ref false (* -i *)
|
|
|
|
and make_archive = ref false (* -a *)
|
1996-11-29 10:36:42 -08:00
|
|
|
and debug = ref false (* -g *)
|
2018-10-15 04:50:06 -07:00
|
|
|
and debug_full = ref false (* For full DWARF support *)
|
2018-07-15 12:01:26 -07:00
|
|
|
and unsafe = ref false (* -unsafe *)
|
2015-12-24 16:04:43 -08:00
|
|
|
and use_linscan = ref false (* -linscan *)
|
1995-05-04 03:15:53 -07:00
|
|
|
and link_everything = ref false (* -linkall *)
|
|
|
|
and custom_runtime = ref false (* -custom *)
|
2015-04-22 03:53:47 -07:00
|
|
|
and no_check_prims = ref false (* -no-check-prims *)
|
2013-04-18 04:58:59 -07:00
|
|
|
and bytecode_compatible_32 = ref false (* -compat-32 *)
|
1996-11-07 03:01:32 -08:00
|
|
|
and output_c_object = ref false (* -output-obj *)
|
2015-07-17 07:31:05 -07:00
|
|
|
and output_complete_object = ref false (* -output-complete-obj *)
|
2019-09-25 00:07:31 -07:00
|
|
|
and output_complete_executable = ref false (* -output-complete-exe *)
|
2013-06-05 09:34:40 -07:00
|
|
|
and all_ccopts = ref ([] : string list) (* -ccopt *)
|
2001-09-06 01:52:32 -07:00
|
|
|
and classic = ref false (* -nolabels *)
|
1995-05-04 03:15:53 -07:00
|
|
|
and nopervasives = ref false (* -nopervasives *)
|
2018-05-18 14:21:01 -07:00
|
|
|
and match_context_rows = ref 32 (* -match-context-rows *)
|
1996-04-29 06:24:35 -07:00
|
|
|
and preprocessor = ref(None : string option) (* -pp *)
|
2013-06-05 09:34:40 -07:00
|
|
|
and all_ppx = ref ([] : string list) (* -ppx *)
|
2018-07-06 05:43:29 -07:00
|
|
|
let absname = ref false (* -absname *)
|
2007-05-16 01:21:41 -07:00
|
|
|
let annotations = ref false (* -annot *)
|
2012-05-30 07:52:37 -07:00
|
|
|
let binary_annotations = ref false (* -annot *)
|
2003-07-17 01:38:28 -07:00
|
|
|
and use_threads = ref false (* -thread *)
|
1997-05-13 11:28:25 -07:00
|
|
|
and noassert = ref false (* -noassert *)
|
1997-05-15 06:30:31 -07:00
|
|
|
and verbose = ref false (* -verbose *)
|
2016-05-03 07:45:25 -07:00
|
|
|
and noversion = ref false (* -no-version *)
|
2004-11-02 02:42:58 -08:00
|
|
|
and noprompt = ref false (* -noprompt *)
|
2012-01-27 04:48:15 -08:00
|
|
|
and nopromptcont = ref false (* -nopromptcont *)
|
2005-01-28 09:52:58 -08:00
|
|
|
and init_file = ref (None : string option) (* -init *)
|
2013-08-04 12:58:09 -07:00
|
|
|
and noinit = ref false (* -noinit *)
|
2014-08-07 02:46:34 -07:00
|
|
|
and open_modules = ref [] (* -open *)
|
2002-02-14 07:17:11 -08:00
|
|
|
and use_prims = ref "" (* -use-prims ... *)
|
|
|
|
and use_runtime = ref "" (* -use-runtime ... *)
|
2019-03-13 03:46:37 -07:00
|
|
|
and plugin = ref false (* -plugin ... *)
|
2002-04-18 00:27:47 -07:00
|
|
|
and principal = ref false (* -principal *)
|
2013-01-29 06:21:12 -08:00
|
|
|
and real_paths = ref true (* -short-paths *)
|
1999-11-08 15:45:01 -08:00
|
|
|
and recursive_types = ref false (* -rectypes *)
|
2009-12-09 01:17:12 -08:00
|
|
|
and strict_sequence = ref false (* -strict-sequence *)
|
2014-08-29 10:14:00 -07:00
|
|
|
and strict_formats = ref false (* -strict-formats *)
|
2009-07-15 07:06:37 -07:00
|
|
|
and applicative_functors = ref true (* -no-app-funct *)
|
2011-03-17 09:18:05 -07:00
|
|
|
and make_runtime = ref false (* -make-runtime *)
|
2008-12-03 10:09:09 -08:00
|
|
|
and c_compiler = ref (None: string option) (* -cc *)
|
2000-03-09 01:12:28 -08:00
|
|
|
and no_auto_link = ref false (* -noautolink *)
|
2001-08-28 07:47:48 -07:00
|
|
|
and dllpaths = ref ([] : string list) (* -dllpath *)
|
2002-02-08 08:55:44 -08:00
|
|
|
and make_package = ref false (* -pack *)
|
2005-08-01 08:51:09 -07:00
|
|
|
and for_package = ref (None: string option) (* -for-pack *)
|
2011-10-19 22:49:38 -07:00
|
|
|
and error_size = ref 500 (* -error-size *)
|
2014-04-25 01:41:13 -07:00
|
|
|
and float_const_prop = ref true (* -no-float-const-prop *)
|
2013-12-19 22:55:26 -08:00
|
|
|
and transparent_modules = ref false (* -trans-mod *)
|
2019-12-24 04:35:42 -08:00
|
|
|
let unique_ids = ref true (* -d(no-)unique-ds *)
|
|
|
|
let locations = ref true (* -d(no-)locations *)
|
2012-10-17 09:09:38 -07:00
|
|
|
let dump_source = ref false (* -dsource *)
|
1999-09-08 10:43:13 -07:00
|
|
|
let dump_parsetree = ref false (* -dparsetree *)
|
2012-12-18 09:19:53 -08:00
|
|
|
and dump_typedtree = ref false (* -dtypedtree *)
|
1999-09-08 10:43:13 -07:00
|
|
|
and dump_rawlambda = ref false (* -drawlambda *)
|
1995-12-15 02:21:58 -08:00
|
|
|
and dump_lambda = ref false (* -dlambda *)
|
2016-01-14 03:27:30 -08:00
|
|
|
and dump_rawclambda = ref false (* -drawclambda *)
|
2012-02-21 09:41:02 -08:00
|
|
|
and dump_clambda = ref false (* -dclambda *)
|
2016-02-09 02:33:57 -08:00
|
|
|
and dump_rawflambda = ref false (* -drawflambda *)
|
2016-01-14 03:27:30 -08:00
|
|
|
and dump_flambda = ref false (* -dflambda *)
|
|
|
|
and dump_flambda_let = ref (None : int option) (* -dflambda-let=... *)
|
|
|
|
and dump_flambda_verbose = ref false (* -dflambda-verbose *)
|
1995-05-04 03:15:53 -07:00
|
|
|
and dump_instr = ref false (* -dinstr *)
|
2018-06-27 06:56:29 -07:00
|
|
|
and keep_camlprimc_file = ref false (* -dcamlprimc *)
|
1995-05-22 04:58:51 -07:00
|
|
|
|
1995-07-20 00:52:12 -07:00
|
|
|
let keep_asm_file = ref false (* -S *)
|
1995-07-13 10:17:20 -07:00
|
|
|
let optimize_for_speed = ref true (* -compact *)
|
2014-08-18 06:28:34 -07:00
|
|
|
and opaque = ref false (* -opaque *)
|
1995-07-02 09:50:39 -07:00
|
|
|
|
|
|
|
and dump_cmm = ref false (* -dcmm *)
|
|
|
|
let dump_selection = ref false (* -dsel *)
|
2014-04-26 03:40:22 -07:00
|
|
|
let dump_cse = ref false (* -dcse *)
|
1995-07-02 09:50:39 -07:00
|
|
|
let dump_live = ref false (* -dlive *)
|
2017-09-15 03:08:14 -07:00
|
|
|
let dump_avail = ref false (* -davail *)
|
1995-07-02 09:50:39 -07:00
|
|
|
let dump_spill = ref false (* -dspill *)
|
|
|
|
let dump_split = ref false (* -dsplit *)
|
|
|
|
let dump_interf = ref false (* -dinterf *)
|
|
|
|
let dump_prefer = ref false (* -dprefer *)
|
|
|
|
let dump_regalloc = ref false (* -dalloc *)
|
|
|
|
let dump_reload = ref false (* -dreload *)
|
1995-08-13 02:31:50 -07:00
|
|
|
let dump_scheduling = ref false (* -dscheduling *)
|
1995-07-02 09:50:39 -07:00
|
|
|
let dump_linear = ref false (* -dlinear *)
|
2015-12-24 16:04:43 -08:00
|
|
|
let dump_interval = ref false (* -dinterval *)
|
1995-07-10 02:48:27 -07:00
|
|
|
let keep_startup_file = ref false (* -dstartup *)
|
1999-05-15 08:10:00 -07:00
|
|
|
let dump_combine = ref false (* -dcombine *)
|
2017-06-09 04:29:21 -07:00
|
|
|
let profile_columns : Profile.column list ref = ref [] (* -dprofile/-dtimings *)
|
2016-02-10 08:52:07 -08:00
|
|
|
|
2017-09-15 03:08:14 -07:00
|
|
|
let debug_runavail = ref false (* -drunavail *)
|
|
|
|
|
1996-10-22 06:37:20 -07:00
|
|
|
let native_code = ref false (* set to true under ocamlopt *)
|
2016-02-10 08:52:07 -08:00
|
|
|
|
2013-06-05 09:34:40 -07:00
|
|
|
let force_slash = ref false (* for ocamldep *)
|
2016-01-14 03:27:30 -08:00
|
|
|
let clambda_checks = ref false (* -clambda-checks *)
|
2000-10-02 07:18:05 -07:00
|
|
|
|
2018-04-06 01:49:57 -07:00
|
|
|
let flambda_invariant_checks =
|
|
|
|
ref Config.with_flambda_invariants (* -flambda-(no-)invariants *)
|
2016-02-10 08:52:07 -08:00
|
|
|
|
2002-06-07 01:03:46 -07:00
|
|
|
let dont_write_files = ref false (* set to true under ocamldoc *)
|
2002-02-14 07:17:11 -08:00
|
|
|
|
2019-02-05 09:05:24 -08:00
|
|
|
let insn_sched_default = true
|
|
|
|
let insn_sched = ref insn_sched_default (* -[no-]insn-sched *)
|
|
|
|
|
2002-02-14 07:17:11 -08:00
|
|
|
let std_include_flag prefix =
|
|
|
|
if !no_std_include then ""
|
|
|
|
else (prefix ^ (Filename.quote Config.standard_library))
|
|
|
|
;;
|
|
|
|
|
|
|
|
let std_include_dir () =
|
|
|
|
if !no_std_include then [] else [Config.standard_library]
|
|
|
|
;;
|
2007-11-06 07:16:56 -08:00
|
|
|
|
|
|
|
let shared = ref false (* -shared *)
|
2008-07-15 08:31:32 -07:00
|
|
|
let dlcode = ref true (* not -nodynlink *)
|
2011-03-17 09:18:05 -07:00
|
|
|
|
2015-01-24 08:35:26 -08:00
|
|
|
let pic_code = ref (match Config.architecture with (* -fPIC *)
|
|
|
|
| "amd64" -> true
|
|
|
|
| _ -> false)
|
|
|
|
|
2013-06-03 11:03:59 -07:00
|
|
|
let runtime_variant = ref "";; (* -runtime-variant *)
|
2019-03-11 04:45:55 -07:00
|
|
|
let with_runtime = ref true;; (* -with-runtime *)
|
2013-09-17 05:45:05 -07:00
|
|
|
|
2015-06-28 06:11:50 -07:00
|
|
|
let keep_docs = ref false (* -keep-docs *)
|
2017-06-30 04:13:06 -07:00
|
|
|
let keep_locs = ref true (* -keep-locs *)
|
2017-09-30 14:20:06 -07:00
|
|
|
let unsafe_string =
|
|
|
|
if Config.safe_string then ref false
|
2017-10-02 04:41:33 -07:00
|
|
|
else ref (not Config.default_safe_string)
|
2016-08-01 07:06:59 -07:00
|
|
|
(* -safe-string / -unsafe-string *)
|
2015-08-15 08:57:51 -07:00
|
|
|
|
2016-02-10 08:52:07 -08:00
|
|
|
let classic_inlining = ref false (* -Oclassic *)
|
|
|
|
let inlining_report = ref false (* -inlining-report *)
|
|
|
|
|
2016-12-06 08:18:04 -08:00
|
|
|
let afl_instrument = ref Config.afl_instrument (* -afl-instrument *)
|
|
|
|
let afl_inst_ratio = ref 100 (* -afl-inst-ratio *)
|
|
|
|
|
2019-06-27 09:07:25 -07:00
|
|
|
let function_sections = ref false (* -function-sections *)
|
|
|
|
|
2016-02-10 08:52:07 -08:00
|
|
|
let simplify_rounds = ref None (* -rounds *)
|
|
|
|
let default_simplify_rounds = ref 1 (* -rounds *)
|
|
|
|
let rounds () =
|
|
|
|
match !simplify_rounds with
|
|
|
|
| None -> !default_simplify_rounds
|
|
|
|
| Some r -> r
|
|
|
|
|
|
|
|
let default_inline_threshold = if Config.flambda then 10. else 10. /. 8.
|
2016-01-14 03:27:30 -08:00
|
|
|
let inline_toplevel_multiplier = 16
|
|
|
|
let default_inline_toplevel_threshold =
|
|
|
|
int_of_float ((float inline_toplevel_multiplier) *. default_inline_threshold)
|
|
|
|
let default_inline_call_cost = 5
|
2016-02-26 08:15:06 -08:00
|
|
|
let default_inline_alloc_cost = 7
|
2016-01-14 03:27:30 -08:00
|
|
|
let default_inline_prim_cost = 3
|
2016-02-08 05:05:38 -08:00
|
|
|
let default_inline_branch_cost = 5
|
|
|
|
let default_inline_indirect_cost = 4
|
2016-02-10 08:52:07 -08:00
|
|
|
let default_inline_branch_factor = 0.1
|
2016-01-14 03:27:30 -08:00
|
|
|
let default_inline_lifting_benefit = 1300
|
2016-02-10 08:52:07 -08:00
|
|
|
let default_inline_max_unroll = 0
|
|
|
|
let default_inline_max_depth = 1
|
2016-01-14 03:27:30 -08:00
|
|
|
|
2016-02-10 08:52:07 -08:00
|
|
|
let inline_threshold = ref (Float_arg_helper.default default_inline_threshold)
|
|
|
|
let inline_toplevel_threshold =
|
|
|
|
ref (Int_arg_helper.default default_inline_toplevel_threshold)
|
2016-01-14 03:27:30 -08:00
|
|
|
let inline_call_cost = ref (Int_arg_helper.default default_inline_call_cost)
|
|
|
|
let inline_alloc_cost = ref (Int_arg_helper.default default_inline_alloc_cost)
|
|
|
|
let inline_prim_cost = ref (Int_arg_helper.default default_inline_prim_cost)
|
|
|
|
let inline_branch_cost =
|
|
|
|
ref (Int_arg_helper.default default_inline_branch_cost)
|
|
|
|
let inline_indirect_cost =
|
|
|
|
ref (Int_arg_helper.default default_inline_indirect_cost)
|
2016-02-10 08:52:07 -08:00
|
|
|
let inline_branch_factor =
|
|
|
|
ref (Float_arg_helper.default default_inline_branch_factor)
|
2016-01-14 03:27:30 -08:00
|
|
|
let inline_lifting_benefit =
|
|
|
|
ref (Int_arg_helper.default default_inline_lifting_benefit)
|
2016-02-10 08:52:07 -08:00
|
|
|
let inline_max_unroll =
|
|
|
|
ref (Int_arg_helper.default default_inline_max_unroll)
|
|
|
|
let inline_max_depth =
|
|
|
|
ref (Int_arg_helper.default default_inline_max_depth)
|
2016-01-14 03:27:30 -08:00
|
|
|
|
|
|
|
|
2016-02-10 08:52:07 -08:00
|
|
|
let unbox_specialised_args = ref true (* -no-unbox-specialised-args *)
|
2016-02-08 05:05:38 -08:00
|
|
|
let unbox_free_vars_of_closures = ref true
|
2016-01-14 03:27:30 -08:00
|
|
|
let unbox_closures = ref false (* -unbox-closures *)
|
2016-02-26 08:15:06 -08:00
|
|
|
let default_unbox_closures_factor = 10
|
|
|
|
let unbox_closures_factor =
|
|
|
|
ref default_unbox_closures_factor (* -unbox-closures-factor *)
|
2016-01-14 03:27:30 -08:00
|
|
|
let remove_unused_arguments = ref false (* -remove-unused-arguments *)
|
|
|
|
|
|
|
|
type inlining_arguments = {
|
|
|
|
inline_call_cost : int option;
|
|
|
|
inline_alloc_cost : int option;
|
|
|
|
inline_prim_cost : int option;
|
|
|
|
inline_branch_cost : int option;
|
|
|
|
inline_indirect_cost : int option;
|
|
|
|
inline_lifting_benefit : int option;
|
2016-02-10 08:52:07 -08:00
|
|
|
inline_branch_factor : float option;
|
|
|
|
inline_max_depth : int option;
|
|
|
|
inline_max_unroll : int option;
|
2016-01-14 03:27:30 -08:00
|
|
|
inline_threshold : float option;
|
|
|
|
inline_toplevel_threshold : int option;
|
|
|
|
}
|
|
|
|
|
2016-02-10 08:52:07 -08:00
|
|
|
let set_int_arg round (arg:Int_arg_helper.parsed ref) default value =
|
|
|
|
let value : int =
|
|
|
|
match value with
|
|
|
|
| None -> default
|
|
|
|
| Some value -> value
|
|
|
|
in
|
|
|
|
match round with
|
|
|
|
| None ->
|
|
|
|
arg := Int_arg_helper.set_base_default value
|
|
|
|
(Int_arg_helper.reset_base_overrides !arg)
|
|
|
|
| Some round ->
|
|
|
|
arg := Int_arg_helper.add_base_override round value !arg
|
|
|
|
|
|
|
|
let set_float_arg round (arg:Float_arg_helper.parsed ref) default value =
|
|
|
|
let value =
|
|
|
|
match value with
|
|
|
|
| None -> default
|
|
|
|
| Some value -> value
|
|
|
|
in
|
|
|
|
match round with
|
|
|
|
| None ->
|
|
|
|
arg := Float_arg_helper.set_base_default value
|
|
|
|
(Float_arg_helper.reset_base_overrides !arg)
|
|
|
|
| Some round ->
|
|
|
|
arg := Float_arg_helper.add_base_override round value !arg
|
2016-01-14 03:27:30 -08:00
|
|
|
|
|
|
|
let use_inlining_arguments_set ?round (arg:inlining_arguments) =
|
|
|
|
let set_int = set_int_arg round in
|
|
|
|
let set_float = set_float_arg round in
|
2016-02-10 08:52:07 -08:00
|
|
|
set_int inline_call_cost default_inline_call_cost arg.inline_call_cost;
|
|
|
|
set_int inline_alloc_cost default_inline_alloc_cost arg.inline_alloc_cost;
|
|
|
|
set_int inline_prim_cost default_inline_prim_cost arg.inline_prim_cost;
|
|
|
|
set_int inline_branch_cost
|
|
|
|
default_inline_branch_cost arg.inline_branch_cost;
|
|
|
|
set_int inline_indirect_cost
|
|
|
|
default_inline_indirect_cost arg.inline_indirect_cost;
|
|
|
|
set_int inline_lifting_benefit
|
|
|
|
default_inline_lifting_benefit arg.inline_lifting_benefit;
|
|
|
|
set_float inline_branch_factor
|
|
|
|
default_inline_branch_factor arg.inline_branch_factor;
|
|
|
|
set_int inline_max_depth
|
|
|
|
default_inline_max_depth arg.inline_max_depth;
|
|
|
|
set_int inline_max_unroll
|
|
|
|
default_inline_max_unroll arg.inline_max_unroll;
|
|
|
|
set_float inline_threshold
|
|
|
|
default_inline_threshold arg.inline_threshold;
|
|
|
|
set_int inline_toplevel_threshold
|
|
|
|
default_inline_toplevel_threshold arg.inline_toplevel_threshold
|
2016-01-14 03:27:30 -08:00
|
|
|
|
|
|
|
(* o1 is the default *)
|
|
|
|
let o1_arguments = {
|
|
|
|
inline_call_cost = None;
|
|
|
|
inline_alloc_cost = None;
|
|
|
|
inline_prim_cost = None;
|
|
|
|
inline_branch_cost = None;
|
|
|
|
inline_indirect_cost = None;
|
|
|
|
inline_lifting_benefit = None;
|
2016-02-10 08:52:07 -08:00
|
|
|
inline_branch_factor = None;
|
|
|
|
inline_max_depth = None;
|
|
|
|
inline_max_unroll = None;
|
2016-01-14 03:27:30 -08:00
|
|
|
inline_threshold = None;
|
|
|
|
inline_toplevel_threshold = None;
|
|
|
|
}
|
|
|
|
|
|
|
|
let classic_arguments = {
|
|
|
|
inline_call_cost = None;
|
|
|
|
inline_alloc_cost = None;
|
|
|
|
inline_prim_cost = None;
|
|
|
|
inline_branch_cost = None;
|
|
|
|
inline_indirect_cost = None;
|
|
|
|
inline_lifting_benefit = None;
|
2016-02-10 08:52:07 -08:00
|
|
|
inline_branch_factor = None;
|
|
|
|
inline_max_depth = None;
|
|
|
|
inline_max_unroll = None;
|
2016-01-14 03:27:30 -08:00
|
|
|
(* [inline_threshold] matches the current compiler's default.
|
|
|
|
Note that this particular fraction can be expressed exactly in
|
|
|
|
floating point. *)
|
|
|
|
inline_threshold = Some (10. /. 8.);
|
|
|
|
(* [inline_toplevel_threshold] is not used in classic mode. *)
|
|
|
|
inline_toplevel_threshold = Some 1;
|
|
|
|
}
|
|
|
|
|
|
|
|
let o2_arguments = {
|
|
|
|
inline_call_cost = Some (2 * default_inline_call_cost);
|
|
|
|
inline_alloc_cost = Some (2 * default_inline_alloc_cost);
|
|
|
|
inline_prim_cost = Some (2 * default_inline_prim_cost);
|
|
|
|
inline_branch_cost = Some (2 * default_inline_branch_cost);
|
|
|
|
inline_indirect_cost = Some (2 * default_inline_indirect_cost);
|
|
|
|
inline_lifting_benefit = None;
|
2016-02-10 08:52:07 -08:00
|
|
|
inline_branch_factor = None;
|
|
|
|
inline_max_depth = Some 2;
|
|
|
|
inline_max_unroll = None;
|
2016-01-14 03:27:30 -08:00
|
|
|
inline_threshold = Some 25.;
|
|
|
|
inline_toplevel_threshold = Some (25 * inline_toplevel_multiplier);
|
|
|
|
}
|
|
|
|
|
|
|
|
let o3_arguments = {
|
|
|
|
inline_call_cost = Some (3 * default_inline_call_cost);
|
|
|
|
inline_alloc_cost = Some (3 * default_inline_alloc_cost);
|
|
|
|
inline_prim_cost = Some (3 * default_inline_prim_cost);
|
|
|
|
inline_branch_cost = Some (3 * default_inline_branch_cost);
|
|
|
|
inline_indirect_cost = Some (3 * default_inline_indirect_cost);
|
|
|
|
inline_lifting_benefit = None;
|
2016-02-10 08:52:07 -08:00
|
|
|
inline_branch_factor = Some 0.;
|
|
|
|
inline_max_depth = Some 3;
|
|
|
|
inline_max_unroll = Some 1;
|
2016-01-14 03:27:30 -08:00
|
|
|
inline_threshold = Some 50.;
|
|
|
|
inline_toplevel_threshold = Some (50 * inline_toplevel_multiplier);
|
|
|
|
}
|
|
|
|
|
|
|
|
let all_passes = ref []
|
|
|
|
let dumped_passes_list = ref []
|
|
|
|
let dumped_pass s =
|
|
|
|
assert(List.mem s !all_passes);
|
|
|
|
List.mem s !dumped_passes_list
|
|
|
|
|
|
|
|
let set_dumped_pass s enabled =
|
2016-02-08 05:05:38 -08:00
|
|
|
if (List.mem s !all_passes) then begin
|
|
|
|
let passes_without_s = List.filter ((<>) s) !dumped_passes_list in
|
|
|
|
let dumped_passes =
|
|
|
|
if enabled then
|
|
|
|
s :: passes_without_s
|
|
|
|
else
|
|
|
|
passes_without_s
|
|
|
|
in
|
|
|
|
dumped_passes_list := dumped_passes
|
|
|
|
end
|
2016-01-14 03:27:30 -08:00
|
|
|
|
2018-07-27 00:51:53 -07:00
|
|
|
let dump_into_file = ref false (* -dump-into-file *)
|
|
|
|
|
2018-10-19 13:20:30 -07:00
|
|
|
type 'a env_reader = {
|
|
|
|
parse : string -> 'a option;
|
2019-02-27 05:28:06 -08:00
|
|
|
print : 'a -> string;
|
2018-10-19 13:20:30 -07:00
|
|
|
usage : string;
|
|
|
|
env_var : string;
|
|
|
|
}
|
|
|
|
|
|
|
|
let color = ref None (* -color *)
|
|
|
|
|
|
|
|
let color_reader = {
|
|
|
|
parse = (function
|
|
|
|
| "auto" -> Some Misc.Color.Auto
|
|
|
|
| "always" -> Some Misc.Color.Always
|
|
|
|
| "never" -> Some Misc.Color.Never
|
|
|
|
| _ -> None);
|
2019-02-27 05:28:06 -08:00
|
|
|
print = (function
|
|
|
|
| Misc.Color.Auto -> "auto"
|
|
|
|
| Misc.Color.Always -> "always"
|
|
|
|
| Misc.Color.Never -> "never");
|
2018-10-19 13:20:30 -07:00
|
|
|
usage = "expected \"auto\", \"always\" or \"never\"";
|
|
|
|
env_var = "OCAML_COLOR";
|
|
|
|
}
|
|
|
|
|
|
|
|
let error_style = ref None (* -error-style *)
|
|
|
|
|
|
|
|
let error_style_reader = {
|
|
|
|
parse = (function
|
|
|
|
| "contextual" -> Some Misc.Error_style.Contextual
|
|
|
|
| "short" -> Some Misc.Error_style.Short
|
|
|
|
| _ -> None);
|
2019-02-27 05:28:06 -08:00
|
|
|
print = (function
|
|
|
|
| Misc.Error_style.Contextual -> "contextual"
|
|
|
|
| Misc.Error_style.Short -> "short");
|
2018-10-19 13:20:30 -07:00
|
|
|
usage = "expected \"contextual\" or \"short\"";
|
|
|
|
env_var = "OCAML_ERROR_STYLE";
|
|
|
|
}
|
2016-05-25 07:29:05 -07:00
|
|
|
|
|
|
|
let unboxed_types = ref false
|
2017-01-17 05:34:35 -08:00
|
|
|
|
2020-10-07 03:32:40 -07:00
|
|
|
(* This is used by the -save-ir-after option. *)
|
|
|
|
module Compiler_ir = struct
|
|
|
|
type t = Linear
|
2020-10-13 06:07:13 -07:00
|
|
|
|
|
|
|
let all = [
|
|
|
|
Linear;
|
|
|
|
]
|
|
|
|
|
2020-10-07 03:32:40 -07:00
|
|
|
let extension t =
|
|
|
|
let ext =
|
|
|
|
match t with
|
2020-10-13 06:07:13 -07:00
|
|
|
| Linear -> "linear"
|
2020-10-07 03:32:40 -07:00
|
|
|
in
|
|
|
|
".cmir-" ^ ext
|
|
|
|
|
2020-10-13 06:07:13 -07:00
|
|
|
(** [extract_extension_with_pass filename] returns the IR whose extension
|
|
|
|
is a prefix of the extension of [filename], and the suffix,
|
|
|
|
which can be used to distinguish different passes on the same IR.
|
|
|
|
For example, [extract_extension_with_pass "foo.cmir-linear123"]
|
|
|
|
returns [Some (Linear, "123")]. *)
|
|
|
|
let extract_extension_with_pass filename =
|
|
|
|
let ext = Filename.extension filename in
|
|
|
|
let ext_len = String.length ext in
|
|
|
|
if ext_len <= 0 then None
|
|
|
|
else begin
|
|
|
|
let is_prefix ir =
|
|
|
|
let s = extension ir in
|
|
|
|
let s_len = String.length s in
|
|
|
|
s_len <= ext_len && s = String.sub ext 0 s_len
|
|
|
|
in
|
|
|
|
let drop_prefix ir =
|
|
|
|
let s = extension ir in
|
|
|
|
let s_len = String.length s in
|
|
|
|
String.sub ext s_len (ext_len - s_len)
|
|
|
|
in
|
|
|
|
let ir = List.find_opt is_prefix all in
|
|
|
|
match ir with
|
|
|
|
| None -> None
|
|
|
|
| Some ir -> Some (ir, drop_prefix ir)
|
|
|
|
end
|
2020-10-07 03:32:40 -07:00
|
|
|
end
|
|
|
|
|
2015-11-10 03:18:48 -08:00
|
|
|
(* This is used by the -stop-after option. *)
|
|
|
|
module Compiler_pass = struct
|
|
|
|
(* If you add a new pass, the following must be updated:
|
|
|
|
- the variable `passes` below
|
|
|
|
- the manpages in man/ocaml{c,opt}.m
|
|
|
|
- the manual manual/manual/cmds/unified-options.etex
|
|
|
|
*)
|
2020-10-13 06:07:13 -07:00
|
|
|
type t = Parsing | Typing | Scheduling | Emit
|
2015-11-10 03:18:48 -08:00
|
|
|
|
|
|
|
let to_string = function
|
|
|
|
| Parsing -> "parsing"
|
|
|
|
| Typing -> "typing"
|
2019-08-26 09:12:14 -07:00
|
|
|
| Scheduling -> "scheduling"
|
2020-10-13 06:07:13 -07:00
|
|
|
| Emit -> "emit"
|
2015-11-10 03:18:48 -08:00
|
|
|
|
|
|
|
let of_string = function
|
|
|
|
| "parsing" -> Some Parsing
|
|
|
|
| "typing" -> Some Typing
|
2019-08-26 09:12:14 -07:00
|
|
|
| "scheduling" -> Some Scheduling
|
2020-10-13 06:07:13 -07:00
|
|
|
| "emit" -> Some Emit
|
2015-11-10 03:18:48 -08:00
|
|
|
| _ -> None
|
|
|
|
|
|
|
|
let rank = function
|
|
|
|
| Parsing -> 0
|
|
|
|
| Typing -> 1
|
2019-08-26 09:12:14 -07:00
|
|
|
| Scheduling -> 50
|
2020-10-13 06:07:13 -07:00
|
|
|
| Emit -> 60
|
2015-11-10 03:18:48 -08:00
|
|
|
|
|
|
|
let passes = [
|
|
|
|
Parsing;
|
|
|
|
Typing;
|
2019-08-26 09:12:14 -07:00
|
|
|
Scheduling;
|
2020-10-13 06:07:13 -07:00
|
|
|
Emit;
|
2015-11-10 03:18:48 -08:00
|
|
|
]
|
2019-08-26 09:12:14 -07:00
|
|
|
let is_compilation_pass _ = true
|
|
|
|
let is_native_only = function
|
|
|
|
| Scheduling -> true
|
2020-10-13 06:07:13 -07:00
|
|
|
| Emit -> true
|
2019-08-26 09:12:14 -07:00
|
|
|
| _ -> false
|
|
|
|
|
|
|
|
let enabled is_native t = not (is_native_only t) || is_native
|
2020-10-07 03:32:40 -07:00
|
|
|
let can_save_ir_after = function
|
|
|
|
| Scheduling -> true
|
|
|
|
| _ -> false
|
2019-08-26 09:12:14 -07:00
|
|
|
|
2020-10-07 03:32:40 -07:00
|
|
|
let available_pass_names ~filter ~native =
|
2019-08-26 09:12:14 -07:00
|
|
|
passes
|
2019-11-04 02:45:08 -08:00
|
|
|
|> List.filter (enabled native)
|
2020-10-07 03:32:40 -07:00
|
|
|
|> List.filter filter
|
2019-08-26 09:12:14 -07:00
|
|
|
|> List.map to_string
|
2020-10-13 06:07:13 -07:00
|
|
|
|
|
|
|
let compare a b =
|
|
|
|
compare (rank a) (rank b)
|
|
|
|
|
|
|
|
let to_output_filename t ~prefix =
|
|
|
|
match t with
|
|
|
|
| Scheduling -> prefix ^ Compiler_ir.(extension Linear)
|
|
|
|
| _ -> Misc.fatal_error "Not supported"
|
|
|
|
|
|
|
|
let of_input_filename name =
|
|
|
|
match Compiler_ir.extract_extension_with_pass name with
|
|
|
|
| Some (Linear, _) -> Some Emit
|
|
|
|
| None -> None
|
2015-11-10 03:18:48 -08:00
|
|
|
end
|
|
|
|
|
|
|
|
let stop_after = ref None (* -stop-after *)
|
|
|
|
|
|
|
|
let should_stop_after pass =
|
2019-11-26 07:55:43 -08:00
|
|
|
if Compiler_pass.(rank Typing <= rank pass) && !print_types then true
|
|
|
|
else
|
|
|
|
match !stop_after with
|
|
|
|
| None -> false
|
|
|
|
| Some stop -> Compiler_pass.rank stop <= Compiler_pass.rank pass
|
2015-11-10 03:18:48 -08:00
|
|
|
|
2020-10-07 03:32:40 -07:00
|
|
|
let save_ir_after = ref []
|
|
|
|
|
|
|
|
let should_save_ir_after pass =
|
|
|
|
List.mem pass !save_ir_after
|
|
|
|
|
|
|
|
let set_save_ir_after pass enabled =
|
|
|
|
let other_passes = List.filter ((<>) pass) !save_ir_after in
|
|
|
|
let new_passes =
|
|
|
|
if enabled then
|
|
|
|
pass :: other_passes
|
|
|
|
else
|
|
|
|
other_passes
|
|
|
|
in
|
|
|
|
save_ir_after := new_passes
|
|
|
|
|
2018-07-23 05:19:41 -07:00
|
|
|
module String = Misc.Stdlib.String
|
|
|
|
|
2017-01-17 05:34:35 -08:00
|
|
|
let arg_spec = ref []
|
2018-07-23 05:19:41 -07:00
|
|
|
let arg_names = ref String.Map.empty
|
2017-05-14 07:44:42 -07:00
|
|
|
|
|
|
|
let reset_arguments () =
|
|
|
|
arg_spec := [];
|
2018-07-23 05:19:41 -07:00
|
|
|
arg_names := String.Map.empty
|
2017-05-14 07:44:42 -07:00
|
|
|
|
2017-01-17 05:34:35 -08:00
|
|
|
let add_arguments loc args =
|
|
|
|
List.iter (function (arg_name, _, _) as arg ->
|
|
|
|
try
|
2018-07-23 05:19:41 -07:00
|
|
|
let loc2 = String.Map.find arg_name !arg_names in
|
2017-01-17 05:34:35 -08:00
|
|
|
Printf.eprintf
|
2019-03-13 03:46:37 -07:00
|
|
|
"Warning: compiler argument %s is already defined:\n" arg_name;
|
2017-01-17 05:34:35 -08:00
|
|
|
Printf.eprintf " First definition: %s\n" loc2;
|
|
|
|
Printf.eprintf " New definition: %s\n" loc;
|
|
|
|
with Not_found ->
|
|
|
|
arg_spec := !arg_spec @ [ arg ];
|
2018-07-23 05:19:41 -07:00
|
|
|
arg_names := String.Map.add arg_name loc !arg_names
|
2017-01-17 05:34:35 -08:00
|
|
|
) args
|
|
|
|
|
|
|
|
let print_arguments usage =
|
|
|
|
Arg.usage !arg_spec usage
|
|
|
|
|
|
|
|
(* This function is almost the same as [Arg.parse_expand], except
|
|
|
|
that [Arg.parse_expand] could not be used because it does not take a
|
|
|
|
reference for [arg_spec].*)
|
2020-06-16 05:32:41 -07:00
|
|
|
let parse_arguments argv f msg =
|
2017-01-17 05:34:35 -08:00
|
|
|
try
|
2020-06-16 05:32:41 -07:00
|
|
|
let argv = ref argv in
|
2020-06-16 07:32:58 -07:00
|
|
|
let current = ref 0 in
|
2017-01-17 05:34:35 -08:00
|
|
|
Arg.parse_and_expand_argv_dynamic current argv arg_spec f msg
|
|
|
|
with
|
|
|
|
| Arg.Bad msg -> Printf.eprintf "%s" msg; exit 2
|
|
|
|
| Arg.Help msg -> Printf.printf "%s" msg; exit 0
|