summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorXavier Leroy <xavier.leroy@inria.fr>2002-08-19 12:23:23 +0000
committerXavier Leroy <xavier.leroy@inria.fr>2002-08-19 12:23:23 +0000
commit161bca8da3359a65ae2853039f84a739df16bad0 (patch)
treed6e4288a221daf9d844950c2d1993a3ba1176eec
parent8ca2c9f049ccc39e65fe62fb05386ac44bde9db5 (diff)
Revu generation du .cmi avec ocamlc -pack: supprimer les dependances sur les modules empaquetes
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@5102 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--typing/env.ml7
-rw-r--r--typing/env.mli4
-rw-r--r--typing/typemod.ml8
3 files changed, 16 insertions, 3 deletions
diff --git a/typing/env.ml b/typing/env.ml
index 4c06c2828..ff7074383 100644
--- a/typing/env.ml
+++ b/typing/env.ml
@@ -709,7 +709,7 @@ let imported_units() =
(* Save a signature to a file *)
-let save_signature sg modname filename =
+let save_signature_with_imports sg modname filename imports =
Btype.cleanup_abbrev ();
Subst.reset_for_saving ();
let sg = Subst.signature (Subst.for_saving Subst.identity) sg in
@@ -719,7 +719,7 @@ let save_signature sg modname filename =
output_value oc (modname, sg);
flush oc;
let crc = Digest.file filename in
- let crcs = (modname, crc) :: imported_units() in
+ let crcs = (modname, crc) :: imports in
output_value oc crcs;
close_out oc;
(* Enter signature in persistent table so that imported_unit()
@@ -739,6 +739,9 @@ let save_signature sg modname filename =
remove_file filename;
raise exn
+let save_signature sg modname filename =
+ save_signature_with_imports sg modname filename (imported_units())
+
(* Make the initial environment *)
let initial = Predef.build_initial_env add_type add_exception empty
diff --git a/typing/env.mli b/typing/env.mli
index 6529ed0be..df1d17339 100644
--- a/typing/env.mli
+++ b/typing/env.mli
@@ -86,6 +86,10 @@ val read_signature: string -> string -> signature
(* Arguments: module name, file name. Results: signature. *)
val save_signature: signature -> string -> string -> unit
(* Arguments: signature, module name, file name. *)
+val save_signature_with_imports:
+ signature -> string -> string -> (string * Digest.t) list -> unit
+ (* Arguments: signature, module name, file name,
+ imported units with their CRCs. *)
(* Return the CRC of the interface of the given compilation unit *)
diff --git a/typing/typemod.ml b/typing/typemod.ml
index ac426f7a2..89963b0d7 100644
--- a/typing/typemod.ml
+++ b/typing/typemod.ml
@@ -564,8 +564,14 @@ let package_units objfiles cmifile modulename =
objfiles in
(* Compute signature of packaged unit *)
let sg = package_signatures Subst.identity units in
+ (* Determine imports *)
+ let unit_names = List.map fst units in
+ let imports =
+ List.filter
+ (fun (name, crc) -> not (List.mem name unit_names))
+ (Env.imported_units()) in
(* Write packaged signature *)
- Env.save_signature sg modulename cmifile
+ Env.save_signature_with_imports sg modulename cmifile imports
(* Error report *)