summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--toplevel/toploop.ml5
-rw-r--r--toplevel/toploop.mli2
2 files changed, 6 insertions, 1 deletions
diff --git a/toplevel/toploop.ml b/toplevel/toploop.ml
index 45c826b84..3b96c3ae2 100644
--- a/toplevel/toploop.ml
+++ b/toplevel/toploop.ml
@@ -357,13 +357,16 @@ let set_paths () =
load_path := "" :: (List.rev !Clflags.include_dirs @ !load_path);
Dll.add_path !load_path
+let initialize_toplevel_env () =
+ toplevel_env := Compile.initial_env()
+
(* The interactive loop *)
exception PPerror
let loop ppf =
fprintf ppf " Objective Caml version %s@.@." Config.version;
- toplevel_env := Compile.initial_env();
+ initialize_toplevel_env ();
let lb = Lexing.from_function refill_lexbuf in
Location.input_name := "";
Location.input_lexbuf := Some lb;
diff --git a/toplevel/toploop.mli b/toplevel/toploop.mli
index 4c3ca35d4..14be3afed 100644
--- a/toplevel/toploop.mli
+++ b/toplevel/toploop.mli
@@ -46,6 +46,8 @@ val directive_table : (string, directive_fun) Hashtbl.t
(* Table of known directives, with their execution function *)
val toplevel_env : Env.t ref
(* Typing environment for the toplevel *)
+val initialize_toplevel_env : unit -> unit
+ (* Initialize the typing environment for the toplevel *)
val print_exception_outcome : formatter -> exn -> unit
(* Print an exception resulting from the evaluation of user code. *)
val execute_phrase : bool -> formatter -> Parsetree.toplevel_phrase -> bool