Use stop_early instead of compile_only

master
Greta Yorsh 2019-11-04 10:08:00 +00:00
parent 4d7d53c805
commit db674344b1
4 changed files with 16 additions and 10 deletions

View File

@ -440,8 +440,7 @@ let read_one_param ppf position name v =
v (String.concat ", " passes)
| Some v ->
let pass = Option.get (P.of_string v) in
Clflags.stop_after := Some pass;
compile_only := P.is_compilation_pass pass
Clflags.stop_after := Some pass
end
| _ ->
if not (List.mem name !can_discard) then begin

View File

@ -50,10 +50,15 @@ let main () =
end;
readenv ppf Before_link;
let module P = Clflags.Compiler_pass in
let stop_early = !compile_only ||
match !stop_after with
| None -> false
| Some p -> P.is_compilation_pass p
in
if
List.length
(List.filter (fun x -> !x)
[make_archive;make_package;compile_only;output_c_object])
[make_archive;make_package;ref stop_early;output_c_object])
> 1
then begin
match !stop_after with
@ -85,7 +90,7 @@ let main () =
revd (extracted_output));
Warnings.check_fatal ();
end
else if not !compile_only && !objfiles <> [] then begin
else if not stop_early && !objfiles <> [] then begin
let target =
if !output_c_object && not !output_complete_executable then
let s = extract_output !output_name in

View File

@ -1816,7 +1816,6 @@ module Default = struct
let _g = set debug
let _i () =
print_types := true;
compile_only := true;
stop_after := (Some Compiler_pass.Typing);
()
let _impl = impl
@ -1839,9 +1838,7 @@ module Default = struct
let module P = Compiler_pass in
match P.of_string pass with
| None -> () (* this should not occur as we use Arg.Symbol *)
| Some pass ->
stop_after := (Some pass);
compile_only := P.is_compilation_pass pass
| Some pass -> stop_after := (Some pass)
let _thread = set use_threads
let _verbose = set verbose
let _version () = print_version_string ()

View File

@ -67,10 +67,15 @@ let main () =
end;
readenv ppf Before_link;
let module P = Clflags.Compiler_pass in
let stop_early = !compile_only ||
match !stop_after with
| None -> false
| Some p -> P.is_compilation_pass p
in
if
List.length (List.filter (fun x -> !x)
[make_package; make_archive; shared;
compile_only; output_c_object]) > 1
ref stop_early; output_c_object]) > 1
then
begin
match !stop_after with
@ -108,7 +113,7 @@ let main () =
(get_objfiles ~with_ocamlparam:false) target);
Warnings.check_fatal ();
end
else if not !compile_only && !objfiles <> [] then begin
else if not stop_early && !objfiles <> [] then begin
let target =
if !output_c_object then
let s = extract_output !output_name in