Merge pull request #575 from shindere/toplever-no-version
Add the -no-version option to the toplevel.master
commit
4a2107be8d
3
Changes
3
Changes
|
@ -30,6 +30,9 @@ OCaml 4.04.0:
|
|||
- MPR#7248: have ocamldep interpret -open arguments in left-to-right order
|
||||
(Gabriel Scherer, report by Anton Bachin)
|
||||
|
||||
- Add the -no-version option to the toplevel
|
||||
(Sébastien Hinderer)
|
||||
|
||||
### Standard library:
|
||||
|
||||
- GPR#427: Obj.is_block is now an inlined OCaml function instead of a
|
||||
|
|
|
@ -501,6 +501,10 @@ let mk__version f =
|
|||
"--version", Arg.Unit f, " Print version and exit"
|
||||
;;
|
||||
|
||||
let mk_no_version f =
|
||||
"-no-version", Arg.Unit f, " Do not print version at startup"
|
||||
;;
|
||||
|
||||
let mk_vmthread f =
|
||||
"-vmthread", Arg.Unit f,
|
||||
" Generate code that supports the threads library with VM-level\n\
|
||||
|
@ -789,6 +793,7 @@ module type Toplevel_options = sig
|
|||
include Common_options
|
||||
val _init : string -> unit
|
||||
val _noinit : unit -> unit
|
||||
val _no_version : unit -> unit
|
||||
val _noprompt : unit -> unit
|
||||
val _nopromptcont : unit -> unit
|
||||
val _stdin : unit -> unit
|
||||
|
@ -1030,6 +1035,7 @@ struct
|
|||
mk_unsafe_string F._unsafe_string;
|
||||
mk_version F._version;
|
||||
mk__version F._version;
|
||||
mk_no_version F._no_version;
|
||||
mk_vnum F._vnum;
|
||||
mk_w F._w;
|
||||
mk_warn_error F._warn_error;
|
||||
|
@ -1228,6 +1234,7 @@ module Make_opttop_options (F : Opttop_options) = struct
|
|||
mk_unsafe_string F._unsafe_string;
|
||||
mk_version F._version;
|
||||
mk__version F._version;
|
||||
mk_no_version F._no_version;
|
||||
mk_vnum F._vnum;
|
||||
mk_w F._w;
|
||||
mk_warn_error F._warn_error;
|
||||
|
|
|
@ -104,6 +104,7 @@ module type Toplevel_options = sig
|
|||
include Common_options
|
||||
val _init : string -> unit
|
||||
val _noinit : unit -> unit
|
||||
val _no_version : unit -> unit
|
||||
val _noprompt : unit -> unit
|
||||
val _nopromptcont : unit -> unit
|
||||
val _stdin : unit -> unit
|
||||
|
|
|
@ -206,6 +206,9 @@ Print version string and exit.
|
|||
.B \-vnum
|
||||
Print short version number and exit.
|
||||
.TP
|
||||
.B \-no\-version
|
||||
Do not print the version banner at startup.
|
||||
.TP
|
||||
.BI \-w \ warning\-list
|
||||
Enable or disable warnings according to the argument
|
||||
.IR warning-list .
|
||||
|
|
|
@ -246,6 +246,9 @@ Print version string and exit.
|
|||
\item["-vnum"]
|
||||
Print short version number and exit.
|
||||
|
||||
\item["-no-version"]
|
||||
Do not print the version banner at startup.
|
||||
|
||||
\item["-w" \var{warning-list}]
|
||||
Enable or disable warnings according to the argument \var{warning-list}.
|
||||
See section~\ref{s:comp-options} for the syntax of the argument.
|
||||
|
|
|
@ -536,7 +536,8 @@ exception PPerror
|
|||
|
||||
let loop ppf =
|
||||
Location.formatter_for_warnings := ppf;
|
||||
fprintf ppf " OCaml version %s - native toplevel@.@." Config.version;
|
||||
if not !Clflags.noversion then
|
||||
fprintf ppf " OCaml version %s - native toplevel@.@." Config.version;
|
||||
initialize_toplevel_env ();
|
||||
let lb = Lexing.from_function refill_lexbuf in
|
||||
Location.init lb "//toplevel//";
|
||||
|
|
|
@ -170,6 +170,7 @@ module Options = Main_args.Make_opttop_options (struct
|
|||
let _unsafe = set fast
|
||||
let _version () = print_version ()
|
||||
let _vnum () = print_version_num ()
|
||||
let _no_version = set noversion
|
||||
let _w s = Warnings.parse_options false s
|
||||
let _warn_error s = Warnings.parse_options true s
|
||||
let _warn_help = Warnings.help_warnings
|
||||
|
|
|
@ -507,7 +507,8 @@ exception PPerror
|
|||
|
||||
let loop ppf =
|
||||
Location.formatter_for_warnings := ppf;
|
||||
fprintf ppf " OCaml version %s@.@." Config.version;
|
||||
if not !Clflags.noversion then
|
||||
fprintf ppf " OCaml version %s@.@." Config.version;
|
||||
begin
|
||||
try initialize_toplevel_env ()
|
||||
with Env.Error _ | Typetexp.Error _ as exn ->
|
||||
|
|
|
@ -97,6 +97,7 @@ module Options = Main_args.Make_bytetop_options (struct
|
|||
let _unsafe_string = set unsafe_string
|
||||
let _version () = print_version ()
|
||||
let _vnum () = print_version_num ()
|
||||
let _no_version = set noversion
|
||||
let _w s = Warnings.parse_options false s
|
||||
let _warn_error s = Warnings.parse_options true s
|
||||
let _warn_help = Warnings.help_warnings
|
||||
|
|
|
@ -67,6 +67,7 @@ and use_threads = ref false (* -thread *)
|
|||
and use_vmthreads = ref false (* -vmthread *)
|
||||
and noassert = ref false (* -noassert *)
|
||||
and verbose = ref false (* -verbose *)
|
||||
and noversion = ref false (* -no-version *)
|
||||
and noprompt = ref false (* -noprompt *)
|
||||
and nopromptcont = ref false (* -nopromptcont *)
|
||||
and init_file = ref (None : string option) (* -init *)
|
||||
|
|
|
@ -97,6 +97,7 @@ val noprompt : bool ref
|
|||
val nopromptcont : bool ref
|
||||
val init_file : string option ref
|
||||
val noinit : bool ref
|
||||
val noversion : bool ref
|
||||
val use_prims : string ref
|
||||
val use_runtime : string ref
|
||||
val principal : bool ref
|
||||
|
|
Loading…
Reference in New Issue