Add codegen for dynamic dispatch functions: call user func and friends
[hiphop-php.git] / hphp / hack / src / hhbc / emit_expression.ml
blob620af0e4d873aeee3cda19a38af8c692e16b75b0
1 (**
2 * Copyright (c) 2017, Facebook, Inc.
3 * All rights reserved.
5 * This source code is licensed under the BSD-style license found in the
6 * LICENSE file in the "hack" directory of this source tree. An additional grant
7 * of patent rights can be found in the PATENTS file in the same directory.
9 *)
11 open Core
12 open Hhbc_ast
13 open Instruction_sequence
15 module A = Ast
16 module H = Hhbc_ast
17 module TC = Hhas_type_constraint
18 module SN = Naming_special_names
19 module CBR = Continue_break_rewriter
21 (* When using the PassX instructions we need to emit the right kind *)
22 module PassByRefKind = struct
23 type t = AllowCell | WarnOnCell | ErrorOnCell
24 end
26 (* Locals, array elements, and properties all support the same range of l-value
27 * operations. *)
28 module LValOp = struct
29 type t =
30 | Set
31 | SetOp of eq_op
32 | IncDec of incdec_op
33 | Unset
34 end
36 let self_name = ref (None : string option)
37 let set_self n = self_name := n
39 let compiler_options = ref Hhbc_options.default
40 let set_compiler_options o = compiler_options := o
42 (* Emit a comment in lieu of instructions for not-yet-implemented features *)
43 let emit_nyi description =
44 instr (IComment ("NYI: " ^ description))
46 let strip_dollar id =
47 String.sub id 1 (String.length id - 1)
49 let make_varray p es = p, A.Array (List.map es ~f:(fun e -> A.AFvalue e))
50 let make_kvarray p kvs =
51 p, A.Array (List.map kvs ~f:(fun (k, v) -> A.AFkvalue (k, v)))
53 (* Strict binary operations; assumes that operands are already on stack *)
54 let from_binop op =
55 let ints_overflow_to_ints =
56 Hhbc_options.ints_overflow_to_ints !compiler_options in
57 match op with
58 | A.Plus -> instr (IOp (if ints_overflow_to_ints then Add else AddO))
59 | A.Minus -> instr (IOp (if ints_overflow_to_ints then Sub else SubO))
60 | A.Star -> instr (IOp (if ints_overflow_to_ints then Mul else MulO))
61 | A.Slash -> instr (IOp Div)
62 | A.Eqeq -> instr (IOp Eq)
63 | A.EQeqeq -> instr (IOp Same)
64 | A.Starstar -> instr (IOp Pow)
65 | A.Diff -> instr (IOp Neq)
66 | A.Diff2 -> instr (IOp NSame)
67 | A.Lt -> instr (IOp Lt)
68 | A.Lte -> instr (IOp Lte)
69 | A.Gt -> instr (IOp Gt)
70 | A.Gte -> instr (IOp Gte)
71 | A.Dot -> instr (IOp Concat)
72 | A.Amp -> instr (IOp BitAnd)
73 | A.Bar -> instr (IOp BitOr)
74 | A.Ltlt -> instr (IOp Shl)
75 | A.Gtgt -> instr (IOp Shr)
76 | A.Percent -> instr (IOp Mod)
77 | A.Xor -> instr (IOp BitXor)
78 | A.Eq _ -> emit_nyi "Eq"
79 | A.AMpamp
80 | A.BArbar ->
81 failwith "short-circuiting operator cannot be generated as a simple binop"
83 let binop_to_eqop op =
84 let ints_overflow_to_ints =
85 Hhbc_options.ints_overflow_to_ints !compiler_options in
86 match op with
87 | A.Plus -> Some (if ints_overflow_to_ints then PlusEqual else PlusEqualO)
88 | A.Minus -> Some (if ints_overflow_to_ints then MinusEqual else MinusEqualO)
89 | A.Star -> Some (if ints_overflow_to_ints then MulEqual else MulEqualO)
90 | A.Slash -> Some DivEqual
91 | A.Starstar -> Some PowEqual
92 | A.Amp -> Some AndEqual
93 | A.Bar -> Some OrEqual
94 | A.Xor -> Some XorEqual
95 | A.Ltlt -> Some SlEqual
96 | A.Gtgt -> Some SrEqual
97 | A.Percent -> Some ModEqual
98 | A.Dot -> Some ConcatEqual
99 | _ -> None
101 let unop_to_incdec_op op =
102 let ints_overflow_to_ints =
103 Hhbc_options.ints_overflow_to_ints !compiler_options in
104 match op with
105 | A.Uincr -> Some (if ints_overflow_to_ints then PreInc else PreIncO)
106 | A.Udecr -> Some (if ints_overflow_to_ints then PreDec else PreDecO)
107 | A.Upincr -> Some (if ints_overflow_to_ints then PostInc else PostIncO)
108 | A.Updecr -> Some (if ints_overflow_to_ints then PostDec else PostDecO)
109 | _ -> None
111 let collection_type = function
112 | "Vector" -> 17
113 | "Map" -> 18
114 | "Set" -> 19
115 | "Pair" -> 20
116 | "ImmVector" -> 21
117 | "ImmMap" -> 22
118 | "ImmSet" -> 23
119 | x -> failwith ("unknown collection type '" ^ x ^ "'")
121 let istype_op id =
122 match id with
123 | "is_int" | "is_integer" -> Some OpInt
124 | "is_bool" -> Some OpBool
125 | "is_float" | "is_real" | "is_double" -> Some OpDbl
126 | "is_string" -> Some OpStr
127 | "is_array" -> Some OpArr
128 | "is_object" -> Some OpObj
129 | "is_null" -> Some OpNull
130 | "is_scalar" -> Some OpScalar
131 | _ -> None
133 (* See EmitterVisitor::getPassByRefKind in emitter.cpp *)
134 let get_passByRefKind expr =
135 let open PassByRefKind in
136 let rec from_non_list_assignment permissive_kind expr =
137 match snd expr with
138 | A.New _ | A.Lvar _ | A.Clone _ -> AllowCell
139 | A.Binop(A.Eq None, (_, A.List _), e) ->
140 from_non_list_assignment WarnOnCell e
141 | A.Array_get(_, Some _) -> permissive_kind
142 | A.Binop(A.Eq _, _, _) -> WarnOnCell
143 | A.Unop((A.Uincr | A.Udecr), _) -> WarnOnCell
144 | _ -> ErrorOnCell in
145 from_non_list_assignment AllowCell expr
147 let get_queryMOpMode op =
148 match op with
149 | QueryOp.CGet -> MemberOpMode.Warn
150 | _ -> MemberOpMode.ModeNone
152 let is_special_function e =
153 match e with
154 | (_, A.Id(_, x))
155 when x = "isset" || x = "empty" || x = "tuple" -> true
156 | _ -> false
158 let extract_shape_field_name_pstring = function
159 | A.SFlit p
160 | A.SFclass_const (_, p) -> p
162 let extract_shape_field_name = function
163 | A.SFlit (_, s)
164 | A.SFclass_const (_, (_, s)) -> s
166 let rec expr_and_newc instr_to_add_new instr_to_add = function
167 | A.AFvalue e ->
168 gather [from_expr e; instr_to_add_new]
169 | A.AFkvalue (k, v) ->
170 gather [
171 emit_two_exprs k v;
172 instr_to_add
175 and from_local x =
176 if x = SN.SpecialIdents.this then instr_this
177 else instr_cgetl (Local.Named x)
179 and emit_two_exprs e1 e2 =
180 (* Special case to make use of CGetL2 *)
181 match e1 with
182 | (_, A.Lvar (_, local)) ->
183 gather [
184 from_expr e2;
185 instr_cgetl2 (Local.Named local);
187 | _ ->
188 gather [
189 from_expr e1;
190 from_expr e2;
193 and emit_is_null e =
194 match e with
195 | (_, A.Lvar (_, id)) ->
196 instr_istypel (Local.Named id) OpNull
197 | _ ->
198 gather [
199 from_expr e;
200 instr_istypec OpNull
203 and emit_binop op e1 e2 =
204 match op with
205 | A.AMpamp -> emit_logical_and e1 e2
206 | A.BArbar -> emit_logical_or e1 e2
207 | A.Eq None -> emit_lval_op LValOp.Set e1 (Some e2)
208 | A.Eq (Some obop) ->
209 begin match binop_to_eqop obop with
210 | None -> emit_nyi "illegal eq op"
211 | Some op -> emit_lval_op (LValOp.SetOp op) e1 (Some e2)
213 | A.EQeqeq when snd e2 = A.Null ->
214 emit_is_null e1
215 | A.EQeqeq when snd e1 = A.Null ->
216 emit_is_null e2
217 | A.Diff2 when snd e2 = A.Null ->
218 gather [
219 emit_is_null e1;
220 instr_not
222 | A.Diff2 when snd e1 = A.Null ->
223 gather [
224 emit_is_null e2;
225 instr_not
227 | _ ->
228 gather [
229 emit_two_exprs e1 e2;
230 from_binop op
233 and emit_instanceof e1 e2 =
234 match (e1, e2) with
235 | (_, (_, A.Id (_, id))) ->
236 gather [
237 from_expr e1;
238 instr_instanceofd id ]
239 | _ ->
240 gather [
241 from_expr e1;
242 from_expr e2;
243 instr_instanceof ]
245 and emit_null_coalesce e1 e2 =
246 let end_label = Label.next_regular () in
247 gather [
248 emit_quiet_expr e1;
249 instr_dup;
250 instr_istypec OpNull;
251 instr_not;
252 instr_jmpnz end_label;
253 instr_popc;
254 from_expr e2;
255 instr_label end_label;
258 and emit_cast hint expr =
259 let op =
260 begin match hint with
261 | A.Happly((_, id), [])
262 when id = SN.Typehints.int
263 || id = SN.Typehints.integer ->
264 instr (IOp CastInt)
265 | A.Happly((_, id), [])
266 when id = SN.Typehints.bool
267 || id = SN.Typehints.boolean ->
268 instr (IOp CastBool)
269 | A.Happly((_, id), [])
270 when id = SN.Typehints.string ->
271 instr (IOp CastString)
272 | A.Happly((_, id), [])
273 when id = SN.Typehints.object_cast ->
274 instr (IOp CastObject)
275 | A.Happly((_, id), [])
276 when id = SN.Typehints.array ->
277 instr (IOp CastArray)
278 | A.Happly((_, id), [])
279 when id = SN.Typehints.real
280 || id = SN.Typehints.double
281 || id = SN.Typehints.float ->
282 instr (IOp CastDouble)
283 (* TODO: unset *)
284 | _ ->
285 emit_nyi "cast type"
286 end in
287 gather [
288 from_expr expr;
292 and emit_conditional_expression etest etrue efalse =
293 match etrue with
294 | Some etrue ->
295 let false_label = Label.next_regular () in
296 let end_label = Label.next_regular () in
297 gather [
298 from_expr etest;
299 instr_jmpz false_label;
300 from_expr etrue;
301 instr_jmp end_label;
302 instr_label false_label;
303 from_expr efalse;
304 instr_label end_label;
306 | None ->
307 let end_label = Label.next_regular () in
308 gather [
309 from_expr etest;
310 instr_dup;
311 instr_jmpnz end_label;
312 instr_popc;
313 from_expr efalse;
314 instr_label end_label;
317 and emit_aget class_expr =
318 match class_expr with
319 | _, A.Lvar (_, id) ->
320 instr (IGet (ClsRefGetL (Local.Named id, 0)))
322 | _ ->
323 gather [
324 from_expr class_expr;
325 instr (IGet (ClsRefGetC 0))
328 and emit_new class_expr args uargs =
329 let nargs = List.length args + List.length uargs in
330 match class_expr with
331 | _, A.Id (_, id) ->
332 gather [
333 instr_fpushctord nargs id;
334 emit_args_and_call args uargs;
335 instr_popr
337 | _ ->
338 gather [
339 emit_aget class_expr;
340 instr_fpushctor nargs 0;
341 emit_args_and_call args uargs;
342 instr_popr
345 and emit_clone expr =
346 gather [
347 from_expr expr;
348 instr_clone;
351 and emit_shape expr fl =
352 let are_values_all_literals =
353 List.for_all fl ~f:(fun (_, e) -> is_literal e)
355 let p = fst expr in
356 if are_values_all_literals then
357 let fl =
358 List.map fl
359 ~f:(fun (fn, e) ->
360 A.AFkvalue ((p,
361 A.String (extract_shape_field_name_pstring fn)), e))
363 from_expr (fst expr, A.Array fl)
364 else
365 let es = List.map fl ~f:(fun (_, e) -> from_expr e) in
366 let keys = List.map fl ~f:(fun (fn, _) -> extract_shape_field_name fn) in
367 gather [
368 gather es;
369 instr_newstructarray keys;
372 and emit_tuple p es =
373 (* Did you know that tuples are functions? *)
374 let af_list = List.map es ~f:(fun e -> A.AFvalue e) in
375 from_expr (p, A.Array af_list)
377 and emit_call_expr expr =
378 let instrs, flavor = emit_flavored_expr expr in
379 gather [
380 instrs;
381 (* If the instruction has produced a ref then unbox it *)
382 if flavor = Flavor.Ref then instr_unboxr else empty
385 and emit_known_class_id cid =
386 gather [
387 instr_string (Utils.strip_ns cid);
388 instr (IGet (ClsRefGetC 0))
391 and emit_class_id cid =
392 if cid = SN.Classes.cStatic
393 then instr (IMisc (LateBoundCls 0))
394 else
395 if cid = SN.Classes.cSelf
396 then match !self_name with
397 | None -> instr (IMisc Self)
398 | Some cid -> emit_known_class_id cid
399 else emit_known_class_id cid
401 and emit_class_get param_num_opt cid id =
402 gather [
403 (* We need to strip off the initial dollar *)
404 instr_string (strip_dollar id);
405 emit_class_id cid;
406 match param_num_opt with
407 | None -> instr (IGet (CGetS 0))
408 | Some i -> instr (ICall (FPassS (i, 0)))
411 and emit_class_const cid id =
412 if id = SN.Members.mClass then instr_string cid
413 else if cid = SN.Classes.cStatic
414 then
415 instrs [
416 IMisc (LateBoundCls 0);
417 ILitConst (ClsCns (id, 0));
419 else if cid = SN.Classes.cSelf
420 then
421 match !self_name with
422 | None ->
423 instrs [
424 IMisc Self;
425 ILitConst (ClsCns (id, 0));
427 | Some cid -> instr (ILitConst (ClsCnsD (id, cid)))
428 else
429 instr (ILitConst (ClsCnsD (id, cid)))
431 and emit_await e =
432 let after_await = Label.next_regular () in
433 gather [
434 from_expr e;
435 instr_dup;
436 instr_istypec OpNull;
437 instr_jmpnz after_await;
438 instr_await;
439 instr_label after_await;
442 and emit_yield = function
443 | A.AFvalue e ->
444 gather [
445 from_expr e;
446 instr_yield;
448 | A.AFkvalue (e1, e2) ->
449 gather [
450 from_expr e1;
451 from_expr e2;
452 instr_yieldk;
455 and emit_yield_break () =
456 gather [
457 instr_null;
458 instr_retc;
461 and emit_string2 exprs =
462 match exprs with
463 | [e] ->
464 gather [
465 from_expr e;
466 instr (IOp CastString)
468 | e1::e2::es ->
469 gather @@ [
470 emit_two_exprs e1 e2;
471 instr (IOp Concat);
472 gather (List.map es (fun e -> gather [from_expr e; instr (IOp Concat)]))
475 | [] -> failwith "String2 with zero arguments is impossible"
477 and emit_lambda fundef ids =
478 (* Closure conversion puts the class number used for CreateCl in the "name"
479 * of the function definition *)
480 let class_num = int_of_string (snd fundef.A.f_name) in
481 gather [
482 (* TODO: deal with explicit use (...) capture variables *)
483 gather @@ List.map ids
484 (fun (x, _isref) -> instr (IGet (CUGetL (Local.Named (snd x)))));
485 instr (IMisc (CreateCl (List.length ids, class_num)))
488 and emit_id (p, s) =
489 match s with
490 | "__FILE__" -> instr (ILitConst File)
491 | "__DIR__" -> instr (ILitConst Dir)
492 | "__LINE__" ->
493 (* If the expression goes on multi lines, we return the last line *)
494 let _, line, _, _ = Pos.info_pos_extended p in
495 instr_int line
496 | "exit" -> emit_exit (p, A.Int (p, "0"))
497 | _ -> instr (ILitConst (Cns s))
499 and rename_xhp (p, s) =
500 (* Translates given :name to xhp_name *)
501 if String_utils.string_starts_with s ":"
502 then (p, "xhp_" ^ (String_utils.lstrip s ":"))
503 else failwith "Incorrectly named xhp element"
505 and emit_xhp p id attributes children =
506 (* Translate into a constructor call. The arguments are:
507 * 1) shape-like array of attributes
508 * 2) vec-like array of children
509 * 3) filename, for debugging
510 * 4) line number, for debugging
512 let convert_xml_attr (name, v) = (A.SFlit name, v) in
513 let attributes = List.map ~f:convert_xml_attr attributes in
514 let attribute_map = p, A.Shape attributes in
515 let children_vec = make_varray p children in
516 let filename = p, A.Id (p, "__FILE__") in
517 let line = p, A.Id (p, "__LINE__") in
518 from_expr @@
519 (p, A.New (
520 (p, A.Id (rename_xhp id)),
521 [attribute_map ; children_vec ; filename ; line],
522 []))
524 and emit_import flavor e =
525 let import_instr = match flavor with
526 | A.Include -> instr @@ IIncludeEvalDefine Incl
527 | A.Require -> instr @@ IIncludeEvalDefine Req
528 | A.IncludeOnce -> instr @@ IIncludeEvalDefine InclOnce
529 | A.RequireOnce -> instr @@ IIncludeEvalDefine ReqOnce
531 gather [
532 from_expr e;
533 import_instr;
536 and emit_lvarvar n (_, id) =
537 gather [
538 instr_cgetl (Local.Named id);
539 gather @@ List.replicate ~num:n instr_cgetn;
542 and emit_call_isset_expr (_, expr_ as expr) =
543 match expr_ with
544 | A.Array_get((_, A.Lvar (_, x)), Some e) when x = SN.Superglobals.globals ->
545 gather [
546 from_expr e;
547 instr (IIsset IssetG)
549 | A.Array_get(base_expr, opt_elem_expr) ->
550 emit_array_get None QueryOp.Isset base_expr opt_elem_expr
551 | A.Obj_get (expr, prop, nullflavor) ->
552 emit_obj_get None QueryOp.Isset expr prop nullflavor
553 | A.Lvar(_, id) ->
554 instr (IIsset (IssetL (Local.Named id)))
555 | _ ->
556 gather [
557 from_expr expr;
558 instr_istypec OpNull;
559 instr_not
562 and emit_call_empty_expr (_, expr_ as expr) =
563 match expr_ with
564 | A.Array_get((_, A.Lvar (_, x)), Some e) when x = SN.Superglobals.globals ->
565 gather [
566 from_expr e;
567 instr (IIsset EmptyG)
569 | A.Array_get(base_expr, opt_elem_expr) ->
570 emit_array_get None QueryOp.Empty base_expr opt_elem_expr
571 | A.Obj_get (expr, prop, nullflavor) ->
572 emit_obj_get None QueryOp.Empty expr prop nullflavor
573 | A.Lvar(_, id) ->
574 instr (IIsset (EmptyL (Local.Named id)))
575 | _ ->
576 gather [
577 from_expr expr;
578 instr_not
581 and emit_unset_expr expr =
582 emit_lval_op_nonlist LValOp.Unset expr empty 0
584 and emit_call_isset_exprs exprs =
585 match exprs with
586 | [] -> emit_nyi "isset()"
587 | [expr] -> emit_call_isset_expr expr
588 | _ ->
589 let n = List.length exprs in
590 let its_done = Label.next_regular () in
591 gather [
592 gather @@
593 List.mapi exprs
594 begin fun i expr ->
595 gather [
596 emit_call_isset_expr expr;
597 if i < n-1 then
598 gather [
599 instr_dup;
600 instr_jmpz its_done;
601 instr_popc
602 ] else empty
604 end;
605 instr_label its_done
608 and emit_exit expr =
609 gather [
610 from_expr expr;
611 instr_exit;
614 and from_expr expr =
615 (* Note that this takes an Ast.expr, not a Nast.expr. *)
616 match snd expr with
617 | A.Float (_, litstr) -> instr_double litstr
618 | A.String (_, litstr) -> instr_string litstr
619 (* TODO deal with integer out of range *)
620 | A.Int (_, litstr) -> instr_int_of_string litstr
621 | A.Null -> instr_null
622 | A.False -> instr_false
623 | A.True -> instr_true
624 | A.Lvar (_, x) -> from_local x
625 | A.Class_const ((_, cid), (_, id)) -> emit_class_const cid id
626 | A.Unop (op, e) -> emit_unop op e
627 | A.Binop (op, e1, e2) -> emit_binop op e1 e2
628 | A.Pipe (e1, e2) -> emit_pipe e1 e2
629 | A.Dollardollar -> instr_cgetl2 Local.Pipe
630 | A.InstanceOf (e1, e2) -> emit_instanceof e1 e2
631 | A.NullCoalesce (e1, e2) -> emit_null_coalesce e1 e2
632 | A.Cast((_, hint), e) -> emit_cast hint e
633 | A.Eif (etest, etrue, efalse) ->
634 emit_conditional_expression etest etrue efalse
635 | A.Expr_list es -> gather @@ List.map es ~f:from_expr
636 | A.Array_get((_, A.Lvar (_, x)), Some e) when x = SN.Superglobals.globals ->
637 gather [
638 from_expr e;
639 instr (IGet CGetG)
641 | A.Array_get(base_expr, opt_elem_expr) ->
642 emit_array_get None QueryOp.CGet base_expr opt_elem_expr
643 | A.Obj_get (expr, prop, nullflavor) ->
644 emit_obj_get None QueryOp.CGet expr prop nullflavor
645 | A.Call ((_, A.Id (_, "isset")), exprs, []) ->
646 emit_call_isset_exprs exprs
647 | A.Call ((_, A.Id (_, "empty")), [expr], []) ->
648 emit_call_empty_expr expr
649 | A.Call ((p, A.Id (_, "tuple")), es, _) -> emit_tuple p es
650 | A.Call _ -> emit_call_expr expr
651 | A.New (typeexpr, args, uargs) -> emit_new typeexpr args uargs
652 | A.Array es -> emit_collection expr es
653 | A.Darray es ->
655 |> List.map ~f:(fun (e1, e2) -> A.AFkvalue (e1, e2))
656 |> emit_collection expr
657 | A.Varray es ->
659 |> List.map ~f:(fun e -> A.AFvalue e)
660 |> emit_collection expr
661 | A.Collection ((pos, name), fields) ->
662 emit_named_collection expr pos name fields
663 | A.Clone e -> emit_clone e
664 | A.Shape fl -> emit_shape expr fl
665 | A.Await e -> emit_await e
666 | A.Yield e -> emit_yield e
667 | A.Yield_break -> emit_yield_break ()
668 | A.Lfun _ ->
669 failwith "expected Lfun to be converted to Efun during closure conversion"
670 | A.Efun (fundef, ids) -> emit_lambda fundef ids
671 | A.Class_get ((_, cid), (_, id)) -> emit_class_get None cid id
672 | A.String2 es -> emit_string2 es
673 | A.Unsafeexpr e -> from_expr e
674 | A.Id id -> emit_id id
675 | A.Xml (id, attributes, children) ->
676 emit_xhp (fst expr) id attributes children
677 | A.Import (flavor, e) -> emit_import flavor e
678 | A.Lvarvar (n, id) -> emit_lvarvar n id
679 (* TODO *)
680 | A.Id_type_arguments (_, _) -> emit_nyi "id_type_arguments"
681 | A.List _ -> emit_nyi "list"
683 and emit_static_collection ~transform_to_collection expr es =
684 let a_label = Label.get_next_data_label () in
685 (* Arrays can either contains values or key/value pairs *)
686 let need_index = match snd expr with
687 | A.Collection ((_, "vec"), _)
688 | A.Collection ((_, "keyset"), _) -> false
689 | _ -> true
691 let _, es =
692 List.fold_left
694 ~init:(0, [])
695 ~f:(fun (index, l) x ->
696 let open Constant_folder in
697 (index + 1, match x with
698 | A.AFvalue e when need_index ->
699 literal_from_expr e :: Int (Int64.of_int index) :: l
700 | A.AFvalue e ->
701 literal_from_expr e :: l
702 | A.AFkvalue (k,v) ->
703 literal_from_expr v :: literal_from_expr k :: l)
706 let es = List.rev es in
707 let lit_constructor = match snd expr with
708 | A.Array _ -> Array (a_label, es)
709 | A.Collection ((_, "dict"), _) -> Dict (a_label, es)
710 | A.Collection ((_, "vec"), _) -> Vec (a_label, es)
711 | A.Collection ((_, "keyset"), _) -> Keyset (a_label, es)
712 | _ -> failwith "impossible"
714 let transform_instr =
715 match transform_to_collection with
716 | Some n -> instr_colfromarray n
717 | None -> empty
719 gather [
720 instr (ILitConst lit_constructor);
721 transform_instr;
724 (* transform_to_collection argument keeps track of
725 * what collection to transform to *)
726 and emit_dynamic_collection ~transform_to_collection expr es =
727 let is_only_values =
728 List.for_all es ~f:(function A.AFkvalue _ -> false | _ -> true)
730 let count = List.length es in
731 if is_only_values && transform_to_collection = None then begin
732 let lit_constructor = match snd expr with
733 | A.Array _ -> NewPackedArray count
734 | A.Collection ((_, "vec"), _) -> NewVecArray count
735 | A.Collection ((_, "keyset"), _) -> NewKeysetArray count
736 | _ -> failwith "impossible"
738 gather [
739 gather @@
740 List.map es
741 ~f:(function A.AFvalue e -> from_expr e | _ -> failwith "impossible");
742 instr @@ ILitConst lit_constructor;
744 end else begin
745 let lit_constructor = match snd expr with
746 | A.Array _ -> NewMixedArray count
747 | A.Collection ((_, "dict"), _) -> NewDictArray count
748 | _ -> failwith "impossible"
750 let transform_instr =
751 match transform_to_collection with
752 | Some n -> instr_colfromarray n
753 | None -> empty
755 let add_elem_instr =
756 if transform_to_collection = None
757 then instr_add_new_elemc
758 else instr_col_add_new_elemc
760 gather @@
761 (instr @@ ILitConst lit_constructor) :: transform_instr ::
762 (List.map es ~f:(expr_and_newc add_elem_instr instr_add_elemc))
765 and emit_named_collection expr pos name fields =
766 match name with
767 | "dict" | "vec" | "keyset" -> emit_collection expr fields
768 | "Vector" | "ImmVector" ->
769 let collection_type = collection_type name in
770 gather [
771 emit_collection (pos, A.Collection ((pos, "vec"), fields)) fields;
772 instr_colfromarray collection_type;
774 | "Set" | "ImmSet" | "Map" | "ImmMap" ->
775 let collection_type = collection_type name in
776 if fields = []
777 then instr_newcol collection_type
778 else
779 emit_collection
780 ~transform_to_collection:collection_type
781 (pos, A.Array fields)
782 fields
783 | "Pair" ->
784 let collection_type = collection_type name in
785 let values = gather @@ List.map
786 fields
787 ~f:(fun x ->
788 expr_and_newc instr_col_add_new_elemc instr_col_add_new_elemc x)
790 gather [
791 instr_newcol collection_type;
792 values;
794 | _ -> failwith @@ "collection: " ^ name ^ " does not exist"
796 and emit_collection ?(transform_to_collection) expr es =
797 if is_literal_afield_list es then
798 emit_static_collection ~transform_to_collection expr es
799 else
800 emit_dynamic_collection ~transform_to_collection expr es
802 and emit_pipe e1 e2 =
803 stash_in_local e1
804 begin fun temp _break_label ->
805 let rewrite_dollardollar e =
806 let rewriter i =
807 match i with
808 | IGet (CGetL2 Local.Pipe) ->
809 IGet (CGetL2 temp)
810 | _ -> i in
811 InstrSeq.map e ~f:rewriter in
812 rewrite_dollardollar (from_expr e2)
815 and emit_logical_and e1 e2 =
816 let left_is_false = Label.next_regular () in
817 let right_is_true = Label.next_regular () in
818 let its_done = Label.next_regular () in
819 gather [
820 from_expr e1;
821 instr_jmpz left_is_false;
822 from_expr e2;
823 instr_jmpnz right_is_true;
824 instr_label left_is_false;
825 instr_false;
826 instr_jmp its_done;
827 instr_label right_is_true;
828 instr_true;
829 instr_label its_done ]
831 and emit_logical_or e1 e2 =
832 let its_true = Label.next_regular () in
833 let its_done = Label.next_regular () in
834 gather [
835 from_expr e1;
836 instr_jmpnz its_true;
837 from_expr e2;
838 instr_jmpnz its_true;
839 instr_false;
840 instr_jmp its_done;
841 instr_label its_true;
842 instr_true;
843 instr_label its_done ]
845 and emit_quiet_expr (_, expr_ as expr) =
846 match expr_ with
847 | A.Lvar (_, x) ->
848 instr_cgetquietl (Local.Named x)
849 | _ ->
850 from_expr expr
852 (* Emit code for e1[e2] or isset(e1[e2]).
853 * If param_num_opt = Some i
854 * then this is the i'th parameter to a function
856 and emit_array_get param_num_opt qop base_expr opt_elem_expr =
857 let mode = get_queryMOpMode qop in
858 let elem_expr_instrs, elem_stack_size = emit_elem_instrs opt_elem_expr in
859 let base_expr_instrs, base_setup_instrs, base_stack_size =
860 emit_base mode elem_stack_size param_num_opt base_expr in
861 let mk = get_elem_member_key 0 opt_elem_expr in
862 let total_stack_size = elem_stack_size + base_stack_size in
863 let final_instr =
864 instr (IFinal (
865 match param_num_opt with
866 | None -> QueryM (total_stack_size, qop, mk)
867 | Some i -> FPassM (i, total_stack_size, mk)
868 )) in
869 gather [
870 base_expr_instrs;
871 elem_expr_instrs;
872 base_setup_instrs;
873 final_instr
876 (* Emit code for e1->e2 or e1?->e2 or isset(e1->e2).
877 * If param_num_opt = Some i
878 * then this is the i'th parameter to a function
880 and emit_obj_get param_num_opt qop expr prop null_flavor =
881 let mode = get_queryMOpMode qop in
882 let prop_expr_instrs, prop_stack_size = emit_prop_instrs prop in
883 let base_expr_instrs, base_setup_instrs, base_stack_size =
884 emit_base mode prop_stack_size param_num_opt expr in
885 let mk = get_prop_member_key null_flavor 0 prop in
886 let total_stack_size = prop_stack_size + base_stack_size in
887 let final_instr =
888 instr (IFinal (
889 match param_num_opt with
890 | None -> QueryM (total_stack_size, qop, mk)
891 | Some i -> FPassM (i, total_stack_size, mk)
892 )) in
893 gather [
894 base_expr_instrs;
895 prop_expr_instrs;
896 base_setup_instrs;
897 final_instr
900 and emit_elem_instrs opt_elem_expr =
901 match opt_elem_expr with
902 (* These all have special inline versions of member keys *)
903 | Some (_, (A.Lvar _ | A.Int _ | A.String _)) -> empty, 0
904 | Some expr -> from_expr expr, 1
905 | None -> empty, 0
907 and emit_prop_instrs (_, expr_ as expr) =
908 match expr_ with
909 (* These all have special inline versions of member keys *)
910 | A.Lvar _ | A.Id _ -> empty, 0
911 | _ -> from_expr expr, 1
913 (* Get the member key for an array element expression: the `elem` in
914 * expressions of the form `base[elem]`.
915 * If the array element is missing, use the special key `W`.
917 and get_elem_member_key stack_index opt_expr =
918 match opt_expr with
919 (* Special case for local *)
920 | Some (_, A.Lvar (_, x)) -> MemberKey.EL (Local.Named x)
921 (* Special case for literal integer *)
922 | Some (_, A.Int (_, str)) -> MemberKey.EI (Int64.of_string str)
923 (* Special case for literal string *)
924 | Some (_, A.String (_, str)) -> MemberKey.ET str
925 (* General case *)
926 | Some _ -> MemberKey.EC stack_index
927 (* ELement missing (so it's array append) *)
928 | None -> MemberKey.W
930 (* Get the member key for a property *)
931 and get_prop_member_key null_flavor stack_index prop_expr =
932 match prop_expr with
933 (* Special case for known property name *)
934 | (_, A.Id (_, str)) ->
935 begin match null_flavor with
936 | Ast.OG_nullthrows -> MemberKey.PT str
937 | Ast.OG_nullsafe -> MemberKey.QT str
939 | (_, A.Lvar (_, x)) -> MemberKey.PL (Local.Named x)
940 (* General case *)
941 | _ -> MemberKey.PC stack_index
943 (* Emit code for a base expression `expr` that forms part of
944 * an element access `expr[elem]` or field access `expr->fld`.
945 * The instructions are divided into three sections:
946 * 1. base and element/property expression instructions:
947 * push non-trivial base and key values on the stack
948 * 2. base selector instructions: a sequence of Base/Dim instructions that
949 * actually constructs the base address from "member keys" that are inlined
950 * in the instructions, or pulled from the key values that
951 * were pushed on the stack in section 1.
952 * 3. (constructed by the caller) a final accessor e.g. QueryM or setter
953 * e.g. SetOpM instruction that has the final key inlined in the
954 * instruction, or pulled from the key values that were pushed on the
955 * stack in section 1.
956 * The function returns a triple (base_instrs, base_setup_instrs, stack_size)
957 * where base_instrs is section 1 above, base_setup_instrs is section 2, and
958 * stack_size is the number of values pushed onto the stack by section 1.
960 * For example, the r-value expression $arr[3][$ix+2]
961 * will compile to
962 * # Section 1, pushing the value of $ix+2 on the stack
963 * Int 2
964 * CGetL2 $ix
965 * AddO
966 * # Section 2, constructing the base address of $arr[3]
967 * BaseL $arr Warn
968 * Dim Warn EI:3
969 * # Section 3, indexing the array using the value at stack position 0 (EC:0)
970 * QueryM 1 CGet EC:0
972 and emit_base mode base_offset param_num_opt (_, expr_ as expr) =
973 let base_mode =
974 match mode with
975 | MemberOpMode.Unset -> MemberOpMode.ModeNone
976 | _ -> mode in
977 match expr_ with
978 | A.Lvar (_, x) when SN.Superglobals.is_superglobal x ->
979 instr_string (strip_dollar x),
980 instr (IBase (BaseGC (base_offset, base_mode))),
983 | A.Lvar (_, x) when x = SN.SpecialIdents.this ->
984 instr (IMisc CheckThis),
985 instr (IBase BaseH),
988 | A.Lvar (_, x) ->
989 empty,
990 instr (IBase (
991 match param_num_opt with
992 | None -> BaseL (Local.Named x, base_mode)
993 | Some i -> FPassBaseL (i, Local.Named x)
997 | A.Array_get((_, A.Lvar (_, x)), Some e) when x = SN.Superglobals.globals ->
998 let elem_expr_instrs = from_expr e in
999 elem_expr_instrs,
1000 instr (IBase (
1001 match param_num_opt with
1002 | None -> BaseGC (base_offset, base_mode)
1003 | Some i -> FPassBaseGC (i, base_offset)
1007 | A.Array_get(base_expr, opt_elem_expr) ->
1008 let elem_expr_instrs, elem_stack_size = emit_elem_instrs opt_elem_expr in
1009 let base_expr_instrs, base_setup_instrs, base_stack_size =
1010 emit_base mode (base_offset + elem_stack_size) param_num_opt base_expr in
1011 let mk = get_elem_member_key base_offset opt_elem_expr in
1012 let total_stack_size = base_stack_size + elem_stack_size in
1013 gather [
1014 base_expr_instrs;
1015 elem_expr_instrs;
1017 gather [
1018 base_setup_instrs;
1019 instr (IBase (
1020 match param_num_opt with
1021 | None -> Dim (mode, mk)
1022 | Some i -> FPassDim (i, mk)
1025 total_stack_size
1027 | A.Obj_get(base_expr, prop_expr, null_flavor) ->
1028 let prop_expr_instrs, prop_stack_size = emit_prop_instrs prop_expr in
1029 let base_expr_instrs, base_setup_instrs, base_stack_size =
1030 emit_base mode (base_offset + prop_stack_size) param_num_opt base_expr in
1031 let mk = get_prop_member_key null_flavor base_offset prop_expr in
1032 let total_stack_size = prop_stack_size + base_stack_size in
1033 let final_instr =
1034 instr (IBase (
1035 match param_num_opt with
1036 | None -> Dim (mode, mk)
1037 | Some i -> FPassDim (i, mk)
1038 )) in
1039 gather [
1040 base_expr_instrs;
1041 prop_expr_instrs;
1043 gather [
1044 base_setup_instrs;
1045 final_instr
1047 total_stack_size
1049 | A.Class_get((_, cid), (_, id)) ->
1050 let prop_expr_instrs = instr_string (strip_dollar id) in
1051 gather [
1052 prop_expr_instrs;
1053 emit_class_id cid
1055 gather [
1056 instr (IBase (BaseSC (base_offset, 0)))
1060 | _ ->
1061 let base_expr_instrs, flavor = emit_flavored_expr expr in
1062 base_expr_instrs,
1063 instr (IBase (if flavor = Flavor.Ref
1064 then BaseR base_offset else BaseC base_offset)),
1067 and instr_fpass kind i =
1068 match kind with
1069 | PassByRefKind.AllowCell -> instr (ICall (FPassC i))
1070 | PassByRefKind.WarnOnCell -> instr (ICall (FPassCW i))
1071 | PassByRefKind.ErrorOnCell -> instr (ICall (FPassCE i))
1073 and instr_fpassr i = instr (ICall (FPassR i))
1075 and emit_arg i ((_, expr_) as e) =
1076 match expr_ with
1077 | A.Lvar (_, x) -> instr_fpassl i (Local.Named x)
1079 | A.Array_get((_, A.Lvar (_, x)), Some e) when x = SN.Superglobals.globals ->
1080 gather [
1081 from_expr e;
1082 instr (ICall (FPassG i))
1085 | A.Array_get(base_expr, opt_elem_expr) ->
1086 emit_array_get (Some i) QueryOp.CGet base_expr opt_elem_expr
1088 | A.Obj_get(e1, e2, nullflavor) ->
1089 emit_obj_get (Some i) QueryOp.CGet e1 e2 nullflavor
1091 | A.Class_get((_, cid), (_, id)) ->
1092 emit_class_get (Some i) cid id
1094 | _ ->
1095 let instrs, flavor = emit_flavored_expr e in
1096 gather [
1097 instrs;
1098 if flavor = Flavor.Ref
1099 then instr_fpassr i
1100 else instr_fpass (get_passByRefKind e) i
1103 and emit_ignored_expr e =
1104 let instrs, flavor = emit_flavored_expr e in
1105 gather [
1106 instrs;
1107 instr_pop flavor;
1110 (* Emit code to construct the argument frame and then make the call *)
1111 and emit_args_and_call args uargs =
1112 let all_args = args @ uargs in
1113 let nargs = List.length all_args in
1114 gather [
1115 gather (List.mapi all_args emit_arg);
1116 if uargs = []
1117 then instr (ICall (FCall nargs))
1118 else instr (ICall (FCallUnpack nargs))
1121 and emit_call_lhs (_, expr_ as expr) nargs =
1122 match expr_ with
1123 | A.Obj_get (obj, (_, A.Id (_, id)), null_flavor) ->
1124 gather [
1125 from_expr obj;
1126 instr (ICall (FPushObjMethodD (nargs, id, null_flavor)));
1129 | A.Class_const ((_, cid), (_, id)) when cid = SN.Classes.cSelf ->
1130 gather [
1131 instr_string id;
1132 emit_class_id cid;
1133 instr (ICall (FPushClsMethodF (nargs, 0)));
1136 | A.Class_const ((_, cid), (_, id)) when cid = SN.Classes.cStatic ->
1137 gather [
1138 instr_string id;
1139 instr (IMisc (LateBoundCls 0));
1140 instr (ICall (FPushClsMethod (nargs, 0)));
1143 | A.Class_const ((_, cid), (_, id)) when cid = SN.Classes.cParent ->
1144 gather [
1145 instr_string id;
1146 instr (IMisc (Parent 0));
1147 instr (ICall (FPushClsMethodF (nargs, 0)));
1150 | A.Class_const ((_, cid), (_, id)) when cid.[0] = '$' ->
1151 gather [
1152 instr_string id;
1153 instr (IGet (ClsRefGetL (Local.Named cid, 0)));
1154 instr (ICall (FPushClsMethod (nargs, 0)))
1157 | A.Class_const ((_, cid), (_, id)) ->
1158 instr (ICall (FPushClsMethodD (nargs, id, cid)))
1160 | A.Id (_, id) ->
1161 instr (ICall (FPushFuncD (nargs, id)))
1163 | _ ->
1164 gather [
1165 from_expr expr;
1166 instr (ICall (FPushFunc nargs))
1169 (* Retuns whether the function is a call_user_func function,
1170 min args, max args *)
1171 and get_call_user_func_info = function
1172 | "call_user_func" -> (true, 1, max_int)
1173 | "call_user_func_array" -> (true, 2, 2)
1174 | "forward_static_call" -> (true, 1, max_int)
1175 | "forward_static_call_array" -> (true, 2, 2)
1176 | "fb_call_user_func_safe" -> (true, 1, max_int)
1177 | "fb_call_user_func_array_safe" -> (true, 2, 2)
1178 | "fb_call_user_func_safe_return" -> (true, 2, max_int)
1179 | _ -> (false, 0, 0)
1181 and is_call_user_func id num_args =
1182 let (is_fn, min_args, max_args) = get_call_user_func_info id in
1183 is_fn && num_args >= min_args && num_args <= max_args
1185 and emit_call_user_func_args i expr =
1186 gather [
1187 from_expr expr;
1188 instr_fpass PassByRefKind.AllowCell i;
1191 and emit_call_user_func id arg args =
1192 let return_default, args = match id with
1193 | "fb_call_user_func_safe_return" ->
1194 begin match args with
1195 | [] -> failwith "fb_call_user_func_safe_return - requires default arg"
1196 | a :: args -> from_expr a, args
1198 | _ -> empty, args
1200 let num_params = List.length args in
1201 let begin_instr = match id with
1202 | "forward_static_call"
1203 | "forward_static_call_array" -> instr_fpushcuff num_params
1204 | "fb_call_user_func_safe"
1205 | "fb_call_user_func_array_safe" ->
1206 gather [instr_null; instr_fpushcuf_safe num_params]
1207 | "fb_call_user_func_safe_return" ->
1208 gather [return_default; instr_fpushcuf_safe num_params]
1209 | _ -> instr_fpushcuf num_params
1211 let call_instr = match id with
1212 | "call_user_func_array"
1213 | "forward_static_call_array"
1214 | "fb_call_user_func_array_safe" -> instr (ICall FCallArray)
1215 | _ -> instr (ICall (FCall num_params))
1217 let end_instr = match id with
1218 | "fb_call_user_func_safe_return" -> instr (ICall CufSafeReturn)
1219 | "fb_call_user_func_safe"
1220 | "fb_call_user_func_array_safe" -> instr (ICall CufSafeArray)
1221 | _ -> empty
1223 let flavor = match id with
1224 | "fb_call_user_func_safe"
1225 | "fb_call_user_func_array_safe" -> Flavor.Cell
1226 | _ -> Flavor.Ref
1228 gather [
1229 from_expr arg;
1230 begin_instr;
1231 gather (List.mapi args emit_call_user_func_args);
1232 call_instr;
1233 end_instr;
1234 ], flavor
1236 and emit_call (_, expr_ as expr) args uargs =
1237 let nargs = List.length args + List.length uargs in
1238 let default () =
1239 gather [
1240 emit_call_lhs expr nargs;
1241 emit_args_and_call args uargs;
1242 ], Flavor.Ref in
1243 match expr_ with
1244 | A.Id (_, id) when id = SN.SpecialFunctions.echo ->
1245 let instrs = gather @@ List.mapi args begin fun i arg ->
1246 gather [
1247 from_expr arg;
1248 instr (IOp Print);
1249 if i = nargs-1 then empty else instr_popc
1250 ] end in
1251 instrs, Flavor.Cell
1253 | A.Id (_, id) when is_call_user_func id (List.length args)->
1254 if List.length uargs != 0 then
1255 failwith "Using argument unpacking for a call_user_func is not supported";
1256 begin match args with
1257 | [] -> failwith "call_user_func - needs a name"
1258 | arg :: args ->
1259 emit_call_user_func id arg args
1262 | A.Id (_, "exit") when List.length args = 1 ->
1263 let e = List.hd_exn args in
1264 emit_exit e, Flavor.Cell
1266 | A.Id (_, id) ->
1267 begin match args, istype_op id with
1268 | [(_, A.Lvar (_, arg_id))], Some i ->
1269 instr (IIsset (IsTypeL (Local.Named arg_id, i))),
1270 Flavor.Cell
1271 | [arg_expr], Some i ->
1272 gather [
1273 from_expr arg_expr;
1274 instr (IIsset (IsTypeC i))
1275 ], Flavor.Cell
1276 | _ -> default ()
1278 | _ -> default ()
1281 (* Emit code for an expression that might leave a cell or reference on the
1282 * stack. Return which flavor it left.
1284 and emit_flavored_expr (_, expr_ as expr) =
1285 match expr_ with
1286 | A.Call (e, args, uargs) when not (is_special_function e) ->
1287 emit_call e args uargs
1288 | _ ->
1289 from_expr expr, Flavor.Cell
1291 and is_literal expr =
1292 match snd expr with
1293 | A.Array afl
1294 | A.Collection ((_, "vec"), afl)
1295 | A.Collection ((_, "keyset"), afl)
1296 | A.Collection ((_, "dict"), afl) -> is_literal_afield_list afl
1297 | A.Float _
1298 | A.String _
1299 | A.Int _
1300 | A.Null
1301 | A.False
1302 | A.True -> true
1303 | _ -> false
1305 and is_literal_afield_list afl =
1306 List.for_all afl
1307 ~f:(function A.AFvalue e -> is_literal e
1308 | A.AFkvalue (k,v) -> is_literal k && is_literal v)
1310 and emit_final_member_op stack_index op mk =
1311 match op with
1312 | LValOp.Set -> instr (IFinal (SetM (stack_index, mk)))
1313 | LValOp.SetOp op -> instr (IFinal (SetOpM (stack_index, op, mk)))
1314 | LValOp.IncDec op -> instr (IFinal (IncDecM (stack_index, op, mk)))
1315 | LValOp.Unset -> instr (IFinal (UnsetM (stack_index, mk)))
1317 and emit_final_local_op op lid =
1318 match op with
1319 | LValOp.Set -> instr (IMutator (SetL lid))
1320 | LValOp.SetOp op -> instr (IMutator (SetOpL (lid, op)))
1321 | LValOp.IncDec op -> instr (IMutator (IncDecL (lid, op)))
1322 | LValOp.Unset -> instr (IMutator (UnsetL lid))
1324 and emit_final_global_op op =
1325 match op with
1326 | LValOp.Set -> instr (IMutator SetG)
1327 | LValOp.SetOp op -> instr (IMutator (SetOpG op))
1328 | LValOp.IncDec op -> instr (IMutator (IncDecG op))
1329 | LValOp.Unset -> instr (IMutator UnsetG)
1331 and emit_final_static_op cid id op =
1332 match op with
1333 | LValOp.Set -> instr (IMutator (SetS 0))
1334 | LValOp.SetOp op -> instr (IMutator (SetOpS (op, 0)))
1335 | LValOp.IncDec op -> instr (IMutator (IncDecS (op, 0)))
1336 | LValOp.Unset ->
1337 gather [
1338 instr_string ("Attempt to unset static property " ^ cid ^ "::" ^ id);
1339 instr (IOp (Fatal FatalOp.Runtime))
1342 (* Given a local $local and a list of integer array indices i_1, ..., i_n,
1343 * generate code to extract the value of $local[i_n]...[i_1]:
1344 * BaseL $local Warn
1345 * Dim Warn EI:i_n ...
1346 * Dim Warn EI:i_2
1347 * QueryM 0 CGet EI:i_1
1349 and emit_array_get_fixed local indices =
1350 gather (
1351 instr (IBase (BaseL (local, MemberOpMode.Warn))) ::
1352 List.rev_mapi indices (fun i ix ->
1353 let mk = MemberKey.EI (Int64.of_int ix) in
1354 if i = 0
1355 then instr (IFinal (QueryM (0, QueryOp.CGet, mk)))
1356 else instr (IBase (Dim (MemberOpMode.Warn, mk))))
1359 (* Generate code for each lvalue assignment in a list destructuring expression.
1360 * Lvalues are assigned right-to-left, regardless of the nesting structure. So
1361 * list($a, list($b, $c)) = $d
1362 * and list(list($a, $b), $c) = $d
1363 * will both assign to $c, $b and $a in that order.
1365 and emit_lval_op_list local indices expr =
1366 match expr with
1367 | (_, A.List exprs) ->
1368 gather @@
1369 List.rev @@
1370 List.mapi exprs (fun i expr -> emit_lval_op_list local (i::indices) expr)
1371 | _ ->
1372 (* Generate code to access the element from the array *)
1373 let access_instrs = emit_array_get_fixed local indices in
1374 (* Generate code to assign to the lvalue *)
1375 let assign_instrs = emit_lval_op_nonlist LValOp.Set expr access_instrs 1 in
1376 gather [
1377 assign_instrs;
1378 instr_popc
1381 (* Emit code for an l-value operation *)
1382 and emit_lval_op op expr1 opt_expr2 =
1383 match op, expr1, opt_expr2 with
1384 (* Special case for list destructuring, only on assignment *)
1385 | LValOp.Set, (_, A.List _), Some expr2 ->
1386 stash_in_local ~leave_on_stack:true expr2
1387 begin fun local _break_label ->
1388 emit_lval_op_list local [] expr1
1390 | _ ->
1391 let rhs_instrs, rhs_stack_size =
1392 match opt_expr2 with
1393 | None -> empty, 0
1394 | Some e -> from_expr e, 1 in
1395 emit_lval_op_nonlist op expr1 rhs_instrs rhs_stack_size
1397 and emit_lval_op_nonlist op (_, expr_) rhs_instrs rhs_stack_size =
1398 match expr_ with
1399 | A.Lvar (_, id) ->
1400 gather [
1401 rhs_instrs;
1402 emit_final_local_op op (Local.Named id)
1405 | A.Array_get((_, A.Lvar (_, x)), Some e) when x = SN.Superglobals.globals ->
1406 gather [
1407 from_expr e;
1408 rhs_instrs;
1409 emit_final_global_op op
1412 | A.Array_get(base_expr, opt_elem_expr) ->
1413 let mode =
1414 match op with
1415 | LValOp.Unset -> MemberOpMode.Unset
1416 | _ -> MemberOpMode.Define in
1417 let elem_expr_instrs, elem_stack_size = emit_elem_instrs opt_elem_expr in
1418 let base_offset = elem_stack_size + rhs_stack_size in
1419 let base_expr_instrs, base_setup_instrs, base_stack_size =
1420 emit_base mode base_offset None base_expr in
1421 let mk = get_elem_member_key rhs_stack_size opt_elem_expr in
1422 let total_stack_size = elem_stack_size + base_stack_size in
1423 let final_instr = emit_final_member_op total_stack_size op mk in
1424 gather [
1425 base_expr_instrs;
1426 elem_expr_instrs;
1427 rhs_instrs;
1428 base_setup_instrs;
1429 final_instr
1432 | A.Obj_get(e1, e2, null_flavor) ->
1433 let mode =
1434 match op with
1435 | LValOp.Unset -> MemberOpMode.Unset
1436 | _ -> MemberOpMode.Define in
1437 let prop_expr_instrs, prop_stack_size = emit_prop_instrs e2 in
1438 let base_offset = prop_stack_size + rhs_stack_size in
1439 let base_expr_instrs, base_setup_instrs, base_stack_size =
1440 emit_base mode base_offset None e1 in
1441 let mk = get_prop_member_key null_flavor rhs_stack_size e2 in
1442 let total_stack_size = prop_stack_size + base_stack_size in
1443 let final_instr = emit_final_member_op total_stack_size op mk in
1444 gather [
1445 base_expr_instrs;
1446 prop_expr_instrs;
1447 rhs_instrs;
1448 base_setup_instrs;
1449 final_instr
1452 | A.Class_get((_, cid), (_, id)) ->
1453 let prop_expr_instrs = instr_string (strip_dollar id) in
1454 let final_instr = emit_final_static_op cid id op in
1455 gather [
1456 prop_expr_instrs;
1457 emit_class_id cid;
1458 rhs_instrs;
1459 final_instr
1462 | _ ->
1463 gather [
1464 emit_nyi "lval expression";
1465 rhs_instrs;
1468 and emit_unop op e =
1469 let ints_overflow_to_ints =
1470 Hhbc_options.ints_overflow_to_ints !compiler_options in
1471 match op with
1472 | A.Utild -> gather [from_expr e; instr (IOp BitNot)]
1473 | A.Unot -> gather [from_expr e; instr (IOp Not)]
1474 | A.Uplus -> gather
1475 [instr (ILitConst (Int (Int64.zero)));
1476 from_expr e;
1477 instr (IOp (if ints_overflow_to_ints then Add else AddO))]
1478 | A.Uminus -> gather
1479 [instr (ILitConst (Int (Int64.zero)));
1480 from_expr e;
1481 instr (IOp (if ints_overflow_to_ints then Sub else SubO))]
1482 | A.Uincr | A.Udecr | A.Upincr | A.Updecr ->
1483 begin match unop_to_incdec_op op with
1484 | None -> emit_nyi "incdec"
1485 | Some incdec_op ->
1486 emit_lval_op (LValOp.IncDec incdec_op) e None
1488 | A.Uref ->
1489 emit_nyi "references"
1491 and from_exprs exprs =
1492 gather (List.map exprs from_expr)
1494 and stash_in_local ?(leave_on_stack=false) e f =
1495 let break_label = Label.next_regular () in
1496 match e with
1497 | (_, A.Lvar (_, id)) ->
1498 gather [
1499 f (Local.Named id) break_label;
1500 instr_label break_label;
1502 | _ ->
1503 let temp = Local.get_unnamed_local () in
1504 let fault_label = Label.next_fault () in
1505 gather [
1506 from_expr e;
1507 instr_setl temp;
1508 instr_popc;
1509 instr_try_fault
1510 fault_label
1511 (* try block *)
1512 (f temp break_label)
1513 (* fault block *)
1514 (gather [
1515 instr_unsetl temp;
1516 instr_unwind ]);
1517 instr_label break_label;
1518 if leave_on_stack then instr_pushl temp else instr_unsetl temp