Skip to content

Commit

Permalink
Merge pull request #10385 from Octachron/6985_more
Browse files Browse the repository at this point in the history
#6985 extended: ghost row types should stay hidden
  • Loading branch information
Octachron committed May 3, 2021
2 parents 5776b22 + 257c4d8 commit fb89e81
Show file tree
Hide file tree
Showing 3 changed files with 35 additions and 3 deletions.
3 changes: 3 additions & 0 deletions Changes
Original file line number Diff line number Diff line change
Expand Up @@ -364,6 +364,9 @@ Working version

### Bug fixes:

- #6985, #10385: remove all ghost row types from included modules
(Florian Angeletti, review by Gabriel Scherer)

* #8857, #10220: Don't clobber GetLastError() in caml_leave_blocking_section
when the systhreads library is loaded.
(David Allsopp, report by Anton Bachin, review by Xavier Leroy)
Expand Down
30 changes: 30 additions & 0 deletions testsuite/tests/typing-modules-bugs/pr6985_extended.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,30 @@
(* TEST
* expect
*)



module Root = struct
type u
and t = private < .. >
end

module Trunk = struct
include Root
type t = A
type u
end

module M: sig
module type s = module type of Trunk
end = struct
module type s = sig
type t = A
type u
end
end
[%%expect {|
module Root : sig type u and t = private < .. > end
module Trunk : sig type t = A type u end
module M : sig module type s = sig type t = A type u end end
|}]
5 changes: 2 additions & 3 deletions typing/mtype.ml
Original file line number Diff line number Diff line change
Expand Up @@ -54,9 +54,8 @@ and strengthen_sig ~aliasable env sg p =
[] -> []
| (Sig_value(_, _, _) as sigelt) :: rem ->
sigelt :: strengthen_sig ~aliasable env rem p
| Sig_type(id, {type_kind=Type_abstract}, _, _) ::
(Sig_type(id', {type_private=Private}, _, _) :: _ as rem)
when Ident.name id = Ident.name id' ^ "#row" ->
| Sig_type(id, {type_kind=Type_abstract}, _, _) :: rem
when Btype.is_row_name (Ident.name id) ->
strengthen_sig ~aliasable env rem p
| Sig_type(id, decl, rs, vis) :: rem ->
let newdecl =
Expand Down

0 comments on commit fb89e81

Please sign in to comment.