OSDN Git Service

Merge branch 'trunk' of git://gcc.gnu.org/git/gcc into rework
[pf3gnuchains/gcc-fork.git] / gcc / ada / gcc-interface / utils2.c
1 /****************************************************************************
2  *                                                                          *
3  *                         GNAT COMPILER COMPONENTS                         *
4  *                                                                          *
5  *                               U T I L S 2                                *
6  *                                                                          *
7  *                          C Implementation File                           *
8  *                                                                          *
9  *          Copyright (C) 1992-2010, Free Software Foundation, Inc.         *
10  *                                                                          *
11  * GNAT is free software;  you can  redistribute it  and/or modify it under *
12  * terms of the  GNU General Public License as published  by the Free Soft- *
13  * ware  Foundation;  either version 3,  or (at your option) any later ver- *
14  * sion.  GNAT is distributed in the hope that it will be useful, but WITH- *
15  * OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY *
16  * or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License *
17  * for  more details.  You should have received a copy of the GNU General   *
18  * Public License along with GCC; see the file COPYING3.  If not see        *
19  * <http://www.gnu.org/licenses/>.                                          *
20  *                                                                          *
21  * GNAT was originally developed  by the GNAT team at  New York University. *
22  * Extensive contributions were provided by Ada Core Technologies Inc.      *
23  *                                                                          *
24  ****************************************************************************/
25
26 #include "config.h"
27 #include "system.h"
28 #include "coretypes.h"
29 #include "tm.h"
30 #include "tree.h"
31 #include "flags.h"
32 #include "ggc.h"
33 #include "output.h"
34 #include "tree-inline.h"
35
36 #include "ada.h"
37 #include "types.h"
38 #include "atree.h"
39 #include "elists.h"
40 #include "namet.h"
41 #include "nlists.h"
42 #include "snames.h"
43 #include "stringt.h"
44 #include "uintp.h"
45 #include "fe.h"
46 #include "sinfo.h"
47 #include "einfo.h"
48 #include "ada-tree.h"
49 #include "gigi.h"
50
51 /* Return the base type of TYPE.  */
52
53 tree
54 get_base_type (tree type)
55 {
56   if (TREE_CODE (type) == RECORD_TYPE
57       && TYPE_JUSTIFIED_MODULAR_P (type))
58     type = TREE_TYPE (TYPE_FIELDS (type));
59
60   while (TREE_TYPE (type)
61          && (TREE_CODE (type) == INTEGER_TYPE
62              || TREE_CODE (type) == REAL_TYPE))
63     type = TREE_TYPE (type);
64
65   return type;
66 }
67 \f
68 /* EXP is a GCC tree representing an address.  See if we can find how
69    strictly the object at that address is aligned.   Return that alignment
70    in bits.  If we don't know anything about the alignment, return 0.  */
71
72 unsigned int
73 known_alignment (tree exp)
74 {
75   unsigned int this_alignment;
76   unsigned int lhs, rhs;
77
78   switch (TREE_CODE (exp))
79     {
80     CASE_CONVERT:
81     case VIEW_CONVERT_EXPR:
82     case NON_LVALUE_EXPR:
83       /* Conversions between pointers and integers don't change the alignment
84          of the underlying object.  */
85       this_alignment = known_alignment (TREE_OPERAND (exp, 0));
86       break;
87
88     case COMPOUND_EXPR:
89       /* The value of a COMPOUND_EXPR is that of it's second operand.  */
90       this_alignment = known_alignment (TREE_OPERAND (exp, 1));
91       break;
92
93     case PLUS_EXPR:
94     case MINUS_EXPR:
95       /* If two address are added, the alignment of the result is the
96          minimum of the two alignments.  */
97       lhs = known_alignment (TREE_OPERAND (exp, 0));
98       rhs = known_alignment (TREE_OPERAND (exp, 1));
99       this_alignment = MIN (lhs, rhs);
100       break;
101
102     case POINTER_PLUS_EXPR:
103       lhs = known_alignment (TREE_OPERAND (exp, 0));
104       rhs = known_alignment (TREE_OPERAND (exp, 1));
105       /* If we don't know the alignment of the offset, we assume that
106          of the base.  */
107       if (rhs == 0)
108         this_alignment = lhs;
109       else
110         this_alignment = MIN (lhs, rhs);
111       break;
112
113     case COND_EXPR:
114       /* If there is a choice between two values, use the smallest one.  */
115       lhs = known_alignment (TREE_OPERAND (exp, 1));
116       rhs = known_alignment (TREE_OPERAND (exp, 2));
117       this_alignment = MIN (lhs, rhs);
118       break;
119
120     case INTEGER_CST:
121       {
122         unsigned HOST_WIDE_INT c = TREE_INT_CST_LOW (exp);
123         /* The first part of this represents the lowest bit in the constant,
124            but it is originally in bytes, not bits.  */
125         this_alignment = MIN (BITS_PER_UNIT * (c & -c), BIGGEST_ALIGNMENT);
126       }
127       break;
128
129     case MULT_EXPR:
130       /* If we know the alignment of just one side, use it.  Otherwise,
131          use the product of the alignments.  */
132       lhs = known_alignment (TREE_OPERAND (exp, 0));
133       rhs = known_alignment (TREE_OPERAND (exp, 1));
134
135       if (lhs == 0)
136         this_alignment = rhs;
137       else if (rhs == 0)
138         this_alignment = lhs;
139       else
140         this_alignment = MIN (lhs * rhs, BIGGEST_ALIGNMENT);
141       break;
142
143     case BIT_AND_EXPR:
144       /* A bit-and expression is as aligned as the maximum alignment of the
145          operands.  We typically get here for a complex lhs and a constant
146          negative power of two on the rhs to force an explicit alignment, so
147          don't bother looking at the lhs.  */
148       this_alignment = known_alignment (TREE_OPERAND (exp, 1));
149       break;
150
151     case ADDR_EXPR:
152       this_alignment = expr_align (TREE_OPERAND (exp, 0));
153       break;
154
155     case CALL_EXPR:
156       {
157         tree t = maybe_inline_call_in_expr (exp);
158         if (t)
159           return known_alignment (t);
160       }
161
162       /* Fall through... */
163
164     default:
165       /* For other pointer expressions, we assume that the pointed-to object
166          is at least as aligned as the pointed-to type.  Beware that we can
167          have a dummy type here (e.g. a Taft Amendment type), for which the
168          alignment is meaningless and should be ignored.  */
169       if (POINTER_TYPE_P (TREE_TYPE (exp))
170           && !TYPE_IS_DUMMY_P (TREE_TYPE (TREE_TYPE (exp))))
171         this_alignment = TYPE_ALIGN (TREE_TYPE (TREE_TYPE (exp)));
172       else
173         this_alignment = 0;
174       break;
175     }
176
177   return this_alignment;
178 }
179 \f
180 /* We have a comparison or assignment operation on two types, T1 and T2, which
181    are either both array types or both record types.  T1 is assumed to be for
182    the left hand side operand, and T2 for the right hand side.  Return the
183    type that both operands should be converted to for the operation, if any.
184    Otherwise return zero.  */
185
186 static tree
187 find_common_type (tree t1, tree t2)
188 {
189   /* ??? As of today, various constructs lead here with types of different
190      sizes even when both constants (e.g. tagged types, packable vs regular
191      component types, padded vs unpadded types, ...).  While some of these
192      would better be handled upstream (types should be made consistent before
193      calling into build_binary_op), some others are really expected and we
194      have to be careful.  */
195
196   /* We must prevent writing more than what the target may hold if this is for
197      an assignment and the case of tagged types is handled in build_binary_op
198      so use the lhs type if it is known to be smaller, or of constant size and
199      the rhs type is not, whatever the modes.  We also force t1 in case of
200      constant size equality to minimize occurrences of view conversions on the
201      lhs of assignments.  */
202   if (TREE_CONSTANT (TYPE_SIZE (t1))
203       && (!TREE_CONSTANT (TYPE_SIZE (t2))
204           || !tree_int_cst_lt (TYPE_SIZE (t2), TYPE_SIZE (t1))))
205     return t1;
206
207   /* Otherwise, if the lhs type is non-BLKmode, use it.  Note that we know
208      that we will not have any alignment problems since, if we did, the
209      non-BLKmode type could not have been used.  */
210   if (TYPE_MODE (t1) != BLKmode)
211     return t1;
212
213   /* If the rhs type is of constant size, use it whatever the modes.  At
214      this point it is known to be smaller, or of constant size and the
215      lhs type is not.  */
216   if (TREE_CONSTANT (TYPE_SIZE (t2)))
217     return t2;
218
219   /* Otherwise, if the rhs type is non-BLKmode, use it.  */
220   if (TYPE_MODE (t2) != BLKmode)
221     return t2;
222
223   /* In this case, both types have variable size and BLKmode.  It's
224      probably best to leave the "type mismatch" because changing it
225      could cause a bad self-referential reference.  */
226   return NULL_TREE;
227 }
228 \f
229 /* Return an expression tree representing an equality comparison of A1 and A2,
230    two objects of type ARRAY_TYPE.  The result should be of type RESULT_TYPE.
231
232    Two arrays are equal in one of two ways: (1) if both have zero length in
233    some dimension (not necessarily the same dimension) or (2) if the lengths
234    in each dimension are equal and the data is equal.  We perform the length
235    tests in as efficient a manner as possible.  */
236
237 static tree
238 compare_arrays (location_t loc, tree result_type, tree a1, tree a2)
239 {
240   tree result = convert (result_type, boolean_true_node);
241   tree a1_is_null = convert (result_type, boolean_false_node);
242   tree a2_is_null = convert (result_type, boolean_false_node);
243   tree t1 = TREE_TYPE (a1);
244   tree t2 = TREE_TYPE (a2);
245   bool a1_side_effects_p = TREE_SIDE_EFFECTS (a1);
246   bool a2_side_effects_p = TREE_SIDE_EFFECTS (a2);
247   bool length_zero_p = false;
248
249   /* If either operand has side-effects, they have to be evaluated only once
250      in spite of the multiple references to the operand in the comparison.  */
251   if (a1_side_effects_p)
252     a1 = gnat_protect_expr (a1);
253
254   if (a2_side_effects_p)
255     a2 = gnat_protect_expr (a2);
256
257   /* Process each dimension separately and compare the lengths.  If any
258      dimension has a length known to be zero, set LENGTH_ZERO_P to true
259      in order to suppress the comparison of the data at the end.  */
260   while (TREE_CODE (t1) == ARRAY_TYPE && TREE_CODE (t2) == ARRAY_TYPE)
261     {
262       tree lb1 = TYPE_MIN_VALUE (TYPE_DOMAIN (t1));
263       tree ub1 = TYPE_MAX_VALUE (TYPE_DOMAIN (t1));
264       tree lb2 = TYPE_MIN_VALUE (TYPE_DOMAIN (t2));
265       tree ub2 = TYPE_MAX_VALUE (TYPE_DOMAIN (t2));
266       tree length1 = size_binop (PLUS_EXPR, size_binop (MINUS_EXPR, ub1, lb1),
267                                  size_one_node);
268       tree length2 = size_binop (PLUS_EXPR, size_binop (MINUS_EXPR, ub2, lb2),
269                                  size_one_node);
270       tree comparison, this_a1_is_null, this_a2_is_null;
271
272       /* If the length of the first array is a constant, swap our operands
273          unless the length of the second array is the constant zero.  */
274       if (TREE_CODE (length1) == INTEGER_CST && !integer_zerop (length2))
275         {
276           tree tem;
277           bool btem;
278
279           tem = a1, a1 = a2, a2 = tem;
280           tem = t1, t1 = t2, t2 = tem;
281           tem = lb1, lb1 = lb2, lb2 = tem;
282           tem = ub1, ub1 = ub2, ub2 = tem;
283           tem = length1, length1 = length2, length2 = tem;
284           tem = a1_is_null, a1_is_null = a2_is_null, a2_is_null = tem;
285           btem = a1_side_effects_p, a1_side_effects_p = a2_side_effects_p,
286           a2_side_effects_p = btem;
287         }
288
289       /* If the length of the second array is the constant zero, we can just
290          use the original stored bounds for the first array and see whether
291          last < first holds.  */
292       if (integer_zerop (length2))
293         {
294           length_zero_p = true;
295
296           ub1 = TYPE_MAX_VALUE (TYPE_INDEX_TYPE (TYPE_DOMAIN (t1)));
297           lb1 = TYPE_MIN_VALUE (TYPE_INDEX_TYPE (TYPE_DOMAIN (t1)));
298
299           comparison = fold_build2_loc (loc, LT_EXPR, result_type, ub1, lb1);
300           comparison = SUBSTITUTE_PLACEHOLDER_IN_EXPR (comparison, a1);
301           if (EXPR_P (comparison))
302             SET_EXPR_LOCATION (comparison, loc);
303
304           this_a1_is_null = comparison;
305           this_a2_is_null = convert (result_type, boolean_true_node);
306         }
307
308       /* Otherwise, if the length is some other constant value, we know that
309          this dimension in the second array cannot be superflat, so we can
310          just use its length computed from the actual stored bounds.  */
311       else if (TREE_CODE (length2) == INTEGER_CST)
312         {
313           tree bt;
314
315           ub1 = TYPE_MAX_VALUE (TYPE_INDEX_TYPE (TYPE_DOMAIN (t1)));
316           lb1 = TYPE_MIN_VALUE (TYPE_INDEX_TYPE (TYPE_DOMAIN (t1)));
317           /* Note that we know that UB2 and LB2 are constant and hence
318              cannot contain a PLACEHOLDER_EXPR.  */
319           ub2 = TYPE_MAX_VALUE (TYPE_INDEX_TYPE (TYPE_DOMAIN (t2)));
320           lb2 = TYPE_MIN_VALUE (TYPE_INDEX_TYPE (TYPE_DOMAIN (t2)));
321           bt = get_base_type (TREE_TYPE (ub1));
322
323           comparison
324             = fold_build2_loc (loc, EQ_EXPR, result_type,
325                                build_binary_op (MINUS_EXPR, bt, ub1, lb1),
326                                build_binary_op (MINUS_EXPR, bt, ub2, lb2));
327           comparison = SUBSTITUTE_PLACEHOLDER_IN_EXPR (comparison, a1);
328           if (EXPR_P (comparison))
329             SET_EXPR_LOCATION (comparison, loc);
330
331           this_a1_is_null
332             = fold_build2_loc (loc, LT_EXPR, result_type, ub1, lb1);
333
334           this_a2_is_null = convert (result_type, boolean_false_node);
335         }
336
337       /* Otherwise, compare the computed lengths.  */
338       else
339         {
340           length1 = SUBSTITUTE_PLACEHOLDER_IN_EXPR (length1, a1);
341           length2 = SUBSTITUTE_PLACEHOLDER_IN_EXPR (length2, a2);
342
343           comparison
344             = fold_build2_loc (loc, EQ_EXPR, result_type, length1, length2);
345
346           /* If the length expression is of the form (cond ? val : 0), assume
347              that cond is equivalent to (length != 0).  That's guaranteed by
348              construction of the array types in gnat_to_gnu_entity.  */
349           if (TREE_CODE (length1) == COND_EXPR
350               && integer_zerop (TREE_OPERAND (length1, 2)))
351             this_a1_is_null
352               = invert_truthvalue_loc (loc, TREE_OPERAND (length1, 0));
353           else
354             this_a1_is_null = fold_build2_loc (loc, EQ_EXPR, result_type,
355                                                length1, size_zero_node);
356
357           /* Likewise for the second array.  */
358           if (TREE_CODE (length2) == COND_EXPR
359               && integer_zerop (TREE_OPERAND (length2, 2)))
360             this_a2_is_null
361               = invert_truthvalue_loc (loc, TREE_OPERAND (length2, 0));
362           else
363             this_a2_is_null = fold_build2_loc (loc, EQ_EXPR, result_type,
364                                                length2, size_zero_node);
365         }
366
367       /* Append expressions for this dimension to the final expressions.  */
368       result = build_binary_op (TRUTH_ANDIF_EXPR, result_type,
369                                 result, comparison);
370
371       a1_is_null = build_binary_op (TRUTH_ORIF_EXPR, result_type,
372                                     this_a1_is_null, a1_is_null);
373
374       a2_is_null = build_binary_op (TRUTH_ORIF_EXPR, result_type,
375                                     this_a2_is_null, a2_is_null);
376
377       t1 = TREE_TYPE (t1);
378       t2 = TREE_TYPE (t2);
379     }
380
381   /* Unless the length of some dimension is known to be zero, compare the
382      data in the array.  */
383   if (!length_zero_p)
384     {
385       tree type = find_common_type (TREE_TYPE (a1), TREE_TYPE (a2));
386       tree comparison;
387
388       if (type)
389         {
390           a1 = convert (type, a1),
391           a2 = convert (type, a2);
392         }
393
394       comparison = fold_build2_loc (loc, EQ_EXPR, result_type, a1, a2);
395
396       result
397         = build_binary_op (TRUTH_ANDIF_EXPR, result_type, result, comparison);
398     }
399
400   /* The result is also true if both sizes are zero.  */
401   result = build_binary_op (TRUTH_ORIF_EXPR, result_type,
402                             build_binary_op (TRUTH_ANDIF_EXPR, result_type,
403                                              a1_is_null, a2_is_null),
404                             result);
405
406   /* If either operand has side-effects, they have to be evaluated before
407      starting the comparison above since the place they would be otherwise
408      evaluated could be wrong.  */
409   if (a1_side_effects_p)
410     result = build2 (COMPOUND_EXPR, result_type, a1, result);
411
412   if (a2_side_effects_p)
413     result = build2 (COMPOUND_EXPR, result_type, a2, result);
414
415   return result;
416 }
417 \f
418 /* Compute the result of applying OP_CODE to LHS and RHS, where both are of
419    type TYPE.  We know that TYPE is a modular type with a nonbinary
420    modulus.  */
421
422 static tree
423 nonbinary_modular_operation (enum tree_code op_code, tree type, tree lhs,
424                              tree rhs)
425 {
426   tree modulus = TYPE_MODULUS (type);
427   unsigned int needed_precision = tree_floor_log2 (modulus) + 1;
428   unsigned int precision;
429   bool unsignedp = true;
430   tree op_type = type;
431   tree result;
432
433   /* If this is an addition of a constant, convert it to a subtraction
434      of a constant since we can do that faster.  */
435   if (op_code == PLUS_EXPR && TREE_CODE (rhs) == INTEGER_CST)
436     {
437       rhs = fold_build2 (MINUS_EXPR, type, modulus, rhs);
438       op_code = MINUS_EXPR;
439     }
440
441   /* For the logical operations, we only need PRECISION bits.  For
442      addition and subtraction, we need one more and for multiplication we
443      need twice as many.  But we never want to make a size smaller than
444      our size. */
445   if (op_code == PLUS_EXPR || op_code == MINUS_EXPR)
446     needed_precision += 1;
447   else if (op_code == MULT_EXPR)
448     needed_precision *= 2;
449
450   precision = MAX (needed_precision, TYPE_PRECISION (op_type));
451
452   /* Unsigned will do for everything but subtraction.  */
453   if (op_code == MINUS_EXPR)
454     unsignedp = false;
455
456   /* If our type is the wrong signedness or isn't wide enough, make a new
457      type and convert both our operands to it.  */
458   if (TYPE_PRECISION (op_type) < precision
459       || TYPE_UNSIGNED (op_type) != unsignedp)
460     {
461       /* Copy the node so we ensure it can be modified to make it modular.  */
462       op_type = copy_node (gnat_type_for_size (precision, unsignedp));
463       modulus = convert (op_type, modulus);
464       SET_TYPE_MODULUS (op_type, modulus);
465       TYPE_MODULAR_P (op_type) = 1;
466       lhs = convert (op_type, lhs);
467       rhs = convert (op_type, rhs);
468     }
469
470   /* Do the operation, then we'll fix it up.  */
471   result = fold_build2 (op_code, op_type, lhs, rhs);
472
473   /* For multiplication, we have no choice but to do a full modulus
474      operation.  However, we want to do this in the narrowest
475      possible size.  */
476   if (op_code == MULT_EXPR)
477     {
478       tree div_type = copy_node (gnat_type_for_size (needed_precision, 1));
479       modulus = convert (div_type, modulus);
480       SET_TYPE_MODULUS (div_type, modulus);
481       TYPE_MODULAR_P (div_type) = 1;
482       result = convert (op_type,
483                         fold_build2 (TRUNC_MOD_EXPR, div_type,
484                                      convert (div_type, result), modulus));
485     }
486
487   /* For subtraction, add the modulus back if we are negative.  */
488   else if (op_code == MINUS_EXPR)
489     {
490       result = gnat_protect_expr (result);
491       result = fold_build3 (COND_EXPR, op_type,
492                             fold_build2 (LT_EXPR, boolean_type_node, result,
493                                          convert (op_type, integer_zero_node)),
494                             fold_build2 (PLUS_EXPR, op_type, result, modulus),
495                             result);
496     }
497
498   /* For the other operations, subtract the modulus if we are >= it.  */
499   else
500     {
501       result = gnat_protect_expr (result);
502       result = fold_build3 (COND_EXPR, op_type,
503                             fold_build2 (GE_EXPR, boolean_type_node,
504                                          result, modulus),
505                             fold_build2 (MINUS_EXPR, op_type,
506                                          result, modulus),
507                             result);
508     }
509
510   return convert (type, result);
511 }
512 \f
513 /* Make a binary operation of kind OP_CODE.  RESULT_TYPE is the type
514    desired for the result.  Usually the operation is to be performed
515    in that type.  For MODIFY_EXPR and ARRAY_REF, RESULT_TYPE may be 0
516    in which case the type to be used will be derived from the operands.
517
518    This function is very much unlike the ones for C and C++ since we
519    have already done any type conversion and matching required.  All we
520    have to do here is validate the work done by SEM and handle subtypes.  */
521
522 tree
523 build_binary_op (enum tree_code op_code, tree result_type,
524                  tree left_operand, tree right_operand)
525 {
526   tree left_type  = TREE_TYPE (left_operand);
527   tree right_type = TREE_TYPE (right_operand);
528   tree left_base_type = get_base_type (left_type);
529   tree right_base_type = get_base_type (right_type);
530   tree operation_type = result_type;
531   tree best_type = NULL_TREE;
532   tree modulus, result;
533   bool has_side_effects = false;
534
535   if (operation_type
536       && TREE_CODE (operation_type) == RECORD_TYPE
537       && TYPE_JUSTIFIED_MODULAR_P (operation_type))
538     operation_type = TREE_TYPE (TYPE_FIELDS (operation_type));
539
540   if (operation_type
541       && !AGGREGATE_TYPE_P (operation_type)
542       && TYPE_EXTRA_SUBTYPE_P (operation_type))
543     operation_type = get_base_type (operation_type);
544
545   modulus = (operation_type
546              && TREE_CODE (operation_type) == INTEGER_TYPE
547              && TYPE_MODULAR_P (operation_type)
548              ? TYPE_MODULUS (operation_type) : NULL_TREE);
549
550   switch (op_code)
551     {
552     case INIT_EXPR:
553     case MODIFY_EXPR:
554       /* If there were integral or pointer conversions on the LHS, remove
555          them; we'll be putting them back below if needed.  Likewise for
556          conversions between array and record types, except for justified
557          modular types.  But don't do this if the right operand is not
558          BLKmode (for packed arrays) unless we are not changing the mode.  */
559       while ((CONVERT_EXPR_P (left_operand)
560               || TREE_CODE (left_operand) == VIEW_CONVERT_EXPR)
561              && (((INTEGRAL_TYPE_P (left_type)
562                    || POINTER_TYPE_P (left_type))
563                   && (INTEGRAL_TYPE_P (TREE_TYPE
564                                        (TREE_OPERAND (left_operand, 0)))
565                       || POINTER_TYPE_P (TREE_TYPE
566                                          (TREE_OPERAND (left_operand, 0)))))
567                  || (((TREE_CODE (left_type) == RECORD_TYPE
568                        && !TYPE_JUSTIFIED_MODULAR_P (left_type))
569                       || TREE_CODE (left_type) == ARRAY_TYPE)
570                      && ((TREE_CODE (TREE_TYPE
571                                      (TREE_OPERAND (left_operand, 0)))
572                           == RECORD_TYPE)
573                          || (TREE_CODE (TREE_TYPE
574                                         (TREE_OPERAND (left_operand, 0)))
575                              == ARRAY_TYPE))
576                      && (TYPE_MODE (right_type) == BLKmode
577                          || (TYPE_MODE (left_type)
578                              == TYPE_MODE (TREE_TYPE
579                                            (TREE_OPERAND
580                                             (left_operand, 0))))))))
581         {
582           left_operand = TREE_OPERAND (left_operand, 0);
583           left_type = TREE_TYPE (left_operand);
584         }
585
586       /* If a class-wide type may be involved, force use of the RHS type.  */
587       if ((TREE_CODE (right_type) == RECORD_TYPE
588            || TREE_CODE (right_type) == UNION_TYPE)
589           && TYPE_ALIGN_OK (right_type))
590         operation_type = right_type;
591
592       /* If we are copying between padded objects with compatible types, use
593          the padded view of the objects, this is very likely more efficient.
594          Likewise for a padded object that is assigned a constructor, if we
595          can convert the constructor to the inner type, to avoid putting a
596          VIEW_CONVERT_EXPR on the LHS.  But don't do so if we wouldn't have
597          actually copied anything.  */
598       else if (TYPE_IS_PADDING_P (left_type)
599                && TREE_CONSTANT (TYPE_SIZE (left_type))
600                && ((TREE_CODE (right_operand) == COMPONENT_REF
601                     && TYPE_IS_PADDING_P
602                        (TREE_TYPE (TREE_OPERAND (right_operand, 0)))
603                     && gnat_types_compatible_p
604                        (left_type,
605                         TREE_TYPE (TREE_OPERAND (right_operand, 0))))
606                    || (TREE_CODE (right_operand) == CONSTRUCTOR
607                        && !CONTAINS_PLACEHOLDER_P
608                            (DECL_SIZE (TYPE_FIELDS (left_type)))))
609                && !integer_zerop (TYPE_SIZE (right_type)))
610         operation_type = left_type;
611
612       /* Find the best type to use for copying between aggregate types.  */
613       else if (((TREE_CODE (left_type) == ARRAY_TYPE
614                  && TREE_CODE (right_type) == ARRAY_TYPE)
615                 || (TREE_CODE (left_type) == RECORD_TYPE
616                     && TREE_CODE (right_type) == RECORD_TYPE))
617                && (best_type = find_common_type (left_type, right_type)))
618         operation_type = best_type;
619
620       /* Otherwise use the LHS type.  */
621       else if (!operation_type)
622         operation_type = left_type;
623
624       /* Ensure everything on the LHS is valid.  If we have a field reference,
625          strip anything that get_inner_reference can handle.  Then remove any
626          conversions between types having the same code and mode.  And mark
627          VIEW_CONVERT_EXPRs with TREE_ADDRESSABLE.  When done, we must have
628          either an INDIRECT_REF, a NULL_EXPR or a DECL node.  */
629       result = left_operand;
630       while (true)
631         {
632           tree restype = TREE_TYPE (result);
633
634           if (TREE_CODE (result) == COMPONENT_REF
635               || TREE_CODE (result) == ARRAY_REF
636               || TREE_CODE (result) == ARRAY_RANGE_REF)
637             while (handled_component_p (result))
638               result = TREE_OPERAND (result, 0);
639           else if (TREE_CODE (result) == REALPART_EXPR
640                    || TREE_CODE (result) == IMAGPART_EXPR
641                    || (CONVERT_EXPR_P (result)
642                        && (((TREE_CODE (restype)
643                              == TREE_CODE (TREE_TYPE
644                                            (TREE_OPERAND (result, 0))))
645                              && (TYPE_MODE (TREE_TYPE
646                                             (TREE_OPERAND (result, 0)))
647                                  == TYPE_MODE (restype)))
648                            || TYPE_ALIGN_OK (restype))))
649             result = TREE_OPERAND (result, 0);
650           else if (TREE_CODE (result) == VIEW_CONVERT_EXPR)
651             {
652               TREE_ADDRESSABLE (result) = 1;
653               result = TREE_OPERAND (result, 0);
654             }
655           else
656             break;
657         }
658
659       gcc_assert (TREE_CODE (result) == INDIRECT_REF
660                   || TREE_CODE (result) == NULL_EXPR
661                   || DECL_P (result));
662
663       /* Convert the right operand to the operation type unless it is
664          either already of the correct type or if the type involves a
665          placeholder, since the RHS may not have the same record type.  */
666       if (operation_type != right_type
667           && !CONTAINS_PLACEHOLDER_P (TYPE_SIZE (operation_type)))
668         {
669           right_operand = convert (operation_type, right_operand);
670           right_type = operation_type;
671         }
672
673       /* If the left operand is not of the same type as the operation
674          type, wrap it up in a VIEW_CONVERT_EXPR.  */
675       if (left_type != operation_type)
676         left_operand = unchecked_convert (operation_type, left_operand, false);
677
678       has_side_effects = true;
679       modulus = NULL_TREE;
680       break;
681
682     case ARRAY_REF:
683       if (!operation_type)
684         operation_type = TREE_TYPE (left_type);
685
686       /* ... fall through ... */
687
688     case ARRAY_RANGE_REF:
689       /* First look through conversion between type variants.  Note that
690          this changes neither the operation type nor the type domain.  */
691       if (TREE_CODE (left_operand) == VIEW_CONVERT_EXPR
692           && TYPE_MAIN_VARIANT (TREE_TYPE (TREE_OPERAND (left_operand, 0)))
693              == TYPE_MAIN_VARIANT (left_type))
694         {
695           left_operand = TREE_OPERAND (left_operand, 0);
696           left_type = TREE_TYPE (left_operand);
697         }
698
699       /* For a range, make sure the element type is consistent.  */
700       if (op_code == ARRAY_RANGE_REF
701           && TREE_TYPE (operation_type) != TREE_TYPE (left_type))
702         operation_type = build_array_type (TREE_TYPE (left_type),
703                                            TYPE_DOMAIN (operation_type));
704
705       /* Then convert the right operand to its base type.  This will prevent
706          unneeded sign conversions when sizetype is wider than integer.  */
707       right_operand = convert (right_base_type, right_operand);
708       right_operand = convert (sizetype, right_operand);
709
710       if (!TREE_CONSTANT (right_operand)
711           || !TREE_CONSTANT (TYPE_MIN_VALUE (right_type)))
712         gnat_mark_addressable (left_operand);
713
714       modulus = NULL_TREE;
715       break;
716
717     case TRUTH_ANDIF_EXPR:
718     case TRUTH_ORIF_EXPR:
719     case TRUTH_AND_EXPR:
720     case TRUTH_OR_EXPR:
721     case TRUTH_XOR_EXPR:
722 #ifdef ENABLE_CHECKING
723       gcc_assert (TREE_CODE (get_base_type (result_type)) == BOOLEAN_TYPE);
724 #endif
725       operation_type = left_base_type;
726       left_operand = convert (operation_type, left_operand);
727       right_operand = convert (operation_type, right_operand);
728       break;
729
730     case GE_EXPR:
731     case LE_EXPR:
732     case GT_EXPR:
733     case LT_EXPR:
734     case EQ_EXPR:
735     case NE_EXPR:
736 #ifdef ENABLE_CHECKING
737       gcc_assert (TREE_CODE (get_base_type (result_type)) == BOOLEAN_TYPE);
738 #endif
739       /* If either operand is a NULL_EXPR, just return a new one.  */
740       if (TREE_CODE (left_operand) == NULL_EXPR)
741         return build2 (op_code, result_type,
742                        build1 (NULL_EXPR, integer_type_node,
743                                TREE_OPERAND (left_operand, 0)),
744                        integer_zero_node);
745
746       else if (TREE_CODE (right_operand) == NULL_EXPR)
747         return build2 (op_code, result_type,
748                        build1 (NULL_EXPR, integer_type_node,
749                                TREE_OPERAND (right_operand, 0)),
750                        integer_zero_node);
751
752       /* If either object is a justified modular types, get the
753          fields from within.  */
754       if (TREE_CODE (left_type) == RECORD_TYPE
755           && TYPE_JUSTIFIED_MODULAR_P (left_type))
756         {
757           left_operand = convert (TREE_TYPE (TYPE_FIELDS (left_type)),
758                                   left_operand);
759           left_type = TREE_TYPE (left_operand);
760           left_base_type = get_base_type (left_type);
761         }
762
763       if (TREE_CODE (right_type) == RECORD_TYPE
764           && TYPE_JUSTIFIED_MODULAR_P (right_type))
765         {
766           right_operand = convert (TREE_TYPE (TYPE_FIELDS (right_type)),
767                                   right_operand);
768           right_type = TREE_TYPE (right_operand);
769           right_base_type = get_base_type (right_type);
770         }
771
772       /* If both objects are arrays, compare them specially.  */
773       if ((TREE_CODE (left_type) == ARRAY_TYPE
774            || (TREE_CODE (left_type) == INTEGER_TYPE
775                && TYPE_HAS_ACTUAL_BOUNDS_P (left_type)))
776           && (TREE_CODE (right_type) == ARRAY_TYPE
777               || (TREE_CODE (right_type) == INTEGER_TYPE
778                   && TYPE_HAS_ACTUAL_BOUNDS_P (right_type))))
779         {
780           result = compare_arrays (input_location,
781                                    result_type, left_operand, right_operand);
782           if (op_code == NE_EXPR)
783             result = invert_truthvalue_loc (EXPR_LOCATION (result), result);
784           else
785             gcc_assert (op_code == EQ_EXPR);
786
787           return result;
788         }
789
790       /* Otherwise, the base types must be the same, unless they are both fat
791          pointer types or record types.  In the latter case, use the best type
792          and convert both operands to that type.  */
793       if (left_base_type != right_base_type)
794         {
795           if (TYPE_IS_FAT_POINTER_P (left_base_type)
796               && TYPE_IS_FAT_POINTER_P (right_base_type))
797             {
798               gcc_assert (TYPE_MAIN_VARIANT (left_base_type)
799                           == TYPE_MAIN_VARIANT (right_base_type));
800               best_type = left_base_type;
801             }
802
803           else if (TREE_CODE (left_base_type) == RECORD_TYPE
804                    && TREE_CODE (right_base_type) == RECORD_TYPE)
805             {
806               /* The only way this is permitted is if both types have the same
807                  name.  In that case, one of them must not be self-referential.
808                  Use it as the best type.  Even better with a fixed size.  */
809               gcc_assert (TYPE_NAME (left_base_type)
810                           && TYPE_NAME (left_base_type)
811                              == TYPE_NAME (right_base_type));
812
813               if (TREE_CONSTANT (TYPE_SIZE (left_base_type)))
814                 best_type = left_base_type;
815               else if (TREE_CONSTANT (TYPE_SIZE (right_base_type)))
816                 best_type = right_base_type;
817               else if (!CONTAINS_PLACEHOLDER_P (TYPE_SIZE (left_base_type)))
818                 best_type = left_base_type;
819               else if (!CONTAINS_PLACEHOLDER_P (TYPE_SIZE (right_base_type)))
820                 best_type = right_base_type;
821               else
822                 gcc_unreachable ();
823             }
824
825           else
826             gcc_unreachable ();
827
828           left_operand = convert (best_type, left_operand);
829           right_operand = convert (best_type, right_operand);
830         }
831       else
832         {
833           left_operand = convert (left_base_type, left_operand);
834           right_operand = convert (right_base_type, right_operand);
835         }
836
837       /* If we are comparing a fat pointer against zero, we just need to
838          compare the data pointer.  */
839       if (TYPE_IS_FAT_POINTER_P (left_base_type)
840           && TREE_CODE (right_operand) == CONSTRUCTOR
841           && integer_zerop (VEC_index (constructor_elt,
842                                        CONSTRUCTOR_ELTS (right_operand),
843                                        0)->value))
844         {
845           left_operand
846             = build_component_ref (left_operand, NULL_TREE,
847                                    TYPE_FIELDS (left_base_type), false);
848           right_operand
849             = convert (TREE_TYPE (left_operand), integer_zero_node);
850         }
851
852       modulus = NULL_TREE;
853       break;
854
855     case LSHIFT_EXPR:
856     case RSHIFT_EXPR:
857     case LROTATE_EXPR:
858     case RROTATE_EXPR:
859        /* The RHS of a shift can be any type.  Also, ignore any modulus
860          (we used to abort, but this is needed for unchecked conversion
861          to modular types).  Otherwise, processing is the same as normal.  */
862       gcc_assert (operation_type == left_base_type);
863       modulus = NULL_TREE;
864       left_operand = convert (operation_type, left_operand);
865       break;
866
867     case BIT_AND_EXPR:
868     case BIT_IOR_EXPR:
869     case BIT_XOR_EXPR:
870       /* For binary modulus, if the inputs are in range, so are the
871          outputs.  */
872       if (modulus && integer_pow2p (modulus))
873         modulus = NULL_TREE;
874       goto common;
875
876     case COMPLEX_EXPR:
877       gcc_assert (TREE_TYPE (result_type) == left_base_type
878                   && TREE_TYPE (result_type) == right_base_type);
879       left_operand = convert (left_base_type, left_operand);
880       right_operand = convert (right_base_type, right_operand);
881       break;
882
883     case TRUNC_DIV_EXPR:   case TRUNC_MOD_EXPR:
884     case CEIL_DIV_EXPR:    case CEIL_MOD_EXPR:
885     case FLOOR_DIV_EXPR:   case FLOOR_MOD_EXPR:
886     case ROUND_DIV_EXPR:   case ROUND_MOD_EXPR:
887       /* These always produce results lower than either operand.  */
888       modulus = NULL_TREE;
889       goto common;
890
891     case POINTER_PLUS_EXPR:
892       gcc_assert (operation_type == left_base_type
893                   && sizetype == right_base_type);
894       left_operand = convert (operation_type, left_operand);
895       right_operand = convert (sizetype, right_operand);
896       break;
897
898     case PLUS_NOMOD_EXPR:
899     case MINUS_NOMOD_EXPR:
900       if (op_code == PLUS_NOMOD_EXPR)
901         op_code = PLUS_EXPR;
902       else
903         op_code = MINUS_EXPR;
904       modulus = NULL_TREE;
905
906       /* ... fall through ... */
907
908     case PLUS_EXPR:
909     case MINUS_EXPR:
910       /* Avoid doing arithmetics in ENUMERAL_TYPE or BOOLEAN_TYPE like the
911          other compilers.  Contrary to C, Ada doesn't allow arithmetics in
912          these types but can generate addition/subtraction for Succ/Pred.  */
913       if (operation_type
914           && (TREE_CODE (operation_type) == ENUMERAL_TYPE
915               || TREE_CODE (operation_type) == BOOLEAN_TYPE))
916         operation_type = left_base_type = right_base_type
917           = gnat_type_for_mode (TYPE_MODE (operation_type),
918                                 TYPE_UNSIGNED (operation_type));
919
920       /* ... fall through ... */
921
922     default:
923     common:
924       /* The result type should be the same as the base types of the
925          both operands (and they should be the same).  Convert
926          everything to the result type.  */
927
928       gcc_assert (operation_type == left_base_type
929                   && left_base_type == right_base_type);
930       left_operand = convert (operation_type, left_operand);
931       right_operand = convert (operation_type, right_operand);
932     }
933
934   if (modulus && !integer_pow2p (modulus))
935     {
936       result = nonbinary_modular_operation (op_code, operation_type,
937                                             left_operand, right_operand);
938       modulus = NULL_TREE;
939     }
940   /* If either operand is a NULL_EXPR, just return a new one.  */
941   else if (TREE_CODE (left_operand) == NULL_EXPR)
942     return build1 (NULL_EXPR, operation_type, TREE_OPERAND (left_operand, 0));
943   else if (TREE_CODE (right_operand) == NULL_EXPR)
944     return build1 (NULL_EXPR, operation_type, TREE_OPERAND (right_operand, 0));
945   else if (op_code == ARRAY_REF || op_code == ARRAY_RANGE_REF)
946     result = fold (build4 (op_code, operation_type, left_operand,
947                            right_operand, NULL_TREE, NULL_TREE));
948   else
949     result
950       = fold_build2 (op_code, operation_type, left_operand, right_operand);
951
952   if (TREE_CONSTANT (result))
953     ;
954   else if (op_code == ARRAY_REF || op_code == ARRAY_RANGE_REF)
955     {
956       TREE_THIS_NOTRAP (result) = 1;
957       if (TYPE_VOLATILE (operation_type))
958         TREE_THIS_VOLATILE (result) = 1;
959     }
960   else
961     TREE_CONSTANT (result)
962       |= (TREE_CONSTANT (left_operand) && TREE_CONSTANT (right_operand));
963
964   TREE_SIDE_EFFECTS (result) |= has_side_effects;
965
966   /* If we are working with modular types, perform the MOD operation
967      if something above hasn't eliminated the need for it.  */
968   if (modulus)
969     result = fold_build2 (FLOOR_MOD_EXPR, operation_type, result,
970                           convert (operation_type, modulus));
971
972   if (result_type && result_type != operation_type)
973     result = convert (result_type, result);
974
975   return result;
976 }
977 \f
978 /* Similar, but for unary operations.  */
979
980 tree
981 build_unary_op (enum tree_code op_code, tree result_type, tree operand)
982 {
983   tree type = TREE_TYPE (operand);
984   tree base_type = get_base_type (type);
985   tree operation_type = result_type;
986   tree result;
987   bool side_effects = false;
988
989   if (operation_type
990       && TREE_CODE (operation_type) == RECORD_TYPE
991       && TYPE_JUSTIFIED_MODULAR_P (operation_type))
992     operation_type = TREE_TYPE (TYPE_FIELDS (operation_type));
993
994   if (operation_type
995       && !AGGREGATE_TYPE_P (operation_type)
996       && TYPE_EXTRA_SUBTYPE_P (operation_type))
997     operation_type = get_base_type (operation_type);
998
999   switch (op_code)
1000     {
1001     case REALPART_EXPR:
1002     case IMAGPART_EXPR:
1003       if (!operation_type)
1004         result_type = operation_type = TREE_TYPE (type);
1005       else
1006         gcc_assert (result_type == TREE_TYPE (type));
1007
1008       result = fold_build1 (op_code, operation_type, operand);
1009       break;
1010
1011     case TRUTH_NOT_EXPR:
1012 #ifdef ENABLE_CHECKING
1013       gcc_assert (TREE_CODE (get_base_type (result_type)) == BOOLEAN_TYPE);
1014 #endif
1015       result = invert_truthvalue_loc (EXPR_LOCATION (operand), operand);
1016       /* When not optimizing, fold the result as invert_truthvalue_loc
1017          doesn't fold the result of comparisons.  This is intended to undo
1018          the trick used for boolean rvalues in gnat_to_gnu.  */
1019       if (!optimize)
1020         result = fold (result);
1021       break;
1022
1023     case ATTR_ADDR_EXPR:
1024     case ADDR_EXPR:
1025       switch (TREE_CODE (operand))
1026         {
1027         case INDIRECT_REF:
1028         case UNCONSTRAINED_ARRAY_REF:
1029           result = TREE_OPERAND (operand, 0);
1030
1031           /* Make sure the type here is a pointer, not a reference.
1032              GCC wants pointer types for function addresses.  */
1033           if (!result_type)
1034             result_type = build_pointer_type (type);
1035
1036           /* If the underlying object can alias everything, propagate the
1037              property since we are effectively retrieving the object.  */
1038           if (POINTER_TYPE_P (TREE_TYPE (result))
1039               && TYPE_REF_CAN_ALIAS_ALL (TREE_TYPE (result)))
1040             {
1041               if (TREE_CODE (result_type) == POINTER_TYPE
1042                   && !TYPE_REF_CAN_ALIAS_ALL (result_type))
1043                 result_type
1044                   = build_pointer_type_for_mode (TREE_TYPE (result_type),
1045                                                  TYPE_MODE (result_type),
1046                                                  true);
1047               else if (TREE_CODE (result_type) == REFERENCE_TYPE
1048                        && !TYPE_REF_CAN_ALIAS_ALL (result_type))
1049                 result_type
1050                   = build_reference_type_for_mode (TREE_TYPE (result_type),
1051                                                    TYPE_MODE (result_type),
1052                                                    true);
1053             }
1054           break;
1055
1056         case NULL_EXPR:
1057           result = operand;
1058           TREE_TYPE (result) = type = build_pointer_type (type);
1059           break;
1060
1061         case COMPOUND_EXPR:
1062           /* Fold a compound expression if it has unconstrained array type
1063              since the middle-end cannot handle it.  But we don't it in the
1064              general case because it may introduce aliasing issues if the
1065              first operand is an indirect assignment and the second operand
1066              the corresponding address, e.g. for an allocator.  */
1067           if (TREE_CODE (type) == UNCONSTRAINED_ARRAY_TYPE)
1068             {
1069               result = build_unary_op (ADDR_EXPR, result_type,
1070                                        TREE_OPERAND (operand, 1));
1071               result = build2 (COMPOUND_EXPR, TREE_TYPE (result),
1072                                TREE_OPERAND (operand, 0), result);
1073               break;
1074             }
1075           goto common;
1076
1077         case ARRAY_REF:
1078         case ARRAY_RANGE_REF:
1079         case COMPONENT_REF:
1080         case BIT_FIELD_REF:
1081             /* If this is for 'Address, find the address of the prefix and add
1082                the offset to the field.  Otherwise, do this the normal way.  */
1083           if (op_code == ATTR_ADDR_EXPR)
1084             {
1085               HOST_WIDE_INT bitsize;
1086               HOST_WIDE_INT bitpos;
1087               tree offset, inner;
1088               enum machine_mode mode;
1089               int unsignedp, volatilep;
1090
1091               inner = get_inner_reference (operand, &bitsize, &bitpos, &offset,
1092                                            &mode, &unsignedp, &volatilep,
1093                                            false);
1094
1095               /* If INNER is a padding type whose field has a self-referential
1096                  size, convert to that inner type.  We know the offset is zero
1097                  and we need to have that type visible.  */
1098               if (TYPE_IS_PADDING_P (TREE_TYPE (inner))
1099                   && CONTAINS_PLACEHOLDER_P
1100                      (TYPE_SIZE (TREE_TYPE (TYPE_FIELDS
1101                                             (TREE_TYPE (inner))))))
1102                 inner = convert (TREE_TYPE (TYPE_FIELDS (TREE_TYPE (inner))),
1103                                  inner);
1104
1105               /* Compute the offset as a byte offset from INNER.  */
1106               if (!offset)
1107                 offset = size_zero_node;
1108
1109               offset = size_binop (PLUS_EXPR, offset,
1110                                    size_int (bitpos / BITS_PER_UNIT));
1111
1112               /* Take the address of INNER, convert the offset to void *, and
1113                  add then.  It will later be converted to the desired result
1114                  type, if any.  */
1115               inner = build_unary_op (ADDR_EXPR, NULL_TREE, inner);
1116               inner = convert (ptr_void_type_node, inner);
1117               result = build_binary_op (POINTER_PLUS_EXPR, ptr_void_type_node,
1118                                         inner, offset);
1119               result = convert (build_pointer_type (TREE_TYPE (operand)),
1120                                 result);
1121               break;
1122             }
1123           goto common;
1124
1125         case CONSTRUCTOR:
1126           /* If this is just a constructor for a padded record, we can
1127              just take the address of the single field and convert it to
1128              a pointer to our type.  */
1129           if (TYPE_IS_PADDING_P (type))
1130             {
1131               result = VEC_index (constructor_elt,
1132                                   CONSTRUCTOR_ELTS (operand),
1133                                   0)->value;
1134               result = convert (build_pointer_type (TREE_TYPE (operand)),
1135                                 build_unary_op (ADDR_EXPR, NULL_TREE, result));
1136               break;
1137             }
1138
1139           goto common;
1140
1141         case NOP_EXPR:
1142           if (AGGREGATE_TYPE_P (type)
1143               && AGGREGATE_TYPE_P (TREE_TYPE (TREE_OPERAND (operand, 0))))
1144             return build_unary_op (ADDR_EXPR, result_type,
1145                                    TREE_OPERAND (operand, 0));
1146
1147           /* ... fallthru ... */
1148
1149         case VIEW_CONVERT_EXPR:
1150           /* If this just a variant conversion or if the conversion doesn't
1151              change the mode, get the result type from this type and go down.
1152              This is needed for conversions of CONST_DECLs, to eventually get
1153              to the address of their CORRESPONDING_VARs.  */
1154           if ((TYPE_MAIN_VARIANT (type)
1155                == TYPE_MAIN_VARIANT (TREE_TYPE (TREE_OPERAND (operand, 0))))
1156               || (TYPE_MODE (type) != BLKmode
1157                   && (TYPE_MODE (type)
1158                       == TYPE_MODE (TREE_TYPE (TREE_OPERAND (operand, 0))))))
1159             return build_unary_op (ADDR_EXPR,
1160                                    (result_type ? result_type
1161                                     : build_pointer_type (type)),
1162                                    TREE_OPERAND (operand, 0));
1163           goto common;
1164
1165         case CONST_DECL:
1166           operand = DECL_CONST_CORRESPONDING_VAR (operand);
1167
1168           /* ... fall through ... */
1169
1170         default:
1171         common:
1172
1173           /* If we are taking the address of a padded record whose field is
1174              contains a template, take the address of the template.  */
1175           if (TYPE_IS_PADDING_P (type)
1176               && TREE_CODE (TREE_TYPE (TYPE_FIELDS (type))) == RECORD_TYPE
1177               && TYPE_CONTAINS_TEMPLATE_P (TREE_TYPE (TYPE_FIELDS (type))))
1178             {
1179               type = TREE_TYPE (TYPE_FIELDS (type));
1180               operand = convert (type, operand);
1181             }
1182
1183           gnat_mark_addressable (operand);
1184           result = build_fold_addr_expr (operand);
1185         }
1186
1187       TREE_CONSTANT (result) = staticp (operand) || TREE_CONSTANT (operand);
1188       break;
1189
1190     case INDIRECT_REF:
1191       /* If we want to refer to an unconstrained array, use the appropriate
1192          expression to do so.  This will never survive down to the back-end.
1193          But if TYPE is a thin pointer, first convert to a fat pointer.  */
1194       if (TYPE_IS_THIN_POINTER_P (type)
1195           && TYPE_UNCONSTRAINED_ARRAY (TREE_TYPE (type)))
1196         {
1197           operand
1198             = convert (TREE_TYPE (TYPE_UNCONSTRAINED_ARRAY (TREE_TYPE (type))),
1199                        operand);
1200           type = TREE_TYPE (operand);
1201         }
1202
1203       if (TYPE_IS_FAT_POINTER_P (type))
1204         {
1205           result = build1 (UNCONSTRAINED_ARRAY_REF,
1206                            TYPE_UNCONSTRAINED_ARRAY (type), operand);
1207           TREE_READONLY (result)
1208             = TYPE_READONLY (TYPE_UNCONSTRAINED_ARRAY (type));
1209         }
1210
1211       /* If we are dereferencing an ADDR_EXPR, return its operand.  */
1212       else if (TREE_CODE (operand) == ADDR_EXPR)
1213         result = TREE_OPERAND (operand, 0);
1214
1215       /* Otherwise, build and fold the indirect reference.  */
1216       else
1217         {
1218           result = build_fold_indirect_ref (operand);
1219           TREE_READONLY (result) = TYPE_READONLY (TREE_TYPE (type));
1220         }
1221
1222       side_effects
1223         = (!TYPE_IS_FAT_POINTER_P (type) && TYPE_VOLATILE (TREE_TYPE (type)));
1224       break;
1225
1226     case NEGATE_EXPR:
1227     case BIT_NOT_EXPR:
1228       {
1229         tree modulus = ((operation_type
1230                          && TREE_CODE (operation_type) == INTEGER_TYPE
1231                          && TYPE_MODULAR_P (operation_type))
1232                         ? TYPE_MODULUS (operation_type) : NULL_TREE);
1233         int mod_pow2 = modulus && integer_pow2p (modulus);
1234
1235         /* If this is a modular type, there are various possibilities
1236            depending on the operation and whether the modulus is a
1237            power of two or not.  */
1238
1239         if (modulus)
1240           {
1241             gcc_assert (operation_type == base_type);
1242             operand = convert (operation_type, operand);
1243
1244             /* The fastest in the negate case for binary modulus is
1245                the straightforward code; the TRUNC_MOD_EXPR below
1246                is an AND operation.  */
1247             if (op_code == NEGATE_EXPR && mod_pow2)
1248               result = fold_build2 (TRUNC_MOD_EXPR, operation_type,
1249                                     fold_build1 (NEGATE_EXPR, operation_type,
1250                                                  operand),
1251                                     modulus);
1252
1253             /* For nonbinary negate case, return zero for zero operand,
1254                else return the modulus minus the operand.  If the modulus
1255                is a power of two minus one, we can do the subtraction
1256                as an XOR since it is equivalent and faster on most machines. */
1257             else if (op_code == NEGATE_EXPR && !mod_pow2)
1258               {
1259                 if (integer_pow2p (fold_build2 (PLUS_EXPR, operation_type,
1260                                                 modulus,
1261                                                 convert (operation_type,
1262                                                          integer_one_node))))
1263                   result = fold_build2 (BIT_XOR_EXPR, operation_type,
1264                                         operand, modulus);
1265                 else
1266                   result = fold_build2 (MINUS_EXPR, operation_type,
1267                                         modulus, operand);
1268
1269                 result = fold_build3 (COND_EXPR, operation_type,
1270                                       fold_build2 (NE_EXPR,
1271                                                    boolean_type_node,
1272                                                    operand,
1273                                                    convert
1274                                                      (operation_type,
1275                                                       integer_zero_node)),
1276                                       result, operand);
1277               }
1278             else
1279               {
1280                 /* For the NOT cases, we need a constant equal to
1281                    the modulus minus one.  For a binary modulus, we
1282                    XOR against the constant and subtract the operand from
1283                    that constant for nonbinary modulus.  */
1284
1285                 tree cnst = fold_build2 (MINUS_EXPR, operation_type, modulus,
1286                                          convert (operation_type,
1287                                                   integer_one_node));
1288
1289                 if (mod_pow2)
1290                   result = fold_build2 (BIT_XOR_EXPR, operation_type,
1291                                         operand, cnst);
1292                 else
1293                   result = fold_build2 (MINUS_EXPR, operation_type,
1294                                         cnst, operand);
1295               }
1296
1297             break;
1298           }
1299       }
1300
1301       /* ... fall through ... */
1302
1303     default:
1304       gcc_assert (operation_type == base_type);
1305       result = fold_build1 (op_code, operation_type,
1306                             convert (operation_type, operand));
1307     }
1308
1309   if (side_effects)
1310     {
1311       TREE_SIDE_EFFECTS (result) = 1;
1312       if (TREE_CODE (result) == INDIRECT_REF)
1313         TREE_THIS_VOLATILE (result) = TYPE_VOLATILE (TREE_TYPE (result));
1314     }
1315
1316   if (result_type && TREE_TYPE (result) != result_type)
1317     result = convert (result_type, result);
1318
1319   return result;
1320 }
1321 \f
1322 /* Similar, but for COND_EXPR.  */
1323
1324 tree
1325 build_cond_expr (tree result_type, tree condition_operand,
1326                  tree true_operand, tree false_operand)
1327 {
1328   bool addr_p = false;
1329   tree result;
1330
1331   /* The front-end verified that result, true and false operands have
1332      same base type.  Convert everything to the result type.  */
1333   true_operand = convert (result_type, true_operand);
1334   false_operand = convert (result_type, false_operand);
1335
1336   /* If the result type is unconstrained, take the address of the operands and
1337      then dereference the result.  Likewise if the result type is passed by
1338      reference, but this is natively handled in the gimplifier.  */
1339   if (TREE_CODE (result_type) == UNCONSTRAINED_ARRAY_TYPE
1340       || CONTAINS_PLACEHOLDER_P (TYPE_SIZE (result_type)))
1341     {
1342       result_type = build_pointer_type (result_type);
1343       true_operand = build_unary_op (ADDR_EXPR, result_type, true_operand);
1344       false_operand = build_unary_op (ADDR_EXPR, result_type, false_operand);
1345       addr_p = true;
1346     }
1347
1348   result = fold_build3 (COND_EXPR, result_type, condition_operand,
1349                         true_operand, false_operand);
1350
1351   /* If we have a common SAVE_EXPR (possibly surrounded by arithmetics)
1352      in both arms, make sure it gets evaluated by moving it ahead of the
1353      conditional expression.  This is necessary because it is evaluated
1354      in only one place at run time and would otherwise be uninitialized
1355      in one of the arms.  */
1356   true_operand = skip_simple_arithmetic (true_operand);
1357   false_operand = skip_simple_arithmetic (false_operand);
1358
1359   if (true_operand == false_operand && TREE_CODE (true_operand) == SAVE_EXPR)
1360     result = build2 (COMPOUND_EXPR, result_type, true_operand, result);
1361
1362   if (addr_p)
1363     result = build_unary_op (INDIRECT_REF, NULL_TREE, result);
1364
1365   return result;
1366 }
1367
1368 /* Similar, but for COMPOUND_EXPR.  */
1369
1370 tree
1371 build_compound_expr (tree result_type, tree stmt_operand, tree expr_operand)
1372 {
1373   bool addr_p = false;
1374   tree result;
1375
1376   /* If the result type is unconstrained, take the address of the operand and
1377      then dereference the result.  Likewise if the result type is passed by
1378      reference, but this is natively handled in the gimplifier.  */
1379   if (TREE_CODE (result_type) == UNCONSTRAINED_ARRAY_TYPE
1380       || CONTAINS_PLACEHOLDER_P (TYPE_SIZE (result_type)))
1381     {
1382       result_type = build_pointer_type (result_type);
1383       expr_operand = build_unary_op (ADDR_EXPR, result_type, expr_operand);
1384       addr_p = true;
1385     }
1386
1387   result = fold_build2 (COMPOUND_EXPR, result_type, stmt_operand,
1388                         expr_operand);
1389
1390   if (addr_p)
1391     result = build_unary_op (INDIRECT_REF, NULL_TREE, result);
1392
1393   return result;
1394 }
1395 /* Similar, but for RETURN_EXPR.  If RET_VAL is non-null, build a RETURN_EXPR
1396    around the assignment of RET_VAL to RET_OBJ.  Otherwise just build a bare
1397    RETURN_EXPR around RESULT_OBJ, which may be null in this case.  */
1398
1399 tree
1400 build_return_expr (tree ret_obj, tree ret_val)
1401 {
1402   tree result_expr;
1403
1404   if (ret_val)
1405     {
1406       /* The gimplifier explicitly enforces the following invariant:
1407
1408               RETURN_EXPR
1409                   |
1410               MODIFY_EXPR
1411               /        \
1412              /          \
1413          RET_OBJ        ...
1414
1415          As a consequence, type consistency dictates that we use the type
1416          of the RET_OBJ as the operation type.  */
1417       tree operation_type = TREE_TYPE (ret_obj);
1418
1419       /* Convert the right operand to the operation type.  Note that it's the
1420          same transformation as in the MODIFY_EXPR case of build_binary_op,
1421          with the assumption that the type cannot involve a placeholder.  */
1422       if (operation_type != TREE_TYPE (ret_val))
1423         ret_val = convert (operation_type, ret_val);
1424
1425       result_expr = build2 (MODIFY_EXPR, operation_type, ret_obj, ret_val);
1426     }
1427   else
1428     result_expr = ret_obj;
1429
1430   return build1 (RETURN_EXPR, void_type_node, result_expr);
1431 }
1432 \f
1433 /* Build a CALL_EXPR to call FUNDECL with one argument, ARG.  Return
1434    the CALL_EXPR.  */
1435
1436 tree
1437 build_call_1_expr (tree fundecl, tree arg)
1438 {
1439   tree call = build_call_nary (TREE_TYPE (TREE_TYPE (fundecl)),
1440                                build_unary_op (ADDR_EXPR, NULL_TREE, fundecl),
1441                                1, arg);
1442   TREE_SIDE_EFFECTS (call) = 1;
1443   return call;
1444 }
1445
1446 /* Build a CALL_EXPR to call FUNDECL with two arguments, ARG1 & ARG2.  Return
1447    the CALL_EXPR.  */
1448
1449 tree
1450 build_call_2_expr (tree fundecl, tree arg1, tree arg2)
1451 {
1452   tree call = build_call_nary (TREE_TYPE (TREE_TYPE (fundecl)),
1453                                build_unary_op (ADDR_EXPR, NULL_TREE, fundecl),
1454                                2, arg1, arg2);
1455   TREE_SIDE_EFFECTS (call) = 1;
1456   return call;
1457 }
1458
1459 /* Likewise to call FUNDECL with no arguments.  */
1460
1461 tree
1462 build_call_0_expr (tree fundecl)
1463 {
1464   /* We rely on build_call_nary to compute TREE_SIDE_EFFECTS.  This makes
1465      it possible to propagate DECL_IS_PURE on parameterless functions.  */
1466   tree call = build_call_nary (TREE_TYPE (TREE_TYPE (fundecl)),
1467                                build_unary_op (ADDR_EXPR, NULL_TREE, fundecl),
1468                                0);
1469   return call;
1470 }
1471 \f
1472 /* Call a function that raises an exception and pass the line number and file
1473    name, if requested.  MSG says which exception function to call.
1474
1475    GNAT_NODE is the gnat node conveying the source location for which the
1476    error should be signaled, or Empty in which case the error is signaled on
1477    the current ref_file_name/input_line.
1478
1479    KIND says which kind of exception this is for
1480    (N_Raise_{Constraint,Storage,Program}_Error).  */
1481
1482 tree
1483 build_call_raise (int msg, Node_Id gnat_node, char kind)
1484 {
1485   tree fndecl = gnat_raise_decls[msg];
1486   tree label = get_exception_label (kind);
1487   tree filename;
1488   int line_number;
1489   const char *str;
1490   int len;
1491
1492   /* If this is to be done as a goto, handle that case.  */
1493   if (label)
1494     {
1495       Entity_Id local_raise = Get_Local_Raise_Call_Entity ();
1496       tree gnu_result = build1 (GOTO_EXPR, void_type_node, label);
1497
1498       /* If Local_Raise is present, generate
1499          Local_Raise (exception'Identity);  */
1500       if (Present (local_raise))
1501         {
1502           tree gnu_local_raise
1503             = gnat_to_gnu_entity (local_raise, NULL_TREE, 0);
1504           tree gnu_exception_entity
1505             = gnat_to_gnu_entity (Get_RT_Exception_Entity (msg), NULL_TREE, 0);
1506           tree gnu_call
1507             = build_call_1_expr (gnu_local_raise,
1508                                  build_unary_op (ADDR_EXPR, NULL_TREE,
1509                                                  gnu_exception_entity));
1510
1511           gnu_result = build2 (COMPOUND_EXPR, void_type_node,
1512                                gnu_call, gnu_result);}
1513
1514       return gnu_result;
1515     }
1516
1517   str
1518     = (Debug_Flag_NN || Exception_Locations_Suppressed)
1519       ? ""
1520       : (gnat_node != Empty && Sloc (gnat_node) != No_Location)
1521         ? IDENTIFIER_POINTER
1522           (get_identifier (Get_Name_String
1523                            (Debug_Source_Name
1524                             (Get_Source_File_Index (Sloc (gnat_node))))))
1525         : ref_filename;
1526
1527   len = strlen (str);
1528   filename = build_string (len, str);
1529   line_number
1530     = (gnat_node != Empty && Sloc (gnat_node) != No_Location)
1531       ? Get_Logical_Line_Number (Sloc(gnat_node)) : input_line;
1532
1533   TREE_TYPE (filename) = build_array_type (unsigned_char_type_node,
1534                                            build_index_type (size_int (len)));
1535
1536   return
1537     build_call_2_expr (fndecl,
1538                        build1 (ADDR_EXPR,
1539                                build_pointer_type (unsigned_char_type_node),
1540                                filename),
1541                        build_int_cst (NULL_TREE, line_number));
1542 }
1543
1544 /* Similar to build_call_raise, for an index or range check exception as
1545    determined by MSG, with extra information generated of the form
1546    "INDEX out of range FIRST..LAST".  */
1547
1548 tree
1549 build_call_raise_range (int msg, Node_Id gnat_node,
1550                         tree index, tree first, tree last)
1551 {
1552   tree call;
1553   tree fndecl = gnat_raise_decls_ext[msg];
1554   tree filename;
1555   int line_number, column_number;
1556   const char *str;
1557   int len;
1558
1559   str
1560     = (Debug_Flag_NN || Exception_Locations_Suppressed)
1561       ? ""
1562       : (gnat_node != Empty && Sloc (gnat_node) != No_Location)
1563         ? IDENTIFIER_POINTER
1564           (get_identifier (Get_Name_String
1565                            (Debug_Source_Name
1566                             (Get_Source_File_Index (Sloc (gnat_node))))))
1567         : ref_filename;
1568
1569   len = strlen (str);
1570   filename = build_string (len, str);
1571   if (gnat_node != Empty && Sloc (gnat_node) != No_Location)
1572     {
1573       line_number = Get_Logical_Line_Number (Sloc (gnat_node));
1574       column_number = Get_Column_Number (Sloc (gnat_node));
1575     }
1576   else
1577     {
1578       line_number = input_line;
1579       column_number = 0;
1580     }
1581
1582   TREE_TYPE (filename) = build_array_type (unsigned_char_type_node,
1583                                            build_index_type (size_int (len)));
1584
1585   call = build_call_nary (TREE_TYPE (TREE_TYPE (fndecl)),
1586                           build_unary_op (ADDR_EXPR, NULL_TREE, fndecl),
1587                           6,
1588                           build1 (ADDR_EXPR,
1589                                   build_pointer_type (unsigned_char_type_node),
1590                                   filename),
1591                           build_int_cst (NULL_TREE, line_number),
1592                           build_int_cst (NULL_TREE, column_number),
1593                           convert (integer_type_node, index),
1594                           convert (integer_type_node, first),
1595                           convert (integer_type_node, last));
1596   TREE_SIDE_EFFECTS (call) = 1;
1597   return call;
1598 }
1599
1600 /* Similar to build_call_raise, with extra information about the column
1601    where the check failed.  */
1602
1603 tree
1604 build_call_raise_column (int msg, Node_Id gnat_node)
1605 {
1606   tree fndecl = gnat_raise_decls_ext[msg];
1607   tree call;
1608   tree filename;
1609   int line_number, column_number;
1610   const char *str;
1611   int len;
1612
1613   str
1614     = (Debug_Flag_NN || Exception_Locations_Suppressed)
1615       ? ""
1616       : (gnat_node != Empty && Sloc (gnat_node) != No_Location)
1617         ? IDENTIFIER_POINTER
1618           (get_identifier (Get_Name_String
1619                            (Debug_Source_Name
1620                             (Get_Source_File_Index (Sloc (gnat_node))))))
1621         : ref_filename;
1622
1623   len = strlen (str);
1624   filename = build_string (len, str);
1625   if (gnat_node != Empty && Sloc (gnat_node) != No_Location)
1626     {
1627       line_number = Get_Logical_Line_Number (Sloc (gnat_node));
1628       column_number = Get_Column_Number (Sloc (gnat_node));
1629     }
1630   else
1631     {
1632       line_number = input_line;
1633       column_number = 0;
1634     }
1635
1636   TREE_TYPE (filename) = build_array_type (unsigned_char_type_node,
1637                                            build_index_type (size_int (len)));
1638
1639   call = build_call_nary (TREE_TYPE (TREE_TYPE (fndecl)),
1640                           build_unary_op (ADDR_EXPR, NULL_TREE, fndecl),
1641                           3,
1642                           build1 (ADDR_EXPR,
1643                                   build_pointer_type (unsigned_char_type_node),
1644                                   filename),
1645                           build_int_cst (NULL_TREE, line_number),
1646                           build_int_cst (NULL_TREE, column_number));
1647   TREE_SIDE_EFFECTS (call) = 1;
1648   return call;
1649 }
1650 \f
1651 /* qsort comparer for the bit positions of two constructor elements
1652    for record components.  */
1653
1654 static int
1655 compare_elmt_bitpos (const PTR rt1, const PTR rt2)
1656 {
1657   const constructor_elt * const elmt1 = (const constructor_elt * const) rt1;
1658   const constructor_elt * const elmt2 = (const constructor_elt * const) rt2;
1659   const_tree const field1 = elmt1->index;
1660   const_tree const field2 = elmt2->index;
1661   const int ret
1662     = tree_int_cst_compare (bit_position (field1), bit_position (field2));
1663
1664   return ret ? ret : (int) (DECL_UID (field1) - DECL_UID (field2));
1665 }
1666
1667 /* Return a CONSTRUCTOR of TYPE whose elements are V.  */
1668
1669 tree
1670 gnat_build_constructor (tree type, VEC(constructor_elt,gc) *v)
1671 {
1672   bool allconstant = (TREE_CODE (TYPE_SIZE (type)) == INTEGER_CST);
1673   bool side_effects = false;
1674   tree result, obj, val;
1675   unsigned int n_elmts;
1676
1677   /* Scan the elements to see if they are all constant or if any has side
1678      effects, to let us set global flags on the resulting constructor.  Count
1679      the elements along the way for possible sorting purposes below.  */
1680   FOR_EACH_CONSTRUCTOR_ELT (v, n_elmts, obj, val)
1681     {
1682       /* The predicate must be in keeping with output_constructor.  */
1683       if (!TREE_CONSTANT (val)
1684           || (TREE_CODE (type) == RECORD_TYPE
1685               && CONSTRUCTOR_BITFIELD_P (obj)
1686               && !initializer_constant_valid_for_bitfield_p (val))
1687           || !initializer_constant_valid_p (val, TREE_TYPE (val)))
1688         allconstant = false;
1689
1690       if (TREE_SIDE_EFFECTS (val))
1691         side_effects = true;
1692     }
1693
1694   /* For record types with constant components only, sort field list
1695      by increasing bit position.  This is necessary to ensure the
1696      constructor can be output as static data.  */
1697   if (allconstant && TREE_CODE (type) == RECORD_TYPE && n_elmts > 1)
1698     VEC_qsort (constructor_elt, v, compare_elmt_bitpos);
1699
1700   result = build_constructor (type, v);
1701   TREE_CONSTANT (result) = TREE_STATIC (result) = allconstant;
1702   TREE_SIDE_EFFECTS (result) = side_effects;
1703   TREE_READONLY (result) = TYPE_READONLY (type) || allconstant;
1704   return result;
1705 }
1706 \f
1707 /* Return a COMPONENT_REF to access a field that is given by COMPONENT,
1708    an IDENTIFIER_NODE giving the name of the field, or FIELD, a FIELD_DECL,
1709    for the field.  Don't fold the result if NO_FOLD_P is true.
1710
1711    We also handle the fact that we might have been passed a pointer to the
1712    actual record and know how to look for fields in variant parts.  */
1713
1714 static tree
1715 build_simple_component_ref (tree record_variable, tree component,
1716                             tree field, bool no_fold_p)
1717 {
1718   tree record_type = TYPE_MAIN_VARIANT (TREE_TYPE (record_variable));
1719   tree ref, inner_variable;
1720
1721   gcc_assert ((TREE_CODE (record_type) == RECORD_TYPE
1722                || TREE_CODE (record_type) == UNION_TYPE
1723                || TREE_CODE (record_type) == QUAL_UNION_TYPE)
1724               && TYPE_SIZE (record_type)
1725               && (component != 0) != (field != 0));
1726
1727   /* If no field was specified, look for a field with the specified name
1728      in the current record only.  */
1729   if (!field)
1730     for (field = TYPE_FIELDS (record_type); field;
1731          field = TREE_CHAIN (field))
1732       if (DECL_NAME (field) == component)
1733         break;
1734
1735   if (!field)
1736     return NULL_TREE;
1737
1738   /* If this field is not in the specified record, see if we can find a field
1739      in the specified record whose original field is the same as this one.  */
1740   if (DECL_CONTEXT (field) != record_type)
1741     {
1742       tree new_field;
1743
1744       /* First loop thru normal components.  */
1745       for (new_field = TYPE_FIELDS (record_type); new_field;
1746            new_field = DECL_CHAIN (new_field))
1747         if (SAME_FIELD_P (field, new_field))
1748           break;
1749
1750       /* Next, see if we're looking for an inherited component in an extension.
1751          If so, look thru the extension directly.  */
1752       if (!new_field
1753           && TREE_CODE (record_variable) == VIEW_CONVERT_EXPR
1754           && TYPE_ALIGN_OK (record_type)
1755           && TREE_CODE (TREE_TYPE (TREE_OPERAND (record_variable, 0)))
1756              == RECORD_TYPE
1757           && TYPE_ALIGN_OK (TREE_TYPE (TREE_OPERAND (record_variable, 0))))
1758         {
1759           ref = build_simple_component_ref (TREE_OPERAND (record_variable, 0),
1760                                             NULL_TREE, field, no_fold_p);
1761           if (ref)
1762             return ref;
1763         }
1764
1765       /* Next, loop thru DECL_INTERNAL_P components if we haven't found
1766          the component in the first search. Doing this search in 2 steps
1767          is required to avoiding hidden homonymous fields in the
1768          _Parent field.  */
1769       if (!new_field)
1770         for (new_field = TYPE_FIELDS (record_type); new_field;
1771              new_field = DECL_CHAIN (new_field))
1772           if (DECL_INTERNAL_P (new_field))
1773             {
1774               tree field_ref
1775                 = build_simple_component_ref (record_variable,
1776                                               NULL_TREE, new_field, no_fold_p);
1777               ref = build_simple_component_ref (field_ref, NULL_TREE, field,
1778                                                 no_fold_p);
1779
1780               if (ref)
1781                 return ref;
1782             }
1783
1784       field = new_field;
1785     }
1786
1787   if (!field)
1788     return NULL_TREE;
1789
1790   /* If the field's offset has overflowed, do not attempt to access it
1791      as doing so may trigger sanity checks deeper in the back-end.
1792      Note that we don't need to warn since this will be done on trying
1793      to declare the object.  */
1794   if (TREE_CODE (DECL_FIELD_OFFSET (field)) == INTEGER_CST
1795       && TREE_OVERFLOW (DECL_FIELD_OFFSET (field)))
1796     return NULL_TREE;
1797
1798   /* Look through conversion between type variants.  Note that this
1799      is transparent as far as the field is concerned.  */
1800   if (TREE_CODE (record_variable) == VIEW_CONVERT_EXPR
1801       && TYPE_MAIN_VARIANT (TREE_TYPE (TREE_OPERAND (record_variable, 0)))
1802          == record_type)
1803     inner_variable = TREE_OPERAND (record_variable, 0);
1804   else
1805     inner_variable = record_variable;
1806
1807   ref = build3 (COMPONENT_REF, TREE_TYPE (field), inner_variable, field,
1808                 NULL_TREE);
1809
1810   if (TREE_READONLY (record_variable) || TREE_READONLY (field))
1811     TREE_READONLY (ref) = 1;
1812   if (TREE_THIS_VOLATILE (record_variable) || TREE_THIS_VOLATILE (field)
1813       || TYPE_VOLATILE (record_type))
1814     TREE_THIS_VOLATILE (ref) = 1;
1815
1816   if (no_fold_p)
1817     return ref;
1818
1819   /* The generic folder may punt in this case because the inner array type
1820      can be self-referential, but folding is in fact not problematic.  */
1821   else if (TREE_CODE (record_variable) == CONSTRUCTOR
1822            && TYPE_CONTAINS_TEMPLATE_P (TREE_TYPE (record_variable)))
1823     {
1824       VEC(constructor_elt,gc) *elts = CONSTRUCTOR_ELTS (record_variable);
1825       unsigned HOST_WIDE_INT idx;
1826       tree index, value;
1827       FOR_EACH_CONSTRUCTOR_ELT (elts, idx, index, value)
1828         if (index == field)
1829           return value;
1830       return ref;
1831     }
1832
1833   else
1834     return fold (ref);
1835 }
1836 \f
1837 /* Like build_simple_component_ref, except that we give an error if the
1838    reference could not be found.  */
1839
1840 tree
1841 build_component_ref (tree record_variable, tree component,
1842                      tree field, bool no_fold_p)
1843 {
1844   tree ref = build_simple_component_ref (record_variable, component, field,
1845                                          no_fold_p);
1846
1847   if (ref)
1848     return ref;
1849
1850   /* If FIELD was specified, assume this is an invalid user field so raise
1851      Constraint_Error.  Otherwise, we have no type to return so abort.  */
1852   gcc_assert (field);
1853   return build1 (NULL_EXPR, TREE_TYPE (field),
1854                  build_call_raise (CE_Discriminant_Check_Failed, Empty,
1855                                    N_Raise_Constraint_Error));
1856 }
1857 \f
1858 /* Helper for build_call_alloc_dealloc, with arguments to be interpreted
1859    identically.  Process the case where a GNAT_PROC to call is provided.  */
1860
1861 static inline tree
1862 build_call_alloc_dealloc_proc (tree gnu_obj, tree gnu_size, tree gnu_type,
1863                                Entity_Id gnat_proc, Entity_Id gnat_pool)
1864 {
1865   tree gnu_proc = gnat_to_gnu (gnat_proc);
1866   tree gnu_proc_addr = build_unary_op (ADDR_EXPR, NULL_TREE, gnu_proc);
1867   tree gnu_call;
1868
1869   /* The storage pools are obviously always tagged types, but the
1870      secondary stack uses the same mechanism and is not tagged.  */
1871   if (Is_Tagged_Type (Etype (gnat_pool)))
1872     {
1873       /* The size is the third parameter; the alignment is the
1874          same type.  */
1875       Entity_Id gnat_size_type
1876         = Etype (Next_Formal (Next_Formal (First_Formal (gnat_proc))));
1877       tree gnu_size_type = gnat_to_gnu_type (gnat_size_type);
1878
1879       tree gnu_pool = gnat_to_gnu (gnat_pool);
1880       tree gnu_pool_addr = build_unary_op (ADDR_EXPR, NULL_TREE, gnu_pool);
1881       tree gnu_align = size_int (TYPE_ALIGN (gnu_type) / BITS_PER_UNIT);
1882
1883       gnu_size = convert (gnu_size_type, gnu_size);
1884       gnu_align = convert (gnu_size_type, gnu_align);
1885
1886       /* The first arg is always the address of the storage pool; next
1887          comes the address of the object, for a deallocator, then the
1888          size and alignment.  */
1889       if (gnu_obj)
1890         gnu_call = build_call_nary (TREE_TYPE (TREE_TYPE (gnu_proc)),
1891                                     gnu_proc_addr, 4, gnu_pool_addr,
1892                                     gnu_obj, gnu_size, gnu_align);
1893       else
1894         gnu_call = build_call_nary (TREE_TYPE (TREE_TYPE (gnu_proc)),
1895                                     gnu_proc_addr, 3, gnu_pool_addr,
1896                                     gnu_size, gnu_align);
1897     }
1898
1899   /* Secondary stack case.  */
1900   else
1901     {
1902       /* The size is the second parameter.  */
1903       Entity_Id gnat_size_type
1904         = Etype (Next_Formal (First_Formal (gnat_proc)));
1905       tree gnu_size_type = gnat_to_gnu_type (gnat_size_type);
1906
1907       gnu_size = convert (gnu_size_type, gnu_size);
1908
1909       /* The first arg is the address of the object, for a deallocator,
1910          then the size.  */
1911       if (gnu_obj)
1912         gnu_call = build_call_nary (TREE_TYPE (TREE_TYPE (gnu_proc)),
1913                                     gnu_proc_addr, 2, gnu_obj, gnu_size);
1914       else
1915         gnu_call = build_call_nary (TREE_TYPE (TREE_TYPE (gnu_proc)),
1916                                     gnu_proc_addr, 1, gnu_size);
1917     }
1918
1919   TREE_SIDE_EFFECTS (gnu_call) = 1;
1920   return gnu_call;
1921 }
1922
1923 /* Helper for build_call_alloc_dealloc, to build and return an allocator for
1924    DATA_SIZE bytes aimed at containing a DATA_TYPE object, using the default
1925    __gnat_malloc allocator.  Honor DATA_TYPE alignments greater than what the
1926    latter offers.  */
1927
1928 static inline tree
1929 maybe_wrap_malloc (tree data_size, tree data_type, Node_Id gnat_node)
1930 {
1931   /* When the DATA_TYPE alignment is stricter than what malloc offers
1932      (super-aligned case), we allocate an "aligning" wrapper type and return
1933      the address of its single data field with the malloc's return value
1934      stored just in front.  */
1935
1936   unsigned int data_align = TYPE_ALIGN (data_type);
1937   unsigned int default_allocator_alignment
1938       = get_target_default_allocator_alignment () * BITS_PER_UNIT;
1939
1940   tree aligning_type
1941     = ((data_align > default_allocator_alignment)
1942        ? make_aligning_type (data_type, data_align, data_size,
1943                              default_allocator_alignment,
1944                              POINTER_SIZE / BITS_PER_UNIT)
1945        : NULL_TREE);
1946
1947   tree size_to_malloc
1948     = aligning_type ? TYPE_SIZE_UNIT (aligning_type) : data_size;
1949
1950   tree malloc_ptr;
1951
1952   /* On VMS, if pointers are 64-bit and the allocator size is 32-bit or
1953      Convention C, allocate 32-bit memory.  */
1954   if (TARGET_ABI_OPEN_VMS
1955       && POINTER_SIZE == 64
1956       && Nkind (gnat_node) == N_Allocator
1957       && (UI_To_Int (Esize (Etype (gnat_node))) == 32
1958           || Convention (Etype (gnat_node)) == Convention_C))
1959     malloc_ptr = build_call_1_expr (malloc32_decl, size_to_malloc);
1960   else
1961     malloc_ptr = build_call_1_expr (malloc_decl, size_to_malloc);
1962
1963   if (aligning_type)
1964     {
1965       /* Latch malloc's return value and get a pointer to the aligning field
1966          first.  */
1967       tree storage_ptr = gnat_protect_expr (malloc_ptr);
1968
1969       tree aligning_record_addr
1970         = convert (build_pointer_type (aligning_type), storage_ptr);
1971
1972       tree aligning_record
1973         = build_unary_op (INDIRECT_REF, NULL_TREE, aligning_record_addr);
1974
1975       tree aligning_field
1976         = build_component_ref (aligning_record, NULL_TREE,
1977                                TYPE_FIELDS (aligning_type), false);
1978
1979       tree aligning_field_addr
1980         = build_unary_op (ADDR_EXPR, NULL_TREE, aligning_field);
1981
1982       /* Then arrange to store the allocator's return value ahead
1983          and return.  */
1984       tree storage_ptr_slot_addr
1985         = build_binary_op (POINTER_PLUS_EXPR, ptr_void_type_node,
1986                            convert (ptr_void_type_node, aligning_field_addr),
1987                            size_int (-(HOST_WIDE_INT) POINTER_SIZE
1988                                      / BITS_PER_UNIT));
1989
1990       tree storage_ptr_slot
1991         = build_unary_op (INDIRECT_REF, NULL_TREE,
1992                           convert (build_pointer_type (ptr_void_type_node),
1993                                    storage_ptr_slot_addr));
1994
1995       return
1996         build2 (COMPOUND_EXPR, TREE_TYPE (aligning_field_addr),
1997                 build_binary_op (MODIFY_EXPR, NULL_TREE,
1998                                  storage_ptr_slot, storage_ptr),
1999                 aligning_field_addr);
2000     }
2001   else
2002     return malloc_ptr;
2003 }
2004
2005 /* Helper for build_call_alloc_dealloc, to release a DATA_TYPE object
2006    designated by DATA_PTR using the __gnat_free entry point.  */
2007
2008 static inline tree
2009 maybe_wrap_free (tree data_ptr, tree data_type)
2010 {
2011   /* In the regular alignment case, we pass the data pointer straight to free.
2012      In the superaligned case, we need to retrieve the initial allocator
2013      return value, stored in front of the data block at allocation time.  */
2014
2015   unsigned int data_align = TYPE_ALIGN (data_type);
2016   unsigned int default_allocator_alignment
2017       = get_target_default_allocator_alignment () * BITS_PER_UNIT;
2018
2019   tree free_ptr;
2020
2021   if (data_align > default_allocator_alignment)
2022     {
2023       /* DATA_FRONT_PTR (void *)
2024          = (void *)DATA_PTR - (void *)sizeof (void *))  */
2025       tree data_front_ptr
2026         = build_binary_op
2027           (POINTER_PLUS_EXPR, ptr_void_type_node,
2028            convert (ptr_void_type_node, data_ptr),
2029            size_int (-(HOST_WIDE_INT) POINTER_SIZE / BITS_PER_UNIT));
2030
2031       /* FREE_PTR (void *) = *(void **)DATA_FRONT_PTR  */
2032       free_ptr
2033         = build_unary_op
2034           (INDIRECT_REF, NULL_TREE,
2035            convert (build_pointer_type (ptr_void_type_node), data_front_ptr));
2036     }
2037   else
2038     free_ptr = data_ptr;
2039
2040   return build_call_1_expr (free_decl, free_ptr);
2041 }
2042
2043 /* Build a GCC tree to call an allocation or deallocation function.
2044    If GNU_OBJ is nonzero, it is an object to deallocate.  Otherwise,
2045    generate an allocator.
2046
2047    GNU_SIZE is the number of bytes to allocate and GNU_TYPE is the contained
2048    object type, used to determine the to-be-honored address alignment.
2049    GNAT_PROC, if present, is a procedure to call and GNAT_POOL is the storage
2050    pool to use.  If not present, malloc and free are used.  GNAT_NODE is used
2051    to provide an error location for restriction violation messages.  */
2052
2053 tree
2054 build_call_alloc_dealloc (tree gnu_obj, tree gnu_size, tree gnu_type,
2055                           Entity_Id gnat_proc, Entity_Id gnat_pool,
2056                           Node_Id gnat_node)
2057 {
2058   gnu_size = SUBSTITUTE_PLACEHOLDER_IN_EXPR (gnu_size, gnu_obj);
2059
2060   /* Explicit proc to call ?  This one is assumed to deal with the type
2061      alignment constraints.  */
2062   if (Present (gnat_proc))
2063     return build_call_alloc_dealloc_proc (gnu_obj, gnu_size, gnu_type,
2064                                           gnat_proc, gnat_pool);
2065
2066   /* Otherwise, object to "free" or "malloc" with possible special processing
2067      for alignments stricter than what the default allocator honors.  */
2068   else if (gnu_obj)
2069     return maybe_wrap_free (gnu_obj, gnu_type);
2070   else
2071     {
2072       /* Assert that we no longer can be called with this special pool.  */
2073       gcc_assert (gnat_pool != -1);
2074
2075       /* Check that we aren't violating the associated restriction.  */
2076       if (!(Nkind (gnat_node) == N_Allocator && Comes_From_Source (gnat_node)))
2077         Check_No_Implicit_Heap_Alloc (gnat_node);
2078
2079       return maybe_wrap_malloc (gnu_size, gnu_type, gnat_node);
2080     }
2081 }
2082 \f
2083 /* Build a GCC tree to correspond to allocating an object of TYPE whose
2084    initial value is INIT, if INIT is nonzero.  Convert the expression to
2085    RESULT_TYPE, which must be some type of pointer.  Return the tree.
2086
2087    GNAT_PROC and GNAT_POOL optionally give the procedure to call and
2088    the storage pool to use.  GNAT_NODE is used to provide an error
2089    location for restriction violation messages.  If IGNORE_INIT_TYPE is
2090    true, ignore the type of INIT for the purpose of determining the size;
2091    this will cause the maximum size to be allocated if TYPE is of
2092    self-referential size.  */
2093
2094 tree
2095 build_allocator (tree type, tree init, tree result_type, Entity_Id gnat_proc,
2096                  Entity_Id gnat_pool, Node_Id gnat_node, bool ignore_init_type)
2097 {
2098   tree size = TYPE_SIZE_UNIT (type);
2099   tree result;
2100
2101   /* If the initializer, if present, is a NULL_EXPR, just return a new one.  */
2102   if (init && TREE_CODE (init) == NULL_EXPR)
2103     return build1 (NULL_EXPR, result_type, TREE_OPERAND (init, 0));
2104
2105   /* If RESULT_TYPE is a fat or thin pointer, set SIZE to be the sum of the
2106      sizes of the object and its template.  Allocate the whole thing and
2107      fill in the parts that are known.  */
2108   else if (TYPE_IS_FAT_OR_THIN_POINTER_P (result_type))
2109     {
2110       tree storage_type
2111         = build_unc_object_type_from_ptr (result_type, type,
2112                                           get_identifier ("ALLOC"), false);
2113       tree template_type = TREE_TYPE (TYPE_FIELDS (storage_type));
2114       tree storage_ptr_type = build_pointer_type (storage_type);
2115       tree storage;
2116
2117       size = SUBSTITUTE_PLACEHOLDER_IN_EXPR (TYPE_SIZE_UNIT (storage_type),
2118                                              init);
2119
2120       /* If the size overflows, pass -1 so the allocator will raise
2121          storage error.  */
2122       if (TREE_CODE (size) == INTEGER_CST && TREE_OVERFLOW (size))
2123         size = ssize_int (-1);
2124
2125       storage = build_call_alloc_dealloc (NULL_TREE, size, storage_type,
2126                                           gnat_proc, gnat_pool, gnat_node);
2127       storage = convert (storage_ptr_type, gnat_protect_expr (storage));
2128
2129       if (TYPE_IS_PADDING_P (type))
2130         {
2131           type = TREE_TYPE (TYPE_FIELDS (type));
2132           if (init)
2133             init = convert (type, init);
2134         }
2135
2136       /* If there is an initializing expression, make a constructor for
2137          the entire object including the bounds and copy it into the
2138          object.  If there is no initializing expression, just set the
2139          bounds.  */
2140       if (init)
2141         {
2142           VEC(constructor_elt,gc) *v = VEC_alloc (constructor_elt, gc, 2);
2143
2144           CONSTRUCTOR_APPEND_ELT (v, TYPE_FIELDS (storage_type),
2145                                   build_template (template_type, type, init));
2146           CONSTRUCTOR_APPEND_ELT (v, DECL_CHAIN (TYPE_FIELDS (storage_type)),
2147                                   init);
2148
2149           return convert
2150             (result_type,
2151              build2 (COMPOUND_EXPR, storage_ptr_type,
2152                      build_binary_op
2153                      (MODIFY_EXPR, storage_type,
2154                       build_unary_op (INDIRECT_REF, NULL_TREE,
2155                                       convert (storage_ptr_type, storage)),
2156                       gnat_build_constructor (storage_type, v)),
2157                      convert (storage_ptr_type, storage)));
2158         }
2159       else
2160         return build2
2161           (COMPOUND_EXPR, result_type,
2162            build_binary_op
2163            (MODIFY_EXPR, template_type,
2164             build_component_ref
2165             (build_unary_op (INDIRECT_REF, NULL_TREE,
2166                              convert (storage_ptr_type, storage)),
2167              NULL_TREE, TYPE_FIELDS (storage_type), false),
2168             build_template (template_type, type, NULL_TREE)),
2169            convert (result_type, convert (storage_ptr_type, storage)));
2170     }
2171
2172   /* If we have an initializing expression, see if its size is simpler
2173      than the size from the type.  */
2174   if (!ignore_init_type && init && TYPE_SIZE_UNIT (TREE_TYPE (init))
2175       && (TREE_CODE (TYPE_SIZE_UNIT (TREE_TYPE (init))) == INTEGER_CST
2176           || CONTAINS_PLACEHOLDER_P (size)))
2177     size = TYPE_SIZE_UNIT (TREE_TYPE (init));
2178
2179   /* If the size is still self-referential, reference the initializing
2180      expression, if it is present.  If not, this must have been a
2181      call to allocate a library-level object, in which case we use
2182      the maximum size.  */
2183   if (CONTAINS_PLACEHOLDER_P (size))
2184     {
2185       if (!ignore_init_type && init)
2186         size = substitute_placeholder_in_expr (size, init);
2187       else
2188         size = max_size (size, true);
2189     }
2190
2191   /* If the size overflows, pass -1 so the allocator will raise
2192      storage error.  */
2193   if (TREE_CODE (size) == INTEGER_CST && TREE_OVERFLOW (size))
2194     size = ssize_int (-1);
2195
2196   result = convert (result_type,
2197                     build_call_alloc_dealloc (NULL_TREE, size, type,
2198                                               gnat_proc, gnat_pool,
2199                                               gnat_node));
2200
2201   /* If we have an initial value, protect the new address, assign the value
2202      and return the address with a COMPOUND_EXPR.  */
2203   if (init)
2204     {
2205       result = gnat_protect_expr (result);
2206       result
2207         = build2 (COMPOUND_EXPR, TREE_TYPE (result),
2208                   build_binary_op
2209                   (MODIFY_EXPR, NULL_TREE,
2210                    build_unary_op (INDIRECT_REF,
2211                                    TREE_TYPE (TREE_TYPE (result)), result),
2212                    init),
2213                   result);
2214     }
2215
2216   return convert (result_type, result);
2217 }
2218 \f
2219 /* Fill in a VMS descriptor for EXPR and return a constructor for it.
2220    GNAT_FORMAL is how we find the descriptor record.  GNAT_ACTUAL is
2221    how we derive the source location to raise C_E on an out of range
2222    pointer. */
2223
2224 tree
2225 fill_vms_descriptor (tree expr, Entity_Id gnat_formal, Node_Id gnat_actual)
2226 {
2227   tree parm_decl = get_gnu_tree (gnat_formal);
2228   tree record_type = TREE_TYPE (TREE_TYPE (parm_decl));
2229   tree field;
2230   const bool do_range_check
2231     = strcmp ("MBO",
2232               IDENTIFIER_POINTER (DECL_NAME (TYPE_FIELDS (record_type))));
2233   VEC(constructor_elt,gc) *v = NULL;
2234
2235   expr = maybe_unconstrained_array (expr);
2236   gnat_mark_addressable (expr);
2237
2238   for (field = TYPE_FIELDS (record_type); field; field = DECL_CHAIN (field))
2239     {
2240       tree conexpr = convert (TREE_TYPE (field),
2241                               SUBSTITUTE_PLACEHOLDER_IN_EXPR
2242                               (DECL_INITIAL (field), expr));
2243
2244       /* Check to ensure that only 32-bit pointers are passed in
2245          32-bit descriptors */
2246       if (do_range_check
2247           && strcmp (IDENTIFIER_POINTER (DECL_NAME (field)), "POINTER") == 0)
2248         {
2249           tree pointer64type
2250             = build_pointer_type_for_mode (void_type_node, DImode, false);
2251           tree addr64expr = build_unary_op (ADDR_EXPR, pointer64type, expr);
2252           tree malloc64low
2253             = build_int_cstu (long_integer_type_node, 0x80000000);
2254
2255           add_stmt (build3 (COND_EXPR, void_type_node,
2256                             build_binary_op (GE_EXPR, boolean_type_node,
2257                                              convert (long_integer_type_node,
2258                                                       addr64expr),
2259                                              malloc64low),
2260                             build_call_raise (CE_Range_Check_Failed,
2261                                               gnat_actual,
2262                                               N_Raise_Constraint_Error),
2263                             NULL_TREE));
2264         }
2265       CONSTRUCTOR_APPEND_ELT (v, field, conexpr);
2266     }
2267
2268   return gnat_build_constructor (record_type, v);
2269 }
2270
2271 /* Indicate that we need to take the address of T and that it therefore
2272    should not be allocated in a register.  Returns true if successful.  */
2273
2274 bool
2275 gnat_mark_addressable (tree t)
2276 {
2277   while (true)
2278     switch (TREE_CODE (t))
2279       {
2280       case ADDR_EXPR:
2281       case COMPONENT_REF:
2282       case ARRAY_REF:
2283       case ARRAY_RANGE_REF:
2284       case REALPART_EXPR:
2285       case IMAGPART_EXPR:
2286       case VIEW_CONVERT_EXPR:
2287       case NON_LVALUE_EXPR:
2288       CASE_CONVERT:
2289         t = TREE_OPERAND (t, 0);
2290         break;
2291
2292       case COMPOUND_EXPR:
2293         t = TREE_OPERAND (t, 1);
2294         break;
2295
2296       case CONSTRUCTOR:
2297         TREE_ADDRESSABLE (t) = 1;
2298         return true;
2299
2300       case VAR_DECL:
2301       case PARM_DECL:
2302       case RESULT_DECL:
2303         TREE_ADDRESSABLE (t) = 1;
2304         return true;
2305
2306       case FUNCTION_DECL:
2307         TREE_ADDRESSABLE (t) = 1;
2308         return true;
2309
2310       case CONST_DECL:
2311         return DECL_CONST_CORRESPONDING_VAR (t)
2312                && gnat_mark_addressable (DECL_CONST_CORRESPONDING_VAR (t));
2313
2314       default:
2315         return true;
2316     }
2317 }
2318 \f
2319 /* Save EXP for later use or reuse.  This is equivalent to save_expr in tree.c
2320    but we know how to handle our own nodes.  */
2321
2322 tree
2323 gnat_save_expr (tree exp)
2324 {
2325   tree type = TREE_TYPE (exp);
2326   enum tree_code code = TREE_CODE (exp);
2327
2328   if (TREE_CONSTANT (exp) || code == SAVE_EXPR || code == NULL_EXPR)
2329     return exp;
2330
2331   if (code == UNCONSTRAINED_ARRAY_REF)
2332     {
2333       tree t = build1 (code, type, gnat_save_expr (TREE_OPERAND (exp, 0)));
2334       TREE_READONLY (t) = TYPE_READONLY (type);
2335       return t;
2336     }
2337
2338   /* If this is a COMPONENT_REF of a fat pointer, save the entire fat pointer.
2339      This may be more efficient, but will also allow us to more easily find
2340      the match for the PLACEHOLDER_EXPR.  */
2341   if (code == COMPONENT_REF
2342       && TYPE_IS_FAT_POINTER_P (TREE_TYPE (TREE_OPERAND (exp, 0))))
2343     return build3 (code, type, gnat_save_expr (TREE_OPERAND (exp, 0)),
2344                    TREE_OPERAND (exp, 1), TREE_OPERAND (exp, 2));
2345
2346   return save_expr (exp);
2347 }
2348
2349 /* Protect EXP for immediate reuse.  This is a variant of gnat_save_expr that
2350    is optimized under the assumption that EXP's value doesn't change before
2351    its subsequent reuse(s) except through its potential reevaluation.  */
2352
2353 tree
2354 gnat_protect_expr (tree exp)
2355 {
2356   tree type = TREE_TYPE (exp);
2357   enum tree_code code = TREE_CODE (exp);
2358
2359   if (TREE_CONSTANT (exp) || code == SAVE_EXPR || code == NULL_EXPR)
2360     return exp;
2361
2362   /* If EXP has no side effects, we theoritically don't need to do anything.
2363      However, we may be recursively passed more and more complex expressions
2364      involving checks which will be reused multiple times and eventually be
2365      unshared for gimplification; in order to avoid a complexity explosion
2366      at that point, we protect any expressions more complex than a simple
2367      arithmetic expression.  */
2368   if (!TREE_SIDE_EFFECTS (exp))
2369     {
2370       tree inner = skip_simple_arithmetic (exp);
2371       if (!EXPR_P (inner) || REFERENCE_CLASS_P (inner))
2372         return exp;
2373     }
2374
2375   /* If this is a conversion, protect what's inside the conversion.  */
2376   if (code == NON_LVALUE_EXPR
2377       || CONVERT_EXPR_CODE_P (code)
2378       || code == VIEW_CONVERT_EXPR)
2379   return build1 (code, type, gnat_protect_expr (TREE_OPERAND (exp, 0)));
2380
2381   /* If we're indirectly referencing something, we only need to protect the
2382      address since the data itself can't change in these situations.  */
2383   if (code == INDIRECT_REF || code == UNCONSTRAINED_ARRAY_REF)
2384     {
2385       tree t = build1 (code, type, gnat_protect_expr (TREE_OPERAND (exp, 0)));
2386       TREE_READONLY (t) = TYPE_READONLY (type);
2387       return t;
2388     }
2389
2390   /* If this is a COMPONENT_REF of a fat pointer, save the entire fat pointer.
2391      This may be more efficient, but will also allow us to more easily find
2392      the match for the PLACEHOLDER_EXPR.  */
2393   if (code == COMPONENT_REF
2394       && TYPE_IS_FAT_POINTER_P (TREE_TYPE (TREE_OPERAND (exp, 0))))
2395     return build3 (code, type, gnat_protect_expr (TREE_OPERAND (exp, 0)),
2396                    TREE_OPERAND (exp, 1), TREE_OPERAND (exp, 2));
2397
2398   /* If this is a fat pointer or something that can be placed in a register,
2399      just make a SAVE_EXPR.  Likewise for a CALL_EXPR as large objects are
2400      returned via invisible reference in most ABIs so the temporary will
2401      directly be filled by the callee.  */
2402   if (TYPE_IS_FAT_POINTER_P (type)
2403       || TYPE_MODE (type) != BLKmode
2404       || code == CALL_EXPR)
2405     return save_expr (exp);
2406
2407   /* Otherwise reference, protect the address and dereference.  */
2408   return
2409     build_unary_op (INDIRECT_REF, type,
2410                     save_expr (build_unary_op (ADDR_EXPR,
2411                                                build_reference_type (type),
2412                                                exp)));
2413 }
2414
2415 /* This is equivalent to stabilize_reference_1 in tree.c but we take an extra
2416    argument to force evaluation of everything.  */
2417
2418 static tree
2419 gnat_stabilize_reference_1 (tree e, bool force)
2420 {
2421   enum tree_code code = TREE_CODE (e);
2422   tree type = TREE_TYPE (e);
2423   tree result;
2424
2425   /* We cannot ignore const expressions because it might be a reference
2426      to a const array but whose index contains side-effects.  But we can
2427      ignore things that are actual constant or that already have been
2428      handled by this function.  */
2429   if (TREE_CONSTANT (e) || code == SAVE_EXPR)
2430     return e;
2431
2432   switch (TREE_CODE_CLASS (code))
2433     {
2434     case tcc_exceptional:
2435     case tcc_declaration:
2436     case tcc_comparison:
2437     case tcc_expression:
2438     case tcc_reference:
2439     case tcc_vl_exp:
2440       /* If this is a COMPONENT_REF of a fat pointer, save the entire
2441          fat pointer.  This may be more efficient, but will also allow
2442          us to more easily find the match for the PLACEHOLDER_EXPR.  */
2443       if (code == COMPONENT_REF
2444           && TYPE_IS_FAT_POINTER_P (TREE_TYPE (TREE_OPERAND (e, 0))))
2445         result
2446           = build3 (code, type,
2447                     gnat_stabilize_reference_1 (TREE_OPERAND (e, 0), force),
2448                     TREE_OPERAND (e, 1), TREE_OPERAND (e, 2));
2449       /* If the expression has side-effects, then encase it in a SAVE_EXPR
2450          so that it will only be evaluated once.  */
2451       /* The tcc_reference and tcc_comparison classes could be handled as
2452          below, but it is generally faster to only evaluate them once.  */
2453       else if (TREE_SIDE_EFFECTS (e) || force)
2454         return save_expr (e);
2455       else
2456         return e;
2457       break;
2458
2459     case tcc_binary:
2460       /* Recursively stabilize each operand.  */
2461       result
2462         = build2 (code, type,
2463                   gnat_stabilize_reference_1 (TREE_OPERAND (e, 0), force),
2464                   gnat_stabilize_reference_1 (TREE_OPERAND (e, 1), force));
2465       break;
2466
2467     case tcc_unary:
2468       /* Recursively stabilize each operand.  */
2469       result
2470         = build1 (code, type,
2471                   gnat_stabilize_reference_1 (TREE_OPERAND (e, 0), force));
2472       break;
2473
2474     default:
2475       gcc_unreachable ();
2476     }
2477
2478   /* See similar handling in gnat_stabilize_reference.  */
2479   TREE_READONLY (result) = TREE_READONLY (e);
2480   TREE_SIDE_EFFECTS (result) |= TREE_SIDE_EFFECTS (e);
2481   TREE_THIS_VOLATILE (result) = TREE_THIS_VOLATILE (e);
2482
2483   if (code == INDIRECT_REF || code == ARRAY_REF || code == ARRAY_RANGE_REF)
2484     TREE_THIS_NOTRAP (result) = TREE_THIS_NOTRAP (e);
2485
2486   return result;
2487 }
2488
2489 /* This is equivalent to stabilize_reference in tree.c but we know how to
2490    handle our own nodes and we take extra arguments.  FORCE says whether to
2491    force evaluation of everything.  We set SUCCESS to true unless we walk
2492    through something we don't know how to stabilize.  */
2493
2494 tree
2495 gnat_stabilize_reference (tree ref, bool force, bool *success)
2496 {
2497   tree type = TREE_TYPE (ref);
2498   enum tree_code code = TREE_CODE (ref);
2499   tree result;
2500
2501   /* Assume we'll success unless proven otherwise.  */
2502   if (success)
2503     *success = true;
2504
2505   switch (code)
2506     {
2507     case CONST_DECL:
2508     case VAR_DECL:
2509     case PARM_DECL:
2510     case RESULT_DECL:
2511       /* No action is needed in this case.  */
2512       return ref;
2513
2514     case ADDR_EXPR:
2515     CASE_CONVERT:
2516     case FLOAT_EXPR:
2517     case FIX_TRUNC_EXPR:
2518     case VIEW_CONVERT_EXPR:
2519       result
2520         = build1 (code, type,
2521                   gnat_stabilize_reference (TREE_OPERAND (ref, 0), force,
2522                                             success));
2523       break;
2524
2525     case INDIRECT_REF:
2526     case UNCONSTRAINED_ARRAY_REF:
2527       result = build1 (code, type,
2528                        gnat_stabilize_reference_1 (TREE_OPERAND (ref, 0),
2529                                                    force));
2530       break;
2531
2532     case COMPONENT_REF:
2533      result = build3 (COMPONENT_REF, type,
2534                       gnat_stabilize_reference (TREE_OPERAND (ref, 0), force,
2535                                                 success),
2536                       TREE_OPERAND (ref, 1), NULL_TREE);
2537       break;
2538
2539     case BIT_FIELD_REF:
2540       result = build3 (BIT_FIELD_REF, type,
2541                        gnat_stabilize_reference (TREE_OPERAND (ref, 0), force,
2542                                                  success),
2543                        gnat_stabilize_reference_1 (TREE_OPERAND (ref, 1),
2544                                                    force),
2545                        gnat_stabilize_reference_1 (TREE_OPERAND (ref, 2),
2546                                                    force));
2547       break;
2548
2549     case ARRAY_REF:
2550     case ARRAY_RANGE_REF:
2551       result = build4 (code, type,
2552                        gnat_stabilize_reference (TREE_OPERAND (ref, 0), force,
2553                                                  success),
2554                        gnat_stabilize_reference_1 (TREE_OPERAND (ref, 1),
2555                                                    force),
2556                        NULL_TREE, NULL_TREE);
2557       break;
2558
2559     case CALL_EXPR:
2560       result = gnat_stabilize_reference_1 (ref, force);
2561       break;
2562
2563     case COMPOUND_EXPR:
2564       result = build2 (COMPOUND_EXPR, type,
2565                        gnat_stabilize_reference (TREE_OPERAND (ref, 0), force,
2566                                                  success),
2567                        gnat_stabilize_reference_1 (TREE_OPERAND (ref, 1),
2568                                                    force));
2569       break;
2570
2571     case CONSTRUCTOR:
2572       /* Constructors with 1 element are used extensively to formally
2573          convert objects to special wrapping types.  */
2574       if (TREE_CODE (type) == RECORD_TYPE
2575           && VEC_length (constructor_elt, CONSTRUCTOR_ELTS (ref)) == 1)
2576         {
2577           tree index
2578             = VEC_index (constructor_elt, CONSTRUCTOR_ELTS (ref), 0)->index;
2579           tree value
2580             = VEC_index (constructor_elt, CONSTRUCTOR_ELTS (ref), 0)->value;
2581           result
2582             = build_constructor_single (type, index,
2583                                         gnat_stabilize_reference_1 (value,
2584                                                                     force));
2585         }
2586       else
2587         {
2588           if (success)
2589             *success = false;
2590           return ref;
2591         }
2592       break;
2593
2594     case ERROR_MARK:
2595       ref = error_mark_node;
2596
2597       /* ...  fall through to failure ... */
2598
2599       /* If arg isn't a kind of lvalue we recognize, make no change.
2600          Caller should recognize the error for an invalid lvalue.  */
2601     default:
2602       if (success)
2603         *success = false;
2604       return ref;
2605     }
2606
2607   /* TREE_THIS_VOLATILE and TREE_SIDE_EFFECTS set on the initial expression
2608      may not be sustained across some paths, such as the way via build1 for
2609      INDIRECT_REF.  We reset those flags here in the general case, which is
2610      consistent with the GCC version of this routine.
2611
2612      Special care should be taken regarding TREE_SIDE_EFFECTS, because some
2613      paths introduce side-effects where there was none initially (e.g. if a
2614      SAVE_EXPR is built) and we also want to keep track of that.  */
2615   TREE_READONLY (result) = TREE_READONLY (ref);
2616   TREE_SIDE_EFFECTS (result) |= TREE_SIDE_EFFECTS (ref);
2617   TREE_THIS_VOLATILE (result) = TREE_THIS_VOLATILE (ref);
2618
2619   return result;
2620 }