Default case of switch node in AST to keep pos
[hiphop-php.git] / hphp / hack / src / hhbc / closure_convert.ml
blobcbdda5df627af87a9c341c63ac810d0d5041dfce
1 (*
2 * Copyright (c) 2017, 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 open Aast
11 open Tast
12 open Ast_scope
13 open Core_kernel
14 open Common
15 module ULS = Unique_list_string
16 module SN = Naming_special_names
17 module SU = Hhbc_string_utils
19 let constant_folding () =
20 Hhbc_options.constant_folding !Hhbc_options.compiler_options
22 let hacksperimental () =
23 Hhbc_options.hacksperimental !Hhbc_options.compiler_options
25 type hoist_kind =
26 (* Def that is already at top-level *)
27 | TopLevel
28 (* Def that was hoisted to top-level *)
29 | Hoisted
31 type convert_result = {
32 ast_defs: (hoist_kind * def) list;
33 global_state: Emit_env.global_state;
36 type variables = {
37 (* all variables declared/used in the scope*)
38 all_vars: SSet.t;
39 (* names of parameters if scope correspond to a function *)
40 parameter_names: SSet.t;
43 type env = {
44 (* Span of function/method body *)
45 pos: Pos.t;
46 (* What is the current context? *)
47 scope: Scope.t;
48 variable_scopes: variables list;
49 (* How many existing classes are there? *)
50 defined_class_count: int;
51 (* How many existing records are there? *)
52 defined_record_count: int;
53 (* How many existing functions are there? *)
54 defined_function_count: int;
55 (* if we are immediately in using statement *)
56 in_using: bool;
59 type per_function_state = {
60 has_finally: bool;
61 has_goto: bool;
62 labels: bool SMap.t;
65 let empty_per_function_state =
66 { has_finally = false; has_goto = false; labels = SMap.empty }
68 (* let to_empty_state_if_no_goto s =
69 (* if function does not have any goto statements inside - it is ok
70 to ignore any labels that might appear in it *)
71 if s.has_goto then s
72 else empty_goto_state *)
74 type state = {
75 (* Number of closures created in the current function *)
76 closure_cnt_per_fun: int;
77 (* Free variables computed so far *)
78 captured_vars: ULS.t;
79 captured_this: bool;
80 captured_generics: ULS.t;
81 (* Closure classes and hoisted inline classes *)
82 hoisted_classes: class_ list;
83 (* Hoisted inline functions *)
84 hoisted_functions: fun_ list;
85 (* Hoisted meth_caller functions *)
86 named_hoisted_functions: fun_ SMap.t;
87 (* Functions with inout_wrappers *)
88 inout_wrappers: fun_ list;
89 (* The current namespace environment *)
90 namespace: Namespace_env.env;
91 (* Set of closure names that used to have explicit 'use' language construct
92 in original anonymous function *)
93 explicit_use_set: SSet.t;
94 (* Closures get converted into methods on a class. We need to keep
95 track of the original namsepace of the closure in order to
96 properly qualify things when that method's body is emitted. *)
97 closure_namespaces: Namespace_env.env SMap.t;
98 (* original enclosing class for closure *)
99 closure_enclosing_classes: class_ SMap.t;
100 (* information about current function *)
101 current_function_state: per_function_state;
102 (*** accumulated information about program ***)
104 (* set of functions that has try-finally block *)
105 functions_with_finally: SSet.t;
106 (* maps name of function that has at least one goto statement
107 to labels in function (bool value denotes whether label appear in using) *)
108 function_to_labels_map: bool SMap.t SMap.t;
109 (* most recent definition of lexical-scoped `let` variables *)
110 let_vars: int SMap.t;
111 (* maps unique name of lambda to Rx level of the declaring scope *)
112 lambda_rx_of_scope: Rx.t SMap.t;
115 let set_has_finally st =
116 if st.current_function_state.has_finally then
118 else
120 st with
121 current_function_state =
122 { st.current_function_state with has_finally = true };
125 let set_label st l v =
127 st with
128 current_function_state =
130 st.current_function_state with
131 labels = SMap.add l v st.current_function_state.labels;
135 let set_has_goto (st : state) =
136 if st.current_function_state.has_goto then
138 else
140 st with
141 current_function_state =
142 { st.current_function_state with has_goto = true };
145 let initial_state popt =
147 closure_cnt_per_fun = 0;
148 captured_vars = ULS.empty;
149 captured_this = false;
150 captured_generics = ULS.empty;
151 hoisted_classes = [];
152 hoisted_functions = [];
153 named_hoisted_functions = SMap.empty;
154 inout_wrappers = [];
155 namespace = Namespace_env.empty_from_popt popt;
156 explicit_use_set = SSet.empty;
157 closure_namespaces = SMap.empty;
158 closure_enclosing_classes = SMap.empty;
159 current_function_state = empty_per_function_state;
160 functions_with_finally = SSet.empty;
161 function_to_labels_map = SMap.empty;
162 let_vars = SMap.empty;
163 lambda_rx_of_scope = SMap.empty;
166 let total_class_count env st =
167 List.length st.hoisted_classes + env.defined_class_count
169 let set_in_using env =
170 if env.in_using then
172 else
173 { env with in_using = true }
175 let reset_in_using env =
176 if env.in_using then
177 { env with in_using = false }
178 else
181 let is_in_lambda scope =
182 match scope with
183 | ScopeItem.Lambda _
184 | ScopeItem.LongLambda _ ->
185 true
186 | _ -> false
188 let should_capture_var env var =
189 let rec aux scope vars =
190 match (scope, vars) with
191 | ([], [{ all_vars; _ }]) -> SSet.mem var all_vars
192 | (x :: xs, { all_vars; parameter_names } :: vs) ->
193 SSet.mem var all_vars
194 || SSet.mem var parameter_names
195 || (is_in_lambda x && aux xs vs)
196 | _ -> false
198 match (env.scope, env.variable_scopes) with
199 | (_ :: xs, { parameter_names; _ } :: vs) ->
200 (* variable used in lambda should be captured if is
201 - not contained in lambda parameter list
203 - it exists in one of enclosing scopes *)
204 (not (SSet.mem var parameter_names)) && aux xs vs
205 | _ -> false
207 let get_let_var st x =
208 let let_vars = st.let_vars in
209 SMap.get x let_vars
211 let next_let_var_id st x =
212 match get_let_var st x with
213 | Some id -> id + 1
214 | None -> 0
216 let update_let_var_id st x =
217 let id = next_let_var_id st x in
218 (id, { st with let_vars = SMap.add x id st.let_vars })
220 (* We prefix the let variable with "$LET_VAR", and add "$%d" suffix for
221 * distinguishing shadowings
222 * This by construction does not clash with other variables, note that dollar
223 * is not allowed as part of variable name by parser, but HHVM is fine with it.
225 let transform_let_var_name name id = Printf.sprintf "$LET_VAR_%s$%d" name id
227 let append_let_vars env let_vars =
228 match env.variable_scopes with
229 | [] -> env
230 | outermost :: rest ->
231 let all_vars = outermost.all_vars in
232 let rec app var idx all_vars =
233 if idx < 0 then
234 all_vars
235 else
236 let var_name = transform_let_var_name var idx in
237 if SSet.mem var_name all_vars then
238 all_vars
239 else
240 app var (idx - 1) (SSet.add var_name all_vars)
242 let all_vars = SMap.fold app let_vars all_vars in
243 { env with variable_scopes = { outermost with all_vars } :: rest }
245 (* Add a variable to the captured variables *)
246 let add_var env st var =
247 (* Don't bother if it's $this, as this is captured implicitly *)
248 if var = Naming_special_names.SpecialIdents.this then
249 { st with captured_this = true }
250 (* If it's bound as a parameter or definite assignment, don't add it *)
251 (* Also don't add the pipe variable and superglobals *)
252 else if
253 (not (should_capture_var env var))
254 || var = Naming_special_names.SpecialIdents.dollardollar
255 || Naming_special_names.Superglobals.globals = var
256 || Naming_special_names.Superglobals.is_superglobal var
257 then
259 else
260 { st with captured_vars = ULS.add st.captured_vars var }
262 let add_generic env st var =
263 let is_reified_tparam is_fun =
264 let tparams =
265 if is_fun then
266 Ast_scope.Scope.get_fun_tparams env.scope
267 else
268 (Ast_scope.Scope.get_class_tparams env.scope).c_tparam_list
270 List.find_mapi
271 tparams
272 ~f:(fun i { tp_name = (_, id); tp_reified = b; _ } ->
273 if b <> Erased && id = var then
274 Some i
275 else
276 None)
278 match is_reified_tparam true with
279 | Some i ->
280 let var = SU.Reified.reified_generic_captured_name true i in
281 { st with captured_generics = ULS.add st.captured_generics var }
282 | None ->
283 (match is_reified_tparam false with
284 | Some i ->
285 let var = SU.Reified.reified_generic_captured_name false i in
286 { st with captured_generics = ULS.add st.captured_generics var }
287 | None -> st)
289 let get_vars scope ~is_closure_body params body =
290 let has_this = Scope.has_this scope in
291 let is_toplevel = Scope.is_toplevel scope in
292 let is_in_static_method = Scope.is_in_static_method scope in
293 Decl_vars.vars_from_ast
294 ~is_closure_body
295 ~has_this
296 ~params
297 ~is_toplevel
298 ~is_in_static_method
299 body
301 let wrap_block b = [Stmt (Pos.none, Block b)]
303 let get_parameter_names (params : fun_param list) =
304 List.fold_left
305 ~init:SSet.empty
306 ~f:(fun s p -> SSet.add p.param_name s)
307 params
309 let env_with_function_like_ env e ~is_closure_body params pos body =
310 let scope = e :: env.scope in
311 let all_vars = get_vars scope ~is_closure_body params (wrap_block body) in
312 let parameter_names = get_parameter_names params in
314 env with
315 scope;
316 pos;
317 variable_scopes = { all_vars; parameter_names } :: env.variable_scopes;
320 let env_with_function_like env e ~is_closure_body fd =
321 env_with_function_like_
324 ~is_closure_body
325 fd.f_params
326 fd.f_span
327 fd.f_body.fb_ast
329 let fun_is_async = function
330 | Ast_defs.FAsync
331 | Ast_defs.FAsyncGenerator ->
332 true
333 | _ -> false
335 let env_with_lambda env fd =
336 let is_async = fun_is_async fd.f_fun_kind in
337 let rx_level = Rx.rx_level_from_ast fd.f_user_attributes in
338 env_with_function_like
340 (ScopeItem.Lambda (is_async, rx_level))
341 ~is_closure_body:true
344 let env_with_longlambda env is_static fd =
345 let is_async = fun_is_async fd.f_fun_kind in
346 let rx_level = Rx.rx_level_from_ast fd.f_user_attributes in
347 env_with_function_like
349 (ScopeItem.LongLambda (is_static, is_async, rx_level))
350 ~is_closure_body:true
353 let strip_id id = SU.strip_global_ns (snd id)
355 let make_class_name cd = SU.Xhp.mangle_id (strip_id cd.c_name)
357 let rec make_scope_name ns (scope : Ast_scope.Scope.t) =
358 match scope with
359 | [] ->
360 begin
361 match ns.Namespace_env.ns_name with
362 | None -> ""
363 | Some n -> n ^ "\\"
365 | ScopeItem.Function fd :: scope ->
366 let fname = strip_id fd.f_name in
367 begin
368 match Scope.get_class scope with
369 | None -> fname
370 | Some cd -> make_class_name cd ^ "::" ^ fname
372 | ScopeItem.Method md :: scope ->
373 let scope_name = make_scope_name ns scope in
374 let scope_name =
375 scope_name
377 if String_utils.string_ends_with scope_name "::" then
379 else
380 "::"
382 scope_name ^ strip_id md.m_name
383 | ScopeItem.Class cd :: _ -> make_class_name cd
384 | _ :: scope -> make_scope_name ns scope
386 let env_with_function env fd =
387 env_with_function_like env (ScopeItem.Function fd) ~is_closure_body:false fd
389 let env_toplevel class_count record_count function_count defs =
390 let scope = Scope.toplevel in
391 let all_vars = get_vars scope ~is_closure_body:false [] defs in
393 scope;
394 pos = Pos.none;
395 variable_scopes = [{ all_vars; parameter_names = SSet.empty }];
396 defined_class_count = class_count;
397 defined_record_count = record_count;
398 defined_function_count = function_count;
399 in_using = false;
402 let env_with_method (env : env) md =
403 env_with_function_like_
405 (ScopeItem.Method md)
406 ~is_closure_body:false
407 md.m_params
408 md.m_span
409 md.m_body.fb_ast
411 let env_with_class env cd =
413 env with
414 scope = [ScopeItem.Class cd];
415 variable_scopes = env.variable_scopes;
418 (* Clear the variables, upon entering a lambda *)
419 let enter_lambda (st : state) =
421 st with
422 captured_vars = ULS.empty;
423 captured_this = false;
424 captured_generics = ULS.empty;
427 let set_namespace st ns = { st with namespace = ns }
429 let reset_function_counts st = { st with closure_cnt_per_fun = 0 }
431 let record_function_state key { has_finally; has_goto; labels } rx_of_scope st
434 (not has_finally)
435 && (not has_goto)
436 && SMap.is_empty labels
437 && rx_of_scope = Rx.NonRx
438 then
440 else
441 let functions_with_finally =
442 if has_finally then
443 SSet.add key st.functions_with_finally
444 else
445 st.functions_with_finally
447 let function_to_labels_map =
448 if not @@ SMap.is_empty labels then
449 SMap.add key labels st.function_to_labels_map
450 else
451 st.function_to_labels_map
453 let lambda_rx_of_scope =
454 if rx_of_scope <> Rx.NonRx then
455 SMap.add key rx_of_scope st.lambda_rx_of_scope
456 else
457 st.lambda_rx_of_scope
460 st with
461 functions_with_finally;
462 function_to_labels_map;
463 lambda_rx_of_scope;
466 (* Make a stub class purely for the purpose of emitting the DefCls instruction
468 let make_defcls cd n =
470 cd with
471 c_method_redeclarations = [];
472 c_consts = [];
473 c_typeconsts = [];
474 c_vars = [];
475 c_methods = [];
476 c_xhp_children = [];
477 c_xhp_attrs = [];
478 c_name = (fst cd.c_name, string_of_int n);
481 (* Make a stub record purely for the purpose of emitting the DefRecord instruction
483 let make_defrecord (cd : class_) n : class_ =
485 cd with
486 c_method_redeclarations = [];
487 c_consts = [];
488 c_typeconsts = [];
489 c_vars = [];
490 c_methods = [];
491 c_xhp_children = [];
492 c_xhp_attrs = [];
493 c_kind = Ast_defs.Crecord;
494 c_name = (fst cd.c_name, string_of_int n);
497 (* Def inline is not implemented yet *)
498 (** let add_class env st cd =
499 * let n = env.defined_class_count + List.length st.hoisted_classes in
500 * { st with hoisted_classes = cd :: st.hoisted_classes },
501 * make_defcls cd n
503 * let add_record env st cd =
504 * st, make_defrecord cd env.defined_record_count *)
506 let make_closure_name env st name =
507 let per_fun_idx = st.closure_cnt_per_fun in
508 SU.Closures.mangle_closure
509 (make_scope_name st.namespace env.scope)
510 per_fun_idx
511 name
513 (* Get the user-provided closure name from the set of user attributes. This is
514 * only allowed in systemlib and in transpiled javascript, otherwise we ignore the
515 * attribute
517 * Returns the filtered list of attributes and the closure name
519 let get_closure_name attrs =
520 let is_closure_name attr = snd attr.ua_name = "__ClosureName" in
521 if Emit_env.is_systemlib () || Emit_env.is_js () then
522 match List.find attrs is_closure_name with
523 | Some { ua_params = [(_, String s)]; _ } ->
524 (List.filter attrs (Fn.compose not is_closure_name), Some s)
525 | _ -> (attrs, None)
526 else
527 (attrs, None)
529 let make_closure
530 ~class_num
532 (env : env)
533 (st : state)
534 lambda_vars
535 (fun_tparams : tparam list)
536 (class_tparams : class_tparams)
537 is_static
539 (body : func_body) =
540 let (user_attrs, name) = get_closure_name fd.f_user_attributes in
541 let md =
543 m_span = fd.f_span;
544 m_annotation = fd.f_annotation;
545 m_final = false;
546 m_abstract = false;
547 m_static = is_static;
548 m_visibility = Aast.Public;
549 m_name = (fst fd.f_name, "__invoke");
550 m_tparams = fun_tparams;
551 m_where_constraints = fd.f_where_constraints;
552 m_variadic = fd.f_variadic;
553 m_params = fd.f_params;
554 m_body = body;
555 m_fun_kind = fd.f_fun_kind;
556 m_user_attributes = user_attrs;
557 m_ret = fd.f_ret;
558 m_external = false;
559 m_doc_comment = fd.f_doc_comment;
562 let make_class_var name : class_var =
564 cv_final = false;
565 cv_xhp_attr = None;
566 cv_abstract = false;
567 cv_visibility = Aast.Private;
568 cv_type = None;
569 cv_id = (p, name);
570 cv_expr = None;
571 cv_user_attributes = [];
572 cv_doc_comment = None;
573 cv_is_promoted_variadic = false;
574 cv_is_static = false;
575 cv_span = p;
578 let cvl =
579 List.map lambda_vars (fun name ->
580 make_class_var (Hhbc_string_utils.Locals.strip_dollar name))
582 let cd =
584 c_span = p;
585 c_annotation = fd.f_annotation;
586 c_mode = fd.f_mode;
587 c_user_attributes = [];
588 c_file_attributes = [];
589 c_final = false;
590 c_is_xhp = false;
591 c_kind = Ast_defs.Cnormal;
592 c_name = (p, make_closure_name env st name);
593 c_tparams = class_tparams;
594 c_extends = [(p, Aast.Happly ((p, "Closure"), []))];
595 c_uses = [];
596 c_use_as_alias = [];
597 c_insteadof_alias = [];
598 c_method_redeclarations = [];
599 c_xhp_attr_uses = [];
600 c_xhp_category = None;
601 c_reqs = [];
602 c_implements = [];
603 c_where_constraints = [];
604 c_consts = [];
605 c_typeconsts = [];
606 c_vars = cvl;
607 c_methods = [md];
608 c_attributes = [];
609 c_xhp_children = [];
610 c_xhp_attrs = [];
611 c_namespace = Namespace_env.empty_with_default;
612 c_enum = None;
613 c_doc_comment = None;
614 c_pu_enums = [];
617 let inline_fundef =
619 fd with
620 f_body = body;
621 f_static = is_static;
622 f_name = (p, string_of_int class_num);
625 (inline_fundef, cd, md)
627 (* Translate special identifiers __CLASS__, __METHOD__ and __FUNCTION__ into
628 * literal strings. It's necessary to do this before closure conversion
629 * because the enclosing class will be changed. *)
630 let convert_id (env : env) p ((pid, str) as id) =
631 let str = String.uppercase str in
632 let return newstr = (p, String newstr) in
633 let name c = (p, String (SU.Xhp.mangle @@ strip_id c.c_name)) in
634 match str with
635 | "__TRAIT__" ->
636 begin
637 match Scope.get_class env.scope with
638 | Some c when c.c_kind = Ast_defs.Ctrait -> name c
639 | _ -> return ""
641 | "__CLASS__" ->
642 begin
643 match Scope.get_class env.scope with
644 | Some c when c.c_kind <> Ast_defs.Ctrait -> name c
645 | Some _ -> (p, Id (pid, snd id))
646 | None -> return ""
648 | "__METHOD__" ->
649 let (prefix, is_trait) =
650 match Scope.get_class env.scope with
651 | None -> ("", false)
652 | Some cd ->
653 ( (SU.Xhp.mangle @@ strip_id cd.c_name) ^ "::",
654 cd.c_kind = Ast_defs.Ctrait )
656 let scope =
657 if not is_trait then
658 env.scope
659 (* for lambdas nested in trait methods HHVM replaces __METHOD__
660 with enclosing method name - do the same and bubble up from lambdas *)
661 else
662 List.drop_while env.scope ~f:(function
663 | ScopeItem.Lambda _
664 | ScopeItem.LongLambda _ ->
665 true
666 | _ -> false)
668 begin
669 match scope with
670 | ScopeItem.Function fd :: _ -> return (prefix ^ strip_id fd.f_name)
671 | ScopeItem.Method md :: _ -> return (prefix ^ strip_id md.m_name)
672 | (ScopeItem.Lambda _ | ScopeItem.LongLambda _) :: _ ->
673 return (prefix ^ "{closure}")
674 (* PHP weirdness: __METHOD__ inside a class outside a method
675 * returns class name *)
676 | ScopeItem.Class cd :: _ -> return @@ strip_id cd.c_name
677 | _ -> return ""
679 | "__FUNCTION__" ->
680 begin
681 match env.scope with
682 | ScopeItem.Function fd :: _ -> return (strip_id fd.f_name)
683 | ScopeItem.Method md :: _ -> return (strip_id md.m_name)
684 | (ScopeItem.Lambda _ | ScopeItem.LongLambda _) :: _ ->
685 return "{closure}"
686 | _ -> return ""
688 | "__LINE__" ->
689 (* If the expression goes on multi lines, we return the last line *)
690 let (_, line, _, _) = Pos.info_pos_extended pid in
691 (p, Int (string_of_int line))
692 | _ -> (p, Id id)
694 let check_if_in_async_context { scope; pos; _ } =
695 let check_valid_fun_kind (_, name) fk =
696 if not (fun_is_async fk) then
697 Emit_fatal.raise_fatal_parse pos
698 @@ "Function '"
699 ^ SU.strip_global_ns name
700 ^ "' contains 'await' but is not declared as async."
702 match scope with
703 | [] ->
704 Emit_fatal.raise_fatal_parse
706 "'await' can only be used inside a function"
707 | ScopeItem.Lambda (is_async, _) :: _
708 | ScopeItem.LongLambda (_, is_async, _) :: _ ->
709 if not is_async then
710 Emit_fatal.raise_fatal_parse
712 "Await may only appear in an async function"
713 | ScopeItem.Class _ :: _ -> () (* Syntax error, wont get here *)
714 | ScopeItem.Function fd :: _ -> check_valid_fun_kind fd.f_name fd.f_fun_kind
715 | ScopeItem.Method md :: _ -> check_valid_fun_kind md.m_name md.m_fun_kind
717 (* meth_caller helpers *)
718 let rec get_scope_fmode scope =
719 match scope with
720 | [] -> FileInfo.Mstrict
721 | ScopeItem.Class cd :: _ -> cd.c_mode
722 | ScopeItem.Function fd :: _ -> fd.f_mode
723 | _ :: scope -> get_scope_fmode scope
725 let make_fn_param (p, lid) is_variadic =
727 param_annotation = Tast_annotate.null_annotation p;
728 param_type_hint = (Typing_make_type.null Tast_annotate.witness, None);
729 param_is_reference = false;
730 param_is_variadic = is_variadic;
731 param_pos = p;
732 param_name = Local_id.get_name lid;
733 param_expr = None;
734 param_callconv = None;
735 param_user_attributes = [];
736 param_visibility = None;
739 let convert_meth_caller_to_func_ptr env st ann pc cls pf func =
740 (* TODO: Use annotation instead of just the position. Needs cleanup in caller.
741 * Remove the following line *)
742 let p = fst ann in
743 let mangle_name = SU.mangle_meth_caller cls func in
744 (* Call __SystemLib\fun() to directly emit function ptr *)
745 let fun_handle =
746 Tast_annotate.with_pos p
747 @@ Call
748 ( Aast.Cnormal,
749 Tast_annotate.with_pos p (Id (p, "\\__systemlib\\fun")),
751 [Tast_annotate.with_pos p (String mangle_name)],
752 [] )
754 if SMap.has_key mangle_name st.named_hoisted_functions then
755 (st, fun_handle)
756 else
757 (* Build a new meth_caller function *)
758 (* invariant(is_a($o, <cls>), 'object must be an instance of <cls>'); *)
759 let obj_var = (p, Local_id.make_unscoped "$o") in
760 let obj_lvar = Tast_annotate.with_pos p (Lvar obj_var) in
761 let assert_invariant =
762 Tast_annotate.with_pos p
763 @@ Call
764 ( Aast.Cnormal,
765 Tast_annotate.with_pos p (Id (p, "invariant")),
767 [ Tast_annotate.with_pos p
768 @@ Call
769 ( Aast.Cnormal,
770 Tast_annotate.with_pos p (Id (p, "is_a")),
772 [obj_lvar; Tast_annotate.with_pos pc (String cls)],
773 [] );
774 Tast_annotate.with_pos
776 (String ("object must be an instance of (" ^ cls ^ ")")) ],
777 [] )
779 (* return $o-><func>(...$args); *)
780 let args_var = (p, Local_id.make_unscoped "$args") in
781 let meth_caller_handle =
782 Tast_annotate.with_pos p
783 @@ Call
784 ( Aast.Cnormal,
785 Tast_annotate.with_pos p
786 @@ Obj_get
787 ( obj_lvar,
788 Tast_annotate.with_pos p (Id (pf, func)),
789 Aast.OG_nullthrows ),
792 [Tast_annotate.with_pos p (Lvar args_var)] )
794 let variadic_param = make_fn_param args_var true in
795 let fd =
797 f_span = p;
798 f_annotation = dummy_saved_env;
799 f_mode = get_scope_fmode env.scope;
800 f_ret = dummy_type_hint;
801 f_name = (p, mangle_name);
802 f_tparams = [];
803 f_where_constraints = [];
804 f_variadic = FVvariadicArg variadic_param;
805 f_params = [make_fn_param obj_var false; variadic_param];
806 f_body =
808 fb_ast =
809 [ (p, Expr assert_invariant);
810 (p, Return (Some meth_caller_handle)) ];
811 fb_annotation = Tast.NoUnsafeBlocks;
813 f_fun_kind = Ast_defs.FSync;
814 f_user_attributes = [{ ua_name = (p, "__MethCaller"); ua_params = [] }];
815 f_file_attributes = [];
816 f_external = false;
817 f_namespace = Namespace_env.empty_with_default;
818 f_doc_comment = None;
819 f_static = false;
822 let named_hoisted_functions =
823 SMap.add mangle_name fd st.named_hoisted_functions
825 ({ st with named_hoisted_functions }, fun_handle)
827 let rec convert_expr env st ((p, expr_) as expr) =
828 Tast.(
829 match expr_ with
830 | Null
831 | True
832 | False
833 | Omitted
834 | Any
835 | Yield_break
836 | Int _
837 | Float _
838 | String _ ->
839 (st, expr)
840 | Varray (targ, es) ->
841 let (st, es) = List.map_env st es (convert_expr env) in
842 let (st, targ) =
843 match targ with
844 | None -> (st, None)
845 | Some targ ->
846 let (st, targ) = convert_hint env st targ in
847 (st, Some targ)
849 (st, (p, Varray (targ, es)))
850 | Darray (tarp, es) ->
851 let convert_pair st (e1, e2) =
852 let (st, e1) = convert_expr env st e1 in
853 let (st, e2) = convert_expr env st e2 in
854 (st, (e1, e2))
856 let convert_tarp st (t1, t2) =
857 let (st, t1) = convert_hint env st t1 in
858 let (st, t2) = convert_hint env st t2 in
859 (st, (t1, t2))
861 let (st, es) = List.map_env st es convert_pair in
862 begin
863 match tarp with
864 | Some typepair ->
865 let (st, tp) = convert_tarp st typepair in
866 (st, (p, Darray (Some tp, es)))
867 | None -> (st, (p, Darray (None, es)))
869 | Array afl ->
870 let (st, afl) = List.map_env st afl (convert_afield env) in
871 (st, (p, Array afl))
872 | Shape pairs ->
873 let (st, pairs) =
874 List.map_env st pairs (fun st (n, e) ->
875 let (st, e) = convert_expr env st e in
876 (st, (n, e)))
878 (st, (p, Shape pairs))
879 | Collection (id, targs, afl) ->
880 let (st, afl) = List.map_env st afl (convert_afield env) in
881 let (st, ta) =
882 match targs with
883 | Some (CollectionTV tv) ->
884 let (st, ta) = convert_hint env st tv in
885 (st, Some (CollectionTV ta))
886 | Some (CollectionTKV (tk, tv)) ->
887 let (st, tk) = convert_hint env st tk in
888 let (st, tv) = convert_hint env st tv in
889 (st, Some (CollectionTKV (tk, tv)))
890 | None -> (st, None)
892 (st, (p, Collection (id, ta, afl)))
893 | ValCollection (k, targ, es) ->
894 let (st, es) = List.map_env st es (convert_expr env) in
895 let (st, targ) =
896 match targ with
897 | None -> (st, None)
898 | Some targ ->
899 let (st, targ) = convert_hint env st targ in
900 (st, Some targ)
902 (st, (p, ValCollection (k, targ, es)))
903 | Pair (e1, e2) ->
904 let (st, e1) = convert_expr env st e1 in
905 let (st, e2) = convert_expr env st e2 in
906 (st, (p, Pair (e1, e2)))
907 | KeyValCollection (k, targ, es) ->
908 let rec zip x y =
909 match (x, y) with
910 | ([], []) -> []
911 | (x :: xs, y :: ys) -> (x, y) :: zip xs ys
912 | _ -> failwith "lists of different lengths"
914 let key_exprs = List.map es fst in
915 let val_exprs = List.map es snd in
916 let (st, key_exprs) = List.map_env st key_exprs (convert_expr env) in
917 let (st, val_exprs) = List.map_env st val_exprs (convert_expr env) in
918 let es = zip key_exprs val_exprs in
919 let (st, targ) =
920 match targ with
921 | None -> (st, None)
922 | Some (t1, t2) ->
923 let (st, t1) = convert_hint env st t1 in
924 let (st, t2) = convert_hint env st t2 in
925 (st, Some (t1, t2))
927 (st, (p, KeyValCollection (k, targ, es)))
928 | Lvar id ->
929 let st = add_var env st (Local_id.get_name (snd id)) in
930 (st, (p, Lvar id))
931 | Clone e ->
932 let (st, e) = convert_expr env st e in
933 (st, (p, Clone e))
934 | Obj_get (e1, e2, flavor) ->
935 let (st, e1) = convert_expr env st e1 in
936 let (st, e2) = convert_prop_expr env st e2 in
937 (st, (p, Obj_get (e1, e2, flavor)))
938 | Array_get (e1, opt_e2) ->
939 let (st, e1) = convert_expr env st e1 in
940 let (st, opt_e2) = convert_opt_expr env st opt_e2 in
941 (st, (p, Array_get (e1, opt_e2)))
942 | Call
943 ( ct,
944 ((_, Id (_, meth_caller)) as e),
945 targs,
946 ([((pc, _), cls); ((pf, _), func)] as el2),
947 [] )
948 when let name = String.lowercase @@ SU.strip_global_ns meth_caller in
949 (name = "hh\\meth_caller" || name = "meth_caller")
950 && Hhbc_options.emit_meth_caller_func_pointers
951 !Hhbc_options.compiler_options ->
952 (match (cls, func) with
953 | ((Class_const _ | String _), String fname) ->
954 let cls =
955 match cls with
956 | Class_const (cid, (_, cs)) when SU.is_class cs ->
957 let (_, (_, ex)) = convert_class_id env st cid in
958 let get_mangle_cls_name =
959 match ex with
960 | CIexpr (_, Id (pc, id))
961 when (not (SU.is_self id))
962 && (not (SU.is_parent id))
963 && not (SU.is_static id) ->
964 let fq_id = Hhbc_id.Class.elaborate_id st.namespace (pc, id) in
965 Hhbc_id.Class.to_raw_string fq_id
966 | _ -> Emit_fatal.raise_fatal_parse pc "Invalid class"
968 get_mangle_cls_name
969 | String name -> name
970 | _ ->
971 Emit_fatal.raise_fatal_parse
973 "Class must be a Class or string type"
975 convert_meth_caller_to_func_ptr env st p pc cls pf fname
976 | _ ->
977 (* For other cases, fallback to create __SystemLib\MethCallerHelper *)
978 (st, (p, Call (ct, e, targs, el2, []))))
979 | Call
980 ( ct,
981 ( ( (_, Class_get ((_, CIexpr (_, Id (_, cid))), _))
982 | (_, Class_const ((_, CIexpr (_, Id (_, cid))), _)) ) as e ),
983 targs,
984 el2,
985 el3 )
986 when SU.is_parent cid ->
987 let st = add_var env st "$this" in
988 let (st, e) = convert_expr env st e in
989 let (st, targs) = convert_hints env st targs in
990 let (st, el2) = convert_exprs env st el2 in
991 let (st, el3) = convert_exprs env st el3 in
992 (st, (p, Call (ct, e, targs, el2, el3)))
993 | Call (_, (_, Id (_, id)), _, es, _) when String.lowercase id = "tuple" ->
994 convert_expr env st (p, Varray (None, es))
995 | Call (ct, e, targs, el2, el3) ->
996 let (st, e) = convert_expr env st e in
997 let (st, targs) = convert_hints env st targs in
998 let (st, el2) = convert_exprs env st el2 in
999 let (st, el3) = convert_exprs env st el3 in
1000 (st, (p, Call (ct, e, targs, el2, el3)))
1001 | String2 el ->
1002 let (st, el) = convert_exprs env st el in
1003 (st, (p, String2 el))
1004 | Yield af ->
1005 let (st, af) = convert_afield env st af in
1006 (st, (p, Yield af))
1007 | Await e ->
1008 check_if_in_async_context env;
1009 let (st, e) = convert_expr env st e in
1010 (st, (p, Await e))
1011 | List el ->
1012 let (st, el) = convert_exprs env st el in
1013 (st, (p, List el))
1014 | Expr_list el ->
1015 let (st, el) = convert_exprs env st el in
1016 (st, (p, Expr_list el))
1017 | Cast (h, e) ->
1018 let (st, e) = convert_expr env st e in
1019 (st, (p, Cast (h, e)))
1020 | Unop (op, e) ->
1021 let (st, e) = convert_expr env st e in
1022 (st, (p, Unop (op, e)))
1023 | Binop (op, e1, e2) ->
1024 let (st, e1) = convert_expr env st e1 in
1025 let (st, e2) = convert_expr env st e2 in
1026 (st, (p, Binop (op, e1, e2)))
1027 | Pipe (id, e1, e2) ->
1028 let (st, e1) = convert_expr env st e1 in
1029 let (st, e2) = convert_expr env st e2 in
1030 (st, (p, Pipe (id, e1, e2)))
1031 | Eif (e1, opt_e2, e3) ->
1032 let (st, e1) = convert_expr env st e1 in
1033 let (st, opt_e2) = convert_opt_expr env st opt_e2 in
1034 let (st, e3) = convert_expr env st e3 in
1035 (st, (p, Eif (e1, opt_e2, e3)))
1036 | Is (e, h) ->
1037 let (st, e) = convert_expr env st e in
1038 let (st, h) = convert_hint env st h in
1039 (st, (p, Is (e, h)))
1040 | As (e, h, b) ->
1041 let (st, e) = convert_expr env st e in
1042 let (st, h) = convert_hint env st h in
1043 (st, (p, As (e, h, b)))
1044 | New (cid, targs, el1, el2, annot) ->
1045 let (st, cid) = convert_class_id env st cid in
1046 let (st, targs) = convert_hints env st targs in
1047 let (st, el1) = convert_exprs env st el1 in
1048 let (st, el2) = convert_exprs env st el2 in
1049 (st, (p, New (cid, targs, el1, el2, annot)))
1050 | Record (cid, is_array, es) ->
1051 let (st, cid) = convert_class_id env st cid in
1052 let convert_pair st (e1, e2) =
1053 let (st, e1) = convert_expr env st e1 in
1054 let (st, e2) = convert_expr env st e2 in
1055 (st, (e1, e2))
1057 let (st, es) = List.map_env st es convert_pair in
1058 (st, (p, Record (cid, is_array, es)))
1059 | Efun (fd, use_vars) -> convert_lambda env st p fd (Some use_vars)
1060 | Lfun (fd, _) -> convert_lambda env st p fd None
1061 | Xml (id, pairs, el) ->
1062 let (st, pairs) = List.map_env st pairs (convert_xhp_attr env) in
1063 let (st, el) = convert_exprs env st el in
1064 (st, (p, Xml (id, pairs, el)))
1065 | BracedExpr e ->
1066 let (st, e) = convert_expr env st e in
1067 (* For strings and lvars we should elide the braces *)
1068 begin
1069 match e with
1070 | (_, Lvar _)
1071 | (_, String _) ->
1072 (st, e)
1073 | _ -> (st, (p, BracedExpr e))
1075 | Import (flavor, e) ->
1076 let (st, e) = convert_expr env st e in
1077 (st, (p, Import (flavor, e)))
1078 | Id (_, id) as ast_id when String_utils.string_starts_with id "$" ->
1079 let st = add_var env st id in
1080 let st = add_generic env st id in
1081 (st, (p, ast_id))
1082 | Id ((pos, var) as id) ->
1083 (match get_let_var st var with
1084 | Some idx ->
1085 let lvar_name = transform_let_var_name var idx in
1086 let st = add_var env st lvar_name in
1087 (st, (p, Lvar (pos, Local_id.make_scoped lvar_name)))
1088 | None ->
1089 let st = add_generic env st var in
1090 (st, convert_id env p id))
1091 | Class_get (cid, n) ->
1092 let (st, cid) = convert_class_id env st cid in
1093 let (st, n) =
1094 match n with
1095 | CGstring id ->
1096 (* TODO: (thomasjiang) T43412864 This does not need to be added into the closure and can be removed *)
1097 let st = add_var env st (snd id) in
1098 (st, n)
1099 | CGexpr e ->
1100 let (st, e) = convert_expr env st e in
1101 (st, CGexpr e)
1103 (st, (p, Class_get (cid, n)))
1104 | Class_const (cid, n) ->
1105 let (st, cid) = convert_class_id env st cid in
1106 (st, (p, Class_const (cid, n)))
1107 | PrefixedString (s, e) ->
1108 let (st, e) = convert_expr env st e in
1109 (st, (p, PrefixedString (s, e)))
1110 | Yield_from e ->
1111 let (st, e) = convert_expr env st e in
1112 (st, (p, Yield_from e))
1113 | Suspend e ->
1114 let (st, e) = convert_expr env st e in
1115 (st, (p, Suspend e))
1116 | ParenthesizedExpr e ->
1117 let (st, e) = convert_expr env st e in
1118 (st, (p, ParenthesizedExpr e))
1119 | Callconv (k, e) ->
1120 let (st, e) = convert_expr env st e in
1121 (st, (p, Callconv (k, e)))
1122 | This
1123 | Lplaceholder _
1124 | Dollardollar _ ->
1125 failwith "TODO Codegen after naming pass on AAST"
1126 | ImmutableVar _ -> failwith "Codegen for 'let' is not supported"
1127 | Fun_id _ -> failwith "TODO Unimplemented closure_convert Fun_id"
1128 | Method_id (_, _) ->
1129 failwith "TODO Unimplemented closure_convert Method_id"
1130 | Method_caller (_, _) ->
1131 failwith "TODO Unimplemented closure_convert Method_caller"
1132 | Smethod_id (_, _) ->
1133 failwith "TODO Unimplemented closure_convert Smethod_id"
1134 | Special_func _ ->
1135 failwith "TODO Unimplemented closure_convert Special_func"
1136 | Assert _ -> failwith "TODO Unimplemented closure_convert Assert"
1137 | Typename id -> (st, (p, Typename id))
1138 | PU_atom _
1139 | PU_identifier _ ->
1140 failwith "TODO(T35357243): Pocket Universes syntax must be erased by now")
1142 and convert_class_id env st (cid : class_id) =
1143 let (annot, cid_) = cid in
1144 match cid_ with
1145 | CIexpr e ->
1146 let (st, e) = convert_expr env st e in
1147 (st, (annot, CIexpr e))
1148 | CI _
1149 | CIparent
1150 | CIself
1151 | CIstatic ->
1152 (st, cid)
1154 and convert_prop_expr env st ((_, expr_) as expr) =
1155 match expr_ with
1156 | Id (_, id) when not (String_utils.string_starts_with id "$") -> (st, expr)
1157 | _ -> convert_expr env st expr
1159 and convert_snd_expr env st (a, b_exp) =
1160 let (s, b_exp) = convert_expr env st b_exp in
1161 (s, (a, b_exp))
1163 and convert_hint env st ((p, h) as hint) =
1164 match h with
1165 | Happly (((_, id) as ast_id), hl) ->
1166 let st = add_generic env st id in
1167 let (st, hl) = convert_hints env st hl in
1168 (st, (p, Happly (ast_id, hl)))
1169 | Hoption h ->
1170 let (st, h) = convert_hint env st h in
1171 (st, (p, Hoption h))
1172 | Hlike h ->
1173 let (st, h) = convert_hint env st h in
1174 (st, (p, Hlike h))
1175 | Hsoft h ->
1176 let (st, h) = convert_hint env st h in
1177 (st, (p, Hsoft h))
1178 | Htuple hl ->
1179 let (st, hl) = convert_hints env st hl in
1180 (st, (p, Htuple hl))
1181 | Hshape { nsi_allows_unknown_fields; nsi_field_map } ->
1182 let (st, nsi_field_map) =
1183 List.fold_left
1184 ~f:(fun (st, acc) sfi ->
1185 let (st, h) = convert_hint env st sfi.sfi_hint in
1186 (st, { sfi with sfi_hint = h } :: acc))
1187 ~init:(st, [])
1188 nsi_field_map
1190 let nsi_field_map = List.rev nsi_field_map in
1191 let info = { nsi_allows_unknown_fields; nsi_field_map } in
1192 (st, (p, Hshape info))
1193 | Haccess _
1194 | Hfun _ ->
1195 (st, hint)
1196 | _ ->
1197 failwith "TODO Unimplemented convert_hints hints not present in legacy AST"
1199 (* Closure-convert a lambda expression, with use_vars_opt = Some vars
1200 * if there is an explicit `use` clause.
1202 and convert_lambda env st p fd use_vars_opt =
1203 (* Remember the current capture and defined set across the lambda *)
1204 let captured_vars = st.captured_vars in
1205 let captured_this = st.captured_this in
1206 let captured_generics = st.captured_generics in
1207 let old_function_state = st.current_function_state in
1208 let st = enter_lambda st in
1209 let old_env = env in
1210 Option.iter
1211 use_vars_opt
1213 (List.iter ~f:(fun (p, id) ->
1214 if Local_id.get_name id = SN.SpecialIdents.this then
1215 Emit_fatal.raise_fatal_parse
1217 "Cannot use $this as lexical variable"));
1218 let env = append_let_vars env st.let_vars in
1219 let rx_of_scope = Scope.rx_of_scope env.scope in
1220 let env =
1221 if Option.is_some use_vars_opt then
1222 env_with_longlambda env false fd
1223 else
1224 env_with_lambda env fd
1226 let (st, block, function_state) =
1227 convert_function_like_body env st fd.f_body
1229 let st = { st with closure_cnt_per_fun = st.closure_cnt_per_fun + 1 } in
1230 let st =
1231 List.filter_map
1232 ~f:(fun p -> hint_of_type_hint p.param_type_hint)
1233 fd.f_params
1234 |> convert_hints env st
1235 |> fst
1237 let st =
1238 match hint_of_type_hint fd.f_ret with
1239 | None -> st
1240 | Some h -> fst @@ convert_hint env st h
1242 let current_generics = ULS.items st.captured_generics in
1243 let fresh_lid name : Aast.lid = (Pos.none, Local_id.make_scoped name) in
1244 let lid_name (lid : Aast.lid) : string = Local_id.get_name (snd lid) in
1245 (* HHVM lists lambda vars in descending order - do the same *)
1246 let lambda_vars =
1247 List.sort ~compare:(fun a b -> compare b a)
1248 @@ ULS.items st.captured_vars
1249 @ current_generics
1251 (* For lambdas with explicit `use` variables, we ignore the computed
1252 * capture set and instead use the explicit set *)
1253 let (lambda_vars, use_vars) =
1254 match use_vars_opt with
1255 | None -> (lambda_vars, List.map lambda_vars fresh_lid)
1256 | Some use_vars ->
1257 (* Remove duplicates (not efficient, but unlikely to be large),
1258 * remove variables that are actually just parameters *)
1259 let use_vars =
1260 List.fold_right use_vars ~init:[] ~f:(fun use_var use_vars ->
1262 List.exists use_vars (fun var' ->
1263 lid_name use_var = lid_name var')
1264 || List.exists fd.f_params (fun p ->
1265 lid_name use_var = p.param_name)
1266 then
1267 use_vars
1268 else
1269 use_var :: use_vars)
1271 (* We still need to append the generics *)
1272 ( List.map use_vars lid_name @ current_generics,
1273 use_vars @ List.map current_generics fresh_lid )
1275 let fun_tparams = Scope.get_fun_tparams env.scope in
1276 let class_tparams = Scope.get_class_tparams env.scope in
1277 let class_num = total_class_count env st in
1278 let rec is_scope_static scope =
1279 match scope with
1280 | ScopeItem.LongLambda (is_static, _, _) :: scope ->
1281 is_static || is_scope_static scope
1282 | ScopeItem.Function _ :: _ -> false
1283 | ScopeItem.Method md :: _ -> md.m_static
1284 | ScopeItem.Lambda _ :: scope -> is_scope_static scope
1285 | _ -> false
1287 let is_static =
1288 let is_static =
1289 (* long lambdas are static if they are annotated as such *)
1290 if Option.is_some use_vars_opt then
1291 fd.f_static
1292 (* short lambdas can be made static if they don't capture this in
1293 any form (including any nested non-static lambdas )*)
1294 else
1295 not st.captured_this
1297 (* check if something can be promoted to static based on enclosing scope *)
1298 if is_static then
1299 is_static
1300 else
1301 is_scope_static env.scope
1303 let (inline_fundef, cd, md) =
1304 make_closure
1305 ~class_num
1306 fd.f_span
1309 lambda_vars
1310 fun_tparams
1311 class_tparams
1312 is_static
1314 block
1316 let explicit_use_set =
1317 if Option.is_some use_vars_opt then
1318 SSet.add (snd inline_fundef.f_name) st.explicit_use_set
1319 else
1320 st.explicit_use_set
1322 let closure_class_name = snd cd.c_name in
1323 let closure_enclosing_classes =
1324 match Scope.get_class env.scope with
1325 | Some cd -> SMap.add closure_class_name cd st.closure_enclosing_classes
1326 | None -> st.closure_enclosing_classes
1328 (* adjust captured $this information *)
1329 let captured_this =
1330 (* we already know that $this is captured *)
1331 captured_this
1332 || (* lambda that was just processed was converted into non-static one *)
1333 not is_static
1335 (* Restore capture and defined set *)
1336 let st =
1338 st with
1339 captured_vars;
1340 captured_this;
1341 captured_generics;
1342 explicit_use_set;
1343 closure_enclosing_classes;
1344 closure_namespaces =
1345 SMap.add closure_class_name st.namespace st.closure_namespaces;
1346 current_function_state = old_function_state;
1349 let st =
1350 record_function_state
1351 (Emit_env.get_unique_id_for_method cd md)
1352 function_state
1353 rx_of_scope
1356 let env = old_env in
1357 (* Add lambda captured vars to current captured vars *)
1358 let st = List.fold_left lambda_vars ~init:st ~f:(add_var env) in
1359 let st =
1360 List.fold_left current_generics ~init:st ~f:(fun st var ->
1361 { st with captured_generics = ULS.add st.captured_generics var })
1363 let st = { st with hoisted_classes = cd :: st.hoisted_classes } in
1364 (st, (p, Efun (inline_fundef, use_vars)))
1366 and convert_hints env st hl = List.map_env st hl (convert_hint env)
1368 and convert_exprs env st el = List.map_env st el (convert_expr env)
1370 and convert_opt_expr env st oe =
1371 match oe with
1372 | None -> (st, None)
1373 | Some e ->
1374 let (st, e) = convert_expr env st e in
1375 (st, Some e)
1377 and convert_stmt (env : env) (st : state) (p, stmt_) : _ * stmt =
1378 let (st, stmt_) =
1379 match stmt_ with
1380 | Expr e ->
1381 let (st, e) = convert_expr env st e in
1382 (st, Expr e)
1383 | Block b ->
1384 let (st, b) = convert_block env st b in
1385 (st, Block b)
1386 | Throw e ->
1387 let (st, e) = convert_expr env st e in
1388 (st, Throw e)
1389 | Return opt_e ->
1390 let (st, opt_e) = convert_opt_expr env st opt_e in
1391 (st, Return opt_e)
1392 | Awaitall (el, b) ->
1393 check_if_in_async_context env;
1394 let (st, el) = List.map_env st el (convert_snd_expr env) in
1395 let (st, b) = convert_block env st b in
1396 (st, Awaitall (el, b))
1397 | If (e, b1, b2) ->
1398 let (st, e) = convert_expr env st e in
1399 let (st, b1) = convert_block env st b1 in
1400 let (st, b2) = convert_block env st b2 in
1401 (st, If (e, b1, b2))
1402 | Do (b, e) ->
1403 let let_vars_copy = st.let_vars in
1404 let (st, b) = convert_block ~scope:false (reset_in_using env) st b in
1405 let (st, e) = convert_expr env st e in
1406 ({ st with let_vars = let_vars_copy }, Do (b, e))
1407 | While (e, b) ->
1408 let (st, e) = convert_expr env st e in
1409 let (st, b) = convert_block (reset_in_using env) st b in
1410 (st, While (e, b))
1411 | For (e1, e2, e3, b) ->
1412 let (st, e1) = convert_expr env st e1 in
1413 let (st, e2) = convert_expr env st e2 in
1414 let let_vars_copy = st.let_vars in
1415 let (st, b) = convert_block ~scope:false (reset_in_using env) st b in
1416 let (st, e3) = convert_expr env st e3 in
1417 ({ st with let_vars = let_vars_copy }, For (e1, e2, e3, b))
1418 | Switch (e, cl) ->
1419 let (st, e) = convert_expr env st e in
1420 let (st, cl) = List.map_env st cl (convert_case (reset_in_using env)) in
1421 (st, Switch (e, cl))
1422 | Foreach (e, ae, b) ->
1423 (match ae with
1424 | As_v _
1425 | As_kv _ ->
1427 | Await_as_v _
1428 | Await_as_kv _ ->
1429 check_if_in_async_context env);
1430 let (st, e) = convert_expr env st e in
1431 let let_vars_copy = st.let_vars in
1432 let (st, ae) = convert_as_expr env st ae in
1433 let (st, b) = convert_block env st b in
1434 ({ st with let_vars = let_vars_copy }, Foreach (e, ae, b))
1435 | Try (b1, cl, b2) ->
1436 let (st, b1) = convert_block env st b1 in
1437 let (st, cl) = List.map_env st cl (convert_catch env) in
1438 let (st, b2) = convert_block (reset_in_using env) st b2 in
1439 let st =
1440 if List.is_empty b2 then
1442 else
1443 set_has_finally st
1445 (st, Try (b1, cl, b2))
1446 | Using ({ us_has_await; us_expr; us_block; _ } as u) ->
1447 if us_has_await then check_if_in_async_context env;
1448 let (st, us_expr) = convert_expr env st us_expr in
1449 let (st, us_block) = convert_block (set_in_using env) st us_block in
1450 let st = set_has_finally st in
1451 (st, Using { u with us_expr; us_block })
1452 | Def_inline _ ->
1453 (* Inline definitions aren't valid Hack anyway. *)
1454 (st, stmt_)
1455 | GotoLabel (_, l) ->
1456 (* record known label in function *)
1457 let st = set_label st l env.in_using in
1458 (st, stmt_)
1459 | Goto _ ->
1460 (* record the fact that function has goto *)
1461 let st = set_has_goto st in
1462 (st, stmt_)
1463 | Let ((_, var), _hint, e) ->
1464 let an = Tast_annotate.with_pos p in
1465 let (st, e) = convert_expr env st e in
1466 let (id, st) = update_let_var_id st (Local_id.get_name var) in
1467 let var_name = transform_let_var_name (Local_id.get_name var) id in
1468 (* We convert let statement to a simple assignment expression for simplicity *)
1469 ( st,
1470 Expr
1471 ( an
1472 @@ Binop
1473 ( Ast_defs.Eq None,
1474 an @@ Lvar (p, Local_id.make_scoped var_name),
1475 e ) ) )
1476 | Fallthrough
1477 | Noop
1478 | Break
1479 | TempBreak _
1480 | Continue
1481 | TempContinue _
1482 | Markup _ ->
1483 (st, stmt_)
1485 (st, (p, stmt_))
1487 and convert_block ?(scope = true) env st stmts =
1488 if scope then
1489 let let_vars_copy = st.let_vars in
1490 let (st, stmts) = List.map_env st stmts (convert_stmt env) in
1491 ({ st with let_vars = let_vars_copy }, stmts)
1492 else
1493 List.map_env st stmts (convert_stmt env)
1495 and convert_function_like_body (env : env) (old_st : state) (body : func_body)
1496 : state * func_body * 'c =
1497 (* reset has_finally/goto_state values on the state *)
1498 let st =
1499 if old_st.current_function_state = empty_per_function_state then
1500 old_st
1501 else
1502 { old_st with current_function_state = empty_per_function_state }
1504 let (st, r) = convert_block env st body.fb_ast in
1505 let function_state = st.current_function_state in
1506 (* restore old has_finally/goto_state values *)
1507 let st =
1508 { st with current_function_state = old_st.current_function_state }
1510 (st, { body with fb_ast = r }, function_state)
1512 and convert_catch env st (ty, (p, catch_var), b) =
1513 let let_vars_copy = st.let_vars in
1514 let catch_var_name = Local_id.get_name catch_var in
1515 (* hacksperimental feature:
1516 variables with name not beginning with dollar are treated as immutable *)
1517 let (st, catch_var) =
1518 if catch_var_name.[0] = '$' || not (hacksperimental ()) then
1519 (st, catch_var)
1520 else
1521 let (id, st) = update_let_var_id st catch_var_name in
1522 let var_name = transform_let_var_name catch_var_name id in
1523 (st, Local_id.make_scoped var_name)
1525 let (st, b) = convert_block env st b in
1526 ({ st with let_vars = let_vars_copy }, (ty, (p, catch_var), b))
1528 and convert_case env st case =
1529 match case with
1530 | Default (p, b) ->
1531 let (st, b) = convert_block env st b in
1532 (st, Default (p, b))
1533 | Case (e, b) ->
1534 let (st, e) = convert_expr env st e in
1535 let (st, b) = convert_block env st b in
1536 (st, Case (e, b))
1538 and convert_as_expr env st aexpr =
1539 let convert_expr env st e =
1540 match e with
1541 | (p1, Id (p2, var)) when hacksperimental () ->
1542 let (id, st) = update_let_var_id st var in
1543 let var_name = transform_let_var_name var id in
1544 (st, (p1, Lvar (p2, Local_id.make_scoped var_name)))
1545 | _ -> convert_expr env st e
1547 match aexpr with
1548 | As_v e ->
1549 let (st, e) = convert_expr env st e in
1550 (st, As_v e)
1551 | Await_as_v (pos, e) ->
1552 let (st, e) = convert_expr env st e in
1553 (st, Await_as_v (pos, e))
1554 | As_kv (e1, e2) ->
1555 let (st, e1) = convert_expr env st e1 in
1556 let (st, e2) = convert_expr env st e2 in
1557 (st, As_kv (e1, e2))
1558 | Await_as_kv (pos, e1, e2) ->
1559 let (st, e1) = convert_expr env st e1 in
1560 let (st, e2) = convert_expr env st e2 in
1561 (st, Await_as_kv (pos, e1, e2))
1563 and convert_afield env st afield =
1564 match afield with
1565 | AFvalue e ->
1566 let (st, e) = convert_expr env st e in
1567 (st, AFvalue e)
1568 | AFkvalue (e1, e2) ->
1569 let (st, e1) = convert_expr env st e1 in
1570 let (st, e2) = convert_expr env st e2 in
1571 (st, AFkvalue (e1, e2))
1573 and convert_xhp_attr env st = function
1574 | Xhp_simple (id, e) ->
1575 let (st, e) = convert_expr env st e in
1576 (st, Xhp_simple (id, e))
1577 | Xhp_spread e ->
1578 let (st, e) = convert_expr env st e in
1579 (st, Xhp_spread e)
1581 and convert_params env st param_list =
1582 let convert_param env st param =
1583 let (st, param_user_attributes) =
1584 convert_user_attributes env st param.param_user_attributes
1586 let (st, param_expr) =
1587 match param.param_expr with
1588 | None -> (st, None)
1589 | Some e ->
1590 let (st, e) = convert_expr env st e in
1591 (st, Some e)
1593 (st, { param with param_expr; param_user_attributes })
1595 List.map_env st param_list (convert_param env)
1597 and convert_user_attributes env st ual =
1598 List.map_env st ual (fun st ua ->
1599 let (st, ua_params) = convert_exprs env st ua.ua_params in
1600 (st, { ua with ua_params }))
1602 and convert_fun env (st : state) (fd : fun_def) =
1603 let env = env_with_function env fd in
1604 let st = reset_function_counts st in
1605 let (st, f_body, function_state) =
1606 convert_function_like_body env st fd.f_body
1608 let st =
1609 record_function_state
1610 (Emit_env.get_unique_id_for_function fd)
1611 function_state
1612 Rx.NonRx
1615 let (st, f_params) = convert_params env st fd.f_params in
1616 let (st, f_user_attributes) =
1617 convert_user_attributes env st fd.f_user_attributes
1619 (st, { fd with f_body; f_params; f_user_attributes })
1621 and add_reified_property cd c_vars =
1623 List.for_all cd.c_tparams.c_tparam_list ~f:(function t ->
1624 t.tp_reified = Erased)
1625 then
1626 c_vars
1627 else
1628 let p = Pos.none in
1630 * varray/vec that holds a list of type structures
1631 * this prop will be initilized during runtime
1633 let hint = Some (p, Happly ((p, "varray"), [])) in
1634 let var =
1636 cv_final = false;
1637 cv_xhp_attr = None;
1638 cv_is_promoted_variadic = false;
1639 cv_doc_comment = None;
1640 cv_abstract = false;
1641 cv_visibility = Aast.Private;
1642 cv_type = hint;
1643 cv_id = (p, SU.Reified.reified_prop_name);
1644 cv_expr = None;
1645 cv_user_attributes = [];
1646 cv_is_static = false;
1647 cv_span = p;
1650 var :: c_vars
1652 and convert_class (env : env) (st : state) (cd : class_) =
1653 let env = env_with_class env cd in
1654 let st = reset_function_counts st in
1655 let (st, c_methods) =
1656 List.map_env st cd.c_methods (convert_class_elt_method env)
1658 let (st, c_consts) =
1659 List.map_env st cd.c_consts (convert_class_elt_const env)
1661 let (st, c_vars) =
1662 List.map_env st cd.c_vars (convert_class_elt_classvar env)
1664 let (st, c_xhp_attrs) =
1665 List.map_env st cd.c_xhp_attrs (convert_class_elt_xhp_attrs env)
1667 let c_vars = add_reified_property cd c_vars in
1668 let (st, c_user_attributes) =
1669 convert_user_attributes env st cd.c_user_attributes
1671 (st, { cd with c_methods; c_vars; c_consts; c_user_attributes; c_xhp_attrs })
1673 and convert_class_elt_const (env : env) st cc =
1674 let (st, cc_expr) = convert_opt_expr env st cc.cc_expr in
1675 (st, { cc with cc_expr })
1677 and convert_class_elt_classvar (env : env) st cv =
1678 let (st, cv_expr) = convert_opt_expr env st cv.cv_expr in
1679 (st, { cv with cv_expr })
1681 and convert_class_elt_method (env : env) st md =
1682 let cls =
1683 match env.scope with
1684 | ScopeItem.Class c :: _ -> c
1685 | _ -> failwith "unexpected scope shape - method is not inside the class"
1687 let env = env_with_method env md in
1688 let st = reset_function_counts st in
1689 let (st, m_body, function_state) =
1690 convert_function_like_body env st md.m_body
1692 let st =
1693 record_function_state
1694 (Emit_env.get_unique_id_for_method cls md)
1695 function_state
1696 Rx.NonRx
1699 let (st, m_params) = convert_params env st md.m_params in
1700 (st, { md with m_body; m_params })
1702 and convert_class_elt_xhp_attrs env st (h, c, v, es) =
1703 let (st, c) = convert_class_elt_classvar env st c in
1704 let (st, es) =
1705 match es with
1706 | None -> (st, es)
1707 | Some (p, opt, es) ->
1708 let (st, es) = convert_exprs env st es in
1709 (st, Some (p, opt, es))
1711 (st, (h, c, v, es))
1713 and convert_gconst env st gconst =
1714 let (st, expr) = convert_expr env st gconst.cst_value in
1715 (st, { gconst with cst_value = expr })
1717 and convert_defs env class_count record_count typedef_count st dl =
1718 match dl with
1719 | [] -> (st, [])
1720 | Fun fd :: dl ->
1721 let let_vars_copy = st.let_vars in
1722 let st = { st with let_vars = SMap.empty } in
1723 let (st, fd) = convert_fun env st fd in
1724 let (st, dl) =
1725 convert_defs env class_count record_count typedef_count st dl
1727 ({ st with let_vars = let_vars_copy }, (TopLevel, Fun fd) :: dl)
1728 (* Convert a top-level class definition into a true class definition and
1729 * a stub class that just corresponds to the DefCls instruction *)
1730 | Class cd :: dl ->
1731 let let_vars_copy = st.let_vars in
1732 let st = { st with let_vars = SMap.empty } in
1733 let (st, cd) = convert_class env st cd in
1734 let stub_class =
1735 if cd.c_kind = Ast_defs.Crecord then
1736 make_defrecord cd record_count
1737 else
1738 make_defcls cd class_count
1740 let (st, dl) =
1741 if cd.c_kind = Ast_defs.Crecord then
1742 convert_defs env class_count (record_count + 1) typedef_count st dl
1743 else
1744 convert_defs env (class_count + 1) record_count typedef_count st dl
1746 ( { st with let_vars = let_vars_copy },
1747 (TopLevel, Class cd)
1748 :: (TopLevel, Stmt (Pos.none, Def_inline (Class stub_class)))
1749 :: dl )
1750 | Stmt stmt :: dl ->
1751 let (st, stmt) = convert_stmt env st stmt in
1752 let (st, dl) =
1753 convert_defs env class_count record_count typedef_count st dl
1755 (st, (TopLevel, Stmt stmt) :: dl)
1756 | Typedef td :: dl ->
1757 let (st, dl) =
1758 convert_defs env class_count record_count (typedef_count + 1) st dl
1760 let (st, t_user_attributes) =
1761 convert_user_attributes env st td.t_user_attributes
1763 let td = { td with t_user_attributes } in
1764 let stub_td =
1765 { td with t_name = (fst td.t_name, string_of_int typedef_count) }
1767 ( st,
1768 (TopLevel, Typedef td)
1769 :: (TopLevel, Stmt (Pos.none, Def_inline (Typedef stub_td)))
1770 :: dl )
1771 | Constant c :: dl ->
1772 let (st, c) = convert_gconst env st c in
1773 let (st, dl) =
1774 convert_defs env class_count record_count typedef_count st dl
1776 (st, (TopLevel, Constant c) :: dl)
1777 | Namespace (_id, dl) :: dl' ->
1778 convert_defs env class_count record_count typedef_count st (dl @ dl')
1779 | NamespaceUse x :: dl ->
1780 let (st, dl) =
1781 convert_defs env class_count record_count typedef_count st dl
1783 (st, (TopLevel, NamespaceUse x) :: dl)
1784 | SetNamespaceEnv ns :: dl ->
1785 let st = set_namespace st ns in
1786 let (st, dl) =
1787 convert_defs env class_count record_count typedef_count st dl
1789 (st, (TopLevel, SetNamespaceEnv ns) :: dl)
1790 | FileAttributes fa :: dl ->
1791 let (st, dl) =
1792 convert_defs env class_count record_count typedef_count st dl
1794 let (st, fa_user_attributes) =
1795 convert_user_attributes env st fa.fa_user_attributes
1797 let fa = { fa with fa_user_attributes } in
1798 (st, (TopLevel, FileAttributes fa) :: dl)
1800 let count_classes (defs : program) =
1801 List.count defs ~f:(function
1802 | Class { c_kind; _ } when c_kind <> Ast_defs.Crecord -> true
1803 | _ -> false)
1805 let count_records defs =
1806 List.count defs ~f:(function
1807 | Class { c_kind = Ast_defs.Crecord; _ } -> true
1808 | _ -> false)
1810 let hoist_toplevel_functions all_defs =
1811 let (funs, nonfuns) =
1812 List.partition_tf all_defs ~f:(function
1813 | (_, Fun _) -> true
1814 | _ -> false)
1816 funs @ nonfuns
1818 (* For all the definitions in a file unit, convert lambdas into classes with
1819 * invoke methods, and hoist inline class and function definitions to top
1820 * level.
1821 * The closure classes and hoisted definitions are placed after the existing
1822 * definitions.
1824 let convert_toplevel_prog ~popt defs =
1825 let defs =
1826 if constant_folding () then
1827 Ast_constant_folder.fold_program defs
1828 else
1829 defs
1831 (* First compute the number of explicit classes in order to generate correct
1832 * integer identifiers for the generated classes. .main counts as a top-level
1833 * function and we place hoisted functions just after that *)
1834 let env = env_toplevel (count_classes defs) (count_records defs) 1 defs in
1835 let st = initial_state popt in
1836 let (st, original_defs) = convert_defs env 0 0 0 st defs in
1837 let main_state = st.current_function_state in
1838 let st =
1839 record_function_state
1840 (Emit_env.get_unique_id_for_main ())
1841 main_state
1842 Rx.NonRx
1845 (* Reorder the functions so that they appear first. This matches the
1846 * behaviour of HHVM. *)
1847 let original_defs = hoist_toplevel_functions original_defs in
1848 let fun_defs =
1849 List.rev_map st.hoisted_functions (fun fd -> (Hoisted, Fun fd))
1851 let named_hoisted_functions = SMap.values st.named_hoisted_functions in
1852 let named_fun_defs =
1853 List.rev_map named_hoisted_functions (fun fd -> (TopLevel, Fun fd))
1855 let class_defs =
1856 List.rev_map st.hoisted_classes (fun cd -> (Hoisted, Class cd))
1858 let ast_defs = fun_defs @ named_fun_defs @ original_defs @ class_defs in
1859 let global_state =
1860 Emit_env.
1862 global_explicit_use_set = st.explicit_use_set;
1863 global_closure_namespaces = st.closure_namespaces;
1864 global_closure_enclosing_classes = st.closure_enclosing_classes;
1865 global_functions_with_finally = st.functions_with_finally;
1866 global_function_to_labels_map = st.function_to_labels_map;
1867 global_lambda_rx_of_scope = st.lambda_rx_of_scope;
1870 { ast_defs; global_state }