env refactoring: avoid external uses of {add_import,crc_units}

There is a small change of behavior in this patch due to a different
handling of weak dependencies (those with crco=None); in
Env.check_consistency, only non-weak dependencies would get
[Env.add_import] called, while the `toplevel/` implementations would
also call [Env.add_import] on weak dependencies. After this patch, we
systematically call [add_import] only on non-weak dependencies, even
in `toplevel/`.

([Gabriel:] As far as I can see, the use of [add_import] in the
toplevel never leads to a use of [Env.imports()] for producing
a dependency list, as the toplevel does not produce cmi/cmo files; are
they just no-ops?)
master
Gabriel Scherer 2019-01-23 23:08:22 +01:00
parent 7ae59eeb8d
commit a6f0caa8de
4 changed files with 16 additions and 31 deletions

View File

@ -118,15 +118,7 @@ let _ = add_directive "cd" (Directive_string dir_cd)
exception Load_failed
let check_consistency ppf filename cu =
try
List.iter
(fun (name, crco) ->
Env.add_import name;
match crco with
None -> ()
| Some crc->
Consistbl.check Env.crc_units name crc filename)
cu.cu_imports
try Env.import_crcs ~source:filename cu.cu_imports
with Consistbl.Inconsistency(name, user, auth) ->
fprintf ppf "@[<hv 0>The files %s@ and %s@ \
disagree over interface %s@]@."

View File

@ -492,14 +492,8 @@ let _ =
Sys.interactive := true;
let crc_intfs = Symtable.init_toplevel() in
Compmisc.init_path false;
List.iter
(fun (name, crco) ->
Env.add_import name;
match crco with
None -> ()
| Some crc->
Consistbl.set Env.crc_units name crc Sys.executable_name)
crc_intfs
Env.import_crcs ~source:Sys.executable_name crc_intfs;
()
let load_ocamlinit ppf =
if !Clflags.noinit then ()

View File

@ -730,16 +730,17 @@ let clear_imports () =
imported_units := String.Set.empty;
imported_opaque_units := String.Set.empty
let import_crcs ~source crcs =
let import_crc (name, crco) =
match crco with
| None -> ()
| Some crc ->
add_import name;
Consistbl.check crc_units name crc source
in List.iter import_crc crcs
let check_consistency ps =
try
List.iter
(fun (name, crco) ->
match crco with
None -> ()
| Some crc ->
add_import name;
Consistbl.check crc_units name crc ps.ps_filename)
ps.ps_crcs;
try import_crcs ~source:ps.ps_filename ps.ps_crcs
with Consistbl.Inconsistency(name, source, auth) ->
error (Inconsistent_import(name, auth, source))

View File

@ -260,14 +260,12 @@ val crc_of_unit: modname -> Digest.t
val imports: unit -> crcs
(* may raise Consistbl.Inconsistency *)
val import_crcs: source:string -> crcs -> unit
(* [is_imported_opaque md] returns true if [md] is an opaque imported module *)
val is_imported_opaque: string -> bool
(* Direct access to the table of imported compilation units with their CRC *)
val crc_units: Consistbl.t
val add_import: string -> unit
(* Summaries -- compact representation of an environment, to be
exported in debugging information. *)