Unopen Compenv in the code base (this is a nop). (#9933)

master
Daniel Bünzli 2020-09-23 22:55:21 +02:00 committed by GitHub
parent eface9f3f6
commit ad12d494a8
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
7 changed files with 58 additions and 64 deletions

View File

@ -14,7 +14,6 @@
(**************************************************************************)
open Misc
open Compenv
type info = {
source_file : string;
@ -33,7 +32,7 @@ let annot i = i.output_prefix ^ ".annot"
let with_info ~native ~tool_name ~source_file ~output_prefix ~dump_ext k =
Compmisc.init_path ();
let module_name = module_of_filename source_file output_prefix in
let module_name = Compenv.module_of_filename source_file output_prefix in
Env.set_unit_name module_name;
let env = Compmisc.initial_env() in
let dump_file = String.concat "." [output_prefix; dump_ext] in

View File

@ -13,8 +13,6 @@
(* *)
(**************************************************************************)
open Compenv
(* Initialize the search path.
[dir] is always searched first (default: the current directory),
then the directories specified with the -I option (in command-line order),
@ -28,7 +26,8 @@ let init_path ?(dir="") () =
!Clflags.include_dirs
in
let dirs =
!last_include_dirs @ dirs @ Config.flexdll_dirs @ !first_include_dirs
!Compenv.last_include_dirs @ dirs @ Config.flexdll_dirs @
!Compenv.first_include_dirs
in
let exp_dirs =
List.map (Misc.expand_directory Config.standard_library) dirs in

View File

@ -1657,7 +1657,6 @@ let options_with_command_line_syntax options r =
module Default = struct
open Clflags
open Compenv
let set r () = r := true
let clear r () = r := false
@ -1688,7 +1687,7 @@ module Default = struct
let _unsafe_string = set unsafe_string
let _w s = Warnings.parse_options false s
let anonymous = anonymous
let anonymous = Compenv.anonymous
end
@ -1708,7 +1707,7 @@ module Default = struct
let _error_style =
Misc.set_or_ignore error_style_reader.parse error_style
let _nopervasives = set nopervasives
let _ppx s = first_ppx := (s :: (!first_ppx))
let _ppx s = Compenv.first_ppx := (s :: (!Compenv.first_ppx))
let _unsafe = set unsafe
let _warn_error s = Warnings.parse_options true s
let _warn_help = Warnings.help_warnings
@ -1826,8 +1825,8 @@ module Default = struct
let _binannot = set binary_annotations
let _c = set compile_only
let _cc s = c_compiler := (Some s)
let _cclib s = defer (ProcessObjects (Misc.rev_split_words s))
let _ccopt s = first_ccopts := (s :: (!first_ccopts))
let _cclib s = Compenv.defer (ProcessObjects (Misc.rev_split_words s))
let _ccopt s = Compenv.first_ccopts := (s :: (!Compenv.first_ccopts))
let _config = Misc.show_config_and_exit
let _config_var = Misc.show_config_variable_and_exit
let _dprofile () = profile_columns := Profile.all_columns
@ -1836,8 +1835,8 @@ module Default = struct
let _for_pack s = for_package := (Some s)
let _g = set debug
let _i = set print_types
let _impl = impl
let _intf = intf
let _impl = Compenv.impl
let _intf = Compenv.intf
let _intf_suffix s = Config.interface_suffix := s
let _keep_docs = set keep_docs
let _keep_locs = set keep_locs
@ -1861,12 +1860,12 @@ module Default = struct
| None -> stop_after := (Some pass)
| Some p ->
if not (p = pass) then
fatal "Please specify at most one -stop-after <pass>."
Compenv.fatal "Please specify at most one -stop-after <pass>."
let _thread = set use_threads
let _verbose = set verbose
let _version () = print_version_string ()
let _vnum () = print_version_string ()
let _where () = print_standard_library ()
let _version () = Compenv.print_version_string ()
let _vnum () = Compenv.print_version_string ()
let _where () = Compenv.print_standard_library ()
let _with_runtime = set with_runtime
let _without_runtime = clear with_runtime
end
@ -1915,18 +1914,18 @@ module Default = struct
let _afl_instrument = set afl_instrument
let _function_sections () =
assert Config.function_sections;
first_ccopts := ("-ffunction-sections" :: (!first_ccopts));
Compenv.first_ccopts := ("-ffunction-sections" ::(!Compenv.first_ccopts));
function_sections := true
let _nodynlink = clear dlcode
let _output_complete_obj () =
set output_c_object (); set output_complete_object ()
let _output_obj = set output_c_object
let _p () =
fatal
Compenv.fatal
"Profiling with \"gprof\" (option `-p') is only supported up to \
OCaml 4.08.0"
let _shared () = shared := true; dlcode := true
let _v () = print_version_and_library "native-code compiler"
let _v () = Compenv.print_version_and_library "native-code compiler"
end
module Odoc_args = struct
@ -1967,7 +1966,7 @@ third-party libraries such as Lwt, but with a different API."
let _custom = set custom_runtime
let _dcamlprimc = set keep_camlprimc_file
let _dinstr = set dump_instr
let _dllib s = defer (ProcessDLLs (Misc.rev_split_words s))
let _dllib s = Compenv.defer (ProcessDLLs (Misc.rev_split_words s))
let _dllpath s = dllpaths := ((!dllpaths) @ [s])
let _make_runtime () =
custom_runtime := true; make_runtime := true; link_everything := true
@ -1981,8 +1980,8 @@ third-party libraries such as Lwt, but with a different API."
let _output_obj () = output_c_object := true; custom_runtime := true
let _use_prims s = use_prims := s
let _use_runtime s = use_runtime := s
let _v () = print_version_and_library "compiler"
let _vmthread () = fatal vmthread_removed_message
let _v () = Compenv.print_version_and_library "compiler"
let _vmthread () = Compenv.fatal vmthread_removed_message
end
end

View File

@ -14,7 +14,6 @@
(**************************************************************************)
open Clflags
open Compenv
let usage = "Usage: ocamlc <options> <files>\nOptions are:"
@ -26,11 +25,11 @@ let main argv ppf =
["-depend", Arg.Unit Makedepend.main_from_option,
"<options> Compute dependencies (use 'ocamlc -depend -help' for details)"];
match
readenv ppf Before_args;
Clflags.parse_arguments argv anonymous usage;
Compenv.readenv ppf Before_args;
Clflags.parse_arguments argv Compenv.anonymous usage;
Compmisc.read_clflags_from_env ();
if !Clflags.plugin then
fatal "-plugin is only supported up to OCaml 4.08.0";
Compenv.fatal "-plugin is only supported up to OCaml 4.08.0";
begin try
Compenv.process_deferred_actions
(ppf,
@ -45,20 +44,21 @@ let main argv ppf =
exit 2
end
end;
readenv ppf Before_link;
Compenv.readenv ppf Before_link;
if
List.length
(List.filter (fun x -> !x)
[make_archive;make_package;stop_early;output_c_object])
[make_archive;make_package;Compenv.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";
Compenv.fatal
"Please specify at most one of -pack, -a, -c, -output-obj";
| Some ((P.Parsing | P.Typing) as p) ->
assert (P.is_compilation_pass p);
Printf.ksprintf fatal
Printf.ksprintf Compenv.fatal
"Options -i and -stop-after (%s) \
are incompatible with -pack, -a, -output-obj"
(String.concat "|"
@ -70,37 +70,37 @@ let main argv ppf =
Bytelibrarian.create_archive
(Compenv.get_objfiles ~with_ocamlparam:false)
(extract_output !output_name);
(Compenv.extract_output !output_name);
Warnings.check_fatal ();
end
else if !make_package then begin
Compmisc.init_path ();
let extracted_output = extract_output !output_name in
let revd = get_objfiles ~with_ocamlparam:false in
let extracted_output = Compenv.extract_output !output_name in
let revd = Compenv.get_objfiles ~with_ocamlparam:false in
Compmisc.with_ppf_dump ~file_prefix:extracted_output (fun ppf_dump ->
Bytepackager.package_files ~ppf_dump (Compmisc.initial_env ())
revd (extracted_output));
Warnings.check_fatal ();
end
else if not !stop_early && !objfiles <> [] then begin
else if not !Compenv.stop_early && !objfiles <> [] then begin
let target =
if !output_c_object && not !output_complete_executable then
let s = extract_output !output_name in
let s = Compenv.extract_output !output_name in
if (Filename.check_suffix s Config.ext_obj
|| Filename.check_suffix s Config.ext_dll
|| Filename.check_suffix s ".c")
then s
else
fatal
Compenv.fatal
(Printf.sprintf
"The extension of the output file must be .c, %s or %s"
Config.ext_obj Config.ext_dll
)
else
default_output !output_name
Compenv.default_output !output_name
in
Compmisc.init_path ();
Bytelink.link (get_objfiles ~with_ocamlparam:true) target;
Bytelink.link (Compenv.get_objfiles ~with_ocamlparam:true) target;
Warnings.check_fatal ();
end;
with

View File

@ -13,7 +13,6 @@
(* *)
(**************************************************************************)
open Compenv
open Parsetree
module String = Misc.Stdlib.String
@ -635,7 +634,7 @@ let run_main argv =
"<plugin> (no longer supported)";
"-pp", Arg.String(fun s -> Clflags.preprocessor := Some s),
"<cmd> Pipe sources through preprocessor <cmd>";
"-ppx", Arg.String (add_to_list first_ppx),
"-ppx", Arg.String (add_to_list Compenv.first_ppx),
"<cmd> Pipe abstract syntax trees through preprocessor <cmd>";
"-shared", Arg.Set shared,
" Generate dependencies for native plugin files (.cmxs targets)";

View File

@ -14,7 +14,6 @@
(**************************************************************************)
open Clflags
open Compenv
module Backend = struct
(* See backend_intf.mli. *)
@ -40,16 +39,16 @@ module Options = Main_args.Make_optcomp_options (Main_args.Default.Optmain)
let main argv ppf =
native_code := true;
match
readenv ppf Before_args;
Compenv.readenv ppf Before_args;
Clflags.add_arguments __LOC__ (Arch.command_line_options @ Options.list);
Clflags.add_arguments __LOC__
["-depend", Arg.Unit Makedepend.main_from_option,
"<options> Compute dependencies \
(use 'ocamlopt -depend -help' for details)"];
Clflags.parse_arguments argv anonymous usage;
Clflags.parse_arguments argv Compenv.anonymous usage;
Compmisc.read_clflags_from_env ();
if !Clflags.plugin then
fatal "-plugin is only supported up to OCaml 4.08.0";
Compenv.fatal "-plugin is only supported up to OCaml 4.08.0";
begin try
Compenv.process_deferred_actions
(ppf,
@ -64,21 +63,21 @@ let main argv ppf =
exit 2
end
end;
readenv ppf Before_link;
Compenv.readenv ppf Before_link;
if
List.length (List.filter (fun x -> !x)
[make_package; make_archive; shared;
stop_early; output_c_object]) > 1
Compenv.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, \
-output-obj";
Compenv.fatal "Please specify at most one of -pack, -a, -shared, -c, \
-output-obj";
| Some ((P.Parsing | P.Typing | P.Scheduling) as p) ->
assert (P.is_compilation_pass p);
Printf.ksprintf fatal
Printf.ksprintf Compenv.fatal
"Options -i and -stop-after (%s) \
are incompatible with -pack, -a, -shared, -output-obj"
(String.concat "|"
@ -86,50 +85,51 @@ let main argv ppf =
end;
if !make_archive then begin
Compmisc.init_path ();
let target = extract_output !output_name in
let target = Compenv.extract_output !output_name in
Asmlibrarian.create_archive
(get_objfiles ~with_ocamlparam:false) target;
(Compenv.get_objfiles ~with_ocamlparam:false) target;
Warnings.check_fatal ();
end
else if !make_package then begin
Compmisc.init_path ();
let target = extract_output !output_name in
let target = Compenv.extract_output !output_name in
Compmisc.with_ppf_dump ~file_prefix:target (fun ppf_dump ->
Asmpackager.package_files ~ppf_dump (Compmisc.initial_env ())
(get_objfiles ~with_ocamlparam:false) target ~backend);
(Compenv.get_objfiles ~with_ocamlparam:false) target ~backend);
Warnings.check_fatal ();
end
else if !shared then begin
Compmisc.init_path ();
let target = extract_output !output_name in
let target = Compenv.extract_output !output_name in
Compmisc.with_ppf_dump ~file_prefix:target (fun ppf_dump ->
Asmlink.link_shared ~ppf_dump
(get_objfiles ~with_ocamlparam:false) target);
(Compenv.get_objfiles ~with_ocamlparam:false) target);
Warnings.check_fatal ();
end
else if not !stop_early && !objfiles <> [] then begin
else if not !Compenv.stop_early && !objfiles <> [] then begin
let target =
if !output_c_object then
let s = extract_output !output_name in
let s = Compenv.extract_output !output_name in
if (Filename.check_suffix s Config.ext_obj
|| Filename.check_suffix s Config.ext_dll)
then s
else
fatal
Compenv.fatal
(Printf.sprintf
"The extension of the output file must be %s or %s"
Config.ext_obj Config.ext_dll
)
else
default_output !output_name
Compenv.default_output !output_name
in
Compmisc.init_path ();
Compmisc.with_ppf_dump ~file_prefix:target (fun ppf_dump ->
Asmlink.link ~ppf_dump (get_objfiles ~with_ocamlparam:true) target);
let objs = Compenv.get_objfiles ~with_ocamlparam:true in
Asmlink.link ~ppf_dump objs target);
Warnings.check_fatal ();
end;
with
| exception (Exit_compiler n) ->
| exception (Compenv.Exit_compiler n) ->
n
| exception x ->
Location.report_exception ppf x;

View File

@ -13,8 +13,6 @@
(* *)
(**************************************************************************)
open Compenv
let usage = "Usage: ocaml <options> <object-files> [script-file [arguments]]\n\
options are:"
@ -43,7 +41,7 @@ let prepare ppf =
try
let res =
let objects =
List.rev (!preload_objects @ !first_objfiles)
List.rev (!preload_objects @ !Compenv.first_objfiles)
in
List.for_all (Topdirs.load_file ppf) objects
in