1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 2001-2005 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 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. --
22 -- GNAT was originally developed by the GNAT team at New York University. --
23 -- Extensive contributions were provided by Ada Core Technologies Inc. --
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
;
37 with Repinfo
; use Repinfo
;
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
64 -- function xxx (V : vtyp) return Unsigned is
66 -- return ... expression involving V.discrim
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.
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
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
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 bytes.
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
122 Comp
: Entity_Id
:= Empty
)
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
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
157 function Get_Max_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
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
194 ----------------------------
195 -- Adjust_Esize_Alignment --
196 ----------------------------
198 procedure Adjust_Esize_Alignment
(E
: Entity_Id
) is
203 -- Nothing to do if size unknown
205 if Unknown_Esize
(E
) then
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
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)
217 Esize_Set
:= Has_Object_Size_Clause
(E
);
219 -- For an object, the issue is whether a size clause is present
222 Esize_Set
:= Has_Size_Clause
(E
);
225 -- If size is known it must be a multiple of the byte size
227 if Esize
(E
) mod SSU
/= 0 then
229 -- If not, and size specified, then give error
233 ("size for& not a multiple of byte size", Size_Clause
(E
), E
);
236 -- Otherwise bump up size to a byte boundary
239 Set_Esize
(E
, (Esize
(E
) + SSU
- 1) / SSU
* SSU
);
243 -- Now we have the size set, it must be a multiple of the alignment
244 -- nothing more we can do here if the alignment is unknown here.
246 if Unknown_Alignment
(E
) then
250 -- At this point both the Esize and Alignment are known, so we need
251 -- to make sure they are consistent.
253 Abits
:= UI_To_Int
(Alignment
(E
)) * SSU
;
255 if Esize
(E
) mod Abits
= 0 then
259 -- Here we have a situation where the Esize is not a multiple of
260 -- the alignment. We must either increase Esize or reduce the
261 -- alignment to correct this situation.
263 -- The case in which we can decrease the alignment is where the
264 -- alignment was not set by an alignment clause, and the type in
265 -- question is a discrete type, where it is definitely safe to
266 -- reduce the alignment. For example:
268 -- t : integer range 1 .. 2;
271 -- In this situation, the initial alignment of t is 4, copied from
272 -- the Integer base type, but it is safe to reduce it to 1 at this
273 -- stage, since we will only be loading a single byte.
275 if Is_Discrete_Type
(Etype
(E
))
276 and then not Has_Alignment_Clause
(E
)
280 exit when Esize
(E
) mod Abits
= 0;
283 Init_Alignment
(E
, Abits
/ SSU
);
287 -- Now the only possible approach left is to increase the Esize
288 -- but we can't do that if the size was set by a specific clause.
292 ("size for& is not a multiple of alignment",
295 -- Otherwise we can indeed increase the size to a multiple of alignment
298 Set_Esize
(E
, ((Esize
(E
) + (Abits
- 1)) / Abits
) * Abits
);
300 end Adjust_Esize_Alignment
;
309 Right_Opnd
: Node_Id
)
316 -- Case of right operand is a constant
318 if Compile_Time_Known_Value
(Right_Opnd
) then
320 R
:= Expr_Value
(Right_Opnd
);
322 -- Case of left operand is a constant
324 elsif Compile_Time_Known_Value
(Left_Opnd
) then
326 R
:= Expr_Value
(Left_Opnd
);
328 -- Neither operand is a constant, do the addition with no optimization
331 return Make_Op_Add
(Loc
, Left_Opnd
, Right_Opnd
);
334 -- Case of left operand is an addition
336 if Nkind
(L
) = N_Op_Add
then
338 -- (C1 + E) + C2 = (C1 + C2) + E
340 if Compile_Time_Known_Value
(Sinfo
.Left_Opnd
(L
)) then
342 (Sinfo
.Left_Opnd
(L
),
343 Expr_Value
(Sinfo
.Left_Opnd
(L
)) + R
);
346 -- (E + C1) + C2 = E + (C1 + C2)
348 elsif Compile_Time_Known_Value
(Sinfo
.Right_Opnd
(L
)) then
350 (Sinfo
.Right_Opnd
(L
),
351 Expr_Value
(Sinfo
.Right_Opnd
(L
)) + R
);
355 -- Case of left operand is a subtraction
357 elsif Nkind
(L
) = N_Op_Subtract
then
359 -- (C1 - E) + C2 = (C1 + C2) + E
361 if Compile_Time_Known_Value
(Sinfo
.Left_Opnd
(L
)) then
363 (Sinfo
.Left_Opnd
(L
),
364 Expr_Value
(Sinfo
.Left_Opnd
(L
)) + R
);
367 -- (E - C1) + C2 = E - (C1 - C2)
369 elsif Compile_Time_Known_Value
(Sinfo
.Right_Opnd
(L
)) then
371 (Sinfo
.Right_Opnd
(L
),
372 Expr_Value
(Sinfo
.Right_Opnd
(L
)) - R
);
377 -- Not optimizable, do the addition
379 return Make_Op_Add
(Loc
, Left_Opnd
, Right_Opnd
);
386 function Assoc_Multiply
389 Right_Opnd
: Node_Id
)
396 -- Case of right operand is a constant
398 if Compile_Time_Known_Value
(Right_Opnd
) then
400 R
:= Expr_Value
(Right_Opnd
);
402 -- Case of left operand is a constant
404 elsif Compile_Time_Known_Value
(Left_Opnd
) then
406 R
:= Expr_Value
(Left_Opnd
);
408 -- Neither operand is a constant, do the multiply with no optimization
411 return Make_Op_Multiply
(Loc
, Left_Opnd
, Right_Opnd
);
414 -- Case of left operand is an multiplication
416 if Nkind
(L
) = N_Op_Multiply
then
418 -- (C1 * E) * C2 = (C1 * C2) + E
420 if Compile_Time_Known_Value
(Sinfo
.Left_Opnd
(L
)) then
422 (Sinfo
.Left_Opnd
(L
),
423 Expr_Value
(Sinfo
.Left_Opnd
(L
)) * R
);
426 -- (E * C1) * C2 = E * (C1 * C2)
428 elsif Compile_Time_Known_Value
(Sinfo
.Right_Opnd
(L
)) then
430 (Sinfo
.Right_Opnd
(L
),
431 Expr_Value
(Sinfo
.Right_Opnd
(L
)) * R
);
436 -- Not optimizable, do the multiplication
438 return Make_Op_Multiply
(Loc
, Left_Opnd
, Right_Opnd
);
445 function Assoc_Subtract
448 Right_Opnd
: Node_Id
)
455 -- Case of right operand is a constant
457 if Compile_Time_Known_Value
(Right_Opnd
) then
459 R
:= Expr_Value
(Right_Opnd
);
461 -- Right operand is a constant, do the subtract with no optimization
464 return Make_Op_Subtract
(Loc
, Left_Opnd
, Right_Opnd
);
467 -- Case of left operand is an addition
469 if Nkind
(L
) = N_Op_Add
then
471 -- (C1 + E) - C2 = (C1 - C2) + E
473 if Compile_Time_Known_Value
(Sinfo
.Left_Opnd
(L
)) then
475 (Sinfo
.Left_Opnd
(L
),
476 Expr_Value
(Sinfo
.Left_Opnd
(L
)) - R
);
479 -- (E + C1) - C2 = E + (C1 - C2)
481 elsif Compile_Time_Known_Value
(Sinfo
.Right_Opnd
(L
)) then
483 (Sinfo
.Right_Opnd
(L
),
484 Expr_Value
(Sinfo
.Right_Opnd
(L
)) - R
);
488 -- Case of left operand is a subtraction
490 elsif Nkind
(L
) = N_Op_Subtract
then
492 -- (C1 - E) - C2 = (C1 - C2) + E
494 if Compile_Time_Known_Value
(Sinfo
.Left_Opnd
(L
)) then
496 (Sinfo
.Left_Opnd
(L
),
497 Expr_Value
(Sinfo
.Left_Opnd
(L
)) + R
);
500 -- (E - C1) - C2 = E - (C1 + C2)
502 elsif Compile_Time_Known_Value
(Sinfo
.Right_Opnd
(L
)) then
504 (Sinfo
.Right_Opnd
(L
),
505 Expr_Value
(Sinfo
.Right_Opnd
(L
)) + R
);
510 -- Not optimizable, do the subtraction
512 return Make_Op_Subtract
(Loc
, Left_Opnd
, Right_Opnd
);
519 function Bits_To_SU
(N
: Node_Id
) return Node_Id
is
521 if Nkind
(N
) = N_Integer_Literal
then
522 Set_Intval
(N
, (Intval
(N
) + (SSU
- 1)) / SSU
);
532 function Compute_Length
(Lo
: Node_Id
; Hi
: Node_Id
) return Node_Id
is
533 Loc
: constant Source_Ptr
:= Sloc
(Lo
);
534 Typ
: constant Entity_Id
:= Etype
(Lo
);
541 -- If the bounds are First and Last attributes for the same dimension
542 -- and both have prefixes that denotes the same entity, then we create
543 -- and return a Length attribute. This may allow the back end to
544 -- generate better code in cases where it already has the length.
546 if Nkind
(Lo
) = N_Attribute_Reference
547 and then Attribute_Name
(Lo
) = Name_First
548 and then Nkind
(Hi
) = N_Attribute_Reference
549 and then Attribute_Name
(Hi
) = Name_Last
550 and then Is_Entity_Name
(Prefix
(Lo
))
551 and then Is_Entity_Name
(Prefix
(Hi
))
552 and then Entity
(Prefix
(Lo
)) = Entity
(Prefix
(Hi
))
557 if Present
(First
(Expressions
(Lo
))) then
558 Lo_Dim
:= Expr_Value
(First
(Expressions
(Lo
)));
561 if Present
(First
(Expressions
(Hi
))) then
562 Hi_Dim
:= Expr_Value
(First
(Expressions
(Hi
)));
565 if Lo_Dim
= Hi_Dim
then
567 Make_Attribute_Reference
(Loc
,
568 Prefix
=> New_Occurrence_Of
569 (Entity
(Prefix
(Lo
)), Loc
),
570 Attribute_Name
=> Name_Length
,
571 Expressions
=> New_List
572 (Make_Integer_Literal
(Loc
, Lo_Dim
)));
576 Lo_Op
:= New_Copy_Tree
(Lo
);
577 Hi_Op
:= New_Copy_Tree
(Hi
);
579 -- If type is enumeration type, then use Pos attribute to convert
580 -- to integer type for which subtraction is a permitted operation.
582 if Is_Enumeration_Type
(Typ
) then
584 Make_Attribute_Reference
(Loc
,
585 Prefix
=> New_Occurrence_Of
(Typ
, Loc
),
586 Attribute_Name
=> Name_Pos
,
587 Expressions
=> New_List
(Lo_Op
));
590 Make_Attribute_Reference
(Loc
,
591 Prefix
=> New_Occurrence_Of
(Typ
, Loc
),
592 Attribute_Name
=> Name_Pos
,
593 Expressions
=> New_List
(Hi_Op
));
601 Right_Opnd
=> Lo_Op
),
602 Right_Opnd
=> Make_Integer_Literal
(Loc
, 1));
605 ----------------------
606 -- Expr_From_SO_Ref --
607 ----------------------
609 function Expr_From_SO_Ref
612 Comp
: Entity_Id
:= Empty
)
618 if Is_Dynamic_SO_Ref
(D
) then
619 Ent
:= Get_Dynamic_SO_Entity
(D
);
621 if Is_Discrim_SO_Function
(Ent
) then
622 -- If a component is passed in whose type matches the type
623 -- of the function formal, then select that component from
624 -- the "V" parameter rather than passing "V" directly.
627 and then Base_Type
(Etype
(Comp
))
628 = Base_Type
(Etype
(First_Formal
(Ent
)))
631 Make_Function_Call
(Loc
,
632 Name
=> New_Occurrence_Of
(Ent
, Loc
),
633 Parameter_Associations
=> New_List
(
634 Make_Selected_Component
(Loc
,
635 Prefix
=> Make_Identifier
(Loc
, Chars
=> Vname
),
636 Selector_Name
=> New_Occurrence_Of
(Comp
, Loc
))));
640 Make_Function_Call
(Loc
,
641 Name
=> New_Occurrence_Of
(Ent
, Loc
),
642 Parameter_Associations
=> New_List
(
643 Make_Identifier
(Loc
, Chars
=> Vname
)));
647 return New_Occurrence_Of
(Ent
, Loc
);
651 return Make_Integer_Literal
(Loc
, D
);
653 end Expr_From_SO_Ref
;
659 function Get_Max_Size
(E
: Entity_Id
) return Node_Id
is
660 Loc
: constant Source_Ptr
:= Sloc
(E
);
668 type Val_Status_Type
is (Const
, Dynamic
);
670 type Val_Type
(Status
: Val_Status_Type
:= Const
) is
673 when Const
=> Val
: Uint
;
674 when Dynamic
=> Nod
: Node_Id
;
677 -- Shows the status of the value so far. Const means that the value
678 -- is constant, and Val is the current constant value. Dynamic means
679 -- that the value is dynamic, and in this case Nod is the Node_Id of
680 -- the expression to compute the value.
683 -- Calculated value so far if Size.Status = Const,
684 -- or expression value so far if Size.Status = Dynamic.
686 SU_Convert_Required
: Boolean := False;
687 -- This is set to True if the final result must be converted from
688 -- bits to storage units (rounding up to a storage unit boundary).
690 -----------------------
691 -- Local Subprograms --
692 -----------------------
694 procedure Max_Discrim
(N
: in out Node_Id
);
695 -- If the node N represents a discriminant, replace it by the maximum
696 -- value of the discriminant.
698 procedure Min_Discrim
(N
: in out Node_Id
);
699 -- If the node N represents a discriminant, replace it by the minimum
700 -- value of the discriminant.
706 procedure Max_Discrim
(N
: in out Node_Id
) is
708 if Nkind
(N
) = N_Identifier
709 and then Ekind
(Entity
(N
)) = E_Discriminant
711 N
:= Type_High_Bound
(Etype
(N
));
719 procedure Min_Discrim
(N
: in out Node_Id
) is
721 if Nkind
(N
) = N_Identifier
722 and then Ekind
(Entity
(N
)) = E_Discriminant
724 N
:= Type_Low_Bound
(Etype
(N
));
728 -- Start of processing for Get_Max_Size
731 pragma Assert
(Size_Depends_On_Discriminant
(E
));
733 -- Initialize status from component size
735 if Known_Static_Component_Size
(E
) then
736 Size
:= (Const
, Component_Size
(E
));
739 Size
:= (Dynamic
, Expr_From_SO_Ref
(Loc
, Component_Size
(E
)));
742 -- Loop through indices
744 Indx
:= First_Index
(E
);
745 while Present
(Indx
) loop
746 Ityp
:= Etype
(Indx
);
747 Lo
:= Type_Low_Bound
(Ityp
);
748 Hi
:= Type_High_Bound
(Ityp
);
753 -- Value of the current subscript range is statically known
755 if Compile_Time_Known_Value
(Lo
)
756 and then Compile_Time_Known_Value
(Hi
)
758 S
:= Expr_Value
(Hi
) - Expr_Value
(Lo
) + 1;
760 -- If known flat bound, entire size of array is zero!
763 return Make_Integer_Literal
(Loc
, 0);
766 -- Current value is constant, evolve value
768 if Size
.Status
= Const
then
769 Size
.Val
:= Size
.Val
* S
;
771 -- Current value is dynamic
774 -- An interesting little optimization, if we have a pending
775 -- conversion from bits to storage units, and the current
776 -- length is a multiple of the storage unit size, then we
777 -- can take the factor out here statically, avoiding some
778 -- extra dynamic computations at the end.
780 if SU_Convert_Required
and then S
mod SSU
= 0 then
782 SU_Convert_Required
:= False;
787 Left_Opnd
=> Size
.Nod
,
789 Make_Integer_Literal
(Loc
, Intval
=> S
));
792 -- Value of the current subscript range is dynamic
795 -- If the current size value is constant, then here is where we
796 -- make a transition to dynamic values, which are always stored
797 -- in storage units, However, we do not want to convert to SU's
798 -- too soon, consider the case of a packed array of single bits,
799 -- we want to do the SU conversion after computing the size in
802 if Size
.Status
= Const
then
804 -- If the current value is a multiple of the storage unit,
805 -- then most certainly we can do the conversion now, simply
806 -- by dividing the current value by the storage unit value.
807 -- If this works, we set SU_Convert_Required to False.
809 if Size
.Val
mod SSU
= 0 then
812 (Dynamic
, Make_Integer_Literal
(Loc
, Size
.Val
/ SSU
));
813 SU_Convert_Required
:= False;
815 -- Otherwise, we go ahead and convert the value in bits,
816 -- and set SU_Convert_Required to True to ensure that the
817 -- final value is indeed properly converted.
820 Size
:= (Dynamic
, Make_Integer_Literal
(Loc
, Size
.Val
));
821 SU_Convert_Required
:= True;
827 Len
:= Compute_Length
(Lo
, Hi
);
829 -- Check possible range of Len
838 Determine_Range
(Len
, OK
, LLo
, LHi
);
840 Len
:= Convert_To
(Standard_Unsigned
, Len
);
842 -- If we cannot verify that range cannot be super-flat,
843 -- we need a max with zero, since length must be non-neg.
845 if not OK
or else LLo
< 0 then
847 Make_Attribute_Reference
(Loc
,
849 New_Occurrence_Of
(Standard_Unsigned
, Loc
),
850 Attribute_Name
=> Name_Max
,
851 Expressions
=> New_List
(
852 Make_Integer_Literal
(Loc
, 0),
861 -- Here after processing all bounds to set sizes. If the value is
862 -- a constant, then it is bits, and we just return the value.
864 if Size
.Status
= Const
then
865 return Make_Integer_Literal
(Loc
, Size
.Val
);
867 -- Case where the value is dynamic
870 -- Do convert from bits to SU's if needed
872 if SU_Convert_Required
then
874 -- The expression required is (Size.Nod + SU - 1) / SU
880 Left_Opnd
=> Size
.Nod
,
881 Right_Opnd
=> Make_Integer_Literal
(Loc
, SSU
- 1)),
882 Right_Opnd
=> Make_Integer_Literal
(Loc
, SSU
));
889 -----------------------
890 -- Layout_Array_Type --
891 -----------------------
893 procedure Layout_Array_Type
(E
: Entity_Id
) is
894 Loc
: constant Source_Ptr
:= Sloc
(E
);
895 Ctyp
: constant Entity_Id
:= Component_Type
(E
);
903 Insert_Typ
: Entity_Id
;
904 -- This is the type with which any generated constants or functions
905 -- will be associated (i.e. inserted into the freeze actions). This
906 -- is normally the type being laid out. The exception occurs when
907 -- we are laying out Itype's which are local to a record type, and
908 -- whose scope is this record type. Such types do not have freeze
909 -- nodes (because we have no place to put them).
911 ------------------------------------
912 -- How An Array Type is Laid Out --
913 ------------------------------------
915 -- Here is what goes on. We need to multiply the component size of
916 -- the array (which has already been set) by the length of each of
917 -- the indexes. If all these values are known at compile time, then
918 -- the resulting size of the array is the appropriate constant value.
920 -- If the component size or at least one bound is dynamic (but no
921 -- discriminants are present), then the size will be computed as an
922 -- expression that calculates the proper size.
924 -- If there is at least one discriminant bound, then the size is also
925 -- computed as an expression, but this expression contains discriminant
926 -- values which are obtained by selecting from a function parameter, and
927 -- the size is given by a function that is passed the variant record in
928 -- question, and whose body is the expression.
930 type Val_Status_Type
is (Const
, Dynamic
, Discrim
);
932 type Val_Type
(Status
: Val_Status_Type
:= Const
) is
937 -- Calculated value so far if Val_Status = Const
939 when Dynamic | Discrim
=>
941 -- Expression value so far if Val_Status /= Const
945 -- Records the value or expression computed so far. Const means that
946 -- the value is constant, and Val is the current constant value.
947 -- Dynamic means that the value is dynamic, and in this case Nod is
948 -- the Node_Id of the expression to compute the value, and Discrim
949 -- means that at least one bound is a discriminant, in which case Nod
950 -- is the expression so far (which will be the body of the function).
953 -- Value of size computed so far. See comments above
955 Vtyp
: Entity_Id
:= Empty
;
956 -- Variant record type for the formal parameter of the
957 -- discriminant function V if Status = Discrim.
959 SU_Convert_Required
: Boolean := False;
960 -- This is set to True if the final result must be converted from
961 -- bits to storage units (rounding up to a storage unit boundary).
963 Storage_Divisor
: Uint
:= UI_From_Int
(SSU
);
964 -- This is the amount that a nonstatic computed size will be divided
965 -- by to convert it from bits to storage units. This is normally
966 -- equal to SSU, but can be reduced in the case of packed components
967 -- that fit evenly into a storage unit.
969 Make_Size_Function
: Boolean := False;
970 -- Indicates whether to request that SO_Ref_From_Expr should
971 -- encapsulate the array size expresion in a function.
973 procedure Discrimify
(N
: in out Node_Id
);
974 -- If N represents a discriminant, then the Size.Status is set to
975 -- Discrim, and Vtyp is set. The parameter N is replaced with the
976 -- proper expression to extract the discriminant value from V.
982 procedure Discrimify
(N
: in out Node_Id
) is
987 if Nkind
(N
) = N_Identifier
988 and then Ekind
(Entity
(N
)) = E_Discriminant
990 Set_Size_Depends_On_Discriminant
(E
);
992 if Size
.Status
/= Discrim
then
993 Decl
:= Parent
(Parent
(Entity
(N
)));
994 Size
:= (Discrim
, Size
.Nod
);
995 Vtyp
:= Defining_Identifier
(Decl
);
1001 Make_Selected_Component
(Loc
,
1002 Prefix
=> Make_Identifier
(Loc
, Chars
=> Vname
),
1003 Selector_Name
=> New_Occurrence_Of
(Entity
(N
), Loc
));
1005 -- Set the Etype attributes of the selected name and its prefix.
1006 -- Analyze_And_Resolve can't be called here because the Vname
1007 -- entity denoted by the prefix will not yet exist (it's created
1008 -- by SO_Ref_From_Expr, called at the end of Layout_Array_Type).
1010 Set_Etype
(Prefix
(N
), Vtyp
);
1015 -- Start of processing for Layout_Array_Type
1018 -- Default alignment is component alignment
1020 if Unknown_Alignment
(E
) then
1021 Set_Alignment
(E
, Alignment
(Ctyp
));
1024 -- Calculate proper type for insertions
1026 if Is_Record_Type
(Underlying_Type
(Scope
(E
))) then
1027 Insert_Typ
:= Underlying_Type
(Scope
(E
));
1032 -- If the component type is a generic formal type then there's no point
1033 -- in determining a size for the array type.
1035 if Is_Generic_Type
(Ctyp
) then
1039 -- Deal with component size if base type
1041 if Ekind
(E
) = E_Array_Type
then
1043 -- Cannot do anything if Esize of component type unknown
1045 if Unknown_Esize
(Ctyp
) then
1049 -- Set component size if not set already
1051 if Unknown_Component_Size
(E
) then
1052 Set_Component_Size
(E
, Esize
(Ctyp
));
1056 -- (RM 13.3 (48)) says that the size of an unconstrained array
1057 -- is implementation defined. We choose to leave it as Unknown
1058 -- here, and the actual behavior is determined by the back end.
1060 if not Is_Constrained
(E
) then
1064 -- Initialize status from component size
1066 if Known_Static_Component_Size
(E
) then
1067 Size
:= (Const
, Component_Size
(E
));
1070 Size
:= (Dynamic
, Expr_From_SO_Ref
(Loc
, Component_Size
(E
)));
1073 -- Loop to process array indices
1075 Indx
:= First_Index
(E
);
1076 while Present
(Indx
) loop
1077 Ityp
:= Etype
(Indx
);
1079 -- If an index of the array is a generic formal type then there's
1080 -- no point in determining a size for the array type.
1082 if Is_Generic_Type
(Ityp
) then
1086 Lo
:= Type_Low_Bound
(Ityp
);
1087 Hi
:= Type_High_Bound
(Ityp
);
1089 -- Value of the current subscript range is statically known
1091 if Compile_Time_Known_Value
(Lo
)
1092 and then Compile_Time_Known_Value
(Hi
)
1094 S
:= Expr_Value
(Hi
) - Expr_Value
(Lo
) + 1;
1096 -- If known flat bound, entire size of array is zero!
1099 Set_Esize
(E
, Uint_0
);
1100 Set_RM_Size
(E
, Uint_0
);
1104 -- If constant, evolve value
1106 if Size
.Status
= Const
then
1107 Size
.Val
:= Size
.Val
* S
;
1109 -- Current value is dynamic
1112 -- An interesting little optimization, if we have a pending
1113 -- conversion from bits to storage units, and the current
1114 -- length is a multiple of the storage unit size, then we
1115 -- can take the factor out here statically, avoiding some
1116 -- extra dynamic computations at the end.
1118 if SU_Convert_Required
and then S
mod SSU
= 0 then
1120 SU_Convert_Required
:= False;
1123 -- Now go ahead and evolve the expression
1126 Assoc_Multiply
(Loc
,
1127 Left_Opnd
=> Size
.Nod
,
1129 Make_Integer_Literal
(Loc
, Intval
=> S
));
1132 -- Value of the current subscript range is dynamic
1135 -- If the current size value is constant, then here is where we
1136 -- make a transition to dynamic values, which are always stored
1137 -- in storage units, However, we do not want to convert to SU's
1138 -- too soon, consider the case of a packed array of single bits,
1139 -- we want to do the SU conversion after computing the size in
1142 if Size
.Status
= Const
then
1144 -- If the current value is a multiple of the storage unit,
1145 -- then most certainly we can do the conversion now, simply
1146 -- by dividing the current value by the storage unit value.
1147 -- If this works, we set SU_Convert_Required to False.
1149 if Size
.Val
mod SSU
= 0 then
1151 (Dynamic
, Make_Integer_Literal
(Loc
, Size
.Val
/ SSU
));
1152 SU_Convert_Required
:= False;
1154 -- If the current value is a factor of the storage unit,
1155 -- then we can use a value of one for the size and reduce
1156 -- the strength of the later division.
1158 elsif SSU
mod Size
.Val
= 0 then
1159 Storage_Divisor
:= SSU
/ Size
.Val
;
1160 Size
:= (Dynamic
, Make_Integer_Literal
(Loc
, Uint_1
));
1161 SU_Convert_Required
:= True;
1163 -- Otherwise, we go ahead and convert the value in bits,
1164 -- and set SU_Convert_Required to True to ensure that the
1165 -- final value is indeed properly converted.
1168 Size
:= (Dynamic
, Make_Integer_Literal
(Loc
, Size
.Val
));
1169 SU_Convert_Required
:= True;
1176 -- Length is hi-lo+1
1178 Len
:= Compute_Length
(Lo
, Hi
);
1180 -- If Len isn't a Length attribute, then its range needs to
1181 -- be checked a possible Max with zero needs to be computed.
1183 if Nkind
(Len
) /= N_Attribute_Reference
1184 or else Attribute_Name
(Len
) /= Name_Length
1192 -- Check possible range of Len
1194 Set_Parent
(Len
, E
);
1195 Determine_Range
(Len
, OK
, LLo
, LHi
);
1197 Len
:= Convert_To
(Standard_Unsigned
, Len
);
1199 -- If range definitely flat or superflat,
1200 -- result size is zero
1202 if OK
and then LHi
<= 0 then
1203 Set_Esize
(E
, Uint_0
);
1204 Set_RM_Size
(E
, Uint_0
);
1208 -- If we cannot verify that range cannot be super-flat,
1209 -- we need a maximum with zero, since length cannot be
1212 if not OK
or else LLo
< 0 then
1214 Make_Attribute_Reference
(Loc
,
1216 New_Occurrence_Of
(Standard_Unsigned
, Loc
),
1217 Attribute_Name
=> Name_Max
,
1218 Expressions
=> New_List
(
1219 Make_Integer_Literal
(Loc
, 0),
1225 -- At this stage, Len has the expression for the length
1228 Assoc_Multiply
(Loc
,
1229 Left_Opnd
=> Size
.Nod
,
1236 -- Here after processing all bounds to set sizes. If the value is
1237 -- a constant, then it is bits, and the only thing we need to do
1238 -- is to check against explicit given size and do alignment adjust.
1240 if Size
.Status
= Const
then
1241 Set_And_Check_Static_Size
(E
, Size
.Val
, Size
.Val
);
1242 Adjust_Esize_Alignment
(E
);
1244 -- Case where the value is dynamic
1247 -- Do convert from bits to SU's if needed
1249 if SU_Convert_Required
then
1251 -- The expression required is:
1252 -- (Size.Nod + Storage_Divisor - 1) / Storage_Divisor
1255 Make_Op_Divide
(Loc
,
1258 Left_Opnd
=> Size
.Nod
,
1259 Right_Opnd
=> Make_Integer_Literal
1260 (Loc
, Storage_Divisor
- 1)),
1261 Right_Opnd
=> Make_Integer_Literal
(Loc
, Storage_Divisor
));
1264 -- If the array entity is not declared at the library level and its
1265 -- not nested within a subprogram that is marked for inlining, then
1266 -- we request that the size expression be encapsulated in a function.
1267 -- Since this expression is not needed in most cases, we prefer not
1268 -- to incur the overhead of the computation on calls to the enclosing
1269 -- subprogram except for subprograms that require the size.
1271 if not Is_Library_Level_Entity
(E
) then
1272 Make_Size_Function
:= True;
1275 Parent_Subp
: Entity_Id
:= Enclosing_Subprogram
(E
);
1278 while Present
(Parent_Subp
) loop
1279 if Is_Inlined
(Parent_Subp
) then
1280 Make_Size_Function
:= False;
1284 Parent_Subp
:= Enclosing_Subprogram
(Parent_Subp
);
1289 -- Now set the dynamic size (the Value_Size is always the same
1290 -- as the Object_Size for arrays whose length is dynamic).
1292 -- ??? If Size.Status = Dynamic, Vtyp will not have been set.
1293 -- The added initialization sets it to Empty now, but is this
1299 (Size
.Nod
, Insert_Typ
, Vtyp
, Make_Func
=> Make_Size_Function
));
1300 Set_RM_Size
(E
, Esize
(E
));
1302 end Layout_Array_Type
;
1308 procedure Layout_Object
(E
: Entity_Id
) is
1309 T
: constant Entity_Id
:= Etype
(E
);
1312 -- Nothing to do if backend does layout
1314 if not Frontend_Layout_On_Target
then
1318 -- Set size if not set for object and known for type. Use the
1319 -- RM_Size if that is known for the type and Esize is not.
1321 if Unknown_Esize
(E
) then
1322 if Known_Esize
(T
) then
1323 Set_Esize
(E
, Esize
(T
));
1325 elsif Known_RM_Size
(T
) then
1326 Set_Esize
(E
, RM_Size
(T
));
1330 -- Set alignment from type if unknown and type alignment known
1332 if Unknown_Alignment
(E
) and then Known_Alignment
(T
) then
1333 Set_Alignment
(E
, Alignment
(T
));
1336 -- Make sure size and alignment are consistent
1338 Adjust_Esize_Alignment
(E
);
1340 -- Final adjustment, if we don't know the alignment, and the Esize
1341 -- was not set by an explicit Object_Size attribute clause, then
1342 -- we reset the Esize to unknown, since we really don't know it.
1344 if Unknown_Alignment
(E
)
1345 and then not Has_Size_Clause
(E
)
1347 Set_Esize
(E
, Uint_0
);
1351 ------------------------
1352 -- Layout_Record_Type --
1353 ------------------------
1355 procedure Layout_Record_Type
(E
: Entity_Id
) is
1356 Loc
: constant Source_Ptr
:= Sloc
(E
);
1360 -- Current component being laid out
1362 Prev_Comp
: Entity_Id
;
1363 -- Previous laid out component
1365 procedure Get_Next_Component_Location
1366 (Prev_Comp
: Entity_Id
;
1368 New_Npos
: out SO_Ref
;
1369 New_Fbit
: out SO_Ref
;
1370 New_NPMax
: out SO_Ref
;
1371 Force_SU
: Boolean);
1372 -- Given the previous component in Prev_Comp, which is already laid
1373 -- out, and the alignment of the following component, lays out the
1374 -- following component, and returns its starting position in New_Npos
1375 -- (Normalized_Position value), New_Fbit (Normalized_First_Bit value),
1376 -- and New_NPMax (Normalized_Position_Max value). If Prev_Comp is empty
1377 -- (no previous component is present), then New_Npos, New_Fbit and
1378 -- New_NPMax are all set to zero on return. This procedure is also
1379 -- used to compute the size of a record or variant by giving it the
1380 -- last component, and the record alignment. Force_SU is used to force
1381 -- the new component location to be aligned on a storage unit boundary,
1382 -- even in a packed record, False means that the new position does not
1383 -- need to be bumped to a storage unit boundary, True means a storage
1384 -- unit boundary is always required.
1386 procedure Layout_Component
(Comp
: Entity_Id
; Prev_Comp
: Entity_Id
);
1387 -- Lays out component Comp, given Prev_Comp, the previously laid-out
1388 -- component (Prev_Comp = Empty if no components laid out yet). The
1389 -- alignment of the record itself is also updated if needed. Both
1390 -- Comp and Prev_Comp can be either components or discriminants.
1392 procedure Layout_Components
1396 RM_Siz
: out SO_Ref
);
1397 -- This procedure lays out the components of the given component list
1398 -- which contains the components starting with From and ending with To.
1399 -- The Next_Entity chain is used to traverse the components. On entry,
1400 -- Prev_Comp is set to the component preceding the list, so that the
1401 -- list is laid out after this component. Prev_Comp is set to Empty if
1402 -- the component list is to be laid out starting at the start of the
1403 -- record. On return, the components are all laid out, and Prev_Comp is
1404 -- set to the last laid out component. On return, Esiz is set to the
1405 -- resulting Object_Size value, which is the length of the record up
1406 -- to and including the last laid out entity. For Esiz, the value is
1407 -- adjusted to match the alignment of the record. RM_Siz is similarly
1408 -- set to the resulting Value_Size value, which is the same length, but
1409 -- not adjusted to meet the alignment. Note that in the case of variant
1410 -- records, Esiz represents the maximum size.
1412 procedure Layout_Non_Variant_Record
;
1413 -- Procedure called to lay out a non-variant record type or subtype
1415 procedure Layout_Variant_Record
;
1416 -- Procedure called to lay out a variant record type. Decl is set to the
1417 -- full type declaration for the variant record.
1419 ---------------------------------
1420 -- Get_Next_Component_Location --
1421 ---------------------------------
1423 procedure Get_Next_Component_Location
1424 (Prev_Comp
: Entity_Id
;
1426 New_Npos
: out SO_Ref
;
1427 New_Fbit
: out SO_Ref
;
1428 New_NPMax
: out SO_Ref
;
1432 -- No previous component, return zero position
1434 if No
(Prev_Comp
) then
1437 New_NPMax
:= Uint_0
;
1441 -- Here we have a previous component
1444 Loc
: constant Source_Ptr
:= Sloc
(Prev_Comp
);
1446 Old_Npos
: constant SO_Ref
:= Normalized_Position
(Prev_Comp
);
1447 Old_Fbit
: constant SO_Ref
:= Normalized_First_Bit
(Prev_Comp
);
1448 Old_NPMax
: constant SO_Ref
:= Normalized_Position_Max
(Prev_Comp
);
1449 Old_Esiz
: constant SO_Ref
:= Esize
(Prev_Comp
);
1451 Old_Maxsz
: Node_Id
;
1452 -- Expression representing maximum size of previous component
1455 -- Case where previous field had a dynamic size
1457 if Is_Dynamic_SO_Ref
(Esize
(Prev_Comp
)) then
1459 -- If the previous field had a dynamic length, then it is
1460 -- required to occupy an integral number of storage units,
1461 -- and start on a storage unit boundary. This means that
1462 -- the Normalized_First_Bit value is zero in the previous
1463 -- component, and the new value is also set to zero.
1467 -- In this case, the new position is given by an expression
1468 -- that is the sum of old normalized position and old size.
1474 Expr_From_SO_Ref
(Loc
, Old_Npos
),
1476 Expr_From_SO_Ref
(Loc
, Old_Esiz
, Prev_Comp
)),
1480 -- Get maximum size of previous component
1482 if Size_Depends_On_Discriminant
(Etype
(Prev_Comp
)) then
1483 Old_Maxsz
:= Get_Max_Size
(Etype
(Prev_Comp
));
1485 Old_Maxsz
:= Expr_From_SO_Ref
(Loc
, Old_Esiz
, Prev_Comp
);
1488 -- Now we can compute the new max position. If the max size
1489 -- is static and the old position is static, then we can
1490 -- compute the new position statically.
1492 if Nkind
(Old_Maxsz
) = N_Integer_Literal
1493 and then Known_Static_Normalized_Position_Max
(Prev_Comp
)
1495 New_NPMax
:= Old_NPMax
+ Intval
(Old_Maxsz
);
1497 -- Otherwise new max position is dynamic
1503 Left_Opnd
=> Expr_From_SO_Ref
(Loc
, Old_NPMax
),
1504 Right_Opnd
=> Old_Maxsz
),
1509 -- Previous field has known static Esize
1512 New_Fbit
:= Old_Fbit
+ Old_Esiz
;
1514 -- Bump New_Fbit to storage unit boundary if required
1516 if New_Fbit
/= 0 and then Force_SU
then
1517 New_Fbit
:= (New_Fbit
+ SSU
- 1) / SSU
* SSU
;
1520 -- If old normalized position is static, we can go ahead
1521 -- and compute the new normalized position directly.
1523 if Known_Static_Normalized_Position
(Prev_Comp
) then
1524 New_Npos
:= Old_Npos
;
1526 if New_Fbit
>= SSU
then
1527 New_Npos
:= New_Npos
+ New_Fbit
/ SSU
;
1528 New_Fbit
:= New_Fbit
mod SSU
;
1531 -- Bump alignment if stricter than prev
1533 if Align
> Alignment
(Etype
(Prev_Comp
)) then
1534 New_Npos
:= (New_Npos
+ Align
- 1) / Align
* Align
;
1537 -- The max position is always equal to the position if
1538 -- the latter is static, since arrays depending on the
1539 -- values of discriminants never have static sizes.
1541 New_NPMax
:= New_Npos
;
1544 -- Case of old normalized position is dynamic
1547 -- If new bit position is within the current storage unit,
1548 -- we can just copy the old position as the result position
1549 -- (we have already set the new first bit value).
1551 if New_Fbit
< SSU
then
1552 New_Npos
:= Old_Npos
;
1553 New_NPMax
:= Old_NPMax
;
1555 -- If new bit position is past the current storage unit, we
1556 -- need to generate a new dynamic value for the position
1557 -- ??? need to deal with alignment
1563 Left_Opnd
=> Expr_From_SO_Ref
(Loc
, Old_Npos
),
1565 Make_Integer_Literal
(Loc
,
1566 Intval
=> New_Fbit
/ SSU
)),
1573 Left_Opnd
=> Expr_From_SO_Ref
(Loc
, Old_NPMax
),
1575 Make_Integer_Literal
(Loc
,
1576 Intval
=> New_Fbit
/ SSU
)),
1579 New_Fbit
:= New_Fbit
mod SSU
;
1584 end Get_Next_Component_Location
;
1586 ----------------------
1587 -- Layout_Component --
1588 ----------------------
1590 procedure Layout_Component
(Comp
: Entity_Id
; Prev_Comp
: Entity_Id
) is
1591 Ctyp
: constant Entity_Id
:= Etype
(Comp
);
1598 -- Parent field is always at start of record, this will overlap
1599 -- the actual fields that are part of the parent, and that's fine
1601 if Chars
(Comp
) = Name_uParent
then
1602 Set_Normalized_Position
(Comp
, Uint_0
);
1603 Set_Normalized_First_Bit
(Comp
, Uint_0
);
1604 Set_Normalized_Position_Max
(Comp
, Uint_0
);
1605 Set_Component_Bit_Offset
(Comp
, Uint_0
);
1606 Set_Esize
(Comp
, Esize
(Ctyp
));
1610 -- Check case of type of component has a scope of the record we
1611 -- are laying out. When this happens, the type in question is an
1612 -- Itype that has not yet been laid out (that's because such
1613 -- types do not get frozen in the normal manner, because there
1614 -- is no place for the freeze nodes).
1616 if Scope
(Ctyp
) = E
then
1620 -- Increase alignment of record if necessary. Note that we do not
1621 -- do this for packed records, which have an alignment of one by
1622 -- default, or for records for which an explicit alignment was
1623 -- specified with an alignment clause.
1625 if not Is_Packed
(E
)
1626 and then not Has_Alignment_Clause
(E
)
1627 and then Alignment
(Ctyp
) > Alignment
(E
)
1629 Set_Alignment
(E
, Alignment
(Ctyp
));
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 exactly
1640 -- what the RM_Size value, as distinct from the Object_Size is
1643 if Is_Packed
(E
) then
1644 Set_Esize
(Comp
, RM_Size
(Ctyp
));
1646 Set_Esize
(Comp
, Esize
(Ctyp
));
1649 -- Compute the component position from the previous one. See if
1650 -- current component requires being on a storage unit boundary.
1652 -- If record is not packed, we always go to a storage unit boundary
1654 if not Is_Packed
(E
) then
1660 -- Elementary types do not need SU boundary in packed record
1662 if Is_Elementary_Type
(Ctyp
) then
1665 -- Packed array types with a modular packed array type do not
1666 -- force a storage unit boundary (since the code generation
1667 -- treats these as equivalent to the underlying modular type),
1669 elsif Is_Array_Type
(Ctyp
)
1670 and then Is_Bit_Packed_Array
(Ctyp
)
1671 and then Is_Modular_Integer_Type
(Packed_Array_Type
(Ctyp
))
1675 -- Record types with known length less than or equal to the length
1676 -- of long long integer can also be unaligned, since they can be
1677 -- treated as scalars.
1679 elsif Is_Record_Type
(Ctyp
)
1680 and then not Is_Dynamic_SO_Ref
(Esize
(Ctyp
))
1681 and then Esize
(Ctyp
) <= Esize
(Standard_Long_Long_Integer
)
1685 -- All other cases force a storage unit boundary, even when packed
1692 -- Now get the next component location
1694 Get_Next_Component_Location
1695 (Prev_Comp
, Alignment
(Ctyp
), Npos
, Fbit
, NPMax
, Forc
);
1696 Set_Normalized_Position
(Comp
, Npos
);
1697 Set_Normalized_First_Bit
(Comp
, Fbit
);
1698 Set_Normalized_Position_Max
(Comp
, NPMax
);
1700 -- Set Component_Bit_Offset in the static case
1702 if Known_Static_Normalized_Position
(Comp
)
1703 and then Known_Normalized_First_Bit
(Comp
)
1705 Set_Component_Bit_Offset
(Comp
, SSU
* Npos
+ Fbit
);
1707 end Layout_Component
;
1709 -----------------------
1710 -- Layout_Components --
1711 -----------------------
1713 procedure Layout_Components
1717 RM_Siz
: out SO_Ref
)
1724 -- Only lay out components if there are some to lay out!
1726 if Present
(From
) then
1728 -- Lay out components with no component clauses
1732 if Ekind
(Comp
) = E_Component
1733 or else Ekind
(Comp
) = E_Discriminant
1735 -- The compatibility of component clauses with composite
1736 -- types isn't checked in Sem_Ch13, so we check it here.
1738 if Present
(Component_Clause
(Comp
)) then
1739 if Is_Composite_Type
(Etype
(Comp
))
1740 and then Esize
(Comp
) < RM_Size
(Etype
(Comp
))
1742 Error_Msg_Uint_1
:= RM_Size
(Etype
(Comp
));
1744 ("size for & too small, minimum allowed is ^",
1745 Component_Clause
(Comp
),
1750 Layout_Component
(Comp
, Prev_Comp
);
1755 exit when Comp
= To
;
1760 -- Set size fields, both are zero if no components
1762 if No
(Prev_Comp
) then
1767 -- First the object size, for which we align past the last
1768 -- field to the alignment of the record (the object size
1769 -- is required to be a multiple of the alignment).
1771 Get_Next_Component_Location
1779 -- If the resulting normalized position is a dynamic reference,
1780 -- then the size is dynamic, and is stored in storage units.
1781 -- In this case, we set the RM_Size to the same value, it is
1782 -- simply not worth distinguishing Esize and RM_Size values in
1783 -- the dynamic case, since the RM has nothing to say about them.
1785 -- Note that a size cannot have been given in this case, since
1786 -- size specifications cannot be given for variable length types.
1789 Align
: constant Uint
:= Alignment
(E
);
1792 if Is_Dynamic_SO_Ref
(End_Npos
) then
1795 -- Set the Object_Size allowing for alignment. In the
1796 -- dynamic case, we have to actually do the runtime
1797 -- computation. We can skip this in the non-packed
1798 -- record case if the last component has a smaller
1799 -- alignment than the overall record alignment.
1801 if Is_Dynamic_SO_Ref
(End_NPMax
) then
1805 or else Alignment
(Etype
(Prev_Comp
)) < Align
1807 -- The expression we build is
1808 -- (expr + align - 1) / align * align
1813 Make_Op_Multiply
(Loc
,
1815 Make_Op_Divide
(Loc
,
1819 Expr_From_SO_Ref
(Loc
, Esiz
),
1821 Make_Integer_Literal
(Loc
,
1822 Intval
=> Align
- 1)),
1824 Make_Integer_Literal
(Loc
, Align
)),
1826 Make_Integer_Literal
(Loc
, Align
)),
1831 -- Here Esiz is static, so we can adjust the alignment
1832 -- directly go give the required aligned value.
1835 Esiz
:= (End_NPMax
+ Align
- 1) / Align
* Align
* SSU
;
1838 -- Case where computed size is static
1841 -- The ending size was computed in Npos in storage units,
1842 -- but the actual size is stored in bits, so adjust
1843 -- accordingly. We also adjust the size to match the
1846 Esiz
:= (End_NPMax
+ Align
- 1) / Align
* Align
* SSU
;
1848 -- Compute the resulting Value_Size (RM_Size). For this
1849 -- purpose we do not force alignment of the record or
1850 -- storage size alignment of the result.
1852 Get_Next_Component_Location
1860 RM_Siz
:= End_Npos
* SSU
+ End_Fbit
;
1861 Set_And_Check_Static_Size
(E
, Esiz
, RM_Siz
);
1865 end Layout_Components
;
1867 -------------------------------
1868 -- Layout_Non_Variant_Record --
1869 -------------------------------
1871 procedure Layout_Non_Variant_Record
is
1876 Layout_Components
(First_Entity
(E
), Last_Entity
(E
), Esiz
, RM_Siz
);
1877 Set_Esize
(E
, Esiz
);
1878 Set_RM_Size
(E
, RM_Siz
);
1879 end Layout_Non_Variant_Record
;
1881 ---------------------------
1882 -- Layout_Variant_Record --
1883 ---------------------------
1885 procedure Layout_Variant_Record
is
1886 Tdef
: constant Node_Id
:= Type_Definition
(Decl
);
1887 Dlist
: constant List_Id
:= Discriminant_Specifications
(Decl
);
1891 RM_Siz_Expr
: Node_Id
:= Empty
;
1892 -- Expression for the evolving RM_Siz value. This is typically a
1893 -- conditional expression which involves tests of discriminant
1894 -- values that are formed as references to the entity V. At
1895 -- the end of scanning all the components, a suitable function
1896 -- is constructed in which V is the parameter.
1898 -----------------------
1899 -- Local Subprograms --
1900 -----------------------
1902 procedure Layout_Component_List
1905 RM_Siz_Expr
: out Node_Id
);
1906 -- Recursive procedure, called to lay out one component list
1907 -- Esiz and RM_Siz_Expr are set to the Object_Size and Value_Size
1908 -- values respectively representing the record size up to and
1909 -- including the last component in the component list (including
1910 -- any variants in this component list). RM_Siz_Expr is returned
1911 -- as an expression which may in the general case involve some
1912 -- references to the discriminants of the current record value,
1913 -- referenced by selecting from the entity V.
1915 ---------------------------
1916 -- Layout_Component_List --
1917 ---------------------------
1919 procedure Layout_Component_List
1922 RM_Siz_Expr
: out Node_Id
)
1924 Citems
: constant List_Id
:= Component_Items
(Clist
);
1925 Vpart
: constant Node_Id
:= Variant_Part
(Clist
);
1929 RMS_Ent
: Entity_Id
;
1932 if Is_Non_Empty_List
(Citems
) then
1934 (From
=> Defining_Identifier
(First
(Citems
)),
1935 To
=> Defining_Identifier
(Last
(Citems
)),
1939 Layout_Components
(Empty
, Empty
, Esiz
, RM_Siz
);
1942 -- Case where no variants are present in the component list
1946 -- The Esiz value has been correctly set by the call to
1947 -- Layout_Components, so there is nothing more to be done.
1949 -- For RM_Siz, we have an SO_Ref value, which we must convert
1950 -- to an appropriate expression.
1952 if Is_Static_SO_Ref
(RM_Siz
) then
1954 Make_Integer_Literal
(Loc
,
1958 RMS_Ent
:= Get_Dynamic_SO_Entity
(RM_Siz
);
1960 -- If the size is represented by a function, then we
1961 -- create an appropriate function call using V as
1962 -- the parameter to the call.
1964 if Is_Discrim_SO_Function
(RMS_Ent
) then
1966 Make_Function_Call
(Loc
,
1967 Name
=> New_Occurrence_Of
(RMS_Ent
, Loc
),
1968 Parameter_Associations
=> New_List
(
1969 Make_Identifier
(Loc
, Chars
=> Vname
)));
1971 -- If the size is represented by a constant, then the
1972 -- expression we want is a reference to this constant
1975 RM_Siz_Expr
:= New_Occurrence_Of
(RMS_Ent
, Loc
);
1979 -- Case where variants are present in this component list
1989 D_Entity
: Entity_Id
;
1992 RM_Siz_Expr
:= Empty
;
1995 Var
:= Last
(Variants
(Vpart
));
1996 while Present
(Var
) loop
1998 Layout_Component_List
1999 (Component_List
(Var
), EsizV
, RM_SizV
);
2001 -- Set the Object_Size. If this is the first variant,
2002 -- we just set the size of this first variant.
2004 if Var
= Last
(Variants
(Vpart
)) then
2007 -- Otherwise the Object_Size is formed as a maximum
2008 -- of Esiz so far from previous variants, and the new
2009 -- Esiz value from the variant we just processed.
2011 -- If both values are static, we can just compute the
2012 -- maximum directly to save building junk nodes.
2014 elsif not Is_Dynamic_SO_Ref
(Esiz
)
2015 and then not Is_Dynamic_SO_Ref
(EsizV
)
2017 Esiz
:= UI_Max
(Esiz
, EsizV
);
2019 -- If either value is dynamic, then we have to generate
2020 -- an appropriate Standard_Unsigned'Max attribute call.
2025 (Make_Attribute_Reference
(Loc
,
2026 Attribute_Name
=> Name_Max
,
2028 New_Occurrence_Of
(Standard_Unsigned
, Loc
),
2029 Expressions
=> New_List
(
2030 Expr_From_SO_Ref
(Loc
, Esiz
),
2031 Expr_From_SO_Ref
(Loc
, EsizV
))),
2036 -- Now deal with Value_Size (RM_Siz). We are aiming at
2037 -- an expression that looks like:
2039 -- if xxDx (V.disc) then rmsiz1
2040 -- else if xxDx (V.disc) then rmsiz2
2043 -- Where rmsiz1, rmsiz2... are the RM_Siz values for the
2044 -- individual variants, and xxDx are the discriminant
2045 -- checking functions generated for the variant type.
2047 -- If this is the first variant, we simply set the
2048 -- result as the expression. Note that this takes
2049 -- care of the others case.
2051 if No
(RM_Siz_Expr
) then
2052 RM_Siz_Expr
:= Bits_To_SU
(RM_SizV
);
2054 -- Otherwise construct the appropriate test
2057 -- The test to be used in general is a call to the
2058 -- discriminant checking function. However, it is
2059 -- definitely worth special casing the very common
2060 -- case where a single value is involved.
2062 Dchoice
:= First
(Discrete_Choices
(Var
));
2064 if No
(Next
(Dchoice
))
2065 and then Nkind
(Dchoice
) /= N_Range
2067 -- Discriminant to be tested
2070 Make_Selected_Component
(Loc
,
2072 Make_Identifier
(Loc
, Chars
=> Vname
),
2075 (Entity
(Name
(Vpart
)), Loc
));
2079 Left_Opnd
=> Discrim
,
2080 Right_Opnd
=> New_Copy
(Dchoice
));
2082 -- Generate a call to the discriminant-checking
2083 -- function for the variant. Note that the result
2084 -- has to be complemented since the function returns
2085 -- False when the passed discriminant value matches.
2088 -- The checking function takes all of the type's
2089 -- discriminants as parameters, so a list of all
2090 -- the selected discriminants must be constructed.
2093 D_Entity
:= First_Discriminant
(E
);
2094 while Present
(D_Entity
) loop
2096 Make_Selected_Component
(Loc
,
2098 Make_Identifier
(Loc
, Chars
=> Vname
),
2104 D_Entity
:= Next_Discriminant
(D_Entity
);
2110 Make_Function_Call
(Loc
,
2113 (Dcheck_Function
(Var
), Loc
),
2114 Parameter_Associations
=>
2119 Make_Conditional_Expression
(Loc
,
2122 (Dtest
, Bits_To_SU
(RM_SizV
), RM_Siz_Expr
));
2129 end Layout_Component_List
;
2131 -- Start of processing for Layout_Variant_Record
2134 -- We need the discriminant checking functions, since we generate
2135 -- calls to these functions for the RM_Size expression, so make
2136 -- sure that these functions have been constructed in time.
2138 Build_Discr_Checking_Funcs
(Decl
);
2140 -- Lay out the discriminants
2143 (From
=> Defining_Identifier
(First
(Dlist
)),
2144 To
=> Defining_Identifier
(Last
(Dlist
)),
2148 -- Lay out the main component list (this will make recursive calls
2149 -- to lay out all component lists nested within variants).
2151 Layout_Component_List
(Component_List
(Tdef
), Esiz
, RM_Siz_Expr
);
2152 Set_Esize
(E
, Esiz
);
2154 -- If the RM_Size is a literal, set its value
2156 if Nkind
(RM_Siz_Expr
) = N_Integer_Literal
then
2157 Set_RM_Size
(E
, Intval
(RM_Siz_Expr
));
2159 -- Otherwise we construct a dynamic SO_Ref
2168 end Layout_Variant_Record
;
2170 -- Start of processing for Layout_Record_Type
2173 -- If this is a cloned subtype, just copy the size fields from the
2174 -- original, nothing else needs to be done in this case, since the
2175 -- components themselves are all shared.
2177 if (Ekind
(E
) = E_Record_Subtype
2178 or else Ekind
(E
) = E_Class_Wide_Subtype
)
2179 and then Present
(Cloned_Subtype
(E
))
2181 Set_Esize
(E
, Esize
(Cloned_Subtype
(E
)));
2182 Set_RM_Size
(E
, RM_Size
(Cloned_Subtype
(E
)));
2183 Set_Alignment
(E
, Alignment
(Cloned_Subtype
(E
)));
2185 -- Another special case, class-wide types. The RM says that the size
2186 -- of such types is implementation defined (RM 13.3(48)). What we do
2187 -- here is to leave the fields set as unknown values, and the backend
2188 -- determines the actual behavior.
2190 elsif Ekind
(E
) = E_Class_Wide_Type
then
2196 -- Initialize alignment conservatively to 1. This value will
2197 -- be increased as necessary during processing of the record.
2199 if Unknown_Alignment
(E
) then
2200 Set_Alignment
(E
, Uint_1
);
2203 -- Initialize previous component. This is Empty unless there
2204 -- are components which have already been laid out by component
2205 -- clauses. If there are such components, we start our lay out of
2206 -- the remaining components following the last such component.
2210 Comp
:= First_Entity
(E
);
2211 while Present
(Comp
) loop
2212 if (Ekind
(Comp
) = E_Component
2213 or else Ekind
(Comp
) = E_Discriminant
)
2214 and then Present
(Component_Clause
(Comp
))
2218 Component_Bit_Offset
(Comp
) >
2219 Component_Bit_Offset
(Prev_Comp
)
2228 -- We have two separate circuits, one for non-variant records and
2229 -- one for variant records. For non-variant records, we simply go
2230 -- through the list of components. This handles all the non-variant
2231 -- cases including those cases of subtypes where there is no full
2232 -- type declaration, so the tree cannot be used to drive the layout.
2233 -- For variant records, we have to drive the layout from the tree
2234 -- since we need to understand the variant structure in this case.
2236 if Present
(Full_View
(E
)) then
2237 Decl
:= Declaration_Node
(Full_View
(E
));
2239 Decl
:= Declaration_Node
(E
);
2242 -- Scan all the components
2244 if Nkind
(Decl
) = N_Full_Type_Declaration
2245 and then Has_Discriminants
(E
)
2246 and then Nkind
(Type_Definition
(Decl
)) = N_Record_Definition
2247 and then Present
(Component_List
(Type_Definition
(Decl
)))
2249 Present
(Variant_Part
(Component_List
(Type_Definition
(Decl
))))
2251 Layout_Variant_Record
;
2253 Layout_Non_Variant_Record
;
2256 end Layout_Record_Type
;
2262 procedure Layout_Type
(E
: Entity_Id
) is
2264 -- For string literal types, for now, kill the size always, this
2265 -- is because gigi does not like or need the size to be set ???
2267 if Ekind
(E
) = E_String_Literal_Subtype
then
2268 Set_Esize
(E
, Uint_0
);
2269 Set_RM_Size
(E
, Uint_0
);
2273 -- For access types, set size/alignment. This is system address
2274 -- size, except for fat pointers (unconstrained array access types),
2275 -- where the size is two times the address size, to accommodate the
2276 -- two pointers that are required for a fat pointer (data and
2277 -- template). Note that E_Access_Protected_Subprogram_Type is not
2278 -- an access type for this purpose since it is not a pointer but is
2279 -- equivalent to a record. For access subtypes, copy the size from
2280 -- the base type since Gigi represents them the same way.
2282 if Is_Access_Type
(E
) then
2284 -- If Esize already set (e.g. by a size clause), then nothing
2285 -- further to be done here.
2287 if Known_Esize
(E
) then
2290 -- Access to subprogram is a strange beast, and we let the
2291 -- backend figure out what is needed (it may be some kind
2292 -- of fat pointer, including the static link for example.
2294 elsif Ekind
(E
) = E_Access_Protected_Subprogram_Type
then
2297 -- For access subtypes, copy the size information from base type
2299 elsif Ekind
(E
) = E_Access_Subtype
then
2300 Set_Size_Info
(E
, Base_Type
(E
));
2301 Set_RM_Size
(E
, RM_Size
(Base_Type
(E
)));
2303 -- For other access types, we use either address size, or, if
2304 -- a fat pointer is used (pointer-to-unconstrained array case),
2305 -- twice the address size to accommodate a fat pointer.
2309 Desig
: Entity_Id
:= Designated_Type
(E
);
2312 if Is_Private_Type
(Desig
)
2313 and then Present
(Full_View
(Desig
))
2315 Desig
:= Full_View
(Desig
);
2318 if Is_Array_Type
(Desig
)
2319 and then not Is_Constrained
(Desig
)
2320 and then not Has_Completion_In_Body
(Desig
)
2321 and then not Debug_Flag_6
2323 Init_Size
(E
, 2 * System_Address_Size
);
2325 -- Check for bad convention set
2327 if Warn_On_Export_Import
2329 (Convention
(E
) = Convention_C
2331 Convention
(E
) = Convention_CPP
)
2334 ("?this access type does not " &
2335 "correspond to C pointer", E
);
2339 Init_Size
(E
, System_Address_Size
);
2344 Set_Elem_Alignment
(E
);
2346 -- Scalar types: set size and alignment
2348 elsif Is_Scalar_Type
(E
) then
2350 -- For discrete types, the RM_Size and Esize must be set
2351 -- already, since this is part of the earlier processing
2352 -- and the front end is always required to lay out the
2353 -- sizes of such types (since they are available as static
2354 -- attributes). All we do is to check that this rule is
2357 if Is_Discrete_Type
(E
) then
2359 -- If the RM_Size is not set, then here is where we set it
2361 -- Note: an RM_Size of zero looks like not set here, but this
2362 -- is a rare case, and we can simply reset it without any harm.
2364 if not Known_RM_Size
(E
) then
2365 Set_Discrete_RM_Size
(E
);
2368 -- If Esize for a discrete type is not set then set it
2370 if not Known_Esize
(E
) then
2376 -- If size is big enough, set it and exit
2378 if S
>= RM_Size
(E
) then
2382 -- If the RM_Size is greater than 64 (happens only
2383 -- when strange values are specified by the user,
2384 -- then Esize is simply a copy of RM_Size, it will
2385 -- be further refined later on)
2388 Set_Esize
(E
, RM_Size
(E
));
2391 -- Otherwise double possible size and keep trying
2400 -- For non-discrete sclar types, if the RM_Size is not set,
2401 -- then set it now to a copy of the Esize if the Esize is set.
2404 if Known_Esize
(E
) and then Unknown_RM_Size
(E
) then
2405 Set_RM_Size
(E
, Esize
(E
));
2409 Set_Elem_Alignment
(E
);
2411 -- Non-elementary (composite) types
2414 -- If RM_Size is known, set Esize if not known
2416 if Known_RM_Size
(E
) and then Unknown_Esize
(E
) then
2418 -- If the alignment is known, we bump the Esize up to the
2419 -- next alignment boundary if it is not already on one.
2421 if Known_Alignment
(E
) then
2423 A
: constant Uint
:= Alignment_In_Bits
(E
);
2424 S
: constant SO_Ref
:= RM_Size
(E
);
2427 Set_Esize
(E
, (S
* A
+ A
- 1) / A
);
2431 -- If Esize is set, and RM_Size is not, RM_Size is copied from
2432 -- Esize at least for now this seems reasonable, and is in any
2433 -- case needed for compatibility with old versions of gigi.
2434 -- look to be unknown.
2436 elsif Known_Esize
(E
) and then Unknown_RM_Size
(E
) then
2437 Set_RM_Size
(E
, Esize
(E
));
2440 -- For array base types, set component size if object size of
2441 -- the component type is known and is a small power of 2 (8,
2442 -- 16, 32, 64), since this is what will always be used.
2444 if Ekind
(E
) = E_Array_Type
2445 and then Unknown_Component_Size
(E
)
2448 CT
: constant Entity_Id
:= Component_Type
(E
);
2451 -- For some reasons, access types can cause trouble,
2452 -- So let's just do this for discrete types ???
2455 and then Is_Discrete_Type
(CT
)
2456 and then Known_Static_Esize
(CT
)
2459 S
: constant Uint
:= Esize
(CT
);
2467 Set_Component_Size
(E
, Esize
(CT
));
2475 -- Lay out array and record types if front end layout set
2477 if Frontend_Layout_On_Target
then
2478 if Is_Array_Type
(E
) and then not Is_Bit_Packed_Array
(E
) then
2479 Layout_Array_Type
(E
);
2480 elsif Is_Record_Type
(E
) then
2481 Layout_Record_Type
(E
);
2484 -- Case of backend layout, we still do a little in the front end
2487 -- Processing for record types
2489 if Is_Record_Type
(E
) then
2491 -- Special remaining processing for record types with a known
2492 -- size of 16, 32, or 64 bits whose alignment is not yet set.
2493 -- For these types, we set a corresponding alignment matching
2494 -- the size if possible, or as large as possible if not.
2496 if Convention
(E
) = Convention_Ada
2497 and then not Debug_Flag_Q
2499 Set_Composite_Alignment
(E
);
2502 -- Procressing for array types
2504 elsif Is_Array_Type
(E
) then
2506 -- For arrays that are required to be atomic, we do the same
2507 -- processing as described above for short records, since we
2508 -- really need to have the alignment set for the whole array.
2510 if Is_Atomic
(E
) and then not Debug_Flag_Q
then
2511 Set_Composite_Alignment
(E
);
2514 -- For unpacked array types, set an alignment of 1 if we know
2515 -- that the component alignment is not greater than 1. The reason
2516 -- we do this is to avoid unnecessary copying of slices of such
2517 -- arrays when passed to subprogram parameters (see special test
2518 -- in Exp_Ch6.Expand_Actuals).
2520 if not Is_Packed
(E
)
2521 and then Unknown_Alignment
(E
)
2523 if Known_Static_Component_Size
(E
)
2524 and then Component_Size
(E
) = 1
2526 Set_Alignment
(E
, Uint_1
);
2532 -- Final step is to check that Esize and RM_Size are compatible
2534 if Known_Static_Esize
(E
) and then Known_Static_RM_Size
(E
) then
2535 if Esize
(E
) < RM_Size
(E
) then
2537 -- Esize is less than RM_Size. That's not good. First we test
2538 -- whether this was set deliberately with an Object_Size clause
2539 -- and if so, object to the clause.
2541 if Has_Object_Size_Clause
(E
) then
2542 Error_Msg_Uint_1
:= RM_Size
(E
);
2544 ("object size is too small, minimum is ^",
2545 Expression
(Get_Attribute_Definition_Clause
2546 (E
, Attribute_Object_Size
)));
2549 -- Adjust Esize up to RM_Size value
2552 Size
: constant Uint
:= RM_Size
(E
);
2555 Set_Esize
(E
, RM_Size
(E
));
2557 -- For scalar types, increase Object_Size to power of 2,
2558 -- but not less than a storage unit in any case (i.e.,
2559 -- normally this means it will be byte addressable).
2561 if Is_Scalar_Type
(E
) then
2562 if Size
<= System_Storage_Unit
then
2563 Init_Esize
(E
, System_Storage_Unit
);
2564 elsif Size
<= 16 then
2566 elsif Size
<= 32 then
2569 Set_Esize
(E
, (Size
+ 63) / 64 * 64);
2572 -- Finally, make sure that alignment is consistent with
2573 -- the newly assigned size.
2575 while Alignment
(E
) * System_Storage_Unit
< Esize
(E
)
2576 and then Alignment
(E
) < Maximum_Alignment
2578 Set_Alignment
(E
, 2 * Alignment
(E
));
2586 ---------------------
2587 -- Rewrite_Integer --
2588 ---------------------
2590 procedure Rewrite_Integer
(N
: Node_Id
; V
: Uint
) is
2591 Loc
: constant Source_Ptr
:= Sloc
(N
);
2592 Typ
: constant Entity_Id
:= Etype
(N
);
2595 Rewrite
(N
, Make_Integer_Literal
(Loc
, Intval
=> V
));
2597 end Rewrite_Integer
;
2599 -------------------------------
2600 -- Set_And_Check_Static_Size --
2601 -------------------------------
2603 procedure Set_And_Check_Static_Size
2610 procedure Check_Size_Too_Small
(Spec
: Uint
; Min
: Uint
);
2611 -- Spec is the number of bit specified in the size clause, and
2612 -- Min is the minimum computed size. An error is given that the
2613 -- specified size is too small if Spec < Min, and in this case
2614 -- both Esize and RM_Size are set to unknown in E. The error
2615 -- message is posted on node SC.
2617 procedure Check_Unused_Bits
(Spec
: Uint
; Max
: Uint
);
2618 -- Spec is the number of bits specified in the size clause, and
2619 -- Max is the maximum computed size. A warning is given about
2620 -- unused bits if Spec > Max. This warning is posted on node SC.
2622 --------------------------
2623 -- Check_Size_Too_Small --
2624 --------------------------
2626 procedure Check_Size_Too_Small
(Spec
: Uint
; Min
: Uint
) is
2629 Error_Msg_Uint_1
:= Min
;
2631 ("size for & too small, minimum allowed is ^", SC
, E
);
2635 end Check_Size_Too_Small
;
2637 -----------------------
2638 -- Check_Unused_Bits --
2639 -----------------------
2641 procedure Check_Unused_Bits
(Spec
: Uint
; Max
: Uint
) is
2644 Error_Msg_Uint_1
:= Spec
- Max
;
2645 Error_Msg_NE
("?^ bits of & unused", SC
, E
);
2647 end Check_Unused_Bits
;
2649 -- Start of processing for Set_And_Check_Static_Size
2652 -- Case where Object_Size (Esize) is already set by a size clause
2654 if Known_Static_Esize
(E
) then
2655 SC
:= Size_Clause
(E
);
2658 SC
:= Get_Attribute_Definition_Clause
(E
, Attribute_Object_Size
);
2661 -- Perform checks on specified size against computed sizes
2663 if Present
(SC
) then
2664 Check_Unused_Bits
(Esize
(E
), Esiz
);
2665 Check_Size_Too_Small
(Esize
(E
), RM_Siz
);
2669 -- Case where Value_Size (RM_Size) is set by specific Value_Size
2670 -- clause (we do not need to worry about Value_Size being set by
2671 -- a Size clause, since that will have set Esize as well, and we
2672 -- already took care of that case).
2674 if Known_Static_RM_Size
(E
) then
2675 SC
:= Get_Attribute_Definition_Clause
(E
, Attribute_Value_Size
);
2677 -- Perform checks on specified size against computed sizes
2679 if Present
(SC
) then
2680 Check_Unused_Bits
(RM_Size
(E
), Esiz
);
2681 Check_Size_Too_Small
(RM_Size
(E
), RM_Siz
);
2685 -- Set sizes if unknown
2687 if Unknown_Esize
(E
) then
2688 Set_Esize
(E
, Esiz
);
2691 if Unknown_RM_Size
(E
) then
2692 Set_RM_Size
(E
, RM_Siz
);
2694 end Set_And_Check_Static_Size
;
2696 -----------------------------
2697 -- Set_Composite_Alignment --
2698 -----------------------------
2700 procedure Set_Composite_Alignment
(E
: Entity_Id
) is
2705 if Unknown_Alignment
(E
) then
2706 if Known_Static_Esize
(E
) then
2709 elsif Unknown_Esize
(E
)
2710 and then Known_Static_RM_Size
(E
)
2718 -- Size is known, alignment is not set
2720 -- Reset alignment to match size if size is exactly 2, 4, or 8 bytes
2722 if Siz
= 2 * System_Storage_Unit
then
2724 elsif Siz
= 4 * System_Storage_Unit
then
2726 elsif Siz
= 8 * System_Storage_Unit
then
2729 -- On VMS, also reset for odd "in between" sizes, e.g. a 17-bit
2730 -- record is given an alignment of 4. This is more consistent with
2731 -- what DEC Ada does.
2733 elsif OpenVMS_On_Target
and then Siz
> System_Storage_Unit
then
2735 if Siz
<= 2 * System_Storage_Unit
then
2737 elsif Siz
<= 4 * System_Storage_Unit
then
2739 elsif Siz
<= 8 * System_Storage_Unit
then
2745 -- No special alignment fiddling needed
2751 -- Here Align is set to the proposed improved alignment
2753 if Align
> Maximum_Alignment
then
2754 Align
:= Maximum_Alignment
;
2757 -- Further processing for record types only to reduce the alignment
2758 -- set by the above processing in some specific cases. We do not
2759 -- do this for atomic records, since we need max alignment there.
2761 if Is_Record_Type
(E
) then
2763 -- For records, there is generally no point in setting alignment
2764 -- higher than word size since we cannot do better than move by
2765 -- words in any case
2767 if Align
> System_Word_Size
/ System_Storage_Unit
then
2768 Align
:= System_Word_Size
/ System_Storage_Unit
;
2771 -- Check components. If any component requires a higher
2772 -- alignment, then we set that higher alignment in any case.
2778 Comp
:= First_Component
(E
);
2779 while Present
(Comp
) loop
2780 if Known_Alignment
(Etype
(Comp
)) then
2782 Calign
: constant Uint
:= Alignment
(Etype
(Comp
));
2785 -- The cases to worry about are when the alignment
2786 -- of the component type is larger than the alignment
2787 -- we have so far, and either there is no component
2788 -- clause for the alignment, or the length set by
2789 -- the component clause matches the alignment set.
2793 (Unknown_Esize
(Comp
)
2794 or else (Known_Static_Esize
(Comp
)
2797 Calign
* System_Storage_Unit
))
2799 Align
:= UI_To_Int
(Calign
);
2804 Next_Component
(Comp
);
2809 -- Set chosen alignment
2811 Set_Alignment
(E
, UI_From_Int
(Align
));
2813 if Known_Static_Esize
(E
)
2814 and then Esize
(E
) < Align
* System_Storage_Unit
2816 Set_Esize
(E
, UI_From_Int
(Align
* System_Storage_Unit
));
2819 end Set_Composite_Alignment
;
2821 --------------------------
2822 -- Set_Discrete_RM_Size --
2823 --------------------------
2825 procedure Set_Discrete_RM_Size
(Def_Id
: Entity_Id
) is
2826 FST
: constant Entity_Id
:= First_Subtype
(Def_Id
);
2829 -- All discrete types except for the base types in standard
2830 -- are constrained, so indicate this by setting Is_Constrained.
2832 Set_Is_Constrained
(Def_Id
);
2834 -- We set generic types to have an unknown size, since the
2835 -- representation of a generic type is irrelevant, in view
2836 -- of the fact that they have nothing to do with code.
2838 if Is_Generic_Type
(Root_Type
(FST
)) then
2839 Set_RM_Size
(Def_Id
, Uint_0
);
2841 -- If the subtype statically matches the first subtype, then
2842 -- it is required to have exactly the same layout. This is
2843 -- required by aliasing considerations.
2845 elsif Def_Id
/= FST
and then
2846 Subtypes_Statically_Match
(Def_Id
, FST
)
2848 Set_RM_Size
(Def_Id
, RM_Size
(FST
));
2849 Set_Size_Info
(Def_Id
, FST
);
2851 -- In all other cases the RM_Size is set to the minimum size.
2852 -- Note that this routine is never called for subtypes for which
2853 -- the RM_Size is set explicitly by an attribute clause.
2856 Set_RM_Size
(Def_Id
, UI_From_Int
(Minimum_Size
(Def_Id
)));
2858 end Set_Discrete_RM_Size
;
2860 ------------------------
2861 -- Set_Elem_Alignment --
2862 ------------------------
2864 procedure Set_Elem_Alignment
(E
: Entity_Id
) is
2866 -- Do not set alignment for packed array types, unless we are doing
2867 -- front end layout, because otherwise this is always handled in the
2870 if Is_Packed_Array_Type
(E
) and then not Frontend_Layout_On_Target
then
2873 -- If there is an alignment clause, then we respect it
2875 elsif Has_Alignment_Clause
(E
) then
2878 -- If the size is not set, then don't attempt to set the alignment. This
2879 -- happens in the backend layout case for access-to-subprogram types.
2881 elsif not Known_Static_Esize
(E
) then
2884 -- For access types, do not set the alignment if the size is less than
2885 -- the allowed minimum size. This avoids cascaded error messages.
2887 elsif Is_Access_Type
(E
)
2888 and then Esize
(E
) < System_Address_Size
2893 -- Here we calculate the alignment as the largest power of two
2894 -- multiple of System.Storage_Unit that does not exceed either
2895 -- the actual size of the type, or the maximum allowed alignment.
2899 UI_To_Int
(Esize
(E
)) / SSU
;
2904 while 2 * A
<= Ttypes
.Maximum_Alignment
2910 -- Now we think we should set the alignment to A, but we
2911 -- skip this if an alignment is already set to a value
2912 -- greater than A (happens for derived types).
2914 -- However, if the alignment is known and too small it
2915 -- must be increased, this happens in a case like:
2917 -- type R is new Character;
2918 -- for R'Size use 16;
2920 -- Here the alignment inherited from Character is 1, but
2921 -- it must be increased to 2 to reflect the increased size.
2923 if Unknown_Alignment
(E
) or else Alignment
(E
) < A
then
2924 Init_Alignment
(E
, A
);
2927 end Set_Elem_Alignment
;
2929 ----------------------
2930 -- SO_Ref_From_Expr --
2931 ----------------------
2933 function SO_Ref_From_Expr
2935 Ins_Type
: Entity_Id
;
2936 Vtype
: Entity_Id
:= Empty
;
2937 Make_Func
: Boolean := False)
2938 return Dynamic_SO_Ref
2940 Loc
: constant Source_Ptr
:= Sloc
(Ins_Type
);
2942 K
: constant Entity_Id
:=
2943 Make_Defining_Identifier
(Loc
,
2944 Chars
=> New_Internal_Name
('K'));
2948 Vtype_Primary_View
: Entity_Id
;
2950 function Check_Node_V_Ref
(N
: Node_Id
) return Traverse_Result
;
2951 -- Function used to check one node for reference to V
2953 function Has_V_Ref
is new Traverse_Func
(Check_Node_V_Ref
);
2954 -- Function used to traverse tree to check for reference to V
2956 ----------------------
2957 -- Check_Node_V_Ref --
2958 ----------------------
2960 function Check_Node_V_Ref
(N
: Node_Id
) return Traverse_Result
is
2962 if Nkind
(N
) = N_Identifier
then
2963 if Chars
(N
) = Vname
then
2972 end Check_Node_V_Ref
;
2974 -- Start of processing for SO_Ref_From_Expr
2977 -- Case of expression is an integer literal, in this case we just
2978 -- return the value (which must always be non-negative, since size
2979 -- and offset values can never be negative).
2981 if Nkind
(Expr
) = N_Integer_Literal
then
2982 pragma Assert
(Intval
(Expr
) >= 0);
2983 return Intval
(Expr
);
2986 -- Case where there is a reference to V, create function
2988 if Has_V_Ref
(Expr
) = Abandon
then
2990 pragma Assert
(Present
(Vtype
));
2992 -- Check whether Vtype is a view of a private type and ensure that
2993 -- we use the primary view of the type (which is denoted by its
2994 -- Etype, whether it's the type's partial or full view entity).
2995 -- This is needed to make sure that we use the same (primary) view
2996 -- of the type for all V formals, whether the current view of the
2997 -- type is the partial or full view, so that types will always
2998 -- match on calls from one size function to another.
3000 if Has_Private_Declaration
(Vtype
) then
3001 Vtype_Primary_View
:= Etype
(Vtype
);
3003 Vtype_Primary_View
:= Vtype
;
3006 Set_Is_Discrim_SO_Function
(K
);
3009 Make_Subprogram_Body
(Loc
,
3012 Make_Function_Specification
(Loc
,
3013 Defining_Unit_Name
=> K
,
3014 Parameter_Specifications
=> New_List
(
3015 Make_Parameter_Specification
(Loc
,
3016 Defining_Identifier
=>
3017 Make_Defining_Identifier
(Loc
, Chars
=> Vname
),
3019 New_Occurrence_Of
(Vtype_Primary_View
, Loc
))),
3020 Result_Definition
=>
3021 New_Occurrence_Of
(Standard_Unsigned
, Loc
)),
3023 Declarations
=> Empty_List
,
3025 Handled_Statement_Sequence
=>
3026 Make_Handled_Sequence_Of_Statements
(Loc
,
3027 Statements
=> New_List
(
3028 Make_Return_Statement
(Loc
,
3029 Expression
=> Expr
))));
3031 -- The caller requests that the expression be encapsulated in
3032 -- a parameterless function.
3034 elsif Make_Func
then
3036 Make_Subprogram_Body
(Loc
,
3039 Make_Function_Specification
(Loc
,
3040 Defining_Unit_Name
=> K
,
3041 Parameter_Specifications
=> Empty_List
,
3042 Result_Definition
=>
3043 New_Occurrence_Of
(Standard_Unsigned
, Loc
)),
3045 Declarations
=> Empty_List
,
3047 Handled_Statement_Sequence
=>
3048 Make_Handled_Sequence_Of_Statements
(Loc
,
3049 Statements
=> New_List
(
3050 Make_Return_Statement
(Loc
, Expression
=> Expr
))));
3052 -- No reference to V and function not requested, so create a constant
3056 Make_Object_Declaration
(Loc
,
3057 Defining_Identifier
=> K
,
3058 Object_Definition
=>
3059 New_Occurrence_Of
(Standard_Unsigned
, Loc
),
3060 Constant_Present
=> True,
3061 Expression
=> Expr
);
3064 Append_Freeze_Action
(Ins_Type
, Decl
);
3066 return Create_Dynamic_SO_Ref
(K
);
3067 end SO_Ref_From_Expr
;