Skip to content

Commit

Permalink
Add Compenv.stop_early flag
Browse files Browse the repository at this point in the history
  • Loading branch information
gretay-js committed Nov 4, 2019
1 parent a992599 commit 4353c75
Show file tree
Hide file tree
Showing 5 changed files with 22 additions and 21 deletions.
7 changes: 7 additions & 0 deletions driver/compenv.ml
Original file line number Diff line number Diff line change
Expand Up @@ -56,6 +56,7 @@ let first_ppx = ref []
let last_ppx = ref []
let first_objfiles = ref []
let last_objfiles = ref []
let stop_early = ref false

(* Check validity of module name *)
let is_unit_name name =
Expand Down Expand Up @@ -670,3 +671,9 @@ let process_deferred_actions env =
fatal "Option -a cannot be used with .cmxa input files.";
List.iter (process_action env) (List.rev !deferred_actions);
output_name := final_output_name;
stop_early :=
!compile_only ||
!print_types ||
match !stop_after with
| None -> false
| Some p -> Clflags.Compiler_pass.is_compilation_pass p;
2 changes: 2 additions & 0 deletions driver/compenv.mli
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,8 @@ val get_objfiles : with_ocamlparam:bool -> string list
val last_objfiles : string list ref
val first_objfiles : string list ref

val stop_early : bool ref

type filename = string

type readenv_position =
Expand Down
11 changes: 3 additions & 8 deletions driver/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -49,18 +49,13 @@ let main () =
end
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;ref stop_early;output_c_object])
[make_archive;make_package;stop_early;output_c_object])
> 1
then begin
let module P = Clflags.Compiler_pass in
match !stop_after with
| None ->
fatal "Please specify at most one of -pack, -a, -c, -output-obj";
Expand Down Expand Up @@ -90,7 +85,7 @@ let main () =
revd (extracted_output));
Warnings.check_fatal ();
end
else if not stop_early && !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
Expand Down
12 changes: 7 additions & 5 deletions driver/main_args.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1814,10 +1814,7 @@ module Default = struct
let _dump_into_file = set dump_into_file
let _for_pack s = for_package := (Some s)
let _g = set debug
let _i () =
print_types := true;
stop_after := (Some Compiler_pass.Typing);
()
let _i = set print_types
let _impl = impl
let _intf = intf
let _intf_suffix s = Config.interface_suffix := s
Expand All @@ -1838,7 +1835,12 @@ 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)
| Some pass ->
match !stop_after with
| None -> stop_after := (Some pass)
| Some p ->
if not (p = pass) then
fatal "Please specify at most one -stop-after <pass>."
let _thread = set use_threads
let _verbose = set verbose
let _version () = print_version_string ()
Expand Down
11 changes: 3 additions & 8 deletions driver/optmain.ml
Original file line number Diff line number Diff line change
Expand Up @@ -66,18 +66,13 @@ let main () =
end
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;
ref stop_early; output_c_object]) > 1
stop_early; output_c_object]) > 1
then
begin
let module P = Clflags.Compiler_pass in
match !stop_after with
| None ->
fatal "Please specify at most one of -pack, -a, -shared, -c, \
Expand Down Expand Up @@ -113,7 +108,7 @@ let main () =
(get_objfiles ~with_ocamlparam:false) target);
Warnings.check_fatal ();
end
else if not stop_early && !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
Expand Down

0 comments on commit 4353c75

Please sign in to comment.