1 /* d-codegen.cc -- Code generation and routines for manipulation of GCC trees.
2 Copyright (C) 2006-2018 Free Software Foundation, Inc.
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)
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.
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/>. */
20 #include "coretypes.h"
22 #include "dmd/aggregate.h"
24 #include "dmd/declaration.h"
25 #include "dmd/identifier.h"
26 #include "dmd/target.h"
27 #include "dmd/template.h"
30 #include "tree-iterator.h"
31 #include "fold-const.h"
32 #include "diagnostic.h"
33 #include "langhooks.h"
35 #include "stringpool.h"
37 #include "stor-layout.h"
44 /* Return the GCC location for the D frontend location LOC. */
47 make_location_t (const Loc
& loc
)
49 location_t gcc_location
= input_location
;
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);
62 /* Return the DECL_CONTEXT for symbol DSYM. */
65 d_decl_context (Dsymbol
*dsym
)
67 Dsymbol
*parent
= dsym
;
68 Declaration
*decl
= dsym
->isDeclaration ();
70 while ((parent
= parent
->toParent ()))
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 ())
77 if (decl
!= NULL
&& decl
->linkage
!= LINKd
)
80 return build_import_decl (parent
);
83 /* Declarations marked as 'static' or '__gshared' are never
84 part of any context except at module level. */
85 if (decl
!= NULL
&& decl
->isDataseg ())
88 /* Nested functions. */
89 FuncDeclaration
*fd
= parent
->isFuncDeclaration ();
91 return get_symbol_decl (fd
);
93 /* Methods of classes or structs. */
94 AggregateDeclaration
*ad
= parent
->isAggregateDeclaration ();
97 tree context
= build_ctype (ad
->type
);
98 /* Want the underlying RECORD_TYPE. */
99 if (ad
->isClassDeclaration ())
100 context
= TREE_TYPE (context
);
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
;
114 /* Return a copy of record TYPE but safe to modify in any way. */
117 copy_aggregate_type (tree type
)
119 tree newtype
= build_distinct_type_copy (type
);
120 TYPE_FIELDS (newtype
) = copy_list (TYPE_FIELDS (type
));
122 for (tree f
= TYPE_FIELDS (newtype
); f
; f
= DECL_CHAIN (f
))
123 DECL_FIELD_CONTEXT (f
) = newtype
;
128 /* Return TRUE if declaration DECL is a reference type. */
131 declaration_reference_p (Declaration
*decl
)
133 Type
*tb
= decl
->type
->toBasetype ();
135 /* Declaration is a reference type. */
136 if (tb
->ty
== Treference
|| decl
->storage_class
& (STCout
| STCref
))
142 /* Returns the real type for declaration DECL. */
145 declaration_type (Declaration
*decl
)
147 /* Lazy declarations are converted to delegates. */
148 if (decl
->storage_class
& STClazy
)
150 TypeFunction
*tf
= TypeFunction::create (NULL
, decl
->type
, false, LINKd
);
151 TypeDelegate
*t
= TypeDelegate::create (tf
);
152 return build_ctype (t
->merge2 ());
155 /* Static array va_list have array->pointer conversions applied. */
156 if (decl
->isParameter () && valist_array_p (decl
->type
))
158 Type
*valist
= decl
->type
->nextOf ()->pointerTo ();
159 valist
= valist
->castMod (decl
->type
->mod
);
160 return build_ctype (valist
);
163 tree type
= build_ctype (decl
->type
);
165 /* Parameter is passed by reference. */
166 if (declaration_reference_p (decl
))
167 return build_reference_type (type
);
169 /* The 'this' parameter is always const. */
170 if (decl
->isThisDeclaration ())
171 return insert_type_modifiers (type
, MODconst
);
176 /* These should match the Declaration versions above
177 Return TRUE if parameter ARG is a reference type. */
180 argument_reference_p (Parameter
*arg
)
182 Type
*tb
= arg
->type
->toBasetype ();
184 /* Parameter is a reference type. */
185 if (tb
->ty
== Treference
|| arg
->storageClass
& (STCout
| STCref
))
188 tree type
= build_ctype (arg
->type
);
189 if (TREE_ADDRESSABLE (type
))
195 /* Returns the real type for parameter ARG. */
198 type_passed_as (Parameter
*arg
)
200 /* Lazy parameters are converted to delegates. */
201 if (arg
->storageClass
& STClazy
)
203 TypeFunction
*tf
= TypeFunction::create (NULL
, arg
->type
, false, LINKd
);
204 TypeDelegate
*t
= TypeDelegate::create (tf
);
205 return build_ctype (t
->merge2 ());
208 /* Static array va_list have array->pointer conversions applied. */
209 if (valist_array_p (arg
->type
))
211 Type
*valist
= arg
->type
->nextOf ()->pointerTo ();
212 valist
= valist
->castMod (arg
->type
->mod
);
213 return build_ctype (valist
);
216 tree type
= build_ctype (arg
->type
);
218 /* Parameter is passed by reference. */
219 if (argument_reference_p (arg
))
220 return build_reference_type (type
);
225 /* Build INTEGER_CST of type TYPE with the value VALUE. */
228 build_integer_cst (dinteger_t value
, tree type
)
230 /* The type is error_mark_node, we can't do anything. */
231 if (error_operand_p (type
))
234 return build_int_cst_type (type
, value
);
237 /* Build REAL_CST of type TOTYPE with the value VALUE. */
240 build_float_cst (const real_t
& value
, Type
*totype
)
243 TypeBasic
*tb
= totype
->isTypeBasic ();
245 gcc_assert (tb
!= NULL
);
247 tree type_node
= build_ctype (tb
);
248 real_convert (&new_value
.rv (), TYPE_MODE (type_node
), &value
.rv ());
250 return build_real (type_node
, new_value
.rv ());
253 /* Returns the .length component from the D dynamic array EXP. */
256 d_array_length (tree exp
)
258 if (error_operand_p (exp
))
261 gcc_assert (TYPE_DYNAMIC_ARRAY (TREE_TYPE (exp
)));
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
);
269 /* Returns the .ptr component from the D dynamic array EXP. */
272 d_array_ptr (tree exp
)
274 if (error_operand_p (exp
))
277 gcc_assert (TYPE_DYNAMIC_ARRAY (TREE_TYPE (exp
)));
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
);
285 /* Returns a constructor for D dynamic array type TYPE of .length LEN
286 and .ptr pointing to DATA. */
289 d_array_value (tree type
, tree len
, tree data
)
291 tree len_field
, ptr_field
;
292 vec
<constructor_elt
, va_gc
> *ce
= NULL
;
294 gcc_assert (TYPE_DYNAMIC_ARRAY (type
));
295 len_field
= TYPE_FIELDS (type
);
296 ptr_field
= TREE_CHAIN (len_field
);
298 len
= convert (TREE_TYPE (len_field
), len
);
299 data
= convert (TREE_TYPE (ptr_field
), data
);
301 CONSTRUCTOR_APPEND_ELT (ce
, len_field
, len
);
302 CONSTRUCTOR_APPEND_ELT (ce
, ptr_field
, data
);
304 return build_constructor (type
, ce
);
307 /* Returns value representing the array length of expression EXP.
308 TYPE could be a dynamic or static array. */
311 get_array_length (tree exp
, Type
*type
)
313 Type
*tb
= type
->toBasetype ();
318 return size_int (((TypeSArray
*) tb
)->dim
->toUInteger ());
321 return d_array_length (exp
);
324 error ("can't determine the length of a %qs", type
->toChars ());
325 return error_mark_node
;
329 /* Create BINFO for a ClassDeclaration's inheritance tree.
330 InterfaceDeclaration's are not included. */
333 build_class_binfo (tree super
, ClassDeclaration
*cd
)
335 tree binfo
= make_tree_binfo (1);
336 tree ctype
= build_ctype (cd
->type
);
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
;
344 BINFO_BASE_APPEND (binfo
, build_class_binfo (binfo
, cd
->baseClass
));
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. */
355 build_interface_binfo (tree super
, ClassDeclaration
*cd
, unsigned& offset
)
357 tree binfo
= make_tree_binfo (cd
->baseclasses
->dim
);
358 tree ctype
= build_ctype (cd
->type
);
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;
366 for (size_t i
= 0; i
< cd
->baseclasses
->dim
; i
++, offset
++)
368 BaseClass
*bc
= (*cd
->baseclasses
)[i
];
369 BINFO_BASE_APPEND (binfo
, build_interface_binfo (binfo
, bc
->sym
, offset
));
375 /* Returns the .funcptr component from the D delegate EXP. */
378 delegate_method (tree exp
)
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
);
387 /* Returns the .object component from the delegate EXP. */
390 delegate_object (tree exp
)
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
);
399 /* Build a delegate literal of type TYPE whose pointer function is
400 METHOD, and hidden object is OBJECT. */
403 build_delegate_cst (tree method
, tree object
, Type
*type
)
405 tree ctor
= make_node (CONSTRUCTOR
);
408 Type
*tb
= type
->toBasetype ();
409 if (tb
->ty
== Tdelegate
)
410 ctype
= build_ctype (type
);
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;
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
);
424 CONSTRUCTOR_ELTS (ctor
) = ce
;
425 TREE_TYPE (ctor
) = ctype
;
430 /* Builds a temporary tree to store the CALLEE and OBJECT
431 of a method call expression of type TYPE. */
434 build_method_call (tree callee
, tree object
, Type
*type
)
436 tree t
= build_delegate_cst (callee
, object
, type
);
437 METHOD_CALL_EXPR (t
) = 1;
441 /* Extract callee and object from T and return in to CALLEE and OBJECT. */
444 extract_from_method_call (tree t
, tree
& callee
, tree
& object
)
446 gcc_assert (METHOD_CALL_EXPR (t
));
447 object
= CONSTRUCTOR_ELT (t
, 0)->value
;
448 callee
= CONSTRUCTOR_ELT (t
, 1)->value
;
451 /* Build a dereference into the virtual table for OBJECT to retrieve
452 a function pointer of type FNTYPE at position INDEX. */
455 build_vindex_ref (tree object
, tree fntype
, size_t index
)
457 /* The vtable is the first field. Interface methods are also in the class's
458 vtable, so we don't need to convert from a class to an interface. */
459 tree result
= build_deref (object
);
460 result
= component_ref (result
, TYPE_FIELDS (TREE_TYPE (result
)));
462 gcc_assert (POINTER_TYPE_P (fntype
));
464 return build_memref (fntype
, result
, size_int (Target::ptrsize
* index
));
467 /* Return TRUE if EXP is a valid lvalue. Lvalue references cannot be
468 made into temporaries, otherwise any assignments will be lost. */
473 const enum tree_code code
= TREE_CODE (exp
);
485 return !FUNC_OR_METHOD_TYPE_P (TREE_TYPE (exp
));
491 return lvalue_p (TREE_OPERAND (exp
, 0));
494 return (lvalue_p (TREE_OPERAND (exp
, 1)
495 ? TREE_OPERAND (exp
, 1)
496 : TREE_OPERAND (exp
, 0))
497 && lvalue_p (TREE_OPERAND (exp
, 2)));
503 return lvalue_p (TREE_OPERAND (exp
, 1));
510 /* Create a SAVE_EXPR if EXP might have unwanted side effects if referenced
511 more than once in an expression. */
514 d_save_expr (tree exp
)
516 if (TREE_SIDE_EFFECTS (exp
))
519 return stabilize_reference (exp
);
521 return save_expr (exp
);
527 /* VALUEP is an expression we want to pre-evaluate or perform a computation on.
528 The expression returned by this function is the part whose value we don't
529 care about, storing the value in VALUEP. Callers must ensure that the
530 returned expression is evaluated before VALUEP. */
533 stabilize_expr (tree
*valuep
)
536 const enum tree_code code
= TREE_CODE (expr
);
543 /* Given ((e1, ...), eN):
544 Store the last RHS 'eN' expression in VALUEP. */
545 lhs
= TREE_OPERAND (expr
, 0);
546 rhs
= TREE_OPERAND (expr
, 1);
547 lhs
= compound_expr (lhs
, stabilize_expr (&rhs
));
556 /* Return a TARGET_EXPR, initializing the DECL with EXP. */
559 build_target_expr (tree decl
, tree exp
)
561 tree type
= TREE_TYPE (decl
);
562 tree result
= build4 (TARGET_EXPR
, type
, decl
, exp
, NULL_TREE
, NULL_TREE
);
564 if (EXPR_HAS_LOCATION (exp
))
565 SET_EXPR_LOCATION (result
, EXPR_LOCATION (exp
));
567 /* If decl must always reside in memory. */
568 if (TREE_ADDRESSABLE (type
))
569 d_mark_addressable (decl
);
571 /* Always set TREE_SIDE_EFFECTS so that expand_expr does not ignore the
572 TARGET_EXPR. If there really turn out to be no side effects, then the
573 optimizer should be able to remove it. */
574 TREE_SIDE_EFFECTS (result
) = 1;
579 /* Like the above function, but initializes a new temporary. */
582 force_target_expr (tree exp
)
584 tree decl
= create_temporary_var (TREE_TYPE (exp
));
586 return build_target_expr (decl
, exp
);
589 /* Returns the address of the expression EXP. */
592 build_address (tree exp
)
594 if (error_operand_p (exp
))
598 tree type
= TREE_TYPE (exp
);
600 if (TREE_CODE (exp
) == STRING_CST
)
602 /* Just convert string literals (char[]) to C-style strings (char *),
603 otherwise the latter method (char[]*) causes conversion problems
604 during gimplification. */
605 ptrtype
= build_pointer_type (TREE_TYPE (type
));
607 else if (TYPE_MAIN_VARIANT (type
) == TYPE_MAIN_VARIANT (va_list_type_node
)
608 && TREE_CODE (TYPE_MAIN_VARIANT (type
)) == ARRAY_TYPE
)
610 /* Special case for va_list, allow arrays to decay to a pointer. */
611 ptrtype
= build_pointer_type (TREE_TYPE (type
));
614 ptrtype
= build_pointer_type (type
);
616 /* Maybe rewrite: &(e1, e2) => (e1, &e2). */
617 tree init
= stabilize_expr (&exp
);
619 /* Can't take the address of a manifest constant, instead use its value. */
620 if (TREE_CODE (exp
) == CONST_DECL
)
621 exp
= DECL_INITIAL (exp
);
623 /* Some expression lowering may request an address of a compile-time constant.
624 Make sure it is assigned to a location we can reference. */
625 if (CONSTANT_CLASS_P (exp
) && TREE_CODE (exp
) != STRING_CST
)
626 exp
= force_target_expr (exp
);
628 d_mark_addressable (exp
);
629 exp
= build_fold_addr_expr_with_type_loc (input_location
, exp
, ptrtype
);
631 if (TREE_CODE (exp
) == ADDR_EXPR
)
632 TREE_NO_TRAMPOLINE (exp
) = 1;
634 return compound_expr (init
, exp
);
637 /* Mark EXP saying that we need to be able to take the
638 address of it; it should not be allocated in a register. */
641 d_mark_addressable (tree exp
)
643 switch (TREE_CODE (exp
))
650 d_mark_addressable (TREE_OPERAND (exp
, 0));
658 TREE_ADDRESSABLE (exp
) = 1;
662 TREE_ADDRESSABLE (exp
) = 1;
666 TREE_ADDRESSABLE (exp
) = 1;
667 d_mark_addressable (TREE_OPERAND (exp
, 0));
677 /* Mark EXP as "used" in the program for the benefit of
678 -Wunused warning purposes. */
681 d_mark_used (tree exp
)
683 switch (TREE_CODE (exp
))
701 d_mark_used (TREE_OPERAND (exp
, 0));
705 d_mark_used (TREE_OPERAND (exp
, 0));
706 d_mark_used (TREE_OPERAND (exp
, 1));
715 /* Mark EXP as read, not just set, for set but not used -Wunused
719 d_mark_read (tree exp
)
721 switch (TREE_CODE (exp
))
726 DECL_READ_P (exp
) = 1;
737 d_mark_read (TREE_OPERAND (exp
, 0));
741 d_mark_read (TREE_OPERAND (exp
, 1));
750 /* Return TRUE if the struct SD is suitable for comparison using memcmp.
751 This is because we don't guarantee that padding is zero-initialized for
752 a stack variable, so we can't use memcmp to compare struct values. */
755 identity_compare_p (StructDeclaration
*sd
)
757 if (sd
->isUnionDeclaration ())
762 for (size_t i
= 0; i
< sd
->fields
.dim
; i
++)
764 VarDeclaration
*vd
= sd
->fields
[i
];
766 /* Check inner data structures. */
767 if (vd
->type
->ty
== Tstruct
)
769 TypeStruct
*ts
= (TypeStruct
*) vd
->type
;
770 if (!identity_compare_p (ts
->sym
))
774 if (offset
<= vd
->offset
)
776 /* There's a hole in the struct. */
777 if (offset
!= vd
->offset
)
780 offset
+= vd
->type
->size ();
784 /* Any trailing padding may not be zero. */
785 if (offset
< sd
->structsize
)
791 /* Lower a field-by-field equality expression between T1 and T2 of type SD.
792 CODE is the EQ_EXPR or NE_EXPR comparison. */
795 lower_struct_comparison (tree_code code
, StructDeclaration
*sd
,
798 tree_code tcode
= (code
== EQ_EXPR
) ? TRUTH_ANDIF_EXPR
: TRUTH_ORIF_EXPR
;
799 tree tmemcmp
= NULL_TREE
;
801 /* We can skip the compare if the structs are empty. */
802 if (sd
->fields
.dim
== 0)
804 tmemcmp
= build_boolop (code
, integer_zero_node
, integer_zero_node
);
805 if (TREE_SIDE_EFFECTS (t2
))
806 tmemcmp
= compound_expr (t2
, tmemcmp
);
807 if (TREE_SIDE_EFFECTS (t1
))
808 tmemcmp
= compound_expr (t1
, tmemcmp
);
813 /* Let back-end take care of union comparisons. */
814 if (sd
->isUnionDeclaration ())
816 tmemcmp
= build_call_expr (builtin_decl_explicit (BUILT_IN_MEMCMP
), 3,
817 build_address (t1
), build_address (t2
),
818 size_int (sd
->structsize
));
820 return build_boolop (code
, tmemcmp
, integer_zero_node
);
823 for (size_t i
= 0; i
< sd
->fields
.dim
; i
++)
825 VarDeclaration
*vd
= sd
->fields
[i
];
826 tree sfield
= get_symbol_decl (vd
);
828 tree t1ref
= component_ref (t1
, sfield
);
829 tree t2ref
= component_ref (t2
, sfield
);
832 if (vd
->type
->ty
== Tstruct
)
834 /* Compare inner data structures. */
835 StructDeclaration
*decl
= ((TypeStruct
*) vd
->type
)->sym
;
836 tcmp
= lower_struct_comparison (code
, decl
, t1ref
, t2ref
);
840 tree stype
= build_ctype (vd
->type
);
841 opt_scalar_int_mode mode
= int_mode_for_mode (TYPE_MODE (stype
));
843 if (vd
->type
->ty
!= Tvector
&& vd
->type
->isintegral ())
845 /* Integer comparison, no special handling required. */
846 tcmp
= build_boolop (code
, t1ref
, t2ref
);
848 else if (mode
.exists ())
850 /* Compare field bits as their corresponding integer type.
851 *((T*) &t1) == *((T*) &t2) */
852 tree tmode
= lang_hooks
.types
.type_for_mode (mode
.require (), 1);
854 if (tmode
== NULL_TREE
)
855 tmode
= make_unsigned_type (GET_MODE_BITSIZE (mode
.require ()));
857 t1ref
= build_vconvert (tmode
, t1ref
);
858 t2ref
= build_vconvert (tmode
, t2ref
);
860 tcmp
= build_boolop (code
, t1ref
, t2ref
);
864 /* Simple memcmp between types. */
865 tcmp
= build_call_expr (builtin_decl_explicit (BUILT_IN_MEMCMP
),
866 3, build_address (t1ref
),
867 build_address (t2ref
),
868 TYPE_SIZE_UNIT (stype
));
870 tcmp
= build_boolop (code
, tcmp
, integer_zero_node
);
874 tmemcmp
= (tmemcmp
) ? build_boolop (tcode
, tmemcmp
, tcmp
) : tcmp
;
881 /* Build an equality expression between two RECORD_TYPES T1 and T2 of type SD.
882 If possible, use memcmp, otherwise field-by-field comparison is done.
883 CODE is the EQ_EXPR or NE_EXPR comparison. */
886 build_struct_comparison (tree_code code
, StructDeclaration
*sd
,
889 /* We can skip the compare if the structs are empty. */
890 if (sd
->fields
.dim
== 0)
892 tree exp
= build_boolop (code
, integer_zero_node
, integer_zero_node
);
893 if (TREE_SIDE_EFFECTS (t2
))
894 exp
= compound_expr (t2
, exp
);
895 if (TREE_SIDE_EFFECTS (t1
))
896 exp
= compound_expr (t1
, exp
);
901 /* Make temporaries to prevent multiple evaluations. */
902 tree t1init
= stabilize_expr (&t1
);
903 tree t2init
= stabilize_expr (&t2
);
906 t1
= d_save_expr (t1
);
907 t2
= d_save_expr (t2
);
909 /* Bitwise comparison of structs not returned in memory may not work
910 due to data holes loosing its zero padding upon return.
911 As a heuristic, small structs are not compared using memcmp either. */
912 if (TYPE_MODE (TREE_TYPE (t1
)) != BLKmode
|| !identity_compare_p (sd
))
913 result
= lower_struct_comparison (code
, sd
, t1
, t2
);
916 /* Do bit compare of structs. */
917 tree size
= size_int (sd
->structsize
);
918 tree tmemcmp
= build_call_expr (builtin_decl_explicit (BUILT_IN_MEMCMP
),
919 3, build_address (t1
),
920 build_address (t2
), size
);
922 result
= build_boolop (code
, tmemcmp
, integer_zero_node
);
925 return compound_expr (compound_expr (t1init
, t2init
), result
);
928 /* Build an equality expression between two ARRAY_TYPES of size LENGTH.
929 The pointer references are T1 and T2, and the element type is SD.
930 CODE is the EQ_EXPR or NE_EXPR comparison. */
933 build_array_struct_comparison (tree_code code
, StructDeclaration
*sd
,
934 tree length
, tree t1
, tree t2
)
936 tree_code tcode
= (code
== EQ_EXPR
) ? TRUTH_ANDIF_EXPR
: TRUTH_ORIF_EXPR
;
938 /* Build temporary for the result of the comparison.
939 Initialize as either 0 or 1 depending on operation. */
940 tree result
= build_local_temp (d_bool_type
);
941 tree init
= build_boolop (code
, integer_zero_node
, integer_zero_node
);
942 add_stmt (build_assign (INIT_EXPR
, result
, init
));
944 /* Cast pointer-to-array to pointer-to-struct. */
945 tree ptrtype
= build_ctype (sd
->type
->pointerTo ());
946 tree lentype
= TREE_TYPE (length
);
948 push_binding_level (level_block
);
951 /* Build temporary locals for length and pointers. */
952 tree t
= build_local_temp (size_type_node
);
953 add_stmt (build_assign (INIT_EXPR
, t
, length
));
956 t
= build_local_temp (ptrtype
);
957 add_stmt (build_assign (INIT_EXPR
, t
, d_convert (ptrtype
, t1
)));
960 t
= build_local_temp (ptrtype
);
961 add_stmt (build_assign (INIT_EXPR
, t
, d_convert (ptrtype
, t2
)));
964 /* Build loop for comparing each element. */
967 /* Exit logic for the loop.
968 if (length == 0 || result OP 0) break; */
969 t
= build_boolop (EQ_EXPR
, length
, d_convert (lentype
, integer_zero_node
));
970 t
= build_boolop (TRUTH_ORIF_EXPR
, t
, build_boolop (code
, result
,
971 boolean_false_node
));
972 t
= build1 (EXIT_EXPR
, void_type_node
, t
);
975 /* Do comparison, caching the value.
976 result = result OP (*t1 == *t2); */
977 t
= build_struct_comparison (code
, sd
, build_deref (t1
), build_deref (t2
));
978 t
= build_boolop (tcode
, result
, t
);
979 t
= modify_expr (result
, t
);
982 /* Move both pointers to next element position.
984 tree size
= d_convert (ptrtype
, TYPE_SIZE_UNIT (TREE_TYPE (ptrtype
)));
985 t
= build2 (POSTINCREMENT_EXPR
, ptrtype
, t1
, size
);
987 t
= build2 (POSTINCREMENT_EXPR
, ptrtype
, t2
, size
);
990 /* Decrease loop counter.
992 t
= build2 (POSTDECREMENT_EXPR
, lentype
, length
,
993 d_convert (lentype
, integer_one_node
));
996 /* Pop statements and finish loop. */
997 tree body
= pop_stmt_list ();
998 add_stmt (build1 (LOOP_EXPR
, void_type_node
, body
));
1000 /* Wrap it up into a bind expression. */
1001 tree stmt_list
= pop_stmt_list ();
1002 tree block
= pop_binding_level ();
1004 body
= build3 (BIND_EXPR
, void_type_node
,
1005 BLOCK_VARS (block
), stmt_list
, block
);
1007 return compound_expr (body
, result
);
1010 /* Create an anonymous field of type ubyte[T] at OFFSET to fill
1011 the alignment hole between OFFSET and FIELDPOS. */
1014 build_alignment_field (tree type
, HOST_WIDE_INT offset
, HOST_WIDE_INT fieldpos
)
1016 tree atype
= make_array_type (Type::tuns8
, fieldpos
- offset
);
1017 tree field
= create_field_decl (atype
, NULL
, 1, 1);
1019 SET_DECL_OFFSET_ALIGN (field
, TYPE_ALIGN (atype
));
1020 DECL_FIELD_OFFSET (field
) = size_int (offset
);
1021 DECL_FIELD_BIT_OFFSET (field
) = bitsize_zero_node
;
1022 DECL_FIELD_CONTEXT (field
) = type
;
1023 DECL_PADDING_P (field
) = 1;
1025 layout_decl (field
, 0);
1030 /* Build a constructor for a variable of aggregate type TYPE using the
1031 initializer INIT, an ordered flat list of fields and values provided
1032 by the frontend. The returned constructor should be a value that
1033 matches the layout of TYPE. */
1036 build_struct_literal (tree type
, vec
<constructor_elt
, va_gc
> *init
)
1038 /* If the initializer was empty, use default zero initialization. */
1039 if (vec_safe_is_empty (init
))
1040 return build_constructor (type
, NULL
);
1042 vec
<constructor_elt
, va_gc
> *ve
= NULL
;
1043 HOST_WIDE_INT offset
= 0;
1044 bool constant_p
= true;
1045 bool fillholes
= true;
1046 bool finished
= false;
1048 /* Filling alignment holes this only applies to structs. */
1049 if (TREE_CODE (type
) != RECORD_TYPE
1050 || CLASS_TYPE_P (type
) || TYPE_PACKED (type
))
1053 /* Walk through each field, matching our initializer list. */
1054 for (tree field
= TYPE_FIELDS (type
); field
; field
= DECL_CHAIN (field
))
1056 bool is_initialized
= false;
1059 if (DECL_NAME (field
) == NULL_TREE
1060 && RECORD_OR_UNION_TYPE_P (TREE_TYPE (field
))
1061 && ANON_AGGR_TYPE_P (TREE_TYPE (field
)))
1063 /* Search all nesting aggregates, if nothing is found, then
1064 this will return an empty initializer to fill the hole. */
1065 value
= build_struct_literal (TREE_TYPE (field
), init
);
1067 if (!initializer_zerop (value
))
1068 is_initialized
= true;
1072 /* Search for the value to initialize the next field. Once found,
1073 pop it from the init list so we don't look at it again. */
1074 unsigned HOST_WIDE_INT idx
;
1077 FOR_EACH_CONSTRUCTOR_ELT (init
, idx
, index
, value
)
1079 /* If the index is NULL, then just assign it to the next field.
1080 This comes from layout_typeinfo(), which generates a flat
1081 list of values that we must shape into the record type. */
1082 if (index
== field
|| index
== NULL_TREE
)
1084 init
->ordered_remove (idx
);
1086 is_initialized
= true;
1094 HOST_WIDE_INT fieldpos
= int_byte_position (field
);
1095 gcc_assert (value
!= NULL_TREE
);
1097 /* Insert anonymous fields in the constructor for padding out
1098 alignment holes in-place between fields. */
1099 if (fillholes
&& offset
< fieldpos
)
1101 tree pfield
= build_alignment_field (type
, offset
, fieldpos
);
1102 tree pvalue
= build_zero_cst (TREE_TYPE (pfield
));
1103 CONSTRUCTOR_APPEND_ELT (ve
, pfield
, pvalue
);
1106 /* Must not initialize fields that overlap. */
1107 if (fieldpos
< offset
)
1109 /* Find the nearest user defined type and field. */
1111 while (ANON_AGGR_TYPE_P (vtype
))
1112 vtype
= TYPE_CONTEXT (vtype
);
1114 tree vfield
= field
;
1115 if (RECORD_OR_UNION_TYPE_P (TREE_TYPE (vfield
))
1116 && ANON_AGGR_TYPE_P (TREE_TYPE (vfield
)))
1117 vfield
= TYPE_FIELDS (TREE_TYPE (vfield
));
1119 /* Must not generate errors for compiler generated fields. */
1120 gcc_assert (TYPE_NAME (vtype
) && DECL_NAME (vfield
));
1121 error ("overlapping initializer for field %qT.%qD",
1122 TYPE_NAME (vtype
), DECL_NAME (vfield
));
1125 if (!TREE_CONSTANT (value
))
1128 CONSTRUCTOR_APPEND_ELT (ve
, field
, value
);
1130 /* For unions, only the first field is initialized, any other field
1131 initializers found for this union are drained and ignored. */
1132 if (TREE_CODE (type
) == UNION_TYPE
)
1136 /* Move offset to the next position in the struct. */
1137 if (TREE_CODE (type
) == RECORD_TYPE
)
1139 offset
= int_byte_position (field
)
1140 + int_size_in_bytes (TREE_TYPE (field
));
1143 /* If all initializers have been assigned, there's nothing else to do. */
1144 if (vec_safe_is_empty (init
))
1148 /* Finally pad out the end of the record. */
1149 if (fillholes
&& offset
< int_size_in_bytes (type
))
1151 tree pfield
= build_alignment_field (type
, offset
,
1152 int_size_in_bytes (type
));
1153 tree pvalue
= build_zero_cst (TREE_TYPE (pfield
));
1154 CONSTRUCTOR_APPEND_ELT (ve
, pfield
, pvalue
);
1157 /* Ensure that we have consumed all values. */
1158 gcc_assert (vec_safe_is_empty (init
) || ANON_AGGR_TYPE_P (type
));
1160 tree ctor
= build_constructor (type
, ve
);
1163 TREE_CONSTANT (ctor
) = 1;
1168 /* Given the TYPE of an anonymous field inside T, return the
1169 FIELD_DECL for the field. If not found return NULL_TREE.
1170 Because anonymous types can nest, we must also search all
1171 anonymous fields that are directly reachable. */
1174 lookup_anon_field (tree t
, tree type
)
1176 t
= TYPE_MAIN_VARIANT (t
);
1178 for (tree field
= TYPE_FIELDS (t
); field
; field
= DECL_CHAIN (field
))
1180 if (DECL_NAME (field
) == NULL_TREE
)
1182 /* If we find it directly, return the field. */
1183 if (type
== TYPE_MAIN_VARIANT (TREE_TYPE (field
)))
1186 /* Otherwise, it could be nested, search harder. */
1187 if (RECORD_OR_UNION_TYPE_P (TREE_TYPE (field
))
1188 && ANON_AGGR_TYPE_P (TREE_TYPE (field
)))
1190 tree subfield
= lookup_anon_field (TREE_TYPE (field
), type
);
1200 /* Builds OBJECT.FIELD component reference. */
1203 component_ref (tree object
, tree field
)
1205 if (error_operand_p (object
) || error_operand_p (field
))
1206 return error_mark_node
;
1208 gcc_assert (TREE_CODE (field
) == FIELD_DECL
);
1210 /* Maybe rewrite: (e1, e2).field => (e1, e2.field) */
1211 tree init
= stabilize_expr (&object
);
1213 /* If the FIELD is from an anonymous aggregate, generate a reference
1214 to the anonymous data member, and recur to find FIELD. */
1215 if (ANON_AGGR_TYPE_P (DECL_CONTEXT (field
)))
1217 tree anonymous_field
= lookup_anon_field (TREE_TYPE (object
),
1218 DECL_CONTEXT (field
));
1219 object
= component_ref (object
, anonymous_field
);
1222 tree result
= fold_build3_loc (input_location
, COMPONENT_REF
,
1223 TREE_TYPE (field
), object
, field
, NULL_TREE
);
1225 return compound_expr (init
, result
);
1228 /* Build an assignment expression of lvalue LHS from value RHS.
1229 CODE is the code for a binary operator that we use to combine
1230 the old value of LHS with RHS to get the new value. */
1233 build_assign (tree_code code
, tree lhs
, tree rhs
)
1235 tree init
= stabilize_expr (&lhs
);
1236 init
= compound_expr (init
, stabilize_expr (&rhs
));
1238 /* If initializing the LHS using a function that returns via NRVO. */
1239 if (code
== INIT_EXPR
&& TREE_CODE (rhs
) == CALL_EXPR
1240 && AGGREGATE_TYPE_P (TREE_TYPE (rhs
))
1241 && aggregate_value_p (TREE_TYPE (rhs
), rhs
))
1243 /* Mark as addressable here, which should ensure the return slot is the
1244 address of the LHS expression, taken care of by back-end. */
1245 d_mark_addressable (lhs
);
1246 CALL_EXPR_RETURN_SLOT_OPT (rhs
) = true;
1249 /* The LHS assignment replaces the temporary in TARGET_EXPR_SLOT. */
1250 if (TREE_CODE (rhs
) == TARGET_EXPR
)
1252 /* If CODE is not INIT_EXPR, can't initialize LHS directly,
1253 since that would cause the LHS to be constructed twice.
1254 So we force the TARGET_EXPR to be expanded without a target. */
1255 if (code
!= INIT_EXPR
)
1256 rhs
= compound_expr (rhs
, TARGET_EXPR_SLOT (rhs
));
1259 d_mark_addressable (lhs
);
1260 rhs
= TARGET_EXPR_INITIAL (rhs
);
1264 tree result
= fold_build2_loc (input_location
, code
,
1265 TREE_TYPE (lhs
), lhs
, rhs
);
1266 return compound_expr (init
, result
);
1269 /* Build an assignment expression of lvalue LHS from value RHS. */
1272 modify_expr (tree lhs
, tree rhs
)
1274 return build_assign (MODIFY_EXPR
, lhs
, rhs
);
1277 /* Return EXP represented as TYPE. */
1280 build_nop (tree type
, tree exp
)
1282 if (error_operand_p (exp
))
1285 /* Maybe rewrite: cast(TYPE)(e1, e2) => (e1, cast(TYPE) e2) */
1286 tree init
= stabilize_expr (&exp
);
1287 exp
= fold_build1_loc (input_location
, NOP_EXPR
, type
, exp
);
1289 return compound_expr (init
, exp
);
1292 /* Return EXP to be viewed as being another type TYPE. Same as build_nop,
1293 except that EXP is type-punned, rather than a straight-forward cast. */
1296 build_vconvert (tree type
, tree exp
)
1298 /* Building *(cast(TYPE *)&e1) directly rather then using VIEW_CONVERT_EXPR
1299 makes sure this works for vector-to-array viewing, or if EXP ends up being
1300 used as the LHS of a MODIFY_EXPR. */
1301 return indirect_ref (type
, build_address (exp
));
1304 /* Maybe warn about ARG being an address that can never be null. */
1307 warn_for_null_address (tree arg
)
1309 if (TREE_CODE (arg
) == ADDR_EXPR
1310 && decl_with_nonnull_addr_p (TREE_OPERAND (arg
, 0)))
1311 warning (OPT_Waddress
,
1312 "the address of %qD will never be %<null%>",
1313 TREE_OPERAND (arg
, 0));
1316 /* Build a boolean ARG0 op ARG1 expression. */
1319 build_boolop (tree_code code
, tree arg0
, tree arg1
)
1321 /* Aggregate comparisons may get lowered to a call to builtin memcmp,
1322 so need to remove all side effects incase its address is taken. */
1323 if (AGGREGATE_TYPE_P (TREE_TYPE (arg0
)))
1324 arg0
= d_save_expr (arg0
);
1325 if (AGGREGATE_TYPE_P (TREE_TYPE (arg1
)))
1326 arg1
= d_save_expr (arg1
);
1328 if (VECTOR_TYPE_P (TREE_TYPE (arg0
)) && VECTOR_TYPE_P (TREE_TYPE (arg1
)))
1330 /* Build a vector comparison.
1331 VEC_COND_EXPR <e1 op e2, { -1, -1, -1, -1 }, { 0, 0, 0, 0 }>; */
1332 tree type
= TREE_TYPE (arg0
);
1333 tree cmptype
= build_same_sized_truth_vector_type (type
);
1334 tree cmp
= fold_build2_loc (input_location
, code
, cmptype
, arg0
, arg1
);
1336 return fold_build3_loc (input_location
, VEC_COND_EXPR
, type
, cmp
,
1337 build_minus_one_cst (type
),
1338 build_zero_cst (type
));
1341 if (code
== EQ_EXPR
|| code
== NE_EXPR
)
1343 /* Check if comparing the address of a variable to null. */
1344 if (POINTER_TYPE_P (TREE_TYPE (arg0
)) && integer_zerop (arg1
))
1345 warn_for_null_address (arg0
);
1346 if (POINTER_TYPE_P (TREE_TYPE (arg1
)) && integer_zerop (arg0
))
1347 warn_for_null_address (arg1
);
1350 return fold_build2_loc (input_location
, code
, d_bool_type
,
1351 arg0
, d_convert (TREE_TYPE (arg0
), arg1
));
1354 /* Return a COND_EXPR. ARG0, ARG1, and ARG2 are the three
1355 arguments to the conditional expression. */
1358 build_condition (tree type
, tree arg0
, tree arg1
, tree arg2
)
1360 if (arg1
== void_node
)
1361 arg1
= build_empty_stmt (input_location
);
1363 if (arg2
== void_node
)
1364 arg2
= build_empty_stmt (input_location
);
1366 return fold_build3_loc (input_location
, COND_EXPR
,
1367 type
, arg0
, arg1
, arg2
);
1371 build_vcondition (tree arg0
, tree arg1
, tree arg2
)
1373 return build_condition (void_type_node
, arg0
, arg1
, arg2
);
1376 /* Build a compound expr to join ARG0 and ARG1 together. */
1379 compound_expr (tree arg0
, tree arg1
)
1381 if (arg1
== NULL_TREE
)
1384 if (arg0
== NULL_TREE
|| !TREE_SIDE_EFFECTS (arg0
))
1387 if (TREE_CODE (arg1
) == TARGET_EXPR
)
1389 /* If the rhs is a TARGET_EXPR, then build the compound expression
1390 inside the target_expr's initializer. This helps the compiler
1391 to eliminate unnecessary temporaries. */
1392 tree init
= compound_expr (arg0
, TARGET_EXPR_INITIAL (arg1
));
1393 TARGET_EXPR_INITIAL (arg1
) = init
;
1398 return fold_build2_loc (input_location
, COMPOUND_EXPR
,
1399 TREE_TYPE (arg1
), arg0
, arg1
);
1402 /* Build a return expression. */
1405 return_expr (tree ret
)
1407 return fold_build1_loc (input_location
, RETURN_EXPR
,
1408 void_type_node
, ret
);
1411 /* Return the product of ARG0 and ARG1 as a size_type_node. */
1414 size_mult_expr (tree arg0
, tree arg1
)
1416 return fold_build2_loc (input_location
, MULT_EXPR
, size_type_node
,
1417 d_convert (size_type_node
, arg0
),
1418 d_convert (size_type_node
, arg1
));
1422 /* Return the real part of CE, which should be a complex expression. */
1427 return fold_build1_loc (input_location
, REALPART_EXPR
,
1428 TREE_TYPE (TREE_TYPE (ce
)), ce
);
1431 /* Return the imaginary part of CE, which should be a complex expression. */
1434 imaginary_part (tree ce
)
1436 return fold_build1_loc (input_location
, IMAGPART_EXPR
,
1437 TREE_TYPE (TREE_TYPE (ce
)), ce
);
1440 /* Build a complex expression of type TYPE using RE and IM. */
1443 complex_expr (tree type
, tree re
, tree im
)
1445 return fold_build2_loc (input_location
, COMPLEX_EXPR
,
1449 /* Cast EXP (which should be a pointer) to TYPE* and then indirect.
1450 The back-end requires this cast in many cases. */
1453 indirect_ref (tree type
, tree exp
)
1455 if (error_operand_p (exp
))
1458 /* Maybe rewrite: *(e1, e2) => (e1, *e2) */
1459 tree init
= stabilize_expr (&exp
);
1461 if (TREE_CODE (TREE_TYPE (exp
)) == REFERENCE_TYPE
)
1462 exp
= fold_build1 (INDIRECT_REF
, type
, exp
);
1465 exp
= build_nop (build_pointer_type (type
), exp
);
1466 exp
= build_deref (exp
);
1469 return compound_expr (init
, exp
);
1472 /* Returns indirect reference of EXP, which must be a pointer type. */
1475 build_deref (tree exp
)
1477 if (error_operand_p (exp
))
1480 /* Maybe rewrite: *(e1, e2) => (e1, *e2) */
1481 tree init
= stabilize_expr (&exp
);
1483 gcc_assert (POINTER_TYPE_P (TREE_TYPE (exp
)));
1485 if (TREE_CODE (exp
) == ADDR_EXPR
)
1486 exp
= TREE_OPERAND (exp
, 0);
1488 exp
= build_fold_indirect_ref (exp
);
1490 return compound_expr (init
, exp
);
1493 /* Builds pointer offset expression PTR[INDEX]. */
1496 build_array_index (tree ptr
, tree index
)
1498 if (error_operand_p (ptr
) || error_operand_p (index
))
1499 return error_mark_node
;
1501 tree ptr_type
= TREE_TYPE (ptr
);
1502 tree target_type
= TREE_TYPE (ptr_type
);
1504 tree type
= lang_hooks
.types
.type_for_size (TYPE_PRECISION (sizetype
),
1505 TYPE_UNSIGNED (sizetype
));
1507 /* Array element size. */
1508 tree size_exp
= size_in_bytes (target_type
);
1510 if (integer_zerop (size_exp
))
1512 /* Test for array of void. */
1513 if (TYPE_MODE (target_type
) == TYPE_MODE (void_type_node
))
1514 index
= fold_convert (type
, index
);
1517 /* Should catch this earlier. */
1518 error ("invalid use of incomplete type %qD", TYPE_NAME (target_type
));
1519 ptr_type
= error_mark_node
;
1522 else if (integer_onep (size_exp
))
1524 /* Array of bytes -- No need to multiply. */
1525 index
= fold_convert (type
, index
);
1529 index
= d_convert (type
, index
);
1530 index
= fold_build2 (MULT_EXPR
, TREE_TYPE (index
),
1531 index
, d_convert (TREE_TYPE (index
), size_exp
));
1532 index
= fold_convert (type
, index
);
1535 if (integer_zerop (index
))
1538 return fold_build2 (POINTER_PLUS_EXPR
, ptr_type
, ptr
, index
);
1541 /* Builds pointer offset expression *(PTR OP OFFSET)
1542 OP could be a plus or minus expression. */
1545 build_offset_op (tree_code op
, tree ptr
, tree offset
)
1547 gcc_assert (op
== MINUS_EXPR
|| op
== PLUS_EXPR
);
1549 tree type
= lang_hooks
.types
.type_for_size (TYPE_PRECISION (sizetype
),
1550 TYPE_UNSIGNED (sizetype
));
1551 offset
= fold_convert (type
, offset
);
1553 if (op
== MINUS_EXPR
)
1554 offset
= fold_build1 (NEGATE_EXPR
, type
, offset
);
1556 return fold_build2 (POINTER_PLUS_EXPR
, TREE_TYPE (ptr
), ptr
, offset
);
1559 /* Builds pointer offset expression *(PTR + OFFSET). */
1562 build_offset (tree ptr
, tree offset
)
1564 return build_offset_op (PLUS_EXPR
, ptr
, offset
);
1568 build_memref (tree type
, tree ptr
, tree offset
)
1570 return fold_build2 (MEM_REF
, type
, ptr
, fold_convert (type
, offset
));
1573 /* Create a tree node to set multiple elements to a single value. */
1576 build_array_set (tree ptr
, tree length
, tree value
)
1578 tree ptrtype
= TREE_TYPE (ptr
);
1579 tree lentype
= TREE_TYPE (length
);
1581 push_binding_level (level_block
);
1584 /* Build temporary locals for length and ptr, and maybe value. */
1585 tree t
= build_local_temp (size_type_node
);
1586 add_stmt (build_assign (INIT_EXPR
, t
, length
));
1589 t
= build_local_temp (ptrtype
);
1590 add_stmt (build_assign (INIT_EXPR
, t
, ptr
));
1593 if (TREE_SIDE_EFFECTS (value
))
1595 t
= build_local_temp (TREE_TYPE (value
));
1596 add_stmt (build_assign (INIT_EXPR
, t
, value
));
1600 /* Build loop to initialize { .length=length, .ptr=ptr } with value. */
1603 /* Exit logic for the loop.
1604 if (length == 0) break; */
1605 t
= build_boolop (EQ_EXPR
, length
, d_convert (lentype
, integer_zero_node
));
1606 t
= build1 (EXIT_EXPR
, void_type_node
, t
);
1609 /* Assign value to the current pointer position.
1611 t
= modify_expr (build_deref (ptr
), value
);
1614 /* Move pointer to next element position.
1616 tree size
= TYPE_SIZE_UNIT (TREE_TYPE (ptrtype
));
1617 t
= build2 (POSTINCREMENT_EXPR
, ptrtype
, ptr
, d_convert (ptrtype
, size
));
1620 /* Decrease loop counter.
1622 t
= build2 (POSTDECREMENT_EXPR
, lentype
, length
,
1623 d_convert (lentype
, integer_one_node
));
1626 /* Pop statements and finish loop. */
1627 tree loop_body
= pop_stmt_list ();
1628 add_stmt (build1 (LOOP_EXPR
, void_type_node
, loop_body
));
1630 /* Wrap it up into a bind expression. */
1631 tree stmt_list
= pop_stmt_list ();
1632 tree block
= pop_binding_level ();
1634 return build3 (BIND_EXPR
, void_type_node
,
1635 BLOCK_VARS (block
), stmt_list
, block
);
1639 /* Build an array of type TYPE where all the elements are VAL. */
1642 build_array_from_val (Type
*type
, tree val
)
1644 gcc_assert (type
->ty
== Tsarray
);
1646 tree etype
= build_ctype (type
->nextOf ());
1648 /* Initializing a multidimensional array. */
1649 if (TREE_CODE (etype
) == ARRAY_TYPE
&& TREE_TYPE (val
) != etype
)
1650 val
= build_array_from_val (type
->nextOf (), val
);
1652 size_t dims
= ((TypeSArray
*) type
)->dim
->toInteger ();
1653 vec
<constructor_elt
, va_gc
> *elms
= NULL
;
1654 vec_safe_reserve (elms
, dims
);
1656 val
= d_convert (etype
, val
);
1658 for (size_t i
= 0; i
< dims
; i
++)
1659 CONSTRUCTOR_APPEND_ELT (elms
, size_int (i
), val
);
1661 return build_constructor (build_ctype (type
), elms
);
1664 /* Implicitly converts void* T to byte* as D allows { void[] a; &a[3]; } */
1667 void_okay_p (tree t
)
1669 tree type
= TREE_TYPE (t
);
1671 if (VOID_TYPE_P (TREE_TYPE (type
)))
1673 tree totype
= build_ctype (Type::tuns8
->pointerTo ());
1674 return fold_convert (totype
, t
);
1680 /* Builds a bounds condition checking that INDEX is between 0 and LEN.
1681 The condition returns the INDEX if true, or throws a RangeError.
1682 If INCLUSIVE, we allow INDEX == LEN to return true also. */
1685 build_bounds_condition (const Loc
& loc
, tree index
, tree len
, bool inclusive
)
1687 if (!array_bounds_check ())
1690 /* Prevent multiple evaluations of the index. */
1691 index
= d_save_expr (index
);
1693 /* Generate INDEX >= LEN && throw RangeError.
1694 No need to check whether INDEX >= 0 as the front-end should
1695 have already taken care of implicit casts to unsigned. */
1696 tree condition
= fold_build2 (inclusive
? GT_EXPR
: GE_EXPR
,
1697 d_bool_type
, index
, len
);
1698 tree boundserr
= d_assert_call (loc
, LIBCALL_ARRAY_BOUNDS
);
1700 return build_condition (TREE_TYPE (index
), condition
, boundserr
, index
);
1703 /* Returns TRUE if array bounds checking code generation is turned on. */
1706 array_bounds_check (void)
1708 FuncDeclaration
*fd
;
1710 switch (global
.params
.useArrayBounds
)
1712 case BOUNDSCHECKoff
:
1718 case BOUNDSCHECKsafeonly
:
1719 /* For D2 safe functions only. */
1720 fd
= d_function_chain
->function
;
1721 if (fd
&& fd
->type
->ty
== Tfunction
)
1723 TypeFunction
*tf
= (TypeFunction
*) fd
->type
;
1724 if (tf
->trust
== TRUSTsafe
)
1734 /* Return an undeclared local temporary of type TYPE
1735 for use with BIND_EXPR. */
1738 create_temporary_var (tree type
)
1740 tree decl
= build_decl (input_location
, VAR_DECL
, NULL_TREE
, type
);
1742 DECL_CONTEXT (decl
) = current_function_decl
;
1743 DECL_ARTIFICIAL (decl
) = 1;
1744 DECL_IGNORED_P (decl
) = 1;
1745 layout_decl (decl
, 0);
1750 /* Return an undeclared local temporary OUT_VAR initialized
1751 with result of expression EXP. */
1754 maybe_temporary_var (tree exp
, tree
*out_var
)
1758 /* Get the base component. */
1759 while (TREE_CODE (t
) == COMPONENT_REF
)
1760 t
= TREE_OPERAND (t
, 0);
1762 if (!DECL_P (t
) && !REFERENCE_CLASS_P (t
))
1764 *out_var
= create_temporary_var (TREE_TYPE (exp
));
1765 DECL_INITIAL (*out_var
) = exp
;
1770 *out_var
= NULL_TREE
;
1775 /* Builds a BIND_EXPR around BODY for the variables VAR_CHAIN. */
1778 bind_expr (tree var_chain
, tree body
)
1780 /* Only handles one var. */
1781 gcc_assert (TREE_CHAIN (var_chain
) == NULL_TREE
);
1783 if (DECL_INITIAL (var_chain
))
1785 tree ini
= build_assign (INIT_EXPR
, var_chain
, DECL_INITIAL (var_chain
));
1786 DECL_INITIAL (var_chain
) = NULL_TREE
;
1787 body
= compound_expr (ini
, body
);
1790 return d_save_expr (build3 (BIND_EXPR
, TREE_TYPE (body
),
1791 var_chain
, body
, NULL_TREE
));
1794 /* Returns the TypeFunction class for Type T.
1795 Assumes T is already ->toBasetype(). */
1798 get_function_type (Type
*t
)
1800 TypeFunction
*tf
= NULL
;
1801 if (t
->ty
== Tpointer
)
1802 t
= t
->nextOf ()->toBasetype ();
1803 if (t
->ty
== Tfunction
)
1804 tf
= (TypeFunction
*) t
;
1805 else if (t
->ty
== Tdelegate
)
1806 tf
= (TypeFunction
*) ((TypeDelegate
*) t
)->next
;
1810 /* Returns TRUE if CALLEE is a plain nested function outside the scope of
1811 CALLER. In which case, CALLEE is being called through an alias that was
1812 passed to CALLER. */
1815 call_by_alias_p (FuncDeclaration
*caller
, FuncDeclaration
*callee
)
1817 if (!callee
->isNested ())
1820 if (caller
->toParent () == callee
->toParent ())
1823 Dsymbol
*dsym
= callee
;
1827 if (dsym
->isTemplateInstance ())
1829 else if (dsym
->isFuncDeclaration () == caller
)
1831 dsym
= dsym
->toParent ();
1837 /* Entry point for call routines. Builds a function call to FD.
1838 OBJECT is the 'this' reference passed and ARGS are the arguments to FD. */
1841 d_build_call_expr (FuncDeclaration
*fd
, tree object
, Expressions
*arguments
)
1843 return d_build_call (get_function_type (fd
->type
),
1844 build_address (get_symbol_decl (fd
)), object
, arguments
);
1847 /* Builds a CALL_EXPR of type TF to CALLABLE. OBJECT holds the 'this' pointer,
1848 ARGUMENTS are evaluated in left to right order, saved and promoted
1852 d_build_call (TypeFunction
*tf
, tree callable
, tree object
,
1853 Expressions
*arguments
)
1855 tree ctype
= TREE_TYPE (callable
);
1856 tree callee
= callable
;
1858 if (POINTER_TYPE_P (ctype
))
1859 ctype
= TREE_TYPE (ctype
);
1861 callee
= build_address (callable
);
1863 gcc_assert (FUNC_OR_METHOD_TYPE_P (ctype
));
1864 gcc_assert (tf
!= NULL
);
1865 gcc_assert (tf
->ty
== Tfunction
);
1867 if (TREE_CODE (ctype
) != FUNCTION_TYPE
&& object
== NULL_TREE
)
1869 /* Front-end apparently doesn't check this. */
1870 if (TREE_CODE (callable
) == FUNCTION_DECL
)
1872 error ("need %<this%> to access member %qE", DECL_NAME (callable
));
1873 return error_mark_node
;
1876 /* Probably an internal error. */
1880 /* Build the argument list for the call. */
1881 vec
<tree
, va_gc
> *args
= NULL
;
1882 tree saved_args
= NULL_TREE
;
1884 /* If this is a delegate call or a nested function being called as
1885 a delegate, the object should not be NULL. */
1886 if (object
!= NULL_TREE
)
1887 vec_safe_push (args
, object
);
1891 /* First pass, evaluated expanded tuples in function arguments. */
1892 for (size_t i
= 0; i
< arguments
->dim
; ++i
)
1895 Expression
*arg
= (*arguments
)[i
];
1896 gcc_assert (arg
->op
!= TOKtuple
);
1898 if (arg
->op
== TOKcomma
)
1900 CommaExp
*ce
= (CommaExp
*) arg
;
1901 tree tce
= build_expr (ce
->e1
);
1902 saved_args
= compound_expr (saved_args
, tce
);
1903 (*arguments
)[i
] = ce
->e2
;
1908 size_t nparams
= Parameter::dim (tf
->parameters
);
1909 /* if _arguments[] is the first argument. */
1910 size_t varargs
= (tf
->linkage
== LINKd
&& tf
->varargs
== 1);
1912 /* Assumes arguments->dim <= formal_args->dim if (!tf->varargs). */
1913 for (size_t i
= 0; i
< arguments
->dim
; ++i
)
1915 Expression
*arg
= (*arguments
)[i
];
1916 tree targ
= build_expr (arg
);
1918 if (i
- varargs
< nparams
&& i
>= varargs
)
1920 /* Actual arguments for declared formal arguments. */
1921 Parameter
*parg
= Parameter::getNth (tf
->parameters
, i
- varargs
);
1922 targ
= convert_for_argument (targ
, parg
);
1925 /* Don't pass empty aggregates by value. */
1926 if (empty_aggregate_p (TREE_TYPE (targ
)) && !TREE_ADDRESSABLE (targ
)
1927 && TREE_CODE (targ
) != CONSTRUCTOR
)
1929 tree t
= build_constructor (TREE_TYPE (targ
), NULL
);
1930 targ
= build2 (COMPOUND_EXPR
, TREE_TYPE (t
), targ
, t
);
1933 vec_safe_push (args
, targ
);
1937 /* Evaluate the callee before calling it. */
1938 if (TREE_SIDE_EFFECTS (callee
))
1940 callee
= d_save_expr (callee
);
1941 saved_args
= compound_expr (callee
, saved_args
);
1944 tree result
= build_call_vec (TREE_TYPE (ctype
), callee
, args
);
1946 /* Enforce left to right evaluation. */
1947 if (tf
->linkage
== LINKd
)
1948 CALL_EXPR_ARGS_ORDERED (result
) = 1;
1950 result
= maybe_expand_intrinsic (result
);
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
)))
1958 CALL_EXPR_RETURN_SLOT_OPT (result
) = true;
1959 result
= force_target_expr (result
);
1962 return compound_expr (saved_args
, result
);
1965 /* Builds a call to AssertError or AssertErrorMsg. */
1968 d_assert_call (const Loc
& loc
, libcall_fn libcall
, tree msg
)
1971 tree line
= size_int (loc
.linnum
);
1973 /* File location is passed as a D string. */
1976 unsigned len
= strlen (loc
.filename
);
1977 tree str
= build_string (len
, loc
.filename
);
1978 TREE_TYPE (str
) = make_array_type (Type::tchar
, len
);
1980 file
= d_array_value (build_ctype (Type::tchar
->arrayOf ()),
1981 size_int (len
), build_address (str
));
1984 file
= null_array_node
;
1987 return build_libcall (libcall
, Type::tvoid
, 3, msg
, file
, line
);
1989 return build_libcall (libcall
, Type::tvoid
, 2, file
, line
);
1992 /* Build and return the correct call to fmod depending on TYPE.
1993 ARG0 and ARG1 are the arguments pass to the function. */
1996 build_float_modulus (tree type
, tree arg0
, tree arg1
)
1998 tree fmodfn
= NULL_TREE
;
1999 tree basetype
= type
;
2001 if (COMPLEX_FLOAT_TYPE_P (basetype
))
2002 basetype
= TREE_TYPE (basetype
);
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
);
2016 error ("tried to perform floating-point modulo division on %qT", type
);
2017 return error_mark_node
;
2020 if (COMPLEX_FLOAT_TYPE_P (type
))
2022 tree re
= build_call_expr (fmodfn
, 2, real_part (arg0
), arg1
);
2023 tree im
= build_call_expr (fmodfn
, 2, imaginary_part (arg0
), arg1
);
2025 return complex_expr (type
, re
, im
);
2028 if (SCALAR_FLOAT_TYPE_P (type
))
2029 return build_call_expr (fmodfn
, 2, arg0
, arg1
);
2031 /* Should have caught this above. */
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. */
2041 build_vthis_function (tree basetype
, tree type
)
2043 gcc_assert (TREE_CODE (type
) == FUNCTION_TYPE
);
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
);
2049 if (RECORD_OR_UNION_TYPE_P (basetype
))
2050 TYPE_METHOD_BASETYPE (fntype
) = TYPE_MAIN_VARIANT (basetype
);
2052 gcc_assert (VOID_TYPE_P (basetype
));
2057 /* If SYM is a nested function, return the static chain to be
2058 used when calling that function from the current function.
2060 If SYM is a nested class or struct, return the static chain
2061 to be used when creating an instance of the class from CFUN. */
2064 get_frame_for_symbol (Dsymbol
*sym
)
2066 FuncDeclaration
*thisfd
2067 = d_function_chain
? d_function_chain
->function
: NULL
;
2068 FuncDeclaration
*fd
= sym
->isFuncDeclaration ();
2069 FuncDeclaration
*fdparent
= NULL
;
2070 FuncDeclaration
*fdoverride
= NULL
;
2074 /* Check that the nested function is properly defined. */
2077 /* Should instead error on line that references 'fd'. */
2078 error_at (make_location_t (fd
->loc
), "nested function missing body");
2079 return null_pointer_node
;
2082 fdparent
= fd
->toParent2 ()->isFuncDeclaration ();
2084 /* Special case for __ensure and __require. */
2085 if ((fd
->ident
== Identifier::idPool ("__ensure")
2086 || fd
->ident
== Identifier::idPool ("__require"))
2087 && fdparent
!= thisfd
)
2089 fdoverride
= fdparent
;
2095 /* It's a class (or struct). NewExp codegen has already determined its
2096 outer scope is not another class, so it must be a function. */
2097 while (sym
&& !sym
->isFuncDeclaration ())
2098 sym
= sym
->toParent2 ();
2100 fdparent
= (FuncDeclaration
*) sym
;
2103 gcc_assert (fdparent
!= NULL
);
2105 if (thisfd
!= fdparent
)
2107 /* If no frame pointer for this function. */
2110 error_at (make_location_t (sym
->loc
),
2111 "is a nested function and cannot be accessed from %qs",
2112 thisfd
->toChars ());
2113 return null_pointer_node
;
2116 /* Make sure we can get the frame pointer to the outer function.
2117 Go up each nesting level until we find the enclosing function. */
2118 Dsymbol
*dsym
= thisfd
;
2122 /* Check if enclosing function is a function. */
2123 FuncDeclaration
*fd
= dsym
->isFuncDeclaration ();
2127 if (fdparent
== fd
->toParent2 ())
2130 gcc_assert (fd
->isNested () || fd
->vthis
);
2131 dsym
= dsym
->toParent2 ();
2135 /* Check if enclosed by an aggregate. That means the current
2136 function must be a member function of that aggregate. */
2137 AggregateDeclaration
*ad
= dsym
->isAggregateDeclaration ();
2141 if (ad
->isClassDeclaration () && fdparent
== ad
->toParent2 ())
2143 if (ad
->isStructDeclaration () && fdparent
== ad
->toParent2 ())
2146 if (!ad
->isNested () || !ad
->vthis
)
2149 error_at (make_location_t (thisfd
->loc
),
2150 "cannot get frame pointer to %qs",
2151 sym
->toPrettyChars ());
2152 return null_pointer_node
;
2155 dsym
= dsym
->toParent2 ();
2159 tree ffo
= get_frameinfo (fdparent
);
2160 if (FRAMEINFO_CREATES_FRAME (ffo
) || FRAMEINFO_STATIC_CHAIN (ffo
))
2162 tree frame_ref
= get_framedecl (thisfd
, fdparent
);
2164 /* If 'thisfd' is a derived member function, then 'fdparent' is the
2165 overridden member function in the base class. Even if there's a
2166 closure environment, we should give the original stack data as the
2167 nested function frame. */
2170 ClassDeclaration
*cdo
= fdoverride
->isThis ()->isClassDeclaration ();
2171 ClassDeclaration
*cd
= thisfd
->isThis ()->isClassDeclaration ();
2172 gcc_assert (cdo
&& cd
);
2175 if (cdo
->isBaseOf (cd
, &offset
) && offset
!= 0)
2177 /* Generate a new frame to pass to the overriden function that
2178 has the 'this' pointer adjusted. */
2179 gcc_assert (offset
!= OFFSET_RUNTIME
);
2181 tree type
= FRAMEINFO_TYPE (get_frameinfo (fdoverride
));
2182 tree fields
= TYPE_FIELDS (type
);
2183 /* The 'this' field comes immediately after the '__chain'. */
2184 tree thisfield
= chain_index (1, fields
);
2185 vec
<constructor_elt
, va_gc
> *ve
= NULL
;
2187 tree framefields
= TYPE_FIELDS (FRAMEINFO_TYPE (ffo
));
2188 frame_ref
= build_deref (frame_ref
);
2190 for (tree field
= fields
; field
; field
= DECL_CHAIN (field
))
2192 tree value
= component_ref (frame_ref
, framefields
);
2193 if (field
== thisfield
)
2194 value
= build_offset (value
, size_int (offset
));
2196 CONSTRUCTOR_APPEND_ELT (ve
, field
, value
);
2197 framefields
= DECL_CHAIN (framefields
);
2200 frame_ref
= build_address (build_constructor (type
, ve
));
2207 return null_pointer_node
;
2210 /* Return the parent function of a nested class CD. */
2212 static FuncDeclaration
*
2213 d_nested_class (ClassDeclaration
*cd
)
2215 FuncDeclaration
*fd
= NULL
;
2216 while (cd
&& cd
->isNested ())
2218 Dsymbol
*dsym
= cd
->toParent2 ();
2219 if ((fd
= dsym
->isFuncDeclaration ()))
2222 cd
= dsym
->isClassDeclaration ();
2227 /* Return the parent function of a nested struct SD. */
2229 static FuncDeclaration
*
2230 d_nested_struct (StructDeclaration
*sd
)
2232 FuncDeclaration
*fd
= NULL
;
2233 while (sd
&& sd
->isNested ())
2235 Dsymbol
*dsym
= sd
->toParent2 ();
2236 if ((fd
= dsym
->isFuncDeclaration ()))
2239 sd
= dsym
->isStructDeclaration ();
2245 /* Starting from the current function FD, try to find a suitable value of
2246 'this' in nested function instances. A suitable 'this' value is an
2247 instance of OCD or a class that has OCD as a base. */
2250 find_this_tree (ClassDeclaration
*ocd
)
2252 FuncDeclaration
*fd
= d_function_chain
? d_function_chain
->function
: NULL
;
2256 AggregateDeclaration
*ad
= fd
->isThis ();
2257 ClassDeclaration
*cd
= ad
? ad
->isClassDeclaration () : NULL
;
2262 return get_decl_tree (fd
->vthis
);
2263 else if (ocd
->isBaseOf (cd
, NULL
))
2264 return convert_expr (get_decl_tree (fd
->vthis
),
2265 cd
->type
, ocd
->type
);
2267 fd
= d_nested_class (cd
);
2271 if (fd
->isNested ())
2273 fd
= fd
->toParent2 ()->isFuncDeclaration ();
2284 /* Retrieve the outer class/struct 'this' value of DECL from
2285 the current function. */
2288 build_vthis (AggregateDeclaration
*decl
)
2290 ClassDeclaration
*cd
= decl
->isClassDeclaration ();
2291 StructDeclaration
*sd
= decl
->isStructDeclaration ();
2293 /* If an aggregate nested in a function has no methods and there are no
2294 other nested functions, any static chain created here will never be
2295 translated. Use a null pointer for the link in this case. */
2296 tree vthis_value
= null_pointer_node
;
2298 if (cd
!= NULL
|| sd
!= NULL
)
2300 Dsymbol
*outer
= decl
->toParent2 ();
2302 /* If the parent is a templated struct, the outer context is instead
2303 the enclosing symbol of where the instantiation happened. */
2304 if (outer
->isStructDeclaration ())
2306 gcc_assert (outer
->parent
&& outer
->parent
->isTemplateInstance ());
2307 outer
= ((TemplateInstance
*) outer
->parent
)->enclosing
;
2310 /* For outer classes, get a suitable 'this' value.
2311 For outer functions, get a suitable frame/closure pointer. */
2312 ClassDeclaration
*cdo
= outer
->isClassDeclaration ();
2313 FuncDeclaration
*fdo
= outer
->isFuncDeclaration ();
2317 vthis_value
= find_this_tree (cdo
);
2318 gcc_assert (vthis_value
!= NULL_TREE
);
2322 tree ffo
= get_frameinfo (fdo
);
2323 if (FRAMEINFO_CREATES_FRAME (ffo
) || FRAMEINFO_STATIC_CHAIN (ffo
)
2324 || fdo
->hasNestedFrameRefs ())
2325 vthis_value
= get_frame_for_symbol (decl
);
2326 else if (cd
!= NULL
)
2328 /* Classes nested in methods are allowed to access any outer
2329 class fields, use the function chain in this case. */
2330 if (fdo
->vthis
&& fdo
->vthis
->type
!= Type::tvoidptr
)
2331 vthis_value
= get_decl_tree (fdo
->vthis
);
2341 /* Build the RECORD_TYPE that describes the function frame or closure type for
2342 the function FD. FFI is the tree holding all frame information. */
2345 build_frame_type (tree ffi
, FuncDeclaration
*fd
)
2347 if (FRAMEINFO_TYPE (ffi
))
2348 return FRAMEINFO_TYPE (ffi
);
2350 tree frame_rec_type
= make_node (RECORD_TYPE
);
2351 char *name
= concat (FRAMEINFO_IS_CLOSURE (ffi
) ? "CLOSURE." : "FRAME.",
2352 fd
->toPrettyChars (), NULL
);
2353 TYPE_NAME (frame_rec_type
) = get_identifier (name
);
2356 tree fields
= NULL_TREE
;
2358 /* Function is a member or nested, so must have field for outer context. */
2361 tree ptr_field
= build_decl (BUILTINS_LOCATION
, FIELD_DECL
,
2362 get_identifier ("__chain"), ptr_type_node
);
2363 DECL_FIELD_CONTEXT (ptr_field
) = frame_rec_type
;
2364 fields
= chainon (NULL_TREE
, ptr_field
);
2365 DECL_NONADDRESSABLE_P (ptr_field
) = 1;
2368 /* The __ensure and __require are called directly, so never make the outer
2369 functions closure, but nevertheless could still be referencing parameters
2370 of the calling function non-locally. So we add all parameters with nested
2371 refs to the function frame, this should also mean overriding methods will
2372 have the same frame layout when inheriting a contract. */
2373 if ((global
.params
.useIn
&& fd
->frequire
)
2374 || (global
.params
.useOut
&& fd
->fensure
))
2378 for (size_t i
= 0; fd
->parameters
&& i
< fd
->parameters
->dim
; i
++)
2380 VarDeclaration
*v
= (*fd
->parameters
)[i
];
2381 /* Remove if already in closureVars so can push to front. */
2382 for (size_t j
= i
; j
< fd
->closureVars
.dim
; j
++)
2384 Dsymbol
*s
= fd
->closureVars
[j
];
2387 fd
->closureVars
.remove (j
);
2391 fd
->closureVars
.insert (i
, v
);
2395 /* Also add hidden 'this' to outer context. */
2398 for (size_t i
= 0; i
< fd
->closureVars
.dim
; i
++)
2400 Dsymbol
*s
= fd
->closureVars
[i
];
2403 fd
->closureVars
.remove (i
);
2407 fd
->closureVars
.insert (0, fd
->vthis
);
2411 for (size_t i
= 0; i
< fd
->closureVars
.dim
; i
++)
2413 VarDeclaration
*v
= fd
->closureVars
[i
];
2414 tree vsym
= get_symbol_decl (v
);
2415 tree ident
= v
->ident
2416 ? get_identifier (v
->ident
->toChars ()) : NULL_TREE
;
2418 tree field
= build_decl (make_location_t (v
->loc
), FIELD_DECL
, ident
,
2420 SET_DECL_LANG_FRAME_FIELD (vsym
, field
);
2421 DECL_FIELD_CONTEXT (field
) = frame_rec_type
;
2422 fields
= chainon (fields
, field
);
2423 TREE_USED (vsym
) = 1;
2425 TREE_ADDRESSABLE (field
) = TREE_ADDRESSABLE (vsym
);
2426 DECL_NONADDRESSABLE_P (field
) = !TREE_ADDRESSABLE (vsym
);
2427 TREE_THIS_VOLATILE (field
) = TREE_THIS_VOLATILE (vsym
);
2429 /* Can't do nrvo if the variable is put in a frame. */
2430 if (fd
->nrvo_can
&& fd
->nrvo_var
== v
)
2433 if (FRAMEINFO_IS_CLOSURE (ffi
))
2435 /* Because the value needs to survive the end of the scope. */
2436 if ((v
->edtor
&& (v
->storage_class
& STCparameter
))
2437 || v
->needsScopeDtor ())
2438 error_at (make_location_t (v
->loc
),
2439 "has scoped destruction, cannot build closure");
2443 TYPE_FIELDS (frame_rec_type
) = fields
;
2444 TYPE_READONLY (frame_rec_type
) = 1;
2445 layout_type (frame_rec_type
);
2446 d_keep (frame_rec_type
);
2448 return frame_rec_type
;
2451 /* Closures are implemented by taking the local variables that
2452 need to survive the scope of the function, and copying them
2453 into a GC allocated chuck of memory. That chunk, called the
2454 closure here, is inserted into the linked list of stack
2455 frames instead of the usual stack frame.
2457 If a closure is not required, but FD still needs a frame to lower
2458 nested refs, then instead build custom static chain decl on stack. */
2461 build_closure (FuncDeclaration
*fd
)
2463 tree ffi
= get_frameinfo (fd
);
2465 if (!FRAMEINFO_CREATES_FRAME (ffi
))
2468 tree type
= FRAMEINFO_TYPE (ffi
);
2469 gcc_assert (COMPLETE_TYPE_P (type
));
2471 tree decl
, decl_ref
;
2473 if (FRAMEINFO_IS_CLOSURE (ffi
))
2475 decl
= build_local_temp (build_pointer_type (type
));
2476 DECL_NAME (decl
) = get_identifier ("__closptr");
2477 decl_ref
= build_deref (decl
);
2479 /* Allocate memory for closure. */
2480 tree arg
= convert (build_ctype (Type::tsize_t
), TYPE_SIZE_UNIT (type
));
2481 tree init
= build_libcall (LIBCALL_ALLOCMEMORY
, Type::tvoidptr
, 1, arg
);
2483 tree init_exp
= build_assign (INIT_EXPR
, decl
,
2484 build_nop (TREE_TYPE (decl
), init
));
2485 add_stmt (init_exp
);
2489 decl
= build_local_temp (type
);
2490 DECL_NAME (decl
) = get_identifier ("__frame");
2494 /* Set the first entry to the parent closure/frame, if any. */
2497 tree chain_field
= component_ref (decl_ref
, TYPE_FIELDS (type
));
2498 tree chain_expr
= modify_expr (chain_field
,
2499 d_function_chain
->static_chain
);
2500 add_stmt (chain_expr
);
2503 /* Copy parameters that are referenced nonlocally. */
2504 for (size_t i
= 0; i
< fd
->closureVars
.dim
; i
++)
2506 VarDeclaration
*v
= fd
->closureVars
[i
];
2508 if (!v
->isParameter ())
2511 tree vsym
= get_symbol_decl (v
);
2513 tree field
= component_ref (decl_ref
, DECL_LANG_FRAME_FIELD (vsym
));
2514 tree expr
= modify_expr (field
, vsym
);
2518 if (!FRAMEINFO_IS_CLOSURE (ffi
))
2519 decl
= build_address (decl
);
2521 d_function_chain
->static_chain
= decl
;
2524 /* Return the frame of FD. This could be a static chain or a closure
2525 passed via the hidden 'this' pointer. */
2528 get_frameinfo (FuncDeclaration
*fd
)
2530 tree fds
= get_symbol_decl (fd
);
2531 if (DECL_LANG_FRAMEINFO (fds
))
2532 return DECL_LANG_FRAMEINFO (fds
);
2534 tree ffi
= make_node (FUNCFRAME_INFO
);
2536 DECL_LANG_FRAMEINFO (fds
) = ffi
;
2538 if (fd
->needsClosure ())
2540 /* Set-up a closure frame, this will be allocated on the heap. */
2541 FRAMEINFO_CREATES_FRAME (ffi
) = 1;
2542 FRAMEINFO_IS_CLOSURE (ffi
) = 1;
2544 else if (fd
->hasNestedFrameRefs ())
2546 /* Functions with nested refs must create a static frame for local
2547 variables to be referenced from. */
2548 FRAMEINFO_CREATES_FRAME (ffi
) = 1;
2552 /* For nested functions, default to creating a frame. Even if there are
2553 no fields to populate the frame, create it anyway, as this will be
2554 used as the record type instead of `void*` for the this parameter. */
2555 if (fd
->vthis
&& fd
->vthis
->type
== Type::tvoidptr
)
2556 FRAMEINFO_CREATES_FRAME (ffi
) = 1;
2558 /* In checkNestedReference, references from contracts are not added to the
2559 closureVars array, so assume all parameters referenced. */
2560 if ((global
.params
.useIn
&& fd
->frequire
)
2561 || (global
.params
.useOut
&& fd
->fensure
))
2562 FRAMEINFO_CREATES_FRAME (ffi
) = 1;
2564 /* If however `fd` is nested (deeply) in a function that creates a
2565 closure, then `fd` instead inherits that closure via hidden vthis
2566 pointer, and doesn't create a stack frame at all. */
2567 FuncDeclaration
*ff
= fd
;
2571 tree ffo
= get_frameinfo (ff
);
2573 if (ff
!= fd
&& FRAMEINFO_CREATES_FRAME (ffo
))
2575 gcc_assert (FRAMEINFO_TYPE (ffo
));
2576 FRAMEINFO_CREATES_FRAME (ffi
) = 0;
2577 FRAMEINFO_STATIC_CHAIN (ffi
) = 1;
2578 FRAMEINFO_IS_CLOSURE (ffi
) = FRAMEINFO_IS_CLOSURE (ffo
);
2579 gcc_assert (COMPLETE_TYPE_P (FRAMEINFO_TYPE (ffo
)));
2580 FRAMEINFO_TYPE (ffi
) = FRAMEINFO_TYPE (ffo
);
2584 /* Stop looking if no frame pointer for this function. */
2585 if (ff
->vthis
== NULL
)
2588 AggregateDeclaration
*ad
= ff
->isThis ();
2589 if (ad
&& ad
->isNested ())
2591 while (ad
->isNested ())
2593 Dsymbol
*d
= ad
->toParent2 ();
2594 ad
= d
->isAggregateDeclaration ();
2595 ff
= d
->isFuncDeclaration ();
2602 ff
= ff
->toParent2 ()->isFuncDeclaration ();
2606 /* Build type now as may be referenced from another module. */
2607 if (FRAMEINFO_CREATES_FRAME (ffi
))
2608 FRAMEINFO_TYPE (ffi
) = build_frame_type (ffi
, fd
);
2613 /* Return a pointer to the frame/closure block of OUTER
2614 so can be accessed from the function INNER. */
2617 get_framedecl (FuncDeclaration
*inner
, FuncDeclaration
*outer
)
2619 tree result
= d_function_chain
->static_chain
;
2620 FuncDeclaration
*fd
= inner
;
2622 while (fd
&& fd
!= outer
)
2624 AggregateDeclaration
*ad
;
2625 ClassDeclaration
*cd
;
2626 StructDeclaration
*sd
;
2628 /* Parent frame link is the first field. */
2629 if (FRAMEINFO_CREATES_FRAME (get_frameinfo (fd
)))
2630 result
= indirect_ref (ptr_type_node
, result
);
2632 if (fd
->isNested ())
2633 fd
= fd
->toParent2 ()->isFuncDeclaration ();
2634 /* The frame/closure record always points to the outer function's
2635 frame, even if there are intervening nested classes or structs.
2636 So, we can just skip over these. */
2637 else if ((ad
= fd
->isThis ()) && (cd
= ad
->isClassDeclaration ()))
2638 fd
= d_nested_class (cd
);
2639 else if ((ad
= fd
->isThis ()) && (sd
= ad
->isStructDeclaration ()))
2640 fd
= d_nested_struct (sd
);
2645 /* Go get our frame record. */
2646 gcc_assert (fd
== outer
);
2647 tree frame_type
= FRAMEINFO_TYPE (get_frameinfo (outer
));
2649 if (frame_type
!= NULL_TREE
)
2651 result
= build_nop (build_pointer_type (frame_type
), result
);
2656 error_at (make_location_t (inner
->loc
),
2657 "forward reference to frame of %qs", outer
->toChars ());
2658 return null_pointer_node
;