FSF GCC merge 02/23/03
[official-gcc.git] / gcc / ada / exp_aggr.adb
bloba83b3b20fa817e1aaf16326d56d799acb99888d0
1 ------------------------------------------------------------------------------
2 -- --
3 -- GNAT COMPILER COMPONENTS --
4 -- --
5 -- E X P _ A G G R --
6 -- --
7 -- B o d y --
8 -- --
9 -- --
10 -- Copyright (C) 1992-2002 Free Software Foundation, Inc. --
11 -- --
12 -- GNAT is free software; you can redistribute it and/or modify it under --
13 -- terms of the GNU General Public License as published by the Free Soft- --
14 -- ware Foundation; either version 2, or (at your option) any later ver- --
15 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
16 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
17 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
18 -- for more details. You should have received a copy of the GNU General --
19 -- Public License distributed with GNAT; see file COPYING. If not, write --
20 -- to the Free Software Foundation, 59 Temple Place - Suite 330, Boston, --
21 -- MA 02111-1307, USA. --
22 -- --
23 -- GNAT was originally developed by the GNAT team at New York University. --
24 -- Extensive contributions were provided by Ada Core Technologies Inc. --
25 -- --
26 ------------------------------------------------------------------------------
28 with Atree; use Atree;
29 with Checks; use Checks;
30 with Debug; use Debug;
31 with Einfo; use Einfo;
32 with Elists; use Elists;
33 with Expander; use Expander;
34 with Exp_Util; use Exp_Util;
35 with Exp_Ch3; use Exp_Ch3;
36 with Exp_Ch7; use Exp_Ch7;
37 with Freeze; use Freeze;
38 with Hostparm; use Hostparm;
39 with Itypes; use Itypes;
40 with Lib; use Lib;
41 with Nmake; use Nmake;
42 with Nlists; use Nlists;
43 with Restrict; use Restrict;
44 with Rtsfind; use Rtsfind;
45 with Ttypes; use Ttypes;
46 with Sem; use Sem;
47 with Sem_Ch3; use Sem_Ch3;
48 with Sem_Eval; use Sem_Eval;
49 with Sem_Res; use Sem_Res;
50 with Sem_Util; use Sem_Util;
51 with Sinfo; use Sinfo;
52 with Snames; use Snames;
53 with Stand; use Stand;
54 with Tbuild; use Tbuild;
55 with Uintp; use Uintp;
57 package body Exp_Aggr is
59 type Case_Bounds is record
60 Choice_Lo : Node_Id;
61 Choice_Hi : Node_Id;
62 Choice_Node : Node_Id;
63 end record;
65 type Case_Table_Type is array (Nat range <>) of Case_Bounds;
66 -- Table type used by Check_Case_Choices procedure
68 procedure Sort_Case_Table (Case_Table : in out Case_Table_Type);
69 -- Sort the Case Table using the Lower Bound of each Choice as the key.
70 -- A simple insertion sort is used since the number of choices in a case
71 -- statement of variant part will usually be small and probably in near
72 -- sorted order.
74 ------------------------------------------------------
75 -- Local subprograms for Record Aggregate Expansion --
76 ------------------------------------------------------
78 procedure Expand_Record_Aggregate
79 (N : Node_Id;
80 Orig_Tag : Node_Id := Empty;
81 Parent_Expr : Node_Id := Empty);
82 -- This is the top level procedure for record aggregate expansion.
83 -- Expansion for record aggregates needs expand aggregates for tagged
84 -- record types. Specifically Expand_Record_Aggregate adds the Tag
85 -- field in front of the Component_Association list that was created
86 -- during resolution by Resolve_Record_Aggregate.
88 -- N is the record aggregate node.
89 -- Orig_Tag is the value of the Tag that has to be provided for this
90 -- specific aggregate. It carries the tag corresponding to the type
91 -- of the outermost aggregate during the recursive expansion
92 -- Parent_Expr is the ancestor part of the original extension
93 -- aggregate
95 procedure Convert_To_Assignments (N : Node_Id; Typ : Entity_Id);
96 -- N is an N_Aggregate of a N_Extension_Aggregate. Typ is the type of
97 -- the aggregate. Transform the given aggregate into a sequence of
98 -- assignments component per component.
100 function Build_Record_Aggr_Code
101 (N : Node_Id;
102 Typ : Entity_Id;
103 Target : Node_Id;
104 Flist : Node_Id := Empty;
105 Obj : Entity_Id := Empty)
106 return List_Id;
107 -- N is an N_Aggregate or a N_Extension_Aggregate. Typ is the type
108 -- of the aggregate. Target is an expression containing the
109 -- location on which the component by component assignments will
110 -- take place. Returns the list of assignments plus all other
111 -- adjustments needed for tagged and controlled types. Flist is an
112 -- expression representing the finalization list on which to
113 -- attach the controlled components if any. Obj is present in the
114 -- object declaration and dynamic allocation cases, it contains
115 -- an entity that allows to know if the value being created needs to be
116 -- attached to the final list in case of pragma finalize_Storage_Only.
118 procedure Initialize_Discriminants (N : Node_Id; Typ : Entity_Id);
119 -- If the type of the aggregate is a type extension with renamed discrimi-
120 -- nants, we must initialize the hidden discriminants of the parent.
121 -- Otherwise, the target object must not be initialized. The discriminants
122 -- are initialized by calling the initialization procedure for the type.
123 -- This is incorrect if the initialization of other components has any
124 -- side effects. We restrict this call to the case where the parent type
125 -- has a variant part, because this is the only case where the hidden
126 -- discriminants are accessed, namely when calling discriminant checking
127 -- functions of the parent type, and when applying a stream attribute to
128 -- an object of the derived type.
130 -----------------------------------------------------
131 -- Local Subprograms for Array Aggregate Expansion --
132 -----------------------------------------------------
134 procedure Convert_To_Positional
135 (N : Node_Id;
136 Max_Others_Replicate : Nat := 5;
137 Handle_Bit_Packed : Boolean := False);
138 -- If possible, convert named notation to positional notation. This
139 -- conversion is possible only in some static cases. If the conversion
140 -- is possible, then N is rewritten with the analyzed converted
141 -- aggregate. The parameter Max_Others_Replicate controls the maximum
142 -- number of values corresponding to an others choice that will be
143 -- converted to positional notation (the default of 5 is the normal
144 -- limit, and reflects the fact that normally the loop is better than
145 -- a lot of separate assignments). Note that this limit gets overridden
146 -- in any case if either of the restrictions No_Elaboration_Code or
147 -- No_Implicit_Loops is set. The parameter Handle_Bit_Packed is usually
148 -- set False (since we do not expect the back end to handle bit packed
149 -- arrays, so the normal case of conversion is pointless), but in the
150 -- special case of a call from Packed_Array_Aggregate_Handled, we set
151 -- this parameter to True, since these are cases we handle in there.
153 procedure Expand_Array_Aggregate (N : Node_Id);
154 -- This is the top-level routine to perform array aggregate expansion.
155 -- N is the N_Aggregate node to be expanded.
157 function Backend_Processing_Possible (N : Node_Id) return Boolean;
158 -- This function checks if array aggregate N can be processed directly
159 -- by Gigi. If this is the case True is returned.
161 function Build_Array_Aggr_Code
162 (N : Node_Id;
163 Index : Node_Id;
164 Into : Node_Id;
165 Scalar_Comp : Boolean;
166 Indices : List_Id := No_List;
167 Flist : Node_Id := Empty)
168 return List_Id;
169 -- This recursive routine returns a list of statements containing the
170 -- loops and assignments that are needed for the expansion of the array
171 -- aggregate N.
173 -- N is the (sub-)aggregate node to be expanded into code.
175 -- Index is the index node corresponding to the array sub-aggregate N.
177 -- Into is the target expression into which we are copying the aggregate.
179 -- Scalar_Comp is True if the component type of the aggregate is scalar.
181 -- Indices is the current list of expressions used to index the
182 -- object we are writing into.
184 -- Flist is an expression representing the finalization list on which
185 -- to attach the controlled components if any.
187 function Number_Of_Choices (N : Node_Id) return Nat;
188 -- Returns the number of discrete choices (not including the others choice
189 -- if present) contained in (sub-)aggregate N.
191 function Late_Expansion
192 (N : Node_Id;
193 Typ : Entity_Id;
194 Target : Node_Id;
195 Flist : Node_Id := Empty;
196 Obj : Entity_Id := Empty)
197 return List_Id;
198 -- N is a nested (record or array) aggregate that has been marked
199 -- with 'Delay_Expansion'. Typ is the expected type of the
200 -- aggregate and Target is a (duplicable) expression that will
201 -- hold the result of the aggregate expansion. Flist is the
202 -- finalization list to be used to attach controlled
203 -- components. 'Obj' when non empty, carries the original object
204 -- being initialized in order to know if it needs to be attached
205 -- to the previous parameter which may not be the case when
206 -- Finalize_Storage_Only is set. Basically this procedure is used
207 -- to implement top-down expansions of nested aggregates. This is
208 -- necessary for avoiding temporaries at each level as well as for
209 -- propagating the right internal finalization list.
211 function Make_OK_Assignment_Statement
212 (Sloc : Source_Ptr;
213 Name : Node_Id;
214 Expression : Node_Id)
215 return Node_Id;
216 -- This is like Make_Assignment_Statement, except that Assignment_OK
217 -- is set in the left operand. All assignments built by this unit
218 -- use this routine. This is needed to deal with assignments to
219 -- initialized constants that are done in place.
221 function Packed_Array_Aggregate_Handled (N : Node_Id) return Boolean;
222 -- Given an array aggregate, this function handles the case of a packed
223 -- array aggregate with all constant values, where the aggregate can be
224 -- evaluated at compile time. If this is possible, then N is rewritten
225 -- to be its proper compile time value with all the components properly
226 -- assembled. The expression is analyzed and resolved and True is
227 -- returned. If this transformation is not possible, N is unchanged
228 -- and False is returned
230 function Safe_Slice_Assignment (N : Node_Id) return Boolean;
231 -- If a slice assignment has an aggregate with a single others_choice,
232 -- the assignment can be done in place even if bounds are not static,
233 -- by converting it into a loop over the discrete range of the slice.
235 ---------------------------------
236 -- Backend_Processing_Possible --
237 ---------------------------------
239 -- Backend processing by Gigi/gcc is possible only if all the following
240 -- conditions are met:
242 -- 1. N is fully positional
244 -- 2. N is not a bit-packed array aggregate;
246 -- 3. The size of N's array type must be known at compile time. Note
247 -- that this implies that the component size is also known
249 -- 4. The array type of N does not follow the Fortran layout convention
250 -- or if it does it must be 1 dimensional.
252 -- 5. The array component type is tagged, which may necessitate
253 -- reassignment of proper tags.
255 function Backend_Processing_Possible (N : Node_Id) return Boolean is
256 Typ : constant Entity_Id := Etype (N);
257 -- Typ is the correct constrained array subtype of the aggregate.
259 function Static_Check (N : Node_Id; Index : Node_Id) return Boolean;
260 -- Recursively checks that N is fully positional, returns true if so.
262 ------------------
263 -- Static_Check --
264 ------------------
266 function Static_Check (N : Node_Id; Index : Node_Id) return Boolean is
267 Expr : Node_Id;
269 begin
270 -- Check for component associations
272 if Present (Component_Associations (N)) then
273 return False;
274 end if;
276 -- Recurse to check subaggregates, which may appear in qualified
277 -- expressions. If delayed, the front-end will have to expand.
279 Expr := First (Expressions (N));
281 while Present (Expr) loop
283 if Is_Delayed_Aggregate (Expr) then
284 return False;
285 end if;
287 if Present (Next_Index (Index))
288 and then not Static_Check (Expr, Next_Index (Index))
289 then
290 return False;
291 end if;
293 Next (Expr);
294 end loop;
296 return True;
297 end Static_Check;
299 -- Start of processing for Backend_Processing_Possible
301 begin
302 -- Checks 2 (array must not be bit packed)
304 if Is_Bit_Packed_Array (Typ) then
305 return False;
306 end if;
308 -- Checks 4 (array must not be multi-dimensional Fortran case)
310 if Convention (Typ) = Convention_Fortran
311 and then Number_Dimensions (Typ) > 1
312 then
313 return False;
314 end if;
316 -- Checks 3 (size of array must be known at compile time)
318 if not Size_Known_At_Compile_Time (Typ) then
319 return False;
320 end if;
322 -- Checks 1 (aggregate must be fully positional)
324 if not Static_Check (N, First_Index (Typ)) then
325 return False;
326 end if;
328 -- Checks 5 (if the component type is tagged, then we may need
329 -- to do tag adjustments; perhaps this should be refined to
330 -- check for any component associations that actually
331 -- need tag adjustment, along the lines of the test that's
332 -- done in Has_Delayed_Nested_Aggregate_Or_Tagged_Comps
333 -- for record aggregates with tagged components, but not
334 -- clear whether it's worthwhile ???; in the case of the
335 -- JVM, object tags are handled implicitly)
337 if Is_Tagged_Type (Component_Type (Typ)) and then not Java_VM then
338 return False;
339 end if;
341 -- Backend processing is possible
343 Set_Compile_Time_Known_Aggregate (N, True);
344 Set_Size_Known_At_Compile_Time (Etype (N), True);
345 return True;
346 end Backend_Processing_Possible;
348 ---------------------------
349 -- Build_Array_Aggr_Code --
350 ---------------------------
352 -- The code that we generate from a one dimensional aggregate is
354 -- 1. If the sub-aggregate contains discrete choices we
356 -- (a) Sort the discrete choices
358 -- (b) Otherwise for each discrete choice that specifies a range we
359 -- emit a loop. If a range specifies a maximum of three values, or
360 -- we are dealing with an expression we emit a sequence of
361 -- assignments instead of a loop.
363 -- (c) Generate the remaining loops to cover the others choice if any.
365 -- 2. If the aggregate contains positional elements we
367 -- (a) translate the positional elements in a series of assignments.
369 -- (b) Generate a final loop to cover the others choice if any.
370 -- Note that this final loop has to be a while loop since the case
372 -- L : Integer := Integer'Last;
373 -- H : Integer := Integer'Last;
374 -- A : array (L .. H) := (1, others =>0);
376 -- cannot be handled by a for loop. Thus for the following
378 -- array (L .. H) := (.. positional elements.., others =>E);
380 -- we always generate something like:
382 -- J : Index_Type := Index_Of_Last_Positional_Element;
383 -- while J < H loop
384 -- J := Index_Base'Succ (J)
385 -- Tmp (J) := E;
386 -- end loop;
388 function Build_Array_Aggr_Code
389 (N : Node_Id;
390 Index : Node_Id;
391 Into : Node_Id;
392 Scalar_Comp : Boolean;
393 Indices : List_Id := No_List;
394 Flist : Node_Id := Empty)
395 return List_Id
397 Loc : constant Source_Ptr := Sloc (N);
398 Index_Base : constant Entity_Id := Base_Type (Etype (Index));
399 Index_Base_L : constant Node_Id := Type_Low_Bound (Index_Base);
400 Index_Base_H : constant Node_Id := Type_High_Bound (Index_Base);
402 function Add (Val : Int; To : Node_Id) return Node_Id;
403 -- Returns an expression where Val is added to expression To,
404 -- unless To+Val is provably out of To's base type range.
405 -- To must be an already analyzed expression.
407 function Empty_Range (L, H : Node_Id) return Boolean;
408 -- Returns True if the range defined by L .. H is certainly empty.
410 function Equal (L, H : Node_Id) return Boolean;
411 -- Returns True if L = H for sure.
413 function Index_Base_Name return Node_Id;
414 -- Returns a new reference to the index type name.
416 function Gen_Assign (Ind : Node_Id; Expr : Node_Id) return List_Id;
417 -- Ind must be a side-effect free expression.
418 -- If the input aggregate N to Build_Loop contains no sub-aggregates,
419 -- This routine returns the assignment statement
421 -- Into (Indices, Ind) := Expr;
423 -- Otherwise we call Build_Code recursively.
425 function Gen_Loop (L, H : Node_Id; Expr : Node_Id) return List_Id;
426 -- Nodes L and H must be side-effect free expressions.
427 -- If the input aggregate N to Build_Loop contains no sub-aggregates,
428 -- This routine returns the for loop statement
430 -- for J in Index_Base'(L) .. Index_Base'(H) loop
431 -- Into (Indices, J) := Expr;
432 -- end loop;
434 -- Otherwise we call Build_Code recursively.
435 -- As an optimization if the loop covers 3 or less scalar elements we
436 -- generate a sequence of assignments.
438 function Gen_While (L, H : Node_Id; Expr : Node_Id) return List_Id;
439 -- Nodes L and H must be side-effect free expressions.
440 -- If the input aggregate N to Build_Loop contains no sub-aggregates,
441 -- This routine returns the while loop statement
443 -- J : Index_Base := L;
444 -- while J < H loop
445 -- J := Index_Base'Succ (J);
446 -- Into (Indices, J) := Expr;
447 -- end loop;
449 -- Otherwise we call Build_Code recursively.
451 function Local_Compile_Time_Known_Value (E : Node_Id) return Boolean;
452 function Local_Expr_Value (E : Node_Id) return Uint;
453 -- These two Local routines are used to replace the corresponding ones
454 -- in sem_eval because while processing the bounds of an aggregate with
455 -- discrete choices whose index type is an enumeration, we build static
456 -- expressions not recognized by Compile_Time_Known_Value as such since
457 -- they have not yet been analyzed and resolved. All the expressions in
458 -- question are things like Index_Base_Name'Val (Const) which we can
459 -- easily recognize as being constant.
461 ---------
462 -- Add --
463 ---------
465 function Add (Val : Int; To : Node_Id) return Node_Id is
466 Expr_Pos : Node_Id;
467 Expr : Node_Id;
468 To_Pos : Node_Id;
470 U_To : Uint;
471 U_Val : Uint := UI_From_Int (Val);
473 begin
474 -- Note: do not try to optimize the case of Val = 0, because
475 -- we need to build a new node with the proper Sloc value anyway.
477 -- First test if we can do constant folding
479 if Local_Compile_Time_Known_Value (To) then
480 U_To := Local_Expr_Value (To) + Val;
482 -- Determine if our constant is outside the range of the index.
483 -- If so return an Empty node. This empty node will be caught
484 -- by Empty_Range below.
486 if Compile_Time_Known_Value (Index_Base_L)
487 and then U_To < Expr_Value (Index_Base_L)
488 then
489 return Empty;
491 elsif Compile_Time_Known_Value (Index_Base_H)
492 and then U_To > Expr_Value (Index_Base_H)
493 then
494 return Empty;
495 end if;
497 Expr_Pos := Make_Integer_Literal (Loc, U_To);
498 Set_Is_Static_Expression (Expr_Pos);
500 if not Is_Enumeration_Type (Index_Base) then
501 Expr := Expr_Pos;
503 -- If we are dealing with enumeration return
504 -- Index_Base'Val (Expr_Pos)
506 else
507 Expr :=
508 Make_Attribute_Reference
509 (Loc,
510 Prefix => Index_Base_Name,
511 Attribute_Name => Name_Val,
512 Expressions => New_List (Expr_Pos));
513 end if;
515 return Expr;
516 end if;
518 -- If we are here no constant folding possible
520 if not Is_Enumeration_Type (Index_Base) then
521 Expr :=
522 Make_Op_Add (Loc,
523 Left_Opnd => Duplicate_Subexpr (To),
524 Right_Opnd => Make_Integer_Literal (Loc, U_Val));
526 -- If we are dealing with enumeration return
527 -- Index_Base'Val (Index_Base'Pos (To) + Val)
529 else
530 To_Pos :=
531 Make_Attribute_Reference
532 (Loc,
533 Prefix => Index_Base_Name,
534 Attribute_Name => Name_Pos,
535 Expressions => New_List (Duplicate_Subexpr (To)));
537 Expr_Pos :=
538 Make_Op_Add (Loc,
539 Left_Opnd => To_Pos,
540 Right_Opnd => Make_Integer_Literal (Loc, U_Val));
542 Expr :=
543 Make_Attribute_Reference
544 (Loc,
545 Prefix => Index_Base_Name,
546 Attribute_Name => Name_Val,
547 Expressions => New_List (Expr_Pos));
548 end if;
550 return Expr;
551 end Add;
553 -----------------
554 -- Empty_Range --
555 -----------------
557 function Empty_Range (L, H : Node_Id) return Boolean is
558 Is_Empty : Boolean := False;
559 Low : Node_Id;
560 High : Node_Id;
562 begin
563 -- First check if L or H were already detected as overflowing the
564 -- index base range type by function Add above. If this is so Add
565 -- returns the empty node.
567 if No (L) or else No (H) then
568 return True;
569 end if;
571 for J in 1 .. 3 loop
572 case J is
574 -- L > H range is empty
576 when 1 =>
577 Low := L;
578 High := H;
580 -- B_L > H range must be empty
582 when 2 =>
583 Low := Index_Base_L;
584 High := H;
586 -- L > B_H range must be empty
588 when 3 =>
589 Low := L;
590 High := Index_Base_H;
591 end case;
593 if Local_Compile_Time_Known_Value (Low)
594 and then Local_Compile_Time_Known_Value (High)
595 then
596 Is_Empty :=
597 UI_Gt (Local_Expr_Value (Low), Local_Expr_Value (High));
598 end if;
600 exit when Is_Empty;
601 end loop;
603 return Is_Empty;
604 end Empty_Range;
606 -----------
607 -- Equal --
608 -----------
610 function Equal (L, H : Node_Id) return Boolean is
611 begin
612 if L = H then
613 return True;
615 elsif Local_Compile_Time_Known_Value (L)
616 and then Local_Compile_Time_Known_Value (H)
617 then
618 return UI_Eq (Local_Expr_Value (L), Local_Expr_Value (H));
619 end if;
621 return False;
622 end Equal;
624 ----------------
625 -- Gen_Assign --
626 ----------------
628 function Gen_Assign (Ind : Node_Id; Expr : Node_Id) return List_Id is
629 L : List_Id := New_List;
630 F : Entity_Id;
631 A : Node_Id;
633 New_Indices : List_Id;
634 Indexed_Comp : Node_Id;
635 Expr_Q : Node_Id;
636 Comp_Type : Entity_Id := Empty;
638 function Add_Loop_Actions (Lis : List_Id) return List_Id;
639 -- Collect insert_actions generated in the construction of a
640 -- loop, and prepend them to the sequence of assignments to
641 -- complete the eventual body of the loop.
643 ----------------------
644 -- Add_Loop_Actions --
645 ----------------------
647 function Add_Loop_Actions (Lis : List_Id) return List_Id is
648 Res : List_Id;
650 begin
651 if Nkind (Parent (Expr)) = N_Component_Association
652 and then Present (Loop_Actions (Parent (Expr)))
653 then
654 Append_List (Lis, Loop_Actions (Parent (Expr)));
655 Res := Loop_Actions (Parent (Expr));
656 Set_Loop_Actions (Parent (Expr), No_List);
657 return Res;
659 else
660 return Lis;
661 end if;
662 end Add_Loop_Actions;
664 -- Start of processing for Gen_Assign
666 begin
667 if No (Indices) then
668 New_Indices := New_List;
669 else
670 New_Indices := New_Copy_List_Tree (Indices);
671 end if;
673 Append_To (New_Indices, Ind);
675 if Present (Flist) then
676 F := New_Copy_Tree (Flist);
678 elsif Present (Etype (N)) and then Controlled_Type (Etype (N)) then
679 if Is_Entity_Name (Into)
680 and then Present (Scope (Entity (Into)))
681 then
682 F := Find_Final_List (Scope (Entity (Into)));
684 else
685 F := Find_Final_List (Current_Scope);
686 end if;
687 else
688 F := 0;
689 end if;
691 if Present (Next_Index (Index)) then
692 return
693 Add_Loop_Actions (
694 Build_Array_Aggr_Code
695 (Expr, Next_Index (Index),
696 Into, Scalar_Comp, New_Indices, F));
697 end if;
699 -- If we get here then we are at a bottom-level (sub-)aggregate
701 Indexed_Comp := Checks_Off (
702 Make_Indexed_Component (Loc,
703 Prefix => New_Copy_Tree (Into),
704 Expressions => New_Indices));
706 Set_Assignment_OK (Indexed_Comp);
708 if Nkind (Expr) = N_Qualified_Expression then
709 Expr_Q := Expression (Expr);
710 else
711 Expr_Q := Expr;
712 end if;
714 if Present (Etype (N))
715 and then Etype (N) /= Any_Composite
716 then
717 Comp_Type := Component_Type (Etype (N));
719 elsif Present (Next (First (New_Indices))) then
721 -- this is a multidimensional array. Recover the component
722 -- type from the outermost aggregate, because subaggregates
723 -- do not have an assigned type.
725 declare
726 P : Node_Id := Parent (Expr);
728 begin
729 while Present (P) loop
731 if Nkind (P) = N_Aggregate
732 and then Present (Etype (P))
733 then
734 Comp_Type := Component_Type (Etype (P));
735 exit;
737 else
738 P := Parent (P);
739 end if;
740 end loop;
741 end;
742 end if;
744 if (Nkind (Expr_Q) = N_Aggregate
745 or else Nkind (Expr_Q) = N_Extension_Aggregate)
746 then
748 -- At this stage the Expression may not have been
749 -- analyzed yet because the array aggregate code has not
750 -- been updated to use the Expansion_Delayed flag and
751 -- avoid analysis altogether to solve the same problem
752 -- (see Resolve_Aggr_Expr) so let's do the analysis of
753 -- non-array aggregates now in order to get the value of
754 -- Expansion_Delayed flag for the inner aggregate ???
756 if Present (Comp_Type) and then not Is_Array_Type (Comp_Type) then
757 Analyze_And_Resolve (Expr_Q, Comp_Type);
758 end if;
760 if Is_Delayed_Aggregate (Expr_Q) then
761 return
762 Add_Loop_Actions (
763 Late_Expansion (Expr_Q, Etype (Expr_Q), Indexed_Comp, F));
764 end if;
765 end if;
767 -- Now generate the assignment with no associated controlled
768 -- actions since the target of the assignment may not have
769 -- been initialized, it is not possible to Finalize it as
770 -- expected by normal controlled assignment. The rest of the
771 -- controlled actions are done manually with the proper
772 -- finalization list coming from the context.
774 A :=
775 Make_OK_Assignment_Statement (Loc,
776 Name => Indexed_Comp,
777 Expression => New_Copy_Tree (Expr));
779 if Present (Comp_Type) and then Controlled_Type (Comp_Type) then
780 Set_No_Ctrl_Actions (A);
781 end if;
783 Append_To (L, A);
785 -- Adjust the tag if tagged (because of possible view
786 -- conversions), unless compiling for the Java VM
787 -- where tags are implicit.
789 if Present (Comp_Type)
790 and then Is_Tagged_Type (Comp_Type)
791 and then not Java_VM
792 then
793 A :=
794 Make_OK_Assignment_Statement (Loc,
795 Name =>
796 Make_Selected_Component (Loc,
797 Prefix => New_Copy_Tree (Indexed_Comp),
798 Selector_Name =>
799 New_Reference_To (Tag_Component (Comp_Type), Loc)),
801 Expression =>
802 Unchecked_Convert_To (RTE (RE_Tag),
803 New_Reference_To (
804 Access_Disp_Table (Comp_Type), Loc)));
806 Append_To (L, A);
807 end if;
809 -- Adjust and Attach the component to the proper final list
810 -- which can be the controller of the outer record object or
811 -- the final list associated with the scope
813 if Present (Comp_Type) and then Controlled_Type (Comp_Type) then
814 Append_List_To (L,
815 Make_Adjust_Call (
816 Ref => New_Copy_Tree (Indexed_Comp),
817 Typ => Comp_Type,
818 Flist_Ref => F,
819 With_Attach => Make_Integer_Literal (Loc, 1)));
820 end if;
822 return Add_Loop_Actions (L);
823 end Gen_Assign;
825 --------------
826 -- Gen_Loop --
827 --------------
829 function Gen_Loop (L, H : Node_Id; Expr : Node_Id) return List_Id is
830 L_J : Node_Id;
832 L_Range : Node_Id;
833 -- Index_Base'(L) .. Index_Base'(H)
835 L_Iteration_Scheme : Node_Id;
836 -- L_J in Index_Base'(L) .. Index_Base'(H)
838 L_Body : List_Id;
839 -- The statements to execute in the loop
841 S : List_Id := New_List;
842 -- list of statement
844 Tcopy : Node_Id;
845 -- Copy of expression tree, used for checking purposes
847 begin
848 -- If loop bounds define an empty range return the null statement
850 if Empty_Range (L, H) then
851 Append_To (S, Make_Null_Statement (Loc));
853 -- The expression must be type-checked even though no component
854 -- of the aggregate will have this value. This is done only for
855 -- actual components of the array, not for subaggregates. Do the
856 -- check on a copy, because the expression may be shared among
857 -- several choices, some of which might be non-null.
859 if Present (Etype (N))
860 and then Is_Array_Type (Etype (N))
861 and then No (Next_Index (Index))
862 then
863 Expander_Mode_Save_And_Set (False);
864 Tcopy := New_Copy_Tree (Expr);
865 Set_Parent (Tcopy, N);
866 Analyze_And_Resolve (Tcopy, Component_Type (Etype (N)));
867 Expander_Mode_Restore;
868 end if;
870 return S;
872 -- If loop bounds are the same then generate an assignment
874 elsif Equal (L, H) then
875 return Gen_Assign (New_Copy_Tree (L), Expr);
877 -- If H - L <= 2 then generate a sequence of assignments
878 -- when we are processing the bottom most aggregate and it contains
879 -- scalar components.
881 elsif No (Next_Index (Index))
882 and then Scalar_Comp
883 and then Local_Compile_Time_Known_Value (L)
884 and then Local_Compile_Time_Known_Value (H)
885 and then Local_Expr_Value (H) - Local_Expr_Value (L) <= 2
886 then
887 Append_List_To (S, Gen_Assign (New_Copy_Tree (L), Expr));
888 Append_List_To (S, Gen_Assign (Add (1, To => L), Expr));
890 if Local_Expr_Value (H) - Local_Expr_Value (L) = 2 then
891 Append_List_To (S, Gen_Assign (Add (2, To => L), Expr));
892 end if;
894 return S;
895 end if;
897 -- Otherwise construct the loop, starting with the loop index L_J
899 L_J := Make_Defining_Identifier (Loc, New_Internal_Name ('J'));
901 -- Construct "L .. H"
903 L_Range :=
904 Make_Range
905 (Loc,
906 Low_Bound => Make_Qualified_Expression
907 (Loc,
908 Subtype_Mark => Index_Base_Name,
909 Expression => L),
910 High_Bound => Make_Qualified_Expression
911 (Loc,
912 Subtype_Mark => Index_Base_Name,
913 Expression => H));
915 -- Construct "for L_J in Index_Base range L .. H"
917 L_Iteration_Scheme :=
918 Make_Iteration_Scheme
919 (Loc,
920 Loop_Parameter_Specification =>
921 Make_Loop_Parameter_Specification
922 (Loc,
923 Defining_Identifier => L_J,
924 Discrete_Subtype_Definition => L_Range));
926 -- Construct the statements to execute in the loop body
928 L_Body := Gen_Assign (New_Reference_To (L_J, Loc), Expr);
930 -- Construct the final loop
932 Append_To (S, Make_Implicit_Loop_Statement
933 (Node => N,
934 Identifier => Empty,
935 Iteration_Scheme => L_Iteration_Scheme,
936 Statements => L_Body));
938 return S;
939 end Gen_Loop;
941 ---------------
942 -- Gen_While --
943 ---------------
945 -- The code built is
947 -- W_J : Index_Base := L;
948 -- while W_J < H loop
949 -- W_J := Index_Base'Succ (W);
950 -- L_Body;
951 -- end loop;
953 function Gen_While (L, H : Node_Id; Expr : Node_Id) return List_Id is
955 W_J : Node_Id;
957 W_Decl : Node_Id;
958 -- W_J : Base_Type := L;
960 W_Iteration_Scheme : Node_Id;
961 -- while W_J < H
963 W_Index_Succ : Node_Id;
964 -- Index_Base'Succ (J)
966 W_Increment : Node_Id;
967 -- W_J := Index_Base'Succ (W)
969 W_Body : List_Id := New_List;
970 -- The statements to execute in the loop
972 S : List_Id := New_List;
973 -- list of statement
975 begin
976 -- If loop bounds define an empty range or are equal return null
978 if Empty_Range (L, H) or else Equal (L, H) then
979 Append_To (S, Make_Null_Statement (Loc));
980 return S;
981 end if;
983 -- Build the decl of W_J
985 W_J := Make_Defining_Identifier (Loc, New_Internal_Name ('J'));
986 W_Decl :=
987 Make_Object_Declaration
988 (Loc,
989 Defining_Identifier => W_J,
990 Object_Definition => Index_Base_Name,
991 Expression => L);
993 -- Theoretically we should do a New_Copy_Tree (L) here, but we know
994 -- that in this particular case L is a fresh Expr generated by
995 -- Add which we are the only ones to use.
997 Append_To (S, W_Decl);
999 -- construct " while W_J < H"
1001 W_Iteration_Scheme :=
1002 Make_Iteration_Scheme
1003 (Loc,
1004 Condition => Make_Op_Lt
1005 (Loc,
1006 Left_Opnd => New_Reference_To (W_J, Loc),
1007 Right_Opnd => New_Copy_Tree (H)));
1009 -- Construct the statements to execute in the loop body
1011 W_Index_Succ :=
1012 Make_Attribute_Reference
1013 (Loc,
1014 Prefix => Index_Base_Name,
1015 Attribute_Name => Name_Succ,
1016 Expressions => New_List (New_Reference_To (W_J, Loc)));
1018 W_Increment :=
1019 Make_OK_Assignment_Statement
1020 (Loc,
1021 Name => New_Reference_To (W_J, Loc),
1022 Expression => W_Index_Succ);
1024 Append_To (W_Body, W_Increment);
1025 Append_List_To (W_Body,
1026 Gen_Assign (New_Reference_To (W_J, Loc), Expr));
1028 -- Construct the final loop
1030 Append_To (S, Make_Implicit_Loop_Statement
1031 (Node => N,
1032 Identifier => Empty,
1033 Iteration_Scheme => W_Iteration_Scheme,
1034 Statements => W_Body));
1036 return S;
1037 end Gen_While;
1039 ---------------------
1040 -- Index_Base_Name --
1041 ---------------------
1043 function Index_Base_Name return Node_Id is
1044 begin
1045 return New_Reference_To (Index_Base, Sloc (N));
1046 end Index_Base_Name;
1048 ------------------------------------
1049 -- Local_Compile_Time_Known_Value --
1050 ------------------------------------
1052 function Local_Compile_Time_Known_Value (E : Node_Id) return Boolean is
1053 begin
1054 return Compile_Time_Known_Value (E)
1055 or else
1056 (Nkind (E) = N_Attribute_Reference
1057 and then Attribute_Name (E) = Name_Val
1058 and then Compile_Time_Known_Value (First (Expressions (E))));
1059 end Local_Compile_Time_Known_Value;
1061 ----------------------
1062 -- Local_Expr_Value --
1063 ----------------------
1065 function Local_Expr_Value (E : Node_Id) return Uint is
1066 begin
1067 if Compile_Time_Known_Value (E) then
1068 return Expr_Value (E);
1069 else
1070 return Expr_Value (First (Expressions (E)));
1071 end if;
1072 end Local_Expr_Value;
1074 -- Build_Array_Aggr_Code Variables
1076 Assoc : Node_Id;
1077 Choice : Node_Id;
1078 Expr : Node_Id;
1080 Others_Expr : Node_Id := Empty;
1082 Aggr_L : constant Node_Id := Low_Bound (Aggregate_Bounds (N));
1083 Aggr_H : constant Node_Id := High_Bound (Aggregate_Bounds (N));
1084 -- The aggregate bounds of this specific sub-aggregate. Note that if
1085 -- the code generated by Build_Array_Aggr_Code is executed then these
1086 -- bounds are OK. Otherwise a Constraint_Error would have been raised.
1088 Aggr_Low : constant Node_Id := Duplicate_Subexpr (Aggr_L);
1089 Aggr_High : constant Node_Id := Duplicate_Subexpr (Aggr_H);
1090 -- After Duplicate_Subexpr these are side-effect free.
1092 Low : Node_Id;
1093 High : Node_Id;
1095 Nb_Choices : Nat := 0;
1096 Table : Case_Table_Type (1 .. Number_Of_Choices (N));
1097 -- Used to sort all the different choice values
1099 Nb_Elements : Int;
1100 -- Number of elements in the positional aggregate
1102 New_Code : List_Id := New_List;
1104 -- Start of processing for Build_Array_Aggr_Code
1106 begin
1107 -- STEP 1: Process component associations
1109 if No (Expressions (N)) then
1111 -- STEP 1 (a): Sort the discrete choices
1113 Assoc := First (Component_Associations (N));
1114 while Present (Assoc) loop
1116 Choice := First (Choices (Assoc));
1117 while Present (Choice) loop
1119 if Nkind (Choice) = N_Others_Choice then
1120 Others_Expr := Expression (Assoc);
1121 exit;
1122 end if;
1124 Get_Index_Bounds (Choice, Low, High);
1126 Nb_Choices := Nb_Choices + 1;
1127 Table (Nb_Choices) := (Choice_Lo => Low,
1128 Choice_Hi => High,
1129 Choice_Node => Expression (Assoc));
1131 Next (Choice);
1132 end loop;
1134 Next (Assoc);
1135 end loop;
1137 -- If there is more than one set of choices these must be static
1138 -- and we can therefore sort them. Remember that Nb_Choices does not
1139 -- account for an others choice.
1141 if Nb_Choices > 1 then
1142 Sort_Case_Table (Table);
1143 end if;
1145 -- STEP 1 (b): take care of the whole set of discrete choices.
1147 for J in 1 .. Nb_Choices loop
1148 Low := Table (J).Choice_Lo;
1149 High := Table (J).Choice_Hi;
1150 Expr := Table (J).Choice_Node;
1152 Append_List (Gen_Loop (Low, High, Expr), To => New_Code);
1153 end loop;
1155 -- STEP 1 (c): generate the remaining loops to cover others choice
1156 -- We don't need to generate loops over empty gaps, but if there is
1157 -- a single empty range we must analyze the expression for semantics
1159 if Present (Others_Expr) then
1160 declare
1161 First : Boolean := True;
1163 begin
1164 for J in 0 .. Nb_Choices loop
1166 if J = 0 then
1167 Low := Aggr_Low;
1168 else
1169 Low := Add (1, To => Table (J).Choice_Hi);
1170 end if;
1172 if J = Nb_Choices then
1173 High := Aggr_High;
1174 else
1175 High := Add (-1, To => Table (J + 1).Choice_Lo);
1176 end if;
1178 -- If this is an expansion within an init_proc, make
1179 -- sure that discriminant references are replaced by
1180 -- the corresponding discriminal.
1182 if Inside_Init_Proc then
1183 if Is_Entity_Name (Low)
1184 and then Ekind (Entity (Low)) = E_Discriminant
1185 then
1186 Set_Entity (Low, Discriminal (Entity (Low)));
1187 end if;
1189 if Is_Entity_Name (High)
1190 and then Ekind (Entity (High)) = E_Discriminant
1191 then
1192 Set_Entity (High, Discriminal (Entity (High)));
1193 end if;
1194 end if;
1196 if First
1197 or else not Empty_Range (Low, High)
1198 then
1199 First := False;
1200 Append_List
1201 (Gen_Loop (Low, High, Others_Expr), To => New_Code);
1202 end if;
1203 end loop;
1204 end;
1205 end if;
1207 -- STEP 2: Process positional components
1209 else
1210 -- STEP 2 (a): Generate the assignments for each positional element
1211 -- Note that here we have to use Aggr_L rather than Aggr_Low because
1212 -- Aggr_L is analyzed and Add wants an analyzed expression.
1214 Expr := First (Expressions (N));
1215 Nb_Elements := -1;
1217 while Present (Expr) loop
1218 Nb_Elements := Nb_Elements + 1;
1219 Append_List (Gen_Assign (Add (Nb_Elements, To => Aggr_L), Expr),
1220 To => New_Code);
1221 Next (Expr);
1222 end loop;
1224 -- STEP 2 (b): Generate final loop if an others choice is present
1225 -- Here Nb_Elements gives the offset of the last positional element.
1227 if Present (Component_Associations (N)) then
1228 Assoc := Last (Component_Associations (N));
1229 Expr := Expression (Assoc);
1231 Append_List (Gen_While (Add (Nb_Elements, To => Aggr_L),
1232 Aggr_High,
1233 Expr),
1234 To => New_Code);
1235 end if;
1236 end if;
1238 return New_Code;
1239 end Build_Array_Aggr_Code;
1241 ----------------------------
1242 -- Build_Record_Aggr_Code --
1243 ----------------------------
1245 function Build_Record_Aggr_Code
1246 (N : Node_Id;
1247 Typ : Entity_Id;
1248 Target : Node_Id;
1249 Flist : Node_Id := Empty;
1250 Obj : Entity_Id := Empty)
1251 return List_Id
1253 Loc : constant Source_Ptr := Sloc (N);
1254 L : constant List_Id := New_List;
1255 Start_L : constant List_Id := New_List;
1256 N_Typ : constant Entity_Id := Etype (N);
1258 Comp : Node_Id;
1259 Instr : Node_Id;
1260 Ref : Node_Id;
1261 F : Node_Id;
1262 Comp_Type : Entity_Id;
1263 Selector : Entity_Id;
1264 Comp_Expr : Node_Id;
1265 Comp_Kind : Node_Kind;
1266 Expr_Q : Node_Id;
1268 Internal_Final_List : Node_Id;
1270 -- If this is an internal aggregate, the External_Final_List is an
1271 -- expression for the controller record of the enclosing type.
1272 -- If the current aggregate has several controlled components, this
1273 -- expression will appear in several calls to attach to the finali-
1274 -- zation list, and it must not be shared.
1276 External_Final_List : Node_Id;
1277 Ancestor_Is_Expression : Boolean := False;
1278 Ancestor_Is_Subtype_Mark : Boolean := False;
1280 Init_Typ : Entity_Id := Empty;
1281 Attach : Node_Id;
1283 function Get_Constraint_Association (T : Entity_Id) return Node_Id;
1284 -- Returns the first discriminant association in the constraint
1285 -- associated with T, if any, otherwise returns Empty.
1287 function Ancestor_Discriminant_Value (Disc : Entity_Id) return Node_Id;
1288 -- Returns the value that the given discriminant of an ancestor
1289 -- type should receive (in the absence of a conflict with the
1290 -- value provided by an ancestor part of an extension aggregate).
1292 procedure Check_Ancestor_Discriminants (Anc_Typ : Entity_Id);
1293 -- Check that each of the discriminant values defined by the
1294 -- ancestor part of an extension aggregate match the corresponding
1295 -- values provided by either an association of the aggregate or
1296 -- by the constraint imposed by a parent type (RM95-4.3.2(8)).
1298 function Init_Controller
1299 (Target : Node_Id;
1300 Typ : Entity_Id;
1301 F : Node_Id;
1302 Attach : Node_Id;
1303 Init_Pr : Boolean)
1304 return List_Id;
1305 -- returns the list of statements necessary to initialize the internal
1306 -- controller of the (possible) ancestor typ into target and attach
1307 -- it to finalization list F. Init_Pr conditions the call to the
1308 -- init_proc since it may already be done due to ancestor initialization
1310 ---------------------------------
1311 -- Ancestor_Discriminant_Value --
1312 ---------------------------------
1314 function Ancestor_Discriminant_Value (Disc : Entity_Id) return Node_Id is
1315 Assoc : Node_Id;
1316 Assoc_Elmt : Elmt_Id;
1317 Aggr_Comp : Entity_Id;
1318 Corresp_Disc : Entity_Id;
1319 Current_Typ : Entity_Id := Base_Type (Typ);
1320 Parent_Typ : Entity_Id;
1321 Parent_Disc : Entity_Id;
1322 Save_Assoc : Node_Id := Empty;
1324 begin
1325 -- First check any discriminant associations to see if
1326 -- any of them provide a value for the discriminant.
1328 if Present (Discriminant_Specifications (Parent (Current_Typ))) then
1329 Assoc := First (Component_Associations (N));
1330 while Present (Assoc) loop
1331 Aggr_Comp := Entity (First (Choices (Assoc)));
1333 if Ekind (Aggr_Comp) = E_Discriminant then
1334 Save_Assoc := Expression (Assoc);
1336 Corresp_Disc := Corresponding_Discriminant (Aggr_Comp);
1337 while Present (Corresp_Disc) loop
1338 -- If found a corresponding discriminant then return
1339 -- the value given in the aggregate. (Note: this is
1340 -- not correct in the presence of side effects. ???)
1342 if Disc = Corresp_Disc then
1343 return Duplicate_Subexpr (Expression (Assoc));
1344 end if;
1345 Corresp_Disc :=
1346 Corresponding_Discriminant (Corresp_Disc);
1347 end loop;
1348 end if;
1350 Next (Assoc);
1351 end loop;
1352 end if;
1354 -- No match found in aggregate, so chain up parent types to find
1355 -- a constraint that defines the value of the discriminant.
1357 Parent_Typ := Etype (Current_Typ);
1358 while Current_Typ /= Parent_Typ loop
1359 if Has_Discriminants (Parent_Typ) then
1360 Parent_Disc := First_Discriminant (Parent_Typ);
1362 -- We either get the association from the subtype indication
1363 -- of the type definition itself, or from the discriminant
1364 -- constraint associated with the type entity (which is
1365 -- preferable, but it's not always present ???)
1367 if Is_Empty_Elmt_List (
1368 Discriminant_Constraint (Current_Typ))
1369 then
1370 Assoc := Get_Constraint_Association (Current_Typ);
1371 Assoc_Elmt := No_Elmt;
1372 else
1373 Assoc_Elmt :=
1374 First_Elmt (Discriminant_Constraint (Current_Typ));
1375 Assoc := Node (Assoc_Elmt);
1376 end if;
1378 -- Traverse the discriminants of the parent type looking
1379 -- for one that corresponds.
1381 while Present (Parent_Disc) and then Present (Assoc) loop
1382 Corresp_Disc := Parent_Disc;
1383 while Present (Corresp_Disc)
1384 and then Disc /= Corresp_Disc
1385 loop
1386 Corresp_Disc :=
1387 Corresponding_Discriminant (Corresp_Disc);
1388 end loop;
1390 if Disc = Corresp_Disc then
1391 if Nkind (Assoc) = N_Discriminant_Association then
1392 Assoc := Expression (Assoc);
1393 end if;
1395 -- If the located association directly denotes
1396 -- a discriminant, then use the value of a saved
1397 -- association of the aggregate. This is a kludge
1398 -- to handle certain cases involving multiple
1399 -- discriminants mapped to a single discriminant
1400 -- of a descendant. It's not clear how to locate the
1401 -- appropriate discriminant value for such cases. ???
1403 if Is_Entity_Name (Assoc)
1404 and then Ekind (Entity (Assoc)) = E_Discriminant
1405 then
1406 Assoc := Save_Assoc;
1407 end if;
1409 return Duplicate_Subexpr (Assoc);
1410 end if;
1412 Next_Discriminant (Parent_Disc);
1414 if No (Assoc_Elmt) then
1415 Next (Assoc);
1416 else
1417 Next_Elmt (Assoc_Elmt);
1418 if Present (Assoc_Elmt) then
1419 Assoc := Node (Assoc_Elmt);
1420 else
1421 Assoc := Empty;
1422 end if;
1423 end if;
1424 end loop;
1425 end if;
1427 Current_Typ := Parent_Typ;
1428 Parent_Typ := Etype (Current_Typ);
1429 end loop;
1431 -- In some cases there's no ancestor value to locate (such as
1432 -- when an ancestor part given by an expression defines the
1433 -- discriminant value).
1435 return Empty;
1436 end Ancestor_Discriminant_Value;
1438 ----------------------------------
1439 -- Check_Ancestor_Discriminants --
1440 ----------------------------------
1442 procedure Check_Ancestor_Discriminants (Anc_Typ : Entity_Id) is
1443 Discr : Entity_Id := First_Discriminant (Base_Type (Anc_Typ));
1444 Disc_Value : Node_Id;
1445 Cond : Node_Id;
1447 begin
1448 while Present (Discr) loop
1449 Disc_Value := Ancestor_Discriminant_Value (Discr);
1451 if Present (Disc_Value) then
1452 Cond := Make_Op_Ne (Loc,
1453 Left_Opnd =>
1454 Make_Selected_Component (Loc,
1455 Prefix => New_Copy_Tree (Target),
1456 Selector_Name => New_Occurrence_Of (Discr, Loc)),
1457 Right_Opnd => Disc_Value);
1459 Append_To (L,
1460 Make_Raise_Constraint_Error (Loc,
1461 Condition => Cond,
1462 Reason => CE_Discriminant_Check_Failed));
1463 end if;
1465 Next_Discriminant (Discr);
1466 end loop;
1467 end Check_Ancestor_Discriminants;
1469 --------------------------------
1470 -- Get_Constraint_Association --
1471 --------------------------------
1473 function Get_Constraint_Association (T : Entity_Id) return Node_Id is
1474 Typ_Def : constant Node_Id := Type_Definition (Parent (T));
1475 Indic : constant Node_Id := Subtype_Indication (Typ_Def);
1477 begin
1478 -- ??? Also need to cover case of a type mark denoting a subtype
1479 -- with constraint.
1481 if Nkind (Indic) = N_Subtype_Indication
1482 and then Present (Constraint (Indic))
1483 then
1484 return First (Constraints (Constraint (Indic)));
1485 end if;
1487 return Empty;
1488 end Get_Constraint_Association;
1490 ---------------------
1491 -- Init_controller --
1492 ---------------------
1494 function Init_Controller
1495 (Target : Node_Id;
1496 Typ : Entity_Id;
1497 F : Node_Id;
1498 Attach : Node_Id;
1499 Init_Pr : Boolean)
1500 return List_Id
1502 Ref : Node_Id;
1503 L : List_Id := New_List;
1505 begin
1506 -- _init_proc (target._controller);
1507 -- initialize (target._controller);
1508 -- Attach_to_Final_List (target._controller, F);
1510 Ref := Make_Selected_Component (Loc,
1511 Prefix => Convert_To (Typ, New_Copy_Tree (Target)),
1512 Selector_Name => Make_Identifier (Loc, Name_uController));
1513 Set_Assignment_OK (Ref);
1515 if Init_Pr then
1516 Append_List_To (L,
1517 Build_Initialization_Call (Loc,
1518 Id_Ref => Ref,
1519 Typ => RTE (RE_Record_Controller),
1520 In_Init_Proc => Within_Init_Proc));
1521 end if;
1523 Append_To (L,
1524 Make_Procedure_Call_Statement (Loc,
1525 Name =>
1526 New_Reference_To (Find_Prim_Op (RTE (RE_Record_Controller),
1527 Name_Initialize), Loc),
1528 Parameter_Associations => New_List (New_Copy_Tree (Ref))));
1530 Append_To (L,
1531 Make_Attach_Call (
1532 Obj_Ref => New_Copy_Tree (Ref),
1533 Flist_Ref => F,
1534 With_Attach => Attach));
1535 return L;
1536 end Init_Controller;
1538 -- Start of processing for Build_Record_Aggr_Code
1540 begin
1542 -- Deal with the ancestor part of extension aggregates
1543 -- or with the discriminants of the root type
1545 if Nkind (N) = N_Extension_Aggregate then
1546 declare
1547 A : constant Node_Id := Ancestor_Part (N);
1549 begin
1551 -- If the ancestor part is a subtype mark "T", we generate
1552 -- _init_proc (T(tmp)); if T is constrained and
1553 -- _init_proc (S(tmp)); where S applies an appropriate
1554 -- constraint if T is unconstrained
1556 if Is_Entity_Name (A) and then Is_Type (Entity (A)) then
1558 Ancestor_Is_Subtype_Mark := True;
1560 if Is_Constrained (Entity (A)) then
1561 Init_Typ := Entity (A);
1563 -- For an ancestor part given by an unconstrained type
1564 -- mark, create a subtype constrained by appropriate
1565 -- corresponding discriminant values coming from either
1566 -- associations of the aggregate or a constraint on
1567 -- a parent type. The subtype will be used to generate
1568 -- the correct default value for the ancestor part.
1570 elsif Has_Discriminants (Entity (A)) then
1571 declare
1572 Anc_Typ : Entity_Id := Entity (A);
1573 Discrim : Entity_Id := First_Discriminant (Anc_Typ);
1574 Anc_Constr : List_Id := New_List;
1575 Disc_Value : Node_Id;
1576 New_Indic : Node_Id;
1577 Subt_Decl : Node_Id;
1578 begin
1579 while Present (Discrim) loop
1580 Disc_Value := Ancestor_Discriminant_Value (Discrim);
1581 Append_To (Anc_Constr, Disc_Value);
1582 Next_Discriminant (Discrim);
1583 end loop;
1585 New_Indic :=
1586 Make_Subtype_Indication (Loc,
1587 Subtype_Mark => New_Occurrence_Of (Anc_Typ, Loc),
1588 Constraint =>
1589 Make_Index_Or_Discriminant_Constraint (Loc,
1590 Constraints => Anc_Constr));
1592 Init_Typ := Create_Itype (Ekind (Anc_Typ), N);
1594 Subt_Decl :=
1595 Make_Subtype_Declaration (Loc,
1596 Defining_Identifier => Init_Typ,
1597 Subtype_Indication => New_Indic);
1599 -- Itypes must be analyzed with checks off
1600 -- Declaration must have a parent for proper
1601 -- handling of subsidiary actions.
1603 Set_Parent (Subt_Decl, N);
1604 Analyze (Subt_Decl, Suppress => All_Checks);
1605 end;
1606 end if;
1608 Ref := Convert_To (Init_Typ, New_Copy_Tree (Target));
1609 Set_Assignment_OK (Ref);
1611 Append_List_To (Start_L,
1612 Build_Initialization_Call (Loc,
1613 Id_Ref => Ref,
1614 Typ => Init_Typ,
1615 In_Init_Proc => Within_Init_Proc));
1617 if Is_Constrained (Entity (A))
1618 and then Has_Discriminants (Entity (A))
1619 then
1620 Check_Ancestor_Discriminants (Entity (A));
1621 end if;
1623 -- If the ancestor part is an expression "E", we generate
1624 -- T(tmp) := E;
1626 else
1627 Ancestor_Is_Expression := True;
1628 Init_Typ := Etype (A);
1630 -- Assign the tag before doing the assignment to make sure
1631 -- that the dispatching call in the subsequent deep_adjust
1632 -- works properly (unless Java_VM, where tags are implicit).
1634 if not Java_VM then
1635 Instr :=
1636 Make_OK_Assignment_Statement (Loc,
1637 Name =>
1638 Make_Selected_Component (Loc,
1639 Prefix => New_Copy_Tree (Target),
1640 Selector_Name => New_Reference_To (
1641 Tag_Component (Base_Type (Typ)), Loc)),
1643 Expression =>
1644 Unchecked_Convert_To (RTE (RE_Tag),
1645 New_Reference_To (
1646 Access_Disp_Table (Base_Type (Typ)), Loc)));
1648 Set_Assignment_OK (Name (Instr));
1649 Append_To (L, Instr);
1650 end if;
1652 -- If the ancestor part is an aggregate, force its full
1653 -- expansion, which was delayed.
1655 if Nkind (A) = N_Qualified_Expression
1656 and then (Nkind (Expression (A)) = N_Aggregate
1657 or else
1658 Nkind (Expression (A)) = N_Extension_Aggregate)
1659 then
1660 Set_Analyzed (A, False);
1661 Set_Analyzed (Expression (A), False);
1662 end if;
1664 Ref := Convert_To (Init_Typ, New_Copy_Tree (Target));
1665 Set_Assignment_OK (Ref);
1666 Append_To (L,
1667 Make_Unsuppress_Block (Loc,
1668 Name_Discriminant_Check,
1669 New_List (
1670 Make_OK_Assignment_Statement (Loc,
1671 Name => Ref,
1672 Expression => A))));
1674 if Has_Discriminants (Init_Typ) then
1675 Check_Ancestor_Discriminants (Init_Typ);
1676 end if;
1677 end if;
1678 end;
1680 else
1681 -- Generate the discriminant expressions, component by component.
1682 -- If the base type is an unchecked union, the discriminants are
1683 -- unknown to the back-end and absent from a value of the type, so
1684 -- assignments for them are not emitted.
1686 if Has_Discriminants (Typ)
1687 and then not Is_Unchecked_Union (Base_Type (Typ))
1688 then
1690 -- ??? The discriminants of the object not inherited in the type
1691 -- of the object should be initialized here
1693 null;
1695 -- Generate discriminant init values
1697 declare
1698 Discriminant : Entity_Id;
1699 Discriminant_Value : Node_Id;
1701 begin
1702 Discriminant := First_Girder_Discriminant (Typ);
1704 while Present (Discriminant) loop
1706 Comp_Expr :=
1707 Make_Selected_Component (Loc,
1708 Prefix => New_Copy_Tree (Target),
1709 Selector_Name => New_Occurrence_Of (Discriminant, Loc));
1711 Discriminant_Value :=
1712 Get_Discriminant_Value (
1713 Discriminant,
1714 N_Typ,
1715 Discriminant_Constraint (N_Typ));
1717 Instr :=
1718 Make_OK_Assignment_Statement (Loc,
1719 Name => Comp_Expr,
1720 Expression => New_Copy_Tree (Discriminant_Value));
1722 Set_No_Ctrl_Actions (Instr);
1723 Append_To (L, Instr);
1725 Next_Girder_Discriminant (Discriminant);
1726 end loop;
1727 end;
1728 end if;
1729 end if;
1731 -- Generate the assignments, component by component
1733 -- tmp.comp1 := Expr1_From_Aggr;
1734 -- tmp.comp2 := Expr2_From_Aggr;
1735 -- ....
1737 Comp := First (Component_Associations (N));
1738 while Present (Comp) loop
1739 Selector := Entity (First (Choices (Comp)));
1741 if Ekind (Selector) /= E_Discriminant
1742 or else Nkind (N) = N_Extension_Aggregate
1743 then
1744 Comp_Type := Etype (Selector);
1745 Comp_Kind := Nkind (Expression (Comp));
1746 Comp_Expr :=
1747 Make_Selected_Component (Loc,
1748 Prefix => New_Copy_Tree (Target),
1749 Selector_Name => New_Occurrence_Of (Selector, Loc));
1751 if Nkind (Expression (Comp)) = N_Qualified_Expression then
1752 Expr_Q := Expression (Expression (Comp));
1753 else
1754 Expr_Q := Expression (Comp);
1755 end if;
1757 -- The controller is the one of the parent type defining
1758 -- the component (in case of inherited components).
1760 if Controlled_Type (Comp_Type) then
1761 Internal_Final_List :=
1762 Make_Selected_Component (Loc,
1763 Prefix => Convert_To (
1764 Scope (Original_Record_Component (Selector)),
1765 New_Copy_Tree (Target)),
1766 Selector_Name =>
1767 Make_Identifier (Loc, Name_uController));
1768 Internal_Final_List :=
1769 Make_Selected_Component (Loc,
1770 Prefix => Internal_Final_List,
1771 Selector_Name => Make_Identifier (Loc, Name_F));
1773 -- The internal final list can be part of a constant object
1775 Set_Assignment_OK (Internal_Final_List);
1776 else
1777 Internal_Final_List := Empty;
1778 end if;
1780 if Is_Delayed_Aggregate (Expr_Q) then
1781 Append_List_To (L,
1782 Late_Expansion (Expr_Q, Comp_Type, Comp_Expr,
1783 Internal_Final_List));
1784 else
1785 Instr :=
1786 Make_OK_Assignment_Statement (Loc,
1787 Name => Comp_Expr,
1788 Expression => Expression (Comp));
1790 Set_No_Ctrl_Actions (Instr);
1791 Append_To (L, Instr);
1793 -- Adjust the tag if tagged (because of possible view
1794 -- conversions), unless compiling for the Java VM
1795 -- where tags are implicit.
1797 -- tmp.comp._tag := comp_typ'tag;
1799 if Is_Tagged_Type (Comp_Type) and then not Java_VM then
1800 Instr :=
1801 Make_OK_Assignment_Statement (Loc,
1802 Name =>
1803 Make_Selected_Component (Loc,
1804 Prefix => New_Copy_Tree (Comp_Expr),
1805 Selector_Name =>
1806 New_Reference_To (Tag_Component (Comp_Type), Loc)),
1808 Expression =>
1809 Unchecked_Convert_To (RTE (RE_Tag),
1810 New_Reference_To (
1811 Access_Disp_Table (Comp_Type), Loc)));
1813 Append_To (L, Instr);
1814 end if;
1816 -- Adjust and Attach the component to the proper controller
1817 -- Adjust (tmp.comp);
1818 -- Attach_To_Final_List (tmp.comp,
1819 -- comp_typ (tmp)._record_controller.f)
1821 if Controlled_Type (Comp_Type) then
1822 Append_List_To (L,
1823 Make_Adjust_Call (
1824 Ref => New_Copy_Tree (Comp_Expr),
1825 Typ => Comp_Type,
1826 Flist_Ref => Internal_Final_List,
1827 With_Attach => Make_Integer_Literal (Loc, 1)));
1828 end if;
1829 end if;
1830 end if;
1832 Next (Comp);
1833 end loop;
1835 -- If the type is tagged, the tag needs to be initialized (unless
1836 -- compiling for the Java VM where tags are implicit). It is done
1837 -- late in the initialization process because in some cases, we call
1838 -- the init_proc of an ancestor which will not leave out the right tag
1840 if Ancestor_Is_Expression then
1841 null;
1843 elsif Is_Tagged_Type (Typ) and then not Java_VM then
1844 Instr :=
1845 Make_OK_Assignment_Statement (Loc,
1846 Name =>
1847 Make_Selected_Component (Loc,
1848 Prefix => New_Copy_Tree (Target),
1849 Selector_Name =>
1850 New_Reference_To (Tag_Component (Base_Type (Typ)), Loc)),
1852 Expression =>
1853 Unchecked_Convert_To (RTE (RE_Tag),
1854 New_Reference_To (Access_Disp_Table (Base_Type (Typ)), Loc)));
1856 Append_To (L, Instr);
1857 end if;
1859 -- Now deal with the various controlled type data structure
1860 -- initializations
1862 if Present (Obj)
1863 and then Finalize_Storage_Only (Typ)
1864 and then (Is_Library_Level_Entity (Obj)
1865 or else Entity (Constant_Value (RTE (RE_Garbage_Collected)))
1866 = Standard_True)
1867 then
1868 Attach := Make_Integer_Literal (Loc, 0);
1870 elsif Nkind (Parent (N)) = N_Qualified_Expression
1871 and then Nkind (Parent (Parent (N))) = N_Allocator
1872 then
1873 Attach := Make_Integer_Literal (Loc, 2);
1875 else
1876 Attach := Make_Integer_Literal (Loc, 1);
1877 end if;
1879 -- Determine the external finalization list. It is either the
1880 -- finalization list of the outer-scope or the one coming from
1881 -- an outer aggregate. When the target is not a temporary, the
1882 -- proper scope is the scope of the target rather than the
1883 -- potentially transient current scope.
1885 if Controlled_Type (Typ) then
1886 if Present (Flist) then
1887 External_Final_List := New_Copy_Tree (Flist);
1889 elsif Is_Entity_Name (Target)
1890 and then Present (Scope (Entity (Target)))
1891 then
1892 External_Final_List := Find_Final_List (Scope (Entity (Target)));
1894 else
1895 External_Final_List := Find_Final_List (Current_Scope);
1896 end if;
1898 else
1899 External_Final_List := Empty;
1900 end if;
1902 -- initialize and attach the outer object in the is_controlled
1903 -- case
1905 if Is_Controlled (Typ) then
1906 if Ancestor_Is_Subtype_Mark then
1907 Ref := Convert_To (Init_Typ, New_Copy_Tree (Target));
1908 Set_Assignment_OK (Ref);
1909 Append_To (L,
1910 Make_Procedure_Call_Statement (Loc,
1911 Name => New_Reference_To (
1912 Find_Prim_Op (Init_Typ, Name_Initialize), Loc),
1913 Parameter_Associations => New_List (New_Copy_Tree (Ref))));
1914 end if;
1916 -- ??? when the ancestor part is an expression, the global
1917 -- object is already attached at the wrong level. It should
1918 -- be detached and re-attached. We have a design problem here.
1920 if Ancestor_Is_Expression
1921 and then Has_Controlled_Component (Init_Typ)
1922 then
1923 null;
1925 elsif Has_Controlled_Component (Typ) then
1926 F := Make_Selected_Component (Loc,
1927 Prefix => New_Copy_Tree (Target),
1928 Selector_Name => Make_Identifier (Loc, Name_uController));
1929 F := Make_Selected_Component (Loc,
1930 Prefix => F,
1931 Selector_Name => Make_Identifier (Loc, Name_F));
1933 Ref := New_Copy_Tree (Target);
1934 Set_Assignment_OK (Ref);
1936 Append_To (L,
1937 Make_Attach_Call (
1938 Obj_Ref => Ref,
1939 Flist_Ref => F,
1940 With_Attach => Make_Integer_Literal (Loc, 1)));
1942 else -- is_Controlled (Typ) and not Has_Controlled_Component (Typ)
1943 Ref := New_Copy_Tree (Target);
1944 Set_Assignment_OK (Ref);
1945 Append_To (Start_L,
1946 Make_Attach_Call (
1947 Obj_Ref => Ref,
1948 Flist_Ref => New_Copy_Tree (External_Final_List),
1949 With_Attach => Attach));
1950 end if;
1951 end if;
1953 -- in the Has_Controlled component case, all the intermediate
1954 -- controllers must be initialized
1956 if Has_Controlled_Component (Typ) then
1957 declare
1958 Inner_Typ : Entity_Id;
1959 Outer_Typ : Entity_Id;
1960 At_Root : Boolean;
1962 begin
1964 Outer_Typ := Base_Type (Typ);
1966 -- find outer type with a controller
1968 while Outer_Typ /= Init_Typ
1969 and then not Has_New_Controlled_Component (Outer_Typ)
1970 loop
1971 Outer_Typ := Etype (Outer_Typ);
1972 end loop;
1974 -- attach it to the outer record controller to the
1975 -- external final list
1977 if Outer_Typ = Init_Typ then
1978 Append_List_To (Start_L,
1979 Init_Controller (
1980 Target => Target,
1981 Typ => Outer_Typ,
1982 F => External_Final_List,
1983 Attach => Attach,
1984 Init_Pr => Ancestor_Is_Expression));
1985 At_Root := True;
1986 Inner_Typ := Init_Typ;
1988 else
1989 Append_List_To (Start_L,
1990 Init_Controller (
1991 Target => Target,
1992 Typ => Outer_Typ,
1993 F => External_Final_List,
1994 Attach => Attach,
1995 Init_Pr => True));
1997 Inner_Typ := Etype (Outer_Typ);
1998 At_Root :=
1999 not Is_Tagged_Type (Typ) or else Inner_Typ = Outer_Typ;
2000 end if;
2002 -- Initialize the internal controllers for tagged types with
2003 -- more than one controller.
2005 while not At_Root and then Inner_Typ /= Init_Typ loop
2006 if Has_New_Controlled_Component (Inner_Typ) then
2007 F :=
2008 Make_Selected_Component (Loc,
2009 Prefix => Convert_To (Outer_Typ, New_Copy_Tree (Target)),
2010 Selector_Name =>
2011 Make_Identifier (Loc, Name_uController));
2012 F := Make_Selected_Component (Loc,
2013 Prefix => F,
2014 Selector_Name => Make_Identifier (Loc, Name_F));
2015 Append_List_To (Start_L,
2016 Init_Controller (
2017 Target => Target,
2018 Typ => Inner_Typ,
2019 F => F,
2020 Attach => Make_Integer_Literal (Loc, 1),
2021 Init_Pr => True));
2022 Outer_Typ := Inner_Typ;
2023 end if;
2025 -- Stop at the root
2027 At_Root := Inner_Typ = Etype (Inner_Typ);
2028 Inner_Typ := Etype (Inner_Typ);
2029 end loop;
2031 -- if not done yet attach the controller of the ancestor part
2033 if Outer_Typ /= Init_Typ
2034 and then Inner_Typ = Init_Typ
2035 and then Has_Controlled_Component (Init_Typ)
2036 then
2037 F :=
2038 Make_Selected_Component (Loc,
2039 Prefix => Convert_To (Outer_Typ, New_Copy_Tree (Target)),
2040 Selector_Name => Make_Identifier (Loc, Name_uController));
2041 F := Make_Selected_Component (Loc,
2042 Prefix => F,
2043 Selector_Name => Make_Identifier (Loc, Name_F));
2045 Attach := Make_Integer_Literal (Loc, 1);
2046 Append_List_To (Start_L,
2047 Init_Controller (
2048 Target => Target,
2049 Typ => Init_Typ,
2050 F => F,
2051 Attach => Attach,
2052 Init_Pr => Ancestor_Is_Expression));
2053 end if;
2054 end;
2055 end if;
2057 Append_List_To (Start_L, L);
2058 return Start_L;
2059 end Build_Record_Aggr_Code;
2061 -------------------------------
2062 -- Convert_Aggr_In_Allocator --
2063 -------------------------------
2065 procedure Convert_Aggr_In_Allocator (Decl, Aggr : Node_Id) is
2066 Loc : constant Source_Ptr := Sloc (Aggr);
2067 Typ : constant Entity_Id := Etype (Aggr);
2068 Temp : constant Entity_Id := Defining_Identifier (Decl);
2069 Occ : constant Node_Id := Unchecked_Convert_To (Typ,
2070 Make_Explicit_Dereference (Loc, New_Reference_To (Temp, Loc)));
2072 Access_Type : constant Entity_Id := Etype (Temp);
2074 begin
2075 Insert_Actions_After (Decl,
2076 Late_Expansion (Aggr, Typ, Occ,
2077 Find_Final_List (Access_Type),
2078 Associated_Final_Chain (Base_Type (Access_Type))));
2079 end Convert_Aggr_In_Allocator;
2081 --------------------------------
2082 -- Convert_Aggr_In_Assignment --
2083 --------------------------------
2085 procedure Convert_Aggr_In_Assignment (N : Node_Id) is
2086 Aggr : Node_Id := Expression (N);
2087 Typ : constant Entity_Id := Etype (Aggr);
2088 Occ : constant Node_Id := New_Copy_Tree (Name (N));
2090 begin
2091 if Nkind (Aggr) = N_Qualified_Expression then
2092 Aggr := Expression (Aggr);
2093 end if;
2095 Insert_Actions_After (N,
2096 Late_Expansion (Aggr, Typ, Occ,
2097 Find_Final_List (Typ, New_Copy_Tree (Occ))));
2098 end Convert_Aggr_In_Assignment;
2100 ---------------------------------
2101 -- Convert_Aggr_In_Object_Decl --
2102 ---------------------------------
2104 procedure Convert_Aggr_In_Object_Decl (N : Node_Id) is
2105 Obj : constant Entity_Id := Defining_Identifier (N);
2106 Aggr : Node_Id := Expression (N);
2107 Loc : constant Source_Ptr := Sloc (Aggr);
2108 Typ : constant Entity_Id := Etype (Aggr);
2109 Occ : constant Node_Id := New_Occurrence_Of (Obj, Loc);
2111 begin
2112 Set_Assignment_OK (Occ);
2114 if Nkind (Aggr) = N_Qualified_Expression then
2115 Aggr := Expression (Aggr);
2116 end if;
2118 Insert_Actions_After (N, Late_Expansion (Aggr, Typ, Occ, Obj => Obj));
2119 Set_No_Initialization (N);
2120 Initialize_Discriminants (N, Typ);
2121 end Convert_Aggr_In_Object_Decl;
2123 ----------------------------
2124 -- Convert_To_Assignments --
2125 ----------------------------
2127 procedure Convert_To_Assignments (N : Node_Id; Typ : Entity_Id) is
2128 Loc : constant Source_Ptr := Sloc (N);
2129 Temp : Entity_Id;
2131 Instr : Node_Id;
2132 Target_Expr : Node_Id;
2133 Parent_Kind : Node_Kind;
2134 Unc_Decl : Boolean := False;
2135 Parent_Node : Node_Id;
2137 begin
2139 Parent_Node := Parent (N);
2140 Parent_Kind := Nkind (Parent_Node);
2142 if Parent_Kind = N_Qualified_Expression then
2144 -- Check if we are in a unconstrained declaration because in this
2145 -- case the current delayed expansion mechanism doesn't work when
2146 -- the declared object size depend on the initializing expr.
2148 begin
2149 Parent_Node := Parent (Parent_Node);
2150 Parent_Kind := Nkind (Parent_Node);
2151 if Parent_Kind = N_Object_Declaration then
2152 Unc_Decl :=
2153 not Is_Entity_Name (Object_Definition (Parent_Node))
2154 or else Has_Discriminants (
2155 Entity (Object_Definition (Parent_Node)))
2156 or else Is_Class_Wide_Type (
2157 Entity (Object_Definition (Parent_Node)));
2158 end if;
2159 end;
2160 end if;
2162 -- Just set the Delay flag in the following cases where the
2163 -- transformation will be done top down from above
2164 -- - internal aggregate (transformed when expanding the parent)
2165 -- - allocators (see Convert_Aggr_In_Allocator)
2166 -- - object decl (see Convert_Aggr_In_Object_Decl)
2167 -- - safe assignments (see Convert_Aggr_Assignments)
2168 -- so far only the assignments in the init_procs are taken
2169 -- into account
2171 if Parent_Kind = N_Aggregate
2172 or else Parent_Kind = N_Extension_Aggregate
2173 or else Parent_Kind = N_Component_Association
2174 or else Parent_Kind = N_Allocator
2175 or else (Parent_Kind = N_Object_Declaration and then not Unc_Decl)
2176 or else (Parent_Kind = N_Assignment_Statement
2177 and then Inside_Init_Proc)
2178 then
2179 Set_Expansion_Delayed (N);
2180 return;
2181 end if;
2183 if Requires_Transient_Scope (Typ) then
2184 Establish_Transient_Scope (N, Sec_Stack =>
2185 Is_Controlled (Typ) or else Has_Controlled_Component (Typ));
2186 end if;
2188 -- Create the temporary
2190 Temp := Make_Defining_Identifier (Loc, New_Internal_Name ('A'));
2192 Instr :=
2193 Make_Object_Declaration (Loc,
2194 Defining_Identifier => Temp,
2195 Object_Definition => New_Occurrence_Of (Typ, Loc));
2197 Set_No_Initialization (Instr);
2198 Insert_Action (N, Instr);
2199 Initialize_Discriminants (Instr, Typ);
2200 Target_Expr := New_Occurrence_Of (Temp, Loc);
2202 Insert_Actions (N, Build_Record_Aggr_Code (N, Typ, Target_Expr));
2203 Rewrite (N, New_Occurrence_Of (Temp, Loc));
2204 Analyze_And_Resolve (N, Typ);
2205 end Convert_To_Assignments;
2207 ---------------------------
2208 -- Convert_To_Positional --
2209 ---------------------------
2211 procedure Convert_To_Positional
2212 (N : Node_Id;
2213 Max_Others_Replicate : Nat := 5;
2214 Handle_Bit_Packed : Boolean := False)
2216 Loc : constant Source_Ptr := Sloc (N);
2217 Typ : constant Entity_Id := Etype (N);
2218 Ndim : constant Pos := Number_Dimensions (Typ);
2219 Xtyp : constant Entity_Id := Etype (First_Index (Typ));
2220 Indx : constant Node_Id := First_Index (Base_Type (Typ));
2221 Blo : constant Node_Id := Type_Low_Bound (Etype (Indx));
2222 Lo : constant Node_Id := Type_Low_Bound (Xtyp);
2223 Hi : constant Node_Id := Type_High_Bound (Xtyp);
2224 Lov : Uint;
2225 Hiv : Uint;
2227 -- The following constant determines the maximum size of an
2228 -- aggregate produced by converting named to positional
2229 -- notation (e.g. from others clauses). This avoids running
2230 -- away with attempts to convert huge aggregates.
2232 -- The normal limit is 5000, but we increase this limit to
2233 -- 2**24 (about 16 million) if Restrictions (No_Elaboration_Code)
2234 -- or Restrictions (No_Implicit_Loops) is specified, since in
2235 -- either case, we are at risk of declaring the program illegal
2236 -- because of this limit.
2238 Max_Aggr_Size : constant Nat :=
2239 5000 + (2 ** 24 - 5000) * Boolean'Pos
2240 (Restrictions (No_Elaboration_Code)
2241 or else
2242 Restrictions (No_Implicit_Loops));
2244 begin
2245 -- For now, we only handle the one dimensional case and aggregates
2246 -- that are not part of a component_association
2248 if Ndim > 1 or else Nkind (Parent (N)) = N_Aggregate
2249 or else Nkind (Parent (N)) = N_Component_Association
2250 then
2251 return;
2252 end if;
2254 -- If already positional, nothing to do!
2256 if No (Component_Associations (N)) then
2257 return;
2258 end if;
2260 -- Bounds need to be known at compile time
2262 if not Compile_Time_Known_Value (Lo)
2263 or else not Compile_Time_Known_Value (Hi)
2264 then
2265 return;
2266 end if;
2268 -- Normally we do not attempt to convert bit packed arrays. The
2269 -- exception is when we are explicitly asked to do so (this call
2270 -- is from the Packed_Array_Aggregate_Handled procedure).
2272 if Is_Bit_Packed_Array (Typ)
2273 and then not Handle_Bit_Packed
2274 then
2275 return;
2276 end if;
2278 -- Do not convert to positional if controlled components are
2279 -- involved since these require special processing
2281 if Has_Controlled_Component (Typ) then
2282 return;
2283 end if;
2285 -- Get bounds and check reasonable size (positive, not too large)
2286 -- Also only handle bounds starting at the base type low bound for now
2287 -- since the compiler isn't able to handle different low bounds yet.
2289 Lov := Expr_Value (Lo);
2290 Hiv := Expr_Value (Hi);
2292 if Hiv < Lov
2293 or else (Hiv - Lov > Max_Aggr_Size)
2294 or else not Compile_Time_Known_Value (Blo)
2295 or else (Lov /= Expr_Value (Blo))
2296 then
2297 return;
2298 end if;
2300 -- Bounds must be in integer range (for array Vals below)
2302 if not UI_Is_In_Int_Range (Lov)
2303 or else
2304 not UI_Is_In_Int_Range (Hiv)
2305 then
2306 return;
2307 end if;
2309 -- Determine if set of alternatives is suitable for conversion
2310 -- and build an array containing the values in sequence.
2312 declare
2313 Vals : array (UI_To_Int (Lov) .. UI_To_Int (Hiv))
2314 of Node_Id := (others => Empty);
2315 -- The values in the aggregate sorted appropriately
2317 Vlist : List_Id;
2318 -- Same data as Vals in list form
2320 Rep_Count : Nat;
2321 -- Used to validate Max_Others_Replicate limit
2323 Elmt : Node_Id;
2324 Num : Int := UI_To_Int (Lov);
2325 Choice : Node_Id;
2326 Lo, Hi : Node_Id;
2328 begin
2329 if Present (Expressions (N)) then
2330 Elmt := First (Expressions (N));
2331 while Present (Elmt) loop
2332 Vals (Num) := Relocate_Node (Elmt);
2333 Num := Num + 1;
2334 Next (Elmt);
2335 end loop;
2336 end if;
2338 Elmt := First (Component_Associations (N));
2339 Component_Loop : while Present (Elmt) loop
2341 Choice := First (Choices (Elmt));
2342 Choice_Loop : while Present (Choice) loop
2344 -- If we have an others choice, fill in the missing elements
2345 -- subject to the limit established by Max_Others_Replicate.
2347 if Nkind (Choice) = N_Others_Choice then
2348 Rep_Count := 0;
2350 for J in Vals'Range loop
2351 if No (Vals (J)) then
2352 Vals (J) := New_Copy_Tree (Expression (Elmt));
2353 Rep_Count := Rep_Count + 1;
2355 -- Check for maximum others replication. Note that
2356 -- we skip this test if either of the restrictions
2357 -- No_Elaboration_Code or No_Implicit_Loops is
2358 -- active, or if this is a preelaborable unit.
2360 if Rep_Count > Max_Others_Replicate
2361 and then not Restrictions (No_Elaboration_Code)
2362 and then not Restrictions (No_Implicit_Loops)
2363 and then not
2364 Is_Preelaborated (Cunit_Entity (Current_Sem_Unit))
2365 then
2366 return;
2367 end if;
2368 end if;
2369 end loop;
2371 exit Component_Loop;
2373 -- Case of a subtype mark
2375 elsif (Nkind (Choice) = N_Identifier
2376 and then Is_Type (Entity (Choice)))
2377 then
2378 Lo := Type_Low_Bound (Etype (Choice));
2379 Hi := Type_High_Bound (Etype (Choice));
2381 -- Case of subtype indication
2383 elsif Nkind (Choice) = N_Subtype_Indication then
2384 Lo := Low_Bound (Range_Expression (Constraint (Choice)));
2385 Hi := High_Bound (Range_Expression (Constraint (Choice)));
2387 -- Case of a range
2389 elsif Nkind (Choice) = N_Range then
2390 Lo := Low_Bound (Choice);
2391 Hi := High_Bound (Choice);
2393 -- Normal subexpression case
2395 else pragma Assert (Nkind (Choice) in N_Subexpr);
2396 if not Compile_Time_Known_Value (Choice) then
2397 return;
2399 else
2400 Vals (UI_To_Int (Expr_Value (Choice))) :=
2401 New_Copy_Tree (Expression (Elmt));
2402 goto Continue;
2403 end if;
2404 end if;
2406 -- Range cases merge with Lo,Hi said
2408 if not Compile_Time_Known_Value (Lo)
2409 or else
2410 not Compile_Time_Known_Value (Hi)
2411 then
2412 return;
2413 else
2414 for J in UI_To_Int (Expr_Value (Lo)) ..
2415 UI_To_Int (Expr_Value (Hi))
2416 loop
2417 Vals (J) := New_Copy_Tree (Expression (Elmt));
2418 end loop;
2419 end if;
2421 <<Continue>>
2422 Next (Choice);
2423 end loop Choice_Loop;
2425 Next (Elmt);
2426 end loop Component_Loop;
2428 -- If we get here the conversion is possible
2430 Vlist := New_List;
2431 for J in Vals'Range loop
2432 Append (Vals (J), Vlist);
2433 end loop;
2435 Rewrite (N, Make_Aggregate (Loc, Expressions => Vlist));
2436 Analyze_And_Resolve (N, Typ);
2437 end;
2438 end Convert_To_Positional;
2440 ----------------------------
2441 -- Expand_Array_Aggregate --
2442 ----------------------------
2444 -- Array aggregate expansion proceeds as follows:
2446 -- 1. If requested we generate code to perform all the array aggregate
2447 -- bound checks, specifically
2449 -- (a) Check that the index range defined by aggregate bounds is
2450 -- compatible with corresponding index subtype.
2452 -- (b) If an others choice is present check that no aggregate
2453 -- index is outside the bounds of the index constraint.
2455 -- (c) For multidimensional arrays make sure that all subaggregates
2456 -- corresponding to the same dimension have the same bounds.
2458 -- 2. Check if the aggregate can be statically processed. If this is the
2459 -- case pass it as is to Gigi. Note that a necessary condition for
2460 -- static processing is that the aggregate be fully positional.
2462 -- 3. If in place aggregate expansion is possible (i.e. no need to create
2463 -- a temporary) then mark the aggregate as such and return. Otherwise
2464 -- create a new temporary and generate the appropriate initialization
2465 -- code.
2467 procedure Expand_Array_Aggregate (N : Node_Id) is
2468 Loc : constant Source_Ptr := Sloc (N);
2470 Typ : constant Entity_Id := Etype (N);
2471 Ctyp : constant Entity_Id := Component_Type (Typ);
2472 -- Typ is the correct constrained array subtype of the aggregate
2473 -- Ctyp is the corresponding component type.
2475 Aggr_Dimension : constant Pos := Number_Dimensions (Typ);
2476 -- Number of aggregate index dimensions.
2478 Aggr_Low : array (1 .. Aggr_Dimension) of Node_Id;
2479 Aggr_High : array (1 .. Aggr_Dimension) of Node_Id;
2480 -- Low and High bounds of the constraint for each aggregate index.
2482 Aggr_Index_Typ : array (1 .. Aggr_Dimension) of Entity_Id;
2483 -- The type of each index.
2485 Maybe_In_Place_OK : Boolean;
2486 -- If the type is neither controlled nor packed and the aggregate
2487 -- is the expression in an assignment, assignment in place may be
2488 -- possible, provided other conditions are met on the LHS.
2490 Others_Present : array (1 .. Aggr_Dimension) of Boolean :=
2491 (others => False);
2492 -- If Others_Present (J) is True, then there is an others choice
2493 -- in one of the sub-aggregates of N at dimension J.
2495 procedure Build_Constrained_Type (Positional : Boolean);
2496 -- If the subtype is not static or unconstrained, build a constrained
2497 -- type using the computable sizes of the aggregate and its sub-
2498 -- aggregates.
2500 procedure Check_Bounds (Aggr_Bounds : Node_Id; Index_Bounds : Node_Id);
2501 -- Checks that the bounds of Aggr_Bounds are within the bounds defined
2502 -- by Index_Bounds.
2504 procedure Check_Same_Aggr_Bounds (Sub_Aggr : Node_Id; Dim : Pos);
2505 -- Checks that in a multi-dimensional array aggregate all subaggregates
2506 -- corresponding to the same dimension have the same bounds.
2507 -- Sub_Aggr is an array sub-aggregate. Dim is the dimension
2508 -- corresponding to the sub-aggregate.
2510 procedure Compute_Others_Present (Sub_Aggr : Node_Id; Dim : Pos);
2511 -- Computes the values of array Others_Present. Sub_Aggr is the
2512 -- array sub-aggregate we start the computation from. Dim is the
2513 -- dimension corresponding to the sub-aggregate.
2515 function Has_Address_Clause (D : Node_Id) return Boolean;
2516 -- If the aggregate is the expression in an object declaration, it
2517 -- cannot be expanded in place. This function does a lookahead in the
2518 -- current declarative part to find an address clause for the object
2519 -- being declared.
2521 function In_Place_Assign_OK return Boolean;
2522 -- Simple predicate to determine whether an aggregate assignment can
2523 -- be done in place, because none of the new values can depend on the
2524 -- components of the target of the assignment.
2526 procedure Others_Check (Sub_Aggr : Node_Id; Dim : Pos);
2527 -- Checks that if an others choice is present in any sub-aggregate no
2528 -- aggregate index is outside the bounds of the index constraint.
2529 -- Sub_Aggr is an array sub-aggregate. Dim is the dimension
2530 -- corresponding to the sub-aggregate.
2532 ----------------------------
2533 -- Build_Constrained_Type --
2534 ----------------------------
2536 procedure Build_Constrained_Type (Positional : Boolean) is
2537 Loc : constant Source_Ptr := Sloc (N);
2538 Agg_Type : Entity_Id;
2539 Comp : Node_Id;
2540 Decl : Node_Id;
2541 Typ : constant Entity_Id := Etype (N);
2542 Indices : List_Id := New_List;
2543 Num : Int;
2544 Sub_Agg : Node_Id;
2546 begin
2547 Agg_Type :=
2548 Make_Defining_Identifier (
2549 Loc, New_Internal_Name ('A'));
2551 -- If the aggregate is purely positional, all its subaggregates
2552 -- have the same size. We collect the dimensions from the first
2553 -- subaggregate at each level.
2555 if Positional then
2556 Sub_Agg := N;
2558 for D in 1 .. Number_Dimensions (Typ) loop
2559 Comp := First (Expressions (Sub_Agg));
2561 Sub_Agg := Comp;
2562 Num := 0;
2564 while Present (Comp) loop
2565 Num := Num + 1;
2566 Next (Comp);
2567 end loop;
2569 Append (
2570 Make_Range (Loc,
2571 Low_Bound => Make_Integer_Literal (Loc, 1),
2572 High_Bound =>
2573 Make_Integer_Literal (Loc, Num)),
2574 Indices);
2575 end loop;
2577 else
2579 -- We know the aggregate type is unconstrained and the
2580 -- aggregate is not processable by the back end, therefore
2581 -- not necessarily positional. Retrieve the bounds of each
2582 -- dimension as computed earlier.
2584 for D in 1 .. Number_Dimensions (Typ) loop
2585 Append (
2586 Make_Range (Loc,
2587 Low_Bound => Aggr_Low (D),
2588 High_Bound => Aggr_High (D)),
2589 Indices);
2590 end loop;
2591 end if;
2593 Decl :=
2594 Make_Full_Type_Declaration (Loc,
2595 Defining_Identifier => Agg_Type,
2596 Type_Definition =>
2597 Make_Constrained_Array_Definition (Loc,
2598 Discrete_Subtype_Definitions => Indices,
2599 Subtype_Indication =>
2600 New_Occurrence_Of (Component_Type (Typ), Loc)));
2602 Insert_Action (N, Decl);
2603 Analyze (Decl);
2604 Set_Etype (N, Agg_Type);
2605 Set_Is_Itype (Agg_Type);
2606 Freeze_Itype (Agg_Type, N);
2607 end Build_Constrained_Type;
2609 ------------------
2610 -- Check_Bounds --
2611 ------------------
2613 procedure Check_Bounds (Aggr_Bounds : Node_Id; Index_Bounds : Node_Id) is
2614 Aggr_Lo : Node_Id;
2615 Aggr_Hi : Node_Id;
2617 Ind_Lo : Node_Id;
2618 Ind_Hi : Node_Id;
2620 Cond : Node_Id := Empty;
2622 begin
2623 Get_Index_Bounds (Aggr_Bounds, Aggr_Lo, Aggr_Hi);
2624 Get_Index_Bounds (Index_Bounds, Ind_Lo, Ind_Hi);
2626 -- Generate the following test:
2628 -- [constraint_error when
2629 -- Aggr_Lo <= Aggr_Hi and then
2630 -- (Aggr_Lo < Ind_Lo or else Aggr_Hi > Ind_Hi)]
2632 -- As an optimization try to see if some tests are trivially vacuos
2633 -- because we are comparing an expression against itself.
2635 if Aggr_Lo = Ind_Lo and then Aggr_Hi = Ind_Hi then
2636 Cond := Empty;
2638 elsif Aggr_Hi = Ind_Hi then
2639 Cond :=
2640 Make_Op_Lt (Loc,
2641 Left_Opnd => Duplicate_Subexpr (Aggr_Lo),
2642 Right_Opnd => Duplicate_Subexpr (Ind_Lo));
2644 elsif Aggr_Lo = Ind_Lo then
2645 Cond :=
2646 Make_Op_Gt (Loc,
2647 Left_Opnd => Duplicate_Subexpr (Aggr_Hi),
2648 Right_Opnd => Duplicate_Subexpr (Ind_Hi));
2650 else
2651 Cond :=
2652 Make_Or_Else (Loc,
2653 Left_Opnd =>
2654 Make_Op_Lt (Loc,
2655 Left_Opnd => Duplicate_Subexpr (Aggr_Lo),
2656 Right_Opnd => Duplicate_Subexpr (Ind_Lo)),
2658 Right_Opnd =>
2659 Make_Op_Gt (Loc,
2660 Left_Opnd => Duplicate_Subexpr (Aggr_Hi),
2661 Right_Opnd => Duplicate_Subexpr (Ind_Hi)));
2662 end if;
2664 if Present (Cond) then
2665 Cond :=
2666 Make_And_Then (Loc,
2667 Left_Opnd =>
2668 Make_Op_Le (Loc,
2669 Left_Opnd => Duplicate_Subexpr (Aggr_Lo),
2670 Right_Opnd => Duplicate_Subexpr (Aggr_Hi)),
2672 Right_Opnd => Cond);
2674 Set_Analyzed (Left_Opnd (Left_Opnd (Cond)), False);
2675 Set_Analyzed (Right_Opnd (Left_Opnd (Cond)), False);
2676 Insert_Action (N,
2677 Make_Raise_Constraint_Error (Loc,
2678 Condition => Cond,
2679 Reason => CE_Length_Check_Failed));
2680 end if;
2681 end Check_Bounds;
2683 ----------------------------
2684 -- Check_Same_Aggr_Bounds --
2685 ----------------------------
2687 procedure Check_Same_Aggr_Bounds (Sub_Aggr : Node_Id; Dim : Pos) is
2688 Sub_Lo : constant Node_Id := Low_Bound (Aggregate_Bounds (Sub_Aggr));
2689 Sub_Hi : constant Node_Id := High_Bound (Aggregate_Bounds (Sub_Aggr));
2690 -- The bounds of this specific sub-aggregate.
2692 Aggr_Lo : constant Node_Id := Aggr_Low (Dim);
2693 Aggr_Hi : constant Node_Id := Aggr_High (Dim);
2694 -- The bounds of the aggregate for this dimension
2696 Ind_Typ : constant Entity_Id := Aggr_Index_Typ (Dim);
2697 -- The index type for this dimension.
2699 Cond : Node_Id := Empty;
2701 Assoc : Node_Id;
2702 Expr : Node_Id;
2704 begin
2705 -- If index checks are on generate the test
2707 -- [constraint_error when
2708 -- Aggr_Lo /= Sub_Lo or else Aggr_Hi /= Sub_Hi]
2710 -- As an optimization try to see if some tests are trivially vacuos
2711 -- because we are comparing an expression against itself. Also for
2712 -- the first dimension the test is trivially vacuous because there
2713 -- is just one aggregate for dimension 1.
2715 if Index_Checks_Suppressed (Ind_Typ) then
2716 Cond := Empty;
2718 elsif Dim = 1
2719 or else (Aggr_Lo = Sub_Lo and then Aggr_Hi = Sub_Hi)
2720 then
2721 Cond := Empty;
2723 elsif Aggr_Hi = Sub_Hi then
2724 Cond :=
2725 Make_Op_Ne (Loc,
2726 Left_Opnd => Duplicate_Subexpr (Aggr_Lo),
2727 Right_Opnd => Duplicate_Subexpr (Sub_Lo));
2729 elsif Aggr_Lo = Sub_Lo then
2730 Cond :=
2731 Make_Op_Ne (Loc,
2732 Left_Opnd => Duplicate_Subexpr (Aggr_Hi),
2733 Right_Opnd => Duplicate_Subexpr (Sub_Hi));
2735 else
2736 Cond :=
2737 Make_Or_Else (Loc,
2738 Left_Opnd =>
2739 Make_Op_Ne (Loc,
2740 Left_Opnd => Duplicate_Subexpr (Aggr_Lo),
2741 Right_Opnd => Duplicate_Subexpr (Sub_Lo)),
2743 Right_Opnd =>
2744 Make_Op_Ne (Loc,
2745 Left_Opnd => Duplicate_Subexpr (Aggr_Hi),
2746 Right_Opnd => Duplicate_Subexpr (Sub_Hi)));
2747 end if;
2749 if Present (Cond) then
2750 Insert_Action (N,
2751 Make_Raise_Constraint_Error (Loc,
2752 Condition => Cond,
2753 Reason => CE_Length_Check_Failed));
2754 end if;
2756 -- Now look inside the sub-aggregate to see if there is more work
2758 if Dim < Aggr_Dimension then
2760 -- Process positional components
2762 if Present (Expressions (Sub_Aggr)) then
2763 Expr := First (Expressions (Sub_Aggr));
2764 while Present (Expr) loop
2765 Check_Same_Aggr_Bounds (Expr, Dim + 1);
2766 Next (Expr);
2767 end loop;
2768 end if;
2770 -- Process component associations
2772 if Present (Component_Associations (Sub_Aggr)) then
2773 Assoc := First (Component_Associations (Sub_Aggr));
2774 while Present (Assoc) loop
2775 Expr := Expression (Assoc);
2776 Check_Same_Aggr_Bounds (Expr, Dim + 1);
2777 Next (Assoc);
2778 end loop;
2779 end if;
2780 end if;
2781 end Check_Same_Aggr_Bounds;
2783 ----------------------------
2784 -- Compute_Others_Present --
2785 ----------------------------
2787 procedure Compute_Others_Present (Sub_Aggr : Node_Id; Dim : Pos) is
2788 Assoc : Node_Id;
2789 Expr : Node_Id;
2791 begin
2792 if Present (Component_Associations (Sub_Aggr)) then
2793 Assoc := Last (Component_Associations (Sub_Aggr));
2795 if Nkind (First (Choices (Assoc))) = N_Others_Choice then
2796 Others_Present (Dim) := True;
2797 end if;
2798 end if;
2800 -- Now look inside the sub-aggregate to see if there is more work
2802 if Dim < Aggr_Dimension then
2804 -- Process positional components
2806 if Present (Expressions (Sub_Aggr)) then
2807 Expr := First (Expressions (Sub_Aggr));
2808 while Present (Expr) loop
2809 Compute_Others_Present (Expr, Dim + 1);
2810 Next (Expr);
2811 end loop;
2812 end if;
2814 -- Process component associations
2816 if Present (Component_Associations (Sub_Aggr)) then
2817 Assoc := First (Component_Associations (Sub_Aggr));
2818 while Present (Assoc) loop
2819 Expr := Expression (Assoc);
2820 Compute_Others_Present (Expr, Dim + 1);
2821 Next (Assoc);
2822 end loop;
2823 end if;
2824 end if;
2825 end Compute_Others_Present;
2827 -------------------------
2828 -- Has_Address_Clause --
2829 -------------------------
2831 function Has_Address_Clause (D : Node_Id) return Boolean is
2832 Id : Entity_Id := Defining_Identifier (D);
2833 Decl : Node_Id := Next (D);
2835 begin
2836 while Present (Decl) loop
2838 if Nkind (Decl) = N_At_Clause
2839 and then Chars (Identifier (Decl)) = Chars (Id)
2840 then
2841 return True;
2843 elsif Nkind (Decl) = N_Attribute_Definition_Clause
2844 and then Chars (Decl) = Name_Address
2845 and then Chars (Name (Decl)) = Chars (Id)
2846 then
2847 return True;
2848 end if;
2850 Next (Decl);
2851 end loop;
2853 return False;
2854 end Has_Address_Clause;
2856 ------------------------
2857 -- In_Place_Assign_OK --
2858 ------------------------
2860 function In_Place_Assign_OK return Boolean is
2861 Aggr_In : Node_Id;
2862 Aggr_Lo : Node_Id;
2863 Aggr_Hi : Node_Id;
2864 Obj_In : Node_Id;
2865 Obj_Lo : Node_Id;
2866 Obj_Hi : Node_Id;
2868 function Is_Others_Aggregate (Aggr : Node_Id) return Boolean;
2869 -- Aggregates that consist of a single Others choice are safe
2870 -- if the single expression is.
2872 function Safe_Aggregate (Aggr : Node_Id) return Boolean;
2873 -- Check recursively that each component of a (sub)aggregate does
2874 -- not depend on the variable being assigned to.
2876 function Safe_Component (Expr : Node_Id) return Boolean;
2877 -- Verify that an expression cannot depend on the variable being
2878 -- assigned to. Room for improvement here (but less than before).
2880 -------------------------
2881 -- Is_Others_Aggregate --
2882 -------------------------
2884 function Is_Others_Aggregate (Aggr : Node_Id) return Boolean is
2885 begin
2886 return No (Expressions (Aggr))
2887 and then Nkind
2888 (First (Choices (First (Component_Associations (Aggr)))))
2889 = N_Others_Choice;
2890 end Is_Others_Aggregate;
2892 --------------------
2893 -- Safe_Aggregate --
2894 --------------------
2896 function Safe_Aggregate (Aggr : Node_Id) return Boolean is
2897 Expr : Node_Id;
2899 begin
2900 if Present (Expressions (Aggr)) then
2901 Expr := First (Expressions (Aggr));
2903 while Present (Expr) loop
2904 if Nkind (Expr) = N_Aggregate then
2905 if not Safe_Aggregate (Expr) then
2906 return False;
2907 end if;
2909 elsif not Safe_Component (Expr) then
2910 return False;
2911 end if;
2913 Next (Expr);
2914 end loop;
2915 end if;
2917 if Present (Component_Associations (Aggr)) then
2918 Expr := First (Component_Associations (Aggr));
2920 while Present (Expr) loop
2921 if Nkind (Expression (Expr)) = N_Aggregate then
2922 if not Safe_Aggregate (Expression (Expr)) then
2923 return False;
2924 end if;
2926 elsif not Safe_Component (Expression (Expr)) then
2927 return False;
2928 end if;
2930 Next (Expr);
2931 end loop;
2932 end if;
2934 return True;
2935 end Safe_Aggregate;
2937 --------------------
2938 -- Safe_Component --
2939 --------------------
2941 function Safe_Component (Expr : Node_Id) return Boolean is
2942 Comp : Node_Id := Expr;
2944 function Check_Component (Comp : Node_Id) return Boolean;
2945 -- Do the recursive traversal, after copy.
2947 function Check_Component (Comp : Node_Id) return Boolean is
2948 begin
2949 if Is_Overloaded (Comp) then
2950 return False;
2951 end if;
2953 return Compile_Time_Known_Value (Comp)
2955 or else (Is_Entity_Name (Comp)
2956 and then Present (Entity (Comp))
2957 and then No (Renamed_Object (Entity (Comp))))
2959 or else (Nkind (Comp) = N_Attribute_Reference
2960 and then Check_Component (Prefix (Comp)))
2962 or else (Nkind (Comp) in N_Binary_Op
2963 and then Check_Component (Left_Opnd (Comp))
2964 and then Check_Component (Right_Opnd (Comp)))
2966 or else (Nkind (Comp) in N_Unary_Op
2967 and then Check_Component (Right_Opnd (Comp)))
2969 or else (Nkind (Comp) = N_Selected_Component
2970 and then Check_Component (Prefix (Comp)));
2971 end Check_Component;
2973 -- Start of processing for Safe_Component
2975 begin
2976 -- If the component appears in an association that may
2977 -- correspond to more than one element, it is not analyzed
2978 -- before the expansion into assignments, to avoid side effects.
2979 -- We analyze, but do not resolve the copy, to obtain sufficient
2980 -- entity information for the checks that follow. If component is
2981 -- overloaded we assume an unsafe function call.
2983 if not Analyzed (Comp) then
2984 if Is_Overloaded (Expr) then
2985 return False;
2987 elsif Nkind (Expr) = N_Aggregate
2988 and then not Is_Others_Aggregate (Expr)
2989 then
2990 return False;
2992 elsif Nkind (Expr) = N_Allocator then
2993 -- For now, too complex to analyze.
2995 return False;
2996 end if;
2998 Comp := New_Copy_Tree (Expr);
2999 Set_Parent (Comp, Parent (Expr));
3000 Analyze (Comp);
3001 end if;
3003 if Nkind (Comp) = N_Aggregate then
3004 return Safe_Aggregate (Comp);
3005 else
3006 return Check_Component (Comp);
3007 end if;
3008 end Safe_Component;
3010 -- Start of processing for In_Place_Assign_OK
3012 begin
3013 if Present (Component_Associations (N)) then
3015 -- On assignment, sliding can take place, so we cannot do the
3016 -- assignment in place unless the bounds of the aggregate are
3017 -- statically equal to those of the target.
3019 -- If the aggregate is given by an others choice, the bounds
3020 -- are derived from the left-hand side, and the assignment is
3021 -- safe if the expression is.
3023 if Is_Others_Aggregate (N) then
3024 return
3025 Safe_Component
3026 (Expression (First (Component_Associations (N))));
3027 end if;
3029 Aggr_In := First_Index (Etype (N));
3030 Obj_In := First_Index (Etype (Name (Parent (N))));
3032 while Present (Aggr_In) loop
3033 Get_Index_Bounds (Aggr_In, Aggr_Lo, Aggr_Hi);
3034 Get_Index_Bounds (Obj_In, Obj_Lo, Obj_Hi);
3036 if not Compile_Time_Known_Value (Aggr_Lo)
3037 or else not Compile_Time_Known_Value (Aggr_Hi)
3038 or else not Compile_Time_Known_Value (Obj_Lo)
3039 or else not Compile_Time_Known_Value (Obj_Hi)
3040 or else Expr_Value (Aggr_Lo) /= Expr_Value (Obj_Lo)
3041 or else Expr_Value (Aggr_Hi) /= Expr_Value (Obj_Hi)
3042 then
3043 return False;
3044 end if;
3046 Next_Index (Aggr_In);
3047 Next_Index (Obj_In);
3048 end loop;
3049 end if;
3051 -- Now check the component values themselves.
3053 return Safe_Aggregate (N);
3054 end In_Place_Assign_OK;
3056 ------------------
3057 -- Others_Check --
3058 ------------------
3060 procedure Others_Check (Sub_Aggr : Node_Id; Dim : Pos) is
3061 Aggr_Lo : constant Node_Id := Aggr_Low (Dim);
3062 Aggr_Hi : constant Node_Id := Aggr_High (Dim);
3063 -- The bounds of the aggregate for this dimension.
3065 Ind_Typ : constant Entity_Id := Aggr_Index_Typ (Dim);
3066 -- The index type for this dimension.
3068 Need_To_Check : Boolean := False;
3070 Choices_Lo : Node_Id := Empty;
3071 Choices_Hi : Node_Id := Empty;
3072 -- The lowest and highest discrete choices for a named sub-aggregate
3074 Nb_Choices : Int := -1;
3075 -- The number of discrete non-others choices in this sub-aggregate
3077 Nb_Elements : Uint := Uint_0;
3078 -- The number of elements in a positional aggregate
3080 Cond : Node_Id := Empty;
3082 Assoc : Node_Id;
3083 Choice : Node_Id;
3084 Expr : Node_Id;
3086 begin
3087 -- Check if we have an others choice. If we do make sure that this
3088 -- sub-aggregate contains at least one element in addition to the
3089 -- others choice.
3091 if Range_Checks_Suppressed (Ind_Typ) then
3092 Need_To_Check := False;
3094 elsif Present (Expressions (Sub_Aggr))
3095 and then Present (Component_Associations (Sub_Aggr))
3096 then
3097 Need_To_Check := True;
3099 elsif Present (Component_Associations (Sub_Aggr)) then
3100 Assoc := Last (Component_Associations (Sub_Aggr));
3102 if Nkind (First (Choices (Assoc))) /= N_Others_Choice then
3103 Need_To_Check := False;
3105 else
3106 -- Count the number of discrete choices. Start with -1
3107 -- because the others choice does not count.
3109 Nb_Choices := -1;
3110 Assoc := First (Component_Associations (Sub_Aggr));
3111 while Present (Assoc) loop
3112 Choice := First (Choices (Assoc));
3113 while Present (Choice) loop
3114 Nb_Choices := Nb_Choices + 1;
3115 Next (Choice);
3116 end loop;
3118 Next (Assoc);
3119 end loop;
3121 -- If there is only an others choice nothing to do
3123 Need_To_Check := (Nb_Choices > 0);
3124 end if;
3126 else
3127 Need_To_Check := False;
3128 end if;
3130 -- If we are dealing with a positional sub-aggregate with an
3131 -- others choice then compute the number or positional elements.
3133 if Need_To_Check and then Present (Expressions (Sub_Aggr)) then
3134 Expr := First (Expressions (Sub_Aggr));
3135 Nb_Elements := Uint_0;
3136 while Present (Expr) loop
3137 Nb_Elements := Nb_Elements + 1;
3138 Next (Expr);
3139 end loop;
3141 -- If the aggregate contains discrete choices and an others choice
3142 -- compute the smallest and largest discrete choice values.
3144 elsif Need_To_Check then
3145 Compute_Choices_Lo_And_Choices_Hi : declare
3147 Table : Case_Table_Type (1 .. Nb_Choices);
3148 -- Used to sort all the different choice values
3150 J : Pos := 1;
3151 Low : Node_Id;
3152 High : Node_Id;
3154 begin
3155 Assoc := First (Component_Associations (Sub_Aggr));
3156 while Present (Assoc) loop
3157 Choice := First (Choices (Assoc));
3158 while Present (Choice) loop
3159 if Nkind (Choice) = N_Others_Choice then
3160 exit;
3161 end if;
3163 Get_Index_Bounds (Choice, Low, High);
3164 Table (J).Choice_Lo := Low;
3165 Table (J).Choice_Hi := High;
3167 J := J + 1;
3168 Next (Choice);
3169 end loop;
3171 Next (Assoc);
3172 end loop;
3174 -- Sort the discrete choices
3176 Sort_Case_Table (Table);
3178 Choices_Lo := Table (1).Choice_Lo;
3179 Choices_Hi := Table (Nb_Choices).Choice_Hi;
3180 end Compute_Choices_Lo_And_Choices_Hi;
3181 end if;
3183 -- If no others choice in this sub-aggregate, or the aggregate
3184 -- comprises only an others choice, nothing to do.
3186 if not Need_To_Check then
3187 Cond := Empty;
3189 -- If we are dealing with an aggregate containing an others
3190 -- choice and positional components, we generate the following test:
3192 -- if Ind_Typ'Pos (Aggr_Lo) + (Nb_Elements - 1) >
3193 -- Ind_Typ'Pos (Aggr_Hi)
3194 -- then
3195 -- raise Constraint_Error;
3196 -- end if;
3198 elsif Nb_Elements > Uint_0 then
3199 Cond :=
3200 Make_Op_Gt (Loc,
3201 Left_Opnd =>
3202 Make_Op_Add (Loc,
3203 Left_Opnd =>
3204 Make_Attribute_Reference (Loc,
3205 Prefix => New_Reference_To (Ind_Typ, Loc),
3206 Attribute_Name => Name_Pos,
3207 Expressions =>
3208 New_List (Duplicate_Subexpr (Aggr_Lo))),
3209 Right_Opnd => Make_Integer_Literal (Loc, Nb_Elements - 1)),
3211 Right_Opnd =>
3212 Make_Attribute_Reference (Loc,
3213 Prefix => New_Reference_To (Ind_Typ, Loc),
3214 Attribute_Name => Name_Pos,
3215 Expressions => New_List (Duplicate_Subexpr (Aggr_Hi))));
3217 -- If we are dealing with an aggregate containing an others
3218 -- choice and discrete choices we generate the following test:
3220 -- [constraint_error when
3221 -- Choices_Lo < Aggr_Lo or else Choices_Hi > Aggr_Hi];
3223 else
3224 Cond :=
3225 Make_Or_Else (Loc,
3226 Left_Opnd =>
3227 Make_Op_Lt (Loc,
3228 Left_Opnd => Duplicate_Subexpr (Choices_Lo),
3229 Right_Opnd => Duplicate_Subexpr (Aggr_Lo)),
3231 Right_Opnd =>
3232 Make_Op_Gt (Loc,
3233 Left_Opnd => Duplicate_Subexpr (Choices_Hi),
3234 Right_Opnd => Duplicate_Subexpr (Aggr_Hi)));
3235 end if;
3237 if Present (Cond) then
3238 Insert_Action (N,
3239 Make_Raise_Constraint_Error (Loc,
3240 Condition => Cond,
3241 Reason => CE_Length_Check_Failed));
3242 end if;
3244 -- Now look inside the sub-aggregate to see if there is more work
3246 if Dim < Aggr_Dimension then
3248 -- Process positional components
3250 if Present (Expressions (Sub_Aggr)) then
3251 Expr := First (Expressions (Sub_Aggr));
3252 while Present (Expr) loop
3253 Others_Check (Expr, Dim + 1);
3254 Next (Expr);
3255 end loop;
3256 end if;
3258 -- Process component associations
3260 if Present (Component_Associations (Sub_Aggr)) then
3261 Assoc := First (Component_Associations (Sub_Aggr));
3262 while Present (Assoc) loop
3263 Expr := Expression (Assoc);
3264 Others_Check (Expr, Dim + 1);
3265 Next (Assoc);
3266 end loop;
3267 end if;
3268 end if;
3269 end Others_Check;
3271 -- Remaining Expand_Array_Aggregate variables
3273 Tmp : Entity_Id;
3274 -- Holds the temporary aggregate value.
3276 Tmp_Decl : Node_Id;
3277 -- Holds the declaration of Tmp.
3279 Aggr_Code : List_Id;
3280 Parent_Node : Node_Id;
3281 Parent_Kind : Node_Kind;
3283 -- Start of processing for Expand_Array_Aggregate
3285 begin
3286 -- Do not touch the special aggregates of attributes used for Asm calls
3288 if Is_RTE (Ctyp, RE_Asm_Input_Operand)
3289 or else Is_RTE (Ctyp, RE_Asm_Output_Operand)
3290 then
3291 return;
3292 end if;
3294 -- If the semantic analyzer has determined that aggregate N will raise
3295 -- Constraint_Error at run-time, then the aggregate node has been
3296 -- replaced with an N_Raise_Constraint_Error node and we should
3297 -- never get here.
3299 pragma Assert (not Raises_Constraint_Error (N));
3301 -- STEP 1: Check (a)
3303 Index_Compatibility_Check : declare
3304 Aggr_Index_Range : Node_Id := First_Index (Typ);
3305 -- The current aggregate index range
3307 Index_Constraint : Node_Id := First_Index (Etype (Typ));
3308 -- The corresponding index constraint against which we have to
3309 -- check the above aggregate index range.
3311 begin
3312 Compute_Others_Present (N, 1);
3314 for J in 1 .. Aggr_Dimension loop
3315 -- There is no need to emit a check if an others choice is
3316 -- present for this array aggregate dimension since in this
3317 -- case one of N's sub-aggregates has taken its bounds from the
3318 -- context and these bounds must have been checked already. In
3319 -- addition all sub-aggregates corresponding to the same
3320 -- dimension must all have the same bounds (checked in (c) below).
3322 if not Range_Checks_Suppressed (Etype (Index_Constraint))
3323 and then not Others_Present (J)
3324 then
3325 -- We don't use Checks.Apply_Range_Check here because it
3326 -- emits a spurious check. Namely it checks that the range
3327 -- defined by the aggregate bounds is non empty. But we know
3328 -- this already if we get here.
3330 Check_Bounds (Aggr_Index_Range, Index_Constraint);
3331 end if;
3333 -- Save the low and high bounds of the aggregate index as well
3334 -- as the index type for later use in checks (b) and (c) below.
3336 Aggr_Low (J) := Low_Bound (Aggr_Index_Range);
3337 Aggr_High (J) := High_Bound (Aggr_Index_Range);
3339 Aggr_Index_Typ (J) := Etype (Index_Constraint);
3341 Next_Index (Aggr_Index_Range);
3342 Next_Index (Index_Constraint);
3343 end loop;
3344 end Index_Compatibility_Check;
3346 -- STEP 1: Check (b)
3348 Others_Check (N, 1);
3350 -- STEP 1: Check (c)
3352 if Aggr_Dimension > 1 then
3353 Check_Same_Aggr_Bounds (N, 1);
3354 end if;
3356 -- STEP 2.
3358 -- First try to convert to positional form. If the result is not
3359 -- an aggregate any more, then we are done with the analysis (it
3360 -- it could be a string literal or an identifier for a temporary
3361 -- variable following this call). If result is an analyzed aggregate
3362 -- the transformation was also successful and we are done as well.
3364 Convert_To_Positional (N);
3366 if Nkind (N) /= N_Aggregate then
3367 return;
3369 elsif Analyzed (N)
3370 and then N /= Original_Node (N)
3371 then
3372 return;
3373 end if;
3375 if Backend_Processing_Possible (N) then
3377 -- If the aggregate is static but the constraints are not, build
3378 -- a static subtype for the aggregate, so that Gigi can place it
3379 -- in static memory. Perform an unchecked_conversion to the non-
3380 -- static type imposed by the context.
3382 declare
3383 Itype : constant Entity_Id := Etype (N);
3384 Index : Node_Id;
3385 Needs_Type : Boolean := False;
3387 begin
3388 Index := First_Index (Itype);
3390 while Present (Index) loop
3391 if not Is_Static_Subtype (Etype (Index)) then
3392 Needs_Type := True;
3393 exit;
3394 else
3395 Next_Index (Index);
3396 end if;
3397 end loop;
3399 if Needs_Type then
3400 Build_Constrained_Type (Positional => True);
3401 Rewrite (N, Unchecked_Convert_To (Itype, N));
3402 Analyze (N);
3403 end if;
3404 end;
3406 return;
3407 end if;
3409 -- Delay expansion for nested aggregates it will be taken care of
3410 -- when the parent aggregate is expanded
3412 Parent_Node := Parent (N);
3413 Parent_Kind := Nkind (Parent_Node);
3415 if Parent_Kind = N_Qualified_Expression then
3416 Parent_Node := Parent (Parent_Node);
3417 Parent_Kind := Nkind (Parent_Node);
3418 end if;
3420 if Parent_Kind = N_Aggregate
3421 or else Parent_Kind = N_Extension_Aggregate
3422 or else Parent_Kind = N_Component_Association
3423 or else (Parent_Kind = N_Object_Declaration
3424 and then Controlled_Type (Typ))
3425 or else (Parent_Kind = N_Assignment_Statement
3426 and then Inside_Init_Proc)
3427 then
3428 Set_Expansion_Delayed (N);
3429 return;
3430 end if;
3432 -- STEP 3.
3434 -- Look if in place aggregate expansion is possible
3436 -- First case to test for is packed array aggregate that we can
3437 -- handle at compile time. If so, return with transformation done.
3439 if Packed_Array_Aggregate_Handled (N) then
3440 return;
3441 end if;
3443 -- For object declarations we build the aggregate in place, unless
3444 -- the array is bit-packed or the component is controlled.
3446 -- For assignments we do the assignment in place if all the component
3447 -- associations have compile-time known values. For other cases we
3448 -- create a temporary. The analysis for safety of on-line assignment
3449 -- is delicate, i.e. we don't know how to do it fully yet ???
3451 if Requires_Transient_Scope (Typ) then
3452 Establish_Transient_Scope
3453 (N, Sec_Stack => Has_Controlled_Component (Typ));
3454 end if;
3456 Maybe_In_Place_OK :=
3457 Comes_From_Source (N)
3458 and then Nkind (Parent (N)) = N_Assignment_Statement
3459 and then not Is_Bit_Packed_Array (Typ)
3460 and then not Has_Controlled_Component (Typ)
3461 and then In_Place_Assign_OK;
3463 if Comes_From_Source (Parent (N))
3464 and then Nkind (Parent (N)) = N_Object_Declaration
3465 and then N = Expression (Parent (N))
3466 and then not Is_Bit_Packed_Array (Typ)
3467 and then not Has_Controlled_Component (Typ)
3468 and then not Has_Address_Clause (Parent (N))
3469 then
3470 Tmp := Defining_Identifier (Parent (N));
3471 Set_No_Initialization (Parent (N));
3472 Set_Expression (Parent (N), Empty);
3474 -- Set the type of the entity, for use in the analysis of the
3475 -- subsequent indexed assignments. If the nominal type is not
3476 -- constrained, build a subtype from the known bounds of the
3477 -- aggregate. If the declaration has a subtype mark, use it,
3478 -- otherwise use the itype of the aggregate.
3480 if not Is_Constrained (Typ) then
3481 Build_Constrained_Type (Positional => False);
3482 elsif Is_Entity_Name (Object_Definition (Parent (N)))
3483 and then Is_Constrained (Entity (Object_Definition (Parent (N))))
3484 then
3485 Set_Etype (Tmp, Entity (Object_Definition (Parent (N))));
3486 else
3487 Set_Size_Known_At_Compile_Time (Typ, False);
3488 Set_Etype (Tmp, Typ);
3489 end if;
3491 elsif Maybe_In_Place_OK
3492 and then Is_Entity_Name (Name (Parent (N)))
3493 then
3494 Tmp := Entity (Name (Parent (N)));
3496 if Etype (Tmp) /= Etype (N) then
3497 Apply_Length_Check (N, Etype (Tmp));
3498 end if;
3500 elsif Maybe_In_Place_OK
3501 and then Nkind (Name (Parent (N))) = N_Explicit_Dereference
3502 and then Is_Entity_Name (Prefix (Name (Parent (N))))
3503 then
3504 Tmp := Name (Parent (N));
3506 if Etype (Tmp) /= Etype (N) then
3507 Apply_Length_Check (N, Etype (Tmp));
3508 end if;
3510 elsif Maybe_In_Place_OK
3511 and then Nkind (Name (Parent (N))) = N_Slice
3512 and then Safe_Slice_Assignment (N)
3513 then
3514 -- Safe_Slice_Assignment rewrites assignment as a loop
3516 return;
3518 else
3519 Maybe_In_Place_OK := False;
3520 Tmp := Make_Defining_Identifier (Loc, New_Internal_Name ('A'));
3521 Tmp_Decl :=
3522 Make_Object_Declaration
3523 (Loc,
3524 Defining_Identifier => Tmp,
3525 Object_Definition => New_Occurrence_Of (Typ, Loc));
3526 Set_No_Initialization (Tmp_Decl, True);
3528 -- If we are within a loop, the temporary will be pushed on the
3529 -- stack at each iteration. If the aggregate is the expression for
3530 -- an allocator, it will be immediately copied to the heap and can
3531 -- be reclaimed at once. We create a transient scope around the
3532 -- aggregate for this purpose.
3534 if Ekind (Current_Scope) = E_Loop
3535 and then Nkind (Parent (Parent (N))) = N_Allocator
3536 then
3537 Establish_Transient_Scope (N, False);
3538 end if;
3540 Insert_Action (N, Tmp_Decl);
3541 end if;
3543 -- Construct and insert the aggregate code. We can safely suppress
3544 -- index checks because this code is guaranteed not to raise CE
3545 -- on index checks. However we should *not* suppress all checks.
3547 declare
3548 Target : Node_Id;
3550 begin
3551 if Nkind (Tmp) = N_Defining_Identifier then
3552 Target := New_Reference_To (Tmp, Loc);
3554 else
3555 -- Name in assignment is explicit dereference.
3557 Target := New_Copy (Tmp);
3558 end if;
3560 Aggr_Code :=
3561 Build_Array_Aggr_Code (N,
3562 Index => First_Index (Typ),
3563 Into => Target,
3564 Scalar_Comp => Is_Scalar_Type (Ctyp));
3565 end;
3567 if Comes_From_Source (Tmp) then
3568 Insert_Actions_After (Parent (N), Aggr_Code);
3570 else
3571 Insert_Actions (N, Aggr_Code);
3572 end if;
3574 -- If the aggregate has been assigned in place, remove the original
3575 -- assignment.
3577 if Nkind (Parent (N)) = N_Assignment_Statement
3578 and then Maybe_In_Place_OK
3579 then
3580 Rewrite (Parent (N), Make_Null_Statement (Loc));
3582 elsif Nkind (Parent (N)) /= N_Object_Declaration
3583 or else Tmp /= Defining_Identifier (Parent (N))
3584 then
3585 Rewrite (N, New_Occurrence_Of (Tmp, Loc));
3586 Analyze_And_Resolve (N, Typ);
3587 end if;
3588 end Expand_Array_Aggregate;
3590 ------------------------
3591 -- Expand_N_Aggregate --
3592 ------------------------
3594 procedure Expand_N_Aggregate (N : Node_Id) is
3595 begin
3596 if Is_Record_Type (Etype (N)) then
3597 Expand_Record_Aggregate (N);
3598 else
3599 Expand_Array_Aggregate (N);
3600 end if;
3601 end Expand_N_Aggregate;
3603 ----------------------------------
3604 -- Expand_N_Extension_Aggregate --
3605 ----------------------------------
3607 -- If the ancestor part is an expression, add a component association for
3608 -- the parent field. If the type of the ancestor part is not the direct
3609 -- parent of the expected type, build recursively the needed ancestors.
3610 -- If the ancestor part is a subtype_mark, replace aggregate with a decla-
3611 -- ration for a temporary of the expected type, followed by individual
3612 -- assignments to the given components.
3614 procedure Expand_N_Extension_Aggregate (N : Node_Id) is
3615 Loc : constant Source_Ptr := Sloc (N);
3616 A : constant Node_Id := Ancestor_Part (N);
3617 Typ : constant Entity_Id := Etype (N);
3619 begin
3620 -- If the ancestor is a subtype mark, an init_proc must be called
3621 -- on the resulting object which thus has to be materialized in
3622 -- the front-end
3624 if Is_Entity_Name (A) and then Is_Type (Entity (A)) then
3625 Convert_To_Assignments (N, Typ);
3627 -- The extension aggregate is transformed into a record aggregate
3628 -- of the following form (c1 and c2 are inherited components)
3630 -- (Exp with c3 => a, c4 => b)
3631 -- ==> (c1 => Exp.c1, c2 => Exp.c2, c1 => a, c2 => b)
3633 else
3634 Set_Etype (N, Typ);
3636 -- No tag is needed in the case of Java_VM
3638 if Java_VM then
3639 Expand_Record_Aggregate (N,
3640 Parent_Expr => A);
3641 else
3642 Expand_Record_Aggregate (N,
3643 Orig_Tag => New_Occurrence_Of (Access_Disp_Table (Typ), Loc),
3644 Parent_Expr => A);
3645 end if;
3646 end if;
3647 end Expand_N_Extension_Aggregate;
3649 -----------------------------
3650 -- Expand_Record_Aggregate --
3651 -----------------------------
3653 procedure Expand_Record_Aggregate
3654 (N : Node_Id;
3655 Orig_Tag : Node_Id := Empty;
3656 Parent_Expr : Node_Id := Empty)
3658 Loc : constant Source_Ptr := Sloc (N);
3659 Comps : constant List_Id := Component_Associations (N);
3660 Typ : constant Entity_Id := Etype (N);
3661 Base_Typ : constant Entity_Id := Base_Type (Typ);
3663 function Has_Delayed_Nested_Aggregate_Or_Tagged_Comps return Boolean;
3664 -- Checks the presence of a nested aggregate which needs Late_Expansion
3665 -- or the presence of tagged components which may need tag adjustment.
3667 --------------------------------------------------
3668 -- Has_Delayed_Nested_Aggregate_Or_Tagged_Comps --
3669 --------------------------------------------------
3671 function Has_Delayed_Nested_Aggregate_Or_Tagged_Comps return Boolean is
3672 C : Node_Id;
3673 Expr_Q : Node_Id;
3675 begin
3676 if No (Comps) then
3677 return False;
3678 end if;
3680 C := First (Comps);
3681 while Present (C) loop
3683 if Nkind (Expression (C)) = N_Qualified_Expression then
3684 Expr_Q := Expression (Expression (C));
3685 else
3686 Expr_Q := Expression (C);
3687 end if;
3689 -- Return true if the aggregate has any associations for
3690 -- tagged components that may require tag adjustment.
3691 -- These are cases where the source expression may have
3692 -- a tag that could differ from the component tag (e.g.,
3693 -- can occur for type conversions and formal parameters).
3694 -- (Tag adjustment is not needed if Java_VM because object
3695 -- tags are implicit in the JVM.)
3697 if Is_Tagged_Type (Etype (Expr_Q))
3698 and then (Nkind (Expr_Q) = N_Type_Conversion
3699 or else (Is_Entity_Name (Expr_Q)
3700 and then Ekind (Entity (Expr_Q)) in Formal_Kind))
3701 and then not Java_VM
3702 then
3703 return True;
3704 end if;
3706 if Is_Delayed_Aggregate (Expr_Q) then
3707 return True;
3708 end if;
3710 Next (C);
3711 end loop;
3713 return False;
3714 end Has_Delayed_Nested_Aggregate_Or_Tagged_Comps;
3716 -- Remaining Expand_Record_Aggregate variables
3718 Tag_Value : Node_Id;
3719 Comp : Entity_Id;
3720 New_Comp : Node_Id;
3722 -- Start of processing for Expand_Record_Aggregate
3724 begin
3725 -- Gigi doesn't handle properly temporaries of variable size
3726 -- so we generate it in the front-end
3728 if not Size_Known_At_Compile_Time (Typ) then
3729 Convert_To_Assignments (N, Typ);
3731 -- Temporaries for controlled aggregates need to be attached to a
3732 -- final chain in order to be properly finalized, so it has to
3733 -- be created in the front-end
3735 elsif Is_Controlled (Typ)
3736 or else Has_Controlled_Component (Base_Type (Typ))
3737 then
3738 Convert_To_Assignments (N, Typ);
3740 elsif Has_Delayed_Nested_Aggregate_Or_Tagged_Comps then
3741 Convert_To_Assignments (N, Typ);
3743 -- If an ancestor is private, some components are not inherited and
3744 -- we cannot expand into a record aggregate
3746 elsif Has_Private_Ancestor (Typ) then
3747 Convert_To_Assignments (N, Typ);
3749 -- ??? The following was done to compile fxacc00.ads in the ACVCs. Gigi
3750 -- is not able to handle the aggregate for Late_Request.
3752 elsif Is_Tagged_Type (Typ) and then Has_Discriminants (Typ) then
3753 Convert_To_Assignments (N, Typ);
3755 -- In all other cases we generate a proper aggregate that
3756 -- can be handled by gigi.
3758 else
3759 -- If no discriminants, nothing special to do
3761 if not Has_Discriminants (Typ) then
3762 null;
3764 -- Case of discriminants present
3766 elsif Is_Derived_Type (Typ) then
3768 -- For untagged types, non-girder discriminants are replaced
3769 -- with girder discriminants, which are the ones that gigi uses
3770 -- to describe the type and its components.
3772 Generate_Aggregate_For_Derived_Type : declare
3773 First_Comp : Node_Id;
3774 Discriminant : Entity_Id;
3775 Constraints : List_Id := New_List;
3776 Decl : Node_Id;
3777 Num_Disc : Int := 0;
3778 Num_Gird : Int := 0;
3780 procedure Prepend_Girder_Values (T : Entity_Id);
3781 -- Scan the list of girder discriminants of the type, and
3782 -- add their values to the aggregate being built.
3784 ---------------------------
3785 -- Prepend_Girder_Values --
3786 ---------------------------
3788 procedure Prepend_Girder_Values (T : Entity_Id) is
3789 begin
3790 Discriminant := First_Girder_Discriminant (T);
3792 while Present (Discriminant) loop
3793 New_Comp :=
3794 Make_Component_Association (Loc,
3795 Choices =>
3796 New_List (New_Occurrence_Of (Discriminant, Loc)),
3798 Expression =>
3799 New_Copy_Tree (
3800 Get_Discriminant_Value (
3801 Discriminant,
3802 Typ,
3803 Discriminant_Constraint (Typ))));
3805 if No (First_Comp) then
3806 Prepend_To (Component_Associations (N), New_Comp);
3807 else
3808 Insert_After (First_Comp, New_Comp);
3809 end if;
3811 First_Comp := New_Comp;
3812 Next_Girder_Discriminant (Discriminant);
3813 end loop;
3814 end Prepend_Girder_Values;
3816 -- Start of processing for Generate_Aggregate_For_Derived_Type
3818 begin
3819 -- Remove the associations for the discriminant of
3820 -- the derived type.
3822 First_Comp := First (Component_Associations (N));
3824 while Present (First_Comp) loop
3825 Comp := First_Comp;
3826 Next (First_Comp);
3828 if Ekind (Entity (First (Choices (Comp)))) =
3829 E_Discriminant
3830 then
3831 Remove (Comp);
3832 Num_Disc := Num_Disc + 1;
3833 end if;
3834 end loop;
3836 -- Insert girder discriminant associations in the correct
3837 -- order. If there are more girder discriminants than new
3838 -- discriminants, there is at least one new discriminant
3839 -- that constrains more than one of the girders. In this
3840 -- case we need to construct a proper subtype of the parent
3841 -- type, in order to supply values to all the components.
3842 -- Otherwise there is one-one correspondence between the
3843 -- constraints and the girder discriminants.
3845 First_Comp := Empty;
3847 Discriminant := First_Girder_Discriminant (Base_Type (Typ));
3849 while Present (Discriminant) loop
3850 Num_Gird := Num_Gird + 1;
3851 Next_Girder_Discriminant (Discriminant);
3852 end loop;
3854 -- Case of more girder discriminants than new discriminants
3856 if Num_Gird > Num_Disc then
3858 -- Create a proper subtype of the parent type, which is
3859 -- the proper implementation type for the aggregate, and
3860 -- convert it to the intended target type.
3862 Discriminant := First_Girder_Discriminant (Base_Type (Typ));
3864 while Present (Discriminant) loop
3865 New_Comp :=
3866 New_Copy_Tree (
3867 Get_Discriminant_Value (
3868 Discriminant,
3869 Typ,
3870 Discriminant_Constraint (Typ)));
3871 Append (New_Comp, Constraints);
3872 Next_Girder_Discriminant (Discriminant);
3873 end loop;
3875 Decl :=
3876 Make_Subtype_Declaration (Loc,
3877 Defining_Identifier =>
3878 Make_Defining_Identifier (Loc,
3879 New_Internal_Name ('T')),
3880 Subtype_Indication =>
3881 Make_Subtype_Indication (Loc,
3882 Subtype_Mark =>
3883 New_Occurrence_Of (Etype (Base_Type (Typ)), Loc),
3884 Constraint =>
3885 Make_Index_Or_Discriminant_Constraint
3886 (Loc, Constraints)));
3888 Insert_Action (N, Decl);
3889 Prepend_Girder_Values (Base_Type (Typ));
3891 Set_Etype (N, Defining_Identifier (Decl));
3892 Set_Analyzed (N);
3894 Rewrite (N, Unchecked_Convert_To (Typ, N));
3895 Analyze (N);
3897 -- Case where we do not have fewer new discriminants than
3898 -- girder discriminants, so in this case we can simply
3899 -- use the girder discriminants of the subtype.
3901 else
3902 Prepend_Girder_Values (Typ);
3903 end if;
3904 end Generate_Aggregate_For_Derived_Type;
3905 end if;
3907 if Is_Tagged_Type (Typ) then
3909 -- The tagged case, _parent and _tag component must be created.
3911 -- Reset null_present unconditionally. tagged records always have
3912 -- at least one field (the tag or the parent)
3914 Set_Null_Record_Present (N, False);
3916 -- When the current aggregate comes from the expansion of an
3917 -- extension aggregate, the parent expr is replaced by an
3918 -- aggregate formed by selected components of this expr
3920 if Present (Parent_Expr)
3921 and then Is_Empty_List (Comps)
3922 then
3923 Comp := First_Entity (Typ);
3924 while Present (Comp) loop
3926 -- Skip all entities that aren't discriminants or components
3928 if Ekind (Comp) /= E_Discriminant
3929 and then Ekind (Comp) /= E_Component
3930 then
3931 null;
3933 -- Skip all expander-generated components
3935 elsif
3936 not Comes_From_Source (Original_Record_Component (Comp))
3937 then
3938 null;
3940 else
3941 New_Comp :=
3942 Make_Selected_Component (Loc,
3943 Prefix =>
3944 Unchecked_Convert_To (Typ,
3945 Duplicate_Subexpr (Parent_Expr, True)),
3947 Selector_Name => New_Occurrence_Of (Comp, Loc));
3949 Append_To (Comps,
3950 Make_Component_Association (Loc,
3951 Choices =>
3952 New_List (New_Occurrence_Of (Comp, Loc)),
3953 Expression =>
3954 New_Comp));
3956 Analyze_And_Resolve (New_Comp, Etype (Comp));
3957 end if;
3959 Next_Entity (Comp);
3960 end loop;
3961 end if;
3963 -- Compute the value for the Tag now, if the type is a root it
3964 -- will be included in the aggregate right away, otherwise it will
3965 -- be propagated to the parent aggregate
3967 if Present (Orig_Tag) then
3968 Tag_Value := Orig_Tag;
3969 elsif Java_VM then
3970 Tag_Value := Empty;
3971 else
3972 Tag_Value := New_Occurrence_Of (Access_Disp_Table (Typ), Loc);
3973 end if;
3975 -- For a derived type, an aggregate for the parent is formed with
3976 -- all the inherited components.
3978 if Is_Derived_Type (Typ) then
3980 declare
3981 First_Comp : Node_Id;
3982 Parent_Comps : List_Id;
3983 Parent_Aggr : Node_Id;
3984 Parent_Name : Node_Id;
3986 begin
3987 -- Remove the inherited component association from the
3988 -- aggregate and store them in the parent aggregate
3990 First_Comp := First (Component_Associations (N));
3991 Parent_Comps := New_List;
3993 while Present (First_Comp)
3994 and then Scope (Original_Record_Component (
3995 Entity (First (Choices (First_Comp))))) /= Base_Typ
3996 loop
3997 Comp := First_Comp;
3998 Next (First_Comp);
3999 Remove (Comp);
4000 Append (Comp, Parent_Comps);
4001 end loop;
4003 Parent_Aggr := Make_Aggregate (Loc,
4004 Component_Associations => Parent_Comps);
4005 Set_Etype (Parent_Aggr, Etype (Base_Type (Typ)));
4007 -- Find the _parent component
4009 Comp := First_Component (Typ);
4010 while Chars (Comp) /= Name_uParent loop
4011 Comp := Next_Component (Comp);
4012 end loop;
4014 Parent_Name := New_Occurrence_Of (Comp, Loc);
4016 -- Insert the parent aggregate
4018 Prepend_To (Component_Associations (N),
4019 Make_Component_Association (Loc,
4020 Choices => New_List (Parent_Name),
4021 Expression => Parent_Aggr));
4023 -- Expand recursively the parent propagating the right Tag
4025 Expand_Record_Aggregate (
4026 Parent_Aggr, Tag_Value, Parent_Expr);
4027 end;
4029 -- For a root type, the tag component is added (unless compiling
4030 -- for the Java VM, where tags are implicit).
4032 elsif not Java_VM then
4033 declare
4034 Tag_Name : constant Node_Id :=
4035 New_Occurrence_Of (Tag_Component (Typ), Loc);
4036 Typ_Tag : constant Entity_Id := RTE (RE_Tag);
4037 Conv_Node : constant Node_Id :=
4038 Unchecked_Convert_To (Typ_Tag, Tag_Value);
4040 begin
4041 Set_Etype (Conv_Node, Typ_Tag);
4042 Prepend_To (Component_Associations (N),
4043 Make_Component_Association (Loc,
4044 Choices => New_List (Tag_Name),
4045 Expression => Conv_Node));
4046 end;
4047 end if;
4048 end if;
4049 end if;
4050 end Expand_Record_Aggregate;
4052 --------------------------
4053 -- Is_Delayed_Aggregate --
4054 --------------------------
4056 function Is_Delayed_Aggregate (N : Node_Id) return Boolean is
4057 Node : Node_Id := N;
4058 Kind : Node_Kind := Nkind (Node);
4059 begin
4060 if Kind = N_Qualified_Expression then
4061 Node := Expression (Node);
4062 Kind := Nkind (Node);
4063 end if;
4065 if Kind /= N_Aggregate and then Kind /= N_Extension_Aggregate then
4066 return False;
4067 else
4068 return Expansion_Delayed (Node);
4069 end if;
4070 end Is_Delayed_Aggregate;
4072 --------------------
4073 -- Late_Expansion --
4074 --------------------
4076 function Late_Expansion
4077 (N : Node_Id;
4078 Typ : Entity_Id;
4079 Target : Node_Id;
4080 Flist : Node_Id := Empty;
4081 Obj : Entity_Id := Empty)
4083 return List_Id is
4085 begin
4086 if Is_Record_Type (Etype (N)) then
4087 return Build_Record_Aggr_Code (N, Typ, Target, Flist, Obj);
4088 else
4089 return
4090 Build_Array_Aggr_Code
4092 First_Index (Typ),
4093 Target,
4094 Is_Scalar_Type (Component_Type (Typ)),
4095 No_List,
4096 Flist);
4097 end if;
4098 end Late_Expansion;
4100 ----------------------------------
4101 -- Make_OK_Assignment_Statement --
4102 ----------------------------------
4104 function Make_OK_Assignment_Statement
4105 (Sloc : Source_Ptr;
4106 Name : Node_Id;
4107 Expression : Node_Id)
4108 return Node_Id
4110 begin
4111 Set_Assignment_OK (Name);
4112 return Make_Assignment_Statement (Sloc, Name, Expression);
4113 end Make_OK_Assignment_Statement;
4115 -----------------------
4116 -- Number_Of_Choices --
4117 -----------------------
4119 function Number_Of_Choices (N : Node_Id) return Nat is
4120 Assoc : Node_Id;
4121 Choice : Node_Id;
4123 Nb_Choices : Nat := 0;
4125 begin
4126 if Present (Expressions (N)) then
4127 return 0;
4128 end if;
4130 Assoc := First (Component_Associations (N));
4131 while Present (Assoc) loop
4133 Choice := First (Choices (Assoc));
4134 while Present (Choice) loop
4136 if Nkind (Choice) /= N_Others_Choice then
4137 Nb_Choices := Nb_Choices + 1;
4138 end if;
4140 Next (Choice);
4141 end loop;
4143 Next (Assoc);
4144 end loop;
4146 return Nb_Choices;
4147 end Number_Of_Choices;
4149 ------------------------------------
4150 -- Packed_Array_Aggregate_Handled --
4151 ------------------------------------
4153 -- The current version of this procedure will handle at compile time
4154 -- any array aggregate that meets these conditions:
4156 -- One dimensional, bit packed
4157 -- Underlying packed type is modular type
4158 -- Bounds are within 32-bit Int range
4159 -- All bounds and values are static
4161 function Packed_Array_Aggregate_Handled (N : Node_Id) return Boolean is
4162 Loc : constant Source_Ptr := Sloc (N);
4163 Typ : constant Entity_Id := Etype (N);
4164 Ctyp : constant Entity_Id := Component_Type (Typ);
4166 Not_Handled : exception;
4167 -- Exception raised if this aggregate cannot be handled
4169 begin
4170 -- For now, handle only one dimensional bit packed arrays
4172 if not Is_Bit_Packed_Array (Typ)
4173 or else Number_Dimensions (Typ) > 1
4174 or else not Is_Modular_Integer_Type (Packed_Array_Type (Typ))
4175 then
4176 return False;
4177 end if;
4179 declare
4180 Csiz : constant Nat := UI_To_Int (Component_Size (Typ));
4182 Lo : Node_Id;
4183 Hi : Node_Id;
4184 -- Bounds of index type
4186 Lob : Uint;
4187 Hib : Uint;
4188 -- Values of bounds if compile time known
4190 function Get_Component_Val (N : Node_Id) return Uint;
4191 -- Given a expression value N of the component type Ctyp, returns
4192 -- A value of Csiz (component size) bits representing this value.
4193 -- If the value is non-static or any other reason exists why the
4194 -- value cannot be returned, then Not_Handled is raised.
4196 -----------------------
4197 -- Get_Component_Val --
4198 -----------------------
4200 function Get_Component_Val (N : Node_Id) return Uint is
4201 Val : Uint;
4203 begin
4204 -- We have to analyze the expression here before doing any further
4205 -- processing here. The analysis of such expressions is deferred
4206 -- till expansion to prevent some problems of premature analysis.
4208 Analyze_And_Resolve (N, Ctyp);
4210 -- Must have a compile time value
4212 if not Compile_Time_Known_Value (N) then
4213 raise Not_Handled;
4214 end if;
4216 Val := Expr_Rep_Value (N);
4218 -- Adjust for bias, and strip proper number of bits
4220 if Has_Biased_Representation (Ctyp) then
4221 Val := Val - Expr_Value (Type_Low_Bound (Ctyp));
4222 end if;
4224 return Val mod Uint_2 ** Csiz;
4225 end Get_Component_Val;
4227 -- Here we know we have a one dimensional bit packed array
4229 begin
4230 Get_Index_Bounds (First_Index (Typ), Lo, Hi);
4232 -- Cannot do anything if bounds are dynamic
4234 if not Compile_Time_Known_Value (Lo)
4235 or else
4236 not Compile_Time_Known_Value (Hi)
4237 then
4238 return False;
4239 end if;
4241 -- Or are silly out of range of int bounds
4243 Lob := Expr_Value (Lo);
4244 Hib := Expr_Value (Hi);
4246 if not UI_Is_In_Int_Range (Lob)
4247 or else
4248 not UI_Is_In_Int_Range (Hib)
4249 then
4250 return False;
4251 end if;
4253 -- At this stage we have a suitable aggregate for handling
4254 -- at compile time (the only remaining checks, are that the
4255 -- values of expressions in the aggregate are compile time
4256 -- known (check performed by Get_Component_Val), and that
4257 -- any subtypes or ranges are statically known.
4259 -- If the aggregate is not fully positional at this stage,
4260 -- then convert it to positional form. Either this will fail,
4261 -- in which case we can do nothing, or it will succeed, in
4262 -- which case we have succeeded in handling the aggregate,
4263 -- or it will stay an aggregate, in which case we have failed
4264 -- to handle this case.
4266 if Present (Component_Associations (N)) then
4267 Convert_To_Positional
4268 (N, Max_Others_Replicate => 64, Handle_Bit_Packed => True);
4269 return Nkind (N) /= N_Aggregate;
4270 end if;
4272 -- Otherwise we are all positional, so convert to proper value
4274 declare
4275 Lov : constant Nat := UI_To_Int (Lob);
4276 Hiv : constant Nat := UI_To_Int (Hib);
4278 Len : constant Nat := Int'Max (0, Hiv - Lov + 1);
4279 -- The length of the array (number of elements)
4281 Aggregate_Val : Uint;
4282 -- Value of aggregate. The value is set in the low order
4283 -- bits of this value. For the little-endian case, the
4284 -- values are stored from low-order to high-order and
4285 -- for the big-endian case the values are stored from
4286 -- high-order to low-order. Note that gigi will take care
4287 -- of the conversions to left justify the value in the big
4288 -- endian case (because of left justified modular type
4289 -- processing), so we do not have to worry about that here.
4291 Lit : Node_Id;
4292 -- Integer literal for resulting constructed value
4294 Shift : Nat;
4295 -- Shift count from low order for next value
4297 Incr : Int;
4298 -- Shift increment for loop
4300 Expr : Node_Id;
4301 -- Next expression from positional parameters of aggregate
4303 begin
4304 -- For little endian, we fill up the low order bits of the
4305 -- target value. For big endian we fill up the high order
4306 -- bits of the target value (which is a left justified
4307 -- modular value).
4309 if Bytes_Big_Endian xor Debug_Flag_8 then
4310 Shift := Csiz * (Len - 1);
4311 Incr := -Csiz;
4312 else
4313 Shift := 0;
4314 Incr := +Csiz;
4315 end if;
4317 -- Loop to set the values
4319 Aggregate_Val := Uint_0;
4320 Expr := First (Expressions (N));
4321 for J in 1 .. Len loop
4322 Aggregate_Val :=
4323 Aggregate_Val + Get_Component_Val (Expr) * Uint_2 ** Shift;
4324 Shift := Shift + Incr;
4325 Next (Expr);
4326 end loop;
4328 -- Now we can rewrite with the proper value
4330 Lit :=
4331 Make_Integer_Literal (Loc,
4332 Intval => Aggregate_Val);
4333 Set_Print_In_Hex (Lit);
4335 -- Construct the expression using this literal. Note that it is
4336 -- important to qualify the literal with its proper modular type
4337 -- since universal integer does not have the required range and
4338 -- also this is a left justified modular type, which is important
4339 -- in the big-endian case.
4341 Rewrite (N,
4342 Unchecked_Convert_To (Typ,
4343 Make_Qualified_Expression (Loc,
4344 Subtype_Mark =>
4345 New_Occurrence_Of (Packed_Array_Type (Typ), Loc),
4346 Expression => Lit)));
4348 Analyze_And_Resolve (N, Typ);
4349 return True;
4350 end;
4351 end;
4353 exception
4354 when Not_Handled =>
4355 return False;
4356 end Packed_Array_Aggregate_Handled;
4358 ------------------------------
4359 -- Initialize_Discriminants --
4360 ------------------------------
4362 procedure Initialize_Discriminants (N : Node_Id; Typ : Entity_Id) is
4363 Loc : constant Source_Ptr := Sloc (N);
4364 Bas : constant Entity_Id := Base_Type (Typ);
4365 Par : constant Entity_Id := Etype (Bas);
4366 Decl : constant Node_Id := Parent (Par);
4367 Ref : Node_Id;
4369 begin
4370 if Is_Tagged_Type (Bas)
4371 and then Is_Derived_Type (Bas)
4372 and then Has_Discriminants (Par)
4373 and then Has_Discriminants (Bas)
4374 and then Number_Discriminants (Bas) /= Number_Discriminants (Par)
4375 and then Nkind (Decl) = N_Full_Type_Declaration
4376 and then Nkind (Type_Definition (Decl)) = N_Record_Definition
4377 and then Present
4378 (Variant_Part (Component_List (Type_Definition (Decl))))
4379 and then Nkind (N) /= N_Extension_Aggregate
4380 then
4382 -- Call init_proc to set discriminants.
4383 -- There should eventually be a special procedure for this ???
4385 Ref := New_Reference_To (Defining_Identifier (N), Loc);
4386 Insert_Actions_After (N,
4387 Build_Initialization_Call (Sloc (N), Ref, Typ));
4388 end if;
4389 end Initialize_Discriminants;
4391 ---------------------------
4392 -- Safe_Slice_Assignment --
4393 ---------------------------
4395 function Safe_Slice_Assignment (N : Node_Id) return Boolean is
4396 Loc : constant Source_Ptr := Sloc (Parent (N));
4397 Pref : constant Node_Id := Prefix (Name (Parent (N)));
4398 Range_Node : constant Node_Id := Discrete_Range (Name (Parent (N)));
4399 Expr : Node_Id;
4400 L_J : Entity_Id;
4401 L_Iter : Node_Id;
4402 L_Body : Node_Id;
4403 Stat : Node_Id;
4405 begin
4406 -- Generate: for J in Range loop Pref (J) := Expr; end loop;
4408 if Comes_From_Source (N)
4409 and then No (Expressions (N))
4410 and then Nkind (First (Choices (First (Component_Associations (N)))))
4411 = N_Others_Choice
4412 then
4413 Expr :=
4414 Expression (First (Component_Associations (N)));
4415 L_J := Make_Defining_Identifier (Loc, New_Internal_Name ('J'));
4417 L_Iter :=
4418 Make_Iteration_Scheme (Loc,
4419 Loop_Parameter_Specification =>
4420 Make_Loop_Parameter_Specification
4421 (Loc,
4422 Defining_Identifier => L_J,
4423 Discrete_Subtype_Definition => Relocate_Node (Range_Node)));
4425 L_Body :=
4426 Make_Assignment_Statement (Loc,
4427 Name =>
4428 Make_Indexed_Component (Loc,
4429 Prefix => Relocate_Node (Pref),
4430 Expressions => New_List (New_Occurrence_Of (L_J, Loc))),
4431 Expression => Relocate_Node (Expr));
4433 -- Construct the final loop
4435 Stat :=
4436 Make_Implicit_Loop_Statement
4437 (Node => Parent (N),
4438 Identifier => Empty,
4439 Iteration_Scheme => L_Iter,
4440 Statements => New_List (L_Body));
4442 Rewrite (Parent (N), Stat);
4443 Analyze (Parent (N));
4444 return True;
4446 else
4447 return False;
4448 end if;
4449 end Safe_Slice_Assignment;
4451 ---------------------
4452 -- Sort_Case_Table --
4453 ---------------------
4455 procedure Sort_Case_Table (Case_Table : in out Case_Table_Type) is
4456 L : Int := Case_Table'First;
4457 U : Int := Case_Table'Last;
4458 K : Int;
4459 J : Int;
4460 T : Case_Bounds;
4462 begin
4463 K := L;
4465 while K /= U loop
4466 T := Case_Table (K + 1);
4467 J := K + 1;
4469 while J /= L
4470 and then Expr_Value (Case_Table (J - 1).Choice_Lo) >
4471 Expr_Value (T.Choice_Lo)
4472 loop
4473 Case_Table (J) := Case_Table (J - 1);
4474 J := J - 1;
4475 end loop;
4477 Case_Table (J) := T;
4478 K := K + 1;
4479 end loop;
4480 end Sort_Case_Table;
4482 end Exp_Aggr;