diff --git a/src/parser/estree_translator.ml b/src/parser/estree_translator.ml index 33c000b8d0d..c67dfe4638c 100644 --- a/src/parser/estree_translator.ml +++ b/src/parser/estree_translator.ml @@ -869,6 +869,7 @@ end with type t = Impl.t) = struct | Any -> any_type loc | Void -> void_type loc | Null -> null_type loc + | This -> this_type loc | Number -> number_type loc | String -> string_type loc | Boolean -> boolean_type loc @@ -893,6 +894,8 @@ end with type t = Impl.t) = struct and null_type loc = node "NullTypeAnnotation" loc [||] + and this_type loc = node "ThisTypeAnnotation" loc [||] + and number_type loc = node "NumberTypeAnnotation" loc [||] and string_type loc = node "StringTypeAnnotation" loc [||] diff --git a/src/parser/lexer_flow.mll b/src/parser/lexer_flow.mll index a31c430652a..156f0d44919 100644 --- a/src/parser/lexer_flow.mll +++ b/src/parser/lexer_flow.mll @@ -525,6 +525,7 @@ "false", T_FALSE; "number", T_NUMBER_TYPE; "string", T_STRING_TYPE; + "this", T_THIS; "void", T_VOID_TYPE; "null", T_NULL; ] diff --git a/src/parser/loc.ml b/src/parser/loc.ml index bda28cb076d..bfca78ce805 100644 --- a/src/parser/loc.ml +++ b/src/parser/loc.ml @@ -67,6 +67,12 @@ let btwn loc1 loc2 = { _end = loc2._end; } +let start loc = { + source = loc.source; + start = loc.start; + _end = loc.start; +} + let btwn_exclusive loc1 loc2 = { source = loc1.source; start = loc1._end; diff --git a/src/parser/parse_error.ml b/src/parser/parse_error.ml index 5da7f096064..7d2a77b3780 100644 --- a/src/parser/parse_error.ml +++ b/src/parser/parse_error.ml @@ -75,6 +75,7 @@ type t = | ExportNamelessFunction | UnsupportedDecorator | MissingTypeParamDefault + | CtorThisParam exception Error of (Loc.t * t) list @@ -170,6 +171,7 @@ module PP = | UnsupportedDecorator -> "Found a decorator in an unsupported position." | MissingTypeParamDefault -> "Type parameter declaration needs a default, \ since a preceding type parameter declaration has a default." + | CtorThisParam -> "Found a `this` pseudo-param on a constructor." end diff --git a/src/parser/parser_flow.ml b/src/parser/parser_flow.ml index 5402ee7d966..e1e04e01f21 100644 --- a/src/parser/parser_flow.ml +++ b/src/parser/parser_flow.ml @@ -238,12 +238,13 @@ end = struct val type_parameter_instantiation : env -> Ast.Type.ParameterInstantiation.t option val generic : env -> Loc.t * Ast.Type.Generic.t val _object : ?allow_static:bool -> env -> Loc.t * Type.Object.t - val function_param_list : env -> Type.Function.Param.t option * Type.Function.Param.t list + val function_this_param : env -> Ast.Type.Function.ThisParam.t + val function_param_list : env -> Type.Function.ThisParam.t * Type.Function.Param.t list * Type.Function.Param.t option val annotation : env -> Ast.Type.annotation val annotation_opt : env -> Ast.Type.annotation option end = struct type param_list_or_type = - | ParamList of (Type.Function.Param.t option * Type.Function.Param.t list) + | ParamList of (Type.Function.ThisParam.t * Type.Function.Param.t list * Type.Function.Param.t option) | Type of Type.t let rec _type env = union env @@ -389,6 +390,7 @@ end = struct | T_STRING_TYPE -> Some Type.String | T_VOID_TYPE -> Some Type.Void | T_NULL -> Some Type.Null + | T_THIS -> Some Type.This | _ -> None and tuple = @@ -425,33 +427,41 @@ end = struct optional; }) - and function_param_list_without_parens = + and function_this_param env = + let name, _ = Parse.identifier_or_reserved_keyword env in + let param = function_param_with_id env name in + if Peek.token env <> T_RPAREN + then Expect.token env T_COMMA; + Type.Function.ThisParam.Explicit param + + and function_param_list_without_parens env this params = let param env = let name, _ = Parse.identifier_or_reserved_keyword env in function_param_with_id env name - - in let rec param_list env acc = + in + let rec param_list env acc = match Peek.token env with | T_EOF - | T_ELLIPSIS - | T_RPAREN as t -> - let rest = if t = T_ELLIPSIS - then begin - Expect.token env T_ELLIPSIS; - Some (param env) - end else None in - rest, List.rev acc + | T_RPAREN -> + this, List.rev acc, None + | T_ELLIPSIS -> + Expect.token env T_ELLIPSIS; + this, List.rev acc, Some (param env) | _ -> let acc = (param env)::acc in if Peek.token env <> T_RPAREN then Expect.token env T_COMMA; param_list env acc - - in fun env -> param_list env + in + param_list env params and function_param_list env = Expect.token env T_LPAREN; - let ret = function_param_list_without_parens env [] in + let this = match Peek.token env with + | T_THIS -> function_this_param env + | _ -> Type.Function.ThisParam.Implicit (Loc.start (Peek.loc env)) + in + let ret = function_param_list_without_parens env this [] in Expect.token env T_RPAREN; ret @@ -461,11 +471,15 @@ end = struct | T_EOF | T_ELLIPSIS -> (* (... is definitely the beginning of a param list *) - ParamList (function_param_list_without_parens env []) + let loc = Loc.start (Peek.loc env) in + let this = Type.Function.ThisParam.Implicit loc in + ParamList (function_param_list_without_parens env this []) | T_RPAREN -> - (* () or is definitely a param list *) - ParamList (None, []) - | T_IDENTIFIER -> + (* () is definitely a param list *) + let loc = Loc.start (Peek.loc env) in + ParamList (Type.Function.ThisParam.Implicit loc, [], None) + | T_IDENTIFIER + | T_THIS -> (* This could be a function parameter or a generic type *) function_param_or_generic_type env | token -> @@ -493,7 +507,9 @@ end = struct typeAnnotation; optional; }) in - ParamList (function_param_list_without_parens env [param]) + let loc = Loc.start (fst name) in + let this = Type.Function.ThisParam.Implicit loc in + ParamList (function_param_list_without_parens env this [param]) | _ -> (* Ok this is definitely a type *) (* Note; what we really want here (absent 2-token LA :) is @@ -513,13 +529,20 @@ end = struct ret and function_param_or_generic_type env = + let token = Peek.token env in let id = Parse.identifier env in match Peek.token env with | T_PLING (* optional param *) | T_COLON -> let param = function_param_with_id env id in ignore (Expect.maybe env T_COMMA); - ParamList (function_param_list_without_parens env [param]) + let this, params = match token with + | T_THIS -> Type.Function.ThisParam.Explicit param, [] + | _ -> + let loc = Loc.start (fst param) in + Type.Function.ThisParam.Implicit loc, [param] + in + ParamList (function_param_list_without_parens env this params) | _ -> Type (union_with env (intersection_with env @@ -529,11 +552,12 @@ end = struct and function_or_group env = let start_loc = Peek.loc env in match param_list_or_type env with - | ParamList (rest, params) -> + | ParamList (this, params, rest) -> Expect.token env T_ARROW; let returnType = _type env in let end_loc = fst returnType in Loc.btwn start_loc end_loc, Type.(Function Function.({ + this; params; returnType; rest; @@ -544,11 +568,12 @@ end = struct and _function env = let start_loc = Peek.loc env in let typeParameters = type_parameter_declaration ~allow_default:false env in - let rest, params = function_param_list env in + let this, params, rest = function_param_list env in Expect.token env T_ARROW; let returnType = _type env in let end_loc = fst returnType in Loc.btwn start_loc end_loc, Type.(Function Function.({ + this; params; returnType; rest; @@ -558,11 +583,12 @@ end = struct and _object = let methodish env start_loc = let typeParameters = type_parameter_declaration ~allow_default:false env in - let rest, params = function_param_list env in + let this, params, rest = function_param_list env in Expect.token env T_COLON; let returnType = _type env in let loc = Loc.btwn start_loc (fst returnType) in loc, Type.Function.({ + this; params; returnType; rest; @@ -796,6 +822,7 @@ end = struct wrap (type_parameter_declaration ~allow_default:false) let type_parameter_instantiation = wrap type_parameter_instantiation let _object ?(allow_static=false) env = wrap (_object ~allow_static) env + let function_this_param = wrap function_this_param let function_param_list = wrap function_param_list let annotation = wrap annotation let annotation_opt = wrap annotation_opt @@ -915,9 +942,13 @@ end = struct in fun env -> Expect.token env T_LPAREN; + let this = match Peek.token env with + | T_THIS -> Type.function_this_param env + | _ -> Ast.Type.Function.ThisParam.Implicit (Loc.start (Peek.loc env)) + in let params, defaults, rest = param_list env ([], [], false) in Expect.token env T_RPAREN; - params, defaults, rest + this, params, defaults, rest let function_body env ~async ~generator = let env = enter_function env ~async ~generator in @@ -972,7 +1003,7 @@ end = struct in (Type.type_parameter_declaration env, Some id) ) in - let params, defaults, rest = function_params env in + let this, params, defaults, rest = function_params env in let returnType = Type.annotation_opt env in let _, body, strict = function_body env ~async ~generator in let simple = is_simple_function_params params defaults rest in @@ -983,6 +1014,7 @@ end = struct | BodyExpression (loc, _) -> loc, true) in Loc.btwn start_loc end_loc, Statement.(FunctionDeclaration Function.({ id; + this; params; defaults; rest; @@ -1609,7 +1641,7 @@ end = struct | _ -> Some (Parse.identifier ~restricted_error:Error.StrictFunctionName env) in id, Type.type_parameter_declaration env end in - let params, defaults, rest = Declaration.function_params env in + let this, params, defaults, rest = Declaration.function_params env in let returnType = Type.annotation_opt env in let end_loc, body, strict = Declaration.function_body env ~async ~generator in @@ -1621,6 +1653,7 @@ end = struct | BodyExpression _ -> true) in Loc.btwn start_loc end_loc, Expression.(Function Function.({ id; + this; params; defaults; rest; @@ -1844,17 +1877,22 @@ end = struct * that it's an async function *) let async = Peek.token ~i:1 env <> T_ARROW && Declaration.async env in let typeParameters = Type.type_parameter_declaration env in - let params, defaults, rest, returnType = + let this, params, defaults, rest, returnType = (* Disallow all fancy features for identifier => body *) if Peek.identifier env && typeParameters = None then let id = Parse.identifier ~restricted_error:Error.StrictParamName env in let param = fst id, Pattern.Identifier id in - [param], [], None, None + let this = + Ast.Type.Function.ThisParam.Implicit (Loc.start (fst id)) + in + this, [param], [], None, None else - let params, defaults, rest = Declaration.function_params env in - params, defaults, rest, Type.annotation_opt env in + let + this, params, defaults, rest = Declaration.function_params env + in + this, params, defaults, rest, Type.annotation_opt env in (* It's hard to tell if an invalid expression was intended to be an * arrow function before we see the =>. If there are no params, that @@ -1888,6 +1926,7 @@ end = struct let loc = Loc.btwn start_loc end_loc in loc, Expression.(ArrowFunction Function.({ id = None; + this; params; defaults; rest; @@ -2054,6 +2093,10 @@ end = struct | Get | Set -> None | _ -> Type.type_parameter_declaration env) in Expect.token env T_LPAREN; + let this = match Peek.token env with + | T_THIS -> Type.function_this_param env + | _ -> Ast.Type.Function.ThisParam.Implicit (Loc.start (Peek.loc env)) + in let params = Ast.Expression.Object.Property.(match kind with | Get -> [] | Set -> @@ -2074,6 +2117,7 @@ end = struct | BodyExpression (loc, _) -> loc, true) in let value = end_loc, Function.({ id = None; + this; params; defaults; rest; @@ -2159,7 +2203,9 @@ end = struct | T_LESS_THAN | T_LPAREN -> let typeParameters = Type.type_parameter_declaration env in - let params, defaults, rest = Declaration.function_params env in + let + this, params, defaults, rest = Declaration.function_params env + in let returnType = Type.annotation_opt env in let _, body, strict = Declaration.function_body env ~async ~generator in @@ -2171,6 +2217,7 @@ end = struct | BodyExpression (loc, _) -> loc, true) in let value = end_loc, Ast.Expression.(Function Function.({ id = None; + this; params; defaults; rest; @@ -2360,7 +2407,7 @@ end = struct }))) | _ -> let typeParameters = Type.type_parameter_declaration env in - let params, defaults, rest = Declaration.function_params env in + let this, params, defaults, rest = Declaration.function_params env in let returnType = Type.annotation_opt env in let _, body, strict = Declaration.function_body env ~async ~generator in @@ -2373,6 +2420,7 @@ end = struct | BodyExpression (loc, _) -> loc, true) in let value = end_loc, Function.({ id = None; + this; params; defaults; rest; @@ -2391,8 +2439,14 @@ end = struct | Expression.Object.Property.Literal (_, { Literal.value = Literal.String "constructor"; _; - }) -> - Class.Method.Constructor + }) -> ( + match static, this with + | false, Type.Function.ThisParam.Explicit (loc, _) -> + error_at env (loc, Error.CtorThisParam); + Class.Method.Constructor + | false, _ -> Class.Method.Constructor + | _ -> Class.Method.Method + ) | _ -> Class.Method.Method) in Ast.Class.(Body.Method (Loc.btwn start_loc end_loc, Method.({ @@ -3081,12 +3135,13 @@ end = struct let id = Parse.identifier env in let start_sig_loc = Peek.loc env in let typeParameters = Type.type_parameter_declaration env in - let rest, params = Type.function_param_list env in + let this, params, rest = Type.function_param_list env in Expect.token env T_COLON; let returnType = Type._type env in let end_loc = fst returnType in let loc = Loc.btwn start_sig_loc end_loc in let value = loc, Ast.Type.(Function {Function. + this; params; returnType; rest; diff --git a/src/parser/spider_monkey_ast.ml b/src/parser/spider_monkey_ast.ml index 0db93b7f8ae..864a0ce943e 100644 --- a/src/parser/spider_monkey_ast.ml +++ b/src/parser/spider_monkey_ast.ml @@ -54,7 +54,14 @@ and Type : sig } end + module ThisParam : sig + type t = + | Implicit of Loc.t + | Explicit of Param.t + end + type t = { + this: ThisParam.t; params: Param.t list; returnType: Type.t; rest: Param.t option; @@ -141,6 +148,7 @@ and Type : sig | Any | Void | Null + | This | Number | String | Boolean @@ -969,6 +977,7 @@ and Function : sig | BodyExpression of Expression.t type t = { id: Identifier.t option; + this: Type.Function.ThisParam.t; params: Pattern.t list; defaults: Expression.t option list; rest: Identifier.t option; diff --git a/src/typing/flow_js.ml b/src/typing/flow_js.ml index 064f4017a13..3e00e0517d2 100644 --- a/src/typing/flow_js.ml +++ b/src/typing/flow_js.ml @@ -928,7 +928,8 @@ let rec __flow cx ((l: Type.t), (u: Type.use_t)) trace = (* The sink component of an annotation constrains values flowing into the annotated site. *) - | _, UseT (use_op, AnnotT (sink_t, _)) -> + | l, UseT (use_op, AnnotT (sink_t, _)) + | ClassT (l), UseT (use_op, ClassT (AnnotT (sink_t, _))) -> let reason = reason_of_t sink_t in rec_flow cx trace (ReposUpperT (reason, l), UseT (use_op, sink_t)) @@ -2400,7 +2401,7 @@ let rec __flow cx ((l: Type.t), (u: Type.use_t)) trace = (***************************************************************) | (_, - UseT (_, InstanceT (reason_inst, _, super, { + UseT (_, InstanceT (reason_inst, static, super, { fields_tmap; methods_tmap; structural = true; @@ -2408,7 +2409,14 @@ let rec __flow cx ((l: Type.t), (u: Type.use_t)) trace = }))) -> structural_subtype cx trace l reason_inst - (super, fields_tmap, methods_tmap) + (super, fields_tmap, methods_tmap); + + (match l, static with + | InstanceT (_, l, _, _), + InstanceT (reason, _, super, { fields_tmap; methods_tmap; _; }) -> + structural_subtype cx trace l reason + (super, fields_tmap, methods_tmap) + | _ -> ()) (********************************************************) (* runtime types derive static types through annotation *) @@ -3437,7 +3445,8 @@ let rec __flow cx ((l: Type.t), (u: Type.use_t)) trace = rec_flow cx trace (next, UseT (use_op, ExtendsT (try_ts_on_failure, l, u))) - | (MixedT _, UseT (_, ExtendsT ([], l, InstanceT (reason_inst, _, super, { + | (MixedT _, + UseT (_, ExtendsT ([], l, InstanceT (reason_inst, static, super, { fields_tmap; methods_tmap; structural = true; @@ -3445,7 +3454,14 @@ let rec __flow cx ((l: Type.t), (u: Type.use_t)) trace = })))) -> structural_subtype cx trace l reason_inst - (super, fields_tmap, methods_tmap) + (super, fields_tmap, methods_tmap); + + (match l, static with + | InstanceT (_, l, _, _), + InstanceT (reason, _, super, { fields_tmap; methods_tmap; _; }) -> + structural_subtype cx trace l reason + (super, fields_tmap, methods_tmap) + | _ -> ()) | (MixedT _, UseT (_, ExtendsT ([], t, tc))) -> let msg = "This type is incompatible with" in @@ -3662,6 +3678,7 @@ and ground_subtype = function | (VoidT _, UseT (_, VoidT _)) | (EmptyT _, _) | (_, UseT (_, MixedT _)) + | (_, UseT (_, ClassT (MixedT _))) | (_, UseT (_, FunProtoT _)) (* MixedT is used for object protos, this is for funcs *) | (AnyT _, _) | (_, UseT (_, AnyT _)) @@ -5939,6 +5956,7 @@ and become cx ?trace r t = match t with (* set the position of the given def type from a reason *) and reposition cx ?trace reason t = + let repos t = mod_reason_of_t (repos_reason (loc_of_reason reason)) t in match t with | OpenT (r, id) -> let constraints = find_graph cx id in @@ -5963,7 +5981,10 @@ and reposition cx ?trace reason t = mk_tvar_where cx reason (fun tvar -> flow_opt cx ?trace (t, ReposLowerT (reason, UseT (UnknownUse, tvar))) ) - | _ -> mod_reason_of_t (repos_reason (loc_of_reason reason)) t + | InstanceT (reason_inst, static, super, insttype) -> + let loc = loc_of_reason reason in + InstanceT (repos_reason loc reason_inst, repos static, super, insttype) + | _ -> repos t (* set the position of the given use type from a reason *) and reposition_use cx ?trace reason t = match t with @@ -6259,8 +6280,8 @@ end superclass. *) (* need to consider only "def" types *) -let rec assert_ground ?(infer=false) cx skip ids t = - let recurse ?infer = assert_ground ?infer cx skip ids in +let rec assert_ground ?(infer=false) ?(in_class=false) cx skip ids t = + let recurse ?infer = assert_ground ?infer ~in_class cx skip ids in match t with | BoundT _ -> () @@ -6297,13 +6318,13 @@ let rec assert_ground ?(infer=false) cx skip ids t = | FunT (_, static, prototype, { this_t; params_tlist; return_t; _ }) -> unify cx static AnyT.t; unify cx prototype AnyT.t; - unify cx this_t AnyT.t; + if in_class then recurse ~infer:true this_t else unify cx this_t AnyT.t; List.iter recurse params_tlist; recurse ~infer:true return_t | PolyT (_, t) | ThisClassT t -> - recurse t + assert_ground ~in_class:true cx skip ids t | ObjT (_, { props_tmap = id; proto_t; _ }) -> unify cx proto_t AnyT.t; @@ -6313,7 +6334,9 @@ let rec assert_ground ?(infer=false) cx skip ids t = recurse t; List.iter recurse ts - | ClassT t + | ClassT t -> + assert_ground ~in_class:true cx skip ids t + | TypeT (_, t) -> recurse t diff --git a/src/typing/func_params.ml b/src/typing/func_params.ml index 43c10401481..36ea2a851ca 100644 --- a/src/typing/func_params.ml +++ b/src/typing/func_params.ml @@ -13,91 +13,108 @@ type param = | Complex of Type.t * binding list | Rest of Type.t * binding type t = { - list: param list; + this: Type.t; + rev_list: param list; defaults: Ast.Expression.t Default.t SMap.t; } -let empty = { - list = []; +let empty this = { + this; + rev_list = []; defaults = SMap.empty } -let add cx type_params_map params pattern default = - Ast.Pattern.(match pattern with - | loc, Identifier (_, { Ast.Identifier.name; typeAnnotation; optional }) -> - let reason = mk_reason (Utils.spf "parameter `%s`" name) loc in - let t = Anno.mk_type_annotation cx type_params_map reason typeAnnotation - in (match default with - | None -> - let t = - if optional - then OptionalT t - else t +let mk cx type_params_map {Ast.Function.this; params; defaults; rest; _} implicit_this = + let add_param params pattern default = + Ast.Pattern.(match pattern with + | loc, Identifier (_, { Ast.Identifier.name; typeAnnotation; optional }) -> + let reason = mk_reason (Utils.spf "parameter `%s`" name) loc in + let t = Anno.mk_type_annotation cx type_params_map reason typeAnnotation + in (match default with + | None -> + let t = + if optional + then OptionalT t + else t + in + Hashtbl.replace (Context.type_table cx) loc t; + let binding = name, t, loc in + let rev_list = Simple (t, binding) :: params.rev_list in + { params with rev_list } + | Some expr -> + (* TODO: assert (not optional) *) + let binding = name, t, loc in + { this = params.this; + rev_list = Simple (OptionalT t, binding) :: params.rev_list; + defaults = SMap.add name (Default.Expr expr) params.defaults }) + | loc, _ -> + let reason = mk_reason "destructuring" loc in + let t = type_of_pattern pattern + |> Anno.mk_type_annotation cx type_params_map reason in + let default = Option.map default Default.expr in + let bindings = ref [] in + let defaults = ref params.defaults in + pattern |> destructuring cx t None default (fun _ loc name default t -> + Hashtbl.replace (Context.type_table cx) loc t; + bindings := (name, t, loc) :: !bindings; + Option.iter default ~f:(fun default -> + defaults := SMap.add name default !defaults + ) + ); + let t = match default with + | Some _ -> OptionalT t + | None -> t (* TODO: assert (not optional) *) in - Hashtbl.replace (Context.type_table cx) loc t; - let binding = name, t, loc in - let list = Simple (t, binding) :: params.list in - { params with list } - | Some expr -> - (* TODO: assert (not optional) *) - let binding = name, t, loc in - { list = Simple (OptionalT t, binding) :: params.list; - defaults = SMap.add name (Default.Expr expr) params.defaults }) - | loc, _ -> - let reason = mk_reason "destructuring" loc in - let t = type_of_pattern pattern - |> Anno.mk_type_annotation cx type_params_map reason in - let default = Option.map default Default.expr in - let bindings = ref [] in - let defaults = ref params.defaults in - pattern |> destructuring cx t None default (fun _ loc name default t -> - Hashtbl.replace (Context.type_table cx) loc t; - bindings := (name, t, loc) :: !bindings; - Option.iter default ~f:(fun default -> - defaults := SMap.add name default !defaults - ) - ); - let t = match default with - | Some _ -> OptionalT t - | None -> t (* TODO: assert (not optional) *) - in - { list = Complex (t, !bindings) :: params.list; - defaults = !defaults }) - -let add_rest cx type_params_map params = - function loc, { Ast.Identifier.name; typeAnnotation; _ } -> - let reason = mk_reason (Utils.spf "rest parameter `%s`" name) loc in - let t = Anno.mk_type_annotation cx type_params_map reason typeAnnotation - in { params with - list = Rest (Anno.mk_rest cx t, (name, t, loc)) :: params.list - } - -let mk cx type_params_map {Ast.Function.params; defaults; rest; _} = + { this = params.this; + rev_list = Complex (t, !bindings) :: params.rev_list; + defaults = !defaults }) + in + let add_rest params = + function loc, { Ast.Identifier.name; typeAnnotation; _ } -> + let reason = mk_reason (Utils.spf "rest parameter `%s`" name) loc in + let t = Anno.mk_type_annotation cx type_params_map reason typeAnnotation + in { params with + rev_list = Rest (Anno.mk_rest cx t, (name, t, loc)) :: params.rev_list + } + in let defaults = if defaults = [] && params <> [] then List.map (fun _ -> None) params else defaults in - let params = List.fold_left2 (add cx type_params_map) empty params defaults in + let this = Ast.Type.Function.ThisParam.(match this with + | Implicit _ -> implicit_this + | Explicit (loc, { Ast.Type.Function.Param.typeAnnotation; _ }) -> + let reason = mk_reason "pseudo-param `this`" loc in + let anno = Some (loc, typeAnnotation) in + Anno.mk_type_annotation cx type_params_map reason anno + ) in + let func_params = { + this; + rev_list = []; + defaults = SMap.empty + } in + let func_params = List.fold_left2 add_param func_params params defaults in match rest with - | Some ident -> add_rest cx type_params_map params ident - | None -> params + | Some ident -> add_rest func_params ident + | None -> func_params +let this params = params.this let names params = - params.list |> List.rev |> List.map (function + params.rev_list |> List.rev |> List.map (function | Simple (_, (name, _, _)) | Rest (_, (name, _, _)) -> name | Complex _ -> "_") let tlist params = - params.list |> List.rev |> List.map (function + params.rev_list |> List.rev |> List.map (function | Simple (t, _) | Complex (t, _) | Rest (t, _) -> t) let iter f params = - params.list |> List.rev |> List.iter (function + params.rev_list |> List.rev |> List.iter (function | Simple (_, b) | Rest (_, b) -> f b | Complex (_, bs) -> List.iter f bs) @@ -110,11 +127,12 @@ let with_default name f params = let subst_binding cx map (name, t, loc) = (name, Flow.subst cx map t, loc) let subst cx map params = - let list = params.list |> List.map (function + let this = Flow.subst cx map params.this in + let rev_list = params.rev_list |> List.map (function | Simple (t, b) -> Simple (Flow.subst cx map t, subst_binding cx map b) | Complex (t, bs) -> Complex (Flow.subst cx map t, List.map (subst_binding cx map) bs) | Rest (t, b) -> Rest (Flow.subst cx map t, subst_binding cx map b)) in - { params with list } + { params with this; rev_list } diff --git a/src/typing/func_params.mli b/src/typing/func_params.mli index 5412df9316b..e0cf5784caf 100644 --- a/src/typing/func_params.mli +++ b/src/typing/func_params.mli @@ -1,24 +1,16 @@ type t (* build up a params value *) -val empty: t -val add: Context.t -> - (Type.t SMap.t) -> (* type params map *) - t -> - Spider_monkey_ast.Pattern.t -> - Spider_monkey_ast.Expression.t option -> (* default expr *) - t -val add_rest: Context.t -> - (Type.t SMap.t) -> (* type params map *) - t -> - Spider_monkey_ast.Identifier.t -> - t - +val empty: Type.t -> t val mk: Context.t -> (Type.t SMap.t) -> (* type params map *) Spider_monkey_ast.Function.t -> + Type.t -> (* implicit `this` pseudoparameter *) t +(* type of the this pseudoparameter*) +val this: t -> Type.t + (* name of each param, in order *) (* destructured params will be "_" *) val names: t -> string list diff --git a/src/typing/statement.ml b/src/typing/statement.ml index a23ea16875a..dfa116d3db5 100644 --- a/src/typing/statement.ml +++ b/src/typing/statement.ml @@ -2726,10 +2726,11 @@ and expression_ ~is_cond cx type_params_map loc e = Ast.Expression.(match e with let reason = mk_reason (spf "super.%s(...)" name) loc in let reason_prop = mk_reason (spf "property `%s`" name) ploc in let super = super_ cx (mk_reason "super" super_loc) in + let this = this_ cx (mk_reason "this" super_loc) in let argts = List.map (expression_or_spread cx type_params_map) arguments in Type_inference_hooks_js.dispatch_call_hook cx name ploc super; Flow.mk_tvar_where cx reason (fun t -> - let funtype = Flow.mk_methodtype super argts t in + let funtype = Flow.mk_methodtype this argts t in Flow.flow cx (super, MethodT (reason, (reason_prop, name), funtype)) ) @@ -4571,6 +4572,7 @@ and mk_super cx type_params_map c targs = (* Makes signatures for fields and methods in a class. *) and mk_class_signature cx reason_c type_params_map is_derived body = Ast.Class.( let _, { Body.body = elements } = body in + let this = SMap.find_unsafe "this" type_params_map in (* In case there is no constructor, pick up a default one. *) let default_methods = @@ -4584,11 +4586,13 @@ and mk_class_signature cx reason_c type_params_map is_derived body = Ast.Class.( else (* Parent class constructors simply return new instances, which is indicated by the VoidT return type *) + let this_reason = replace_reason "pseudo-param `this`" reason_c in + let this_repos = Flow_js.reposition cx this_reason this in SMap.singleton "constructor" { meth_reason = replace_reason "default constructor" reason_c; meth_tparams = []; meth_tparams_map = SMap.empty; - meth_params = Func_params.empty; + meth_params = Func_params.empty this_repos; meth_return_type = VoidT.t; } in @@ -4642,7 +4646,8 @@ and mk_class_signature cx reason_c type_params_map is_derived body = Ast.Class.( let typeparams, type_params_map = Anno.mk_type_param_declarations cx type_params_map typeParameters in - let meth_params = Func_params.mk cx type_params_map func in + let implicit_this = if static then ClassT this else this in + let meth_params = Func_params.mk cx type_params_map func implicit_this in let meth_return_type = mk_return_type cx type_params_map func in let reason_desc = (match kind with | Method.Method -> spf "method `%s`" name @@ -4811,7 +4816,7 @@ and mk_class_elements cx instance_info static_info tparams body = Ast.Class.( warn_or_ignore_decorators cx decorators; - let this, super, class_sig = + let _, super, class_sig = if static then static_info else instance_info in @@ -4852,7 +4857,7 @@ and mk_class_elements cx instance_info static_info tparams body = Ast.Class.( MixedT (replace_reason "no next" meth_reason, Mixed_everything) ) in mk_body None cx tparams_map ~kind:function_kind ~derived_ctor - meth_params return_type body this super yield next; + meth_params return_type body super yield next; ); ignore (Abnormal.swap_saved Abnormal.Return save_return); ignore (Abnormal.swap_saved Abnormal.Throw save_throw) @@ -4912,7 +4917,8 @@ and mk_methodtype method_sig = method_sig.meth_reason, Flow.dummy_static method_sig.meth_reason, Flow.dummy_prototype, - Flow.mk_functiontype + Flow.mk_methodtype + (Func_params.this method_sig.meth_params) (Func_params.tlist method_sig.meth_params) ?params_names:(Some (Func_params.names method_sig.meth_params)) method_sig.meth_return_type @@ -5308,6 +5314,16 @@ and remove_this typeparams type_params_map = and return type, check the body against that signature by adding `this` and super` to the environment, and return the signature. *) and function_decl id cx type_params_map reason func this super = + (match func with + | { Ast.Function. + this = Ast.Type.Function.ThisParam.Explicit (loc, _); + _; + } -> + let msg = + "explicit this pseudo-parameters are not allowed on functions" in + FlowError.add_error cx (loc, [msg]) + | _ -> ()); + let { Ast.Function. typeParameters = type_params; async; generator; @@ -5320,7 +5336,7 @@ and function_decl id cx type_params_map reason func this super = let typeparams, type_params_map = Anno.mk_type_param_declarations cx type_params_map type_params in - let params = Func_params.mk cx type_params_map func in + let params = Func_params.mk cx type_params_map func this in let ret = mk_return_type cx type_params_map func in let save_return = Abnormal.clear_saved Abnormal.Return in @@ -5339,7 +5355,7 @@ and function_decl id cx type_params_map reason func this super = MixedT (replace_reason "no next" reason, Mixed_everything) ) in - mk_body id cx type_params_map ~kind params ret body this super yield next; + mk_body id cx type_params_map ~kind params ret body super yield next; ); ignore (Abnormal.swap_saved Abnormal.Return save_return); @@ -5384,7 +5400,7 @@ and define_internal cx reason x = ignore Env.(set_var cx ix (Flow.filter_optional cx reason opt) reason) and mk_body id cx type_params_map ~kind ?(derived_ctor=false) - params ret body this super yield next = + params ret body super yield next = let loc = Ast.Function.(match body with | BodyBlock (loc, _) @@ -5429,6 +5445,7 @@ and mk_body id cx type_params_map ~kind ?(derived_ctor=false) Scope.add_entry name entry function_scope); (* special bindings for this, super, and return value slot *) + let this = Func_params.this params in initialize_this_super derived_ctor this super function_scope; Scope.( let new_entry t = diff --git a/src/typing/type_annotation.ml b/src/typing/type_annotation.ml index 3dcf9844335..c7fe2cead2d 100644 --- a/src/typing/type_annotation.ml +++ b/src/typing/type_annotation.ml @@ -58,6 +58,19 @@ let rec convert cx type_params_map = Ast.Type.(function | loc, Null -> NullT.at loc +| loc, This -> + if SMap.mem "this" type_params_map then + (* We model a this type like a type parameter. The bound on a this + type reflects the interface of `this` exposed in the current + environment. Currently, we only support this types in a class + environment: a this type in class C is bounded by C. *) + let reason = mk_reason "`this` type" loc in + Flow_js.reposition cx reason (SMap.find_unsafe "this" type_params_map) + else ( + FlowError.add_warning cx (loc, ["Unexpected use of `this` type"]); + AnyT.t + ) + | loc, Number -> NumT.at loc | loc, String -> StrT.at loc @@ -235,21 +248,6 @@ let rec convert cx type_params_map = Ast.Type.(function AbstractT t ) - | "this" -> - if SMap.mem "this" type_params_map then - (* We model a this type like a type parameter. The bound on a this - type reflects the interface of `this` exposed in the current - environment. Currently, we only support this types in a class - environment: a this type in class C is bounded by C. *) - check_type_param_arity cx loc typeParameters 0 (fun () -> - let reason = mk_reason "`this` type" loc in - Flow_js.reposition cx reason (SMap.find_unsafe "this" type_params_map) - ) - else ( - FlowError.add_warning cx (loc, ["Unexpected use of `this` type"]); - AnyT.t - ) - (* Class is the type of the class whose instances are of type T *) | "Class" -> check_type_param_arity cx loc typeParameters 1 (fun () -> @@ -348,7 +346,12 @@ let rec convert cx type_params_map = Ast.Type.(function end -| loc, Function { Function.params; returnType; rest; typeParameters } -> +| _, Function { Function.this = Function.ThisParam.Explicit (loc, _); _ } -> + let msg = "Unsupported explicit this pseudoparameter found in function type" in + FlowError.add_error cx (loc, [msg]); + AnyT.t + +| loc, Function { Function.this = Function.ThisParam.Implicit _; params; returnType; rest; typeParameters } -> let typeparams, type_params_map = mk_type_param_declarations cx type_params_map typeParameters in diff --git a/tests/class_type/class_type.exp b/tests/class_type/class_type.exp index c82edb53368..b34e160e6b4 100644 --- a/tests/class_type/class_type.exp +++ b/tests/class_type/class_type.exp @@ -1,2 +1,8 @@ +test2.js:35 + 35: static gn(): Class { + ^ Y. This type is incompatible with + 29: static gn(): Class { + ^^^^ some incompatible instantiation of `this` -Found 0 errors + +Found 1 error diff --git a/tests/class_type/test2.js b/tests/class_type/test2.js new file mode 100644 index 00000000000..f94a46c8535 --- /dev/null +++ b/tests/class_type/test2.js @@ -0,0 +1,40 @@ +class A {} +class B extends A {} + +class K { + static gn() { + return this; + } +} + +class L extends K { + static gn() { // Bug: False positive. This is a NG. + return L; + } +} + +class W { + fn(): Class { + return B; + } + static fn(): Class { + return B; + } + static gn(): Class { + return W; + } +} + +class X extends W { + static gn(): Class { + return this; + } +} + +class Y extends X { + static gn(): Class { + return Y; + } +} + +var a: Class = X.gn(); diff --git a/tests/interface/interface.exp b/tests/interface/interface.exp index c15054d5022..45d86f7318c 100644 --- a/tests/interface/interface.exp +++ b/tests/interface/interface.exp @@ -108,5 +108,41 @@ test3.js:6 6: (k.y: number); // error: y is string in I ^^^^^^ number - -Found 19 errors +test4.js:8 + 8: var p: A & I = a; // NG + ^ property `fn` of I. Property not found in + 8: var p: A & I = a; // NG + ^ A + +test4.js:8 + 8: var p: A & I = a; // NG + ^ property `gn` of statics of I. Property not found in + 8: var p: A & I = a; // NG + ^ statics of A + +test4.js:9 + 9: var P: Class & Class = A; // NG + ^ property `gn` of statics of I. Property not found in + 6: class A {} + ^ statics of A + +test4.js:9 + 9: var P: Class & Class = A; // NG + ^ property `fn` of I. Property not found in + 9: var P: Class & Class = A; // NG + ^ A + +test4.js:20 + 20: var q: A & I = b; // OK + ^ property `gn` of statics of I. Property not found in + 20: var q: A & I = b; // OK + ^ statics of B + +test4.js:21 + 21: var Q: Class & Class = B; // OK + ^ property `gn` of statics of I. Property not found in + 11: class B extends A { + ^ statics of B + + +Found 25 errors diff --git a/tests/interface/test4.js b/tests/interface/test4.js new file mode 100644 index 00000000000..f734dc9a44a --- /dev/null +++ b/tests/interface/test4.js @@ -0,0 +1,21 @@ +interface I { + fn(): number; + static gn(): number; +} + +class A {} +var a = new A(); +var p: A & I = a; // NG +var P: Class & Class = A; // NG + +class B extends A { + fn(): number { + return 1; + } + gn(): number { + return 2; + } +} +var b = new B(); +var q: A & I = b; // OK +var Q: Class & Class = B; // OK diff --git a/tests/this_param/.flowconfig b/tests/this_param/.flowconfig new file mode 100644 index 00000000000..e69de29bb2d diff --git a/tests/this_param/ctor.js b/tests/this_param/ctor.js new file mode 100644 index 00000000000..e08cc95c0ff --- /dev/null +++ b/tests/this_param/ctor.js @@ -0,0 +1,3 @@ +class A { + constructor(this: this) {} +} diff --git a/tests/this_param/explicit.js b/tests/this_param/explicit.js new file mode 100644 index 00000000000..26620bf8299 --- /dev/null +++ b/tests/this_param/explicit.js @@ -0,0 +1,10 @@ +class A { + method(this: Class) {} + static staticMethod(this: this) {} +} + +var a = new A(); +a.method(); // NG + +// False positive. Most likely a problem with the "knot" of `fix_this_class`. +A.staticMethod(); // NG diff --git a/tests/this_param/function.js b/tests/this_param/function.js new file mode 100644 index 00000000000..088e84980d7 --- /dev/null +++ b/tests/this_param/function.js @@ -0,0 +1,14 @@ +function fn(this: { x: number }, x: string): string { + return x + this.x; +} + +class A { + method(): number { + function k(this: any): number { + return 5; + } + return k(); + } +} + +var k = (this: any) => 5; diff --git a/tests/this_param/interface.js b/tests/this_param/interface.js new file mode 100644 index 00000000000..4402c504b1f --- /dev/null +++ b/tests/this_param/interface.js @@ -0,0 +1,89 @@ +interface I { + anotherMethod(): number; + static anotherStaticMethod(): number; +} + +class A { + x: number; + static x: number; + method(this: this & I): number { + return this.x + this.anotherMethod(); + } + static staticMethod(this: Class & Class): number { + // TODO: There's a commutativity problem here. + // `Class & I != I & Class`. Add tests for intersections that + // include `ThisClassT`s. + return this.x + this.anotherStaticMethod(); + } +} +A.x = 1 + +var a = new A(); // OK +var n1: number = a.method(); // NG +var n2: number = A.staticMethod(); // NG + +class B extends A { + anotherMethod(): string { + // NGish: Incompatible with the `this` constraint on `method`. + return "another method"; + } + static anotherStaticMethod(): string { + // NGish: Incompatible with the `this` constraint on `staticMethod`. + return "another static method"; + } +} + +var b = new B(); +var s1: string = b.anotherMethod(); // OK: Breaks a type requirement on + // `method`'s `this` pseudo-param, but + // that's okay on a `B` instance. +var n3: number = b.method(); // NG: The return type on `anotherMethod` of `B` + // breaks the constraint on `method`'s `this` + // pseudo-param. +var s2: string = B.anotherStaticMethod(); // OK: Analogous to `s1`. + +// False positive. Flow ignores the following error, unless I comment out `n3` +// above. If I move the `s3` above `n3`, then `s3` errors and the `n3` error is +// ignored. Is this a bug or a feature? If bug, it traces to an `Ops.peek` +// call in `typecheck_error`, where the call yields the prior function call's +// loc. +var s3: number = B.staticMethod(); // NG: The return type on + // `anotherStaticMethod` of `B` breaks the + // constraint on `staticMethod`'s `this` + // pseudo-param. + +class C extends A { + anotherMethod() { + return 5; + } + static anotherStaticMethod() { + return 2; + } +} + +var c = new C(); +var n3: number = c.method(); // OK +var n4: number = C.staticMethod(); // OK + +// TJP TODO: In tests, generalize the following to a generic so that #1369 can be closed. Remove this note. +class K { + method(this: I): number { + return this.anotherMethod(); // OK + } + methodCaller(): number { + return this.method(); // NG: The implicit pseudo-param of `methodCaller`, + // i.e. `this`, doesn't satisfy the `I` interface. + } +} + +var k = new K(); // OK +var n5: number = k.method(); // NG: `k` doesn't satisfy the requirements of `I` +var n6: number = k.methodCaller(); + +var ell = { + fn: K.prototype.method +}; +var n7: number = ell.fn(); // NG + +var fn = K.prototype.method; +var n8: number = fn(); // NG diff --git a/tests/this_param/object.js b/tests/this_param/object.js new file mode 100644 index 00000000000..95a2d2195aa --- /dev/null +++ b/tests/this_param/object.js @@ -0,0 +1,98 @@ +type I = { + anotherMethod(): number; +}; + +type J = { + anotherStaticMethod(): number; +}; + +class A { + x: number; + static x: number; + method(this: this & I): number { + return this.anotherMethod(); + } + static staticMethod(this: J & Class): number { + return this.anotherStaticMethod(); + } +} +A.x = 1 + +var a = new A(); +var n1: number = a.method(); // NG +var n2: number = A.staticMethod(); // NG + +class B extends A { + anotherMethod(): string { + // NG: Incompatible with the `this` constraint on `method`. + return "another method"; + } + static anotherStaticMethod(): string { + // NG: Incompatible with the `this` constraint on `staticMethod`. + return "another static method"; + } +} + +var b = new B(); +var s1: string = b.anotherMethod(); +var n3: number = b.method(); // NG +var s2: string = B.anotherStaticMethod(); + +// False negative. This is an error, but the errors include a possibly +// unnecessary error, i.e. `J & Class` incompatible with +// `class B extends A`. This traces back to the InstanceT ~> ObjT flow: found +// fields get `rec_unify`ed instead of `rec_flow`ed (I suspect that this has to +// do with the dynamism of objects under flow). +var s3: number = B.staticMethod(); // NG + +class C extends A { + anotherMethod() { + return 5; + } + static anotherStaticMethod() { + return 2; + } +} + +var c = new C(); +var n3: number = c.method(); + +// False negative. +var n4: number = C.staticMethod(); // OK + +class K { + method(this: I): number { + return this.anotherMethod(); + } + methodCaller(): number { + return this.method(); // NG + } +} + +var k = new K(); +var n5: number = k.method(); // NG +var n6: number = k.methodCaller(); + +var ell = { + anotherMethod(): number { + return 3; + }, + fn: K.prototype.method +}; + +var n7: number = ell.fn(); + +class Issue1369 { + _x: T; + getXMultBy(this: Issue1369, y: number): number { + return this._x * y; + } +} + +var s = new Issue1369(); +s._x = 5; +s.getXMultBy(3); + +var t = new Issue1369(); +t._x = "a string"; +t.getXMultBy(4); // NG diff --git a/tests/this_param/this_param.exp b/tests/this_param/this_param.exp new file mode 100644 index 00000000000..612ef8bdb56 --- /dev/null +++ b/tests/this_param/this_param.exp @@ -0,0 +1,223 @@ +ctor.js:2 + 2: constructor(this: this) {} + ^^^^^^^^^^ Found a `this` pseudo-param on a constructor. + +explicit.js:7 + 7: a.method(); // NG + ^^^^^^^^^^ call of method `method` + 7: a.method(); // NG + ^ A. This type is incompatible with + 2: method(this: Class) {} + ^^^^ class type: `this` type + +function.js:1 + 1: function fn(this: { x: number }, x: string): string { + ^^^^^^^^^^^^^^^^^^^ explicit this pseudo-parameters are not allowed on functions + +function.js:7 + 7: function k(this: any): number { + ^^^^^^^^^ explicit this pseudo-parameters are not allowed on functions + +function.js:14 + 14: var k = (this: any) => 5; + ^^^^^^^^^ explicit this pseudo-parameters are not allowed on functions + +interface.js:22 + 22: var n1: number = a.method(); // NG + ^^^^^^^^^^ call of method `method` + 9: method(this: this & I): number { + ^ property `anotherMethod` of I. Property not found in + 22: var n1: number = a.method(); // NG + ^ A + +interface.js:22 + 22: var n1: number = a.method(); // NG + ^^^^^^^^^^ call of method `method` + 9: method(this: this & I): number { + ^ property `anotherStaticMethod` of statics of I. Property not found in + 22: var n1: number = a.method(); // NG + ^ statics of A + +interface.js:23 + 23: var n2: number = A.staticMethod(); // NG + ^^^^^^^^^^^^^^^^ call of method `staticMethod` + 12: static staticMethod(this: Class & Class): number { + ^ property `anotherStaticMethod` of statics of I. Property not found in + 6: class A { + ^ statics of A + +interface.js:23 + 23: var n2: number = A.staticMethod(); // NG + ^^^^^^^^^^^^^^^^ call of method `staticMethod` + 12: static staticMethod(this: Class & Class): number { + ^ property `anotherMethod` of I. Property not found in + 23: var n2: number = A.staticMethod(); // NG + ^ A + +interface.js:40 + 40: var n3: number = b.method(); // NG: The return type on `anotherMethod` of `B` + ^^^^^^^^^^ call of method `method` + 26: anotherMethod(): string { + ^^^^^^ string. This type is incompatible with + 2: anotherMethod(): number; + ^^^^^^ number + +interface.js:40 + 40: var n3: number = b.method(); // NG: The return type on `anotherMethod` of `B` + ^^^^^^^^^^ call of method `method` + 30: static anotherStaticMethod(): string { + ^^^^^^ string. This type is incompatible with + 3: static anotherStaticMethod(): number; + ^^^^^^ number + +interface.js:70 + 70: method(this: I): number { + ^ property `anotherMethod` of I. Property not found in + 86: var n7: number = ell.fn(); // NG + ^^^ object literal + +interface.js:74 + 74: return this.method(); // NG: The implicit pseudo-param of `methodCaller`, + ^^^^^^^^^^^^^ call of method `method` + 70: method(this: I): number { + ^ property `anotherMethod` of I. Property not found in + 69: class K { + ^ K + +interface.js:74 + 74: return this.method(); // NG: The implicit pseudo-param of `methodCaller`, + ^^^^^^^^^^^^^ call of method `method` + 70: method(this: I): number { + ^ property `anotherStaticMethod` of statics of I. Property not found in + 69: class K { + ^ statics of K + +interface.js:80 + 80: var n5: number = k.method(); // NG: `k` doesn't satisfy the requirements of `I` + ^^^^^^^^^^ call of method `method` + 70: method(this: I): number { + ^ property `anotherMethod` of I. Property not found in + 80: var n5: number = k.method(); // NG: `k` doesn't satisfy the requirements of `I` + ^ K + +interface.js:80 + 80: var n5: number = k.method(); // NG: `k` doesn't satisfy the requirements of `I` + ^^^^^^^^^^ call of method `method` + 70: method(this: I): number { + ^ property `anotherStaticMethod` of statics of I. Property not found in + 80: var n5: number = k.method(); // NG: `k` doesn't satisfy the requirements of `I` + ^ statics of K + +interface.js:89 + 89: var n8: number = fn(); // NG + ^^^^ function call + 70: method(this: I): number { + ^ property `anotherMethod` of I. Property not found in +global object + +object.js:22 + 22: var n1: number = a.method(); // NG + ^^^^^^^^^^ call of method `method` + 12: method(this: this & I): number { + ^ property `anotherMethod`. Property not found in + 22: var n1: number = a.method(); // NG + ^ A + +object.js:23 + 23: var n2: number = A.staticMethod(); // NG + ^^^^^^^^^^^^^^^^ call of method `staticMethod` + 15: static staticMethod(this: J & Class): number { + ^ property `anotherStaticMethod`. Property not found in + 23: var n2: number = A.staticMethod(); // NG + ^ statics of A + +object.js:38 + 38: var n3: number = b.method(); // NG + ^^^^^^^^^^ call of method `method` + 2: anotherMethod(): number; + ^^^^^^ number. This type is incompatible with + 26: anotherMethod(): string { + ^^^^^^ string + +object.js:38 + 38: var n3: number = b.method(); // NG + ^^^^^^^^^^ call of method `method` + 26: anotherMethod(): string { + ^^^^^^ string. This type is incompatible with + 2: anotherMethod(): number; + ^^^^^^ number + +object.js:46 + 46: var s3: number = B.staticMethod(); // NG + ^^^^^^^^^^^^^^^^ call of method `staticMethod` + 6: anotherStaticMethod(): number; + ^^^^^^ number. This type is incompatible with + 30: static anotherStaticMethod(): string { + ^^^^^^ string + +object.js:46 + 46: var s3: number = B.staticMethod(); // NG + ^^^^^^^^^^^^^^^^ call of method `staticMethod` + 15: static staticMethod(this: J & Class): number { + ^^^^^^^^^^^^^^^ intersection. This type is incompatible with + 25: class B extends A { + ^ class type: `this` type + Member 1: + 5: type J = { + ^ object type + Error: + 5: type J = { + ^ object type. This type is incompatible with + 25: class B extends A { + ^ class type: `this` type + Member 2: + 15: static staticMethod(this: J & Class): number { + ^^^^ class type: some incompatible instantiation of `this` + Error: + 25: class B extends A { + ^ B. This type is incompatible with + 15: static staticMethod(this: J & Class): number { + ^^^^ some incompatible instantiation of `this` + +object.js:46 + 46: var s3: number = B.staticMethod(); // NG + ^^^^^^^^^^^^^^^^ call of method `staticMethod` + 30: static anotherStaticMethod(): string { + ^^^^^^ string. This type is incompatible with + 6: anotherStaticMethod(): number; + ^^^^^^ number + +object.js:61 + 61: var n4: number = C.staticMethod(); // OK + ^^^^^^^^^^^^^^^^ call of method `staticMethod` + 48: class C extends A { + ^ C. This type is incompatible with + 15: static staticMethod(this: J & Class): number { + ^^^^ some incompatible instantiation of `this` + +object.js:68 + 68: return this.method(); // NG + ^^^^^^^^^^^^^ call of method `method` + 64: method(this: I): number { + ^ property `anotherMethod`. Property not found in + 63: class K { + ^ K + +object.js:73 + 73: var n5: number = k.method(); // NG + ^^^^^^^^^^ call of method `method` + 64: method(this: I): number { + ^ property `anotherMethod`. Property not found in + 73: var n5: number = k.method(); // NG + ^ K + +object.js:98 + 98: t.getXMultBy(4); // NG + ^^^^^^^^^^^^^^^ call of method `getXMultBy` + 97: t._x = "a string"; + ^^^^^^^^^^ string. This type is incompatible with + 87: getXMultBy(this: Issue1369, y: number): number { + ^^^^^^ number + + +Found 28 errors diff --git a/tests/this_type/generics.js b/tests/this_type/generics.js index 0514ed85ae1..8cd73346d59 100644 --- a/tests/this_type/generics.js +++ b/tests/this_type/generics.js @@ -6,3 +6,46 @@ class Implicit { arg: X; val: X; } class ImplicitNumber extends Implicit { arg: number; } (new ImplicitNumber().val: string) // error: number ~> string + +class A {} + +class B extends A { + x: T; + constructor(x: T) { + super(); + this.x = x; + } + method(): this { + return new this.constructor(this.x); + } + static staticMethod(x: T): this { + return new this(x); + } +} + +class C extends B { +/* Demo bugs in calls on `super` + method() { + var t = super.method(); + t.x += 5; + return t; + } + static staticMethod(x) { + var t = super.staticMethod(x); + t.x += 6; + return t; + } +*/ +} + +var a = new A(); +var b1 = new B(1); +var b2 = new B("a string"); +var b3 = new B(null); +var c1: C = new C(2); +var c2 = new C("another string"); // NG +var c3 = new C(null); // NG + +c1 = b1.method(); // NG +c1 = b2.method(); // NG +c1 = b3.method(); // NG diff --git a/tests/this_type/super.js b/tests/this_type/super.js new file mode 100644 index 00000000000..2c8d6ad4590 --- /dev/null +++ b/tests/this_type/super.js @@ -0,0 +1,20 @@ +// @flow +class A { + method(): this { + return new this.constructor(); + } + static staticMethod(): this { + return new this(); + } +} + +class B extends A { +/* Demo bugs in calls on `super` + method() { + return super.method(); + } + static staticMethod(x) { + return super.staticMethod(x); + } +*/ +} diff --git a/tests/this_type/this_type.exp b/tests/this_type/this_type.exp index 8ef9e0684bb..b5f673d0635 100644 --- a/tests/this_type/this_type.exp +++ b/tests/this_type/this_type.exp @@ -92,6 +92,40 @@ generics.js:8 8: (new ImplicitNumber().val: string) // error: number ~> string ^^^^^^ string +generics.js:46 + 46: var c2 = new C("another string"); // NG + ^^^^^^^^^^^^^^^^^^^^^^^ constructor call + 46: var c2 = new C("another string"); // NG + ^^^^^^^^^^^^^^^^ string. This type is incompatible with + 26: class C extends B { + ^^^^^^ number + +generics.js:47 + 47: var c3 = new C(null); // NG + ^^^^^^^^^^^ constructor call + 47: var c3 = new C(null); // NG + ^^^^ null. This type is incompatible with + 26: class C extends B { + ^^^^^^ number + +generics.js:49 + 49: c1 = b1.method(); // NG + ^^^^^^^^^^^ B. This type is incompatible with + 45: var c1: C = new C(2); + ^ C + +generics.js:50 + 50: c1 = b2.method(); // NG + ^^^^^^^^^^^ B. This type is incompatible with + 45: var c1: C = new C(2); + ^ C + +generics.js:51 + 51: c1 = b3.method(); // NG + ^^^^^^^^^^^ B. This type is incompatible with + 45: var c1: C = new C(2); + ^ C + import.js:8 8: foo(): B1 { return new B1(); } // error ^^ B1. This type is incompatible with @@ -205,4 +239,4 @@ test.js:56 ^^^^ `this` type. contravariant position (expected `this` to occur only covariantly) -Found 41 errors +Found 46 errors