* gcc.c (getenv_spec_function): New function.
[official-gcc.git] / gcc / ada / layout.adb
blobb5b1ef97e53430f79680486a6686c24241803ea9
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-2006, 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 2, 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 COPYING. If not, write --
19 -- to the Free Software Foundation, 51 Franklin Street, Fifth Floor, --
20 -- Boston, MA 02110-1301, USA. --
21 -- --
22 -- GNAT was originally developed by the GNAT team at New York University. --
23 -- Extensive contributions were provided by Ada Core Technologies Inc. --
24 -- --
25 ------------------------------------------------------------------------------
27 with Atree; use Atree;
28 with Checks; use Checks;
29 with Debug; use Debug;
30 with Einfo; use Einfo;
31 with Errout; use Errout;
32 with Exp_Ch3; use Exp_Ch3;
33 with Exp_Util; use Exp_Util;
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 procedure Adjust_Esize_Alignment (E : Entity_Id);
74 -- E is the entity for a type or object. This procedure checks that the
75 -- size and alignment are compatible, and if not either gives an error
76 -- message if they cannot be adjusted or else adjusts them appropriately.
78 function Assoc_Add
79 (Loc : Source_Ptr;
80 Left_Opnd : Node_Id;
81 Right_Opnd : Node_Id) return Node_Id;
82 -- This is like Make_Op_Add except that it optimizes some cases knowing
83 -- that associative rearrangement is allowed for constant folding if one
84 -- of the operands is a compile time known value.
86 function Assoc_Multiply
87 (Loc : Source_Ptr;
88 Left_Opnd : Node_Id;
89 Right_Opnd : Node_Id) return Node_Id;
90 -- This is like Make_Op_Multiply except that it optimizes some cases
91 -- knowing that associative rearrangement is allowed for constant
92 -- folding if one of the operands is a compile time known value
94 function Assoc_Subtract
95 (Loc : Source_Ptr;
96 Left_Opnd : Node_Id;
97 Right_Opnd : Node_Id) return Node_Id;
98 -- This is like Make_Op_Subtract except that it optimizes some cases
99 -- knowing that associative rearrangement is allowed for constant
100 -- folding if one of the operands is a compile time known value
102 function Bits_To_SU (N : Node_Id) return Node_Id;
103 -- This is used when we cross the boundary from static sizes in bits to
104 -- dynamic sizes in storage units. If the argument N is anything other
105 -- than an integer literal, it is returned unchanged, but if it is an
106 -- integer literal, then it is taken as a size in bits, and is replaced
107 -- by the corresponding size in storage units.
109 function Compute_Length (Lo : Node_Id; Hi : Node_Id) return Node_Id;
110 -- Given expressions for the low bound (Lo) and the high bound (Hi),
111 -- Build an expression for the value hi-lo+1, converted to type
112 -- Standard.Unsigned. Takes care of the case where the operands
113 -- are of an enumeration type (so that the subtraction cannot be
114 -- done directly) by applying the Pos operator to Hi/Lo first.
116 function Expr_From_SO_Ref
117 (Loc : Source_Ptr;
118 D : SO_Ref;
119 Comp : Entity_Id := Empty) return Node_Id;
120 -- Given a value D from a size or offset field, return an expression
121 -- representing the value stored. If the value is known at compile time,
122 -- then an N_Integer_Literal is returned with the appropriate value. If
123 -- the value references a constant entity, then an N_Identifier node
124 -- referencing this entity is returned. If the value denotes a size
125 -- function, then returns a call node denoting the given function, with
126 -- a single actual parameter that either refers to the parameter V of
127 -- an enclosing size function (if Comp is Empty or its type doesn't match
128 -- the function's formal), or else is a selected component V.c when Comp
129 -- denotes a component c whose type matches that of the function formal.
130 -- The Loc value is used for the Sloc value of constructed notes.
132 function SO_Ref_From_Expr
133 (Expr : Node_Id;
134 Ins_Type : Entity_Id;
135 Vtype : Entity_Id := Empty;
136 Make_Func : Boolean := False) return Dynamic_SO_Ref;
137 -- This routine is used in the case where a size/offset value is dynamic
138 -- and is represented by the expression Expr. SO_Ref_From_Expr checks if
139 -- the Expr contains a reference to the identifier V, and if so builds
140 -- a function depending on discriminants of the formal parameter V which
141 -- is of type Vtype. Otherwise, if the parameter Make_Func is True, then
142 -- Expr will be encapsulated in a parameterless function; if Make_Func is
143 -- False, then a constant entity with the value Expr is built. The result
144 -- is a Dynamic_SO_Ref to the created entity. Note that Vtype can be
145 -- omitted if Expr does not contain any reference to V, the created entity.
146 -- The declaration created is inserted in the freeze actions of Ins_Type,
147 -- which also supplies the Sloc for created nodes. This function also takes
148 -- care of making sure that the expression is properly analyzed and
149 -- resolved (which may not be the case yet if we build the expression
150 -- in this unit).
152 function Get_Max_SU_Size (E : Entity_Id) return Node_Id;
153 -- E is an array type or subtype that has at least one index bound that
154 -- is the value of a record discriminant. For such an array, the function
155 -- computes an expression that yields the maximum possible size of the
156 -- array in storage units. The result is not defined for any other type,
157 -- or for arrays that do not depend on discriminants, and it is a fatal
158 -- error to call this unless Size_Depends_On_Discriminant (E) is True.
160 procedure Layout_Array_Type (E : Entity_Id);
161 -- Front-end layout of non-bit-packed array type or subtype
163 procedure Layout_Record_Type (E : Entity_Id);
164 -- Front-end layout of record type
166 procedure Rewrite_Integer (N : Node_Id; V : Uint);
167 -- Rewrite node N with an integer literal whose value is V. The Sloc
168 -- for the new node is taken from N, and the type of the literal is
169 -- set to a copy of the type of N on entry.
171 procedure Set_And_Check_Static_Size
172 (E : Entity_Id;
173 Esiz : SO_Ref;
174 RM_Siz : SO_Ref);
175 -- This procedure is called to check explicit given sizes (possibly
176 -- stored in the Esize and RM_Size fields of E) against computed
177 -- Object_Size (Esiz) and Value_Size (RM_Siz) values. Appropriate
178 -- errors and warnings are posted if specified sizes are inconsistent
179 -- with specified sizes. On return, the Esize and RM_Size fields of
180 -- E are set (either from previously given values, or from the newly
181 -- computed values, as appropriate).
183 procedure Set_Composite_Alignment (E : Entity_Id);
184 -- This procedure is called for record types and subtypes, and also for
185 -- atomic array types and subtypes. If no alignment is set, and the size
186 -- is 2 or 4 (or 8 if the word size is 8), then the alignment is set to
187 -- match the size.
189 ----------------------------
190 -- Adjust_Esize_Alignment --
191 ----------------------------
193 procedure Adjust_Esize_Alignment (E : Entity_Id) is
194 Abits : Int;
195 Esize_Set : Boolean;
197 begin
198 -- Nothing to do if size unknown
200 if Unknown_Esize (E) then
201 return;
202 end if;
204 -- Determine if size is constrained by an attribute definition clause
205 -- which must be obeyed. If so, we cannot increase the size in this
206 -- routine.
208 -- For a type, the issue is whether an object size clause has been
209 -- set. A normal size clause constrains only the value size (RM_Size)
211 if Is_Type (E) then
212 Esize_Set := Has_Object_Size_Clause (E);
214 -- For an object, the issue is whether a size clause is present
216 else
217 Esize_Set := Has_Size_Clause (E);
218 end if;
220 -- If size is known it must be a multiple of the storage unit size
222 if Esize (E) mod SSU /= 0 then
224 -- If not, and size specified, then give error
226 if Esize_Set then
227 Error_Msg_NE
228 ("size for& not a multiple of storage unit size",
229 Size_Clause (E), E);
230 return;
232 -- Otherwise bump up size to a storage unit boundary
234 else
235 Set_Esize (E, (Esize (E) + SSU - 1) / SSU * SSU);
236 end if;
237 end if;
239 -- Now we have the size set, it must be a multiple of the alignment
240 -- nothing more we can do here if the alignment is unknown here.
242 if Unknown_Alignment (E) then
243 return;
244 end if;
246 -- At this point both the Esize and Alignment are known, so we need
247 -- to make sure they are consistent.
249 Abits := UI_To_Int (Alignment (E)) * SSU;
251 if Esize (E) mod Abits = 0 then
252 return;
253 end if;
255 -- Here we have a situation where the Esize is not a multiple of
256 -- the alignment. We must either increase Esize or reduce the
257 -- alignment to correct this situation.
259 -- The case in which we can decrease the alignment is where the
260 -- alignment was not set by an alignment clause, and the type in
261 -- question is a discrete type, where it is definitely safe to
262 -- reduce the alignment. For example:
264 -- t : integer range 1 .. 2;
265 -- for t'size use 8;
267 -- In this situation, the initial alignment of t is 4, copied from
268 -- the Integer base type, but it is safe to reduce it to 1 at this
269 -- stage, since we will only be loading a single storage unit.
271 if Is_Discrete_Type (Etype (E))
272 and then not Has_Alignment_Clause (E)
273 then
274 loop
275 Abits := Abits / 2;
276 exit when Esize (E) mod Abits = 0;
277 end loop;
279 Init_Alignment (E, Abits / SSU);
280 return;
281 end if;
283 -- Now the only possible approach left is to increase the Esize
284 -- but we can't do that if the size was set by a specific clause.
286 if Esize_Set then
287 Error_Msg_NE
288 ("size for& is not a multiple of alignment",
289 Size_Clause (E), E);
291 -- Otherwise we can indeed increase the size to a multiple of alignment
293 else
294 Set_Esize (E, ((Esize (E) + (Abits - 1)) / Abits) * Abits);
295 end if;
296 end Adjust_Esize_Alignment;
298 ---------------
299 -- Assoc_Add --
300 ---------------
302 function Assoc_Add
303 (Loc : Source_Ptr;
304 Left_Opnd : Node_Id;
305 Right_Opnd : Node_Id) return Node_Id
307 L : Node_Id;
308 R : Uint;
310 begin
311 -- Case of right operand is a constant
313 if Compile_Time_Known_Value (Right_Opnd) then
314 L := Left_Opnd;
315 R := Expr_Value (Right_Opnd);
317 -- Case of left operand is a constant
319 elsif Compile_Time_Known_Value (Left_Opnd) then
320 L := Right_Opnd;
321 R := Expr_Value (Left_Opnd);
323 -- Neither operand is a constant, do the addition with no optimization
325 else
326 return Make_Op_Add (Loc, Left_Opnd, Right_Opnd);
327 end if;
329 -- Case of left operand is an addition
331 if Nkind (L) = N_Op_Add then
333 -- (C1 + E) + C2 = (C1 + C2) + E
335 if Compile_Time_Known_Value (Sinfo.Left_Opnd (L)) then
336 Rewrite_Integer
337 (Sinfo.Left_Opnd (L),
338 Expr_Value (Sinfo.Left_Opnd (L)) + R);
339 return L;
341 -- (E + C1) + C2 = E + (C1 + C2)
343 elsif Compile_Time_Known_Value (Sinfo.Right_Opnd (L)) then
344 Rewrite_Integer
345 (Sinfo.Right_Opnd (L),
346 Expr_Value (Sinfo.Right_Opnd (L)) + R);
347 return L;
348 end if;
350 -- Case of left operand is a subtraction
352 elsif Nkind (L) = N_Op_Subtract then
354 -- (C1 - E) + C2 = (C1 + C2) + E
356 if Compile_Time_Known_Value (Sinfo.Left_Opnd (L)) then
357 Rewrite_Integer
358 (Sinfo.Left_Opnd (L),
359 Expr_Value (Sinfo.Left_Opnd (L)) + R);
360 return L;
362 -- (E - C1) + C2 = E - (C1 - C2)
364 elsif Compile_Time_Known_Value (Sinfo.Right_Opnd (L)) then
365 Rewrite_Integer
366 (Sinfo.Right_Opnd (L),
367 Expr_Value (Sinfo.Right_Opnd (L)) - R);
368 return L;
369 end if;
370 end if;
372 -- Not optimizable, do the addition
374 return Make_Op_Add (Loc, Left_Opnd, Right_Opnd);
375 end Assoc_Add;
377 --------------------
378 -- Assoc_Multiply --
379 --------------------
381 function Assoc_Multiply
382 (Loc : Source_Ptr;
383 Left_Opnd : Node_Id;
384 Right_Opnd : Node_Id) return Node_Id
386 L : Node_Id;
387 R : Uint;
389 begin
390 -- Case of right operand is a constant
392 if Compile_Time_Known_Value (Right_Opnd) then
393 L := Left_Opnd;
394 R := Expr_Value (Right_Opnd);
396 -- Case of left operand is a constant
398 elsif Compile_Time_Known_Value (Left_Opnd) then
399 L := Right_Opnd;
400 R := Expr_Value (Left_Opnd);
402 -- Neither operand is a constant, do the multiply with no optimization
404 else
405 return Make_Op_Multiply (Loc, Left_Opnd, Right_Opnd);
406 end if;
408 -- Case of left operand is an multiplication
410 if Nkind (L) = N_Op_Multiply then
412 -- (C1 * E) * C2 = (C1 * C2) + E
414 if Compile_Time_Known_Value (Sinfo.Left_Opnd (L)) then
415 Rewrite_Integer
416 (Sinfo.Left_Opnd (L),
417 Expr_Value (Sinfo.Left_Opnd (L)) * R);
418 return L;
420 -- (E * C1) * C2 = E * (C1 * C2)
422 elsif Compile_Time_Known_Value (Sinfo.Right_Opnd (L)) then
423 Rewrite_Integer
424 (Sinfo.Right_Opnd (L),
425 Expr_Value (Sinfo.Right_Opnd (L)) * R);
426 return L;
427 end if;
428 end if;
430 -- Not optimizable, do the multiplication
432 return Make_Op_Multiply (Loc, Left_Opnd, Right_Opnd);
433 end Assoc_Multiply;
435 --------------------
436 -- Assoc_Subtract --
437 --------------------
439 function Assoc_Subtract
440 (Loc : Source_Ptr;
441 Left_Opnd : Node_Id;
442 Right_Opnd : Node_Id) return Node_Id
444 L : Node_Id;
445 R : Uint;
447 begin
448 -- Case of right operand is a constant
450 if Compile_Time_Known_Value (Right_Opnd) then
451 L := Left_Opnd;
452 R := Expr_Value (Right_Opnd);
454 -- Right operand is a constant, do the subtract with no optimization
456 else
457 return Make_Op_Subtract (Loc, Left_Opnd, Right_Opnd);
458 end if;
460 -- Case of left operand is an addition
462 if Nkind (L) = N_Op_Add then
464 -- (C1 + E) - C2 = (C1 - C2) + E
466 if Compile_Time_Known_Value (Sinfo.Left_Opnd (L)) then
467 Rewrite_Integer
468 (Sinfo.Left_Opnd (L),
469 Expr_Value (Sinfo.Left_Opnd (L)) - R);
470 return L;
472 -- (E + C1) - C2 = E + (C1 - C2)
474 elsif Compile_Time_Known_Value (Sinfo.Right_Opnd (L)) then
475 Rewrite_Integer
476 (Sinfo.Right_Opnd (L),
477 Expr_Value (Sinfo.Right_Opnd (L)) - R);
478 return L;
479 end if;
481 -- Case of left operand is a subtraction
483 elsif Nkind (L) = N_Op_Subtract then
485 -- (C1 - E) - C2 = (C1 - C2) + E
487 if Compile_Time_Known_Value (Sinfo.Left_Opnd (L)) then
488 Rewrite_Integer
489 (Sinfo.Left_Opnd (L),
490 Expr_Value (Sinfo.Left_Opnd (L)) + R);
491 return L;
493 -- (E - C1) - C2 = E - (C1 + C2)
495 elsif Compile_Time_Known_Value (Sinfo.Right_Opnd (L)) then
496 Rewrite_Integer
497 (Sinfo.Right_Opnd (L),
498 Expr_Value (Sinfo.Right_Opnd (L)) + R);
499 return L;
500 end if;
501 end if;
503 -- Not optimizable, do the subtraction
505 return Make_Op_Subtract (Loc, Left_Opnd, Right_Opnd);
506 end Assoc_Subtract;
508 ----------------
509 -- Bits_To_SU --
510 ----------------
512 function Bits_To_SU (N : Node_Id) return Node_Id is
513 begin
514 if Nkind (N) = N_Integer_Literal then
515 Set_Intval (N, (Intval (N) + (SSU - 1)) / SSU);
516 end if;
518 return N;
519 end Bits_To_SU;
521 --------------------
522 -- Compute_Length --
523 --------------------
525 function Compute_Length (Lo : Node_Id; Hi : Node_Id) return Node_Id is
526 Loc : constant Source_Ptr := Sloc (Lo);
527 Typ : constant Entity_Id := Etype (Lo);
528 Lo_Op : Node_Id;
529 Hi_Op : Node_Id;
530 Lo_Dim : Uint;
531 Hi_Dim : Uint;
533 begin
534 -- If the bounds are First and Last attributes for the same dimension
535 -- and both have prefixes that denotes the same entity, then we create
536 -- and return a Length attribute. This may allow the back end to
537 -- generate better code in cases where it already has the length.
539 if Nkind (Lo) = N_Attribute_Reference
540 and then Attribute_Name (Lo) = Name_First
541 and then Nkind (Hi) = N_Attribute_Reference
542 and then Attribute_Name (Hi) = Name_Last
543 and then Is_Entity_Name (Prefix (Lo))
544 and then Is_Entity_Name (Prefix (Hi))
545 and then Entity (Prefix (Lo)) = Entity (Prefix (Hi))
546 then
547 Lo_Dim := Uint_1;
548 Hi_Dim := Uint_1;
550 if Present (First (Expressions (Lo))) then
551 Lo_Dim := Expr_Value (First (Expressions (Lo)));
552 end if;
554 if Present (First (Expressions (Hi))) then
555 Hi_Dim := Expr_Value (First (Expressions (Hi)));
556 end if;
558 if Lo_Dim = Hi_Dim then
559 return
560 Make_Attribute_Reference (Loc,
561 Prefix => New_Occurrence_Of
562 (Entity (Prefix (Lo)), Loc),
563 Attribute_Name => Name_Length,
564 Expressions => New_List
565 (Make_Integer_Literal (Loc, Lo_Dim)));
566 end if;
567 end if;
569 Lo_Op := New_Copy_Tree (Lo);
570 Hi_Op := New_Copy_Tree (Hi);
572 -- If type is enumeration type, then use Pos attribute to convert
573 -- to integer type for which subtraction is a permitted operation.
575 if Is_Enumeration_Type (Typ) then
576 Lo_Op :=
577 Make_Attribute_Reference (Loc,
578 Prefix => New_Occurrence_Of (Typ, Loc),
579 Attribute_Name => Name_Pos,
580 Expressions => New_List (Lo_Op));
582 Hi_Op :=
583 Make_Attribute_Reference (Loc,
584 Prefix => New_Occurrence_Of (Typ, Loc),
585 Attribute_Name => Name_Pos,
586 Expressions => New_List (Hi_Op));
587 end if;
589 return
590 Assoc_Add (Loc,
591 Left_Opnd =>
592 Assoc_Subtract (Loc,
593 Left_Opnd => Hi_Op,
594 Right_Opnd => Lo_Op),
595 Right_Opnd => Make_Integer_Literal (Loc, 1));
596 end Compute_Length;
598 ----------------------
599 -- Expr_From_SO_Ref --
600 ----------------------
602 function Expr_From_SO_Ref
603 (Loc : Source_Ptr;
604 D : SO_Ref;
605 Comp : Entity_Id := Empty) return Node_Id
607 Ent : Entity_Id;
609 begin
610 if Is_Dynamic_SO_Ref (D) then
611 Ent := Get_Dynamic_SO_Entity (D);
613 if Is_Discrim_SO_Function (Ent) then
614 -- If a component is passed in whose type matches the type
615 -- of the function formal, then select that component from
616 -- the "V" parameter rather than passing "V" directly.
618 if Present (Comp)
619 and then Base_Type (Etype (Comp))
620 = Base_Type (Etype (First_Formal (Ent)))
621 then
622 return
623 Make_Function_Call (Loc,
624 Name => New_Occurrence_Of (Ent, Loc),
625 Parameter_Associations => New_List (
626 Make_Selected_Component (Loc,
627 Prefix => Make_Identifier (Loc, Chars => Vname),
628 Selector_Name => New_Occurrence_Of (Comp, Loc))));
630 else
631 return
632 Make_Function_Call (Loc,
633 Name => New_Occurrence_Of (Ent, Loc),
634 Parameter_Associations => New_List (
635 Make_Identifier (Loc, Chars => Vname)));
636 end if;
638 else
639 return New_Occurrence_Of (Ent, Loc);
640 end if;
642 else
643 return Make_Integer_Literal (Loc, D);
644 end if;
645 end Expr_From_SO_Ref;
647 ---------------------
648 -- Get_Max_SU_Size --
649 ---------------------
651 function Get_Max_SU_Size (E : Entity_Id) return Node_Id is
652 Loc : constant Source_Ptr := Sloc (E);
653 Indx : Node_Id;
654 Ityp : Entity_Id;
655 Lo : Node_Id;
656 Hi : Node_Id;
657 S : Uint;
658 Len : Node_Id;
660 type Val_Status_Type is (Const, Dynamic);
662 type Val_Type (Status : Val_Status_Type := Const) is
663 record
664 case Status is
665 when Const => Val : Uint;
666 when Dynamic => Nod : Node_Id;
667 end case;
668 end record;
669 -- Shows the status of the value so far. Const means that the value
670 -- is constant, and Val is the current constant value. Dynamic means
671 -- that the value is dynamic, and in this case Nod is the Node_Id of
672 -- the expression to compute the value.
674 Size : Val_Type;
675 -- Calculated value so far if Size.Status = Const,
676 -- or expression value so far if Size.Status = Dynamic.
678 SU_Convert_Required : Boolean := False;
679 -- This is set to True if the final result must be converted from
680 -- bits to storage units (rounding up to a storage unit boundary).
682 -----------------------
683 -- Local Subprograms --
684 -----------------------
686 procedure Max_Discrim (N : in out Node_Id);
687 -- If the node N represents a discriminant, replace it by the maximum
688 -- value of the discriminant.
690 procedure Min_Discrim (N : in out Node_Id);
691 -- If the node N represents a discriminant, replace it by the minimum
692 -- value of the discriminant.
694 -----------------
695 -- Max_Discrim --
696 -----------------
698 procedure Max_Discrim (N : in out Node_Id) is
699 begin
700 if Nkind (N) = N_Identifier
701 and then Ekind (Entity (N)) = E_Discriminant
702 then
703 N := Type_High_Bound (Etype (N));
704 end if;
705 end Max_Discrim;
707 -----------------
708 -- Min_Discrim --
709 -----------------
711 procedure Min_Discrim (N : in out Node_Id) is
712 begin
713 if Nkind (N) = N_Identifier
714 and then Ekind (Entity (N)) = E_Discriminant
715 then
716 N := Type_Low_Bound (Etype (N));
717 end if;
718 end Min_Discrim;
720 -- Start of processing for Get_Max_SU_Size
722 begin
723 pragma Assert (Size_Depends_On_Discriminant (E));
725 -- Initialize status from component size
727 if Known_Static_Component_Size (E) then
728 Size := (Const, Component_Size (E));
730 else
731 Size := (Dynamic, Expr_From_SO_Ref (Loc, Component_Size (E)));
732 end if;
734 -- Loop through indices
736 Indx := First_Index (E);
737 while Present (Indx) loop
738 Ityp := Etype (Indx);
739 Lo := Type_Low_Bound (Ityp);
740 Hi := Type_High_Bound (Ityp);
742 Min_Discrim (Lo);
743 Max_Discrim (Hi);
745 -- Value of the current subscript range is statically known
747 if Compile_Time_Known_Value (Lo)
748 and then Compile_Time_Known_Value (Hi)
749 then
750 S := Expr_Value (Hi) - Expr_Value (Lo) + 1;
752 -- If known flat bound, entire size of array is zero!
754 if S <= 0 then
755 return Make_Integer_Literal (Loc, 0);
756 end if;
758 -- Current value is constant, evolve value
760 if Size.Status = Const then
761 Size.Val := Size.Val * S;
763 -- Current value is dynamic
765 else
766 -- An interesting little optimization, if we have a pending
767 -- conversion from bits to storage units, and the current
768 -- length is a multiple of the storage unit size, then we
769 -- can take the factor out here statically, avoiding some
770 -- extra dynamic computations at the end.
772 if SU_Convert_Required and then S mod SSU = 0 then
773 S := S / SSU;
774 SU_Convert_Required := False;
775 end if;
777 Size.Nod :=
778 Assoc_Multiply (Loc,
779 Left_Opnd => Size.Nod,
780 Right_Opnd =>
781 Make_Integer_Literal (Loc, Intval => S));
782 end if;
784 -- Value of the current subscript range is dynamic
786 else
787 -- If the current size value is constant, then here is where we
788 -- make a transition to dynamic values, which are always stored
789 -- in storage units, However, we do not want to convert to SU's
790 -- too soon, consider the case of a packed array of single bits,
791 -- we want to do the SU conversion after computing the size in
792 -- this case.
794 if Size.Status = Const then
796 -- If the current value is a multiple of the storage unit,
797 -- then most certainly we can do the conversion now, simply
798 -- by dividing the current value by the storage unit value.
799 -- If this works, we set SU_Convert_Required to False.
801 if Size.Val mod SSU = 0 then
803 Size :=
804 (Dynamic, Make_Integer_Literal (Loc, Size.Val / SSU));
805 SU_Convert_Required := False;
807 -- Otherwise, we go ahead and convert the value in bits,
808 -- and set SU_Convert_Required to True to ensure that the
809 -- final value is indeed properly converted.
811 else
812 Size := (Dynamic, Make_Integer_Literal (Loc, Size.Val));
813 SU_Convert_Required := True;
814 end if;
815 end if;
817 -- Length is hi-lo+1
819 Len := Compute_Length (Lo, Hi);
821 -- Check possible range of Len
823 declare
824 OK : Boolean;
825 LLo : Uint;
826 LHi : Uint;
828 begin
829 Set_Parent (Len, E);
830 Determine_Range (Len, OK, LLo, LHi);
832 Len := Convert_To (Standard_Unsigned, Len);
834 -- If we cannot verify that range cannot be super-flat,
835 -- we need a max with zero, since length must be non-neg.
837 if not OK or else LLo < 0 then
838 Len :=
839 Make_Attribute_Reference (Loc,
840 Prefix =>
841 New_Occurrence_Of (Standard_Unsigned, Loc),
842 Attribute_Name => Name_Max,
843 Expressions => New_List (
844 Make_Integer_Literal (Loc, 0),
845 Len));
846 end if;
847 end;
848 end if;
850 Next_Index (Indx);
851 end loop;
853 -- Here after processing all bounds to set sizes. If the value is
854 -- a constant, then it is bits, so we convert to storage units.
856 if Size.Status = Const then
857 return Bits_To_SU (Make_Integer_Literal (Loc, Size.Val));
859 -- Case where the value is dynamic
861 else
862 -- Do convert from bits to SU's if needed
864 if SU_Convert_Required then
866 -- The expression required is (Size.Nod + SU - 1) / SU
868 Size.Nod :=
869 Make_Op_Divide (Loc,
870 Left_Opnd =>
871 Make_Op_Add (Loc,
872 Left_Opnd => Size.Nod,
873 Right_Opnd => Make_Integer_Literal (Loc, SSU - 1)),
874 Right_Opnd => Make_Integer_Literal (Loc, SSU));
875 end if;
877 return Size.Nod;
878 end if;
879 end Get_Max_SU_Size;
881 -----------------------
882 -- Layout_Array_Type --
883 -----------------------
885 procedure Layout_Array_Type (E : Entity_Id) is
886 Loc : constant Source_Ptr := Sloc (E);
887 Ctyp : constant Entity_Id := Component_Type (E);
888 Indx : Node_Id;
889 Ityp : Entity_Id;
890 Lo : Node_Id;
891 Hi : Node_Id;
892 S : Uint;
893 Len : Node_Id;
895 Insert_Typ : Entity_Id;
896 -- This is the type with which any generated constants or functions
897 -- will be associated (i.e. inserted into the freeze actions). This
898 -- is normally the type being laid out. The exception occurs when
899 -- we are laying out Itype's which are local to a record type, and
900 -- whose scope is this record type. Such types do not have freeze
901 -- nodes (because we have no place to put them).
903 ------------------------------------
904 -- How An Array Type is Laid Out --
905 ------------------------------------
907 -- Here is what goes on. We need to multiply the component size of
908 -- the array (which has already been set) by the length of each of
909 -- the indexes. If all these values are known at compile time, then
910 -- the resulting size of the array is the appropriate constant value.
912 -- If the component size or at least one bound is dynamic (but no
913 -- discriminants are present), then the size will be computed as an
914 -- expression that calculates the proper size.
916 -- If there is at least one discriminant bound, then the size is also
917 -- computed as an expression, but this expression contains discriminant
918 -- values which are obtained by selecting from a function parameter, and
919 -- the size is given by a function that is passed the variant record in
920 -- question, and whose body is the expression.
922 type Val_Status_Type is (Const, Dynamic, Discrim);
924 type Val_Type (Status : Val_Status_Type := Const) is
925 record
926 case Status is
927 when Const =>
928 Val : Uint;
929 -- Calculated value so far if Val_Status = Const
931 when Dynamic | Discrim =>
932 Nod : Node_Id;
933 -- Expression value so far if Val_Status /= Const
935 end case;
936 end record;
937 -- Records the value or expression computed so far. Const means that
938 -- the value is constant, and Val is the current constant value.
939 -- Dynamic means that the value is dynamic, and in this case Nod is
940 -- the Node_Id of the expression to compute the value, and Discrim
941 -- means that at least one bound is a discriminant, in which case Nod
942 -- is the expression so far (which will be the body of the function).
944 Size : Val_Type;
945 -- Value of size computed so far. See comments above
947 Vtyp : Entity_Id := Empty;
948 -- Variant record type for the formal parameter of the
949 -- discriminant function V if Status = Discrim.
951 SU_Convert_Required : Boolean := False;
952 -- This is set to True if the final result must be converted from
953 -- bits to storage units (rounding up to a storage unit boundary).
955 Storage_Divisor : Uint := UI_From_Int (SSU);
956 -- This is the amount that a nonstatic computed size will be divided
957 -- by to convert it from bits to storage units. This is normally
958 -- equal to SSU, but can be reduced in the case of packed components
959 -- that fit evenly into a storage unit.
961 Make_Size_Function : Boolean := False;
962 -- Indicates whether to request that SO_Ref_From_Expr should
963 -- encapsulate the array size expresion in a function.
965 procedure Discrimify (N : in out Node_Id);
966 -- If N represents a discriminant, then the Size.Status is set to
967 -- Discrim, and Vtyp is set. The parameter N is replaced with the
968 -- proper expression to extract the discriminant value from V.
970 ----------------
971 -- Discrimify --
972 ----------------
974 procedure Discrimify (N : in out Node_Id) is
975 Decl : Node_Id;
976 Typ : Entity_Id;
978 begin
979 if Nkind (N) = N_Identifier
980 and then Ekind (Entity (N)) = E_Discriminant
981 then
982 Set_Size_Depends_On_Discriminant (E);
984 if Size.Status /= Discrim then
985 Decl := Parent (Parent (Entity (N)));
986 Size := (Discrim, Size.Nod);
987 Vtyp := Defining_Identifier (Decl);
988 end if;
990 Typ := Etype (N);
992 N :=
993 Make_Selected_Component (Loc,
994 Prefix => Make_Identifier (Loc, Chars => Vname),
995 Selector_Name => New_Occurrence_Of (Entity (N), Loc));
997 -- Set the Etype attributes of the selected name and its prefix.
998 -- Analyze_And_Resolve can't be called here because the Vname
999 -- entity denoted by the prefix will not yet exist (it's created
1000 -- by SO_Ref_From_Expr, called at the end of Layout_Array_Type).
1002 Set_Etype (Prefix (N), Vtyp);
1003 Set_Etype (N, Typ);
1004 end if;
1005 end Discrimify;
1007 -- Start of processing for Layout_Array_Type
1009 begin
1010 -- Default alignment is component alignment
1012 if Unknown_Alignment (E) then
1013 Set_Alignment (E, Alignment (Ctyp));
1014 end if;
1016 -- Calculate proper type for insertions
1018 if Is_Record_Type (Underlying_Type (Scope (E))) then
1019 Insert_Typ := Underlying_Type (Scope (E));
1020 else
1021 Insert_Typ := E;
1022 end if;
1024 -- If the component type is a generic formal type then there's no point
1025 -- in determining a size for the array type.
1027 if Is_Generic_Type (Ctyp) then
1028 return;
1029 end if;
1031 -- Deal with component size if base type
1033 if Ekind (E) = E_Array_Type then
1035 -- Cannot do anything if Esize of component type unknown
1037 if Unknown_Esize (Ctyp) then
1038 return;
1039 end if;
1041 -- Set component size if not set already
1043 if Unknown_Component_Size (E) then
1044 Set_Component_Size (E, Esize (Ctyp));
1045 end if;
1046 end if;
1048 -- (RM 13.3 (48)) says that the size of an unconstrained array
1049 -- is implementation defined. We choose to leave it as Unknown
1050 -- here, and the actual behavior is determined by the back end.
1052 if not Is_Constrained (E) then
1053 return;
1054 end if;
1056 -- Initialize status from component size
1058 if Known_Static_Component_Size (E) then
1059 Size := (Const, Component_Size (E));
1061 else
1062 Size := (Dynamic, Expr_From_SO_Ref (Loc, Component_Size (E)));
1063 end if;
1065 -- Loop to process array indices
1067 Indx := First_Index (E);
1068 while Present (Indx) loop
1069 Ityp := Etype (Indx);
1071 -- If an index of the array is a generic formal type then there's
1072 -- no point in determining a size for the array type.
1074 if Is_Generic_Type (Ityp) then
1075 return;
1076 end if;
1078 Lo := Type_Low_Bound (Ityp);
1079 Hi := Type_High_Bound (Ityp);
1081 -- Value of the current subscript range is statically known
1083 if Compile_Time_Known_Value (Lo)
1084 and then Compile_Time_Known_Value (Hi)
1085 then
1086 S := Expr_Value (Hi) - Expr_Value (Lo) + 1;
1088 -- If known flat bound, entire size of array is zero!
1090 if S <= 0 then
1091 Set_Esize (E, Uint_0);
1092 Set_RM_Size (E, Uint_0);
1093 return;
1094 end if;
1096 -- If constant, evolve value
1098 if Size.Status = Const then
1099 Size.Val := Size.Val * S;
1101 -- Current value is dynamic
1103 else
1104 -- An interesting little optimization, if we have a pending
1105 -- conversion from bits to storage units, and the current
1106 -- length is a multiple of the storage unit size, then we
1107 -- can take the factor out here statically, avoiding some
1108 -- extra dynamic computations at the end.
1110 if SU_Convert_Required and then S mod SSU = 0 then
1111 S := S / SSU;
1112 SU_Convert_Required := False;
1113 end if;
1115 -- Now go ahead and evolve the expression
1117 Size.Nod :=
1118 Assoc_Multiply (Loc,
1119 Left_Opnd => Size.Nod,
1120 Right_Opnd =>
1121 Make_Integer_Literal (Loc, Intval => S));
1122 end if;
1124 -- Value of the current subscript range is dynamic
1126 else
1127 -- If the current size value is constant, then here is where we
1128 -- make a transition to dynamic values, which are always stored
1129 -- in storage units, However, we do not want to convert to SU's
1130 -- too soon, consider the case of a packed array of single bits,
1131 -- we want to do the SU conversion after computing the size in
1132 -- this case.
1134 if Size.Status = Const then
1136 -- If the current value is a multiple of the storage unit,
1137 -- then most certainly we can do the conversion now, simply
1138 -- by dividing the current value by the storage unit value.
1139 -- If this works, we set SU_Convert_Required to False.
1141 if Size.Val mod SSU = 0 then
1142 Size :=
1143 (Dynamic, Make_Integer_Literal (Loc, Size.Val / SSU));
1144 SU_Convert_Required := False;
1146 -- If the current value is a factor of the storage unit,
1147 -- then we can use a value of one for the size and reduce
1148 -- the strength of the later division.
1150 elsif SSU mod Size.Val = 0 then
1151 Storage_Divisor := SSU / Size.Val;
1152 Size := (Dynamic, Make_Integer_Literal (Loc, Uint_1));
1153 SU_Convert_Required := True;
1155 -- Otherwise, we go ahead and convert the value in bits,
1156 -- and set SU_Convert_Required to True to ensure that the
1157 -- final value is indeed properly converted.
1159 else
1160 Size := (Dynamic, Make_Integer_Literal (Loc, Size.Val));
1161 SU_Convert_Required := True;
1162 end if;
1163 end if;
1165 Discrimify (Lo);
1166 Discrimify (Hi);
1168 -- Length is hi-lo+1
1170 Len := Compute_Length (Lo, Hi);
1172 -- If Len isn't a Length attribute, then its range needs to
1173 -- be checked a possible Max with zero needs to be computed.
1175 if Nkind (Len) /= N_Attribute_Reference
1176 or else Attribute_Name (Len) /= Name_Length
1177 then
1178 declare
1179 OK : Boolean;
1180 LLo : Uint;
1181 LHi : Uint;
1183 begin
1184 -- Check possible range of Len
1186 Set_Parent (Len, E);
1187 Determine_Range (Len, OK, LLo, LHi);
1189 Len := Convert_To (Standard_Unsigned, Len);
1191 -- If range definitely flat or superflat,
1192 -- result size is zero
1194 if OK and then LHi <= 0 then
1195 Set_Esize (E, Uint_0);
1196 Set_RM_Size (E, Uint_0);
1197 return;
1198 end if;
1200 -- If we cannot verify that range cannot be super-flat,
1201 -- we need a maximum with zero, since length cannot be
1202 -- negative.
1204 if not OK or else LLo < 0 then
1205 Len :=
1206 Make_Attribute_Reference (Loc,
1207 Prefix =>
1208 New_Occurrence_Of (Standard_Unsigned, Loc),
1209 Attribute_Name => Name_Max,
1210 Expressions => New_List (
1211 Make_Integer_Literal (Loc, 0),
1212 Len));
1213 end if;
1214 end;
1215 end if;
1217 -- At this stage, Len has the expression for the length
1219 Size.Nod :=
1220 Assoc_Multiply (Loc,
1221 Left_Opnd => Size.Nod,
1222 Right_Opnd => Len);
1223 end if;
1225 Next_Index (Indx);
1226 end loop;
1228 -- Here after processing all bounds to set sizes. If the value is
1229 -- a constant, then it is bits, and the only thing we need to do
1230 -- is to check against explicit given size and do alignment adjust.
1232 if Size.Status = Const then
1233 Set_And_Check_Static_Size (E, Size.Val, Size.Val);
1234 Adjust_Esize_Alignment (E);
1236 -- Case where the value is dynamic
1238 else
1239 -- Do convert from bits to SU's if needed
1241 if SU_Convert_Required then
1243 -- The expression required is:
1244 -- (Size.Nod + Storage_Divisor - 1) / Storage_Divisor
1246 Size.Nod :=
1247 Make_Op_Divide (Loc,
1248 Left_Opnd =>
1249 Make_Op_Add (Loc,
1250 Left_Opnd => Size.Nod,
1251 Right_Opnd => Make_Integer_Literal
1252 (Loc, Storage_Divisor - 1)),
1253 Right_Opnd => Make_Integer_Literal (Loc, Storage_Divisor));
1254 end if;
1256 -- If the array entity is not declared at the library level and its
1257 -- not nested within a subprogram that is marked for inlining, then
1258 -- we request that the size expression be encapsulated in a function.
1259 -- Since this expression is not needed in most cases, we prefer not
1260 -- to incur the overhead of the computation on calls to the enclosing
1261 -- subprogram except for subprograms that require the size.
1263 if not Is_Library_Level_Entity (E) then
1264 Make_Size_Function := True;
1266 declare
1267 Parent_Subp : Entity_Id := Enclosing_Subprogram (E);
1269 begin
1270 while Present (Parent_Subp) loop
1271 if Is_Inlined (Parent_Subp) then
1272 Make_Size_Function := False;
1273 exit;
1274 end if;
1276 Parent_Subp := Enclosing_Subprogram (Parent_Subp);
1277 end loop;
1278 end;
1279 end if;
1281 -- Now set the dynamic size (the Value_Size is always the same
1282 -- as the Object_Size for arrays whose length is dynamic).
1284 -- ??? If Size.Status = Dynamic, Vtyp will not have been set.
1285 -- The added initialization sets it to Empty now, but is this
1286 -- correct?
1288 Set_Esize
1290 SO_Ref_From_Expr
1291 (Size.Nod, Insert_Typ, Vtyp, Make_Func => Make_Size_Function));
1292 Set_RM_Size (E, Esize (E));
1293 end if;
1294 end Layout_Array_Type;
1296 -------------------
1297 -- Layout_Object --
1298 -------------------
1300 procedure Layout_Object (E : Entity_Id) is
1301 T : constant Entity_Id := Etype (E);
1303 begin
1304 -- Nothing to do if backend does layout
1306 if not Frontend_Layout_On_Target then
1307 return;
1308 end if;
1310 -- Set size if not set for object and known for type. Use the
1311 -- RM_Size if that is known for the type and Esize is not.
1313 if Unknown_Esize (E) then
1314 if Known_Esize (T) then
1315 Set_Esize (E, Esize (T));
1317 elsif Known_RM_Size (T) then
1318 Set_Esize (E, RM_Size (T));
1319 end if;
1320 end if;
1322 -- Set alignment from type if unknown and type alignment known
1324 if Unknown_Alignment (E) and then Known_Alignment (T) then
1325 Set_Alignment (E, Alignment (T));
1326 end if;
1328 -- Make sure size and alignment are consistent
1330 Adjust_Esize_Alignment (E);
1332 -- Final adjustment, if we don't know the alignment, and the Esize
1333 -- was not set by an explicit Object_Size attribute clause, then
1334 -- we reset the Esize to unknown, since we really don't know it.
1336 if Unknown_Alignment (E)
1337 and then not Has_Size_Clause (E)
1338 then
1339 Set_Esize (E, Uint_0);
1340 end if;
1341 end Layout_Object;
1343 ------------------------
1344 -- Layout_Record_Type --
1345 ------------------------
1347 procedure Layout_Record_Type (E : Entity_Id) is
1348 Loc : constant Source_Ptr := Sloc (E);
1349 Decl : Node_Id;
1351 Comp : Entity_Id;
1352 -- Current component being laid out
1354 Prev_Comp : Entity_Id;
1355 -- Previous laid out component
1357 procedure Get_Next_Component_Location
1358 (Prev_Comp : Entity_Id;
1359 Align : Uint;
1360 New_Npos : out SO_Ref;
1361 New_Fbit : out SO_Ref;
1362 New_NPMax : out SO_Ref;
1363 Force_SU : Boolean);
1364 -- Given the previous component in Prev_Comp, which is already laid
1365 -- out, and the alignment of the following component, lays out the
1366 -- following component, and returns its starting position in New_Npos
1367 -- (Normalized_Position value), New_Fbit (Normalized_First_Bit value),
1368 -- and New_NPMax (Normalized_Position_Max value). If Prev_Comp is empty
1369 -- (no previous component is present), then New_Npos, New_Fbit and
1370 -- New_NPMax are all set to zero on return. This procedure is also
1371 -- used to compute the size of a record or variant by giving it the
1372 -- last component, and the record alignment. Force_SU is used to force
1373 -- the new component location to be aligned on a storage unit boundary,
1374 -- even in a packed record, False means that the new position does not
1375 -- need to be bumped to a storage unit boundary, True means a storage
1376 -- unit boundary is always required.
1378 procedure Layout_Component (Comp : Entity_Id; Prev_Comp : Entity_Id);
1379 -- Lays out component Comp, given Prev_Comp, the previously laid-out
1380 -- component (Prev_Comp = Empty if no components laid out yet). The
1381 -- alignment of the record itself is also updated if needed. Both
1382 -- Comp and Prev_Comp can be either components or discriminants.
1384 procedure Layout_Components
1385 (From : Entity_Id;
1386 To : Entity_Id;
1387 Esiz : out SO_Ref;
1388 RM_Siz : out SO_Ref);
1389 -- This procedure lays out the components of the given component list
1390 -- which contains the components starting with From and ending with To.
1391 -- The Next_Entity chain is used to traverse the components. On entry,
1392 -- Prev_Comp is set to the component preceding the list, so that the
1393 -- list is laid out after this component. Prev_Comp is set to Empty if
1394 -- the component list is to be laid out starting at the start of the
1395 -- record. On return, the components are all laid out, and Prev_Comp is
1396 -- set to the last laid out component. On return, Esiz is set to the
1397 -- resulting Object_Size value, which is the length of the record up
1398 -- to and including the last laid out entity. For Esiz, the value is
1399 -- adjusted to match the alignment of the record. RM_Siz is similarly
1400 -- set to the resulting Value_Size value, which is the same length, but
1401 -- not adjusted to meet the alignment. Note that in the case of variant
1402 -- records, Esiz represents the maximum size.
1404 procedure Layout_Non_Variant_Record;
1405 -- Procedure called to lay out a non-variant record type or subtype
1407 procedure Layout_Variant_Record;
1408 -- Procedure called to lay out a variant record type. Decl is set to the
1409 -- full type declaration for the variant record.
1411 ---------------------------------
1412 -- Get_Next_Component_Location --
1413 ---------------------------------
1415 procedure Get_Next_Component_Location
1416 (Prev_Comp : Entity_Id;
1417 Align : Uint;
1418 New_Npos : out SO_Ref;
1419 New_Fbit : out SO_Ref;
1420 New_NPMax : out SO_Ref;
1421 Force_SU : Boolean)
1423 begin
1424 -- No previous component, return zero position
1426 if No (Prev_Comp) then
1427 New_Npos := Uint_0;
1428 New_Fbit := Uint_0;
1429 New_NPMax := Uint_0;
1430 return;
1431 end if;
1433 -- Here we have a previous component
1435 declare
1436 Loc : constant Source_Ptr := Sloc (Prev_Comp);
1438 Old_Npos : constant SO_Ref := Normalized_Position (Prev_Comp);
1439 Old_Fbit : constant SO_Ref := Normalized_First_Bit (Prev_Comp);
1440 Old_NPMax : constant SO_Ref := Normalized_Position_Max (Prev_Comp);
1441 Old_Esiz : constant SO_Ref := Esize (Prev_Comp);
1443 Old_Maxsz : Node_Id;
1444 -- Expression representing maximum size of previous component
1446 begin
1447 -- Case where previous field had a dynamic size
1449 if Is_Dynamic_SO_Ref (Esize (Prev_Comp)) then
1451 -- If the previous field had a dynamic length, then it is
1452 -- required to occupy an integral number of storage units,
1453 -- and start on a storage unit boundary. This means that
1454 -- the Normalized_First_Bit value is zero in the previous
1455 -- component, and the new value is also set to zero.
1457 New_Fbit := Uint_0;
1459 -- In this case, the new position is given by an expression
1460 -- that is the sum of old normalized position and old size.
1462 New_Npos :=
1463 SO_Ref_From_Expr
1464 (Assoc_Add (Loc,
1465 Left_Opnd =>
1466 Expr_From_SO_Ref (Loc, Old_Npos),
1467 Right_Opnd =>
1468 Expr_From_SO_Ref (Loc, Old_Esiz, Prev_Comp)),
1469 Ins_Type => E,
1470 Vtype => E);
1472 -- Get maximum size of previous component
1474 if Size_Depends_On_Discriminant (Etype (Prev_Comp)) then
1475 Old_Maxsz := Get_Max_SU_Size (Etype (Prev_Comp));
1476 else
1477 Old_Maxsz := Expr_From_SO_Ref (Loc, Old_Esiz, Prev_Comp);
1478 end if;
1480 -- Now we can compute the new max position. If the max size
1481 -- is static and the old position is static, then we can
1482 -- compute the new position statically.
1484 if Nkind (Old_Maxsz) = N_Integer_Literal
1485 and then Known_Static_Normalized_Position_Max (Prev_Comp)
1486 then
1487 New_NPMax := Old_NPMax + Intval (Old_Maxsz);
1489 -- Otherwise new max position is dynamic
1491 else
1492 New_NPMax :=
1493 SO_Ref_From_Expr
1494 (Assoc_Add (Loc,
1495 Left_Opnd => Expr_From_SO_Ref (Loc, Old_NPMax),
1496 Right_Opnd => Old_Maxsz),
1497 Ins_Type => E,
1498 Vtype => E);
1499 end if;
1501 -- Previous field has known static Esize
1503 else
1504 New_Fbit := Old_Fbit + Old_Esiz;
1506 -- Bump New_Fbit to storage unit boundary if required
1508 if New_Fbit /= 0 and then Force_SU then
1509 New_Fbit := (New_Fbit + SSU - 1) / SSU * SSU;
1510 end if;
1512 -- If old normalized position is static, we can go ahead
1513 -- and compute the new normalized position directly.
1515 if Known_Static_Normalized_Position (Prev_Comp) then
1516 New_Npos := Old_Npos;
1518 if New_Fbit >= SSU then
1519 New_Npos := New_Npos + New_Fbit / SSU;
1520 New_Fbit := New_Fbit mod SSU;
1521 end if;
1523 -- Bump alignment if stricter than prev
1525 if Align > Alignment (Etype (Prev_Comp)) then
1526 New_Npos := (New_Npos + Align - 1) / Align * Align;
1527 end if;
1529 -- The max position is always equal to the position if
1530 -- the latter is static, since arrays depending on the
1531 -- values of discriminants never have static sizes.
1533 New_NPMax := New_Npos;
1534 return;
1536 -- Case of old normalized position is dynamic
1538 else
1539 -- If new bit position is within the current storage unit,
1540 -- we can just copy the old position as the result position
1541 -- (we have already set the new first bit value).
1543 if New_Fbit < SSU then
1544 New_Npos := Old_Npos;
1545 New_NPMax := Old_NPMax;
1547 -- If new bit position is past the current storage unit, we
1548 -- need to generate a new dynamic value for the position
1549 -- ??? need to deal with alignment
1551 else
1552 New_Npos :=
1553 SO_Ref_From_Expr
1554 (Assoc_Add (Loc,
1555 Left_Opnd => Expr_From_SO_Ref (Loc, Old_Npos),
1556 Right_Opnd =>
1557 Make_Integer_Literal (Loc,
1558 Intval => New_Fbit / SSU)),
1559 Ins_Type => E,
1560 Vtype => E);
1562 New_NPMax :=
1563 SO_Ref_From_Expr
1564 (Assoc_Add (Loc,
1565 Left_Opnd => Expr_From_SO_Ref (Loc, Old_NPMax),
1566 Right_Opnd =>
1567 Make_Integer_Literal (Loc,
1568 Intval => New_Fbit / SSU)),
1569 Ins_Type => E,
1570 Vtype => E);
1571 New_Fbit := New_Fbit mod SSU;
1572 end if;
1573 end if;
1574 end if;
1575 end;
1576 end Get_Next_Component_Location;
1578 ----------------------
1579 -- Layout_Component --
1580 ----------------------
1582 procedure Layout_Component (Comp : Entity_Id; Prev_Comp : Entity_Id) is
1583 Ctyp : constant Entity_Id := Etype (Comp);
1584 ORC : constant Entity_Id := Original_Record_Component (Comp);
1585 Npos : SO_Ref;
1586 Fbit : SO_Ref;
1587 NPMax : SO_Ref;
1588 Forc : Boolean;
1590 begin
1591 -- Increase alignment of record if necessary. Note that we do not
1592 -- do this for packed records, which have an alignment of one by
1593 -- default, or for records for which an explicit alignment was
1594 -- specified with an alignment clause.
1596 if not Is_Packed (E)
1597 and then not Has_Alignment_Clause (E)
1598 and then Alignment (Ctyp) > Alignment (E)
1599 then
1600 Set_Alignment (E, Alignment (Ctyp));
1601 end if;
1603 -- If original component set, then use same layout
1605 if Present (ORC) and then ORC /= Comp then
1606 Set_Normalized_Position (Comp, Normalized_Position (ORC));
1607 Set_Normalized_First_Bit (Comp, Normalized_First_Bit (ORC));
1608 Set_Normalized_Position_Max (Comp, Normalized_Position_Max (ORC));
1609 Set_Component_Bit_Offset (Comp, Component_Bit_Offset (ORC));
1610 Set_Esize (Comp, Esize (ORC));
1611 return;
1612 end if;
1614 -- Parent field is always at start of record, this will overlap
1615 -- the actual fields that are part of the parent, and that's fine
1617 if Chars (Comp) = Name_uParent then
1618 Set_Normalized_Position (Comp, Uint_0);
1619 Set_Normalized_First_Bit (Comp, Uint_0);
1620 Set_Normalized_Position_Max (Comp, Uint_0);
1621 Set_Component_Bit_Offset (Comp, Uint_0);
1622 Set_Esize (Comp, Esize (Ctyp));
1623 return;
1624 end if;
1626 -- Check case of type of component has a scope of the record we
1627 -- are laying out. When this happens, the type in question is an
1628 -- Itype that has not yet been laid out (that's because such
1629 -- types do not get frozen in the normal manner, because there
1630 -- is no place for the freeze nodes).
1632 if Scope (Ctyp) = E then
1633 Layout_Type (Ctyp);
1634 end if;
1636 -- If component already laid out, then we are done
1638 if Known_Normalized_Position (Comp) then
1639 return;
1640 end if;
1642 -- Set size of component from type. We use the Esize except in a
1643 -- packed record, where we use the RM_Size (since that is exactly
1644 -- what the RM_Size value, as distinct from the Object_Size is
1645 -- useful for!)
1647 if Is_Packed (E) then
1648 Set_Esize (Comp, RM_Size (Ctyp));
1649 else
1650 Set_Esize (Comp, Esize (Ctyp));
1651 end if;
1653 -- Compute the component position from the previous one. See if
1654 -- current component requires being on a storage unit boundary.
1656 -- If record is not packed, we always go to a storage unit boundary
1658 if not Is_Packed (E) then
1659 Forc := True;
1661 -- Packed cases
1663 else
1664 -- Elementary types do not need SU boundary in packed record
1666 if Is_Elementary_Type (Ctyp) then
1667 Forc := False;
1669 -- Packed array types with a modular packed array type do not
1670 -- force a storage unit boundary (since the code generation
1671 -- treats these as equivalent to the underlying modular type),
1673 elsif Is_Array_Type (Ctyp)
1674 and then Is_Bit_Packed_Array (Ctyp)
1675 and then Is_Modular_Integer_Type (Packed_Array_Type (Ctyp))
1676 then
1677 Forc := False;
1679 -- Record types with known length less than or equal to the length
1680 -- of long long integer can also be unaligned, since they can be
1681 -- treated as scalars.
1683 elsif Is_Record_Type (Ctyp)
1684 and then not Is_Dynamic_SO_Ref (Esize (Ctyp))
1685 and then Esize (Ctyp) <= Esize (Standard_Long_Long_Integer)
1686 then
1687 Forc := False;
1689 -- All other cases force a storage unit boundary, even when packed
1691 else
1692 Forc := True;
1693 end if;
1694 end if;
1696 -- Now get the next component location
1698 Get_Next_Component_Location
1699 (Prev_Comp, Alignment (Ctyp), Npos, Fbit, NPMax, Forc);
1700 Set_Normalized_Position (Comp, Npos);
1701 Set_Normalized_First_Bit (Comp, Fbit);
1702 Set_Normalized_Position_Max (Comp, NPMax);
1704 -- Set Component_Bit_Offset in the static case
1706 if Known_Static_Normalized_Position (Comp)
1707 and then Known_Normalized_First_Bit (Comp)
1708 then
1709 Set_Component_Bit_Offset (Comp, SSU * Npos + Fbit);
1710 end if;
1711 end Layout_Component;
1713 -----------------------
1714 -- Layout_Components --
1715 -----------------------
1717 procedure Layout_Components
1718 (From : Entity_Id;
1719 To : Entity_Id;
1720 Esiz : out SO_Ref;
1721 RM_Siz : out SO_Ref)
1723 End_Npos : SO_Ref;
1724 End_Fbit : SO_Ref;
1725 End_NPMax : SO_Ref;
1727 begin
1728 -- Only lay out components if there are some to lay out!
1730 if Present (From) then
1732 -- Lay out components with no component clauses
1734 Comp := From;
1735 loop
1736 if Ekind (Comp) = E_Component
1737 or else Ekind (Comp) = E_Discriminant
1738 then
1739 -- The compatibility of component clauses with composite
1740 -- types isn't checked in Sem_Ch13, so we check it here.
1742 if Present (Component_Clause (Comp)) then
1743 if Is_Composite_Type (Etype (Comp))
1744 and then Esize (Comp) < RM_Size (Etype (Comp))
1745 then
1746 Error_Msg_Uint_1 := RM_Size (Etype (Comp));
1747 Error_Msg_NE
1748 ("size for & too small, minimum allowed is ^",
1749 Component_Clause (Comp),
1750 Comp);
1751 end if;
1753 else
1754 Layout_Component (Comp, Prev_Comp);
1755 Prev_Comp := Comp;
1756 end if;
1757 end if;
1759 exit when Comp = To;
1760 Next_Entity (Comp);
1761 end loop;
1762 end if;
1764 -- Set size fields, both are zero if no components
1766 if No (Prev_Comp) then
1767 Esiz := Uint_0;
1768 RM_Siz := Uint_0;
1770 -- If record subtype with non-static discriminants, then we don't
1771 -- know which variant will be the one which gets chosen. We don't
1772 -- just want to set the maximum size from the base, because the
1773 -- size should depend on the particular variant.
1775 -- What we do is to use the RM_Size of the base type, which has
1776 -- the necessary conditional computation of the size, using the
1777 -- size information for the particular variant chosen. Records
1778 -- with default discriminants for example have an Esize that is
1779 -- set to the maximum of all variants, but that's not what we
1780 -- want for a constrained subtype.
1782 elsif Ekind (E) = E_Record_Subtype
1783 and then not Has_Static_Discriminants (E)
1784 then
1785 declare
1786 BT : constant Node_Id := Base_Type (E);
1787 begin
1788 Esiz := RM_Size (BT);
1789 RM_Siz := RM_Size (BT);
1790 Set_Alignment (E, Alignment (BT));
1791 end;
1793 else
1794 -- First the object size, for which we align past the last field
1795 -- to the alignment of the record (the object size is required to
1796 -- be a multiple of the alignment).
1798 Get_Next_Component_Location
1799 (Prev_Comp,
1800 Alignment (E),
1801 End_Npos,
1802 End_Fbit,
1803 End_NPMax,
1804 Force_SU => True);
1806 -- If the resulting normalized position is a dynamic reference,
1807 -- then the size is dynamic, and is stored in storage units. In
1808 -- this case, we set the RM_Size to the same value, it is simply
1809 -- not worth distinguishing Esize and RM_Size values in the
1810 -- dynamic case, since the RM has nothing to say about them.
1812 -- Note that a size cannot have been given in this case, since
1813 -- size specifications cannot be given for variable length types.
1815 declare
1816 Align : constant Uint := Alignment (E);
1818 begin
1819 if Is_Dynamic_SO_Ref (End_Npos) then
1820 RM_Siz := End_Npos;
1822 -- Set the Object_Size allowing for the alignment. In the
1823 -- dynamic case, we must do the actual runtime computation.
1824 -- We can skip this in the non-packed record case if the
1825 -- last component has a smaller alignment than the overall
1826 -- record alignment.
1828 if Is_Dynamic_SO_Ref (End_NPMax) then
1829 Esiz := End_NPMax;
1831 if Is_Packed (E)
1832 or else Alignment (Etype (Prev_Comp)) < Align
1833 then
1834 -- The expression we build is:
1835 -- (expr + align - 1) / align * align
1837 Esiz :=
1838 SO_Ref_From_Expr
1839 (Expr =>
1840 Make_Op_Multiply (Loc,
1841 Left_Opnd =>
1842 Make_Op_Divide (Loc,
1843 Left_Opnd =>
1844 Make_Op_Add (Loc,
1845 Left_Opnd =>
1846 Expr_From_SO_Ref (Loc, Esiz),
1847 Right_Opnd =>
1848 Make_Integer_Literal (Loc,
1849 Intval => Align - 1)),
1850 Right_Opnd =>
1851 Make_Integer_Literal (Loc, Align)),
1852 Right_Opnd =>
1853 Make_Integer_Literal (Loc, Align)),
1854 Ins_Type => E,
1855 Vtype => E);
1856 end if;
1858 -- Here Esiz is static, so we can adjust the alignment
1859 -- directly go give the required aligned value.
1861 else
1862 Esiz := (End_NPMax + Align - 1) / Align * Align * SSU;
1863 end if;
1865 -- Case where computed size is static
1867 else
1868 -- The ending size was computed in Npos in storage units,
1869 -- but the actual size is stored in bits, so adjust
1870 -- accordingly. We also adjust the size to match the
1871 -- alignment here.
1873 Esiz := (End_NPMax + Align - 1) / Align * Align * SSU;
1875 -- Compute the resulting Value_Size (RM_Size). For this
1876 -- purpose we do not force alignment of the record or
1877 -- storage size alignment of the result.
1879 Get_Next_Component_Location
1880 (Prev_Comp,
1881 Uint_0,
1882 End_Npos,
1883 End_Fbit,
1884 End_NPMax,
1885 Force_SU => False);
1887 RM_Siz := End_Npos * SSU + End_Fbit;
1888 Set_And_Check_Static_Size (E, Esiz, RM_Siz);
1889 end if;
1890 end;
1891 end if;
1892 end Layout_Components;
1894 -------------------------------
1895 -- Layout_Non_Variant_Record --
1896 -------------------------------
1898 procedure Layout_Non_Variant_Record is
1899 Esiz : SO_Ref;
1900 RM_Siz : SO_Ref;
1901 begin
1902 Layout_Components (First_Entity (E), Last_Entity (E), Esiz, RM_Siz);
1903 Set_Esize (E, Esiz);
1904 Set_RM_Size (E, RM_Siz);
1905 end Layout_Non_Variant_Record;
1907 ---------------------------
1908 -- Layout_Variant_Record --
1909 ---------------------------
1911 procedure Layout_Variant_Record is
1912 Tdef : constant Node_Id := Type_Definition (Decl);
1913 First_Discr : Entity_Id;
1914 Last_Discr : Entity_Id;
1915 Esiz : SO_Ref;
1916 RM_Siz : SO_Ref;
1918 RM_Siz_Expr : Node_Id := Empty;
1919 -- Expression for the evolving RM_Siz value. This is typically a
1920 -- conditional expression which involves tests of discriminant
1921 -- values that are formed as references to the entity V. At
1922 -- the end of scanning all the components, a suitable function
1923 -- is constructed in which V is the parameter.
1925 -----------------------
1926 -- Local Subprograms --
1927 -----------------------
1929 procedure Layout_Component_List
1930 (Clist : Node_Id;
1931 Esiz : out SO_Ref;
1932 RM_Siz_Expr : out Node_Id);
1933 -- Recursive procedure, called to lay out one component list
1934 -- Esiz and RM_Siz_Expr are set to the Object_Size and Value_Size
1935 -- values respectively representing the record size up to and
1936 -- including the last component in the component list (including
1937 -- any variants in this component list). RM_Siz_Expr is returned
1938 -- as an expression which may in the general case involve some
1939 -- references to the discriminants of the current record value,
1940 -- referenced by selecting from the entity V.
1942 ---------------------------
1943 -- Layout_Component_List --
1944 ---------------------------
1946 procedure Layout_Component_List
1947 (Clist : Node_Id;
1948 Esiz : out SO_Ref;
1949 RM_Siz_Expr : out Node_Id)
1951 Citems : constant List_Id := Component_Items (Clist);
1952 Vpart : constant Node_Id := Variant_Part (Clist);
1953 Prv : Node_Id;
1954 Var : Node_Id;
1955 RM_Siz : Uint;
1956 RMS_Ent : Entity_Id;
1958 begin
1959 if Is_Non_Empty_List (Citems) then
1960 Layout_Components
1961 (From => Defining_Identifier (First (Citems)),
1962 To => Defining_Identifier (Last (Citems)),
1963 Esiz => Esiz,
1964 RM_Siz => RM_Siz);
1965 else
1966 Layout_Components (Empty, Empty, Esiz, RM_Siz);
1967 end if;
1969 -- Case where no variants are present in the component list
1971 if No (Vpart) then
1973 -- The Esiz value has been correctly set by the call to
1974 -- Layout_Components, so there is nothing more to be done.
1976 -- For RM_Siz, we have an SO_Ref value, which we must convert
1977 -- to an appropriate expression.
1979 if Is_Static_SO_Ref (RM_Siz) then
1980 RM_Siz_Expr :=
1981 Make_Integer_Literal (Loc,
1982 Intval => RM_Siz);
1984 else
1985 RMS_Ent := Get_Dynamic_SO_Entity (RM_Siz);
1987 -- If the size is represented by a function, then we
1988 -- create an appropriate function call using V as
1989 -- the parameter to the call.
1991 if Is_Discrim_SO_Function (RMS_Ent) then
1992 RM_Siz_Expr :=
1993 Make_Function_Call (Loc,
1994 Name => New_Occurrence_Of (RMS_Ent, Loc),
1995 Parameter_Associations => New_List (
1996 Make_Identifier (Loc, Chars => Vname)));
1998 -- If the size is represented by a constant, then the
1999 -- expression we want is a reference to this constant
2001 else
2002 RM_Siz_Expr := New_Occurrence_Of (RMS_Ent, Loc);
2003 end if;
2004 end if;
2006 -- Case where variants are present in this component list
2008 else
2009 declare
2010 EsizV : SO_Ref;
2011 RM_SizV : Node_Id;
2012 Dchoice : Node_Id;
2013 Discrim : Node_Id;
2014 Dtest : Node_Id;
2015 D_List : List_Id;
2016 D_Entity : Entity_Id;
2018 begin
2019 RM_Siz_Expr := Empty;
2020 Prv := Prev_Comp;
2022 Var := Last (Variants (Vpart));
2023 while Present (Var) loop
2024 Prev_Comp := Prv;
2025 Layout_Component_List
2026 (Component_List (Var), EsizV, RM_SizV);
2028 -- Set the Object_Size. If this is the first variant,
2029 -- we just set the size of this first variant.
2031 if Var = Last (Variants (Vpart)) then
2032 Esiz := EsizV;
2034 -- Otherwise the Object_Size is formed as a maximum
2035 -- of Esiz so far from previous variants, and the new
2036 -- Esiz value from the variant we just processed.
2038 -- If both values are static, we can just compute the
2039 -- maximum directly to save building junk nodes.
2041 elsif not Is_Dynamic_SO_Ref (Esiz)
2042 and then not Is_Dynamic_SO_Ref (EsizV)
2043 then
2044 Esiz := UI_Max (Esiz, EsizV);
2046 -- If either value is dynamic, then we have to generate
2047 -- an appropriate Standard_Unsigned'Max attribute call.
2048 -- If one of the values is static then it needs to be
2049 -- converted from bits to storage units to be compatible
2050 -- with the dynamic value.
2052 else
2053 if Is_Static_SO_Ref (Esiz) then
2054 Esiz := (Esiz + SSU - 1) / SSU;
2055 end if;
2057 if Is_Static_SO_Ref (EsizV) then
2058 EsizV := (EsizV + SSU - 1) / SSU;
2059 end if;
2061 Esiz :=
2062 SO_Ref_From_Expr
2063 (Make_Attribute_Reference (Loc,
2064 Attribute_Name => Name_Max,
2065 Prefix =>
2066 New_Occurrence_Of (Standard_Unsigned, Loc),
2067 Expressions => New_List (
2068 Expr_From_SO_Ref (Loc, Esiz),
2069 Expr_From_SO_Ref (Loc, EsizV))),
2070 Ins_Type => E,
2071 Vtype => E);
2072 end if;
2074 -- Now deal with Value_Size (RM_Siz). We are aiming at
2075 -- an expression that looks like:
2077 -- if xxDx (V.disc) then rmsiz1
2078 -- else if xxDx (V.disc) then rmsiz2
2079 -- else ...
2081 -- Where rmsiz1, rmsiz2... are the RM_Siz values for the
2082 -- individual variants, and xxDx are the discriminant
2083 -- checking functions generated for the variant type.
2085 -- If this is the first variant, we simply set the
2086 -- result as the expression. Note that this takes
2087 -- care of the others case.
2089 if No (RM_Siz_Expr) then
2090 RM_Siz_Expr := Bits_To_SU (RM_SizV);
2092 -- Otherwise construct the appropriate test
2094 else
2095 -- The test to be used in general is a call to the
2096 -- discriminant checking function. However, it is
2097 -- definitely worth special casing the very common
2098 -- case where a single value is involved.
2100 Dchoice := First (Discrete_Choices (Var));
2102 if No (Next (Dchoice))
2103 and then Nkind (Dchoice) /= N_Range
2104 then
2105 -- Discriminant to be tested
2107 Discrim :=
2108 Make_Selected_Component (Loc,
2109 Prefix =>
2110 Make_Identifier (Loc, Chars => Vname),
2111 Selector_Name =>
2112 New_Occurrence_Of
2113 (Entity (Name (Vpart)), Loc));
2115 Dtest :=
2116 Make_Op_Eq (Loc,
2117 Left_Opnd => Discrim,
2118 Right_Opnd => New_Copy (Dchoice));
2120 -- Generate a call to the discriminant-checking
2121 -- function for the variant. Note that the result
2122 -- has to be complemented since the function returns
2123 -- False when the passed discriminant value matches.
2125 else
2126 -- The checking function takes all of the type's
2127 -- discriminants as parameters, so a list of all
2128 -- the selected discriminants must be constructed.
2130 D_List := New_List;
2131 D_Entity := First_Discriminant (E);
2132 while Present (D_Entity) loop
2133 Append (
2134 Make_Selected_Component (Loc,
2135 Prefix =>
2136 Make_Identifier (Loc, Chars => Vname),
2137 Selector_Name =>
2138 New_Occurrence_Of
2139 (D_Entity, Loc)),
2140 D_List);
2142 D_Entity := Next_Discriminant (D_Entity);
2143 end loop;
2145 Dtest :=
2146 Make_Op_Not (Loc,
2147 Right_Opnd =>
2148 Make_Function_Call (Loc,
2149 Name =>
2150 New_Occurrence_Of
2151 (Dcheck_Function (Var), Loc),
2152 Parameter_Associations =>
2153 D_List));
2154 end if;
2156 RM_Siz_Expr :=
2157 Make_Conditional_Expression (Loc,
2158 Expressions =>
2159 New_List
2160 (Dtest, Bits_To_SU (RM_SizV), RM_Siz_Expr));
2161 end if;
2163 Prev (Var);
2164 end loop;
2165 end;
2166 end if;
2167 end Layout_Component_List;
2169 -- Start of processing for Layout_Variant_Record
2171 begin
2172 -- We need the discriminant checking functions, since we generate
2173 -- calls to these functions for the RM_Size expression, so make
2174 -- sure that these functions have been constructed in time.
2176 Build_Discr_Checking_Funcs (Decl);
2178 -- Lay out the discriminants
2180 First_Discr := First_Discriminant (E);
2181 Last_Discr := First_Discr;
2182 while Present (Next_Discriminant (Last_Discr)) loop
2183 Next_Discriminant (Last_Discr);
2184 end loop;
2186 Layout_Components
2187 (From => First_Discr,
2188 To => Last_Discr,
2189 Esiz => Esiz,
2190 RM_Siz => RM_Siz);
2192 -- Lay out the main component list (this will make recursive calls
2193 -- to lay out all component lists nested within variants).
2195 Layout_Component_List (Component_List (Tdef), Esiz, RM_Siz_Expr);
2196 Set_Esize (E, Esiz);
2198 -- If the RM_Size is a literal, set its value
2200 if Nkind (RM_Siz_Expr) = N_Integer_Literal then
2201 Set_RM_Size (E, Intval (RM_Siz_Expr));
2203 -- Otherwise we construct a dynamic SO_Ref
2205 else
2206 Set_RM_Size (E,
2207 SO_Ref_From_Expr
2208 (RM_Siz_Expr,
2209 Ins_Type => E,
2210 Vtype => E));
2211 end if;
2212 end Layout_Variant_Record;
2214 -- Start of processing for Layout_Record_Type
2216 begin
2217 -- If this is a cloned subtype, just copy the size fields from the
2218 -- original, nothing else needs to be done in this case, since the
2219 -- components themselves are all shared.
2221 if (Ekind (E) = E_Record_Subtype
2222 or else
2223 Ekind (E) = E_Class_Wide_Subtype)
2224 and then Present (Cloned_Subtype (E))
2225 then
2226 Set_Esize (E, Esize (Cloned_Subtype (E)));
2227 Set_RM_Size (E, RM_Size (Cloned_Subtype (E)));
2228 Set_Alignment (E, Alignment (Cloned_Subtype (E)));
2230 -- Another special case, class-wide types. The RM says that the size
2231 -- of such types is implementation defined (RM 13.3(48)). What we do
2232 -- here is to leave the fields set as unknown values, and the backend
2233 -- determines the actual behavior.
2235 elsif Ekind (E) = E_Class_Wide_Type then
2236 null;
2238 -- All other cases
2240 else
2241 -- Initialize alignment conservatively to 1. This value will
2242 -- be increased as necessary during processing of the record.
2244 if Unknown_Alignment (E) then
2245 Set_Alignment (E, Uint_1);
2246 end if;
2248 -- Initialize previous component. This is Empty unless there
2249 -- are components which have already been laid out by component
2250 -- clauses. If there are such components, we start our lay out of
2251 -- the remaining components following the last such component.
2253 Prev_Comp := Empty;
2255 Comp := First_Entity (E);
2256 while Present (Comp) loop
2257 if (Ekind (Comp) = E_Component
2258 or else Ekind (Comp) = E_Discriminant)
2259 and then Present (Component_Clause (Comp))
2260 then
2261 if No (Prev_Comp)
2262 or else
2263 Component_Bit_Offset (Comp) >
2264 Component_Bit_Offset (Prev_Comp)
2265 then
2266 Prev_Comp := Comp;
2267 end if;
2268 end if;
2270 Next_Entity (Comp);
2271 end loop;
2273 -- We have two separate circuits, one for non-variant records and
2274 -- one for variant records. For non-variant records, we simply go
2275 -- through the list of components. This handles all the non-variant
2276 -- cases including those cases of subtypes where there is no full
2277 -- type declaration, so the tree cannot be used to drive the layout.
2278 -- For variant records, we have to drive the layout from the tree
2279 -- since we need to understand the variant structure in this case.
2281 if Present (Full_View (E)) then
2282 Decl := Declaration_Node (Full_View (E));
2283 else
2284 Decl := Declaration_Node (E);
2285 end if;
2287 -- Scan all the components
2289 if Nkind (Decl) = N_Full_Type_Declaration
2290 and then Has_Discriminants (E)
2291 and then Nkind (Type_Definition (Decl)) = N_Record_Definition
2292 and then Present (Component_List (Type_Definition (Decl)))
2293 and then
2294 Present (Variant_Part (Component_List (Type_Definition (Decl))))
2295 then
2296 Layout_Variant_Record;
2297 else
2298 Layout_Non_Variant_Record;
2299 end if;
2300 end if;
2301 end Layout_Record_Type;
2303 -----------------
2304 -- Layout_Type --
2305 -----------------
2307 procedure Layout_Type (E : Entity_Id) is
2308 begin
2309 -- For string literal types, for now, kill the size always, this
2310 -- is because gigi does not like or need the size to be set ???
2312 if Ekind (E) = E_String_Literal_Subtype then
2313 Set_Esize (E, Uint_0);
2314 Set_RM_Size (E, Uint_0);
2315 return;
2316 end if;
2318 -- For access types, set size/alignment. This is system address
2319 -- size, except for fat pointers (unconstrained array access types),
2320 -- where the size is two times the address size, to accommodate the
2321 -- two pointers that are required for a fat pointer (data and
2322 -- template). Note that E_Access_Protected_Subprogram_Type is not
2323 -- an access type for this purpose since it is not a pointer but is
2324 -- equivalent to a record. For access subtypes, copy the size from
2325 -- the base type since Gigi represents them the same way.
2327 if Is_Access_Type (E) then
2329 -- If Esize already set (e.g. by a size clause), then nothing
2330 -- further to be done here.
2332 if Known_Esize (E) then
2333 null;
2335 -- Access to subprogram is a strange beast, and we let the
2336 -- backend figure out what is needed (it may be some kind
2337 -- of fat pointer, including the static link for example.
2339 elsif Ekind (E) = E_Access_Protected_Subprogram_Type then
2340 null;
2342 -- For access subtypes, copy the size information from base type
2344 elsif Ekind (E) = E_Access_Subtype then
2345 Set_Size_Info (E, Base_Type (E));
2346 Set_RM_Size (E, RM_Size (Base_Type (E)));
2348 -- For other access types, we use either address size, or, if
2349 -- a fat pointer is used (pointer-to-unconstrained array case),
2350 -- twice the address size to accommodate a fat pointer.
2352 else
2353 declare
2354 Desig : Entity_Id := Designated_Type (E);
2356 begin
2357 if Is_Private_Type (Desig)
2358 and then Present (Full_View (Desig))
2359 then
2360 Desig := Full_View (Desig);
2361 end if;
2363 if Is_Array_Type (Desig)
2364 and then not Is_Constrained (Desig)
2365 and then not Has_Completion_In_Body (Desig)
2366 and then not Debug_Flag_6
2367 then
2368 Init_Size (E, 2 * System_Address_Size);
2370 -- Check for bad convention set
2372 if Warn_On_Export_Import
2373 and then
2374 (Convention (E) = Convention_C
2375 or else
2376 Convention (E) = Convention_CPP)
2377 then
2378 Error_Msg_N
2379 ("?this access type does not " &
2380 "correspond to C pointer", E);
2381 end if;
2383 else
2384 Init_Size (E, System_Address_Size);
2385 end if;
2386 end;
2387 end if;
2389 -- On VMS, reset size to 32 for convention C access type if no
2390 -- explicit size clause is given and the default size is 64. Really
2391 -- we do not know the size, since depending on options for the VMS
2392 -- compiler, the size of a pointer type can be 32 or 64, but choosing
2393 -- 32 as the default improves compatibility with legacy VMS code.
2395 -- Note: we do not use Has_Size_Clause in the test below, because we
2396 -- want to catch the case of a derived type inheriting a size clause.
2397 -- We want to consider this to be an explicit size clause for this
2398 -- purpose, since it would be weird not to inherit the size in this
2399 -- case.
2401 if OpenVMS_On_Target
2402 and then (Convention (E) = Convention_C
2403 or else
2404 Convention (E) = Convention_CPP)
2405 and then No (Get_Attribute_Definition_Clause (E, Attribute_Size))
2406 and then Esize (E) = 64
2407 then
2408 Init_Size (E, 32);
2409 end if;
2411 Set_Elem_Alignment (E);
2413 -- Scalar types: set size and alignment
2415 elsif Is_Scalar_Type (E) then
2417 -- For discrete types, the RM_Size and Esize must be set
2418 -- already, since this is part of the earlier processing
2419 -- and the front end is always required to lay out the
2420 -- sizes of such types (since they are available as static
2421 -- attributes). All we do is to check that this rule is
2422 -- indeed obeyed!
2424 if Is_Discrete_Type (E) then
2426 -- If the RM_Size is not set, then here is where we set it
2428 -- Note: an RM_Size of zero looks like not set here, but this
2429 -- is a rare case, and we can simply reset it without any harm.
2431 if not Known_RM_Size (E) then
2432 Set_Discrete_RM_Size (E);
2433 end if;
2435 -- If Esize for a discrete type is not set then set it
2437 if not Known_Esize (E) then
2438 declare
2439 S : Int := 8;
2441 begin
2442 loop
2443 -- If size is big enough, set it and exit
2445 if S >= RM_Size (E) then
2446 Init_Esize (E, S);
2447 exit;
2449 -- If the RM_Size is greater than 64 (happens only
2450 -- when strange values are specified by the user,
2451 -- then Esize is simply a copy of RM_Size, it will
2452 -- be further refined later on)
2454 elsif S = 64 then
2455 Set_Esize (E, RM_Size (E));
2456 exit;
2458 -- Otherwise double possible size and keep trying
2460 else
2461 S := S * 2;
2462 end if;
2463 end loop;
2464 end;
2465 end if;
2467 -- For non-discrete sclar types, if the RM_Size is not set,
2468 -- then set it now to a copy of the Esize if the Esize is set.
2470 else
2471 if Known_Esize (E) and then Unknown_RM_Size (E) then
2472 Set_RM_Size (E, Esize (E));
2473 end if;
2474 end if;
2476 Set_Elem_Alignment (E);
2478 -- Non-elementary (composite) types
2480 else
2481 -- If RM_Size is known, set Esize if not known
2483 if Known_RM_Size (E) and then Unknown_Esize (E) then
2485 -- If the alignment is known, we bump the Esize up to the
2486 -- next alignment boundary if it is not already on one.
2488 if Known_Alignment (E) then
2489 declare
2490 A : constant Uint := Alignment_In_Bits (E);
2491 S : constant SO_Ref := RM_Size (E);
2493 begin
2494 Set_Esize (E, (S * A + A - 1) / A);
2495 end;
2496 end if;
2498 -- If Esize is set, and RM_Size is not, RM_Size is copied from
2499 -- Esize at least for now this seems reasonable, and is in any
2500 -- case needed for compatibility with old versions of gigi.
2501 -- look to be unknown.
2503 elsif Known_Esize (E) and then Unknown_RM_Size (E) then
2504 Set_RM_Size (E, Esize (E));
2505 end if;
2507 -- For array base types, set component size if object size of
2508 -- the component type is known and is a small power of 2 (8,
2509 -- 16, 32, 64), since this is what will always be used.
2511 if Ekind (E) = E_Array_Type
2512 and then Unknown_Component_Size (E)
2513 then
2514 declare
2515 CT : constant Entity_Id := Component_Type (E);
2517 begin
2518 -- For some reasons, access types can cause trouble,
2519 -- So let's just do this for discrete types ???
2521 if Present (CT)
2522 and then Is_Discrete_Type (CT)
2523 and then Known_Static_Esize (CT)
2524 then
2525 declare
2526 S : constant Uint := Esize (CT);
2528 begin
2529 if S = 8 or else
2530 S = 16 or else
2531 S = 32 or else
2532 S = 64
2533 then
2534 Set_Component_Size (E, Esize (CT));
2535 end if;
2536 end;
2537 end if;
2538 end;
2539 end if;
2540 end if;
2542 -- Lay out array and record types if front end layout set
2544 if Frontend_Layout_On_Target then
2545 if Is_Array_Type (E) and then not Is_Bit_Packed_Array (E) then
2546 Layout_Array_Type (E);
2547 elsif Is_Record_Type (E) then
2548 Layout_Record_Type (E);
2549 end if;
2551 -- Case of backend layout, we still do a little in the front end
2553 else
2554 -- Processing for record types
2556 if Is_Record_Type (E) then
2558 -- Special remaining processing for record types with a known
2559 -- size of 16, 32, or 64 bits whose alignment is not yet set.
2560 -- For these types, we set a corresponding alignment matching
2561 -- the size if possible, or as large as possible if not.
2563 if Convention (E) = Convention_Ada
2564 and then not Debug_Flag_Q
2565 then
2566 Set_Composite_Alignment (E);
2567 end if;
2569 -- Procressing for array types
2571 elsif Is_Array_Type (E) then
2573 -- For arrays that are required to be atomic, we do the same
2574 -- processing as described above for short records, since we
2575 -- really need to have the alignment set for the whole array.
2577 if Is_Atomic (E) and then not Debug_Flag_Q then
2578 Set_Composite_Alignment (E);
2579 end if;
2581 -- For unpacked array types, set an alignment of 1 if we know
2582 -- that the component alignment is not greater than 1. The reason
2583 -- we do this is to avoid unnecessary copying of slices of such
2584 -- arrays when passed to subprogram parameters (see special test
2585 -- in Exp_Ch6.Expand_Actuals).
2587 if not Is_Packed (E)
2588 and then Unknown_Alignment (E)
2589 then
2590 if Known_Static_Component_Size (E)
2591 and then Component_Size (E) = 1
2592 then
2593 Set_Alignment (E, Uint_1);
2594 end if;
2595 end if;
2596 end if;
2597 end if;
2599 -- Final step is to check that Esize and RM_Size are compatible
2601 if Known_Static_Esize (E) and then Known_Static_RM_Size (E) then
2602 if Esize (E) < RM_Size (E) then
2604 -- Esize is less than RM_Size. That's not good. First we test
2605 -- whether this was set deliberately with an Object_Size clause
2606 -- and if so, object to the clause.
2608 if Has_Object_Size_Clause (E) then
2609 Error_Msg_Uint_1 := RM_Size (E);
2610 Error_Msg_F
2611 ("object size is too small, minimum is ^",
2612 Expression (Get_Attribute_Definition_Clause
2613 (E, Attribute_Object_Size)));
2614 end if;
2616 -- Adjust Esize up to RM_Size value
2618 declare
2619 Size : constant Uint := RM_Size (E);
2621 begin
2622 Set_Esize (E, RM_Size (E));
2624 -- For scalar types, increase Object_Size to power of 2,
2625 -- but not less than a storage unit in any case (i.e.,
2626 -- normally this means it will be storage-unit addressable).
2628 if Is_Scalar_Type (E) then
2629 if Size <= System_Storage_Unit then
2630 Init_Esize (E, System_Storage_Unit);
2631 elsif Size <= 16 then
2632 Init_Esize (E, 16);
2633 elsif Size <= 32 then
2634 Init_Esize (E, 32);
2635 else
2636 Set_Esize (E, (Size + 63) / 64 * 64);
2637 end if;
2639 -- Finally, make sure that alignment is consistent with
2640 -- the newly assigned size.
2642 while Alignment (E) * System_Storage_Unit < Esize (E)
2643 and then Alignment (E) < Maximum_Alignment
2644 loop
2645 Set_Alignment (E, 2 * Alignment (E));
2646 end loop;
2647 end if;
2648 end;
2649 end if;
2650 end if;
2651 end Layout_Type;
2653 ---------------------
2654 -- Rewrite_Integer --
2655 ---------------------
2657 procedure Rewrite_Integer (N : Node_Id; V : Uint) is
2658 Loc : constant Source_Ptr := Sloc (N);
2659 Typ : constant Entity_Id := Etype (N);
2661 begin
2662 Rewrite (N, Make_Integer_Literal (Loc, Intval => V));
2663 Set_Etype (N, Typ);
2664 end Rewrite_Integer;
2666 -------------------------------
2667 -- Set_And_Check_Static_Size --
2668 -------------------------------
2670 procedure Set_And_Check_Static_Size
2671 (E : Entity_Id;
2672 Esiz : SO_Ref;
2673 RM_Siz : SO_Ref)
2675 SC : Node_Id;
2677 procedure Check_Size_Too_Small (Spec : Uint; Min : Uint);
2678 -- Spec is the number of bit specified in the size clause, and
2679 -- Min is the minimum computed size. An error is given that the
2680 -- specified size is too small if Spec < Min, and in this case
2681 -- both Esize and RM_Size are set to unknown in E. The error
2682 -- message is posted on node SC.
2684 procedure Check_Unused_Bits (Spec : Uint; Max : Uint);
2685 -- Spec is the number of bits specified in the size clause, and
2686 -- Max is the maximum computed size. A warning is given about
2687 -- unused bits if Spec > Max. This warning is posted on node SC.
2689 --------------------------
2690 -- Check_Size_Too_Small --
2691 --------------------------
2693 procedure Check_Size_Too_Small (Spec : Uint; Min : Uint) is
2694 begin
2695 if Spec < Min then
2696 Error_Msg_Uint_1 := Min;
2697 Error_Msg_NE
2698 ("size for & too small, minimum allowed is ^", SC, E);
2699 Init_Esize (E);
2700 Init_RM_Size (E);
2701 end if;
2702 end Check_Size_Too_Small;
2704 -----------------------
2705 -- Check_Unused_Bits --
2706 -----------------------
2708 procedure Check_Unused_Bits (Spec : Uint; Max : Uint) is
2709 begin
2710 if Spec > Max then
2711 Error_Msg_Uint_1 := Spec - Max;
2712 Error_Msg_NE ("?^ bits of & unused", SC, E);
2713 end if;
2714 end Check_Unused_Bits;
2716 -- Start of processing for Set_And_Check_Static_Size
2718 begin
2719 -- Case where Object_Size (Esize) is already set by a size clause
2721 if Known_Static_Esize (E) then
2722 SC := Size_Clause (E);
2724 if No (SC) then
2725 SC := Get_Attribute_Definition_Clause (E, Attribute_Object_Size);
2726 end if;
2728 -- Perform checks on specified size against computed sizes
2730 if Present (SC) then
2731 Check_Unused_Bits (Esize (E), Esiz);
2732 Check_Size_Too_Small (Esize (E), RM_Siz);
2733 end if;
2734 end if;
2736 -- Case where Value_Size (RM_Size) is set by specific Value_Size
2737 -- clause (we do not need to worry about Value_Size being set by
2738 -- a Size clause, since that will have set Esize as well, and we
2739 -- already took care of that case).
2741 if Known_Static_RM_Size (E) then
2742 SC := Get_Attribute_Definition_Clause (E, Attribute_Value_Size);
2744 -- Perform checks on specified size against computed sizes
2746 if Present (SC) then
2747 Check_Unused_Bits (RM_Size (E), Esiz);
2748 Check_Size_Too_Small (RM_Size (E), RM_Siz);
2749 end if;
2750 end if;
2752 -- Set sizes if unknown
2754 if Unknown_Esize (E) then
2755 Set_Esize (E, Esiz);
2756 end if;
2758 if Unknown_RM_Size (E) then
2759 Set_RM_Size (E, RM_Siz);
2760 end if;
2761 end Set_And_Check_Static_Size;
2763 -----------------------------
2764 -- Set_Composite_Alignment --
2765 -----------------------------
2767 procedure Set_Composite_Alignment (E : Entity_Id) is
2768 Siz : Uint;
2769 Align : Nat;
2771 begin
2772 if Unknown_Alignment (E) then
2773 if Known_Static_Esize (E) then
2774 Siz := Esize (E);
2776 elsif Unknown_Esize (E)
2777 and then Known_Static_RM_Size (E)
2778 then
2779 Siz := RM_Size (E);
2781 else
2782 return;
2783 end if;
2785 -- Size is known, alignment is not set
2787 -- Reset alignment to match size if size is exactly 2, 4, or 8
2788 -- storage units.
2790 if Siz = 2 * System_Storage_Unit then
2791 Align := 2;
2792 elsif Siz = 4 * System_Storage_Unit then
2793 Align := 4;
2794 elsif Siz = 8 * System_Storage_Unit then
2795 Align := 8;
2797 -- On VMS, also reset for odd "in between" sizes, e.g. a 17-bit
2798 -- record is given an alignment of 4. This is more consistent with
2799 -- what DEC Ada does.
2801 elsif OpenVMS_On_Target and then Siz > System_Storage_Unit then
2803 if Siz <= 2 * System_Storage_Unit then
2804 Align := 2;
2805 elsif Siz <= 4 * System_Storage_Unit then
2806 Align := 4;
2807 elsif Siz <= 8 * System_Storage_Unit then
2808 Align := 8;
2809 else
2810 return;
2811 end if;
2813 -- No special alignment fiddling needed
2815 else
2816 return;
2817 end if;
2819 -- Here Align is set to the proposed improved alignment
2821 if Align > Maximum_Alignment then
2822 Align := Maximum_Alignment;
2823 end if;
2825 -- Further processing for record types only to reduce the alignment
2826 -- set by the above processing in some specific cases. We do not
2827 -- do this for atomic records, since we need max alignment there.
2829 if Is_Record_Type (E) then
2831 -- For records, there is generally no point in setting alignment
2832 -- higher than word size since we cannot do better than move by
2833 -- words in any case
2835 if Align > System_Word_Size / System_Storage_Unit then
2836 Align := System_Word_Size / System_Storage_Unit;
2837 end if;
2839 -- Check components. If any component requires a higher
2840 -- alignment, then we set that higher alignment in any case.
2842 declare
2843 Comp : Entity_Id;
2845 begin
2846 Comp := First_Component (E);
2847 while Present (Comp) loop
2848 if Known_Alignment (Etype (Comp)) then
2849 declare
2850 Calign : constant Uint := Alignment (Etype (Comp));
2852 begin
2853 -- The cases to worry about are when the alignment
2854 -- of the component type is larger than the alignment
2855 -- we have so far, and either there is no component
2856 -- clause for the alignment, or the length set by
2857 -- the component clause matches the alignment set.
2859 if Calign > Align
2860 and then
2861 (Unknown_Esize (Comp)
2862 or else (Known_Static_Esize (Comp)
2863 and then
2864 Esize (Comp) =
2865 Calign * System_Storage_Unit))
2866 then
2867 Align := UI_To_Int (Calign);
2868 end if;
2869 end;
2870 end if;
2872 Next_Component (Comp);
2873 end loop;
2874 end;
2875 end if;
2877 -- Set chosen alignment
2879 Set_Alignment (E, UI_From_Int (Align));
2881 if Known_Static_Esize (E)
2882 and then Esize (E) < Align * System_Storage_Unit
2883 then
2884 Set_Esize (E, UI_From_Int (Align * System_Storage_Unit));
2885 end if;
2886 end if;
2887 end Set_Composite_Alignment;
2889 --------------------------
2890 -- Set_Discrete_RM_Size --
2891 --------------------------
2893 procedure Set_Discrete_RM_Size (Def_Id : Entity_Id) is
2894 FST : constant Entity_Id := First_Subtype (Def_Id);
2896 begin
2897 -- All discrete types except for the base types in standard
2898 -- are constrained, so indicate this by setting Is_Constrained.
2900 Set_Is_Constrained (Def_Id);
2902 -- We set generic types to have an unknown size, since the
2903 -- representation of a generic type is irrelevant, in view
2904 -- of the fact that they have nothing to do with code.
2906 if Is_Generic_Type (Root_Type (FST)) then
2907 Set_RM_Size (Def_Id, Uint_0);
2909 -- If the subtype statically matches the first subtype, then
2910 -- it is required to have exactly the same layout. This is
2911 -- required by aliasing considerations.
2913 elsif Def_Id /= FST and then
2914 Subtypes_Statically_Match (Def_Id, FST)
2915 then
2916 Set_RM_Size (Def_Id, RM_Size (FST));
2917 Set_Size_Info (Def_Id, FST);
2919 -- In all other cases the RM_Size is set to the minimum size.
2920 -- Note that this routine is never called for subtypes for which
2921 -- the RM_Size is set explicitly by an attribute clause.
2923 else
2924 Set_RM_Size (Def_Id, UI_From_Int (Minimum_Size (Def_Id)));
2925 end if;
2926 end Set_Discrete_RM_Size;
2928 ------------------------
2929 -- Set_Elem_Alignment --
2930 ------------------------
2932 procedure Set_Elem_Alignment (E : Entity_Id) is
2933 begin
2934 -- Do not set alignment for packed array types, unless we are doing
2935 -- front end layout, because otherwise this is always handled in the
2936 -- backend.
2938 if Is_Packed_Array_Type (E) and then not Frontend_Layout_On_Target then
2939 return;
2941 -- If there is an alignment clause, then we respect it
2943 elsif Has_Alignment_Clause (E) then
2944 return;
2946 -- If the size is not set, then don't attempt to set the alignment. This
2947 -- happens in the backend layout case for access-to-subprogram types.
2949 elsif not Known_Static_Esize (E) then
2950 return;
2952 -- For access types, do not set the alignment if the size is less than
2953 -- the allowed minimum size. This avoids cascaded error messages.
2955 elsif Is_Access_Type (E)
2956 and then Esize (E) < System_Address_Size
2957 then
2958 return;
2959 end if;
2961 -- Here we calculate the alignment as the largest power of two
2962 -- multiple of System.Storage_Unit that does not exceed either
2963 -- the actual size of the type, or the maximum allowed alignment.
2965 declare
2966 S : constant Int :=
2967 UI_To_Int (Esize (E)) / SSU;
2968 A : Nat;
2970 begin
2971 A := 1;
2972 while 2 * A <= Ttypes.Maximum_Alignment
2973 and then 2 * A <= S
2974 loop
2975 A := 2 * A;
2976 end loop;
2978 -- Now we think we should set the alignment to A, but we
2979 -- skip this if an alignment is already set to a value
2980 -- greater than A (happens for derived types).
2982 -- However, if the alignment is known and too small it
2983 -- must be increased, this happens in a case like:
2985 -- type R is new Character;
2986 -- for R'Size use 16;
2988 -- Here the alignment inherited from Character is 1, but
2989 -- it must be increased to 2 to reflect the increased size.
2991 if Unknown_Alignment (E) or else Alignment (E) < A then
2992 Init_Alignment (E, A);
2993 end if;
2994 end;
2995 end Set_Elem_Alignment;
2997 ----------------------
2998 -- SO_Ref_From_Expr --
2999 ----------------------
3001 function SO_Ref_From_Expr
3002 (Expr : Node_Id;
3003 Ins_Type : Entity_Id;
3004 Vtype : Entity_Id := Empty;
3005 Make_Func : Boolean := False) return Dynamic_SO_Ref
3007 Loc : constant Source_Ptr := Sloc (Ins_Type);
3009 K : constant Entity_Id :=
3010 Make_Defining_Identifier (Loc,
3011 Chars => New_Internal_Name ('K'));
3013 Decl : Node_Id;
3015 Vtype_Primary_View : Entity_Id;
3017 function Check_Node_V_Ref (N : Node_Id) return Traverse_Result;
3018 -- Function used to check one node for reference to V
3020 function Has_V_Ref is new Traverse_Func (Check_Node_V_Ref);
3021 -- Function used to traverse tree to check for reference to V
3023 ----------------------
3024 -- Check_Node_V_Ref --
3025 ----------------------
3027 function Check_Node_V_Ref (N : Node_Id) return Traverse_Result is
3028 begin
3029 if Nkind (N) = N_Identifier then
3030 if Chars (N) = Vname then
3031 return Abandon;
3032 else
3033 return Skip;
3034 end if;
3036 else
3037 return OK;
3038 end if;
3039 end Check_Node_V_Ref;
3041 -- Start of processing for SO_Ref_From_Expr
3043 begin
3044 -- Case of expression is an integer literal, in this case we just
3045 -- return the value (which must always be non-negative, since size
3046 -- and offset values can never be negative).
3048 if Nkind (Expr) = N_Integer_Literal then
3049 pragma Assert (Intval (Expr) >= 0);
3050 return Intval (Expr);
3051 end if;
3053 -- Case where there is a reference to V, create function
3055 if Has_V_Ref (Expr) = Abandon then
3057 pragma Assert (Present (Vtype));
3059 -- Check whether Vtype is a view of a private type and ensure that
3060 -- we use the primary view of the type (which is denoted by its
3061 -- Etype, whether it's the type's partial or full view entity).
3062 -- This is needed to make sure that we use the same (primary) view
3063 -- of the type for all V formals, whether the current view of the
3064 -- type is the partial or full view, so that types will always
3065 -- match on calls from one size function to another.
3067 if Has_Private_Declaration (Vtype) then
3068 Vtype_Primary_View := Etype (Vtype);
3069 else
3070 Vtype_Primary_View := Vtype;
3071 end if;
3073 Set_Is_Discrim_SO_Function (K);
3075 Decl :=
3076 Make_Subprogram_Body (Loc,
3078 Specification =>
3079 Make_Function_Specification (Loc,
3080 Defining_Unit_Name => K,
3081 Parameter_Specifications => New_List (
3082 Make_Parameter_Specification (Loc,
3083 Defining_Identifier =>
3084 Make_Defining_Identifier (Loc, Chars => Vname),
3085 Parameter_Type =>
3086 New_Occurrence_Of (Vtype_Primary_View, Loc))),
3087 Result_Definition =>
3088 New_Occurrence_Of (Standard_Unsigned, Loc)),
3090 Declarations => Empty_List,
3092 Handled_Statement_Sequence =>
3093 Make_Handled_Sequence_Of_Statements (Loc,
3094 Statements => New_List (
3095 Make_Return_Statement (Loc,
3096 Expression => Expr))));
3098 -- The caller requests that the expression be encapsulated in
3099 -- a parameterless function.
3101 elsif Make_Func then
3102 Decl :=
3103 Make_Subprogram_Body (Loc,
3105 Specification =>
3106 Make_Function_Specification (Loc,
3107 Defining_Unit_Name => K,
3108 Parameter_Specifications => Empty_List,
3109 Result_Definition =>
3110 New_Occurrence_Of (Standard_Unsigned, Loc)),
3112 Declarations => Empty_List,
3114 Handled_Statement_Sequence =>
3115 Make_Handled_Sequence_Of_Statements (Loc,
3116 Statements => New_List (
3117 Make_Return_Statement (Loc, Expression => Expr))));
3119 -- No reference to V and function not requested, so create a constant
3121 else
3122 Decl :=
3123 Make_Object_Declaration (Loc,
3124 Defining_Identifier => K,
3125 Object_Definition =>
3126 New_Occurrence_Of (Standard_Unsigned, Loc),
3127 Constant_Present => True,
3128 Expression => Expr);
3129 end if;
3131 Append_Freeze_Action (Ins_Type, Decl);
3132 Analyze (Decl);
3133 return Create_Dynamic_SO_Ref (K);
3134 end SO_Ref_From_Expr;
3136 end Layout;