1 /* d-codegen.cc --  Code generation and routines for manipulation of GCC trees.
2    Copyright (C) 2006-2020 Free Software Foundation, Inc.
3 
4 GCC is free software; you can redistribute it and/or modify
5 it under the terms of the GNU General Public License as published by
6 the Free Software Foundation; either version 3, or (at your option)
7 any later version.
8 
9 GCC is distributed in the hope that it will be useful,
10 but WITHOUT ANY WARRANTY; without even the implied warranty of
11 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
12 GNU General Public License for more details.
13 
14 You should have received a copy of the GNU General Public License
15 along with GCC; see the file COPYING3.  If not see
16 <http://www.gnu.org/licenses/>.  */
17 
18 #include "config.h"
19 #include "system.h"
20 #include "coretypes.h"
21 
22 #include "dmd/aggregate.h"
23 #include "dmd/ctfe.h"
24 #include "dmd/declaration.h"
25 #include "dmd/identifier.h"
26 #include "dmd/target.h"
27 #include "dmd/template.h"
28 
29 #include "tree.h"
30 #include "tree-iterator.h"
31 #include "fold-const.h"
32 #include "diagnostic.h"
33 #include "langhooks.h"
34 #include "target.h"
35 #include "stringpool.h"
36 #include "varasm.h"
37 #include "stor-layout.h"
38 #include "attribs.h"
39 #include "function.h"
40 
41 #include "d-tree.h"
42 
43 
44 /* Return the GCC location for the D frontend location LOC.  */
45 
46 location_t
make_location_t(const Loc & loc)47 make_location_t (const Loc& loc)
48 {
49   location_t gcc_location = input_location;
50 
51   if (loc.filename)
52     {
53       linemap_add (line_table, LC_ENTER, 0, loc.filename, loc.linnum);
54       linemap_line_start (line_table, loc.linnum, 0);
55       gcc_location = linemap_position_for_column (line_table, loc.charnum);
56       linemap_add (line_table, LC_LEAVE, 0, NULL, 0);
57     }
58 
59   return gcc_location;
60 }
61 
62 /* Return the DECL_CONTEXT for symbol DSYM.  */
63 
64 tree
d_decl_context(Dsymbol * dsym)65 d_decl_context (Dsymbol *dsym)
66 {
67   Dsymbol *parent = dsym;
68   Declaration *decl = dsym->isDeclaration ();
69   AggregateDeclaration *ad = dsym->isAggregateDeclaration ();
70 
71   while ((parent = parent->toParent2 ()))
72     {
73       /* We've reached the top-level module namespace.
74 	 Set DECL_CONTEXT as the NAMESPACE_DECL of the enclosing module,
75 	 but only for extern(D) symbols.  */
76       if (parent->isModule ())
77 	{
78 	  if ((decl != NULL && decl->linkage != LINKd)
79 	      || (ad != NULL && ad->classKind != ClassKind::d))
80 	    return NULL_TREE;
81 
82 	  return build_import_decl (parent);
83 	}
84 
85       /* Declarations marked as 'static' or '__gshared' are never
86 	 part of any context except at module level.  */
87       if (decl != NULL && decl->isDataseg ())
88 	continue;
89 
90       /* Nested functions.  */
91       FuncDeclaration *fd = parent->isFuncDeclaration ();
92       if (fd != NULL)
93 	return get_symbol_decl (fd);
94 
95       /* Methods of classes or structs.  */
96       AggregateDeclaration *ad = parent->isAggregateDeclaration ();
97       if (ad != NULL)
98 	{
99 	  tree context = build_ctype (ad->type);
100 	  /* Want the underlying RECORD_TYPE.  */
101 	  if (ad->isClassDeclaration ())
102 	    context = TREE_TYPE (context);
103 
104 	  return context;
105 	}
106     }
107 
108   return NULL_TREE;
109 }
110 
111 /* Return a copy of record TYPE but safe to modify in any way.  */
112 
113 tree
copy_aggregate_type(tree type)114 copy_aggregate_type (tree type)
115 {
116   tree newtype = build_distinct_type_copy (type);
117   TYPE_FIELDS (newtype) = copy_list (TYPE_FIELDS (type));
118 
119   for (tree f = TYPE_FIELDS (newtype); f; f = DECL_CHAIN (f))
120     DECL_FIELD_CONTEXT (f) = newtype;
121 
122   return newtype;
123 }
124 
125 /* Return TRUE if declaration DECL is a reference type.  */
126 
127 bool
declaration_reference_p(Declaration * decl)128 declaration_reference_p (Declaration *decl)
129 {
130   Type *tb = decl->type->toBasetype ();
131 
132   /* Declaration is a reference type.  */
133   if (tb->ty == Treference || decl->storage_class & (STCout | STCref))
134     return true;
135 
136   return false;
137 }
138 
139 /* Returns the real type for declaration DECL.  */
140 
141 tree
declaration_type(Declaration * decl)142 declaration_type (Declaration *decl)
143 {
144   /* Lazy declarations are converted to delegates.  */
145   if (decl->storage_class & STClazy)
146     {
147       TypeFunction *tf = TypeFunction::create (NULL, decl->type, false, LINKd);
148       TypeDelegate *t = TypeDelegate::create (tf);
149       return build_ctype (t->merge2 ());
150     }
151 
152   /* Static array va_list have array->pointer conversions applied.  */
153   if (decl->isParameter () && valist_array_p (decl->type))
154     {
155       Type *valist = decl->type->nextOf ()->pointerTo ();
156       valist = valist->castMod (decl->type->mod);
157       return build_ctype (valist);
158     }
159 
160   tree type = build_ctype (decl->type);
161 
162   /* Parameter is passed by reference.  */
163   if (declaration_reference_p (decl))
164     return build_reference_type (type);
165 
166   /* The 'this' parameter is always const.  */
167   if (decl->isThisDeclaration ())
168     return insert_type_modifiers (type, MODconst);
169 
170   return type;
171 }
172 
173 /* These should match the Declaration versions above
174    Return TRUE if parameter ARG is a reference type.  */
175 
176 bool
parameter_reference_p(Parameter * arg)177 parameter_reference_p (Parameter *arg)
178 {
179   Type *tb = arg->type->toBasetype ();
180 
181   /* Parameter is a reference type.  */
182   if (tb->ty == Treference || arg->storageClass & (STCout | STCref))
183     return true;
184 
185   return false;
186 }
187 
188 /* Returns the real type for parameter ARG.  */
189 
190 tree
parameter_type(Parameter * arg)191 parameter_type (Parameter *arg)
192 {
193   /* Lazy parameters are converted to delegates.  */
194   if (arg->storageClass & STClazy)
195     {
196       TypeFunction *tf = TypeFunction::create (NULL, arg->type, false, LINKd);
197       TypeDelegate *t = TypeDelegate::create (tf);
198       return build_ctype (t->merge2 ());
199     }
200 
201   /* Static array va_list have array->pointer conversions applied.  */
202   if (valist_array_p (arg->type))
203     {
204       Type *valist = arg->type->nextOf ()->pointerTo ();
205       valist = valist->castMod (arg->type->mod);
206       return build_ctype (valist);
207     }
208 
209   tree type = build_ctype (arg->type);
210 
211   /* Parameter is passed by reference.  */
212   if (parameter_reference_p (arg))
213     return build_reference_type (type);
214 
215   /* Pass non-POD structs by invisible reference.  */
216   if (TREE_ADDRESSABLE (type))
217     {
218       type = build_reference_type (type);
219       /* There are no other pointer to this temporary.  */
220       type = build_qualified_type (type, TYPE_QUAL_RESTRICT);
221     }
222 
223   /* Front-end has already taken care of type promotions.  */
224   return type;
225 }
226 
227 /* Build INTEGER_CST of type TYPE with the value VALUE.  */
228 
229 tree
build_integer_cst(dinteger_t value,tree type)230 build_integer_cst (dinteger_t value, tree type)
231 {
232   /* The type is error_mark_node, we can't do anything.  */
233   if (error_operand_p (type))
234     return type;
235 
236   return build_int_cst_type (type, value);
237 }
238 
239 /* Build REAL_CST of type TOTYPE with the value VALUE.  */
240 
241 tree
build_float_cst(const real_t & value,Type * totype)242 build_float_cst (const real_t& value, Type *totype)
243 {
244   real_t new_value;
245   TypeBasic *tb = totype->isTypeBasic ();
246 
247   gcc_assert (tb != NULL);
248 
249   tree type_node = build_ctype (tb);
250   real_convert (&new_value.rv (), TYPE_MODE (type_node), &value.rv ());
251 
252   return build_real (type_node, new_value.rv ());
253 }
254 
255 /* Returns the .length component from the D dynamic array EXP.  */
256 
257 tree
d_array_length(tree exp)258 d_array_length (tree exp)
259 {
260   if (error_operand_p (exp))
261     return exp;
262 
263   gcc_assert (TYPE_DYNAMIC_ARRAY (TREE_TYPE (exp)));
264 
265   /* Get the back-end type for the array and pick out the array
266      length field (assumed to be the first field).  */
267   tree len_field = TYPE_FIELDS (TREE_TYPE (exp));
268   return component_ref (exp, len_field);
269 }
270 
271 /* Returns the .ptr component from the D dynamic array EXP.  */
272 
273 tree
d_array_ptr(tree exp)274 d_array_ptr (tree exp)
275 {
276   if (error_operand_p (exp))
277     return exp;
278 
279   gcc_assert (TYPE_DYNAMIC_ARRAY (TREE_TYPE (exp)));
280 
281   /* Get the back-end type for the array and pick out the array
282      data pointer field (assumed to be the second field).  */
283   tree ptr_field = TREE_CHAIN (TYPE_FIELDS (TREE_TYPE (exp)));
284   return component_ref (exp, ptr_field);
285 }
286 
287 /* Returns a constructor for D dynamic array type TYPE of .length LEN
288    and .ptr pointing to DATA.  */
289 
290 tree
d_array_value(tree type,tree len,tree data)291 d_array_value (tree type, tree len, tree data)
292 {
293   tree len_field, ptr_field;
294   vec<constructor_elt, va_gc> *ce = NULL;
295 
296   gcc_assert (TYPE_DYNAMIC_ARRAY (type));
297   len_field = TYPE_FIELDS (type);
298   ptr_field = TREE_CHAIN (len_field);
299 
300   len = convert (TREE_TYPE (len_field), len);
301   data = convert (TREE_TYPE (ptr_field), data);
302 
303   CONSTRUCTOR_APPEND_ELT (ce, len_field, len);
304   CONSTRUCTOR_APPEND_ELT (ce, ptr_field, data);
305 
306   return build_constructor (type, ce);
307 }
308 
309 /* Returns value representing the array length of expression EXP.
310    TYPE could be a dynamic or static array.  */
311 
312 tree
get_array_length(tree exp,Type * type)313 get_array_length (tree exp, Type *type)
314 {
315   Type *tb = type->toBasetype ();
316 
317   switch (tb->ty)
318     {
319     case Tsarray:
320       return size_int (((TypeSArray *) tb)->dim->toUInteger ());
321 
322     case Tarray:
323       return d_array_length (exp);
324 
325     default:
326       error ("cannot determine the length of a %qs", type->toChars ());
327       return error_mark_node;
328     }
329 }
330 
331 /* Create BINFO for a ClassDeclaration's inheritance tree.
332    InterfaceDeclaration's are not included.  */
333 
334 tree
build_class_binfo(tree super,ClassDeclaration * cd)335 build_class_binfo (tree super, ClassDeclaration *cd)
336 {
337   tree binfo = make_tree_binfo (1);
338   tree ctype = build_ctype (cd->type);
339 
340   /* Want RECORD_TYPE, not POINTER_TYPE.  */
341   BINFO_TYPE (binfo) = TREE_TYPE (ctype);
342   BINFO_INHERITANCE_CHAIN (binfo) = super;
343   BINFO_OFFSET (binfo) = integer_zero_node;
344 
345   if (cd->baseClass)
346     BINFO_BASE_APPEND (binfo, build_class_binfo (binfo, cd->baseClass));
347 
348   return binfo;
349 }
350 
351 /* Create BINFO for an InterfaceDeclaration's inheritance tree.
352    In order to access all inherited methods in the debugger,
353    the entire tree must be described.
354    This function makes assumptions about interface layout.  */
355 
356 tree
build_interface_binfo(tree super,ClassDeclaration * cd,unsigned & offset)357 build_interface_binfo (tree super, ClassDeclaration *cd, unsigned& offset)
358 {
359   tree binfo = make_tree_binfo (cd->baseclasses->dim);
360   tree ctype = build_ctype (cd->type);
361 
362   /* Want RECORD_TYPE, not POINTER_TYPE.  */
363   BINFO_TYPE (binfo) = TREE_TYPE (ctype);
364   BINFO_INHERITANCE_CHAIN (binfo) = super;
365   BINFO_OFFSET (binfo) = size_int (offset * Target::ptrsize);
366   BINFO_VIRTUAL_P (binfo) = 1;
367 
368   for (size_t i = 0; i < cd->baseclasses->dim; i++, offset++)
369     {
370       BaseClass *bc = (*cd->baseclasses)[i];
371       BINFO_BASE_APPEND (binfo, build_interface_binfo (binfo, bc->sym, offset));
372     }
373 
374   return binfo;
375 }
376 
377 /* Returns the .funcptr component from the D delegate EXP.  */
378 
379 tree
delegate_method(tree exp)380 delegate_method (tree exp)
381 {
382   /* Get the back-end type for the delegate and pick out the funcptr field
383      (assumed to be the second field).  */
384   gcc_assert (TYPE_DELEGATE (TREE_TYPE (exp)));
385   tree method_field = TREE_CHAIN (TYPE_FIELDS (TREE_TYPE (exp)));
386   return component_ref (exp, method_field);
387 }
388 
389 /* Returns the .object component from the delegate EXP.  */
390 
391 tree
delegate_object(tree exp)392 delegate_object (tree exp)
393 {
394   /* Get the back-end type for the delegate and pick out the object field
395      (assumed to be the first field).  */
396   gcc_assert (TYPE_DELEGATE (TREE_TYPE (exp)));
397   tree obj_field = TYPE_FIELDS (TREE_TYPE (exp));
398   return component_ref (exp, obj_field);
399 }
400 
401 /* Build a delegate literal of type TYPE whose pointer function is
402    METHOD, and hidden object is OBJECT.  */
403 
404 tree
build_delegate_cst(tree method,tree object,Type * type)405 build_delegate_cst (tree method, tree object, Type *type)
406 {
407   tree ctor = make_node (CONSTRUCTOR);
408   tree ctype;
409 
410   Type *tb = type->toBasetype ();
411   if (tb->ty == Tdelegate)
412     ctype = build_ctype (type);
413   else
414     {
415       /* Convert a function method into an anonymous delegate.  */
416       ctype = make_struct_type ("delegate()", 2,
417 				get_identifier ("object"), TREE_TYPE (object),
418 				get_identifier ("func"), TREE_TYPE (method));
419       TYPE_DELEGATE (ctype) = 1;
420     }
421 
422   vec<constructor_elt, va_gc> *ce = NULL;
423   CONSTRUCTOR_APPEND_ELT (ce, TYPE_FIELDS (ctype), object);
424   CONSTRUCTOR_APPEND_ELT (ce, TREE_CHAIN (TYPE_FIELDS (ctype)), method);
425 
426   CONSTRUCTOR_ELTS (ctor) = ce;
427   TREE_TYPE (ctor) = ctype;
428 
429   return ctor;
430 }
431 
432 /* Builds a temporary tree to store the CALLEE and OBJECT
433    of a method call expression of type TYPE.  */
434 
435 tree
build_method_call(tree callee,tree object,Type * type)436 build_method_call (tree callee, tree object, Type *type)
437 {
438   tree t = build_delegate_cst (callee, object, type);
439   METHOD_CALL_EXPR (t) = 1;
440   return t;
441 }
442 
443 /* Extract callee and object from T and return in to CALLEE and OBJECT.  */
444 
445 void
extract_from_method_call(tree t,tree & callee,tree & object)446 extract_from_method_call (tree t, tree& callee, tree& object)
447 {
448   gcc_assert (METHOD_CALL_EXPR (t));
449   object = CONSTRUCTOR_ELT (t, 0)->value;
450   callee = CONSTRUCTOR_ELT (t, 1)->value;
451 }
452 
453 /* Build a typeof(null) constant of type TYPE.  Handles certain special case
454    conversions, where the underlying type is an aggregate with a nullable
455    interior pointer.  */
456 
457 tree
build_typeof_null_value(Type * type)458 build_typeof_null_value (Type *type)
459 {
460   Type *tb = type->toBasetype ();
461   tree value;
462 
463   /* For dynamic arrays, set length and pointer fields to zero.  */
464   if (tb->ty == Tarray)
465     value = d_array_value (build_ctype (type), size_int (0), null_pointer_node);
466 
467   /* For associative arrays, set the pointer field to null.  */
468   else if (tb->ty == Taarray)
469     {
470       tree ctype = build_ctype (type);
471       gcc_assert (TYPE_ASSOCIATIVE_ARRAY (ctype));
472 
473       value = build_constructor_single (ctype, TYPE_FIELDS (ctype),
474 					null_pointer_node);
475     }
476 
477   /* For delegates, set the frame and function pointer fields to null.  */
478   else if (tb->ty == Tdelegate)
479     value = build_delegate_cst (null_pointer_node, null_pointer_node, type);
480 
481   /* Simple zero constant for all other types.  */
482   else
483     value = build_zero_cst (build_ctype (type));
484 
485   TREE_CONSTANT (value) = 1;
486   return value;
487 }
488 
489 /* Build a dereference into the virtual table for OBJECT to retrieve
490    a function pointer of type FNTYPE at position INDEX.  */
491 
492 tree
build_vindex_ref(tree object,tree fntype,size_t index)493 build_vindex_ref (tree object, tree fntype, size_t index)
494 {
495   /* The vtable is the first field.  Interface methods are also in the class's
496      vtable, so we don't need to convert from a class to an interface.  */
497   tree result = build_deref (object);
498   result = component_ref (result, TYPE_FIELDS (TREE_TYPE (result)));
499 
500   gcc_assert (POINTER_TYPE_P (fntype));
501 
502   return build_memref (fntype, result, size_int (Target::ptrsize * index));
503 }
504 
505 /* Return TRUE if EXP is a valid lvalue.  Lvalue references cannot be
506    made into temporaries, otherwise any assignments will be lost.  */
507 
508 static bool
lvalue_p(tree exp)509 lvalue_p (tree exp)
510 {
511   const enum tree_code code = TREE_CODE (exp);
512 
513   switch (code)
514     {
515     case SAVE_EXPR:
516       return false;
517 
518     case ARRAY_REF:
519     case INDIRECT_REF:
520     case VAR_DECL:
521     case PARM_DECL:
522     case RESULT_DECL:
523       return !FUNC_OR_METHOD_TYPE_P (TREE_TYPE (exp));
524 
525     case IMAGPART_EXPR:
526     case REALPART_EXPR:
527     case COMPONENT_REF:
528     CASE_CONVERT:
529       return lvalue_p (TREE_OPERAND (exp, 0));
530 
531     case COND_EXPR:
532       return (lvalue_p (TREE_OPERAND (exp, 1)
533 			? TREE_OPERAND (exp, 1)
534 			: TREE_OPERAND (exp, 0))
535 	      && lvalue_p (TREE_OPERAND (exp, 2)));
536 
537     case TARGET_EXPR:
538       return true;
539 
540     case COMPOUND_EXPR:
541       return lvalue_p (TREE_OPERAND (exp, 1));
542 
543     default:
544       return false;
545     }
546 }
547 
548 /* Create a SAVE_EXPR if EXP might have unwanted side effects if referenced
549    more than once in an expression.  */
550 
551 tree
d_save_expr(tree exp)552 d_save_expr (tree exp)
553 {
554   if (TREE_SIDE_EFFECTS (exp))
555     {
556       if (lvalue_p (exp))
557 	return stabilize_reference (exp);
558 
559       return save_expr (exp);
560     }
561 
562   return exp;
563 }
564 
565 /* VALUEP is an expression we want to pre-evaluate or perform a computation on.
566    The expression returned by this function is the part whose value we don't
567    care about, storing the value in VALUEP.  Callers must ensure that the
568    returned expression is evaluated before VALUEP.  */
569 
570 tree
stabilize_expr(tree * valuep)571 stabilize_expr (tree *valuep)
572 {
573   tree expr = *valuep;
574   const enum tree_code code = TREE_CODE (expr);
575   tree lhs;
576   tree rhs;
577 
578   switch (code)
579     {
580     case COMPOUND_EXPR:
581       /* Given ((e1, ...), eN):
582 	 Store the last RHS 'eN' expression in VALUEP.  */
583       lhs = TREE_OPERAND (expr, 0);
584       rhs = TREE_OPERAND (expr, 1);
585       lhs = compound_expr (lhs, stabilize_expr (&rhs));
586       *valuep = rhs;
587       return lhs;
588 
589     default:
590       return NULL_TREE;
591     }
592 }
593 
594 /* Return a TARGET_EXPR, initializing the DECL with EXP.  */
595 
596 tree
build_target_expr(tree decl,tree exp)597 build_target_expr (tree decl, tree exp)
598 {
599   tree type = TREE_TYPE (decl);
600   tree result = build4 (TARGET_EXPR, type, decl, exp, NULL_TREE, NULL_TREE);
601 
602   if (EXPR_HAS_LOCATION (exp))
603     SET_EXPR_LOCATION (result, EXPR_LOCATION (exp));
604 
605   /* If decl must always reside in memory.  */
606   if (TREE_ADDRESSABLE (type))
607     d_mark_addressable (decl);
608 
609   /* Always set TREE_SIDE_EFFECTS so that expand_expr does not ignore the
610      TARGET_EXPR.  If there really turn out to be no side effects, then the
611      optimizer should be able to remove it.  */
612   TREE_SIDE_EFFECTS (result) = 1;
613 
614   return result;
615 }
616 
617 /* Like the above function, but initializes a new temporary.  */
618 
619 tree
force_target_expr(tree exp)620 force_target_expr (tree exp)
621 {
622   tree decl = build_decl (input_location, VAR_DECL, NULL_TREE,
623 			  TREE_TYPE (exp));
624   DECL_CONTEXT (decl) = current_function_decl;
625   DECL_ARTIFICIAL (decl) = 1;
626   DECL_IGNORED_P (decl) = 1;
627   layout_decl (decl, 0);
628 
629   return build_target_expr (decl, exp);
630 }
631 
632 /* Returns the address of the expression EXP.  */
633 
634 tree
build_address(tree exp)635 build_address (tree exp)
636 {
637   if (error_operand_p (exp))
638     return exp;
639 
640   tree ptrtype;
641   tree type = TREE_TYPE (exp);
642 
643   if (TREE_CODE (exp) == STRING_CST)
644     {
645       /* Just convert string literals (char[]) to C-style strings (char *),
646 	 otherwise the latter method (char[]*) causes conversion problems
647 	 during gimplification.  */
648       ptrtype = build_pointer_type (TREE_TYPE (type));
649     }
650   else if (TYPE_MAIN_VARIANT (type) == TYPE_MAIN_VARIANT (va_list_type_node)
651 	   && TREE_CODE (TYPE_MAIN_VARIANT (type)) == ARRAY_TYPE)
652     {
653       /* Special case for va_list, allow arrays to decay to a pointer.  */
654       ptrtype = build_pointer_type (TREE_TYPE (type));
655     }
656   else
657     ptrtype = build_pointer_type (type);
658 
659   /* Maybe rewrite: &(e1, e2) => (e1, &e2).  */
660   tree init = stabilize_expr (&exp);
661 
662   /* Can't take the address of a manifest constant, instead use its value.  */
663   if (TREE_CODE (exp) == CONST_DECL)
664     exp = DECL_INITIAL (exp);
665 
666   /* Some expression lowering may request an address of a compile-time constant,
667      or other non-lvalue expression.  Make sure it is assigned to a location we
668      can reference.  */
669   if ((CONSTANT_CLASS_P (exp) && TREE_CODE (exp) != STRING_CST)
670       || TREE_CODE (exp) == CALL_EXPR)
671     exp = force_target_expr (exp);
672 
673   d_mark_addressable (exp);
674   exp = build_fold_addr_expr_with_type_loc (input_location, exp, ptrtype);
675 
676   if (TREE_CODE (exp) == ADDR_EXPR)
677     TREE_NO_TRAMPOLINE (exp) = 1;
678 
679   return compound_expr (init, exp);
680 }
681 
682 /* Mark EXP saying that we need to be able to take the
683    address of it; it should not be allocated in a register.  */
684 
685 tree
d_mark_addressable(tree exp)686 d_mark_addressable (tree exp)
687 {
688   switch (TREE_CODE (exp))
689     {
690     case ADDR_EXPR:
691     case COMPONENT_REF:
692     case ARRAY_REF:
693     case REALPART_EXPR:
694     case IMAGPART_EXPR:
695       d_mark_addressable (TREE_OPERAND (exp, 0));
696       break;
697 
698     case PARM_DECL:
699     case VAR_DECL:
700     case RESULT_DECL:
701     case CONST_DECL:
702     case FUNCTION_DECL:
703       TREE_ADDRESSABLE (exp) = 1;
704       break;
705 
706     case CONSTRUCTOR:
707       TREE_ADDRESSABLE (exp) = 1;
708       break;
709 
710     case TARGET_EXPR:
711       TREE_ADDRESSABLE (exp) = 1;
712       d_mark_addressable (TREE_OPERAND (exp, 0));
713       break;
714 
715     default:
716       break;
717     }
718 
719   return exp;
720 }
721 
722 /* Mark EXP as "used" in the program for the benefit of
723    -Wunused warning purposes.  */
724 
725 tree
d_mark_used(tree exp)726 d_mark_used (tree exp)
727 {
728   switch (TREE_CODE (exp))
729     {
730     case VAR_DECL:
731     case CONST_DECL:
732     case PARM_DECL:
733     case RESULT_DECL:
734     case FUNCTION_DECL:
735       TREE_USED (exp) = 1;
736       break;
737 
738     case ARRAY_REF:
739     case COMPONENT_REF:
740     case MODIFY_EXPR:
741     case REALPART_EXPR:
742     case IMAGPART_EXPR:
743     case NOP_EXPR:
744     case CONVERT_EXPR:
745     case ADDR_EXPR:
746       d_mark_used (TREE_OPERAND (exp, 0));
747       break;
748 
749     case COMPOUND_EXPR:
750       d_mark_used (TREE_OPERAND (exp, 0));
751       d_mark_used (TREE_OPERAND (exp, 1));
752       break;
753 
754     default:
755       break;
756     }
757   return exp;
758 }
759 
760 /* Mark EXP as read, not just set, for set but not used -Wunused
761    warning purposes.  */
762 
763 tree
d_mark_read(tree exp)764 d_mark_read (tree exp)
765 {
766   switch (TREE_CODE (exp))
767     {
768     case VAR_DECL:
769     case PARM_DECL:
770       TREE_USED (exp) = 1;
771       DECL_READ_P (exp) = 1;
772       break;
773 
774     case ARRAY_REF:
775     case COMPONENT_REF:
776     case MODIFY_EXPR:
777     case REALPART_EXPR:
778     case IMAGPART_EXPR:
779     case NOP_EXPR:
780     case CONVERT_EXPR:
781     case ADDR_EXPR:
782       d_mark_read (TREE_OPERAND (exp, 0));
783       break;
784 
785     case COMPOUND_EXPR:
786       d_mark_read (TREE_OPERAND (exp, 1));
787       break;
788 
789     default:
790       break;
791     }
792   return exp;
793 }
794 
795 /* Return TRUE if the struct SD is suitable for comparison using memcmp.
796    This is because we don't guarantee that padding is zero-initialized for
797    a stack variable, so we can't use memcmp to compare struct values.  */
798 
799 bool
identity_compare_p(StructDeclaration * sd)800 identity_compare_p (StructDeclaration *sd)
801 {
802   if (sd->isUnionDeclaration ())
803     return true;
804 
805   unsigned offset = 0;
806 
807   for (size_t i = 0; i < sd->fields.dim; i++)
808     {
809       VarDeclaration *vd = sd->fields[i];
810       Type *tb = vd->type->toBasetype ();
811 
812       /* Check inner data structures.  */
813       if (tb->ty == Tstruct)
814 	{
815 	  TypeStruct *ts = (TypeStruct *) tb;
816 	  if (!identity_compare_p (ts->sym))
817 	    return false;
818 	}
819 
820       /* Check for types that may have padding.  */
821       if ((tb->ty == Tcomplex80 || tb->ty == Tfloat80 || tb->ty == Timaginary80)
822 	  && Target::realpad != 0)
823 	return false;
824 
825       if (offset <= vd->offset)
826 	{
827 	  /* There's a hole in the struct.  */
828 	  if (offset != vd->offset)
829 	    return false;
830 
831 	  offset += vd->type->size ();
832 	}
833     }
834 
835   /* Any trailing padding may not be zero.  */
836   if (offset < sd->structsize)
837     return false;
838 
839   return true;
840 }
841 
842 /* Build a floating-point identity comparison between T1 and T2, ignoring any
843    excessive padding in the type.  CODE is EQ_EXPR or NE_EXPR comparison.  */
844 
845 tree
build_float_identity(tree_code code,tree t1,tree t2)846 build_float_identity (tree_code code, tree t1, tree t2)
847 {
848   tree tmemcmp = builtin_decl_explicit (BUILT_IN_MEMCMP);
849   tree size = size_int (TYPE_PRECISION (TREE_TYPE (t1)) / BITS_PER_UNIT);
850 
851   tree result = build_call_expr (tmemcmp, 3, build_address (t1),
852 				 build_address (t2), size);
853   return build_boolop (code, result, integer_zero_node);
854 }
855 
856 /* Lower a field-by-field equality expression between T1 and T2 of type SD.
857    CODE is the EQ_EXPR or NE_EXPR comparison.  */
858 
859 static tree
lower_struct_comparison(tree_code code,StructDeclaration * sd,tree t1,tree t2)860 lower_struct_comparison (tree_code code, StructDeclaration *sd,
861 			 tree t1, tree t2)
862 {
863   tree_code tcode = (code == EQ_EXPR) ? TRUTH_ANDIF_EXPR : TRUTH_ORIF_EXPR;
864   tree tmemcmp = NULL_TREE;
865 
866   /* We can skip the compare if the structs are empty.  */
867   if (sd->fields.dim == 0)
868     {
869       tmemcmp = build_boolop (code, integer_zero_node, integer_zero_node);
870       if (TREE_SIDE_EFFECTS (t2))
871 	tmemcmp = compound_expr (t2, tmemcmp);
872       if (TREE_SIDE_EFFECTS (t1))
873 	tmemcmp = compound_expr (t1, tmemcmp);
874 
875       return tmemcmp;
876     }
877 
878   /* Let back-end take care of union comparisons.  */
879   if (sd->isUnionDeclaration ())
880     {
881       tmemcmp = build_call_expr (builtin_decl_explicit (BUILT_IN_MEMCMP), 3,
882 				 build_address (t1), build_address (t2),
883 				 size_int (sd->structsize));
884 
885       return build_boolop (code, tmemcmp, integer_zero_node);
886     }
887 
888   for (size_t i = 0; i < sd->fields.dim; i++)
889     {
890       VarDeclaration *vd = sd->fields[i];
891       Type *type = vd->type->toBasetype ();
892       tree sfield = get_symbol_decl (vd);
893 
894       tree t1ref = component_ref (t1, sfield);
895       tree t2ref = component_ref (t2, sfield);
896       tree tcmp;
897 
898       if (type->ty == Tstruct)
899 	{
900 	  /* Compare inner data structures.  */
901 	  StructDeclaration *decl = ((TypeStruct *) type)->sym;
902 	  tcmp = lower_struct_comparison (code, decl, t1ref, t2ref);
903 	}
904       else if (type->ty != Tvector && type->isintegral ())
905 	{
906 	  /* Integer comparison, no special handling required.  */
907 	  tcmp = build_boolop (code, t1ref, t2ref);
908 	}
909       else if (type->ty != Tvector && type->isfloating ())
910 	{
911 	  /* Floating-point comparison, don't compare padding in type.  */
912 	  if (!type->iscomplex ())
913 	    tcmp = build_float_identity (code, t1ref, t2ref);
914 	  else
915 	    {
916 	      tree req = build_float_identity (code, real_part (t1ref),
917 					       real_part (t2ref));
918 	      tree ieq = build_float_identity (code, imaginary_part (t1ref),
919 					       imaginary_part (t2ref));
920 
921 	      tcmp = build_boolop (tcode, req, ieq);
922 	    }
923 	}
924       else
925 	{
926 	  tree stype = build_ctype (type);
927 	  opt_scalar_int_mode mode = int_mode_for_mode (TYPE_MODE (stype));
928 
929 	  if (mode.exists ())
930 	    {
931 	      /* Compare field bits as their corresponding integer type.
932 		    *((T*) &t1) == *((T*) &t2)  */
933 	      tree tmode = lang_hooks.types.type_for_mode (mode.require (), 1);
934 
935 	      if (tmode == NULL_TREE)
936 		tmode = make_unsigned_type (GET_MODE_BITSIZE (mode.require ()));
937 
938 	      t1ref = build_vconvert (tmode, t1ref);
939 	      t2ref = build_vconvert (tmode, t2ref);
940 
941 	      tcmp = build_boolop (code, t1ref, t2ref);
942 	    }
943 	  else
944 	    {
945 	      /* Simple memcmp between types.  */
946 	      tcmp = build_call_expr (builtin_decl_explicit (BUILT_IN_MEMCMP),
947 				      3, build_address (t1ref),
948 				      build_address (t2ref),
949 				      TYPE_SIZE_UNIT (stype));
950 
951 	      tcmp = build_boolop (code, tcmp, integer_zero_node);
952 	    }
953 	}
954 
955       tmemcmp = (tmemcmp) ? build_boolop (tcode, tmemcmp, tcmp) : tcmp;
956     }
957 
958   return tmemcmp;
959 }
960 
961 
962 /* Build an equality expression between two RECORD_TYPES T1 and T2 of type SD.
963    If possible, use memcmp, otherwise field-by-field comparison is done.
964    CODE is the EQ_EXPR or NE_EXPR comparison.  */
965 
966 tree
build_struct_comparison(tree_code code,StructDeclaration * sd,tree t1,tree t2)967 build_struct_comparison (tree_code code, StructDeclaration *sd,
968 			 tree t1, tree t2)
969 {
970   /* We can skip the compare if the structs are empty.  */
971   if (sd->fields.dim == 0)
972     {
973       tree exp = build_boolop (code, integer_zero_node, integer_zero_node);
974       if (TREE_SIDE_EFFECTS (t2))
975 	exp = compound_expr (t2, exp);
976       if (TREE_SIDE_EFFECTS (t1))
977 	exp = compound_expr (t1, exp);
978 
979       return exp;
980     }
981 
982   /* Make temporaries to prevent multiple evaluations.  */
983   tree t1init = stabilize_expr (&t1);
984   tree t2init = stabilize_expr (&t2);
985   tree result;
986 
987   t1 = d_save_expr (t1);
988   t2 = d_save_expr (t2);
989 
990   /* Bitwise comparison of structs not returned in memory may not work
991      due to data holes loosing its zero padding upon return.
992      As a heuristic, small structs are not compared using memcmp either.  */
993   if (TYPE_MODE (TREE_TYPE (t1)) != BLKmode || !identity_compare_p (sd))
994     result = lower_struct_comparison (code, sd, t1, t2);
995   else
996     {
997       /* Do bit compare of structs.  */
998       tree size = size_int (sd->structsize);
999       tree tmemcmp = build_call_expr (builtin_decl_explicit (BUILT_IN_MEMCMP),
1000 				      3, build_address (t1),
1001 				      build_address (t2), size);
1002 
1003       result = build_boolop (code, tmemcmp, integer_zero_node);
1004     }
1005 
1006   return compound_expr (compound_expr (t1init, t2init), result);
1007 }
1008 
1009 /* Build an equality expression between two ARRAY_TYPES of size LENGTH.
1010    The pointer references are T1 and T2, and the element type is SD.
1011    CODE is the EQ_EXPR or NE_EXPR comparison.  */
1012 
1013 tree
build_array_struct_comparison(tree_code code,StructDeclaration * sd,tree length,tree t1,tree t2)1014 build_array_struct_comparison (tree_code code, StructDeclaration *sd,
1015 			       tree length, tree t1, tree t2)
1016 {
1017   tree_code tcode = (code == EQ_EXPR) ? TRUTH_ANDIF_EXPR : TRUTH_ORIF_EXPR;
1018 
1019   /* Build temporary for the result of the comparison.
1020      Initialize as either 0 or 1 depending on operation.  */
1021   tree result = build_local_temp (d_bool_type);
1022   tree init = build_boolop (code, integer_zero_node, integer_zero_node);
1023   add_stmt (build_assign (INIT_EXPR, result, init));
1024 
1025   /* Cast pointer-to-array to pointer-to-struct.  */
1026   tree ptrtype = build_ctype (sd->type->pointerTo ());
1027   tree lentype = TREE_TYPE (length);
1028 
1029   push_binding_level (level_block);
1030   push_stmt_list ();
1031 
1032   /* Build temporary locals for length and pointers.  */
1033   tree t = build_local_temp (size_type_node);
1034   add_stmt (build_assign (INIT_EXPR, t, length));
1035   length = t;
1036 
1037   t = build_local_temp (ptrtype);
1038   add_stmt (build_assign (INIT_EXPR, t, d_convert (ptrtype, t1)));
1039   t1 = t;
1040 
1041   t = build_local_temp (ptrtype);
1042   add_stmt (build_assign (INIT_EXPR, t, d_convert (ptrtype, t2)));
1043   t2 = t;
1044 
1045   /* Build loop for comparing each element.  */
1046   push_stmt_list ();
1047 
1048   /* Exit logic for the loop.
1049 	if (length == 0 || result OP 0) break;  */
1050   t = build_boolop (EQ_EXPR, length, d_convert (lentype, integer_zero_node));
1051   t = build_boolop (TRUTH_ORIF_EXPR, t, build_boolop (code, result,
1052 						      boolean_false_node));
1053   t = build1 (EXIT_EXPR, void_type_node, t);
1054   add_stmt (t);
1055 
1056   /* Do comparison, caching the value.
1057 	result = result OP (*t1 == *t2);  */
1058   t = build_struct_comparison (code, sd, build_deref (t1), build_deref (t2));
1059   t = build_boolop (tcode, result, t);
1060   t = modify_expr (result, t);
1061   add_stmt (t);
1062 
1063   /* Move both pointers to next element position.
1064 	t1++, t2++;  */
1065   tree size = d_convert (ptrtype, TYPE_SIZE_UNIT (TREE_TYPE (ptrtype)));
1066   t = build2 (POSTINCREMENT_EXPR, ptrtype, t1, size);
1067   add_stmt (t);
1068   t = build2 (POSTINCREMENT_EXPR, ptrtype, t2, size);
1069   add_stmt (t);
1070 
1071   /* Decrease loop counter.
1072 	length -= 1;  */
1073   t = build2 (POSTDECREMENT_EXPR, lentype, length,
1074 	     d_convert (lentype, integer_one_node));
1075   add_stmt (t);
1076 
1077   /* Pop statements and finish loop.  */
1078   tree body = pop_stmt_list ();
1079   add_stmt (build1 (LOOP_EXPR, void_type_node, body));
1080 
1081   /* Wrap it up into a bind expression.  */
1082   tree stmt_list = pop_stmt_list ();
1083   tree block = pop_binding_level ();
1084 
1085   body = build3 (BIND_EXPR, void_type_node,
1086 		 BLOCK_VARS (block), stmt_list, block);
1087 
1088   return compound_expr (body, result);
1089 }
1090 
1091 /* Build a constructor for a variable of aggregate type TYPE using the
1092    initializer INIT, an ordered flat list of fields and values provided
1093    by the frontend.  The returned constructor should be a value that
1094    matches the layout of TYPE.  */
1095 
1096 tree
build_struct_literal(tree type,vec<constructor_elt,va_gc> * init)1097 build_struct_literal (tree type, vec<constructor_elt, va_gc> *init)
1098 {
1099   /* If the initializer was empty, use default zero initialization.  */
1100   if (vec_safe_is_empty (init))
1101     return build_constructor (type, NULL);
1102 
1103   vec<constructor_elt, va_gc> *ve = NULL;
1104   HOST_WIDE_INT offset = 0;
1105   bool constant_p = true;
1106   bool finished = false;
1107 
1108   /* Walk through each field, matching our initializer list.  */
1109   for (tree field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
1110     {
1111       bool is_initialized = false;
1112       tree value;
1113 
1114       if (DECL_NAME (field) == NULL_TREE
1115 	  && RECORD_OR_UNION_TYPE_P (TREE_TYPE (field))
1116 	  && ANON_AGGR_TYPE_P (TREE_TYPE (field)))
1117 	{
1118 	  /* Search all nesting aggregates, if nothing is found, then
1119 	     this will return an empty initializer to fill the hole.  */
1120 	  value = build_struct_literal (TREE_TYPE (field), init);
1121 
1122 	  if (!initializer_zerop (value))
1123 	    is_initialized = true;
1124 	}
1125       else
1126 	{
1127 	  /* Search for the value to initialize the next field.  Once found,
1128 	     pop it from the init list so we don't look at it again.  */
1129 	  unsigned HOST_WIDE_INT idx;
1130 	  tree index;
1131 
1132 	  FOR_EACH_CONSTRUCTOR_ELT (init, idx, index, value)
1133 	    {
1134 	      /* If the index is NULL, then just assign it to the next field.
1135 		 This comes from layout_typeinfo(), which generates a flat
1136 		 list of values that we must shape into the record type.  */
1137 	      if (index == field || index == NULL_TREE)
1138 		{
1139 		  init->ordered_remove (idx);
1140 		  if (!finished)
1141 		    is_initialized = true;
1142 		  break;
1143 		}
1144 	    }
1145 	}
1146 
1147       if (is_initialized)
1148 	{
1149 	  HOST_WIDE_INT fieldpos = int_byte_position (field);
1150 	  gcc_assert (value != NULL_TREE);
1151 
1152 	  /* Must not initialize fields that overlap.  */
1153 	  if (fieldpos < offset)
1154 	    {
1155 	      /* Find the nearest user defined type and field.  */
1156 	      tree vtype = type;
1157 	      while (ANON_AGGR_TYPE_P (vtype))
1158 		vtype = TYPE_CONTEXT (vtype);
1159 
1160 	      tree vfield = field;
1161 	      if (RECORD_OR_UNION_TYPE_P (TREE_TYPE (vfield))
1162 		  && ANON_AGGR_TYPE_P (TREE_TYPE (vfield)))
1163 		vfield = TYPE_FIELDS (TREE_TYPE (vfield));
1164 
1165 	      /* Must not generate errors for compiler generated fields.  */
1166 	      gcc_assert (TYPE_NAME (vtype) && DECL_NAME (vfield));
1167 	      error ("overlapping initializer for field %qT.%qD",
1168 		     TYPE_NAME (vtype), DECL_NAME (vfield));
1169 	    }
1170 
1171 	  if (!TREE_CONSTANT (value))
1172 	    constant_p = false;
1173 
1174 	  CONSTRUCTOR_APPEND_ELT (ve, field, value);
1175 
1176 	  /* For unions, only the first field is initialized, any other field
1177 	     initializers found for this union are drained and ignored.  */
1178 	  if (TREE_CODE (type) == UNION_TYPE)
1179 	    finished = true;
1180 	}
1181 
1182       /* Move offset to the next position in the struct.  */
1183       if (TREE_CODE (type) == RECORD_TYPE)
1184 	{
1185 	  offset = int_byte_position (field)
1186 	    + int_size_in_bytes (TREE_TYPE (field));
1187 	}
1188 
1189       /* If all initializers have been assigned, there's nothing else to do.  */
1190       if (vec_safe_is_empty (init))
1191 	break;
1192     }
1193 
1194   /* Ensure that we have consumed all values.  */
1195   gcc_assert (vec_safe_is_empty (init) || ANON_AGGR_TYPE_P (type));
1196 
1197   tree ctor = build_constructor (type, ve);
1198 
1199   if (constant_p)
1200     TREE_CONSTANT (ctor) = 1;
1201 
1202   return ctor;
1203 }
1204 
1205 /* Given the TYPE of an anonymous field inside T, return the
1206    FIELD_DECL for the field.  If not found return NULL_TREE.
1207    Because anonymous types can nest, we must also search all
1208    anonymous fields that are directly reachable.  */
1209 
1210 static tree
lookup_anon_field(tree t,tree type)1211 lookup_anon_field (tree t, tree type)
1212 {
1213   t = TYPE_MAIN_VARIANT (t);
1214 
1215   for (tree field = TYPE_FIELDS (t); field; field = DECL_CHAIN (field))
1216     {
1217       if (DECL_NAME (field) == NULL_TREE)
1218 	{
1219 	  /* If we find it directly, return the field.  */
1220 	  if (type == TYPE_MAIN_VARIANT (TREE_TYPE (field)))
1221 	    return field;
1222 
1223 	  /* Otherwise, it could be nested, search harder.  */
1224 	  if (RECORD_OR_UNION_TYPE_P (TREE_TYPE (field))
1225 	      && ANON_AGGR_TYPE_P (TREE_TYPE (field)))
1226 	    {
1227 	      tree subfield = lookup_anon_field (TREE_TYPE (field), type);
1228 	      if (subfield)
1229 		return subfield;
1230 	    }
1231 	}
1232     }
1233 
1234   return NULL_TREE;
1235 }
1236 
1237 /* Builds OBJECT.FIELD component reference.  */
1238 
1239 tree
component_ref(tree object,tree field)1240 component_ref (tree object, tree field)
1241 {
1242   if (error_operand_p (object) || error_operand_p (field))
1243     return error_mark_node;
1244 
1245   gcc_assert (TREE_CODE (field) == FIELD_DECL);
1246 
1247   /* Maybe rewrite: (e1, e2).field => (e1, e2.field)  */
1248   tree init = stabilize_expr (&object);
1249 
1250   /* If the FIELD is from an anonymous aggregate, generate a reference
1251      to the anonymous data member, and recur to find FIELD.  */
1252   if (ANON_AGGR_TYPE_P (DECL_CONTEXT (field)))
1253     {
1254       tree anonymous_field = lookup_anon_field (TREE_TYPE (object),
1255 						DECL_CONTEXT (field));
1256       object = component_ref (object, anonymous_field);
1257     }
1258 
1259   tree result = fold_build3_loc (input_location, COMPONENT_REF,
1260 				 TREE_TYPE (field), object, field, NULL_TREE);
1261 
1262   return compound_expr (init, result);
1263 }
1264 
1265 /* Build an assignment expression of lvalue LHS from value RHS.
1266    CODE is the code for a binary operator that we use to combine
1267    the old value of LHS with RHS to get the new value.  */
1268 
1269 tree
build_assign(tree_code code,tree lhs,tree rhs)1270 build_assign (tree_code code, tree lhs, tree rhs)
1271 {
1272   tree init = stabilize_expr (&lhs);
1273   init = compound_expr (init, stabilize_expr (&rhs));
1274 
1275   /* If initializing the LHS using a function that returns via NRVO.  */
1276   if (code == INIT_EXPR && TREE_CODE (rhs) == CALL_EXPR
1277       && AGGREGATE_TYPE_P (TREE_TYPE (rhs))
1278       && aggregate_value_p (TREE_TYPE (rhs), rhs))
1279     {
1280       /* Mark as addressable here, which should ensure the return slot is the
1281 	 address of the LHS expression, taken care of by back-end.  */
1282       d_mark_addressable (lhs);
1283       CALL_EXPR_RETURN_SLOT_OPT (rhs) = true;
1284     }
1285 
1286   /* The LHS assignment replaces the temporary in TARGET_EXPR_SLOT.  */
1287   if (TREE_CODE (rhs) == TARGET_EXPR)
1288     {
1289       /* If CODE is not INIT_EXPR, can't initialize LHS directly,
1290 	 since that would cause the LHS to be constructed twice.
1291 	 So we force the TARGET_EXPR to be expanded without a target.  */
1292       if (code != INIT_EXPR)
1293 	{
1294 	  init = compound_expr (init, rhs);
1295 	  rhs = TARGET_EXPR_SLOT (rhs);
1296 	}
1297       else
1298 	{
1299 	  d_mark_addressable (lhs);
1300 	  rhs = TARGET_EXPR_INITIAL (rhs);
1301 	}
1302     }
1303 
1304   tree result = fold_build2_loc (input_location, code,
1305 				 TREE_TYPE (lhs), lhs, rhs);
1306   return compound_expr (init, result);
1307 }
1308 
1309 /* Build an assignment expression of lvalue LHS from value RHS.  */
1310 
1311 tree
modify_expr(tree lhs,tree rhs)1312 modify_expr (tree lhs, tree rhs)
1313 {
1314   return build_assign (MODIFY_EXPR, lhs, rhs);
1315 }
1316 
1317 /* Return EXP represented as TYPE.  */
1318 
1319 tree
build_nop(tree type,tree exp)1320 build_nop (tree type, tree exp)
1321 {
1322   if (error_operand_p (exp))
1323     return exp;
1324 
1325   /* Maybe rewrite: cast(TYPE)(e1, e2) => (e1, cast(TYPE) e2)  */
1326   tree init = stabilize_expr (&exp);
1327   exp = fold_build1_loc (input_location, NOP_EXPR, type, exp);
1328 
1329   return compound_expr (init, exp);
1330 }
1331 
1332 /* Return EXP to be viewed as being another type TYPE.  Same as build_nop,
1333    except that EXP is type-punned, rather than a straight-forward cast.  */
1334 
1335 tree
build_vconvert(tree type,tree exp)1336 build_vconvert (tree type, tree exp)
1337 {
1338   /* Building *(cast(TYPE *)&e1) directly rather then using VIEW_CONVERT_EXPR
1339      makes sure this works for vector-to-array viewing, or if EXP ends up being
1340      used as the LHS of a MODIFY_EXPR.  */
1341   return indirect_ref (type, build_address (exp));
1342 }
1343 
1344 /* Maybe warn about ARG being an address that can never be null.  */
1345 
1346 static void
warn_for_null_address(tree arg)1347 warn_for_null_address (tree arg)
1348 {
1349   if (TREE_CODE (arg) == ADDR_EXPR
1350       && decl_with_nonnull_addr_p (TREE_OPERAND (arg, 0)))
1351     warning (OPT_Waddress,
1352 	     "the address of %qD will never be %<null%>",
1353 	     TREE_OPERAND (arg, 0));
1354 }
1355 
1356 /* Build a boolean ARG0 op ARG1 expression.  */
1357 
1358 tree
build_boolop(tree_code code,tree arg0,tree arg1)1359 build_boolop (tree_code code, tree arg0, tree arg1)
1360 {
1361   /* Aggregate comparisons may get lowered to a call to builtin memcmp,
1362      so need to remove all side effects incase its address is taken.  */
1363   if (AGGREGATE_TYPE_P (TREE_TYPE (arg0)))
1364     arg0 = d_save_expr (arg0);
1365   if (AGGREGATE_TYPE_P (TREE_TYPE (arg1)))
1366     arg1 = d_save_expr (arg1);
1367 
1368   if (VECTOR_TYPE_P (TREE_TYPE (arg0)) && VECTOR_TYPE_P (TREE_TYPE (arg1)))
1369     {
1370       /* Build a vector comparison.
1371 	 VEC_COND_EXPR <e1 op e2, { -1, -1, -1, -1 }, { 0, 0, 0, 0 }>; */
1372       tree type = TREE_TYPE (arg0);
1373       tree cmptype = truth_type_for (type);
1374       tree cmp = fold_build2_loc (input_location, code, cmptype, arg0, arg1);
1375 
1376       return fold_build3_loc (input_location, VEC_COND_EXPR, type, cmp,
1377 			      build_minus_one_cst (type),
1378 			      build_zero_cst (type));
1379     }
1380 
1381   if (code == EQ_EXPR || code == NE_EXPR)
1382     {
1383       /* Check if comparing the address of a variable to null.  */
1384       if (POINTER_TYPE_P (TREE_TYPE (arg0)) && integer_zerop (arg1))
1385 	warn_for_null_address (arg0);
1386       if (POINTER_TYPE_P (TREE_TYPE (arg1)) && integer_zerop (arg0))
1387 	warn_for_null_address (arg1);
1388     }
1389 
1390   return fold_build2_loc (input_location, code, d_bool_type,
1391 			  arg0, d_convert (TREE_TYPE (arg0), arg1));
1392 }
1393 
1394 /* Return a COND_EXPR.  ARG0, ARG1, and ARG2 are the three
1395    arguments to the conditional expression.  */
1396 
1397 tree
build_condition(tree type,tree arg0,tree arg1,tree arg2)1398 build_condition (tree type, tree arg0, tree arg1, tree arg2)
1399 {
1400   if (arg1 == void_node)
1401     arg1 = build_empty_stmt (input_location);
1402 
1403   if (arg2 == void_node)
1404     arg2 = build_empty_stmt (input_location);
1405 
1406   return fold_build3_loc (input_location, COND_EXPR,
1407 			  type, arg0, arg1, arg2);
1408 }
1409 
1410 tree
build_vcondition(tree arg0,tree arg1,tree arg2)1411 build_vcondition (tree arg0, tree arg1, tree arg2)
1412 {
1413   return build_condition (void_type_node, arg0, arg1, arg2);
1414 }
1415 
1416 /* Build a compound expr to join ARG0 and ARG1 together.  */
1417 
1418 tree
compound_expr(tree arg0,tree arg1)1419 compound_expr (tree arg0, tree arg1)
1420 {
1421   if (arg1 == NULL_TREE)
1422     return arg0;
1423 
1424   if (arg0 == NULL_TREE || !TREE_SIDE_EFFECTS (arg0))
1425     return arg1;
1426 
1427   if (TREE_CODE (arg1) == TARGET_EXPR)
1428     {
1429       /* If the rhs is a TARGET_EXPR, then build the compound expression
1430 	 inside the target_expr's initializer.  This helps the compiler
1431 	 to eliminate unnecessary temporaries.  */
1432       tree init = compound_expr (arg0, TARGET_EXPR_INITIAL (arg1));
1433       TARGET_EXPR_INITIAL (arg1) = init;
1434 
1435       return arg1;
1436     }
1437 
1438   return fold_build2_loc (input_location, COMPOUND_EXPR,
1439 			  TREE_TYPE (arg1), arg0, arg1);
1440 }
1441 
1442 /* Build a return expression.  */
1443 
1444 tree
return_expr(tree ret)1445 return_expr (tree ret)
1446 {
1447   return fold_build1_loc (input_location, RETURN_EXPR,
1448 			  void_type_node, ret);
1449 }
1450 
1451 /* Return the product of ARG0 and ARG1 as a size_type_node.  */
1452 
1453 tree
size_mult_expr(tree arg0,tree arg1)1454 size_mult_expr (tree arg0, tree arg1)
1455 {
1456   return fold_build2_loc (input_location, MULT_EXPR, size_type_node,
1457 			  d_convert (size_type_node, arg0),
1458 			  d_convert (size_type_node, arg1));
1459 
1460 }
1461 
1462 /* Return the real part of CE, which should be a complex expression.  */
1463 
1464 tree
real_part(tree ce)1465 real_part (tree ce)
1466 {
1467   return fold_build1_loc (input_location, REALPART_EXPR,
1468 			  TREE_TYPE (TREE_TYPE (ce)), ce);
1469 }
1470 
1471 /* Return the imaginary part of CE, which should be a complex expression.  */
1472 
1473 tree
imaginary_part(tree ce)1474 imaginary_part (tree ce)
1475 {
1476   return fold_build1_loc (input_location, IMAGPART_EXPR,
1477 			  TREE_TYPE (TREE_TYPE (ce)), ce);
1478 }
1479 
1480 /* Build a complex expression of type TYPE using RE and IM.  */
1481 
1482 tree
complex_expr(tree type,tree re,tree im)1483 complex_expr (tree type, tree re, tree im)
1484 {
1485   return fold_build2_loc (input_location, COMPLEX_EXPR,
1486 			  type, re, im);
1487 }
1488 
1489 /* Cast EXP (which should be a pointer) to TYPE* and then indirect.
1490    The back-end requires this cast in many cases.  */
1491 
1492 tree
indirect_ref(tree type,tree exp)1493 indirect_ref (tree type, tree exp)
1494 {
1495   if (error_operand_p (exp))
1496     return exp;
1497 
1498   /* Maybe rewrite: *(e1, e2) => (e1, *e2)  */
1499   tree init = stabilize_expr (&exp);
1500 
1501   if (TREE_CODE (TREE_TYPE (exp)) == REFERENCE_TYPE)
1502     exp = fold_build1 (INDIRECT_REF, type, exp);
1503   else
1504     {
1505       exp = build_nop (build_pointer_type (type), exp);
1506       exp = build_deref (exp);
1507     }
1508 
1509   return compound_expr (init, exp);
1510 }
1511 
1512 /* Returns indirect reference of EXP, which must be a pointer type.  */
1513 
1514 tree
build_deref(tree exp)1515 build_deref (tree exp)
1516 {
1517   if (error_operand_p (exp))
1518     return exp;
1519 
1520   /* Maybe rewrite: *(e1, e2) => (e1, *e2)  */
1521   tree init = stabilize_expr (&exp);
1522 
1523   gcc_assert (POINTER_TYPE_P (TREE_TYPE (exp)));
1524 
1525   if (TREE_CODE (exp) == ADDR_EXPR)
1526     exp = TREE_OPERAND (exp, 0);
1527   else
1528     exp = build_fold_indirect_ref (exp);
1529 
1530   return compound_expr (init, exp);
1531 }
1532 
1533 /* Builds pointer offset expression PTR[INDEX].  */
1534 
1535 tree
build_array_index(tree ptr,tree index)1536 build_array_index (tree ptr, tree index)
1537 {
1538   if (error_operand_p (ptr) || error_operand_p (index))
1539     return error_mark_node;
1540 
1541   tree ptr_type = TREE_TYPE (ptr);
1542   tree target_type = TREE_TYPE (ptr_type);
1543 
1544   tree type = lang_hooks.types.type_for_size (TYPE_PRECISION (sizetype),
1545 					      TYPE_UNSIGNED (sizetype));
1546 
1547   /* Array element size.  */
1548   tree size_exp = size_in_bytes (target_type);
1549 
1550   if (integer_zerop (size_exp))
1551     {
1552       /* Test for array of void.  */
1553       if (TYPE_MODE (target_type) == TYPE_MODE (void_type_node))
1554 	index = fold_convert (type, index);
1555       else
1556 	{
1557 	  /* Should catch this earlier.  */
1558 	  error ("invalid use of incomplete type %qD", TYPE_NAME (target_type));
1559 	  ptr_type = error_mark_node;
1560 	}
1561     }
1562   else if (integer_onep (size_exp))
1563     {
1564       /* Array of bytes -- No need to multiply.  */
1565       index = fold_convert (type, index);
1566     }
1567   else
1568     {
1569       index = d_convert (type, index);
1570       index = fold_build2 (MULT_EXPR, TREE_TYPE (index),
1571 			   index, d_convert (TREE_TYPE (index), size_exp));
1572       index = fold_convert (type, index);
1573     }
1574 
1575   if (integer_zerop (index))
1576     return ptr;
1577 
1578   return fold_build2 (POINTER_PLUS_EXPR, ptr_type, ptr, index);
1579 }
1580 
1581 /* Builds pointer offset expression *(PTR OP OFFSET)
1582    OP could be a plus or minus expression.  */
1583 
1584 tree
build_offset_op(tree_code op,tree ptr,tree offset)1585 build_offset_op (tree_code op, tree ptr, tree offset)
1586 {
1587   gcc_assert (op == MINUS_EXPR || op == PLUS_EXPR);
1588 
1589   tree type = lang_hooks.types.type_for_size (TYPE_PRECISION (sizetype),
1590 					      TYPE_UNSIGNED (sizetype));
1591   offset = fold_convert (type, offset);
1592 
1593   if (op == MINUS_EXPR)
1594     offset = fold_build1 (NEGATE_EXPR, type, offset);
1595 
1596   return fold_build2 (POINTER_PLUS_EXPR, TREE_TYPE (ptr), ptr, offset);
1597 }
1598 
1599 /* Builds pointer offset expression *(PTR + OFFSET).  */
1600 
1601 tree
build_offset(tree ptr,tree offset)1602 build_offset (tree ptr, tree offset)
1603 {
1604   return build_offset_op (PLUS_EXPR, ptr, offset);
1605 }
1606 
1607 tree
build_memref(tree type,tree ptr,tree offset)1608 build_memref (tree type, tree ptr, tree offset)
1609 {
1610   return fold_build2 (MEM_REF, type, ptr, fold_convert (type, offset));
1611 }
1612 
1613 /* Create a tree node to set multiple elements to a single value.  */
1614 
1615 tree
build_array_set(tree ptr,tree length,tree value)1616 build_array_set (tree ptr, tree length, tree value)
1617 {
1618   tree ptrtype = TREE_TYPE (ptr);
1619   tree lentype = TREE_TYPE (length);
1620 
1621   push_binding_level (level_block);
1622   push_stmt_list ();
1623 
1624   /* Build temporary locals for length and ptr, and maybe value.  */
1625   tree t = build_local_temp (size_type_node);
1626   add_stmt (build_assign (INIT_EXPR, t, length));
1627   length = t;
1628 
1629   t = build_local_temp (ptrtype);
1630   add_stmt (build_assign (INIT_EXPR, t, ptr));
1631   ptr = t;
1632 
1633   if (TREE_SIDE_EFFECTS (value))
1634     {
1635       t = build_local_temp (TREE_TYPE (value));
1636       add_stmt (build_assign (INIT_EXPR, t, value));
1637       value = t;
1638     }
1639 
1640   /* Build loop to initialize { .length=length, .ptr=ptr } with value.  */
1641   push_stmt_list ();
1642 
1643   /* Exit logic for the loop.
1644 	if (length == 0) break;  */
1645   t = build_boolop (EQ_EXPR, length, d_convert (lentype, integer_zero_node));
1646   t = build1 (EXIT_EXPR, void_type_node, t);
1647   add_stmt (t);
1648 
1649   /* Assign value to the current pointer position.
1650 	*ptr = value;  */
1651   t = modify_expr (build_deref (ptr), value);
1652   add_stmt (t);
1653 
1654   /* Move pointer to next element position.
1655 	ptr++;  */
1656   tree size = TYPE_SIZE_UNIT (TREE_TYPE (ptrtype));
1657   t = build2 (POSTINCREMENT_EXPR, ptrtype, ptr, d_convert (ptrtype, size));
1658   add_stmt (t);
1659 
1660   /* Decrease loop counter.
1661 	length -= 1;  */
1662   t = build2 (POSTDECREMENT_EXPR, lentype, length,
1663 	      d_convert (lentype, integer_one_node));
1664   add_stmt (t);
1665 
1666   /* Pop statements and finish loop.  */
1667   tree loop_body = pop_stmt_list ();
1668   add_stmt (build1 (LOOP_EXPR, void_type_node, loop_body));
1669 
1670   /* Wrap it up into a bind expression.  */
1671   tree stmt_list = pop_stmt_list ();
1672   tree block = pop_binding_level ();
1673 
1674   return build3 (BIND_EXPR, void_type_node,
1675 		 BLOCK_VARS (block), stmt_list, block);
1676 }
1677 
1678 
1679 /* Build an array of type TYPE where all the elements are VAL.  */
1680 
1681 tree
build_array_from_val(Type * type,tree val)1682 build_array_from_val (Type *type, tree val)
1683 {
1684   gcc_assert (type->ty == Tsarray);
1685 
1686   tree etype = build_ctype (type->nextOf ());
1687 
1688   /* Initializing a multidimensional array.  */
1689   if (TREE_CODE (etype) == ARRAY_TYPE && TREE_TYPE (val) != etype)
1690     val = build_array_from_val (type->nextOf (), val);
1691 
1692   size_t dims = ((TypeSArray *) type)->dim->toInteger ();
1693   vec<constructor_elt, va_gc> *elms = NULL;
1694   vec_safe_reserve (elms, dims);
1695 
1696   val = d_convert (etype, val);
1697 
1698   for (size_t i = 0; i < dims; i++)
1699     CONSTRUCTOR_APPEND_ELT (elms, size_int (i), val);
1700 
1701   return build_constructor (build_ctype (type), elms);
1702 }
1703 
1704 /* Implicitly converts void* T to byte* as D allows { void[] a; &a[3]; }  */
1705 
1706 tree
void_okay_p(tree t)1707 void_okay_p (tree t)
1708 {
1709   tree type = TREE_TYPE (t);
1710 
1711   if (VOID_TYPE_P (TREE_TYPE (type)))
1712     {
1713       tree totype = build_ctype (Type::tuns8->pointerTo ());
1714       return fold_convert (totype, t);
1715     }
1716 
1717   return t;
1718 }
1719 
1720 /* Builds a bounds condition checking that INDEX is between 0 and LEN.
1721    The condition returns the INDEX if true, or throws a RangeError.
1722    If INCLUSIVE, we allow INDEX == LEN to return true also.  */
1723 
1724 tree
build_bounds_condition(const Loc & loc,tree index,tree len,bool inclusive)1725 build_bounds_condition (const Loc& loc, tree index, tree len, bool inclusive)
1726 {
1727   if (!array_bounds_check ())
1728     return index;
1729 
1730   /* Prevent multiple evaluations of the index.  */
1731   index = d_save_expr (index);
1732 
1733   /* Generate INDEX >= LEN && throw RangeError.
1734      No need to check whether INDEX >= 0 as the front-end should
1735      have already taken care of implicit casts to unsigned.  */
1736   tree condition = fold_build2 (inclusive ? GT_EXPR : GE_EXPR,
1737 				d_bool_type, index, len);
1738   /* Terminate the program with a trap if no D runtime present.  */
1739   tree boundserr = (global.params.checkAction == CHECKACTION_D)
1740     ? d_assert_call (loc, LIBCALL_ARRAY_BOUNDS)
1741     : build_call_expr (builtin_decl_explicit (BUILT_IN_TRAP), 0);
1742 
1743   return build_condition (TREE_TYPE (index), condition, boundserr, index);
1744 }
1745 
1746 /* Returns TRUE if array bounds checking code generation is turned on.  */
1747 
1748 bool
array_bounds_check(void)1749 array_bounds_check (void)
1750 {
1751   FuncDeclaration *fd;
1752 
1753   switch (global.params.useArrayBounds)
1754     {
1755     case BOUNDSCHECKoff:
1756       return false;
1757 
1758     case BOUNDSCHECKon:
1759       return true;
1760 
1761     case BOUNDSCHECKsafeonly:
1762       /* For D2 safe functions only.  */
1763       fd = d_function_chain->function;
1764       if (fd && fd->type->ty == Tfunction)
1765 	{
1766 	  TypeFunction *tf = (TypeFunction *) fd->type;
1767 	  if (tf->trust == TRUSTsafe)
1768 	    return true;
1769 	}
1770       return false;
1771 
1772     default:
1773       gcc_unreachable ();
1774     }
1775 }
1776 
1777 /* Returns the TypeFunction class for Type T.
1778    Assumes T is already ->toBasetype().  */
1779 
1780 TypeFunction *
get_function_type(Type * t)1781 get_function_type (Type *t)
1782 {
1783   TypeFunction *tf = NULL;
1784   if (t->ty == Tpointer)
1785     t = t->nextOf ()->toBasetype ();
1786   if (t->ty == Tfunction)
1787     tf = (TypeFunction *) t;
1788   else if (t->ty == Tdelegate)
1789     tf = (TypeFunction *) ((TypeDelegate *) t)->next;
1790   return tf;
1791 }
1792 
1793 /* Returns TRUE if CALLEE is a plain nested function outside the scope of
1794    CALLER.  In which case, CALLEE is being called through an alias that was
1795    passed to CALLER.  */
1796 
1797 bool
call_by_alias_p(FuncDeclaration * caller,FuncDeclaration * callee)1798 call_by_alias_p (FuncDeclaration *caller, FuncDeclaration *callee)
1799 {
1800   if (!callee->isNested ())
1801     return false;
1802 
1803   if (caller->toParent () == callee->toParent ())
1804     return false;
1805 
1806   Dsymbol *dsym = callee;
1807 
1808   while (dsym)
1809     {
1810       if (dsym->isTemplateInstance ())
1811 	return false;
1812       else if (dsym->isFuncDeclaration () == caller)
1813 	return false;
1814       dsym = dsym->toParent ();
1815     }
1816 
1817   return true;
1818 }
1819 
1820 /* Entry point for call routines.  Builds a function call to FD.
1821    OBJECT is the 'this' reference passed and ARGS are the arguments to FD.  */
1822 
1823 tree
d_build_call_expr(FuncDeclaration * fd,tree object,Expressions * arguments)1824 d_build_call_expr (FuncDeclaration *fd, tree object, Expressions *arguments)
1825 {
1826   return d_build_call (get_function_type (fd->type),
1827 		       build_address (get_symbol_decl (fd)), object, arguments);
1828 }
1829 
1830 /* Builds a CALL_EXPR of type TF to CALLABLE.  OBJECT holds the 'this' pointer,
1831    ARGUMENTS are evaluated in left to right order, saved and promoted
1832    before passing.  */
1833 
1834 tree
d_build_call(TypeFunction * tf,tree callable,tree object,Expressions * arguments)1835 d_build_call (TypeFunction *tf, tree callable, tree object,
1836 	      Expressions *arguments)
1837 {
1838   tree ctype = TREE_TYPE (callable);
1839   tree callee = callable;
1840 
1841   if (POINTER_TYPE_P (ctype))
1842     ctype = TREE_TYPE (ctype);
1843   else
1844     callee = build_address (callable);
1845 
1846   gcc_assert (FUNC_OR_METHOD_TYPE_P (ctype));
1847   gcc_assert (tf != NULL);
1848   gcc_assert (tf->ty == Tfunction);
1849 
1850   if (TREE_CODE (ctype) != FUNCTION_TYPE && object == NULL_TREE)
1851     {
1852       /* Front-end apparently doesn't check this.  */
1853       if (TREE_CODE (callable) == FUNCTION_DECL)
1854 	{
1855 	  error ("need %<this%> to access member %qE", DECL_NAME (callable));
1856 	  return error_mark_node;
1857 	}
1858 
1859       /* Probably an internal error.  */
1860       gcc_unreachable ();
1861     }
1862 
1863   /* Build the argument list for the call.  */
1864   vec<tree, va_gc> *args = NULL;
1865   tree saved_args = NULL_TREE;
1866 
1867   /* If this is a delegate call or a nested function being called as
1868      a delegate, the object should not be NULL.  */
1869   if (object != NULL_TREE)
1870     vec_safe_push (args, object);
1871 
1872   if (arguments)
1873     {
1874       /* First pass, evaluated expanded tuples in function arguments.  */
1875       for (size_t i = 0; i < arguments->dim; ++i)
1876 	{
1877 	Lagain:
1878 	  Expression *arg = (*arguments)[i];
1879 	  gcc_assert (arg->op != TOKtuple);
1880 
1881 	  if (arg->op == TOKcomma)
1882 	    {
1883 	      CommaExp *ce = (CommaExp *) arg;
1884 	      tree tce = build_expr (ce->e1);
1885 	      saved_args = compound_expr (saved_args, tce);
1886 	      (*arguments)[i] = ce->e2;
1887 	      goto Lagain;
1888 	    }
1889 	}
1890 
1891       size_t nparams = Parameter::dim (tf->parameters);
1892       /* if _arguments[] is the first argument.  */
1893       size_t varargs = (tf->linkage == LINKd && tf->varargs == 1);
1894 
1895       /* Assumes arguments->dim <= formal_args->dim if (!tf->varargs).  */
1896       for (size_t i = 0; i < arguments->dim; ++i)
1897 	{
1898 	  Expression *arg = (*arguments)[i];
1899 	  tree targ = build_expr (arg);
1900 
1901 	  if (i - varargs < nparams && i >= varargs)
1902 	    {
1903 	      /* Actual arguments for declared formal arguments.  */
1904 	      Parameter *parg = Parameter::getNth (tf->parameters, i - varargs);
1905 	      targ = convert_for_argument (targ, parg);
1906 	    }
1907 
1908 	  /* Don't pass empty aggregates by value.  */
1909 	  if (empty_aggregate_p (TREE_TYPE (targ)) && !TREE_ADDRESSABLE (targ)
1910 	      && TREE_CODE (targ) != CONSTRUCTOR)
1911 	    {
1912 	      tree t = build_constructor (TREE_TYPE (targ), NULL);
1913 	      targ = build2 (COMPOUND_EXPR, TREE_TYPE (t), targ, t);
1914 	    }
1915 
1916 	  /* Parameter is a struct or array passed by invisible reference.  */
1917 	  if (TREE_ADDRESSABLE (TREE_TYPE (targ)))
1918 	    {
1919 	      Type *t = arg->type->toBasetype ()->baseElemOf ();
1920 	      gcc_assert (t->ty == Tstruct);
1921 	      StructDeclaration *sd = ((TypeStruct *) t)->sym;
1922 
1923 	      /* Nested structs also have ADDRESSABLE set, but if the type has
1924 		 neither a copy constructor nor a destructor available, then we
1925 		 need to take care of copying its value before passing it.  */
1926 	      if (arg->op == TOKstructliteral || (!sd->postblit && !sd->dtor))
1927 		targ = force_target_expr (targ);
1928 
1929 	      targ = convert (build_reference_type (TREE_TYPE (targ)),
1930 			      build_address (targ));
1931 	    }
1932 
1933 	  vec_safe_push (args, targ);
1934 	}
1935     }
1936 
1937   /* Evaluate the callee before calling it.  */
1938   if (TREE_SIDE_EFFECTS (callee))
1939     {
1940       callee = d_save_expr (callee);
1941       saved_args = compound_expr (callee, saved_args);
1942     }
1943 
1944   tree result = build_call_vec (TREE_TYPE (ctype), callee, args);
1945 
1946   /* Enforce left to right evaluation.  */
1947   if (tf->linkage == LINKd)
1948     CALL_EXPR_ARGS_ORDERED (result) = 1;
1949 
1950   result = maybe_expand_intrinsic (result);
1951 
1952   /* Return the value in a temporary slot so that it can be evaluated
1953      multiple times by the caller.  */
1954   if (TREE_CODE (result) == CALL_EXPR
1955       && AGGREGATE_TYPE_P (TREE_TYPE (result))
1956       && TREE_ADDRESSABLE (TREE_TYPE (result)))
1957     {
1958       CALL_EXPR_RETURN_SLOT_OPT (result) = true;
1959       result = force_target_expr (result);
1960     }
1961 
1962   return compound_expr (saved_args, result);
1963 }
1964 
1965 /* Builds a call to AssertError or AssertErrorMsg.  */
1966 
1967 tree
d_assert_call(const Loc & loc,libcall_fn libcall,tree msg)1968 d_assert_call (const Loc& loc, libcall_fn libcall, tree msg)
1969 {
1970   tree file;
1971   tree line = size_int (loc.linnum);
1972 
1973   /* File location is passed as a D string.  */
1974   if (loc.filename)
1975     {
1976       unsigned len = strlen (loc.filename);
1977       tree str = build_string (len, loc.filename);
1978       TREE_TYPE (str) = make_array_type (Type::tchar, len);
1979 
1980       file = d_array_value (build_ctype (Type::tchar->arrayOf ()),
1981 			    size_int (len), build_address (str));
1982     }
1983   else
1984     file = null_array_node;
1985 
1986   if (msg != NULL)
1987     return build_libcall (libcall, Type::tvoid, 3, msg, file, line);
1988   else
1989     return build_libcall (libcall, Type::tvoid, 2, file, line);
1990 }
1991 
1992 /* Build and return the correct call to fmod depending on TYPE.
1993    ARG0 and ARG1 are the arguments pass to the function.  */
1994 
1995 tree
build_float_modulus(tree type,tree arg0,tree arg1)1996 build_float_modulus (tree type, tree arg0, tree arg1)
1997 {
1998   tree fmodfn = NULL_TREE;
1999   tree basetype = type;
2000 
2001   if (COMPLEX_FLOAT_TYPE_P (basetype))
2002     basetype = TREE_TYPE (basetype);
2003 
2004   if (TYPE_MAIN_VARIANT (basetype) == double_type_node
2005       || TYPE_MAIN_VARIANT (basetype) == idouble_type_node)
2006     fmodfn = builtin_decl_explicit (BUILT_IN_FMOD);
2007   else if (TYPE_MAIN_VARIANT (basetype) == float_type_node
2008 	   || TYPE_MAIN_VARIANT (basetype) == ifloat_type_node)
2009     fmodfn = builtin_decl_explicit (BUILT_IN_FMODF);
2010   else if (TYPE_MAIN_VARIANT (basetype) == long_double_type_node
2011 	   || TYPE_MAIN_VARIANT (basetype) == ireal_type_node)
2012     fmodfn = builtin_decl_explicit (BUILT_IN_FMODL);
2013 
2014   if (!fmodfn)
2015     {
2016       error ("tried to perform floating-point modulo division on %qT", type);
2017       return error_mark_node;
2018     }
2019 
2020   if (COMPLEX_FLOAT_TYPE_P (type))
2021     {
2022       tree re = build_call_expr (fmodfn, 2, real_part (arg0), arg1);
2023       tree im = build_call_expr (fmodfn, 2, imaginary_part (arg0), arg1);
2024 
2025       return complex_expr (type, re, im);
2026     }
2027 
2028   if (SCALAR_FLOAT_TYPE_P (type))
2029     return build_call_expr (fmodfn, 2, arg0, arg1);
2030 
2031   /* Should have caught this above.  */
2032   gcc_unreachable ();
2033 }
2034 
2035 /* Build a function type whose first argument is a pointer to BASETYPE,
2036    which is to be used for the 'vthis' context parameter for TYPE.
2037    The base type may be a record for member functions, or a void for
2038    nested functions and delegates.  */
2039 
2040 tree
build_vthis_function(tree basetype,tree type)2041 build_vthis_function (tree basetype, tree type)
2042 {
2043   gcc_assert (TREE_CODE (type) == FUNCTION_TYPE);
2044 
2045   tree argtypes = tree_cons (NULL_TREE, build_pointer_type (basetype),
2046 			     TYPE_ARG_TYPES (type));
2047   tree fntype = build_function_type (TREE_TYPE (type), argtypes);
2048 
2049   if (RECORD_OR_UNION_TYPE_P (basetype))
2050     TYPE_METHOD_BASETYPE (fntype) = TYPE_MAIN_VARIANT (basetype);
2051   else
2052     gcc_assert (VOID_TYPE_P (basetype));
2053 
2054   return fntype;
2055 }
2056 
2057 /* Raise an error at that the context pointer of the function or object SYM is
2058    not accessible from the current scope.  */
2059 
2060 tree
error_no_frame_access(Dsymbol * sym)2061 error_no_frame_access (Dsymbol *sym)
2062 {
2063   error_at (input_location, "cannot get frame pointer to %qs",
2064 	    sym->toPrettyChars ());
2065   return null_pointer_node;
2066 }
2067 
2068 /* If SYM is a nested function, return the static chain to be
2069    used when calling that function from the current function.
2070 
2071    If SYM is a nested class or struct, return the static chain
2072    to be used when creating an instance of the class from CFUN.  */
2073 
2074 tree
get_frame_for_symbol(Dsymbol * sym)2075 get_frame_for_symbol (Dsymbol *sym)
2076 {
2077   FuncDeclaration *thisfd
2078     = d_function_chain ? d_function_chain->function : NULL;
2079   FuncDeclaration *fd = sym->isFuncDeclaration ();
2080   FuncDeclaration *fdparent = NULL;
2081   FuncDeclaration *fdoverride = NULL;
2082 
2083   if (fd != NULL)
2084     {
2085       /* Check that the nested function is properly defined.  */
2086       if (!fd->fbody)
2087 	{
2088 	  /* Should instead error on line that references 'fd'.  */
2089 	  error_at (make_location_t (fd->loc), "nested function missing body");
2090 	  return null_pointer_node;
2091 	}
2092 
2093       fdparent = fd->toParent2 ()->isFuncDeclaration ();
2094 
2095       /* Special case for __ensure and __require.  */
2096       if ((fd->ident == Identifier::idPool ("__ensure")
2097 	   || fd->ident == Identifier::idPool ("__require"))
2098 	  && fdparent != thisfd)
2099 	{
2100 	  fdoverride = fdparent;
2101 	  fdparent = thisfd;
2102 	}
2103     }
2104   else
2105     {
2106       /* It's a class (or struct).  NewExp codegen has already determined its
2107 	 outer scope is not another class, so it must be a function.  */
2108       while (sym && !sym->isFuncDeclaration ())
2109 	sym = sym->toParent2 ();
2110 
2111       fdparent = (FuncDeclaration *) sym;
2112     }
2113 
2114   /* Not a nested function, there is no frame pointer to pass.  */
2115   if (fdparent == NULL)
2116     {
2117       /* Only delegate literals report as being nested, even if they are in
2118 	 global scope.  */
2119       gcc_assert (fd && fd->isFuncLiteralDeclaration ());
2120       return null_pointer_node;
2121     }
2122 
2123   gcc_assert (thisfd != NULL);
2124 
2125   if (thisfd != fdparent)
2126     {
2127       /* If no frame pointer for this function.  */
2128       if (!thisfd->vthis)
2129 	{
2130 	  error_at (make_location_t (sym->loc),
2131 		    "%qs is a nested function and cannot be accessed from %qs",
2132 		    fdparent->toPrettyChars (), thisfd->toPrettyChars ());
2133 	  return null_pointer_node;
2134 	}
2135 
2136       /* Make sure we can get the frame pointer to the outer function.
2137 	 Go up each nesting level until we find the enclosing function.  */
2138       Dsymbol *dsym = thisfd;
2139 
2140       while (fd != dsym)
2141 	{
2142 	  /* Check if enclosing function is a function.  */
2143 	  FuncDeclaration *fdp = dsym->isFuncDeclaration ();
2144 	  Dsymbol *parent = dsym->toParent2 ();
2145 
2146 	  if (fdp != NULL)
2147 	    {
2148 	      if (fdparent == parent)
2149 		break;
2150 
2151 	      gcc_assert (fdp->isNested () || fdp->vthis);
2152 	      dsym = parent;
2153 	      continue;
2154 	    }
2155 
2156 	  /* Check if enclosed by an aggregate.  That means the current
2157 	     function must be a member function of that aggregate.  */
2158 	  AggregateDeclaration *adp = dsym->isAggregateDeclaration ();
2159 
2160 	  if (adp != NULL)
2161 	    {
2162 	      if ((adp->isClassDeclaration () || adp->isStructDeclaration ())
2163 		  && fdparent == parent)
2164 		break;
2165 	    }
2166 
2167 	  /* No frame to outer function found.  */
2168 	  if (!adp || !adp->isNested () || !adp->vthis)
2169 	    return error_no_frame_access (sym);
2170 
2171 	  dsym = parent;
2172 	}
2173     }
2174 
2175   tree ffo = get_frameinfo (fdparent);
2176   if (FRAMEINFO_CREATES_FRAME (ffo) || FRAMEINFO_STATIC_CHAIN (ffo))
2177     {
2178       tree frame_ref = get_framedecl (thisfd, fdparent);
2179 
2180       /* If 'thisfd' is a derived member function, then 'fdparent' is the
2181 	 overridden member function in the base class.  Even if there's a
2182 	 closure environment, we should give the original stack data as the
2183 	 nested function frame.  */
2184       if (fdoverride)
2185 	{
2186 	  ClassDeclaration *cdo = fdoverride->isThis ()->isClassDeclaration ();
2187 	  ClassDeclaration *cd = thisfd->isThis ()->isClassDeclaration ();
2188 	  gcc_assert (cdo && cd);
2189 
2190 	  int offset;
2191 	  if (cdo->isBaseOf (cd, &offset) && offset != 0)
2192 	    {
2193 	      /* Generate a new frame to pass to the overriden function that
2194 		 has the 'this' pointer adjusted.  */
2195 	      gcc_assert (offset != OFFSET_RUNTIME);
2196 
2197 	      tree type = FRAMEINFO_TYPE (get_frameinfo (fdoverride));
2198 	      tree fields = TYPE_FIELDS (type);
2199 	      /* The 'this' field comes immediately after the '__chain'.  */
2200 	      tree thisfield = chain_index (1, fields);
2201 	      vec<constructor_elt, va_gc> *ve = NULL;
2202 
2203 	      tree framefields = TYPE_FIELDS (FRAMEINFO_TYPE (ffo));
2204 	      frame_ref = build_deref (frame_ref);
2205 
2206 	      for (tree field = fields; field; field = DECL_CHAIN (field))
2207 		{
2208 		  tree value = component_ref (frame_ref, framefields);
2209 		  if (field == thisfield)
2210 		    value = build_offset (value, size_int (offset));
2211 
2212 		  CONSTRUCTOR_APPEND_ELT (ve, field, value);
2213 		  framefields = DECL_CHAIN (framefields);
2214 		}
2215 
2216 	      frame_ref = build_address (build_constructor (type, ve));
2217 	    }
2218 	}
2219 
2220       return frame_ref;
2221     }
2222 
2223   return null_pointer_node;
2224 }
2225 
2226 /* Return the parent function of a nested class CD.  */
2227 
2228 static FuncDeclaration *
d_nested_class(ClassDeclaration * cd)2229 d_nested_class (ClassDeclaration *cd)
2230 {
2231   FuncDeclaration *fd = NULL;
2232   while (cd && cd->isNested ())
2233     {
2234       Dsymbol *dsym = cd->toParent2 ();
2235       if ((fd = dsym->isFuncDeclaration ()))
2236 	return fd;
2237       else
2238 	cd = dsym->isClassDeclaration ();
2239     }
2240   return NULL;
2241 }
2242 
2243 /* Return the parent function of a nested struct SD.  */
2244 
2245 static FuncDeclaration *
d_nested_struct(StructDeclaration * sd)2246 d_nested_struct (StructDeclaration *sd)
2247 {
2248   FuncDeclaration *fd = NULL;
2249   while (sd && sd->isNested ())
2250     {
2251       Dsymbol *dsym = sd->toParent2 ();
2252       if ((fd = dsym->isFuncDeclaration ()))
2253 	return fd;
2254       else
2255 	sd = dsym->isStructDeclaration ();
2256     }
2257   return NULL;
2258 }
2259 
2260 
2261 /* Starting from the current function FD, try to find a suitable value of
2262    'this' in nested function instances.  A suitable 'this' value is an
2263    instance of OCD or a class that has OCD as a base.  */
2264 
2265 static tree
find_this_tree(ClassDeclaration * ocd)2266 find_this_tree (ClassDeclaration *ocd)
2267 {
2268   FuncDeclaration *fd = d_function_chain ? d_function_chain->function : NULL;
2269 
2270   while (fd)
2271     {
2272       AggregateDeclaration *ad = fd->isThis ();
2273       ClassDeclaration *cd = ad ? ad->isClassDeclaration () : NULL;
2274 
2275       if (cd != NULL)
2276 	{
2277 	  if (ocd == cd)
2278 	    return get_decl_tree (fd->vthis);
2279 	  else if (ocd->isBaseOf (cd, NULL))
2280 	    return convert_expr (get_decl_tree (fd->vthis),
2281 				 cd->type, ocd->type);
2282 
2283 	  fd = d_nested_class (cd);
2284 	}
2285       else
2286 	{
2287 	  if (fd->isNested ())
2288 	    {
2289 	      fd = fd->toParent2 ()->isFuncDeclaration ();
2290 	      continue;
2291 	    }
2292 
2293 	  fd = NULL;
2294 	}
2295     }
2296 
2297   return NULL_TREE;
2298 }
2299 
2300 /* Retrieve the outer class/struct 'this' value of DECL from
2301    the current function.  */
2302 
2303 tree
build_vthis(AggregateDeclaration * decl)2304 build_vthis (AggregateDeclaration *decl)
2305 {
2306   ClassDeclaration *cd = decl->isClassDeclaration ();
2307   StructDeclaration *sd = decl->isStructDeclaration ();
2308 
2309   /* If an aggregate nested in a function has no methods and there are no
2310      other nested functions, any static chain created here will never be
2311      translated.  Use a null pointer for the link in this case.  */
2312   tree vthis_value = null_pointer_node;
2313 
2314   if (cd != NULL || sd != NULL)
2315     {
2316       Dsymbol *outer = decl->toParent2 ();
2317 
2318       /* If the parent is a templated struct, the outer context is instead
2319 	 the enclosing symbol of where the instantiation happened.  */
2320       if (outer->isStructDeclaration ())
2321 	{
2322 	  gcc_assert (outer->parent && outer->parent->isTemplateInstance ());
2323 	  outer = ((TemplateInstance *) outer->parent)->enclosing;
2324 	}
2325 
2326       /* For outer classes, get a suitable 'this' value.
2327 	 For outer functions, get a suitable frame/closure pointer.  */
2328       ClassDeclaration *cdo = outer->isClassDeclaration ();
2329       FuncDeclaration *fdo = outer->isFuncDeclaration ();
2330 
2331       if (cdo)
2332 	{
2333 	  vthis_value = find_this_tree (cdo);
2334 	  gcc_assert (vthis_value != NULL_TREE);
2335 	}
2336       else if (fdo)
2337 	{
2338 	  tree ffo = get_frameinfo (fdo);
2339 	  if (FRAMEINFO_CREATES_FRAME (ffo) || FRAMEINFO_STATIC_CHAIN (ffo)
2340 	      || fdo->hasNestedFrameRefs ())
2341 	    vthis_value = get_frame_for_symbol (decl);
2342 	  else if (cd != NULL)
2343 	    {
2344 	      /* Classes nested in methods are allowed to access any outer
2345 		 class fields, use the function chain in this case.  */
2346 	      if (fdo->vthis && fdo->vthis->type != Type::tvoidptr)
2347 		vthis_value = get_decl_tree (fdo->vthis);
2348 	    }
2349 	}
2350       else
2351 	gcc_unreachable ();
2352     }
2353 
2354   return vthis_value;
2355 }
2356 
2357 /* Build the RECORD_TYPE that describes the function frame or closure type for
2358    the function FD.  FFI is the tree holding all frame information.  */
2359 
2360 static tree
build_frame_type(tree ffi,FuncDeclaration * fd)2361 build_frame_type (tree ffi, FuncDeclaration *fd)
2362 {
2363   if (FRAMEINFO_TYPE (ffi))
2364     return FRAMEINFO_TYPE (ffi);
2365 
2366   tree frame_rec_type = make_node (RECORD_TYPE);
2367   char *name = concat (FRAMEINFO_IS_CLOSURE (ffi) ? "CLOSURE." : "FRAME.",
2368 		       fd->toPrettyChars (), NULL);
2369   TYPE_NAME (frame_rec_type) = get_identifier (name);
2370   free (name);
2371 
2372   tree fields = NULL_TREE;
2373 
2374   /* Function is a member or nested, so must have field for outer context.  */
2375   if (fd->vthis)
2376     {
2377       tree ptr_field = build_decl (BUILTINS_LOCATION, FIELD_DECL,
2378 				   get_identifier ("__chain"), ptr_type_node);
2379       DECL_FIELD_CONTEXT (ptr_field) = frame_rec_type;
2380       fields = chainon (NULL_TREE, ptr_field);
2381       DECL_NONADDRESSABLE_P (ptr_field) = 1;
2382     }
2383 
2384   /* The __ensure and __require are called directly, so never make the outer
2385      functions closure, but nevertheless could still be referencing parameters
2386      of the calling function non-locally.  So we add all parameters with nested
2387      refs to the function frame, this should also mean overriding methods will
2388      have the same frame layout when inheriting a contract.  */
2389   if ((global.params.useIn && fd->frequire)
2390       || (global.params.useOut && fd->fensure))
2391     {
2392       if (fd->parameters)
2393 	{
2394 	  for (size_t i = 0; fd->parameters && i < fd->parameters->dim; i++)
2395 	    {
2396 	      VarDeclaration *v = (*fd->parameters)[i];
2397 	      /* Remove if already in closureVars so can push to front.  */
2398 	      for (size_t j = i; j < fd->closureVars.dim; j++)
2399 		{
2400 		  Dsymbol *s = fd->closureVars[j];
2401 		  if (s == v)
2402 		    {
2403 		      fd->closureVars.remove (j);
2404 		      break;
2405 		    }
2406 		}
2407 	      fd->closureVars.insert (i, v);
2408 	    }
2409 	}
2410 
2411       /* Also add hidden 'this' to outer context.  */
2412       if (fd->vthis)
2413 	{
2414 	  for (size_t i = 0; i < fd->closureVars.dim; i++)
2415 	    {
2416 	      Dsymbol *s = fd->closureVars[i];
2417 	      if (s == fd->vthis)
2418 		{
2419 		  fd->closureVars.remove (i);
2420 		  break;
2421 		}
2422 	    }
2423 	  fd->closureVars.insert (0, fd->vthis);
2424 	}
2425     }
2426 
2427   for (size_t i = 0; i < fd->closureVars.dim; i++)
2428     {
2429       VarDeclaration *v = fd->closureVars[i];
2430       tree vsym = get_symbol_decl (v);
2431       tree ident = v->ident
2432 	? get_identifier (v->ident->toChars ()) : NULL_TREE;
2433 
2434       tree field = build_decl (make_location_t (v->loc), FIELD_DECL, ident,
2435 			       TREE_TYPE (vsym));
2436       SET_DECL_LANG_FRAME_FIELD (vsym, field);
2437       DECL_FIELD_CONTEXT (field) = frame_rec_type;
2438       fields = chainon (fields, field);
2439       TREE_USED (vsym) = 1;
2440 
2441       TREE_ADDRESSABLE (field) = TREE_ADDRESSABLE (vsym);
2442       DECL_NONADDRESSABLE_P (field) = !TREE_ADDRESSABLE (vsym);
2443       TREE_THIS_VOLATILE (field) = TREE_THIS_VOLATILE (vsym);
2444 
2445       /* Can't do nrvo if the variable is put in a frame.  */
2446       if (fd->nrvo_can && fd->nrvo_var == v)
2447 	fd->nrvo_can = 0;
2448 
2449       if (FRAMEINFO_IS_CLOSURE (ffi))
2450 	{
2451 	  /* Because the value needs to survive the end of the scope.  */
2452 	  if ((v->edtor && (v->storage_class & STCparameter))
2453 	      || v->needsScopeDtor ())
2454 	    error_at (make_location_t (v->loc),
2455 		      "has scoped destruction, cannot build closure");
2456 	}
2457     }
2458 
2459   TYPE_FIELDS (frame_rec_type) = fields;
2460   TYPE_READONLY (frame_rec_type) = 1;
2461   layout_type (frame_rec_type);
2462   d_keep (frame_rec_type);
2463 
2464   return frame_rec_type;
2465 }
2466 
2467 /* Closures are implemented by taking the local variables that
2468    need to survive the scope of the function, and copying them
2469    into a GC allocated chuck of memory.  That chunk, called the
2470    closure here, is inserted into the linked list of stack
2471    frames instead of the usual stack frame.
2472 
2473    If a closure is not required, but FD still needs a frame to lower
2474    nested refs, then instead build custom static chain decl on stack.  */
2475 
2476 void
build_closure(FuncDeclaration * fd)2477 build_closure (FuncDeclaration *fd)
2478 {
2479   tree ffi = get_frameinfo (fd);
2480 
2481   if (!FRAMEINFO_CREATES_FRAME (ffi))
2482     return;
2483 
2484   tree type = FRAMEINFO_TYPE (ffi);
2485   gcc_assert (COMPLETE_TYPE_P (type));
2486 
2487   tree decl, decl_ref;
2488 
2489   if (FRAMEINFO_IS_CLOSURE (ffi))
2490     {
2491       decl = build_local_temp (build_pointer_type (type));
2492       DECL_NAME (decl) = get_identifier ("__closptr");
2493       decl_ref = build_deref (decl);
2494 
2495       /* Allocate memory for closure.  */
2496       tree arg = convert (build_ctype (Type::tsize_t), TYPE_SIZE_UNIT (type));
2497       tree init = build_libcall (LIBCALL_ALLOCMEMORY, Type::tvoidptr, 1, arg);
2498 
2499       tree init_exp = build_assign (INIT_EXPR, decl,
2500 				    build_nop (TREE_TYPE (decl), init));
2501       add_stmt (init_exp);
2502     }
2503   else
2504     {
2505       decl = build_local_temp (type);
2506       DECL_NAME (decl) = get_identifier ("__frame");
2507       decl_ref = decl;
2508     }
2509 
2510   /* Set the first entry to the parent closure/frame, if any.  */
2511   if (fd->vthis)
2512     {
2513       tree chain_field = component_ref (decl_ref, TYPE_FIELDS (type));
2514       tree chain_expr = modify_expr (chain_field,
2515 				     d_function_chain->static_chain);
2516       add_stmt (chain_expr);
2517     }
2518 
2519   /* Copy parameters that are referenced nonlocally.  */
2520   for (size_t i = 0; i < fd->closureVars.dim; i++)
2521     {
2522       VarDeclaration *v = fd->closureVars[i];
2523 
2524       if (!v->isParameter ())
2525 	continue;
2526 
2527       tree vsym = get_symbol_decl (v);
2528 
2529       tree field = component_ref (decl_ref, DECL_LANG_FRAME_FIELD (vsym));
2530       tree expr = modify_expr (field, vsym);
2531       add_stmt (expr);
2532     }
2533 
2534   if (!FRAMEINFO_IS_CLOSURE (ffi))
2535     decl = build_address (decl);
2536 
2537   d_function_chain->static_chain = decl;
2538 }
2539 
2540 /* Return the frame of FD.  This could be a static chain or a closure
2541    passed via the hidden 'this' pointer.  */
2542 
2543 tree
get_frameinfo(FuncDeclaration * fd)2544 get_frameinfo (FuncDeclaration *fd)
2545 {
2546   tree fds = get_symbol_decl (fd);
2547   if (DECL_LANG_FRAMEINFO (fds))
2548     return DECL_LANG_FRAMEINFO (fds);
2549 
2550   tree ffi = make_node (FUNCFRAME_INFO);
2551 
2552   DECL_LANG_FRAMEINFO (fds) = ffi;
2553 
2554   if (fd->needsClosure ())
2555     {
2556       /* Set-up a closure frame, this will be allocated on the heap.  */
2557       FRAMEINFO_CREATES_FRAME (ffi) = 1;
2558       FRAMEINFO_IS_CLOSURE (ffi) = 1;
2559     }
2560   else if (fd->hasNestedFrameRefs ())
2561     {
2562       /* Functions with nested refs must create a static frame for local
2563 	 variables to be referenced from.  */
2564       FRAMEINFO_CREATES_FRAME (ffi) = 1;
2565     }
2566   else
2567     {
2568       /* For nested functions, default to creating a frame.  Even if there are
2569 	 no fields to populate the frame, create it anyway, as this will be
2570 	 used as the record type instead of `void*` for the this parameter.  */
2571       if (fd->vthis && fd->vthis->type == Type::tvoidptr)
2572 	FRAMEINFO_CREATES_FRAME (ffi) = 1;
2573 
2574       /* In checkNestedReference, references from contracts are not added to the
2575 	 closureVars array, so assume all parameters referenced.  */
2576       if ((global.params.useIn && fd->frequire)
2577 	  || (global.params.useOut && fd->fensure))
2578 	FRAMEINFO_CREATES_FRAME (ffi) = 1;
2579 
2580       /* If however `fd` is nested (deeply) in a function that creates a
2581 	 closure, then `fd` instead inherits that closure via hidden vthis
2582 	 pointer, and doesn't create a stack frame at all.  */
2583       FuncDeclaration *ff = fd;
2584 
2585       while (ff)
2586 	{
2587 	  tree ffo = get_frameinfo (ff);
2588 
2589 	  if (ff != fd && FRAMEINFO_CREATES_FRAME (ffo))
2590 	    {
2591 	      gcc_assert (FRAMEINFO_TYPE (ffo));
2592 	      FRAMEINFO_CREATES_FRAME (ffi) = 0;
2593 	      FRAMEINFO_STATIC_CHAIN (ffi) = 1;
2594 	      FRAMEINFO_IS_CLOSURE (ffi) = FRAMEINFO_IS_CLOSURE (ffo);
2595 	      gcc_assert (COMPLETE_TYPE_P (FRAMEINFO_TYPE (ffo)));
2596 	      FRAMEINFO_TYPE (ffi) = FRAMEINFO_TYPE (ffo);
2597 	      break;
2598 	    }
2599 
2600 	  /* Stop looking if no frame pointer for this function.  */
2601 	  if (ff->vthis == NULL)
2602 	    break;
2603 
2604 	  AggregateDeclaration *ad = ff->isThis ();
2605 	  if (ad && ad->isNested ())
2606 	    {
2607 	      while (ad->isNested ())
2608 		{
2609 		  Dsymbol *d = ad->toParent2 ();
2610 		  ad = d->isAggregateDeclaration ();
2611 		  ff = d->isFuncDeclaration ();
2612 
2613 		  if (ad == NULL)
2614 		    break;
2615 		}
2616 	    }
2617 	  else
2618 	    ff = ff->toParent2 ()->isFuncDeclaration ();
2619 	}
2620     }
2621 
2622   /* Build type now as may be referenced from another module.  */
2623   if (FRAMEINFO_CREATES_FRAME (ffi))
2624     FRAMEINFO_TYPE (ffi) = build_frame_type (ffi, fd);
2625 
2626   return ffi;
2627 }
2628 
2629 /* Return a pointer to the frame/closure block of OUTER
2630    so can be accessed from the function INNER.  */
2631 
2632 tree
get_framedecl(FuncDeclaration * inner,FuncDeclaration * outer)2633 get_framedecl (FuncDeclaration *inner, FuncDeclaration *outer)
2634 {
2635   tree result = d_function_chain->static_chain;
2636   FuncDeclaration *fd = inner;
2637 
2638   while (fd && fd != outer)
2639     {
2640       AggregateDeclaration *ad;
2641       ClassDeclaration *cd;
2642       StructDeclaration *sd;
2643 
2644       /* Parent frame link is the first field.  */
2645       if (FRAMEINFO_CREATES_FRAME (get_frameinfo (fd)))
2646 	result = indirect_ref (ptr_type_node, result);
2647 
2648       if (fd->isNested ())
2649 	fd = fd->toParent2 ()->isFuncDeclaration ();
2650       /* The frame/closure record always points to the outer function's
2651 	 frame, even if there are intervening nested classes or structs.
2652 	 So, we can just skip over these.  */
2653       else if ((ad = fd->isThis ()) && (cd = ad->isClassDeclaration ()))
2654 	fd = d_nested_class (cd);
2655       else if ((ad = fd->isThis ()) && (sd = ad->isStructDeclaration ()))
2656 	fd = d_nested_struct (sd);
2657       else
2658 	break;
2659     }
2660 
2661   if (fd != outer)
2662     return error_no_frame_access (outer);
2663 
2664   /* Go get our frame record.  */
2665   tree frame_type = FRAMEINFO_TYPE (get_frameinfo (outer));
2666 
2667   if (frame_type != NULL_TREE)
2668     {
2669       result = build_nop (build_pointer_type (frame_type), result);
2670       return result;
2671     }
2672   else
2673     {
2674       error_at (make_location_t (inner->loc),
2675 		"forward reference to frame of %qs", outer->toChars ());
2676       return null_pointer_node;
2677     }
2678 }
2679