Update concepts branch to revision 131834
[official-gcc.git] / gcc / ada / layout.adb
blobc6dec0aa379fd275e8cdc514b84f5290213e846b
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-2008, 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_Ch13; use Sem_Ch13;
40 with Sem_Eval; use Sem_Eval;
41 with Sem_Util; use Sem_Util;
42 with Sinfo; use Sinfo;
43 with Snames; use Snames;
44 with Stand; use Stand;
45 with Targparm; use Targparm;
46 with Tbuild; use Tbuild;
47 with Ttypes; use Ttypes;
48 with Uintp; use Uintp;
50 package body Layout is
52 ------------------------
53 -- Local Declarations --
54 ------------------------
56 SSU : constant Int := Ttypes.System_Storage_Unit;
57 -- Short hand for System_Storage_Unit
59 Vname : constant Name_Id := Name_uV;
60 -- Formal parameter name used for functions generated for size offset
61 -- values that depend on the discriminant. All such functions have the
62 -- following form:
64 -- function xxx (V : vtyp) return Unsigned is
65 -- begin
66 -- return ... expression involving V.discrim
67 -- end xxx;
69 -----------------------
70 -- Local Subprograms --
71 -----------------------
73 function Assoc_Add
74 (Loc : Source_Ptr;
75 Left_Opnd : Node_Id;
76 Right_Opnd : Node_Id) return Node_Id;
77 -- This is like Make_Op_Add except that it optimizes some cases knowing
78 -- that associative rearrangement is allowed for constant folding if one
79 -- of the operands is a compile time known value.
81 function Assoc_Multiply
82 (Loc : Source_Ptr;
83 Left_Opnd : Node_Id;
84 Right_Opnd : Node_Id) return Node_Id;
85 -- This is like Make_Op_Multiply except that it optimizes some cases
86 -- knowing that associative rearrangement is allowed for constant
87 -- folding if one of the operands is a compile time known value
89 function Assoc_Subtract
90 (Loc : Source_Ptr;
91 Left_Opnd : Node_Id;
92 Right_Opnd : Node_Id) return Node_Id;
93 -- This is like Make_Op_Subtract except that it optimizes some cases
94 -- knowing that associative rearrangement is allowed for constant
95 -- folding if one of the operands is a compile time known value
97 function Bits_To_SU (N : Node_Id) return Node_Id;
98 -- This is used when we cross the boundary from static sizes in bits to
99 -- dynamic sizes in storage units. If the argument N is anything other
100 -- than an integer literal, it is returned unchanged, but if it is an
101 -- integer literal, then it is taken as a size in bits, and is replaced
102 -- by the corresponding size in storage units.
104 function Compute_Length (Lo : Node_Id; Hi : Node_Id) return Node_Id;
105 -- Given expressions for the low bound (Lo) and the high bound (Hi),
106 -- Build an expression for the value hi-lo+1, converted to type
107 -- Standard.Unsigned. Takes care of the case where the operands
108 -- are of an enumeration type (so that the subtraction cannot be
109 -- done directly) by applying the Pos operator to Hi/Lo first.
111 function Expr_From_SO_Ref
112 (Loc : Source_Ptr;
113 D : SO_Ref;
114 Comp : Entity_Id := Empty) return Node_Id;
115 -- Given a value D from a size or offset field, return an expression
116 -- representing the value stored. If the value is known at compile time,
117 -- then an N_Integer_Literal is returned with the appropriate value. If
118 -- the value references a constant entity, then an N_Identifier node
119 -- referencing this entity is returned. If the value denotes a size
120 -- function, then returns a call node denoting the given function, with
121 -- a single actual parameter that either refers to the parameter V of
122 -- an enclosing size function (if Comp is Empty or its type doesn't match
123 -- the function's formal), or else is a selected component V.c when Comp
124 -- denotes a component c whose type matches that of the function formal.
125 -- The Loc value is used for the Sloc value of constructed notes.
127 function SO_Ref_From_Expr
128 (Expr : Node_Id;
129 Ins_Type : Entity_Id;
130 Vtype : Entity_Id := Empty;
131 Make_Func : Boolean := False) return Dynamic_SO_Ref;
132 -- This routine is used in the case where a size/offset value is dynamic
133 -- and is represented by the expression Expr. SO_Ref_From_Expr checks if
134 -- the Expr contains a reference to the identifier V, and if so builds
135 -- a function depending on discriminants of the formal parameter V which
136 -- is of type Vtype. Otherwise, if the parameter Make_Func is True, then
137 -- Expr will be encapsulated in a parameterless function; if Make_Func is
138 -- False, then a constant entity with the value Expr is built. The result
139 -- is a Dynamic_SO_Ref to the created entity. Note that Vtype can be
140 -- omitted if Expr does not contain any reference to V, the created entity.
141 -- The declaration created is inserted in the freeze actions of Ins_Type,
142 -- which also supplies the Sloc for created nodes. This function also takes
143 -- care of making sure that the expression is properly analyzed and
144 -- resolved (which may not be the case yet if we build the expression
145 -- in this unit).
147 function Get_Max_SU_Size (E : Entity_Id) return Node_Id;
148 -- E is an array type or subtype that has at least one index bound that
149 -- is the value of a record discriminant. For such an array, the function
150 -- computes an expression that yields the maximum possible size of the
151 -- array in storage units. The result is not defined for any other type,
152 -- or for arrays that do not depend on discriminants, and it is a fatal
153 -- error to call this unless Size_Depends_On_Discriminant (E) is True.
155 procedure Layout_Array_Type (E : Entity_Id);
156 -- Front-end layout of non-bit-packed array type or subtype
158 procedure Layout_Record_Type (E : Entity_Id);
159 -- Front-end layout of record type
161 procedure Rewrite_Integer (N : Node_Id; V : Uint);
162 -- Rewrite node N with an integer literal whose value is V. The Sloc
163 -- for the new node is taken from N, and the type of the literal is
164 -- set to a copy of the type of N on entry.
166 procedure Set_And_Check_Static_Size
167 (E : Entity_Id;
168 Esiz : SO_Ref;
169 RM_Siz : SO_Ref);
170 -- This procedure is called to check explicit given sizes (possibly
171 -- stored in the Esize and RM_Size fields of E) against computed
172 -- Object_Size (Esiz) and Value_Size (RM_Siz) values. Appropriate
173 -- errors and warnings are posted if specified sizes are inconsistent
174 -- with specified sizes. On return, the Esize and RM_Size fields of
175 -- E are set (either from previously given values, or from the newly
176 -- computed values, as appropriate).
178 procedure Set_Composite_Alignment (E : Entity_Id);
179 -- This procedure is called for record types and subtypes, and also for
180 -- atomic array types and subtypes. If no alignment is set, and the size
181 -- is 2 or 4 (or 8 if the word size is 8), then the alignment is set to
182 -- match the size.
184 ----------------------------
185 -- Adjust_Esize_Alignment --
186 ----------------------------
188 procedure Adjust_Esize_Alignment (E : Entity_Id) is
189 Abits : Int;
190 Esize_Set : Boolean;
192 begin
193 -- Nothing to do if size unknown
195 if Unknown_Esize (E) then
196 return;
197 end if;
199 -- Determine if size is constrained by an attribute definition clause
200 -- which must be obeyed. If so, we cannot increase the size in this
201 -- routine.
203 -- For a type, the issue is whether an object size clause has been
204 -- set. A normal size clause constrains only the value size (RM_Size)
206 if Is_Type (E) then
207 Esize_Set := Has_Object_Size_Clause (E);
209 -- For an object, the issue is whether a size clause is present
211 else
212 Esize_Set := Has_Size_Clause (E);
213 end if;
215 -- If size is known it must be a multiple of the storage unit size
217 if Esize (E) mod SSU /= 0 then
219 -- If not, and size specified, then give error
221 if Esize_Set then
222 Error_Msg_NE
223 ("size for& not a multiple of storage unit size",
224 Size_Clause (E), E);
225 return;
227 -- Otherwise bump up size to a storage unit boundary
229 else
230 Set_Esize (E, (Esize (E) + SSU - 1) / SSU * SSU);
231 end if;
232 end if;
234 -- Now we have the size set, it must be a multiple of the alignment
235 -- nothing more we can do here if the alignment is unknown here.
237 if Unknown_Alignment (E) then
238 return;
239 end if;
241 -- At this point both the Esize and Alignment are known, so we need
242 -- to make sure they are consistent.
244 Abits := UI_To_Int (Alignment (E)) * SSU;
246 if Esize (E) mod Abits = 0 then
247 return;
248 end if;
250 -- Here we have a situation where the Esize is not a multiple of
251 -- the alignment. We must either increase Esize or reduce the
252 -- alignment to correct this situation.
254 -- The case in which we can decrease the alignment is where the
255 -- alignment was not set by an alignment clause, and the type in
256 -- question is a discrete type, where it is definitely safe to
257 -- reduce the alignment. For example:
259 -- t : integer range 1 .. 2;
260 -- for t'size use 8;
262 -- In this situation, the initial alignment of t is 4, copied from
263 -- the Integer base type, but it is safe to reduce it to 1 at this
264 -- stage, since we will only be loading a single storage unit.
266 if Is_Discrete_Type (Etype (E))
267 and then not Has_Alignment_Clause (E)
268 then
269 loop
270 Abits := Abits / 2;
271 exit when Esize (E) mod Abits = 0;
272 end loop;
274 Init_Alignment (E, Abits / SSU);
275 return;
276 end if;
278 -- Now the only possible approach left is to increase the Esize
279 -- but we can't do that if the size was set by a specific clause.
281 if Esize_Set then
282 Error_Msg_NE
283 ("size for& is not a multiple of alignment",
284 Size_Clause (E), E);
286 -- Otherwise we can indeed increase the size to a multiple of alignment
288 else
289 Set_Esize (E, ((Esize (E) + (Abits - 1)) / Abits) * Abits);
290 end if;
291 end Adjust_Esize_Alignment;
293 ---------------
294 -- Assoc_Add --
295 ---------------
297 function Assoc_Add
298 (Loc : Source_Ptr;
299 Left_Opnd : Node_Id;
300 Right_Opnd : Node_Id) return Node_Id
302 L : Node_Id;
303 R : Uint;
305 begin
306 -- Case of right operand is a constant
308 if Compile_Time_Known_Value (Right_Opnd) then
309 L := Left_Opnd;
310 R := Expr_Value (Right_Opnd);
312 -- Case of left operand is a constant
314 elsif Compile_Time_Known_Value (Left_Opnd) then
315 L := Right_Opnd;
316 R := Expr_Value (Left_Opnd);
318 -- Neither operand is a constant, do the addition with no optimization
320 else
321 return Make_Op_Add (Loc, Left_Opnd, Right_Opnd);
322 end if;
324 -- Case of left operand is an addition
326 if Nkind (L) = N_Op_Add then
328 -- (C1 + E) + C2 = (C1 + C2) + E
330 if Compile_Time_Known_Value (Sinfo.Left_Opnd (L)) then
331 Rewrite_Integer
332 (Sinfo.Left_Opnd (L),
333 Expr_Value (Sinfo.Left_Opnd (L)) + R);
334 return L;
336 -- (E + C1) + C2 = E + (C1 + C2)
338 elsif Compile_Time_Known_Value (Sinfo.Right_Opnd (L)) then
339 Rewrite_Integer
340 (Sinfo.Right_Opnd (L),
341 Expr_Value (Sinfo.Right_Opnd (L)) + R);
342 return L;
343 end if;
345 -- Case of left operand is a subtraction
347 elsif Nkind (L) = N_Op_Subtract then
349 -- (C1 - E) + C2 = (C1 + C2) + E
351 if Compile_Time_Known_Value (Sinfo.Left_Opnd (L)) then
352 Rewrite_Integer
353 (Sinfo.Left_Opnd (L),
354 Expr_Value (Sinfo.Left_Opnd (L)) + R);
355 return L;
357 -- (E - C1) + C2 = E - (C1 - C2)
359 elsif Compile_Time_Known_Value (Sinfo.Right_Opnd (L)) then
360 Rewrite_Integer
361 (Sinfo.Right_Opnd (L),
362 Expr_Value (Sinfo.Right_Opnd (L)) - R);
363 return L;
364 end if;
365 end if;
367 -- Not optimizable, do the addition
369 return Make_Op_Add (Loc, Left_Opnd, Right_Opnd);
370 end Assoc_Add;
372 --------------------
373 -- Assoc_Multiply --
374 --------------------
376 function Assoc_Multiply
377 (Loc : Source_Ptr;
378 Left_Opnd : Node_Id;
379 Right_Opnd : Node_Id) return Node_Id
381 L : Node_Id;
382 R : Uint;
384 begin
385 -- Case of right operand is a constant
387 if Compile_Time_Known_Value (Right_Opnd) then
388 L := Left_Opnd;
389 R := Expr_Value (Right_Opnd);
391 -- Case of left operand is a constant
393 elsif Compile_Time_Known_Value (Left_Opnd) then
394 L := Right_Opnd;
395 R := Expr_Value (Left_Opnd);
397 -- Neither operand is a constant, do the multiply with no optimization
399 else
400 return Make_Op_Multiply (Loc, Left_Opnd, Right_Opnd);
401 end if;
403 -- Case of left operand is an multiplication
405 if Nkind (L) = N_Op_Multiply then
407 -- (C1 * E) * C2 = (C1 * C2) + E
409 if Compile_Time_Known_Value (Sinfo.Left_Opnd (L)) then
410 Rewrite_Integer
411 (Sinfo.Left_Opnd (L),
412 Expr_Value (Sinfo.Left_Opnd (L)) * R);
413 return L;
415 -- (E * C1) * C2 = E * (C1 * C2)
417 elsif Compile_Time_Known_Value (Sinfo.Right_Opnd (L)) then
418 Rewrite_Integer
419 (Sinfo.Right_Opnd (L),
420 Expr_Value (Sinfo.Right_Opnd (L)) * R);
421 return L;
422 end if;
423 end if;
425 -- Not optimizable, do the multiplication
427 return Make_Op_Multiply (Loc, Left_Opnd, Right_Opnd);
428 end Assoc_Multiply;
430 --------------------
431 -- Assoc_Subtract --
432 --------------------
434 function Assoc_Subtract
435 (Loc : Source_Ptr;
436 Left_Opnd : Node_Id;
437 Right_Opnd : Node_Id) return Node_Id
439 L : Node_Id;
440 R : Uint;
442 begin
443 -- Case of right operand is a constant
445 if Compile_Time_Known_Value (Right_Opnd) then
446 L := Left_Opnd;
447 R := Expr_Value (Right_Opnd);
449 -- Right operand is a constant, do the subtract with no optimization
451 else
452 return Make_Op_Subtract (Loc, Left_Opnd, Right_Opnd);
453 end if;
455 -- Case of left operand is an addition
457 if Nkind (L) = N_Op_Add then
459 -- (C1 + E) - C2 = (C1 - C2) + E
461 if Compile_Time_Known_Value (Sinfo.Left_Opnd (L)) then
462 Rewrite_Integer
463 (Sinfo.Left_Opnd (L),
464 Expr_Value (Sinfo.Left_Opnd (L)) - R);
465 return L;
467 -- (E + C1) - C2 = E + (C1 - C2)
469 elsif Compile_Time_Known_Value (Sinfo.Right_Opnd (L)) then
470 Rewrite_Integer
471 (Sinfo.Right_Opnd (L),
472 Expr_Value (Sinfo.Right_Opnd (L)) - R);
473 return L;
474 end if;
476 -- Case of left operand is a subtraction
478 elsif Nkind (L) = N_Op_Subtract then
480 -- (C1 - E) - C2 = (C1 - C2) + E
482 if Compile_Time_Known_Value (Sinfo.Left_Opnd (L)) then
483 Rewrite_Integer
484 (Sinfo.Left_Opnd (L),
485 Expr_Value (Sinfo.Left_Opnd (L)) + R);
486 return L;
488 -- (E - C1) - C2 = E - (C1 + C2)
490 elsif Compile_Time_Known_Value (Sinfo.Right_Opnd (L)) then
491 Rewrite_Integer
492 (Sinfo.Right_Opnd (L),
493 Expr_Value (Sinfo.Right_Opnd (L)) + R);
494 return L;
495 end if;
496 end if;
498 -- Not optimizable, do the subtraction
500 return Make_Op_Subtract (Loc, Left_Opnd, Right_Opnd);
501 end Assoc_Subtract;
503 ----------------
504 -- Bits_To_SU --
505 ----------------
507 function Bits_To_SU (N : Node_Id) return Node_Id is
508 begin
509 if Nkind (N) = N_Integer_Literal then
510 Set_Intval (N, (Intval (N) + (SSU - 1)) / SSU);
511 end if;
513 return N;
514 end Bits_To_SU;
516 --------------------
517 -- Compute_Length --
518 --------------------
520 function Compute_Length (Lo : Node_Id; Hi : Node_Id) return Node_Id is
521 Loc : constant Source_Ptr := Sloc (Lo);
522 Typ : constant Entity_Id := Etype (Lo);
523 Lo_Op : Node_Id;
524 Hi_Op : Node_Id;
525 Lo_Dim : Uint;
526 Hi_Dim : Uint;
528 begin
529 -- If the bounds are First and Last attributes for the same dimension
530 -- and both have prefixes that denotes the same entity, then we create
531 -- and return a Length attribute. This may allow the back end to
532 -- generate better code in cases where it already has the length.
534 if Nkind (Lo) = N_Attribute_Reference
535 and then Attribute_Name (Lo) = Name_First
536 and then Nkind (Hi) = N_Attribute_Reference
537 and then Attribute_Name (Hi) = Name_Last
538 and then Is_Entity_Name (Prefix (Lo))
539 and then Is_Entity_Name (Prefix (Hi))
540 and then Entity (Prefix (Lo)) = Entity (Prefix (Hi))
541 then
542 Lo_Dim := Uint_1;
543 Hi_Dim := Uint_1;
545 if Present (First (Expressions (Lo))) then
546 Lo_Dim := Expr_Value (First (Expressions (Lo)));
547 end if;
549 if Present (First (Expressions (Hi))) then
550 Hi_Dim := Expr_Value (First (Expressions (Hi)));
551 end if;
553 if Lo_Dim = Hi_Dim then
554 return
555 Make_Attribute_Reference (Loc,
556 Prefix => New_Occurrence_Of
557 (Entity (Prefix (Lo)), Loc),
558 Attribute_Name => Name_Length,
559 Expressions => New_List
560 (Make_Integer_Literal (Loc, Lo_Dim)));
561 end if;
562 end if;
564 Lo_Op := New_Copy_Tree (Lo);
565 Hi_Op := New_Copy_Tree (Hi);
567 -- If type is enumeration type, then use Pos attribute to convert
568 -- to integer type for which subtraction is a permitted operation.
570 if Is_Enumeration_Type (Typ) then
571 Lo_Op :=
572 Make_Attribute_Reference (Loc,
573 Prefix => New_Occurrence_Of (Typ, Loc),
574 Attribute_Name => Name_Pos,
575 Expressions => New_List (Lo_Op));
577 Hi_Op :=
578 Make_Attribute_Reference (Loc,
579 Prefix => New_Occurrence_Of (Typ, Loc),
580 Attribute_Name => Name_Pos,
581 Expressions => New_List (Hi_Op));
582 end if;
584 return
585 Assoc_Add (Loc,
586 Left_Opnd =>
587 Assoc_Subtract (Loc,
588 Left_Opnd => Hi_Op,
589 Right_Opnd => Lo_Op),
590 Right_Opnd => Make_Integer_Literal (Loc, 1));
591 end Compute_Length;
593 ----------------------
594 -- Expr_From_SO_Ref --
595 ----------------------
597 function Expr_From_SO_Ref
598 (Loc : Source_Ptr;
599 D : SO_Ref;
600 Comp : Entity_Id := Empty) return Node_Id
602 Ent : Entity_Id;
604 begin
605 if Is_Dynamic_SO_Ref (D) then
606 Ent := Get_Dynamic_SO_Entity (D);
608 if Is_Discrim_SO_Function (Ent) then
609 -- If a component is passed in whose type matches the type
610 -- of the function formal, then select that component from
611 -- the "V" parameter rather than passing "V" directly.
613 if Present (Comp)
614 and then Base_Type (Etype (Comp))
615 = Base_Type (Etype (First_Formal (Ent)))
616 then
617 return
618 Make_Function_Call (Loc,
619 Name => New_Occurrence_Of (Ent, Loc),
620 Parameter_Associations => New_List (
621 Make_Selected_Component (Loc,
622 Prefix => Make_Identifier (Loc, Chars => Vname),
623 Selector_Name => New_Occurrence_Of (Comp, Loc))));
625 else
626 return
627 Make_Function_Call (Loc,
628 Name => New_Occurrence_Of (Ent, Loc),
629 Parameter_Associations => New_List (
630 Make_Identifier (Loc, Chars => Vname)));
631 end if;
633 else
634 return New_Occurrence_Of (Ent, Loc);
635 end if;
637 else
638 return Make_Integer_Literal (Loc, D);
639 end if;
640 end Expr_From_SO_Ref;
642 ---------------------
643 -- Get_Max_SU_Size --
644 ---------------------
646 function Get_Max_SU_Size (E : Entity_Id) return Node_Id is
647 Loc : constant Source_Ptr := Sloc (E);
648 Indx : Node_Id;
649 Ityp : Entity_Id;
650 Lo : Node_Id;
651 Hi : Node_Id;
652 S : Uint;
653 Len : Node_Id;
655 type Val_Status_Type is (Const, Dynamic);
657 type Val_Type (Status : Val_Status_Type := Const) is
658 record
659 case Status is
660 when Const => Val : Uint;
661 when Dynamic => Nod : Node_Id;
662 end case;
663 end record;
664 -- Shows the status of the value so far. Const means that the value
665 -- is constant, and Val is the current constant value. Dynamic means
666 -- that the value is dynamic, and in this case Nod is the Node_Id of
667 -- the expression to compute the value.
669 Size : Val_Type;
670 -- Calculated value so far if Size.Status = Const,
671 -- or expression value so far if Size.Status = Dynamic.
673 SU_Convert_Required : Boolean := False;
674 -- This is set to True if the final result must be converted from
675 -- bits to storage units (rounding up to a storage unit boundary).
677 -----------------------
678 -- Local Subprograms --
679 -----------------------
681 procedure Max_Discrim (N : in out Node_Id);
682 -- If the node N represents a discriminant, replace it by the maximum
683 -- value of the discriminant.
685 procedure Min_Discrim (N : in out Node_Id);
686 -- If the node N represents a discriminant, replace it by the minimum
687 -- value of the discriminant.
689 -----------------
690 -- Max_Discrim --
691 -----------------
693 procedure Max_Discrim (N : in out Node_Id) is
694 begin
695 if Nkind (N) = N_Identifier
696 and then Ekind (Entity (N)) = E_Discriminant
697 then
698 N := Type_High_Bound (Etype (N));
699 end if;
700 end Max_Discrim;
702 -----------------
703 -- Min_Discrim --
704 -----------------
706 procedure Min_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_Low_Bound (Etype (N));
712 end if;
713 end Min_Discrim;
715 -- Start of processing for Get_Max_SU_Size
717 begin
718 pragma Assert (Size_Depends_On_Discriminant (E));
720 -- Initialize status from component size
722 if Known_Static_Component_Size (E) then
723 Size := (Const, Component_Size (E));
725 else
726 Size := (Dynamic, Expr_From_SO_Ref (Loc, Component_Size (E)));
727 end if;
729 -- Loop through indices
731 Indx := First_Index (E);
732 while Present (Indx) loop
733 Ityp := Etype (Indx);
734 Lo := Type_Low_Bound (Ityp);
735 Hi := Type_High_Bound (Ityp);
737 Min_Discrim (Lo);
738 Max_Discrim (Hi);
740 -- Value of the current subscript range is statically known
742 if Compile_Time_Known_Value (Lo)
743 and then Compile_Time_Known_Value (Hi)
744 then
745 S := Expr_Value (Hi) - Expr_Value (Lo) + 1;
747 -- If known flat bound, entire size of array is zero!
749 if S <= 0 then
750 return Make_Integer_Literal (Loc, 0);
751 end if;
753 -- Current value is constant, evolve value
755 if Size.Status = Const then
756 Size.Val := Size.Val * S;
758 -- Current value is dynamic
760 else
761 -- An interesting little optimization, if we have a pending
762 -- conversion from bits to storage units, and the current
763 -- length is a multiple of the storage unit size, then we
764 -- can take the factor out here statically, avoiding some
765 -- extra dynamic computations at the end.
767 if SU_Convert_Required and then S mod SSU = 0 then
768 S := S / SSU;
769 SU_Convert_Required := False;
770 end if;
772 Size.Nod :=
773 Assoc_Multiply (Loc,
774 Left_Opnd => Size.Nod,
775 Right_Opnd =>
776 Make_Integer_Literal (Loc, Intval => S));
777 end if;
779 -- Value of the current subscript range is dynamic
781 else
782 -- If the current size value is constant, then here is where we
783 -- make a transition to dynamic values, which are always stored
784 -- in storage units, However, we do not want to convert to SU's
785 -- too soon, consider the case of a packed array of single bits,
786 -- we want to do the SU conversion after computing the size in
787 -- this case.
789 if Size.Status = Const then
791 -- If the current value is a multiple of the storage unit,
792 -- then most certainly we can do the conversion now, simply
793 -- by dividing the current value by the storage unit value.
794 -- If this works, we set SU_Convert_Required to False.
796 if Size.Val mod SSU = 0 then
798 Size :=
799 (Dynamic, Make_Integer_Literal (Loc, Size.Val / SSU));
800 SU_Convert_Required := False;
802 -- Otherwise, we go ahead and convert the value in bits,
803 -- and set SU_Convert_Required to True to ensure that the
804 -- final value is indeed properly converted.
806 else
807 Size := (Dynamic, Make_Integer_Literal (Loc, Size.Val));
808 SU_Convert_Required := True;
809 end if;
810 end if;
812 -- Length is hi-lo+1
814 Len := Compute_Length (Lo, Hi);
816 -- Check possible range of Len
818 declare
819 OK : Boolean;
820 LLo : Uint;
821 LHi : Uint;
822 pragma Warnings (Off, LHi);
824 begin
825 Set_Parent (Len, E);
826 Determine_Range (Len, OK, LLo, LHi);
828 Len := Convert_To (Standard_Unsigned, Len);
830 -- If we cannot verify that range cannot be super-flat,
831 -- we need a max with zero, since length must be non-neg.
833 if not OK or else LLo < 0 then
834 Len :=
835 Make_Attribute_Reference (Loc,
836 Prefix =>
837 New_Occurrence_Of (Standard_Unsigned, Loc),
838 Attribute_Name => Name_Max,
839 Expressions => New_List (
840 Make_Integer_Literal (Loc, 0),
841 Len));
842 end if;
843 end;
844 end if;
846 Next_Index (Indx);
847 end loop;
849 -- Here after processing all bounds to set sizes. If the value is
850 -- a constant, then it is bits, so we convert to storage units.
852 if Size.Status = Const then
853 return Bits_To_SU (Make_Integer_Literal (Loc, Size.Val));
855 -- Case where the value is dynamic
857 else
858 -- Do convert from bits to SU's if needed
860 if SU_Convert_Required then
862 -- The expression required is (Size.Nod + SU - 1) / SU
864 Size.Nod :=
865 Make_Op_Divide (Loc,
866 Left_Opnd =>
867 Make_Op_Add (Loc,
868 Left_Opnd => Size.Nod,
869 Right_Opnd => Make_Integer_Literal (Loc, SSU - 1)),
870 Right_Opnd => Make_Integer_Literal (Loc, SSU));
871 end if;
873 return Size.Nod;
874 end if;
875 end Get_Max_SU_Size;
877 -----------------------
878 -- Layout_Array_Type --
879 -----------------------
881 procedure Layout_Array_Type (E : Entity_Id) is
882 Loc : constant Source_Ptr := Sloc (E);
883 Ctyp : constant Entity_Id := Component_Type (E);
884 Indx : Node_Id;
885 Ityp : Entity_Id;
886 Lo : Node_Id;
887 Hi : Node_Id;
888 S : Uint;
889 Len : Node_Id;
891 Insert_Typ : Entity_Id;
892 -- This is the type with which any generated constants or functions
893 -- will be associated (i.e. inserted into the freeze actions). This
894 -- is normally the type being laid out. The exception occurs when
895 -- we are laying out Itype's which are local to a record type, and
896 -- whose scope is this record type. Such types do not have freeze
897 -- nodes (because we have no place to put them).
899 ------------------------------------
900 -- How An Array Type is Laid Out --
901 ------------------------------------
903 -- Here is what goes on. We need to multiply the component size of
904 -- the array (which has already been set) by the length of each of
905 -- the indexes. If all these values are known at compile time, then
906 -- the resulting size of the array is the appropriate constant value.
908 -- If the component size or at least one bound is dynamic (but no
909 -- discriminants are present), then the size will be computed as an
910 -- expression that calculates the proper size.
912 -- If there is at least one discriminant bound, then the size is also
913 -- computed as an expression, but this expression contains discriminant
914 -- values which are obtained by selecting from a function parameter, and
915 -- the size is given by a function that is passed the variant record in
916 -- question, and whose body is the expression.
918 type Val_Status_Type is (Const, Dynamic, Discrim);
920 type Val_Type (Status : Val_Status_Type := Const) is
921 record
922 case Status is
923 when Const =>
924 Val : Uint;
925 -- Calculated value so far if Val_Status = Const
927 when Dynamic | Discrim =>
928 Nod : Node_Id;
929 -- Expression value so far if Val_Status /= Const
931 end case;
932 end record;
933 -- Records the value or expression computed so far. Const means that
934 -- the value is constant, and Val is the current constant value.
935 -- Dynamic means that the value is dynamic, and in this case Nod is
936 -- the Node_Id of the expression to compute the value, and Discrim
937 -- means that at least one bound is a discriminant, in which case Nod
938 -- is the expression so far (which will be the body of the function).
940 Size : Val_Type;
941 -- Value of size computed so far. See comments above
943 Vtyp : Entity_Id := Empty;
944 -- Variant record type for the formal parameter of the
945 -- discriminant function V if Status = Discrim.
947 SU_Convert_Required : Boolean := False;
948 -- This is set to True if the final result must be converted from
949 -- bits to storage units (rounding up to a storage unit boundary).
951 Storage_Divisor : Uint := UI_From_Int (SSU);
952 -- This is the amount that a nonstatic computed size will be divided
953 -- by to convert it from bits to storage units. This is normally
954 -- equal to SSU, but can be reduced in the case of packed components
955 -- that fit evenly into a storage unit.
957 Make_Size_Function : Boolean := False;
958 -- Indicates whether to request that SO_Ref_From_Expr should
959 -- encapsulate the array size expression in a function.
961 procedure Discrimify (N : in out Node_Id);
962 -- If N represents a discriminant, then the Size.Status is set to
963 -- Discrim, and Vtyp is set. The parameter N is replaced with the
964 -- proper expression to extract the discriminant value from V.
966 ----------------
967 -- Discrimify --
968 ----------------
970 procedure Discrimify (N : in out Node_Id) is
971 Decl : Node_Id;
972 Typ : Entity_Id;
974 begin
975 if Nkind (N) = N_Identifier
976 and then Ekind (Entity (N)) = E_Discriminant
977 then
978 Set_Size_Depends_On_Discriminant (E);
980 if Size.Status /= Discrim then
981 Decl := Parent (Parent (Entity (N)));
982 Size := (Discrim, Size.Nod);
983 Vtyp := Defining_Identifier (Decl);
984 end if;
986 Typ := Etype (N);
988 N :=
989 Make_Selected_Component (Loc,
990 Prefix => Make_Identifier (Loc, Chars => Vname),
991 Selector_Name => New_Occurrence_Of (Entity (N), Loc));
993 -- Set the Etype attributes of the selected name and its prefix.
994 -- Analyze_And_Resolve can't be called here because the Vname
995 -- entity denoted by the prefix will not yet exist (it's created
996 -- by SO_Ref_From_Expr, called at the end of Layout_Array_Type).
998 Set_Etype (Prefix (N), Vtyp);
999 Set_Etype (N, Typ);
1000 end if;
1001 end Discrimify;
1003 -- Start of processing for Layout_Array_Type
1005 begin
1006 -- Default alignment is component alignment
1008 if Unknown_Alignment (E) then
1009 Set_Alignment (E, Alignment (Ctyp));
1010 end if;
1012 -- Calculate proper type for insertions
1014 if Is_Record_Type (Underlying_Type (Scope (E))) then
1015 Insert_Typ := Underlying_Type (Scope (E));
1016 else
1017 Insert_Typ := E;
1018 end if;
1020 -- If the component type is a generic formal type then there's no point
1021 -- in determining a size for the array type.
1023 if Is_Generic_Type (Ctyp) then
1024 return;
1025 end if;
1027 -- Deal with component size if base type
1029 if Ekind (E) = E_Array_Type then
1031 -- Cannot do anything if Esize of component type unknown
1033 if Unknown_Esize (Ctyp) then
1034 return;
1035 end if;
1037 -- Set component size if not set already
1039 if Unknown_Component_Size (E) then
1040 Set_Component_Size (E, Esize (Ctyp));
1041 end if;
1042 end if;
1044 -- (RM 13.3 (48)) says that the size of an unconstrained array
1045 -- is implementation defined. We choose to leave it as Unknown
1046 -- here, and the actual behavior is determined by the back end.
1048 if not Is_Constrained (E) then
1049 return;
1050 end if;
1052 -- Initialize status from component size
1054 if Known_Static_Component_Size (E) then
1055 Size := (Const, Component_Size (E));
1057 else
1058 Size := (Dynamic, Expr_From_SO_Ref (Loc, Component_Size (E)));
1059 end if;
1061 -- Loop to process array indices
1063 Indx := First_Index (E);
1064 while Present (Indx) loop
1065 Ityp := Etype (Indx);
1067 -- If an index of the array is a generic formal type then there's
1068 -- no point in determining a size for the array type.
1070 if Is_Generic_Type (Ityp) then
1071 return;
1072 end if;
1074 Lo := Type_Low_Bound (Ityp);
1075 Hi := Type_High_Bound (Ityp);
1077 -- Value of the current subscript range is statically known
1079 if Compile_Time_Known_Value (Lo)
1080 and then Compile_Time_Known_Value (Hi)
1081 then
1082 S := Expr_Value (Hi) - Expr_Value (Lo) + 1;
1084 -- If known flat bound, entire size of array is zero!
1086 if S <= 0 then
1087 Set_Esize (E, Uint_0);
1088 Set_RM_Size (E, Uint_0);
1089 return;
1090 end if;
1092 -- If constant, evolve value
1094 if Size.Status = Const then
1095 Size.Val := Size.Val * S;
1097 -- Current value is dynamic
1099 else
1100 -- An interesting little optimization, if we have a pending
1101 -- conversion from bits to storage units, and the current
1102 -- length is a multiple of the storage unit size, then we
1103 -- can take the factor out here statically, avoiding some
1104 -- extra dynamic computations at the end.
1106 if SU_Convert_Required and then S mod SSU = 0 then
1107 S := S / SSU;
1108 SU_Convert_Required := False;
1109 end if;
1111 -- Now go ahead and evolve the expression
1113 Size.Nod :=
1114 Assoc_Multiply (Loc,
1115 Left_Opnd => Size.Nod,
1116 Right_Opnd =>
1117 Make_Integer_Literal (Loc, Intval => S));
1118 end if;
1120 -- Value of the current subscript range is dynamic
1122 else
1123 -- If the current size value is constant, then here is where we
1124 -- make a transition to dynamic values, which are always stored
1125 -- in storage units, However, we do not want to convert to SU's
1126 -- too soon, consider the case of a packed array of single bits,
1127 -- we want to do the SU conversion after computing the size in
1128 -- this case.
1130 if Size.Status = Const then
1132 -- If the current value is a multiple of the storage unit,
1133 -- then most certainly we can do the conversion now, simply
1134 -- by dividing the current value by the storage unit value.
1135 -- If this works, we set SU_Convert_Required to False.
1137 if Size.Val mod SSU = 0 then
1138 Size :=
1139 (Dynamic, Make_Integer_Literal (Loc, Size.Val / SSU));
1140 SU_Convert_Required := False;
1142 -- If the current value is a factor of the storage unit,
1143 -- then we can use a value of one for the size and reduce
1144 -- the strength of the later division.
1146 elsif SSU mod Size.Val = 0 then
1147 Storage_Divisor := SSU / Size.Val;
1148 Size := (Dynamic, Make_Integer_Literal (Loc, Uint_1));
1149 SU_Convert_Required := True;
1151 -- Otherwise, we go ahead and convert the value in bits,
1152 -- and set SU_Convert_Required to True to ensure that the
1153 -- final value is indeed properly converted.
1155 else
1156 Size := (Dynamic, Make_Integer_Literal (Loc, Size.Val));
1157 SU_Convert_Required := True;
1158 end if;
1159 end if;
1161 Discrimify (Lo);
1162 Discrimify (Hi);
1164 -- Length is hi-lo+1
1166 Len := Compute_Length (Lo, Hi);
1168 -- If Len isn't a Length attribute, then its range needs to
1169 -- be checked a possible Max with zero needs to be computed.
1171 if Nkind (Len) /= N_Attribute_Reference
1172 or else Attribute_Name (Len) /= Name_Length
1173 then
1174 declare
1175 OK : Boolean;
1176 LLo : Uint;
1177 LHi : Uint;
1179 begin
1180 -- Check possible range of Len
1182 Set_Parent (Len, E);
1183 Determine_Range (Len, OK, LLo, LHi);
1185 Len := Convert_To (Standard_Unsigned, Len);
1187 -- If range definitely flat or superflat,
1188 -- result size is zero
1190 if OK and then LHi <= 0 then
1191 Set_Esize (E, Uint_0);
1192 Set_RM_Size (E, Uint_0);
1193 return;
1194 end if;
1196 -- If we cannot verify that range cannot be super-flat,
1197 -- we need a maximum with zero, since length cannot be
1198 -- negative.
1200 if not OK or else LLo < 0 then
1201 Len :=
1202 Make_Attribute_Reference (Loc,
1203 Prefix =>
1204 New_Occurrence_Of (Standard_Unsigned, Loc),
1205 Attribute_Name => Name_Max,
1206 Expressions => New_List (
1207 Make_Integer_Literal (Loc, 0),
1208 Len));
1209 end if;
1210 end;
1211 end if;
1213 -- At this stage, Len has the expression for the length
1215 Size.Nod :=
1216 Assoc_Multiply (Loc,
1217 Left_Opnd => Size.Nod,
1218 Right_Opnd => Len);
1219 end if;
1221 Next_Index (Indx);
1222 end loop;
1224 -- Here after processing all bounds to set sizes. If the value is
1225 -- a constant, then it is bits, and the only thing we need to do
1226 -- is to check against explicit given size and do alignment adjust.
1228 if Size.Status = Const then
1229 Set_And_Check_Static_Size (E, Size.Val, Size.Val);
1230 Adjust_Esize_Alignment (E);
1232 -- Case where the value is dynamic
1234 else
1235 -- Do convert from bits to SU's if needed
1237 if SU_Convert_Required then
1239 -- The expression required is:
1240 -- (Size.Nod + Storage_Divisor - 1) / Storage_Divisor
1242 Size.Nod :=
1243 Make_Op_Divide (Loc,
1244 Left_Opnd =>
1245 Make_Op_Add (Loc,
1246 Left_Opnd => Size.Nod,
1247 Right_Opnd => Make_Integer_Literal
1248 (Loc, Storage_Divisor - 1)),
1249 Right_Opnd => Make_Integer_Literal (Loc, Storage_Divisor));
1250 end if;
1252 -- If the array entity is not declared at the library level and its
1253 -- not nested within a subprogram that is marked for inlining, then
1254 -- we request that the size expression be encapsulated in a function.
1255 -- Since this expression is not needed in most cases, we prefer not
1256 -- to incur the overhead of the computation on calls to the enclosing
1257 -- subprogram except for subprograms that require the size.
1259 if not Is_Library_Level_Entity (E) then
1260 Make_Size_Function := True;
1262 declare
1263 Parent_Subp : Entity_Id := Enclosing_Subprogram (E);
1265 begin
1266 while Present (Parent_Subp) loop
1267 if Is_Inlined (Parent_Subp) then
1268 Make_Size_Function := False;
1269 exit;
1270 end if;
1272 Parent_Subp := Enclosing_Subprogram (Parent_Subp);
1273 end loop;
1274 end;
1275 end if;
1277 -- Now set the dynamic size (the Value_Size is always the same
1278 -- as the Object_Size for arrays whose length is dynamic).
1280 -- ??? If Size.Status = Dynamic, Vtyp will not have been set.
1281 -- The added initialization sets it to Empty now, but is this
1282 -- correct?
1284 Set_Esize
1286 SO_Ref_From_Expr
1287 (Size.Nod, Insert_Typ, Vtyp, Make_Func => Make_Size_Function));
1288 Set_RM_Size (E, Esize (E));
1289 end if;
1290 end Layout_Array_Type;
1292 -------------------
1293 -- Layout_Object --
1294 -------------------
1296 procedure Layout_Object (E : Entity_Id) is
1297 T : constant Entity_Id := Etype (E);
1299 begin
1300 -- Nothing to do if backend does layout
1302 if not Frontend_Layout_On_Target then
1303 return;
1304 end if;
1306 -- Set size if not set for object and known for type. Use the
1307 -- RM_Size if that is known for the type and Esize is not.
1309 if Unknown_Esize (E) then
1310 if Known_Esize (T) then
1311 Set_Esize (E, Esize (T));
1313 elsif Known_RM_Size (T) then
1314 Set_Esize (E, RM_Size (T));
1315 end if;
1316 end if;
1318 -- Set alignment from type if unknown and type alignment known
1320 if Unknown_Alignment (E) and then Known_Alignment (T) then
1321 Set_Alignment (E, Alignment (T));
1322 end if;
1324 -- Make sure size and alignment are consistent
1326 Adjust_Esize_Alignment (E);
1328 -- Final adjustment, if we don't know the alignment, and the Esize
1329 -- was not set by an explicit Object_Size attribute clause, then
1330 -- we reset the Esize to unknown, since we really don't know it.
1332 if Unknown_Alignment (E)
1333 and then not Has_Size_Clause (E)
1334 then
1335 Set_Esize (E, Uint_0);
1336 end if;
1337 end Layout_Object;
1339 ------------------------
1340 -- Layout_Record_Type --
1341 ------------------------
1343 procedure Layout_Record_Type (E : Entity_Id) is
1344 Loc : constant Source_Ptr := Sloc (E);
1345 Decl : Node_Id;
1347 Comp : Entity_Id;
1348 -- Current component being laid out
1350 Prev_Comp : Entity_Id;
1351 -- Previous laid out component
1353 procedure Get_Next_Component_Location
1354 (Prev_Comp : Entity_Id;
1355 Align : Uint;
1356 New_Npos : out SO_Ref;
1357 New_Fbit : out SO_Ref;
1358 New_NPMax : out SO_Ref;
1359 Force_SU : Boolean);
1360 -- Given the previous component in Prev_Comp, which is already laid
1361 -- out, and the alignment of the following component, lays out the
1362 -- following component, and returns its starting position in New_Npos
1363 -- (Normalized_Position value), New_Fbit (Normalized_First_Bit value),
1364 -- and New_NPMax (Normalized_Position_Max value). If Prev_Comp is empty
1365 -- (no previous component is present), then New_Npos, New_Fbit and
1366 -- New_NPMax are all set to zero on return. This procedure is also
1367 -- used to compute the size of a record or variant by giving it the
1368 -- last component, and the record alignment. Force_SU is used to force
1369 -- the new component location to be aligned on a storage unit boundary,
1370 -- even in a packed record, False means that the new position does not
1371 -- need to be bumped to a storage unit boundary, True means a storage
1372 -- unit boundary is always required.
1374 procedure Layout_Component (Comp : Entity_Id; Prev_Comp : Entity_Id);
1375 -- Lays out component Comp, given Prev_Comp, the previously laid-out
1376 -- component (Prev_Comp = Empty if no components laid out yet). The
1377 -- alignment of the record itself is also updated if needed. Both
1378 -- Comp and Prev_Comp can be either components or discriminants.
1380 procedure Layout_Components
1381 (From : Entity_Id;
1382 To : Entity_Id;
1383 Esiz : out SO_Ref;
1384 RM_Siz : out SO_Ref);
1385 -- This procedure lays out the components of the given component list
1386 -- which contains the components starting with From and ending with To.
1387 -- The Next_Entity chain is used to traverse the components. On entry,
1388 -- Prev_Comp is set to the component preceding the list, so that the
1389 -- list is laid out after this component. Prev_Comp is set to Empty if
1390 -- the component list is to be laid out starting at the start of the
1391 -- record. On return, the components are all laid out, and Prev_Comp is
1392 -- set to the last laid out component. On return, Esiz is set to the
1393 -- resulting Object_Size value, which is the length of the record up
1394 -- to and including the last laid out entity. For Esiz, the value is
1395 -- adjusted to match the alignment of the record. RM_Siz is similarly
1396 -- set to the resulting Value_Size value, which is the same length, but
1397 -- not adjusted to meet the alignment. Note that in the case of variant
1398 -- records, Esiz represents the maximum size.
1400 procedure Layout_Non_Variant_Record;
1401 -- Procedure called to lay out a non-variant record type or subtype
1403 procedure Layout_Variant_Record;
1404 -- Procedure called to lay out a variant record type. Decl is set to the
1405 -- full type declaration for the variant record.
1407 ---------------------------------
1408 -- Get_Next_Component_Location --
1409 ---------------------------------
1411 procedure Get_Next_Component_Location
1412 (Prev_Comp : Entity_Id;
1413 Align : Uint;
1414 New_Npos : out SO_Ref;
1415 New_Fbit : out SO_Ref;
1416 New_NPMax : out SO_Ref;
1417 Force_SU : Boolean)
1419 begin
1420 -- No previous component, return zero position
1422 if No (Prev_Comp) then
1423 New_Npos := Uint_0;
1424 New_Fbit := Uint_0;
1425 New_NPMax := Uint_0;
1426 return;
1427 end if;
1429 -- Here we have a previous component
1431 declare
1432 Loc : constant Source_Ptr := Sloc (Prev_Comp);
1434 Old_Npos : constant SO_Ref := Normalized_Position (Prev_Comp);
1435 Old_Fbit : constant SO_Ref := Normalized_First_Bit (Prev_Comp);
1436 Old_NPMax : constant SO_Ref := Normalized_Position_Max (Prev_Comp);
1437 Old_Esiz : constant SO_Ref := Esize (Prev_Comp);
1439 Old_Maxsz : Node_Id;
1440 -- Expression representing maximum size of previous component
1442 begin
1443 -- Case where previous field had a dynamic size
1445 if Is_Dynamic_SO_Ref (Esize (Prev_Comp)) then
1447 -- If the previous field had a dynamic length, then it is
1448 -- required to occupy an integral number of storage units,
1449 -- and start on a storage unit boundary. This means that
1450 -- the Normalized_First_Bit value is zero in the previous
1451 -- component, and the new value is also set to zero.
1453 New_Fbit := Uint_0;
1455 -- In this case, the new position is given by an expression
1456 -- that is the sum of old normalized position and old size.
1458 New_Npos :=
1459 SO_Ref_From_Expr
1460 (Assoc_Add (Loc,
1461 Left_Opnd =>
1462 Expr_From_SO_Ref (Loc, Old_Npos),
1463 Right_Opnd =>
1464 Expr_From_SO_Ref (Loc, Old_Esiz, Prev_Comp)),
1465 Ins_Type => E,
1466 Vtype => E);
1468 -- Get maximum size of previous component
1470 if Size_Depends_On_Discriminant (Etype (Prev_Comp)) then
1471 Old_Maxsz := Get_Max_SU_Size (Etype (Prev_Comp));
1472 else
1473 Old_Maxsz := Expr_From_SO_Ref (Loc, Old_Esiz, Prev_Comp);
1474 end if;
1476 -- Now we can compute the new max position. If the max size
1477 -- is static and the old position is static, then we can
1478 -- compute the new position statically.
1480 if Nkind (Old_Maxsz) = N_Integer_Literal
1481 and then Known_Static_Normalized_Position_Max (Prev_Comp)
1482 then
1483 New_NPMax := Old_NPMax + Intval (Old_Maxsz);
1485 -- Otherwise new max position is dynamic
1487 else
1488 New_NPMax :=
1489 SO_Ref_From_Expr
1490 (Assoc_Add (Loc,
1491 Left_Opnd => Expr_From_SO_Ref (Loc, Old_NPMax),
1492 Right_Opnd => Old_Maxsz),
1493 Ins_Type => E,
1494 Vtype => E);
1495 end if;
1497 -- Previous field has known static Esize
1499 else
1500 New_Fbit := Old_Fbit + Old_Esiz;
1502 -- Bump New_Fbit to storage unit boundary if required
1504 if New_Fbit /= 0 and then Force_SU then
1505 New_Fbit := (New_Fbit + SSU - 1) / SSU * SSU;
1506 end if;
1508 -- If old normalized position is static, we can go ahead
1509 -- and compute the new normalized position directly.
1511 if Known_Static_Normalized_Position (Prev_Comp) then
1512 New_Npos := Old_Npos;
1514 if New_Fbit >= SSU then
1515 New_Npos := New_Npos + New_Fbit / SSU;
1516 New_Fbit := New_Fbit mod SSU;
1517 end if;
1519 -- Bump alignment if stricter than prev
1521 if Align > Alignment (Etype (Prev_Comp)) then
1522 New_Npos := (New_Npos + Align - 1) / Align * Align;
1523 end if;
1525 -- The max position is always equal to the position if
1526 -- the latter is static, since arrays depending on the
1527 -- values of discriminants never have static sizes.
1529 New_NPMax := New_Npos;
1530 return;
1532 -- Case of old normalized position is dynamic
1534 else
1535 -- If new bit position is within the current storage unit,
1536 -- we can just copy the old position as the result position
1537 -- (we have already set the new first bit value).
1539 if New_Fbit < SSU then
1540 New_Npos := Old_Npos;
1541 New_NPMax := Old_NPMax;
1543 -- If new bit position is past the current storage unit, we
1544 -- need to generate a new dynamic value for the position
1545 -- ??? need to deal with alignment
1547 else
1548 New_Npos :=
1549 SO_Ref_From_Expr
1550 (Assoc_Add (Loc,
1551 Left_Opnd => Expr_From_SO_Ref (Loc, Old_Npos),
1552 Right_Opnd =>
1553 Make_Integer_Literal (Loc,
1554 Intval => New_Fbit / SSU)),
1555 Ins_Type => E,
1556 Vtype => E);
1558 New_NPMax :=
1559 SO_Ref_From_Expr
1560 (Assoc_Add (Loc,
1561 Left_Opnd => Expr_From_SO_Ref (Loc, Old_NPMax),
1562 Right_Opnd =>
1563 Make_Integer_Literal (Loc,
1564 Intval => New_Fbit / SSU)),
1565 Ins_Type => E,
1566 Vtype => E);
1567 New_Fbit := New_Fbit mod SSU;
1568 end if;
1569 end if;
1570 end if;
1571 end;
1572 end Get_Next_Component_Location;
1574 ----------------------
1575 -- Layout_Component --
1576 ----------------------
1578 procedure Layout_Component (Comp : Entity_Id; Prev_Comp : Entity_Id) is
1579 Ctyp : constant Entity_Id := Etype (Comp);
1580 ORC : constant Entity_Id := Original_Record_Component (Comp);
1581 Npos : SO_Ref;
1582 Fbit : SO_Ref;
1583 NPMax : SO_Ref;
1584 Forc : Boolean;
1586 begin
1587 -- Increase alignment of record if necessary. Note that we do not
1588 -- do this for packed records, which have an alignment of one by
1589 -- default, or for records for which an explicit alignment was
1590 -- specified with an alignment clause.
1592 if not Is_Packed (E)
1593 and then not Has_Alignment_Clause (E)
1594 and then Alignment (Ctyp) > Alignment (E)
1595 then
1596 Set_Alignment (E, Alignment (Ctyp));
1597 end if;
1599 -- If original component set, then use same layout
1601 if Present (ORC) and then ORC /= Comp then
1602 Set_Normalized_Position (Comp, Normalized_Position (ORC));
1603 Set_Normalized_First_Bit (Comp, Normalized_First_Bit (ORC));
1604 Set_Normalized_Position_Max (Comp, Normalized_Position_Max (ORC));
1605 Set_Component_Bit_Offset (Comp, Component_Bit_Offset (ORC));
1606 Set_Esize (Comp, Esize (ORC));
1607 return;
1608 end if;
1610 -- Parent field is always at start of record, this will overlap
1611 -- the actual fields that are part of the parent, and that's fine
1613 if Chars (Comp) = Name_uParent then
1614 Set_Normalized_Position (Comp, Uint_0);
1615 Set_Normalized_First_Bit (Comp, Uint_0);
1616 Set_Normalized_Position_Max (Comp, Uint_0);
1617 Set_Component_Bit_Offset (Comp, Uint_0);
1618 Set_Esize (Comp, Esize (Ctyp));
1619 return;
1620 end if;
1622 -- Check case of type of component has a scope of the record we
1623 -- are laying out. When this happens, the type in question is an
1624 -- Itype that has not yet been laid out (that's because such
1625 -- types do not get frozen in the normal manner, because there
1626 -- is no place for the freeze nodes).
1628 if Scope (Ctyp) = E then
1629 Layout_Type (Ctyp);
1630 end if;
1632 -- If component already laid out, then we are done
1634 if Known_Normalized_Position (Comp) then
1635 return;
1636 end if;
1638 -- Set size of component from type. We use the Esize except in a
1639 -- packed record, where we use the RM_Size (since that is exactly
1640 -- what the RM_Size value, as distinct from the Object_Size is
1641 -- useful for!)
1643 if Is_Packed (E) then
1644 Set_Esize (Comp, RM_Size (Ctyp));
1645 else
1646 Set_Esize (Comp, Esize (Ctyp));
1647 end if;
1649 -- Compute the component position from the previous one. See if
1650 -- current component requires being on a storage unit boundary.
1652 -- If record is not packed, we always go to a storage unit boundary
1654 if not Is_Packed (E) then
1655 Forc := True;
1657 -- Packed cases
1659 else
1660 -- Elementary types do not need SU boundary in packed record
1662 if Is_Elementary_Type (Ctyp) then
1663 Forc := False;
1665 -- Packed array types with a modular packed array type do not
1666 -- force a storage unit boundary (since the code generation
1667 -- treats these as equivalent to the underlying modular type),
1669 elsif Is_Array_Type (Ctyp)
1670 and then Is_Bit_Packed_Array (Ctyp)
1671 and then Is_Modular_Integer_Type (Packed_Array_Type (Ctyp))
1672 then
1673 Forc := False;
1675 -- Record types with known length less than or equal to the length
1676 -- of long long integer can also be unaligned, since they can be
1677 -- treated as scalars.
1679 elsif Is_Record_Type (Ctyp)
1680 and then not Is_Dynamic_SO_Ref (Esize (Ctyp))
1681 and then Esize (Ctyp) <= Esize (Standard_Long_Long_Integer)
1682 then
1683 Forc := False;
1685 -- All other cases force a storage unit boundary, even when packed
1687 else
1688 Forc := True;
1689 end if;
1690 end if;
1692 -- Now get the next component location
1694 Get_Next_Component_Location
1695 (Prev_Comp, Alignment (Ctyp), Npos, Fbit, NPMax, Forc);
1696 Set_Normalized_Position (Comp, Npos);
1697 Set_Normalized_First_Bit (Comp, Fbit);
1698 Set_Normalized_Position_Max (Comp, NPMax);
1700 -- Set Component_Bit_Offset in the static case
1702 if Known_Static_Normalized_Position (Comp)
1703 and then Known_Normalized_First_Bit (Comp)
1704 then
1705 Set_Component_Bit_Offset (Comp, SSU * Npos + Fbit);
1706 end if;
1707 end Layout_Component;
1709 -----------------------
1710 -- Layout_Components --
1711 -----------------------
1713 procedure Layout_Components
1714 (From : Entity_Id;
1715 To : Entity_Id;
1716 Esiz : out SO_Ref;
1717 RM_Siz : out SO_Ref)
1719 End_Npos : SO_Ref;
1720 End_Fbit : SO_Ref;
1721 End_NPMax : SO_Ref;
1723 begin
1724 -- Only lay out components if there are some to lay out!
1726 if Present (From) then
1728 -- Lay out components with no component clauses
1730 Comp := From;
1731 loop
1732 if Ekind (Comp) = E_Component
1733 or else Ekind (Comp) = E_Discriminant
1734 then
1735 -- The compatibility of component clauses with composite
1736 -- types isn't checked in Sem_Ch13, so we check it here.
1738 if Present (Component_Clause (Comp)) then
1739 if Is_Composite_Type (Etype (Comp))
1740 and then Esize (Comp) < RM_Size (Etype (Comp))
1741 then
1742 Error_Msg_Uint_1 := RM_Size (Etype (Comp));
1743 Error_Msg_NE
1744 ("size for & too small, minimum allowed is ^",
1745 Component_Clause (Comp),
1746 Comp);
1747 end if;
1749 else
1750 Layout_Component (Comp, Prev_Comp);
1751 Prev_Comp := Comp;
1752 end if;
1753 end if;
1755 exit when Comp = To;
1756 Next_Entity (Comp);
1757 end loop;
1758 end if;
1760 -- Set size fields, both are zero if no components
1762 if No (Prev_Comp) then
1763 Esiz := Uint_0;
1764 RM_Siz := Uint_0;
1766 -- If record subtype with non-static discriminants, then we don't
1767 -- know which variant will be the one which gets chosen. We don't
1768 -- just want to set the maximum size from the base, because the
1769 -- size should depend on the particular variant.
1771 -- What we do is to use the RM_Size of the base type, which has
1772 -- the necessary conditional computation of the size, using the
1773 -- size information for the particular variant chosen. Records
1774 -- with default discriminants for example have an Esize that is
1775 -- set to the maximum of all variants, but that's not what we
1776 -- want for a constrained subtype.
1778 elsif Ekind (E) = E_Record_Subtype
1779 and then not Has_Static_Discriminants (E)
1780 then
1781 declare
1782 BT : constant Node_Id := Base_Type (E);
1783 begin
1784 Esiz := RM_Size (BT);
1785 RM_Siz := RM_Size (BT);
1786 Set_Alignment (E, Alignment (BT));
1787 end;
1789 else
1790 -- First the object size, for which we align past the last field
1791 -- to the alignment of the record (the object size is required to
1792 -- be a multiple of the alignment).
1794 Get_Next_Component_Location
1795 (Prev_Comp,
1796 Alignment (E),
1797 End_Npos,
1798 End_Fbit,
1799 End_NPMax,
1800 Force_SU => True);
1802 -- If the resulting normalized position is a dynamic reference,
1803 -- then the size is dynamic, and is stored in storage units. In
1804 -- this case, we set the RM_Size to the same value, it is simply
1805 -- not worth distinguishing Esize and RM_Size values in the
1806 -- dynamic case, since the RM has nothing to say about them.
1808 -- Note that a size cannot have been given in this case, since
1809 -- size specifications cannot be given for variable length types.
1811 declare
1812 Align : constant Uint := Alignment (E);
1814 begin
1815 if Is_Dynamic_SO_Ref (End_Npos) then
1816 RM_Siz := End_Npos;
1818 -- Set the Object_Size allowing for the alignment. In the
1819 -- dynamic case, we must do the actual runtime computation.
1820 -- We can skip this in the non-packed record case if the
1821 -- last component has a smaller alignment than the overall
1822 -- record alignment.
1824 if Is_Dynamic_SO_Ref (End_NPMax) then
1825 Esiz := End_NPMax;
1827 if Is_Packed (E)
1828 or else Alignment (Etype (Prev_Comp)) < Align
1829 then
1830 -- The expression we build is:
1831 -- (expr + align - 1) / align * align
1833 Esiz :=
1834 SO_Ref_From_Expr
1835 (Expr =>
1836 Make_Op_Multiply (Loc,
1837 Left_Opnd =>
1838 Make_Op_Divide (Loc,
1839 Left_Opnd =>
1840 Make_Op_Add (Loc,
1841 Left_Opnd =>
1842 Expr_From_SO_Ref (Loc, Esiz),
1843 Right_Opnd =>
1844 Make_Integer_Literal (Loc,
1845 Intval => Align - 1)),
1846 Right_Opnd =>
1847 Make_Integer_Literal (Loc, Align)),
1848 Right_Opnd =>
1849 Make_Integer_Literal (Loc, Align)),
1850 Ins_Type => E,
1851 Vtype => E);
1852 end if;
1854 -- Here Esiz is static, so we can adjust the alignment
1855 -- directly go give the required aligned value.
1857 else
1858 Esiz := (End_NPMax + Align - 1) / Align * Align * SSU;
1859 end if;
1861 -- Case where computed size is static
1863 else
1864 -- The ending size was computed in Npos in storage units,
1865 -- but the actual size is stored in bits, so adjust
1866 -- accordingly. We also adjust the size to match the
1867 -- alignment here.
1869 Esiz := (End_NPMax + Align - 1) / Align * Align * SSU;
1871 -- Compute the resulting Value_Size (RM_Size). For this
1872 -- purpose we do not force alignment of the record or
1873 -- storage size alignment of the result.
1875 Get_Next_Component_Location
1876 (Prev_Comp,
1877 Uint_0,
1878 End_Npos,
1879 End_Fbit,
1880 End_NPMax,
1881 Force_SU => False);
1883 RM_Siz := End_Npos * SSU + End_Fbit;
1884 Set_And_Check_Static_Size (E, Esiz, RM_Siz);
1885 end if;
1886 end;
1887 end if;
1888 end Layout_Components;
1890 -------------------------------
1891 -- Layout_Non_Variant_Record --
1892 -------------------------------
1894 procedure Layout_Non_Variant_Record is
1895 Esiz : SO_Ref;
1896 RM_Siz : SO_Ref;
1897 begin
1898 Layout_Components (First_Entity (E), Last_Entity (E), Esiz, RM_Siz);
1899 Set_Esize (E, Esiz);
1900 Set_RM_Size (E, RM_Siz);
1901 end Layout_Non_Variant_Record;
1903 ---------------------------
1904 -- Layout_Variant_Record --
1905 ---------------------------
1907 procedure Layout_Variant_Record is
1908 Tdef : constant Node_Id := Type_Definition (Decl);
1909 First_Discr : Entity_Id;
1910 Last_Discr : Entity_Id;
1911 Esiz : SO_Ref;
1913 RM_Siz : SO_Ref;
1914 pragma Warnings (Off, SO_Ref);
1916 RM_Siz_Expr : Node_Id := Empty;
1917 -- Expression for the evolving RM_Siz value. This is typically a
1918 -- conditional expression which involves tests of discriminant
1919 -- values that are formed as references to the entity V. At
1920 -- the end of scanning all the components, a suitable function
1921 -- is constructed in which V is the parameter.
1923 -----------------------
1924 -- Local Subprograms --
1925 -----------------------
1927 procedure Layout_Component_List
1928 (Clist : Node_Id;
1929 Esiz : out SO_Ref;
1930 RM_Siz_Expr : out Node_Id);
1931 -- Recursive procedure, called to lay out one component list
1932 -- Esiz and RM_Siz_Expr are set to the Object_Size and Value_Size
1933 -- values respectively representing the record size up to and
1934 -- including the last component in the component list (including
1935 -- any variants in this component list). RM_Siz_Expr is returned
1936 -- as an expression which may in the general case involve some
1937 -- references to the discriminants of the current record value,
1938 -- referenced by selecting from the entity V.
1940 ---------------------------
1941 -- Layout_Component_List --
1942 ---------------------------
1944 procedure Layout_Component_List
1945 (Clist : Node_Id;
1946 Esiz : out SO_Ref;
1947 RM_Siz_Expr : out Node_Id)
1949 Citems : constant List_Id := Component_Items (Clist);
1950 Vpart : constant Node_Id := Variant_Part (Clist);
1951 Prv : Node_Id;
1952 Var : Node_Id;
1953 RM_Siz : Uint;
1954 RMS_Ent : Entity_Id;
1956 begin
1957 if Is_Non_Empty_List (Citems) then
1958 Layout_Components
1959 (From => Defining_Identifier (First (Citems)),
1960 To => Defining_Identifier (Last (Citems)),
1961 Esiz => Esiz,
1962 RM_Siz => RM_Siz);
1963 else
1964 Layout_Components (Empty, Empty, Esiz, RM_Siz);
1965 end if;
1967 -- Case where no variants are present in the component list
1969 if No (Vpart) then
1971 -- The Esiz value has been correctly set by the call to
1972 -- Layout_Components, so there is nothing more to be done.
1974 -- For RM_Siz, we have an SO_Ref value, which we must convert
1975 -- to an appropriate expression.
1977 if Is_Static_SO_Ref (RM_Siz) then
1978 RM_Siz_Expr :=
1979 Make_Integer_Literal (Loc,
1980 Intval => RM_Siz);
1982 else
1983 RMS_Ent := Get_Dynamic_SO_Entity (RM_Siz);
1985 -- If the size is represented by a function, then we
1986 -- create an appropriate function call using V as
1987 -- the parameter to the call.
1989 if Is_Discrim_SO_Function (RMS_Ent) then
1990 RM_Siz_Expr :=
1991 Make_Function_Call (Loc,
1992 Name => New_Occurrence_Of (RMS_Ent, Loc),
1993 Parameter_Associations => New_List (
1994 Make_Identifier (Loc, Chars => Vname)));
1996 -- If the size is represented by a constant, then the
1997 -- expression we want is a reference to this constant
1999 else
2000 RM_Siz_Expr := New_Occurrence_Of (RMS_Ent, Loc);
2001 end if;
2002 end if;
2004 -- Case where variants are present in this component list
2006 else
2007 declare
2008 EsizV : SO_Ref;
2009 RM_SizV : Node_Id;
2010 Dchoice : Node_Id;
2011 Discrim : Node_Id;
2012 Dtest : Node_Id;
2013 D_List : List_Id;
2014 D_Entity : Entity_Id;
2016 begin
2017 RM_Siz_Expr := Empty;
2018 Prv := Prev_Comp;
2020 Var := Last (Variants (Vpart));
2021 while Present (Var) loop
2022 Prev_Comp := Prv;
2023 Layout_Component_List
2024 (Component_List (Var), EsizV, RM_SizV);
2026 -- Set the Object_Size. If this is the first variant,
2027 -- we just set the size of this first variant.
2029 if Var = Last (Variants (Vpart)) then
2030 Esiz := EsizV;
2032 -- Otherwise the Object_Size is formed as a maximum
2033 -- of Esiz so far from previous variants, and the new
2034 -- Esiz value from the variant we just processed.
2036 -- If both values are static, we can just compute the
2037 -- maximum directly to save building junk nodes.
2039 elsif not Is_Dynamic_SO_Ref (Esiz)
2040 and then not Is_Dynamic_SO_Ref (EsizV)
2041 then
2042 Esiz := UI_Max (Esiz, EsizV);
2044 -- If either value is dynamic, then we have to generate
2045 -- an appropriate Standard_Unsigned'Max attribute call.
2046 -- If one of the values is static then it needs to be
2047 -- converted from bits to storage units to be compatible
2048 -- with the dynamic value.
2050 else
2051 if Is_Static_SO_Ref (Esiz) then
2052 Esiz := (Esiz + SSU - 1) / SSU;
2053 end if;
2055 if Is_Static_SO_Ref (EsizV) then
2056 EsizV := (EsizV + SSU - 1) / SSU;
2057 end if;
2059 Esiz :=
2060 SO_Ref_From_Expr
2061 (Make_Attribute_Reference (Loc,
2062 Attribute_Name => Name_Max,
2063 Prefix =>
2064 New_Occurrence_Of (Standard_Unsigned, Loc),
2065 Expressions => New_List (
2066 Expr_From_SO_Ref (Loc, Esiz),
2067 Expr_From_SO_Ref (Loc, EsizV))),
2068 Ins_Type => E,
2069 Vtype => E);
2070 end if;
2072 -- Now deal with Value_Size (RM_Siz). We are aiming at
2073 -- an expression that looks like:
2075 -- if xxDx (V.disc) then rmsiz1
2076 -- else if xxDx (V.disc) then rmsiz2
2077 -- else ...
2079 -- Where rmsiz1, rmsiz2... are the RM_Siz values for the
2080 -- individual variants, and xxDx are the discriminant
2081 -- checking functions generated for the variant type.
2083 -- If this is the first variant, we simply set the
2084 -- result as the expression. Note that this takes
2085 -- care of the others case.
2087 if No (RM_Siz_Expr) then
2088 RM_Siz_Expr := Bits_To_SU (RM_SizV);
2090 -- Otherwise construct the appropriate test
2092 else
2093 -- The test to be used in general is a call to the
2094 -- discriminant checking function. However, it is
2095 -- definitely worth special casing the very common
2096 -- case where a single value is involved.
2098 Dchoice := First (Discrete_Choices (Var));
2100 if No (Next (Dchoice))
2101 and then Nkind (Dchoice) /= N_Range
2102 then
2103 -- Discriminant to be tested
2105 Discrim :=
2106 Make_Selected_Component (Loc,
2107 Prefix =>
2108 Make_Identifier (Loc, Chars => Vname),
2109 Selector_Name =>
2110 New_Occurrence_Of
2111 (Entity (Name (Vpart)), Loc));
2113 Dtest :=
2114 Make_Op_Eq (Loc,
2115 Left_Opnd => Discrim,
2116 Right_Opnd => New_Copy (Dchoice));
2118 -- Generate a call to the discriminant-checking
2119 -- function for the variant. Note that the result
2120 -- has to be complemented since the function returns
2121 -- False when the passed discriminant value matches.
2123 else
2124 -- The checking function takes all of the type's
2125 -- discriminants as parameters, so a list of all
2126 -- the selected discriminants must be constructed.
2128 D_List := New_List;
2129 D_Entity := First_Discriminant (E);
2130 while Present (D_Entity) loop
2131 Append (
2132 Make_Selected_Component (Loc,
2133 Prefix =>
2134 Make_Identifier (Loc, Chars => Vname),
2135 Selector_Name =>
2136 New_Occurrence_Of
2137 (D_Entity, Loc)),
2138 D_List);
2140 D_Entity := Next_Discriminant (D_Entity);
2141 end loop;
2143 Dtest :=
2144 Make_Op_Not (Loc,
2145 Right_Opnd =>
2146 Make_Function_Call (Loc,
2147 Name =>
2148 New_Occurrence_Of
2149 (Dcheck_Function (Var), Loc),
2150 Parameter_Associations =>
2151 D_List));
2152 end if;
2154 RM_Siz_Expr :=
2155 Make_Conditional_Expression (Loc,
2156 Expressions =>
2157 New_List
2158 (Dtest, Bits_To_SU (RM_SizV), RM_Siz_Expr));
2159 end if;
2161 Prev (Var);
2162 end loop;
2163 end;
2164 end if;
2165 end Layout_Component_List;
2167 -- Start of processing for Layout_Variant_Record
2169 begin
2170 -- We need the discriminant checking functions, since we generate
2171 -- calls to these functions for the RM_Size expression, so make
2172 -- sure that these functions have been constructed in time.
2174 Build_Discr_Checking_Funcs (Decl);
2176 -- Lay out the discriminants
2178 First_Discr := First_Discriminant (E);
2179 Last_Discr := First_Discr;
2180 while Present (Next_Discriminant (Last_Discr)) loop
2181 Next_Discriminant (Last_Discr);
2182 end loop;
2184 Layout_Components
2185 (From => First_Discr,
2186 To => Last_Discr,
2187 Esiz => Esiz,
2188 RM_Siz => RM_Siz);
2190 -- Lay out the main component list (this will make recursive calls
2191 -- to lay out all component lists nested within variants).
2193 Layout_Component_List (Component_List (Tdef), Esiz, RM_Siz_Expr);
2194 Set_Esize (E, Esiz);
2196 -- If the RM_Size is a literal, set its value
2198 if Nkind (RM_Siz_Expr) = N_Integer_Literal then
2199 Set_RM_Size (E, Intval (RM_Siz_Expr));
2201 -- Otherwise we construct a dynamic SO_Ref
2203 else
2204 Set_RM_Size (E,
2205 SO_Ref_From_Expr
2206 (RM_Siz_Expr,
2207 Ins_Type => E,
2208 Vtype => E));
2209 end if;
2210 end Layout_Variant_Record;
2212 -- Start of processing for Layout_Record_Type
2214 begin
2215 -- If this is a cloned subtype, just copy the size fields from the
2216 -- original, nothing else needs to be done in this case, since the
2217 -- components themselves are all shared.
2219 if (Ekind (E) = E_Record_Subtype
2220 or else
2221 Ekind (E) = E_Class_Wide_Subtype)
2222 and then Present (Cloned_Subtype (E))
2223 then
2224 Set_Esize (E, Esize (Cloned_Subtype (E)));
2225 Set_RM_Size (E, RM_Size (Cloned_Subtype (E)));
2226 Set_Alignment (E, Alignment (Cloned_Subtype (E)));
2228 -- Another special case, class-wide types. The RM says that the size
2229 -- of such types is implementation defined (RM 13.3(48)). What we do
2230 -- here is to leave the fields set as unknown values, and the backend
2231 -- determines the actual behavior.
2233 elsif Ekind (E) = E_Class_Wide_Type then
2234 null;
2236 -- All other cases
2238 else
2239 -- Initialize alignment conservatively to 1. This value will
2240 -- be increased as necessary during processing of the record.
2242 if Unknown_Alignment (E) then
2243 Set_Alignment (E, Uint_1);
2244 end if;
2246 -- Initialize previous component. This is Empty unless there
2247 -- are components which have already been laid out by component
2248 -- clauses. If there are such components, we start our lay out of
2249 -- the remaining components following the last such component.
2251 Prev_Comp := Empty;
2253 Comp := First_Component_Or_Discriminant (E);
2254 while Present (Comp) loop
2255 if Present (Component_Clause (Comp)) then
2256 if No (Prev_Comp)
2257 or else
2258 Component_Bit_Offset (Comp) >
2259 Component_Bit_Offset (Prev_Comp)
2260 then
2261 Prev_Comp := Comp;
2262 end if;
2263 end if;
2265 Next_Component_Or_Discriminant (Comp);
2266 end loop;
2268 -- We have two separate circuits, one for non-variant records and
2269 -- one for variant records. For non-variant records, we simply go
2270 -- through the list of components. This handles all the non-variant
2271 -- cases including those cases of subtypes where there is no full
2272 -- type declaration, so the tree cannot be used to drive the layout.
2273 -- For variant records, we have to drive the layout from the tree
2274 -- since we need to understand the variant structure in this case.
2276 if Present (Full_View (E)) then
2277 Decl := Declaration_Node (Full_View (E));
2278 else
2279 Decl := Declaration_Node (E);
2280 end if;
2282 -- Scan all the components
2284 if Nkind (Decl) = N_Full_Type_Declaration
2285 and then Has_Discriminants (E)
2286 and then Nkind (Type_Definition (Decl)) = N_Record_Definition
2287 and then Present (Component_List (Type_Definition (Decl)))
2288 and then
2289 Present (Variant_Part (Component_List (Type_Definition (Decl))))
2290 then
2291 Layout_Variant_Record;
2292 else
2293 Layout_Non_Variant_Record;
2294 end if;
2295 end if;
2296 end Layout_Record_Type;
2298 -----------------
2299 -- Layout_Type --
2300 -----------------
2302 procedure Layout_Type (E : Entity_Id) is
2303 Desig_Type : Entity_Id;
2305 begin
2306 -- For string literal types, for now, kill the size always, this
2307 -- is because gigi does not like or need the size to be set ???
2309 if Ekind (E) = E_String_Literal_Subtype then
2310 Set_Esize (E, Uint_0);
2311 Set_RM_Size (E, Uint_0);
2312 return;
2313 end if;
2315 -- For access types, set size/alignment. This is system address
2316 -- size, except for fat pointers (unconstrained array access types),
2317 -- where the size is two times the address size, to accommodate the
2318 -- two pointers that are required for a fat pointer (data and
2319 -- template). Note that E_Access_Protected_Subprogram_Type is not
2320 -- an access type for this purpose since it is not a pointer but is
2321 -- equivalent to a record. For access subtypes, copy the size from
2322 -- the base type since Gigi represents them the same way.
2324 if Is_Access_Type (E) then
2326 Desig_Type := Underlying_Type (Designated_Type (E));
2328 -- If we only have a limited view of the type, see whether the
2329 -- non-limited view is available.
2331 if From_With_Type (Designated_Type (E))
2332 and then Ekind (Designated_Type (E)) = E_Incomplete_Type
2333 and then Present (Non_Limited_View (Designated_Type (E)))
2334 then
2335 Desig_Type := Non_Limited_View (Designated_Type (E));
2336 end if;
2338 -- If Esize already set (e.g. by a size clause), then nothing
2339 -- further to be done here.
2341 if Known_Esize (E) then
2342 null;
2344 -- Access to subprogram is a strange beast, and we let the
2345 -- backend figure out what is needed (it may be some kind
2346 -- of fat pointer, including the static link for example.
2348 elsif Is_Access_Protected_Subprogram_Type (E) then
2349 null;
2351 -- For access subtypes, copy the size information from base type
2353 elsif Ekind (E) = E_Access_Subtype then
2354 Set_Size_Info (E, Base_Type (E));
2355 Set_RM_Size (E, RM_Size (Base_Type (E)));
2357 -- For other access types, we use either address size, or, if
2358 -- a fat pointer is used (pointer-to-unconstrained array case),
2359 -- twice the address size to accommodate a fat pointer.
2361 elsif Present (Desig_Type)
2362 and then Is_Array_Type (Desig_Type)
2363 and then not Is_Constrained (Desig_Type)
2364 and then not Has_Completion_In_Body (Desig_Type)
2365 and then not Debug_Flag_6
2366 then
2367 Init_Size (E, 2 * System_Address_Size);
2369 -- Check for bad convention set
2371 if Warn_On_Export_Import
2372 and then
2373 (Convention (E) = Convention_C
2374 or else
2375 Convention (E) = Convention_CPP)
2376 then
2377 Error_Msg_N
2378 ("?this access type does not correspond to C pointer", E);
2379 end if;
2381 -- If the designated type is a limited view it is unanalyzed. We
2382 -- can examine the declaration itself to determine whether it will
2383 -- need a fat pointer.
2385 elsif Present (Desig_Type)
2386 and then Present (Parent (Desig_Type))
2387 and then Nkind (Parent (Desig_Type)) = N_Full_Type_Declaration
2388 and then
2389 Nkind (Type_Definition (Parent (Desig_Type)))
2390 = N_Unconstrained_Array_Definition
2391 then
2392 Init_Size (E, 2 * System_Address_Size);
2394 -- When the target is AAMP, access-to-subprogram types are fat
2395 -- pointers consisting of the subprogram address and a static
2396 -- link (with the exception of library-level access types,
2397 -- where a simple subprogram address is used).
2399 elsif AAMP_On_Target
2400 and then
2401 (Ekind (E) = E_Anonymous_Access_Subprogram_Type
2402 or else (Ekind (E) = E_Access_Subprogram_Type
2403 and then Present (Enclosing_Subprogram (E))))
2404 then
2405 Init_Size (E, 2 * System_Address_Size);
2407 else
2408 Init_Size (E, System_Address_Size);
2409 end if;
2411 -- On VMS, reset size to 32 for convention C access type if no
2412 -- explicit size clause is given and the default size is 64. Really
2413 -- we do not know the size, since depending on options for the VMS
2414 -- compiler, the size of a pointer type can be 32 or 64, but
2415 -- choosing 32 as the default improves compatibility with legacy
2416 -- VMS code.
2418 -- Note: we do not use Has_Size_Clause in the test below, because we
2419 -- want to catch the case of a derived type inheriting a size
2420 -- clause. We want to consider this to be an explicit size clause
2421 -- for this purpose, since it would be weird not to inherit the size
2422 -- in this case.
2424 -- We do NOT do this if we are in -gnatdm mode on a non-VMS target
2425 -- since in that case we want the normal pointer representation.
2427 if Opt.True_VMS_Target
2428 and then (Convention (E) = Convention_C
2429 or else
2430 Convention (E) = Convention_CPP)
2431 and then No (Get_Attribute_Definition_Clause (E, Attribute_Size))
2432 and then Esize (E) = 64
2433 then
2434 Init_Size (E, 32);
2435 end if;
2437 Set_Elem_Alignment (E);
2439 -- Scalar types: set size and alignment
2441 elsif Is_Scalar_Type (E) then
2443 -- For discrete types, the RM_Size and Esize must be set
2444 -- already, since this is part of the earlier processing
2445 -- and the front end is always required to lay out the
2446 -- sizes of such types (since they are available as static
2447 -- attributes). All we do is to check that this rule is
2448 -- indeed obeyed!
2450 if Is_Discrete_Type (E) then
2452 -- If the RM_Size is not set, then here is where we set it
2454 -- Note: an RM_Size of zero looks like not set here, but this
2455 -- is a rare case, and we can simply reset it without any harm.
2457 if not Known_RM_Size (E) then
2458 Set_Discrete_RM_Size (E);
2459 end if;
2461 -- If Esize for a discrete type is not set then set it
2463 if not Known_Esize (E) then
2464 declare
2465 S : Int := 8;
2467 begin
2468 loop
2469 -- If size is big enough, set it and exit
2471 if S >= RM_Size (E) then
2472 Init_Esize (E, S);
2473 exit;
2475 -- If the RM_Size is greater than 64 (happens only
2476 -- when strange values are specified by the user,
2477 -- then Esize is simply a copy of RM_Size, it will
2478 -- be further refined later on)
2480 elsif S = 64 then
2481 Set_Esize (E, RM_Size (E));
2482 exit;
2484 -- Otherwise double possible size and keep trying
2486 else
2487 S := S * 2;
2488 end if;
2489 end loop;
2490 end;
2491 end if;
2493 -- For non-discrete scalar types, if the RM_Size is not set,
2494 -- then set it now to a copy of the Esize if the Esize is set.
2496 else
2497 if Known_Esize (E) and then Unknown_RM_Size (E) then
2498 Set_RM_Size (E, Esize (E));
2499 end if;
2500 end if;
2502 Set_Elem_Alignment (E);
2504 -- Non-elementary (composite) types
2506 else
2507 -- If RM_Size is known, set Esize if not known
2509 if Known_RM_Size (E) and then Unknown_Esize (E) then
2511 -- If the alignment is known, we bump the Esize up to the
2512 -- next alignment boundary if it is not already on one.
2514 if Known_Alignment (E) then
2515 declare
2516 A : constant Uint := Alignment_In_Bits (E);
2517 S : constant SO_Ref := RM_Size (E);
2518 begin
2519 Set_Esize (E, (S + A - 1) / A * A);
2520 end;
2521 end if;
2523 -- If Esize is set, and RM_Size is not, RM_Size is copied from
2524 -- Esize at least for now this seems reasonable, and is in any
2525 -- case needed for compatibility with old versions of gigi.
2526 -- look to be unknown.
2528 elsif Known_Esize (E) and then Unknown_RM_Size (E) then
2529 Set_RM_Size (E, Esize (E));
2530 end if;
2532 -- For array base types, set component size if object size of
2533 -- the component type is known and is a small power of 2 (8,
2534 -- 16, 32, 64), since this is what will always be used.
2536 if Ekind (E) = E_Array_Type
2537 and then Unknown_Component_Size (E)
2538 then
2539 declare
2540 CT : constant Entity_Id := Component_Type (E);
2542 begin
2543 -- For some reasons, access types can cause trouble,
2544 -- So let's just do this for discrete types ???
2546 if Present (CT)
2547 and then Is_Discrete_Type (CT)
2548 and then Known_Static_Esize (CT)
2549 then
2550 declare
2551 S : constant Uint := Esize (CT);
2553 begin
2554 if S = 8 or else
2555 S = 16 or else
2556 S = 32 or else
2557 S = 64
2558 then
2559 Set_Component_Size (E, Esize (CT));
2560 end if;
2561 end;
2562 end if;
2563 end;
2564 end if;
2565 end if;
2567 -- Lay out array and record types if front end layout set
2569 if Frontend_Layout_On_Target then
2570 if Is_Array_Type (E) and then not Is_Bit_Packed_Array (E) then
2571 Layout_Array_Type (E);
2572 elsif Is_Record_Type (E) then
2573 Layout_Record_Type (E);
2574 end if;
2576 -- Case of backend layout, we still do a little in the front end
2578 else
2579 -- Processing for record types
2581 if Is_Record_Type (E) then
2583 -- Special remaining processing for record types with a known
2584 -- size of 16, 32, or 64 bits whose alignment is not yet set.
2585 -- For these types, we set a corresponding alignment matching
2586 -- the size if possible, or as large as possible if not.
2588 if Convention (E) = Convention_Ada
2589 and then not Debug_Flag_Q
2590 then
2591 Set_Composite_Alignment (E);
2592 end if;
2594 -- Processing for array types
2596 elsif Is_Array_Type (E) then
2598 -- For arrays that are required to be atomic, we do the same
2599 -- processing as described above for short records, since we
2600 -- really need to have the alignment set for the whole array.
2602 if Is_Atomic (E) and then not Debug_Flag_Q then
2603 Set_Composite_Alignment (E);
2604 end if;
2606 -- For unpacked array types, set an alignment of 1 if we know
2607 -- that the component alignment is not greater than 1. The reason
2608 -- we do this is to avoid unnecessary copying of slices of such
2609 -- arrays when passed to subprogram parameters (see special test
2610 -- in Exp_Ch6.Expand_Actuals).
2612 if not Is_Packed (E)
2613 and then Unknown_Alignment (E)
2614 then
2615 if Known_Static_Component_Size (E)
2616 and then Component_Size (E) = 1
2617 then
2618 Set_Alignment (E, Uint_1);
2619 end if;
2620 end if;
2621 end if;
2622 end if;
2624 -- Final step is to check that Esize and RM_Size are compatible
2626 if Known_Static_Esize (E) and then Known_Static_RM_Size (E) then
2627 if Esize (E) < RM_Size (E) then
2629 -- Esize is less than RM_Size. That's not good. First we test
2630 -- whether this was set deliberately with an Object_Size clause
2631 -- and if so, object to the clause.
2633 if Has_Object_Size_Clause (E) then
2634 Error_Msg_Uint_1 := RM_Size (E);
2635 Error_Msg_F
2636 ("object size is too small, minimum allowed is ^",
2637 Expression (Get_Attribute_Definition_Clause
2638 (E, Attribute_Object_Size)));
2639 end if;
2641 -- Adjust Esize up to RM_Size value
2643 declare
2644 Size : constant Uint := RM_Size (E);
2646 begin
2647 Set_Esize (E, RM_Size (E));
2649 -- For scalar types, increase Object_Size to power of 2,
2650 -- but not less than a storage unit in any case (i.e.,
2651 -- normally this means it will be storage-unit addressable).
2653 if Is_Scalar_Type (E) then
2654 if Size <= System_Storage_Unit then
2655 Init_Esize (E, System_Storage_Unit);
2656 elsif Size <= 16 then
2657 Init_Esize (E, 16);
2658 elsif Size <= 32 then
2659 Init_Esize (E, 32);
2660 else
2661 Set_Esize (E, (Size + 63) / 64 * 64);
2662 end if;
2664 -- Finally, make sure that alignment is consistent with
2665 -- the newly assigned size.
2667 while Alignment (E) * System_Storage_Unit < Esize (E)
2668 and then Alignment (E) < Maximum_Alignment
2669 loop
2670 Set_Alignment (E, 2 * Alignment (E));
2671 end loop;
2672 end if;
2673 end;
2674 end if;
2675 end if;
2676 end Layout_Type;
2678 ---------------------
2679 -- Rewrite_Integer --
2680 ---------------------
2682 procedure Rewrite_Integer (N : Node_Id; V : Uint) is
2683 Loc : constant Source_Ptr := Sloc (N);
2684 Typ : constant Entity_Id := Etype (N);
2686 begin
2687 Rewrite (N, Make_Integer_Literal (Loc, Intval => V));
2688 Set_Etype (N, Typ);
2689 end Rewrite_Integer;
2691 -------------------------------
2692 -- Set_And_Check_Static_Size --
2693 -------------------------------
2695 procedure Set_And_Check_Static_Size
2696 (E : Entity_Id;
2697 Esiz : SO_Ref;
2698 RM_Siz : SO_Ref)
2700 SC : Node_Id;
2702 procedure Check_Size_Too_Small (Spec : Uint; Min : Uint);
2703 -- Spec is the number of bit specified in the size clause, and
2704 -- Min is the minimum computed size. An error is given that the
2705 -- specified size is too small if Spec < Min, and in this case
2706 -- both Esize and RM_Size are set to unknown in E. The error
2707 -- message is posted on node SC.
2709 procedure Check_Unused_Bits (Spec : Uint; Max : Uint);
2710 -- Spec is the number of bits specified in the size clause, and
2711 -- Max is the maximum computed size. A warning is given about
2712 -- unused bits if Spec > Max. This warning is posted on node SC.
2714 --------------------------
2715 -- Check_Size_Too_Small --
2716 --------------------------
2718 procedure Check_Size_Too_Small (Spec : Uint; Min : Uint) is
2719 begin
2720 if Spec < Min then
2721 Error_Msg_Uint_1 := Min;
2722 Error_Msg_NE
2723 ("size for & too small, minimum allowed is ^", SC, E);
2724 Init_Esize (E);
2725 Init_RM_Size (E);
2726 end if;
2727 end Check_Size_Too_Small;
2729 -----------------------
2730 -- Check_Unused_Bits --
2731 -----------------------
2733 procedure Check_Unused_Bits (Spec : Uint; Max : Uint) is
2734 begin
2735 if Spec > Max then
2736 Error_Msg_Uint_1 := Spec - Max;
2737 Error_Msg_NE ("?^ bits of & unused", SC, E);
2738 end if;
2739 end Check_Unused_Bits;
2741 -- Start of processing for Set_And_Check_Static_Size
2743 begin
2744 -- Case where Object_Size (Esize) is already set by a size clause
2746 if Known_Static_Esize (E) then
2747 SC := Size_Clause (E);
2749 if No (SC) then
2750 SC := Get_Attribute_Definition_Clause (E, Attribute_Object_Size);
2751 end if;
2753 -- Perform checks on specified size against computed sizes
2755 if Present (SC) then
2756 Check_Unused_Bits (Esize (E), Esiz);
2757 Check_Size_Too_Small (Esize (E), RM_Siz);
2758 end if;
2759 end if;
2761 -- Case where Value_Size (RM_Size) is set by specific Value_Size
2762 -- clause (we do not need to worry about Value_Size being set by
2763 -- a Size clause, since that will have set Esize as well, and we
2764 -- already took care of that case).
2766 if Known_Static_RM_Size (E) then
2767 SC := Get_Attribute_Definition_Clause (E, Attribute_Value_Size);
2769 -- Perform checks on specified size against computed sizes
2771 if Present (SC) then
2772 Check_Unused_Bits (RM_Size (E), Esiz);
2773 Check_Size_Too_Small (RM_Size (E), RM_Siz);
2774 end if;
2775 end if;
2777 -- Set sizes if unknown
2779 if Unknown_Esize (E) then
2780 Set_Esize (E, Esiz);
2781 end if;
2783 if Unknown_RM_Size (E) then
2784 Set_RM_Size (E, RM_Siz);
2785 end if;
2786 end Set_And_Check_Static_Size;
2788 -----------------------------
2789 -- Set_Composite_Alignment --
2790 -----------------------------
2792 procedure Set_Composite_Alignment (E : Entity_Id) is
2793 Siz : Uint;
2794 Align : Nat;
2796 begin
2797 -- If alignment is already set, then nothing to do
2799 if Known_Alignment (E) then
2800 return;
2801 end if;
2803 -- Alignment is not known, see if we can set it, taking into account
2804 -- the setting of the Optimize_Alignment mode.
2806 -- If Optimize_Alignment is set to Space, then packed records always
2807 -- have an alignment of 1. But don't do anything for atomic records
2808 -- since we may need higher alignment for indivisible access.
2810 if Optimize_Alignment_Space (E)
2811 and then Is_Record_Type (E)
2812 and then Is_Packed (E)
2813 and then not Is_Atomic (E)
2814 then
2815 Align := 1;
2817 -- Not a record, or not packed
2819 else
2820 -- The only other cases we worry about here are where the size is
2821 -- statically known at compile time.
2823 if Known_Static_Esize (E) then
2824 Siz := Esize (E);
2826 elsif Unknown_Esize (E)
2827 and then Known_Static_RM_Size (E)
2828 then
2829 Siz := RM_Size (E);
2831 else
2832 return;
2833 end if;
2835 -- Size is known, alignment is not set
2837 -- Reset alignment to match size if the known size is exactly 2, 4,
2838 -- or 8 storage units.
2840 if Siz = 2 * System_Storage_Unit then
2841 Align := 2;
2842 elsif Siz = 4 * System_Storage_Unit then
2843 Align := 4;
2844 elsif Siz = 8 * System_Storage_Unit then
2845 Align := 8;
2847 -- If Optimize_Alignment is set to Space, then make sure the
2848 -- alignment matches the size, for example, if the size is 17
2849 -- bytes then we want an alignment of 1 for the type.
2851 elsif Optimize_Alignment_Space (E) then
2852 if Siz mod (8 * System_Storage_Unit) = 0 then
2853 Align := 8;
2854 elsif Siz mod (4 * System_Storage_Unit) = 0 then
2855 Align := 4;
2856 elsif Siz mod (2 * System_Storage_Unit) = 0 then
2857 Align := 2;
2858 else
2859 Align := 1;
2860 end if;
2862 -- If Optimize_Alignment is set to Time, then we reset for odd
2863 -- "in between sizes", for example a 17 bit record is given an
2864 -- alignment of 4. Note that this matches the old VMS behavior
2865 -- in versions of GNAT prior to 6.1.1.
2867 elsif Optimize_Alignment_Time (E)
2868 and then Siz > System_Storage_Unit
2869 and then Siz <= 8 * System_Storage_Unit
2870 then
2871 if Siz <= 2 * System_Storage_Unit then
2872 Align := 2;
2873 elsif Siz <= 4 * System_Storage_Unit then
2874 Align := 4;
2875 else -- Siz <= 8 * System_Storage_Unit then
2876 Align := 8;
2877 end if;
2879 -- No special alignment fiddling needed
2881 else
2882 return;
2883 end if;
2884 end if;
2886 -- Here we have Set Align to the proposed improved value. Make sure the
2887 -- value set does not exceed Maximum_Alignment for the target.
2889 if Align > Maximum_Alignment then
2890 Align := Maximum_Alignment;
2891 end if;
2893 -- Further processing for record types only to reduce the alignment
2894 -- set by the above processing in some specific cases. We do not
2895 -- do this for atomic records, since we need max alignment there,
2897 if Is_Record_Type (E) and then not Is_Atomic (E) then
2899 -- For records, there is generally no point in setting alignment
2900 -- higher than word size since we cannot do better than move by
2901 -- words in any case. Omit this if we are optimizing for time,
2902 -- since conceivably we may be able to do better.
2904 if Align > System_Word_Size / System_Storage_Unit
2905 and then not Optimize_Alignment_Time (E)
2906 then
2907 Align := System_Word_Size / System_Storage_Unit;
2908 end if;
2910 -- Check components. If any component requires a higher alignment,
2911 -- then we set that higher alignment in any case. Don't do this if
2912 -- we have Optimize_Alignment set to Space. Note that that covers
2913 -- the case of packed records, where we already set alignment to 1.
2915 if not Optimize_Alignment_Space (E) then
2916 declare
2917 Comp : Entity_Id;
2919 begin
2920 Comp := First_Component (E);
2921 while Present (Comp) loop
2922 if Known_Alignment (Etype (Comp)) then
2923 declare
2924 Calign : constant Uint := Alignment (Etype (Comp));
2926 begin
2927 -- The cases to process are when the alignment of the
2928 -- component type is larger than the alignment we have
2929 -- so far, and either there is no component clause for
2930 -- the component, or the length set by the component
2931 -- clause matches the length of the component type.
2933 if Calign > Align
2934 and then
2935 (Unknown_Esize (Comp)
2936 or else (Known_Static_Esize (Comp)
2937 and then
2938 Esize (Comp) =
2939 Calign * System_Storage_Unit))
2940 then
2941 Align := UI_To_Int (Calign);
2942 end if;
2943 end;
2944 end if;
2946 Next_Component (Comp);
2947 end loop;
2948 end;
2949 end if;
2950 end if;
2952 -- Set chosen alignment, and increase Esize if necessary to match
2953 -- the chosen alignment.
2955 Set_Alignment (E, UI_From_Int (Align));
2957 if Known_Static_Esize (E)
2958 and then Esize (E) < Align * System_Storage_Unit
2959 then
2960 Set_Esize (E, UI_From_Int (Align * System_Storage_Unit));
2961 end if;
2962 end Set_Composite_Alignment;
2964 --------------------------
2965 -- Set_Discrete_RM_Size --
2966 --------------------------
2968 procedure Set_Discrete_RM_Size (Def_Id : Entity_Id) is
2969 FST : constant Entity_Id := First_Subtype (Def_Id);
2971 begin
2972 -- All discrete types except for the base types in standard
2973 -- are constrained, so indicate this by setting Is_Constrained.
2975 Set_Is_Constrained (Def_Id);
2977 -- We set generic types to have an unknown size, since the
2978 -- representation of a generic type is irrelevant, in view
2979 -- of the fact that they have nothing to do with code.
2981 if Is_Generic_Type (Root_Type (FST)) then
2982 Set_RM_Size (Def_Id, Uint_0);
2984 -- If the subtype statically matches the first subtype, then
2985 -- it is required to have exactly the same layout. This is
2986 -- required by aliasing considerations.
2988 elsif Def_Id /= FST and then
2989 Subtypes_Statically_Match (Def_Id, FST)
2990 then
2991 Set_RM_Size (Def_Id, RM_Size (FST));
2992 Set_Size_Info (Def_Id, FST);
2994 -- In all other cases the RM_Size is set to the minimum size.
2995 -- Note that this routine is never called for subtypes for which
2996 -- the RM_Size is set explicitly by an attribute clause.
2998 else
2999 Set_RM_Size (Def_Id, UI_From_Int (Minimum_Size (Def_Id)));
3000 end if;
3001 end Set_Discrete_RM_Size;
3003 ------------------------
3004 -- Set_Elem_Alignment --
3005 ------------------------
3007 procedure Set_Elem_Alignment (E : Entity_Id) is
3008 begin
3009 -- Do not set alignment for packed array types, unless we are doing
3010 -- front end layout, because otherwise this is always handled in the
3011 -- backend.
3013 if Is_Packed_Array_Type (E) and then not Frontend_Layout_On_Target then
3014 return;
3016 -- If there is an alignment clause, then we respect it
3018 elsif Has_Alignment_Clause (E) then
3019 return;
3021 -- If the size is not set, then don't attempt to set the alignment. This
3022 -- happens in the backend layout case for access-to-subprogram types.
3024 elsif not Known_Static_Esize (E) then
3025 return;
3027 -- For access types, do not set the alignment if the size is less than
3028 -- the allowed minimum size. This avoids cascaded error messages.
3030 elsif Is_Access_Type (E)
3031 and then Esize (E) < System_Address_Size
3032 then
3033 return;
3034 end if;
3036 -- Here we calculate the alignment as the largest power of two
3037 -- multiple of System.Storage_Unit that does not exceed either
3038 -- the actual size of the type, or the maximum allowed alignment.
3040 declare
3041 S : constant Int :=
3042 UI_To_Int (Esize (E)) / SSU;
3043 A : Nat;
3045 begin
3046 A := 1;
3047 while 2 * A <= Ttypes.Maximum_Alignment
3048 and then 2 * A <= S
3049 loop
3050 A := 2 * A;
3051 end loop;
3053 -- Now we think we should set the alignment to A, but we
3054 -- skip this if an alignment is already set to a value
3055 -- greater than A (happens for derived types).
3057 -- However, if the alignment is known and too small it
3058 -- must be increased, this happens in a case like:
3060 -- type R is new Character;
3061 -- for R'Size use 16;
3063 -- Here the alignment inherited from Character is 1, but
3064 -- it must be increased to 2 to reflect the increased size.
3066 if Unknown_Alignment (E) or else Alignment (E) < A then
3067 Init_Alignment (E, A);
3068 end if;
3069 end;
3070 end Set_Elem_Alignment;
3072 ----------------------
3073 -- SO_Ref_From_Expr --
3074 ----------------------
3076 function SO_Ref_From_Expr
3077 (Expr : Node_Id;
3078 Ins_Type : Entity_Id;
3079 Vtype : Entity_Id := Empty;
3080 Make_Func : Boolean := False) return Dynamic_SO_Ref
3082 Loc : constant Source_Ptr := Sloc (Ins_Type);
3084 K : constant Entity_Id :=
3085 Make_Defining_Identifier (Loc,
3086 Chars => New_Internal_Name ('K'));
3088 Decl : Node_Id;
3090 Vtype_Primary_View : Entity_Id;
3092 function Check_Node_V_Ref (N : Node_Id) return Traverse_Result;
3093 -- Function used to check one node for reference to V
3095 function Has_V_Ref is new Traverse_Func (Check_Node_V_Ref);
3096 -- Function used to traverse tree to check for reference to V
3098 ----------------------
3099 -- Check_Node_V_Ref --
3100 ----------------------
3102 function Check_Node_V_Ref (N : Node_Id) return Traverse_Result is
3103 begin
3104 if Nkind (N) = N_Identifier then
3105 if Chars (N) = Vname then
3106 return Abandon;
3107 else
3108 return Skip;
3109 end if;
3111 else
3112 return OK;
3113 end if;
3114 end Check_Node_V_Ref;
3116 -- Start of processing for SO_Ref_From_Expr
3118 begin
3119 -- Case of expression is an integer literal, in this case we just
3120 -- return the value (which must always be non-negative, since size
3121 -- and offset values can never be negative).
3123 if Nkind (Expr) = N_Integer_Literal then
3124 pragma Assert (Intval (Expr) >= 0);
3125 return Intval (Expr);
3126 end if;
3128 -- Case where there is a reference to V, create function
3130 if Has_V_Ref (Expr) = Abandon then
3132 pragma Assert (Present (Vtype));
3134 -- Check whether Vtype is a view of a private type and ensure that
3135 -- we use the primary view of the type (which is denoted by its
3136 -- Etype, whether it's the type's partial or full view entity).
3137 -- This is needed to make sure that we use the same (primary) view
3138 -- of the type for all V formals, whether the current view of the
3139 -- type is the partial or full view, so that types will always
3140 -- match on calls from one size function to another.
3142 if Has_Private_Declaration (Vtype) then
3143 Vtype_Primary_View := Etype (Vtype);
3144 else
3145 Vtype_Primary_View := Vtype;
3146 end if;
3148 Set_Is_Discrim_SO_Function (K);
3150 Decl :=
3151 Make_Subprogram_Body (Loc,
3153 Specification =>
3154 Make_Function_Specification (Loc,
3155 Defining_Unit_Name => K,
3156 Parameter_Specifications => New_List (
3157 Make_Parameter_Specification (Loc,
3158 Defining_Identifier =>
3159 Make_Defining_Identifier (Loc, Chars => Vname),
3160 Parameter_Type =>
3161 New_Occurrence_Of (Vtype_Primary_View, Loc))),
3162 Result_Definition =>
3163 New_Occurrence_Of (Standard_Unsigned, Loc)),
3165 Declarations => Empty_List,
3167 Handled_Statement_Sequence =>
3168 Make_Handled_Sequence_Of_Statements (Loc,
3169 Statements => New_List (
3170 Make_Simple_Return_Statement (Loc,
3171 Expression => Expr))));
3173 -- The caller requests that the expression be encapsulated in
3174 -- a parameterless function.
3176 elsif Make_Func then
3177 Decl :=
3178 Make_Subprogram_Body (Loc,
3180 Specification =>
3181 Make_Function_Specification (Loc,
3182 Defining_Unit_Name => K,
3183 Parameter_Specifications => Empty_List,
3184 Result_Definition =>
3185 New_Occurrence_Of (Standard_Unsigned, Loc)),
3187 Declarations => Empty_List,
3189 Handled_Statement_Sequence =>
3190 Make_Handled_Sequence_Of_Statements (Loc,
3191 Statements => New_List (
3192 Make_Simple_Return_Statement (Loc, Expression => Expr))));
3194 -- No reference to V and function not requested, so create a constant
3196 else
3197 Decl :=
3198 Make_Object_Declaration (Loc,
3199 Defining_Identifier => K,
3200 Object_Definition =>
3201 New_Occurrence_Of (Standard_Unsigned, Loc),
3202 Constant_Present => True,
3203 Expression => Expr);
3204 end if;
3206 Append_Freeze_Action (Ins_Type, Decl);
3207 Analyze (Decl);
3208 return Create_Dynamic_SO_Ref (K);
3209 end SO_Ref_From_Expr;
3211 end Layout;