Avoid warning 58 in flambda ocamlnat

master
Leo White 2020-04-02 09:07:32 +01:00
parent cba5a765a2
commit 9e61a063c3
5 changed files with 15 additions and 5 deletions

View File

@ -360,7 +360,7 @@ let execute_phrase print_outcome ppf phr =
| Result _ ->
if Config.flambda then
(* CR-someday trefis: *)
()
Env.register_import_as_opaque (Ident.name module_ident)
else
Compilenv.record_global_approx_toplevel ();
if print_outcome then

View File

@ -790,6 +790,9 @@ let crc_of_unit name =
let is_imported_opaque modname =
Persistent_env.is_imported_opaque persistent_env modname
let register_import_as_opaque modname =
Persistent_env.register_import_as_opaque persistent_env modname
let reset_declaration_caches () =
Types.Uid.Tbl.clear value_declarations;
Types.Uid.Tbl.clear type_declarations;

View File

@ -370,9 +370,12 @@ val imports: unit -> crcs
(* may raise Persistent_env.Consistbl.Inconsistency *)
val import_crcs: source:string -> crcs -> unit
(* [is_imported_opaque md] returns true if [md] is an opaque imported module *)
(* [is_imported_opaque md] returns true if [md] is an opaque imported module *)
val is_imported_opaque: modname -> bool
(* [register_import_as_opaque md] registers [md] as an opaque imported module *)
val register_import_as_opaque: modname -> unit
(* Summaries -- compact representation of an environment, to be
exported in debugging information. *)

View File

@ -104,7 +104,7 @@ let clear_missing {persistent_structures; _} =
let add_import {imported_units; _} s =
imported_units := String.Set.add s !imported_units
let add_imported_opaque {imported_opaque_units; _} s =
let register_import_as_opaque {imported_opaque_units; _} s =
imported_opaque_units := String.Set.add s !imported_opaque_units
let find_in_cache {persistent_structures; _} s =
@ -164,7 +164,7 @@ let save_pers_struct penv crc ps pm =
| Rectypes -> ()
| Alerts _ -> ()
| Unsafe_string -> ()
| Opaque -> add_imported_opaque penv modname)
| Opaque -> register_import_as_opaque penv modname)
ps.ps_flags;
Consistbl.set crc_units modname crc ps.ps_filename;
add_import penv modname
@ -190,7 +190,7 @@ let acknowledge_pers_struct penv check modname pers_sig pm =
if Config.safe_string then
error (Depend_on_unsafe_string_unit(ps.ps_name));
| Alerts _ -> ()
| Opaque -> add_imported_opaque penv modname)
| Opaque -> register_import_as_opaque penv modname)
ps.ps_flags;
if check then check_consistency penv ps;
let {persistent_structures; _} = penv in

View File

@ -77,6 +77,10 @@ val is_imported : 'a t -> modname -> bool
in [penv] as an opaque module *)
val is_imported_opaque : 'a t -> modname -> bool
(* [register_import_as_opaque penv md] registers [md] in [penv] as an
opaque module *)
val register_import_as_opaque : 'a t -> modname -> unit
val make_cmi : 'a t -> modname -> Types.signature -> alerts
-> Cmi_format.cmi_infos