Skip to content

Commit

Permalink
Rename stop_after_pass_names to available_pass_names
Browse files Browse the repository at this point in the history
  • Loading branch information
gretay-js committed Nov 4, 2019
1 parent db67434 commit a992599
Show file tree
Hide file tree
Showing 6 changed files with 7 additions and 10 deletions.
2 changes: 1 addition & 1 deletion driver/compenv.ml
Original file line number Diff line number Diff line change
Expand Up @@ -432,7 +432,7 @@ let read_one_param ppf position name v =

| "stop-after" ->
let module P = Clflags.Compiler_pass in
let passes = P.stop_after_pass_names ~native:!native_code in
let passes = P.available_pass_names ~native:!native_code in
begin match List.find_opt (String.equal v) passes with
| None ->
Printf.ksprintf (print_error ppf)
Expand Down
2 changes: 1 addition & 1 deletion driver/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -70,7 +70,7 @@ let main () =
"Options -i and -stop-after (%s) \
are incompatible with -pack, -a, -output-obj"
(String.concat "|"
(Clflags.Compiler_pass.stop_after_pass_names ~native:false))
(Clflags.Compiler_pass.available_pass_names ~native:false))
| Some P.Scheduling -> assert false (* native only *)
end;
if !make_archive then begin
Expand Down
2 changes: 1 addition & 1 deletion driver/main_args.ml
Original file line number Diff line number Diff line change
Expand Up @@ -108,7 +108,7 @@ let mk_function_sections f =

let mk_stop_after ~native f =
"-stop-after",
Arg.Symbol (Clflags.Compiler_pass.stop_after_pass_names ~native, f),
Arg.Symbol (Clflags.Compiler_pass.available_pass_names ~native, f),
" Stop after the given compilation pass."
;;

Expand Down
2 changes: 1 addition & 1 deletion driver/optmain.ml
Original file line number Diff line number Diff line change
Expand Up @@ -88,7 +88,7 @@ let main () =
"Options -i and -stop-after (%s) \
are incompatible with -pack, -a, -shared, -output-obj"
(String.concat "|"
(Clflags.Compiler_pass.stop_after_pass_names ~native:true))
(Clflags.Compiler_pass.available_pass_names ~native:true))
end;
if !make_archive then begin
Compmisc.init_path ();
Expand Down
7 changes: 2 additions & 5 deletions utils/clflags.ml
Original file line number Diff line number Diff line change
Expand Up @@ -450,13 +450,10 @@ module Compiler_pass = struct

let enabled is_native t = not (is_native_only t) || is_native

let pass_names is_native =
let available_pass_names ~native =
passes
|> List.filter (enabled is_native)
|> List.filter (enabled native)
|> List.map to_string

let stop_after_pass_names ~native =
pass_names native
end

let stop_after = ref None (* -stop-after *)
Expand Down
2 changes: 1 addition & 1 deletion utils/clflags.mli
Original file line number Diff line number Diff line change
Expand Up @@ -239,7 +239,7 @@ module Compiler_pass : sig
val of_string : string -> t option
val to_string : t -> string
val is_compilation_pass : t -> bool
val stop_after_pass_names : native:bool -> string list
val available_pass_names : native:bool -> string list
end
val stop_after : Compiler_pass.t option ref
val should_stop_after : Compiler_pass.t -> bool
Expand Down

0 comments on commit a992599

Please sign in to comment.