Skip to content

Commit

Permalink
flambda-backend: Persistent environment and reproducibility (ocaml#533)
Browse files Browse the repository at this point in the history
  • Loading branch information
xclerc committed Feb 21, 2022
1 parent 4a0c89f commit d8956b0
Show file tree
Hide file tree
Showing 11 changed files with 16 additions and 15 deletions.
2 changes: 1 addition & 1 deletion debugger/command_line.ml
Original file line number Diff line number Diff line change
Expand Up @@ -263,7 +263,7 @@ let instr_dir ppf lexbuf =
if new_directory = [] then begin
if yes_or_no "Reinitialize directory list" then begin
Load_path.init !default_load_path;
Envaux.reset_cache ();
Envaux.reset_cache ~preserve_persistent_env:false;
Hashtbl.clear Debugger_config.load_path_for;
flush_buffer_list ()
end
Expand Down
2 changes: 1 addition & 1 deletion debugger/parameters.ml
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,7 @@ let topdirs_path = ref (Filename.concat Config.standard_library "compiler-libs")

let add_path dir =
Load_path.add_dir dir;
Envaux.reset_cache()
Envaux.reset_cache ~preserve_persistent_env:false

let add_path_for mdl dir =
let old = try Hashtbl.find load_path_for mdl with Not_found -> [] in
Expand Down
2 changes: 1 addition & 1 deletion debugger/program_management.ml
Original file line number Diff line number Diff line change
Expand Up @@ -129,7 +129,7 @@ let initialize_loading () =
Symbols.clear_symbols ();
Symbols.read_symbols 0 !program_name;
Load_path.init (Load_path.get_paths () @ !Symbols.program_source_dirs);
Envaux.reset_cache ();
Envaux.reset_cache ~preserve_persistent_env:false;
if !debug_loading then
prerr_endline "Opening a socket...";
open_connection !socket_name
Expand Down
2 changes: 1 addition & 1 deletion driver/compmisc.ml
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ let init_path ?(dir="") () =
let exp_dirs =
List.map (Misc.expand_directory Config.standard_library) dirs in
Load_path.init (dir :: List.rev_append exp_dirs (Clflags.std_include_dir ()));
Env.reset_cache ()
Env.reset_cache ~preserve_persistent_env:false

(* Return the initial environment in which compilation proceeds. *)

Expand Down
2 changes: 1 addition & 1 deletion tools/ocamlcmt.ml
Original file line number Diff line number Diff line change
Expand Up @@ -173,7 +173,7 @@ let main () =
| Some "-" -> None
| Some _ as x -> x
in
Envaux.reset_cache ();
Envaux.reset_cache ~preserve_persistent_env:false;
List.iter Load_path.add_dir cmt.cmt_loadpath;
Cmt2annot.gen_annot target_filename
~sourcefile:cmt.cmt_sourcefile
Expand Down
5 changes: 3 additions & 2 deletions typing/env.ml
Original file line number Diff line number Diff line change
Expand Up @@ -858,9 +858,10 @@ let reset_declaration_caches () =
Types.Uid.Tbl.clear !used_constructors;
()

let reset_cache () =
let reset_cache ~preserve_persistent_env =
Current_unit_name.set "";
Persistent_env.clear !persistent_env;
if not preserve_persistent_env then
Persistent_env.clear !persistent_env;
reset_declaration_caches ();
()

Expand Down
2 changes: 1 addition & 1 deletion typing/env.mli
Original file line number Diff line number Diff line change
Expand Up @@ -362,7 +362,7 @@ val add_lock : Types.value_mode -> t -> t
val add_region_lock : t -> t

(* Initialize the cache of in-core module interfaces. *)
val reset_cache: unit -> unit
val reset_cache: preserve_persistent_env:bool -> unit

(* To be called before each toplevel phrase. *)
val reset_cache_toplevel: unit -> unit
Expand Down
4 changes: 2 additions & 2 deletions typing/envaux.ml
Original file line number Diff line number Diff line change
Expand Up @@ -24,9 +24,9 @@ exception Error of error
let env_cache =
(Hashtbl.create 59 : ((Env.summary * Subst.t), Env.t) Hashtbl.t)

let reset_cache () =
let reset_cache ~preserve_persistent_env =
Hashtbl.clear env_cache;
Env.reset_cache()
Env.reset_cache ~preserve_persistent_env

let rec env_from_summary sum subst =
try
Expand Down
2 changes: 1 addition & 1 deletion typing/envaux.mli
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ val env_from_summary : Env.summary -> Subst.t -> Env.t

(* Empty the environment caches. To be called when load_path changes. *)

val reset_cache: unit -> unit
val reset_cache: preserve_persistent_env:bool -> unit

val env_of_only_summary : Env.t -> Env.t

Expand Down
6 changes: 3 additions & 3 deletions typing/typemod.ml
Original file line number Diff line number Diff line change
Expand Up @@ -2987,7 +2987,7 @@ let () =
None
)

let reset () =
Env.reset_cache ();
Envaux.reset_cache ();
let reset ~preserve_persistent_env =
Env.reset_cache ~preserve_persistent_env;
Envaux.reset_cache ~preserve_persistent_env;
Typetexp.reset_type_variables ()
2 changes: 1 addition & 1 deletion typing/typemod.mli
Original file line number Diff line number Diff line change
Expand Up @@ -139,4 +139,4 @@ val report_error: Env.t -> formatter -> error -> unit

(** Clear several bits of global state that may retain large amounts of memory
after typechecking is finished. *)
val reset : unit -> unit
val reset : preserve_persistent_env:bool -> unit

0 comments on commit d8956b0

Please sign in to comment.