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