Merge pull request #9688 from stedolan/main-compiler-libs

Expose the main entrypoint in compilerlibs
master
Stephen Dolan 2020-07-06 13:03:02 +01:00 committed by GitHub
commit 088fa01b3e
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
15 changed files with 341 additions and 312 deletions

74
.depend
View File

@ -5856,36 +5856,9 @@ driver/errors.cmx : \
driver/errors.cmi
driver/errors.cmi :
driver/main.cmo : \
utils/warnings.cmi \
utils/profile.cmi \
driver/makedepend.cmi \
driver/main_args.cmi \
parsing/location.cmi \
utils/config.cmi \
driver/compmisc.cmi \
driver/compile.cmi \
driver/compenv.cmi \
utils/clflags.cmi \
bytecomp/bytepackager.cmi \
bytecomp/bytelink.cmi \
bytecomp/bytelibrarian.cmi \
driver/main.cmi
driver/maindriver.cmi
driver/main.cmx : \
utils/warnings.cmx \
utils/profile.cmx \
driver/makedepend.cmx \
driver/main_args.cmx \
parsing/location.cmx \
utils/config.cmx \
driver/compmisc.cmx \
driver/compile.cmx \
driver/compenv.cmx \
utils/clflags.cmx \
bytecomp/bytepackager.cmx \
bytecomp/bytelink.cmx \
bytecomp/bytelibrarian.cmx \
driver/main.cmi
driver/main.cmi :
driver/maindriver.cmx
driver/main_args.cmo : \
utils/warnings.cmi \
utils/profile.cmi \
@ -5903,6 +5876,37 @@ driver/main_args.cmx : \
utils/clflags.cmx \
driver/main_args.cmi
driver/main_args.cmi :
driver/maindriver.cmo : \
utils/warnings.cmi \
utils/profile.cmi \
driver/makedepend.cmi \
driver/main_args.cmi \
parsing/location.cmi \
utils/config.cmi \
driver/compmisc.cmi \
driver/compile.cmi \
driver/compenv.cmi \
utils/clflags.cmi \
bytecomp/bytepackager.cmi \
bytecomp/bytelink.cmi \
bytecomp/bytelibrarian.cmi \
driver/maindriver.cmi
driver/maindriver.cmx : \
utils/warnings.cmx \
utils/profile.cmx \
driver/makedepend.cmx \
driver/main_args.cmx \
parsing/location.cmx \
utils/config.cmx \
driver/compmisc.cmx \
driver/compile.cmx \
driver/compenv.cmx \
utils/clflags.cmx \
bytecomp/bytepackager.cmx \
bytecomp/bytelink.cmx \
bytecomp/bytelibrarian.cmx \
driver/maindriver.cmi
driver/maindriver.cmi :
driver/makedepend.cmo : \
driver/pparse.cmi \
parsing/parsetree.cmi \
@ -5972,6 +5976,10 @@ driver/opterrors.cmx : \
driver/opterrors.cmi
driver/opterrors.cmi :
driver/optmain.cmo : \
driver/optmaindriver.cmi
driver/optmain.cmx : \
driver/optmaindriver.cmx
driver/optmaindriver.cmo : \
utils/warnings.cmi \
utils/profile.cmi \
asmcomp/proc.cmi \
@ -5990,8 +5998,8 @@ driver/optmain.cmo : \
asmcomp/asmlink.cmi \
asmcomp/asmlibrarian.cmi \
asmcomp/arch.cmo \
driver/optmain.cmi
driver/optmain.cmx : \
driver/optmaindriver.cmi
driver/optmaindriver.cmx : \
utils/warnings.cmx \
utils/profile.cmx \
asmcomp/proc.cmx \
@ -6010,8 +6018,8 @@ driver/optmain.cmx : \
asmcomp/asmlink.cmx \
asmcomp/asmlibrarian.cmx \
asmcomp/arch.cmx \
driver/optmain.cmi
driver/optmain.cmi :
driver/optmaindriver.cmi
driver/optmaindriver.cmi :
driver/pparse.cmo : \
utils/warnings.cmi \
utils/profile.cmi \

View File

