Restore -vmthreads flag as an error (#2312)

This GPR restores -vmthread with an adapted version of the deprecation message as an error message and also keeps the use_vmthreads part of ppx contexts.

* Partially revert #2289
* Convert -vmthread to an error
* Neuter use_vmthreads in ppx context
* Remove Clflags.use_vmthreads
master
David Allsopp 2019-03-13 09:46:30 +00:00 committed by Xavier Leroy
parent f9099524e2
commit 6e84987715
6 changed files with 24 additions and 0 deletions

View File

@ -21,6 +21,12 @@ let usage = "Usage: ocamlc <options> <files>\nOptions are:"
(* Error messages to standard error formatter *)
let ppf = Format.err_formatter
let vmthread_removed_message = "\
The -vmthread argument of ocamlc is no longer supported\n\
since OCaml 4.09.0. Please switch to system threads, which have the\n\
same API. Lightweight threads with VM-level scheduling are provided by\n\
third-party libraries such as Lwt, but with a different API."
module Options = Main_args.Make_bytecomp_options (struct
let set r () = r := true
let unset r () = r := false
@ -102,6 +108,7 @@ module Options = Main_args.Make_bytecomp_options (struct
let _strict_formats = set strict_formats
let _no_strict_formats = unset strict_formats
let _thread = set use_threads
let _vmthread = fun () -> fatal vmthread_removed_message
let _unboxed_types = set unboxed_types
let _no_unboxed_types = unset unboxed_types
let _unsafe = set unsafe

View File

@ -562,6 +562,11 @@ let mk_no_version f =
"-no-version", Arg.Unit f, " Do not print version at startup"
;;
let mk_vmthread f =
"-vmthread", Arg.Unit f,
" (no longer supported)"
;;
let mk_vnum f =
"-vnum", Arg.Unit f, " Print version number and exit"
;;
@ -958,6 +963,7 @@ module type Bytecomp_options = sig
val _dllib : string -> unit
val _dllpath : string -> unit
val _make_runtime : unit -> unit
val _vmthread : unit -> unit
val _use_runtime : string -> unit
val _dinstr : unit -> unit
@ -1060,6 +1066,7 @@ module type Ocamldoc_options = sig
val _thread : unit -> unit
val _v : unit -> unit
val _verbose : unit -> unit
val _vmthread : unit -> unit
end
module type Arg_list = sig
@ -1146,6 +1153,7 @@ struct
mk_verbose F._verbose;
mk_version F._version;
mk__version F._version;
mk_vmthread F._vmthread;
mk_vnum F._vnum;
mk_w F._w;
mk_warn_error F._warn_error;
@ -1521,6 +1529,7 @@ struct
mk_verbose F._verbose;
mk_version F._version;
mk__version F._version;
mk_vmthread F._vmthread;
mk_vnum F._vnum;
mk_w F._w;
mk__ F.anonymous;

View File

@ -140,6 +140,7 @@ module type Bytecomp_options = sig
val _dllib : string -> unit
val _dllpath : string -> unit
val _make_runtime : unit -> unit
val _vmthread : unit -> unit
val _use_runtime : string -> unit
val _dinstr : unit -> unit
@ -241,6 +242,7 @@ module type Ocamldoc_options = sig
val _thread : unit -> unit
val _v : unit -> unit
val _verbose : unit -> unit
val _vmthread : unit -> unit
end;;
module type Arg_list = sig

View File

@ -227,6 +227,7 @@ module Options = Main_args.Make_ocamldoc_options(struct
let _strict_formats = set Clflags.strict_formats
let _no_strict_formats = unset Clflags.strict_formats
let _thread = set Clflags.use_threads
let _vmthread = ignore
let _unboxed_types = set Clflags.unboxed_types
let _no_unboxed_types = unset Clflags.unboxed_types
let _unsafe () = assert false

View File

@ -803,6 +803,7 @@ module PpxContext = struct
lid "for_package", make_option make_string !Clflags.for_package;
lid "debug", make_bool !Clflags.debug;
lid "use_threads", make_bool !Clflags.use_threads;
lid "use_vmthreads", make_bool false;
lid "recursive_types", make_bool !Clflags.recursive_types;
lid "principal", make_bool !Clflags.principal;
lid "transparent_modules", make_bool !Clflags.transparent_modules;
@ -876,6 +877,9 @@ module PpxContext = struct
Clflags.debug := get_bool payload
| "use_threads" ->
Clflags.use_threads := get_bool payload
| "use_vmthreads" ->
if get_bool payload then
raise_errorf "Internal error: vmthreads not supported after 4.09.0"
| "recursive_types" ->
Clflags.recursive_types := get_bool payload
| "principal" ->

View File

@ -94,6 +94,7 @@ module Options = Main_args.Make_bytecomp_options (struct
let _strict_formats = ignore
let _no_strict_formats = ignore
let _thread = ignore
let _vmthread = ignore
let _unboxed_types = ignore
let _no_unboxed_types = ignore
let _unsafe = ignore