summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorAlain Frisch <alain@frisch.fr>2013-08-29 10:06:50 +0000
committerAlain Frisch <alain@frisch.fr>2013-08-29 10:06:50 +0000
commit6f15a5da7b420f91b68e03ee18c94e0d3bfa8857 (patch)
tree9c67baeddd0846e5ab23b0289674cb212c765042
parent842f6794a956a726f73e9beb63e679cf7a9d679b (diff)
These two files slipped through a synchronization with trunk.
git-svn-id: http://caml.inria.fr/svn/ocaml/branches/extension_points@14043 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--driver/compmisc.ml58
-rw-r--r--driver/compmisc.mli15
2 files changed, 73 insertions, 0 deletions
diff --git a/driver/compmisc.ml b/driver/compmisc.ml
new file mode 100644
index 000000000..8f974f4be
--- /dev/null
+++ b/driver/compmisc.ml
@@ -0,0 +1,58 @@
+(***********************************************************************)
+(* *)
+(* OCaml *)
+(* *)
+(* Fabrice Le Fessant, EPI Gallium, INRIA Paris-Rocquencourt *)
+(* *)
+(* Copyright 2013 Institut National de Recherche en Informatique et *)
+(* en Automatique. All rights reserved. This file is distributed *)
+(* under the terms of the Q Public License version 1.0. *)
+(* *)
+(***********************************************************************)
+
+open Compenv
+
+(* Initialize the search path.
+ The current directory is always searched first,
+ then the directories specified with the -I option (in command-line order),
+ then the standard library directory (unless the -nostdlib option is given).
+ *)
+
+let init_path native =
+ let dirs =
+ if !Clflags.use_threads then "+threads" :: !Clflags.include_dirs
+ else if !Clflags.use_vmthreads && not native then
+ "+vmthreads" :: !Clflags.include_dirs
+ else
+ !last_include_dirs @
+ !Clflags.include_dirs @
+ !first_include_dirs
+ in
+ let exp_dirs =
+ List.map (Misc.expand_directory Config.standard_library) dirs in
+ Config.load_path := "" ::
+ List.rev_append exp_dirs (Clflags.std_include_dir ());
+ Env.reset_cache ()
+
+(* Return the initial environment in which compilation proceeds. *)
+
+(* Note: do not do init_path() in initial_env, this breaks
+ toplevel initialization (PR#1775) *)
+
+let open_implicit_module m env =
+ try
+ Env.open_pers_signature m env
+ with Not_found ->
+ Misc.fatal_error (Printf.sprintf "cannot open implicit module %S" m)
+
+let initial_env () =
+ Ident.reinit();
+ let env =
+ if !Clflags.nopervasives
+ then Env.initial
+ else
+ open_implicit_module "Pervasives" Env.initial
+ in
+ List.fold_left (fun env m ->
+ open_implicit_module m env
+ ) env !implicit_modules
diff --git a/driver/compmisc.mli b/driver/compmisc.mli
new file mode 100644
index 000000000..4c8cb0647
--- /dev/null
+++ b/driver/compmisc.mli
@@ -0,0 +1,15 @@
+(***********************************************************************)
+(* *)
+(* OCaml *)
+(* *)
+(* Fabrice Le Fessant, EPI Gallium, INRIA Paris-Rocquencourt *)
+(* *)
+(* Copyright 2013 Institut National de Recherche en Informatique et *)
+(* en Automatique. All rights reserved. This file is distributed *)
+(* under the terms of the Q Public License version 1.0. *)
+(* *)
+(***********************************************************************)
+
+val init_path : bool -> unit
+val initial_env : unit -> Env.t
+