Rip out legacy reactivity from the typechecker and HackC
[hiphop-php.git] / hphp / hack / src / naming / naming.ml
bloba5c02a5c18030cb3221a5ac4df2368d7e8c3f0d0
1 (*
2 * Copyright (c) 2015, Facebook, Inc.
3 * All rights reserved.
5 * This source code is licensed under the MIT license found in the
6 * LICENSE file in the "hack" directory of this source tree.
8 *)
10 (** Module "naming" a program.
12 * The naming phase consists in several things
13 * 1- get all the global names
14 * 2- transform all the local names into a unique identifier
17 open Hh_prelude
18 open Common
19 open Utils
20 open String_utils
21 module N = Aast
22 module SN = Naming_special_names
23 module NS = Namespaces
24 module Partial = Partial_provider
25 module GEnv = Naming_global.GEnv
27 (*****************************************************************************)
28 (* The types *)
29 (*****************************************************************************)
31 (* We want to keep the positions of names that have been
32 * replaced by identifiers.
34 type positioned_ident = Pos.t * Local_id.t
36 type is_final = bool
38 type genv = {
39 (* strict? decl? partial? *)
40 in_mode: FileInfo.mode;
41 (* various options that control the strictness of the typechecker *)
42 ctx: Provider_context.t;
43 (* In function foo<T1, ..., Tn> or class<T1, ..., Tn>, the field
44 * type_params knows T1 .. Tn. It is able to find out about the
45 * constraint on these parameters. *)
46 type_params: SSet.t;
47 (* The current class, None if we are in a function *)
48 current_cls: (Ast_defs.id * Ast_defs.class_kind * is_final) option;
49 (* Namespace environment, e.g., what namespace we're in and what use
50 * declarations are in play. *)
51 namespace: Namespace_env.env;
54 (* Handler called when we see an unbound name. *)
55 type unbound_handler = Pos.t * string -> positioned_ident
57 (* The primitives to manipulate the naming environment *)
58 module Env : sig
59 type lenv
61 val empty_local : unbound_handler option -> lenv
63 val make_class_env : Provider_context.t -> Nast.class_ -> genv * lenv
65 val make_typedef_env : Provider_context.t -> Nast.typedef -> genv * lenv
67 val make_top_level_env : Provider_context.t -> genv * lenv
69 val make_fun_decl_genv : Provider_context.t -> Nast.fun_ -> genv
71 val make_file_attributes_env :
72 Provider_context.t -> FileInfo.mode -> Aast.nsenv -> genv * lenv
74 val make_const_env : Provider_context.t -> Nast.gconst -> genv * lenv
76 val add_lvar : genv * lenv -> Ast_defs.id -> positioned_ident -> unit
78 val add_param : genv * lenv -> Nast.fun_param -> genv * lenv
80 val new_lvar : genv * lenv -> Ast_defs.id -> positioned_ident
82 val lvar : genv * lenv -> Ast_defs.id -> positioned_ident
84 val scope : genv * lenv -> (genv * lenv -> 'a) -> 'a
86 val remove_locals : genv * lenv -> Ast_defs.id list -> unit
87 end = struct
88 type map = positioned_ident SMap.t
90 (* The local environment *)
91 type lenv = {
92 (* The set of locals *)
93 locals: map ref;
94 (* Handler called when we see an unbound name.
95 * This is used to compute an approximation of the list of captured
96 * variables for closures: when we see an undefined variable, we add it
97 * to the list of captured variables.
99 * See expr_lambda for details.
101 unbound_handler: unbound_handler option;
104 let get_tparam_names paraml =
105 List.fold_right
106 ~init:SSet.empty
107 ~f:(fun { Aast.tp_name = (_, x); _ } acc -> SSet.add x acc)
108 paraml
110 let empty_local unbound_handler = { locals = ref SMap.empty; unbound_handler }
112 let make_class_genv ctx tparams mode (cid, ckind) namespace final =
114 in_mode = mode;
115 ctx;
116 type_params = get_tparam_names tparams;
117 current_cls = Some (cid, ckind, final);
118 namespace;
121 let make_class_env ctx c =
122 let genv =
123 make_class_genv
125 c.Aast.c_tparams
126 c.Aast.c_mode
127 (c.Aast.c_name, c.Aast.c_kind)
128 c.Aast.c_namespace
129 c.Aast.c_final
131 let lenv = empty_local None in
132 (genv, lenv)
134 let make_typedef_genv ctx tparams tdef_namespace =
136 in_mode = FileInfo.Mstrict;
137 ctx;
138 type_params = get_tparam_names tparams;
139 current_cls = None;
140 namespace = tdef_namespace;
143 let make_typedef_env ctx tdef =
144 let genv =
145 make_typedef_genv ctx tdef.Aast.t_tparams tdef.Aast.t_namespace
147 let lenv = empty_local None in
148 (genv, lenv)
150 let make_fun_genv ctx params f_mode f_namespace =
152 in_mode = f_mode;
153 ctx;
154 type_params = get_tparam_names params;
155 current_cls = None;
156 namespace = f_namespace;
159 let make_fun_decl_genv ctx f =
160 make_fun_genv ctx f.Aast.f_tparams f.Aast.f_mode f.Aast.f_namespace
162 let make_const_genv ctx cst =
164 in_mode = cst.Aast.cst_mode;
165 ctx;
166 type_params = SSet.empty;
167 current_cls = None;
168 namespace = cst.Aast.cst_namespace;
171 let make_top_level_genv ctx =
173 in_mode = FileInfo.Mpartial;
174 ctx;
175 type_params = SSet.empty;
176 current_cls = None;
177 namespace = Namespace_env.empty_with_default;
180 let make_top_level_env ctx =
181 let genv = make_top_level_genv ctx in
182 let lenv = empty_local None in
183 let env = (genv, lenv) in
186 let make_file_attributes_genv ctx mode namespace =
188 in_mode = mode;
189 ctx;
190 type_params = SSet.empty;
191 current_cls = None;
192 namespace;
195 let make_file_attributes_env ctx mode namespace =
196 let genv = make_file_attributes_genv ctx mode namespace in
197 let lenv = empty_local None in
198 let env = (genv, lenv) in
201 let make_const_env ctx cst =
202 let genv = make_const_genv ctx cst in
203 let lenv = empty_local None in
204 let env = (genv, lenv) in
207 (* Adds a local variable, without any check *)
208 let add_lvar (_, lenv) (_, name) (p, x) =
209 lenv.locals := SMap.add name (p, x) !(lenv.locals);
212 let add_param env param =
213 let p_name = param.N.param_name in
214 let id = Local_id.make_unscoped p_name in
215 let p_pos = param.N.param_pos in
216 let () = add_lvar env (p_pos, p_name) (p_pos, id) in
219 (* Defines a new local variable.
220 Side effects:
221 1) if the local is not in the local environment then it is added.
222 Return value: the given position and deduced/created identifier. *)
223 let new_lvar (_, lenv) (p, x) =
224 let lcl = SMap.find_opt x !(lenv.locals) in
225 let ident =
226 match lcl with
227 | Some lcl -> snd lcl
228 | None ->
229 let ident = Local_id.make_unscoped x in
230 lenv.locals := SMap.add x (p, ident) !(lenv.locals);
231 ident
233 (p, ident)
235 let handle_undefined_variable (_genv, env) (p, x) =
236 match env.unbound_handler with
237 | None -> (p, Local_id.make_unscoped x)
238 | Some f -> f (p, x)
240 (* Function used to name a local variable *)
241 let lvar (genv, env) (p, x) =
242 let (p, ident) =
244 SN.Superglobals.is_superglobal x
245 && FileInfo.equal_mode genv.in_mode FileInfo.Mpartial
246 then
247 (p, Local_id.make_unscoped x)
248 else
249 let lcl = SMap.find_opt x !(env.locals) in
250 match lcl with
251 | Some lcl -> (p, snd lcl)
252 | None -> handle_undefined_variable (genv, env) (p, x)
254 (p, ident)
256 (* Scope, keep the locals, go and name the body, and leave the
257 * local environment intact
259 let scope env f =
260 let (_genv, lenv) = env in
261 let lenv_copy = !(lenv.locals) in
262 let res = f env in
263 lenv.locals := lenv_copy;
266 let remove_locals env vars =
267 let (_genv, lenv) = env in
268 lenv.locals :=
269 List.fold_left
270 vars
271 ~f:(fun l id -> SMap.remove (snd id) l)
272 ~init:!(lenv.locals)
275 (*****************************************************************************)
276 (* Helpers *)
277 (*****************************************************************************)
279 let elaborate_namespaces =
280 new Naming_elaborate_namespaces_endo.generic_elaborator
282 let check_repetition s param =
283 let name = param.Aast.param_name in
284 if SSet.mem name s then Errors.already_bound param.Aast.param_pos name;
285 if not (String.equal name SN.SpecialIdents.placeholder) then
286 SSet.add name s
287 else
290 let check_name (p, name) =
291 (* We perform this check here because currently, naming edits the AST to add
292 * a parent node of this class to enums during the AST transform *)
294 ( String.equal name SN.Classes.cHH_BuiltinEnum
295 || String.equal name SN.Classes.cHH_BuiltinEnumClass )
296 && not (string_ends_with (Relative_path.suffix (Pos.filename p)) ".hhi")
297 then
298 Errors.using_internal_class p (strip_ns name)
300 let convert_shape_name env = function
301 | Ast_defs.SFlit_int (pos, s) -> Ast_defs.SFlit_int (pos, s)
302 | Ast_defs.SFlit_str (pos, s) -> Ast_defs.SFlit_str (pos, s)
303 | Ast_defs.SFclass_const ((class_pos, class_name), (const_pos, const_name)) ->
304 (* e.g. Foo::BAR or self::BAR. The first tuple is the use of Foo, second is the use of BAR *)
305 (* We will resolve class-name 'self' *)
306 let class_name =
307 if String.equal class_name SN.Classes.cSelf then (
308 match (fst env).current_cls with
309 | Some ((_class_decl_pos, class_name), _, _) -> class_name
310 | None ->
311 Errors.self_outside_class class_pos;
312 SN.Classes.cUnknown
313 ) else
314 let () = check_name (class_pos, class_name) in
315 class_name
317 Ast_defs.SFclass_const ((class_pos, class_name), (const_pos, const_name))
319 let arg_unpack_unexpected = function
320 | None -> ()
321 | Some (pos, _) ->
322 Errors.naming_too_few_arguments pos;
325 (************************************************************************)
326 (* Naming of type hints *)
327 (************************************************************************)
330 * The existing hint function goes from Ast_defs.hint -> Nast.hint
331 * This hint function goes from Aast.hint -> Nast.hint
332 * Used with with Ast_to_nast to go from Ast_defs.hint -> Nast.hint
334 let rec hint
335 ?(forbid_this = false)
336 ?(allow_retonly = false)
337 ?(allow_wildcard = false)
338 ?(allow_like = false)
339 ?(in_where_clause = false)
340 ?(tp_depth = 0)
342 (hh : Aast.hint) =
343 let (p, h) = hh in
344 ( p,
345 hint_
346 ~forbid_this
347 ~allow_retonly
348 ~allow_wildcard
349 ~allow_like
350 ~in_where_clause
351 ~tp_depth
353 (p, h) )
355 and contexts env ctxs =
356 let (pos, hl) = ctxs in
357 let hl =
358 List.map
359 ~f:(fun h ->
360 match h with
361 | (p, Aast.Happly ((_, wildcard), []))
362 when String.equal wildcard SN.Typehints.wildcard ->
363 (* More helpful wildcard error for coeffects. We expect all valid
364 * wildcard hints to be transformed into Hfun_context *)
365 Errors.invalid_wildcard_context p;
366 (p, N.Herr)
367 | _ -> hint env h)
370 (pos, hl)
372 and hfun env hl il variadic_hint ctxs h readonly_ret =
373 let variadic_hint = Option.map variadic_hint (hint env) in
374 let hl = List.map ~f:(hint env) hl in
375 let ctxs = Option.map ~f:(contexts env) ctxs in
376 N.Hfun
379 hf_param_tys = hl;
380 hf_param_info = il;
381 hf_variadic_ty = variadic_hint;
382 hf_ctxs = ctxs;
383 hf_return_ty = hint ~allow_retonly:true env h;
384 hf_is_readonly_return = readonly_ret;
387 and hint_
388 ~forbid_this
389 ~allow_retonly
390 ~allow_wildcard
391 ~allow_like
392 ~in_where_clause
393 ?(tp_depth = 0)
395 (p, x) =
396 let tcopt = Provider_context.get_tcopt (fst env).ctx in
397 let like_type_hints_enabled = TypecheckerOptions.like_type_hints tcopt in
398 let hint = hint ~forbid_this ~allow_wildcard ~allow_like in
399 match x with
400 | Aast.Hunion hl -> N.Hunion (List.map hl ~f:(hint ~allow_retonly env))
401 | Aast.Hintersection hl ->
402 N.Hintersection (List.map hl ~f:(hint ~allow_retonly env))
403 | Aast.Htuple hl ->
404 N.Htuple (List.map hl ~f:(hint ~allow_retonly ~tp_depth:(tp_depth + 1) env))
405 | Aast.Hoption h ->
406 (* void/noreturn are permitted for Typing.option_return_only_typehint *)
407 N.Hoption (hint ~allow_retonly env h)
408 | Aast.Hlike h ->
409 if not (allow_like || like_type_hints_enabled) then
410 Errors.experimental_feature p "like-types";
411 N.Hlike (hint ~allow_retonly env h)
412 | Aast.Hsoft h ->
413 let h = hint ~allow_retonly env h in
414 if TypecheckerOptions.interpret_soft_types_as_like_types tcopt then
415 N.Hlike h
416 else
417 snd h
418 | Aast.Hfun
419 Aast.
421 hf_param_tys = hl;
422 hf_param_info = il;
423 hf_variadic_ty = variadic_hint;
424 hf_ctxs = ctxs;
425 hf_return_ty = h;
426 hf_is_readonly_return = readonly_ret;
427 } ->
428 hfun env hl il variadic_hint ctxs h readonly_ret
429 | Aast.Happly (((p, _x) as id), hl) ->
430 let hint_id =
431 hint_id ~forbid_this ~allow_retonly ~allow_wildcard ~tp_depth env id hl
433 (match hint_id with
434 | N.Hprim _
435 | N.Hmixed
436 | N.Hnonnull
437 | N.Hdynamic
438 | N.Hnothing ->
439 if not (List.is_empty hl) then Errors.unexpected_type_arguments p
440 | _ -> ());
441 hint_id
442 | Aast.Haccess ((pos, root_id), ids) ->
443 let root_ty =
444 match root_id with
445 | Aast.Happly ((pos, x), _) when String.equal x SN.Classes.cSelf ->
446 begin
447 match (fst env).current_cls with
448 | None ->
449 Errors.self_outside_class pos;
450 N.Herr
451 | Some (cid, _, _) -> N.Happly (cid, [])
453 | Aast.Happly ((pos, x), _)
454 when String.equal x SN.Classes.cStatic
455 || String.equal x SN.Classes.cParent ->
456 Errors.invalid_type_access_root (pos, x);
457 N.Herr
458 | Aast.Happly (root, _) ->
459 let h =
460 hint_id
461 ~forbid_this
462 ~allow_retonly
463 ~allow_wildcard:false
464 ~tp_depth
466 root
469 begin
470 match h with
471 | N.Hthis
472 | N.Happly _ ->
474 | N.Habstr _ when in_where_clause -> h
475 | _ ->
476 Errors.invalid_type_access_root root;
477 N.Herr
479 | Aast.Hvar n -> N.Hvar n
480 | _ ->
481 Errors.internal_error
483 "Malformed hint: expected Haccess (Happly ...) from ast_to_nast";
484 N.Herr
486 N.Haccess ((pos, root_ty), ids)
487 | Aast.Hshape { Aast.nsi_allows_unknown_fields; nsi_field_map } ->
488 let nsi_field_map =
489 List.map
490 ~f:(fun { Aast.sfi_optional; sfi_hint; sfi_name } ->
491 let new_key = convert_shape_name env sfi_name in
492 let new_field =
494 N.sfi_optional;
495 sfi_hint =
496 hint ~allow_retonly ~tp_depth:(tp_depth + 1) env sfi_hint;
497 sfi_name = new_key;
500 new_field)
501 nsi_field_map
503 N.Hshape { N.nsi_allows_unknown_fields; nsi_field_map }
504 | Aast.Hmixed -> N.Hmixed
505 | Aast.Hfun_context n -> N.Hfun_context n
506 | Aast.Hvar n -> N.Hvar n
507 | Aast.Herr
508 | Aast.Hany
509 | Aast.Hnonnull
510 | Aast.Habstr _
511 | Aast.Hdarray _
512 | Aast.Hvarray _
513 | Aast.Hvarray_or_darray _
514 | Aast.Hvec_or_dict _
515 | Aast.Hprim _
516 | Aast.Hthis
517 | Aast.Hdynamic
518 | Aast.Hnothing ->
519 Errors.internal_error Pos.none "Unexpected hint not present on legacy AST";
520 N.Herr
522 and hint_id
523 ~forbid_this ~allow_retonly ~allow_wildcard ~tp_depth env ((p, x) as id) hl
525 let params = (fst env).type_params in
526 (* some common Xhp screw ups *)
527 if String.equal x "Xhp" || String.equal x ":Xhp" || String.equal x "XHP" then
528 Errors.disallowed_xhp_type p x;
529 match try_castable_hint ~forbid_this ~allow_wildcard ~tp_depth env p x hl with
530 | Some h -> h
531 | None ->
532 begin
533 match x with
534 | x when String.equal x SN.Typehints.wildcard ->
535 if allow_wildcard && tp_depth >= 1 (* prevents 3 as _ *) then
536 if not (List.is_empty hl) then (
537 Errors.typaram_applied_to_type p x;
538 N.Herr
539 ) else
540 N.Happly (id, [])
541 else (
542 Errors.wildcard_hint_disallowed p;
543 N.Herr
546 when String.equal x ("\\" ^ SN.Typehints.void)
547 || String.equal x ("\\" ^ SN.Typehints.null)
548 || String.equal x ("\\" ^ SN.Typehints.noreturn)
549 || String.equal x ("\\" ^ SN.Typehints.int)
550 || String.equal x ("\\" ^ SN.Typehints.bool)
551 || String.equal x ("\\" ^ SN.Typehints.float)
552 || String.equal x ("\\" ^ SN.Typehints.num)
553 || String.equal x ("\\" ^ SN.Typehints.string)
554 || String.equal x ("\\" ^ SN.Typehints.resource)
555 || String.equal x ("\\" ^ SN.Typehints.mixed)
556 || String.equal x ("\\" ^ SN.Typehints.nonnull)
557 || String.equal x ("\\" ^ SN.Typehints.arraykey) ->
558 Errors.primitive_toplevel p;
559 N.Herr
560 | x when String.equal x ("\\" ^ SN.Typehints.nothing) ->
561 Errors.primitive_toplevel p;
562 N.Herr
563 | x when String.equal x SN.Typehints.void && allow_retonly ->
564 N.Hprim N.Tvoid
565 | x when String.equal x SN.Typehints.void ->
566 Errors.return_only_typehint p `void;
567 N.Herr
568 | x when String.equal x SN.Typehints.noreturn && allow_retonly ->
569 N.Hprim N.Tnoreturn
570 | x when String.equal x SN.Typehints.noreturn ->
571 Errors.return_only_typehint p `noreturn;
572 N.Herr
573 | x when String.equal x SN.Typehints.null -> N.Hprim N.Tnull
574 | x when String.equal x SN.Typehints.num -> N.Hprim N.Tnum
575 | x when String.equal x SN.Typehints.resource -> N.Hprim N.Tresource
576 | x when String.equal x SN.Typehints.arraykey -> N.Hprim N.Tarraykey
577 | x when String.equal x SN.Typehints.mixed -> N.Hmixed
578 | x when String.equal x SN.Typehints.nonnull -> N.Hnonnull
579 | x when String.equal x SN.Typehints.dynamic -> N.Hdynamic
580 | x when String.equal x SN.Typehints.nothing -> N.Hnothing
581 | x when String.equal x SN.Typehints.this && not forbid_this ->
582 if not (phys_equal hl []) then Errors.this_no_argument p;
583 N.Hthis
584 | x when String.equal x SN.Typehints.this ->
585 Errors.this_type_forbidden p;
586 N.Herr
587 (* TODO: Duplicate of a Typing[4101] error if namespaced correctly
588 * T56198838 *)
590 when (String.equal x SN.Classes.cClassname || String.equal x "classname")
591 && List.length hl <> 1 ->
592 Errors.classname_param p;
593 N.Hprim N.Tstring
594 | _ when String.(lowercase x = SN.Typehints.this) ->
595 Errors.lowercase_this p x;
596 N.Herr
597 | _ when SSet.mem x params ->
598 let tcopt = Provider_context.get_tcopt (fst env).ctx in
599 let hl =
601 (not (TypecheckerOptions.higher_kinded_types tcopt))
602 && not (List.is_empty hl)
603 then (
604 Errors.typaram_applied_to_type p x;
606 ) else
610 N.Habstr
611 ( x,
612 hintl
613 ~allow_wildcard
614 ~forbid_this
615 ~allow_retonly:true
616 ~tp_depth:(tp_depth + 1)
618 hl )
619 | _ ->
620 let () = check_name id in
621 N.Happly
622 ( id,
623 hintl
624 ~allow_wildcard
625 ~forbid_this
626 ~allow_retonly:true
627 ~tp_depth:(tp_depth + 1)
629 hl )
632 (* Hints that are valid both as casts and type annotations. Neither
633 * casts nor annotations are a strict subset of the other: For
634 * instance, 'object' is not a valid annotation. Thus callers will
635 * have to handle the remaining cases. *)
636 and try_castable_hint
637 ?(forbid_this = false) ?(allow_wildcard = false) ~tp_depth env p x hl =
638 let hint =
639 hint
640 ~forbid_this
641 ~tp_depth:(tp_depth + 1)
642 ~allow_wildcard
643 ~allow_retonly:false
645 let unif env =
646 TypecheckerOptions.array_unification
647 (Provider_context.get_tcopt (fst env).ctx)
649 let canon = String.lowercase x in
650 let opt_hint =
651 match canon with
652 | nm when String.equal nm SN.Typehints.int -> Some (N.Hprim N.Tint)
653 | nm when String.equal nm SN.Typehints.bool -> Some (N.Hprim N.Tbool)
654 | nm when String.equal nm SN.Typehints.float -> Some (N.Hprim N.Tfloat)
655 | nm when String.equal nm SN.Typehints.string -> Some (N.Hprim N.Tstring)
656 | nm when String.equal nm SN.Typehints.darray ->
657 Some
658 (match hl with
659 | [] ->
660 if Partial.should_check_error (fst env).in_mode 2071 then
661 Errors.too_few_type_arguments p;
662 if unif env then
663 N.Happly ((p, SN.Collections.cDict), [(p, N.Hany); (p, N.Hany)])
664 else
665 N.Hdarray ((p, N.Hany), (p, N.Hany))
666 | [_] ->
667 Errors.too_few_type_arguments p;
668 N.Hany
669 | [key_; val_] ->
670 if unif env then
671 N.Happly ((p, SN.Collections.cDict), [hint env key_; hint env val_])
672 else
673 N.Hdarray (hint env key_, hint env val_)
674 | _ ->
675 Errors.too_many_type_arguments p;
676 N.Hany)
677 | nm when String.equal nm SN.Typehints.varray ->
678 Some
679 (match hl with
680 | [] ->
681 if Partial.should_check_error (fst env).in_mode 2071 then
682 Errors.too_few_type_arguments p;
683 if unif env then
684 N.Happly ((p, SN.Collections.cVec), [(p, N.Hany)])
685 else
686 N.Hvarray (p, N.Hany)
687 | [val_] ->
688 if unif env then
689 N.Happly ((p, SN.Collections.cVec), [hint env val_])
690 else
691 N.Hvarray (hint env val_)
692 | _ ->
693 Errors.too_many_type_arguments p;
694 N.Hany)
695 | nm when String.equal nm SN.Typehints.varray_or_darray ->
696 Some
697 (match hl with
698 | [] ->
699 if Partial.should_check_error (fst env).in_mode 2071 then
700 Errors.too_few_type_arguments p;
702 if unif env then
703 N.Hvec_or_dict (None, (p, N.Hany))
704 else
705 (* Warning: These Hanys are here because they produce subtle
706 errors because of interaction with tco_experimental_isarray
707 if you change them to Herr *)
708 N.Hvarray_or_darray (None, (p, N.Hany))
709 | [val_] ->
710 if unif env then
711 N.Hvec_or_dict (None, hint env val_)
712 else
713 N.Hvarray_or_darray (None, hint env val_)
714 | [key; val_] ->
715 if unif env then
716 N.Hvec_or_dict (Some (hint env key), hint env val_)
717 else
718 N.Hvarray_or_darray (Some (hint env key), hint env val_)
719 | _ ->
720 Errors.too_many_type_arguments p;
721 N.Hany)
722 | nm when String.equal nm SN.Typehints.vec_or_dict ->
723 Some
724 (match hl with
725 | [] ->
726 if Partial.should_check_error (fst env).in_mode 2071 then
727 Errors.too_few_type_arguments p;
729 N.Hvec_or_dict (None, (p, N.Hany))
730 | [val_] -> N.Hvec_or_dict (None, hint env val_)
731 | [key; val_] -> N.Hvec_or_dict (Some (hint env key), hint env val_)
732 | _ ->
733 Errors.too_many_type_arguments p;
734 N.Hany)
735 | _ -> None
737 let () =
738 match opt_hint with
739 | Some _ when not (String.equal canon x) ->
740 Errors.primitive_invalid_alias p x canon
741 | _ -> ()
743 opt_hint
745 and hintl ~forbid_this ~allow_retonly ~allow_wildcard ~tp_depth env l =
746 List.map ~f:(hint ~forbid_this ~allow_retonly ~allow_wildcard ~tp_depth env) l
748 let constraint_ ?(forbid_this = false) env (ck, h) =
749 (ck, hint ~forbid_this env h)
751 let targ env (p, t) =
752 ( p,
753 hint
754 ~allow_wildcard:true
755 ~forbid_this:false
756 ~allow_retonly:true
757 ~tp_depth:1
761 let targl env _ tal = List.map tal ~f:(targ env)
763 (**************************************************************************)
764 (* All the methods and static methods of an interface are "implicitly"
765 * declared as abstract
767 (**************************************************************************)
769 let add_abstract m = { m with N.m_abstract = true }
771 let add_abstractl methods = List.map methods add_abstract
773 let interface c constructor methods smethods =
774 if not (Ast_defs.is_c_interface c.Aast.c_kind) then
775 (constructor, methods, smethods)
776 else
777 let constructor = Option.map constructor add_abstract in
778 let methods = add_abstractl methods in
779 let smethods = add_abstractl smethods in
780 (constructor, methods, smethods)
782 let ensure_name_not_dynamic env e =
783 match e with
784 | (_, (Aast.Id _ | Aast.Lvar _)) -> ()
785 | (p, _) ->
786 if Partial.should_check_error (fst env).in_mode 2078 then
787 Errors.dynamic_class_name_in_strict_mode p
789 (* Naming of a class *)
790 let rec class_ ctx c =
791 let env = Env.make_class_env ctx c in
792 let c =
793 elaborate_namespaces#on_class_
794 (Naming_elaborate_namespaces_endo.make_env (fst env).namespace)
797 let where_constraints =
798 type_where_constraints env c.Aast.c_where_constraints
800 let name = c.Aast.c_name in
801 let (constructor, smethods, methods) = Aast.split_methods c in
802 let smethods = List.map ~f:(method_ (fst env)) smethods in
803 let (sprops, props) = Aast.split_vars c in
804 let sprops = List.map ~f:(class_prop_static env) sprops in
805 let attrs = user_attributes env c.Aast.c_user_attributes in
806 let const = Naming_attributes.find SN.UserAttributes.uaConst attrs in
807 let props = List.map ~f:(class_prop_non_static ~const env) props in
808 let xhp_attrs = List.map ~f:(xhp_attribute_decl env) c.Aast.c_xhp_attrs in
809 (* These would be out of order with the old attributes, but that shouldn't matter? *)
810 let props = props @ xhp_attrs in
811 let (enum_bound, enum, in_enum_class) =
812 match c.Aast.c_enum with
813 | Some enum -> enum_ env name enum
814 | None -> (None, None, false)
816 let parents = List.map c.Aast.c_extends (hint ~allow_retonly:false env) in
817 let parents =
818 match enum_bound with
819 (* Make enums implicitly extend the BuiltinEnum/BuiltinEnumClass classes in
820 * order to provide utility methods.
822 | Some bound ->
823 let pos = fst name in
824 let builtin =
825 if in_enum_class then
826 SN.Classes.cHH_BuiltinEnumClass
827 else
828 SN.Classes.cHH_BuiltinEnum
830 let parent = (pos, N.Happly ((pos, builtin), [bound])) in
831 parent :: parents
832 | None -> parents
834 let methods = List.map ~f:(method_ (fst env)) methods in
835 let uses = List.map ~f:(hint env) c.Aast.c_uses in
836 let xhp_attr_uses = List.map ~f:(hint env) c.Aast.c_xhp_attr_uses in
837 let (c_req_extends, c_req_implements) = Aast.split_reqs c in
839 (not (List.is_empty c_req_implements))
840 && not (Ast_defs.is_c_trait c.Aast.c_kind)
841 then
842 Errors.invalid_req_implements (fst (List.hd_exn c_req_implements));
843 let req_implements = List.map ~f:(hint env) c_req_implements in
844 let req_implements = List.map ~f:(fun h -> (h, false)) req_implements in
846 (not (List.is_empty c_req_extends))
847 && (not (Ast_defs.is_c_trait c.Aast.c_kind))
848 && not (Ast_defs.is_c_interface c.Aast.c_kind)
849 then
850 Errors.invalid_req_extends (fst (List.hd_exn c_req_extends));
851 let req_extends = List.map ~f:(hint env) c_req_extends in
852 let req_extends = List.map ~f:(fun h -> (h, true)) req_extends in
853 (* Setting a class type parameters constraint to the 'this' type is weird
854 * so lets forbid it for now.
856 let tparam_l = type_paraml ~forbid_this:true env c.Aast.c_tparams in
857 let consts = List.map ~f:(class_const env ~in_enum_class) c.Aast.c_consts in
858 let typeconsts = List.map ~f:(typeconst env) c.Aast.c_typeconsts in
859 let implements =
860 List.map ~f:(hint ~allow_retonly:false env) c.Aast.c_implements
862 let constructor = Option.map constructor (method_ (fst env)) in
863 let (constructor, methods, smethods) =
864 interface c constructor methods smethods
866 let file_attributes =
867 file_attributes ctx c.Aast.c_mode c.Aast.c_file_attributes
869 let c_tparams = tparam_l in
870 let methods =
871 match constructor with
872 | None -> smethods @ methods
873 | Some c -> (c :: smethods) @ methods
876 N.c_annotation = ();
877 N.c_span = c.Aast.c_span;
878 N.c_mode = c.Aast.c_mode;
879 N.c_final = c.Aast.c_final;
880 N.c_is_xhp = c.Aast.c_is_xhp;
881 N.c_has_xhp_keyword = c.Aast.c_has_xhp_keyword;
882 N.c_kind = c.Aast.c_kind;
883 N.c_name = name;
884 N.c_tparams;
885 N.c_extends = parents;
886 N.c_uses = uses;
887 (* c_use_as_alias and c_insteadof_alias are PHP features not supported
888 * in Hack but are required since we have runtime support for it
890 N.c_use_as_alias = [];
891 N.c_insteadof_alias = [];
892 N.c_xhp_attr_uses = xhp_attr_uses;
893 N.c_xhp_category = c.Aast.c_xhp_category;
894 N.c_reqs = req_extends @ req_implements;
895 N.c_implements = implements;
896 N.c_implements_dynamic = c.Aast.c_implements_dynamic;
897 N.c_where_constraints = where_constraints;
898 N.c_consts = consts;
899 N.c_typeconsts = typeconsts;
900 N.c_vars = sprops @ props;
901 N.c_methods = methods;
902 N.c_user_attributes = attrs;
903 N.c_file_attributes = file_attributes;
904 N.c_namespace = c.Aast.c_namespace;
905 N.c_enum = enum;
906 N.c_doc_comment = c.Aast.c_doc_comment;
907 N.c_xhp_children = c.Aast.c_xhp_children;
908 (* Naming and typechecking shouldn't use these fields *)
909 N.c_attributes = [];
910 N.c_xhp_attrs = [];
911 N.c_emit_id = c.Aast.c_emit_id;
914 and user_attributes env attrl =
915 let seen = Caml.Hashtbl.create 0 in
916 let validate_seen ua_name =
917 let (pos, name) = ua_name in
918 let existing_attr_pos =
919 (try Some (Caml.Hashtbl.find seen name) with Caml.Not_found -> None)
921 match existing_attr_pos with
922 | Some p ->
923 Errors.duplicate_user_attribute ua_name p;
924 false
925 | None ->
926 Caml.Hashtbl.add seen name pos;
927 true
929 let on_attr acc { Aast.ua_name; ua_params } =
930 let () = check_name ua_name in
931 if not (validate_seen ua_name) then
933 else
934 let attr =
935 { N.ua_name; N.ua_params = List.map ~f:(expr env) ua_params }
937 attr :: acc
939 List.fold_left ~init:[] ~f:on_attr attrl
941 and file_attributes ctx mode fal = List.map ~f:(file_attribute ctx mode) fal
943 and file_attribute ctx mode fa =
944 let env = Env.make_file_attributes_env ctx mode fa.Aast.fa_namespace in
945 let ua = user_attributes env fa.Aast.fa_user_attributes in
946 N.{ fa_user_attributes = ua; fa_namespace = fa.Aast.fa_namespace }
948 (* h cv is_required maybe_enum *)
949 and xhp_attribute_decl env (h, cv, tag, maybe_enum) =
950 let (p, id) = cv.Aast.cv_id in
951 let default = cv.Aast.cv_expr in
952 let is_required = Option.is_some tag in
953 if is_required && Option.is_some default then
954 Errors.xhp_required_with_default p id;
955 let hint_ =
956 match maybe_enum with
957 | Some (pos, items) ->
958 let is_int item =
959 match item with
960 | (_, Aast.Int _) -> true
961 | _ -> false
963 let contains_int = List.exists ~f:is_int items in
964 let is_string item =
965 match item with
966 | (_, Aast.String _)
967 | (_, Aast.String2 _) ->
968 true
969 | _ -> false
971 let contains_str = List.exists ~f:is_string items in
972 if contains_int && not contains_str then
973 Some (pos, Aast.Happly ((pos, "int"), []))
974 else if (not contains_int) && contains_str then
975 Some (pos, Aast.Happly ((pos, "string"), []))
976 else
977 Some (pos, Aast.Happly ((pos, "mixed"), []))
978 | _ -> Aast.hint_of_type_hint h
980 let hint_ =
981 match hint_ with
982 | Some (p, Aast.Hoption _) ->
983 if is_required then Errors.xhp_optional_required_attr p id;
984 hint_
985 | Some (_, Aast.Happly ((_, "mixed"), [])) -> hint_
986 | Some (p, h) ->
987 let has_default =
988 match default with
989 | None
990 | Some (_, Aast.Null) ->
991 false
992 | _ -> true
994 if is_required || has_default then
995 hint_
996 else
997 Some (p, Aast.Hoption (p, h))
998 | None -> None
1000 let hint_ = ((), hint_) in
1001 let hint_ = Aast.type_hint_option_map hint_ ~f:(hint env) in
1002 let (expr, _) = class_prop_expr_is_xhp env cv in
1003 let xhp_attr_info = Some { N.xai_tag = tag } in
1005 N.cv_final = cv.Aast.cv_final;
1006 N.cv_xhp_attr = xhp_attr_info;
1007 N.cv_readonly = cv.Aast.cv_readonly;
1008 N.cv_abstract = cv.Aast.cv_abstract;
1009 N.cv_visibility = cv.Aast.cv_visibility;
1010 N.cv_type = hint_;
1011 N.cv_id = cv.Aast.cv_id;
1012 N.cv_expr = expr;
1013 N.cv_user_attributes = [];
1014 N.cv_is_promoted_variadic = cv.Aast.cv_is_promoted_variadic;
1015 N.cv_doc_comment = cv.Aast.cv_doc_comment (* Can make None to save space *);
1016 N.cv_is_static = cv.Aast.cv_is_static;
1017 N.cv_span = cv.Aast.cv_span;
1020 and enum_ env enum_name e =
1021 let open Aast in
1022 let pos = fst enum_name in
1023 let enum_hint = (pos, Happly (enum_name, [])) in
1024 let is_enum_class = e.e_enum_class in
1025 let old_base = e.e_base in
1026 let new_base = hint env old_base in
1027 let bound =
1028 if is_enum_class then
1029 (* Turn the base type of the enum class into MemberOf<E, base> *)
1030 let elt = (pos, SN.Classes.cMemberOf) in
1031 let h = (pos, Happly (elt, [enum_hint; old_base])) in
1032 hint env h
1033 else
1034 enum_hint
1036 let enum =
1038 N.e_base = new_base;
1039 N.e_constraint = Option.map e.e_constraint (hint env);
1040 N.e_includes = List.map ~f:(hint env) e.e_includes;
1041 N.e_enum_class = is_enum_class;
1044 (Some bound, Some enum, is_enum_class)
1046 and type_paraml ?(forbid_this = false) env tparams =
1047 List.map tparams ~f:(type_param ~forbid_this env)
1050 We need to be careful regarding the scoping of type variables:
1051 Type parameters are always in scope simultaneously: Given
1052 class C<T1 ... , T2 ... , Tn ...>,
1053 all type parameters are in scope in the constraints of all other ones (and the where constraints,
1054 in case of functions).
1055 For consitency, the same holds for nested type parameters (i.e., type parameters of type
1056 parameters). Given
1057 class Foo<T<T1 ... , ...., Tn ... > ... >
1058 every Ti is in scope of the constraints of all other Tj, and in the constraints on T itself.
1060 and type_param ~forbid_this (genv, lenv) t =
1061 begin
1063 TypecheckerOptions.experimental_feature_enabled
1064 (Provider_context.get_tcopt genv.ctx)
1065 TypecheckerOptions.experimental_type_param_shadowing
1066 then
1067 (* Treat type params as inline class declarations that don't go into the naming heap *)
1068 let (pos, name) =
1069 NS.elaborate_id genv.namespace NS.ElaborateClass t.Aast.tp_name
1071 match Naming_provider.get_type_pos genv.ctx name with
1072 | Some def_pos ->
1073 let (def_pos, _) = GEnv.get_full_pos genv.ctx (def_pos, name) in
1074 Errors.error_name_already_bound name name pos def_pos
1075 | None ->
1076 (match GEnv.type_canon_name genv.ctx name with
1077 | Some canonical ->
1078 let def_pos =
1079 Option.value ~default:Pos.none (GEnv.type_pos genv.ctx canonical)
1081 Errors.error_name_already_bound name canonical pos def_pos
1082 | None -> ())
1083 end;
1084 let hk_types_enabled =
1085 TypecheckerOptions.higher_kinded_types (Provider_context.get_tcopt genv.ctx)
1087 ( if (not hk_types_enabled) && (not @@ List.is_empty t.Aast.tp_parameters) then
1088 let (pos, name) = t.Aast.tp_name in
1089 Errors.tparam_with_tparam pos name );
1091 (* Bring all type parameters into scope at once before traversing nested tparams,
1092 as per the note above *)
1093 let env = (extend_tparams genv t.Aast.tp_parameters, lenv) in
1094 let tp_parameters =
1095 if hk_types_enabled then
1096 List.map t.Aast.tp_parameters (type_param ~forbid_this env)
1097 else
1100 (* Use the env with all nested tparams still in scope *)
1101 let tp_constraints =
1102 List.map t.Aast.tp_constraints (constraint_ ~forbid_this env)
1105 N.tp_variance = t.Aast.tp_variance;
1106 tp_name = t.Aast.tp_name;
1107 tp_parameters;
1108 tp_constraints;
1109 tp_reified = t.Aast.tp_reified;
1110 tp_user_attributes = user_attributes env t.Aast.tp_user_attributes;
1113 and type_where_constraints env locl_cstrl =
1114 List.map
1115 ~f:(fun (h1, ck, h2) ->
1116 let ty1 = hint ~in_where_clause:true env h1 in
1117 let ty2 = hint ~in_where_clause:true env h2 in
1118 (ty1, ck, ty2))
1119 locl_cstrl
1121 and class_prop_expr_is_xhp env cv =
1122 let expr = Option.map cv.Aast.cv_expr (expr env) in
1123 let expr =
1125 FileInfo.equal_mode (fst env).in_mode FileInfo.Mhhi && Option.is_none expr
1126 then
1127 Some (fst cv.Aast.cv_id, N.Any)
1128 else
1129 expr
1131 let is_xhp =
1132 try String.(sub (snd cv.Aast.cv_id) 0 1 = ":")
1133 with Invalid_argument _ -> false
1135 (expr, is_xhp)
1137 and make_xhp_attr = function
1138 | true -> Some { N.xai_tag = None }
1139 | false -> None
1141 and class_prop_static env cv =
1142 let attrs = user_attributes env cv.Aast.cv_user_attributes in
1143 let lsb = Naming_attributes.mem SN.UserAttributes.uaLSB attrs in
1144 let forbid_this = not lsb in
1145 let h =
1146 Aast.type_hint_option_map ~f:(hint ~forbid_this env) cv.Aast.cv_type
1148 let (expr, is_xhp) = class_prop_expr_is_xhp env cv in
1150 N.cv_final = cv.Aast.cv_final;
1151 N.cv_xhp_attr = make_xhp_attr is_xhp;
1152 N.cv_abstract = cv.Aast.cv_abstract;
1153 N.cv_readonly = cv.Aast.cv_readonly;
1154 N.cv_visibility = cv.Aast.cv_visibility;
1155 N.cv_type = h;
1156 N.cv_id = cv.Aast.cv_id;
1157 N.cv_expr = expr;
1158 N.cv_user_attributes = attrs;
1159 N.cv_is_promoted_variadic = cv.Aast.cv_is_promoted_variadic;
1160 N.cv_doc_comment = cv.Aast.cv_doc_comment (* Can make None to save space *);
1161 N.cv_is_static = cv.Aast.cv_is_static;
1162 N.cv_span = cv.Aast.cv_span;
1165 and class_prop_non_static env ?(const = None) cv =
1166 let h = Aast.type_hint_option_map ~f:(hint env) cv.Aast.cv_type in
1167 let attrs = user_attributes env cv.Aast.cv_user_attributes in
1168 (* if class is __Const, make all member fields __Const *)
1169 let attrs =
1170 match const with
1171 | Some c ->
1172 if not (Naming_attributes.mem SN.UserAttributes.uaConst attrs) then
1173 c :: attrs
1174 else
1175 attrs
1176 | None -> attrs
1178 let (expr, is_xhp) = class_prop_expr_is_xhp env cv in
1180 N.cv_final = cv.Aast.cv_final;
1181 N.cv_xhp_attr = make_xhp_attr is_xhp;
1182 N.cv_visibility = cv.Aast.cv_visibility;
1183 N.cv_readonly = cv.Aast.cv_readonly;
1184 N.cv_type = h;
1185 N.cv_abstract = cv.Aast.cv_abstract;
1186 N.cv_id = cv.Aast.cv_id;
1187 N.cv_expr = expr;
1188 N.cv_user_attributes = attrs;
1189 N.cv_is_promoted_variadic = cv.Aast.cv_is_promoted_variadic;
1190 N.cv_doc_comment = cv.Aast.cv_doc_comment (* Can make None to save space *);
1191 N.cv_is_static = cv.Aast.cv_is_static;
1192 N.cv_span = cv.Aast.cv_span;
1195 and check_constant_expression env ~in_enum_class (pos, e) =
1196 if not in_enum_class then
1197 check_constant_expr env (pos, e)
1198 else
1199 true
1201 and check_constant_expr env (pos, e) =
1202 match e with
1203 | Aast.Id _
1204 | Aast.Null
1205 | Aast.True
1206 | Aast.False
1207 | Aast.Int _
1208 | Aast.Float _
1209 | Aast.String _ ->
1210 true
1211 | Aast.Class_const ((_, Aast.CIexpr (_, cls)), _)
1212 when match cls with
1213 | Aast.Id (_, "static") -> false
1214 | _ -> true ->
1215 true
1216 | Aast.Unop
1217 ((Ast_defs.Uplus | Ast_defs.Uminus | Ast_defs.Utild | Ast_defs.Unot), e)
1219 check_constant_expr env e
1220 | Aast.Binop (op, e1, e2) ->
1221 (* Only assignment is invalid *)
1222 begin
1223 match op with
1224 | Ast_defs.Eq _ ->
1225 Errors.illegal_constant pos;
1226 false
1227 | _ -> check_constant_expr env e1 && check_constant_expr env e2
1229 | Aast.Eif (e1, e2, e3) ->
1230 check_constant_expr env e1
1231 && Option.for_all e2 (check_constant_expr env)
1232 && check_constant_expr env e3
1233 | Aast.Darray (_, l) ->
1234 List.for_all l ~f:(fun (e1, e2) ->
1235 check_constant_expr env e1 && check_constant_expr env e2)
1236 | Aast.Varray (_, l) -> List.for_all l ~f:(check_constant_expr env)
1237 | Aast.Shape fdl ->
1238 (* Only check the values because shape field names are always legal *)
1239 List.for_all fdl ~f:(fun (_, e) -> check_constant_expr env e)
1240 | Aast.Call ((_, Aast.Id (_, cn)), _, el, unpacked_element)
1241 when String.equal cn SN.AutoimportedFunctions.fun_
1242 || String.equal cn SN.AutoimportedFunctions.class_meth
1243 || String.equal cn SN.StdlibFunctions.array_mark_legacy
1244 (* Tuples are not really function calls, they are just parsed that way*)
1245 || String.equal cn SN.SpecialFunctions.tuple ->
1246 arg_unpack_unexpected unpacked_element;
1247 List.for_all el ~f:(check_constant_expr env)
1248 | Aast.FunctionPointer ((Aast.FP_id _ | Aast.FP_class_const _), _) -> true
1249 | Aast.Collection (id, _, l) ->
1250 let (p, cn) = NS.elaborate_id (fst env).namespace NS.ElaborateClass id in
1251 (* Only vec/keyset/dict are allowed because they are value types *)
1253 String.equal cn SN.Collections.cVec
1254 || String.equal cn SN.Collections.cKeyset
1255 || String.equal cn SN.Collections.cDict
1256 then
1257 List.for_all l ~f:(check_afield_constant_expr env)
1258 else (
1259 Errors.illegal_constant p;
1260 false
1262 | Aast.As (e, (_, Aast.Hlike _), _) -> check_constant_expr env e
1263 | Aast.As (e, (_, Aast.Happly (id, [_])), _) ->
1264 let (p, cn) = NS.elaborate_id (fst env).namespace NS.ElaborateClass id in
1265 if String.equal cn SN.FB.cIncorrectType then
1266 check_constant_expr env e
1267 else (
1268 Errors.illegal_constant p;
1269 false
1271 | _ ->
1272 Errors.illegal_constant pos;
1273 false
1275 and check_afield_constant_expr env afield =
1276 match afield with
1277 | Aast.AFvalue e -> check_constant_expr env e
1278 | Aast.AFkvalue (e1, e2) ->
1279 check_constant_expr env e1 && check_constant_expr env e2
1281 and constant_expr env ~in_enum_class e =
1282 let valid_constant_expression =
1283 check_constant_expression env ~in_enum_class e
1285 if valid_constant_expression then
1286 expr env e
1287 else
1288 (fst e, N.Any)
1290 and class_const env ~in_enum_class cc =
1291 let h = Option.map cc.Aast.cc_type (hint env) in
1292 let e = Option.map cc.Aast.cc_expr (constant_expr env ~in_enum_class) in
1294 N.cc_type = h;
1295 N.cc_id = cc.Aast.cc_id;
1296 N.cc_expr = e;
1297 N.cc_doc_comment = cc.Aast.cc_doc_comment;
1300 and typeconst env t =
1301 let abstract =
1302 match t.Aast.c_tconst_abstract with
1303 | Aast.TCAbstract (Some default) ->
1304 Aast.TCAbstract (Some (hint env default))
1305 | _ -> t.Aast.c_tconst_abstract
1307 let as_constraint = Option.map t.Aast.c_tconst_as_constraint (hint env) in
1308 let type_ = Option.map t.Aast.c_tconst_type (hint env) in
1309 let attrs = user_attributes env t.Aast.c_tconst_user_attributes in
1312 c_tconst_abstract = abstract;
1313 c_tconst_name = t.Aast.c_tconst_name;
1314 c_tconst_as_constraint = as_constraint;
1315 c_tconst_type = type_;
1316 c_tconst_user_attributes = attrs;
1317 c_tconst_span = t.Aast.c_tconst_span;
1318 c_tconst_doc_comment = t.Aast.c_tconst_doc_comment;
1319 c_tconst_is_ctx = t.Aast.c_tconst_is_ctx;
1322 and method_ genv m =
1323 let genv = extend_tparams genv m.Aast.m_tparams in
1324 let env = (genv, Env.empty_local None) in
1325 (* Cannot use 'this' if it is a public instance method *)
1326 let (variadicity, paraml) = fun_paraml env m.Aast.m_params in
1327 let tparam_l = type_paraml env m.Aast.m_tparams in
1328 let where_constraints =
1329 type_where_constraints env m.Aast.m_where_constraints
1331 let ret =
1332 Aast.type_hint_option_map ~f:(hint ~allow_retonly:true env) m.Aast.m_ret
1334 let body =
1335 match genv.in_mode with
1336 | FileInfo.Mhhi ->
1337 { N.fb_ast = []; fb_annotation = Nast.NamedWithUnsafeBlocks }
1338 | FileInfo.Mstrict
1339 | FileInfo.Mpartial ->
1340 if Nast.is_body_named m.Aast.m_body then
1341 let env = List.fold_left ~f:Env.add_param m.N.m_params ~init:env in
1342 let env =
1343 match m.N.m_variadic with
1344 | N.FVellipsis _
1345 | N.FVnonVariadic ->
1347 | N.FVvariadicArg param -> Env.add_param env param
1349 let fub_ast = block env m.N.m_body.N.fb_ast in
1350 let annotation = Nast.Named in
1351 { N.fb_ast = fub_ast; fb_annotation = annotation }
1352 else
1353 failwith "ast_to_nast error unnamedbody in method_"
1355 let attrs = user_attributes env m.Aast.m_user_attributes in
1356 let m_ctxs = Option.map ~f:(contexts env) m.Aast.m_ctxs in
1357 let m_unsafe_ctxs = Option.map ~f:(contexts env) m.Aast.m_unsafe_ctxs in
1359 N.m_annotation = ();
1360 N.m_span = m.Aast.m_span;
1361 N.m_final = m.Aast.m_final;
1362 N.m_visibility = m.Aast.m_visibility;
1363 N.m_abstract = m.Aast.m_abstract;
1364 N.m_readonly_this = m.Aast.m_readonly_this;
1365 N.m_static = m.Aast.m_static;
1366 N.m_name = m.Aast.m_name;
1367 N.m_tparams = tparam_l;
1368 N.m_where_constraints = where_constraints;
1369 N.m_params = paraml;
1370 N.m_ctxs;
1371 N.m_unsafe_ctxs;
1372 N.m_body = body;
1373 N.m_fun_kind = m.Aast.m_fun_kind;
1374 N.m_readonly_ret = m.Aast.m_readonly_ret;
1375 N.m_ret = ret;
1376 N.m_variadic = variadicity;
1377 N.m_user_attributes = attrs;
1378 N.m_external = m.Aast.m_external;
1379 N.m_doc_comment = m.Aast.m_doc_comment;
1382 and fun_paraml env paraml =
1383 let _ = List.fold_left ~f:check_repetition ~init:SSet.empty paraml in
1384 let (variadicity, paraml) = determine_variadicity env paraml in
1385 (variadicity, List.map ~f:(fun_param env) paraml)
1387 (* Variadic params are removed from the list *)
1388 and determine_variadicity env paraml =
1389 match paraml with
1390 | [] -> (N.FVnonVariadic, [])
1391 | [x] ->
1392 begin
1393 match (x.Aast.param_is_variadic, x.Aast.param_name) with
1394 | (false, _) -> (N.FVnonVariadic, paraml)
1395 | (true, "...") -> (N.FVellipsis x.Aast.param_pos, [])
1396 | (true, _) -> (N.FVvariadicArg (fun_param env x), [])
1398 | x :: rl ->
1399 let (variadicity, rl) = determine_variadicity env rl in
1400 (variadicity, x :: rl)
1402 and fun_param env (param : Nast.fun_param) =
1403 let p = param.Aast.param_pos in
1404 let name = param.Aast.param_name in
1405 let ident = Local_id.make_unscoped name in
1406 Env.add_lvar env (p, name) (p, ident);
1407 let tyhi =
1408 Aast.type_hint_option_map param.Aast.param_type_hint ~f:(hint env)
1410 let eopt = Option.map param.Aast.param_expr (expr env) in
1412 N.param_annotation = p;
1413 param_type_hint = tyhi;
1414 param_is_variadic = param.Aast.param_is_variadic;
1415 param_pos = p;
1416 param_name = name;
1417 param_expr = eopt;
1418 param_callconv = param.Aast.param_callconv;
1419 param_readonly = param.Aast.param_readonly;
1420 param_user_attributes = user_attributes env param.Aast.param_user_attributes;
1421 param_visibility = param.Aast.param_visibility;
1424 and extend_tparams genv paraml =
1425 let params =
1426 List.fold_right
1427 paraml
1428 ~init:genv.type_params
1429 ~f:(fun { Aast.tp_name = (_, x); _ } acc -> SSet.add x acc)
1431 { genv with type_params = params }
1433 and fun_ ctx f =
1434 let genv = Env.make_fun_decl_genv ctx f in
1435 let lenv = Env.empty_local None in
1436 let env = (genv, lenv) in
1437 let f =
1438 elaborate_namespaces#on_fun_def
1439 (Naming_elaborate_namespaces_endo.make_env (fst env).namespace)
1442 let where_constraints =
1443 type_where_constraints env f.Aast.f_where_constraints
1445 let h =
1446 Aast.type_hint_option_map ~f:(hint ~allow_retonly:true env) f.Aast.f_ret
1448 let (variadicity, paraml) = fun_paraml env f.Aast.f_params in
1449 let f_tparams = type_paraml env f.Aast.f_tparams in
1450 let f_kind = f.Aast.f_fun_kind in
1451 let body =
1452 match genv.in_mode with
1453 | FileInfo.Mhhi ->
1454 { N.fb_ast = []; fb_annotation = Nast.NamedWithUnsafeBlocks }
1455 | FileInfo.Mstrict
1456 | FileInfo.Mpartial ->
1457 if Nast.is_body_named f.Aast.f_body then
1458 let env = List.fold_left ~f:Env.add_param paraml ~init:env in
1459 let env =
1460 match variadicity with
1461 | N.FVellipsis _
1462 | N.FVnonVariadic ->
1464 | N.FVvariadicArg param -> Env.add_param env param
1466 let fb_ast = block env f.Aast.f_body.Aast.fb_ast in
1467 let annotation = Nast.Named in
1468 { N.fb_ast; fb_annotation = annotation }
1469 else
1470 failwith "ast_to_nast error unnamedbody in fun_"
1472 let f_ctxs = Option.map ~f:(contexts env) f.Aast.f_ctxs in
1473 let f_unsafe_ctxs = Option.map ~f:(contexts env) f.Aast.f_unsafe_ctxs in
1474 let file_attributes =
1475 file_attributes ctx f.Aast.f_mode f.Aast.f_file_attributes
1477 let named_fun =
1479 N.f_annotation = ();
1480 f_span = f.Aast.f_span;
1481 f_mode = f.Aast.f_mode;
1482 f_readonly_ret = f.Aast.f_readonly_ret;
1483 f_ret = h;
1484 f_name = f.Aast.f_name;
1485 f_tparams;
1486 f_where_constraints = where_constraints;
1487 f_params = paraml;
1488 (* TODO(T70095684) double-check f_ctxs *)
1489 f_ctxs;
1490 f_unsafe_ctxs;
1491 f_body = body;
1492 f_fun_kind = f_kind;
1493 f_variadic = variadicity;
1494 f_user_attributes = user_attributes env f.Aast.f_user_attributes;
1495 f_file_attributes = file_attributes;
1496 f_external = f.Aast.f_external;
1497 f_namespace = f.Aast.f_namespace;
1498 f_doc_comment = f.Aast.f_doc_comment;
1499 f_static = f.Aast.f_static;
1502 named_fun
1504 and get_using_vars es =
1505 List.concat_map es (fun (_, e) ->
1506 match e with
1507 (* Simple assignment to local of form `$lvar = e` *)
1508 | Aast.Binop (Ast_defs.Eq None, (_, Aast.Lvar (p, lid)), _) ->
1509 [(p, Local_id.get_name lid)]
1510 (* Arbitrary expression. This will be assigned to a temporary *)
1511 | _ -> [])
1513 and stmt env (pos, st) =
1514 let stmt =
1515 match st with
1516 | Aast.Block _ -> failwith "stmt block error"
1517 | Aast.Fallthrough -> N.Fallthrough
1518 | Aast.Noop -> N.Noop
1519 | Aast.Markup _ -> N.Noop
1520 | Aast.AssertEnv _ -> N.Noop
1521 | Aast.Break -> Aast.Break
1522 | Aast.Continue -> Aast.Continue
1523 | Aast.Throw e -> N.Throw (expr env e)
1524 | Aast.Return e -> N.Return (Option.map e (expr env))
1525 | Aast.Yield_break -> N.Yield_break
1526 | Aast.Awaitall (el, b) -> awaitall_stmt env el b
1527 | Aast.If (e, b1, b2) -> if_stmt env e b1 b2
1528 | Aast.Do (b, e) -> do_stmt env b e
1529 | Aast.While (e, b) -> N.While (expr env e, block env b)
1530 | Aast.Using s ->
1531 using_stmt env s.Aast.us_has_await s.Aast.us_exprs s.Aast.us_block
1532 | Aast.For (st1, e, st2, b) -> for_stmt env st1 e st2 b
1533 | Aast.Switch (e, cl) -> switch_stmt env e cl
1534 | Aast.Foreach (e, ae, b) -> foreach_stmt env e ae b
1535 | Aast.Try (b, cl, fb) -> try_stmt env b cl fb
1536 | Aast.Expr (cp, Aast.Call ((p, Aast.Id (fp, fn)), hl, el, unpacked_element))
1537 when String.equal fn SN.AutoimportedFunctions.invariant ->
1538 (* invariant is subject to a source-code transform in the HHVM
1539 * runtime: the arguments to invariant are lazily evaluated only in
1540 * the case in which the invariant condition does not hold. So:
1542 * invariant_violation(<condition>, <format>, <format_args...>)
1544 * ... is rewritten as:
1546 * if (!<condition>) {
1547 * invariant_violation(<format>, <format_args...>);
1550 begin
1551 match el with
1552 | []
1553 | [_] ->
1554 Errors.naming_too_few_arguments p;
1555 N.Expr (cp, N.Any)
1556 | (cond_p, cond) :: el ->
1557 let violation =
1558 ( cp,
1559 Aast.Call
1560 ( (p, Aast.Id (fp, SN.AutoimportedFunctions.invariant_violation)),
1563 unpacked_element ) )
1565 (match cond with
1566 | Aast.False ->
1567 (* a false <condition> means unconditional invariant_violation *)
1568 N.Expr (expr env violation)
1569 | _ ->
1570 let (b1, b2) =
1571 ([(cp, Aast.Expr violation)], [(Pos.none, Aast.Noop)])
1573 let cond = (cond_p, Aast.Unop (Ast_defs.Unot, (cond_p, cond))) in
1574 if_stmt env cond b1 b2)
1576 | Aast.Expr e -> N.Expr (expr env e)
1578 (pos, stmt)
1580 and if_stmt env e b1 b2 =
1581 let e = expr env e in
1582 Env.scope env (fun env ->
1583 let b1 = branch env b1 in
1584 let b2 = branch env b2 in
1585 N.If (e, b1, b2))
1587 and do_stmt env b e =
1588 let b = block ~new_scope:false env b in
1589 let e = expr env e in
1590 N.Do (b, e)
1592 (* Scoping is essentially that of do: block is always executed *)
1593 and using_stmt env has_await (loc, e) b =
1594 let vars = get_using_vars e in
1595 let e = List.map ~f:(expr env) e in
1596 let b = block ~new_scope:false env b in
1597 Env.remove_locals env vars;
1598 N.Using
1601 us_is_block_scoped = false;
1602 (* This isn't used for naming so provide a default *)
1603 us_has_await = has_await;
1604 us_exprs = (loc, e);
1605 us_block = b;
1608 and for_stmt env e1 e2 e3 b =
1609 (* The initialization and condition expression should be in the outer scope,
1610 * as they are always executed. *)
1611 let e1 = exprl env e1 in
1612 let e2 = oexpr env e2 in
1613 Env.scope env (fun env ->
1614 (* The third expression (iteration step) should have the same scope as the
1615 * block, as it is not always executed. *)
1616 let b = block ~new_scope:false env b in
1617 let e3 = exprl env e3 in
1618 N.For (e1, e2, e3, b))
1620 and switch_stmt env e cl =
1621 let e = expr env e in
1622 Env.scope env (fun env ->
1623 let cl = casel env cl in
1624 N.Switch (e, cl))
1626 and foreach_stmt env e ae b =
1627 let e = expr env e in
1628 Env.scope env (fun env ->
1629 let ae = as_expr env ae in
1630 let b = block env b in
1631 N.Foreach (e, ae, b))
1633 and get_lvalues (acc : Pos.t SMap.t) (p, e) : Pos.t SMap.t =
1634 match e with
1635 | Aast.List lv -> List.fold_left ~init:acc ~f:get_lvalues lv
1636 | Aast.Lvar (_, lid) -> SMap.add (Local_id.to_string lid) p acc
1637 | _ -> acc
1639 and as_expr env ae =
1640 let handle_v ev =
1641 match ev with
1642 | (p, Aast.Id _) ->
1643 Errors.expected_variable p;
1644 (p, N.Lvar (Env.new_lvar env (p, "__internal_placeholder")))
1645 | ev ->
1646 let vars = get_lvalues SMap.empty ev in
1647 SMap.iter (fun x p -> ignore (Env.new_lvar env (p, x))) vars;
1648 expr env ev
1650 let handle_k ek =
1651 match ek with
1652 | (_, Aast.Lvar (p, lid)) ->
1653 let x = (p, Local_id.get_name lid) in
1654 (p, N.Lvar (Env.new_lvar env x))
1655 | (p, _) ->
1656 Errors.expected_variable p;
1657 (p, N.Lvar (Env.new_lvar env (p, "__internal_placeholder")))
1659 match ae with
1660 | Aast.As_v ev ->
1661 let ev = handle_v ev in
1662 N.As_v ev
1663 | Aast.As_kv (k, ev) ->
1664 let k = handle_k k in
1665 let ev = handle_v ev in
1666 N.As_kv (k, ev)
1667 | N.Await_as_v (p, ev) ->
1668 let ev = handle_v ev in
1669 N.Await_as_v (p, ev)
1670 | N.Await_as_kv (p, k, ev) ->
1671 let k = handle_k k in
1672 let ev = handle_v ev in
1673 N.Await_as_kv (p, k, ev)
1675 and try_stmt env b cl fb =
1676 Env.scope env (fun env ->
1677 let fb = branch env fb in
1678 let b = branch env b in
1679 let cl = catchl env cl in
1680 N.Try (b, cl, fb))
1682 and stmt_list stl env =
1683 match stl with
1684 | [] -> []
1685 | (_, Aast.Block b) :: rest ->
1686 let b = stmt_list b env in
1687 let rest = stmt_list rest env in
1688 b @ rest
1689 | x :: rest ->
1690 let x = stmt env x in
1691 let rest = stmt_list rest env in
1692 x :: rest
1694 and block ?(new_scope = true) env stl =
1695 if new_scope then
1696 Env.scope env (stmt_list stl)
1697 else
1698 stmt_list stl env
1700 and branch env stmt_l = Env.scope env (stmt_list stmt_l)
1702 and awaitall_stmt env el b =
1703 let el =
1704 List.map
1705 ~f:(fun (e1, e2) ->
1706 let e2 = expr env e2 in
1707 let e1 =
1708 match e1 with
1709 | Some lid ->
1710 let e = (Pos.none, Aast.Lvar lid) in
1711 let vars = get_lvalues SMap.empty e in
1712 SMap.iter (fun x p -> ignore (Env.new_lvar env (p, x))) vars;
1714 | None -> None
1716 (e1, e2))
1719 let s = block env b in
1720 N.Awaitall (el, s)
1722 and expr_obj_get_name env expr_ =
1723 match expr_ with
1724 | (p, Aast.Id x) -> (p, N.Id x)
1725 | (p, e) -> expr env (p, e)
1727 and exprl env l = List.map ~f:(expr env) l
1729 and oexpr env e = Option.map e (expr env)
1731 and expr env (p, e) = (p, expr_ env p e)
1733 and expr_ env p (e : Nast.expr_) =
1734 match e with
1735 | Aast.Varray (ta, l) ->
1736 N.Varray (Option.map ~f:(targ env) ta, List.map l (expr env))
1737 | Aast.Darray (tap, l) ->
1738 let nargs =
1739 Option.map ~f:(fun (t1, t2) -> (targ env t1, targ env t2)) tap
1741 N.Darray (nargs, List.map l (fun (e1, e2) -> (expr env e1, expr env e2)))
1742 | Aast.Collection (id, tal, l) ->
1743 let (p, cn) = NS.elaborate_id (fst env).namespace NS.ElaborateClass id in
1744 begin
1745 match cn with
1746 | x when Nast.is_vc_kind x ->
1747 let ta =
1748 match tal with
1749 | Some (Aast.CollectionTV tv) -> Some (targ env tv)
1750 | Some (Aast.CollectionTKV _) ->
1751 Errors.naming_too_many_arguments p;
1752 None
1753 | None -> None
1755 N.ValCollection
1756 (Nast.get_vc_kind cn, ta, List.map l (afield_value env cn))
1757 | x when Nast.is_kvc_kind x ->
1758 let ta =
1759 match tal with
1760 | Some (Aast.CollectionTV _) ->
1761 Errors.naming_too_few_arguments p;
1762 None
1763 | Some (Aast.CollectionTKV (tk, tv)) -> Some (targ env tk, targ env tv)
1764 | None -> None
1766 N.KeyValCollection
1767 (Nast.get_kvc_kind cn, ta, List.map l (afield_kvalue env cn))
1768 | x when String.equal x SN.Collections.cPair ->
1769 let ta =
1770 match tal with
1771 | Some (Aast.CollectionTV _) ->
1772 Errors.naming_too_few_arguments p;
1773 None
1774 | Some (Aast.CollectionTKV (tk, tv)) -> Some (targ env tk, targ env tv)
1775 | None -> None
1777 begin
1778 match l with
1779 | [] ->
1780 Errors.naming_too_few_arguments p;
1781 N.Any
1782 | [e1; e2] ->
1783 let pn = SN.Collections.cPair in
1784 N.Pair (ta, afield_value env pn e1, afield_value env pn e2)
1785 | _ ->
1786 Errors.naming_too_many_arguments p;
1787 N.Any
1789 | _ ->
1790 Errors.expected_collection p cn;
1791 N.Any
1793 | Aast.Clone e -> N.Clone (expr env e)
1794 | Aast.Null -> N.Null
1795 | Aast.True -> N.True
1796 | Aast.False -> N.False
1797 | Aast.Int s -> N.Int s
1798 | Aast.Float s -> N.Float s
1799 | Aast.String s -> N.String s
1800 | Aast.String2 idl -> N.String2 (string2 env idl)
1801 | Aast.PrefixedString (n, e) -> N.PrefixedString (n, expr env e)
1802 | Aast.Id x -> N.Id x
1803 | Aast.Lvar (_, x)
1804 when String.equal (Local_id.to_string x) SN.SpecialIdents.this ->
1805 N.This
1806 | Aast.Lvar (p, x)
1807 when String.equal (Local_id.to_string x) SN.SpecialIdents.dollardollar ->
1808 N.Dollardollar (p, Local_id.make_unscoped SN.SpecialIdents.dollardollar)
1809 | Aast.Lvar (p, x)
1810 when String.equal (Local_id.to_string x) SN.SpecialIdents.placeholder ->
1811 N.Lplaceholder p
1812 | Aast.Lvar x ->
1813 let x = (fst x, Local_id.to_string @@ snd x) in
1814 N.Lvar (Env.lvar env x)
1815 | Aast.Obj_get (e1, e2, nullsafe, in_parens) ->
1816 (* If we encounter Obj_get(_,_,true) by itself, then it means "?->"
1817 is being used for instance property access; see the case below for
1818 handling nullsafe instance method calls to see how this works *)
1819 N.Obj_get (expr env e1, expr_obj_get_name env e2, nullsafe, in_parens)
1820 | Aast.Array_get ((p, Aast.Lvar x), None) ->
1821 let x = (fst x, Local_id.to_string @@ snd x) in
1822 let id = (p, N.Lvar (Env.lvar env x)) in
1823 N.Array_get (id, None)
1824 | Aast.Array_get (e1, e2) -> N.Array_get (expr env e1, oexpr env e2)
1825 | Aast.Class_get
1826 ((_, Aast.CIexpr (_, Aast.Id x1)), Aast.CGstring x2, in_parens) ->
1827 N.Class_get (make_class_id env x1, N.CGstring x2, in_parens)
1828 | Aast.Class_get
1829 ((_, Aast.CIexpr (_, Aast.Lvar (p, lid))), Aast.CGstring x2, in_parens) ->
1830 let x1 = (p, Local_id.to_string lid) in
1831 N.Class_get (make_class_id env x1, N.CGstring x2, in_parens)
1832 | Aast.Class_get ((_, Aast.CIexpr x1), Aast.CGstring _, _) ->
1833 ensure_name_not_dynamic env x1;
1834 N.Any
1835 | Aast.Class_get ((_, Aast.CIexpr x1), Aast.CGexpr x2, _) ->
1836 ensure_name_not_dynamic env x1;
1837 ensure_name_not_dynamic env x2;
1838 N.Any
1839 | Aast.Class_get _ -> failwith "Error in Ast_to_nast module for Class_get"
1840 | Aast.Class_const ((_, Aast.CIexpr (_, Aast.Id x1)), ((_, str) as x2))
1841 when String.equal str "class" ->
1842 N.Class_const (make_class_id env x1, x2)
1843 | Aast.Class_const ((_, Aast.CIexpr (_, Aast.Id x1)), x2) ->
1844 N.Class_const (make_class_id env x1, x2)
1845 | Aast.Class_const ((_, Aast.CIexpr (_, Aast.Lvar (p, lid))), x2) ->
1846 let x1 = (p, Local_id.to_string lid) in
1847 N.Class_const (make_class_id env x1, x2)
1848 | Aast.Class_const _ -> (* TODO: report error in strict mode *) N.Any
1849 | Aast.Call ((_, Aast.Id (p, pseudo_func)), tal, el, unpacked_element)
1850 when String.equal pseudo_func SN.SpecialFunctions.echo ->
1851 arg_unpack_unexpected unpacked_element;
1852 N.Call ((p, N.Id (p, pseudo_func)), targl env p tal, exprl env el, None)
1853 | Aast.Call ((p, Aast.Id (_, cn)), tal, el, _)
1854 when String.equal cn SN.StdlibFunctions.call_user_func ->
1855 Errors.deprecated_use
1857 ( "The builtin "
1858 ^ Markdown_lite.md_codify (Utils.strip_ns cn)
1859 ^ " is deprecated." );
1860 begin
1861 match el with
1862 | [] ->
1863 Errors.naming_too_few_arguments p;
1864 N.Any
1865 | f :: el -> N.Call (expr env f, targl env p tal, exprl env el, None)
1867 | Aast.Call ((p, Aast.Id (_, cn)), _, el, unpacked_element)
1868 when String.equal cn SN.AutoimportedFunctions.fun_ ->
1869 arg_unpack_unexpected unpacked_element;
1870 begin
1871 match el with
1872 | [] ->
1873 Errors.naming_too_few_arguments p;
1874 N.Any
1875 | [(p, Aast.String x)] -> N.Fun_id (p, x)
1876 | [(p, _)] ->
1877 Errors.illegal_fun p;
1878 N.Any
1879 | _ ->
1880 Errors.naming_too_many_arguments p;
1881 N.Any
1883 | Aast.Call ((p, Aast.Id (_, cn)), _, el, unpacked_element)
1884 when String.equal cn SN.AutoimportedFunctions.inst_meth ->
1885 arg_unpack_unexpected unpacked_element;
1886 begin
1887 match el with
1888 | []
1889 | [_] ->
1890 Errors.naming_too_few_arguments p;
1891 N.Any
1892 | [instance; (p, Aast.String meth)] ->
1893 N.Method_id (expr env instance, (p, meth))
1894 | [(p, _); _] ->
1895 Errors.illegal_inst_meth p;
1896 N.Any
1897 | _ ->
1898 Errors.naming_too_many_arguments p;
1899 N.Any
1901 | Aast.Call ((p, Aast.Id (_, cn)), _, el, unpacked_element)
1902 when String.equal cn SN.AutoimportedFunctions.meth_caller ->
1903 arg_unpack_unexpected unpacked_element;
1904 begin
1905 match el with
1906 | []
1907 | [_] ->
1908 Errors.naming_too_few_arguments p;
1909 N.Any
1910 | [e1; e2] ->
1911 begin
1912 match (expr env e1, expr env e2) with
1913 | ((pc, N.String cl), (pm, N.String meth)) ->
1914 let () = check_name (pc, cl) in
1915 N.Method_caller ((pc, cl), (pm, meth))
1916 | ((_, N.Class_const ((_, N.CI cl), (_, mem))), (pm, N.String meth))
1917 when String.equal mem SN.Members.mClass ->
1918 let () = check_name cl in
1919 N.Method_caller (cl, (pm, meth))
1920 | ((p, _), _) ->
1921 Errors.illegal_meth_caller p;
1922 N.Any
1924 | _ ->
1925 Errors.naming_too_many_arguments p;
1926 N.Any
1928 | Aast.Call ((p, Aast.Id (_, cn)), _, el, unpacked_element)
1929 when String.equal cn SN.AutoimportedFunctions.class_meth ->
1930 arg_unpack_unexpected unpacked_element;
1931 begin
1932 match el with
1933 | []
1934 | [_] ->
1935 Errors.naming_too_few_arguments p;
1936 N.Any
1937 | [e1; e2] ->
1938 begin
1939 match (expr env e1, expr env e2) with
1940 | ((pc, N.String cl), (pm, N.String meth)) ->
1941 let () = check_name (pc, cl) in
1942 let cid = N.CI (pc, cl) in
1943 N.Smethod_id ((pc, cid), (pm, meth))
1944 | ((_, N.Id (pc, const)), (pm, N.String meth))
1945 when String.equal const SN.PseudoConsts.g__CLASS__ ->
1946 (* All of these that use current_cls aren't quite correct
1947 * inside a trait, as the class should be the using class.
1948 * It's sufficient for typechecking purposes (we require
1949 * subclass to be compatible with the trait member/method
1950 * declarations).
1952 (match (fst env).current_cls with
1953 | Some (cid, _, true) ->
1954 let cid = N.CI (pc, snd cid) in
1955 N.Smethod_id ((p, cid), (pm, meth))
1956 | Some (cid, kind, false) ->
1957 let is_trait = Ast_defs.is_c_trait kind in
1958 Errors.class_meth_non_final_CLASS p is_trait (snd cid);
1959 N.Any
1960 | None ->
1961 Errors.illegal_class_meth p;
1962 N.Any)
1963 | ((_, N.Class_const ((pc, N.CI cl), (_, mem))), (pm, N.String meth))
1964 when String.equal mem SN.Members.mClass ->
1965 let () = check_name cl in
1966 let cid = N.CI cl in
1967 N.Smethod_id ((pc, cid), (pm, meth))
1968 | ((p, N.Class_const ((pc, N.CIself), (_, mem))), (pm, N.String meth))
1969 when String.equal mem SN.Members.mClass ->
1970 (match (fst env).current_cls with
1971 | Some (_cid, _, true) -> N.Smethod_id ((pc, N.CIself), (pm, meth))
1972 | Some (cid, _, false) ->
1973 Errors.class_meth_non_final_self p (snd cid);
1974 N.Any
1975 | None ->
1976 Errors.illegal_class_meth p;
1977 N.Any)
1978 | ( (p, N.Class_const ((pc, N.CIstatic), (_, mem))),
1979 (pm, N.String meth) )
1980 when String.equal mem SN.Members.mClass ->
1981 (match (fst env).current_cls with
1982 | Some (_cid, _, _) -> N.Smethod_id ((pc, N.CIstatic), (pm, meth))
1983 | None ->
1984 Errors.illegal_class_meth p;
1985 N.Any)
1986 | ((p, _), _) ->
1987 Errors.illegal_class_meth p;
1988 N.Any
1990 | _ ->
1991 Errors.naming_too_many_arguments p;
1992 N.Any
1994 | Aast.Call ((p, Aast.Id (_, cn)), _, el, unpacked_element)
1995 when String.equal cn SN.SpecialFunctions.tuple ->
1996 arg_unpack_unexpected unpacked_element;
1997 (match el with
1998 | [] ->
1999 Errors.naming_too_few_arguments p;
2000 N.Any
2001 | el -> N.List (exprl env el))
2002 | Aast.Call ((p, Aast.Id f), tal, el, unpacked_element) ->
2003 N.Call
2004 ((p, N.Id f), targl env p tal, exprl env el, oexpr env unpacked_element)
2005 (* match *)
2006 (* Handle nullsafe instance method calls here. Because Obj_get is used
2007 for both instance property access and instance method calls, we need
2008 to match the entire "Call(Obj_get(..), ..)" pattern here so that we
2009 only match instance method calls *)
2010 | Aast.Call
2011 ( (p, Aast.Obj_get (e1, e2, Aast.OG_nullsafe, in_parens)),
2012 tal,
2014 unpacked_element ) ->
2015 N.Call
2016 ( ( p,
2017 N.Obj_get
2018 (expr env e1, expr_obj_get_name env e2, N.OG_nullsafe, in_parens) ),
2019 targl env p tal,
2020 exprl env el,
2021 oexpr env unpacked_element )
2022 (* Handle all kinds of calls that weren't handled by any of the cases above *)
2023 | Aast.Call (e, tal, el, unpacked_element) ->
2024 N.Call
2025 (expr env e, targl env p tal, exprl env el, oexpr env unpacked_element)
2026 | Aast.FunctionPointer (Aast.FP_id fid, targs) ->
2027 N.FunctionPointer (N.FP_id fid, targl env p targs)
2028 | Aast.FunctionPointer
2029 (Aast.FP_class_const ((_, Aast.CIexpr (_, Aast.Id x1)), x2), targs) ->
2030 N.FunctionPointer
2031 (N.FP_class_const (make_class_id env x1, x2), targl env p targs)
2032 | Aast.FunctionPointer
2033 (Aast.FP_class_const ((_, Aast.CIexpr (_, Aast.Lvar (p, lid))), x2), targs)
2035 let x1 = (p, Local_id.to_string lid) in
2036 N.FunctionPointer
2037 (N.FP_class_const (make_class_id env x1, x2), targl env p targs)
2038 | Aast.FunctionPointer _ -> N.Any
2039 | Aast.Yield e -> N.Yield (afield env e)
2040 | Aast.Await e -> N.Await (expr env e)
2041 | Aast.List el -> N.List (exprl env el)
2042 | Aast.Cast (ty, e2) ->
2043 let ((p, x), hl) =
2044 match ty with
2045 | (_, Aast.Happly (id, hl)) -> (id, hl)
2046 | _ -> assert false
2048 let ty =
2049 match try_castable_hint ~tp_depth:1 env p x hl with
2050 | Some ty -> (p, ty)
2051 | None ->
2052 let h = hint env ty in
2053 Errors.object_cast p;
2056 N.Cast (ty, expr env e2)
2057 | Aast.ExpressionTree et ->
2058 N.ExpressionTree
2061 et_hint = hint env et.et_hint;
2062 et_src_expr = expr env et.et_src_expr;
2063 et_desugared_expr = expr env et.et_desugared_expr;
2065 | Aast.ET_Splice e -> N.ET_Splice (expr env e)
2066 | Aast.Unop (uop, e) -> N.Unop (uop, expr env e)
2067 | Aast.Binop ((Ast_defs.Eq None as op), lv, e2) ->
2068 let e2 = expr env e2 in
2069 let vars = get_lvalues SMap.empty lv in
2070 SMap.iter (fun x p -> ignore (Env.new_lvar env (p, x))) vars;
2071 N.Binop (op, expr env lv, e2)
2072 | Aast.Binop ((Ast_defs.Eq _ as bop), e1, e2) ->
2073 N.Binop (bop, expr env e1, expr env e2)
2074 | Aast.Binop (bop, e1, e2) -> N.Binop (bop, expr env e1, expr env e2)
2075 | Aast.Pipe (dollardollar, e1, e2) ->
2076 N.Pipe
2077 ( (fst dollardollar, Local_id.make_unscoped SN.SpecialIdents.dollardollar),
2078 expr env e1,
2079 expr env e2 )
2080 | Aast.Eif (e1, e2opt, e3) ->
2081 (* The order matters here, of course -- e1 can define vars that need to
2082 * be available in e2 and e3. *)
2083 let e1 = expr env e1 in
2084 let (e2opt, e3) =
2085 Env.scope env (fun env ->
2086 let e2opt = Env.scope env (fun env -> oexpr env e2opt) in
2087 let e3 = Env.scope env (fun env -> expr env e3) in
2088 (e2opt, e3))
2090 N.Eif (e1, e2opt, e3)
2091 | Aast.Is (e, h) ->
2092 N.Is (expr env e, hint ~allow_wildcard:true ~allow_like:true env h)
2093 | Aast.As (e, h, b) ->
2094 N.As (expr env e, hint ~allow_wildcard:true ~allow_like:true env h, b)
2095 | Aast.New ((_, Aast.CIexpr (p, Aast.Id x)), tal, el, unpacked_element, _) ->
2096 N.New
2097 ( make_class_id env x,
2098 targl env p tal,
2099 exprl env el,
2100 oexpr env unpacked_element,
2102 | Aast.New
2103 ((_, Aast.CIexpr (_, Aast.Lvar (pos, x))), tal, el, unpacked_element, p)
2105 N.New
2106 ( make_class_id env (pos, Local_id.to_string x),
2107 targl env p tal,
2108 exprl env el,
2109 oexpr env unpacked_element,
2111 | Aast.New ((_, Aast.CIexpr (p, _e)), tal, el, unpacked_element, _) ->
2112 if Partial.should_check_error (fst env).in_mode 2060 then
2113 Errors.dynamic_new_in_strict_mode p;
2114 N.New
2115 ( make_class_id env (p, SN.Classes.cUnknown),
2116 targl env p tal,
2117 exprl env el,
2118 oexpr env unpacked_element,
2120 | Aast.New _ -> failwith "ast_to_nast aast.new"
2121 | Aast.Record (id, l) ->
2122 let () = check_name id in
2123 let l = List.map l (fun (e1, e2) -> (expr env e1, expr env e2)) in
2124 N.Record (id, l)
2125 | Aast.Efun (f, idl) ->
2126 let idl =
2127 List.fold_right idl ~init:[] ~f:(fun ((p, x) as id) acc ->
2128 if String.equal (Local_id.to_string x) SN.SpecialIdents.this then (
2129 Errors.this_as_lexical_variable p;
2131 ) else
2132 id :: acc)
2134 let idl = List.map ~f:(fun (p, lid) -> (p, Local_id.to_string lid)) idl in
2135 let idl' = List.map idl (Env.lvar env) in
2136 let env = (fst env, Env.empty_local None) in
2137 List.iter2_exn idl idl' (Env.add_lvar env);
2138 let f = expr_lambda env f in
2139 N.Efun (f, idl')
2140 | Aast.Lfun (_, _ :: _) -> assert false
2141 | Aast.Lfun (f, []) ->
2142 (* We have to build the capture list while we're finding names in
2143 the closure body---accumulate it in to_capture. *)
2144 let to_capture = ref [] in
2145 let handle_unbound (p, x) =
2146 let cap = Env.lvar env (p, x) in
2147 to_capture := cap :: !to_capture;
2150 let lenv = Env.empty_local @@ Some handle_unbound in
2151 let env = (fst env, lenv) in
2152 let f = expr_lambda env f in
2153 N.Lfun (f, !to_capture)
2154 | Aast.Xml (x, al, el) ->
2155 let () = check_name x in
2156 N.Xml (x, attrl env al, exprl env el)
2157 | Aast.Shape fdl ->
2158 let shp =
2159 List.map fdl ~f:(fun (pname, value) ->
2160 (convert_shape_name env pname, expr env value))
2162 N.Shape shp
2163 | Aast.Import _ -> N.Any
2164 | Aast.Omitted -> N.Omitted
2165 | Aast.Callconv (kind, e) -> N.Callconv (kind, expr env e)
2166 | Aast.EnumAtom x -> N.EnumAtom x
2167 | Aast.ReadonlyExpr e -> N.ReadonlyExpr (expr env e)
2168 (* The below were not found on the AST.ml so they are not implemented here *)
2169 | Aast.ValCollection _
2170 | Aast.KeyValCollection _
2171 | Aast.This
2172 | Aast.Dollardollar _
2173 | Aast.Lplaceholder _
2174 | Aast.Fun_id _
2175 | Aast.Method_id _
2176 | Aast.Method_caller _
2177 | Aast.Smethod_id _
2178 | Aast.Pair _
2179 | Aast.Any ->
2180 Errors.internal_error
2182 "Malformed expr: Expr not found on legacy AST: T39599317";
2183 Aast.Any
2185 and expr_lambda env f =
2186 let h =
2187 Aast.type_hint_option_map ~f:(hint ~allow_retonly:true env) f.Aast.f_ret
2189 let (variadicity, paraml) = fun_paraml env f.Aast.f_params in
2190 (* The bodies of lambdas go through naming in the containing local
2191 * environment *)
2192 let body_nast = f_body env f.Aast.f_body in
2193 let annotation = Nast.Named in
2194 let f_ctxs = Option.map ~f:(contexts env) f.Aast.f_ctxs in
2195 let f_unsafe_ctxs = Option.map ~f:(contexts env) f.Aast.f_unsafe_ctxs in
2196 (* These could all be probably be replaced with a {... where ...} *)
2197 let body = { N.fb_ast = body_nast; fb_annotation = annotation } in
2199 N.f_annotation = ();
2200 f_span = f.Aast.f_span;
2201 f_mode = (fst env).in_mode;
2202 f_readonly_ret = f.Aast.f_readonly_ret;
2203 f_ret = h;
2204 f_name = f.Aast.f_name;
2205 f_params = paraml;
2206 f_tparams = [];
2207 f_ctxs;
2208 f_unsafe_ctxs;
2209 f_where_constraints = [];
2210 f_body = body;
2211 f_fun_kind = f.Aast.f_fun_kind;
2212 f_variadic = variadicity;
2213 f_file_attributes = [];
2214 f_user_attributes = user_attributes env f.Aast.f_user_attributes;
2215 f_external = f.Aast.f_external;
2216 f_namespace = f.Aast.f_namespace;
2217 f_doc_comment = f.Aast.f_doc_comment;
2218 f_static = f.Aast.f_static;
2221 and f_body env f_body =
2222 if Nast.is_body_named f_body then
2223 block env f_body.Aast.fb_ast
2224 else
2225 failwith "Malformed f_body: unexpected UnnamedBody from ast_to_nast"
2227 and make_class_id env ((p, x) as cid) =
2228 ( p,
2229 match x with
2230 | x when String.equal x SN.Classes.cParent ->
2231 if Option.is_none (fst env).current_cls then
2232 let () = Errors.parent_outside_class p in
2233 N.CI (p, SN.Classes.cUnknown)
2234 else
2235 N.CIparent
2236 | x when String.equal x SN.Classes.cSelf ->
2237 if Option.is_none (fst env).current_cls then
2238 let () = Errors.self_outside_class p in
2239 N.CI (p, SN.Classes.cUnknown)
2240 else
2241 N.CIself
2242 | x when String.equal x SN.Classes.cStatic ->
2243 if Option.is_none (fst env).current_cls then
2244 let () = Errors.static_outside_class p in
2245 N.CI (p, SN.Classes.cUnknown)
2246 else
2247 N.CIstatic
2248 | x when String.equal x SN.SpecialIdents.this -> N.CIexpr (p, N.This)
2249 | x when String.equal x SN.SpecialIdents.dollardollar ->
2250 (* We won't reach here for "new $$" because the parser creates a
2251 * proper Ast_defs.Dollardollar node, so make_class_id won't be called with
2252 * that node. In fact, the parser creates an Ast_defs.Dollardollar for all
2253 * "$$" except in positions where a classname is expected, like in
2254 * static member access. So, we only reach here for things
2255 * like "$$::someMethod()". *)
2256 N.CIexpr
2257 (p, N.Lvar (p, Local_id.make_unscoped SN.SpecialIdents.dollardollar))
2258 | x when Char.equal x.[0] '$' -> N.CIexpr (p, N.Lvar (Env.lvar env cid))
2259 | _ ->
2260 let () = check_name cid in
2261 N.CI cid )
2263 and casel env l = List.map l (case env)
2265 and case env c =
2266 match c with
2267 | Aast.Default (p, b) ->
2268 let b = branch env b in
2269 N.Default (p, b)
2270 | Aast.Case (e, b) ->
2271 let e = expr env e in
2272 let b = branch env b in
2273 N.Case (e, b)
2275 and catchl env l = List.map l (catch env)
2277 and catch env ((p1, lid1), (p2, lid2), b) =
2278 Env.scope env (fun env ->
2279 let name2 = Local_id.get_name lid2 in
2280 let x2 = Env.new_lvar env (p2, name2) in
2281 let b = branch env b in
2282 let () = check_name (p1, lid1) in
2283 ((p1, lid1), x2, b))
2285 and afield env field =
2286 match field with
2287 | Aast.AFvalue e -> N.AFvalue (expr env e)
2288 | Aast.AFkvalue (e1, e2) -> N.AFkvalue (expr env e1, expr env e2)
2290 and afield_value env cname field =
2291 match field with
2292 | Aast.AFvalue e -> expr env e
2293 | Aast.AFkvalue (e1, _e2) ->
2294 Errors.unexpected_arrow (fst e1) cname;
2295 expr env e1
2297 and afield_kvalue env cname field =
2298 match field with
2299 | Aast.AFvalue e ->
2300 Errors.missing_arrow (fst e) cname;
2301 ( expr env e,
2302 expr
2304 ( fst e,
2305 Aast.Lvar (fst e, Local_id.make_unscoped "__internal_placeholder") )
2307 | Aast.AFkvalue (e1, e2) -> (expr env e1, expr env e2)
2309 and attrl env l = List.map ~f:(attr env) l
2311 and attr env at =
2312 match at with
2313 | Aast.Xhp_simple (x, e) -> N.Xhp_simple (x, expr env e)
2314 | Aast.Xhp_spread e -> N.Xhp_spread (expr env e)
2316 and string2 env idl = List.map idl (expr env)
2318 let record_field env rf =
2319 let (id, h, e) = rf in
2320 let h = hint env h in
2321 let e = oexpr env e in
2322 (id, h, e)
2324 let record_def ctx rd =
2325 let env = Env.make_top_level_env ctx in
2326 let rd =
2327 elaborate_namespaces#on_record_def
2328 (Naming_elaborate_namespaces_endo.make_env (fst env).namespace)
2331 let attrs = user_attributes env rd.Aast.rd_user_attributes in
2332 let extends =
2333 match rd.Aast.rd_extends with
2334 | Some extends -> Some (hint env extends)
2335 | None -> None
2337 let fields = List.map rd.Aast.rd_fields ~f:(record_field env) in
2339 N.rd_annotation = ();
2340 rd_name = rd.Aast.rd_name;
2341 rd_abstract = rd.Aast.rd_abstract;
2342 rd_extends = extends;
2343 rd_fields = fields;
2344 rd_user_attributes = attrs;
2345 rd_namespace = rd.Aast.rd_namespace;
2346 rd_span = rd.Aast.rd_span;
2347 rd_doc_comment = rd.Aast.rd_doc_comment;
2348 rd_emit_id = rd.Aast.rd_emit_id;
2351 (**************************************************************************)
2352 (* Typedefs *)
2353 (**************************************************************************)
2355 let typedef ctx tdef =
2356 let env = Env.make_typedef_env ctx tdef in
2357 let tdef =
2358 elaborate_namespaces#on_typedef
2359 (Naming_elaborate_namespaces_endo.make_env (fst env).namespace)
2360 tdef
2362 let tconstraint = Option.map tdef.Aast.t_constraint (hint env) in
2363 let tparaml = type_paraml env tdef.Aast.t_tparams in
2364 let attrs = user_attributes env tdef.Aast.t_user_attributes in
2366 N.t_annotation = ();
2367 t_name = tdef.Aast.t_name;
2368 t_tparams = tparaml;
2369 t_constraint = tconstraint;
2370 t_kind = hint env tdef.Aast.t_kind;
2371 t_user_attributes = attrs;
2372 t_mode = tdef.Aast.t_mode;
2373 t_namespace = tdef.Aast.t_namespace;
2374 t_vis = tdef.Aast.t_vis;
2375 t_span = tdef.Aast.t_span;
2376 t_emit_id = tdef.Aast.t_emit_id;
2379 (**************************************************************************)
2380 (* Global constants *)
2381 (**************************************************************************)
2383 let global_const ctx cst =
2384 let env = Env.make_const_env ctx cst in
2385 let cst =
2386 elaborate_namespaces#on_gconst
2387 (Naming_elaborate_namespaces_endo.make_env (fst env).namespace)
2390 let hint = Option.map cst.Aast.cst_type (hint env) in
2391 let e = constant_expr env false cst.Aast.cst_value in
2393 N.cst_annotation = ();
2394 cst_mode = cst.Aast.cst_mode;
2395 cst_name = cst.Aast.cst_name;
2396 cst_type = hint;
2397 cst_value = e;
2398 cst_namespace = cst.Aast.cst_namespace;
2399 cst_span = cst.Aast.cst_span;
2400 cst_emit_id = cst.Aast.cst_emit_id;
2403 (**************************************************************************)
2404 (* The entry point to CHECK the program, and transform the program *)
2405 (**************************************************************************)
2407 let program ctx ast =
2408 let ast =
2409 elaborate_namespaces#on_program
2410 (Naming_elaborate_namespaces_endo.make_env
2411 Namespace_env.empty_with_default)
2414 let top_level_env = ref (Env.make_top_level_env ctx) in
2415 let rec aux acc def =
2416 match def with
2417 | Aast.Fun f -> N.Fun (fun_ ctx f) :: acc
2418 | Aast.Class c -> N.Class (class_ ctx c) :: acc
2419 | Aast.Stmt (_, Aast.Noop)
2420 | Aast.Stmt (_, Aast.Markup _) ->
2422 | Aast.Stmt s -> N.Stmt (stmt !top_level_env s) :: acc
2423 | Aast.RecordDef rd -> N.RecordDef (record_def ctx rd) :: acc
2424 | Aast.Typedef t -> N.Typedef (typedef ctx t) :: acc
2425 | Aast.Constant cst -> N.Constant (global_const ctx cst) :: acc
2426 | Aast.Namespace (_ns, aast) -> List.fold_left ~f:aux ~init:[] aast @ acc
2427 | Aast.NamespaceUse _ -> acc
2428 | Aast.SetNamespaceEnv nsenv ->
2429 let (genv, lenv) = !top_level_env in
2430 let genv = { genv with namespace = nsenv } in
2431 top_level_env := (genv, lenv);
2433 | Aast.FileAttributes _ -> acc
2435 let on_program aast =
2436 let nast = List.fold_left ~f:aux ~init:[] aast in
2437 List.rev nast
2439 on_program ast