Merged revisions 208012,208018-208019,208021,208023-208030,208033,208037,208040-20804...
[official-gcc.git] / main / gcc / ada / layout.adb
blob829d75c2eb923d233b1b578ee19b4df0e40cf0ae
1 ------------------------------------------------------------------------------
2 -- --
3 -- GNAT COMPILER COMPONENTS --
4 -- --
5 -- L A Y O U T --
6 -- --
7 -- B o d y --
8 -- --
9 -- Copyright (C) 2001-2013, Free Software Foundation, Inc. --
10 -- --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 3, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING3. If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license. --
20 -- --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
23 -- --
24 ------------------------------------------------------------------------------
26 with Atree; use Atree;
27 with Checks; use Checks;
28 with Debug; use Debug;
29 with Einfo; use Einfo;
30 with Errout; use Errout;
31 with Exp_Ch3; use Exp_Ch3;
32 with Exp_Util; use Exp_Util;
33 with Namet; use Namet;
34 with Nlists; use Nlists;
35 with Nmake; use Nmake;
36 with Opt; use Opt;
37 with Repinfo; use Repinfo;
38 with Sem; use Sem;
39 with Sem_Aux; use Sem_Aux;
40 with Sem_Case; use Sem_Case;
41 with Sem_Ch13; use Sem_Ch13;
42 with Sem_Eval; use Sem_Eval;
43 with Sem_Util; use Sem_Util;
44 with Sinfo; use Sinfo;
45 with Snames; use Snames;
46 with Stand; use Stand;
47 with Targparm; use Targparm;
48 with Tbuild; use Tbuild;
49 with Ttypes; use Ttypes;
50 with Uintp; use Uintp;
52 package body Layout is
54 ------------------------
55 -- Local Declarations --
56 ------------------------
58 SSU : constant Int := Ttypes.System_Storage_Unit;
59 -- Short hand for System_Storage_Unit
61 Vname : constant Name_Id := Name_uV;
62 -- Formal parameter name used for functions generated for size offset
63 -- values that depend on the discriminant. All such functions have the
64 -- following form:
66 -- function xxx (V : vtyp) return Unsigned is
67 -- begin
68 -- return ... expression involving V.discrim
69 -- end xxx;
71 -----------------------
72 -- Local Subprograms --
73 -----------------------
75 function Assoc_Add
76 (Loc : Source_Ptr;
77 Left_Opnd : Node_Id;
78 Right_Opnd : Node_Id) return Node_Id;
79 -- This is like Make_Op_Add except that it optimizes some cases knowing
80 -- that associative rearrangement is allowed for constant folding if one
81 -- of the operands is a compile time known value.
83 function Assoc_Multiply
84 (Loc : Source_Ptr;
85 Left_Opnd : Node_Id;
86 Right_Opnd : Node_Id) return Node_Id;
87 -- This is like Make_Op_Multiply except that it optimizes some cases
88 -- knowing that associative rearrangement is allowed for constant folding
89 -- if one of the operands is a compile time known value
91 function Assoc_Subtract
92 (Loc : Source_Ptr;
93 Left_Opnd : Node_Id;
94 Right_Opnd : Node_Id) return Node_Id;
95 -- This is like Make_Op_Subtract except that it optimizes some cases
96 -- knowing that associative rearrangement is allowed for constant folding
97 -- if one of the operands is a compile time known value
99 function Bits_To_SU (N : Node_Id) return Node_Id;
100 -- This is used when we cross the boundary from static sizes in bits to
101 -- dynamic sizes in storage units. If the argument N is anything other
102 -- than an integer literal, it is returned unchanged, but if it is an
103 -- integer literal, then it is taken as a size in bits, and is replaced
104 -- by the corresponding size in storage units.
106 function Compute_Length (Lo : Node_Id; Hi : Node_Id) return Node_Id;
107 -- Given expressions for the low bound (Lo) and the high bound (Hi),
108 -- Build an expression for the value hi-lo+1, converted to type
109 -- Standard.Unsigned. Takes care of the case where the operands
110 -- are of an enumeration type (so that the subtraction cannot be
111 -- done directly) by applying the Pos operator to Hi/Lo first.
113 procedure Compute_Size_Depends_On_Discriminant (E : Entity_Id);
114 -- Given an array type or an array subtype E, compute whether its size
115 -- depends on the value of one or more discriminants and set the flag
116 -- Size_Depends_On_Discriminant accordingly. This need not be called
117 -- in front end layout mode since it does the computation on its own.
119 function Expr_From_SO_Ref
120 (Loc : Source_Ptr;
121 D : SO_Ref;
122 Comp : Entity_Id := Empty) return Node_Id;
123 -- Given a value D from a size or offset field, return an expression
124 -- representing the value stored. If the value is known at compile time,
125 -- then an N_Integer_Literal is returned with the appropriate value. If
126 -- the value references a constant entity, then an N_Identifier node
127 -- referencing this entity is returned. If the value denotes a size
128 -- function, then returns a call node denoting the given function, with
129 -- a single actual parameter that either refers to the parameter V of
130 -- an enclosing size function (if Comp is Empty or its type doesn't match
131 -- the function's formal), or else is a selected component V.c when Comp
132 -- denotes a component c whose type matches that of the function formal.
133 -- The Loc value is used for the Sloc value of constructed notes.
135 function SO_Ref_From_Expr
136 (Expr : Node_Id;
137 Ins_Type : Entity_Id;
138 Vtype : Entity_Id := Empty;
139 Make_Func : Boolean := False) return Dynamic_SO_Ref;
140 -- This routine is used in the case where a size/offset value is dynamic
141 -- and is represented by the expression Expr. SO_Ref_From_Expr checks if
142 -- the Expr contains a reference to the identifier V, and if so builds
143 -- a function depending on discriminants of the formal parameter V which
144 -- is of type Vtype. Otherwise, if the parameter Make_Func is True, then
145 -- Expr will be encapsulated in a parameterless function; if Make_Func is
146 -- False, then a constant entity with the value Expr is built. The result
147 -- is a Dynamic_SO_Ref to the created entity. Note that Vtype can be
148 -- omitted if Expr does not contain any reference to V, the created entity.
149 -- The declaration created is inserted in the freeze actions of Ins_Type,
150 -- which also supplies the Sloc for created nodes. This function also takes
151 -- care of making sure that the expression is properly analyzed and
152 -- resolved (which may not be the case yet if we build the expression
153 -- in this unit).
155 function Get_Max_SU_Size (E : Entity_Id) return Node_Id;
156 -- E is an array type or subtype that has at least one index bound that
157 -- is the value of a record discriminant. For such an array, the function
158 -- computes an expression that yields the maximum possible size of the
159 -- array in storage units. The result is not defined for any other type,
160 -- or for arrays that do not depend on discriminants, and it is a fatal
161 -- error to call this unless Size_Depends_On_Discriminant (E) is True.
163 procedure Layout_Array_Type (E : Entity_Id);
164 -- Front-end layout of non-bit-packed array type or subtype
166 procedure Layout_Record_Type (E : Entity_Id);
167 -- Front-end layout of record type
169 procedure Rewrite_Integer (N : Node_Id; V : Uint);
170 -- Rewrite node N with an integer literal whose value is V. The Sloc for
171 -- the new node is taken from N, and the type of the literal is set to a
172 -- copy of the type of N on entry.
174 procedure Set_And_Check_Static_Size
175 (E : Entity_Id;
176 Esiz : SO_Ref;
177 RM_Siz : SO_Ref);
178 -- This procedure is called to check explicit given sizes (possibly stored
179 -- in the Esize and RM_Size fields of E) against computed Object_Size
180 -- (Esiz) and Value_Size (RM_Siz) values. Appropriate errors and warnings
181 -- are posted if specified sizes are inconsistent with specified sizes. On
182 -- return, Esize and RM_Size fields of E are set (either from previously
183 -- given values, or from the newly computed values, as appropriate).
185 procedure Set_Composite_Alignment (E : Entity_Id);
186 -- This procedure is called for record types and subtypes, and also for
187 -- atomic array types and subtypes. If no alignment is set, and the size
188 -- is 2 or 4 (or 8 if the word size is 8), then the alignment is set to
189 -- match the size.
191 ----------------------------
192 -- Adjust_Esize_Alignment --
193 ----------------------------
195 procedure Adjust_Esize_Alignment (E : Entity_Id) is
196 Abits : Int;
197 Esize_Set : Boolean;
199 begin
200 -- Nothing to do if size unknown
202 if Unknown_Esize (E) then
203 return;
204 end if;
206 -- Determine if size is constrained by an attribute definition clause
207 -- which must be obeyed. If so, we cannot increase the size in this
208 -- routine.
210 -- For a type, the issue is whether an object size clause has been set.
211 -- A normal size clause constrains only the value size (RM_Size)
213 if Is_Type (E) then
214 Esize_Set := Has_Object_Size_Clause (E);
216 -- For an object, the issue is whether a size clause is present
218 else
219 Esize_Set := Has_Size_Clause (E);
220 end if;
222 -- If size is known it must be a multiple of the storage unit size
224 if Esize (E) mod SSU /= 0 then
226 -- If not, and size specified, then give error
228 if Esize_Set then
229 Error_Msg_NE
230 ("size for& not a multiple of storage unit size",
231 Size_Clause (E), E);
232 return;
234 -- Otherwise bump up size to a storage unit boundary
236 else
237 Set_Esize (E, (Esize (E) + SSU - 1) / SSU * SSU);
238 end if;
239 end if;
241 -- Now we have the size set, it must be a multiple of the alignment
242 -- nothing more we can do here if the alignment is unknown here.
244 if Unknown_Alignment (E) then
245 return;
246 end if;
248 -- At this point both the Esize and Alignment are known, so we need
249 -- to make sure they are consistent.
251 Abits := UI_To_Int (Alignment (E)) * SSU;
253 if Esize (E) mod Abits = 0 then
254 return;
255 end if;
257 -- Here we have a situation where the Esize is not a multiple of the
258 -- alignment. We must either increase Esize or reduce the alignment to
259 -- correct this situation.
261 -- The case in which we can decrease the alignment is where the
262 -- alignment was not set by an alignment clause, and the type in
263 -- question is a discrete type, where it is definitely safe to reduce
264 -- the alignment. For example:
266 -- t : integer range 1 .. 2;
267 -- for t'size use 8;
269 -- In this situation, the initial alignment of t is 4, copied from
270 -- the Integer base type, but it is safe to reduce it to 1 at this
271 -- stage, since we will only be loading a single storage unit.
273 if Is_Discrete_Type (Etype (E))
274 and then not Has_Alignment_Clause (E)
275 then
276 loop
277 Abits := Abits / 2;
278 exit when Esize (E) mod Abits = 0;
279 end loop;
281 Init_Alignment (E, Abits / SSU);
282 return;
283 end if;
285 -- Now the only possible approach left is to increase the Esize but we
286 -- can't do that if the size was set by a specific clause.
288 if Esize_Set then
289 Error_Msg_NE
290 ("size for& is not a multiple of alignment",
291 Size_Clause (E), E);
293 -- Otherwise we can indeed increase the size to a multiple of alignment
295 else
296 Set_Esize (E, ((Esize (E) + (Abits - 1)) / Abits) * Abits);
297 end if;
298 end Adjust_Esize_Alignment;
300 ---------------
301 -- Assoc_Add --
302 ---------------
304 function Assoc_Add
305 (Loc : Source_Ptr;
306 Left_Opnd : Node_Id;
307 Right_Opnd : Node_Id) return Node_Id
309 L : Node_Id;
310 R : Uint;
312 begin
313 -- Case of right operand is a constant
315 if Compile_Time_Known_Value (Right_Opnd) then
316 L := Left_Opnd;
317 R := Expr_Value (Right_Opnd);
319 -- Case of left operand is a constant
321 elsif Compile_Time_Known_Value (Left_Opnd) then
322 L := Right_Opnd;
323 R := Expr_Value (Left_Opnd);
325 -- Neither operand is a constant, do the addition with no optimization
327 else
328 return Make_Op_Add (Loc, Left_Opnd, Right_Opnd);
329 end if;
331 -- Case of left operand is an addition
333 if Nkind (L) = N_Op_Add then
335 -- (C1 + E) + C2 = (C1 + C2) + E
337 if Compile_Time_Known_Value (Sinfo.Left_Opnd (L)) then
338 Rewrite_Integer
339 (Sinfo.Left_Opnd (L),
340 Expr_Value (Sinfo.Left_Opnd (L)) + R);
341 return L;
343 -- (E + C1) + C2 = E + (C1 + C2)
345 elsif Compile_Time_Known_Value (Sinfo.Right_Opnd (L)) then
346 Rewrite_Integer
347 (Sinfo.Right_Opnd (L),
348 Expr_Value (Sinfo.Right_Opnd (L)) + R);
349 return L;
350 end if;
352 -- Case of left operand is a subtraction
354 elsif Nkind (L) = N_Op_Subtract then
356 -- (C1 - E) + C2 = (C1 + C2) + E
358 if Compile_Time_Known_Value (Sinfo.Left_Opnd (L)) then
359 Rewrite_Integer
360 (Sinfo.Left_Opnd (L),
361 Expr_Value (Sinfo.Left_Opnd (L)) + R);
362 return L;
364 -- (E - C1) + C2 = E - (C1 - C2)
366 elsif Compile_Time_Known_Value (Sinfo.Right_Opnd (L)) then
367 Rewrite_Integer
368 (Sinfo.Right_Opnd (L),
369 Expr_Value (Sinfo.Right_Opnd (L)) - R);
370 return L;
371 end if;
372 end if;
374 -- Not optimizable, do the addition
376 return Make_Op_Add (Loc, Left_Opnd, Right_Opnd);
377 end Assoc_Add;
379 --------------------
380 -- Assoc_Multiply --
381 --------------------
383 function Assoc_Multiply
384 (Loc : Source_Ptr;
385 Left_Opnd : Node_Id;
386 Right_Opnd : Node_Id) return Node_Id
388 L : Node_Id;
389 R : Uint;
391 begin
392 -- Case of right operand is a constant
394 if Compile_Time_Known_Value (Right_Opnd) then
395 L := Left_Opnd;
396 R := Expr_Value (Right_Opnd);
398 -- Case of left operand is a constant
400 elsif Compile_Time_Known_Value (Left_Opnd) then
401 L := Right_Opnd;
402 R := Expr_Value (Left_Opnd);
404 -- Neither operand is a constant, do the multiply with no optimization
406 else
407 return Make_Op_Multiply (Loc, Left_Opnd, Right_Opnd);
408 end if;
410 -- Case of left operand is an multiplication
412 if Nkind (L) = N_Op_Multiply then
414 -- (C1 * E) * C2 = (C1 * C2) + E
416 if Compile_Time_Known_Value (Sinfo.Left_Opnd (L)) then
417 Rewrite_Integer
418 (Sinfo.Left_Opnd (L),
419 Expr_Value (Sinfo.Left_Opnd (L)) * R);
420 return L;
422 -- (E * C1) * C2 = E * (C1 * C2)
424 elsif Compile_Time_Known_Value (Sinfo.Right_Opnd (L)) then
425 Rewrite_Integer
426 (Sinfo.Right_Opnd (L),
427 Expr_Value (Sinfo.Right_Opnd (L)) * R);
428 return L;
429 end if;
430 end if;
432 -- Not optimizable, do the multiplication
434 return Make_Op_Multiply (Loc, Left_Opnd, Right_Opnd);
435 end Assoc_Multiply;
437 --------------------
438 -- Assoc_Subtract --
439 --------------------
441 function Assoc_Subtract
442 (Loc : Source_Ptr;
443 Left_Opnd : Node_Id;
444 Right_Opnd : Node_Id) return Node_Id
446 L : Node_Id;
447 R : Uint;
449 begin
450 -- Case of right operand is a constant
452 if Compile_Time_Known_Value (Right_Opnd) then
453 L := Left_Opnd;
454 R := Expr_Value (Right_Opnd);
456 -- Right operand is a constant, do the subtract with no optimization
458 else
459 return Make_Op_Subtract (Loc, Left_Opnd, Right_Opnd);
460 end if;
462 -- Case of left operand is an addition
464 if Nkind (L) = N_Op_Add then
466 -- (C1 + E) - C2 = (C1 - C2) + E
468 if Compile_Time_Known_Value (Sinfo.Left_Opnd (L)) then
469 Rewrite_Integer
470 (Sinfo.Left_Opnd (L),
471 Expr_Value (Sinfo.Left_Opnd (L)) - R);
472 return L;
474 -- (E + C1) - C2 = E + (C1 - C2)
476 elsif Compile_Time_Known_Value (Sinfo.Right_Opnd (L)) then
477 Rewrite_Integer
478 (Sinfo.Right_Opnd (L),
479 Expr_Value (Sinfo.Right_Opnd (L)) - R);
480 return L;
481 end if;
483 -- Case of left operand is a subtraction
485 elsif Nkind (L) = N_Op_Subtract then
487 -- (C1 - E) - C2 = (C1 - C2) + E
489 if Compile_Time_Known_Value (Sinfo.Left_Opnd (L)) then
490 Rewrite_Integer
491 (Sinfo.Left_Opnd (L),
492 Expr_Value (Sinfo.Left_Opnd (L)) + R);
493 return L;
495 -- (E - C1) - C2 = E - (C1 + C2)
497 elsif Compile_Time_Known_Value (Sinfo.Right_Opnd (L)) then
498 Rewrite_Integer
499 (Sinfo.Right_Opnd (L),
500 Expr_Value (Sinfo.Right_Opnd (L)) + R);
501 return L;
502 end if;
503 end if;
505 -- Not optimizable, do the subtraction
507 return Make_Op_Subtract (Loc, Left_Opnd, Right_Opnd);
508 end Assoc_Subtract;
510 ----------------
511 -- Bits_To_SU --
512 ----------------
514 function Bits_To_SU (N : Node_Id) return Node_Id is
515 begin
516 if Nkind (N) = N_Integer_Literal then
517 Set_Intval (N, (Intval (N) + (SSU - 1)) / SSU);
518 end if;
520 return N;
521 end Bits_To_SU;
523 --------------------
524 -- Compute_Length --
525 --------------------
527 function Compute_Length (Lo : Node_Id; Hi : Node_Id) return Node_Id is
528 Loc : constant Source_Ptr := Sloc (Lo);
529 Typ : constant Entity_Id := Etype (Lo);
530 Lo_Op : Node_Id;
531 Hi_Op : Node_Id;
532 Lo_Dim : Uint;
533 Hi_Dim : Uint;
535 begin
536 -- If the bounds are First and Last attributes for the same dimension
537 -- and both have prefixes that denotes the same entity, then we create
538 -- and return a Length attribute. This may allow the back end to
539 -- generate better code in cases where it already has the length.
541 if Nkind (Lo) = N_Attribute_Reference
542 and then Attribute_Name (Lo) = Name_First
543 and then Nkind (Hi) = N_Attribute_Reference
544 and then Attribute_Name (Hi) = Name_Last
545 and then Is_Entity_Name (Prefix (Lo))
546 and then Is_Entity_Name (Prefix (Hi))
547 and then Entity (Prefix (Lo)) = Entity (Prefix (Hi))
548 then
549 Lo_Dim := Uint_1;
550 Hi_Dim := Uint_1;
552 if Present (First (Expressions (Lo))) then
553 Lo_Dim := Expr_Value (First (Expressions (Lo)));
554 end if;
556 if Present (First (Expressions (Hi))) then
557 Hi_Dim := Expr_Value (First (Expressions (Hi)));
558 end if;
560 if Lo_Dim = Hi_Dim then
561 return
562 Make_Attribute_Reference (Loc,
563 Prefix => New_Occurrence_Of
564 (Entity (Prefix (Lo)), Loc),
565 Attribute_Name => Name_Length,
566 Expressions => New_List
567 (Make_Integer_Literal (Loc, Lo_Dim)));
568 end if;
569 end if;
571 Lo_Op := New_Copy_Tree (Lo);
572 Hi_Op := New_Copy_Tree (Hi);
574 -- If type is enumeration type, then use Pos attribute to convert
575 -- to integer type for which subtraction is a permitted operation.
577 if Is_Enumeration_Type (Typ) then
578 Lo_Op :=
579 Make_Attribute_Reference (Loc,
580 Prefix => New_Occurrence_Of (Typ, Loc),
581 Attribute_Name => Name_Pos,
582 Expressions => New_List (Lo_Op));
584 Hi_Op :=
585 Make_Attribute_Reference (Loc,
586 Prefix => New_Occurrence_Of (Typ, Loc),
587 Attribute_Name => Name_Pos,
588 Expressions => New_List (Hi_Op));
589 end if;
591 return
592 Assoc_Add (Loc,
593 Left_Opnd =>
594 Assoc_Subtract (Loc,
595 Left_Opnd => Hi_Op,
596 Right_Opnd => Lo_Op),
597 Right_Opnd => Make_Integer_Literal (Loc, 1));
598 end Compute_Length;
600 ----------------------
601 -- Expr_From_SO_Ref --
602 ----------------------
604 function Expr_From_SO_Ref
605 (Loc : Source_Ptr;
606 D : SO_Ref;
607 Comp : Entity_Id := Empty) return Node_Id
609 Ent : Entity_Id;
611 begin
612 if Is_Dynamic_SO_Ref (D) then
613 Ent := Get_Dynamic_SO_Entity (D);
615 if Is_Discrim_SO_Function (Ent) then
617 -- If a component is passed in whose type matches the type of
618 -- the function formal, then select that component from the "V"
619 -- parameter rather than passing "V" directly.
621 if Present (Comp)
622 and then Base_Type (Etype (Comp))
623 = Base_Type (Etype (First_Formal (Ent)))
624 then
625 return
626 Make_Function_Call (Loc,
627 Name => New_Occurrence_Of (Ent, Loc),
628 Parameter_Associations => New_List (
629 Make_Selected_Component (Loc,
630 Prefix => Make_Identifier (Loc, Vname),
631 Selector_Name => New_Occurrence_Of (Comp, Loc))));
633 else
634 return
635 Make_Function_Call (Loc,
636 Name => New_Occurrence_Of (Ent, Loc),
637 Parameter_Associations => New_List (
638 Make_Identifier (Loc, Vname)));
639 end if;
641 else
642 return New_Occurrence_Of (Ent, Loc);
643 end if;
645 else
646 return Make_Integer_Literal (Loc, D);
647 end if;
648 end Expr_From_SO_Ref;
650 ---------------------
651 -- Get_Max_SU_Size --
652 ---------------------
654 function Get_Max_SU_Size (E : Entity_Id) return Node_Id is
655 Loc : constant Source_Ptr := Sloc (E);
656 Indx : Node_Id;
657 Ityp : Entity_Id;
658 Lo : Node_Id;
659 Hi : Node_Id;
660 S : Uint;
661 Len : Node_Id;
663 type Val_Status_Type is (Const, Dynamic);
665 type Val_Type (Status : Val_Status_Type := Const) is
666 record
667 case Status is
668 when Const => Val : Uint;
669 when Dynamic => Nod : Node_Id;
670 end case;
671 end record;
672 -- Shows the status of the value so far. Const means that the value is
673 -- constant, and Val is the current constant value. Dynamic means that
674 -- the value is dynamic, and in this case Nod is the Node_Id of the
675 -- expression to compute the value.
677 Size : Val_Type;
678 -- Calculated value so far if Size.Status = Const,
679 -- or expression value so far if Size.Status = Dynamic.
681 SU_Convert_Required : Boolean := False;
682 -- This is set to True if the final result must be converted from bits
683 -- to storage units (rounding up to a storage unit boundary).
685 -----------------------
686 -- Local Subprograms --
687 -----------------------
689 procedure Max_Discrim (N : in out Node_Id);
690 -- If the node N represents a discriminant, replace it by the maximum
691 -- value of the discriminant.
693 procedure Min_Discrim (N : in out Node_Id);
694 -- If the node N represents a discriminant, replace it by the minimum
695 -- value of the discriminant.
697 -----------------
698 -- Max_Discrim --
699 -----------------
701 procedure Max_Discrim (N : in out Node_Id) is
702 begin
703 if Nkind (N) = N_Identifier
704 and then Ekind (Entity (N)) = E_Discriminant
705 then
706 N := Type_High_Bound (Etype (N));
707 end if;
708 end Max_Discrim;
710 -----------------
711 -- Min_Discrim --
712 -----------------
714 procedure Min_Discrim (N : in out Node_Id) is
715 begin
716 if Nkind (N) = N_Identifier
717 and then Ekind (Entity (N)) = E_Discriminant
718 then
719 N := Type_Low_Bound (Etype (N));
720 end if;
721 end Min_Discrim;
723 -- Start of processing for Get_Max_SU_Size
725 begin
726 pragma Assert (Size_Depends_On_Discriminant (E));
728 -- Initialize status from component size
730 if Known_Static_Component_Size (E) then
731 Size := (Const, Component_Size (E));
733 else
734 Size := (Dynamic, Expr_From_SO_Ref (Loc, Component_Size (E)));
735 end if;
737 -- Loop through indexes
739 Indx := First_Index (E);
740 while Present (Indx) loop
741 Ityp := Etype (Indx);
742 Lo := Type_Low_Bound (Ityp);
743 Hi := Type_High_Bound (Ityp);
745 Min_Discrim (Lo);
746 Max_Discrim (Hi);
748 -- Value of the current subscript range is statically known
750 if Compile_Time_Known_Value (Lo)
751 and then Compile_Time_Known_Value (Hi)
752 then
753 S := Expr_Value (Hi) - Expr_Value (Lo) + 1;
755 -- If known flat bound, entire size of array is zero
757 if S <= 0 then
758 return Make_Integer_Literal (Loc, 0);
759 end if;
761 -- Current value is constant, evolve value
763 if Size.Status = Const then
764 Size.Val := Size.Val * S;
766 -- Current value is dynamic
768 else
769 -- An interesting little optimization, if we have a pending
770 -- conversion from bits to storage units, and the current
771 -- length is a multiple of the storage unit size, then we
772 -- can take the factor out here statically, avoiding some
773 -- extra dynamic computations at the end.
775 if SU_Convert_Required and then S mod SSU = 0 then
776 S := S / SSU;
777 SU_Convert_Required := False;
778 end if;
780 Size.Nod :=
781 Assoc_Multiply (Loc,
782 Left_Opnd => Size.Nod,
783 Right_Opnd =>
784 Make_Integer_Literal (Loc, Intval => S));
785 end if;
787 -- Value of the current subscript range is dynamic
789 else
790 -- If the current size value is constant, then here is where we
791 -- make a transition to dynamic values, which are always stored
792 -- in storage units, However, we do not want to convert to SU's
793 -- too soon, consider the case of a packed array of single bits,
794 -- we want to do the SU conversion after computing the size in
795 -- this case.
797 if Size.Status = Const then
799 -- If the current value is a multiple of the storage unit,
800 -- then most certainly we can do the conversion now, simply
801 -- by dividing the current value by the storage unit value.
802 -- If this works, we set SU_Convert_Required to False.
804 if Size.Val mod SSU = 0 then
806 Size :=
807 (Dynamic, Make_Integer_Literal (Loc, Size.Val / SSU));
808 SU_Convert_Required := False;
810 -- Otherwise, we go ahead and convert the value in bits, and
811 -- set SU_Convert_Required to True to ensure that the final
812 -- value is indeed properly converted.
814 else
815 Size := (Dynamic, Make_Integer_Literal (Loc, Size.Val));
816 SU_Convert_Required := True;
817 end if;
818 end if;
820 -- Length is hi-lo+1
822 Len := Compute_Length (Lo, Hi);
824 -- Check possible range of Len
826 declare
827 OK : Boolean;
828 LLo : Uint;
829 LHi : Uint;
830 pragma Warnings (Off, LHi);
832 begin
833 Set_Parent (Len, E);
834 Determine_Range (Len, OK, LLo, LHi);
836 Len := Convert_To (Standard_Unsigned, Len);
838 -- If we cannot verify that range cannot be super-flat, we need
839 -- a max with zero, since length must be non-negative.
841 if not OK or else LLo < 0 then
842 Len :=
843 Make_Attribute_Reference (Loc,
844 Prefix =>
845 New_Occurrence_Of (Standard_Unsigned, Loc),
846 Attribute_Name => Name_Max,
847 Expressions => New_List (
848 Make_Integer_Literal (Loc, 0),
849 Len));
850 end if;
851 end;
852 end if;
854 Next_Index (Indx);
855 end loop;
857 -- Here after processing all bounds to set sizes. If the value is a
858 -- constant, then it is bits, so we convert to storage units.
860 if Size.Status = Const then
861 return Bits_To_SU (Make_Integer_Literal (Loc, Size.Val));
863 -- Case where the value is dynamic
865 else
866 -- Do convert from bits to SU's if needed
868 if SU_Convert_Required then
870 -- The expression required is (Size.Nod + SU - 1) / SU
872 Size.Nod :=
873 Make_Op_Divide (Loc,
874 Left_Opnd =>
875 Make_Op_Add (Loc,
876 Left_Opnd => Size.Nod,
877 Right_Opnd => Make_Integer_Literal (Loc, SSU - 1)),
878 Right_Opnd => Make_Integer_Literal (Loc, SSU));
879 end if;
881 return Size.Nod;
882 end if;
883 end Get_Max_SU_Size;
885 -----------------------
886 -- Layout_Array_Type --
887 -----------------------
889 procedure Layout_Array_Type (E : Entity_Id) is
890 Loc : constant Source_Ptr := Sloc (E);
891 Ctyp : constant Entity_Id := Component_Type (E);
892 Indx : Node_Id;
893 Ityp : Entity_Id;
894 Lo : Node_Id;
895 Hi : Node_Id;
896 S : Uint;
897 Len : Node_Id;
899 Insert_Typ : Entity_Id;
900 -- This is the type with which any generated constants or functions
901 -- will be associated (i.e. inserted into the freeze actions). This
902 -- is normally the type being laid out. The exception occurs when
903 -- we are laying out Itype's which are local to a record type, and
904 -- whose scope is this record type. Such types do not have freeze
905 -- nodes (because we have no place to put them).
907 ------------------------------------
908 -- How An Array Type is Laid Out --
909 ------------------------------------
911 -- Here is what goes on. We need to multiply the component size of the
912 -- array (which has already been set) by the length of each of the
913 -- indexes. If all these values are known at compile time, then the
914 -- resulting size of the array is the appropriate constant value.
916 -- If the component size or at least one bound is dynamic (but no
917 -- discriminants are present), then the size will be computed as an
918 -- expression that calculates the proper size.
920 -- If there is at least one discriminant bound, then the size is also
921 -- computed as an expression, but this expression contains discriminant
922 -- values which are obtained by selecting from a function parameter, and
923 -- the size is given by a function that is passed the variant record in
924 -- question, and whose body is the expression.
926 type Val_Status_Type is (Const, Dynamic, Discrim);
928 type Val_Type (Status : Val_Status_Type := Const) is
929 record
930 case Status is
931 when Const =>
932 Val : Uint;
933 -- Calculated value so far if Val_Status = Const
935 when Dynamic | Discrim =>
936 Nod : Node_Id;
937 -- Expression value so far if Val_Status /= Const
939 end case;
940 end record;
941 -- Records the value or expression computed so far. Const means that
942 -- the value is constant, and Val is the current constant value.
943 -- Dynamic means that the value is dynamic, and in this case Nod is
944 -- the Node_Id of the expression to compute the value, and Discrim
945 -- means that at least one bound is a discriminant, in which case Nod
946 -- is the expression so far (which will be the body of the function).
948 Size : Val_Type;
949 -- Value of size computed so far. See comments above
951 Vtyp : Entity_Id := Empty;
952 -- Variant record type for the formal parameter of the discriminant
953 -- function V if Status = Discrim.
955 SU_Convert_Required : Boolean := False;
956 -- This is set to True if the final result must be converted from
957 -- bits to storage units (rounding up to a storage unit boundary).
959 Storage_Divisor : Uint := UI_From_Int (SSU);
960 -- This is the amount that a nonstatic computed size will be divided
961 -- by to convert it from bits to storage units. This is normally
962 -- equal to SSU, but can be reduced in the case of packed components
963 -- that fit evenly into a storage unit.
965 Make_Size_Function : Boolean := False;
966 -- Indicates whether to request that SO_Ref_From_Expr should
967 -- encapsulate the array size expression in a function.
969 procedure Discrimify (N : in out Node_Id);
970 -- If N represents a discriminant, then the Size.Status is set to
971 -- Discrim, and Vtyp is set. The parameter N is replaced with the
972 -- proper expression to extract the discriminant value from V.
974 ----------------
975 -- Discrimify --
976 ----------------
978 procedure Discrimify (N : in out Node_Id) is
979 Decl : Node_Id;
980 Typ : Entity_Id;
982 begin
983 if Nkind (N) = N_Identifier
984 and then Ekind (Entity (N)) = E_Discriminant
985 then
986 Set_Size_Depends_On_Discriminant (E);
988 if Size.Status /= Discrim then
989 Decl := Parent (Parent (Entity (N)));
990 Size := (Discrim, Size.Nod);
991 Vtyp := Defining_Identifier (Decl);
992 end if;
994 Typ := Etype (N);
996 N :=
997 Make_Selected_Component (Loc,
998 Prefix => Make_Identifier (Loc, Vname),
999 Selector_Name => New_Occurrence_Of (Entity (N), Loc));
1001 -- Set the Etype attributes of the selected name and its prefix.
1002 -- Analyze_And_Resolve can't be called here because the Vname
1003 -- entity denoted by the prefix will not yet exist (it's created
1004 -- by SO_Ref_From_Expr, called at the end of Layout_Array_Type).
1006 Set_Etype (Prefix (N), Vtyp);
1007 Set_Etype (N, Typ);
1008 end if;
1009 end Discrimify;
1011 -- Start of processing for Layout_Array_Type
1013 begin
1014 -- Default alignment is component alignment
1016 if Unknown_Alignment (E) then
1017 Set_Alignment (E, Alignment (Ctyp));
1018 end if;
1020 -- Calculate proper type for insertions
1022 if Is_Record_Type (Underlying_Type (Scope (E))) then
1023 Insert_Typ := Underlying_Type (Scope (E));
1024 else
1025 Insert_Typ := E;
1026 end if;
1028 -- If the component type is a generic formal type then there's no point
1029 -- in determining a size for the array type.
1031 if Is_Generic_Type (Ctyp) then
1032 return;
1033 end if;
1035 -- Deal with component size if base type
1037 if Ekind (E) = E_Array_Type then
1039 -- Cannot do anything if Esize of component type unknown
1041 if Unknown_Esize (Ctyp) then
1042 return;
1043 end if;
1045 -- Set component size if not set already
1047 if Unknown_Component_Size (E) then
1048 Set_Component_Size (E, Esize (Ctyp));
1049 end if;
1050 end if;
1052 -- (RM 13.3 (48)) says that the size of an unconstrained array
1053 -- is implementation defined. We choose to leave it as Unknown
1054 -- here, and the actual behavior is determined by the back end.
1056 if not Is_Constrained (E) then
1057 return;
1058 end if;
1060 -- Initialize status from component size
1062 if Known_Static_Component_Size (E) then
1063 Size := (Const, Component_Size (E));
1065 else
1066 Size := (Dynamic, Expr_From_SO_Ref (Loc, Component_Size (E)));
1067 end if;
1069 -- Loop to process array indexes
1071 Indx := First_Index (E);
1072 while Present (Indx) loop
1073 Ityp := Etype (Indx);
1075 -- If an index of the array is a generic formal type then there is
1076 -- no point in determining a size for the array type.
1078 if Is_Generic_Type (Ityp) then
1079 return;
1080 end if;
1082 Lo := Type_Low_Bound (Ityp);
1083 Hi := Type_High_Bound (Ityp);
1085 -- Value of the current subscript range is statically known
1087 if Compile_Time_Known_Value (Lo)
1088 and then Compile_Time_Known_Value (Hi)
1089 then
1090 S := Expr_Value (Hi) - Expr_Value (Lo) + 1;
1092 -- If known flat bound, entire size of array is zero
1094 if S <= 0 then
1095 Set_Esize (E, Uint_0);
1096 Set_RM_Size (E, Uint_0);
1097 return;
1098 end if;
1100 -- If constant, evolve value
1102 if Size.Status = Const then
1103 Size.Val := Size.Val * S;
1105 -- Current value is dynamic
1107 else
1108 -- An interesting little optimization, if we have a pending
1109 -- conversion from bits to storage units, and the current
1110 -- length is a multiple of the storage unit size, then we
1111 -- can take the factor out here statically, avoiding some
1112 -- extra dynamic computations at the end.
1114 if SU_Convert_Required and then S mod SSU = 0 then
1115 S := S / SSU;
1116 SU_Convert_Required := False;
1117 end if;
1119 -- Now go ahead and evolve the expression
1121 Size.Nod :=
1122 Assoc_Multiply (Loc,
1123 Left_Opnd => Size.Nod,
1124 Right_Opnd =>
1125 Make_Integer_Literal (Loc, Intval => S));
1126 end if;
1128 -- Value of the current subscript range is dynamic
1130 else
1131 -- If the current size value is constant, then here is where we
1132 -- make a transition to dynamic values, which are always stored
1133 -- in storage units, However, we do not want to convert to SU's
1134 -- too soon, consider the case of a packed array of single bits,
1135 -- we want to do the SU conversion after computing the size in
1136 -- this case.
1138 if Size.Status = Const then
1140 -- If the current value is a multiple of the storage unit,
1141 -- then most certainly we can do the conversion now, simply
1142 -- by dividing the current value by the storage unit value.
1143 -- If this works, we set SU_Convert_Required to False.
1145 if Size.Val mod SSU = 0 then
1146 Size :=
1147 (Dynamic, Make_Integer_Literal (Loc, Size.Val / SSU));
1148 SU_Convert_Required := False;
1150 -- If the current value is a factor of the storage unit, then
1151 -- we can use a value of one for the size and reduce the
1152 -- strength of the later division.
1154 elsif SSU mod Size.Val = 0 then
1155 Storage_Divisor := SSU / Size.Val;
1156 Size := (Dynamic, Make_Integer_Literal (Loc, Uint_1));
1157 SU_Convert_Required := True;
1159 -- Otherwise, we go ahead and convert the value in bits, and
1160 -- set SU_Convert_Required to True to ensure that the final
1161 -- value is indeed properly converted.
1163 else
1164 Size := (Dynamic, Make_Integer_Literal (Loc, Size.Val));
1165 SU_Convert_Required := True;
1166 end if;
1167 end if;
1169 Discrimify (Lo);
1170 Discrimify (Hi);
1172 -- Length is hi-lo+1
1174 Len := Compute_Length (Lo, Hi);
1176 -- If Len isn't a Length attribute, then its range needs to be
1177 -- checked a possible Max with zero needs to be computed.
1179 if Nkind (Len) /= N_Attribute_Reference
1180 or else Attribute_Name (Len) /= Name_Length
1181 then
1182 declare
1183 OK : Boolean;
1184 LLo : Uint;
1185 LHi : Uint;
1187 begin
1188 -- Check possible range of Len
1190 Set_Parent (Len, E);
1191 Determine_Range (Len, OK, LLo, LHi);
1193 Len := Convert_To (Standard_Unsigned, Len);
1195 -- If range definitely flat or superflat,
1196 -- result size is zero
1198 if OK and then LHi <= 0 then
1199 Set_Esize (E, Uint_0);
1200 Set_RM_Size (E, Uint_0);
1201 return;
1202 end if;
1204 -- If we cannot verify that range cannot be super-flat, we
1205 -- need a max with zero, since length cannot be negative.
1207 if not OK or else LLo < 0 then
1208 Len :=
1209 Make_Attribute_Reference (Loc,
1210 Prefix =>
1211 New_Occurrence_Of (Standard_Unsigned, Loc),
1212 Attribute_Name => Name_Max,
1213 Expressions => New_List (
1214 Make_Integer_Literal (Loc, 0),
1215 Len));
1216 end if;
1217 end;
1218 end if;
1220 -- At this stage, Len has the expression for the length
1222 Size.Nod :=
1223 Assoc_Multiply (Loc,
1224 Left_Opnd => Size.Nod,
1225 Right_Opnd => Len);
1226 end if;
1228 Next_Index (Indx);
1229 end loop;
1231 -- Here after processing all bounds to set sizes. If the value is a
1232 -- constant, then it is bits, and the only thing we need to do is to
1233 -- check against explicit given size and do alignment adjust.
1235 if Size.Status = Const then
1236 Set_And_Check_Static_Size (E, Size.Val, Size.Val);
1237 Adjust_Esize_Alignment (E);
1239 -- Case where the value is dynamic
1241 else
1242 -- Do convert from bits to SU's if needed
1244 if SU_Convert_Required then
1246 -- The expression required is:
1247 -- (Size.Nod + Storage_Divisor - 1) / Storage_Divisor
1249 Size.Nod :=
1250 Make_Op_Divide (Loc,
1251 Left_Opnd =>
1252 Make_Op_Add (Loc,
1253 Left_Opnd => Size.Nod,
1254 Right_Opnd => Make_Integer_Literal
1255 (Loc, Storage_Divisor - 1)),
1256 Right_Opnd => Make_Integer_Literal (Loc, Storage_Divisor));
1257 end if;
1259 -- If the array entity is not declared at the library level and its
1260 -- not nested within a subprogram that is marked for inlining, then
1261 -- we request that the size expression be encapsulated in a function.
1262 -- Since this expression is not needed in most cases, we prefer not
1263 -- to incur the overhead of the computation on calls to the enclosing
1264 -- subprogram except for subprograms that require the size.
1266 if not Is_Library_Level_Entity (E) then
1267 Make_Size_Function := True;
1269 declare
1270 Parent_Subp : Entity_Id := Enclosing_Subprogram (E);
1272 begin
1273 while Present (Parent_Subp) loop
1274 if Is_Inlined (Parent_Subp) then
1275 Make_Size_Function := False;
1276 exit;
1277 end if;
1279 Parent_Subp := Enclosing_Subprogram (Parent_Subp);
1280 end loop;
1281 end;
1282 end if;
1284 -- Now set the dynamic size (the Value_Size is always the same as the
1285 -- Object_Size for arrays whose length is dynamic).
1287 -- ??? If Size.Status = Dynamic, Vtyp will not have been set.
1288 -- The added initialization sets it to Empty now, but is this
1289 -- correct?
1291 Set_Esize
1293 SO_Ref_From_Expr
1294 (Size.Nod, Insert_Typ, Vtyp, Make_Func => Make_Size_Function));
1295 Set_RM_Size (E, Esize (E));
1296 end if;
1297 end Layout_Array_Type;
1299 ------------------------------------------
1300 -- Compute_Size_Depends_On_Discriminant --
1301 ------------------------------------------
1303 procedure Compute_Size_Depends_On_Discriminant (E : Entity_Id) is
1304 Indx : Node_Id;
1305 Ityp : Entity_Id;
1306 Lo : Node_Id;
1307 Hi : Node_Id;
1308 Res : Boolean := False;
1310 begin
1311 -- Loop to process array indexes
1313 Indx := First_Index (E);
1314 while Present (Indx) loop
1315 Ityp := Etype (Indx);
1317 -- If an index of the array is a generic formal type then there is
1318 -- no point in determining a size for the array type.
1320 if Is_Generic_Type (Ityp) then
1321 return;
1322 end if;
1324 Lo := Type_Low_Bound (Ityp);
1325 Hi := Type_High_Bound (Ityp);
1327 if (Nkind (Lo) = N_Identifier
1328 and then Ekind (Entity (Lo)) = E_Discriminant)
1329 or else
1330 (Nkind (Hi) = N_Identifier
1331 and then Ekind (Entity (Hi)) = E_Discriminant)
1332 then
1333 Res := True;
1334 end if;
1336 Next_Index (Indx);
1337 end loop;
1339 if Res then
1340 Set_Size_Depends_On_Discriminant (E);
1341 end if;
1342 end Compute_Size_Depends_On_Discriminant;
1344 -------------------
1345 -- Layout_Object --
1346 -------------------
1348 procedure Layout_Object (E : Entity_Id) is
1349 T : constant Entity_Id := Etype (E);
1351 begin
1352 -- Nothing to do if backend does layout
1354 if not Frontend_Layout_On_Target then
1355 return;
1356 end if;
1358 -- Set size if not set for object and known for type. Use the RM_Size if
1359 -- that is known for the type and Esize is not.
1361 if Unknown_Esize (E) then
1362 if Known_Esize (T) then
1363 Set_Esize (E, Esize (T));
1365 elsif Known_RM_Size (T) then
1366 Set_Esize (E, RM_Size (T));
1367 end if;
1368 end if;
1370 -- Set alignment from type if unknown and type alignment known
1372 if Unknown_Alignment (E) and then Known_Alignment (T) then
1373 Set_Alignment (E, Alignment (T));
1374 end if;
1376 -- Make sure size and alignment are consistent
1378 Adjust_Esize_Alignment (E);
1380 -- Final adjustment, if we don't know the alignment, and the Esize was
1381 -- not set by an explicit Object_Size attribute clause, then we reset
1382 -- the Esize to unknown, since we really don't know it.
1384 if Unknown_Alignment (E)
1385 and then not Has_Size_Clause (E)
1386 then
1387 Set_Esize (E, Uint_0);
1388 end if;
1389 end Layout_Object;
1391 ------------------------
1392 -- Layout_Record_Type --
1393 ------------------------
1395 procedure Layout_Record_Type (E : Entity_Id) is
1396 Loc : constant Source_Ptr := Sloc (E);
1397 Decl : Node_Id;
1399 Comp : Entity_Id;
1400 -- Current component being laid out
1402 Prev_Comp : Entity_Id;
1403 -- Previous laid out component
1405 procedure Get_Next_Component_Location
1406 (Prev_Comp : Entity_Id;
1407 Align : Uint;
1408 New_Npos : out SO_Ref;
1409 New_Fbit : out SO_Ref;
1410 New_NPMax : out SO_Ref;
1411 Force_SU : Boolean);
1412 -- Given the previous component in Prev_Comp, which is already laid
1413 -- out, and the alignment of the following component, lays out the
1414 -- following component, and returns its starting position in New_Npos
1415 -- (Normalized_Position value), New_Fbit (Normalized_First_Bit value),
1416 -- and New_NPMax (Normalized_Position_Max value). If Prev_Comp is empty
1417 -- (no previous component is present), then New_Npos, New_Fbit and
1418 -- New_NPMax are all set to zero on return. This procedure is also
1419 -- used to compute the size of a record or variant by giving it the
1420 -- last component, and the record alignment. Force_SU is used to force
1421 -- the new component location to be aligned on a storage unit boundary,
1422 -- even in a packed record, False means that the new position does not
1423 -- need to be bumped to a storage unit boundary, True means a storage
1424 -- unit boundary is always required.
1426 procedure Layout_Component (Comp : Entity_Id; Prev_Comp : Entity_Id);
1427 -- Lays out component Comp, given Prev_Comp, the previously laid-out
1428 -- component (Prev_Comp = Empty if no components laid out yet). The
1429 -- alignment of the record itself is also updated if needed. Both
1430 -- Comp and Prev_Comp can be either components or discriminants.
1432 procedure Layout_Components
1433 (From : Entity_Id;
1434 To : Entity_Id;
1435 Esiz : out SO_Ref;
1436 RM_Siz : out SO_Ref);
1437 -- This procedure lays out the components of the given component list
1438 -- which contains the components starting with From and ending with To.
1439 -- The Next_Entity chain is used to traverse the components. On entry,
1440 -- Prev_Comp is set to the component preceding the list, so that the
1441 -- list is laid out after this component. Prev_Comp is set to Empty if
1442 -- the component list is to be laid out starting at the start of the
1443 -- record. On return, the components are all laid out, and Prev_Comp is
1444 -- set to the last laid out component. On return, Esiz is set to the
1445 -- resulting Object_Size value, which is the length of the record up
1446 -- to and including the last laid out entity. For Esiz, the value is
1447 -- adjusted to match the alignment of the record. RM_Siz is similarly
1448 -- set to the resulting Value_Size value, which is the same length, but
1449 -- not adjusted to meet the alignment. Note that in the case of variant
1450 -- records, Esiz represents the maximum size.
1452 procedure Layout_Non_Variant_Record;
1453 -- Procedure called to lay out a non-variant record type or subtype
1455 procedure Layout_Variant_Record;
1456 -- Procedure called to lay out a variant record type. Decl is set to the
1457 -- full type declaration for the variant record.
1459 ---------------------------------
1460 -- Get_Next_Component_Location --
1461 ---------------------------------
1463 procedure Get_Next_Component_Location
1464 (Prev_Comp : Entity_Id;
1465 Align : Uint;
1466 New_Npos : out SO_Ref;
1467 New_Fbit : out SO_Ref;
1468 New_NPMax : out SO_Ref;
1469 Force_SU : Boolean)
1471 begin
1472 -- No previous component, return zero position
1474 if No (Prev_Comp) then
1475 New_Npos := Uint_0;
1476 New_Fbit := Uint_0;
1477 New_NPMax := Uint_0;
1478 return;
1479 end if;
1481 -- Here we have a previous component
1483 declare
1484 Loc : constant Source_Ptr := Sloc (Prev_Comp);
1486 Old_Npos : constant SO_Ref := Normalized_Position (Prev_Comp);
1487 Old_Fbit : constant SO_Ref := Normalized_First_Bit (Prev_Comp);
1488 Old_NPMax : constant SO_Ref := Normalized_Position_Max (Prev_Comp);
1489 Old_Esiz : constant SO_Ref := Esize (Prev_Comp);
1491 Old_Maxsz : Node_Id;
1492 -- Expression representing maximum size of previous component
1494 begin
1495 -- Case where previous field had a dynamic size
1497 if Is_Dynamic_SO_Ref (Esize (Prev_Comp)) then
1499 -- If the previous field had a dynamic length, then it is
1500 -- required to occupy an integral number of storage units,
1501 -- and start on a storage unit boundary. This means that
1502 -- the Normalized_First_Bit value is zero in the previous
1503 -- component, and the new value is also set to zero.
1505 New_Fbit := Uint_0;
1507 -- In this case, the new position is given by an expression
1508 -- that is the sum of old normalized position and old size.
1510 New_Npos :=
1511 SO_Ref_From_Expr
1512 (Assoc_Add (Loc,
1513 Left_Opnd =>
1514 Expr_From_SO_Ref (Loc, Old_Npos),
1515 Right_Opnd =>
1516 Expr_From_SO_Ref (Loc, Old_Esiz, Prev_Comp)),
1517 Ins_Type => E,
1518 Vtype => E);
1520 -- Get maximum size of previous component
1522 if Size_Depends_On_Discriminant (Etype (Prev_Comp)) then
1523 Old_Maxsz := Get_Max_SU_Size (Etype (Prev_Comp));
1524 else
1525 Old_Maxsz := Expr_From_SO_Ref (Loc, Old_Esiz, Prev_Comp);
1526 end if;
1528 -- Now we can compute the new max position. If the max size
1529 -- is static and the old position is static, then we can
1530 -- compute the new position statically.
1532 if Nkind (Old_Maxsz) = N_Integer_Literal
1533 and then Known_Static_Normalized_Position_Max (Prev_Comp)
1534 then
1535 New_NPMax := Old_NPMax + Intval (Old_Maxsz);
1537 -- Otherwise new max position is dynamic
1539 else
1540 New_NPMax :=
1541 SO_Ref_From_Expr
1542 (Assoc_Add (Loc,
1543 Left_Opnd => Expr_From_SO_Ref (Loc, Old_NPMax),
1544 Right_Opnd => Old_Maxsz),
1545 Ins_Type => E,
1546 Vtype => E);
1547 end if;
1549 -- Previous field has known static Esize
1551 else
1552 New_Fbit := Old_Fbit + Old_Esiz;
1554 -- Bump New_Fbit to storage unit boundary if required
1556 if New_Fbit /= 0 and then Force_SU then
1557 New_Fbit := (New_Fbit + SSU - 1) / SSU * SSU;
1558 end if;
1560 -- If old normalized position is static, we can go ahead and
1561 -- compute the new normalized position directly.
1563 if Known_Static_Normalized_Position (Prev_Comp) then
1564 New_Npos := Old_Npos;
1566 if New_Fbit >= SSU then
1567 New_Npos := New_Npos + New_Fbit / SSU;
1568 New_Fbit := New_Fbit mod SSU;
1569 end if;
1571 -- Bump alignment if stricter than prev
1573 if Align > Alignment (Etype (Prev_Comp)) then
1574 New_Npos := (New_Npos + Align - 1) / Align * Align;
1575 end if;
1577 -- The max position is always equal to the position if
1578 -- the latter is static, since arrays depending on the
1579 -- values of discriminants never have static sizes.
1581 New_NPMax := New_Npos;
1582 return;
1584 -- Case of old normalized position is dynamic
1586 else
1587 -- If new bit position is within the current storage unit,
1588 -- we can just copy the old position as the result position
1589 -- (we have already set the new first bit value).
1591 if New_Fbit < SSU then
1592 New_Npos := Old_Npos;
1593 New_NPMax := Old_NPMax;
1595 -- If new bit position is past the current storage unit, we
1596 -- need to generate a new dynamic value for the position
1597 -- ??? need to deal with alignment
1599 else
1600 New_Npos :=
1601 SO_Ref_From_Expr
1602 (Assoc_Add (Loc,
1603 Left_Opnd => Expr_From_SO_Ref (Loc, Old_Npos),
1604 Right_Opnd =>
1605 Make_Integer_Literal (Loc,
1606 Intval => New_Fbit / SSU)),
1607 Ins_Type => E,
1608 Vtype => E);
1610 New_NPMax :=
1611 SO_Ref_From_Expr
1612 (Assoc_Add (Loc,
1613 Left_Opnd => Expr_From_SO_Ref (Loc, Old_NPMax),
1614 Right_Opnd =>
1615 Make_Integer_Literal (Loc,
1616 Intval => New_Fbit / SSU)),
1617 Ins_Type => E,
1618 Vtype => E);
1619 New_Fbit := New_Fbit mod SSU;
1620 end if;
1621 end if;
1622 end if;
1623 end;
1624 end Get_Next_Component_Location;
1626 ----------------------
1627 -- Layout_Component --
1628 ----------------------
1630 procedure Layout_Component (Comp : Entity_Id; Prev_Comp : Entity_Id) is
1631 Ctyp : constant Entity_Id := Etype (Comp);
1632 ORC : constant Entity_Id := Original_Record_Component (Comp);
1633 Npos : SO_Ref;
1634 Fbit : SO_Ref;
1635 NPMax : SO_Ref;
1636 Forc : Boolean;
1638 begin
1639 -- Increase alignment of record if necessary. Note that we do not
1640 -- do this for packed records, which have an alignment of one by
1641 -- default, or for records for which an explicit alignment was
1642 -- specified with an alignment clause.
1644 if not Is_Packed (E)
1645 and then not Has_Alignment_Clause (E)
1646 and then Alignment (Ctyp) > Alignment (E)
1647 then
1648 Set_Alignment (E, Alignment (Ctyp));
1649 end if;
1651 -- If original component set, then use same layout
1653 if Present (ORC) and then ORC /= Comp then
1654 Set_Normalized_Position (Comp, Normalized_Position (ORC));
1655 Set_Normalized_First_Bit (Comp, Normalized_First_Bit (ORC));
1656 Set_Normalized_Position_Max (Comp, Normalized_Position_Max (ORC));
1657 Set_Component_Bit_Offset (Comp, Component_Bit_Offset (ORC));
1658 Set_Esize (Comp, Esize (ORC));
1659 return;
1660 end if;
1662 -- Parent field is always at start of record, this will overlap
1663 -- the actual fields that are part of the parent, and that's fine
1665 if Chars (Comp) = Name_uParent then
1666 Set_Normalized_Position (Comp, Uint_0);
1667 Set_Normalized_First_Bit (Comp, Uint_0);
1668 Set_Normalized_Position_Max (Comp, Uint_0);
1669 Set_Component_Bit_Offset (Comp, Uint_0);
1670 Set_Esize (Comp, Esize (Ctyp));
1671 return;
1672 end if;
1674 -- Check case of type of component has a scope of the record we are
1675 -- laying out. When this happens, the type in question is an Itype
1676 -- that has not yet been laid out (that's because such types do not
1677 -- get frozen in the normal manner, because there is no place for
1678 -- the freeze nodes).
1680 if Scope (Ctyp) = E then
1681 Layout_Type (Ctyp);
1682 end if;
1684 -- If component already laid out, then we are done
1686 if Known_Normalized_Position (Comp) then
1687 return;
1688 end if;
1690 -- Set size of component from type. We use the Esize except in a
1691 -- packed record, where we use the RM_Size (since that is what the
1692 -- RM_Size value, as distinct from the Object_Size is useful for).
1694 if Is_Packed (E) then
1695 Set_Esize (Comp, RM_Size (Ctyp));
1696 else
1697 Set_Esize (Comp, Esize (Ctyp));
1698 end if;
1700 -- Compute the component position from the previous one. See if
1701 -- current component requires being on a storage unit boundary.
1703 -- If record is not packed, we always go to a storage unit boundary
1705 if not Is_Packed (E) then
1706 Forc := True;
1708 -- Packed cases
1710 else
1711 -- Elementary types do not need SU boundary in packed record
1713 if Is_Elementary_Type (Ctyp) then
1714 Forc := False;
1716 -- Packed array types with a modular packed array type do not
1717 -- force a storage unit boundary (since the code generation
1718 -- treats these as equivalent to the underlying modular type),
1720 elsif Is_Array_Type (Ctyp)
1721 and then Is_Bit_Packed_Array (Ctyp)
1722 and then Is_Modular_Integer_Type (Packed_Array_Type (Ctyp))
1723 then
1724 Forc := False;
1726 -- Record types with known length less than or equal to the length
1727 -- of long long integer can also be unaligned, since they can be
1728 -- treated as scalars.
1730 elsif Is_Record_Type (Ctyp)
1731 and then not Is_Dynamic_SO_Ref (Esize (Ctyp))
1732 and then Esize (Ctyp) <= Esize (Standard_Long_Long_Integer)
1733 then
1734 Forc := False;
1736 -- All other cases force a storage unit boundary, even when packed
1738 else
1739 Forc := True;
1740 end if;
1741 end if;
1743 -- Now get the next component location
1745 Get_Next_Component_Location
1746 (Prev_Comp, Alignment (Ctyp), Npos, Fbit, NPMax, Forc);
1747 Set_Normalized_Position (Comp, Npos);
1748 Set_Normalized_First_Bit (Comp, Fbit);
1749 Set_Normalized_Position_Max (Comp, NPMax);
1751 -- Set Component_Bit_Offset in the static case
1753 if Known_Static_Normalized_Position (Comp)
1754 and then Known_Normalized_First_Bit (Comp)
1755 then
1756 Set_Component_Bit_Offset (Comp, SSU * Npos + Fbit);
1757 end if;
1758 end Layout_Component;
1760 -----------------------
1761 -- Layout_Components --
1762 -----------------------
1764 procedure Layout_Components
1765 (From : Entity_Id;
1766 To : Entity_Id;
1767 Esiz : out SO_Ref;
1768 RM_Siz : out SO_Ref)
1770 End_Npos : SO_Ref;
1771 End_Fbit : SO_Ref;
1772 End_NPMax : SO_Ref;
1774 begin
1775 -- Only lay out components if there are some to lay out
1777 if Present (From) then
1779 -- Lay out components with no component clauses
1781 Comp := From;
1782 loop
1783 if Ekind (Comp) = E_Component
1784 or else Ekind (Comp) = E_Discriminant
1785 then
1786 -- The compatibility of component clauses with composite
1787 -- types isn't checked in Sem_Ch13, so we check it here.
1789 if Present (Component_Clause (Comp)) then
1790 if Is_Composite_Type (Etype (Comp))
1791 and then Esize (Comp) < RM_Size (Etype (Comp))
1792 then
1793 Error_Msg_Uint_1 := RM_Size (Etype (Comp));
1794 Error_Msg_NE
1795 ("size for & too small, minimum allowed is ^",
1796 Component_Clause (Comp),
1797 Comp);
1798 end if;
1800 else
1801 Layout_Component (Comp, Prev_Comp);
1802 Prev_Comp := Comp;
1803 end if;
1804 end if;
1806 exit when Comp = To;
1807 Next_Entity (Comp);
1808 end loop;
1809 end if;
1811 -- Set size fields, both are zero if no components
1813 if No (Prev_Comp) then
1814 Esiz := Uint_0;
1815 RM_Siz := Uint_0;
1817 -- If record subtype with non-static discriminants, then we don't
1818 -- know which variant will be the one which gets chosen. We don't
1819 -- just want to set the maximum size from the base, because the
1820 -- size should depend on the particular variant.
1822 -- What we do is to use the RM_Size of the base type, which has
1823 -- the necessary conditional computation of the size, using the
1824 -- size information for the particular variant chosen. Records
1825 -- with default discriminants for example have an Esize that is
1826 -- set to the maximum of all variants, but that's not what we
1827 -- want for a constrained subtype.
1829 elsif Ekind (E) = E_Record_Subtype
1830 and then not Has_Static_Discriminants (E)
1831 then
1832 declare
1833 BT : constant Node_Id := Base_Type (E);
1834 begin
1835 Esiz := RM_Size (BT);
1836 RM_Siz := RM_Size (BT);
1837 Set_Alignment (E, Alignment (BT));
1838 end;
1840 else
1841 -- First the object size, for which we align past the last field
1842 -- to the alignment of the record (the object size is required to
1843 -- be a multiple of the alignment).
1845 Get_Next_Component_Location
1846 (Prev_Comp,
1847 Alignment (E),
1848 End_Npos,
1849 End_Fbit,
1850 End_NPMax,
1851 Force_SU => True);
1853 -- If the resulting normalized position is a dynamic reference,
1854 -- then the size is dynamic, and is stored in storage units. In
1855 -- this case, we set the RM_Size to the same value, it is simply
1856 -- not worth distinguishing Esize and RM_Size values in the
1857 -- dynamic case, since the RM has nothing to say about them.
1859 -- Note that a size cannot have been given in this case, since
1860 -- size specifications cannot be given for variable length types.
1862 declare
1863 Align : constant Uint := Alignment (E);
1865 begin
1866 if Is_Dynamic_SO_Ref (End_Npos) then
1867 RM_Siz := End_Npos;
1869 -- Set the Object_Size allowing for the alignment. In the
1870 -- dynamic case, we must do the actual runtime computation.
1871 -- We can skip this in the non-packed record case if the
1872 -- last component has a smaller alignment than the overall
1873 -- record alignment.
1875 if Is_Dynamic_SO_Ref (End_NPMax) then
1876 Esiz := End_NPMax;
1878 if Is_Packed (E)
1879 or else Alignment (Etype (Prev_Comp)) < Align
1880 then
1881 -- The expression we build is:
1882 -- (expr + align - 1) / align * align
1884 Esiz :=
1885 SO_Ref_From_Expr
1886 (Expr =>
1887 Make_Op_Multiply (Loc,
1888 Left_Opnd =>
1889 Make_Op_Divide (Loc,
1890 Left_Opnd =>
1891 Make_Op_Add (Loc,
1892 Left_Opnd =>
1893 Expr_From_SO_Ref (Loc, Esiz),
1894 Right_Opnd =>
1895 Make_Integer_Literal (Loc,
1896 Intval => Align - 1)),
1897 Right_Opnd =>
1898 Make_Integer_Literal (Loc, Align)),
1899 Right_Opnd =>
1900 Make_Integer_Literal (Loc, Align)),
1901 Ins_Type => E,
1902 Vtype => E);
1903 end if;
1905 -- Here Esiz is static, so we can adjust the alignment
1906 -- directly go give the required aligned value.
1908 else
1909 Esiz := (End_NPMax + Align - 1) / Align * Align * SSU;
1910 end if;
1912 -- Case where computed size is static
1914 else
1915 -- The ending size was computed in Npos in storage units,
1916 -- but the actual size is stored in bits, so adjust
1917 -- accordingly. We also adjust the size to match the
1918 -- alignment here.
1920 Esiz := (End_NPMax + Align - 1) / Align * Align * SSU;
1922 -- Compute the resulting Value_Size (RM_Size). For this
1923 -- purpose we do not force alignment of the record or
1924 -- storage size alignment of the result.
1926 Get_Next_Component_Location
1927 (Prev_Comp,
1928 Uint_0,
1929 End_Npos,
1930 End_Fbit,
1931 End_NPMax,
1932 Force_SU => False);
1934 RM_Siz := End_Npos * SSU + End_Fbit;
1935 Set_And_Check_Static_Size (E, Esiz, RM_Siz);
1936 end if;
1937 end;
1938 end if;
1939 end Layout_Components;
1941 -------------------------------
1942 -- Layout_Non_Variant_Record --
1943 -------------------------------
1945 procedure Layout_Non_Variant_Record is
1946 Esiz : SO_Ref;
1947 RM_Siz : SO_Ref;
1948 begin
1949 Layout_Components (First_Entity (E), Last_Entity (E), Esiz, RM_Siz);
1950 Set_Esize (E, Esiz);
1951 Set_RM_Size (E, RM_Siz);
1952 end Layout_Non_Variant_Record;
1954 ---------------------------
1955 -- Layout_Variant_Record --
1956 ---------------------------
1958 procedure Layout_Variant_Record is
1959 Tdef : constant Node_Id := Type_Definition (Decl);
1960 First_Discr : Entity_Id;
1961 Last_Discr : Entity_Id;
1962 Esiz : SO_Ref;
1964 RM_Siz : SO_Ref;
1965 pragma Warnings (Off, SO_Ref);
1967 RM_Siz_Expr : Node_Id := Empty;
1968 -- Expression for the evolving RM_Siz value. This is typically an if
1969 -- expression which involves tests of discriminant values that are
1970 -- formed as references to the entity V. At the end of scanning all
1971 -- the components, a suitable function is constructed in which V is
1972 -- the parameter.
1974 -----------------------
1975 -- Local Subprograms --
1976 -----------------------
1978 procedure Layout_Component_List
1979 (Clist : Node_Id;
1980 Esiz : out SO_Ref;
1981 RM_Siz_Expr : out Node_Id);
1982 -- Recursive procedure, called to lay out one component list Esiz
1983 -- and RM_Siz_Expr are set to the Object_Size and Value_Size values
1984 -- respectively representing the record size up to and including the
1985 -- last component in the component list (including any variants in
1986 -- this component list). RM_Siz_Expr is returned as an expression
1987 -- which may in the general case involve some references to the
1988 -- discriminants of the current record value, referenced by selecting
1989 -- from the entity V.
1991 ---------------------------
1992 -- Layout_Component_List --
1993 ---------------------------
1995 procedure Layout_Component_List
1996 (Clist : Node_Id;
1997 Esiz : out SO_Ref;
1998 RM_Siz_Expr : out Node_Id)
2000 Citems : constant List_Id := Component_Items (Clist);
2001 Vpart : constant Node_Id := Variant_Part (Clist);
2002 Prv : Node_Id;
2003 Var : Node_Id;
2004 RM_Siz : Uint;
2005 RMS_Ent : Entity_Id;
2007 begin
2008 if Is_Non_Empty_List (Citems) then
2009 Layout_Components
2010 (From => Defining_Identifier (First (Citems)),
2011 To => Defining_Identifier (Last (Citems)),
2012 Esiz => Esiz,
2013 RM_Siz => RM_Siz);
2014 else
2015 Layout_Components (Empty, Empty, Esiz, RM_Siz);
2016 end if;
2018 -- Case where no variants are present in the component list
2020 if No (Vpart) then
2022 -- The Esiz value has been correctly set by the call to
2023 -- Layout_Components, so there is nothing more to be done.
2025 -- For RM_Siz, we have an SO_Ref value, which we must convert
2026 -- to an appropriate expression.
2028 if Is_Static_SO_Ref (RM_Siz) then
2029 RM_Siz_Expr :=
2030 Make_Integer_Literal (Loc,
2031 Intval => RM_Siz);
2033 else
2034 RMS_Ent := Get_Dynamic_SO_Entity (RM_Siz);
2036 -- If the size is represented by a function, then we create
2037 -- an appropriate function call using V as the parameter to
2038 -- the call.
2040 if Is_Discrim_SO_Function (RMS_Ent) then
2041 RM_Siz_Expr :=
2042 Make_Function_Call (Loc,
2043 Name => New_Occurrence_Of (RMS_Ent, Loc),
2044 Parameter_Associations => New_List (
2045 Make_Identifier (Loc, Vname)));
2047 -- If the size is represented by a constant, then the
2048 -- expression we want is a reference to this constant
2050 else
2051 RM_Siz_Expr := New_Occurrence_Of (RMS_Ent, Loc);
2052 end if;
2053 end if;
2055 -- Case where variants are present in this component list
2057 else
2058 declare
2059 EsizV : SO_Ref;
2060 RM_SizV : Node_Id;
2061 Dchoice : Node_Id;
2062 Discrim : Node_Id;
2063 Dtest : Node_Id;
2064 D_List : List_Id;
2065 D_Entity : Entity_Id;
2067 begin
2068 RM_Siz_Expr := Empty;
2069 Prv := Prev_Comp;
2071 Var := Last (Variants (Vpart));
2072 while Present (Var) loop
2073 Prev_Comp := Prv;
2074 Layout_Component_List
2075 (Component_List (Var), EsizV, RM_SizV);
2077 -- Set the Object_Size. If this is the first variant,
2078 -- we just set the size of this first variant.
2080 if Var = Last (Variants (Vpart)) then
2081 Esiz := EsizV;
2083 -- Otherwise the Object_Size is formed as a maximum
2084 -- of Esiz so far from previous variants, and the new
2085 -- Esiz value from the variant we just processed.
2087 -- If both values are static, we can just compute the
2088 -- maximum directly to save building junk nodes.
2090 elsif not Is_Dynamic_SO_Ref (Esiz)
2091 and then not Is_Dynamic_SO_Ref (EsizV)
2092 then
2093 Esiz := UI_Max (Esiz, EsizV);
2095 -- If either value is dynamic, then we have to generate
2096 -- an appropriate Standard_Unsigned'Max attribute call.
2097 -- If one of the values is static then it needs to be
2098 -- converted from bits to storage units to be compatible
2099 -- with the dynamic value.
2101 else
2102 if Is_Static_SO_Ref (Esiz) then
2103 Esiz := (Esiz + SSU - 1) / SSU;
2104 end if;
2106 if Is_Static_SO_Ref (EsizV) then
2107 EsizV := (EsizV + SSU - 1) / SSU;
2108 end if;
2110 Esiz :=
2111 SO_Ref_From_Expr
2112 (Make_Attribute_Reference (Loc,
2113 Attribute_Name => Name_Max,
2114 Prefix =>
2115 New_Occurrence_Of (Standard_Unsigned, Loc),
2116 Expressions => New_List (
2117 Expr_From_SO_Ref (Loc, Esiz),
2118 Expr_From_SO_Ref (Loc, EsizV))),
2119 Ins_Type => E,
2120 Vtype => E);
2121 end if;
2123 -- Now deal with Value_Size (RM_Siz). We are aiming at
2124 -- an expression that looks like:
2126 -- if xxDx (V.disc) then rmsiz1
2127 -- else if xxDx (V.disc) then rmsiz2
2128 -- else ...
2130 -- Where rmsiz1, rmsiz2... are the RM_Siz values for the
2131 -- individual variants, and xxDx are the discriminant
2132 -- checking functions generated for the variant type.
2134 -- If this is the first variant, we simply set the result
2135 -- as the expression. Note that this takes care of the
2136 -- others case.
2138 if No (RM_Siz_Expr) then
2140 -- If this is the only variant and the size is a
2141 -- literal, then use bit size as is, otherwise convert
2142 -- to storage units and continue to the next variant.
2144 if No (Prev (Var))
2145 and then Nkind (RM_SizV) = N_Integer_Literal
2146 then
2147 RM_Siz_Expr := RM_SizV;
2148 else
2149 RM_Siz_Expr := Bits_To_SU (RM_SizV);
2150 end if;
2152 -- Otherwise construct the appropriate test
2154 else
2155 -- The test to be used in general is a call to the
2156 -- discriminant checking function. However, it is
2157 -- definitely worth special casing the very common
2158 -- case where a single value is involved.
2160 Dchoice := First (Discrete_Choices (Var));
2162 if No (Next (Dchoice))
2163 and then Nkind (Dchoice) /= N_Range
2164 then
2165 -- Discriminant to be tested
2167 Discrim :=
2168 Make_Selected_Component (Loc,
2169 Prefix =>
2170 Make_Identifier (Loc, Vname),
2171 Selector_Name =>
2172 New_Occurrence_Of
2173 (Entity (Name (Vpart)), Loc));
2175 Dtest :=
2176 Make_Op_Eq (Loc,
2177 Left_Opnd => Discrim,
2178 Right_Opnd => New_Copy (Dchoice));
2180 -- Generate a call to the discriminant-checking
2181 -- function for the variant. Note that the result
2182 -- has to be complemented since the function returns
2183 -- False when the passed discriminant value matches.
2185 else
2186 -- The checking function takes all of the type's
2187 -- discriminants as parameters, so a list of all
2188 -- the selected discriminants must be constructed.
2190 D_List := New_List;
2191 D_Entity := First_Discriminant (E);
2192 while Present (D_Entity) loop
2193 Append (
2194 Make_Selected_Component (Loc,
2195 Prefix =>
2196 Make_Identifier (Loc, Vname),
2197 Selector_Name =>
2198 New_Occurrence_Of (D_Entity, Loc)),
2199 D_List);
2201 D_Entity := Next_Discriminant (D_Entity);
2202 end loop;
2204 Dtest :=
2205 Make_Op_Not (Loc,
2206 Right_Opnd =>
2207 Make_Function_Call (Loc,
2208 Name =>
2209 New_Occurrence_Of
2210 (Dcheck_Function (Var), Loc),
2211 Parameter_Associations =>
2212 D_List));
2213 end if;
2215 RM_Siz_Expr :=
2216 Make_If_Expression (Loc,
2217 Expressions =>
2218 New_List
2219 (Dtest, Bits_To_SU (RM_SizV), RM_Siz_Expr));
2220 end if;
2222 Prev (Var);
2223 end loop;
2224 end;
2225 end if;
2226 end Layout_Component_List;
2228 Others_Present : Boolean;
2229 pragma Warnings (Off, Others_Present);
2230 -- Indicates others present, not used in this case
2232 procedure Non_Static_Choice_Error (Choice : Node_Id);
2233 -- Error routine invoked by the generic instantiation below when
2234 -- the variant part has a nonstatic choice.
2236 package Variant_Choices_Processing is new
2237 Generic_Check_Choices
2238 (Process_Empty_Choice => No_OP,
2239 Process_Non_Static_Choice => Non_Static_Choice_Error,
2240 Process_Associated_Node => No_OP);
2241 use Variant_Choices_Processing;
2243 -----------------------------
2244 -- Non_Static_Choice_Error --
2245 -----------------------------
2247 procedure Non_Static_Choice_Error (Choice : Node_Id) is
2248 begin
2249 Flag_Non_Static_Expr
2250 ("choice given in case expression is not static!", Choice);
2251 end Non_Static_Choice_Error;
2253 -- Start of processing for Layout_Variant_Record
2255 begin
2256 -- Call Check_Choices here to ensure that Others_Discrete_Choices
2257 -- gets set on any 'others' choice before the discriminant-checking
2258 -- functions are generated. Otherwise the function for the 'others'
2259 -- alternative will unconditionally return True, causing discriminant
2260 -- checks to fail. However, Check_Choices is now normally delayed
2261 -- until the type's freeze entity is processed, due to requirements
2262 -- coming from subtype predicates, so doing it at this point is
2263 -- probably not right in general, but it's not clear how else to deal
2264 -- with this situation. Perhaps we should only generate declarations
2265 -- for the checking functions here, and somehow delay generation of
2266 -- their bodies, but that would be a nontrivial change. ???
2268 declare
2269 VP : constant Node_Id :=
2270 Variant_Part (Component_List (Type_Definition (Decl)));
2271 begin
2272 Check_Choices
2273 (VP, Variants (VP), Etype (Name (VP)), Others_Present);
2274 end;
2276 -- We need the discriminant checking functions, since we generate
2277 -- calls to these functions for the RM_Size expression, so make
2278 -- sure that these functions have been constructed in time.
2280 Build_Discr_Checking_Funcs (Decl);
2282 -- Lay out the discriminants
2284 First_Discr := First_Discriminant (E);
2285 Last_Discr := First_Discr;
2286 while Present (Next_Discriminant (Last_Discr)) loop
2287 Next_Discriminant (Last_Discr);
2288 end loop;
2290 Layout_Components
2291 (From => First_Discr,
2292 To => Last_Discr,
2293 Esiz => Esiz,
2294 RM_Siz => RM_Siz);
2296 -- Lay out the main component list (this will make recursive calls
2297 -- to lay out all component lists nested within variants).
2299 Layout_Component_List (Component_List (Tdef), Esiz, RM_Siz_Expr);
2300 Set_Esize (E, Esiz);
2302 -- If the RM_Size is a literal, set its value
2304 if Nkind (RM_Siz_Expr) = N_Integer_Literal then
2305 Set_RM_Size (E, Intval (RM_Siz_Expr));
2307 -- Otherwise we construct a dynamic SO_Ref
2309 else
2310 Set_RM_Size (E,
2311 SO_Ref_From_Expr
2312 (RM_Siz_Expr,
2313 Ins_Type => E,
2314 Vtype => E));
2315 end if;
2316 end Layout_Variant_Record;
2318 -- Start of processing for Layout_Record_Type
2320 begin
2321 -- If this is a cloned subtype, just copy the size fields from the
2322 -- original, nothing else needs to be done in this case, since the
2323 -- components themselves are all shared.
2325 if Ekind_In (E, E_Record_Subtype, E_Class_Wide_Subtype)
2326 and then Present (Cloned_Subtype (E))
2327 then
2328 Set_Esize (E, Esize (Cloned_Subtype (E)));
2329 Set_RM_Size (E, RM_Size (Cloned_Subtype (E)));
2330 Set_Alignment (E, Alignment (Cloned_Subtype (E)));
2332 -- Another special case, class-wide types. The RM says that the size
2333 -- of such types is implementation defined (RM 13.3(48)). What we do
2334 -- here is to leave the fields set as unknown values, and the backend
2335 -- determines the actual behavior.
2337 elsif Ekind (E) = E_Class_Wide_Type then
2338 null;
2340 -- All other cases
2342 else
2343 -- Initialize alignment conservatively to 1. This value will be
2344 -- increased as necessary during processing of the record.
2346 if Unknown_Alignment (E) then
2347 Set_Alignment (E, Uint_1);
2348 end if;
2350 -- Initialize previous component. This is Empty unless there are
2351 -- components which have already been laid out by component clauses.
2352 -- If there are such components, we start our lay out of the
2353 -- remaining components following the last such component.
2355 Prev_Comp := Empty;
2357 Comp := First_Component_Or_Discriminant (E);
2358 while Present (Comp) loop
2359 if Present (Component_Clause (Comp)) then
2360 if No (Prev_Comp)
2361 or else
2362 Component_Bit_Offset (Comp) >
2363 Component_Bit_Offset (Prev_Comp)
2364 then
2365 Prev_Comp := Comp;
2366 end if;
2367 end if;
2369 Next_Component_Or_Discriminant (Comp);
2370 end loop;
2372 -- We have two separate circuits, one for non-variant records and
2373 -- one for variant records. For non-variant records, we simply go
2374 -- through the list of components. This handles all the non-variant
2375 -- cases including those cases of subtypes where there is no full
2376 -- type declaration, so the tree cannot be used to drive the layout.
2377 -- For variant records, we have to drive the layout from the tree
2378 -- since we need to understand the variant structure in this case.
2380 if Present (Full_View (E)) then
2381 Decl := Declaration_Node (Full_View (E));
2382 else
2383 Decl := Declaration_Node (E);
2384 end if;
2386 -- Scan all the components
2388 if Nkind (Decl) = N_Full_Type_Declaration
2389 and then Has_Discriminants (E)
2390 and then Nkind (Type_Definition (Decl)) = N_Record_Definition
2391 and then Present (Component_List (Type_Definition (Decl)))
2392 and then
2393 Present (Variant_Part (Component_List (Type_Definition (Decl))))
2394 then
2395 Layout_Variant_Record;
2396 else
2397 Layout_Non_Variant_Record;
2398 end if;
2399 end if;
2400 end Layout_Record_Type;
2402 -----------------
2403 -- Layout_Type --
2404 -----------------
2406 procedure Layout_Type (E : Entity_Id) is
2407 Desig_Type : Entity_Id;
2409 begin
2410 -- For string literal types, for now, kill the size always, this is
2411 -- because gigi does not like or need the size to be set ???
2413 if Ekind (E) = E_String_Literal_Subtype then
2414 Set_Esize (E, Uint_0);
2415 Set_RM_Size (E, Uint_0);
2416 return;
2417 end if;
2419 -- For access types, set size/alignment. This is system address size,
2420 -- except for fat pointers (unconstrained array access types), where the
2421 -- size is two times the address size, to accommodate the two pointers
2422 -- that are required for a fat pointer (data and template). Note that
2423 -- E_Access_Protected_Subprogram_Type is not an access type for this
2424 -- purpose since it is not a pointer but is equivalent to a record. For
2425 -- access subtypes, copy the size from the base type since Gigi
2426 -- represents them the same way.
2428 if Is_Access_Type (E) then
2430 Desig_Type := Underlying_Type (Designated_Type (E));
2432 -- If we only have a limited view of the type, see whether the
2433 -- non-limited view is available.
2435 if From_Limited_With (Designated_Type (E))
2436 and then Ekind (Designated_Type (E)) = E_Incomplete_Type
2437 and then Present (Non_Limited_View (Designated_Type (E)))
2438 then
2439 Desig_Type := Non_Limited_View (Designated_Type (E));
2440 end if;
2442 -- If Esize already set (e.g. by a size clause), then nothing further
2443 -- to be done here.
2445 if Known_Esize (E) then
2446 null;
2448 -- Access to subprogram is a strange beast, and we let the backend
2449 -- figure out what is needed (it may be some kind of fat pointer,
2450 -- including the static link for example.
2452 elsif Is_Access_Protected_Subprogram_Type (E) then
2453 null;
2455 -- For access subtypes, copy the size information from base type
2457 elsif Ekind (E) = E_Access_Subtype then
2458 Set_Size_Info (E, Base_Type (E));
2459 Set_RM_Size (E, RM_Size (Base_Type (E)));
2461 -- For other access types, we use either address size, or, if a fat
2462 -- pointer is used (pointer-to-unconstrained array case), twice the
2463 -- address size to accommodate a fat pointer.
2465 elsif Present (Desig_Type)
2466 and then Is_Array_Type (Desig_Type)
2467 and then not Is_Constrained (Desig_Type)
2468 and then not Has_Completion_In_Body (Desig_Type)
2469 and then not Debug_Flag_6
2470 then
2471 Init_Size (E, 2 * System_Address_Size);
2473 -- Check for bad convention set
2475 if Warn_On_Export_Import
2476 and then
2477 (Convention (E) = Convention_C
2478 or else
2479 Convention (E) = Convention_CPP)
2480 then
2481 Error_Msg_N
2482 ("?x?this access type does not correspond to C pointer", E);
2483 end if;
2485 -- If the designated type is a limited view it is unanalyzed. We can
2486 -- examine the declaration itself to determine whether it will need a
2487 -- fat pointer.
2489 elsif Present (Desig_Type)
2490 and then Present (Parent (Desig_Type))
2491 and then Nkind (Parent (Desig_Type)) = N_Full_Type_Declaration
2492 and then
2493 Nkind (Type_Definition (Parent (Desig_Type)))
2494 = N_Unconstrained_Array_Definition
2495 and then not Debug_Flag_6
2496 then
2497 Init_Size (E, 2 * System_Address_Size);
2499 -- When the target is AAMP, access-to-subprogram types are fat
2500 -- pointers consisting of the subprogram address and a static link,
2501 -- with the exception of library-level access types (including
2502 -- library-level anonymous access types, such as for components),
2503 -- where a simple subprogram address is used.
2505 elsif AAMP_On_Target
2506 and then
2507 ((Ekind (E) = E_Access_Subprogram_Type
2508 and then Present (Enclosing_Subprogram (E)))
2509 or else
2510 (Ekind (E) = E_Anonymous_Access_Subprogram_Type
2511 and then
2512 (not Is_Local_Anonymous_Access (E)
2513 or else Present (Enclosing_Subprogram (E)))))
2514 then
2515 Init_Size (E, 2 * System_Address_Size);
2516 else
2517 Init_Size (E, System_Address_Size);
2518 end if;
2520 -- On VMS, reset size to 32 for convention C access type if no
2521 -- explicit size clause is given and the default size is 64. Really
2522 -- we do not know the size, since depending on options for the VMS
2523 -- compiler, the size of a pointer type can be 32 or 64, but choosing
2524 -- 32 as the default improves compatibility with legacy VMS code.
2526 -- Note: we do not use Has_Size_Clause in the test below, because we
2527 -- want to catch the case of a derived type inheriting a size clause.
2528 -- We want to consider this to be an explicit size clause for this
2529 -- purpose, since it would be weird not to inherit the size in this
2530 -- case.
2532 -- We do NOT do this if we are in -gnatdm mode on a non-VMS target
2533 -- since in that case we want the normal pointer representation.
2535 if Opt.True_VMS_Target
2536 and then (Convention (E) = Convention_C
2537 or else
2538 Convention (E) = Convention_CPP)
2539 and then No (Get_Attribute_Definition_Clause (E, Attribute_Size))
2540 and then Esize (E) = 64
2541 then
2542 Init_Size (E, 32);
2543 end if;
2545 Set_Elem_Alignment (E);
2547 -- Scalar types: set size and alignment
2549 elsif Is_Scalar_Type (E) then
2551 -- For discrete types, the RM_Size and Esize must be set already,
2552 -- since this is part of the earlier processing and the front end is
2553 -- always required to lay out the sizes of such types (since they are
2554 -- available as static attributes). All we do is to check that this
2555 -- rule is indeed obeyed.
2557 if Is_Discrete_Type (E) then
2559 -- If the RM_Size is not set, then here is where we set it
2561 -- Note: an RM_Size of zero looks like not set here, but this
2562 -- is a rare case, and we can simply reset it without any harm.
2564 if not Known_RM_Size (E) then
2565 Set_Discrete_RM_Size (E);
2566 end if;
2568 -- If Esize for a discrete type is not set then set it
2570 if not Known_Esize (E) then
2571 declare
2572 S : Int := 8;
2574 begin
2575 loop
2576 -- If size is big enough, set it and exit
2578 if S >= RM_Size (E) then
2579 Init_Esize (E, S);
2580 exit;
2582 -- If the RM_Size is greater than 64 (happens only when
2583 -- strange values are specified by the user, then Esize
2584 -- is simply a copy of RM_Size, it will be further
2585 -- refined later on)
2587 elsif S = 64 then
2588 Set_Esize (E, RM_Size (E));
2589 exit;
2591 -- Otherwise double possible size and keep trying
2593 else
2594 S := S * 2;
2595 end if;
2596 end loop;
2597 end;
2598 end if;
2600 -- For non-discrete scalar types, if the RM_Size is not set, then set
2601 -- it now to a copy of the Esize if the Esize is set.
2603 else
2604 if Known_Esize (E) and then Unknown_RM_Size (E) then
2605 Set_RM_Size (E, Esize (E));
2606 end if;
2607 end if;
2609 Set_Elem_Alignment (E);
2611 -- Non-elementary (composite) types
2613 else
2614 -- For packed arrays, take size and alignment values from the packed
2615 -- array type if a packed array type has been created and the fields
2616 -- are not currently set.
2618 if Is_Array_Type (E) and then Present (Packed_Array_Type (E)) then
2619 declare
2620 PAT : constant Entity_Id := Packed_Array_Type (E);
2622 begin
2623 if Unknown_Esize (E) then
2624 Set_Esize (E, Esize (PAT));
2625 end if;
2627 if Unknown_RM_Size (E) then
2628 Set_RM_Size (E, RM_Size (PAT));
2629 end if;
2631 if Unknown_Alignment (E) then
2632 Set_Alignment (E, Alignment (PAT));
2633 end if;
2634 end;
2635 end if;
2637 -- If Esize is set, and RM_Size is not, RM_Size is copied from Esize.
2638 -- At least for now this seems reasonable, and is in any case needed
2639 -- for compatibility with old versions of gigi.
2641 if Known_Esize (E) and then Unknown_RM_Size (E) then
2642 Set_RM_Size (E, Esize (E));
2643 end if;
2645 -- For array base types, set component size if object size of the
2646 -- component type is known and is a small power of 2 (8, 16, 32, 64),
2647 -- since this is what will always be used.
2649 if Ekind (E) = E_Array_Type
2650 and then Unknown_Component_Size (E)
2651 then
2652 declare
2653 CT : constant Entity_Id := Component_Type (E);
2655 begin
2656 -- For some reasons, access types can cause trouble, So let's
2657 -- just do this for scalar types ???
2659 if Present (CT)
2660 and then Is_Scalar_Type (CT)
2661 and then Known_Static_Esize (CT)
2662 then
2663 declare
2664 S : constant Uint := Esize (CT);
2665 begin
2666 if Addressable (S) then
2667 Set_Component_Size (E, S);
2668 end if;
2669 end;
2670 end if;
2671 end;
2672 end if;
2673 end if;
2675 -- Lay out array and record types if front end layout set
2677 if Frontend_Layout_On_Target then
2678 if Is_Array_Type (E) and then not Is_Bit_Packed_Array (E) then
2679 Layout_Array_Type (E);
2680 elsif Is_Record_Type (E) then
2681 Layout_Record_Type (E);
2682 end if;
2684 -- Case of backend layout, we still do a little in the front end
2686 else
2687 -- Processing for record types
2689 if Is_Record_Type (E) then
2691 -- Special remaining processing for record types with a known
2692 -- size of 16, 32, or 64 bits whose alignment is not yet set.
2693 -- For these types, we set a corresponding alignment matching
2694 -- the size if possible, or as large as possible if not.
2696 if Convention (E) = Convention_Ada
2697 and then not Debug_Flag_Q
2698 then
2699 Set_Composite_Alignment (E);
2700 end if;
2702 -- Processing for array types
2704 elsif Is_Array_Type (E) then
2706 -- For arrays that are required to be atomic, we do the same
2707 -- processing as described above for short records, since we
2708 -- really need to have the alignment set for the whole array.
2710 if Is_Atomic (E) and then not Debug_Flag_Q then
2711 Set_Composite_Alignment (E);
2712 end if;
2714 -- For unpacked array types, set an alignment of 1 if we know
2715 -- that the component alignment is not greater than 1. The reason
2716 -- we do this is to avoid unnecessary copying of slices of such
2717 -- arrays when passed to subprogram parameters (see special test
2718 -- in Exp_Ch6.Expand_Actuals).
2720 if not Is_Packed (E)
2721 and then Unknown_Alignment (E)
2722 then
2723 if Known_Static_Component_Size (E)
2724 and then Component_Size (E) = 1
2725 then
2726 Set_Alignment (E, Uint_1);
2727 end if;
2728 end if;
2730 -- We need to know whether the size depends on the value of one
2731 -- or more discriminants to select the return mechanism. Skip if
2732 -- errors are present, to prevent cascaded messages.
2734 if Serious_Errors_Detected = 0 then
2735 Compute_Size_Depends_On_Discriminant (E);
2736 end if;
2738 end if;
2739 end if;
2741 -- Final step is to check that Esize and RM_Size are compatible
2743 if Known_Static_Esize (E) and then Known_Static_RM_Size (E) then
2744 if Esize (E) < RM_Size (E) then
2746 -- Esize is less than RM_Size. That's not good. First we test
2747 -- whether this was set deliberately with an Object_Size clause
2748 -- and if so, object to the clause.
2750 if Has_Object_Size_Clause (E) then
2751 Error_Msg_Uint_1 := RM_Size (E);
2752 Error_Msg_F
2753 ("object size is too small, minimum allowed is ^",
2754 Expression (Get_Attribute_Definition_Clause
2755 (E, Attribute_Object_Size)));
2756 end if;
2758 -- Adjust Esize up to RM_Size value
2760 declare
2761 Size : constant Uint := RM_Size (E);
2763 begin
2764 Set_Esize (E, RM_Size (E));
2766 -- For scalar types, increase Object_Size to power of 2, but
2767 -- not less than a storage unit in any case (i.e., normally
2768 -- this means it will be storage-unit addressable).
2770 if Is_Scalar_Type (E) then
2771 if Size <= System_Storage_Unit then
2772 Init_Esize (E, System_Storage_Unit);
2773 elsif Size <= 16 then
2774 Init_Esize (E, 16);
2775 elsif Size <= 32 then
2776 Init_Esize (E, 32);
2777 else
2778 Set_Esize (E, (Size + 63) / 64 * 64);
2779 end if;
2781 -- Finally, make sure that alignment is consistent with
2782 -- the newly assigned size.
2784 while Alignment (E) * System_Storage_Unit < Esize (E)
2785 and then Alignment (E) < Maximum_Alignment
2786 loop
2787 Set_Alignment (E, 2 * Alignment (E));
2788 end loop;
2789 end if;
2790 end;
2791 end if;
2792 end if;
2793 end Layout_Type;
2795 ---------------------
2796 -- Rewrite_Integer --
2797 ---------------------
2799 procedure Rewrite_Integer (N : Node_Id; V : Uint) is
2800 Loc : constant Source_Ptr := Sloc (N);
2801 Typ : constant Entity_Id := Etype (N);
2802 begin
2803 Rewrite (N, Make_Integer_Literal (Loc, Intval => V));
2804 Set_Etype (N, Typ);
2805 end Rewrite_Integer;
2807 -------------------------------
2808 -- Set_And_Check_Static_Size --
2809 -------------------------------
2811 procedure Set_And_Check_Static_Size
2812 (E : Entity_Id;
2813 Esiz : SO_Ref;
2814 RM_Siz : SO_Ref)
2816 SC : Node_Id;
2818 procedure Check_Size_Too_Small (Spec : Uint; Min : Uint);
2819 -- Spec is the number of bit specified in the size clause, and Min is
2820 -- the minimum computed size. An error is given that the specified size
2821 -- is too small if Spec < Min, and in this case both Esize and RM_Size
2822 -- are set to unknown in E. The error message is posted on node SC.
2824 procedure Check_Unused_Bits (Spec : Uint; Max : Uint);
2825 -- Spec is the number of bits specified in the size clause, and Max is
2826 -- the maximum computed size. A warning is given about unused bits if
2827 -- Spec > Max. This warning is posted on node SC.
2829 --------------------------
2830 -- Check_Size_Too_Small --
2831 --------------------------
2833 procedure Check_Size_Too_Small (Spec : Uint; Min : Uint) is
2834 begin
2835 if Spec < Min then
2836 Error_Msg_Uint_1 := Min;
2837 Error_Msg_NE ("size for & too small, minimum allowed is ^", SC, E);
2838 Init_Esize (E);
2839 Init_RM_Size (E);
2840 end if;
2841 end Check_Size_Too_Small;
2843 -----------------------
2844 -- Check_Unused_Bits --
2845 -----------------------
2847 procedure Check_Unused_Bits (Spec : Uint; Max : Uint) is
2848 begin
2849 if Spec > Max then
2850 Error_Msg_Uint_1 := Spec - Max;
2851 Error_Msg_NE ("??^ bits of & unused", SC, E);
2852 end if;
2853 end Check_Unused_Bits;
2855 -- Start of processing for Set_And_Check_Static_Size
2857 begin
2858 -- Case where Object_Size (Esize) is already set by a size clause
2860 if Known_Static_Esize (E) then
2861 SC := Size_Clause (E);
2863 if No (SC) then
2864 SC := Get_Attribute_Definition_Clause (E, Attribute_Object_Size);
2865 end if;
2867 -- Perform checks on specified size against computed sizes
2869 if Present (SC) then
2870 Check_Unused_Bits (Esize (E), Esiz);
2871 Check_Size_Too_Small (Esize (E), RM_Siz);
2872 end if;
2873 end if;
2875 -- Case where Value_Size (RM_Size) is set by specific Value_Size clause
2876 -- (we do not need to worry about Value_Size being set by a Size clause,
2877 -- since that will have set Esize as well, and we already took care of
2878 -- that case).
2880 if Known_Static_RM_Size (E) then
2881 SC := Get_Attribute_Definition_Clause (E, Attribute_Value_Size);
2883 -- Perform checks on specified size against computed sizes
2885 if Present (SC) then
2886 Check_Unused_Bits (RM_Size (E), Esiz);
2887 Check_Size_Too_Small (RM_Size (E), RM_Siz);
2888 end if;
2889 end if;
2891 -- Set sizes if unknown
2893 if Unknown_Esize (E) then
2894 Set_Esize (E, Esiz);
2895 end if;
2897 if Unknown_RM_Size (E) then
2898 Set_RM_Size (E, RM_Siz);
2899 end if;
2900 end Set_And_Check_Static_Size;
2902 -----------------------------
2903 -- Set_Composite_Alignment --
2904 -----------------------------
2906 procedure Set_Composite_Alignment (E : Entity_Id) is
2907 Siz : Uint;
2908 Align : Nat;
2910 begin
2911 -- If alignment is already set, then nothing to do
2913 if Known_Alignment (E) then
2914 return;
2915 end if;
2917 -- Alignment is not known, see if we can set it, taking into account
2918 -- the setting of the Optimize_Alignment mode.
2920 -- If Optimize_Alignment is set to Space, then we try to give packed
2921 -- records an aligmment of 1, unless there is some reason we can't.
2923 if Optimize_Alignment_Space (E)
2924 and then Is_Record_Type (E)
2925 and then Is_Packed (E)
2926 then
2927 -- No effect for record with atomic components
2929 if Is_Atomic (E) then
2930 Error_Msg_N ("Optimize_Alignment has no effect for &??", E);
2931 Error_Msg_N ("\pragma ignored for atomic record??", E);
2932 return;
2933 end if;
2935 -- No effect if independent components
2937 if Has_Independent_Components (E) then
2938 Error_Msg_N ("Optimize_Alignment has no effect for &??", E);
2939 Error_Msg_N
2940 ("\pragma ignored for record with independent components??", E);
2941 return;
2942 end if;
2944 -- No effect if any component is atomic or is a by reference type
2946 declare
2947 Ent : Entity_Id;
2948 begin
2949 Ent := First_Component_Or_Discriminant (E);
2950 while Present (Ent) loop
2951 if Is_By_Reference_Type (Etype (Ent))
2952 or else Is_Atomic (Etype (Ent))
2953 or else Is_Atomic (Ent)
2954 then
2955 Error_Msg_N ("Optimize_Alignment has no effect for &??", E);
2956 Error_Msg_N
2957 ("\pragma is ignored if atomic components present??", E);
2958 return;
2959 else
2960 Next_Component_Or_Discriminant (Ent);
2961 end if;
2962 end loop;
2963 end;
2965 -- Optimize_Alignment has no effect on variable length record
2967 if not Size_Known_At_Compile_Time (E) then
2968 Error_Msg_N ("Optimize_Alignment has no effect for &??", E);
2969 Error_Msg_N ("\pragma is ignored for variable length record??", E);
2970 return;
2971 end if;
2973 -- All tests passed, we can set alignment to 1
2975 Align := 1;
2977 -- Not a record, or not packed
2979 else
2980 -- The only other cases we worry about here are where the size is
2981 -- statically known at compile time.
2983 if Known_Static_Esize (E) then
2984 Siz := Esize (E);
2986 elsif Unknown_Esize (E)
2987 and then Known_Static_RM_Size (E)
2988 then
2989 Siz := RM_Size (E);
2991 else
2992 return;
2993 end if;
2995 -- Size is known, alignment is not set
2997 -- Reset alignment to match size if the known size is exactly 2, 4,
2998 -- or 8 storage units.
3000 if Siz = 2 * System_Storage_Unit then
3001 Align := 2;
3002 elsif Siz = 4 * System_Storage_Unit then
3003 Align := 4;
3004 elsif Siz = 8 * System_Storage_Unit then
3005 Align := 8;
3007 -- If Optimize_Alignment is set to Space, then make sure the
3008 -- alignment matches the size, for example, if the size is 17
3009 -- bytes then we want an alignment of 1 for the type.
3011 elsif Optimize_Alignment_Space (E) then
3012 if Siz mod (8 * System_Storage_Unit) = 0 then
3013 Align := 8;
3014 elsif Siz mod (4 * System_Storage_Unit) = 0 then
3015 Align := 4;
3016 elsif Siz mod (2 * System_Storage_Unit) = 0 then
3017 Align := 2;
3018 else
3019 Align := 1;
3020 end if;
3022 -- If Optimize_Alignment is set to Time, then we reset for odd
3023 -- "in between sizes", for example a 17 bit record is given an
3024 -- alignment of 4. Note that this matches the old VMS behavior
3025 -- in versions of GNAT prior to 6.1.1.
3027 elsif Optimize_Alignment_Time (E)
3028 and then Siz > System_Storage_Unit
3029 and then Siz <= 8 * System_Storage_Unit
3030 then
3031 if Siz <= 2 * System_Storage_Unit then
3032 Align := 2;
3033 elsif Siz <= 4 * System_Storage_Unit then
3034 Align := 4;
3035 else -- Siz <= 8 * System_Storage_Unit then
3036 Align := 8;
3037 end if;
3039 -- No special alignment fiddling needed
3041 else
3042 return;
3043 end if;
3044 end if;
3046 -- Here we have Set Align to the proposed improved value. Make sure the
3047 -- value set does not exceed Maximum_Alignment for the target.
3049 if Align > Maximum_Alignment then
3050 Align := Maximum_Alignment;
3051 end if;
3053 -- Further processing for record types only to reduce the alignment
3054 -- set by the above processing in some specific cases. We do not
3055 -- do this for atomic records, since we need max alignment there,
3057 if Is_Record_Type (E) and then not Is_Atomic (E) then
3059 -- For records, there is generally no point in setting alignment
3060 -- higher than word size since we cannot do better than move by
3061 -- words in any case. Omit this if we are optimizing for time,
3062 -- since conceivably we may be able to do better.
3064 if Align > System_Word_Size / System_Storage_Unit
3065 and then not Optimize_Alignment_Time (E)
3066 then
3067 Align := System_Word_Size / System_Storage_Unit;
3068 end if;
3070 -- Check components. If any component requires a higher alignment,
3071 -- then we set that higher alignment in any case. Don't do this if
3072 -- we have Optimize_Alignment set to Space. Note that that covers
3073 -- the case of packed records, where we already set alignment to 1.
3075 if not Optimize_Alignment_Space (E) then
3076 declare
3077 Comp : Entity_Id;
3079 begin
3080 Comp := First_Component (E);
3081 while Present (Comp) loop
3082 if Known_Alignment (Etype (Comp)) then
3083 declare
3084 Calign : constant Uint := Alignment (Etype (Comp));
3086 begin
3087 -- The cases to process are when the alignment of the
3088 -- component type is larger than the alignment we have
3089 -- so far, and either there is no component clause for
3090 -- the component, or the length set by the component
3091 -- clause matches the length of the component type.
3093 if Calign > Align
3094 and then
3095 (Unknown_Esize (Comp)
3096 or else (Known_Static_Esize (Comp)
3097 and then
3098 Esize (Comp) =
3099 Calign * System_Storage_Unit))
3100 then
3101 Align := UI_To_Int (Calign);
3102 end if;
3103 end;
3104 end if;
3106 Next_Component (Comp);
3107 end loop;
3108 end;
3109 end if;
3110 end if;
3112 -- Set chosen alignment, and increase Esize if necessary to match the
3113 -- chosen alignment.
3115 Set_Alignment (E, UI_From_Int (Align));
3117 if Known_Static_Esize (E)
3118 and then Esize (E) < Align * System_Storage_Unit
3119 then
3120 Set_Esize (E, UI_From_Int (Align * System_Storage_Unit));
3121 end if;
3122 end Set_Composite_Alignment;
3124 --------------------------
3125 -- Set_Discrete_RM_Size --
3126 --------------------------
3128 procedure Set_Discrete_RM_Size (Def_Id : Entity_Id) is
3129 FST : constant Entity_Id := First_Subtype (Def_Id);
3131 begin
3132 -- All discrete types except for the base types in standard are
3133 -- constrained, so indicate this by setting Is_Constrained.
3135 Set_Is_Constrained (Def_Id);
3137 -- Set generic types to have an unknown size, since the representation
3138 -- of a generic type is irrelevant, in view of the fact that they have
3139 -- nothing to do with code.
3141 if Is_Generic_Type (Root_Type (FST)) then
3142 Set_RM_Size (Def_Id, Uint_0);
3144 -- If the subtype statically matches the first subtype, then it is
3145 -- required to have exactly the same layout. This is required by
3146 -- aliasing considerations.
3148 elsif Def_Id /= FST and then
3149 Subtypes_Statically_Match (Def_Id, FST)
3150 then
3151 Set_RM_Size (Def_Id, RM_Size (FST));
3152 Set_Size_Info (Def_Id, FST);
3154 -- In all other cases the RM_Size is set to the minimum size. Note that
3155 -- this routine is never called for subtypes for which the RM_Size is
3156 -- set explicitly by an attribute clause.
3158 else
3159 Set_RM_Size (Def_Id, UI_From_Int (Minimum_Size (Def_Id)));
3160 end if;
3161 end Set_Discrete_RM_Size;
3163 ------------------------
3164 -- Set_Elem_Alignment --
3165 ------------------------
3167 procedure Set_Elem_Alignment (E : Entity_Id) is
3168 begin
3169 -- Do not set alignment for packed array types, unless we are doing
3170 -- front end layout, because otherwise this is always handled in the
3171 -- backend.
3173 if Is_Packed_Array_Type (E) and then not Frontend_Layout_On_Target then
3174 return;
3176 -- If there is an alignment clause, then we respect it
3178 elsif Has_Alignment_Clause (E) then
3179 return;
3181 -- If the size is not set, then don't attempt to set the alignment. This
3182 -- happens in the backend layout case for access-to-subprogram types.
3184 elsif not Known_Static_Esize (E) then
3185 return;
3187 -- For access types, do not set the alignment if the size is less than
3188 -- the allowed minimum size. This avoids cascaded error messages.
3190 elsif Is_Access_Type (E)
3191 and then Esize (E) < System_Address_Size
3192 then
3193 return;
3194 end if;
3196 -- Here we calculate the alignment as the largest power of two multiple
3197 -- of System.Storage_Unit that does not exceed either the object size of
3198 -- the type, or the maximum allowed alignment.
3200 declare
3201 S : Int;
3202 A : Nat;
3204 Max_Alignment : Nat;
3206 begin
3207 -- The given Esize may be larger that int'last because of a previous
3208 -- error, and the call to UI_To_Int will fail, so use default.
3210 if Esize (E) / SSU > Ttypes.Maximum_Alignment then
3211 S := Ttypes.Maximum_Alignment;
3213 -- If this is an access type and the target doesn't have strict
3214 -- alignment and we are not doing front end layout, then cap the
3215 -- alignment to that of a regular access type. This will avoid
3216 -- giving fat pointers twice the usual alignment for no practical
3217 -- benefit since the misalignment doesn't really matter.
3219 elsif Is_Access_Type (E)
3220 and then not Target_Strict_Alignment
3221 and then not Frontend_Layout_On_Target
3222 then
3223 S := System_Address_Size / SSU;
3225 else
3226 S := UI_To_Int (Esize (E)) / SSU;
3227 end if;
3229 -- If the default alignment of "double" floating-point types is
3230 -- specifically capped, enforce the cap.
3232 if Ttypes.Target_Double_Float_Alignment > 0
3233 and then S = 8
3234 and then Is_Floating_Point_Type (E)
3235 then
3236 Max_Alignment := Ttypes.Target_Double_Float_Alignment;
3238 -- If the default alignment of "double" or larger scalar types is
3239 -- specifically capped, enforce the cap.
3241 elsif Ttypes.Target_Double_Scalar_Alignment > 0
3242 and then S >= 8
3243 and then Is_Scalar_Type (E)
3244 then
3245 Max_Alignment := Ttypes.Target_Double_Scalar_Alignment;
3247 -- Otherwise enforce the overall alignment cap
3249 else
3250 Max_Alignment := Ttypes.Maximum_Alignment;
3251 end if;
3253 A := 1;
3254 while 2 * A <= Max_Alignment and then 2 * A <= S loop
3255 A := 2 * A;
3256 end loop;
3258 -- If alignment is currently not set, then we can safetly set it to
3259 -- this new calculated value.
3261 if Unknown_Alignment (E) then
3262 Init_Alignment (E, A);
3264 -- Cases where we have inherited an alignment
3266 -- For constructed types, always reset the alignment, these are
3267 -- Generally invisible to the user anyway, and that way we are
3268 -- sure that no constructed types have weird alignments.
3270 elsif not Comes_From_Source (E) then
3271 Init_Alignment (E, A);
3273 -- If this inherited alignment is the same as the one we computed,
3274 -- then obviously everything is fine, and we do not need to reset it.
3276 elsif Alignment (E) = A then
3277 null;
3279 -- Now we come to the difficult cases where we have inherited an
3280 -- alignment and size, but overridden the size but not the alignment.
3282 elsif Has_Size_Clause (E) or else Has_Object_Size_Clause (E) then
3284 -- This is tricky, it might be thought that we should try to
3285 -- inherit the alignment, since that's what the RM implies, but
3286 -- that leads to complex rules and oddities. Consider for example:
3288 -- type R is new Character;
3289 -- for R'Size use 16;
3291 -- It seems quite bogus in this case to inherit an alignment of 1
3292 -- from the parent type Character. Furthermore, if that's what the
3293 -- programmer really wanted for some odd reason, then they could
3294 -- specify the alignment they wanted.
3296 -- Furthermore we really don't want to inherit the alignment in
3297 -- the case of a specified Object_Size for a subtype, since then
3298 -- there would be no way of overriding to give a reasonable value
3299 -- (we don't have an Object_Subtype attribute). Consider:
3301 -- subtype R is new Character;
3302 -- for R'Object_Size use 16;
3304 -- If we inherit the alignment of 1, then we have an odd
3305 -- inefficient alignment for the subtype, which cannot be fixed.
3307 -- So we make the decision that if Size (or Object_Size) is given
3308 -- (and, in the case of a first subtype, the alignment is not set
3309 -- with a specific alignment clause). We reset the alignment to
3310 -- the appropriate value for the specified size. This is a nice
3311 -- simple rule to implement and document.
3313 -- There is one slight glitch, which is that a confirming size
3314 -- clause can now change the alignment, which, if we really think
3315 -- that confirming rep clauses should have no effect, is a no-no.
3317 -- type R is new Character;
3318 -- for R'Alignment use 2;
3319 -- type S is new R;
3320 -- for S'Size use Character'Size;
3322 -- Now the alignment of S is 1 instead of 2, as a result of
3323 -- applying the above rule to the confirming rep clause for S. Not
3324 -- clear this is worth worrying about. If we recorded whether a
3325 -- size clause was confirming we could avoid this, but right now
3326 -- we have no way of doing that or easily figuring it out, so we
3327 -- don't bother.
3329 -- Historical note. In versions of GNAT prior to Nov 6th, 2010, an
3330 -- odd distinction was made between inherited alignments greater
3331 -- than the computed alignment (where the larger alignment was
3332 -- inherited) and inherited alignments smaller than the computed
3333 -- alignment (where the smaller alignment was overridden). This
3334 -- was a dubious fix to get around an ACATS problem which seems
3335 -- to have disappeared anyway, and in any case, this peculiarity
3336 -- was never documented.
3338 Init_Alignment (E, A);
3340 -- If no Size (or Object_Size) was specified, then we inherited the
3341 -- object size, so we should inherit the alignment as well and not
3342 -- modify it. This takes care of cases like:
3344 -- type R is new Integer;
3345 -- for R'Alignment use 1;
3346 -- subtype S is R;
3348 -- Here we have R has a default Object_Size of 32, and a specified
3349 -- alignment of 1, and it seeems right for S to inherit both values.
3351 else
3352 null;
3353 end if;
3354 end;
3355 end Set_Elem_Alignment;
3357 ----------------------
3358 -- SO_Ref_From_Expr --
3359 ----------------------
3361 function SO_Ref_From_Expr
3362 (Expr : Node_Id;
3363 Ins_Type : Entity_Id;
3364 Vtype : Entity_Id := Empty;
3365 Make_Func : Boolean := False) return Dynamic_SO_Ref
3367 Loc : constant Source_Ptr := Sloc (Ins_Type);
3368 K : constant Entity_Id := Make_Temporary (Loc, 'K');
3369 Decl : Node_Id;
3371 Vtype_Primary_View : Entity_Id;
3373 function Check_Node_V_Ref (N : Node_Id) return Traverse_Result;
3374 -- Function used to check one node for reference to V
3376 function Has_V_Ref is new Traverse_Func (Check_Node_V_Ref);
3377 -- Function used to traverse tree to check for reference to V
3379 ----------------------
3380 -- Check_Node_V_Ref --
3381 ----------------------
3383 function Check_Node_V_Ref (N : Node_Id) return Traverse_Result is
3384 begin
3385 if Nkind (N) = N_Identifier then
3386 if Chars (N) = Vname then
3387 return Abandon;
3388 else
3389 return Skip;
3390 end if;
3392 else
3393 return OK;
3394 end if;
3395 end Check_Node_V_Ref;
3397 -- Start of processing for SO_Ref_From_Expr
3399 begin
3400 -- Case of expression is an integer literal, in this case we just
3401 -- return the value (which must always be non-negative, since size
3402 -- and offset values can never be negative).
3404 if Nkind (Expr) = N_Integer_Literal then
3405 pragma Assert (Intval (Expr) >= 0);
3406 return Intval (Expr);
3407 end if;
3409 -- Case where there is a reference to V, create function
3411 if Has_V_Ref (Expr) = Abandon then
3413 pragma Assert (Present (Vtype));
3415 -- Check whether Vtype is a view of a private type and ensure that
3416 -- we use the primary view of the type (which is denoted by its
3417 -- Etype, whether it's the type's partial or full view entity).
3418 -- This is needed to make sure that we use the same (primary) view
3419 -- of the type for all V formals, whether the current view of the
3420 -- type is the partial or full view, so that types will always
3421 -- match on calls from one size function to another.
3423 if Has_Private_Declaration (Vtype) then
3424 Vtype_Primary_View := Etype (Vtype);
3425 else
3426 Vtype_Primary_View := Vtype;
3427 end if;
3429 Set_Is_Discrim_SO_Function (K);
3431 Decl :=
3432 Make_Subprogram_Body (Loc,
3434 Specification =>
3435 Make_Function_Specification (Loc,
3436 Defining_Unit_Name => K,
3437 Parameter_Specifications => New_List (
3438 Make_Parameter_Specification (Loc,
3439 Defining_Identifier =>
3440 Make_Defining_Identifier (Loc, Chars => Vname),
3441 Parameter_Type =>
3442 New_Occurrence_Of (Vtype_Primary_View, Loc))),
3443 Result_Definition =>
3444 New_Occurrence_Of (Standard_Unsigned, Loc)),
3446 Declarations => Empty_List,
3448 Handled_Statement_Sequence =>
3449 Make_Handled_Sequence_Of_Statements (Loc,
3450 Statements => New_List (
3451 Make_Simple_Return_Statement (Loc,
3452 Expression => Expr))));
3454 -- The caller requests that the expression be encapsulated in a
3455 -- parameterless function.
3457 elsif Make_Func then
3458 Decl :=
3459 Make_Subprogram_Body (Loc,
3461 Specification =>
3462 Make_Function_Specification (Loc,
3463 Defining_Unit_Name => K,
3464 Parameter_Specifications => Empty_List,
3465 Result_Definition =>
3466 New_Occurrence_Of (Standard_Unsigned, Loc)),
3468 Declarations => Empty_List,
3470 Handled_Statement_Sequence =>
3471 Make_Handled_Sequence_Of_Statements (Loc,
3472 Statements => New_List (
3473 Make_Simple_Return_Statement (Loc, Expression => Expr))));
3475 -- No reference to V and function not requested, so create a constant
3477 else
3478 Decl :=
3479 Make_Object_Declaration (Loc,
3480 Defining_Identifier => K,
3481 Object_Definition =>
3482 New_Occurrence_Of (Standard_Unsigned, Loc),
3483 Constant_Present => True,
3484 Expression => Expr);
3485 end if;
3487 Append_Freeze_Action (Ins_Type, Decl);
3488 Analyze (Decl);
3489 return Create_Dynamic_SO_Ref (K);
3490 end SO_Ref_From_Expr;
3492 end Layout;