OSDN Git Service

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