Daily bump.
[official-gcc.git] / gcc / ada / layout.adb
blob4373a970ec4fbbc496573daed0d10e5a62669261
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-2016, 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)) and then not Has_Alignment_Clause (E)
274 then
275 loop
276 Abits := Abits / 2;
277 exit when Esize (E) mod Abits = 0;
278 end loop;
280 Init_Alignment (E, Abits / SSU);
281 return;
282 end if;
284 -- Now the only possible approach left is to increase the Esize but we
285 -- can't do that if the size was set by a specific clause.
287 if Esize_Set then
288 Error_Msg_NE
289 ("size for& is not a multiple of alignment",
290 Size_Clause (E), E);
292 -- Otherwise we can indeed increase the size to a multiple of alignment
294 else
295 Set_Esize (E, ((Esize (E) + (Abits - 1)) / Abits) * Abits);
296 end if;
297 end Adjust_Esize_Alignment;
299 ---------------
300 -- Assoc_Add --
301 ---------------
303 function Assoc_Add
304 (Loc : Source_Ptr;
305 Left_Opnd : Node_Id;
306 Right_Opnd : Node_Id) return Node_Id
308 L : Node_Id;
309 R : Uint;
311 begin
312 -- Case of right operand is a constant
314 if Compile_Time_Known_Value (Right_Opnd) then
315 L := Left_Opnd;
316 R := Expr_Value (Right_Opnd);
318 -- Case of left operand is a constant
320 elsif Compile_Time_Known_Value (Left_Opnd) then
321 L := Right_Opnd;
322 R := Expr_Value (Left_Opnd);
324 -- Neither operand is a constant, do the addition with no optimization
326 else
327 return Make_Op_Add (Loc, Left_Opnd, Right_Opnd);
328 end if;
330 -- Case of left operand is an addition
332 if Nkind (L) = N_Op_Add then
334 -- (C1 + E) + C2 = (C1 + C2) + E
336 if Compile_Time_Known_Value (Sinfo.Left_Opnd (L)) then
337 Rewrite_Integer
338 (Sinfo.Left_Opnd (L),
339 Expr_Value (Sinfo.Left_Opnd (L)) + R);
340 return L;
342 -- (E + C1) + C2 = E + (C1 + C2)
344 elsif Compile_Time_Known_Value (Sinfo.Right_Opnd (L)) then
345 Rewrite_Integer
346 (Sinfo.Right_Opnd (L),
347 Expr_Value (Sinfo.Right_Opnd (L)) + R);
348 return L;
349 end if;
351 -- Case of left operand is a subtraction
353 elsif Nkind (L) = N_Op_Subtract then
355 -- (C1 - E) + C2 = (C1 + C2) - E
357 if Compile_Time_Known_Value (Sinfo.Left_Opnd (L)) then
358 Rewrite_Integer
359 (Sinfo.Left_Opnd (L),
360 Expr_Value (Sinfo.Left_Opnd (L)) + R);
361 return L;
363 -- (E - C1) + C2 = E - (C1 - C2)
365 -- If the type is unsigned then only do the optimization if C1 >= C2,
366 -- to avoid creating a negative literal that can't be used with the
367 -- unsigned type.
369 elsif Compile_Time_Known_Value (Sinfo.Right_Opnd (L))
370 and then (not Is_Unsigned_Type (Etype (Sinfo.Right_Opnd (L)))
371 or else Expr_Value (Sinfo.Right_Opnd (L)) >= R)
372 then
373 Rewrite_Integer
374 (Sinfo.Right_Opnd (L),
375 Expr_Value (Sinfo.Right_Opnd (L)) - R);
376 return L;
377 end if;
378 end if;
380 -- Not optimizable, do the addition
382 return Make_Op_Add (Loc, Left_Opnd, Right_Opnd);
383 end Assoc_Add;
385 --------------------
386 -- Assoc_Multiply --
387 --------------------
389 function Assoc_Multiply
390 (Loc : Source_Ptr;
391 Left_Opnd : Node_Id;
392 Right_Opnd : Node_Id) return Node_Id
394 L : Node_Id;
395 R : Uint;
397 begin
398 -- Case of right operand is a constant
400 if Compile_Time_Known_Value (Right_Opnd) then
401 L := Left_Opnd;
402 R := Expr_Value (Right_Opnd);
404 -- Case of left operand is a constant
406 elsif Compile_Time_Known_Value (Left_Opnd) then
407 L := Right_Opnd;
408 R := Expr_Value (Left_Opnd);
410 -- Neither operand is a constant, do the multiply with no optimization
412 else
413 return Make_Op_Multiply (Loc, Left_Opnd, Right_Opnd);
414 end if;
416 -- Case of left operand is an multiplication
418 if Nkind (L) = N_Op_Multiply then
420 -- (C1 * E) * C2 = (C1 * C2) + E
422 if Compile_Time_Known_Value (Sinfo.Left_Opnd (L)) then
423 Rewrite_Integer
424 (Sinfo.Left_Opnd (L),
425 Expr_Value (Sinfo.Left_Opnd (L)) * R);
426 return L;
428 -- (E * C1) * C2 = E * (C1 * C2)
430 elsif Compile_Time_Known_Value (Sinfo.Right_Opnd (L)) then
431 Rewrite_Integer
432 (Sinfo.Right_Opnd (L),
433 Expr_Value (Sinfo.Right_Opnd (L)) * R);
434 return L;
435 end if;
436 end if;
438 -- Not optimizable, do the multiplication
440 return Make_Op_Multiply (Loc, Left_Opnd, Right_Opnd);
441 end Assoc_Multiply;
443 --------------------
444 -- Assoc_Subtract --
445 --------------------
447 function Assoc_Subtract
448 (Loc : Source_Ptr;
449 Left_Opnd : Node_Id;
450 Right_Opnd : Node_Id) return Node_Id
452 L : Node_Id;
453 R : Uint;
455 begin
456 -- Case of right operand is a constant
458 if Compile_Time_Known_Value (Right_Opnd) then
459 L := Left_Opnd;
460 R := Expr_Value (Right_Opnd);
462 -- Right operand is a constant, do the subtract with no optimization
464 else
465 return Make_Op_Subtract (Loc, Left_Opnd, Right_Opnd);
466 end if;
468 -- Case of left operand is an addition
470 if Nkind (L) = N_Op_Add then
472 -- (C1 + E) - C2 = (C1 - C2) + E
474 if Compile_Time_Known_Value (Sinfo.Left_Opnd (L)) then
475 Rewrite_Integer
476 (Sinfo.Left_Opnd (L),
477 Expr_Value (Sinfo.Left_Opnd (L)) - R);
478 return L;
480 -- (E + C1) - C2 = E + (C1 - C2)
482 elsif Compile_Time_Known_Value (Sinfo.Right_Opnd (L)) then
483 Rewrite_Integer
484 (Sinfo.Right_Opnd (L),
485 Expr_Value (Sinfo.Right_Opnd (L)) - R);
486 return L;
487 end if;
489 -- Case of left operand is a subtraction
491 elsif Nkind (L) = N_Op_Subtract then
493 -- (C1 - E) - C2 = (C1 - C2) + E
495 if Compile_Time_Known_Value (Sinfo.Left_Opnd (L)) then
496 Rewrite_Integer
497 (Sinfo.Left_Opnd (L),
498 Expr_Value (Sinfo.Left_Opnd (L)) + R);
499 return L;
501 -- (E - C1) - C2 = E - (C1 + C2)
503 elsif Compile_Time_Known_Value (Sinfo.Right_Opnd (L)) then
504 Rewrite_Integer
505 (Sinfo.Right_Opnd (L),
506 Expr_Value (Sinfo.Right_Opnd (L)) + R);
507 return L;
508 end if;
509 end if;
511 -- Not optimizable, do the subtraction
513 return Make_Op_Subtract (Loc, Left_Opnd, Right_Opnd);
514 end Assoc_Subtract;
516 ----------------
517 -- Bits_To_SU --
518 ----------------
520 function Bits_To_SU (N : Node_Id) return Node_Id is
521 begin
522 if Nkind (N) = N_Integer_Literal then
523 Set_Intval (N, (Intval (N) + (SSU - 1)) / SSU);
524 end if;
526 return N;
527 end Bits_To_SU;
529 --------------------
530 -- Compute_Length --
531 --------------------
533 function Compute_Length (Lo : Node_Id; Hi : Node_Id) return Node_Id is
534 Loc : constant Source_Ptr := Sloc (Lo);
535 Typ : constant Entity_Id := Etype (Lo);
536 Lo_Op : Node_Id;
537 Hi_Op : Node_Id;
538 Lo_Dim : Uint;
539 Hi_Dim : Uint;
541 begin
542 -- If the bounds are First and Last attributes for the same dimension
543 -- and both have prefixes that denotes the same entity, then we create
544 -- and return a Length attribute. This may allow the back end to
545 -- generate better code in cases where it already has the length.
547 if Nkind (Lo) = N_Attribute_Reference
548 and then Attribute_Name (Lo) = Name_First
549 and then Nkind (Hi) = N_Attribute_Reference
550 and then Attribute_Name (Hi) = Name_Last
551 and then Is_Entity_Name (Prefix (Lo))
552 and then Is_Entity_Name (Prefix (Hi))
553 and then Entity (Prefix (Lo)) = Entity (Prefix (Hi))
554 then
555 Lo_Dim := Uint_1;
556 Hi_Dim := Uint_1;
558 if Present (First (Expressions (Lo))) then
559 Lo_Dim := Expr_Value (First (Expressions (Lo)));
560 end if;
562 if Present (First (Expressions (Hi))) then
563 Hi_Dim := Expr_Value (First (Expressions (Hi)));
564 end if;
566 if Lo_Dim = Hi_Dim then
567 return
568 Make_Attribute_Reference (Loc,
569 Prefix => New_Occurrence_Of
570 (Entity (Prefix (Lo)), Loc),
571 Attribute_Name => Name_Length,
572 Expressions => New_List
573 (Make_Integer_Literal (Loc, Lo_Dim)));
574 end if;
575 end if;
577 Lo_Op := New_Copy_Tree (Lo);
578 Hi_Op := New_Copy_Tree (Hi);
580 -- If type is enumeration type, then use Pos attribute to convert
581 -- to integer type for which subtraction is a permitted operation.
583 if Is_Enumeration_Type (Typ) then
584 Lo_Op :=
585 Make_Attribute_Reference (Loc,
586 Prefix => New_Occurrence_Of (Typ, Loc),
587 Attribute_Name => Name_Pos,
588 Expressions => New_List (Lo_Op));
590 Hi_Op :=
591 Make_Attribute_Reference (Loc,
592 Prefix => New_Occurrence_Of (Typ, Loc),
593 Attribute_Name => Name_Pos,
594 Expressions => New_List (Hi_Op));
595 end if;
597 return
598 Assoc_Add (Loc,
599 Left_Opnd =>
600 Assoc_Subtract (Loc,
601 Left_Opnd => Hi_Op,
602 Right_Opnd => Lo_Op),
603 Right_Opnd => Make_Integer_Literal (Loc, 1));
604 end Compute_Length;
606 ----------------------
607 -- Expr_From_SO_Ref --
608 ----------------------
610 function Expr_From_SO_Ref
611 (Loc : Source_Ptr;
612 D : SO_Ref;
613 Comp : Entity_Id := Empty) return Node_Id
615 Ent : Entity_Id;
617 begin
618 if Is_Dynamic_SO_Ref (D) then
619 Ent := Get_Dynamic_SO_Entity (D);
621 if Is_Discrim_SO_Function (Ent) then
623 -- If a component is passed in whose type matches the type of
624 -- the function formal, then select that component from the "V"
625 -- parameter rather than passing "V" directly.
627 if Present (Comp)
628 and then Base_Type (Etype (Comp)) =
629 Base_Type (Etype (First_Formal (Ent)))
630 then
631 return
632 Make_Function_Call (Loc,
633 Name => New_Occurrence_Of (Ent, Loc),
634 Parameter_Associations => New_List (
635 Make_Selected_Component (Loc,
636 Prefix => Make_Identifier (Loc, Vname),
637 Selector_Name => New_Occurrence_Of (Comp, Loc))));
639 else
640 return
641 Make_Function_Call (Loc,
642 Name => New_Occurrence_Of (Ent, Loc),
643 Parameter_Associations => New_List (
644 Make_Identifier (Loc, Vname)));
645 end if;
647 else
648 return New_Occurrence_Of (Ent, Loc);
649 end if;
651 else
652 return Make_Integer_Literal (Loc, D);
653 end if;
654 end Expr_From_SO_Ref;
656 ---------------------
657 -- Get_Max_SU_Size --
658 ---------------------
660 function Get_Max_SU_Size (E : Entity_Id) return Node_Id is
661 Loc : constant Source_Ptr := Sloc (E);
662 Indx : Node_Id;
663 Ityp : Entity_Id;
664 Lo : Node_Id;
665 Hi : Node_Id;
666 S : Uint;
667 Len : Node_Id;
669 type Val_Status_Type is (Const, Dynamic);
671 type Val_Type (Status : Val_Status_Type := Const) is record
672 case Status is
673 when Const => Val : Uint;
674 when Dynamic => Nod : Node_Id;
675 end case;
676 end record;
677 -- Shows the status of the value so far. Const means that the value is
678 -- constant, and Val is the current constant value. Dynamic means that
679 -- the value is dynamic, and in this case Nod is the Node_Id of the
680 -- expression to compute the value.
682 Size : Val_Type;
683 -- Calculated value so far if Size.Status = Const,
684 -- or expression value so far if Size.Status = Dynamic.
686 SU_Convert_Required : Boolean := False;
687 -- This is set to True if the final result must be converted from bits
688 -- to storage units (rounding up to a storage unit boundary).
690 -----------------------
691 -- Local Subprograms --
692 -----------------------
694 procedure Max_Discrim (N : in out Node_Id);
695 -- If the node N represents a discriminant, replace it by the maximum
696 -- value of the discriminant.
698 procedure Min_Discrim (N : in out Node_Id);
699 -- If the node N represents a discriminant, replace it by the minimum
700 -- value of the discriminant.
702 -----------------
703 -- Max_Discrim --
704 -----------------
706 procedure Max_Discrim (N : in out Node_Id) is
707 begin
708 if Nkind (N) = N_Identifier
709 and then Ekind (Entity (N)) = E_Discriminant
710 then
711 N := Type_High_Bound (Etype (N));
712 end if;
713 end Max_Discrim;
715 -----------------
716 -- Min_Discrim --
717 -----------------
719 procedure Min_Discrim (N : in out Node_Id) is
720 begin
721 if Nkind (N) = N_Identifier
722 and then Ekind (Entity (N)) = E_Discriminant
723 then
724 N := Type_Low_Bound (Etype (N));
725 end if;
726 end Min_Discrim;
728 -- Start of processing for Get_Max_SU_Size
730 begin
731 pragma Assert (Size_Depends_On_Discriminant (E));
733 -- Initialize status from component size
735 if Known_Static_Component_Size (E) then
736 Size := (Const, Component_Size (E));
738 else
739 Size := (Dynamic, Expr_From_SO_Ref (Loc, Component_Size (E)));
740 end if;
742 -- Loop through indexes
744 Indx := First_Index (E);
745 while Present (Indx) loop
746 Ityp := Etype (Indx);
747 Lo := Type_Low_Bound (Ityp);
748 Hi := Type_High_Bound (Ityp);
750 Min_Discrim (Lo);
751 Max_Discrim (Hi);
753 -- Value of the current subscript range is statically known
755 if Compile_Time_Known_Value (Lo)
756 and then
757 Compile_Time_Known_Value (Hi)
758 then
759 S := Expr_Value (Hi) - Expr_Value (Lo) + 1;
761 -- If known flat bound, entire size of array is zero
763 if S <= 0 then
764 return Make_Integer_Literal (Loc, 0);
765 end if;
767 -- Current value is constant, evolve value
769 if Size.Status = Const then
770 Size.Val := Size.Val * S;
772 -- Current value is dynamic
774 else
775 -- An interesting little optimization, if we have a pending
776 -- conversion from bits to storage units, and the current
777 -- length is a multiple of the storage unit size, then we
778 -- can take the factor out here statically, avoiding some
779 -- extra dynamic computations at the end.
781 if SU_Convert_Required and then S mod SSU = 0 then
782 S := S / SSU;
783 SU_Convert_Required := False;
784 end if;
786 Size.Nod :=
787 Assoc_Multiply (Loc,
788 Left_Opnd => Size.Nod,
789 Right_Opnd =>
790 Make_Integer_Literal (Loc, Intval => S));
791 end if;
793 -- Value of the current subscript range is dynamic
795 else
796 -- If the current size value is constant, then here is where we
797 -- make a transition to dynamic values, which are always stored
798 -- in storage units, However, we do not want to convert to SU's
799 -- too soon, consider the case of a packed array of single bits,
800 -- we want to do the SU conversion after computing the size in
801 -- this case.
803 if Size.Status = Const then
805 -- If the current value is a multiple of the storage unit,
806 -- then most certainly we can do the conversion now, simply
807 -- by dividing the current value by the storage unit value.
808 -- If this works, we set SU_Convert_Required to False.
810 if Size.Val mod SSU = 0 then
812 Size :=
813 (Dynamic, Make_Integer_Literal (Loc, Size.Val / SSU));
814 SU_Convert_Required := False;
816 -- Otherwise, we go ahead and convert the value in bits, and
817 -- set SU_Convert_Required to True to ensure that the final
818 -- value is indeed properly converted.
820 else
821 Size := (Dynamic, Make_Integer_Literal (Loc, Size.Val));
822 SU_Convert_Required := True;
823 end if;
824 end if;
826 -- Length is hi-lo+1
828 Len := Compute_Length (Lo, Hi);
830 -- Check possible range of Len
832 declare
833 OK : Boolean;
834 LLo : Uint;
835 LHi : Uint;
836 pragma Warnings (Off, LHi);
838 begin
839 Set_Parent (Len, E);
840 Determine_Range (Len, OK, LLo, LHi);
842 Len := Convert_To (Standard_Unsigned, Len);
844 -- If we cannot verify that range cannot be super-flat, we need
845 -- a max with zero, since length must be non-negative.
847 if not OK or else LLo < 0 then
848 Len :=
849 Make_Attribute_Reference (Loc,
850 Prefix =>
851 New_Occurrence_Of (Standard_Unsigned, Loc),
852 Attribute_Name => Name_Max,
853 Expressions => New_List (
854 Make_Integer_Literal (Loc, 0),
855 Len));
856 end if;
857 end;
858 end if;
860 Next_Index (Indx);
861 end loop;
863 -- Here after processing all bounds to set sizes. If the value is a
864 -- constant, then it is bits, so we convert to storage units.
866 if Size.Status = Const then
867 return Bits_To_SU (Make_Integer_Literal (Loc, Size.Val));
869 -- Case where the value is dynamic
871 else
872 -- Do convert from bits to SU's if needed
874 if SU_Convert_Required then
876 -- The expression required is (Size.Nod + SU - 1) / SU
878 Size.Nod :=
879 Make_Op_Divide (Loc,
880 Left_Opnd =>
881 Make_Op_Add (Loc,
882 Left_Opnd => Size.Nod,
883 Right_Opnd => Make_Integer_Literal (Loc, SSU - 1)),
884 Right_Opnd => Make_Integer_Literal (Loc, SSU));
885 end if;
887 return Size.Nod;
888 end if;
889 end Get_Max_SU_Size;
891 -----------------------
892 -- Layout_Array_Type --
893 -----------------------
895 procedure Layout_Array_Type (E : Entity_Id) is
896 Loc : constant Source_Ptr := Sloc (E);
897 Ctyp : constant Entity_Id := Component_Type (E);
898 Indx : Node_Id;
899 Ityp : Entity_Id;
900 Lo : Node_Id;
901 Hi : Node_Id;
902 S : Uint;
903 Len : Node_Id;
905 Insert_Typ : Entity_Id;
906 -- This is the type with which any generated constants or functions
907 -- will be associated (i.e. inserted into the freeze actions). This
908 -- is normally the type being laid out. The exception occurs when
909 -- we are laying out Itype's which are local to a record type, and
910 -- whose scope is this record type. Such types do not have freeze
911 -- nodes (because we have no place to put them).
913 ------------------------------------
914 -- How An Array Type is Laid Out --
915 ------------------------------------
917 -- Here is what goes on. We need to multiply the component size of the
918 -- array (which has already been set) by the length of each of the
919 -- indexes. If all these values are known at compile time, then the
920 -- resulting size of the array is the appropriate constant value.
922 -- If the component size or at least one bound is dynamic (but no
923 -- discriminants are present), then the size will be computed as an
924 -- expression that calculates the proper size.
926 -- If there is at least one discriminant bound, then the size is also
927 -- computed as an expression, but this expression contains discriminant
928 -- values which are obtained by selecting from a function parameter, and
929 -- the size is given by a function that is passed the variant record in
930 -- question, and whose body is the expression.
932 type Val_Status_Type is (Const, Dynamic, Discrim);
934 type Val_Type (Status : Val_Status_Type := Const) is record
935 case Status is
936 when Const =>
937 Val : Uint;
938 -- Calculated value so far if Val_Status = Const
940 when Discrim
941 | Dynamic
943 Nod : Node_Id;
944 -- Expression value so far if Val_Status /= Const
945 end case;
946 end record;
947 -- Records the value or expression computed so far. Const means that
948 -- the value is constant, and Val is the current constant value.
949 -- Dynamic means that the value is dynamic, and in this case Nod is
950 -- the Node_Id of the expression to compute the value, and Discrim
951 -- means that at least one bound is a discriminant, in which case Nod
952 -- is the expression so far (which will be the body of the function).
954 Size : Val_Type;
955 -- Value of size computed so far. See comments above
957 Vtyp : Entity_Id := Empty;
958 -- Variant record type for the formal parameter of the discriminant
959 -- function V if Status = Discrim.
961 SU_Convert_Required : Boolean := False;
962 -- This is set to True if the final result must be converted from
963 -- bits to storage units (rounding up to a storage unit boundary).
965 Storage_Divisor : Uint := UI_From_Int (SSU);
966 -- This is the amount that a nonstatic computed size will be divided
967 -- by to convert it from bits to storage units. This is normally
968 -- equal to SSU, but can be reduced in the case of packed components
969 -- that fit evenly into a storage unit.
971 Make_Size_Function : Boolean := False;
972 -- Indicates whether to request that SO_Ref_From_Expr should
973 -- encapsulate the array size expression in a function.
975 procedure Discrimify (N : in out Node_Id);
976 -- If N represents a discriminant, then the Size.Status is set to
977 -- Discrim, and Vtyp is set. The parameter N is replaced with the
978 -- proper expression to extract the discriminant value from V.
980 ----------------
981 -- Discrimify --
982 ----------------
984 procedure Discrimify (N : in out Node_Id) is
985 Decl : Node_Id;
986 Typ : Entity_Id;
988 begin
989 if Nkind (N) = N_Identifier
990 and then Ekind (Entity (N)) = E_Discriminant
991 then
992 Set_Size_Depends_On_Discriminant (E);
994 if Size.Status /= Discrim then
995 Decl := Parent (Parent (Entity (N)));
996 Size := (Discrim, Size.Nod);
997 Vtyp := Defining_Identifier (Decl);
998 end if;
1000 Typ := Etype (N);
1002 N :=
1003 Make_Selected_Component (Loc,
1004 Prefix => Make_Identifier (Loc, Vname),
1005 Selector_Name => New_Occurrence_Of (Entity (N), Loc));
1007 -- Set the Etype attributes of the selected name and its prefix.
1008 -- Analyze_And_Resolve can't be called here because the Vname
1009 -- entity denoted by the prefix will not yet exist (it's created
1010 -- by SO_Ref_From_Expr, called at the end of Layout_Array_Type).
1012 Set_Etype (Prefix (N), Vtyp);
1013 Set_Etype (N, Typ);
1014 end if;
1015 end Discrimify;
1017 -- Start of processing for Layout_Array_Type
1019 begin
1020 -- Default alignment is component alignment
1022 if Unknown_Alignment (E) then
1023 Set_Alignment (E, Alignment (Ctyp));
1024 end if;
1026 -- Calculate proper type for insertions
1028 if Is_Record_Type (Underlying_Type (Scope (E))) then
1029 Insert_Typ := Underlying_Type (Scope (E));
1030 else
1031 Insert_Typ := E;
1032 end if;
1034 -- If the component type is a generic formal type then there's no point
1035 -- in determining a size for the array type.
1037 if Is_Generic_Type (Ctyp) then
1038 return;
1039 end if;
1041 -- Deal with component size if base type
1043 if Ekind (E) = E_Array_Type then
1045 -- Cannot do anything if Esize of component type unknown
1047 if Unknown_Esize (Ctyp) then
1048 return;
1049 end if;
1051 -- Set component size if not set already
1053 if Unknown_Component_Size (E) then
1054 Set_Component_Size (E, Esize (Ctyp));
1055 end if;
1056 end if;
1058 -- (RM 13.3 (48)) says that the size of an unconstrained array
1059 -- is implementation defined. We choose to leave it as Unknown
1060 -- here, and the actual behavior is determined by the back end.
1062 if not Is_Constrained (E) then
1063 return;
1064 end if;
1066 -- Initialize status from component size
1068 if Known_Static_Component_Size (E) then
1069 Size := (Const, Component_Size (E));
1071 else
1072 Size := (Dynamic, Expr_From_SO_Ref (Loc, Component_Size (E)));
1073 end if;
1075 -- Loop to process array indexes
1077 Indx := First_Index (E);
1078 while Present (Indx) loop
1079 Ityp := Etype (Indx);
1081 -- If an index of the array is a generic formal type then there is
1082 -- no point in determining a size for the array type.
1084 if Is_Generic_Type (Ityp) then
1085 return;
1086 end if;
1088 Lo := Type_Low_Bound (Ityp);
1089 Hi := Type_High_Bound (Ityp);
1091 -- Value of the current subscript range is statically known
1093 if Compile_Time_Known_Value (Lo)
1094 and then
1095 Compile_Time_Known_Value (Hi)
1096 then
1097 S := Expr_Value (Hi) - Expr_Value (Lo) + 1;
1099 -- If known flat bound, entire size of array is zero
1101 if S <= 0 then
1102 Set_Esize (E, Uint_0);
1103 Set_RM_Size (E, Uint_0);
1104 return;
1105 end if;
1107 -- If constant, evolve value
1109 if Size.Status = Const then
1110 Size.Val := Size.Val * S;
1112 -- Current value is dynamic
1114 else
1115 -- An interesting little optimization, if we have a pending
1116 -- conversion from bits to storage units, and the current
1117 -- length is a multiple of the storage unit size, then we
1118 -- can take the factor out here statically, avoiding some
1119 -- extra dynamic computations at the end.
1121 if SU_Convert_Required and then S mod SSU = 0 then
1122 S := S / SSU;
1123 SU_Convert_Required := False;
1124 end if;
1126 -- Now go ahead and evolve the expression
1128 Size.Nod :=
1129 Assoc_Multiply (Loc,
1130 Left_Opnd => Size.Nod,
1131 Right_Opnd =>
1132 Make_Integer_Literal (Loc, Intval => S));
1133 end if;
1135 -- Value of the current subscript range is dynamic
1137 else
1138 -- If the current size value is constant, then here is where we
1139 -- make a transition to dynamic values, which are always stored
1140 -- in storage units, However, we do not want to convert to SU's
1141 -- too soon, consider the case of a packed array of single bits,
1142 -- we want to do the SU conversion after computing the size in
1143 -- this case.
1145 if Size.Status = Const then
1147 -- If the current value is a multiple of the storage unit,
1148 -- then most certainly we can do the conversion now, simply
1149 -- by dividing the current value by the storage unit value.
1150 -- If this works, we set SU_Convert_Required to False.
1152 if Size.Val mod SSU = 0 then
1153 Size :=
1154 (Dynamic, Make_Integer_Literal (Loc, Size.Val / SSU));
1155 SU_Convert_Required := False;
1157 -- If the current value is a factor of the storage unit, then
1158 -- we can use a value of one for the size and reduce the
1159 -- strength of the later division.
1161 elsif SSU mod Size.Val = 0 then
1162 Storage_Divisor := SSU / Size.Val;
1163 Size := (Dynamic, Make_Integer_Literal (Loc, Uint_1));
1164 SU_Convert_Required := True;
1166 -- Otherwise, we go ahead and convert the value in bits, and
1167 -- set SU_Convert_Required to True to ensure that the final
1168 -- value is indeed properly converted.
1170 else
1171 Size := (Dynamic, Make_Integer_Literal (Loc, Size.Val));
1172 SU_Convert_Required := True;
1173 end if;
1174 end if;
1176 Discrimify (Lo);
1177 Discrimify (Hi);
1179 -- Length is hi-lo+1
1181 Len := Compute_Length (Lo, Hi);
1183 -- If Len isn't a Length attribute, then its range needs to be
1184 -- checked a possible Max with zero needs to be computed.
1186 if Nkind (Len) /= N_Attribute_Reference
1187 or else Attribute_Name (Len) /= Name_Length
1188 then
1189 declare
1190 OK : Boolean;
1191 LLo : Uint;
1192 LHi : Uint;
1194 begin
1195 -- Check possible range of Len
1197 Set_Parent (Len, E);
1198 Determine_Range (Len, OK, LLo, LHi);
1200 Len := Convert_To (Standard_Unsigned, Len);
1202 -- If range definitely flat or superflat, result size is 0
1204 if OK and then LHi <= 0 then
1205 Set_Esize (E, Uint_0);
1206 Set_RM_Size (E, Uint_0);
1207 return;
1208 end if;
1210 -- If we cannot verify that range cannot be super-flat, we
1211 -- need a max with zero, since length cannot be negative.
1213 if not OK or else LLo < 0 then
1214 Len :=
1215 Make_Attribute_Reference (Loc,
1216 Prefix =>
1217 New_Occurrence_Of (Standard_Unsigned, Loc),
1218 Attribute_Name => Name_Max,
1219 Expressions => New_List (
1220 Make_Integer_Literal (Loc, 0),
1221 Len));
1222 end if;
1223 end;
1224 end if;
1226 -- At this stage, Len has the expression for the length
1228 Size.Nod :=
1229 Assoc_Multiply (Loc,
1230 Left_Opnd => Size.Nod,
1231 Right_Opnd => Len);
1232 end if;
1234 Next_Index (Indx);
1235 end loop;
1237 -- Here after processing all bounds to set sizes. If the value is a
1238 -- constant, then it is bits, and the only thing we need to do is to
1239 -- check against explicit given size and do alignment adjust.
1241 if Size.Status = Const then
1242 Set_And_Check_Static_Size (E, Size.Val, Size.Val);
1243 Adjust_Esize_Alignment (E);
1245 -- Case where the value is dynamic
1247 else
1248 -- Do convert from bits to SU's if needed
1250 if SU_Convert_Required then
1252 -- The expression required is:
1253 -- (Size.Nod + Storage_Divisor - 1) / Storage_Divisor
1255 Size.Nod :=
1256 Make_Op_Divide (Loc,
1257 Left_Opnd =>
1258 Make_Op_Add (Loc,
1259 Left_Opnd => Size.Nod,
1260 Right_Opnd => Make_Integer_Literal
1261 (Loc, Storage_Divisor - 1)),
1262 Right_Opnd => Make_Integer_Literal (Loc, Storage_Divisor));
1263 end if;
1265 -- If the array entity is not declared at the library level and its
1266 -- not nested within a subprogram that is marked for inlining, then
1267 -- we request that the size expression be encapsulated in a function.
1268 -- Since this expression is not needed in most cases, we prefer not
1269 -- to incur the overhead of the computation on calls to the enclosing
1270 -- subprogram except for subprograms that require the size.
1272 if not Is_Library_Level_Entity (E) then
1273 Make_Size_Function := True;
1275 declare
1276 Parent_Subp : Entity_Id := Enclosing_Subprogram (E);
1278 begin
1279 while Present (Parent_Subp) loop
1280 if Is_Inlined (Parent_Subp) then
1281 Make_Size_Function := False;
1282 exit;
1283 end if;
1285 Parent_Subp := Enclosing_Subprogram (Parent_Subp);
1286 end loop;
1287 end;
1288 end if;
1290 -- Now set the dynamic size (the Value_Size is always the same as the
1291 -- Object_Size for arrays whose length is dynamic).
1293 -- ??? If Size.Status = Dynamic, Vtyp will not have been set.
1294 -- The added initialization sets it to Empty now, but is this
1295 -- correct?
1297 Set_Esize
1299 SO_Ref_From_Expr
1300 (Size.Nod, Insert_Typ, Vtyp, Make_Func => Make_Size_Function));
1301 Set_RM_Size (E, Esize (E));
1302 end if;
1303 end Layout_Array_Type;
1305 ------------------------------------------
1306 -- Compute_Size_Depends_On_Discriminant --
1307 ------------------------------------------
1309 procedure Compute_Size_Depends_On_Discriminant (E : Entity_Id) is
1310 Indx : Node_Id;
1311 Ityp : Entity_Id;
1312 Lo : Node_Id;
1313 Hi : Node_Id;
1314 Res : Boolean := False;
1316 begin
1317 -- Loop to process array indexes
1319 Indx := First_Index (E);
1320 while Present (Indx) loop
1321 Ityp := Etype (Indx);
1323 -- If an index of the array is a generic formal type then there is
1324 -- no point in determining a size for the array type.
1326 if Is_Generic_Type (Ityp) then
1327 return;
1328 end if;
1330 Lo := Type_Low_Bound (Ityp);
1331 Hi := Type_High_Bound (Ityp);
1333 if (Nkind (Lo) = N_Identifier
1334 and then Ekind (Entity (Lo)) = E_Discriminant)
1335 or else
1336 (Nkind (Hi) = N_Identifier
1337 and then Ekind (Entity (Hi)) = E_Discriminant)
1338 then
1339 Res := True;
1340 end if;
1342 Next_Index (Indx);
1343 end loop;
1345 if Res then
1346 Set_Size_Depends_On_Discriminant (E);
1347 end if;
1348 end Compute_Size_Depends_On_Discriminant;
1350 -------------------
1351 -- Layout_Object --
1352 -------------------
1354 procedure Layout_Object (E : Entity_Id) is
1355 T : constant Entity_Id := Etype (E);
1357 begin
1358 -- Nothing to do if backend does layout
1360 if not Frontend_Layout_On_Target then
1361 return;
1362 end if;
1364 -- Set size if not set for object and known for type. Use the RM_Size if
1365 -- that is known for the type and Esize is not.
1367 if Unknown_Esize (E) then
1368 if Known_Esize (T) then
1369 Set_Esize (E, Esize (T));
1371 elsif Known_RM_Size (T) then
1372 Set_Esize (E, RM_Size (T));
1373 end if;
1374 end if;
1376 -- Set alignment from type if unknown and type alignment known
1378 if Unknown_Alignment (E) and then Known_Alignment (T) then
1379 Set_Alignment (E, Alignment (T));
1380 end if;
1382 -- Make sure size and alignment are consistent
1384 Adjust_Esize_Alignment (E);
1386 -- Final adjustment, if we don't know the alignment, and the Esize was
1387 -- not set by an explicit Object_Size attribute clause, then we reset
1388 -- the Esize to unknown, since we really don't know it.
1390 if Unknown_Alignment (E) and then not Has_Size_Clause (E) then
1391 Set_Esize (E, Uint_0);
1392 end if;
1393 end Layout_Object;
1395 ------------------------
1396 -- Layout_Record_Type --
1397 ------------------------
1399 procedure Layout_Record_Type (E : Entity_Id) is
1400 Loc : constant Source_Ptr := Sloc (E);
1401 Decl : Node_Id;
1403 Comp : Entity_Id;
1404 -- Current component being laid out
1406 Prev_Comp : Entity_Id;
1407 -- Previous laid out component
1409 procedure Get_Next_Component_Location
1410 (Prev_Comp : Entity_Id;
1411 Align : Uint;
1412 New_Npos : out SO_Ref;
1413 New_Fbit : out SO_Ref;
1414 New_NPMax : out SO_Ref;
1415 Force_SU : Boolean);
1416 -- Given the previous component in Prev_Comp, which is already laid
1417 -- out, and the alignment of the following component, lays out the
1418 -- following component, and returns its starting position in New_Npos
1419 -- (Normalized_Position value), New_Fbit (Normalized_First_Bit value),
1420 -- and New_NPMax (Normalized_Position_Max value). If Prev_Comp is empty
1421 -- (no previous component is present), then New_Npos, New_Fbit and
1422 -- New_NPMax are all set to zero on return. This procedure is also
1423 -- used to compute the size of a record or variant by giving it the
1424 -- last component, and the record alignment. Force_SU is used to force
1425 -- the new component location to be aligned on a storage unit boundary,
1426 -- even in a packed record, False means that the new position does not
1427 -- need to be bumped to a storage unit boundary, True means a storage
1428 -- unit boundary is always required.
1430 procedure Layout_Component (Comp : Entity_Id; Prev_Comp : Entity_Id);
1431 -- Lays out component Comp, given Prev_Comp, the previously laid-out
1432 -- component (Prev_Comp = Empty if no components laid out yet). The
1433 -- alignment of the record itself is also updated if needed. Both
1434 -- Comp and Prev_Comp can be either components or discriminants.
1436 procedure Layout_Components
1437 (From : Entity_Id;
1438 To : Entity_Id;
1439 Esiz : out SO_Ref;
1440 RM_Siz : out SO_Ref);
1441 -- This procedure lays out the components of the given component list
1442 -- which contains the components starting with From and ending with To.
1443 -- The Next_Entity chain is used to traverse the components. On entry,
1444 -- Prev_Comp is set to the component preceding the list, so that the
1445 -- list is laid out after this component. Prev_Comp is set to Empty if
1446 -- the component list is to be laid out starting at the start of the
1447 -- record. On return, the components are all laid out, and Prev_Comp is
1448 -- set to the last laid out component. On return, Esiz is set to the
1449 -- resulting Object_Size value, which is the length of the record up
1450 -- to and including the last laid out entity. For Esiz, the value is
1451 -- adjusted to match the alignment of the record. RM_Siz is similarly
1452 -- set to the resulting Value_Size value, which is the same length, but
1453 -- not adjusted to meet the alignment. Note that in the case of variant
1454 -- records, Esiz represents the maximum size.
1456 procedure Layout_Non_Variant_Record;
1457 -- Procedure called to lay out a non-variant record type or subtype
1459 procedure Layout_Variant_Record;
1460 -- Procedure called to lay out a variant record type. Decl is set to the
1461 -- full type declaration for the variant record.
1463 ---------------------------------
1464 -- Get_Next_Component_Location --
1465 ---------------------------------
1467 procedure Get_Next_Component_Location
1468 (Prev_Comp : Entity_Id;
1469 Align : Uint;
1470 New_Npos : out SO_Ref;
1471 New_Fbit : out SO_Ref;
1472 New_NPMax : out SO_Ref;
1473 Force_SU : Boolean)
1475 begin
1476 -- No previous component, return zero position
1478 if No (Prev_Comp) then
1479 New_Npos := Uint_0;
1480 New_Fbit := Uint_0;
1481 New_NPMax := Uint_0;
1482 return;
1483 end if;
1485 -- Here we have a previous component
1487 declare
1488 Loc : constant Source_Ptr := Sloc (Prev_Comp);
1490 Old_Npos : constant SO_Ref := Normalized_Position (Prev_Comp);
1491 Old_Fbit : constant SO_Ref := Normalized_First_Bit (Prev_Comp);
1492 Old_NPMax : constant SO_Ref := Normalized_Position_Max (Prev_Comp);
1493 Old_Esiz : constant SO_Ref := Esize (Prev_Comp);
1495 Old_Maxsz : Node_Id;
1496 -- Expression representing maximum size of previous component
1498 begin
1499 -- Case where previous field had a dynamic size
1501 if Is_Dynamic_SO_Ref (Esize (Prev_Comp)) then
1503 -- If the previous field had a dynamic length, then it is
1504 -- required to occupy an integral number of storage units,
1505 -- and start on a storage unit boundary. This means that
1506 -- the Normalized_First_Bit value is zero in the previous
1507 -- component, and the new value is also set to zero.
1509 New_Fbit := Uint_0;
1511 -- In this case, the new position is given by an expression
1512 -- that is the sum of old normalized position and old size.
1514 New_Npos :=
1515 SO_Ref_From_Expr
1516 (Assoc_Add (Loc,
1517 Left_Opnd =>
1518 Expr_From_SO_Ref (Loc, Old_Npos),
1519 Right_Opnd =>
1520 Expr_From_SO_Ref (Loc, Old_Esiz, Prev_Comp)),
1521 Ins_Type => E,
1522 Vtype => E);
1524 -- Get maximum size of previous component
1526 if Size_Depends_On_Discriminant (Etype (Prev_Comp)) then
1527 Old_Maxsz := Get_Max_SU_Size (Etype (Prev_Comp));
1528 else
1529 Old_Maxsz := Expr_From_SO_Ref (Loc, Old_Esiz, Prev_Comp);
1530 end if;
1532 -- Now we can compute the new max position. If the max size
1533 -- is static and the old position is static, then we can
1534 -- compute the new position statically.
1536 if Nkind (Old_Maxsz) = N_Integer_Literal
1537 and then Known_Static_Normalized_Position_Max (Prev_Comp)
1538 then
1539 New_NPMax := Old_NPMax + Intval (Old_Maxsz);
1541 -- Otherwise new max position is dynamic
1543 else
1544 New_NPMax :=
1545 SO_Ref_From_Expr
1546 (Assoc_Add (Loc,
1547 Left_Opnd => Expr_From_SO_Ref (Loc, Old_NPMax),
1548 Right_Opnd => Old_Maxsz),
1549 Ins_Type => E,
1550 Vtype => E);
1551 end if;
1553 -- Previous field has known static Esize
1555 else
1556 New_Fbit := Old_Fbit + Old_Esiz;
1558 -- Bump New_Fbit to storage unit boundary if required
1560 if New_Fbit /= 0 and then Force_SU then
1561 New_Fbit := (New_Fbit + SSU - 1) / SSU * SSU;
1562 end if;
1564 -- If old normalized position is static, we can go ahead and
1565 -- compute the new normalized position directly.
1567 if Known_Static_Normalized_Position (Prev_Comp) then
1568 New_Npos := Old_Npos;
1570 if New_Fbit >= SSU then
1571 New_Npos := New_Npos + New_Fbit / SSU;
1572 New_Fbit := New_Fbit mod SSU;
1573 end if;
1575 -- Bump alignment if stricter than prev
1577 if Align > Alignment (Etype (Prev_Comp)) then
1578 New_Npos := (New_Npos + Align - 1) / Align * Align;
1579 end if;
1581 -- The max position is always equal to the position if
1582 -- the latter is static, since arrays depending on the
1583 -- values of discriminants never have static sizes.
1585 New_NPMax := New_Npos;
1586 return;
1588 -- Case of old normalized position is dynamic
1590 else
1591 -- If new bit position is within the current storage unit,
1592 -- we can just copy the old position as the result position
1593 -- (we have already set the new first bit value).
1595 if New_Fbit < SSU then
1596 New_Npos := Old_Npos;
1597 New_NPMax := Old_NPMax;
1599 -- If new bit position is past the current storage unit, we
1600 -- need to generate a new dynamic value for the position
1601 -- ??? need to deal with alignment
1603 else
1604 New_Npos :=
1605 SO_Ref_From_Expr
1606 (Assoc_Add (Loc,
1607 Left_Opnd => Expr_From_SO_Ref (Loc, Old_Npos),
1608 Right_Opnd =>
1609 Make_Integer_Literal (Loc,
1610 Intval => New_Fbit / SSU)),
1611 Ins_Type => E,
1612 Vtype => E);
1614 New_NPMax :=
1615 SO_Ref_From_Expr
1616 (Assoc_Add (Loc,
1617 Left_Opnd => Expr_From_SO_Ref (Loc, Old_NPMax),
1618 Right_Opnd =>
1619 Make_Integer_Literal (Loc,
1620 Intval => New_Fbit / SSU)),
1621 Ins_Type => E,
1622 Vtype => E);
1623 New_Fbit := New_Fbit mod SSU;
1624 end if;
1625 end if;
1626 end if;
1627 end;
1628 end Get_Next_Component_Location;
1630 ----------------------
1631 -- Layout_Component --
1632 ----------------------
1634 procedure Layout_Component (Comp : Entity_Id; Prev_Comp : Entity_Id) is
1635 Ctyp : constant Entity_Id := Etype (Comp);
1636 ORC : constant Entity_Id := Original_Record_Component (Comp);
1637 Npos : SO_Ref;
1638 Fbit : SO_Ref;
1639 NPMax : SO_Ref;
1640 Forc : Boolean;
1642 begin
1643 -- Increase alignment of record if necessary. Note that we do not
1644 -- do this for packed records, which have an alignment of one by
1645 -- default, or for records for which an explicit alignment was
1646 -- specified with an alignment clause.
1648 if not Is_Packed (E)
1649 and then not Has_Alignment_Clause (E)
1650 and then Alignment (Ctyp) > Alignment (E)
1651 then
1652 Set_Alignment (E, Alignment (Ctyp));
1653 end if;
1655 -- If original component set, then use same layout
1657 if Present (ORC) and then ORC /= Comp then
1658 Set_Normalized_Position (Comp, Normalized_Position (ORC));
1659 Set_Normalized_First_Bit (Comp, Normalized_First_Bit (ORC));
1660 Set_Normalized_Position_Max (Comp, Normalized_Position_Max (ORC));
1661 Set_Component_Bit_Offset (Comp, Component_Bit_Offset (ORC));
1662 Set_Esize (Comp, Esize (ORC));
1663 return;
1664 end if;
1666 -- Parent field is always at start of record, this will overlap
1667 -- the actual fields that are part of the parent, and that's fine
1669 if Chars (Comp) = Name_uParent then
1670 Set_Normalized_Position (Comp, Uint_0);
1671 Set_Normalized_First_Bit (Comp, Uint_0);
1672 Set_Normalized_Position_Max (Comp, Uint_0);
1673 Set_Component_Bit_Offset (Comp, Uint_0);
1674 Set_Esize (Comp, Esize (Ctyp));
1675 return;
1676 end if;
1678 -- Check case of type of component has a scope of the record we are
1679 -- laying out. When this happens, the type in question is an Itype
1680 -- that has not yet been laid out (that's because such types do not
1681 -- get frozen in the normal manner, because there is no place for
1682 -- the freeze nodes).
1684 if Scope (Ctyp) = E then
1685 Layout_Type (Ctyp);
1686 end if;
1688 -- If component already laid out, then we are done
1690 if Known_Normalized_Position (Comp) then
1691 return;
1692 end if;
1694 -- Set size of component from type. We use the Esize except in a
1695 -- packed record, where we use the RM_Size (since that is what the
1696 -- RM_Size value, as distinct from the Object_Size is useful for).
1698 if Is_Packed (E) then
1699 Set_Esize (Comp, RM_Size (Ctyp));
1700 else
1701 Set_Esize (Comp, Esize (Ctyp));
1702 end if;
1704 -- Compute the component position from the previous one. See if
1705 -- current component requires being on a storage unit boundary.
1707 -- If record is not packed, we always go to a storage unit boundary
1709 if not Is_Packed (E) then
1710 Forc := True;
1712 -- Packed cases
1714 else
1715 -- Elementary types do not need SU boundary in packed record
1717 if Is_Elementary_Type (Ctyp) then
1718 Forc := False;
1720 -- Packed array types with a modular packed array type do not
1721 -- force a storage unit boundary (since the code generation
1722 -- treats these as equivalent to the underlying modular type),
1724 elsif Is_Array_Type (Ctyp)
1725 and then Is_Bit_Packed_Array (Ctyp)
1726 and then Is_Modular_Integer_Type (Packed_Array_Impl_Type (Ctyp))
1727 then
1728 Forc := False;
1730 -- Record types with known length less than or equal to the length
1731 -- of long long integer can also be unaligned, since they can be
1732 -- treated as scalars.
1734 elsif Is_Record_Type (Ctyp)
1735 and then not Is_Dynamic_SO_Ref (Esize (Ctyp))
1736 and then Esize (Ctyp) <= Esize (Standard_Long_Long_Integer)
1737 then
1738 Forc := False;
1740 -- All other cases force a storage unit boundary, even when packed
1742 else
1743 Forc := True;
1744 end if;
1745 end if;
1747 -- Now get the next component location
1749 Get_Next_Component_Location
1750 (Prev_Comp, Alignment (Ctyp), Npos, Fbit, NPMax, Forc);
1751 Set_Normalized_Position (Comp, Npos);
1752 Set_Normalized_First_Bit (Comp, Fbit);
1753 Set_Normalized_Position_Max (Comp, NPMax);
1755 -- Set Component_Bit_Offset in the static case
1757 if Known_Static_Normalized_Position (Comp)
1758 and then Known_Normalized_First_Bit (Comp)
1759 then
1760 Set_Component_Bit_Offset (Comp, SSU * Npos + Fbit);
1761 end if;
1762 end Layout_Component;
1764 -----------------------
1765 -- Layout_Components --
1766 -----------------------
1768 procedure Layout_Components
1769 (From : Entity_Id;
1770 To : Entity_Id;
1771 Esiz : out SO_Ref;
1772 RM_Siz : out SO_Ref)
1774 End_Npos : SO_Ref;
1775 End_Fbit : SO_Ref;
1776 End_NPMax : SO_Ref;
1778 begin
1779 -- Only lay out components if there are some to lay out
1781 if Present (From) then
1783 -- Lay out components with no component clauses
1785 Comp := From;
1786 loop
1787 if Ekind (Comp) = E_Component
1788 or else Ekind (Comp) = E_Discriminant
1789 then
1790 -- The compatibility of component clauses with composite
1791 -- types isn't checked in Sem_Ch13, so we check it here.
1793 if Present (Component_Clause (Comp)) then
1794 if Is_Composite_Type (Etype (Comp))
1795 and then Esize (Comp) < RM_Size (Etype (Comp))
1796 then
1797 Error_Msg_Uint_1 := RM_Size (Etype (Comp));
1798 Error_Msg_NE
1799 ("size for & too small, minimum allowed is ^",
1800 Component_Clause (Comp),
1801 Comp);
1802 end if;
1804 else
1805 Layout_Component (Comp, Prev_Comp);
1806 Prev_Comp := Comp;
1807 end if;
1808 end if;
1810 exit when Comp = To;
1811 Next_Entity (Comp);
1812 end loop;
1813 end if;
1815 -- Set size fields, both are zero if no components
1817 if No (Prev_Comp) then
1818 Esiz := Uint_0;
1819 RM_Siz := Uint_0;
1821 -- If record subtype with non-static discriminants, then we don't
1822 -- know which variant will be the one which gets chosen. We don't
1823 -- just want to set the maximum size from the base, because the
1824 -- size should depend on the particular variant.
1826 -- What we do is to use the RM_Size of the base type, which has
1827 -- the necessary conditional computation of the size, using the
1828 -- size information for the particular variant chosen. Records
1829 -- with default discriminants for example have an Esize that is
1830 -- set to the maximum of all variants, but that's not what we
1831 -- want for a constrained subtype.
1833 elsif Ekind (E) = E_Record_Subtype
1834 and then not Has_Static_Discriminants (E)
1835 then
1836 declare
1837 BT : constant Node_Id := Base_Type (E);
1838 begin
1839 Esiz := RM_Size (BT);
1840 RM_Siz := RM_Size (BT);
1841 Set_Alignment (E, Alignment (BT));
1842 end;
1844 else
1845 -- First the object size, for which we align past the last field
1846 -- to the alignment of the record (the object size is required to
1847 -- be a multiple of the alignment).
1849 Get_Next_Component_Location
1850 (Prev_Comp,
1851 Alignment (E),
1852 End_Npos,
1853 End_Fbit,
1854 End_NPMax,
1855 Force_SU => True);
1857 -- If the resulting normalized position is a dynamic reference,
1858 -- then the size is dynamic, and is stored in storage units. In
1859 -- this case, we set the RM_Size to the same value, it is simply
1860 -- not worth distinguishing Esize and RM_Size values in the
1861 -- dynamic case, since the RM has nothing to say about them.
1863 -- Note that a size cannot have been given in this case, since
1864 -- size specifications cannot be given for variable length types.
1866 declare
1867 Align : constant Uint := Alignment (E);
1869 begin
1870 if Is_Dynamic_SO_Ref (End_Npos) then
1871 RM_Siz := End_Npos;
1873 -- Set the Object_Size allowing for the alignment. In the
1874 -- dynamic case, we must do the actual runtime computation.
1875 -- We can skip this in the non-packed record case if the
1876 -- last component has a smaller alignment than the overall
1877 -- record alignment.
1879 if Is_Dynamic_SO_Ref (End_NPMax) then
1880 Esiz := End_NPMax;
1882 if Is_Packed (E)
1883 or else Alignment (Etype (Prev_Comp)) < Align
1884 then
1885 -- The expression we build is:
1886 -- (expr + align - 1) / align * align
1888 Esiz :=
1889 SO_Ref_From_Expr
1890 (Expr =>
1891 Make_Op_Multiply (Loc,
1892 Left_Opnd =>
1893 Make_Op_Divide (Loc,
1894 Left_Opnd =>
1895 Make_Op_Add (Loc,
1896 Left_Opnd =>
1897 Expr_From_SO_Ref (Loc, Esiz),
1898 Right_Opnd =>
1899 Make_Integer_Literal (Loc,
1900 Intval => Align - 1)),
1901 Right_Opnd =>
1902 Make_Integer_Literal (Loc, Align)),
1903 Right_Opnd =>
1904 Make_Integer_Literal (Loc, Align)),
1905 Ins_Type => E,
1906 Vtype => E);
1907 end if;
1909 -- Here Esiz is static, so we can adjust the alignment
1910 -- directly go give the required aligned value.
1912 else
1913 Esiz := (End_NPMax + Align - 1) / Align * Align * SSU;
1914 end if;
1916 -- Case where computed size is static
1918 else
1919 -- The ending size was computed in Npos in storage units,
1920 -- but the actual size is stored in bits, so adjust
1921 -- accordingly. We also adjust the size to match the
1922 -- alignment here.
1924 Esiz := (End_NPMax + Align - 1) / Align * Align * SSU;
1926 -- Compute the resulting Value_Size (RM_Size). For this
1927 -- purpose we do not force alignment of the record or
1928 -- storage size alignment of the result.
1930 Get_Next_Component_Location
1931 (Prev_Comp,
1932 Uint_0,
1933 End_Npos,
1934 End_Fbit,
1935 End_NPMax,
1936 Force_SU => False);
1938 RM_Siz := End_Npos * SSU + End_Fbit;
1939 Set_And_Check_Static_Size (E, Esiz, RM_Siz);
1940 end if;
1941 end;
1942 end if;
1943 end Layout_Components;
1945 -------------------------------
1946 -- Layout_Non_Variant_Record --
1947 -------------------------------
1949 procedure Layout_Non_Variant_Record is
1950 Esiz : SO_Ref;
1951 RM_Siz : SO_Ref;
1952 begin
1953 Layout_Components (First_Entity (E), Last_Entity (E), Esiz, RM_Siz);
1954 Set_Esize (E, Esiz);
1955 Set_RM_Size (E, RM_Siz);
1956 end Layout_Non_Variant_Record;
1958 ---------------------------
1959 -- Layout_Variant_Record --
1960 ---------------------------
1962 procedure Layout_Variant_Record is
1963 Tdef : constant Node_Id := Type_Definition (Decl);
1964 First_Discr : Entity_Id;
1965 Last_Discr : Entity_Id;
1966 Esiz : SO_Ref;
1968 RM_Siz : SO_Ref;
1969 pragma Warnings (Off, SO_Ref);
1971 RM_Siz_Expr : Node_Id := Empty;
1972 -- Expression for the evolving RM_Siz value. This is typically an if
1973 -- expression which involves tests of discriminant values that are
1974 -- formed as references to the entity V. At the end of scanning all
1975 -- the components, a suitable function is constructed in which V is
1976 -- the parameter.
1978 -----------------------
1979 -- Local Subprograms --
1980 -----------------------
1982 procedure Layout_Component_List
1983 (Clist : Node_Id;
1984 Esiz : out SO_Ref;
1985 RM_Siz_Expr : out Node_Id);
1986 -- Recursive procedure, called to lay out one component list Esiz
1987 -- and RM_Siz_Expr are set to the Object_Size and Value_Size values
1988 -- respectively representing the record size up to and including the
1989 -- last component in the component list (including any variants in
1990 -- this component list). RM_Siz_Expr is returned as an expression
1991 -- which may in the general case involve some references to the
1992 -- discriminants of the current record value, referenced by selecting
1993 -- from the entity V.
1995 ---------------------------
1996 -- Layout_Component_List --
1997 ---------------------------
1999 procedure Layout_Component_List
2000 (Clist : Node_Id;
2001 Esiz : out SO_Ref;
2002 RM_Siz_Expr : out Node_Id)
2004 Citems : constant List_Id := Component_Items (Clist);
2005 Vpart : constant Node_Id := Variant_Part (Clist);
2006 Prv : Node_Id;
2007 Var : Node_Id;
2008 RM_Siz : Uint;
2009 RMS_Ent : Entity_Id;
2011 begin
2012 if Is_Non_Empty_List (Citems) then
2013 Layout_Components
2014 (From => Defining_Identifier (First (Citems)),
2015 To => Defining_Identifier (Last (Citems)),
2016 Esiz => Esiz,
2017 RM_Siz => RM_Siz);
2018 else
2019 Layout_Components (Empty, Empty, Esiz, RM_Siz);
2020 end if;
2022 -- Case where no variants are present in the component list
2024 if No (Vpart) then
2026 -- The Esiz value has been correctly set by the call to
2027 -- Layout_Components, so there is nothing more to be done.
2029 -- For RM_Siz, we have an SO_Ref value, which we must convert
2030 -- to an appropriate expression.
2032 if Is_Static_SO_Ref (RM_Siz) then
2033 RM_Siz_Expr :=
2034 Make_Integer_Literal (Loc,
2035 Intval => RM_Siz);
2037 else
2038 RMS_Ent := Get_Dynamic_SO_Entity (RM_Siz);
2040 -- If the size is represented by a function, then we create
2041 -- an appropriate function call using V as the parameter to
2042 -- the call.
2044 if Is_Discrim_SO_Function (RMS_Ent) then
2045 RM_Siz_Expr :=
2046 Make_Function_Call (Loc,
2047 Name => New_Occurrence_Of (RMS_Ent, Loc),
2048 Parameter_Associations => New_List (
2049 Make_Identifier (Loc, Vname)));
2051 -- If the size is represented by a constant, then the
2052 -- expression we want is a reference to this constant
2054 else
2055 RM_Siz_Expr := New_Occurrence_Of (RMS_Ent, Loc);
2056 end if;
2057 end if;
2059 -- Case where variants are present in this component list
2061 else
2062 declare
2063 EsizV : SO_Ref;
2064 RM_SizV : Node_Id;
2065 Dchoice : Node_Id;
2066 Discrim : Node_Id;
2067 Dtest : Node_Id;
2068 D_List : List_Id;
2069 D_Entity : Entity_Id;
2071 begin
2072 RM_Siz_Expr := Empty;
2073 Prv := Prev_Comp;
2075 Var := Last (Variants (Vpart));
2076 while Present (Var) loop
2077 Prev_Comp := Prv;
2078 Layout_Component_List
2079 (Component_List (Var), EsizV, RM_SizV);
2081 -- Set the Object_Size. If this is the first variant,
2082 -- we just set the size of this first variant.
2084 if Var = Last (Variants (Vpart)) then
2085 Esiz := EsizV;
2087 -- Otherwise the Object_Size is formed as a maximum
2088 -- of Esiz so far from previous variants, and the new
2089 -- Esiz value from the variant we just processed.
2091 -- If both values are static, we can just compute the
2092 -- maximum directly to save building junk nodes.
2094 elsif not Is_Dynamic_SO_Ref (Esiz)
2095 and then not Is_Dynamic_SO_Ref (EsizV)
2096 then
2097 Esiz := UI_Max (Esiz, EsizV);
2099 -- If either value is dynamic, then we have to generate
2100 -- an appropriate Standard_Unsigned'Max attribute call.
2101 -- If one of the values is static then it needs to be
2102 -- converted from bits to storage units to be compatible
2103 -- with the dynamic value.
2105 else
2106 if Is_Static_SO_Ref (Esiz) then
2107 Esiz := (Esiz + SSU - 1) / SSU;
2108 end if;
2110 if Is_Static_SO_Ref (EsizV) then
2111 EsizV := (EsizV + SSU - 1) / SSU;
2112 end if;
2114 Esiz :=
2115 SO_Ref_From_Expr
2116 (Make_Attribute_Reference (Loc,
2117 Attribute_Name => Name_Max,
2118 Prefix =>
2119 New_Occurrence_Of (Standard_Unsigned, Loc),
2120 Expressions => New_List (
2121 Expr_From_SO_Ref (Loc, Esiz),
2122 Expr_From_SO_Ref (Loc, EsizV))),
2123 Ins_Type => E,
2124 Vtype => E);
2125 end if;
2127 -- Now deal with Value_Size (RM_Siz). We are aiming at
2128 -- an expression that looks like:
2130 -- if xxDx (V.disc) then rmsiz1
2131 -- else if xxDx (V.disc) then rmsiz2
2132 -- else ...
2134 -- Where rmsiz1, rmsiz2... are the RM_Siz values for the
2135 -- individual variants, and xxDx are the discriminant
2136 -- checking functions generated for the variant type.
2138 -- If this is the first variant, we simply set the result
2139 -- as the expression. Note that this takes care of the
2140 -- others case.
2142 if No (RM_Siz_Expr) then
2144 -- If this is the only variant and the size is a
2145 -- literal, then use bit size as is, otherwise convert
2146 -- to storage units and continue to the next variant.
2148 if No (Prev (Var))
2149 and then Nkind (RM_SizV) = N_Integer_Literal
2150 then
2151 RM_Siz_Expr := RM_SizV;
2152 else
2153 RM_Siz_Expr := Bits_To_SU (RM_SizV);
2154 end if;
2156 -- Otherwise construct the appropriate test
2158 else
2159 -- The test to be used in general is a call to the
2160 -- discriminant checking function. However, it is
2161 -- definitely worth special casing the very common
2162 -- case where a single value is involved.
2164 Dchoice := First (Discrete_Choices (Var));
2166 if No (Next (Dchoice))
2167 and then Nkind (Dchoice) /= N_Range
2168 then
2169 -- Discriminant to be tested
2171 Discrim :=
2172 Make_Selected_Component (Loc,
2173 Prefix =>
2174 Make_Identifier (Loc, Vname),
2175 Selector_Name =>
2176 New_Occurrence_Of
2177 (Entity (Name (Vpart)), Loc));
2179 Dtest :=
2180 Make_Op_Eq (Loc,
2181 Left_Opnd => Discrim,
2182 Right_Opnd => New_Copy (Dchoice));
2184 -- Generate a call to the discriminant-checking
2185 -- function for the variant. Note that the result
2186 -- has to be complemented since the function returns
2187 -- False when the passed discriminant value matches.
2189 else
2190 -- The checking function takes all of the type's
2191 -- discriminants as parameters, so a list of all
2192 -- the selected discriminants must be constructed.
2194 D_List := New_List;
2195 D_Entity := First_Discriminant (E);
2196 while Present (D_Entity) loop
2197 Append_To (D_List,
2198 Make_Selected_Component (Loc,
2199 Prefix =>
2200 Make_Identifier (Loc, Vname),
2201 Selector_Name =>
2202 New_Occurrence_Of (D_Entity, Loc)));
2204 D_Entity := Next_Discriminant (D_Entity);
2205 end loop;
2207 Dtest :=
2208 Make_Op_Not (Loc,
2209 Right_Opnd =>
2210 Make_Function_Call (Loc,
2211 Name =>
2212 New_Occurrence_Of
2213 (Dcheck_Function (Var), Loc),
2214 Parameter_Associations =>
2215 D_List));
2216 end if;
2218 RM_Siz_Expr :=
2219 Make_If_Expression (Loc,
2220 Expressions =>
2221 New_List
2222 (Dtest, Bits_To_SU (RM_SizV), RM_Siz_Expr));
2223 end if;
2225 Prev (Var);
2226 end loop;
2227 end;
2228 end if;
2229 end Layout_Component_List;
2231 Others_Present : Boolean;
2232 pragma Warnings (Off, Others_Present);
2233 -- Indicates others present, not used in this case
2235 procedure Non_Static_Choice_Error (Choice : Node_Id);
2236 -- Error routine invoked by the generic instantiation below when
2237 -- the variant part has a nonstatic choice.
2239 package Variant_Choices_Processing is new
2240 Generic_Check_Choices
2241 (Process_Empty_Choice => No_OP,
2242 Process_Non_Static_Choice => Non_Static_Choice_Error,
2243 Process_Associated_Node => No_OP);
2244 use Variant_Choices_Processing;
2246 -----------------------------
2247 -- Non_Static_Choice_Error --
2248 -----------------------------
2250 procedure Non_Static_Choice_Error (Choice : Node_Id) is
2251 begin
2252 Flag_Non_Static_Expr
2253 ("choice given in case expression is not static!", Choice);
2254 end Non_Static_Choice_Error;
2256 -- Start of processing for Layout_Variant_Record
2258 begin
2259 -- Call Check_Choices here to ensure that Others_Discrete_Choices
2260 -- gets set on any 'others' choice before the discriminant-checking
2261 -- functions are generated. Otherwise the function for the 'others'
2262 -- alternative will unconditionally return True, causing discriminant
2263 -- checks to fail. However, Check_Choices is now normally delayed
2264 -- until the type's freeze entity is processed, due to requirements
2265 -- coming from subtype predicates, so doing it at this point is
2266 -- probably not right in general, but it's not clear how else to deal
2267 -- with this situation. Perhaps we should only generate declarations
2268 -- for the checking functions here, and somehow delay generation of
2269 -- their bodies, but that would be a nontrivial change. ???
2271 declare
2272 VP : constant Node_Id :=
2273 Variant_Part (Component_List (Type_Definition (Decl)));
2274 begin
2275 Check_Choices
2276 (VP, Variants (VP), Etype (Name (VP)), Others_Present);
2277 end;
2279 -- We need the discriminant checking functions, since we generate
2280 -- calls to these functions for the RM_Size expression, so make
2281 -- sure that these functions have been constructed in time.
2283 Build_Discr_Checking_Funcs (Decl);
2285 -- Lay out the discriminants
2287 First_Discr := First_Discriminant (E);
2288 Last_Discr := First_Discr;
2289 while Present (Next_Discriminant (Last_Discr)) loop
2290 Next_Discriminant (Last_Discr);
2291 end loop;
2293 Layout_Components
2294 (From => First_Discr,
2295 To => Last_Discr,
2296 Esiz => Esiz,
2297 RM_Siz => RM_Siz);
2299 -- Lay out the main component list (this will make recursive calls
2300 -- to lay out all component lists nested within variants).
2302 Layout_Component_List (Component_List (Tdef), Esiz, RM_Siz_Expr);
2303 Set_Esize (E, Esiz);
2305 -- If the RM_Size is a literal, set its value
2307 if Nkind (RM_Siz_Expr) = N_Integer_Literal then
2308 Set_RM_Size (E, Intval (RM_Siz_Expr));
2310 -- Otherwise we construct a dynamic SO_Ref
2312 else
2313 Set_RM_Size (E,
2314 SO_Ref_From_Expr
2315 (RM_Siz_Expr,
2316 Ins_Type => E,
2317 Vtype => E));
2318 end if;
2319 end Layout_Variant_Record;
2321 -- Start of processing for Layout_Record_Type
2323 begin
2324 -- If this is a cloned subtype, just copy the size fields from the
2325 -- original, nothing else needs to be done in this case, since the
2326 -- components themselves are all shared.
2328 if Ekind_In (E, E_Record_Subtype, E_Class_Wide_Subtype)
2329 and then Present (Cloned_Subtype (E))
2330 then
2331 Set_Esize (E, Esize (Cloned_Subtype (E)));
2332 Set_RM_Size (E, RM_Size (Cloned_Subtype (E)));
2333 Set_Alignment (E, Alignment (Cloned_Subtype (E)));
2335 -- Another special case, class-wide types. The RM says that the size
2336 -- of such types is implementation defined (RM 13.3(48)). What we do
2337 -- here is to leave the fields set as unknown values, and the backend
2338 -- determines the actual behavior.
2340 elsif Ekind (E) = E_Class_Wide_Type then
2341 null;
2343 -- All other cases
2345 else
2346 -- Initialize alignment conservatively to 1. This value will be
2347 -- increased as necessary during processing of the record.
2349 if Unknown_Alignment (E) then
2350 Set_Alignment (E, Uint_1);
2351 end if;
2353 -- Initialize previous component. This is Empty unless there are
2354 -- components which have already been laid out by component clauses.
2355 -- If there are such components, we start our lay out of the
2356 -- remaining components following the last such component.
2358 Prev_Comp := Empty;
2360 Comp := First_Component_Or_Discriminant (E);
2361 while Present (Comp) loop
2362 if Present (Component_Clause (Comp)) then
2363 if No (Prev_Comp)
2364 or else
2365 Component_Bit_Offset (Comp) >
2366 Component_Bit_Offset (Prev_Comp)
2367 then
2368 Prev_Comp := Comp;
2369 end if;
2370 end if;
2372 Next_Component_Or_Discriminant (Comp);
2373 end loop;
2375 -- We have two separate circuits, one for non-variant records and
2376 -- one for variant records. For non-variant records, we simply go
2377 -- through the list of components. This handles all the non-variant
2378 -- cases including those cases of subtypes where there is no full
2379 -- type declaration, so the tree cannot be used to drive the layout.
2380 -- For variant records, we have to drive the layout from the tree
2381 -- since we need to understand the variant structure in this case.
2383 if Present (Full_View (E)) then
2384 Decl := Declaration_Node (Full_View (E));
2385 else
2386 Decl := Declaration_Node (E);
2387 end if;
2389 -- Scan all the components
2391 if Nkind (Decl) = N_Full_Type_Declaration
2392 and then Has_Discriminants (E)
2393 and then Nkind (Type_Definition (Decl)) = N_Record_Definition
2394 and then Present (Component_List (Type_Definition (Decl)))
2395 and then
2396 Present (Variant_Part (Component_List (Type_Definition (Decl))))
2397 then
2398 Layout_Variant_Record;
2399 else
2400 Layout_Non_Variant_Record;
2401 end if;
2402 end if;
2403 end Layout_Record_Type;
2405 -----------------
2406 -- Layout_Type --
2407 -----------------
2409 procedure Layout_Type (E : Entity_Id) is
2410 Desig_Type : Entity_Id;
2412 begin
2413 -- For string literal types, for now, kill the size always, this is
2414 -- because gigi does not like or need the size to be set ???
2416 if Ekind (E) = E_String_Literal_Subtype then
2417 Set_Esize (E, Uint_0);
2418 Set_RM_Size (E, Uint_0);
2419 return;
2420 end if;
2422 -- For access types, set size/alignment. This is system address size,
2423 -- except for fat pointers (unconstrained array access types), where the
2424 -- size is two times the address size, to accommodate the two pointers
2425 -- that are required for a fat pointer (data and template). Note that
2426 -- E_Access_Protected_Subprogram_Type is not an access type for this
2427 -- purpose since it is not a pointer but is equivalent to a record. For
2428 -- access subtypes, copy the size from the base type since Gigi
2429 -- represents them the same way.
2431 if Is_Access_Type (E) then
2432 Desig_Type := Underlying_Type (Designated_Type (E));
2434 -- If we only have a limited view of the type, see whether the
2435 -- non-limited view is available.
2437 if From_Limited_With (Designated_Type (E))
2438 and then Ekind (Designated_Type (E)) = E_Incomplete_Type
2439 and then Present (Non_Limited_View (Designated_Type (E)))
2440 then
2441 Desig_Type := Non_Limited_View (Designated_Type (E));
2442 end if;
2444 -- If Esize already set (e.g. by a size clause), then nothing further
2445 -- to be done here.
2447 if Known_Esize (E) then
2448 null;
2450 -- Access to subprogram is a strange beast, and we let the backend
2451 -- figure out what is needed (it may be some kind of fat pointer,
2452 -- including the static link for example.
2454 elsif Is_Access_Protected_Subprogram_Type (E) then
2455 null;
2457 -- For access subtypes, copy the size information from base type
2459 elsif Ekind (E) = E_Access_Subtype then
2460 Set_Size_Info (E, Base_Type (E));
2461 Set_RM_Size (E, RM_Size (Base_Type (E)));
2463 -- For other access types, we use either address size, or, if a fat
2464 -- pointer is used (pointer-to-unconstrained array case), twice the
2465 -- address size to accommodate a fat pointer.
2467 elsif Present (Desig_Type)
2468 and then Is_Array_Type (Desig_Type)
2469 and then not Is_Constrained (Desig_Type)
2470 and then not Has_Completion_In_Body (Desig_Type)
2472 -- Debug Flag -gnatd6 says make all pointers to unconstrained thin
2474 and then not Debug_Flag_6
2475 then
2476 Init_Size (E, 2 * System_Address_Size);
2478 -- Check for bad convention set
2480 if Warn_On_Export_Import
2481 and then
2482 (Convention (E) = Convention_C
2483 or else
2484 Convention (E) = Convention_CPP)
2485 then
2486 Error_Msg_N
2487 ("?x?this access type does not correspond to C pointer", E);
2488 end if;
2490 -- If the designated type is a limited view it is unanalyzed. We can
2491 -- examine the declaration itself to determine whether it will need a
2492 -- fat pointer.
2494 elsif Present (Desig_Type)
2495 and then Present (Parent (Desig_Type))
2496 and then Nkind (Parent (Desig_Type)) = N_Full_Type_Declaration
2497 and then Nkind (Type_Definition (Parent (Desig_Type))) =
2498 N_Unconstrained_Array_Definition
2499 and then not Debug_Flag_6
2500 then
2501 Init_Size (E, 2 * System_Address_Size);
2503 -- Normal case of thin pointer
2505 else
2506 Init_Size (E, System_Address_Size);
2507 end if;
2509 Set_Elem_Alignment (E);
2511 -- Scalar types: set size and alignment
2513 elsif Is_Scalar_Type (E) then
2515 -- For discrete types, the RM_Size and Esize must be set already,
2516 -- since this is part of the earlier processing and the front end is
2517 -- always required to lay out the sizes of such types (since they are
2518 -- available as static attributes). All we do is to check that this
2519 -- rule is indeed obeyed.
2521 if Is_Discrete_Type (E) then
2523 -- If the RM_Size is not set, then here is where we set it
2525 -- Note: an RM_Size of zero looks like not set here, but this
2526 -- is a rare case, and we can simply reset it without any harm.
2528 if not Known_RM_Size (E) then
2529 Set_Discrete_RM_Size (E);
2530 end if;
2532 -- If Esize for a discrete type is not set then set it
2534 if not Known_Esize (E) then
2535 declare
2536 S : Int := 8;
2538 begin
2539 loop
2540 -- If size is big enough, set it and exit
2542 if S >= RM_Size (E) then
2543 Init_Esize (E, S);
2544 exit;
2546 -- If the RM_Size is greater than 64 (happens only when
2547 -- strange values are specified by the user, then Esize
2548 -- is simply a copy of RM_Size, it will be further
2549 -- refined later on)
2551 elsif S = 64 then
2552 Set_Esize (E, RM_Size (E));
2553 exit;
2555 -- Otherwise double possible size and keep trying
2557 else
2558 S := S * 2;
2559 end if;
2560 end loop;
2561 end;
2562 end if;
2564 -- For non-discrete scalar types, if the RM_Size is not set, then set
2565 -- it now to a copy of the Esize if the Esize is set.
2567 else
2568 if Known_Esize (E) and then Unknown_RM_Size (E) then
2569 Set_RM_Size (E, Esize (E));
2570 end if;
2571 end if;
2573 Set_Elem_Alignment (E);
2575 -- Non-elementary (composite) types
2577 else
2578 -- For packed arrays, take size and alignment values from the packed
2579 -- array type if a packed array type has been created and the fields
2580 -- are not currently set.
2582 if Is_Array_Type (E)
2583 and then Present (Packed_Array_Impl_Type (E))
2584 then
2585 declare
2586 PAT : constant Entity_Id := Packed_Array_Impl_Type (E);
2588 begin
2589 if Unknown_Esize (E) then
2590 Set_Esize (E, Esize (PAT));
2591 end if;
2593 if Unknown_RM_Size (E) then
2594 Set_RM_Size (E, RM_Size (PAT));
2595 end if;
2597 if Unknown_Alignment (E) then
2598 Set_Alignment (E, Alignment (PAT));
2599 end if;
2600 end;
2601 end if;
2603 -- If Esize is set, and RM_Size is not, RM_Size is copied from Esize.
2604 -- At least for now this seems reasonable, and is in any case needed
2605 -- for compatibility with old versions of gigi.
2607 if Known_Esize (E) and then Unknown_RM_Size (E) then
2608 Set_RM_Size (E, Esize (E));
2609 end if;
2611 -- For array base types, set component size if object size of the
2612 -- component type is known and is a small power of 2 (8, 16, 32, 64),
2613 -- since this is what will always be used.
2615 if Ekind (E) = E_Array_Type and then Unknown_Component_Size (E) then
2616 declare
2617 CT : constant Entity_Id := Component_Type (E);
2619 begin
2620 -- For some reason, access types can cause trouble, So let's
2621 -- just do this for scalar types ???
2623 if Present (CT)
2624 and then Is_Scalar_Type (CT)
2625 and then Known_Static_Esize (CT)
2626 then
2627 declare
2628 S : constant Uint := Esize (CT);
2629 begin
2630 if Addressable (S) then
2631 Set_Component_Size (E, S);
2632 end if;
2633 end;
2634 end if;
2635 end;
2636 end if;
2637 end if;
2639 -- Lay out array and record types if front end layout set
2641 if Frontend_Layout_On_Target then
2642 if Is_Array_Type (E) and then not Is_Bit_Packed_Array (E) then
2643 Layout_Array_Type (E);
2644 elsif Is_Record_Type (E) then
2645 Layout_Record_Type (E);
2646 end if;
2648 -- Case of backend layout, we still do a little in the front end
2650 else
2651 -- Processing for record types
2653 if Is_Record_Type (E) then
2655 -- Special remaining processing for record types with a known
2656 -- size of 16, 32, or 64 bits whose alignment is not yet set.
2657 -- For these types, we set a corresponding alignment matching
2658 -- the size if possible, or as large as possible if not.
2660 if Convention (E) = Convention_Ada and then not Debug_Flag_Q then
2661 Set_Composite_Alignment (E);
2662 end if;
2664 -- Processing for array types
2666 elsif Is_Array_Type (E) then
2668 -- For arrays that are required to be atomic/VFA, we do the same
2669 -- processing as described above for short records, since we
2670 -- really need to have the alignment set for the whole array.
2672 if Is_Atomic_Or_VFA (E) and then not Debug_Flag_Q then
2673 Set_Composite_Alignment (E);
2674 end if;
2676 -- For unpacked array types, set an alignment of 1 if we know
2677 -- that the component alignment is not greater than 1. The reason
2678 -- we do this is to avoid unnecessary copying of slices of such
2679 -- arrays when passed to subprogram parameters (see special test
2680 -- in Exp_Ch6.Expand_Actuals).
2682 if not Is_Packed (E) and then Unknown_Alignment (E) then
2683 if Known_Static_Component_Size (E)
2684 and then Component_Size (E) = 1
2685 then
2686 Set_Alignment (E, Uint_1);
2687 end if;
2688 end if;
2690 -- We need to know whether the size depends on the value of one
2691 -- or more discriminants to select the return mechanism. Skip if
2692 -- errors are present, to prevent cascaded messages.
2694 if Serious_Errors_Detected = 0 then
2695 Compute_Size_Depends_On_Discriminant (E);
2696 end if;
2698 end if;
2699 end if;
2701 -- Final step is to check that Esize and RM_Size are compatible
2703 if Known_Static_Esize (E) and then Known_Static_RM_Size (E) then
2704 if Esize (E) < RM_Size (E) then
2706 -- Esize is less than RM_Size. That's not good. First we test
2707 -- whether this was set deliberately with an Object_Size clause
2708 -- and if so, object to the clause.
2710 if Has_Object_Size_Clause (E) then
2711 Error_Msg_Uint_1 := RM_Size (E);
2712 Error_Msg_F
2713 ("object size is too small, minimum allowed is ^",
2714 Expression (Get_Attribute_Definition_Clause
2715 (E, Attribute_Object_Size)));
2716 end if;
2718 -- Adjust Esize up to RM_Size value
2720 declare
2721 Size : constant Uint := RM_Size (E);
2723 begin
2724 Set_Esize (E, RM_Size (E));
2726 -- For scalar types, increase Object_Size to power of 2, but
2727 -- not less than a storage unit in any case (i.e., normally
2728 -- this means it will be storage-unit addressable).
2730 if Is_Scalar_Type (E) then
2731 if Size <= System_Storage_Unit then
2732 Init_Esize (E, System_Storage_Unit);
2733 elsif Size <= 16 then
2734 Init_Esize (E, 16);
2735 elsif Size <= 32 then
2736 Init_Esize (E, 32);
2737 else
2738 Set_Esize (E, (Size + 63) / 64 * 64);
2739 end if;
2741 -- Finally, make sure that alignment is consistent with
2742 -- the newly assigned size.
2744 while Alignment (E) * System_Storage_Unit < Esize (E)
2745 and then Alignment (E) < Maximum_Alignment
2746 loop
2747 Set_Alignment (E, 2 * Alignment (E));
2748 end loop;
2749 end if;
2750 end;
2751 end if;
2752 end if;
2753 end Layout_Type;
2755 ---------------------
2756 -- Rewrite_Integer --
2757 ---------------------
2759 procedure Rewrite_Integer (N : Node_Id; V : Uint) is
2760 Loc : constant Source_Ptr := Sloc (N);
2761 Typ : constant Entity_Id := Etype (N);
2762 begin
2763 Rewrite (N, Make_Integer_Literal (Loc, Intval => V));
2764 Set_Etype (N, Typ);
2765 end Rewrite_Integer;
2767 -------------------------------
2768 -- Set_And_Check_Static_Size --
2769 -------------------------------
2771 procedure Set_And_Check_Static_Size
2772 (E : Entity_Id;
2773 Esiz : SO_Ref;
2774 RM_Siz : SO_Ref)
2776 SC : Node_Id;
2778 procedure Check_Size_Too_Small (Spec : Uint; Min : Uint);
2779 -- Spec is the number of bit specified in the size clause, and Min is
2780 -- the minimum computed size. An error is given that the specified size
2781 -- is too small if Spec < Min, and in this case both Esize and RM_Size
2782 -- are set to unknown in E. The error message is posted on node SC.
2784 procedure Check_Unused_Bits (Spec : Uint; Max : Uint);
2785 -- Spec is the number of bits specified in the size clause, and Max is
2786 -- the maximum computed size. A warning is given about unused bits if
2787 -- Spec > Max. This warning is posted on node SC.
2789 --------------------------
2790 -- Check_Size_Too_Small --
2791 --------------------------
2793 procedure Check_Size_Too_Small (Spec : Uint; Min : Uint) is
2794 begin
2795 if Spec < Min then
2796 Error_Msg_Uint_1 := Min;
2797 Error_Msg_NE ("size for & too small, minimum allowed is ^", SC, E);
2798 Init_Esize (E);
2799 Init_RM_Size (E);
2800 end if;
2801 end Check_Size_Too_Small;
2803 -----------------------
2804 -- Check_Unused_Bits --
2805 -----------------------
2807 procedure Check_Unused_Bits (Spec : Uint; Max : Uint) is
2808 begin
2809 if Spec > Max then
2810 Error_Msg_Uint_1 := Spec - Max;
2811 Error_Msg_NE ("??^ bits of & unused", SC, E);
2812 end if;
2813 end Check_Unused_Bits;
2815 -- Start of processing for Set_And_Check_Static_Size
2817 begin
2818 -- Case where Object_Size (Esize) is already set by a size clause
2820 if Known_Static_Esize (E) then
2821 SC := Size_Clause (E);
2823 if No (SC) then
2824 SC := Get_Attribute_Definition_Clause (E, Attribute_Object_Size);
2825 end if;
2827 -- Perform checks on specified size against computed sizes
2829 if Present (SC) then
2830 Check_Unused_Bits (Esize (E), Esiz);
2831 Check_Size_Too_Small (Esize (E), RM_Siz);
2832 end if;
2833 end if;
2835 -- Case where Value_Size (RM_Size) is set by specific Value_Size clause
2836 -- (we do not need to worry about Value_Size being set by a Size clause,
2837 -- since that will have set Esize as well, and we already took care of
2838 -- that case).
2840 if Known_Static_RM_Size (E) then
2841 SC := Get_Attribute_Definition_Clause (E, Attribute_Value_Size);
2843 -- Perform checks on specified size against computed sizes
2845 if Present (SC) then
2846 Check_Unused_Bits (RM_Size (E), Esiz);
2847 Check_Size_Too_Small (RM_Size (E), RM_Siz);
2848 end if;
2849 end if;
2851 -- Set sizes if unknown
2853 if Unknown_Esize (E) then
2854 Set_Esize (E, Esiz);
2855 end if;
2857 if Unknown_RM_Size (E) then
2858 Set_RM_Size (E, RM_Siz);
2859 end if;
2860 end Set_And_Check_Static_Size;
2862 -----------------------------
2863 -- Set_Composite_Alignment --
2864 -----------------------------
2866 procedure Set_Composite_Alignment (E : Entity_Id) is
2867 Siz : Uint;
2868 Align : Nat;
2870 begin
2871 -- If alignment is already set, then nothing to do
2873 if Known_Alignment (E) then
2874 return;
2875 end if;
2877 -- Alignment is not known, see if we can set it, taking into account
2878 -- the setting of the Optimize_Alignment mode.
2880 -- If Optimize_Alignment is set to Space, then we try to give packed
2881 -- records an aligmment of 1, unless there is some reason we can't.
2883 if Optimize_Alignment_Space (E)
2884 and then Is_Record_Type (E)
2885 and then Is_Packed (E)
2886 then
2887 -- No effect for record with atomic/VFA components
2889 if Is_Atomic_Or_VFA (E) then
2890 Error_Msg_N ("Optimize_Alignment has no effect for &??", E);
2892 if Is_Atomic (E) then
2893 Error_Msg_N
2894 ("\pragma ignored for atomic record??", E);
2895 else
2896 Error_Msg_N
2897 ("\pragma ignored for bolatile full access record??", E);
2898 end if;
2900 return;
2901 end if;
2903 -- No effect if independent components
2905 if Has_Independent_Components (E) then
2906 Error_Msg_N ("Optimize_Alignment has no effect for &??", E);
2907 Error_Msg_N
2908 ("\pragma ignored for record with independent components??", E);
2909 return;
2910 end if;
2912 -- No effect if any component is atomic/VFA or is a by-reference type
2914 declare
2915 Ent : Entity_Id;
2917 begin
2918 Ent := First_Component_Or_Discriminant (E);
2919 while Present (Ent) loop
2920 if Is_By_Reference_Type (Etype (Ent))
2921 or else Is_Atomic_Or_VFA (Etype (Ent))
2922 or else Is_Atomic_Or_VFA (Ent)
2923 then
2924 Error_Msg_N ("Optimize_Alignment has no effect for &??", E);
2926 if Is_Atomic (Etype (Ent)) or else Is_Atomic (Ent) then
2927 Error_Msg_N
2928 ("\pragma is ignored if atomic "
2929 & "components present??", E);
2930 else
2931 Error_Msg_N
2932 ("\pragma is ignored if bolatile full access "
2933 & "components present??", E);
2934 end if;
2936 return;
2937 else
2938 Next_Component_Or_Discriminant (Ent);
2939 end if;
2940 end loop;
2941 end;
2943 -- Optimize_Alignment has no effect on variable length record
2945 if not Size_Known_At_Compile_Time (E) then
2946 Error_Msg_N ("Optimize_Alignment has no effect for &??", E);
2947 Error_Msg_N ("\pragma is ignored for variable length record??", E);
2948 return;
2949 end if;
2951 -- All tests passed, we can set alignment to 1
2953 Align := 1;
2955 -- Not a record, or not packed
2957 else
2958 -- The only other cases we worry about here are where the size is
2959 -- statically known at compile time.
2961 if Known_Static_Esize (E) then
2962 Siz := Esize (E);
2963 elsif Unknown_Esize (E) and then Known_Static_RM_Size (E) then
2964 Siz := RM_Size (E);
2965 else
2966 return;
2967 end if;
2969 -- Size is known, alignment is not set
2971 -- Reset alignment to match size if the known size is exactly 2, 4,
2972 -- or 8 storage units.
2974 if Siz = 2 * System_Storage_Unit then
2975 Align := 2;
2976 elsif Siz = 4 * System_Storage_Unit then
2977 Align := 4;
2978 elsif Siz = 8 * System_Storage_Unit then
2979 Align := 8;
2981 -- If Optimize_Alignment is set to Space, then make sure the
2982 -- alignment matches the size, for example, if the size is 17
2983 -- bytes then we want an alignment of 1 for the type.
2985 elsif Optimize_Alignment_Space (E) then
2986 if Siz mod (8 * System_Storage_Unit) = 0 then
2987 Align := 8;
2988 elsif Siz mod (4 * System_Storage_Unit) = 0 then
2989 Align := 4;
2990 elsif Siz mod (2 * System_Storage_Unit) = 0 then
2991 Align := 2;
2992 else
2993 Align := 1;
2994 end if;
2996 -- If Optimize_Alignment is set to Time, then we reset for odd
2997 -- "in between sizes", for example a 17 bit record is given an
2998 -- alignment of 4.
3000 elsif Optimize_Alignment_Time (E)
3001 and then Siz > System_Storage_Unit
3002 and then Siz <= 8 * System_Storage_Unit
3003 then
3004 if Siz <= 2 * System_Storage_Unit then
3005 Align := 2;
3006 elsif Siz <= 4 * System_Storage_Unit then
3007 Align := 4;
3008 else -- Siz <= 8 * System_Storage_Unit then
3009 Align := 8;
3010 end if;
3012 -- No special alignment fiddling needed
3014 else
3015 return;
3016 end if;
3017 end if;
3019 -- Here we have Set Align to the proposed improved value. Make sure the
3020 -- value set does not exceed Maximum_Alignment for the target.
3022 if Align > Maximum_Alignment then
3023 Align := Maximum_Alignment;
3024 end if;
3026 -- Further processing for record types only to reduce the alignment
3027 -- set by the above processing in some specific cases. We do not
3028 -- do this for atomic/VFA records, since we need max alignment there,
3030 if Is_Record_Type (E) and then not Is_Atomic_Or_VFA (E) then
3032 -- For records, there is generally no point in setting alignment
3033 -- higher than word size since we cannot do better than move by
3034 -- words in any case. Omit this if we are optimizing for time,
3035 -- since conceivably we may be able to do better.
3037 if Align > System_Word_Size / System_Storage_Unit
3038 and then not Optimize_Alignment_Time (E)
3039 then
3040 Align := System_Word_Size / System_Storage_Unit;
3041 end if;
3043 -- Check components. If any component requires a higher alignment,
3044 -- then we set that higher alignment in any case. Don't do this if
3045 -- we have Optimize_Alignment set to Space. Note that that covers
3046 -- the case of packed records, where we already set alignment to 1.
3048 if not Optimize_Alignment_Space (E) then
3049 declare
3050 Comp : Entity_Id;
3052 begin
3053 Comp := First_Component (E);
3054 while Present (Comp) loop
3055 if Known_Alignment (Etype (Comp)) then
3056 declare
3057 Calign : constant Uint := Alignment (Etype (Comp));
3059 begin
3060 -- The cases to process are when the alignment of the
3061 -- component type is larger than the alignment we have
3062 -- so far, and either there is no component clause for
3063 -- the component, or the length set by the component
3064 -- clause matches the length of the component type.
3066 if Calign > Align
3067 and then
3068 (Unknown_Esize (Comp)
3069 or else (Known_Static_Esize (Comp)
3070 and then
3071 Esize (Comp) =
3072 Calign * System_Storage_Unit))
3073 then
3074 Align := UI_To_Int (Calign);
3075 end if;
3076 end;
3077 end if;
3079 Next_Component (Comp);
3080 end loop;
3081 end;
3082 end if;
3083 end if;
3085 -- Set chosen alignment, and increase Esize if necessary to match the
3086 -- chosen alignment.
3088 Set_Alignment (E, UI_From_Int (Align));
3090 if Known_Static_Esize (E)
3091 and then Esize (E) < Align * System_Storage_Unit
3092 then
3093 Set_Esize (E, UI_From_Int (Align * System_Storage_Unit));
3094 end if;
3095 end Set_Composite_Alignment;
3097 --------------------------
3098 -- Set_Discrete_RM_Size --
3099 --------------------------
3101 procedure Set_Discrete_RM_Size (Def_Id : Entity_Id) is
3102 FST : constant Entity_Id := First_Subtype (Def_Id);
3104 begin
3105 -- All discrete types except for the base types in standard are
3106 -- constrained, so indicate this by setting Is_Constrained.
3108 Set_Is_Constrained (Def_Id);
3110 -- Set generic types to have an unknown size, since the representation
3111 -- of a generic type is irrelevant, in view of the fact that they have
3112 -- nothing to do with code.
3114 if Is_Generic_Type (Root_Type (FST)) then
3115 Set_RM_Size (Def_Id, Uint_0);
3117 -- If the subtype statically matches the first subtype, then it is
3118 -- required to have exactly the same layout. This is required by
3119 -- aliasing considerations.
3121 elsif Def_Id /= FST and then
3122 Subtypes_Statically_Match (Def_Id, FST)
3123 then
3124 Set_RM_Size (Def_Id, RM_Size (FST));
3125 Set_Size_Info (Def_Id, FST);
3127 -- In all other cases the RM_Size is set to the minimum size. Note that
3128 -- this routine is never called for subtypes for which the RM_Size is
3129 -- set explicitly by an attribute clause.
3131 else
3132 Set_RM_Size (Def_Id, UI_From_Int (Minimum_Size (Def_Id)));
3133 end if;
3134 end Set_Discrete_RM_Size;
3136 ------------------------
3137 -- Set_Elem_Alignment --
3138 ------------------------
3140 procedure Set_Elem_Alignment (E : Entity_Id) is
3141 begin
3142 -- Do not set alignment for packed array types, unless we are doing
3143 -- front end layout, because otherwise this is always handled in the
3144 -- backend.
3146 if Is_Packed_Array_Impl_Type (E)
3147 and then not Frontend_Layout_On_Target
3148 then
3149 return;
3151 -- If there is an alignment clause, then we respect it
3153 elsif Has_Alignment_Clause (E) then
3154 return;
3156 -- If the size is not set, then don't attempt to set the alignment. This
3157 -- happens in the backend layout case for access-to-subprogram types.
3159 elsif not Known_Static_Esize (E) then
3160 return;
3162 -- For access types, do not set the alignment if the size is less than
3163 -- the allowed minimum size. This avoids cascaded error messages.
3165 elsif Is_Access_Type (E) and then Esize (E) < System_Address_Size then
3166 return;
3167 end if;
3169 -- Here we calculate the alignment as the largest power of two multiple
3170 -- of System.Storage_Unit that does not exceed either the object size of
3171 -- the type, or the maximum allowed alignment.
3173 declare
3174 S : Int;
3175 A : Nat;
3177 Max_Alignment : Nat;
3179 begin
3180 -- The given Esize may be larger that int'last because of a previous
3181 -- error, and the call to UI_To_Int will fail, so use default.
3183 if Esize (E) / SSU > Ttypes.Maximum_Alignment then
3184 S := Ttypes.Maximum_Alignment;
3186 -- If this is an access type and the target doesn't have strict
3187 -- alignment and we are not doing front end layout, then cap the
3188 -- alignment to that of a regular access type. This will avoid
3189 -- giving fat pointers twice the usual alignment for no practical
3190 -- benefit since the misalignment doesn't really matter.
3192 elsif Is_Access_Type (E)
3193 and then not Target_Strict_Alignment
3194 and then not Frontend_Layout_On_Target
3195 then
3196 S := System_Address_Size / SSU;
3198 else
3199 S := UI_To_Int (Esize (E)) / SSU;
3200 end if;
3202 -- If the default alignment of "double" floating-point types is
3203 -- specifically capped, enforce the cap.
3205 if Ttypes.Target_Double_Float_Alignment > 0
3206 and then S = 8
3207 and then Is_Floating_Point_Type (E)
3208 then
3209 Max_Alignment := Ttypes.Target_Double_Float_Alignment;
3211 -- If the default alignment of "double" or larger scalar types is
3212 -- specifically capped, enforce the cap.
3214 elsif Ttypes.Target_Double_Scalar_Alignment > 0
3215 and then S >= 8
3216 and then Is_Scalar_Type (E)
3217 then
3218 Max_Alignment := Ttypes.Target_Double_Scalar_Alignment;
3220 -- Otherwise enforce the overall alignment cap
3222 else
3223 Max_Alignment := Ttypes.Maximum_Alignment;
3224 end if;
3226 A := 1;
3227 while 2 * A <= Max_Alignment and then 2 * A <= S loop
3228 A := 2 * A;
3229 end loop;
3231 -- If alignment is currently not set, then we can safely set it to
3232 -- this new calculated value.
3234 if Unknown_Alignment (E) then
3235 Init_Alignment (E, A);
3237 -- Cases where we have inherited an alignment
3239 -- For constructed types, always reset the alignment, these are
3240 -- generally invisible to the user anyway, and that way we are
3241 -- sure that no constructed types have weird alignments.
3243 elsif not Comes_From_Source (E) then
3244 Init_Alignment (E, A);
3246 -- If this inherited alignment is the same as the one we computed,
3247 -- then obviously everything is fine, and we do not need to reset it.
3249 elsif Alignment (E) = A then
3250 null;
3252 else
3253 -- Now we come to the difficult cases of subtypes for which we
3254 -- have inherited an alignment different from the computed one.
3255 -- We resort to the presence of alignment and size clauses to
3256 -- guide our choices. Note that they can generally be present
3257 -- only on the first subtype (except for Object_Size) and that
3258 -- we need to look at the Rep_Item chain to correctly handle
3259 -- derived types.
3261 declare
3262 FST : constant Entity_Id := First_Subtype (E);
3264 function Has_Attribute_Clause
3265 (E : Entity_Id;
3266 Id : Attribute_Id) return Boolean;
3267 -- Wrapper around Get_Attribute_Definition_Clause which tests
3268 -- for the presence of the specified attribute clause.
3270 --------------------------
3271 -- Has_Attribute_Clause --
3272 --------------------------
3274 function Has_Attribute_Clause
3275 (E : Entity_Id;
3276 Id : Attribute_Id) return Boolean is
3277 begin
3278 return Present (Get_Attribute_Definition_Clause (E, Id));
3279 end Has_Attribute_Clause;
3281 begin
3282 -- If the alignment comes from a clause, then we respect it.
3283 -- Consider for example:
3285 -- type R is new Character;
3286 -- for R'Alignment use 1;
3287 -- for R'Size use 16;
3288 -- subtype S is R;
3290 -- Here R has a specified size of 16 and a specified alignment
3291 -- of 1, and it seems right for S to inherit both values.
3293 if Has_Attribute_Clause (FST, Attribute_Alignment) then
3294 null;
3296 -- Now we come to the cases where we have inherited alignment
3297 -- and size, and overridden the size but not the alignment.
3299 elsif Has_Attribute_Clause (FST, Attribute_Size)
3300 or else Has_Attribute_Clause (FST, Attribute_Object_Size)
3301 or else Has_Attribute_Clause (E, Attribute_Object_Size)
3302 then
3303 -- This is tricky, it might be thought that we should try to
3304 -- inherit the alignment, since that's what the RM implies,
3305 -- but that leads to complex rules and oddities. Consider
3306 -- for example:
3308 -- type R is new Character;
3309 -- for R'Size use 16;
3311 -- It seems quite bogus in this case to inherit an alignment
3312 -- of 1 from the parent type Character. Furthermore, if that
3313 -- is what the programmer really wanted for some odd reason,
3314 -- then he could specify the alignment directly.
3316 -- Moreover we really don't want to inherit the alignment in
3317 -- the case of a specified Object_Size for a subtype, since
3318 -- there would be no way of overriding to give a reasonable
3319 -- value (as we don't have an Object_Alignment attribute).
3320 -- Consider for example:
3322 -- subtype R is Character;
3323 -- for R'Object_Size use 16;
3325 -- If we inherit the alignment of 1, then it will be very
3326 -- inefficient for the subtype and this cannot be fixed.
3328 -- So we make the decision that if Size (or Object_Size) is
3329 -- given and the alignment is not specified with a clause,
3330 -- we reset the alignment to the appropriate value for the
3331 -- specified size. This is a nice simple rule to implement
3332 -- and document.
3334 -- There is a theoretical glitch, which is that a confirming
3335 -- size clause could now change the alignment, which, if we
3336 -- really think that confirming rep clauses should have no
3337 -- effect, could be seen as a no-no. However that's already
3338 -- implemented by Alignment_Check_For_Size_Change so we do
3339 -- not change the philosophy here.
3341 -- Historical note: in versions prior to Nov 6th, 2011, an
3342 -- odd distinction was made between inherited alignments
3343 -- larger than the computed alignment (where the larger
3344 -- alignment was inherited) and inherited alignments smaller
3345 -- than the computed alignment (where the smaller alignment
3346 -- was overridden). This was a dubious fix to get around an
3347 -- ACATS problem which seems to have disappeared anyway, and
3348 -- in any case, this peculiarity was never documented.
3350 Init_Alignment (E, A);
3352 -- If no Size (or Object_Size) was specified, then we have
3353 -- inherited the object size, so we should also inherit the
3354 -- alignment and not modify it.
3356 else
3357 null;
3358 end if;
3359 end;
3360 end if;
3361 end;
3362 end Set_Elem_Alignment;
3364 ----------------------
3365 -- SO_Ref_From_Expr --
3366 ----------------------
3368 function SO_Ref_From_Expr
3369 (Expr : Node_Id;
3370 Ins_Type : Entity_Id;
3371 Vtype : Entity_Id := Empty;
3372 Make_Func : Boolean := False) return Dynamic_SO_Ref
3374 Loc : constant Source_Ptr := Sloc (Ins_Type);
3375 K : constant Entity_Id := Make_Temporary (Loc, 'K');
3376 Decl : Node_Id;
3378 Vtype_Primary_View : Entity_Id;
3380 function Check_Node_V_Ref (N : Node_Id) return Traverse_Result;
3381 -- Function used to check one node for reference to V
3383 function Has_V_Ref is new Traverse_Func (Check_Node_V_Ref);
3384 -- Function used to traverse tree to check for reference to V
3386 ----------------------
3387 -- Check_Node_V_Ref --
3388 ----------------------
3390 function Check_Node_V_Ref (N : Node_Id) return Traverse_Result is
3391 begin
3392 if Nkind (N) = N_Identifier then
3393 if Chars (N) = Vname then
3394 return Abandon;
3395 else
3396 return Skip;
3397 end if;
3399 else
3400 return OK;
3401 end if;
3402 end Check_Node_V_Ref;
3404 -- Start of processing for SO_Ref_From_Expr
3406 begin
3407 -- Case of expression is an integer literal, in this case we just
3408 -- return the value (which must always be non-negative, since size
3409 -- and offset values can never be negative).
3411 if Nkind (Expr) = N_Integer_Literal then
3412 pragma Assert (Intval (Expr) >= 0);
3413 return Intval (Expr);
3414 end if;
3416 -- Case where there is a reference to V, create function
3418 if Has_V_Ref (Expr) = Abandon then
3420 pragma Assert (Present (Vtype));
3422 -- Check whether Vtype is a view of a private type and ensure that
3423 -- we use the primary view of the type (which is denoted by its
3424 -- Etype, whether it's the type's partial or full view entity).
3425 -- This is needed to make sure that we use the same (primary) view
3426 -- of the type for all V formals, whether the current view of the
3427 -- type is the partial or full view, so that types will always
3428 -- match on calls from one size function to another.
3430 if Has_Private_Declaration (Vtype) then
3431 Vtype_Primary_View := Etype (Vtype);
3432 else
3433 Vtype_Primary_View := Vtype;
3434 end if;
3436 Set_Is_Discrim_SO_Function (K);
3438 Decl :=
3439 Make_Subprogram_Body (Loc,
3441 Specification =>
3442 Make_Function_Specification (Loc,
3443 Defining_Unit_Name => K,
3444 Parameter_Specifications => New_List (
3445 Make_Parameter_Specification (Loc,
3446 Defining_Identifier =>
3447 Make_Defining_Identifier (Loc, Chars => Vname),
3448 Parameter_Type =>
3449 New_Occurrence_Of (Vtype_Primary_View, Loc))),
3450 Result_Definition =>
3451 New_Occurrence_Of (Standard_Unsigned, Loc)),
3453 Declarations => Empty_List,
3455 Handled_Statement_Sequence =>
3456 Make_Handled_Sequence_Of_Statements (Loc,
3457 Statements => New_List (
3458 Make_Simple_Return_Statement (Loc,
3459 Expression => Expr))));
3461 -- The caller requests that the expression be encapsulated in a
3462 -- parameterless function.
3464 elsif Make_Func then
3465 Decl :=
3466 Make_Subprogram_Body (Loc,
3468 Specification =>
3469 Make_Function_Specification (Loc,
3470 Defining_Unit_Name => K,
3471 Parameter_Specifications => Empty_List,
3472 Result_Definition =>
3473 New_Occurrence_Of (Standard_Unsigned, Loc)),
3475 Declarations => Empty_List,
3477 Handled_Statement_Sequence =>
3478 Make_Handled_Sequence_Of_Statements (Loc,
3479 Statements => New_List (
3480 Make_Simple_Return_Statement (Loc, Expression => Expr))));
3482 -- No reference to V and function not requested, so create a constant
3484 else
3485 Decl :=
3486 Make_Object_Declaration (Loc,
3487 Defining_Identifier => K,
3488 Object_Definition =>
3489 New_Occurrence_Of (Standard_Unsigned, Loc),
3490 Constant_Present => True,
3491 Expression => Expr);
3492 end if;
3494 Append_Freeze_Action (Ins_Type, Decl);
3495 Analyze (Decl);
3496 return Create_Dynamic_SO_Ref (K);
3497 end SO_Ref_From_Expr;
3499 end Layout;