Fix PR#6593: Functor application in tests/basic-modules fails
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@15413 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02master
parent
2a6db79e0e
commit
67f3768100
2
Changes
2
Changes
|
@ -21,7 +21,7 @@ Type system:
|
|||
This is done by adding equations to submodules when expanding aliases.
|
||||
In theory this may be incompatible is some corner cases defining a module
|
||||
type through inference, but no breakage known on published code.
|
||||
|
||||
- PR#6593: Functor application in tests/basic-modules fails after commit 15405
|
||||
|
||||
OCaml 4.02.1:
|
||||
-------------
|
||||
|
|
BIN
boot/ocamlc
BIN
boot/ocamlc
Binary file not shown.
BIN
boot/ocamldep
BIN
boot/ocamldep
Binary file not shown.
BIN
boot/ocamllex
BIN
boot/ocamllex
Binary file not shown.
|
@ -1,3 +1,12 @@
|
|||
tests/basic
|
||||
tests/basic-float
|
||||
tests/basic-io
|
||||
tests/basic-io-2
|
||||
tests/basic-manyargs
|
||||
tests/basic-modules
|
||||
tests/basic-more
|
||||
tests/basic-multdef
|
||||
tests/basic-private
|
||||
tests/typing-extensions
|
||||
tests/typing-fstclassmod
|
||||
tests/typing-gadts
|
||||
|
|
|
@ -293,7 +293,7 @@ let current_unit = ref ""
|
|||
|
||||
type pers_struct =
|
||||
{ ps_name: string;
|
||||
ps_sig: signature;
|
||||
ps_sig: signature Lazy.t;
|
||||
ps_comps: module_components;
|
||||
ps_crcs: (string * Digest.t option) list;
|
||||
mutable ps_crcs_checked: bool;
|
||||
|
@ -348,7 +348,7 @@ let read_pers_struct modname filename =
|
|||
(Mty_signature sign)
|
||||
in
|
||||
let ps = { ps_name = name;
|
||||
ps_sig = sign;
|
||||
ps_sig = lazy (Subst.signature Subst.identity sign);
|
||||
ps_comps = comps;
|
||||
ps_crcs = crcs;
|
||||
ps_filename = filename;
|
||||
|
@ -489,7 +489,7 @@ let find_module ~alias path env =
|
|||
with Not_found ->
|
||||
if Ident.persistent id then
|
||||
let ps = find_pers_struct (Ident.name id) in
|
||||
md (Mty_signature(ps.ps_sig))
|
||||
md (Mty_signature(Lazy.force ps.ps_sig))
|
||||
else raise Not_found
|
||||
end
|
||||
| Pdot(p, s, pos) ->
|
||||
|
@ -1552,7 +1552,8 @@ let open_signature slot root sg env0 =
|
|||
|
||||
let open_pers_signature name env =
|
||||
let ps = find_pers_struct name in
|
||||
open_signature None (Pident(Ident.create_persistent name)) ps.ps_sig env
|
||||
open_signature None (Pident(Ident.create_persistent name))
|
||||
(Lazy.force ps.ps_sig) env
|
||||
|
||||
let open_signature ?(loc = Location.none) ?(toplevel = false) ovf root sg env =
|
||||
if not toplevel && ovf = Asttypes.Fresh && not loc.Location.loc_ghost
|
||||
|
@ -1589,7 +1590,7 @@ let open_signature ?(loc = Location.none) ?(toplevel = false) ovf root sg env =
|
|||
let read_signature modname filename =
|
||||
let ps = read_pers_struct modname filename in
|
||||
check_consistency ps;
|
||||
ps.ps_sig
|
||||
Lazy.force ps.ps_sig
|
||||
|
||||
(* Return the CRC of the interface of the given compilation unit *)
|
||||
|
||||
|
@ -1635,7 +1636,7 @@ let save_signature_with_imports sg modname filename imports =
|
|||
(Pident(Ident.create_persistent modname)) (Mty_signature sg) in
|
||||
let ps =
|
||||
{ ps_name = modname;
|
||||
ps_sig = sg;
|
||||
ps_sig = lazy (Subst.signature Subst.identity sg);
|
||||
ps_comps = comps;
|
||||
ps_crcs = (cmi.cmi_name, Some crc) :: imports;
|
||||
ps_filename = filename;
|
||||
|
@ -1709,7 +1710,7 @@ let fold_modules f lid env acc =
|
|||
None -> acc
|
||||
| Some ps ->
|
||||
f name (Pident(Ident.create_persistent name))
|
||||
(md (Mty_signature ps.ps_sig)) acc)
|
||||
(md (Mty_signature (Lazy.force ps.ps_sig))) acc)
|
||||
persistent_structures
|
||||
acc
|
||||
| Some l ->
|
||||
|
|
Loading…
Reference in New Issue