Introduce the -without-runtime option.

master
Lucas Pluvinage 2019-03-11 12:45:55 +01:00
parent bcf176cfd5
commit e61263c0ac
15 changed files with 63 additions and 6 deletions

View File

@ -39,6 +39,11 @@ Working version
(Jules Aguillon, with help from Armaël Guéneau,
review by Gabriel Scherer and Florian Angeletti)
- #2309: New options -with-runtime and -without-runtime in ocamlopt/ocamlc
that control the inclusion of the runtime system in the generated program.
(Lucas Pluvinage, review by Daniel Bünzli, Damien Doligez, David Allsopp
and Florian Angeletti)
- #2314: Remove support for gprof profiling.
(Mark Shinwell, review by Xavier Clerc and Stephen Dolan)

View File

@ -111,7 +111,7 @@ let add_ccobjs origin l =
let runtime_lib () =
let libname = "libasmrun" ^ !Clflags.runtime_variant ^ ext_lib in
try
if !Clflags.nopervasives then []
if !Clflags.nopervasives || (not !Clflags.with_runtime) then []
else [ Load_path.find libname ]
with Not_found ->
raise(Error(File_not_found libname))

View File

@ -303,14 +303,16 @@ let link_bytecode ?final_name tolink exec_name standalone =
raise (Error (Wrong_object_name exec_name));
| _ -> ()) tolink;
Misc.remove_file exec_name; (* avoid permission problems, cf PR#8354 *)
let output_permissions = if !Clflags.with_runtime then 0o777 else 0o666
in
let outchan =
open_out_gen [Open_wronly; Open_trunc; Open_creat; Open_binary]
0o777 exec_name in
output_permissions exec_name in
Misc.try_finally
~always:(fun () -> close_out outchan)
~exceptionally:(fun () -> remove_file exec_name)
(fun () ->
if standalone then begin
if standalone && !Clflags.with_runtime then begin
(* Copy the header *)
try
let header =
@ -324,7 +326,8 @@ let link_bytecode ?final_name tolink exec_name standalone =
end;
Bytesections.init_record outchan;
(* The path to the bytecode interpreter (in use_runtime mode) *)
if String.length !Clflags.use_runtime > 0 then begin
if String.length !Clflags.use_runtime > 0 && !Clflags.with_runtime then
begin
let runtime = make_absolute !Clflags.use_runtime in
let runtime =
(* shebang mustn't exceed 128 including the #! and \0 *)
@ -538,7 +541,10 @@ let link_bytecode_as_c tolink outfile =
(* Build a custom runtime *)
let build_custom_runtime prim_name exec_name =
let runtime_lib = "-lcamlrun" ^ !Clflags.runtime_variant in
let runtime_lib =
if (not !Clflags.with_runtime)
then ""
else "-lcamlrun" ^ !Clflags.runtime_variant in
let debug_prefix_map =
if Config.c_has_debug_prefix_map && not !Clflags.keep_camlprimc_file then
[Printf.sprintf "-fdebug-prefix-map=%s=camlprim.c" prim_name]
@ -662,7 +668,10 @@ let link objfiles output_name =
else Ccomp.MainDll, Config.bytecomp_c_libraries
in
if not (
let runtime_lib = "-lcamlrun" ^ !Clflags.runtime_variant in
let runtime_lib =
if (not !Clflags.with_runtime)
then ""
else "-lcamlrun" ^ !Clflags.runtime_variant in
Ccomp.call_linker mode output_name
([obj_file] @ List.rev !Clflags.ccobjs @ [runtime_lib])
c_libs

View File

@ -232,6 +232,7 @@ let read_one_param ppf position name v =
| "pp" -> preprocessor := Some v
| "runtime-variant" -> runtime_variant := v
| "with-runtime" -> set "with-runtime" [ with_runtime ] v
| "open" ->
open_modules := List.rev_append (String.split_on_char ',' v) !open_modules
| "cc" -> c_compiler := Some v

View File

@ -101,6 +101,8 @@ module Options = Main_args.Make_bytecomp_options (struct
let _rectypes = set recursive_types
let _no_rectypes = unset recursive_types
let _runtime_variant s = runtime_variant := s
let _with_runtime = set with_runtime
let _without_runtime = unset with_runtime
let _safe_string = unset unsafe_string
let _short_paths = unset real_paths
let _strict_sequence = set strict_sequence

View File

@ -454,6 +454,16 @@ let mk_runtime_variant f =
"<str> Use the <str> variant of the run-time system"
;;
let mk_with_runtime f =
"-with-runtime", Arg.Unit f,
"Include the runtime system in the generated program (default)"
;;
let mk_without_runtime f =
"-without-runtime", Arg.Unit f,
"Don't include the runtime system in the generated program."
;;
let mk_S f =
"-S", Arg.Unit f, " Keep intermediate assembly file"
;;
@ -930,6 +940,8 @@ module type Compiler_options = sig
val _no_principal : unit -> unit
val _rectypes : unit -> unit
val _runtime_variant : string -> unit
val _with_runtime : unit -> unit
val _without_runtime : unit -> unit
val _safe_string : unit -> unit
val _short_paths : unit -> unit
val _thread : unit -> unit
@ -1144,6 +1156,8 @@ struct
mk_rectypes F._rectypes;
mk_no_rectypes F._no_rectypes;
mk_runtime_variant F._runtime_variant;
mk_with_runtime F._with_runtime;
mk_without_runtime F._without_runtime;
mk_safe_string F._safe_string;
mk_short_paths F._short_paths;
mk_strict_sequence F._strict_sequence;
@ -1332,6 +1346,8 @@ struct
mk_remove_unused_arguments F._remove_unused_arguments;
mk_rounds F._rounds;
mk_runtime_variant F._runtime_variant;
mk_with_runtime F._with_runtime;
mk_without_runtime F._without_runtime;
mk_S F._S;
mk_safe_string F._safe_string;
mk_shared F._shared;

View File

@ -96,6 +96,8 @@ module type Compiler_options = sig
val _no_principal : unit -> unit
val _rectypes : unit -> unit
val _runtime_variant : string -> unit
val _with_runtime : unit -> unit
val _without_runtime : unit -> unit
val _safe_string : unit -> unit
val _short_paths : unit -> unit
val _thread : unit -> unit

View File

@ -181,6 +181,8 @@ module Options = Main_args.Make_optcomp_options (struct
let _no_rectypes = clear recursive_types
let _remove_unused_arguments = set remove_unused_arguments
let _runtime_variant s = runtime_variant := s
let _with_runtime = set with_runtime
let _without_runtime = clear with_runtime
let _safe_string = clear unsafe_string
let _short_paths = clear real_paths
let _strict_sequence = set strict_sequence

View File

@ -1056,6 +1056,10 @@ Show the description of all available warning numbers.
.B \-where
Print the location of the standard library, then exit.
.TP
.B \-without-runtime
The compiler does not include the runtime system (nor a reference to it) in the
generated program; it must be supplied separately.
.TP
.BI \- \ file
Process
.I file

View File

@ -684,6 +684,10 @@ Show the description of all available warning numbers.
.B \-where
Print the location of the standard library, then exit.
.TP
.B \-without-runtime
The compiler does not include the runtime system (nor a reference to it) in the
generated program; it must be supplied separately.
.TP
.BI \- \ file
Process
.I file

View File

@ -779,6 +779,12 @@ Show the description of all available warning numbers.
Print the location of the standard library, then exit.
}%notop
\notop{%
\item["-without-runtime"]
The compiler does not include the runtime system (nor a reference to it) in the
generated program; it must be supplied separately.
}
\item["-" \var{file}]
\notop{Process \var{file} as a file name, even if it starts with a dash ("-")
character.}

View File

@ -87,6 +87,8 @@ module Options = Main_args.Make_bytecomp_options (struct
let _rectypes = ignore
let _no_rectypes = ignore
let _runtime_variant = ignore
let _with_runtime = ignore
let _without_runtime = ignore
let _safe_string = ignore
let _short_paths = ignore
let _strict_sequence = ignore

View File

@ -108,6 +108,8 @@ module Options = Main_args.Make_optcomp_options (struct
let _no_rectypes = ignore
let _remove_unused_arguments = ignore
let _runtime_variant = ignore
let _with_runtime = ignore
let _without_runtime = ignore
let _S = ignore
let _safe_string = ignore
let _short_paths = ignore

View File

@ -163,6 +163,7 @@ let pic_code = ref (match Config.architecture with (* -fPIC *)
| _ -> false)
let runtime_variant = ref "";; (* -runtime-variant *)
let with_runtime = ref true;; (* -with-runtime *)
let keep_docs = ref false (* -keep-docs *)
let keep_locs = ref true (* -keep-locs *)

View File

@ -185,6 +185,7 @@ val shared : bool ref
val dlcode : bool ref
val pic_code : bool ref
val runtime_variant : string ref
val with_runtime : bool ref
val force_slash : bool ref
val keep_docs : bool ref
val keep_locs : bool ref