Dead
[official-gcc.git] / gomp-20050608-branch / gcc / ada / layout.adb
blobb24b4d80010dc6989e2b69c1ef97ae6aff29c05e
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-2005, 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)
82 return Node_Id;
83 -- This is like Make_Op_Add except that it optimizes some cases knowing
84 -- that associative rearrangement is allowed for constant folding if one
85 -- of the operands is a compile time known value.
87 function Assoc_Multiply
88 (Loc : Source_Ptr;
89 Left_Opnd : Node_Id;
90 Right_Opnd : Node_Id)
91 return Node_Id;
92 -- This is like Make_Op_Multiply except that it optimizes some cases
93 -- knowing that associative rearrangement is allowed for constant
94 -- folding if one of the operands is a compile time known value
96 function Assoc_Subtract
97 (Loc : Source_Ptr;
98 Left_Opnd : Node_Id;
99 Right_Opnd : Node_Id)
100 return Node_Id;
101 -- This is like Make_Op_Subtract except that it optimizes some cases
102 -- knowing that associative rearrangement is allowed for constant
103 -- folding if one of the operands is a compile time known value
105 function Bits_To_SU (N : Node_Id) return Node_Id;
106 -- This is used when we cross the boundary from static sizes in bits to
107 -- dynamic sizes in storage units. If the argument N is anything other
108 -- than an integer literal, it is returned unchanged, but if it is an
109 -- integer literal, then it is taken as a size in bits, and is replaced
110 -- by the corresponding size in storage units.
112 function Compute_Length (Lo : Node_Id; Hi : Node_Id) return Node_Id;
113 -- Given expressions for the low bound (Lo) and the high bound (Hi),
114 -- Build an expression for the value hi-lo+1, converted to type
115 -- Standard.Unsigned. Takes care of the case where the operands
116 -- are of an enumeration type (so that the subtraction cannot be
117 -- done directly) by applying the Pos operator to Hi/Lo first.
119 function Expr_From_SO_Ref
120 (Loc : Source_Ptr;
121 D : SO_Ref;
122 Comp : Entity_Id := Empty)
123 return Node_Id;
124 -- Given a value D from a size or offset field, return an expression
125 -- representing the value stored. If the value is known at compile time,
126 -- then an N_Integer_Literal is returned with the appropriate value. If
127 -- the value references a constant entity, then an N_Identifier node
128 -- referencing this entity is returned. If the value denotes a size
129 -- function, then returns a call node denoting the given function, with
130 -- a single actual parameter that either refers to the parameter V of
131 -- an enclosing size function (if Comp is Empty or its type doesn't match
132 -- the function's formal), or else is a selected component V.c when Comp
133 -- denotes a component c whose type matches that of the function formal.
134 -- The Loc value is used for the Sloc value of constructed notes.
136 function SO_Ref_From_Expr
137 (Expr : Node_Id;
138 Ins_Type : Entity_Id;
139 Vtype : Entity_Id := Empty;
140 Make_Func : Boolean := False)
141 return Dynamic_SO_Ref;
142 -- This routine is used in the case where a size/offset value is dynamic
143 -- and is represented by the expression Expr. SO_Ref_From_Expr checks if
144 -- the Expr contains a reference to the identifier V, and if so builds
145 -- a function depending on discriminants of the formal parameter V which
146 -- is of type Vtype. Otherwise, if the parameter Make_Func is True, then
147 -- Expr will be encapsulated in a parameterless function; if Make_Func is
148 -- False, then a constant entity with the value Expr is built. The result
149 -- is a Dynamic_SO_Ref to the created entity. Note that Vtype can be
150 -- omitted if Expr does not contain any reference to V, the created entity.
151 -- The declaration created is inserted in the freeze actions of Ins_Type,
152 -- which also supplies the Sloc for created nodes. This function also takes
153 -- care of making sure that the expression is properly analyzed and
154 -- resolved (which may not be the case yet if we build the expression
155 -- in this unit).
157 function Get_Max_SU_Size (E : Entity_Id) return Node_Id;
158 -- E is an array type or subtype that has at least one index bound that
159 -- is the value of a record discriminant. For such an array, the function
160 -- computes an expression that yields the maximum possible size of the
161 -- array in storage units. The result is not defined for any other type,
162 -- or for arrays that do not depend on discriminants, and it is a fatal
163 -- error to call this unless Size_Depends_On_Discriminant (E) is True.
165 procedure Layout_Array_Type (E : Entity_Id);
166 -- Front-end layout of non-bit-packed array type or subtype
168 procedure Layout_Record_Type (E : Entity_Id);
169 -- Front-end layout of record type
171 procedure Rewrite_Integer (N : Node_Id; V : Uint);
172 -- Rewrite node N with an integer literal whose value is V. The Sloc
173 -- for the new node is taken from N, and the type of the literal is
174 -- set to a copy of the type of N on entry.
176 procedure Set_And_Check_Static_Size
177 (E : Entity_Id;
178 Esiz : SO_Ref;
179 RM_Siz : SO_Ref);
180 -- This procedure is called to check explicit given sizes (possibly
181 -- stored in the Esize and RM_Size fields of E) against computed
182 -- Object_Size (Esiz) and Value_Size (RM_Siz) values. Appropriate
183 -- errors and warnings are posted if specified sizes are inconsistent
184 -- with specified sizes. On return, the Esize and RM_Size fields of
185 -- E are set (either from previously given values, or from the newly
186 -- computed values, as appropriate).
188 procedure Set_Composite_Alignment (E : Entity_Id);
189 -- This procedure is called for record types and subtypes, and also for
190 -- atomic array types and subtypes. If no alignment is set, and the size
191 -- is 2 or 4 (or 8 if the word size is 8), then the alignment is set to
192 -- match the size.
194 ----------------------------
195 -- Adjust_Esize_Alignment --
196 ----------------------------
198 procedure Adjust_Esize_Alignment (E : Entity_Id) is
199 Abits : Int;
200 Esize_Set : Boolean;
202 begin
203 -- Nothing to do if size unknown
205 if Unknown_Esize (E) then
206 return;
207 end if;
209 -- Determine if size is constrained by an attribute definition clause
210 -- which must be obeyed. If so, we cannot increase the size in this
211 -- routine.
213 -- For a type, the issue is whether an object size clause has been
214 -- set. A normal size clause constrains only the value size (RM_Size)
216 if Is_Type (E) then
217 Esize_Set := Has_Object_Size_Clause (E);
219 -- For an object, the issue is whether a size clause is present
221 else
222 Esize_Set := Has_Size_Clause (E);
223 end if;
225 -- If size is known it must be a multiple of the storage unit size
227 if Esize (E) mod SSU /= 0 then
229 -- If not, and size specified, then give error
231 if Esize_Set then
232 Error_Msg_NE
233 ("size for& not a multiple of storage unit size",
234 Size_Clause (E), E);
235 return;
237 -- Otherwise bump up size to a storage unit boundary
239 else
240 Set_Esize (E, (Esize (E) + SSU - 1) / SSU * SSU);
241 end if;
242 end if;
244 -- Now we have the size set, it must be a multiple of the alignment
245 -- nothing more we can do here if the alignment is unknown here.
247 if Unknown_Alignment (E) then
248 return;
249 end if;
251 -- At this point both the Esize and Alignment are known, so we need
252 -- to make sure they are consistent.
254 Abits := UI_To_Int (Alignment (E)) * SSU;
256 if Esize (E) mod Abits = 0 then
257 return;
258 end if;
260 -- Here we have a situation where the Esize is not a multiple of
261 -- the alignment. We must either increase Esize or reduce the
262 -- alignment to correct this situation.
264 -- The case in which we can decrease the alignment is where the
265 -- alignment was not set by an alignment clause, and the type in
266 -- question is a discrete type, where it is definitely safe to
267 -- reduce the alignment. For example:
269 -- t : integer range 1 .. 2;
270 -- for t'size use 8;
272 -- In this situation, the initial alignment of t is 4, copied from
273 -- the Integer base type, but it is safe to reduce it to 1 at this
274 -- stage, since we will only be loading a single storage unit.
276 if Is_Discrete_Type (Etype (E))
277 and then not Has_Alignment_Clause (E)
278 then
279 loop
280 Abits := Abits / 2;
281 exit when Esize (E) mod Abits = 0;
282 end loop;
284 Init_Alignment (E, Abits / SSU);
285 return;
286 end if;
288 -- Now the only possible approach left is to increase the Esize
289 -- but we can't do that if the size was set by a specific clause.
291 if Esize_Set then
292 Error_Msg_NE
293 ("size for& is not a multiple of alignment",
294 Size_Clause (E), E);
296 -- Otherwise we can indeed increase the size to a multiple of alignment
298 else
299 Set_Esize (E, ((Esize (E) + (Abits - 1)) / Abits) * Abits);
300 end if;
301 end Adjust_Esize_Alignment;
303 ---------------
304 -- Assoc_Add --
305 ---------------
307 function Assoc_Add
308 (Loc : Source_Ptr;
309 Left_Opnd : Node_Id;
310 Right_Opnd : Node_Id)
311 return Node_Id
313 L : Node_Id;
314 R : Uint;
316 begin
317 -- Case of right operand is a constant
319 if Compile_Time_Known_Value (Right_Opnd) then
320 L := Left_Opnd;
321 R := Expr_Value (Right_Opnd);
323 -- Case of left operand is a constant
325 elsif Compile_Time_Known_Value (Left_Opnd) then
326 L := Right_Opnd;
327 R := Expr_Value (Left_Opnd);
329 -- Neither operand is a constant, do the addition with no optimization
331 else
332 return Make_Op_Add (Loc, Left_Opnd, Right_Opnd);
333 end if;
335 -- Case of left operand is an addition
337 if Nkind (L) = N_Op_Add then
339 -- (C1 + E) + C2 = (C1 + C2) + E
341 if Compile_Time_Known_Value (Sinfo.Left_Opnd (L)) then
342 Rewrite_Integer
343 (Sinfo.Left_Opnd (L),
344 Expr_Value (Sinfo.Left_Opnd (L)) + R);
345 return L;
347 -- (E + C1) + C2 = E + (C1 + C2)
349 elsif Compile_Time_Known_Value (Sinfo.Right_Opnd (L)) then
350 Rewrite_Integer
351 (Sinfo.Right_Opnd (L),
352 Expr_Value (Sinfo.Right_Opnd (L)) + R);
353 return L;
354 end if;
356 -- Case of left operand is a subtraction
358 elsif Nkind (L) = N_Op_Subtract then
360 -- (C1 - E) + C2 = (C1 + C2) + E
362 if Compile_Time_Known_Value (Sinfo.Left_Opnd (L)) then
363 Rewrite_Integer
364 (Sinfo.Left_Opnd (L),
365 Expr_Value (Sinfo.Left_Opnd (L)) + R);
366 return L;
368 -- (E - C1) + C2 = E - (C1 - C2)
370 elsif Compile_Time_Known_Value (Sinfo.Right_Opnd (L)) then
371 Rewrite_Integer
372 (Sinfo.Right_Opnd (L),
373 Expr_Value (Sinfo.Right_Opnd (L)) - R);
374 return L;
375 end if;
376 end if;
378 -- Not optimizable, do the addition
380 return Make_Op_Add (Loc, Left_Opnd, Right_Opnd);
381 end Assoc_Add;
383 --------------------
384 -- Assoc_Multiply --
385 --------------------
387 function Assoc_Multiply
388 (Loc : Source_Ptr;
389 Left_Opnd : Node_Id;
390 Right_Opnd : Node_Id)
391 return Node_Id
393 L : Node_Id;
394 R : Uint;
396 begin
397 -- Case of right operand is a constant
399 if Compile_Time_Known_Value (Right_Opnd) then
400 L := Left_Opnd;
401 R := Expr_Value (Right_Opnd);
403 -- Case of left operand is a constant
405 elsif Compile_Time_Known_Value (Left_Opnd) then
406 L := Right_Opnd;
407 R := Expr_Value (Left_Opnd);
409 -- Neither operand is a constant, do the multiply with no optimization
411 else
412 return Make_Op_Multiply (Loc, Left_Opnd, Right_Opnd);
413 end if;
415 -- Case of left operand is an multiplication
417 if Nkind (L) = N_Op_Multiply then
419 -- (C1 * E) * C2 = (C1 * C2) + E
421 if Compile_Time_Known_Value (Sinfo.Left_Opnd (L)) then
422 Rewrite_Integer
423 (Sinfo.Left_Opnd (L),
424 Expr_Value (Sinfo.Left_Opnd (L)) * R);
425 return L;
427 -- (E * C1) * C2 = E * (C1 * C2)
429 elsif Compile_Time_Known_Value (Sinfo.Right_Opnd (L)) then
430 Rewrite_Integer
431 (Sinfo.Right_Opnd (L),
432 Expr_Value (Sinfo.Right_Opnd (L)) * R);
433 return L;
434 end if;
435 end if;
437 -- Not optimizable, do the multiplication
439 return Make_Op_Multiply (Loc, Left_Opnd, Right_Opnd);
440 end Assoc_Multiply;
442 --------------------
443 -- Assoc_Subtract --
444 --------------------
446 function Assoc_Subtract
447 (Loc : Source_Ptr;
448 Left_Opnd : Node_Id;
449 Right_Opnd : Node_Id)
450 return Node_Id
452 L : Node_Id;
453 R : Uint;
455 begin
456 -- Case of right operand is a constant
458 if Compile_Time_Known_Value (Right_Opnd) then
459 L := Left_Opnd;
460 R := Expr_Value (Right_Opnd);
462 -- Right operand is a constant, do the subtract with no optimization
464 else
465 return Make_Op_Subtract (Loc, Left_Opnd, Right_Opnd);
466 end if;
468 -- Case of left operand is an addition
470 if Nkind (L) = N_Op_Add then
472 -- (C1 + E) - C2 = (C1 - C2) + E
474 if Compile_Time_Known_Value (Sinfo.Left_Opnd (L)) then
475 Rewrite_Integer
476 (Sinfo.Left_Opnd (L),
477 Expr_Value (Sinfo.Left_Opnd (L)) - R);
478 return L;
480 -- (E + C1) - C2 = E + (C1 - C2)
482 elsif Compile_Time_Known_Value (Sinfo.Right_Opnd (L)) then
483 Rewrite_Integer
484 (Sinfo.Right_Opnd (L),
485 Expr_Value (Sinfo.Right_Opnd (L)) - R);
486 return L;
487 end if;
489 -- Case of left operand is a subtraction
491 elsif Nkind (L) = N_Op_Subtract then
493 -- (C1 - E) - C2 = (C1 - C2) + E
495 if Compile_Time_Known_Value (Sinfo.Left_Opnd (L)) then
496 Rewrite_Integer
497 (Sinfo.Left_Opnd (L),
498 Expr_Value (Sinfo.Left_Opnd (L)) + R);
499 return L;
501 -- (E - C1) - C2 = E - (C1 + C2)
503 elsif Compile_Time_Known_Value (Sinfo.Right_Opnd (L)) then
504 Rewrite_Integer
505 (Sinfo.Right_Opnd (L),
506 Expr_Value (Sinfo.Right_Opnd (L)) + R);
507 return L;
508 end if;
509 end if;
511 -- Not optimizable, do the subtraction
513 return Make_Op_Subtract (Loc, Left_Opnd, Right_Opnd);
514 end Assoc_Subtract;
516 ----------------
517 -- Bits_To_SU --
518 ----------------
520 function Bits_To_SU (N : Node_Id) return Node_Id is
521 begin
522 if Nkind (N) = N_Integer_Literal then
523 Set_Intval (N, (Intval (N) + (SSU - 1)) / SSU);
524 end if;
526 return N;
527 end Bits_To_SU;
529 --------------------
530 -- Compute_Length --
531 --------------------
533 function Compute_Length (Lo : Node_Id; Hi : Node_Id) return Node_Id is
534 Loc : constant Source_Ptr := Sloc (Lo);
535 Typ : constant Entity_Id := Etype (Lo);
536 Lo_Op : Node_Id;
537 Hi_Op : Node_Id;
538 Lo_Dim : Uint;
539 Hi_Dim : Uint;
541 begin
542 -- If the bounds are First and Last attributes for the same dimension
543 -- and both have prefixes that denotes the same entity, then we create
544 -- and return a Length attribute. This may allow the back end to
545 -- generate better code in cases where it already has the length.
547 if Nkind (Lo) = N_Attribute_Reference
548 and then Attribute_Name (Lo) = Name_First
549 and then Nkind (Hi) = N_Attribute_Reference
550 and then Attribute_Name (Hi) = Name_Last
551 and then Is_Entity_Name (Prefix (Lo))
552 and then Is_Entity_Name (Prefix (Hi))
553 and then Entity (Prefix (Lo)) = Entity (Prefix (Hi))
554 then
555 Lo_Dim := Uint_1;
556 Hi_Dim := Uint_1;
558 if Present (First (Expressions (Lo))) then
559 Lo_Dim := Expr_Value (First (Expressions (Lo)));
560 end if;
562 if Present (First (Expressions (Hi))) then
563 Hi_Dim := Expr_Value (First (Expressions (Hi)));
564 end if;
566 if Lo_Dim = Hi_Dim then
567 return
568 Make_Attribute_Reference (Loc,
569 Prefix => New_Occurrence_Of
570 (Entity (Prefix (Lo)), Loc),
571 Attribute_Name => Name_Length,
572 Expressions => New_List
573 (Make_Integer_Literal (Loc, Lo_Dim)));
574 end if;
575 end if;
577 Lo_Op := New_Copy_Tree (Lo);
578 Hi_Op := New_Copy_Tree (Hi);
580 -- If type is enumeration type, then use Pos attribute to convert
581 -- to integer type for which subtraction is a permitted operation.
583 if Is_Enumeration_Type (Typ) then
584 Lo_Op :=
585 Make_Attribute_Reference (Loc,
586 Prefix => New_Occurrence_Of (Typ, Loc),
587 Attribute_Name => Name_Pos,
588 Expressions => New_List (Lo_Op));
590 Hi_Op :=
591 Make_Attribute_Reference (Loc,
592 Prefix => New_Occurrence_Of (Typ, Loc),
593 Attribute_Name => Name_Pos,
594 Expressions => New_List (Hi_Op));
595 end if;
597 return
598 Assoc_Add (Loc,
599 Left_Opnd =>
600 Assoc_Subtract (Loc,
601 Left_Opnd => Hi_Op,
602 Right_Opnd => Lo_Op),
603 Right_Opnd => Make_Integer_Literal (Loc, 1));
604 end Compute_Length;
606 ----------------------
607 -- Expr_From_SO_Ref --
608 ----------------------
610 function Expr_From_SO_Ref
611 (Loc : Source_Ptr;
612 D : SO_Ref;
613 Comp : Entity_Id := Empty)
614 return Node_Id
616 Ent : Entity_Id;
618 begin
619 if Is_Dynamic_SO_Ref (D) then
620 Ent := Get_Dynamic_SO_Entity (D);
622 if Is_Discrim_SO_Function (Ent) then
623 -- If a component is passed in whose type matches the type
624 -- of the function formal, then select that component from
625 -- the "V" parameter rather than passing "V" directly.
627 if Present (Comp)
628 and then Base_Type (Etype (Comp))
629 = Base_Type (Etype (First_Formal (Ent)))
630 then
631 return
632 Make_Function_Call (Loc,
633 Name => New_Occurrence_Of (Ent, Loc),
634 Parameter_Associations => New_List (
635 Make_Selected_Component (Loc,
636 Prefix => Make_Identifier (Loc, Chars => Vname),
637 Selector_Name => New_Occurrence_Of (Comp, Loc))));
639 else
640 return
641 Make_Function_Call (Loc,
642 Name => New_Occurrence_Of (Ent, Loc),
643 Parameter_Associations => New_List (
644 Make_Identifier (Loc, Chars => Vname)));
645 end if;
647 else
648 return New_Occurrence_Of (Ent, Loc);
649 end if;
651 else
652 return Make_Integer_Literal (Loc, D);
653 end if;
654 end Expr_From_SO_Ref;
656 ---------------------
657 -- Get_Max_SU_Size --
658 ---------------------
660 function Get_Max_SU_Size (E : Entity_Id) return Node_Id is
661 Loc : constant Source_Ptr := Sloc (E);
662 Indx : Node_Id;
663 Ityp : Entity_Id;
664 Lo : Node_Id;
665 Hi : Node_Id;
666 S : Uint;
667 Len : Node_Id;
669 type Val_Status_Type is (Const, Dynamic);
671 type Val_Type (Status : Val_Status_Type := Const) is
672 record
673 case Status is
674 when Const => Val : Uint;
675 when Dynamic => Nod : Node_Id;
676 end case;
677 end record;
678 -- Shows the status of the value so far. Const means that the value
679 -- is constant, and Val is the current constant value. Dynamic means
680 -- that the value is dynamic, and in this case Nod is the Node_Id of
681 -- the expression to compute the value.
683 Size : Val_Type;
684 -- Calculated value so far if Size.Status = Const,
685 -- or expression value so far if Size.Status = Dynamic.
687 SU_Convert_Required : Boolean := False;
688 -- This is set to True if the final result must be converted from
689 -- bits to storage units (rounding up to a storage unit boundary).
691 -----------------------
692 -- Local Subprograms --
693 -----------------------
695 procedure Max_Discrim (N : in out Node_Id);
696 -- If the node N represents a discriminant, replace it by the maximum
697 -- value of the discriminant.
699 procedure Min_Discrim (N : in out Node_Id);
700 -- If the node N represents a discriminant, replace it by the minimum
701 -- value of the discriminant.
703 -----------------
704 -- Max_Discrim --
705 -----------------
707 procedure Max_Discrim (N : in out Node_Id) is
708 begin
709 if Nkind (N) = N_Identifier
710 and then Ekind (Entity (N)) = E_Discriminant
711 then
712 N := Type_High_Bound (Etype (N));
713 end if;
714 end Max_Discrim;
716 -----------------
717 -- Min_Discrim --
718 -----------------
720 procedure Min_Discrim (N : in out Node_Id) is
721 begin
722 if Nkind (N) = N_Identifier
723 and then Ekind (Entity (N)) = E_Discriminant
724 then
725 N := Type_Low_Bound (Etype (N));
726 end if;
727 end Min_Discrim;
729 -- Start of processing for Get_Max_SU_Size
731 begin
732 pragma Assert (Size_Depends_On_Discriminant (E));
734 -- Initialize status from component size
736 if Known_Static_Component_Size (E) then
737 Size := (Const, Component_Size (E));
739 else
740 Size := (Dynamic, Expr_From_SO_Ref (Loc, Component_Size (E)));
741 end if;
743 -- Loop through indices
745 Indx := First_Index (E);
746 while Present (Indx) loop
747 Ityp := Etype (Indx);
748 Lo := Type_Low_Bound (Ityp);
749 Hi := Type_High_Bound (Ityp);
751 Min_Discrim (Lo);
752 Max_Discrim (Hi);
754 -- Value of the current subscript range is statically known
756 if Compile_Time_Known_Value (Lo)
757 and then Compile_Time_Known_Value (Hi)
758 then
759 S := Expr_Value (Hi) - Expr_Value (Lo) + 1;
761 -- If known flat bound, entire size of array is zero!
763 if S <= 0 then
764 return Make_Integer_Literal (Loc, 0);
765 end if;
767 -- Current value is constant, evolve value
769 if Size.Status = Const then
770 Size.Val := Size.Val * S;
772 -- Current value is dynamic
774 else
775 -- An interesting little optimization, if we have a pending
776 -- conversion from bits to storage units, and the current
777 -- length is a multiple of the storage unit size, then we
778 -- can take the factor out here statically, avoiding some
779 -- extra dynamic computations at the end.
781 if SU_Convert_Required and then S mod SSU = 0 then
782 S := S / SSU;
783 SU_Convert_Required := False;
784 end if;
786 Size.Nod :=
787 Assoc_Multiply (Loc,
788 Left_Opnd => Size.Nod,
789 Right_Opnd =>
790 Make_Integer_Literal (Loc, Intval => S));
791 end if;
793 -- Value of the current subscript range is dynamic
795 else
796 -- If the current size value is constant, then here is where we
797 -- make a transition to dynamic values, which are always stored
798 -- in storage units, However, we do not want to convert to SU's
799 -- too soon, consider the case of a packed array of single bits,
800 -- we want to do the SU conversion after computing the size in
801 -- this case.
803 if Size.Status = Const then
805 -- If the current value is a multiple of the storage unit,
806 -- then most certainly we can do the conversion now, simply
807 -- by dividing the current value by the storage unit value.
808 -- If this works, we set SU_Convert_Required to False.
810 if Size.Val mod SSU = 0 then
812 Size :=
813 (Dynamic, Make_Integer_Literal (Loc, Size.Val / SSU));
814 SU_Convert_Required := False;
816 -- Otherwise, we go ahead and convert the value in bits,
817 -- and set SU_Convert_Required to True to ensure that the
818 -- final value is indeed properly converted.
820 else
821 Size := (Dynamic, Make_Integer_Literal (Loc, Size.Val));
822 SU_Convert_Required := True;
823 end if;
824 end if;
826 -- Length is hi-lo+1
828 Len := Compute_Length (Lo, Hi);
830 -- Check possible range of Len
832 declare
833 OK : Boolean;
834 LLo : Uint;
835 LHi : Uint;
837 begin
838 Set_Parent (Len, E);
839 Determine_Range (Len, OK, LLo, LHi);
841 Len := Convert_To (Standard_Unsigned, Len);
843 -- If we cannot verify that range cannot be super-flat,
844 -- we need a max with zero, since length must be non-neg.
846 if not OK or else LLo < 0 then
847 Len :=
848 Make_Attribute_Reference (Loc,
849 Prefix =>
850 New_Occurrence_Of (Standard_Unsigned, Loc),
851 Attribute_Name => Name_Max,
852 Expressions => New_List (
853 Make_Integer_Literal (Loc, 0),
854 Len));
855 end if;
856 end;
857 end if;
859 Next_Index (Indx);
860 end loop;
862 -- Here after processing all bounds to set sizes. If the value is
863 -- a constant, then it is bits, so we convert to storage units.
865 if Size.Status = Const then
866 return Bits_To_SU (Make_Integer_Literal (Loc, Size.Val));
868 -- Case where the value is dynamic
870 else
871 -- Do convert from bits to SU's if needed
873 if SU_Convert_Required then
875 -- The expression required is (Size.Nod + SU - 1) / SU
877 Size.Nod :=
878 Make_Op_Divide (Loc,
879 Left_Opnd =>
880 Make_Op_Add (Loc,
881 Left_Opnd => Size.Nod,
882 Right_Opnd => Make_Integer_Literal (Loc, SSU - 1)),
883 Right_Opnd => Make_Integer_Literal (Loc, SSU));
884 end if;
886 return Size.Nod;
887 end if;
888 end Get_Max_SU_Size;
890 -----------------------
891 -- Layout_Array_Type --
892 -----------------------
894 procedure Layout_Array_Type (E : Entity_Id) is
895 Loc : constant Source_Ptr := Sloc (E);
896 Ctyp : constant Entity_Id := Component_Type (E);
897 Indx : Node_Id;
898 Ityp : Entity_Id;
899 Lo : Node_Id;
900 Hi : Node_Id;
901 S : Uint;
902 Len : Node_Id;
904 Insert_Typ : Entity_Id;
905 -- This is the type with which any generated constants or functions
906 -- will be associated (i.e. inserted into the freeze actions). This
907 -- is normally the type being laid out. The exception occurs when
908 -- we are laying out Itype's which are local to a record type, and
909 -- whose scope is this record type. Such types do not have freeze
910 -- nodes (because we have no place to put them).
912 ------------------------------------
913 -- How An Array Type is Laid Out --
914 ------------------------------------
916 -- Here is what goes on. We need to multiply the component size of
917 -- the array (which has already been set) by the length of each of
918 -- the indexes. If all these values are known at compile time, then
919 -- the resulting size of the array is the appropriate constant value.
921 -- If the component size or at least one bound is dynamic (but no
922 -- discriminants are present), then the size will be computed as an
923 -- expression that calculates the proper size.
925 -- If there is at least one discriminant bound, then the size is also
926 -- computed as an expression, but this expression contains discriminant
927 -- values which are obtained by selecting from a function parameter, and
928 -- the size is given by a function that is passed the variant record in
929 -- question, and whose body is the expression.
931 type Val_Status_Type is (Const, Dynamic, Discrim);
933 type Val_Type (Status : Val_Status_Type := Const) is
934 record
935 case Status is
936 when Const =>
937 Val : Uint;
938 -- Calculated value so far if Val_Status = Const
940 when Dynamic | Discrim =>
941 Nod : Node_Id;
942 -- Expression value so far if Val_Status /= Const
944 end case;
945 end record;
946 -- Records the value or expression computed so far. Const means that
947 -- the value is constant, and Val is the current constant value.
948 -- Dynamic means that the value is dynamic, and in this case Nod is
949 -- the Node_Id of the expression to compute the value, and Discrim
950 -- means that at least one bound is a discriminant, in which case Nod
951 -- is the expression so far (which will be the body of the function).
953 Size : Val_Type;
954 -- Value of size computed so far. See comments above
956 Vtyp : Entity_Id := Empty;
957 -- Variant record type for the formal parameter of the
958 -- discriminant function V if Status = Discrim.
960 SU_Convert_Required : Boolean := False;
961 -- This is set to True if the final result must be converted from
962 -- bits to storage units (rounding up to a storage unit boundary).
964 Storage_Divisor : Uint := UI_From_Int (SSU);
965 -- This is the amount that a nonstatic computed size will be divided
966 -- by to convert it from bits to storage units. This is normally
967 -- equal to SSU, but can be reduced in the case of packed components
968 -- that fit evenly into a storage unit.
970 Make_Size_Function : Boolean := False;
971 -- Indicates whether to request that SO_Ref_From_Expr should
972 -- encapsulate the array size expresion in a function.
974 procedure Discrimify (N : in out Node_Id);
975 -- If N represents a discriminant, then the Size.Status is set to
976 -- Discrim, and Vtyp is set. The parameter N is replaced with the
977 -- proper expression to extract the discriminant value from V.
979 ----------------
980 -- Discrimify --
981 ----------------
983 procedure Discrimify (N : in out Node_Id) is
984 Decl : Node_Id;
985 Typ : Entity_Id;
987 begin
988 if Nkind (N) = N_Identifier
989 and then Ekind (Entity (N)) = E_Discriminant
990 then
991 Set_Size_Depends_On_Discriminant (E);
993 if Size.Status /= Discrim then
994 Decl := Parent (Parent (Entity (N)));
995 Size := (Discrim, Size.Nod);
996 Vtyp := Defining_Identifier (Decl);
997 end if;
999 Typ := Etype (N);
1001 N :=
1002 Make_Selected_Component (Loc,
1003 Prefix => Make_Identifier (Loc, Chars => Vname),
1004 Selector_Name => New_Occurrence_Of (Entity (N), Loc));
1006 -- Set the Etype attributes of the selected name and its prefix.
1007 -- Analyze_And_Resolve can't be called here because the Vname
1008 -- entity denoted by the prefix will not yet exist (it's created
1009 -- by SO_Ref_From_Expr, called at the end of Layout_Array_Type).
1011 Set_Etype (Prefix (N), Vtyp);
1012 Set_Etype (N, Typ);
1013 end if;
1014 end Discrimify;
1016 -- Start of processing for Layout_Array_Type
1018 begin
1019 -- Default alignment is component alignment
1021 if Unknown_Alignment (E) then
1022 Set_Alignment (E, Alignment (Ctyp));
1023 end if;
1025 -- Calculate proper type for insertions
1027 if Is_Record_Type (Underlying_Type (Scope (E))) then
1028 Insert_Typ := Underlying_Type (Scope (E));
1029 else
1030 Insert_Typ := E;
1031 end if;
1033 -- If the component type is a generic formal type then there's no point
1034 -- in determining a size for the array type.
1036 if Is_Generic_Type (Ctyp) then
1037 return;
1038 end if;
1040 -- Deal with component size if base type
1042 if Ekind (E) = E_Array_Type then
1044 -- Cannot do anything if Esize of component type unknown
1046 if Unknown_Esize (Ctyp) then
1047 return;
1048 end if;
1050 -- Set component size if not set already
1052 if Unknown_Component_Size (E) then
1053 Set_Component_Size (E, Esize (Ctyp));
1054 end if;
1055 end if;
1057 -- (RM 13.3 (48)) says that the size of an unconstrained array
1058 -- is implementation defined. We choose to leave it as Unknown
1059 -- here, and the actual behavior is determined by the back end.
1061 if not Is_Constrained (E) then
1062 return;
1063 end if;
1065 -- Initialize status from component size
1067 if Known_Static_Component_Size (E) then
1068 Size := (Const, Component_Size (E));
1070 else
1071 Size := (Dynamic, Expr_From_SO_Ref (Loc, Component_Size (E)));
1072 end if;
1074 -- Loop to process array indices
1076 Indx := First_Index (E);
1077 while Present (Indx) loop
1078 Ityp := Etype (Indx);
1080 -- If an index of the array is a generic formal type then there's
1081 -- no point in determining a size for the array type.
1083 if Is_Generic_Type (Ityp) then
1084 return;
1085 end if;
1087 Lo := Type_Low_Bound (Ityp);
1088 Hi := Type_High_Bound (Ityp);
1090 -- Value of the current subscript range is statically known
1092 if Compile_Time_Known_Value (Lo)
1093 and then Compile_Time_Known_Value (Hi)
1094 then
1095 S := Expr_Value (Hi) - Expr_Value (Lo) + 1;
1097 -- If known flat bound, entire size of array is zero!
1099 if S <= 0 then
1100 Set_Esize (E, Uint_0);
1101 Set_RM_Size (E, Uint_0);
1102 return;
1103 end if;
1105 -- If constant, evolve value
1107 if Size.Status = Const then
1108 Size.Val := Size.Val * S;
1110 -- Current value is dynamic
1112 else
1113 -- An interesting little optimization, if we have a pending
1114 -- conversion from bits to storage units, and the current
1115 -- length is a multiple of the storage unit size, then we
1116 -- can take the factor out here statically, avoiding some
1117 -- extra dynamic computations at the end.
1119 if SU_Convert_Required and then S mod SSU = 0 then
1120 S := S / SSU;
1121 SU_Convert_Required := False;
1122 end if;
1124 -- Now go ahead and evolve the expression
1126 Size.Nod :=
1127 Assoc_Multiply (Loc,
1128 Left_Opnd => Size.Nod,
1129 Right_Opnd =>
1130 Make_Integer_Literal (Loc, Intval => S));
1131 end if;
1133 -- Value of the current subscript range is dynamic
1135 else
1136 -- If the current size value is constant, then here is where we
1137 -- make a transition to dynamic values, which are always stored
1138 -- in storage units, However, we do not want to convert to SU's
1139 -- too soon, consider the case of a packed array of single bits,
1140 -- we want to do the SU conversion after computing the size in
1141 -- this case.
1143 if Size.Status = Const then
1145 -- If the current value is a multiple of the storage unit,
1146 -- then most certainly we can do the conversion now, simply
1147 -- by dividing the current value by the storage unit value.
1148 -- If this works, we set SU_Convert_Required to False.
1150 if Size.Val mod SSU = 0 then
1151 Size :=
1152 (Dynamic, Make_Integer_Literal (Loc, Size.Val / SSU));
1153 SU_Convert_Required := False;
1155 -- If the current value is a factor of the storage unit,
1156 -- then we can use a value of one for the size and reduce
1157 -- the strength of the later division.
1159 elsif SSU mod Size.Val = 0 then
1160 Storage_Divisor := SSU / Size.Val;
1161 Size := (Dynamic, Make_Integer_Literal (Loc, Uint_1));
1162 SU_Convert_Required := True;
1164 -- Otherwise, we go ahead and convert the value in bits,
1165 -- and set SU_Convert_Required to True to ensure that the
1166 -- final value is indeed properly converted.
1168 else
1169 Size := (Dynamic, Make_Integer_Literal (Loc, Size.Val));
1170 SU_Convert_Required := True;
1171 end if;
1172 end if;
1174 Discrimify (Lo);
1175 Discrimify (Hi);
1177 -- Length is hi-lo+1
1179 Len := Compute_Length (Lo, Hi);
1181 -- If Len isn't a Length attribute, then its range needs to
1182 -- be checked a possible Max with zero needs to be computed.
1184 if Nkind (Len) /= N_Attribute_Reference
1185 or else Attribute_Name (Len) /= Name_Length
1186 then
1187 declare
1188 OK : Boolean;
1189 LLo : Uint;
1190 LHi : Uint;
1192 begin
1193 -- Check possible range of Len
1195 Set_Parent (Len, E);
1196 Determine_Range (Len, OK, LLo, LHi);
1198 Len := Convert_To (Standard_Unsigned, Len);
1200 -- If range definitely flat or superflat,
1201 -- result size is zero
1203 if OK and then LHi <= 0 then
1204 Set_Esize (E, Uint_0);
1205 Set_RM_Size (E, Uint_0);
1206 return;
1207 end if;
1209 -- If we cannot verify that range cannot be super-flat,
1210 -- we need a maximum with zero, since length cannot be
1211 -- negative.
1213 if not OK or else LLo < 0 then
1214 Len :=
1215 Make_Attribute_Reference (Loc,
1216 Prefix =>
1217 New_Occurrence_Of (Standard_Unsigned, Loc),
1218 Attribute_Name => Name_Max,
1219 Expressions => New_List (
1220 Make_Integer_Literal (Loc, 0),
1221 Len));
1222 end if;
1223 end;
1224 end if;
1226 -- At this stage, Len has the expression for the length
1228 Size.Nod :=
1229 Assoc_Multiply (Loc,
1230 Left_Opnd => Size.Nod,
1231 Right_Opnd => Len);
1232 end if;
1234 Next_Index (Indx);
1235 end loop;
1237 -- Here after processing all bounds to set sizes. If the value is
1238 -- a constant, then it is bits, and the only thing we need to do
1239 -- is to check against explicit given size and do alignment adjust.
1241 if Size.Status = Const then
1242 Set_And_Check_Static_Size (E, Size.Val, Size.Val);
1243 Adjust_Esize_Alignment (E);
1245 -- Case where the value is dynamic
1247 else
1248 -- Do convert from bits to SU's if needed
1250 if SU_Convert_Required then
1252 -- The expression required is:
1253 -- (Size.Nod + Storage_Divisor - 1) / Storage_Divisor
1255 Size.Nod :=
1256 Make_Op_Divide (Loc,
1257 Left_Opnd =>
1258 Make_Op_Add (Loc,
1259 Left_Opnd => Size.Nod,
1260 Right_Opnd => Make_Integer_Literal
1261 (Loc, Storage_Divisor - 1)),
1262 Right_Opnd => Make_Integer_Literal (Loc, Storage_Divisor));
1263 end if;
1265 -- If the array entity is not declared at the library level and its
1266 -- not nested within a subprogram that is marked for inlining, then
1267 -- we request that the size expression be encapsulated in a function.
1268 -- Since this expression is not needed in most cases, we prefer not
1269 -- to incur the overhead of the computation on calls to the enclosing
1270 -- subprogram except for subprograms that require the size.
1272 if not Is_Library_Level_Entity (E) then
1273 Make_Size_Function := True;
1275 declare
1276 Parent_Subp : Entity_Id := Enclosing_Subprogram (E);
1278 begin
1279 while Present (Parent_Subp) loop
1280 if Is_Inlined (Parent_Subp) then
1281 Make_Size_Function := False;
1282 exit;
1283 end if;
1285 Parent_Subp := Enclosing_Subprogram (Parent_Subp);
1286 end loop;
1287 end;
1288 end if;
1290 -- Now set the dynamic size (the Value_Size is always the same
1291 -- as the Object_Size for arrays whose length is dynamic).
1293 -- ??? If Size.Status = Dynamic, Vtyp will not have been set.
1294 -- The added initialization sets it to Empty now, but is this
1295 -- correct?
1297 Set_Esize
1299 SO_Ref_From_Expr
1300 (Size.Nod, Insert_Typ, Vtyp, Make_Func => Make_Size_Function));
1301 Set_RM_Size (E, Esize (E));
1302 end if;
1303 end Layout_Array_Type;
1305 -------------------
1306 -- Layout_Object --
1307 -------------------
1309 procedure Layout_Object (E : Entity_Id) is
1310 T : constant Entity_Id := Etype (E);
1312 begin
1313 -- Nothing to do if backend does layout
1315 if not Frontend_Layout_On_Target then
1316 return;
1317 end if;
1319 -- Set size if not set for object and known for type. Use the
1320 -- RM_Size if that is known for the type and Esize is not.
1322 if Unknown_Esize (E) then
1323 if Known_Esize (T) then
1324 Set_Esize (E, Esize (T));
1326 elsif Known_RM_Size (T) then
1327 Set_Esize (E, RM_Size (T));
1328 end if;
1329 end if;
1331 -- Set alignment from type if unknown and type alignment known
1333 if Unknown_Alignment (E) and then Known_Alignment (T) then
1334 Set_Alignment (E, Alignment (T));
1335 end if;
1337 -- Make sure size and alignment are consistent
1339 Adjust_Esize_Alignment (E);
1341 -- Final adjustment, if we don't know the alignment, and the Esize
1342 -- was not set by an explicit Object_Size attribute clause, then
1343 -- we reset the Esize to unknown, since we really don't know it.
1345 if Unknown_Alignment (E)
1346 and then not Has_Size_Clause (E)
1347 then
1348 Set_Esize (E, Uint_0);
1349 end if;
1350 end Layout_Object;
1352 ------------------------
1353 -- Layout_Record_Type --
1354 ------------------------
1356 procedure Layout_Record_Type (E : Entity_Id) is
1357 Loc : constant Source_Ptr := Sloc (E);
1358 Decl : Node_Id;
1360 Comp : Entity_Id;
1361 -- Current component being laid out
1363 Prev_Comp : Entity_Id;
1364 -- Previous laid out component
1366 procedure Get_Next_Component_Location
1367 (Prev_Comp : Entity_Id;
1368 Align : Uint;
1369 New_Npos : out SO_Ref;
1370 New_Fbit : out SO_Ref;
1371 New_NPMax : out SO_Ref;
1372 Force_SU : Boolean);
1373 -- Given the previous component in Prev_Comp, which is already laid
1374 -- out, and the alignment of the following component, lays out the
1375 -- following component, and returns its starting position in New_Npos
1376 -- (Normalized_Position value), New_Fbit (Normalized_First_Bit value),
1377 -- and New_NPMax (Normalized_Position_Max value). If Prev_Comp is empty
1378 -- (no previous component is present), then New_Npos, New_Fbit and
1379 -- New_NPMax are all set to zero on return. This procedure is also
1380 -- used to compute the size of a record or variant by giving it the
1381 -- last component, and the record alignment. Force_SU is used to force
1382 -- the new component location to be aligned on a storage unit boundary,
1383 -- even in a packed record, False means that the new position does not
1384 -- need to be bumped to a storage unit boundary, True means a storage
1385 -- unit boundary is always required.
1387 procedure Layout_Component (Comp : Entity_Id; Prev_Comp : Entity_Id);
1388 -- Lays out component Comp, given Prev_Comp, the previously laid-out
1389 -- component (Prev_Comp = Empty if no components laid out yet). The
1390 -- alignment of the record itself is also updated if needed. Both
1391 -- Comp and Prev_Comp can be either components or discriminants.
1393 procedure Layout_Components
1394 (From : Entity_Id;
1395 To : Entity_Id;
1396 Esiz : out SO_Ref;
1397 RM_Siz : out SO_Ref);
1398 -- This procedure lays out the components of the given component list
1399 -- which contains the components starting with From and ending with To.
1400 -- The Next_Entity chain is used to traverse the components. On entry,
1401 -- Prev_Comp is set to the component preceding the list, so that the
1402 -- list is laid out after this component. Prev_Comp is set to Empty if
1403 -- the component list is to be laid out starting at the start of the
1404 -- record. On return, the components are all laid out, and Prev_Comp is
1405 -- set to the last laid out component. On return, Esiz is set to the
1406 -- resulting Object_Size value, which is the length of the record up
1407 -- to and including the last laid out entity. For Esiz, the value is
1408 -- adjusted to match the alignment of the record. RM_Siz is similarly
1409 -- set to the resulting Value_Size value, which is the same length, but
1410 -- not adjusted to meet the alignment. Note that in the case of variant
1411 -- records, Esiz represents the maximum size.
1413 procedure Layout_Non_Variant_Record;
1414 -- Procedure called to lay out a non-variant record type or subtype
1416 procedure Layout_Variant_Record;
1417 -- Procedure called to lay out a variant record type. Decl is set to the
1418 -- full type declaration for the variant record.
1420 ---------------------------------
1421 -- Get_Next_Component_Location --
1422 ---------------------------------
1424 procedure Get_Next_Component_Location
1425 (Prev_Comp : Entity_Id;
1426 Align : Uint;
1427 New_Npos : out SO_Ref;
1428 New_Fbit : out SO_Ref;
1429 New_NPMax : out SO_Ref;
1430 Force_SU : Boolean)
1432 begin
1433 -- No previous component, return zero position
1435 if No (Prev_Comp) then
1436 New_Npos := Uint_0;
1437 New_Fbit := Uint_0;
1438 New_NPMax := Uint_0;
1439 return;
1440 end if;
1442 -- Here we have a previous component
1444 declare
1445 Loc : constant Source_Ptr := Sloc (Prev_Comp);
1447 Old_Npos : constant SO_Ref := Normalized_Position (Prev_Comp);
1448 Old_Fbit : constant SO_Ref := Normalized_First_Bit (Prev_Comp);
1449 Old_NPMax : constant SO_Ref := Normalized_Position_Max (Prev_Comp);
1450 Old_Esiz : constant SO_Ref := Esize (Prev_Comp);
1452 Old_Maxsz : Node_Id;
1453 -- Expression representing maximum size of previous component
1455 begin
1456 -- Case where previous field had a dynamic size
1458 if Is_Dynamic_SO_Ref (Esize (Prev_Comp)) then
1460 -- If the previous field had a dynamic length, then it is
1461 -- required to occupy an integral number of storage units,
1462 -- and start on a storage unit boundary. This means that
1463 -- the Normalized_First_Bit value is zero in the previous
1464 -- component, and the new value is also set to zero.
1466 New_Fbit := Uint_0;
1468 -- In this case, the new position is given by an expression
1469 -- that is the sum of old normalized position and old size.
1471 New_Npos :=
1472 SO_Ref_From_Expr
1473 (Assoc_Add (Loc,
1474 Left_Opnd =>
1475 Expr_From_SO_Ref (Loc, Old_Npos),
1476 Right_Opnd =>
1477 Expr_From_SO_Ref (Loc, Old_Esiz, Prev_Comp)),
1478 Ins_Type => E,
1479 Vtype => E);
1481 -- Get maximum size of previous component
1483 if Size_Depends_On_Discriminant (Etype (Prev_Comp)) then
1484 Old_Maxsz := Get_Max_SU_Size (Etype (Prev_Comp));
1485 else
1486 Old_Maxsz := Expr_From_SO_Ref (Loc, Old_Esiz, Prev_Comp);
1487 end if;
1489 -- Now we can compute the new max position. If the max size
1490 -- is static and the old position is static, then we can
1491 -- compute the new position statically.
1493 if Nkind (Old_Maxsz) = N_Integer_Literal
1494 and then Known_Static_Normalized_Position_Max (Prev_Comp)
1495 then
1496 New_NPMax := Old_NPMax + Intval (Old_Maxsz);
1498 -- Otherwise new max position is dynamic
1500 else
1501 New_NPMax :=
1502 SO_Ref_From_Expr
1503 (Assoc_Add (Loc,
1504 Left_Opnd => Expr_From_SO_Ref (Loc, Old_NPMax),
1505 Right_Opnd => Old_Maxsz),
1506 Ins_Type => E,
1507 Vtype => E);
1508 end if;
1510 -- Previous field has known static Esize
1512 else
1513 New_Fbit := Old_Fbit + Old_Esiz;
1515 -- Bump New_Fbit to storage unit boundary if required
1517 if New_Fbit /= 0 and then Force_SU then
1518 New_Fbit := (New_Fbit + SSU - 1) / SSU * SSU;
1519 end if;
1521 -- If old normalized position is static, we can go ahead
1522 -- and compute the new normalized position directly.
1524 if Known_Static_Normalized_Position (Prev_Comp) then
1525 New_Npos := Old_Npos;
1527 if New_Fbit >= SSU then
1528 New_Npos := New_Npos + New_Fbit / SSU;
1529 New_Fbit := New_Fbit mod SSU;
1530 end if;
1532 -- Bump alignment if stricter than prev
1534 if Align > Alignment (Etype (Prev_Comp)) then
1535 New_Npos := (New_Npos + Align - 1) / Align * Align;
1536 end if;
1538 -- The max position is always equal to the position if
1539 -- the latter is static, since arrays depending on the
1540 -- values of discriminants never have static sizes.
1542 New_NPMax := New_Npos;
1543 return;
1545 -- Case of old normalized position is dynamic
1547 else
1548 -- If new bit position is within the current storage unit,
1549 -- we can just copy the old position as the result position
1550 -- (we have already set the new first bit value).
1552 if New_Fbit < SSU then
1553 New_Npos := Old_Npos;
1554 New_NPMax := Old_NPMax;
1556 -- If new bit position is past the current storage unit, we
1557 -- need to generate a new dynamic value for the position
1558 -- ??? need to deal with alignment
1560 else
1561 New_Npos :=
1562 SO_Ref_From_Expr
1563 (Assoc_Add (Loc,
1564 Left_Opnd => Expr_From_SO_Ref (Loc, Old_Npos),
1565 Right_Opnd =>
1566 Make_Integer_Literal (Loc,
1567 Intval => New_Fbit / SSU)),
1568 Ins_Type => E,
1569 Vtype => E);
1571 New_NPMax :=
1572 SO_Ref_From_Expr
1573 (Assoc_Add (Loc,
1574 Left_Opnd => Expr_From_SO_Ref (Loc, Old_NPMax),
1575 Right_Opnd =>
1576 Make_Integer_Literal (Loc,
1577 Intval => New_Fbit / SSU)),
1578 Ins_Type => E,
1579 Vtype => E);
1580 New_Fbit := New_Fbit mod SSU;
1581 end if;
1582 end if;
1583 end if;
1584 end;
1585 end Get_Next_Component_Location;
1587 ----------------------
1588 -- Layout_Component --
1589 ----------------------
1591 procedure Layout_Component (Comp : Entity_Id; Prev_Comp : Entity_Id) is
1592 Ctyp : constant Entity_Id := Etype (Comp);
1593 Npos : SO_Ref;
1594 Fbit : SO_Ref;
1595 NPMax : SO_Ref;
1596 Forc : Boolean;
1598 begin
1599 -- Parent field is always at start of record, this will overlap
1600 -- the actual fields that are part of the parent, and that's fine
1602 if Chars (Comp) = Name_uParent then
1603 Set_Normalized_Position (Comp, Uint_0);
1604 Set_Normalized_First_Bit (Comp, Uint_0);
1605 Set_Normalized_Position_Max (Comp, Uint_0);
1606 Set_Component_Bit_Offset (Comp, Uint_0);
1607 Set_Esize (Comp, Esize (Ctyp));
1608 return;
1609 end if;
1611 -- Check case of type of component has a scope of the record we
1612 -- are laying out. When this happens, the type in question is an
1613 -- Itype that has not yet been laid out (that's because such
1614 -- types do not get frozen in the normal manner, because there
1615 -- is no place for the freeze nodes).
1617 if Scope (Ctyp) = E then
1618 Layout_Type (Ctyp);
1619 end if;
1621 -- Increase alignment of record if necessary. Note that we do not
1622 -- do this for packed records, which have an alignment of one by
1623 -- default, or for records for which an explicit alignment was
1624 -- specified with an alignment clause.
1626 if not Is_Packed (E)
1627 and then not Has_Alignment_Clause (E)
1628 and then Alignment (Ctyp) > Alignment (E)
1629 then
1630 Set_Alignment (E, Alignment (Ctyp));
1631 end if;
1633 -- If component already laid out, then we are done
1635 if Known_Normalized_Position (Comp) then
1636 return;
1637 end if;
1639 -- Set size of component from type. We use the Esize except in a
1640 -- packed record, where we use the RM_Size (since that is exactly
1641 -- what the RM_Size value, as distinct from the Object_Size is
1642 -- useful for!)
1644 if Is_Packed (E) then
1645 Set_Esize (Comp, RM_Size (Ctyp));
1646 else
1647 Set_Esize (Comp, Esize (Ctyp));
1648 end if;
1650 -- Compute the component position from the previous one. See if
1651 -- current component requires being on a storage unit boundary.
1653 -- If record is not packed, we always go to a storage unit boundary
1655 if not Is_Packed (E) then
1656 Forc := True;
1658 -- Packed cases
1660 else
1661 -- Elementary types do not need SU boundary in packed record
1663 if Is_Elementary_Type (Ctyp) then
1664 Forc := False;
1666 -- Packed array types with a modular packed array type do not
1667 -- force a storage unit boundary (since the code generation
1668 -- treats these as equivalent to the underlying modular type),
1670 elsif Is_Array_Type (Ctyp)
1671 and then Is_Bit_Packed_Array (Ctyp)
1672 and then Is_Modular_Integer_Type (Packed_Array_Type (Ctyp))
1673 then
1674 Forc := False;
1676 -- Record types with known length less than or equal to the length
1677 -- of long long integer can also be unaligned, since they can be
1678 -- treated as scalars.
1680 elsif Is_Record_Type (Ctyp)
1681 and then not Is_Dynamic_SO_Ref (Esize (Ctyp))
1682 and then Esize (Ctyp) <= Esize (Standard_Long_Long_Integer)
1683 then
1684 Forc := False;
1686 -- All other cases force a storage unit boundary, even when packed
1688 else
1689 Forc := True;
1690 end if;
1691 end if;
1693 -- Now get the next component location
1695 Get_Next_Component_Location
1696 (Prev_Comp, Alignment (Ctyp), Npos, Fbit, NPMax, Forc);
1697 Set_Normalized_Position (Comp, Npos);
1698 Set_Normalized_First_Bit (Comp, Fbit);
1699 Set_Normalized_Position_Max (Comp, NPMax);
1701 -- Set Component_Bit_Offset in the static case
1703 if Known_Static_Normalized_Position (Comp)
1704 and then Known_Normalized_First_Bit (Comp)
1705 then
1706 Set_Component_Bit_Offset (Comp, SSU * Npos + Fbit);
1707 end if;
1708 end Layout_Component;
1710 -----------------------
1711 -- Layout_Components --
1712 -----------------------
1714 procedure Layout_Components
1715 (From : Entity_Id;
1716 To : Entity_Id;
1717 Esiz : out SO_Ref;
1718 RM_Siz : out SO_Ref)
1720 End_Npos : SO_Ref;
1721 End_Fbit : SO_Ref;
1722 End_NPMax : SO_Ref;
1724 begin
1725 -- Only lay out components if there are some to lay out!
1727 if Present (From) then
1729 -- Lay out components with no component clauses
1731 Comp := From;
1732 loop
1733 if Ekind (Comp) = E_Component
1734 or else Ekind (Comp) = E_Discriminant
1735 then
1736 -- The compatibility of component clauses with composite
1737 -- types isn't checked in Sem_Ch13, so we check it here.
1739 if Present (Component_Clause (Comp)) then
1740 if Is_Composite_Type (Etype (Comp))
1741 and then Esize (Comp) < RM_Size (Etype (Comp))
1742 then
1743 Error_Msg_Uint_1 := RM_Size (Etype (Comp));
1744 Error_Msg_NE
1745 ("size for & too small, minimum allowed is ^",
1746 Component_Clause (Comp),
1747 Comp);
1748 end if;
1750 else
1751 Layout_Component (Comp, Prev_Comp);
1752 Prev_Comp := Comp;
1753 end if;
1754 end if;
1756 exit when Comp = To;
1757 Next_Entity (Comp);
1758 end loop;
1759 end if;
1761 -- Set size fields, both are zero if no components
1763 if No (Prev_Comp) then
1764 Esiz := Uint_0;
1765 RM_Siz := Uint_0;
1767 else
1768 -- First the object size, for which we align past the last
1769 -- field to the alignment of the record (the object size
1770 -- is required to be a multiple of the alignment).
1772 Get_Next_Component_Location
1773 (Prev_Comp,
1774 Alignment (E),
1775 End_Npos,
1776 End_Fbit,
1777 End_NPMax,
1778 Force_SU => True);
1780 -- If the resulting normalized position is a dynamic reference,
1781 -- then the size is dynamic, and is stored in storage units.
1782 -- In this case, we set the RM_Size to the same value, it is
1783 -- simply not worth distinguishing Esize and RM_Size values in
1784 -- the dynamic case, since the RM has nothing to say about them.
1786 -- Note that a size cannot have been given in this case, since
1787 -- size specifications cannot be given for variable length types.
1789 declare
1790 Align : constant Uint := Alignment (E);
1792 begin
1793 if Is_Dynamic_SO_Ref (End_Npos) then
1794 RM_Siz := End_Npos;
1796 -- Set the Object_Size allowing for alignment. In the
1797 -- dynamic case, we have to actually do the runtime
1798 -- computation. We can skip this in the non-packed
1799 -- record case if the last component has a smaller
1800 -- alignment than the overall record alignment.
1802 if Is_Dynamic_SO_Ref (End_NPMax) then
1803 Esiz := End_NPMax;
1805 if Is_Packed (E)
1806 or else Alignment (Etype (Prev_Comp)) < Align
1807 then
1808 -- The expression we build is
1809 -- (expr + align - 1) / align * align
1811 Esiz :=
1812 SO_Ref_From_Expr
1813 (Expr =>
1814 Make_Op_Multiply (Loc,
1815 Left_Opnd =>
1816 Make_Op_Divide (Loc,
1817 Left_Opnd =>
1818 Make_Op_Add (Loc,
1819 Left_Opnd =>
1820 Expr_From_SO_Ref (Loc, Esiz),
1821 Right_Opnd =>
1822 Make_Integer_Literal (Loc,
1823 Intval => Align - 1)),
1824 Right_Opnd =>
1825 Make_Integer_Literal (Loc, Align)),
1826 Right_Opnd =>
1827 Make_Integer_Literal (Loc, Align)),
1828 Ins_Type => E,
1829 Vtype => E);
1830 end if;
1832 -- Here Esiz is static, so we can adjust the alignment
1833 -- directly go give the required aligned value.
1835 else
1836 Esiz := (End_NPMax + Align - 1) / Align * Align * SSU;
1837 end if;
1839 -- Case where computed size is static
1841 else
1842 -- The ending size was computed in Npos in storage units,
1843 -- but the actual size is stored in bits, so adjust
1844 -- accordingly. We also adjust the size to match the
1845 -- alignment here.
1847 Esiz := (End_NPMax + Align - 1) / Align * Align * SSU;
1849 -- Compute the resulting Value_Size (RM_Size). For this
1850 -- purpose we do not force alignment of the record or
1851 -- storage size alignment of the result.
1853 Get_Next_Component_Location
1854 (Prev_Comp,
1855 Uint_0,
1856 End_Npos,
1857 End_Fbit,
1858 End_NPMax,
1859 Force_SU => False);
1861 RM_Siz := End_Npos * SSU + End_Fbit;
1862 Set_And_Check_Static_Size (E, Esiz, RM_Siz);
1863 end if;
1864 end;
1865 end if;
1866 end Layout_Components;
1868 -------------------------------
1869 -- Layout_Non_Variant_Record --
1870 -------------------------------
1872 procedure Layout_Non_Variant_Record is
1873 Esiz : SO_Ref;
1874 RM_Siz : SO_Ref;
1876 begin
1877 Layout_Components (First_Entity (E), Last_Entity (E), Esiz, RM_Siz);
1878 Set_Esize (E, Esiz);
1879 Set_RM_Size (E, RM_Siz);
1880 end Layout_Non_Variant_Record;
1882 ---------------------------
1883 -- Layout_Variant_Record --
1884 ---------------------------
1886 procedure Layout_Variant_Record is
1887 Tdef : constant Node_Id := Type_Definition (Decl);
1888 Dlist : constant List_Id := Discriminant_Specifications (Decl);
1889 Esiz : SO_Ref;
1890 RM_Siz : SO_Ref;
1892 RM_Siz_Expr : Node_Id := Empty;
1893 -- Expression for the evolving RM_Siz value. This is typically a
1894 -- conditional expression which involves tests of discriminant
1895 -- values that are formed as references to the entity V. At
1896 -- the end of scanning all the components, a suitable function
1897 -- is constructed in which V is the parameter.
1899 -----------------------
1900 -- Local Subprograms --
1901 -----------------------
1903 procedure Layout_Component_List
1904 (Clist : Node_Id;
1905 Esiz : out SO_Ref;
1906 RM_Siz_Expr : out Node_Id);
1907 -- Recursive procedure, called to lay out one component list
1908 -- Esiz and RM_Siz_Expr are set to the Object_Size and Value_Size
1909 -- values respectively representing the record size up to and
1910 -- including the last component in the component list (including
1911 -- any variants in this component list). RM_Siz_Expr is returned
1912 -- as an expression which may in the general case involve some
1913 -- references to the discriminants of the current record value,
1914 -- referenced by selecting from the entity V.
1916 ---------------------------
1917 -- Layout_Component_List --
1918 ---------------------------
1920 procedure Layout_Component_List
1921 (Clist : Node_Id;
1922 Esiz : out SO_Ref;
1923 RM_Siz_Expr : out Node_Id)
1925 Citems : constant List_Id := Component_Items (Clist);
1926 Vpart : constant Node_Id := Variant_Part (Clist);
1927 Prv : Node_Id;
1928 Var : Node_Id;
1929 RM_Siz : Uint;
1930 RMS_Ent : Entity_Id;
1932 begin
1933 if Is_Non_Empty_List (Citems) then
1934 Layout_Components
1935 (From => Defining_Identifier (First (Citems)),
1936 To => Defining_Identifier (Last (Citems)),
1937 Esiz => Esiz,
1938 RM_Siz => RM_Siz);
1939 else
1940 Layout_Components (Empty, Empty, Esiz, RM_Siz);
1941 end if;
1943 -- Case where no variants are present in the component list
1945 if No (Vpart) then
1947 -- The Esiz value has been correctly set by the call to
1948 -- Layout_Components, so there is nothing more to be done.
1950 -- For RM_Siz, we have an SO_Ref value, which we must convert
1951 -- to an appropriate expression.
1953 if Is_Static_SO_Ref (RM_Siz) then
1954 RM_Siz_Expr :=
1955 Make_Integer_Literal (Loc,
1956 Intval => RM_Siz);
1958 else
1959 RMS_Ent := Get_Dynamic_SO_Entity (RM_Siz);
1961 -- If the size is represented by a function, then we
1962 -- create an appropriate function call using V as
1963 -- the parameter to the call.
1965 if Is_Discrim_SO_Function (RMS_Ent) then
1966 RM_Siz_Expr :=
1967 Make_Function_Call (Loc,
1968 Name => New_Occurrence_Of (RMS_Ent, Loc),
1969 Parameter_Associations => New_List (
1970 Make_Identifier (Loc, Chars => Vname)));
1972 -- If the size is represented by a constant, then the
1973 -- expression we want is a reference to this constant
1975 else
1976 RM_Siz_Expr := New_Occurrence_Of (RMS_Ent, Loc);
1977 end if;
1978 end if;
1980 -- Case where variants are present in this component list
1982 else
1983 declare
1984 EsizV : SO_Ref;
1985 RM_SizV : Node_Id;
1986 Dchoice : Node_Id;
1987 Discrim : Node_Id;
1988 Dtest : Node_Id;
1989 D_List : List_Id;
1990 D_Entity : Entity_Id;
1992 begin
1993 RM_Siz_Expr := Empty;
1994 Prv := Prev_Comp;
1996 Var := Last (Variants (Vpart));
1997 while Present (Var) loop
1998 Prev_Comp := Prv;
1999 Layout_Component_List
2000 (Component_List (Var), EsizV, RM_SizV);
2002 -- Set the Object_Size. If this is the first variant,
2003 -- we just set the size of this first variant.
2005 if Var = Last (Variants (Vpart)) then
2006 Esiz := EsizV;
2008 -- Otherwise the Object_Size is formed as a maximum
2009 -- of Esiz so far from previous variants, and the new
2010 -- Esiz value from the variant we just processed.
2012 -- If both values are static, we can just compute the
2013 -- maximum directly to save building junk nodes.
2015 elsif not Is_Dynamic_SO_Ref (Esiz)
2016 and then not Is_Dynamic_SO_Ref (EsizV)
2017 then
2018 Esiz := UI_Max (Esiz, EsizV);
2020 -- If either value is dynamic, then we have to generate
2021 -- an appropriate Standard_Unsigned'Max attribute call.
2023 else
2024 Esiz :=
2025 SO_Ref_From_Expr
2026 (Make_Attribute_Reference (Loc,
2027 Attribute_Name => Name_Max,
2028 Prefix =>
2029 New_Occurrence_Of (Standard_Unsigned, Loc),
2030 Expressions => New_List (
2031 Expr_From_SO_Ref (Loc, Esiz),
2032 Expr_From_SO_Ref (Loc, EsizV))),
2033 Ins_Type => E,
2034 Vtype => E);
2035 end if;
2037 -- Now deal with Value_Size (RM_Siz). We are aiming at
2038 -- an expression that looks like:
2040 -- if xxDx (V.disc) then rmsiz1
2041 -- else if xxDx (V.disc) then rmsiz2
2042 -- else ...
2044 -- Where rmsiz1, rmsiz2... are the RM_Siz values for the
2045 -- individual variants, and xxDx are the discriminant
2046 -- checking functions generated for the variant type.
2048 -- If this is the first variant, we simply set the
2049 -- result as the expression. Note that this takes
2050 -- care of the others case.
2052 if No (RM_Siz_Expr) then
2053 RM_Siz_Expr := Bits_To_SU (RM_SizV);
2055 -- Otherwise construct the appropriate test
2057 else
2058 -- The test to be used in general is a call to the
2059 -- discriminant checking function. However, it is
2060 -- definitely worth special casing the very common
2061 -- case where a single value is involved.
2063 Dchoice := First (Discrete_Choices (Var));
2065 if No (Next (Dchoice))
2066 and then Nkind (Dchoice) /= N_Range
2067 then
2068 -- Discriminant to be tested
2070 Discrim :=
2071 Make_Selected_Component (Loc,
2072 Prefix =>
2073 Make_Identifier (Loc, Chars => Vname),
2074 Selector_Name =>
2075 New_Occurrence_Of
2076 (Entity (Name (Vpart)), Loc));
2078 Dtest :=
2079 Make_Op_Eq (Loc,
2080 Left_Opnd => Discrim,
2081 Right_Opnd => New_Copy (Dchoice));
2083 -- Generate a call to the discriminant-checking
2084 -- function for the variant. Note that the result
2085 -- has to be complemented since the function returns
2086 -- False when the passed discriminant value matches.
2088 else
2089 -- The checking function takes all of the type's
2090 -- discriminants as parameters, so a list of all
2091 -- the selected discriminants must be constructed.
2093 D_List := New_List;
2094 D_Entity := First_Discriminant (E);
2095 while Present (D_Entity) loop
2096 Append (
2097 Make_Selected_Component (Loc,
2098 Prefix =>
2099 Make_Identifier (Loc, Chars => Vname),
2100 Selector_Name =>
2101 New_Occurrence_Of
2102 (D_Entity, Loc)),
2103 D_List);
2105 D_Entity := Next_Discriminant (D_Entity);
2106 end loop;
2108 Dtest :=
2109 Make_Op_Not (Loc,
2110 Right_Opnd =>
2111 Make_Function_Call (Loc,
2112 Name =>
2113 New_Occurrence_Of
2114 (Dcheck_Function (Var), Loc),
2115 Parameter_Associations =>
2116 D_List));
2117 end if;
2119 RM_Siz_Expr :=
2120 Make_Conditional_Expression (Loc,
2121 Expressions =>
2122 New_List
2123 (Dtest, Bits_To_SU (RM_SizV), RM_Siz_Expr));
2124 end if;
2126 Prev (Var);
2127 end loop;
2128 end;
2129 end if;
2130 end Layout_Component_List;
2132 -- Start of processing for Layout_Variant_Record
2134 begin
2135 -- We need the discriminant checking functions, since we generate
2136 -- calls to these functions for the RM_Size expression, so make
2137 -- sure that these functions have been constructed in time.
2139 Build_Discr_Checking_Funcs (Decl);
2141 -- Lay out the discriminants
2143 Layout_Components
2144 (From => Defining_Identifier (First (Dlist)),
2145 To => Defining_Identifier (Last (Dlist)),
2146 Esiz => Esiz,
2147 RM_Siz => RM_Siz);
2149 -- Lay out the main component list (this will make recursive calls
2150 -- to lay out all component lists nested within variants).
2152 Layout_Component_List (Component_List (Tdef), Esiz, RM_Siz_Expr);
2153 Set_Esize (E, Esiz);
2155 -- If the RM_Size is a literal, set its value
2157 if Nkind (RM_Siz_Expr) = N_Integer_Literal then
2158 Set_RM_Size (E, Intval (RM_Siz_Expr));
2160 -- Otherwise we construct a dynamic SO_Ref
2162 else
2163 Set_RM_Size (E,
2164 SO_Ref_From_Expr
2165 (RM_Siz_Expr,
2166 Ins_Type => E,
2167 Vtype => E));
2168 end if;
2169 end Layout_Variant_Record;
2171 -- Start of processing for Layout_Record_Type
2173 begin
2174 -- If this is a cloned subtype, just copy the size fields from the
2175 -- original, nothing else needs to be done in this case, since the
2176 -- components themselves are all shared.
2178 if (Ekind (E) = E_Record_Subtype
2179 or else Ekind (E) = E_Class_Wide_Subtype)
2180 and then Present (Cloned_Subtype (E))
2181 then
2182 Set_Esize (E, Esize (Cloned_Subtype (E)));
2183 Set_RM_Size (E, RM_Size (Cloned_Subtype (E)));
2184 Set_Alignment (E, Alignment (Cloned_Subtype (E)));
2186 -- Another special case, class-wide types. The RM says that the size
2187 -- of such types is implementation defined (RM 13.3(48)). What we do
2188 -- here is to leave the fields set as unknown values, and the backend
2189 -- determines the actual behavior.
2191 elsif Ekind (E) = E_Class_Wide_Type then
2192 null;
2194 -- All other cases
2196 else
2197 -- Initialize alignment conservatively to 1. This value will
2198 -- be increased as necessary during processing of the record.
2200 if Unknown_Alignment (E) then
2201 Set_Alignment (E, Uint_1);
2202 end if;
2204 -- Initialize previous component. This is Empty unless there
2205 -- are components which have already been laid out by component
2206 -- clauses. If there are such components, we start our lay out of
2207 -- the remaining components following the last such component.
2209 Prev_Comp := Empty;
2211 Comp := First_Entity (E);
2212 while Present (Comp) loop
2213 if (Ekind (Comp) = E_Component
2214 or else Ekind (Comp) = E_Discriminant)
2215 and then Present (Component_Clause (Comp))
2216 then
2217 if No (Prev_Comp)
2218 or else
2219 Component_Bit_Offset (Comp) >
2220 Component_Bit_Offset (Prev_Comp)
2221 then
2222 Prev_Comp := Comp;
2223 end if;
2224 end if;
2226 Next_Entity (Comp);
2227 end loop;
2229 -- We have two separate circuits, one for non-variant records and
2230 -- one for variant records. For non-variant records, we simply go
2231 -- through the list of components. This handles all the non-variant
2232 -- cases including those cases of subtypes where there is no full
2233 -- type declaration, so the tree cannot be used to drive the layout.
2234 -- For variant records, we have to drive the layout from the tree
2235 -- since we need to understand the variant structure in this case.
2237 if Present (Full_View (E)) then
2238 Decl := Declaration_Node (Full_View (E));
2239 else
2240 Decl := Declaration_Node (E);
2241 end if;
2243 -- Scan all the components
2245 if Nkind (Decl) = N_Full_Type_Declaration
2246 and then Has_Discriminants (E)
2247 and then Nkind (Type_Definition (Decl)) = N_Record_Definition
2248 and then Present (Component_List (Type_Definition (Decl)))
2249 and then
2250 Present (Variant_Part (Component_List (Type_Definition (Decl))))
2251 then
2252 Layout_Variant_Record;
2253 else
2254 Layout_Non_Variant_Record;
2255 end if;
2256 end if;
2257 end Layout_Record_Type;
2259 -----------------
2260 -- Layout_Type --
2261 -----------------
2263 procedure Layout_Type (E : Entity_Id) is
2264 begin
2265 -- For string literal types, for now, kill the size always, this
2266 -- is because gigi does not like or need the size to be set ???
2268 if Ekind (E) = E_String_Literal_Subtype then
2269 Set_Esize (E, Uint_0);
2270 Set_RM_Size (E, Uint_0);
2271 return;
2272 end if;
2274 -- For access types, set size/alignment. This is system address
2275 -- size, except for fat pointers (unconstrained array access types),
2276 -- where the size is two times the address size, to accommodate the
2277 -- two pointers that are required for a fat pointer (data and
2278 -- template). Note that E_Access_Protected_Subprogram_Type is not
2279 -- an access type for this purpose since it is not a pointer but is
2280 -- equivalent to a record. For access subtypes, copy the size from
2281 -- the base type since Gigi represents them the same way.
2283 if Is_Access_Type (E) then
2285 -- If Esize already set (e.g. by a size clause), then nothing
2286 -- further to be done here.
2288 if Known_Esize (E) then
2289 null;
2291 -- Access to subprogram is a strange beast, and we let the
2292 -- backend figure out what is needed (it may be some kind
2293 -- of fat pointer, including the static link for example.
2295 elsif Ekind (E) = E_Access_Protected_Subprogram_Type then
2296 null;
2298 -- For access subtypes, copy the size information from base type
2300 elsif Ekind (E) = E_Access_Subtype then
2301 Set_Size_Info (E, Base_Type (E));
2302 Set_RM_Size (E, RM_Size (Base_Type (E)));
2304 -- For other access types, we use either address size, or, if
2305 -- a fat pointer is used (pointer-to-unconstrained array case),
2306 -- twice the address size to accommodate a fat pointer.
2308 else
2309 declare
2310 Desig : Entity_Id := Designated_Type (E);
2312 begin
2313 if Is_Private_Type (Desig)
2314 and then Present (Full_View (Desig))
2315 then
2316 Desig := Full_View (Desig);
2317 end if;
2319 if Is_Array_Type (Desig)
2320 and then not Is_Constrained (Desig)
2321 and then not Has_Completion_In_Body (Desig)
2322 and then not Debug_Flag_6
2323 then
2324 Init_Size (E, 2 * System_Address_Size);
2326 -- Check for bad convention set
2328 if Warn_On_Export_Import
2329 and then
2330 (Convention (E) = Convention_C
2331 or else
2332 Convention (E) = Convention_CPP)
2333 then
2334 Error_Msg_N
2335 ("?this access type does not " &
2336 "correspond to C pointer", E);
2337 end if;
2339 else
2340 Init_Size (E, System_Address_Size);
2341 end if;
2342 end;
2343 end if;
2345 Set_Elem_Alignment (E);
2347 -- Scalar types: set size and alignment
2349 elsif Is_Scalar_Type (E) then
2351 -- For discrete types, the RM_Size and Esize must be set
2352 -- already, since this is part of the earlier processing
2353 -- and the front end is always required to lay out the
2354 -- sizes of such types (since they are available as static
2355 -- attributes). All we do is to check that this rule is
2356 -- indeed obeyed!
2358 if Is_Discrete_Type (E) then
2360 -- If the RM_Size is not set, then here is where we set it
2362 -- Note: an RM_Size of zero looks like not set here, but this
2363 -- is a rare case, and we can simply reset it without any harm.
2365 if not Known_RM_Size (E) then
2366 Set_Discrete_RM_Size (E);
2367 end if;
2369 -- If Esize for a discrete type is not set then set it
2371 if not Known_Esize (E) then
2372 declare
2373 S : Int := 8;
2375 begin
2376 loop
2377 -- If size is big enough, set it and exit
2379 if S >= RM_Size (E) then
2380 Init_Esize (E, S);
2381 exit;
2383 -- If the RM_Size is greater than 64 (happens only
2384 -- when strange values are specified by the user,
2385 -- then Esize is simply a copy of RM_Size, it will
2386 -- be further refined later on)
2388 elsif S = 64 then
2389 Set_Esize (E, RM_Size (E));
2390 exit;
2392 -- Otherwise double possible size and keep trying
2394 else
2395 S := S * 2;
2396 end if;
2397 end loop;
2398 end;
2399 end if;
2401 -- For non-discrete sclar types, if the RM_Size is not set,
2402 -- then set it now to a copy of the Esize if the Esize is set.
2404 else
2405 if Known_Esize (E) and then Unknown_RM_Size (E) then
2406 Set_RM_Size (E, Esize (E));
2407 end if;
2408 end if;
2410 Set_Elem_Alignment (E);
2412 -- Non-elementary (composite) types
2414 else
2415 -- If RM_Size is known, set Esize if not known
2417 if Known_RM_Size (E) and then Unknown_Esize (E) then
2419 -- If the alignment is known, we bump the Esize up to the
2420 -- next alignment boundary if it is not already on one.
2422 if Known_Alignment (E) then
2423 declare
2424 A : constant Uint := Alignment_In_Bits (E);
2425 S : constant SO_Ref := RM_Size (E);
2427 begin
2428 Set_Esize (E, (S * A + A - 1) / A);
2429 end;
2430 end if;
2432 -- If Esize is set, and RM_Size is not, RM_Size is copied from
2433 -- Esize at least for now this seems reasonable, and is in any
2434 -- case needed for compatibility with old versions of gigi.
2435 -- look to be unknown.
2437 elsif Known_Esize (E) and then Unknown_RM_Size (E) then
2438 Set_RM_Size (E, Esize (E));
2439 end if;
2441 -- For array base types, set component size if object size of
2442 -- the component type is known and is a small power of 2 (8,
2443 -- 16, 32, 64), since this is what will always be used.
2445 if Ekind (E) = E_Array_Type
2446 and then Unknown_Component_Size (E)
2447 then
2448 declare
2449 CT : constant Entity_Id := Component_Type (E);
2451 begin
2452 -- For some reasons, access types can cause trouble,
2453 -- So let's just do this for discrete types ???
2455 if Present (CT)
2456 and then Is_Discrete_Type (CT)
2457 and then Known_Static_Esize (CT)
2458 then
2459 declare
2460 S : constant Uint := Esize (CT);
2462 begin
2463 if S = 8 or else
2464 S = 16 or else
2465 S = 32 or else
2466 S = 64
2467 then
2468 Set_Component_Size (E, Esize (CT));
2469 end if;
2470 end;
2471 end if;
2472 end;
2473 end if;
2474 end if;
2476 -- Lay out array and record types if front end layout set
2478 if Frontend_Layout_On_Target then
2479 if Is_Array_Type (E) and then not Is_Bit_Packed_Array (E) then
2480 Layout_Array_Type (E);
2481 elsif Is_Record_Type (E) then
2482 Layout_Record_Type (E);
2483 end if;
2485 -- Case of backend layout, we still do a little in the front end
2487 else
2488 -- Processing for record types
2490 if Is_Record_Type (E) then
2492 -- Special remaining processing for record types with a known
2493 -- size of 16, 32, or 64 bits whose alignment is not yet set.
2494 -- For these types, we set a corresponding alignment matching
2495 -- the size if possible, or as large as possible if not.
2497 if Convention (E) = Convention_Ada
2498 and then not Debug_Flag_Q
2499 then
2500 Set_Composite_Alignment (E);
2501 end if;
2503 -- Procressing for array types
2505 elsif Is_Array_Type (E) then
2507 -- For arrays that are required to be atomic, we do the same
2508 -- processing as described above for short records, since we
2509 -- really need to have the alignment set for the whole array.
2511 if Is_Atomic (E) and then not Debug_Flag_Q then
2512 Set_Composite_Alignment (E);
2513 end if;
2515 -- For unpacked array types, set an alignment of 1 if we know
2516 -- that the component alignment is not greater than 1. The reason
2517 -- we do this is to avoid unnecessary copying of slices of such
2518 -- arrays when passed to subprogram parameters (see special test
2519 -- in Exp_Ch6.Expand_Actuals).
2521 if not Is_Packed (E)
2522 and then Unknown_Alignment (E)
2523 then
2524 if Known_Static_Component_Size (E)
2525 and then Component_Size (E) = 1
2526 then
2527 Set_Alignment (E, Uint_1);
2528 end if;
2529 end if;
2530 end if;
2531 end if;
2533 -- Final step is to check that Esize and RM_Size are compatible
2535 if Known_Static_Esize (E) and then Known_Static_RM_Size (E) then
2536 if Esize (E) < RM_Size (E) then
2538 -- Esize is less than RM_Size. That's not good. First we test
2539 -- whether this was set deliberately with an Object_Size clause
2540 -- and if so, object to the clause.
2542 if Has_Object_Size_Clause (E) then
2543 Error_Msg_Uint_1 := RM_Size (E);
2544 Error_Msg_F
2545 ("object size is too small, minimum is ^",
2546 Expression (Get_Attribute_Definition_Clause
2547 (E, Attribute_Object_Size)));
2548 end if;
2550 -- Adjust Esize up to RM_Size value
2552 declare
2553 Size : constant Uint := RM_Size (E);
2555 begin
2556 Set_Esize (E, RM_Size (E));
2558 -- For scalar types, increase Object_Size to power of 2,
2559 -- but not less than a storage unit in any case (i.e.,
2560 -- normally this means it will be storage-unit addressable).
2562 if Is_Scalar_Type (E) then
2563 if Size <= System_Storage_Unit then
2564 Init_Esize (E, System_Storage_Unit);
2565 elsif Size <= 16 then
2566 Init_Esize (E, 16);
2567 elsif Size <= 32 then
2568 Init_Esize (E, 32);
2569 else
2570 Set_Esize (E, (Size + 63) / 64 * 64);
2571 end if;
2573 -- Finally, make sure that alignment is consistent with
2574 -- the newly assigned size.
2576 while Alignment (E) * System_Storage_Unit < Esize (E)
2577 and then Alignment (E) < Maximum_Alignment
2578 loop
2579 Set_Alignment (E, 2 * Alignment (E));
2580 end loop;
2581 end if;
2582 end;
2583 end if;
2584 end if;
2585 end Layout_Type;
2587 ---------------------
2588 -- Rewrite_Integer --
2589 ---------------------
2591 procedure Rewrite_Integer (N : Node_Id; V : Uint) is
2592 Loc : constant Source_Ptr := Sloc (N);
2593 Typ : constant Entity_Id := Etype (N);
2595 begin
2596 Rewrite (N, Make_Integer_Literal (Loc, Intval => V));
2597 Set_Etype (N, Typ);
2598 end Rewrite_Integer;
2600 -------------------------------
2601 -- Set_And_Check_Static_Size --
2602 -------------------------------
2604 procedure Set_And_Check_Static_Size
2605 (E : Entity_Id;
2606 Esiz : SO_Ref;
2607 RM_Siz : SO_Ref)
2609 SC : Node_Id;
2611 procedure Check_Size_Too_Small (Spec : Uint; Min : Uint);
2612 -- Spec is the number of bit specified in the size clause, and
2613 -- Min is the minimum computed size. An error is given that the
2614 -- specified size is too small if Spec < Min, and in this case
2615 -- both Esize and RM_Size are set to unknown in E. The error
2616 -- message is posted on node SC.
2618 procedure Check_Unused_Bits (Spec : Uint; Max : Uint);
2619 -- Spec is the number of bits specified in the size clause, and
2620 -- Max is the maximum computed size. A warning is given about
2621 -- unused bits if Spec > Max. This warning is posted on node SC.
2623 --------------------------
2624 -- Check_Size_Too_Small --
2625 --------------------------
2627 procedure Check_Size_Too_Small (Spec : Uint; Min : Uint) is
2628 begin
2629 if Spec < Min then
2630 Error_Msg_Uint_1 := Min;
2631 Error_Msg_NE
2632 ("size for & too small, minimum allowed is ^", SC, E);
2633 Init_Esize (E);
2634 Init_RM_Size (E);
2635 end if;
2636 end Check_Size_Too_Small;
2638 -----------------------
2639 -- Check_Unused_Bits --
2640 -----------------------
2642 procedure Check_Unused_Bits (Spec : Uint; Max : Uint) is
2643 begin
2644 if Spec > Max then
2645 Error_Msg_Uint_1 := Spec - Max;
2646 Error_Msg_NE ("?^ bits of & unused", SC, E);
2647 end if;
2648 end Check_Unused_Bits;
2650 -- Start of processing for Set_And_Check_Static_Size
2652 begin
2653 -- Case where Object_Size (Esize) is already set by a size clause
2655 if Known_Static_Esize (E) then
2656 SC := Size_Clause (E);
2658 if No (SC) then
2659 SC := Get_Attribute_Definition_Clause (E, Attribute_Object_Size);
2660 end if;
2662 -- Perform checks on specified size against computed sizes
2664 if Present (SC) then
2665 Check_Unused_Bits (Esize (E), Esiz);
2666 Check_Size_Too_Small (Esize (E), RM_Siz);
2667 end if;
2668 end if;
2670 -- Case where Value_Size (RM_Size) is set by specific Value_Size
2671 -- clause (we do not need to worry about Value_Size being set by
2672 -- a Size clause, since that will have set Esize as well, and we
2673 -- already took care of that case).
2675 if Known_Static_RM_Size (E) then
2676 SC := Get_Attribute_Definition_Clause (E, Attribute_Value_Size);
2678 -- Perform checks on specified size against computed sizes
2680 if Present (SC) then
2681 Check_Unused_Bits (RM_Size (E), Esiz);
2682 Check_Size_Too_Small (RM_Size (E), RM_Siz);
2683 end if;
2684 end if;
2686 -- Set sizes if unknown
2688 if Unknown_Esize (E) then
2689 Set_Esize (E, Esiz);
2690 end if;
2692 if Unknown_RM_Size (E) then
2693 Set_RM_Size (E, RM_Siz);
2694 end if;
2695 end Set_And_Check_Static_Size;
2697 -----------------------------
2698 -- Set_Composite_Alignment --
2699 -----------------------------
2701 procedure Set_Composite_Alignment (E : Entity_Id) is
2702 Siz : Uint;
2703 Align : Nat;
2705 begin
2706 if Unknown_Alignment (E) then
2707 if Known_Static_Esize (E) then
2708 Siz := Esize (E);
2710 elsif Unknown_Esize (E)
2711 and then Known_Static_RM_Size (E)
2712 then
2713 Siz := RM_Size (E);
2715 else
2716 return;
2717 end if;
2719 -- Size is known, alignment is not set
2721 -- Reset alignment to match size if size is exactly 2, 4, or 8
2722 -- storage units.
2724 if Siz = 2 * System_Storage_Unit then
2725 Align := 2;
2726 elsif Siz = 4 * System_Storage_Unit then
2727 Align := 4;
2728 elsif Siz = 8 * System_Storage_Unit then
2729 Align := 8;
2731 -- On VMS, also reset for odd "in between" sizes, e.g. a 17-bit
2732 -- record is given an alignment of 4. This is more consistent with
2733 -- what DEC Ada does.
2735 elsif OpenVMS_On_Target and then Siz > System_Storage_Unit then
2737 if Siz <= 2 * System_Storage_Unit then
2738 Align := 2;
2739 elsif Siz <= 4 * System_Storage_Unit then
2740 Align := 4;
2741 elsif Siz <= 8 * System_Storage_Unit then
2742 Align := 8;
2743 else
2744 return;
2745 end if;
2747 -- No special alignment fiddling needed
2749 else
2750 return;
2751 end if;
2753 -- Here Align is set to the proposed improved alignment
2755 if Align > Maximum_Alignment then
2756 Align := Maximum_Alignment;
2757 end if;
2759 -- Further processing for record types only to reduce the alignment
2760 -- set by the above processing in some specific cases. We do not
2761 -- do this for atomic records, since we need max alignment there.
2763 if Is_Record_Type (E) then
2765 -- For records, there is generally no point in setting alignment
2766 -- higher than word size since we cannot do better than move by
2767 -- words in any case
2769 if Align > System_Word_Size / System_Storage_Unit then
2770 Align := System_Word_Size / System_Storage_Unit;
2771 end if;
2773 -- Check components. If any component requires a higher
2774 -- alignment, then we set that higher alignment in any case.
2776 declare
2777 Comp : Entity_Id;
2779 begin
2780 Comp := First_Component (E);
2781 while Present (Comp) loop
2782 if Known_Alignment (Etype (Comp)) then
2783 declare
2784 Calign : constant Uint := Alignment (Etype (Comp));
2786 begin
2787 -- The cases to worry about are when the alignment
2788 -- of the component type is larger than the alignment
2789 -- we have so far, and either there is no component
2790 -- clause for the alignment, or the length set by
2791 -- the component clause matches the alignment set.
2793 if Calign > Align
2794 and then
2795 (Unknown_Esize (Comp)
2796 or else (Known_Static_Esize (Comp)
2797 and then
2798 Esize (Comp) =
2799 Calign * System_Storage_Unit))
2800 then
2801 Align := UI_To_Int (Calign);
2802 end if;
2803 end;
2804 end if;
2806 Next_Component (Comp);
2807 end loop;
2808 end;
2809 end if;
2811 -- Set chosen alignment
2813 Set_Alignment (E, UI_From_Int (Align));
2815 if Known_Static_Esize (E)
2816 and then Esize (E) < Align * System_Storage_Unit
2817 then
2818 Set_Esize (E, UI_From_Int (Align * System_Storage_Unit));
2819 end if;
2820 end if;
2821 end Set_Composite_Alignment;
2823 --------------------------
2824 -- Set_Discrete_RM_Size --
2825 --------------------------
2827 procedure Set_Discrete_RM_Size (Def_Id : Entity_Id) is
2828 FST : constant Entity_Id := First_Subtype (Def_Id);
2830 begin
2831 -- All discrete types except for the base types in standard
2832 -- are constrained, so indicate this by setting Is_Constrained.
2834 Set_Is_Constrained (Def_Id);
2836 -- We set generic types to have an unknown size, since the
2837 -- representation of a generic type is irrelevant, in view
2838 -- of the fact that they have nothing to do with code.
2840 if Is_Generic_Type (Root_Type (FST)) then
2841 Set_RM_Size (Def_Id, Uint_0);
2843 -- If the subtype statically matches the first subtype, then
2844 -- it is required to have exactly the same layout. This is
2845 -- required by aliasing considerations.
2847 elsif Def_Id /= FST and then
2848 Subtypes_Statically_Match (Def_Id, FST)
2849 then
2850 Set_RM_Size (Def_Id, RM_Size (FST));
2851 Set_Size_Info (Def_Id, FST);
2853 -- In all other cases the RM_Size is set to the minimum size.
2854 -- Note that this routine is never called for subtypes for which
2855 -- the RM_Size is set explicitly by an attribute clause.
2857 else
2858 Set_RM_Size (Def_Id, UI_From_Int (Minimum_Size (Def_Id)));
2859 end if;
2860 end Set_Discrete_RM_Size;
2862 ------------------------
2863 -- Set_Elem_Alignment --
2864 ------------------------
2866 procedure Set_Elem_Alignment (E : Entity_Id) is
2867 begin
2868 -- Do not set alignment for packed array types, unless we are doing
2869 -- front end layout, because otherwise this is always handled in the
2870 -- backend.
2872 if Is_Packed_Array_Type (E) and then not Frontend_Layout_On_Target then
2873 return;
2875 -- If there is an alignment clause, then we respect it
2877 elsif Has_Alignment_Clause (E) then
2878 return;
2880 -- If the size is not set, then don't attempt to set the alignment. This
2881 -- happens in the backend layout case for access-to-subprogram types.
2883 elsif not Known_Static_Esize (E) then
2884 return;
2886 -- For access types, do not set the alignment if the size is less than
2887 -- the allowed minimum size. This avoids cascaded error messages.
2889 elsif Is_Access_Type (E)
2890 and then Esize (E) < System_Address_Size
2891 then
2892 return;
2893 end if;
2895 -- Here we calculate the alignment as the largest power of two
2896 -- multiple of System.Storage_Unit that does not exceed either
2897 -- the actual size of the type, or the maximum allowed alignment.
2899 declare
2900 S : constant Int :=
2901 UI_To_Int (Esize (E)) / SSU;
2902 A : Nat;
2904 begin
2905 A := 1;
2906 while 2 * A <= Ttypes.Maximum_Alignment
2907 and then 2 * A <= S
2908 loop
2909 A := 2 * A;
2910 end loop;
2912 -- Now we think we should set the alignment to A, but we
2913 -- skip this if an alignment is already set to a value
2914 -- greater than A (happens for derived types).
2916 -- However, if the alignment is known and too small it
2917 -- must be increased, this happens in a case like:
2919 -- type R is new Character;
2920 -- for R'Size use 16;
2922 -- Here the alignment inherited from Character is 1, but
2923 -- it must be increased to 2 to reflect the increased size.
2925 if Unknown_Alignment (E) or else Alignment (E) < A then
2926 Init_Alignment (E, A);
2927 end if;
2928 end;
2929 end Set_Elem_Alignment;
2931 ----------------------
2932 -- SO_Ref_From_Expr --
2933 ----------------------
2935 function SO_Ref_From_Expr
2936 (Expr : Node_Id;
2937 Ins_Type : Entity_Id;
2938 Vtype : Entity_Id := Empty;
2939 Make_Func : Boolean := False)
2940 return Dynamic_SO_Ref
2942 Loc : constant Source_Ptr := Sloc (Ins_Type);
2944 K : constant Entity_Id :=
2945 Make_Defining_Identifier (Loc,
2946 Chars => New_Internal_Name ('K'));
2948 Decl : Node_Id;
2950 Vtype_Primary_View : Entity_Id;
2952 function Check_Node_V_Ref (N : Node_Id) return Traverse_Result;
2953 -- Function used to check one node for reference to V
2955 function Has_V_Ref is new Traverse_Func (Check_Node_V_Ref);
2956 -- Function used to traverse tree to check for reference to V
2958 ----------------------
2959 -- Check_Node_V_Ref --
2960 ----------------------
2962 function Check_Node_V_Ref (N : Node_Id) return Traverse_Result is
2963 begin
2964 if Nkind (N) = N_Identifier then
2965 if Chars (N) = Vname then
2966 return Abandon;
2967 else
2968 return Skip;
2969 end if;
2971 else
2972 return OK;
2973 end if;
2974 end Check_Node_V_Ref;
2976 -- Start of processing for SO_Ref_From_Expr
2978 begin
2979 -- Case of expression is an integer literal, in this case we just
2980 -- return the value (which must always be non-negative, since size
2981 -- and offset values can never be negative).
2983 if Nkind (Expr) = N_Integer_Literal then
2984 pragma Assert (Intval (Expr) >= 0);
2985 return Intval (Expr);
2986 end if;
2988 -- Case where there is a reference to V, create function
2990 if Has_V_Ref (Expr) = Abandon then
2992 pragma Assert (Present (Vtype));
2994 -- Check whether Vtype is a view of a private type and ensure that
2995 -- we use the primary view of the type (which is denoted by its
2996 -- Etype, whether it's the type's partial or full view entity).
2997 -- This is needed to make sure that we use the same (primary) view
2998 -- of the type for all V formals, whether the current view of the
2999 -- type is the partial or full view, so that types will always
3000 -- match on calls from one size function to another.
3002 if Has_Private_Declaration (Vtype) then
3003 Vtype_Primary_View := Etype (Vtype);
3004 else
3005 Vtype_Primary_View := Vtype;
3006 end if;
3008 Set_Is_Discrim_SO_Function (K);
3010 Decl :=
3011 Make_Subprogram_Body (Loc,
3013 Specification =>
3014 Make_Function_Specification (Loc,
3015 Defining_Unit_Name => K,
3016 Parameter_Specifications => New_List (
3017 Make_Parameter_Specification (Loc,
3018 Defining_Identifier =>
3019 Make_Defining_Identifier (Loc, Chars => Vname),
3020 Parameter_Type =>
3021 New_Occurrence_Of (Vtype_Primary_View, Loc))),
3022 Result_Definition =>
3023 New_Occurrence_Of (Standard_Unsigned, Loc)),
3025 Declarations => Empty_List,
3027 Handled_Statement_Sequence =>
3028 Make_Handled_Sequence_Of_Statements (Loc,
3029 Statements => New_List (
3030 Make_Return_Statement (Loc,
3031 Expression => Expr))));
3033 -- The caller requests that the expression be encapsulated in
3034 -- a parameterless function.
3036 elsif Make_Func then
3037 Decl :=
3038 Make_Subprogram_Body (Loc,
3040 Specification =>
3041 Make_Function_Specification (Loc,
3042 Defining_Unit_Name => K,
3043 Parameter_Specifications => Empty_List,
3044 Result_Definition =>
3045 New_Occurrence_Of (Standard_Unsigned, Loc)),
3047 Declarations => Empty_List,
3049 Handled_Statement_Sequence =>
3050 Make_Handled_Sequence_Of_Statements (Loc,
3051 Statements => New_List (
3052 Make_Return_Statement (Loc, Expression => Expr))));
3054 -- No reference to V and function not requested, so create a constant
3056 else
3057 Decl :=
3058 Make_Object_Declaration (Loc,
3059 Defining_Identifier => K,
3060 Object_Definition =>
3061 New_Occurrence_Of (Standard_Unsigned, Loc),
3062 Constant_Present => True,
3063 Expression => Expr);
3064 end if;
3066 Append_Freeze_Action (Ins_Type, Decl);
3067 Analyze (Decl);
3068 return Create_Dynamic_SO_Ref (K);
3069 end SO_Ref_From_Expr;
3071 end Layout;