File tree Expand file tree Collapse file tree 3 files changed +48
-1
lines changed
testsuite/tests/typing-modules Expand file tree Collapse file tree 3 files changed +48
-1
lines changed Original file line number Diff line number Diff line change @@ -221,6 +221,9 @@ Working version
221221 currying optimisation accidentally disabled by #10340.
222222 (Stephen Dolan, review by Gabriel Scherer)
223223
224+ - #11732: Ensure that types from packed modules are always generalised
225+ (Stephen Dolan and Leo White, review by Jacques Garrigue)
226+
224227OCaml 5.0
225228---------
226229
Original file line number Diff line number Diff line change 1+ (* TEST
2+ * expect
3+ *)
4+ type (_, _) equ = Refl : ('q , 'q ) equ
5+
6+ module type Ty = sig type t end
7+ type 'a modu = (module Ty with type t = 'a )
8+
9+ type 'q1 packed =
10+ P : 'q0 modu * ('q0 , 'q1 ) equ -> 'q1 packed
11+
12+ (* Adds a module M to the environment where M.t equals an existential *)
13+ let repack (type q ) (x : q packed ) : q modu =
14+ match x with
15+ | P (p , eq ) ->
16+ let module M = (val p) in
17+ let Refl = eq in
18+ (module M )
19+
20+ [%% expect{|
21+ type (_, _) equ = Refl : ('q , 'q ) equ
22+ module type Ty = sig type t end
23+ type 'a modu = (module Ty with type t = 'a )
24+ type 'q1 packed = P : 'q0 modu * ('q0 , 'q1 ) equ -> 'q1 packed
25+ val repack : 'q packed -> 'q modu = < fun>
26+ |}]
27+
28+ (* Same, using a polymorphic function rather than an existential *)
29+
30+ let mkmod (type a ) () : a modu =
31+ (module struct type t = a end )
32+
33+ let f (type foo ) (intish : (foo, int) equ ) =
34+ let module M = (val (mkmod () : foo modu)) in
35+ let Refl = intish in
36+ let module C : sig type t = int end = M in
37+ ()
38+
39+ [%% expect{|
40+ val mkmod : unit -> 'a modu = < fun>
41+ val f : ('foo , int ) equ -> unit = < fun>
42+ |}]
Original file line number Diff line number Diff line change @@ -2038,9 +2038,11 @@ and package_constraints env loc mty constrs =
20382038 end
20392039
20402040let modtype_of_package env loc p fl =
2041+ (* We call Ctype.correct_levels to ensure that the types being added to the
2042+ module type are at generic_level. *)
20412043 let mty =
20422044 package_constraints env loc (Mty_ident p)
2043- (List. map (fun (n , t ) -> ( Longident. flatten n, t) ) fl)
2045+ (List. map (fun (n , t ) -> Longident. flatten n, Ctype. correct_levels t ) fl)
20442046 in
20452047 Subst. modtype Keep Subst. identity mty
20462048
You can’t perform that action at this time.
0 commit comments