Skip to content

Commit

Permalink
Ensure that Ctype.nongen always calls remove_mode_variables (ocaml#70)
Browse files Browse the repository at this point in the history
  • Loading branch information
stedolan authored Nov 29, 2022
1 parent 6c50831 commit a6c0e75
Show file tree
Hide file tree
Showing 5 changed files with 34 additions and 9 deletions.
9 changes: 9 additions & 0 deletions testsuite/tests/typing-local/regression_class_dep.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
class c =
object
method private m () () = 0
end

class virtual cv =
object
method virtual private m : unit -> unit -> int
end
18 changes: 18 additions & 0 deletions testsuite/tests/typing-local/regression_class_type.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,18 @@
(* TEST
readonly_files = "regression_class_dep.ml"
* setup-ocamlc.opt-build-env
** ocamlc.opt
module = "regression_class_dep.ml"
*** ocamlc.opt
module = ""
flags = "-c"
*)

(* https://github.com/ocaml-flambda/ocaml-jst/issues/65 *)

module Dep = Regression_class_dep
class c fname =
object
inherit Dep.c
inherit Dep.cv
end
1 change: 1 addition & 0 deletions typing/ctype.ml
Original file line number Diff line number Diff line change
Expand Up @@ -5214,6 +5214,7 @@ let rec nongen_schema_rec env ty =

(* Return whether all variables of type [ty] are generic. *)
let nongen_schema env ty =
remove_mode_variables ty;
visited := TypeSet.empty;
try
nongen_schema_rec env ty;
Expand Down
5 changes: 3 additions & 2 deletions typing/ctype.mli
Original file line number Diff line number Diff line change
Expand Up @@ -398,11 +398,12 @@ val remove_mode_variables: type_expr -> unit

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

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

val free_variables: ?env:Env.t -> type_expr -> type_expr list
(* If env present, then check for incomplete definitions too *)
Expand Down
10 changes: 3 additions & 7 deletions typing/typemod.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1938,17 +1938,13 @@ and nongen_signature_item env f = function
| Sig_module(_id, _, md, _, _) -> nongen_modtype env f md.md_type
| _ -> false

let nongen_ty env ty =
Ctype.remove_mode_variables ty;
Ctype.nongen_schema env ty

let check_nongen_signature_item env sig_item =
match sig_item with
Sig_value(_id, vd, _) ->
if nongen_ty env vd.val_type then
if Ctype.nongen_schema env vd.val_type then
raise (Error (vd.val_loc, env, Non_generalizable vd.val_type))
| Sig_module (_id, _, md, _, _) ->
if nongen_modtype env nongen_ty md.md_type then
if nongen_modtype env Ctype.nongen_schema md.md_type then
raise(Error(md.md_loc, env, Non_generalizable_module md.md_type))
| _ -> ()

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

Expand Down

0 comments on commit a6c0e75

Please sign in to comment.