types: allow class type paths in #t

master
Florian Angeletti 2020-01-08 16:23:10 +01:00
parent 73554e3aa9
commit dc56d71b53
6 changed files with 30 additions and 12 deletions

View File

@ -13,6 +13,10 @@ Working version
- #6673, #1132: Relax the handling of explicit polymorphic types
(Leo White, review by Jacques Garrigue and Gabriel Scherer)
- #9232: allow any class type paths in #-types,
For instance, "val f: #F(X).t -> unit" is now allowed.
(Florian Angeletti, review by Gabriel Scherer, suggestion by Leo White)
### Runtime system:
- #9119: Make [caml_stat_resize_noexc] compatible with the [realloc]

File diff suppressed because one or more lines are too long

View File

@ -16,7 +16,7 @@ typexpr:
| polymorphic-variant-type
| '<' ['..'] '>'
| '<' method-type { ';' method-type } [';' || ';' '..'] '>'
| '#' class-path
| '#' classtype-path
| typexpr '#' class-path
| '(' typexpr { ',' typexpr } ')' '#' class-path
;
@ -215,17 +215,17 @@ literature) that stands for any number of extra method types.
\subsubsection*{sss:typexpr-sharp-types}{\#-types}
The type @'#' class-path@ is a special kind of abbreviation. This
The type @'#' classtype-path@ is a special kind of abbreviation. This
abbreviation unifies with the type of any object belonging to a subclass
of class @class-path@.
of the class type @classtype-path@.
%
It is handled in a special way as it usually hides a type variable (an
ellipsis, representing the methods that may be added in a subclass).
In particular, it vanishes when the ellipsis gets instantiated.
%
Each type expression @'#' class-path@ defines a new type variable, so
type @'#' class-path '->' '#' class-path@ is usually not the same as
type @('#' class-path 'as' "'" ident) '->' "'" ident@.
Each type expression @'#' classtype-path@ defines a new type variable, so
type @'#' classtype-path '->' '#' classtype-path@ is usually not the same as
type @('#' classtype-path 'as' "'" ident) '->' "'" ident@.
%
Use of \#-types to abbreviate polymorphic variant types is deprecated.

View File

@ -47,7 +47,6 @@ let iterator =
let loc = ty.ptyp_loc in
match ty.ptyp_desc with
| Ptyp_tuple ([] | [_]) -> invalid_tuple loc
| Ptyp_class (id, _) -> simple_longident id
| Ptyp_package (_, cstrs) ->
List.iter (fun (id, _) -> simple_longident id) cstrs
| _ -> ()

View File

@ -3273,7 +3273,7 @@ atomic_type:
{ Ptyp_object ([], Closed) }
| tys = actual_type_parameters
HASH
cid = mkrhs(class_longident)
cid = mkrhs(clty_longident)
{ Ptyp_class(cid, tys) }
| LBRACKET tag_field RBRACKET
(* not row_field; see CONFLICTS *)

View File

@ -66,6 +66,21 @@ and ['a] d : unit -> object constraint 'a = int #c end
|}];;
(* class ['a] c : unit -> object constraint 'a = int end
and ['a] d : unit -> object constraint 'a = int #c end *)
(* Class type constraint *)
module F(X:sig type t end) = struct
class type ['a] c = object
method m: 'a -> X.t
end
end
class ['a] c = object
constraint 'a = 'a #F(Int).c
end
[%%expect {|
module F :
functor (X : sig type t end) ->
sig class type ['a] c = object method m : 'a -> X.t end end
class ['a] c : object constraint 'a = < m : 'a -> Int.t; .. > end
|}]
(* Self as parameter *)
class ['a] c (x : 'a) = object (self : 'b)