summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorXavier Leroy <xavier.leroy@inria.fr>2000-04-10 14:59:00 +0000
committerXavier Leroy <xavier.leroy@inria.fr>2000-04-10 14:59:00 +0000
commit10ceb26643238f44ad052e0afb36e8ef4c5b2012 (patch)
tree14998ad2bc12aab08b02d50469c7ef2790cf6392
parentc546d3683d01c70fcd737d46bb280aae91bd9aa3 (diff)
Amelioration du message d'erreur 'inconsistent assumptions'
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@3050 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--typing/env.ml16
1 files changed, 11 insertions, 5 deletions
diff --git a/typing/env.ml b/typing/env.ml
index 61a10c917..fd2bf67ee 100644
--- a/typing/env.ml
+++ b/typing/env.ml
@@ -92,7 +92,8 @@ type pers_struct =
{ ps_name: string;
ps_sig: signature;
ps_comps: module_components;
- ps_crcs: (string * Digest.t) list }
+ ps_crcs: (string * Digest.t) list;
+ ps_filename: string }
let persistent_structures =
(Hashtbl.create 17 : (string, pers_struct) Hashtbl.t)
@@ -117,7 +118,8 @@ let read_pers_struct modname filename =
let ps = { ps_name = name;
ps_sig = sign;
ps_comps = comps;
- ps_crcs = crcs } in
+ ps_crcs = crcs;
+ ps_filename = filename } in
if ps.ps_name <> modname then
raise(Error(Illegal_renaming(ps.ps_name, filename)));
Hashtbl.add persistent_structures modname ps;
@@ -779,7 +781,7 @@ let imported_units() =
Hashtbl.add units_xref name (crc, source);
imported_units := (name, crc) :: !imported_units in
Hashtbl.iter
- (fun name ps -> List.iter (add_unit ps.ps_name) ps.ps_crcs)
+ (fun name ps -> List.iter (add_unit ps.ps_filename) ps.ps_crcs)
persistent_structures;
!imported_units
@@ -801,7 +803,11 @@ let save_signature sg modname filename =
(* Enter signature in persistent table so that imported_unit()
will also return its crc *)
let ps =
- { ps_name = modname; ps_sig = sg; ps_comps = comps; ps_crcs = crcs } in
+ { ps_name = modname;
+ ps_sig = sg;
+ ps_comps = comps;
+ ps_crcs = crcs;
+ ps_filename = filename } in
Hashtbl.add persistent_structures modname ps;
close_out oc
with exn ->
@@ -829,6 +835,6 @@ let report_error ppf = function
"Wrong file naming: %s@ contains the compiled interface for@ %s"
filename modname
| Inconsistent_import(name, source1, source2) -> fprintf ppf
- "@[<hv>The compiled interfaces for %s@ and %s@ \
+ "@[<hov>The compiled interfaces %s@ and %s@ \
make inconsistent assumptions over interface %s@]"
source1 source2 name;;