1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 2001-2010, Free Software Foundation, Inc. --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 3, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING3. If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license. --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
24 ------------------------------------------------------------------------------
26 with Atree
; use Atree
;
27 with Checks
; use Checks
;
28 with Debug
; use Debug
;
29 with Einfo
; use Einfo
;
30 with Errout
; use Errout
;
31 with Exp_Ch3
; use Exp_Ch3
;
32 with Exp_Util
; use Exp_Util
;
33 with Namet
; use Namet
;
34 with Nlists
; use Nlists
;
35 with Nmake
; use Nmake
;
37 with Repinfo
; use Repinfo
;
39 with Sem_Aux
; use Sem_Aux
;
40 with Sem_Ch13
; use Sem_Ch13
;
41 with Sem_Eval
; use Sem_Eval
;
42 with Sem_Util
; use Sem_Util
;
43 with Sinfo
; use Sinfo
;
44 with Snames
; use Snames
;
45 with Stand
; use Stand
;
46 with Targparm
; use Targparm
;
47 with Tbuild
; use Tbuild
;
48 with Ttypes
; use Ttypes
;
49 with Uintp
; use Uintp
;
51 package body Layout
is
53 ------------------------
54 -- Local Declarations --
55 ------------------------
57 SSU
: constant Int
:= Ttypes
.System_Storage_Unit
;
58 -- Short hand for System_Storage_Unit
60 Vname
: constant Name_Id
:= Name_uV
;
61 -- Formal parameter name used for functions generated for size offset
62 -- values that depend on the discriminant. All such functions have the
65 -- function xxx (V : vtyp) return Unsigned is
67 -- return ... expression involving V.discrim
70 -----------------------
71 -- Local Subprograms --
72 -----------------------
77 Right_Opnd
: Node_Id
) return Node_Id
;
78 -- This is like Make_Op_Add except that it optimizes some cases knowing
79 -- that associative rearrangement is allowed for constant folding if one
80 -- of the operands is a compile time known value.
82 function Assoc_Multiply
85 Right_Opnd
: Node_Id
) return Node_Id
;
86 -- This is like Make_Op_Multiply except that it optimizes some cases
87 -- knowing that associative rearrangement is allowed for constant folding
88 -- if one of the operands is a compile time known value
90 function Assoc_Subtract
93 Right_Opnd
: Node_Id
) return Node_Id
;
94 -- This is like Make_Op_Subtract except that it optimizes some cases
95 -- knowing that associative rearrangement is allowed for constant folding
96 -- if one of the operands is a compile time known value
98 function Bits_To_SU
(N
: Node_Id
) return Node_Id
;
99 -- This is used when we cross the boundary from static sizes in bits to
100 -- dynamic sizes in storage units. If the argument N is anything other
101 -- than an integer literal, it is returned unchanged, but if it is an
102 -- integer literal, then it is taken as a size in bits, and is replaced
103 -- by the corresponding size in storage units.
105 function Compute_Length
(Lo
: Node_Id
; Hi
: Node_Id
) return Node_Id
;
106 -- Given expressions for the low bound (Lo) and the high bound (Hi),
107 -- Build an expression for the value hi-lo+1, converted to type
108 -- Standard.Unsigned. Takes care of the case where the operands
109 -- are of an enumeration type (so that the subtraction cannot be
110 -- done directly) by applying the Pos operator to Hi/Lo first.
112 function Expr_From_SO_Ref
115 Comp
: Entity_Id
:= Empty
) return Node_Id
;
116 -- Given a value D from a size or offset field, return an expression
117 -- representing the value stored. If the value is known at compile time,
118 -- then an N_Integer_Literal is returned with the appropriate value. If
119 -- the value references a constant entity, then an N_Identifier node
120 -- referencing this entity is returned. If the value denotes a size
121 -- function, then returns a call node denoting the given function, with
122 -- a single actual parameter that either refers to the parameter V of
123 -- an enclosing size function (if Comp is Empty or its type doesn't match
124 -- the function's formal), or else is a selected component V.c when Comp
125 -- denotes a component c whose type matches that of the function formal.
126 -- The Loc value is used for the Sloc value of constructed notes.
128 function SO_Ref_From_Expr
130 Ins_Type
: Entity_Id
;
131 Vtype
: Entity_Id
:= Empty
;
132 Make_Func
: Boolean := False) return Dynamic_SO_Ref
;
133 -- This routine is used in the case where a size/offset value is dynamic
134 -- and is represented by the expression Expr. SO_Ref_From_Expr checks if
135 -- the Expr contains a reference to the identifier V, and if so builds
136 -- a function depending on discriminants of the formal parameter V which
137 -- is of type Vtype. Otherwise, if the parameter Make_Func is True, then
138 -- Expr will be encapsulated in a parameterless function; if Make_Func is
139 -- False, then a constant entity with the value Expr is built. The result
140 -- is a Dynamic_SO_Ref to the created entity. Note that Vtype can be
141 -- omitted if Expr does not contain any reference to V, the created entity.
142 -- The declaration created is inserted in the freeze actions of Ins_Type,
143 -- which also supplies the Sloc for created nodes. This function also takes
144 -- care of making sure that the expression is properly analyzed and
145 -- resolved (which may not be the case yet if we build the expression
148 function Get_Max_SU_Size
(E
: Entity_Id
) return Node_Id
;
149 -- E is an array type or subtype that has at least one index bound that
150 -- is the value of a record discriminant. For such an array, the function
151 -- computes an expression that yields the maximum possible size of the
152 -- array in storage units. The result is not defined for any other type,
153 -- or for arrays that do not depend on discriminants, and it is a fatal
154 -- error to call this unless Size_Depends_On_Discriminant (E) is True.
156 procedure Layout_Array_Type
(E
: Entity_Id
);
157 -- Front-end layout of non-bit-packed array type or subtype
159 procedure Layout_Record_Type
(E
: Entity_Id
);
160 -- Front-end layout of record type
162 procedure Rewrite_Integer
(N
: Node_Id
; V
: Uint
);
163 -- Rewrite node N with an integer literal whose value is V. The Sloc for
164 -- the new node is taken from N, and the type of the literal is set to a
165 -- copy of the type of N on entry.
167 procedure Set_And_Check_Static_Size
171 -- This procedure is called to check explicit given sizes (possibly stored
172 -- in the Esize and RM_Size fields of E) against computed Object_Size
173 -- (Esiz) and Value_Size (RM_Siz) values. Appropriate errors and warnings
174 -- are posted if specified sizes are inconsistent with specified sizes. On
175 -- return, Esize and RM_Size fields of E are set (either from previously
176 -- given values, or from the newly computed values, as appropriate).
178 procedure Set_Composite_Alignment
(E
: Entity_Id
);
179 -- This procedure is called for record types and subtypes, and also for
180 -- atomic array types and subtypes. If no alignment is set, and the size
181 -- is 2 or 4 (or 8 if the word size is 8), then the alignment is set to
184 ----------------------------
185 -- Adjust_Esize_Alignment --
186 ----------------------------
188 procedure Adjust_Esize_Alignment
(E
: Entity_Id
) is
193 -- Nothing to do if size unknown
195 if Unknown_Esize
(E
) then
199 -- Determine if size is constrained by an attribute definition clause
200 -- which must be obeyed. If so, we cannot increase the size in this
203 -- For a type, the issue is whether an object size clause has been set.
204 -- A normal size clause constrains only the value size (RM_Size)
207 Esize_Set
:= Has_Object_Size_Clause
(E
);
209 -- For an object, the issue is whether a size clause is present
212 Esize_Set
:= Has_Size_Clause
(E
);
215 -- If size is known it must be a multiple of the storage unit size
217 if Esize
(E
) mod SSU
/= 0 then
219 -- If not, and size specified, then give error
223 ("size for& not a multiple of storage unit size",
227 -- Otherwise bump up size to a storage unit boundary
230 Set_Esize
(E
, (Esize
(E
) + SSU
- 1) / SSU
* SSU
);
234 -- Now we have the size set, it must be a multiple of the alignment
235 -- nothing more we can do here if the alignment is unknown here.
237 if Unknown_Alignment
(E
) then
241 -- At this point both the Esize and Alignment are known, so we need
242 -- to make sure they are consistent.
244 Abits
:= UI_To_Int
(Alignment
(E
)) * SSU
;
246 if Esize
(E
) mod Abits
= 0 then
250 -- Here we have a situation where the Esize is not a multiple of the
251 -- alignment. We must either increase Esize or reduce the alignment to
252 -- correct this situation.
254 -- The case in which we can decrease the alignment is where the
255 -- alignment was not set by an alignment clause, and the type in
256 -- question is a discrete type, where it is definitely safe to reduce
257 -- the alignment. For example:
259 -- t : integer range 1 .. 2;
262 -- In this situation, the initial alignment of t is 4, copied from
263 -- the Integer base type, but it is safe to reduce it to 1 at this
264 -- stage, since we will only be loading a single storage unit.
266 if Is_Discrete_Type
(Etype
(E
))
267 and then not Has_Alignment_Clause
(E
)
271 exit when Esize
(E
) mod Abits
= 0;
274 Init_Alignment
(E
, Abits
/ SSU
);
278 -- Now the only possible approach left is to increase the Esize but we
279 -- can't do that if the size was set by a specific clause.
283 ("size for& is not a multiple of alignment",
286 -- Otherwise we can indeed increase the size to a multiple of alignment
289 Set_Esize
(E
, ((Esize
(E
) + (Abits
- 1)) / Abits
) * Abits
);
291 end Adjust_Esize_Alignment
;
300 Right_Opnd
: Node_Id
) return Node_Id
306 -- Case of right operand is a constant
308 if Compile_Time_Known_Value
(Right_Opnd
) then
310 R
:= Expr_Value
(Right_Opnd
);
312 -- Case of left operand is a constant
314 elsif Compile_Time_Known_Value
(Left_Opnd
) then
316 R
:= Expr_Value
(Left_Opnd
);
318 -- Neither operand is a constant, do the addition with no optimization
321 return Make_Op_Add
(Loc
, Left_Opnd
, Right_Opnd
);
324 -- Case of left operand is an addition
326 if Nkind
(L
) = N_Op_Add
then
328 -- (C1 + E) + C2 = (C1 + C2) + E
330 if Compile_Time_Known_Value
(Sinfo
.Left_Opnd
(L
)) then
332 (Sinfo
.Left_Opnd
(L
),
333 Expr_Value
(Sinfo
.Left_Opnd
(L
)) + R
);
336 -- (E + C1) + C2 = E + (C1 + C2)
338 elsif Compile_Time_Known_Value
(Sinfo
.Right_Opnd
(L
)) then
340 (Sinfo
.Right_Opnd
(L
),
341 Expr_Value
(Sinfo
.Right_Opnd
(L
)) + R
);
345 -- Case of left operand is a subtraction
347 elsif Nkind
(L
) = N_Op_Subtract
then
349 -- (C1 - E) + C2 = (C1 + C2) + E
351 if Compile_Time_Known_Value
(Sinfo
.Left_Opnd
(L
)) then
353 (Sinfo
.Left_Opnd
(L
),
354 Expr_Value
(Sinfo
.Left_Opnd
(L
)) + R
);
357 -- (E - C1) + C2 = E - (C1 - C2)
359 elsif Compile_Time_Known_Value
(Sinfo
.Right_Opnd
(L
)) then
361 (Sinfo
.Right_Opnd
(L
),
362 Expr_Value
(Sinfo
.Right_Opnd
(L
)) - R
);
367 -- Not optimizable, do the addition
369 return Make_Op_Add
(Loc
, Left_Opnd
, Right_Opnd
);
376 function Assoc_Multiply
379 Right_Opnd
: Node_Id
) return Node_Id
385 -- Case of right operand is a constant
387 if Compile_Time_Known_Value
(Right_Opnd
) then
389 R
:= Expr_Value
(Right_Opnd
);
391 -- Case of left operand is a constant
393 elsif Compile_Time_Known_Value
(Left_Opnd
) then
395 R
:= Expr_Value
(Left_Opnd
);
397 -- Neither operand is a constant, do the multiply with no optimization
400 return Make_Op_Multiply
(Loc
, Left_Opnd
, Right_Opnd
);
403 -- Case of left operand is an multiplication
405 if Nkind
(L
) = N_Op_Multiply
then
407 -- (C1 * E) * C2 = (C1 * C2) + E
409 if Compile_Time_Known_Value
(Sinfo
.Left_Opnd
(L
)) then
411 (Sinfo
.Left_Opnd
(L
),
412 Expr_Value
(Sinfo
.Left_Opnd
(L
)) * R
);
415 -- (E * C1) * C2 = E * (C1 * C2)
417 elsif Compile_Time_Known_Value
(Sinfo
.Right_Opnd
(L
)) then
419 (Sinfo
.Right_Opnd
(L
),
420 Expr_Value
(Sinfo
.Right_Opnd
(L
)) * R
);
425 -- Not optimizable, do the multiplication
427 return Make_Op_Multiply
(Loc
, Left_Opnd
, Right_Opnd
);
434 function Assoc_Subtract
437 Right_Opnd
: Node_Id
) return Node_Id
443 -- Case of right operand is a constant
445 if Compile_Time_Known_Value
(Right_Opnd
) then
447 R
:= Expr_Value
(Right_Opnd
);
449 -- Right operand is a constant, do the subtract with no optimization
452 return Make_Op_Subtract
(Loc
, Left_Opnd
, Right_Opnd
);
455 -- Case of left operand is an addition
457 if Nkind
(L
) = N_Op_Add
then
459 -- (C1 + E) - C2 = (C1 - C2) + E
461 if Compile_Time_Known_Value
(Sinfo
.Left_Opnd
(L
)) then
463 (Sinfo
.Left_Opnd
(L
),
464 Expr_Value
(Sinfo
.Left_Opnd
(L
)) - R
);
467 -- (E + C1) - C2 = E + (C1 - C2)
469 elsif Compile_Time_Known_Value
(Sinfo
.Right_Opnd
(L
)) then
471 (Sinfo
.Right_Opnd
(L
),
472 Expr_Value
(Sinfo
.Right_Opnd
(L
)) - R
);
476 -- Case of left operand is a subtraction
478 elsif Nkind
(L
) = N_Op_Subtract
then
480 -- (C1 - E) - C2 = (C1 - C2) + E
482 if Compile_Time_Known_Value
(Sinfo
.Left_Opnd
(L
)) then
484 (Sinfo
.Left_Opnd
(L
),
485 Expr_Value
(Sinfo
.Left_Opnd
(L
)) + R
);
488 -- (E - C1) - C2 = E - (C1 + C2)
490 elsif Compile_Time_Known_Value
(Sinfo
.Right_Opnd
(L
)) then
492 (Sinfo
.Right_Opnd
(L
),
493 Expr_Value
(Sinfo
.Right_Opnd
(L
)) + R
);
498 -- Not optimizable, do the subtraction
500 return Make_Op_Subtract
(Loc
, Left_Opnd
, Right_Opnd
);
507 function Bits_To_SU
(N
: Node_Id
) return Node_Id
is
509 if Nkind
(N
) = N_Integer_Literal
then
510 Set_Intval
(N
, (Intval
(N
) + (SSU
- 1)) / SSU
);
520 function Compute_Length
(Lo
: Node_Id
; Hi
: Node_Id
) return Node_Id
is
521 Loc
: constant Source_Ptr
:= Sloc
(Lo
);
522 Typ
: constant Entity_Id
:= Etype
(Lo
);
529 -- If the bounds are First and Last attributes for the same dimension
530 -- and both have prefixes that denotes the same entity, then we create
531 -- and return a Length attribute. This may allow the back end to
532 -- generate better code in cases where it already has the length.
534 if Nkind
(Lo
) = N_Attribute_Reference
535 and then Attribute_Name
(Lo
) = Name_First
536 and then Nkind
(Hi
) = N_Attribute_Reference
537 and then Attribute_Name
(Hi
) = Name_Last
538 and then Is_Entity_Name
(Prefix
(Lo
))
539 and then Is_Entity_Name
(Prefix
(Hi
))
540 and then Entity
(Prefix
(Lo
)) = Entity
(Prefix
(Hi
))
545 if Present
(First
(Expressions
(Lo
))) then
546 Lo_Dim
:= Expr_Value
(First
(Expressions
(Lo
)));
549 if Present
(First
(Expressions
(Hi
))) then
550 Hi_Dim
:= Expr_Value
(First
(Expressions
(Hi
)));
553 if Lo_Dim
= Hi_Dim
then
555 Make_Attribute_Reference
(Loc
,
556 Prefix
=> New_Occurrence_Of
557 (Entity
(Prefix
(Lo
)), Loc
),
558 Attribute_Name
=> Name_Length
,
559 Expressions
=> New_List
560 (Make_Integer_Literal
(Loc
, Lo_Dim
)));
564 Lo_Op
:= New_Copy_Tree
(Lo
);
565 Hi_Op
:= New_Copy_Tree
(Hi
);
567 -- If type is enumeration type, then use Pos attribute to convert
568 -- to integer type for which subtraction is a permitted operation.
570 if Is_Enumeration_Type
(Typ
) then
572 Make_Attribute_Reference
(Loc
,
573 Prefix
=> New_Occurrence_Of
(Typ
, Loc
),
574 Attribute_Name
=> Name_Pos
,
575 Expressions
=> New_List
(Lo_Op
));
578 Make_Attribute_Reference
(Loc
,
579 Prefix
=> New_Occurrence_Of
(Typ
, Loc
),
580 Attribute_Name
=> Name_Pos
,
581 Expressions
=> New_List
(Hi_Op
));
589 Right_Opnd
=> Lo_Op
),
590 Right_Opnd
=> Make_Integer_Literal
(Loc
, 1));
593 ----------------------
594 -- Expr_From_SO_Ref --
595 ----------------------
597 function Expr_From_SO_Ref
600 Comp
: Entity_Id
:= Empty
) return Node_Id
605 if Is_Dynamic_SO_Ref
(D
) then
606 Ent
:= Get_Dynamic_SO_Entity
(D
);
608 if Is_Discrim_SO_Function
(Ent
) then
610 -- If a component is passed in whose type matches the type of
611 -- the function formal, then select that component from the "V"
612 -- parameter rather than passing "V" directly.
615 and then Base_Type
(Etype
(Comp
))
616 = Base_Type
(Etype
(First_Formal
(Ent
)))
619 Make_Function_Call
(Loc
,
620 Name
=> New_Occurrence_Of
(Ent
, Loc
),
621 Parameter_Associations
=> New_List
(
622 Make_Selected_Component
(Loc
,
623 Prefix
=> Make_Identifier
(Loc
, Chars
=> Vname
),
624 Selector_Name
=> New_Occurrence_Of
(Comp
, Loc
))));
628 Make_Function_Call
(Loc
,
629 Name
=> New_Occurrence_Of
(Ent
, Loc
),
630 Parameter_Associations
=> New_List
(
631 Make_Identifier
(Loc
, Chars
=> Vname
)));
635 return New_Occurrence_Of
(Ent
, Loc
);
639 return Make_Integer_Literal
(Loc
, D
);
641 end Expr_From_SO_Ref
;
643 ---------------------
644 -- Get_Max_SU_Size --
645 ---------------------
647 function Get_Max_SU_Size
(E
: Entity_Id
) return Node_Id
is
648 Loc
: constant Source_Ptr
:= Sloc
(E
);
656 type Val_Status_Type
is (Const
, Dynamic
);
658 type Val_Type
(Status
: Val_Status_Type
:= Const
) is
661 when Const
=> Val
: Uint
;
662 when Dynamic
=> Nod
: Node_Id
;
665 -- Shows the status of the value so far. Const means that the value is
666 -- constant, and Val is the current constant value. Dynamic means that
667 -- the value is dynamic, and in this case Nod is the Node_Id of the
668 -- expression to compute the value.
671 -- Calculated value so far if Size.Status = Const,
672 -- or expression value so far if Size.Status = Dynamic.
674 SU_Convert_Required
: Boolean := False;
675 -- This is set to True if the final result must be converted from bits
676 -- to storage units (rounding up to a storage unit boundary).
678 -----------------------
679 -- Local Subprograms --
680 -----------------------
682 procedure Max_Discrim
(N
: in out Node_Id
);
683 -- If the node N represents a discriminant, replace it by the maximum
684 -- value of the discriminant.
686 procedure Min_Discrim
(N
: in out Node_Id
);
687 -- If the node N represents a discriminant, replace it by the minimum
688 -- value of the discriminant.
694 procedure Max_Discrim
(N
: in out Node_Id
) is
696 if Nkind
(N
) = N_Identifier
697 and then Ekind
(Entity
(N
)) = E_Discriminant
699 N
:= Type_High_Bound
(Etype
(N
));
707 procedure Min_Discrim
(N
: in out Node_Id
) is
709 if Nkind
(N
) = N_Identifier
710 and then Ekind
(Entity
(N
)) = E_Discriminant
712 N
:= Type_Low_Bound
(Etype
(N
));
716 -- Start of processing for Get_Max_SU_Size
719 pragma Assert
(Size_Depends_On_Discriminant
(E
));
721 -- Initialize status from component size
723 if Known_Static_Component_Size
(E
) then
724 Size
:= (Const
, Component_Size
(E
));
727 Size
:= (Dynamic
, Expr_From_SO_Ref
(Loc
, Component_Size
(E
)));
730 -- Loop through indices
732 Indx
:= First_Index
(E
);
733 while Present
(Indx
) loop
734 Ityp
:= Etype
(Indx
);
735 Lo
:= Type_Low_Bound
(Ityp
);
736 Hi
:= Type_High_Bound
(Ityp
);
741 -- Value of the current subscript range is statically known
743 if Compile_Time_Known_Value
(Lo
)
744 and then Compile_Time_Known_Value
(Hi
)
746 S
:= Expr_Value
(Hi
) - Expr_Value
(Lo
) + 1;
748 -- If known flat bound, entire size of array is zero!
751 return Make_Integer_Literal
(Loc
, 0);
754 -- Current value is constant, evolve value
756 if Size
.Status
= Const
then
757 Size
.Val
:= Size
.Val
* S
;
759 -- Current value is dynamic
762 -- An interesting little optimization, if we have a pending
763 -- conversion from bits to storage units, and the current
764 -- length is a multiple of the storage unit size, then we
765 -- can take the factor out here statically, avoiding some
766 -- extra dynamic computations at the end.
768 if SU_Convert_Required
and then S
mod SSU
= 0 then
770 SU_Convert_Required
:= False;
775 Left_Opnd
=> Size
.Nod
,
777 Make_Integer_Literal
(Loc
, Intval
=> S
));
780 -- Value of the current subscript range is dynamic
783 -- If the current size value is constant, then here is where we
784 -- make a transition to dynamic values, which are always stored
785 -- in storage units, However, we do not want to convert to SU's
786 -- too soon, consider the case of a packed array of single bits,
787 -- we want to do the SU conversion after computing the size in
790 if Size
.Status
= Const
then
792 -- If the current value is a multiple of the storage unit,
793 -- then most certainly we can do the conversion now, simply
794 -- by dividing the current value by the storage unit value.
795 -- If this works, we set SU_Convert_Required to False.
797 if Size
.Val
mod SSU
= 0 then
800 (Dynamic
, Make_Integer_Literal
(Loc
, Size
.Val
/ SSU
));
801 SU_Convert_Required
:= False;
803 -- Otherwise, we go ahead and convert the value in bits, and
804 -- set SU_Convert_Required to True to ensure that the final
805 -- value is indeed properly converted.
808 Size
:= (Dynamic
, Make_Integer_Literal
(Loc
, Size
.Val
));
809 SU_Convert_Required
:= True;
815 Len
:= Compute_Length
(Lo
, Hi
);
817 -- Check possible range of Len
823 pragma Warnings
(Off
, LHi
);
827 Determine_Range
(Len
, OK
, LLo
, LHi
);
829 Len
:= Convert_To
(Standard_Unsigned
, Len
);
831 -- If we cannot verify that range cannot be super-flat, we need
832 -- a max with zero, since length must be non-negative.
834 if not OK
or else LLo
< 0 then
836 Make_Attribute_Reference
(Loc
,
838 New_Occurrence_Of
(Standard_Unsigned
, Loc
),
839 Attribute_Name
=> Name_Max
,
840 Expressions
=> New_List
(
841 Make_Integer_Literal
(Loc
, 0),
850 -- Here after processing all bounds to set sizes. If the value is a
851 -- constant, then it is bits, so we convert to storage units.
853 if Size
.Status
= Const
then
854 return Bits_To_SU
(Make_Integer_Literal
(Loc
, Size
.Val
));
856 -- Case where the value is dynamic
859 -- Do convert from bits to SU's if needed
861 if SU_Convert_Required
then
863 -- The expression required is (Size.Nod + SU - 1) / SU
869 Left_Opnd
=> Size
.Nod
,
870 Right_Opnd
=> Make_Integer_Literal
(Loc
, SSU
- 1)),
871 Right_Opnd
=> Make_Integer_Literal
(Loc
, SSU
));
878 -----------------------
879 -- Layout_Array_Type --
880 -----------------------
882 procedure Layout_Array_Type
(E
: Entity_Id
) is
883 Loc
: constant Source_Ptr
:= Sloc
(E
);
884 Ctyp
: constant Entity_Id
:= Component_Type
(E
);
892 Insert_Typ
: Entity_Id
;
893 -- This is the type with which any generated constants or functions
894 -- will be associated (i.e. inserted into the freeze actions). This
895 -- is normally the type being laid out. The exception occurs when
896 -- we are laying out Itype's which are local to a record type, and
897 -- whose scope is this record type. Such types do not have freeze
898 -- nodes (because we have no place to put them).
900 ------------------------------------
901 -- How An Array Type is Laid Out --
902 ------------------------------------
904 -- Here is what goes on. We need to multiply the component size of the
905 -- array (which has already been set) by the length of each of the
906 -- indexes. If all these values are known at compile time, then the
907 -- resulting size of the array is the appropriate constant value.
909 -- If the component size or at least one bound is dynamic (but no
910 -- discriminants are present), then the size will be computed as an
911 -- expression that calculates the proper size.
913 -- If there is at least one discriminant bound, then the size is also
914 -- computed as an expression, but this expression contains discriminant
915 -- values which are obtained by selecting from a function parameter, and
916 -- the size is given by a function that is passed the variant record in
917 -- question, and whose body is the expression.
919 type Val_Status_Type
is (Const
, Dynamic
, Discrim
);
921 type Val_Type
(Status
: Val_Status_Type
:= Const
) is
926 -- Calculated value so far if Val_Status = Const
928 when Dynamic | Discrim
=>
930 -- Expression value so far if Val_Status /= Const
934 -- Records the value or expression computed so far. Const means that
935 -- the value is constant, and Val is the current constant value.
936 -- Dynamic means that the value is dynamic, and in this case Nod is
937 -- the Node_Id of the expression to compute the value, and Discrim
938 -- means that at least one bound is a discriminant, in which case Nod
939 -- is the expression so far (which will be the body of the function).
942 -- Value of size computed so far. See comments above
944 Vtyp
: Entity_Id
:= Empty
;
945 -- Variant record type for the formal parameter of the discriminant
946 -- function V if Status = Discrim.
948 SU_Convert_Required
: Boolean := False;
949 -- This is set to True if the final result must be converted from
950 -- bits to storage units (rounding up to a storage unit boundary).
952 Storage_Divisor
: Uint
:= UI_From_Int
(SSU
);
953 -- This is the amount that a nonstatic computed size will be divided
954 -- by to convert it from bits to storage units. This is normally
955 -- equal to SSU, but can be reduced in the case of packed components
956 -- that fit evenly into a storage unit.
958 Make_Size_Function
: Boolean := False;
959 -- Indicates whether to request that SO_Ref_From_Expr should
960 -- encapsulate the array size expression in a function.
962 procedure Discrimify
(N
: in out Node_Id
);
963 -- If N represents a discriminant, then the Size.Status is set to
964 -- Discrim, and Vtyp is set. The parameter N is replaced with the
965 -- proper expression to extract the discriminant value from V.
971 procedure Discrimify
(N
: in out Node_Id
) is
976 if Nkind
(N
) = N_Identifier
977 and then Ekind
(Entity
(N
)) = E_Discriminant
979 Set_Size_Depends_On_Discriminant
(E
);
981 if Size
.Status
/= Discrim
then
982 Decl
:= Parent
(Parent
(Entity
(N
)));
983 Size
:= (Discrim
, Size
.Nod
);
984 Vtyp
:= Defining_Identifier
(Decl
);
990 Make_Selected_Component
(Loc
,
991 Prefix
=> Make_Identifier
(Loc
, Chars
=> Vname
),
992 Selector_Name
=> New_Occurrence_Of
(Entity
(N
), Loc
));
994 -- Set the Etype attributes of the selected name and its prefix.
995 -- Analyze_And_Resolve can't be called here because the Vname
996 -- entity denoted by the prefix will not yet exist (it's created
997 -- by SO_Ref_From_Expr, called at the end of Layout_Array_Type).
999 Set_Etype
(Prefix
(N
), Vtyp
);
1004 -- Start of processing for Layout_Array_Type
1007 -- Default alignment is component alignment
1009 if Unknown_Alignment
(E
) then
1010 Set_Alignment
(E
, Alignment
(Ctyp
));
1013 -- Calculate proper type for insertions
1015 if Is_Record_Type
(Underlying_Type
(Scope
(E
))) then
1016 Insert_Typ
:= Underlying_Type
(Scope
(E
));
1021 -- If the component type is a generic formal type then there's no point
1022 -- in determining a size for the array type.
1024 if Is_Generic_Type
(Ctyp
) then
1028 -- Deal with component size if base type
1030 if Ekind
(E
) = E_Array_Type
then
1032 -- Cannot do anything if Esize of component type unknown
1034 if Unknown_Esize
(Ctyp
) then
1038 -- Set component size if not set already
1040 if Unknown_Component_Size
(E
) then
1041 Set_Component_Size
(E
, Esize
(Ctyp
));
1045 -- (RM 13.3 (48)) says that the size of an unconstrained array
1046 -- is implementation defined. We choose to leave it as Unknown
1047 -- here, and the actual behavior is determined by the back end.
1049 if not Is_Constrained
(E
) then
1053 -- Initialize status from component size
1055 if Known_Static_Component_Size
(E
) then
1056 Size
:= (Const
, Component_Size
(E
));
1059 Size
:= (Dynamic
, Expr_From_SO_Ref
(Loc
, Component_Size
(E
)));
1062 -- Loop to process array indices
1064 Indx
:= First_Index
(E
);
1065 while Present
(Indx
) loop
1066 Ityp
:= Etype
(Indx
);
1068 -- If an index of the array is a generic formal type then there is
1069 -- no point in determining a size for the array type.
1071 if Is_Generic_Type
(Ityp
) then
1075 Lo
:= Type_Low_Bound
(Ityp
);
1076 Hi
:= Type_High_Bound
(Ityp
);
1078 -- Value of the current subscript range is statically known
1080 if Compile_Time_Known_Value
(Lo
)
1081 and then Compile_Time_Known_Value
(Hi
)
1083 S
:= Expr_Value
(Hi
) - Expr_Value
(Lo
) + 1;
1085 -- If known flat bound, entire size of array is zero!
1088 Set_Esize
(E
, Uint_0
);
1089 Set_RM_Size
(E
, Uint_0
);
1093 -- If constant, evolve value
1095 if Size
.Status
= Const
then
1096 Size
.Val
:= Size
.Val
* S
;
1098 -- Current value is dynamic
1101 -- An interesting little optimization, if we have a pending
1102 -- conversion from bits to storage units, and the current
1103 -- length is a multiple of the storage unit size, then we
1104 -- can take the factor out here statically, avoiding some
1105 -- extra dynamic computations at the end.
1107 if SU_Convert_Required
and then S
mod SSU
= 0 then
1109 SU_Convert_Required
:= False;
1112 -- Now go ahead and evolve the expression
1115 Assoc_Multiply
(Loc
,
1116 Left_Opnd
=> Size
.Nod
,
1118 Make_Integer_Literal
(Loc
, Intval
=> S
));
1121 -- Value of the current subscript range is dynamic
1124 -- If the current size value is constant, then here is where we
1125 -- make a transition to dynamic values, which are always stored
1126 -- in storage units, However, we do not want to convert to SU's
1127 -- too soon, consider the case of a packed array of single bits,
1128 -- we want to do the SU conversion after computing the size in
1131 if Size
.Status
= Const
then
1133 -- If the current value is a multiple of the storage unit,
1134 -- then most certainly we can do the conversion now, simply
1135 -- by dividing the current value by the storage unit value.
1136 -- If this works, we set SU_Convert_Required to False.
1138 if Size
.Val
mod SSU
= 0 then
1140 (Dynamic
, Make_Integer_Literal
(Loc
, Size
.Val
/ SSU
));
1141 SU_Convert_Required
:= False;
1143 -- If the current value is a factor of the storage unit, then
1144 -- we can use a value of one for the size and reduce the
1145 -- strength of the later division.
1147 elsif SSU
mod Size
.Val
= 0 then
1148 Storage_Divisor
:= SSU
/ Size
.Val
;
1149 Size
:= (Dynamic
, Make_Integer_Literal
(Loc
, Uint_1
));
1150 SU_Convert_Required
:= True;
1152 -- Otherwise, we go ahead and convert the value in bits, and
1153 -- set SU_Convert_Required to True to ensure that the final
1154 -- value is indeed properly converted.
1157 Size
:= (Dynamic
, Make_Integer_Literal
(Loc
, Size
.Val
));
1158 SU_Convert_Required
:= True;
1165 -- Length is hi-lo+1
1167 Len
:= Compute_Length
(Lo
, Hi
);
1169 -- If Len isn't a Length attribute, then its range needs to be
1170 -- checked a possible Max with zero needs to be computed.
1172 if Nkind
(Len
) /= N_Attribute_Reference
1173 or else Attribute_Name
(Len
) /= Name_Length
1181 -- Check possible range of Len
1183 Set_Parent
(Len
, E
);
1184 Determine_Range
(Len
, OK
, LLo
, LHi
);
1186 Len
:= Convert_To
(Standard_Unsigned
, Len
);
1188 -- If range definitely flat or superflat,
1189 -- result size is zero
1191 if OK
and then LHi
<= 0 then
1192 Set_Esize
(E
, Uint_0
);
1193 Set_RM_Size
(E
, Uint_0
);
1197 -- If we cannot verify that range cannot be super-flat, we
1198 -- need a max with zero, since length cannot be negative.
1200 if not OK
or else LLo
< 0 then
1202 Make_Attribute_Reference
(Loc
,
1204 New_Occurrence_Of
(Standard_Unsigned
, Loc
),
1205 Attribute_Name
=> Name_Max
,
1206 Expressions
=> New_List
(
1207 Make_Integer_Literal
(Loc
, 0),
1213 -- At this stage, Len has the expression for the length
1216 Assoc_Multiply
(Loc
,
1217 Left_Opnd
=> Size
.Nod
,
1224 -- Here after processing all bounds to set sizes. If the value is a
1225 -- constant, then it is bits, and the only thing we need to do is to
1226 -- check against explicit given size and do alignment adjust.
1228 if Size
.Status
= Const
then
1229 Set_And_Check_Static_Size
(E
, Size
.Val
, Size
.Val
);
1230 Adjust_Esize_Alignment
(E
);
1232 -- Case where the value is dynamic
1235 -- Do convert from bits to SU's if needed
1237 if SU_Convert_Required
then
1239 -- The expression required is:
1240 -- (Size.Nod + Storage_Divisor - 1) / Storage_Divisor
1243 Make_Op_Divide
(Loc
,
1246 Left_Opnd
=> Size
.Nod
,
1247 Right_Opnd
=> Make_Integer_Literal
1248 (Loc
, Storage_Divisor
- 1)),
1249 Right_Opnd
=> Make_Integer_Literal
(Loc
, Storage_Divisor
));
1252 -- If the array entity is not declared at the library level and its
1253 -- not nested within a subprogram that is marked for inlining, then
1254 -- we request that the size expression be encapsulated in a function.
1255 -- Since this expression is not needed in most cases, we prefer not
1256 -- to incur the overhead of the computation on calls to the enclosing
1257 -- subprogram except for subprograms that require the size.
1259 if not Is_Library_Level_Entity
(E
) then
1260 Make_Size_Function
:= True;
1263 Parent_Subp
: Entity_Id
:= Enclosing_Subprogram
(E
);
1266 while Present
(Parent_Subp
) loop
1267 if Is_Inlined
(Parent_Subp
) then
1268 Make_Size_Function
:= False;
1272 Parent_Subp
:= Enclosing_Subprogram
(Parent_Subp
);
1277 -- Now set the dynamic size (the Value_Size is always the same
1278 -- as the Object_Size for arrays whose length is dynamic).
1280 -- ??? If Size.Status = Dynamic, Vtyp will not have been set.
1281 -- The added initialization sets it to Empty now, but is this
1287 (Size
.Nod
, Insert_Typ
, Vtyp
, Make_Func
=> Make_Size_Function
));
1288 Set_RM_Size
(E
, Esize
(E
));
1290 end Layout_Array_Type
;
1296 procedure Layout_Object
(E
: Entity_Id
) is
1297 T
: constant Entity_Id
:= Etype
(E
);
1300 -- Nothing to do if backend does layout
1302 if not Frontend_Layout_On_Target
then
1306 -- Set size if not set for object and known for type. Use the RM_Size if
1307 -- that is known for the type and Esize is not.
1309 if Unknown_Esize
(E
) then
1310 if Known_Esize
(T
) then
1311 Set_Esize
(E
, Esize
(T
));
1313 elsif Known_RM_Size
(T
) then
1314 Set_Esize
(E
, RM_Size
(T
));
1318 -- Set alignment from type if unknown and type alignment known
1320 if Unknown_Alignment
(E
) and then Known_Alignment
(T
) then
1321 Set_Alignment
(E
, Alignment
(T
));
1324 -- Make sure size and alignment are consistent
1326 Adjust_Esize_Alignment
(E
);
1328 -- Final adjustment, if we don't know the alignment, and the Esize was
1329 -- not set by an explicit Object_Size attribute clause, then we reset
1330 -- the Esize to unknown, since we really don't know it.
1332 if Unknown_Alignment
(E
)
1333 and then not Has_Size_Clause
(E
)
1335 Set_Esize
(E
, Uint_0
);
1339 ------------------------
1340 -- Layout_Record_Type --
1341 ------------------------
1343 procedure Layout_Record_Type
(E
: Entity_Id
) is
1344 Loc
: constant Source_Ptr
:= Sloc
(E
);
1348 -- Current component being laid out
1350 Prev_Comp
: Entity_Id
;
1351 -- Previous laid out component
1353 procedure Get_Next_Component_Location
1354 (Prev_Comp
: Entity_Id
;
1356 New_Npos
: out SO_Ref
;
1357 New_Fbit
: out SO_Ref
;
1358 New_NPMax
: out SO_Ref
;
1359 Force_SU
: Boolean);
1360 -- Given the previous component in Prev_Comp, which is already laid
1361 -- out, and the alignment of the following component, lays out the
1362 -- following component, and returns its starting position in New_Npos
1363 -- (Normalized_Position value), New_Fbit (Normalized_First_Bit value),
1364 -- and New_NPMax (Normalized_Position_Max value). If Prev_Comp is empty
1365 -- (no previous component is present), then New_Npos, New_Fbit and
1366 -- New_NPMax are all set to zero on return. This procedure is also
1367 -- used to compute the size of a record or variant by giving it the
1368 -- last component, and the record alignment. Force_SU is used to force
1369 -- the new component location to be aligned on a storage unit boundary,
1370 -- even in a packed record, False means that the new position does not
1371 -- need to be bumped to a storage unit boundary, True means a storage
1372 -- unit boundary is always required.
1374 procedure Layout_Component
(Comp
: Entity_Id
; Prev_Comp
: Entity_Id
);
1375 -- Lays out component Comp, given Prev_Comp, the previously laid-out
1376 -- component (Prev_Comp = Empty if no components laid out yet). The
1377 -- alignment of the record itself is also updated if needed. Both
1378 -- Comp and Prev_Comp can be either components or discriminants.
1380 procedure Layout_Components
1384 RM_Siz
: out SO_Ref
);
1385 -- This procedure lays out the components of the given component list
1386 -- which contains the components starting with From and ending with To.
1387 -- The Next_Entity chain is used to traverse the components. On entry,
1388 -- Prev_Comp is set to the component preceding the list, so that the
1389 -- list is laid out after this component. Prev_Comp is set to Empty if
1390 -- the component list is to be laid out starting at the start of the
1391 -- record. On return, the components are all laid out, and Prev_Comp is
1392 -- set to the last laid out component. On return, Esiz is set to the
1393 -- resulting Object_Size value, which is the length of the record up
1394 -- to and including the last laid out entity. For Esiz, the value is
1395 -- adjusted to match the alignment of the record. RM_Siz is similarly
1396 -- set to the resulting Value_Size value, which is the same length, but
1397 -- not adjusted to meet the alignment. Note that in the case of variant
1398 -- records, Esiz represents the maximum size.
1400 procedure Layout_Non_Variant_Record
;
1401 -- Procedure called to lay out a non-variant record type or subtype
1403 procedure Layout_Variant_Record
;
1404 -- Procedure called to lay out a variant record type. Decl is set to the
1405 -- full type declaration for the variant record.
1407 ---------------------------------
1408 -- Get_Next_Component_Location --
1409 ---------------------------------
1411 procedure Get_Next_Component_Location
1412 (Prev_Comp
: Entity_Id
;
1414 New_Npos
: out SO_Ref
;
1415 New_Fbit
: out SO_Ref
;
1416 New_NPMax
: out SO_Ref
;
1420 -- No previous component, return zero position
1422 if No
(Prev_Comp
) then
1425 New_NPMax
:= Uint_0
;
1429 -- Here we have a previous component
1432 Loc
: constant Source_Ptr
:= Sloc
(Prev_Comp
);
1434 Old_Npos
: constant SO_Ref
:= Normalized_Position
(Prev_Comp
);
1435 Old_Fbit
: constant SO_Ref
:= Normalized_First_Bit
(Prev_Comp
);
1436 Old_NPMax
: constant SO_Ref
:= Normalized_Position_Max
(Prev_Comp
);
1437 Old_Esiz
: constant SO_Ref
:= Esize
(Prev_Comp
);
1439 Old_Maxsz
: Node_Id
;
1440 -- Expression representing maximum size of previous component
1443 -- Case where previous field had a dynamic size
1445 if Is_Dynamic_SO_Ref
(Esize
(Prev_Comp
)) then
1447 -- If the previous field had a dynamic length, then it is
1448 -- required to occupy an integral number of storage units,
1449 -- and start on a storage unit boundary. This means that
1450 -- the Normalized_First_Bit value is zero in the previous
1451 -- component, and the new value is also set to zero.
1455 -- In this case, the new position is given by an expression
1456 -- that is the sum of old normalized position and old size.
1462 Expr_From_SO_Ref
(Loc
, Old_Npos
),
1464 Expr_From_SO_Ref
(Loc
, Old_Esiz
, Prev_Comp
)),
1468 -- Get maximum size of previous component
1470 if Size_Depends_On_Discriminant
(Etype
(Prev_Comp
)) then
1471 Old_Maxsz
:= Get_Max_SU_Size
(Etype
(Prev_Comp
));
1473 Old_Maxsz
:= Expr_From_SO_Ref
(Loc
, Old_Esiz
, Prev_Comp
);
1476 -- Now we can compute the new max position. If the max size
1477 -- is static and the old position is static, then we can
1478 -- compute the new position statically.
1480 if Nkind
(Old_Maxsz
) = N_Integer_Literal
1481 and then Known_Static_Normalized_Position_Max
(Prev_Comp
)
1483 New_NPMax
:= Old_NPMax
+ Intval
(Old_Maxsz
);
1485 -- Otherwise new max position is dynamic
1491 Left_Opnd
=> Expr_From_SO_Ref
(Loc
, Old_NPMax
),
1492 Right_Opnd
=> Old_Maxsz
),
1497 -- Previous field has known static Esize
1500 New_Fbit
:= Old_Fbit
+ Old_Esiz
;
1502 -- Bump New_Fbit to storage unit boundary if required
1504 if New_Fbit
/= 0 and then Force_SU
then
1505 New_Fbit
:= (New_Fbit
+ SSU
- 1) / SSU
* SSU
;
1508 -- If old normalized position is static, we can go ahead and
1509 -- compute the new normalized position directly.
1511 if Known_Static_Normalized_Position
(Prev_Comp
) then
1512 New_Npos
:= Old_Npos
;
1514 if New_Fbit
>= SSU
then
1515 New_Npos
:= New_Npos
+ New_Fbit
/ SSU
;
1516 New_Fbit
:= New_Fbit
mod SSU
;
1519 -- Bump alignment if stricter than prev
1521 if Align
> Alignment
(Etype
(Prev_Comp
)) then
1522 New_Npos
:= (New_Npos
+ Align
- 1) / Align
* Align
;
1525 -- The max position is always equal to the position if
1526 -- the latter is static, since arrays depending on the
1527 -- values of discriminants never have static sizes.
1529 New_NPMax
:= New_Npos
;
1532 -- Case of old normalized position is dynamic
1535 -- If new bit position is within the current storage unit,
1536 -- we can just copy the old position as the result position
1537 -- (we have already set the new first bit value).
1539 if New_Fbit
< SSU
then
1540 New_Npos
:= Old_Npos
;
1541 New_NPMax
:= Old_NPMax
;
1543 -- If new bit position is past the current storage unit, we
1544 -- need to generate a new dynamic value for the position
1545 -- ??? need to deal with alignment
1551 Left_Opnd
=> Expr_From_SO_Ref
(Loc
, Old_Npos
),
1553 Make_Integer_Literal
(Loc
,
1554 Intval
=> New_Fbit
/ SSU
)),
1561 Left_Opnd
=> Expr_From_SO_Ref
(Loc
, Old_NPMax
),
1563 Make_Integer_Literal
(Loc
,
1564 Intval
=> New_Fbit
/ SSU
)),
1567 New_Fbit
:= New_Fbit
mod SSU
;
1572 end Get_Next_Component_Location
;
1574 ----------------------
1575 -- Layout_Component --
1576 ----------------------
1578 procedure Layout_Component
(Comp
: Entity_Id
; Prev_Comp
: Entity_Id
) is
1579 Ctyp
: constant Entity_Id
:= Etype
(Comp
);
1580 ORC
: constant Entity_Id
:= Original_Record_Component
(Comp
);
1587 -- Increase alignment of record if necessary. Note that we do not
1588 -- do this for packed records, which have an alignment of one by
1589 -- default, or for records for which an explicit alignment was
1590 -- specified with an alignment clause.
1592 if not Is_Packed
(E
)
1593 and then not Has_Alignment_Clause
(E
)
1594 and then Alignment
(Ctyp
) > Alignment
(E
)
1596 Set_Alignment
(E
, Alignment
(Ctyp
));
1599 -- If original component set, then use same layout
1601 if Present
(ORC
) and then ORC
/= Comp
then
1602 Set_Normalized_Position
(Comp
, Normalized_Position
(ORC
));
1603 Set_Normalized_First_Bit
(Comp
, Normalized_First_Bit
(ORC
));
1604 Set_Normalized_Position_Max
(Comp
, Normalized_Position_Max
(ORC
));
1605 Set_Component_Bit_Offset
(Comp
, Component_Bit_Offset
(ORC
));
1606 Set_Esize
(Comp
, Esize
(ORC
));
1610 -- Parent field is always at start of record, this will overlap
1611 -- the actual fields that are part of the parent, and that's fine
1613 if Chars
(Comp
) = Name_uParent
then
1614 Set_Normalized_Position
(Comp
, Uint_0
);
1615 Set_Normalized_First_Bit
(Comp
, Uint_0
);
1616 Set_Normalized_Position_Max
(Comp
, Uint_0
);
1617 Set_Component_Bit_Offset
(Comp
, Uint_0
);
1618 Set_Esize
(Comp
, Esize
(Ctyp
));
1622 -- Check case of type of component has a scope of the record we are
1623 -- laying out. When this happens, the type in question is an Itype
1624 -- that has not yet been laid out (that's because such types do not
1625 -- get frozen in the normal manner, because there is no place for
1626 -- the freeze nodes).
1628 if Scope
(Ctyp
) = E
then
1632 -- If component already laid out, then we are done
1634 if Known_Normalized_Position
(Comp
) then
1638 -- Set size of component from type. We use the Esize except in a
1639 -- packed record, where we use the RM_Size (since that is what the
1640 -- RM_Size value, as distinct from the Object_Size is useful for!)
1642 if Is_Packed
(E
) then
1643 Set_Esize
(Comp
, RM_Size
(Ctyp
));
1645 Set_Esize
(Comp
, Esize
(Ctyp
));
1648 -- Compute the component position from the previous one. See if
1649 -- current component requires being on a storage unit boundary.
1651 -- If record is not packed, we always go to a storage unit boundary
1653 if not Is_Packed
(E
) then
1659 -- Elementary types do not need SU boundary in packed record
1661 if Is_Elementary_Type
(Ctyp
) then
1664 -- Packed array types with a modular packed array type do not
1665 -- force a storage unit boundary (since the code generation
1666 -- treats these as equivalent to the underlying modular type),
1668 elsif Is_Array_Type
(Ctyp
)
1669 and then Is_Bit_Packed_Array
(Ctyp
)
1670 and then Is_Modular_Integer_Type
(Packed_Array_Type
(Ctyp
))
1674 -- Record types with known length less than or equal to the length
1675 -- of long long integer can also be unaligned, since they can be
1676 -- treated as scalars.
1678 elsif Is_Record_Type
(Ctyp
)
1679 and then not Is_Dynamic_SO_Ref
(Esize
(Ctyp
))
1680 and then Esize
(Ctyp
) <= Esize
(Standard_Long_Long_Integer
)
1684 -- All other cases force a storage unit boundary, even when packed
1691 -- Now get the next component location
1693 Get_Next_Component_Location
1694 (Prev_Comp
, Alignment
(Ctyp
), Npos
, Fbit
, NPMax
, Forc
);
1695 Set_Normalized_Position
(Comp
, Npos
);
1696 Set_Normalized_First_Bit
(Comp
, Fbit
);
1697 Set_Normalized_Position_Max
(Comp
, NPMax
);
1699 -- Set Component_Bit_Offset in the static case
1701 if Known_Static_Normalized_Position
(Comp
)
1702 and then Known_Normalized_First_Bit
(Comp
)
1704 Set_Component_Bit_Offset
(Comp
, SSU
* Npos
+ Fbit
);
1706 end Layout_Component
;
1708 -----------------------
1709 -- Layout_Components --
1710 -----------------------
1712 procedure Layout_Components
1716 RM_Siz
: out SO_Ref
)
1723 -- Only lay out components if there are some to lay out!
1725 if Present
(From
) then
1727 -- Lay out components with no component clauses
1731 if Ekind
(Comp
) = E_Component
1732 or else Ekind
(Comp
) = E_Discriminant
1734 -- The compatibility of component clauses with composite
1735 -- types isn't checked in Sem_Ch13, so we check it here.
1737 if Present
(Component_Clause
(Comp
)) then
1738 if Is_Composite_Type
(Etype
(Comp
))
1739 and then Esize
(Comp
) < RM_Size
(Etype
(Comp
))
1741 Error_Msg_Uint_1
:= RM_Size
(Etype
(Comp
));
1743 ("size for & too small, minimum allowed is ^",
1744 Component_Clause
(Comp
),
1749 Layout_Component
(Comp
, Prev_Comp
);
1754 exit when Comp
= To
;
1759 -- Set size fields, both are zero if no components
1761 if No
(Prev_Comp
) then
1765 -- If record subtype with non-static discriminants, then we don't
1766 -- know which variant will be the one which gets chosen. We don't
1767 -- just want to set the maximum size from the base, because the
1768 -- size should depend on the particular variant.
1770 -- What we do is to use the RM_Size of the base type, which has
1771 -- the necessary conditional computation of the size, using the
1772 -- size information for the particular variant chosen. Records
1773 -- with default discriminants for example have an Esize that is
1774 -- set to the maximum of all variants, but that's not what we
1775 -- want for a constrained subtype.
1777 elsif Ekind
(E
) = E_Record_Subtype
1778 and then not Has_Static_Discriminants
(E
)
1781 BT
: constant Node_Id
:= Base_Type
(E
);
1783 Esiz
:= RM_Size
(BT
);
1784 RM_Siz
:= RM_Size
(BT
);
1785 Set_Alignment
(E
, Alignment
(BT
));
1789 -- First the object size, for which we align past the last field
1790 -- to the alignment of the record (the object size is required to
1791 -- be a multiple of the alignment).
1793 Get_Next_Component_Location
1801 -- If the resulting normalized position is a dynamic reference,
1802 -- then the size is dynamic, and is stored in storage units. In
1803 -- this case, we set the RM_Size to the same value, it is simply
1804 -- not worth distinguishing Esize and RM_Size values in the
1805 -- dynamic case, since the RM has nothing to say about them.
1807 -- Note that a size cannot have been given in this case, since
1808 -- size specifications cannot be given for variable length types.
1811 Align
: constant Uint
:= Alignment
(E
);
1814 if Is_Dynamic_SO_Ref
(End_Npos
) then
1817 -- Set the Object_Size allowing for the alignment. In the
1818 -- dynamic case, we must do the actual runtime computation.
1819 -- We can skip this in the non-packed record case if the
1820 -- last component has a smaller alignment than the overall
1821 -- record alignment.
1823 if Is_Dynamic_SO_Ref
(End_NPMax
) then
1827 or else Alignment
(Etype
(Prev_Comp
)) < Align
1829 -- The expression we build is:
1830 -- (expr + align - 1) / align * align
1835 Make_Op_Multiply
(Loc
,
1837 Make_Op_Divide
(Loc
,
1841 Expr_From_SO_Ref
(Loc
, Esiz
),
1843 Make_Integer_Literal
(Loc
,
1844 Intval
=> Align
- 1)),
1846 Make_Integer_Literal
(Loc
, Align
)),
1848 Make_Integer_Literal
(Loc
, Align
)),
1853 -- Here Esiz is static, so we can adjust the alignment
1854 -- directly go give the required aligned value.
1857 Esiz
:= (End_NPMax
+ Align
- 1) / Align
* Align
* SSU
;
1860 -- Case where computed size is static
1863 -- The ending size was computed in Npos in storage units,
1864 -- but the actual size is stored in bits, so adjust
1865 -- accordingly. We also adjust the size to match the
1868 Esiz
:= (End_NPMax
+ Align
- 1) / Align
* Align
* SSU
;
1870 -- Compute the resulting Value_Size (RM_Size). For this
1871 -- purpose we do not force alignment of the record or
1872 -- storage size alignment of the result.
1874 Get_Next_Component_Location
1882 RM_Siz
:= End_Npos
* SSU
+ End_Fbit
;
1883 Set_And_Check_Static_Size
(E
, Esiz
, RM_Siz
);
1887 end Layout_Components
;
1889 -------------------------------
1890 -- Layout_Non_Variant_Record --
1891 -------------------------------
1893 procedure Layout_Non_Variant_Record
is
1897 Layout_Components
(First_Entity
(E
), Last_Entity
(E
), Esiz
, RM_Siz
);
1898 Set_Esize
(E
, Esiz
);
1899 Set_RM_Size
(E
, RM_Siz
);
1900 end Layout_Non_Variant_Record
;
1902 ---------------------------
1903 -- Layout_Variant_Record --
1904 ---------------------------
1906 procedure Layout_Variant_Record
is
1907 Tdef
: constant Node_Id
:= Type_Definition
(Decl
);
1908 First_Discr
: Entity_Id
;
1909 Last_Discr
: Entity_Id
;
1913 pragma Warnings
(Off
, SO_Ref
);
1915 RM_Siz_Expr
: Node_Id
:= Empty
;
1916 -- Expression for the evolving RM_Siz value. This is typically a
1917 -- conditional expression which involves tests of discriminant values
1918 -- that are formed as references to the entity V. At the end of
1919 -- scanning all the components, a suitable function is constructed
1920 -- in which V is the parameter.
1922 -----------------------
1923 -- Local Subprograms --
1924 -----------------------
1926 procedure Layout_Component_List
1929 RM_Siz_Expr
: out Node_Id
);
1930 -- Recursive procedure, called to lay out one component list Esiz
1931 -- and RM_Siz_Expr are set to the Object_Size and Value_Size values
1932 -- respectively representing the record size up to and including the
1933 -- last component in the component list (including any variants in
1934 -- this component list). RM_Siz_Expr is returned as an expression
1935 -- which may in the general case involve some references to the
1936 -- discriminants of the current record value, referenced by selecting
1937 -- from the entity V.
1939 ---------------------------
1940 -- Layout_Component_List --
1941 ---------------------------
1943 procedure Layout_Component_List
1946 RM_Siz_Expr
: out Node_Id
)
1948 Citems
: constant List_Id
:= Component_Items
(Clist
);
1949 Vpart
: constant Node_Id
:= Variant_Part
(Clist
);
1953 RMS_Ent
: Entity_Id
;
1956 if Is_Non_Empty_List
(Citems
) then
1958 (From
=> Defining_Identifier
(First
(Citems
)),
1959 To
=> Defining_Identifier
(Last
(Citems
)),
1963 Layout_Components
(Empty
, Empty
, Esiz
, RM_Siz
);
1966 -- Case where no variants are present in the component list
1970 -- The Esiz value has been correctly set by the call to
1971 -- Layout_Components, so there is nothing more to be done.
1973 -- For RM_Siz, we have an SO_Ref value, which we must convert
1974 -- to an appropriate expression.
1976 if Is_Static_SO_Ref
(RM_Siz
) then
1978 Make_Integer_Literal
(Loc
,
1982 RMS_Ent
:= Get_Dynamic_SO_Entity
(RM_Siz
);
1984 -- If the size is represented by a function, then we create
1985 -- an appropriate function call using V as the parameter to
1988 if Is_Discrim_SO_Function
(RMS_Ent
) then
1990 Make_Function_Call
(Loc
,
1991 Name
=> New_Occurrence_Of
(RMS_Ent
, Loc
),
1992 Parameter_Associations
=> New_List
(
1993 Make_Identifier
(Loc
, Chars
=> Vname
)));
1995 -- If the size is represented by a constant, then the
1996 -- expression we want is a reference to this constant
1999 RM_Siz_Expr
:= New_Occurrence_Of
(RMS_Ent
, Loc
);
2003 -- Case where variants are present in this component list
2013 D_Entity
: Entity_Id
;
2016 RM_Siz_Expr
:= Empty
;
2019 Var
:= Last
(Variants
(Vpart
));
2020 while Present
(Var
) loop
2022 Layout_Component_List
2023 (Component_List
(Var
), EsizV
, RM_SizV
);
2025 -- Set the Object_Size. If this is the first variant,
2026 -- we just set the size of this first variant.
2028 if Var
= Last
(Variants
(Vpart
)) then
2031 -- Otherwise the Object_Size is formed as a maximum
2032 -- of Esiz so far from previous variants, and the new
2033 -- Esiz value from the variant we just processed.
2035 -- If both values are static, we can just compute the
2036 -- maximum directly to save building junk nodes.
2038 elsif not Is_Dynamic_SO_Ref
(Esiz
)
2039 and then not Is_Dynamic_SO_Ref
(EsizV
)
2041 Esiz
:= UI_Max
(Esiz
, EsizV
);
2043 -- If either value is dynamic, then we have to generate
2044 -- an appropriate Standard_Unsigned'Max attribute call.
2045 -- If one of the values is static then it needs to be
2046 -- converted from bits to storage units to be compatible
2047 -- with the dynamic value.
2050 if Is_Static_SO_Ref
(Esiz
) then
2051 Esiz
:= (Esiz
+ SSU
- 1) / SSU
;
2054 if Is_Static_SO_Ref
(EsizV
) then
2055 EsizV
:= (EsizV
+ SSU
- 1) / SSU
;
2060 (Make_Attribute_Reference
(Loc
,
2061 Attribute_Name
=> Name_Max
,
2063 New_Occurrence_Of
(Standard_Unsigned
, Loc
),
2064 Expressions
=> New_List
(
2065 Expr_From_SO_Ref
(Loc
, Esiz
),
2066 Expr_From_SO_Ref
(Loc
, EsizV
))),
2071 -- Now deal with Value_Size (RM_Siz). We are aiming at
2072 -- an expression that looks like:
2074 -- if xxDx (V.disc) then rmsiz1
2075 -- else if xxDx (V.disc) then rmsiz2
2078 -- Where rmsiz1, rmsiz2... are the RM_Siz values for the
2079 -- individual variants, and xxDx are the discriminant
2080 -- checking functions generated for the variant type.
2082 -- If this is the first variant, we simply set the result
2083 -- as the expression. Note that this takes care of the
2086 if No
(RM_Siz_Expr
) then
2087 RM_Siz_Expr
:= Bits_To_SU
(RM_SizV
);
2089 -- Otherwise construct the appropriate test
2092 -- The test to be used in general is a call to the
2093 -- discriminant checking function. However, it is
2094 -- definitely worth special casing the very common
2095 -- case where a single value is involved.
2097 Dchoice
:= First
(Discrete_Choices
(Var
));
2099 if No
(Next
(Dchoice
))
2100 and then Nkind
(Dchoice
) /= N_Range
2102 -- Discriminant to be tested
2105 Make_Selected_Component
(Loc
,
2107 Make_Identifier
(Loc
, Chars
=> Vname
),
2110 (Entity
(Name
(Vpart
)), Loc
));
2114 Left_Opnd
=> Discrim
,
2115 Right_Opnd
=> New_Copy
(Dchoice
));
2117 -- Generate a call to the discriminant-checking
2118 -- function for the variant. Note that the result
2119 -- has to be complemented since the function returns
2120 -- False when the passed discriminant value matches.
2123 -- The checking function takes all of the type's
2124 -- discriminants as parameters, so a list of all
2125 -- the selected discriminants must be constructed.
2128 D_Entity
:= First_Discriminant
(E
);
2129 while Present
(D_Entity
) loop
2131 Make_Selected_Component
(Loc
,
2133 Make_Identifier
(Loc
, Chars
=> Vname
),
2139 D_Entity
:= Next_Discriminant
(D_Entity
);
2145 Make_Function_Call
(Loc
,
2148 (Dcheck_Function
(Var
), Loc
),
2149 Parameter_Associations
=>
2154 Make_Conditional_Expression
(Loc
,
2157 (Dtest
, Bits_To_SU
(RM_SizV
), RM_Siz_Expr
));
2164 end Layout_Component_List
;
2166 -- Start of processing for Layout_Variant_Record
2169 -- We need the discriminant checking functions, since we generate
2170 -- calls to these functions for the RM_Size expression, so make
2171 -- sure that these functions have been constructed in time.
2173 Build_Discr_Checking_Funcs
(Decl
);
2175 -- Lay out the discriminants
2177 First_Discr
:= First_Discriminant
(E
);
2178 Last_Discr
:= First_Discr
;
2179 while Present
(Next_Discriminant
(Last_Discr
)) loop
2180 Next_Discriminant
(Last_Discr
);
2184 (From
=> First_Discr
,
2189 -- Lay out the main component list (this will make recursive calls
2190 -- to lay out all component lists nested within variants).
2192 Layout_Component_List
(Component_List
(Tdef
), Esiz
, RM_Siz_Expr
);
2193 Set_Esize
(E
, Esiz
);
2195 -- If the RM_Size is a literal, set its value
2197 if Nkind
(RM_Siz_Expr
) = N_Integer_Literal
then
2198 Set_RM_Size
(E
, Intval
(RM_Siz_Expr
));
2200 -- Otherwise we construct a dynamic SO_Ref
2209 end Layout_Variant_Record
;
2211 -- Start of processing for Layout_Record_Type
2214 -- If this is a cloned subtype, just copy the size fields from the
2215 -- original, nothing else needs to be done in this case, since the
2216 -- components themselves are all shared.
2218 if (Ekind
(E
) = E_Record_Subtype
2220 Ekind
(E
) = E_Class_Wide_Subtype
)
2221 and then Present
(Cloned_Subtype
(E
))
2223 Set_Esize
(E
, Esize
(Cloned_Subtype
(E
)));
2224 Set_RM_Size
(E
, RM_Size
(Cloned_Subtype
(E
)));
2225 Set_Alignment
(E
, Alignment
(Cloned_Subtype
(E
)));
2227 -- Another special case, class-wide types. The RM says that the size
2228 -- of such types is implementation defined (RM 13.3(48)). What we do
2229 -- here is to leave the fields set as unknown values, and the backend
2230 -- determines the actual behavior.
2232 elsif Ekind
(E
) = E_Class_Wide_Type
then
2238 -- Initialize alignment conservatively to 1. This value will be
2239 -- increased as necessary during processing of the record.
2241 if Unknown_Alignment
(E
) then
2242 Set_Alignment
(E
, Uint_1
);
2245 -- Initialize previous component. This is Empty unless there are
2246 -- components which have already been laid out by component clauses.
2247 -- If there are such components, we start our lay out of the
2248 -- remaining components following the last such component.
2252 Comp
:= First_Component_Or_Discriminant
(E
);
2253 while Present
(Comp
) loop
2254 if Present
(Component_Clause
(Comp
)) then
2257 Component_Bit_Offset
(Comp
) >
2258 Component_Bit_Offset
(Prev_Comp
)
2264 Next_Component_Or_Discriminant
(Comp
);
2267 -- We have two separate circuits, one for non-variant records and
2268 -- one for variant records. For non-variant records, we simply go
2269 -- through the list of components. This handles all the non-variant
2270 -- cases including those cases of subtypes where there is no full
2271 -- type declaration, so the tree cannot be used to drive the layout.
2272 -- For variant records, we have to drive the layout from the tree
2273 -- since we need to understand the variant structure in this case.
2275 if Present
(Full_View
(E
)) then
2276 Decl
:= Declaration_Node
(Full_View
(E
));
2278 Decl
:= Declaration_Node
(E
);
2281 -- Scan all the components
2283 if Nkind
(Decl
) = N_Full_Type_Declaration
2284 and then Has_Discriminants
(E
)
2285 and then Nkind
(Type_Definition
(Decl
)) = N_Record_Definition
2286 and then Present
(Component_List
(Type_Definition
(Decl
)))
2288 Present
(Variant_Part
(Component_List
(Type_Definition
(Decl
))))
2290 Layout_Variant_Record
;
2292 Layout_Non_Variant_Record
;
2295 end Layout_Record_Type
;
2301 procedure Layout_Type
(E
: Entity_Id
) is
2302 Desig_Type
: Entity_Id
;
2305 -- For string literal types, for now, kill the size always, this is
2306 -- because gigi does not like or need the size to be set ???
2308 if Ekind
(E
) = E_String_Literal_Subtype
then
2309 Set_Esize
(E
, Uint_0
);
2310 Set_RM_Size
(E
, Uint_0
);
2314 -- For access types, set size/alignment. This is system address size,
2315 -- except for fat pointers (unconstrained array access types), where the
2316 -- size is two times the address size, to accommodate the two pointers
2317 -- that are required for a fat pointer (data and template). Note that
2318 -- E_Access_Protected_Subprogram_Type is not an access type for this
2319 -- purpose since it is not a pointer but is equivalent to a record. For
2320 -- access subtypes, copy the size from the base type since Gigi
2321 -- represents them the same way.
2323 if Is_Access_Type
(E
) then
2325 Desig_Type
:= Underlying_Type
(Designated_Type
(E
));
2327 -- If we only have a limited view of the type, see whether the
2328 -- non-limited view is available.
2330 if From_With_Type
(Designated_Type
(E
))
2331 and then Ekind
(Designated_Type
(E
)) = E_Incomplete_Type
2332 and then Present
(Non_Limited_View
(Designated_Type
(E
)))
2334 Desig_Type
:= Non_Limited_View
(Designated_Type
(E
));
2337 -- If Esize already set (e.g. by a size clause), then nothing further
2340 if Known_Esize
(E
) then
2343 -- Access to subprogram is a strange beast, and we let the backend
2344 -- figure out what is needed (it may be some kind of fat pointer,
2345 -- including the static link for example.
2347 elsif Is_Access_Protected_Subprogram_Type
(E
) then
2350 -- For access subtypes, copy the size information from base type
2352 elsif Ekind
(E
) = E_Access_Subtype
then
2353 Set_Size_Info
(E
, Base_Type
(E
));
2354 Set_RM_Size
(E
, RM_Size
(Base_Type
(E
)));
2356 -- For other access types, we use either address size, or, if a fat
2357 -- pointer is used (pointer-to-unconstrained array case), twice the
2358 -- address size to accommodate a fat pointer.
2360 elsif Present
(Desig_Type
)
2361 and then Is_Array_Type
(Desig_Type
)
2362 and then not Is_Constrained
(Desig_Type
)
2363 and then not Has_Completion_In_Body
(Desig_Type
)
2364 and then not Debug_Flag_6
2366 Init_Size
(E
, 2 * System_Address_Size
);
2368 -- Check for bad convention set
2370 if Warn_On_Export_Import
2372 (Convention
(E
) = Convention_C
2374 Convention
(E
) = Convention_CPP
)
2377 ("?this access type does not correspond to C pointer", E
);
2380 -- If the designated type is a limited view it is unanalyzed. We can
2381 -- examine the declaration itself to determine whether it will need a
2384 elsif Present
(Desig_Type
)
2385 and then Present
(Parent
(Desig_Type
))
2386 and then Nkind
(Parent
(Desig_Type
)) = N_Full_Type_Declaration
2388 Nkind
(Type_Definition
(Parent
(Desig_Type
)))
2389 = N_Unconstrained_Array_Definition
2391 Init_Size
(E
, 2 * System_Address_Size
);
2393 -- When the target is AAMP, access-to-subprogram types are fat
2394 -- pointers consisting of the subprogram address and a static link
2395 -- (with the exception of library-level access types, where a simple
2396 -- subprogram address is used).
2398 elsif AAMP_On_Target
2400 (Ekind
(E
) = E_Anonymous_Access_Subprogram_Type
2401 or else (Ekind
(E
) = E_Access_Subprogram_Type
2402 and then Present
(Enclosing_Subprogram
(E
))))
2404 Init_Size
(E
, 2 * System_Address_Size
);
2407 Init_Size
(E
, System_Address_Size
);
2410 -- On VMS, reset size to 32 for convention C access type if no
2411 -- explicit size clause is given and the default size is 64. Really
2412 -- we do not know the size, since depending on options for the VMS
2413 -- compiler, the size of a pointer type can be 32 or 64, but choosing
2414 -- 32 as the default improves compatibility with legacy VMS code.
2416 -- Note: we do not use Has_Size_Clause in the test below, because we
2417 -- want to catch the case of a derived type inheriting a size clause.
2418 -- We want to consider this to be an explicit size clause for this
2419 -- purpose, since it would be weird not to inherit the size in this
2422 -- We do NOT do this if we are in -gnatdm mode on a non-VMS target
2423 -- since in that case we want the normal pointer representation.
2425 if Opt
.True_VMS_Target
2426 and then (Convention
(E
) = Convention_C
2428 Convention
(E
) = Convention_CPP
)
2429 and then No
(Get_Attribute_Definition_Clause
(E
, Attribute_Size
))
2430 and then Esize
(E
) = 64
2435 Set_Elem_Alignment
(E
);
2437 -- Scalar types: set size and alignment
2439 elsif Is_Scalar_Type
(E
) then
2441 -- For discrete types, the RM_Size and Esize must be set already,
2442 -- since this is part of the earlier processing and the front end is
2443 -- always required to lay out the sizes of such types (since they are
2444 -- available as static attributes). All we do is to check that this
2445 -- rule is indeed obeyed!
2447 if Is_Discrete_Type
(E
) then
2449 -- If the RM_Size is not set, then here is where we set it
2451 -- Note: an RM_Size of zero looks like not set here, but this
2452 -- is a rare case, and we can simply reset it without any harm.
2454 if not Known_RM_Size
(E
) then
2455 Set_Discrete_RM_Size
(E
);
2458 -- If Esize for a discrete type is not set then set it
2460 if not Known_Esize
(E
) then
2466 -- If size is big enough, set it and exit
2468 if S
>= RM_Size
(E
) then
2472 -- If the RM_Size is greater than 64 (happens only when
2473 -- strange values are specified by the user, then Esize
2474 -- is simply a copy of RM_Size, it will be further
2475 -- refined later on)
2478 Set_Esize
(E
, RM_Size
(E
));
2481 -- Otherwise double possible size and keep trying
2490 -- For non-discrete scalar types, if the RM_Size is not set, then set
2491 -- it now to a copy of the Esize if the Esize is set.
2494 if Known_Esize
(E
) and then Unknown_RM_Size
(E
) then
2495 Set_RM_Size
(E
, Esize
(E
));
2499 Set_Elem_Alignment
(E
);
2501 -- Non-elementary (composite) types
2504 -- For packed arrays, take size and alignment values from the packed
2505 -- array type if a packed array type has been created and the fields
2506 -- are not currently set.
2508 if Is_Array_Type
(E
) and then Present
(Packed_Array_Type
(E
)) then
2510 PAT
: constant Entity_Id
:= Packed_Array_Type
(E
);
2513 if Unknown_Esize
(E
) then
2514 Set_Esize
(E
, Esize
(PAT
));
2517 if Unknown_RM_Size
(E
) then
2518 Set_RM_Size
(E
, RM_Size
(PAT
));
2521 if Unknown_Alignment
(E
) then
2522 Set_Alignment
(E
, Alignment
(PAT
));
2527 -- If RM_Size is known, set Esize if not known
2529 if Known_RM_Size
(E
) and then Unknown_Esize
(E
) then
2531 -- If the alignment is known, we bump the Esize up to the next
2532 -- alignment boundary if it is not already on one.
2534 if Known_Alignment
(E
) then
2536 A
: constant Uint
:= Alignment_In_Bits
(E
);
2537 S
: constant SO_Ref
:= RM_Size
(E
);
2539 Set_Esize
(E
, (S
+ A
- 1) / A
* A
);
2543 -- If Esize is set, and RM_Size is not, RM_Size is copied from Esize.
2544 -- At least for now this seems reasonable, and is in any case needed
2545 -- for compatibility with old versions of gigi.
2547 elsif Known_Esize
(E
) and then Unknown_RM_Size
(E
) then
2548 Set_RM_Size
(E
, Esize
(E
));
2551 -- For array base types, set component size if object size of the
2552 -- component type is known and is a small power of 2 (8, 16, 32, 64),
2553 -- since this is what will always be used.
2555 if Ekind
(E
) = E_Array_Type
2556 and then Unknown_Component_Size
(E
)
2559 CT
: constant Entity_Id
:= Component_Type
(E
);
2562 -- For some reasons, access types can cause trouble, So let's
2563 -- just do this for scalar types ???
2566 and then Is_Scalar_Type
(CT
)
2567 and then Known_Static_Esize
(CT
)
2570 S
: constant Uint
:= Esize
(CT
);
2578 Set_Component_Size
(E
, Esize
(CT
));
2586 -- Lay out array and record types if front end layout set
2588 if Frontend_Layout_On_Target
then
2589 if Is_Array_Type
(E
) and then not Is_Bit_Packed_Array
(E
) then
2590 Layout_Array_Type
(E
);
2591 elsif Is_Record_Type
(E
) then
2592 Layout_Record_Type
(E
);
2595 -- Case of backend layout, we still do a little in the front end
2598 -- Processing for record types
2600 if Is_Record_Type
(E
) then
2602 -- Special remaining processing for record types with a known
2603 -- size of 16, 32, or 64 bits whose alignment is not yet set.
2604 -- For these types, we set a corresponding alignment matching
2605 -- the size if possible, or as large as possible if not.
2607 if Convention
(E
) = Convention_Ada
2608 and then not Debug_Flag_Q
2610 Set_Composite_Alignment
(E
);
2613 -- Processing for array types
2615 elsif Is_Array_Type
(E
) then
2617 -- For arrays that are required to be atomic, we do the same
2618 -- processing as described above for short records, since we
2619 -- really need to have the alignment set for the whole array.
2621 if Is_Atomic
(E
) and then not Debug_Flag_Q
then
2622 Set_Composite_Alignment
(E
);
2625 -- For unpacked array types, set an alignment of 1 if we know
2626 -- that the component alignment is not greater than 1. The reason
2627 -- we do this is to avoid unnecessary copying of slices of such
2628 -- arrays when passed to subprogram parameters (see special test
2629 -- in Exp_Ch6.Expand_Actuals).
2631 if not Is_Packed
(E
)
2632 and then Unknown_Alignment
(E
)
2634 if Known_Static_Component_Size
(E
)
2635 and then Component_Size
(E
) = 1
2637 Set_Alignment
(E
, Uint_1
);
2643 -- Final step is to check that Esize and RM_Size are compatible
2645 if Known_Static_Esize
(E
) and then Known_Static_RM_Size
(E
) then
2646 if Esize
(E
) < RM_Size
(E
) then
2648 -- Esize is less than RM_Size. That's not good. First we test
2649 -- whether this was set deliberately with an Object_Size clause
2650 -- and if so, object to the clause.
2652 if Has_Object_Size_Clause
(E
) then
2653 Error_Msg_Uint_1
:= RM_Size
(E
);
2655 ("object size is too small, minimum allowed is ^",
2656 Expression
(Get_Attribute_Definition_Clause
2657 (E
, Attribute_Object_Size
)));
2660 -- Adjust Esize up to RM_Size value
2663 Size
: constant Uint
:= RM_Size
(E
);
2666 Set_Esize
(E
, RM_Size
(E
));
2668 -- For scalar types, increase Object_Size to power of 2, but
2669 -- not less than a storage unit in any case (i.e., normally
2670 -- this means it will be storage-unit addressable).
2672 if Is_Scalar_Type
(E
) then
2673 if Size
<= System_Storage_Unit
then
2674 Init_Esize
(E
, System_Storage_Unit
);
2675 elsif Size
<= 16 then
2677 elsif Size
<= 32 then
2680 Set_Esize
(E
, (Size
+ 63) / 64 * 64);
2683 -- Finally, make sure that alignment is consistent with
2684 -- the newly assigned size.
2686 while Alignment
(E
) * System_Storage_Unit
< Esize
(E
)
2687 and then Alignment
(E
) < Maximum_Alignment
2689 Set_Alignment
(E
, 2 * Alignment
(E
));
2697 ---------------------
2698 -- Rewrite_Integer --
2699 ---------------------
2701 procedure Rewrite_Integer
(N
: Node_Id
; V
: Uint
) is
2702 Loc
: constant Source_Ptr
:= Sloc
(N
);
2703 Typ
: constant Entity_Id
:= Etype
(N
);
2705 Rewrite
(N
, Make_Integer_Literal
(Loc
, Intval
=> V
));
2707 end Rewrite_Integer
;
2709 -------------------------------
2710 -- Set_And_Check_Static_Size --
2711 -------------------------------
2713 procedure Set_And_Check_Static_Size
2720 procedure Check_Size_Too_Small
(Spec
: Uint
; Min
: Uint
);
2721 -- Spec is the number of bit specified in the size clause, and Min is
2722 -- the minimum computed size. An error is given that the specified size
2723 -- is too small if Spec < Min, and in this case both Esize and RM_Size
2724 -- are set to unknown in E. The error message is posted on node SC.
2726 procedure Check_Unused_Bits
(Spec
: Uint
; Max
: Uint
);
2727 -- Spec is the number of bits specified in the size clause, and Max is
2728 -- the maximum computed size. A warning is given about unused bits if
2729 -- Spec > Max. This warning is posted on node SC.
2731 --------------------------
2732 -- Check_Size_Too_Small --
2733 --------------------------
2735 procedure Check_Size_Too_Small
(Spec
: Uint
; Min
: Uint
) is
2738 Error_Msg_Uint_1
:= Min
;
2739 Error_Msg_NE
("size for & too small, minimum allowed is ^", SC
, E
);
2743 end Check_Size_Too_Small
;
2745 -----------------------
2746 -- Check_Unused_Bits --
2747 -----------------------
2749 procedure Check_Unused_Bits
(Spec
: Uint
; Max
: Uint
) is
2752 Error_Msg_Uint_1
:= Spec
- Max
;
2753 Error_Msg_NE
("?^ bits of & unused", SC
, E
);
2755 end Check_Unused_Bits
;
2757 -- Start of processing for Set_And_Check_Static_Size
2760 -- Case where Object_Size (Esize) is already set by a size clause
2762 if Known_Static_Esize
(E
) then
2763 SC
:= Size_Clause
(E
);
2766 SC
:= Get_Attribute_Definition_Clause
(E
, Attribute_Object_Size
);
2769 -- Perform checks on specified size against computed sizes
2771 if Present
(SC
) then
2772 Check_Unused_Bits
(Esize
(E
), Esiz
);
2773 Check_Size_Too_Small
(Esize
(E
), RM_Siz
);
2777 -- Case where Value_Size (RM_Size) is set by specific Value_Size clause
2778 -- (we do not need to worry about Value_Size being set by a Size clause,
2779 -- since that will have set Esize as well, and we already took care of
2782 if Known_Static_RM_Size
(E
) then
2783 SC
:= Get_Attribute_Definition_Clause
(E
, Attribute_Value_Size
);
2785 -- Perform checks on specified size against computed sizes
2787 if Present
(SC
) then
2788 Check_Unused_Bits
(RM_Size
(E
), Esiz
);
2789 Check_Size_Too_Small
(RM_Size
(E
), RM_Siz
);
2793 -- Set sizes if unknown
2795 if Unknown_Esize
(E
) then
2796 Set_Esize
(E
, Esiz
);
2799 if Unknown_RM_Size
(E
) then
2800 Set_RM_Size
(E
, RM_Siz
);
2802 end Set_And_Check_Static_Size
;
2804 -----------------------------
2805 -- Set_Composite_Alignment --
2806 -----------------------------
2808 procedure Set_Composite_Alignment
(E
: Entity_Id
) is
2813 -- If alignment is already set, then nothing to do
2815 if Known_Alignment
(E
) then
2819 -- Alignment is not known, see if we can set it, taking into account
2820 -- the setting of the Optimize_Alignment mode.
2822 -- If Optimize_Alignment is set to Space, then packed records always
2823 -- have an alignment of 1. But don't do anything for atomic records
2824 -- since we may need higher alignment for indivisible access.
2826 if Optimize_Alignment_Space
(E
)
2827 and then Is_Record_Type
(E
)
2828 and then Is_Packed
(E
)
2829 and then not Is_Atomic
(E
)
2833 -- Not a record, or not packed
2836 -- The only other cases we worry about here are where the size is
2837 -- statically known at compile time.
2839 if Known_Static_Esize
(E
) then
2842 elsif Unknown_Esize
(E
)
2843 and then Known_Static_RM_Size
(E
)
2851 -- Size is known, alignment is not set
2853 -- Reset alignment to match size if the known size is exactly 2, 4,
2854 -- or 8 storage units.
2856 if Siz
= 2 * System_Storage_Unit
then
2858 elsif Siz
= 4 * System_Storage_Unit
then
2860 elsif Siz
= 8 * System_Storage_Unit
then
2863 -- If Optimize_Alignment is set to Space, then make sure the
2864 -- alignment matches the size, for example, if the size is 17
2865 -- bytes then we want an alignment of 1 for the type.
2867 elsif Optimize_Alignment_Space
(E
) then
2868 if Siz
mod (8 * System_Storage_Unit
) = 0 then
2870 elsif Siz
mod (4 * System_Storage_Unit
) = 0 then
2872 elsif Siz
mod (2 * System_Storage_Unit
) = 0 then
2878 -- If Optimize_Alignment is set to Time, then we reset for odd
2879 -- "in between sizes", for example a 17 bit record is given an
2880 -- alignment of 4. Note that this matches the old VMS behavior
2881 -- in versions of GNAT prior to 6.1.1.
2883 elsif Optimize_Alignment_Time
(E
)
2884 and then Siz
> System_Storage_Unit
2885 and then Siz
<= 8 * System_Storage_Unit
2887 if Siz
<= 2 * System_Storage_Unit
then
2889 elsif Siz
<= 4 * System_Storage_Unit
then
2891 else -- Siz <= 8 * System_Storage_Unit then
2895 -- No special alignment fiddling needed
2902 -- Here we have Set Align to the proposed improved value. Make sure the
2903 -- value set does not exceed Maximum_Alignment for the target.
2905 if Align
> Maximum_Alignment
then
2906 Align
:= Maximum_Alignment
;
2909 -- Further processing for record types only to reduce the alignment
2910 -- set by the above processing in some specific cases. We do not
2911 -- do this for atomic records, since we need max alignment there,
2913 if Is_Record_Type
(E
) and then not Is_Atomic
(E
) then
2915 -- For records, there is generally no point in setting alignment
2916 -- higher than word size since we cannot do better than move by
2917 -- words in any case. Omit this if we are optimizing for time,
2918 -- since conceivably we may be able to do better.
2920 if Align
> System_Word_Size
/ System_Storage_Unit
2921 and then not Optimize_Alignment_Time
(E
)
2923 Align
:= System_Word_Size
/ System_Storage_Unit
;
2926 -- Check components. If any component requires a higher alignment,
2927 -- then we set that higher alignment in any case. Don't do this if
2928 -- we have Optimize_Alignment set to Space. Note that that covers
2929 -- the case of packed records, where we already set alignment to 1.
2931 if not Optimize_Alignment_Space
(E
) then
2936 Comp
:= First_Component
(E
);
2937 while Present
(Comp
) loop
2938 if Known_Alignment
(Etype
(Comp
)) then
2940 Calign
: constant Uint
:= Alignment
(Etype
(Comp
));
2943 -- The cases to process are when the alignment of the
2944 -- component type is larger than the alignment we have
2945 -- so far, and either there is no component clause for
2946 -- the component, or the length set by the component
2947 -- clause matches the length of the component type.
2951 (Unknown_Esize
(Comp
)
2952 or else (Known_Static_Esize
(Comp
)
2955 Calign
* System_Storage_Unit
))
2957 Align
:= UI_To_Int
(Calign
);
2962 Next_Component
(Comp
);
2968 -- Set chosen alignment, and increase Esize if necessary to match the
2969 -- chosen alignment.
2971 Set_Alignment
(E
, UI_From_Int
(Align
));
2973 if Known_Static_Esize
(E
)
2974 and then Esize
(E
) < Align
* System_Storage_Unit
2976 Set_Esize
(E
, UI_From_Int
(Align
* System_Storage_Unit
));
2978 end Set_Composite_Alignment
;
2980 --------------------------
2981 -- Set_Discrete_RM_Size --
2982 --------------------------
2984 procedure Set_Discrete_RM_Size
(Def_Id
: Entity_Id
) is
2985 FST
: constant Entity_Id
:= First_Subtype
(Def_Id
);
2988 -- All discrete types except for the base types in standard are
2989 -- constrained, so indicate this by setting Is_Constrained.
2991 Set_Is_Constrained
(Def_Id
);
2993 -- Set generic types to have an unknown size, since the representation
2994 -- of a generic type is irrelevant, in view of the fact that they have
2995 -- nothing to do with code.
2997 if Is_Generic_Type
(Root_Type
(FST
)) then
2998 Set_RM_Size
(Def_Id
, Uint_0
);
3000 -- If the subtype statically matches the first subtype, then it is
3001 -- required to have exactly the same layout. This is required by
3002 -- aliasing considerations.
3004 elsif Def_Id
/= FST
and then
3005 Subtypes_Statically_Match
(Def_Id
, FST
)
3007 Set_RM_Size
(Def_Id
, RM_Size
(FST
));
3008 Set_Size_Info
(Def_Id
, FST
);
3010 -- In all other cases the RM_Size is set to the minimum size. Note that
3011 -- this routine is never called for subtypes for which the RM_Size is
3012 -- set explicitly by an attribute clause.
3015 Set_RM_Size
(Def_Id
, UI_From_Int
(Minimum_Size
(Def_Id
)));
3017 end Set_Discrete_RM_Size
;
3019 ------------------------
3020 -- Set_Elem_Alignment --
3021 ------------------------
3023 procedure Set_Elem_Alignment
(E
: Entity_Id
) is
3025 -- Do not set alignment for packed array types, unless we are doing
3026 -- front end layout, because otherwise this is always handled in the
3029 if Is_Packed_Array_Type
(E
) and then not Frontend_Layout_On_Target
then
3032 -- If there is an alignment clause, then we respect it
3034 elsif Has_Alignment_Clause
(E
) then
3037 -- If the size is not set, then don't attempt to set the alignment. This
3038 -- happens in the backend layout case for access-to-subprogram types.
3040 elsif not Known_Static_Esize
(E
) then
3043 -- For access types, do not set the alignment if the size is less than
3044 -- the allowed minimum size. This avoids cascaded error messages.
3046 elsif Is_Access_Type
(E
)
3047 and then Esize
(E
) < System_Address_Size
3052 -- Here we calculate the alignment as the largest power of two multiple
3053 -- of System.Storage_Unit that does not exceed either the actual size of
3054 -- the type, or the maximum allowed alignment.
3057 S
: constant Int
:= UI_To_Int
(Esize
(E
)) / SSU
;
3059 Max_Alignment
: Nat
;
3062 -- If the default alignment of "double" floating-point types is
3063 -- specifically capped, enforce the cap.
3065 if Ttypes
.Target_Double_Float_Alignment
> 0
3067 and then Is_Floating_Point_Type
(E
)
3069 Max_Alignment
:= Ttypes
.Target_Double_Float_Alignment
;
3071 -- If the default alignment of "double" or larger scalar types is
3072 -- specifically capped, enforce the cap.
3074 elsif Ttypes
.Target_Double_Scalar_Alignment
> 0
3076 and then Is_Scalar_Type
(E
)
3078 Max_Alignment
:= Ttypes
.Target_Double_Scalar_Alignment
;
3080 -- Otherwise enforce the overall alignment cap
3083 Max_Alignment
:= Ttypes
.Maximum_Alignment
;
3087 while 2 * A
<= Max_Alignment
and then 2 * A
<= S
loop
3091 -- Now we think we should set the alignment to A, but we skip this if
3092 -- an alignment is already set to a value greater than A (happens for
3095 -- However, if the alignment is known and too small it must be
3096 -- increased, this happens in a case like:
3098 -- type R is new Character;
3099 -- for R'Size use 16;
3101 -- Here the alignment inherited from Character is 1, but it must be
3102 -- increased to 2 to reflect the increased size.
3104 if Unknown_Alignment
(E
) or else Alignment
(E
) < A
then
3105 Init_Alignment
(E
, A
);
3108 end Set_Elem_Alignment
;
3110 ----------------------
3111 -- SO_Ref_From_Expr --
3112 ----------------------
3114 function SO_Ref_From_Expr
3116 Ins_Type
: Entity_Id
;
3117 Vtype
: Entity_Id
:= Empty
;
3118 Make_Func
: Boolean := False) return Dynamic_SO_Ref
3120 Loc
: constant Source_Ptr
:= Sloc
(Ins_Type
);
3121 K
: constant Entity_Id
:= Make_Temporary
(Loc
, 'K');
3124 Vtype_Primary_View
: Entity_Id
;
3126 function Check_Node_V_Ref
(N
: Node_Id
) return Traverse_Result
;
3127 -- Function used to check one node for reference to V
3129 function Has_V_Ref
is new Traverse_Func
(Check_Node_V_Ref
);
3130 -- Function used to traverse tree to check for reference to V
3132 ----------------------
3133 -- Check_Node_V_Ref --
3134 ----------------------
3136 function Check_Node_V_Ref
(N
: Node_Id
) return Traverse_Result
is
3138 if Nkind
(N
) = N_Identifier
then
3139 if Chars
(N
) = Vname
then
3148 end Check_Node_V_Ref
;
3150 -- Start of processing for SO_Ref_From_Expr
3153 -- Case of expression is an integer literal, in this case we just
3154 -- return the value (which must always be non-negative, since size
3155 -- and offset values can never be negative).
3157 if Nkind
(Expr
) = N_Integer_Literal
then
3158 pragma Assert
(Intval
(Expr
) >= 0);
3159 return Intval
(Expr
);
3162 -- Case where there is a reference to V, create function
3164 if Has_V_Ref
(Expr
) = Abandon
then
3166 pragma Assert
(Present
(Vtype
));
3168 -- Check whether Vtype is a view of a private type and ensure that
3169 -- we use the primary view of the type (which is denoted by its
3170 -- Etype, whether it's the type's partial or full view entity).
3171 -- This is needed to make sure that we use the same (primary) view
3172 -- of the type for all V formals, whether the current view of the
3173 -- type is the partial or full view, so that types will always
3174 -- match on calls from one size function to another.
3176 if Has_Private_Declaration
(Vtype
) then
3177 Vtype_Primary_View
:= Etype
(Vtype
);
3179 Vtype_Primary_View
:= Vtype
;
3182 Set_Is_Discrim_SO_Function
(K
);
3185 Make_Subprogram_Body
(Loc
,
3188 Make_Function_Specification
(Loc
,
3189 Defining_Unit_Name
=> K
,
3190 Parameter_Specifications
=> New_List
(
3191 Make_Parameter_Specification
(Loc
,
3192 Defining_Identifier
=>
3193 Make_Defining_Identifier
(Loc
, Chars
=> Vname
),
3195 New_Occurrence_Of
(Vtype_Primary_View
, Loc
))),
3196 Result_Definition
=>
3197 New_Occurrence_Of
(Standard_Unsigned
, Loc
)),
3199 Declarations
=> Empty_List
,
3201 Handled_Statement_Sequence
=>
3202 Make_Handled_Sequence_Of_Statements
(Loc
,
3203 Statements
=> New_List
(
3204 Make_Simple_Return_Statement
(Loc
,
3205 Expression
=> Expr
))));
3207 -- The caller requests that the expression be encapsulated in a
3208 -- parameterless function.
3210 elsif Make_Func
then
3212 Make_Subprogram_Body
(Loc
,
3215 Make_Function_Specification
(Loc
,
3216 Defining_Unit_Name
=> K
,
3217 Parameter_Specifications
=> Empty_List
,
3218 Result_Definition
=>
3219 New_Occurrence_Of
(Standard_Unsigned
, Loc
)),
3221 Declarations
=> Empty_List
,
3223 Handled_Statement_Sequence
=>
3224 Make_Handled_Sequence_Of_Statements
(Loc
,
3225 Statements
=> New_List
(
3226 Make_Simple_Return_Statement
(Loc
, Expression
=> Expr
))));
3228 -- No reference to V and function not requested, so create a constant
3232 Make_Object_Declaration
(Loc
,
3233 Defining_Identifier
=> K
,
3234 Object_Definition
=>
3235 New_Occurrence_Of
(Standard_Unsigned
, Loc
),
3236 Constant_Present
=> True,
3237 Expression
=> Expr
);
3240 Append_Freeze_Action
(Ins_Type
, Decl
);
3242 return Create_Dynamic_SO_Ref
(K
);
3243 end SO_Ref_From_Expr
;