@ -218,6 +218,9 @@ Working version
(Nicolás Ojeda Bär, review by David Allsopp, Sébastien Hinderer and Gabriel
Scherer)
- #9688: Expose the main entrypoint in compilerlibs
(Stephen Dolan, review by Nicolás Ojeda Bär, Greta Yorsh and David Allsopp)
### Build system:
- #7121, #9558: Always the autoconf-discovered ld in PACKLD. For

View File

@ -99,7 +99,7 @@ COMMON=$(UTILS) $(PARSING) $(TYPING) $(LAMBDA) $(COMP)
BYTECOMP=bytecomp/instruct.cmo bytecomp/bytegen.cmo \
bytecomp/printinstr.cmo bytecomp/emitcode.cmo \
bytecomp/bytelink.cmo bytecomp/bytelibrarian.cmo bytecomp/bytepackager.cmo \
driver/errors.cmo driver/compile.cmo
driver/errors.cmo driver/compile.cmo driver/maindriver.cmo
BYTECOMP_CMI=
INTEL_ASM=\
@ -153,7 +153,7 @@ ASMCOMP=\
asmcomp/branch_relaxation.cmo \
asmcomp/emitaux.cmo asmcomp/emit.cmo asmcomp/asmgen.cmo \
asmcomp/asmlink.cmo asmcomp/asmlibrarian.cmo asmcomp/asmpackager.cmo \
driver/opterrors.cmo driver/optcompile.cmo
driver/opterrors.cmo driver/optcompile.cmo driver/optmaindriver.cmo
ASMCOMP_CMI=$(ARCH_SPECIFIC_ASMCOMP_CMI)
# Files under middle_end/ are not to reference files under asmcomp/.

View File

@ -15,6 +15,8 @@
open Clflags
exception Exit_compiler of int
let output_prefix name =
let oname =
match !output_name with
@ -27,17 +29,19 @@ let print_version_and_library compiler =
print_string Config.version; print_newline();
print_string "Standard library directory: ";
print_string Config.standard_library; print_newline();
exit 0
raise (Exit_compiler 0)
let print_version_string () =
print_string Config.version; print_newline(); exit 0
print_string Config.version; print_newline();
raise (Exit_compiler 0)
let print_standard_library () =
print_string Config.standard_library; print_newline(); exit 0
print_string Config.standard_library; print_newline();
raise (Exit_compiler 0)
let fatal err =
prerr_endline err;
exit 2
raise (Exit_compiler 2)
let extract_output = function
| Some s -> s
@ -603,7 +607,7 @@ let process_action
| ProcessCFile name ->
readenv ppf (Before_compile name);
Location.input_name := name;
if Ccomp.compile_file name <> 0 then exit 2;
if Ccomp.compile_file name <> 0 then raise (Exit_compiler 2);
ccobjs := c_object_of_filename name :: !ccobjs
| ProcessObjects names ->
ccobjs := names @ !ccobjs

View File

@ -13,6 +13,8 @@
(* *)
(**************************************************************************)
exception Exit_compiler of int
val module_of_filename : string -> string -> string
val output_prefix : string -> string

View File

