Use Tuple in lowerer and hackc
[hiphop-php.git] / hphp / hack / src / naming / naming.ml
blob194d9b2e04cbb02d93b400f7f1152569dfdd6bb3
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 ?(ignore_hack_arr = false)
341 ?(tp_depth = 0)
343 (hh : Aast.hint) =
344 let (p, h) = hh in
345 ( p,
346 hint_
347 ~forbid_this
348 ~allow_retonly
349 ~allow_wildcard
350 ~allow_like
351 ~in_where_clause
352 ~ignore_hack_arr
353 ~tp_depth
355 (p, h) )
357 and contexts env ctxs =
358 let (pos, hl) = ctxs in
359 let hl =
360 List.map
361 ~f:(fun h ->
362 match h with
363 | (p, Aast.Happly ((_, wildcard), []))
364 when String.equal wildcard SN.Typehints.wildcard ->
365 (* More helpful wildcard error for coeffects. We expect all valid
366 * wildcard hints to be transformed into Hfun_context *)
367 Errors.invalid_wildcard_context p;
368 (p, N.Herr)
369 | _ -> hint env h)
372 (pos, hl)
374 and hfun env ro hl il variadic_hint ctxs h readonly_ret =
375 let variadic_hint = Option.map variadic_hint (hint env) in
376 let hl = List.map ~f:(hint env) hl in
377 let ctxs = Option.map ~f:(contexts env) ctxs in
378 N.Hfun
381 hf_is_readonly = ro;
382 hf_param_tys = hl;
383 hf_param_info = il;
384 hf_variadic_ty = variadic_hint;
385 hf_ctxs = ctxs;
386 hf_return_ty = hint ~allow_retonly:true env h;
387 hf_is_readonly_return = readonly_ret;
390 and hint_
391 ~forbid_this
392 ~allow_retonly
393 ~allow_wildcard
394 ~allow_like
395 ~in_where_clause
396 ~ignore_hack_arr
397 ?(tp_depth = 0)
399 (p, x) =
400 let tcopt = Provider_context.get_tcopt (fst env).ctx in
401 let like_type_hints_enabled = TypecheckerOptions.like_type_hints tcopt in
402 let hint = hint ~forbid_this ~allow_wildcard ~allow_like in
403 match x with
404 | Aast.Hunion hl -> N.Hunion (List.map hl ~f:(hint ~allow_retonly env))
405 | Aast.Hintersection hl ->
406 N.Hintersection (List.map hl ~f:(hint ~allow_retonly env))
407 | Aast.Htuple hl ->
408 N.Htuple (List.map hl ~f:(hint ~allow_retonly ~tp_depth:(tp_depth + 1) env))
409 | Aast.Hoption h ->
410 (* void/noreturn are permitted for Typing.option_return_only_typehint *)
411 N.Hoption (hint ~allow_retonly env h)
412 | Aast.Hlike h ->
413 if not (allow_like || like_type_hints_enabled) then
414 Errors.experimental_feature p "like-types";
415 N.Hlike (hint ~allow_retonly env h)
416 | Aast.Hsoft h ->
417 let h = hint ~allow_retonly env h in
418 if TypecheckerOptions.interpret_soft_types_as_like_types tcopt then
419 N.Hlike h
420 else
421 snd h
422 | Aast.Hfun
423 Aast.
425 hf_is_readonly = ro;
426 hf_param_tys = hl;
427 hf_param_info = il;
428 hf_variadic_ty = variadic_hint;
429 hf_ctxs = ctxs;
430 hf_return_ty = h;
431 hf_is_readonly_return = readonly_ret;
432 } ->
433 hfun env ro hl il variadic_hint ctxs h readonly_ret
434 | Aast.Happly (((p, _x) as id), hl) ->
435 let hint_id =
436 hint_id
437 ~forbid_this
438 ~allow_retonly
439 ~allow_wildcard
440 ~ignore_hack_arr
441 ~tp_depth
446 (match hint_id with
447 | N.Hprim _
448 | N.Hmixed
449 | N.Hnonnull
450 | N.Hdynamic
451 | N.Hnothing ->
452 if not (List.is_empty hl) then Errors.unexpected_type_arguments p
453 | _ -> ());
454 hint_id
455 | Aast.Haccess ((pos, root_id), ids) ->
456 let root_ty =
457 match root_id with
458 | Aast.Happly ((pos, x), _) when String.equal x SN.Classes.cSelf ->
459 begin
460 match (fst env).current_cls with
461 | None ->
462 Errors.self_outside_class pos;
463 N.Herr
464 | Some (cid, _, _) -> N.Happly (cid, [])
466 | Aast.Happly ((pos, x), _)
467 when String.equal x SN.Classes.cStatic
468 || String.equal x SN.Classes.cParent ->
469 Errors.invalid_type_access_root (pos, x);
470 N.Herr
471 | Aast.Happly (root, _) ->
472 let h =
473 hint_id
474 ~forbid_this
475 ~allow_retonly
476 ~allow_wildcard:false
477 ~ignore_hack_arr:false
478 ~tp_depth
480 root
483 begin
484 match h with
485 | N.Hthis
486 | N.Happly _ ->
488 | N.Habstr _ when in_where_clause -> h
489 | _ ->
490 Errors.invalid_type_access_root root;
491 N.Herr
493 | Aast.Hvar n -> N.Hvar n
494 | _ ->
495 Errors.internal_error
497 "Malformed hint: expected Haccess (Happly ...) from ast_to_nast";
498 N.Herr
500 N.Haccess ((pos, root_ty), ids)
501 | Aast.Hshape { Aast.nsi_allows_unknown_fields; nsi_field_map } ->
502 let nsi_field_map =
503 List.map
504 ~f:(fun { Aast.sfi_optional; sfi_hint; sfi_name } ->
505 let new_key = convert_shape_name env sfi_name in
506 let new_field =
508 N.sfi_optional;
509 sfi_hint =
510 hint ~allow_retonly ~tp_depth:(tp_depth + 1) env sfi_hint;
511 sfi_name = new_key;
514 new_field)
515 nsi_field_map
517 N.Hshape { N.nsi_allows_unknown_fields; nsi_field_map }
518 | Aast.Hmixed -> N.Hmixed
519 | Aast.Hfun_context n -> N.Hfun_context n
520 | Aast.Hvar n -> N.Hvar n
521 | Aast.Herr
522 | Aast.Hany
523 | Aast.Hnonnull
524 | Aast.Habstr _
525 | Aast.Hdarray _
526 | Aast.Hvarray _
527 | Aast.Hvarray_or_darray _
528 | Aast.Hvec_or_dict _
529 | Aast.Hprim _
530 | Aast.Hthis
531 | Aast.Hdynamic
532 | Aast.Hnothing ->
533 Errors.internal_error Pos.none "Unexpected hint not present on legacy AST";
534 N.Herr
536 and hint_id
537 ~forbid_this
538 ~allow_retonly
539 ~allow_wildcard
540 ~ignore_hack_arr
541 ~tp_depth
543 ((p, x) as id)
544 hl =
545 let params = (fst env).type_params in
546 (* some common Xhp screw ups *)
547 if String.equal x "Xhp" || String.equal x ":Xhp" || String.equal x "XHP" then
548 Errors.disallowed_xhp_type p x;
549 match
550 try_castable_hint
551 ~forbid_this
552 ~allow_wildcard
553 ~ignore_hack_arr
554 ~tp_depth
559 with
560 | Some h -> h
561 | None ->
562 begin
563 match x with
564 | x when String.equal x SN.Typehints.wildcard ->
565 if allow_wildcard && tp_depth >= 1 (* prevents 3 as _ *) then
566 if not (List.is_empty hl) then (
567 Errors.typaram_applied_to_type p x;
568 N.Herr
569 ) else
570 N.Happly (id, [])
571 else (
572 Errors.wildcard_hint_disallowed p;
573 N.Herr
576 when String.equal x ("\\" ^ SN.Typehints.void)
577 || String.equal x ("\\" ^ SN.Typehints.null)
578 || String.equal x ("\\" ^ SN.Typehints.noreturn)
579 || String.equal x ("\\" ^ SN.Typehints.int)
580 || String.equal x ("\\" ^ SN.Typehints.bool)
581 || String.equal x ("\\" ^ SN.Typehints.float)
582 || String.equal x ("\\" ^ SN.Typehints.num)
583 || String.equal x ("\\" ^ SN.Typehints.string)
584 || String.equal x ("\\" ^ SN.Typehints.resource)
585 || String.equal x ("\\" ^ SN.Typehints.mixed)
586 || String.equal x ("\\" ^ SN.Typehints.nonnull)
587 || String.equal x ("\\" ^ SN.Typehints.arraykey) ->
588 Errors.primitive_toplevel p;
589 N.Herr
590 | x when String.equal x ("\\" ^ SN.Typehints.nothing) ->
591 Errors.primitive_toplevel p;
592 N.Herr
593 | x when String.equal x SN.Typehints.void && allow_retonly ->
594 N.Hprim N.Tvoid
595 | x when String.equal x SN.Typehints.void ->
596 Errors.return_only_typehint p `void;
597 N.Herr
598 | x when String.equal x SN.Typehints.noreturn && allow_retonly ->
599 N.Hprim N.Tnoreturn
600 | x when String.equal x SN.Typehints.noreturn ->
601 Errors.return_only_typehint p `noreturn;
602 N.Herr
603 | x when String.equal x SN.Typehints.null -> N.Hprim N.Tnull
604 | x when String.equal x SN.Typehints.num -> N.Hprim N.Tnum
605 | x when String.equal x SN.Typehints.resource -> N.Hprim N.Tresource
606 | x when String.equal x SN.Typehints.arraykey -> N.Hprim N.Tarraykey
607 | x when String.equal x SN.Typehints.mixed -> N.Hmixed
608 | x when String.equal x SN.Typehints.nonnull -> N.Hnonnull
609 | x when String.equal x SN.Typehints.dynamic -> N.Hdynamic
610 | x when String.equal x SN.Typehints.nothing -> N.Hnothing
611 | x when String.equal x SN.Typehints.this && not forbid_this ->
612 if not (phys_equal hl []) then Errors.this_no_argument p;
613 N.Hthis
614 | x when String.equal x SN.Typehints.this ->
615 Errors.this_type_forbidden p;
616 N.Herr
617 (* TODO: Duplicate of a Typing[4101] error if namespaced correctly
618 * T56198838 *)
620 when (String.equal x SN.Classes.cClassname || String.equal x "classname")
621 && List.length hl <> 1 ->
622 Errors.classname_param p;
623 N.Hprim N.Tstring
624 | _ when String.(lowercase x = SN.Typehints.this) ->
625 Errors.lowercase_this p x;
626 N.Herr
627 | _ when SSet.mem x params ->
628 let tcopt = Provider_context.get_tcopt (fst env).ctx in
629 let hl =
631 (not (TypecheckerOptions.higher_kinded_types tcopt))
632 && not (List.is_empty hl)
633 then (
634 Errors.typaram_applied_to_type p x;
636 ) else
640 N.Habstr
641 ( x,
642 hintl
643 ~allow_wildcard
644 ~forbid_this
645 ~allow_retonly:true
646 ~tp_depth:(tp_depth + 1)
648 hl )
649 | _ ->
650 let () = check_name id in
651 N.Happly
652 ( id,
653 hintl
654 ~allow_wildcard
655 ~forbid_this
656 ~allow_retonly:true
657 ~tp_depth:(tp_depth + 1)
659 hl )
662 (* Hints that are valid both as casts and type annotations. Neither
663 * casts nor annotations are a strict subset of the other: For
664 * instance, 'object' is not a valid annotation. Thus callers will
665 * have to handle the remaining cases. *)
666 and try_castable_hint
667 ?(forbid_this = false)
668 ?(allow_wildcard = false)
669 ~ignore_hack_arr
670 ~tp_depth
674 hl =
675 let hint =
676 hint
677 ~forbid_this
678 ~tp_depth:(tp_depth + 1)
679 ~allow_wildcard
680 ~allow_retonly:false
682 let unif env =
683 (not ignore_hack_arr)
684 && TypecheckerOptions.hack_arr_dv_arrs
685 (Provider_context.get_tcopt (fst env).ctx)
687 let canon = String.lowercase x in
688 let opt_hint =
689 match canon with
690 | nm when String.equal nm SN.Typehints.int -> Some (N.Hprim N.Tint)
691 | nm when String.equal nm SN.Typehints.bool -> Some (N.Hprim N.Tbool)
692 | nm when String.equal nm SN.Typehints.float -> Some (N.Hprim N.Tfloat)
693 | nm when String.equal nm SN.Typehints.string -> Some (N.Hprim N.Tstring)
694 | nm when String.equal nm SN.Typehints.darray ->
695 Some
696 (match hl with
697 | [] ->
698 if Partial.should_check_error (fst env).in_mode 2071 then
699 Errors.too_few_type_arguments p;
700 if unif env then
701 N.Happly ((p, SN.Collections.cDict), [(p, N.Hany); (p, N.Hany)])
702 else
703 N.Hdarray ((p, N.Hany), (p, N.Hany))
704 | [_] ->
705 Errors.too_few_type_arguments p;
706 N.Hany
707 | [key_; val_] ->
708 if unif env then
709 N.Happly ((p, SN.Collections.cDict), [hint env key_; hint env val_])
710 else
711 N.Hdarray (hint env key_, hint env val_)
712 | _ ->
713 Errors.too_many_type_arguments p;
714 N.Hany)
715 | nm when String.equal nm SN.Typehints.varray ->
716 Some
717 (match hl with
718 | [] ->
719 if Partial.should_check_error (fst env).in_mode 2071 then
720 Errors.too_few_type_arguments p;
721 if unif env then
722 N.Happly ((p, SN.Collections.cVec), [(p, N.Hany)])
723 else
724 N.Hvarray (p, N.Hany)
725 | [val_] ->
726 if unif env then
727 N.Happly ((p, SN.Collections.cVec), [hint env val_])
728 else
729 N.Hvarray (hint env val_)
730 | _ ->
731 Errors.too_many_type_arguments p;
732 N.Hany)
733 | nm when String.equal nm SN.Typehints.varray_or_darray ->
734 Some
735 (match hl with
736 | [] ->
737 if Partial.should_check_error (fst env).in_mode 2071 then
738 Errors.too_few_type_arguments p;
740 if unif env then
741 N.Hvec_or_dict (None, (p, N.Hany))
742 else
743 (* Warning: These Hanys are here because they produce subtle
744 errors because of interaction with tco_experimental_isarray
745 if you change them to Herr *)
746 N.Hvarray_or_darray (None, (p, N.Hany))
747 | [val_] ->
748 if unif env then
749 N.Hvec_or_dict (None, hint env val_)
750 else
751 N.Hvarray_or_darray (None, hint env val_)
752 | [key; val_] ->
753 if unif env then
754 N.Hvec_or_dict (Some (hint env key), hint env val_)
755 else
756 N.Hvarray_or_darray (Some (hint env key), hint env val_)
757 | _ ->
758 Errors.too_many_type_arguments p;
759 N.Hany)
760 | nm when String.equal nm SN.Typehints.vec_or_dict ->
761 Some
762 (match hl with
763 | [] ->
764 if Partial.should_check_error (fst env).in_mode 2071 then
765 Errors.too_few_type_arguments p;
767 N.Hvec_or_dict (None, (p, N.Hany))
768 | [val_] -> N.Hvec_or_dict (None, hint env val_)
769 | [key; val_] -> N.Hvec_or_dict (Some (hint env key), hint env val_)
770 | _ ->
771 Errors.too_many_type_arguments p;
772 N.Hany)
773 | _ -> None
775 let () =
776 match opt_hint with
777 | Some _ when not (String.equal canon x) ->
778 Errors.primitive_invalid_alias p x canon
779 | _ -> ()
781 opt_hint
783 and hintl ~forbid_this ~allow_retonly ~allow_wildcard ~tp_depth env l =
784 List.map ~f:(hint ~forbid_this ~allow_retonly ~allow_wildcard ~tp_depth env) l
786 let constraint_ ?(forbid_this = false) env (ck, h) =
787 (ck, hint ~forbid_this env h)
789 let targ env (p, t) =
790 ( p,
791 hint
792 ~allow_wildcard:true
793 ~forbid_this:false
794 ~allow_retonly:true
795 ~tp_depth:1
799 let targl env _ tal = List.map tal ~f:(targ env)
801 (**************************************************************************)
802 (* All the methods and static methods of an interface are "implicitly"
803 * declared as abstract
805 (**************************************************************************)
807 let add_abstract m = { m with N.m_abstract = true }
809 let add_abstractl methods = List.map methods add_abstract
811 let interface c constructor methods smethods =
812 if not (Ast_defs.is_c_interface c.Aast.c_kind) then
813 (constructor, methods, smethods)
814 else
815 let constructor = Option.map constructor add_abstract in
816 let methods = add_abstractl methods in
817 let smethods = add_abstractl smethods in
818 (constructor, methods, smethods)
820 let ensure_name_not_dynamic env e =
821 match e with
822 | (_, (Aast.Id _ | Aast.Lvar _)) -> ()
823 | (p, _) ->
824 if Partial.should_check_error (fst env).in_mode 2078 then
825 Errors.dynamic_class_name_in_strict_mode p
827 (* Naming of a class *)
828 let rec class_ ctx c =
829 let env = Env.make_class_env ctx c in
830 let c =
831 elaborate_namespaces#on_class_
832 (Naming_elaborate_namespaces_endo.make_env (fst env).namespace)
835 let where_constraints =
836 type_where_constraints env c.Aast.c_where_constraints
838 let name = c.Aast.c_name in
839 let (constructor, smethods, methods) = Aast.split_methods c in
840 let smethods = List.map ~f:(method_ (fst env)) smethods in
841 let (sprops, props) = Aast.split_vars c in
842 let sprops = List.map ~f:(class_prop_static env) sprops in
843 let attrs = user_attributes env c.Aast.c_user_attributes in
844 let const = Naming_attributes.find SN.UserAttributes.uaConst attrs in
845 let props = List.map ~f:(class_prop_non_static ~const env) props in
846 let xhp_attrs = List.map ~f:(xhp_attribute_decl env) c.Aast.c_xhp_attrs in
847 (* These would be out of order with the old attributes, but that shouldn't matter? *)
848 let props = props @ xhp_attrs in
849 let (enum_bound, enum, in_enum_class) =
850 match c.Aast.c_enum with
851 | Some enum -> enum_ env name enum
852 | None -> (None, None, false)
854 let parents = List.map c.Aast.c_extends (hint ~allow_retonly:false env) in
855 let parents =
856 match enum_bound with
857 (* Make enums implicitly extend the BuiltinEnum/BuiltinEnumClass classes in
858 * order to provide utility methods.
860 | Some bound ->
861 let pos = fst name in
862 let builtin =
863 if in_enum_class then
864 SN.Classes.cHH_BuiltinEnumClass
865 else
866 SN.Classes.cHH_BuiltinEnum
868 let parent = (pos, N.Happly ((pos, builtin), [bound])) in
869 parent :: parents
870 | None -> parents
872 let methods = List.map ~f:(method_ (fst env)) methods in
873 let uses = List.map ~f:(hint env) c.Aast.c_uses in
874 let xhp_attr_uses = List.map ~f:(hint env) c.Aast.c_xhp_attr_uses in
875 let (c_req_extends, c_req_implements) = Aast.split_reqs c in
877 (not (List.is_empty c_req_implements))
878 && not (Ast_defs.is_c_trait c.Aast.c_kind)
879 then
880 Errors.invalid_req_implements (fst (List.hd_exn c_req_implements));
881 let req_implements = List.map ~f:(hint env) c_req_implements in
882 let req_implements = List.map ~f:(fun h -> (h, false)) req_implements in
884 (not (List.is_empty c_req_extends))
885 && (not (Ast_defs.is_c_trait c.Aast.c_kind))
886 && not (Ast_defs.is_c_interface c.Aast.c_kind)
887 then
888 Errors.invalid_req_extends (fst (List.hd_exn c_req_extends));
889 let req_extends = List.map ~f:(hint env) c_req_extends in
890 let req_extends = List.map ~f:(fun h -> (h, true)) req_extends in
891 (* Setting a class type parameters constraint to the 'this' type is weird
892 * so lets forbid it for now.
894 let tparam_l = type_paraml ~forbid_this:true env c.Aast.c_tparams in
895 let consts = List.map ~f:(class_const env ~in_enum_class) c.Aast.c_consts in
896 let typeconsts = List.map ~f:(typeconst env) c.Aast.c_typeconsts in
897 let implements =
898 List.map ~f:(hint ~allow_retonly:false env) c.Aast.c_implements
900 let constructor = Option.map constructor (method_ (fst env)) in
901 let (constructor, methods, smethods) =
902 interface c constructor methods smethods
904 let file_attributes =
905 file_attributes ctx c.Aast.c_mode c.Aast.c_file_attributes
907 let c_tparams = tparam_l in
908 let methods =
909 match constructor with
910 | None -> smethods @ methods
911 | Some c -> (c :: smethods) @ methods
914 N.c_annotation = ();
915 N.c_span = c.Aast.c_span;
916 N.c_mode = c.Aast.c_mode;
917 N.c_final = c.Aast.c_final;
918 N.c_is_xhp = c.Aast.c_is_xhp;
919 N.c_has_xhp_keyword = c.Aast.c_has_xhp_keyword;
920 N.c_kind = c.Aast.c_kind;
921 N.c_name = name;
922 N.c_tparams;
923 N.c_extends = parents;
924 N.c_uses = uses;
925 (* c_use_as_alias and c_insteadof_alias are PHP features not supported
926 * in Hack but are required since we have runtime support for it
928 N.c_use_as_alias = [];
929 N.c_insteadof_alias = [];
930 N.c_xhp_attr_uses = xhp_attr_uses;
931 N.c_xhp_category = c.Aast.c_xhp_category;
932 N.c_reqs = req_extends @ req_implements;
933 N.c_implements = implements;
934 N.c_support_dynamic_type = c.Aast.c_support_dynamic_type;
935 N.c_where_constraints = where_constraints;
936 N.c_consts = consts;
937 N.c_typeconsts = typeconsts;
938 N.c_vars = sprops @ props;
939 N.c_methods = methods;
940 N.c_user_attributes = attrs;
941 N.c_file_attributes = file_attributes;
942 N.c_namespace = c.Aast.c_namespace;
943 N.c_enum = enum;
944 N.c_doc_comment = c.Aast.c_doc_comment;
945 N.c_xhp_children = c.Aast.c_xhp_children;
946 (* Naming and typechecking shouldn't use these fields *)
947 N.c_attributes = [];
948 N.c_xhp_attrs = [];
949 N.c_emit_id = c.Aast.c_emit_id;
952 and user_attributes env attrl =
953 let seen = Caml.Hashtbl.create 0 in
954 let validate_seen ua_name =
955 let (pos, name) = ua_name in
956 let existing_attr_pos =
957 (try Some (Caml.Hashtbl.find seen name) with Caml.Not_found -> None)
959 match existing_attr_pos with
960 | Some p ->
961 Errors.duplicate_user_attribute ua_name p;
962 false
963 | None ->
964 Caml.Hashtbl.add seen name pos;
965 true
967 let on_attr acc { Aast.ua_name; ua_params } =
968 let () = check_name ua_name in
969 if not (validate_seen ua_name) then
971 else
972 let attr =
973 { N.ua_name; N.ua_params = List.map ~f:(expr env) ua_params }
975 attr :: acc
977 List.fold_left ~init:[] ~f:on_attr attrl
979 and file_attributes ctx mode fal = List.map ~f:(file_attribute ctx mode) fal
981 and file_attribute ctx mode fa =
982 let env = Env.make_file_attributes_env ctx mode fa.Aast.fa_namespace in
983 let ua = user_attributes env fa.Aast.fa_user_attributes in
984 N.{ fa_user_attributes = ua; fa_namespace = fa.Aast.fa_namespace }
986 (* h cv is_required maybe_enum *)
987 and xhp_attribute_decl env (h, cv, tag, maybe_enum) =
988 let (p, id) = cv.Aast.cv_id in
989 let default = cv.Aast.cv_expr in
990 let is_required = Option.is_some tag in
991 if is_required && Option.is_some default then
992 Errors.xhp_required_with_default p id;
993 let hint_ =
994 match maybe_enum with
995 | Some (pos, items) ->
996 let is_int item =
997 match item with
998 | (_, Aast.Int _) -> true
999 | _ -> false
1001 let contains_int = List.exists ~f:is_int items in
1002 let is_string item =
1003 match item with
1004 | (_, Aast.String _)
1005 | (_, Aast.String2 _) ->
1006 true
1007 | _ -> false
1009 let contains_str = List.exists ~f:is_string items in
1010 if contains_int && not contains_str then
1011 Some (pos, Aast.Happly ((pos, "int"), []))
1012 else if (not contains_int) && contains_str then
1013 Some (pos, Aast.Happly ((pos, "string"), []))
1014 else
1015 Some (pos, Aast.Happly ((pos, "mixed"), []))
1016 | _ -> Aast.hint_of_type_hint h
1018 let hint_ =
1019 match hint_ with
1020 | Some (p, Aast.Hoption _) ->
1021 if is_required then Errors.xhp_optional_required_attr p id;
1022 hint_
1023 | Some (_, Aast.Happly ((_, "mixed"), [])) -> hint_
1024 | Some (p, h) ->
1025 let has_default =
1026 match default with
1027 | None
1028 | Some (_, Aast.Null) ->
1029 false
1030 | _ -> true
1032 if is_required || has_default then
1033 hint_
1034 else
1035 Some (p, Aast.Hoption (p, h))
1036 | None -> None
1038 let hint_ = ((), hint_) in
1039 let hint_ = Aast.type_hint_option_map hint_ ~f:(hint env) in
1040 let (expr, _) = class_prop_expr_is_xhp env cv in
1041 let enum_values =
1042 match cv.Aast.cv_xhp_attr with
1043 | Some xai -> xai.Aast.xai_enum_values
1044 | None -> []
1046 let xhp_attr_info =
1047 Some { N.xai_tag = tag; N.xai_enum_values = enum_values }
1050 N.cv_final = cv.Aast.cv_final;
1051 N.cv_xhp_attr = xhp_attr_info;
1052 N.cv_readonly = cv.Aast.cv_readonly;
1053 N.cv_abstract = cv.Aast.cv_abstract;
1054 N.cv_visibility = cv.Aast.cv_visibility;
1055 N.cv_type = hint_;
1056 N.cv_id = cv.Aast.cv_id;
1057 N.cv_expr = expr;
1058 N.cv_user_attributes = [];
1059 N.cv_is_promoted_variadic = cv.Aast.cv_is_promoted_variadic;
1060 N.cv_doc_comment = cv.Aast.cv_doc_comment (* Can make None to save space *);
1061 N.cv_is_static = cv.Aast.cv_is_static;
1062 N.cv_span = cv.Aast.cv_span;
1065 and enum_ env enum_name e =
1066 let open Aast in
1067 let pos = fst enum_name in
1068 let enum_hint = (pos, Happly (enum_name, [])) in
1069 let is_enum_class = e.e_enum_class in
1070 let old_base = e.e_base in
1071 let new_base = hint env old_base in
1072 let bound =
1073 if is_enum_class then
1074 (* Turn the base type of the enum class into MemberOf<E, base> *)
1075 let elt = (pos, SN.Classes.cMemberOf) in
1076 let h = (pos, Happly (elt, [enum_hint; old_base])) in
1077 hint env h
1078 else
1079 enum_hint
1081 let enum =
1083 N.e_base = new_base;
1084 N.e_constraint = Option.map e.e_constraint (hint env);
1085 N.e_includes = List.map ~f:(hint env) e.e_includes;
1086 N.e_enum_class = is_enum_class;
1089 (Some bound, Some enum, is_enum_class)
1091 and type_paraml ?(forbid_this = false) env tparams =
1092 List.map tparams ~f:(type_param ~forbid_this env)
1095 We need to be careful regarding the scoping of type variables:
1096 Type parameters are always in scope simultaneously: Given
1097 class C<T1 ... , T2 ... , Tn ...>,
1098 all type parameters are in scope in the constraints of all other ones (and the where constraints,
1099 in case of functions).
1100 For consitency, the same holds for nested type parameters (i.e., type parameters of type
1101 parameters). Given
1102 class Foo<T<T1 ... , ...., Tn ... > ... >
1103 every Ti is in scope of the constraints of all other Tj, and in the constraints on T itself.
1105 and type_param ~forbid_this (genv, lenv) t =
1106 begin
1108 TypecheckerOptions.experimental_feature_enabled
1109 (Provider_context.get_tcopt genv.ctx)
1110 TypecheckerOptions.experimental_type_param_shadowing
1111 then
1112 (* Treat type params as inline class declarations that don't go into the naming heap *)
1113 let (pos, name) =
1114 NS.elaborate_id genv.namespace NS.ElaborateClass t.Aast.tp_name
1116 match Naming_provider.get_type_pos genv.ctx name with
1117 | Some def_pos ->
1118 let (def_pos, _) = GEnv.get_type_full_pos genv.ctx (def_pos, name) in
1119 Errors.error_name_already_bound name name pos def_pos
1120 | None ->
1121 (match GEnv.type_canon_name genv.ctx name with
1122 | Some canonical ->
1123 let def_pos =
1124 Option.value ~default:Pos.none (GEnv.type_pos genv.ctx canonical)
1126 Errors.error_name_already_bound name canonical pos def_pos
1127 | None -> ())
1128 end;
1129 let hk_types_enabled =
1130 TypecheckerOptions.higher_kinded_types (Provider_context.get_tcopt genv.ctx)
1132 ( if (not hk_types_enabled) && (not @@ List.is_empty t.Aast.tp_parameters) then
1133 let (pos, name) = t.Aast.tp_name in
1134 Errors.tparam_with_tparam pos name );
1136 (* Bring all type parameters into scope at once before traversing nested tparams,
1137 as per the note above *)
1138 let env = (extend_tparams genv t.Aast.tp_parameters, lenv) in
1139 let tp_parameters =
1140 if hk_types_enabled then
1141 List.map t.Aast.tp_parameters (type_param ~forbid_this env)
1142 else
1145 (* Use the env with all nested tparams still in scope *)
1146 let tp_constraints =
1147 List.map t.Aast.tp_constraints (constraint_ ~forbid_this env)
1150 N.tp_variance = t.Aast.tp_variance;
1151 tp_name = t.Aast.tp_name;
1152 tp_parameters;
1153 tp_constraints;
1154 tp_reified = t.Aast.tp_reified;
1155 tp_user_attributes = user_attributes env t.Aast.tp_user_attributes;
1158 and type_where_constraints env locl_cstrl =
1159 List.map
1160 ~f:(fun (h1, ck, h2) ->
1161 let ty1 = hint ~in_where_clause:true env h1 in
1162 let ty2 = hint ~in_where_clause:true env h2 in
1163 (ty1, ck, ty2))
1164 locl_cstrl
1166 and class_prop_expr_is_xhp env cv =
1167 let expr = Option.map cv.Aast.cv_expr (expr env) in
1168 let expr =
1170 FileInfo.equal_mode (fst env).in_mode FileInfo.Mhhi && Option.is_none expr
1171 then
1172 Some (fst cv.Aast.cv_id, N.Any)
1173 else
1174 expr
1176 let is_xhp =
1177 try String.(sub (snd cv.Aast.cv_id) 0 1 = ":")
1178 with Invalid_argument _ -> false
1180 (expr, is_xhp)
1182 and make_xhp_attr = function
1183 | true -> Some { N.xai_tag = None; N.xai_enum_values = [] }
1184 | false -> None
1186 and class_prop_static env cv =
1187 let attrs = user_attributes env cv.Aast.cv_user_attributes in
1188 let lsb = Naming_attributes.mem SN.UserAttributes.uaLSB attrs in
1189 let forbid_this = not lsb in
1190 let h =
1191 Aast.type_hint_option_map ~f:(hint ~forbid_this env) cv.Aast.cv_type
1193 let (expr, is_xhp) = class_prop_expr_is_xhp env cv in
1195 N.cv_final = cv.Aast.cv_final;
1196 N.cv_xhp_attr = make_xhp_attr is_xhp;
1197 N.cv_abstract = cv.Aast.cv_abstract;
1198 N.cv_readonly = cv.Aast.cv_readonly;
1199 N.cv_visibility = cv.Aast.cv_visibility;
1200 N.cv_type = h;
1201 N.cv_id = cv.Aast.cv_id;
1202 N.cv_expr = expr;
1203 N.cv_user_attributes = attrs;
1204 N.cv_is_promoted_variadic = cv.Aast.cv_is_promoted_variadic;
1205 N.cv_doc_comment = cv.Aast.cv_doc_comment (* Can make None to save space *);
1206 N.cv_is_static = cv.Aast.cv_is_static;
1207 N.cv_span = cv.Aast.cv_span;
1210 and class_prop_non_static env ?(const = None) cv =
1211 let h = Aast.type_hint_option_map ~f:(hint env) cv.Aast.cv_type in
1212 let attrs = user_attributes env cv.Aast.cv_user_attributes in
1213 (* if class is __Const, make all member fields __Const *)
1214 let attrs =
1215 match const with
1216 | Some c ->
1217 if not (Naming_attributes.mem SN.UserAttributes.uaConst attrs) then
1218 c :: attrs
1219 else
1220 attrs
1221 | None -> attrs
1223 let (expr, is_xhp) = class_prop_expr_is_xhp env cv in
1225 N.cv_final = cv.Aast.cv_final;
1226 N.cv_xhp_attr = make_xhp_attr is_xhp;
1227 N.cv_visibility = cv.Aast.cv_visibility;
1228 N.cv_readonly = cv.Aast.cv_readonly;
1229 N.cv_type = h;
1230 N.cv_abstract = cv.Aast.cv_abstract;
1231 N.cv_id = cv.Aast.cv_id;
1232 N.cv_expr = expr;
1233 N.cv_user_attributes = attrs;
1234 N.cv_is_promoted_variadic = cv.Aast.cv_is_promoted_variadic;
1235 N.cv_doc_comment = cv.Aast.cv_doc_comment (* Can make None to save space *);
1236 N.cv_is_static = cv.Aast.cv_is_static;
1237 N.cv_span = cv.Aast.cv_span;
1240 and check_constant_expression env ~in_enum_class (pos, e) =
1241 if not in_enum_class then
1242 check_constant_expr env (pos, e)
1243 else
1244 true
1246 and check_constant_expr env (pos, e) =
1247 match e with
1248 | Aast.Id _
1249 | Aast.Null
1250 | Aast.True
1251 | Aast.False
1252 | Aast.Int _
1253 | Aast.Float _
1254 | Aast.String _ ->
1255 true
1256 | Aast.Class_const ((_, Aast.CIexpr (_, cls)), _)
1257 when match cls with
1258 | Aast.Id (_, "static") -> false
1259 | _ -> true ->
1260 true
1261 | Aast.Unop
1262 ((Ast_defs.Uplus | Ast_defs.Uminus | Ast_defs.Utild | Ast_defs.Unot), e)
1264 check_constant_expr env e
1265 | Aast.Binop (op, e1, e2) ->
1266 (* Only assignment is invalid *)
1267 begin
1268 match op with
1269 | Ast_defs.Eq _ ->
1270 Errors.illegal_constant pos;
1271 false
1272 | _ -> check_constant_expr env e1 && check_constant_expr env e2
1274 | Aast.Eif (e1, e2, e3) ->
1275 check_constant_expr env e1
1276 && Option.for_all e2 (check_constant_expr env)
1277 && check_constant_expr env e3
1278 | Aast.Darray (_, l) ->
1279 List.for_all l ~f:(fun (e1, e2) ->
1280 check_constant_expr env e1 && check_constant_expr env e2)
1281 | Aast.Varray (_, l) -> List.for_all l ~f:(check_constant_expr env)
1282 | Aast.Shape fdl ->
1283 (* Only check the values because shape field names are always legal *)
1284 List.for_all fdl ~f:(fun (_, e) -> check_constant_expr env e)
1285 | Aast.Call ((_, Aast.Id (_, cn)), _, el, unpacked_element)
1286 when String.equal cn SN.AutoimportedFunctions.fun_
1287 || String.equal cn SN.AutoimportedFunctions.class_meth
1288 || String.equal cn SN.StdlibFunctions.array_mark_legacy ->
1289 arg_unpack_unexpected unpacked_element;
1290 List.for_all el ~f:(check_constant_expr env)
1291 | Aast.Tuple el -> List.for_all el ~f:(check_constant_expr env)
1292 | Aast.FunctionPointer ((Aast.FP_id _ | Aast.FP_class_const _), _) -> true
1293 | Aast.Collection (id, _, l) ->
1294 let (p, cn) = NS.elaborate_id (fst env).namespace NS.ElaborateClass id in
1295 (* Only vec/keyset/dict are allowed because they are value types *)
1297 String.equal cn SN.Collections.cVec
1298 || String.equal cn SN.Collections.cKeyset
1299 || String.equal cn SN.Collections.cDict
1300 then
1301 List.for_all l ~f:(check_afield_constant_expr env)
1302 else (
1303 Errors.illegal_constant p;
1304 false
1306 | Aast.As (e, (_, Aast.Hlike _), _) -> check_constant_expr env e
1307 | Aast.As (e, (_, Aast.Happly (id, [_])), _) ->
1308 let (p, cn) = NS.elaborate_id (fst env).namespace NS.ElaborateClass id in
1309 if String.equal cn SN.FB.cIncorrectType then
1310 check_constant_expr env e
1311 else (
1312 Errors.illegal_constant p;
1313 false
1315 | _ ->
1316 Errors.illegal_constant pos;
1317 false
1319 and check_afield_constant_expr env afield =
1320 match afield with
1321 | Aast.AFvalue e -> check_constant_expr env e
1322 | Aast.AFkvalue (e1, e2) ->
1323 check_constant_expr env e1 && check_constant_expr env e2
1325 and constant_expr env ~in_enum_class e =
1326 let valid_constant_expression =
1327 check_constant_expression env ~in_enum_class e
1329 if valid_constant_expression then
1330 expr env e
1331 else
1332 (fst e, N.Any)
1334 and class_const env ~in_enum_class cc =
1335 let h = Option.map cc.Aast.cc_type (hint env) in
1336 let e = Option.map cc.Aast.cc_expr (constant_expr env ~in_enum_class) in
1338 N.cc_type = h;
1339 N.cc_id = cc.Aast.cc_id;
1340 N.cc_expr = e;
1341 N.cc_doc_comment = cc.Aast.cc_doc_comment;
1344 and typeconst env t =
1345 let open Aast in
1346 let tconst =
1347 match t.c_tconst_kind with
1348 | TCAbstract { c_atc_as_constraint; c_atc_super_constraint; c_atc_default }
1350 TCAbstract
1352 c_atc_as_constraint = Option.map ~f:(hint env) c_atc_as_constraint;
1353 c_atc_super_constraint =
1354 Option.map ~f:(hint env) c_atc_super_constraint;
1355 c_atc_default = Option.map ~f:(hint env) c_atc_default;
1357 | TCConcrete { c_tc_type } -> TCConcrete { c_tc_type = hint env c_tc_type }
1358 | TCPartiallyAbstract { c_patc_constraint; c_patc_type } ->
1359 TCPartiallyAbstract
1361 c_patc_constraint = hint env c_patc_constraint;
1362 c_patc_type = hint env c_patc_type;
1365 let attrs = user_attributes env t.Aast.c_tconst_user_attributes in
1368 c_tconst_user_attributes = attrs;
1369 c_tconst_name = t.Aast.c_tconst_name;
1370 c_tconst_kind = tconst;
1371 c_tconst_span = t.Aast.c_tconst_span;
1372 c_tconst_doc_comment = t.Aast.c_tconst_doc_comment;
1373 c_tconst_is_ctx = t.Aast.c_tconst_is_ctx;
1376 and method_ genv m =
1377 let genv = extend_tparams genv m.Aast.m_tparams in
1378 let env = (genv, Env.empty_local None) in
1379 (* Cannot use 'this' if it is a public instance method *)
1380 let (variadicity, paraml) = fun_paraml env m.Aast.m_params in
1381 let tparam_l = type_paraml env m.Aast.m_tparams in
1382 let where_constraints =
1383 type_where_constraints env m.Aast.m_where_constraints
1385 let ret =
1386 Aast.type_hint_option_map ~f:(hint ~allow_retonly:true env) m.Aast.m_ret
1388 let body =
1389 match genv.in_mode with
1390 | FileInfo.Mhhi ->
1391 { N.fb_ast = []; fb_annotation = Nast.NamedWithUnsafeBlocks }
1392 | FileInfo.Mstrict
1393 | FileInfo.Mpartial ->
1394 if Nast.is_body_named m.Aast.m_body then
1395 let env = List.fold_left ~f:Env.add_param m.N.m_params ~init:env in
1396 let env =
1397 match m.N.m_variadic with
1398 | N.FVellipsis _
1399 | N.FVnonVariadic ->
1401 | N.FVvariadicArg param -> Env.add_param env param
1403 let fub_ast = block env m.N.m_body.N.fb_ast in
1404 let annotation = Nast.Named in
1405 { N.fb_ast = fub_ast; fb_annotation = annotation }
1406 else
1407 failwith "ast_to_nast error unnamedbody in method_"
1409 let attrs = user_attributes env m.Aast.m_user_attributes in
1410 let m_ctxs = Option.map ~f:(contexts env) m.Aast.m_ctxs in
1411 let m_unsafe_ctxs = Option.map ~f:(contexts env) m.Aast.m_unsafe_ctxs in
1413 N.m_annotation = ();
1414 N.m_span = m.Aast.m_span;
1415 N.m_final = m.Aast.m_final;
1416 N.m_visibility = m.Aast.m_visibility;
1417 N.m_abstract = m.Aast.m_abstract;
1418 N.m_readonly_this = m.Aast.m_readonly_this;
1419 N.m_static = m.Aast.m_static;
1420 N.m_name = m.Aast.m_name;
1421 N.m_tparams = tparam_l;
1422 N.m_where_constraints = where_constraints;
1423 N.m_params = paraml;
1424 N.m_ctxs;
1425 N.m_unsafe_ctxs;
1426 N.m_body = body;
1427 N.m_fun_kind = m.Aast.m_fun_kind;
1428 N.m_readonly_ret = m.Aast.m_readonly_ret;
1429 N.m_ret = ret;
1430 N.m_variadic = variadicity;
1431 N.m_user_attributes = attrs;
1432 N.m_external = m.Aast.m_external;
1433 N.m_doc_comment = m.Aast.m_doc_comment;
1436 and fun_paraml env paraml =
1437 let _ = List.fold_left ~f:check_repetition ~init:SSet.empty paraml in
1438 let (variadicity, paraml) = determine_variadicity env paraml in
1439 (variadicity, List.map ~f:(fun_param env) paraml)
1441 (* Variadic params are removed from the list *)
1442 and determine_variadicity env paraml =
1443 match paraml with
1444 | [] -> (N.FVnonVariadic, [])
1445 | [x] ->
1446 begin
1447 match (x.Aast.param_is_variadic, x.Aast.param_name) with
1448 | (false, _) -> (N.FVnonVariadic, paraml)
1449 | (true, "...") -> (N.FVellipsis x.Aast.param_pos, [])
1450 | (true, _) -> (N.FVvariadicArg (fun_param env x), [])
1452 | x :: rl ->
1453 let (variadicity, rl) = determine_variadicity env rl in
1454 (variadicity, x :: rl)
1456 and fun_param env (param : Nast.fun_param) =
1457 let p = param.Aast.param_pos in
1458 let name = param.Aast.param_name in
1459 let ident = Local_id.make_unscoped name in
1460 Env.add_lvar env (p, name) (p, ident);
1461 let tyhi =
1462 Aast.type_hint_option_map param.Aast.param_type_hint ~f:(hint env)
1464 let eopt = Option.map param.Aast.param_expr (expr env) in
1466 N.param_annotation = p;
1467 param_type_hint = tyhi;
1468 param_is_variadic = param.Aast.param_is_variadic;
1469 param_pos = p;
1470 param_name = name;
1471 param_expr = eopt;
1472 param_callconv = param.Aast.param_callconv;
1473 param_readonly = param.Aast.param_readonly;
1474 param_user_attributes = user_attributes env param.Aast.param_user_attributes;
1475 param_visibility = param.Aast.param_visibility;
1478 and extend_tparams genv paraml =
1479 let params =
1480 List.fold_right
1481 paraml
1482 ~init:genv.type_params
1483 ~f:(fun { Aast.tp_name = (_, x); _ } acc -> SSet.add x acc)
1485 { genv with type_params = params }
1487 and fun_ ctx f =
1488 let genv = Env.make_fun_decl_genv ctx f in
1489 let lenv = Env.empty_local None in
1490 let env = (genv, lenv) in
1491 let f =
1492 elaborate_namespaces#on_fun_def
1493 (Naming_elaborate_namespaces_endo.make_env (fst env).namespace)
1496 let where_constraints =
1497 type_where_constraints env f.Aast.f_where_constraints
1499 let h =
1500 Aast.type_hint_option_map ~f:(hint ~allow_retonly:true env) f.Aast.f_ret
1502 let (variadicity, paraml) = fun_paraml env f.Aast.f_params in
1503 let f_tparams = type_paraml env f.Aast.f_tparams in
1504 let f_kind = f.Aast.f_fun_kind in
1505 let body =
1506 match genv.in_mode with
1507 | FileInfo.Mhhi ->
1508 { N.fb_ast = []; fb_annotation = Nast.NamedWithUnsafeBlocks }
1509 | FileInfo.Mstrict
1510 | FileInfo.Mpartial ->
1511 if Nast.is_body_named f.Aast.f_body then
1512 let env = List.fold_left ~f:Env.add_param paraml ~init:env in
1513 let env =
1514 match variadicity with
1515 | N.FVellipsis _
1516 | N.FVnonVariadic ->
1518 | N.FVvariadicArg param -> Env.add_param env param
1520 let fb_ast = block env f.Aast.f_body.Aast.fb_ast in
1521 let annotation = Nast.Named in
1522 { N.fb_ast; fb_annotation = annotation }
1523 else
1524 failwith "ast_to_nast error unnamedbody in fun_"
1526 let f_ctxs = Option.map ~f:(contexts env) f.Aast.f_ctxs in
1527 let f_unsafe_ctxs = Option.map ~f:(contexts env) f.Aast.f_unsafe_ctxs in
1528 let file_attributes =
1529 file_attributes ctx f.Aast.f_mode f.Aast.f_file_attributes
1531 let named_fun =
1533 N.f_annotation = ();
1534 f_readonly_this = f.Aast.f_readonly_this;
1535 f_span = f.Aast.f_span;
1536 f_mode = f.Aast.f_mode;
1537 f_readonly_ret = f.Aast.f_readonly_ret;
1538 f_ret = h;
1539 f_name = f.Aast.f_name;
1540 f_tparams;
1541 f_where_constraints = where_constraints;
1542 f_params = paraml;
1543 (* TODO(T70095684) double-check f_ctxs *)
1544 f_ctxs;
1545 f_unsafe_ctxs;
1546 f_body = body;
1547 f_fun_kind = f_kind;
1548 f_variadic = variadicity;
1549 f_user_attributes = user_attributes env f.Aast.f_user_attributes;
1550 f_file_attributes = file_attributes;
1551 f_external = f.Aast.f_external;
1552 f_namespace = f.Aast.f_namespace;
1553 f_doc_comment = f.Aast.f_doc_comment;
1556 named_fun
1558 and get_using_vars es =
1559 List.concat_map es (fun (_, e) ->
1560 match e with
1561 (* Simple assignment to local of form `$lvar = e` *)
1562 | Aast.Binop (Ast_defs.Eq None, (_, Aast.Lvar (p, lid)), _) ->
1563 [(p, Local_id.get_name lid)]
1564 (* Arbitrary expression. This will be assigned to a temporary *)
1565 | _ -> [])
1567 and stmt env (pos, st) =
1568 let stmt =
1569 match st with
1570 | Aast.Block _ -> failwith "stmt block error"
1571 | Aast.Fallthrough -> N.Fallthrough
1572 | Aast.Noop -> N.Noop
1573 | Aast.Markup _ -> N.Noop
1574 | Aast.AssertEnv _ -> N.Noop
1575 | Aast.Break -> Aast.Break
1576 | Aast.Continue -> Aast.Continue
1577 | Aast.Throw e -> N.Throw (expr env e)
1578 | Aast.Return e -> N.Return (Option.map e (expr env))
1579 | Aast.Yield_break -> N.Yield_break
1580 | Aast.Awaitall (el, b) -> awaitall_stmt env el b
1581 | Aast.If (e, b1, b2) -> if_stmt env e b1 b2
1582 | Aast.Do (b, e) -> do_stmt env b e
1583 | Aast.While (e, b) -> N.While (expr env e, block env b)
1584 | Aast.Using s ->
1585 using_stmt env s.Aast.us_has_await s.Aast.us_exprs s.Aast.us_block
1586 | Aast.For (st1, e, st2, b) -> for_stmt env st1 e st2 b
1587 | Aast.Switch (e, cl) -> switch_stmt env e cl
1588 | Aast.Foreach (e, ae, b) -> foreach_stmt env e ae b
1589 | Aast.Try (b, cl, fb) -> try_stmt env b cl fb
1590 | Aast.Expr (cp, Aast.Call ((p, Aast.Id (fp, fn)), hl, el, unpacked_element))
1591 when String.equal fn SN.AutoimportedFunctions.invariant ->
1592 (* invariant is subject to a source-code transform in the HHVM
1593 * runtime: the arguments to invariant are lazily evaluated only in
1594 * the case in which the invariant condition does not hold. So:
1596 * invariant_violation(<condition>, <format>, <format_args...>)
1598 * ... is rewritten as:
1600 * if (!<condition>) {
1601 * invariant_violation(<format>, <format_args...>);
1604 begin
1605 match el with
1606 | []
1607 | [_] ->
1608 Errors.naming_too_few_arguments p;
1609 N.Expr (cp, N.Any)
1610 | (cond_p, cond) :: el ->
1611 let violation =
1612 ( cp,
1613 Aast.Call
1614 ( (p, Aast.Id (fp, SN.AutoimportedFunctions.invariant_violation)),
1617 unpacked_element ) )
1619 (match cond with
1620 | Aast.False ->
1621 (* a false <condition> means unconditional invariant_violation *)
1622 N.Expr (expr env violation)
1623 | _ ->
1624 let (b1, b2) =
1625 ([(cp, Aast.Expr violation)], [(Pos.none, Aast.Noop)])
1627 let cond = (cond_p, Aast.Unop (Ast_defs.Unot, (cond_p, cond))) in
1628 if_stmt env cond b1 b2)
1630 | Aast.Expr e -> N.Expr (expr env e)
1632 (pos, stmt)
1634 and if_stmt env e b1 b2 =
1635 let e = expr env e in
1636 Env.scope env (fun env ->
1637 let b1 = branch env b1 in
1638 let b2 = branch env b2 in
1639 N.If (e, b1, b2))
1641 and do_stmt env b e =
1642 let b = block ~new_scope:false env b in
1643 let e = expr env e in
1644 N.Do (b, e)
1646 (* Scoping is essentially that of do: block is always executed *)
1647 and using_stmt env has_await (loc, e) b =
1648 let vars = get_using_vars e in
1649 let e = List.map ~f:(expr env) e in
1650 let b = block ~new_scope:false env b in
1651 Env.remove_locals env vars;
1652 N.Using
1655 us_is_block_scoped = false;
1656 (* This isn't used for naming so provide a default *)
1657 us_has_await = has_await;
1658 us_exprs = (loc, e);
1659 us_block = b;
1662 and for_stmt env e1 e2 e3 b =
1663 (* The initialization and condition expression should be in the outer scope,
1664 * as they are always executed. *)
1665 let e1 = exprl env e1 in
1666 let e2 = oexpr env e2 in
1667 Env.scope env (fun env ->
1668 (* The third expression (iteration step) should have the same scope as the
1669 * block, as it is not always executed. *)
1670 let b = block ~new_scope:false env b in
1671 let e3 = exprl env e3 in
1672 N.For (e1, e2, e3, b))
1674 and switch_stmt env e cl =
1675 let e = expr env e in
1676 Env.scope env (fun env ->
1677 let cl = casel env cl in
1678 N.Switch (e, cl))
1680 and foreach_stmt env e ae b =
1681 let e = expr env e in
1682 Env.scope env (fun env ->
1683 let ae = as_expr env ae in
1684 let b = block env b in
1685 N.Foreach (e, ae, b))
1687 and get_lvalues (acc : Pos.t SMap.t) (p, e) : Pos.t SMap.t =
1688 match e with
1689 | Aast.List lv -> List.fold_left ~init:acc ~f:get_lvalues lv
1690 | Aast.Lvar (_, lid) -> SMap.add (Local_id.to_string lid) p acc
1691 | _ -> acc
1693 and as_expr env ae =
1694 let handle_v ev =
1695 match ev with
1696 | (p, Aast.Id _) ->
1697 Errors.expected_variable p;
1698 (p, N.Lvar (Env.new_lvar env (p, "__internal_placeholder")))
1699 | ev ->
1700 let vars = get_lvalues SMap.empty ev in
1701 SMap.iter (fun x p -> ignore (Env.new_lvar env (p, x))) vars;
1702 expr env ev
1704 let handle_k ek =
1705 match ek with
1706 | (_, Aast.Lvar (p, lid)) ->
1707 let x = (p, Local_id.get_name lid) in
1708 (p, N.Lvar (Env.new_lvar env x))
1709 | (p, _) ->
1710 Errors.expected_variable p;
1711 (p, N.Lvar (Env.new_lvar env (p, "__internal_placeholder")))
1713 match ae with
1714 | Aast.As_v ev ->
1715 let ev = handle_v ev in
1716 N.As_v ev
1717 | Aast.As_kv (k, ev) ->
1718 let k = handle_k k in
1719 let ev = handle_v ev in
1720 N.As_kv (k, ev)
1721 | N.Await_as_v (p, ev) ->
1722 let ev = handle_v ev in
1723 N.Await_as_v (p, ev)
1724 | N.Await_as_kv (p, k, ev) ->
1725 let k = handle_k k in
1726 let ev = handle_v ev in
1727 N.Await_as_kv (p, k, ev)
1729 and try_stmt env b cl fb =
1730 Env.scope env (fun env ->
1731 let fb = branch env fb in
1732 let b = branch env b in
1733 let cl = catchl env cl in
1734 N.Try (b, cl, fb))
1736 and stmt_list stl env =
1737 match stl with
1738 | [] -> []
1739 | (_, Aast.Block b) :: rest ->
1740 let b = stmt_list b env in
1741 let rest = stmt_list rest env in
1742 b @ rest
1743 | x :: rest ->
1744 let x = stmt env x in
1745 let rest = stmt_list rest env in
1746 x :: rest
1748 and block ?(new_scope = true) env stl =
1749 if new_scope then
1750 Env.scope env (stmt_list stl)
1751 else
1752 stmt_list stl env
1754 and branch env stmt_l = Env.scope env (stmt_list stmt_l)
1756 and awaitall_stmt env el b =
1757 let el =
1758 List.map
1759 ~f:(fun (e1, e2) ->
1760 let e2 = expr env e2 in
1761 let e1 =
1762 match e1 with
1763 | Some lid ->
1764 let e = (Pos.none, Aast.Lvar lid) in
1765 let vars = get_lvalues SMap.empty e in
1766 SMap.iter (fun x p -> ignore (Env.new_lvar env (p, x))) vars;
1768 | None -> None
1770 (e1, e2))
1773 let s = block env b in
1774 N.Awaitall (el, s)
1776 and expr_obj_get_name env expr_ =
1777 match expr_ with
1778 | (p, Aast.Id x) -> (p, N.Id x)
1779 | (p, e) -> expr env (p, e)
1781 and exprl env l = List.map ~f:(expr env) l
1783 and oexpr env e = Option.map e (expr env)
1785 and expr env (p, e) = (p, expr_ env p e)
1787 and expr_ env p (e : Nast.expr_) =
1788 match e with
1789 | Aast.Varray (ta, l) ->
1790 N.Varray (Option.map ~f:(targ env) ta, List.map l (expr env))
1791 | Aast.Darray (tap, l) ->
1792 let nargs =
1793 Option.map ~f:(fun (t1, t2) -> (targ env t1, targ env t2)) tap
1795 N.Darray (nargs, List.map l (fun (e1, e2) -> (expr env e1, expr env e2)))
1796 | Aast.Collection (id, tal, l) ->
1797 let (p, cn) = NS.elaborate_id (fst env).namespace NS.ElaborateClass id in
1798 begin
1799 match cn with
1800 | x when Nast.is_vc_kind x ->
1801 let ta =
1802 match tal with
1803 | Some (Aast.CollectionTV tv) -> Some (targ env tv)
1804 | Some (Aast.CollectionTKV _) ->
1805 Errors.naming_too_many_arguments p;
1806 None
1807 | None -> None
1809 N.ValCollection
1810 (Nast.get_vc_kind cn, ta, List.map l (afield_value env cn))
1811 | x when Nast.is_kvc_kind x ->
1812 let ta =
1813 match tal with
1814 | Some (Aast.CollectionTV _) ->
1815 Errors.naming_too_few_arguments p;
1816 None
1817 | Some (Aast.CollectionTKV (tk, tv)) -> Some (targ env tk, targ env tv)
1818 | None -> None
1820 N.KeyValCollection
1821 (Nast.get_kvc_kind cn, ta, List.map l (afield_kvalue env cn))
1822 | x when String.equal x SN.Collections.cPair ->
1823 let ta =
1824 match tal with
1825 | Some (Aast.CollectionTV _) ->
1826 Errors.naming_too_few_arguments p;
1827 None
1828 | Some (Aast.CollectionTKV (tk, tv)) -> Some (targ env tk, targ env tv)
1829 | None -> None
1831 begin
1832 match l with
1833 | [] ->
1834 Errors.naming_too_few_arguments p;
1835 N.Any
1836 | [e1; e2] ->
1837 let pn = SN.Collections.cPair in
1838 N.Pair (ta, afield_value env pn e1, afield_value env pn e2)
1839 | _ ->
1840 Errors.naming_too_many_arguments p;
1841 N.Any
1843 | _ ->
1844 Errors.expected_collection p cn;
1845 N.Any
1847 | Aast.Clone e -> N.Clone (expr env e)
1848 | Aast.Null -> N.Null
1849 | Aast.True -> N.True
1850 | Aast.False -> N.False
1851 | Aast.Int s -> N.Int s
1852 | Aast.Float s -> N.Float s
1853 | Aast.String s -> N.String s
1854 | Aast.String2 idl -> N.String2 (string2 env idl)
1855 | Aast.PrefixedString (n, e) -> N.PrefixedString (n, expr env e)
1856 | Aast.Id x -> N.Id x
1857 | Aast.Lvar (_, x)
1858 when String.equal (Local_id.to_string x) SN.SpecialIdents.this ->
1859 N.This
1860 | Aast.Lvar (p, x)
1861 when String.equal (Local_id.to_string x) SN.SpecialIdents.dollardollar ->
1862 N.Dollardollar (p, Local_id.make_unscoped SN.SpecialIdents.dollardollar)
1863 | Aast.Lvar (p, x)
1864 when String.equal (Local_id.to_string x) SN.SpecialIdents.placeholder ->
1865 N.Lplaceholder p
1866 | Aast.Lvar x ->
1867 let x = (fst x, Local_id.to_string @@ snd x) in
1868 N.Lvar (Env.lvar env x)
1869 | Aast.Obj_get (e1, e2, nullsafe, in_parens) ->
1870 (* If we encounter Obj_get(_,_,true) by itself, then it means "?->"
1871 is being used for instance property access; see the case below for
1872 handling nullsafe instance method calls to see how this works *)
1873 N.Obj_get (expr env e1, expr_obj_get_name env e2, nullsafe, in_parens)
1874 | Aast.Array_get ((p, Aast.Lvar x), None) ->
1875 let x = (fst x, Local_id.to_string @@ snd x) in
1876 let id = (p, N.Lvar (Env.lvar env x)) in
1877 N.Array_get (id, None)
1878 | Aast.Array_get (e1, e2) -> N.Array_get (expr env e1, oexpr env e2)
1879 | Aast.Class_get
1880 ((_, Aast.CIexpr (_, Aast.Id x1)), Aast.CGstring x2, in_parens) ->
1881 N.Class_get (make_class_id env x1, N.CGstring x2, in_parens)
1882 | Aast.Class_get
1883 ((_, Aast.CIexpr (_, Aast.Lvar (p, lid))), Aast.CGstring x2, in_parens) ->
1884 let x1 = (p, Local_id.to_string lid) in
1885 N.Class_get (make_class_id env x1, N.CGstring x2, in_parens)
1886 | Aast.Class_get ((_, Aast.CIexpr x1), Aast.CGstring _, _) ->
1887 ensure_name_not_dynamic env x1;
1888 N.Any
1889 | Aast.Class_get ((_, Aast.CIexpr x1), Aast.CGexpr x2, _) ->
1890 ensure_name_not_dynamic env x1;
1891 ensure_name_not_dynamic env x2;
1892 N.Any
1893 | Aast.Class_get _ -> failwith "Error in Ast_to_nast module for Class_get"
1894 | Aast.Class_const ((_, Aast.CIexpr (_, Aast.Id x1)), ((_, str) as x2))
1895 when String.equal str "class" ->
1896 N.Class_const (make_class_id env x1, x2)
1897 | Aast.Class_const ((_, Aast.CIexpr (_, Aast.Id x1)), x2) ->
1898 N.Class_const (make_class_id env x1, x2)
1899 | Aast.Class_const ((_, Aast.CIexpr (_, Aast.Lvar (p, lid))), x2) ->
1900 let x1 = (p, Local_id.to_string lid) in
1901 N.Class_const (make_class_id env x1, x2)
1902 | Aast.Class_const _ -> (* TODO: report error in strict mode *) N.Any
1903 | Aast.Call ((_, Aast.Id (p, pseudo_func)), tal, el, unpacked_element)
1904 when String.equal pseudo_func SN.SpecialFunctions.echo ->
1905 arg_unpack_unexpected unpacked_element;
1906 N.Call ((p, N.Id (p, pseudo_func)), targl env p tal, exprl env el, None)
1907 | Aast.Call ((p, Aast.Id (_, cn)), tal, el, _)
1908 when String.equal cn SN.StdlibFunctions.call_user_func ->
1909 Errors.deprecated_use
1911 ( "The builtin "
1912 ^ Markdown_lite.md_codify (Utils.strip_ns cn)
1913 ^ " is deprecated." );
1914 begin
1915 match el with
1916 | [] ->
1917 Errors.naming_too_few_arguments p;
1918 N.Any
1919 | f :: el -> N.Call (expr env f, targl env p tal, exprl env el, None)
1921 | Aast.Call ((p, Aast.Id (_, cn)), _, el, unpacked_element)
1922 when String.equal cn SN.AutoimportedFunctions.fun_ ->
1923 arg_unpack_unexpected unpacked_element;
1924 begin
1925 match el with
1926 | [] ->
1927 Errors.naming_too_few_arguments p;
1928 N.Any
1929 | [(p, Aast.String x)] -> N.Fun_id (p, x)
1930 | [(p, _)] ->
1931 Errors.illegal_fun p;
1932 N.Any
1933 | _ ->
1934 Errors.naming_too_many_arguments p;
1935 N.Any
1937 | Aast.Call ((p, Aast.Id (_, cn)), _, el, unpacked_element)
1938 when String.equal cn SN.AutoimportedFunctions.inst_meth ->
1939 arg_unpack_unexpected unpacked_element;
1940 begin
1941 match el with
1942 | []
1943 | [_] ->
1944 Errors.naming_too_few_arguments p;
1945 N.Any
1946 | [instance; (p, Aast.String meth)] ->
1947 N.Method_id (expr env instance, (p, meth))
1948 | [(p, _); _] ->
1949 Errors.illegal_inst_meth p;
1950 N.Any
1951 | _ ->
1952 Errors.naming_too_many_arguments p;
1953 N.Any
1955 | Aast.Call ((p, Aast.Id (_, cn)), _, el, unpacked_element)
1956 when String.equal cn SN.AutoimportedFunctions.meth_caller ->
1957 arg_unpack_unexpected unpacked_element;
1958 begin
1959 match el with
1960 | []
1961 | [_] ->
1962 Errors.naming_too_few_arguments p;
1963 N.Any
1964 | [e1; e2] ->
1965 begin
1966 match (expr env e1, expr env e2) with
1967 | ((pc, N.String cl), (pm, N.String meth)) ->
1968 let () = check_name (pc, cl) in
1969 N.Method_caller ((pc, cl), (pm, meth))
1970 | ((_, N.Class_const ((_, N.CI cl), (_, mem))), (pm, N.String meth))
1971 when String.equal mem SN.Members.mClass ->
1972 let () = check_name cl in
1973 N.Method_caller (cl, (pm, meth))
1974 | ((p, _), _) ->
1975 Errors.illegal_meth_caller p;
1976 N.Any
1978 | _ ->
1979 Errors.naming_too_many_arguments p;
1980 N.Any
1982 | Aast.Call ((p, Aast.Id (_, cn)), _, el, unpacked_element)
1983 when String.equal cn SN.AutoimportedFunctions.class_meth ->
1984 arg_unpack_unexpected unpacked_element;
1985 begin
1986 match el with
1987 | []
1988 | [_] ->
1989 Errors.naming_too_few_arguments p;
1990 N.Any
1991 | [e1; e2] ->
1992 begin
1993 match (expr env e1, expr env e2) with
1994 | ((pc, N.String cl), (pm, N.String meth)) ->
1995 let () = check_name (pc, cl) in
1996 let cid = N.CI (pc, cl) in
1997 N.Smethod_id ((pc, cid), (pm, meth))
1998 | ((_, N.Id (pc, const)), (pm, N.String meth))
1999 when String.equal const SN.PseudoConsts.g__CLASS__ ->
2000 (* All of these that use current_cls aren't quite correct
2001 * inside a trait, as the class should be the using class.
2002 * It's sufficient for typechecking purposes (we require
2003 * subclass to be compatible with the trait member/method
2004 * declarations).
2006 (match (fst env).current_cls with
2007 | Some (cid, _, true) ->
2008 let cid = N.CI (pc, snd cid) in
2009 N.Smethod_id ((p, cid), (pm, meth))
2010 | Some (cid, kind, false) ->
2011 let is_trait = Ast_defs.is_c_trait kind in
2012 Errors.class_meth_non_final_CLASS p is_trait (snd cid);
2013 N.Any
2014 | None ->
2015 Errors.illegal_class_meth p;
2016 N.Any)
2017 | ((_, N.Class_const ((pc, N.CI cl), (_, mem))), (pm, N.String meth))
2018 when String.equal mem SN.Members.mClass ->
2019 let () = check_name cl in
2020 let cid = N.CI cl in
2021 N.Smethod_id ((pc, cid), (pm, meth))
2022 | ((p, N.Class_const ((pc, N.CIself), (_, mem))), (pm, N.String meth))
2023 when String.equal mem SN.Members.mClass ->
2024 (match (fst env).current_cls with
2025 | Some (_cid, _, true) -> N.Smethod_id ((pc, N.CIself), (pm, meth))
2026 | Some (cid, _, false) ->
2027 Errors.class_meth_non_final_self p (snd cid);
2028 N.Any
2029 | None ->
2030 Errors.illegal_class_meth p;
2031 N.Any)
2032 | ( (p, N.Class_const ((pc, N.CIstatic), (_, mem))),
2033 (pm, N.String meth) )
2034 when String.equal mem SN.Members.mClass ->
2035 (match (fst env).current_cls with
2036 | Some (_cid, _, _) -> N.Smethod_id ((pc, N.CIstatic), (pm, meth))
2037 | None ->
2038 Errors.illegal_class_meth p;
2039 N.Any)
2040 | ((p, _), _) ->
2041 Errors.illegal_class_meth p;
2042 N.Any
2044 | _ ->
2045 Errors.naming_too_many_arguments p;
2046 N.Any
2048 | Aast.Tuple el ->
2049 (match el with
2050 | [] ->
2051 Errors.naming_too_few_arguments p;
2052 N.Any
2053 | el -> N.Tuple (exprl env el))
2054 | Aast.Call ((p, Aast.Id f), tal, el, unpacked_element) ->
2055 N.Call
2056 ((p, N.Id f), targl env p tal, exprl env el, oexpr env unpacked_element)
2057 (* match *)
2058 (* Handle nullsafe instance method calls here. Because Obj_get is used
2059 for both instance property access and instance method calls, we need
2060 to match the entire "Call(Obj_get(..), ..)" pattern here so that we
2061 only match instance method calls *)
2062 | Aast.Call
2063 ( (p, Aast.Obj_get (e1, e2, Aast.OG_nullsafe, in_parens)),
2064 tal,
2066 unpacked_element ) ->
2067 N.Call
2068 ( ( p,
2069 N.Obj_get
2070 (expr env e1, expr_obj_get_name env e2, N.OG_nullsafe, in_parens) ),
2071 targl env p tal,
2072 exprl env el,
2073 oexpr env unpacked_element )
2074 (* Handle all kinds of calls that weren't handled by any of the cases above *)
2075 | Aast.Call (e, tal, el, unpacked_element) ->
2076 N.Call
2077 (expr env e, targl env p tal, exprl env el, oexpr env unpacked_element)
2078 | Aast.FunctionPointer (Aast.FP_id fid, targs) ->
2079 N.FunctionPointer (N.FP_id fid, targl env p targs)
2080 | Aast.FunctionPointer
2081 (Aast.FP_class_const ((_, Aast.CIexpr (_, Aast.Id x1)), x2), targs) ->
2082 N.FunctionPointer
2083 (N.FP_class_const (make_class_id env x1, x2), targl env p targs)
2084 | Aast.FunctionPointer
2085 (Aast.FP_class_const ((_, Aast.CIexpr (_, Aast.Lvar (p, lid))), x2), targs)
2087 let x1 = (p, Local_id.to_string lid) in
2088 N.FunctionPointer
2089 (N.FP_class_const (make_class_id env x1, x2), targl env p targs)
2090 | Aast.FunctionPointer _ -> N.Any
2091 | Aast.Yield e -> N.Yield (afield env e)
2092 | Aast.Await e -> N.Await (expr env e)
2093 | Aast.List el -> N.List (exprl env el)
2094 | Aast.Cast (ty, e2) ->
2095 let ((p, x), hl) =
2096 match ty with
2097 | (_, Aast.Happly (id, hl)) -> (id, hl)
2098 | _ -> assert false
2100 let ty =
2101 match try_castable_hint ~tp_depth:1 ~ignore_hack_arr:false env p x hl with
2102 | Some ty -> (p, ty)
2103 | None ->
2104 let h = hint env ty in
2105 Errors.object_cast p;
2108 N.Cast (ty, expr env e2)
2109 | Aast.ExpressionTree et ->
2110 N.ExpressionTree
2113 et_hint = hint env et.et_hint;
2114 et_splices = block env et.et_splices;
2115 et_virtualized_expr = expr env et.et_virtualized_expr;
2116 et_runtime_expr = expr env et.et_runtime_expr;
2118 | Aast.ET_Splice e -> N.ET_Splice (expr env e)
2119 | Aast.Unop (uop, e) -> N.Unop (uop, expr env e)
2120 | Aast.Binop ((Ast_defs.Eq None as op), lv, e2) ->
2121 let e2 = expr env e2 in
2122 let vars = get_lvalues SMap.empty lv in
2123 SMap.iter (fun x p -> ignore (Env.new_lvar env (p, x))) vars;
2124 N.Binop (op, expr env lv, e2)
2125 | Aast.Binop ((Ast_defs.Eq _ as bop), e1, e2) ->
2126 N.Binop (bop, expr env e1, expr env e2)
2127 | Aast.Binop (bop, e1, e2) -> N.Binop (bop, expr env e1, expr env e2)
2128 | Aast.Pipe (dollardollar, e1, e2) ->
2129 N.Pipe
2130 ( (fst dollardollar, Local_id.make_unscoped SN.SpecialIdents.dollardollar),
2131 expr env e1,
2132 expr env e2 )
2133 | Aast.Eif (e1, e2opt, e3) ->
2134 (* The order matters here, of course -- e1 can define vars that need to
2135 * be available in e2 and e3. *)
2136 let e1 = expr env e1 in
2137 let (e2opt, e3) =
2138 Env.scope env (fun env ->
2139 let e2opt = Env.scope env (fun env -> oexpr env e2opt) in
2140 let e3 = Env.scope env (fun env -> expr env e3) in
2141 (e2opt, e3))
2143 N.Eif (e1, e2opt, e3)
2144 | Aast.Is (e, h) ->
2145 N.Is
2146 ( expr env e,
2147 hint ~allow_wildcard:true ~allow_like:true ~ignore_hack_arr:true env h
2149 | Aast.As (e, h, b) ->
2150 N.As
2151 ( expr env e,
2152 hint ~allow_wildcard:true ~allow_like:true ~ignore_hack_arr:true env h,
2154 | Aast.New ((_, Aast.CIexpr (p, Aast.Id x)), tal, el, unpacked_element, _) ->
2155 N.New
2156 ( make_class_id env x,
2157 targl env p tal,
2158 exprl env el,
2159 oexpr env unpacked_element,
2161 | Aast.New
2162 ((_, Aast.CIexpr (_, Aast.Lvar (pos, x))), tal, el, unpacked_element, p)
2164 N.New
2165 ( make_class_id env (pos, Local_id.to_string x),
2166 targl env p tal,
2167 exprl env el,
2168 oexpr env unpacked_element,
2170 | Aast.New ((_, Aast.CIexpr (p, _e)), tal, el, unpacked_element, _) ->
2171 if Partial.should_check_error (fst env).in_mode 2060 then
2172 Errors.dynamic_new_in_strict_mode p;
2173 N.New
2174 ( make_class_id env (p, SN.Classes.cUnknown),
2175 targl env p tal,
2176 exprl env el,
2177 oexpr env unpacked_element,
2179 | Aast.New _ -> failwith "ast_to_nast aast.new"
2180 | Aast.Record (id, l) ->
2181 let () = check_name id in
2182 let l = List.map l (fun (e1, e2) -> (expr env e1, expr env e2)) in
2183 N.Record (id, l)
2184 | Aast.Efun (f, idl) ->
2185 let idl =
2186 List.fold_right idl ~init:[] ~f:(fun ((p, x) as id) acc ->
2187 if String.equal (Local_id.to_string x) SN.SpecialIdents.this then (
2188 Errors.this_as_lexical_variable p;
2190 ) else
2191 id :: acc)
2193 let idl = List.map ~f:(fun (p, lid) -> (p, Local_id.to_string lid)) idl in
2194 let idl' = List.map idl (Env.lvar env) in
2195 let env = (fst env, Env.empty_local None) in
2196 List.iter2_exn idl idl' (Env.add_lvar env);
2197 let f = expr_lambda env f in
2198 N.Efun (f, idl')
2199 | Aast.Lfun (_, _ :: _) -> assert false
2200 | Aast.Lfun (f, []) ->
2201 (* We have to build the capture list while we're finding names in
2202 the closure body---accumulate it in to_capture. *)
2203 let to_capture = ref [] in
2204 let handle_unbound (p, x) =
2205 let cap = Env.lvar env (p, x) in
2206 to_capture := cap :: !to_capture;
2209 let lenv = Env.empty_local @@ Some handle_unbound in
2210 let env = (fst env, lenv) in
2211 let f = expr_lambda env f in
2212 N.Lfun (f, !to_capture)
2213 | Aast.Xml (x, al, el) ->
2214 let () = check_name x in
2215 N.Xml (x, attrl env al, exprl env el)
2216 | Aast.Shape fdl ->
2217 let shp =
2218 List.map fdl ~f:(fun (pname, value) ->
2219 (convert_shape_name env pname, expr env value))
2221 N.Shape shp
2222 | Aast.Import _ -> N.Any
2223 | Aast.Omitted -> N.Omitted
2224 | Aast.Callconv (kind, e) -> N.Callconv (kind, expr env e)
2225 | Aast.EnumAtom x -> N.EnumAtom x
2226 | Aast.ReadonlyExpr e -> N.ReadonlyExpr (expr env e)
2227 (* The below were not found on the AST.ml so they are not implemented here *)
2228 | Aast.ValCollection _
2229 | Aast.KeyValCollection _
2230 | Aast.This
2231 | Aast.Dollardollar _
2232 | Aast.Lplaceholder _
2233 | Aast.Fun_id _
2234 | Aast.Method_id _
2235 | Aast.Method_caller _
2236 | Aast.Smethod_id _
2237 | Aast.Pair _
2238 | Aast.Any
2239 | Aast.Hole _ ->
2240 Errors.internal_error
2242 "Malformed expr: Expr not found on legacy AST: T39599317";
2243 Aast.Any
2245 and expr_lambda env f =
2246 let h =
2247 Aast.type_hint_option_map ~f:(hint ~allow_retonly:true env) f.Aast.f_ret
2249 let (variadicity, paraml) = fun_paraml env f.Aast.f_params in
2250 (* The bodies of lambdas go through naming in the containing local
2251 * environment *)
2252 let body_nast = f_body env f.Aast.f_body in
2253 let annotation = Nast.Named in
2254 let f_ctxs = Option.map ~f:(contexts env) f.Aast.f_ctxs in
2255 let f_unsafe_ctxs = Option.map ~f:(contexts env) f.Aast.f_unsafe_ctxs in
2256 (* These could all be probably be replaced with a {... where ...} *)
2257 let body = { N.fb_ast = body_nast; fb_annotation = annotation } in
2259 N.f_annotation = ();
2260 f_readonly_this = f.Aast.f_readonly_this;
2261 f_span = f.Aast.f_span;
2262 f_mode = (fst env).in_mode;
2263 f_readonly_ret = f.Aast.f_readonly_ret;
2264 f_ret = h;
2265 f_name = f.Aast.f_name;
2266 f_params = paraml;
2267 f_tparams = [];
2268 f_ctxs;
2269 f_unsafe_ctxs;
2270 f_where_constraints = [];
2271 f_body = body;
2272 f_fun_kind = f.Aast.f_fun_kind;
2273 f_variadic = variadicity;
2274 f_file_attributes = [];
2275 f_user_attributes = user_attributes env f.Aast.f_user_attributes;
2276 f_external = f.Aast.f_external;
2277 f_namespace = f.Aast.f_namespace;
2278 f_doc_comment = f.Aast.f_doc_comment;
2281 and f_body env f_body =
2282 if Nast.is_body_named f_body then
2283 block env f_body.Aast.fb_ast
2284 else
2285 failwith "Malformed f_body: unexpected UnnamedBody from ast_to_nast"
2287 and make_class_id env ((p, x) as cid) =
2288 ( p,
2289 match x with
2290 | x when String.equal x SN.Classes.cParent ->
2291 if Option.is_none (fst env).current_cls then
2292 let () = Errors.parent_outside_class p in
2293 N.CI (p, SN.Classes.cUnknown)
2294 else
2295 N.CIparent
2296 | x when String.equal x SN.Classes.cSelf ->
2297 if Option.is_none (fst env).current_cls then
2298 let () = Errors.self_outside_class p in
2299 N.CI (p, SN.Classes.cUnknown)
2300 else
2301 N.CIself
2302 | x when String.equal x SN.Classes.cStatic ->
2303 if Option.is_none (fst env).current_cls then
2304 let () = Errors.static_outside_class p in
2305 N.CI (p, SN.Classes.cUnknown)
2306 else
2307 N.CIstatic
2308 | x when String.equal x SN.SpecialIdents.this -> N.CIexpr (p, N.This)
2309 | x when String.equal x SN.SpecialIdents.dollardollar ->
2310 (* We won't reach here for "new $$" because the parser creates a
2311 * proper Ast_defs.Dollardollar node, so make_class_id won't be called with
2312 * that node. In fact, the parser creates an Ast_defs.Dollardollar for all
2313 * "$$" except in positions where a classname is expected, like in
2314 * static member access. So, we only reach here for things
2315 * like "$$::someMethod()". *)
2316 N.CIexpr
2317 (p, N.Lvar (p, Local_id.make_unscoped SN.SpecialIdents.dollardollar))
2318 | x when Char.equal x.[0] '$' -> N.CIexpr (p, N.Lvar (Env.lvar env cid))
2319 | _ ->
2320 let () = check_name cid in
2321 N.CI cid )
2323 and casel env l = List.map l (case env)
2325 and case env c =
2326 match c with
2327 | Aast.Default (p, b) ->
2328 let b = branch env b in
2329 N.Default (p, b)
2330 | Aast.Case (e, b) ->
2331 let e = expr env e in
2332 let b = branch env b in
2333 N.Case (e, b)
2335 and catchl env l = List.map l (catch env)
2337 and catch env ((p1, lid1), (p2, lid2), b) =
2338 Env.scope env (fun env ->
2339 let name2 = Local_id.get_name lid2 in
2340 let x2 = Env.new_lvar env (p2, name2) in
2341 let b = branch env b in
2342 let () = check_name (p1, lid1) in
2343 ((p1, lid1), x2, b))
2345 and afield env field =
2346 match field with
2347 | Aast.AFvalue e -> N.AFvalue (expr env e)
2348 | Aast.AFkvalue (e1, e2) -> N.AFkvalue (expr env e1, expr env e2)
2350 and afield_value env cname field =
2351 match field with
2352 | Aast.AFvalue e -> expr env e
2353 | Aast.AFkvalue (e1, _e2) ->
2354 Errors.unexpected_arrow (fst e1) cname;
2355 expr env e1
2357 and afield_kvalue env cname field =
2358 match field with
2359 | Aast.AFvalue e ->
2360 Errors.missing_arrow (fst e) cname;
2361 ( expr env e,
2362 expr
2364 ( fst e,
2365 Aast.Lvar (fst e, Local_id.make_unscoped "__internal_placeholder") )
2367 | Aast.AFkvalue (e1, e2) -> (expr env e1, expr env e2)
2369 and attrl env l = List.map ~f:(attr env) l
2371 and attr env at =
2372 match at with
2373 | Aast.Xhp_simple { Aast.xs_name; xs_type; xs_expr = e } ->
2374 N.Xhp_simple { Aast.xs_name; xs_type; xs_expr = expr env e }
2375 | Aast.Xhp_spread e -> N.Xhp_spread (expr env e)
2377 and string2 env idl = List.map idl (expr env)
2379 let record_field env rf =
2380 let (id, h, e) = rf in
2381 let h = hint env h in
2382 let e = oexpr env e in
2383 (id, h, e)
2385 let record_def ctx rd =
2386 let env = Env.make_top_level_env ctx in
2387 let rd =
2388 elaborate_namespaces#on_record_def
2389 (Naming_elaborate_namespaces_endo.make_env (fst env).namespace)
2392 let attrs = user_attributes env rd.Aast.rd_user_attributes in
2393 let extends =
2394 match rd.Aast.rd_extends with
2395 | Some extends -> Some (hint env extends)
2396 | None -> None
2398 let fields = List.map rd.Aast.rd_fields ~f:(record_field env) in
2400 N.rd_annotation = ();
2401 rd_name = rd.Aast.rd_name;
2402 rd_abstract = rd.Aast.rd_abstract;
2403 rd_extends = extends;
2404 rd_fields = fields;
2405 rd_user_attributes = attrs;
2406 rd_namespace = rd.Aast.rd_namespace;
2407 rd_span = rd.Aast.rd_span;
2408 rd_doc_comment = rd.Aast.rd_doc_comment;
2409 rd_emit_id = rd.Aast.rd_emit_id;
2412 (**************************************************************************)
2413 (* Typedefs *)
2414 (**************************************************************************)
2416 let typedef ctx tdef =
2417 let env = Env.make_typedef_env ctx tdef in
2418 let tdef =
2419 elaborate_namespaces#on_typedef
2420 (Naming_elaborate_namespaces_endo.make_env (fst env).namespace)
2421 tdef
2423 let tconstraint = Option.map tdef.Aast.t_constraint (hint env) in
2424 let tparaml = type_paraml env tdef.Aast.t_tparams in
2425 let attrs = user_attributes env tdef.Aast.t_user_attributes in
2427 N.t_annotation = ();
2428 t_name = tdef.Aast.t_name;
2429 t_tparams = tparaml;
2430 t_constraint = tconstraint;
2431 t_kind = hint env tdef.Aast.t_kind;
2432 t_user_attributes = attrs;
2433 t_mode = tdef.Aast.t_mode;
2434 t_namespace = tdef.Aast.t_namespace;
2435 t_vis = tdef.Aast.t_vis;
2436 t_span = tdef.Aast.t_span;
2437 t_emit_id = tdef.Aast.t_emit_id;
2440 (**************************************************************************)
2441 (* Global constants *)
2442 (**************************************************************************)
2444 let global_const ctx cst =
2445 let env = Env.make_const_env ctx cst in
2446 let cst =
2447 elaborate_namespaces#on_gconst
2448 (Naming_elaborate_namespaces_endo.make_env (fst env).namespace)
2451 let hint = Option.map cst.Aast.cst_type (hint env) in
2452 let e = constant_expr env false cst.Aast.cst_value in
2454 N.cst_annotation = ();
2455 cst_mode = cst.Aast.cst_mode;
2456 cst_name = cst.Aast.cst_name;
2457 cst_type = hint;
2458 cst_value = e;
2459 cst_namespace = cst.Aast.cst_namespace;
2460 cst_span = cst.Aast.cst_span;
2461 cst_emit_id = cst.Aast.cst_emit_id;
2464 (**************************************************************************)
2465 (* The entry point to CHECK the program, and transform the program *)
2466 (**************************************************************************)
2468 let program ctx ast =
2469 let ast =
2470 elaborate_namespaces#on_program
2471 (Naming_elaborate_namespaces_endo.make_env
2472 Namespace_env.empty_with_default)
2475 let top_level_env = ref (Env.make_top_level_env ctx) in
2476 let rec aux acc def =
2477 match def with
2478 | Aast.Fun f -> N.Fun (fun_ ctx f) :: acc
2479 | Aast.Class c -> N.Class (class_ ctx c) :: acc
2480 | Aast.Stmt (_, Aast.Noop)
2481 | Aast.Stmt (_, Aast.Markup _) ->
2483 | Aast.Stmt s -> N.Stmt (stmt !top_level_env s) :: acc
2484 | Aast.RecordDef rd -> N.RecordDef (record_def ctx rd) :: acc
2485 | Aast.Typedef t -> N.Typedef (typedef ctx t) :: acc
2486 | Aast.Constant cst -> N.Constant (global_const ctx cst) :: acc
2487 | Aast.Namespace (_ns, aast) -> List.fold_left ~f:aux ~init:[] aast @ acc
2488 | Aast.NamespaceUse _ -> acc
2489 | Aast.SetNamespaceEnv nsenv ->
2490 let (genv, lenv) = !top_level_env in
2491 let genv = { genv with namespace = nsenv } in
2492 top_level_env := (genv, lenv);
2494 | Aast.FileAttributes _ -> acc
2496 let on_program aast =
2497 let nast = List.fold_left ~f:aux ~init:[] aast in
2498 List.rev nast
2500 on_program ast