Skip to content

Commit a6c0e75

Browse files
authored
Ensure that Ctype.nongen always calls remove_mode_variables (ocaml#70)
1 parent 6c50831 commit a6c0e75

File tree

5 files changed

+34
-9
lines changed

5 files changed

+34
-9
lines changed
Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,9 @@
1+
class c =
2+
object
3+
method private m () () = 0
4+
end
5+
6+
class virtual cv =
7+
object
8+
method virtual private m : unit -> unit -> int
9+
end
Lines changed: 18 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,18 @@
1+
(* TEST
2+
readonly_files = "regression_class_dep.ml"
3+
* setup-ocamlc.opt-build-env
4+
** ocamlc.opt
5+
module = "regression_class_dep.ml"
6+
*** ocamlc.opt
7+
module = ""
8+
flags = "-c"
9+
*)
10+
11+
(* https://github.com/ocaml-flambda/ocaml-jst/issues/65 *)
12+
13+
module Dep = Regression_class_dep
14+
class c fname =
15+
object
16+
inherit Dep.c
17+
inherit Dep.cv
18+
end

typing/ctype.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -5214,6 +5214,7 @@ let rec nongen_schema_rec env ty =
52145214

52155215
(* Return whether all variables of type [ty] are generic. *)
52165216
let nongen_schema env ty =
5217+
remove_mode_variables ty;
52175218
visited := TypeSet.empty;
52185219
try
52195220
nongen_schema_rec env ty;

typing/ctype.mli

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -398,11 +398,12 @@ val remove_mode_variables: type_expr -> unit
398398

399399
val nongen_schema: Env.t -> type_expr -> bool
400400
(* Check whether the given type scheme contains no non-generic
401-
type variables *)
401+
type variables, and ensure mode variables are fully determined *)
402402

403403
val nongen_class_declaration: class_declaration -> bool
404404
(* Check whether the given class type contains no non-generic
405-
type variables. Uses the empty environment. *)
405+
type variables, and ensures mode variables are fully determined.
406+
Uses the empty environment. *)
406407

407408
val free_variables: ?env:Env.t -> type_expr -> type_expr list
408409
(* If env present, then check for incomplete definitions too *)

typing/typemod.ml

Lines changed: 3 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1938,17 +1938,13 @@ and nongen_signature_item env f = function
19381938
| Sig_module(_id, _, md, _, _) -> nongen_modtype env f md.md_type
19391939
| _ -> false
19401940

1941-
let nongen_ty env ty =
1942-
Ctype.remove_mode_variables ty;
1943-
Ctype.nongen_schema env ty
1944-
19451941
let check_nongen_signature_item env sig_item =
19461942
match sig_item with
19471943
Sig_value(_id, vd, _) ->
1948-
if nongen_ty env vd.val_type then
1944+
if Ctype.nongen_schema env vd.val_type then
19491945
raise (Error (vd.val_loc, env, Non_generalizable vd.val_type))
19501946
| Sig_module (_id, _, md, _, _) ->
1951-
if nongen_modtype env nongen_ty md.md_type then
1947+
if nongen_modtype env Ctype.nongen_schema md.md_type then
19521948
raise(Error(md.md_loc, env, Non_generalizable_module md.md_type))
19531949
| _ -> ()
19541950

@@ -2983,7 +2979,7 @@ let type_module_type_of env smod =
29832979
in
29842980
let mty = Mtype.scrape_for_type_of ~remove_aliases env tmty.mod_type in
29852981
(* PR#5036: must not contain non-generalized type variables *)
2986-
if nongen_modtype env nongen_ty mty then
2982+
if nongen_modtype env Ctype.nongen_schema mty then
29872983
raise(Error(smod.pmod_loc, env, Non_generalizable_module mty));
29882984
tmty, mty
29892985

0 commit comments

Comments
 (0)