@ -1,116 +1,2 @@
(**************************************************************************)
(* *)
(* 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. *)
(* *)
(**************************************************************************)
open Clflags
open Compenv
let usage = "Usage: ocamlc <options> <files>\nOptions are:"
(* Error messages to standard error formatter *)
let ppf = Format.err_formatter
module Options = Main_args.Make_bytecomp_options (Main_args.Default.Main)
let main () =
Clflags.add_arguments __LOC__ Options.list;
Clflags.add_arguments __LOC__
["-depend", Arg.Unit Makedepend.main_from_option,
"<options> Compute dependencies (use 'ocamlc -depend -help' for details)"];
try
readenv ppf Before_args;
Clflags.parse_arguments anonymous usage;
Compmisc.read_clflags_from_env ();
if !Clflags.plugin then
fatal "-plugin is only supported up to OCaml 4.08.0";
begin try
Compenv.process_deferred_actions
(ppf,
Compile.implementation,
Compile.interface,
".cmo",
".cma");
with Arg.Bad msg ->
begin
prerr_endline msg;
Clflags.print_arguments usage;
exit 2
end
end;
readenv ppf Before_link;
if
List.length
(List.filter (fun x -> !x)
[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";
| Some ((P.Parsing | P.Typing) as p) ->
assert (P.is_compilation_pass p);
Printf.ksprintf fatal
"Options -i and -stop-after (%s) \
are incompatible with -pack, -a, -output-obj"
(String.concat "|"
(Clflags.Compiler_pass.available_pass_names ~native:false))
| Some P.Scheduling -> assert false (* native only *)
end;
if !make_archive then begin
Compmisc.init_path ();
Bytelibrarian.create_archive
(Compenv.get_objfiles ~with_ocamlparam:false)
(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
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
let target =
if !output_c_object && not !output_complete_executable then
let s = 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
(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
in
Compmisc.init_path ();
Bytelink.link (get_objfiles ~with_ocamlparam:true) target;
Warnings.check_fatal ();
end;
with x ->
Location.report_exception ppf x;
exit 2
let () =
main ();
Profile.print Format.std_formatter !Clflags.profile_columns;
exit 0
exit (Maindriver.main Sys.argv Format.err_formatter)

View File

@ -1875,12 +1875,12 @@ module Default = struct
let print_version () =
Printf.printf "The OCaml toplevel, version %s\n" Sys.ocaml_version;
exit 0;
raise (Compenv.Exit_compiler 0);
;;
let print_version_num () =
Printf.printf "%s\n" Sys.ocaml_version;
exit 0;
raise (Compenv.Exit_compiler 0);
;;
let _args (_:string) = (* placeholder: wrap_expand Arg.read_arg *) [||]

114
driver/maindriver.ml Normal file
View File

@ -0,0 +1,114 @@
(**************************************************************************)
(* *)
(* 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. *)
(* *)
(**************************************************************************)
open Clflags
open Compenv
let usage = "Usage: ocamlc <options> <files>\nOptions are:"
module Options = Main_args.Make_bytecomp_options (Main_args.Default.Main)
let main argv ppf =
Clflags.add_arguments __LOC__ Options.list;
Clflags.add_arguments __LOC__
["-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;
Compmisc.read_clflags_from_env ();
if !Clflags.plugin then
fatal "-plugin is only supported up to OCaml 4.08.0";
begin try
Compenv.process_deferred_actions
(ppf,
Compile.implementation,
Compile.interface,
".cmo",
".cma");
with Arg.Bad msg ->
begin
prerr_endline msg;
Clflags.print_arguments usage;
exit 2
end
end;
readenv ppf Before_link;
if
List.length
(List.filter (fun x -> !x)
[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";
| Some ((P.Parsing | P.Typing) as p) ->
assert (P.is_compilation_pass p);
Printf.ksprintf fatal
"Options -i and -stop-after (%s) \
are incompatible with -pack, -a, -output-obj"
(String.concat "|"
(Clflags.Compiler_pass.available_pass_names ~native:false))
| Some P.Scheduling -> assert false (* native only *)
end;
if !make_archive then begin
Compmisc.init_path ();
Bytelibrarian.create_archive
(Compenv.get_objfiles ~with_ocamlparam:false)
(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
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
let target =
if !output_c_object && not !output_complete_executable then
let s = 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
(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
in
Compmisc.init_path ();
Bytelink.link (get_objfiles ~with_ocamlparam:true) target;
Warnings.check_fatal ();
end;
with
| exception (Compenv.Exit_compiler n) ->
n
| exception x ->
Location.report_exception ppf x;
2
| () ->
Profile.print Format.std_formatter !Clflags.profile_columns;
0

View File

@ -13,6 +13,9 @@
(* *)
(**************************************************************************)
(*
this "empty" file is here to speed up garbage collection in ocamlc.opt
*)
(* [main argv ppf] runs the compiler with arguments [argv], printing any
errors encountered to [ppf], and returns the exit code.
NB: Due to internal state in the compiler, calling [main] twice during
the same process is unsupported. *)
val main : string array -> Format.formatter -> int

View File

@ -575,7 +575,7 @@ let print_version_num () =
exit 0;
;;
let main () =
let run_main argv =
Clflags.classic := false;
Compenv.readenv ppf Before_args;
Clflags.reset_arguments (); (* reset arguments from ocamlc/ocamlopt *)
@ -643,19 +643,23 @@ let main () =
Printf.sprintf "Usage: %s [options] <source files>\nOptions are:"
(Filename.basename Sys.argv.(0))
in
Clflags.parse_arguments file_dependencies usage;
Clflags.parse_arguments argv file_dependencies usage;
Compenv.readenv ppf Before_link;
if !sort_files then sort_files_by_dependencies !files
else List.iter print_file_dependencies (List.sort compare !files);
exit (if Error_occurred.get () then 2 else 0)
let main () =
run_main Sys.argv
let main_from_option () =
if Sys.argv.(1) <> "-depend" then begin
Printf.eprintf
"Fatal error: argument -depend must be used as first argument.\n%!";
exit 2;
end;
incr Arg.current;
Sys.argv.(0) <- Sys.argv.(0) ^ " -depend";
Sys.argv.(!Arg.current) <- Sys.argv.(0);
main ()
let args =
Array.concat [ [| Sys.argv.(0) ^ " -depend" |];
Array.sub Sys.argv 2 (Array.length Sys.argv - 2) ] in
Sys.argv.(0) <- args.(0);
run_main args

View File

@ -1,139 +1,2 @@
(**************************************************************************)
(* *)
(* 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. *)
(* *)
(**************************************************************************)
open Clflags
open Compenv
module Backend = struct
(* See backend_intf.mli. *)
let symbol_for_global' = Compilenv.symbol_for_global'
let closure_symbol = Compilenv.closure_symbol
let really_import_approx = Import_approx.really_import_approx
let import_symbol = Import_approx.import_symbol
let size_int = Arch.size_int
let big_endian = Arch.big_endian
let max_sensible_number_of_arguments =
(* The "-1" is to allow for a potential closure environment parameter. *)
Proc.max_arguments_for_tailcalls - 1
end
let backend = (module Backend : Backend_intf.S)
let usage = "Usage: ocamlopt <options> <files>\nOptions are:"
module Options = Main_args.Make_optcomp_options (Main_args.Default.Optmain)
let main () =
native_code := true;
let ppf = Format.err_formatter in
try
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 anonymous usage;
Compmisc.read_clflags_from_env ();
if !Clflags.plugin then
fatal "-plugin is only supported up to OCaml 4.08.0";
begin try
Compenv.process_deferred_actions
(ppf,
Optcompile.implementation ~backend,
Optcompile.interface,
".cmx",
".cmxa");
with Arg.Bad msg ->
begin
prerr_endline msg;
Clflags.print_arguments usage;
exit 2
end
end;
readenv ppf Before_link;
if
List.length (List.filter (fun x -> !x)
[make_package; make_archive; shared;
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";
| Some ((P.Parsing | P.Typing | P.Scheduling) as p) ->
assert (P.is_compilation_pass p);
Printf.ksprintf fatal
"Options -i and -stop-after (%s) \
are incompatible with -pack, -a, -shared, -output-obj"
(String.concat "|"
(Clflags.Compiler_pass.available_pass_names ~native:true))
end;
if !make_archive then begin
Compmisc.init_path ();
let target = extract_output !output_name in
Asmlibrarian.create_archive
(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
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);
Warnings.check_fatal ();
end
else if !shared then begin
Compmisc.init_path ();
let target = 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);
Warnings.check_fatal ();
end
else if not !stop_early && !objfiles <> [] then begin
let target =
if !output_c_object then
let s = extract_output !output_name in
if (Filename.check_suffix s Config.ext_obj
|| Filename.check_suffix s Config.ext_dll)
then s
else
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
in
Compmisc.init_path ();
Compmisc.with_ppf_dump ~file_prefix:target (fun ppf_dump ->
Asmlink.link ~ppf_dump (get_objfiles ~with_ocamlparam:true) target);
Warnings.check_fatal ();
end;
with x ->
Location.report_exception ppf x;
exit 2
let () =
main ();
Profile.print Format.std_formatter !Clflags.profile_columns;
exit 0
exit (Optmaindriver.main Sys.argv Format.err_formatter)

139
driver/optmaindriver.ml Normal file
View File

@ -0,0 +1,139 @@
(**************************************************************************)
(* *)
(* 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. *)
(* *)
(**************************************************************************)
open Clflags
open Compenv
module Backend = struct
(* See backend_intf.mli. *)
let symbol_for_global' = Compilenv.symbol_for_global'
let closure_symbol = Compilenv.closure_symbol
let really_import_approx = Import_approx.really_import_approx
let import_symbol = Import_approx.import_symbol
let size_int = Arch.size_int
let big_endian = Arch.big_endian
let max_sensible_number_of_arguments =
(* The "-1" is to allow for a potential closure environment parameter. *)
Proc.max_arguments_for_tailcalls - 1
end
let backend = (module Backend : Backend_intf.S)
let usage = "Usage: ocamlopt <options> <files>\nOptions are:"
module Options = Main_args.Make_optcomp_options (Main_args.Default.Optmain)
let main argv ppf =
native_code := true;
match
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;
Compmisc.read_clflags_from_env ();
if !Clflags.plugin then
fatal "-plugin is only supported up to OCaml 4.08.0";
begin try
Compenv.process_deferred_actions
(ppf,
Optcompile.implementation ~backend,
Optcompile.interface,
".cmx",
".cmxa");
with Arg.Bad msg ->
begin
prerr_endline msg;
Clflags.print_arguments usage;
exit 2
end
end;
readenv ppf Before_link;
if
List.length (List.filter (fun x -> !x)
[make_package; make_archive; shared;
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";
| Some ((P.Parsing | P.Typing | P.Scheduling) as p) ->
assert (P.is_compilation_pass p);
Printf.ksprintf fatal
"Options -i and -stop-after (%s) \
are incompatible with -pack, -a, -shared, -output-obj"
(String.concat "|"
(Clflags.Compiler_pass.available_pass_names ~native:true))
end;
if !make_archive then begin
Compmisc.init_path ();
let target = extract_output !output_name in
Asmlibrarian.create_archive
(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
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);
Warnings.check_fatal ();
end
else if !shared then begin
Compmisc.init_path ();
let target = 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);
Warnings.check_fatal ();
end
else if not !stop_early && !objfiles <> [] then begin
let target =
if !output_c_object then
let s = extract_output !output_name in
if (Filename.check_suffix s Config.ext_obj
|| Filename.check_suffix s Config.ext_dll)
then s
else
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
in
Compmisc.init_path ();
Compmisc.with_ppf_dump ~file_prefix:target (fun ppf_dump ->
Asmlink.link ~ppf_dump (get_objfiles ~with_ocamlparam:true) target);
Warnings.check_fatal ();
end;
with
| exception (Exit_compiler n) ->
n
| exception x ->
Location.report_exception ppf x;
2
| () ->
Profile.print Format.std_formatter !Clflags.profile_columns;
0

View File

@ -13,6 +13,9 @@
(* *)
(**************************************************************************)
(*
this "empty" file is here to speed up garbage collection in ocamlopt.opt
*)
(* [main argv ppf] runs the compiler with arguments [argv], printing any
errors encountered to [ppf], and returns the exit code.
NB: Due to internal state in the compiler, calling [main] twice during
the same process is unsupported. *)
val main : string array -> Format.formatter -> int

View File

@ -494,10 +494,10 @@ let print_arguments 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].*)
let parse_arguments f msg =
let parse_arguments argv f msg =
try
let argv = ref Sys.argv in
let current = ref (!Arg.current) in
let argv = ref argv in
let current = ref 0 in
Arg.parse_and_expand_argv_dynamic current argv arg_spec f msg
with
| Arg.Bad msg -> Printf.eprintf "%s" msg; exit 2

View File

@ -254,10 +254,10 @@ val arg_spec : (string * Arg.spec * string) list ref
added. *)
val add_arguments : string -> (string * Arg.spec * string) list -> unit
(* [parse_arguments anon_arg usage] will parse the arguments, using
(* [parse_arguments argv anon_arg usage] will parse the arguments, using
the arguments provided in [Clflags.arg_spec].
*)
val parse_arguments : Arg.anon_fun -> string -> unit
val parse_arguments : string array -> Arg.anon_fun -> string -> unit
(* [print_arguments usage] print the standard usage message *)
val print_arguments : string -> unit