1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 2001-2014, 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_Case
; use Sem_Case
;
41 with Sem_Ch13
; use Sem_Ch13
;
42 with Sem_Eval
; use Sem_Eval
;
43 with Sem_Util
; use Sem_Util
;
44 with Sinfo
; use Sinfo
;
45 with Snames
; use Snames
;
46 with Stand
; use Stand
;
47 with Targparm
; use Targparm
;
48 with Tbuild
; use Tbuild
;
49 with Ttypes
; use Ttypes
;
50 with Uintp
; use Uintp
;
52 package body Layout
is
54 ------------------------
55 -- Local Declarations --
56 ------------------------
58 SSU
: constant Int
:= Ttypes
.System_Storage_Unit
;
59 -- Short hand for System_Storage_Unit
61 Vname
: constant Name_Id
:= Name_uV
;
62 -- Formal parameter name used for functions generated for size offset
63 -- values that depend on the discriminant. All such functions have the
66 -- function xxx (V : vtyp) return Unsigned is
68 -- return ... expression involving V.discrim
71 -----------------------
72 -- Local Subprograms --
73 -----------------------
78 Right_Opnd
: Node_Id
) return Node_Id
;
79 -- This is like Make_Op_Add except that it optimizes some cases knowing
80 -- that associative rearrangement is allowed for constant folding if one
81 -- of the operands is a compile time known value.
83 function Assoc_Multiply
86 Right_Opnd
: Node_Id
) return Node_Id
;
87 -- This is like Make_Op_Multiply except that it optimizes some cases
88 -- knowing that associative rearrangement is allowed for constant folding
89 -- if one of the operands is a compile time known value
91 function Assoc_Subtract
94 Right_Opnd
: Node_Id
) return Node_Id
;
95 -- This is like Make_Op_Subtract except that it optimizes some cases
96 -- knowing that associative rearrangement is allowed for constant folding
97 -- if one of the operands is a compile time known value
99 function Bits_To_SU
(N
: Node_Id
) return Node_Id
;
100 -- This is used when we cross the boundary from static sizes in bits to
101 -- dynamic sizes in storage units. If the argument N is anything other
102 -- than an integer literal, it is returned unchanged, but if it is an
103 -- integer literal, then it is taken as a size in bits, and is replaced
104 -- by the corresponding size in storage units.
106 function Compute_Length
(Lo
: Node_Id
; Hi
: Node_Id
) return Node_Id
;
107 -- Given expressions for the low bound (Lo) and the high bound (Hi),
108 -- Build an expression for the value hi-lo+1, converted to type
109 -- Standard.Unsigned. Takes care of the case where the operands
110 -- are of an enumeration type (so that the subtraction cannot be
111 -- done directly) by applying the Pos operator to Hi/Lo first.
113 procedure Compute_Size_Depends_On_Discriminant
(E
: Entity_Id
);
114 -- Given an array type or an array subtype E, compute whether its size
115 -- depends on the value of one or more discriminants and set the flag
116 -- Size_Depends_On_Discriminant accordingly. This need not be called
117 -- in front end layout mode since it does the computation on its own.
119 function Expr_From_SO_Ref
122 Comp
: Entity_Id
:= Empty
) return Node_Id
;
123 -- Given a value D from a size or offset field, return an expression
124 -- representing the value stored. If the value is known at compile time,
125 -- then an N_Integer_Literal is returned with the appropriate value. If
126 -- the value references a constant entity, then an N_Identifier node
127 -- referencing this entity is returned. If the value denotes a size
128 -- function, then returns a call node denoting the given function, with
129 -- a single actual parameter that either refers to the parameter V of
130 -- an enclosing size function (if Comp is Empty or its type doesn't match
131 -- the function's formal), or else is a selected component V.c when Comp
132 -- denotes a component c whose type matches that of the function formal.
133 -- The Loc value is used for the Sloc value of constructed notes.
135 function SO_Ref_From_Expr
137 Ins_Type
: Entity_Id
;
138 Vtype
: Entity_Id
:= Empty
;
139 Make_Func
: Boolean := False) return Dynamic_SO_Ref
;
140 -- This routine is used in the case where a size/offset value is dynamic
141 -- and is represented by the expression Expr. SO_Ref_From_Expr checks if
142 -- the Expr contains a reference to the identifier V, and if so builds
143 -- a function depending on discriminants of the formal parameter V which
144 -- is of type Vtype. Otherwise, if the parameter Make_Func is True, then
145 -- Expr will be encapsulated in a parameterless function; if Make_Func is
146 -- False, then a constant entity with the value Expr is built. The result
147 -- is a Dynamic_SO_Ref to the created entity. Note that Vtype can be
148 -- omitted if Expr does not contain any reference to V, the created entity.
149 -- The declaration created is inserted in the freeze actions of Ins_Type,
150 -- which also supplies the Sloc for created nodes. This function also takes
151 -- care of making sure that the expression is properly analyzed and
152 -- resolved (which may not be the case yet if we build the expression
155 function Get_Max_SU_Size
(E
: Entity_Id
) return Node_Id
;
156 -- E is an array type or subtype that has at least one index bound that
157 -- is the value of a record discriminant. For such an array, the function
158 -- computes an expression that yields the maximum possible size of the
159 -- array in storage units. The result is not defined for any other type,
160 -- or for arrays that do not depend on discriminants, and it is a fatal
161 -- error to call this unless Size_Depends_On_Discriminant (E) is True.
163 procedure Layout_Array_Type
(E
: Entity_Id
);
164 -- Front-end layout of non-bit-packed array type or subtype
166 procedure Layout_Record_Type
(E
: Entity_Id
);
167 -- Front-end layout of record type
169 procedure Rewrite_Integer
(N
: Node_Id
; V
: Uint
);
170 -- Rewrite node N with an integer literal whose value is V. The Sloc for
171 -- the new node is taken from N, and the type of the literal is set to a
172 -- copy of the type of N on entry.
174 procedure Set_And_Check_Static_Size
178 -- This procedure is called to check explicit given sizes (possibly stored
179 -- in the Esize and RM_Size fields of E) against computed Object_Size
180 -- (Esiz) and Value_Size (RM_Siz) values. Appropriate errors and warnings
181 -- are posted if specified sizes are inconsistent with specified sizes. On
182 -- return, Esize and RM_Size fields of E are set (either from previously
183 -- given values, or from the newly computed values, as appropriate).
185 procedure Set_Composite_Alignment
(E
: Entity_Id
);
186 -- This procedure is called for record types and subtypes, and also for
187 -- atomic array types and subtypes. If no alignment is set, and the size
188 -- is 2 or 4 (or 8 if the word size is 8), then the alignment is set to
191 ----------------------------
192 -- Adjust_Esize_Alignment --
193 ----------------------------
195 procedure Adjust_Esize_Alignment
(E
: Entity_Id
) is
200 -- Nothing to do if size unknown
202 if Unknown_Esize
(E
) then
206 -- Determine if size is constrained by an attribute definition clause
207 -- which must be obeyed. If so, we cannot increase the size in this
210 -- For a type, the issue is whether an object size clause has been set.
211 -- A normal size clause constrains only the value size (RM_Size)
214 Esize_Set
:= Has_Object_Size_Clause
(E
);
216 -- For an object, the issue is whether a size clause is present
219 Esize_Set
:= Has_Size_Clause
(E
);
222 -- If size is known it must be a multiple of the storage unit size
224 if Esize
(E
) mod SSU
/= 0 then
226 -- If not, and size specified, then give error
230 ("size for& not a multiple of storage unit size",
234 -- Otherwise bump up size to a storage unit boundary
237 Set_Esize
(E
, (Esize
(E
) + SSU
- 1) / SSU
* SSU
);
241 -- Now we have the size set, it must be a multiple of the alignment
242 -- nothing more we can do here if the alignment is unknown here.
244 if Unknown_Alignment
(E
) then
248 -- At this point both the Esize and Alignment are known, so we need
249 -- to make sure they are consistent.
251 Abits
:= UI_To_Int
(Alignment
(E
)) * SSU
;
253 if Esize
(E
) mod Abits
= 0 then
257 -- Here we have a situation where the Esize is not a multiple of the
258 -- alignment. We must either increase Esize or reduce the alignment to
259 -- correct this situation.
261 -- The case in which we can decrease the alignment is where the
262 -- alignment was not set by an alignment clause, and the type in
263 -- question is a discrete type, where it is definitely safe to reduce
264 -- the alignment. For example:
266 -- t : integer range 1 .. 2;
269 -- In this situation, the initial alignment of t is 4, copied from
270 -- the Integer base type, but it is safe to reduce it to 1 at this
271 -- stage, since we will only be loading a single storage unit.
273 if Is_Discrete_Type
(Etype
(E
)) and then not Has_Alignment_Clause
(E
)
277 exit when Esize
(E
) mod Abits
= 0;
280 Init_Alignment
(E
, Abits
/ SSU
);
284 -- Now the only possible approach left is to increase the Esize but we
285 -- can't do that if the size was set by a specific clause.
289 ("size for& is not a multiple of alignment",
292 -- Otherwise we can indeed increase the size to a multiple of alignment
295 Set_Esize
(E
, ((Esize
(E
) + (Abits
- 1)) / Abits
) * Abits
);
297 end Adjust_Esize_Alignment
;
306 Right_Opnd
: Node_Id
) return Node_Id
312 -- Case of right operand is a constant
314 if Compile_Time_Known_Value
(Right_Opnd
) then
316 R
:= Expr_Value
(Right_Opnd
);
318 -- Case of left operand is a constant
320 elsif Compile_Time_Known_Value
(Left_Opnd
) then
322 R
:= Expr_Value
(Left_Opnd
);
324 -- Neither operand is a constant, do the addition with no optimization
327 return Make_Op_Add
(Loc
, Left_Opnd
, Right_Opnd
);
330 -- Case of left operand is an addition
332 if Nkind
(L
) = N_Op_Add
then
334 -- (C1 + E) + C2 = (C1 + C2) + E
336 if Compile_Time_Known_Value
(Sinfo
.Left_Opnd
(L
)) then
338 (Sinfo
.Left_Opnd
(L
),
339 Expr_Value
(Sinfo
.Left_Opnd
(L
)) + R
);
342 -- (E + C1) + C2 = E + (C1 + C2)
344 elsif Compile_Time_Known_Value
(Sinfo
.Right_Opnd
(L
)) then
346 (Sinfo
.Right_Opnd
(L
),
347 Expr_Value
(Sinfo
.Right_Opnd
(L
)) + R
);
351 -- Case of left operand is a subtraction
353 elsif Nkind
(L
) = N_Op_Subtract
then
355 -- (C1 - E) + C2 = (C1 + C2) - E
357 if Compile_Time_Known_Value
(Sinfo
.Left_Opnd
(L
)) then
359 (Sinfo
.Left_Opnd
(L
),
360 Expr_Value
(Sinfo
.Left_Opnd
(L
)) + R
);
363 -- (E - C1) + C2 = E - (C1 - C2)
365 -- If the type is unsigned then only do the optimization if C1 >= C2,
366 -- to avoid creating a negative literal that can't be used with the
369 elsif Compile_Time_Known_Value
(Sinfo
.Right_Opnd
(L
))
370 and then (not Is_Unsigned_Type
(Etype
(Sinfo
.Right_Opnd
(L
)))
371 or else Expr_Value
(Sinfo
.Right_Opnd
(L
)) >= R
)
374 (Sinfo
.Right_Opnd
(L
),
375 Expr_Value
(Sinfo
.Right_Opnd
(L
)) - R
);
380 -- Not optimizable, do the addition
382 return Make_Op_Add
(Loc
, Left_Opnd
, Right_Opnd
);
389 function Assoc_Multiply
392 Right_Opnd
: Node_Id
) return Node_Id
398 -- Case of right operand is a constant
400 if Compile_Time_Known_Value
(Right_Opnd
) then
402 R
:= Expr_Value
(Right_Opnd
);
404 -- Case of left operand is a constant
406 elsif Compile_Time_Known_Value
(Left_Opnd
) then
408 R
:= Expr_Value
(Left_Opnd
);
410 -- Neither operand is a constant, do the multiply with no optimization
413 return Make_Op_Multiply
(Loc
, Left_Opnd
, Right_Opnd
);
416 -- Case of left operand is an multiplication
418 if Nkind
(L
) = N_Op_Multiply
then
420 -- (C1 * E) * C2 = (C1 * C2) + E
422 if Compile_Time_Known_Value
(Sinfo
.Left_Opnd
(L
)) then
424 (Sinfo
.Left_Opnd
(L
),
425 Expr_Value
(Sinfo
.Left_Opnd
(L
)) * R
);
428 -- (E * C1) * C2 = E * (C1 * C2)
430 elsif Compile_Time_Known_Value
(Sinfo
.Right_Opnd
(L
)) then
432 (Sinfo
.Right_Opnd
(L
),
433 Expr_Value
(Sinfo
.Right_Opnd
(L
)) * R
);
438 -- Not optimizable, do the multiplication
440 return Make_Op_Multiply
(Loc
, Left_Opnd
, Right_Opnd
);
447 function Assoc_Subtract
450 Right_Opnd
: Node_Id
) return Node_Id
456 -- Case of right operand is a constant
458 if Compile_Time_Known_Value
(Right_Opnd
) then
460 R
:= Expr_Value
(Right_Opnd
);
462 -- Right operand is a constant, do the subtract with no optimization
465 return Make_Op_Subtract
(Loc
, Left_Opnd
, Right_Opnd
);
468 -- Case of left operand is an addition
470 if Nkind
(L
) = N_Op_Add
then
472 -- (C1 + E) - C2 = (C1 - C2) + E
474 if Compile_Time_Known_Value
(Sinfo
.Left_Opnd
(L
)) then
476 (Sinfo
.Left_Opnd
(L
),
477 Expr_Value
(Sinfo
.Left_Opnd
(L
)) - R
);
480 -- (E + C1) - C2 = E + (C1 - C2)
482 elsif Compile_Time_Known_Value
(Sinfo
.Right_Opnd
(L
)) then
484 (Sinfo
.Right_Opnd
(L
),
485 Expr_Value
(Sinfo
.Right_Opnd
(L
)) - R
);
489 -- Case of left operand is a subtraction
491 elsif Nkind
(L
) = N_Op_Subtract
then
493 -- (C1 - E) - C2 = (C1 - C2) + E
495 if Compile_Time_Known_Value
(Sinfo
.Left_Opnd
(L
)) then
497 (Sinfo
.Left_Opnd
(L
),
498 Expr_Value
(Sinfo
.Left_Opnd
(L
)) + R
);
501 -- (E - C1) - C2 = E - (C1 + C2)
503 elsif Compile_Time_Known_Value
(Sinfo
.Right_Opnd
(L
)) then
505 (Sinfo
.Right_Opnd
(L
),
506 Expr_Value
(Sinfo
.Right_Opnd
(L
)) + R
);
511 -- Not optimizable, do the subtraction
513 return Make_Op_Subtract
(Loc
, Left_Opnd
, Right_Opnd
);
520 function Bits_To_SU
(N
: Node_Id
) return Node_Id
is
522 if Nkind
(N
) = N_Integer_Literal
then
523 Set_Intval
(N
, (Intval
(N
) + (SSU
- 1)) / SSU
);
533 function Compute_Length
(Lo
: Node_Id
; Hi
: Node_Id
) return Node_Id
is
534 Loc
: constant Source_Ptr
:= Sloc
(Lo
);
535 Typ
: constant Entity_Id
:= Etype
(Lo
);
542 -- If the bounds are First and Last attributes for the same dimension
543 -- and both have prefixes that denotes the same entity, then we create
544 -- and return a Length attribute. This may allow the back end to
545 -- generate better code in cases where it already has the length.
547 if Nkind
(Lo
) = N_Attribute_Reference
548 and then Attribute_Name
(Lo
) = Name_First
549 and then Nkind
(Hi
) = N_Attribute_Reference
550 and then Attribute_Name
(Hi
) = Name_Last
551 and then Is_Entity_Name
(Prefix
(Lo
))
552 and then Is_Entity_Name
(Prefix
(Hi
))
553 and then Entity
(Prefix
(Lo
)) = Entity
(Prefix
(Hi
))
558 if Present
(First
(Expressions
(Lo
))) then
559 Lo_Dim
:= Expr_Value
(First
(Expressions
(Lo
)));
562 if Present
(First
(Expressions
(Hi
))) then
563 Hi_Dim
:= Expr_Value
(First
(Expressions
(Hi
)));
566 if Lo_Dim
= Hi_Dim
then
568 Make_Attribute_Reference
(Loc
,
569 Prefix
=> New_Occurrence_Of
570 (Entity
(Prefix
(Lo
)), Loc
),
571 Attribute_Name
=> Name_Length
,
572 Expressions
=> New_List
573 (Make_Integer_Literal
(Loc
, Lo_Dim
)));
577 Lo_Op
:= New_Copy_Tree
(Lo
);
578 Hi_Op
:= New_Copy_Tree
(Hi
);
580 -- If type is enumeration type, then use Pos attribute to convert
581 -- to integer type for which subtraction is a permitted operation.
583 if Is_Enumeration_Type
(Typ
) then
585 Make_Attribute_Reference
(Loc
,
586 Prefix
=> New_Occurrence_Of
(Typ
, Loc
),
587 Attribute_Name
=> Name_Pos
,
588 Expressions
=> New_List
(Lo_Op
));
591 Make_Attribute_Reference
(Loc
,
592 Prefix
=> New_Occurrence_Of
(Typ
, Loc
),
593 Attribute_Name
=> Name_Pos
,
594 Expressions
=> New_List
(Hi_Op
));
602 Right_Opnd
=> Lo_Op
),
603 Right_Opnd
=> Make_Integer_Literal
(Loc
, 1));
606 ----------------------
607 -- Expr_From_SO_Ref --
608 ----------------------
610 function Expr_From_SO_Ref
613 Comp
: Entity_Id
:= Empty
) return Node_Id
618 if Is_Dynamic_SO_Ref
(D
) then
619 Ent
:= Get_Dynamic_SO_Entity
(D
);
621 if Is_Discrim_SO_Function
(Ent
) then
623 -- If a component is passed in whose type matches the type of
624 -- the function formal, then select that component from the "V"
625 -- parameter rather than passing "V" directly.
628 and then Base_Type
(Etype
(Comp
)) =
629 Base_Type
(Etype
(First_Formal
(Ent
)))
632 Make_Function_Call
(Loc
,
633 Name
=> New_Occurrence_Of
(Ent
, Loc
),
634 Parameter_Associations
=> New_List
(
635 Make_Selected_Component
(Loc
,
636 Prefix
=> Make_Identifier
(Loc
, Vname
),
637 Selector_Name
=> New_Occurrence_Of
(Comp
, Loc
))));
641 Make_Function_Call
(Loc
,
642 Name
=> New_Occurrence_Of
(Ent
, Loc
),
643 Parameter_Associations
=> New_List
(
644 Make_Identifier
(Loc
, Vname
)));
648 return New_Occurrence_Of
(Ent
, Loc
);
652 return Make_Integer_Literal
(Loc
, D
);
654 end Expr_From_SO_Ref
;
656 ---------------------
657 -- Get_Max_SU_Size --
658 ---------------------
660 function Get_Max_SU_Size
(E
: Entity_Id
) return Node_Id
is
661 Loc
: constant Source_Ptr
:= Sloc
(E
);
669 type Val_Status_Type
is (Const
, Dynamic
);
671 type Val_Type
(Status
: Val_Status_Type
:= Const
) is
674 when Const
=> Val
: Uint
;
675 when Dynamic
=> Nod
: Node_Id
;
678 -- Shows the status of the value so far. Const means that the value is
679 -- constant, and Val is the current constant value. Dynamic means that
680 -- the value is dynamic, and in this case Nod is the Node_Id of the
681 -- expression to compute the value.
684 -- Calculated value so far if Size.Status = Const,
685 -- or expression value so far if Size.Status = Dynamic.
687 SU_Convert_Required
: Boolean := False;
688 -- This is set to True if the final result must be converted from bits
689 -- to storage units (rounding up to a storage unit boundary).
691 -----------------------
692 -- Local Subprograms --
693 -----------------------
695 procedure Max_Discrim
(N
: in out Node_Id
);
696 -- If the node N represents a discriminant, replace it by the maximum
697 -- value of the discriminant.
699 procedure Min_Discrim
(N
: in out Node_Id
);
700 -- If the node N represents a discriminant, replace it by the minimum
701 -- value of the discriminant.
707 procedure Max_Discrim
(N
: in out Node_Id
) is
709 if Nkind
(N
) = N_Identifier
710 and then Ekind
(Entity
(N
)) = E_Discriminant
712 N
:= Type_High_Bound
(Etype
(N
));
720 procedure Min_Discrim
(N
: in out Node_Id
) is
722 if Nkind
(N
) = N_Identifier
723 and then Ekind
(Entity
(N
)) = E_Discriminant
725 N
:= Type_Low_Bound
(Etype
(N
));
729 -- Start of processing for Get_Max_SU_Size
732 pragma Assert
(Size_Depends_On_Discriminant
(E
));
734 -- Initialize status from component size
736 if Known_Static_Component_Size
(E
) then
737 Size
:= (Const
, Component_Size
(E
));
740 Size
:= (Dynamic
, Expr_From_SO_Ref
(Loc
, Component_Size
(E
)));
743 -- Loop through indexes
745 Indx
:= First_Index
(E
);
746 while Present
(Indx
) loop
747 Ityp
:= Etype
(Indx
);
748 Lo
:= Type_Low_Bound
(Ityp
);
749 Hi
:= Type_High_Bound
(Ityp
);
754 -- Value of the current subscript range is statically known
756 if Compile_Time_Known_Value
(Lo
)
758 Compile_Time_Known_Value
(Hi
)
760 S
:= Expr_Value
(Hi
) - Expr_Value
(Lo
) + 1;
762 -- If known flat bound, entire size of array is zero
765 return Make_Integer_Literal
(Loc
, 0);
768 -- Current value is constant, evolve value
770 if Size
.Status
= Const
then
771 Size
.Val
:= Size
.Val
* S
;
773 -- Current value is dynamic
776 -- An interesting little optimization, if we have a pending
777 -- conversion from bits to storage units, and the current
778 -- length is a multiple of the storage unit size, then we
779 -- can take the factor out here statically, avoiding some
780 -- extra dynamic computations at the end.
782 if SU_Convert_Required
and then S
mod SSU
= 0 then
784 SU_Convert_Required
:= False;
789 Left_Opnd
=> Size
.Nod
,
791 Make_Integer_Literal
(Loc
, Intval
=> S
));
794 -- Value of the current subscript range is dynamic
797 -- If the current size value is constant, then here is where we
798 -- make a transition to dynamic values, which are always stored
799 -- in storage units, However, we do not want to convert to SU's
800 -- too soon, consider the case of a packed array of single bits,
801 -- we want to do the SU conversion after computing the size in
804 if Size
.Status
= Const
then
806 -- If the current value is a multiple of the storage unit,
807 -- then most certainly we can do the conversion now, simply
808 -- by dividing the current value by the storage unit value.
809 -- If this works, we set SU_Convert_Required to False.
811 if Size
.Val
mod SSU
= 0 then
814 (Dynamic
, Make_Integer_Literal
(Loc
, Size
.Val
/ SSU
));
815 SU_Convert_Required
:= False;
817 -- Otherwise, we go ahead and convert the value in bits, and
818 -- set SU_Convert_Required to True to ensure that the final
819 -- value is indeed properly converted.
822 Size
:= (Dynamic
, Make_Integer_Literal
(Loc
, Size
.Val
));
823 SU_Convert_Required
:= True;
829 Len
:= Compute_Length
(Lo
, Hi
);
831 -- Check possible range of Len
837 pragma Warnings
(Off
, LHi
);
841 Determine_Range
(Len
, OK
, LLo
, LHi
);
843 Len
:= Convert_To
(Standard_Unsigned
, Len
);
845 -- If we cannot verify that range cannot be super-flat, we need
846 -- a max with zero, since length must be non-negative.
848 if not OK
or else LLo
< 0 then
850 Make_Attribute_Reference
(Loc
,
852 New_Occurrence_Of
(Standard_Unsigned
, Loc
),
853 Attribute_Name
=> Name_Max
,
854 Expressions
=> New_List
(
855 Make_Integer_Literal
(Loc
, 0),
864 -- Here after processing all bounds to set sizes. If the value is a
865 -- constant, then it is bits, so we convert to storage units.
867 if Size
.Status
= Const
then
868 return Bits_To_SU
(Make_Integer_Literal
(Loc
, Size
.Val
));
870 -- Case where the value is dynamic
873 -- Do convert from bits to SU's if needed
875 if SU_Convert_Required
then
877 -- The expression required is (Size.Nod + SU - 1) / SU
883 Left_Opnd
=> Size
.Nod
,
884 Right_Opnd
=> Make_Integer_Literal
(Loc
, SSU
- 1)),
885 Right_Opnd
=> Make_Integer_Literal
(Loc
, SSU
));
892 -----------------------
893 -- Layout_Array_Type --
894 -----------------------
896 procedure Layout_Array_Type
(E
: Entity_Id
) is
897 Loc
: constant Source_Ptr
:= Sloc
(E
);
898 Ctyp
: constant Entity_Id
:= Component_Type
(E
);
906 Insert_Typ
: Entity_Id
;
907 -- This is the type with which any generated constants or functions
908 -- will be associated (i.e. inserted into the freeze actions). This
909 -- is normally the type being laid out. The exception occurs when
910 -- we are laying out Itype's which are local to a record type, and
911 -- whose scope is this record type. Such types do not have freeze
912 -- nodes (because we have no place to put them).
914 ------------------------------------
915 -- How An Array Type is Laid Out --
916 ------------------------------------
918 -- Here is what goes on. We need to multiply the component size of the
919 -- array (which has already been set) by the length of each of the
920 -- indexes. If all these values are known at compile time, then the
921 -- resulting size of the array is the appropriate constant value.
923 -- If the component size or at least one bound is dynamic (but no
924 -- discriminants are present), then the size will be computed as an
925 -- expression that calculates the proper size.
927 -- If there is at least one discriminant bound, then the size is also
928 -- computed as an expression, but this expression contains discriminant
929 -- values which are obtained by selecting from a function parameter, and
930 -- the size is given by a function that is passed the variant record in
931 -- question, and whose body is the expression.
933 type Val_Status_Type
is (Const
, Dynamic
, Discrim
);
935 type Val_Type
(Status
: Val_Status_Type
:= Const
) is
940 -- Calculated value so far if Val_Status = Const
942 when Dynamic | Discrim
=>
944 -- Expression value so far if Val_Status /= Const
948 -- Records the value or expression computed so far. Const means that
949 -- the value is constant, and Val is the current constant value.
950 -- Dynamic means that the value is dynamic, and in this case Nod is
951 -- the Node_Id of the expression to compute the value, and Discrim
952 -- means that at least one bound is a discriminant, in which case Nod
953 -- is the expression so far (which will be the body of the function).
956 -- Value of size computed so far. See comments above
958 Vtyp
: Entity_Id
:= Empty
;
959 -- Variant record type for the formal parameter of the discriminant
960 -- function V if Status = Discrim.
962 SU_Convert_Required
: Boolean := False;
963 -- This is set to True if the final result must be converted from
964 -- bits to storage units (rounding up to a storage unit boundary).
966 Storage_Divisor
: Uint
:= UI_From_Int
(SSU
);
967 -- This is the amount that a nonstatic computed size will be divided
968 -- by to convert it from bits to storage units. This is normally
969 -- equal to SSU, but can be reduced in the case of packed components
970 -- that fit evenly into a storage unit.
972 Make_Size_Function
: Boolean := False;
973 -- Indicates whether to request that SO_Ref_From_Expr should
974 -- encapsulate the array size expression in a function.
976 procedure Discrimify
(N
: in out Node_Id
);
977 -- If N represents a discriminant, then the Size.Status is set to
978 -- Discrim, and Vtyp is set. The parameter N is replaced with the
979 -- proper expression to extract the discriminant value from V.
985 procedure Discrimify
(N
: in out Node_Id
) is
990 if Nkind
(N
) = N_Identifier
991 and then Ekind
(Entity
(N
)) = E_Discriminant
993 Set_Size_Depends_On_Discriminant
(E
);
995 if Size
.Status
/= Discrim
then
996 Decl
:= Parent
(Parent
(Entity
(N
)));
997 Size
:= (Discrim
, Size
.Nod
);
998 Vtyp
:= Defining_Identifier
(Decl
);
1004 Make_Selected_Component
(Loc
,
1005 Prefix
=> Make_Identifier
(Loc
, Vname
),
1006 Selector_Name
=> New_Occurrence_Of
(Entity
(N
), Loc
));
1008 -- Set the Etype attributes of the selected name and its prefix.
1009 -- Analyze_And_Resolve can't be called here because the Vname
1010 -- entity denoted by the prefix will not yet exist (it's created
1011 -- by SO_Ref_From_Expr, called at the end of Layout_Array_Type).
1013 Set_Etype
(Prefix
(N
), Vtyp
);
1018 -- Start of processing for Layout_Array_Type
1021 -- Default alignment is component alignment
1023 if Unknown_Alignment
(E
) then
1024 Set_Alignment
(E
, Alignment
(Ctyp
));
1027 -- Calculate proper type for insertions
1029 if Is_Record_Type
(Underlying_Type
(Scope
(E
))) then
1030 Insert_Typ
:= Underlying_Type
(Scope
(E
));
1035 -- If the component type is a generic formal type then there's no point
1036 -- in determining a size for the array type.
1038 if Is_Generic_Type
(Ctyp
) then
1042 -- Deal with component size if base type
1044 if Ekind
(E
) = E_Array_Type
then
1046 -- Cannot do anything if Esize of component type unknown
1048 if Unknown_Esize
(Ctyp
) then
1052 -- Set component size if not set already
1054 if Unknown_Component_Size
(E
) then
1055 Set_Component_Size
(E
, Esize
(Ctyp
));
1059 -- (RM 13.3 (48)) says that the size of an unconstrained array
1060 -- is implementation defined. We choose to leave it as Unknown
1061 -- here, and the actual behavior is determined by the back end.
1063 if not Is_Constrained
(E
) then
1067 -- Initialize status from component size
1069 if Known_Static_Component_Size
(E
) then
1070 Size
:= (Const
, Component_Size
(E
));
1073 Size
:= (Dynamic
, Expr_From_SO_Ref
(Loc
, Component_Size
(E
)));
1076 -- Loop to process array indexes
1078 Indx
:= First_Index
(E
);
1079 while Present
(Indx
) loop
1080 Ityp
:= Etype
(Indx
);
1082 -- If an index of the array is a generic formal type then there is
1083 -- no point in determining a size for the array type.
1085 if Is_Generic_Type
(Ityp
) then
1089 Lo
:= Type_Low_Bound
(Ityp
);
1090 Hi
:= Type_High_Bound
(Ityp
);
1092 -- Value of the current subscript range is statically known
1094 if Compile_Time_Known_Value
(Lo
)
1096 Compile_Time_Known_Value
(Hi
)
1098 S
:= Expr_Value
(Hi
) - Expr_Value
(Lo
) + 1;
1100 -- If known flat bound, entire size of array is zero
1103 Set_Esize
(E
, Uint_0
);
1104 Set_RM_Size
(E
, Uint_0
);
1108 -- If constant, evolve value
1110 if Size
.Status
= Const
then
1111 Size
.Val
:= Size
.Val
* S
;
1113 -- Current value is dynamic
1116 -- An interesting little optimization, if we have a pending
1117 -- conversion from bits to storage units, and the current
1118 -- length is a multiple of the storage unit size, then we
1119 -- can take the factor out here statically, avoiding some
1120 -- extra dynamic computations at the end.
1122 if SU_Convert_Required
and then S
mod SSU
= 0 then
1124 SU_Convert_Required
:= False;
1127 -- Now go ahead and evolve the expression
1130 Assoc_Multiply
(Loc
,
1131 Left_Opnd
=> Size
.Nod
,
1133 Make_Integer_Literal
(Loc
, Intval
=> S
));
1136 -- Value of the current subscript range is dynamic
1139 -- If the current size value is constant, then here is where we
1140 -- make a transition to dynamic values, which are always stored
1141 -- in storage units, However, we do not want to convert to SU's
1142 -- too soon, consider the case of a packed array of single bits,
1143 -- we want to do the SU conversion after computing the size in
1146 if Size
.Status
= Const
then
1148 -- If the current value is a multiple of the storage unit,
1149 -- then most certainly we can do the conversion now, simply
1150 -- by dividing the current value by the storage unit value.
1151 -- If this works, we set SU_Convert_Required to False.
1153 if Size
.Val
mod SSU
= 0 then
1155 (Dynamic
, Make_Integer_Literal
(Loc
, Size
.Val
/ SSU
));
1156 SU_Convert_Required
:= False;
1158 -- If the current value is a factor of the storage unit, then
1159 -- we can use a value of one for the size and reduce the
1160 -- strength of the later division.
1162 elsif SSU
mod Size
.Val
= 0 then
1163 Storage_Divisor
:= SSU
/ Size
.Val
;
1164 Size
:= (Dynamic
, Make_Integer_Literal
(Loc
, Uint_1
));
1165 SU_Convert_Required
:= True;
1167 -- Otherwise, we go ahead and convert the value in bits, and
1168 -- set SU_Convert_Required to True to ensure that the final
1169 -- value is indeed properly converted.
1172 Size
:= (Dynamic
, Make_Integer_Literal
(Loc
, Size
.Val
));
1173 SU_Convert_Required
:= True;
1180 -- Length is hi-lo+1
1182 Len
:= Compute_Length
(Lo
, Hi
);
1184 -- If Len isn't a Length attribute, then its range needs to be
1185 -- checked a possible Max with zero needs to be computed.
1187 if Nkind
(Len
) /= N_Attribute_Reference
1188 or else Attribute_Name
(Len
) /= Name_Length
1196 -- Check possible range of Len
1198 Set_Parent
(Len
, E
);
1199 Determine_Range
(Len
, OK
, LLo
, LHi
);
1201 Len
:= Convert_To
(Standard_Unsigned
, Len
);
1203 -- If range definitely flat or superflat, result size is 0
1205 if OK
and then LHi
<= 0 then
1206 Set_Esize
(E
, Uint_0
);
1207 Set_RM_Size
(E
, Uint_0
);
1211 -- If we cannot verify that range cannot be super-flat, we
1212 -- need a max with zero, since length cannot be negative.
1214 if not OK
or else LLo
< 0 then
1216 Make_Attribute_Reference
(Loc
,
1218 New_Occurrence_Of
(Standard_Unsigned
, Loc
),
1219 Attribute_Name
=> Name_Max
,
1220 Expressions
=> New_List
(
1221 Make_Integer_Literal
(Loc
, 0),
1227 -- At this stage, Len has the expression for the length
1230 Assoc_Multiply
(Loc
,
1231 Left_Opnd
=> Size
.Nod
,
1238 -- Here after processing all bounds to set sizes. If the value is a
1239 -- constant, then it is bits, and the only thing we need to do is to
1240 -- check against explicit given size and do alignment adjust.
1242 if Size
.Status
= Const
then
1243 Set_And_Check_Static_Size
(E
, Size
.Val
, Size
.Val
);
1244 Adjust_Esize_Alignment
(E
);
1246 -- Case where the value is dynamic
1249 -- Do convert from bits to SU's if needed
1251 if SU_Convert_Required
then
1253 -- The expression required is:
1254 -- (Size.Nod + Storage_Divisor - 1) / Storage_Divisor
1257 Make_Op_Divide
(Loc
,
1260 Left_Opnd
=> Size
.Nod
,
1261 Right_Opnd
=> Make_Integer_Literal
1262 (Loc
, Storage_Divisor
- 1)),
1263 Right_Opnd
=> Make_Integer_Literal
(Loc
, Storage_Divisor
));
1266 -- If the array entity is not declared at the library level and its
1267 -- not nested within a subprogram that is marked for inlining, then
1268 -- we request that the size expression be encapsulated in a function.
1269 -- Since this expression is not needed in most cases, we prefer not
1270 -- to incur the overhead of the computation on calls to the enclosing
1271 -- subprogram except for subprograms that require the size.
1273 if not Is_Library_Level_Entity
(E
) then
1274 Make_Size_Function
:= True;
1277 Parent_Subp
: Entity_Id
:= Enclosing_Subprogram
(E
);
1280 while Present
(Parent_Subp
) loop
1281 if Is_Inlined
(Parent_Subp
) then
1282 Make_Size_Function
:= False;
1286 Parent_Subp
:= Enclosing_Subprogram
(Parent_Subp
);
1291 -- Now set the dynamic size (the Value_Size is always the same as the
1292 -- Object_Size for arrays whose length is dynamic).
1294 -- ??? If Size.Status = Dynamic, Vtyp will not have been set.
1295 -- The added initialization sets it to Empty now, but is this
1301 (Size
.Nod
, Insert_Typ
, Vtyp
, Make_Func
=> Make_Size_Function
));
1302 Set_RM_Size
(E
, Esize
(E
));
1304 end Layout_Array_Type
;
1306 ------------------------------------------
1307 -- Compute_Size_Depends_On_Discriminant --
1308 ------------------------------------------
1310 procedure Compute_Size_Depends_On_Discriminant
(E
: Entity_Id
) is
1315 Res
: Boolean := False;
1318 -- Loop to process array indexes
1320 Indx
:= First_Index
(E
);
1321 while Present
(Indx
) loop
1322 Ityp
:= Etype
(Indx
);
1324 -- If an index of the array is a generic formal type then there is
1325 -- no point in determining a size for the array type.
1327 if Is_Generic_Type
(Ityp
) then
1331 Lo
:= Type_Low_Bound
(Ityp
);
1332 Hi
:= Type_High_Bound
(Ityp
);
1334 if (Nkind
(Lo
) = N_Identifier
1335 and then Ekind
(Entity
(Lo
)) = E_Discriminant
)
1337 (Nkind
(Hi
) = N_Identifier
1338 and then Ekind
(Entity
(Hi
)) = E_Discriminant
)
1347 Set_Size_Depends_On_Discriminant
(E
);
1349 end Compute_Size_Depends_On_Discriminant
;
1355 procedure Layout_Object
(E
: Entity_Id
) is
1356 T
: constant Entity_Id
:= Etype
(E
);
1359 -- Nothing to do if backend does layout
1361 if not Frontend_Layout_On_Target
then
1365 -- Set size if not set for object and known for type. Use the RM_Size if
1366 -- that is known for the type and Esize is not.
1368 if Unknown_Esize
(E
) then
1369 if Known_Esize
(T
) then
1370 Set_Esize
(E
, Esize
(T
));
1372 elsif Known_RM_Size
(T
) then
1373 Set_Esize
(E
, RM_Size
(T
));
1377 -- Set alignment from type if unknown and type alignment known
1379 if Unknown_Alignment
(E
) and then Known_Alignment
(T
) then
1380 Set_Alignment
(E
, Alignment
(T
));
1383 -- Make sure size and alignment are consistent
1385 Adjust_Esize_Alignment
(E
);
1387 -- Final adjustment, if we don't know the alignment, and the Esize was
1388 -- not set by an explicit Object_Size attribute clause, then we reset
1389 -- the Esize to unknown, since we really don't know it.
1391 if Unknown_Alignment
(E
) and then not Has_Size_Clause
(E
) then
1392 Set_Esize
(E
, Uint_0
);
1396 ------------------------
1397 -- Layout_Record_Type --
1398 ------------------------
1400 procedure Layout_Record_Type
(E
: Entity_Id
) is
1401 Loc
: constant Source_Ptr
:= Sloc
(E
);
1405 -- Current component being laid out
1407 Prev_Comp
: Entity_Id
;
1408 -- Previous laid out component
1410 procedure Get_Next_Component_Location
1411 (Prev_Comp
: Entity_Id
;
1413 New_Npos
: out SO_Ref
;
1414 New_Fbit
: out SO_Ref
;
1415 New_NPMax
: out SO_Ref
;
1416 Force_SU
: Boolean);
1417 -- Given the previous component in Prev_Comp, which is already laid
1418 -- out, and the alignment of the following component, lays out the
1419 -- following component, and returns its starting position in New_Npos
1420 -- (Normalized_Position value), New_Fbit (Normalized_First_Bit value),
1421 -- and New_NPMax (Normalized_Position_Max value). If Prev_Comp is empty
1422 -- (no previous component is present), then New_Npos, New_Fbit and
1423 -- New_NPMax are all set to zero on return. This procedure is also
1424 -- used to compute the size of a record or variant by giving it the
1425 -- last component, and the record alignment. Force_SU is used to force
1426 -- the new component location to be aligned on a storage unit boundary,
1427 -- even in a packed record, False means that the new position does not
1428 -- need to be bumped to a storage unit boundary, True means a storage
1429 -- unit boundary is always required.
1431 procedure Layout_Component
(Comp
: Entity_Id
; Prev_Comp
: Entity_Id
);
1432 -- Lays out component Comp, given Prev_Comp, the previously laid-out
1433 -- component (Prev_Comp = Empty if no components laid out yet). The
1434 -- alignment of the record itself is also updated if needed. Both
1435 -- Comp and Prev_Comp can be either components or discriminants.
1437 procedure Layout_Components
1441 RM_Siz
: out SO_Ref
);
1442 -- This procedure lays out the components of the given component list
1443 -- which contains the components starting with From and ending with To.
1444 -- The Next_Entity chain is used to traverse the components. On entry,
1445 -- Prev_Comp is set to the component preceding the list, so that the
1446 -- list is laid out after this component. Prev_Comp is set to Empty if
1447 -- the component list is to be laid out starting at the start of the
1448 -- record. On return, the components are all laid out, and Prev_Comp is
1449 -- set to the last laid out component. On return, Esiz is set to the
1450 -- resulting Object_Size value, which is the length of the record up
1451 -- to and including the last laid out entity. For Esiz, the value is
1452 -- adjusted to match the alignment of the record. RM_Siz is similarly
1453 -- set to the resulting Value_Size value, which is the same length, but
1454 -- not adjusted to meet the alignment. Note that in the case of variant
1455 -- records, Esiz represents the maximum size.
1457 procedure Layout_Non_Variant_Record
;
1458 -- Procedure called to lay out a non-variant record type or subtype
1460 procedure Layout_Variant_Record
;
1461 -- Procedure called to lay out a variant record type. Decl is set to the
1462 -- full type declaration for the variant record.
1464 ---------------------------------
1465 -- Get_Next_Component_Location --
1466 ---------------------------------
1468 procedure Get_Next_Component_Location
1469 (Prev_Comp
: Entity_Id
;
1471 New_Npos
: out SO_Ref
;
1472 New_Fbit
: out SO_Ref
;
1473 New_NPMax
: out SO_Ref
;
1477 -- No previous component, return zero position
1479 if No
(Prev_Comp
) then
1482 New_NPMax
:= Uint_0
;
1486 -- Here we have a previous component
1489 Loc
: constant Source_Ptr
:= Sloc
(Prev_Comp
);
1491 Old_Npos
: constant SO_Ref
:= Normalized_Position
(Prev_Comp
);
1492 Old_Fbit
: constant SO_Ref
:= Normalized_First_Bit
(Prev_Comp
);
1493 Old_NPMax
: constant SO_Ref
:= Normalized_Position_Max
(Prev_Comp
);
1494 Old_Esiz
: constant SO_Ref
:= Esize
(Prev_Comp
);
1496 Old_Maxsz
: Node_Id
;
1497 -- Expression representing maximum size of previous component
1500 -- Case where previous field had a dynamic size
1502 if Is_Dynamic_SO_Ref
(Esize
(Prev_Comp
)) then
1504 -- If the previous field had a dynamic length, then it is
1505 -- required to occupy an integral number of storage units,
1506 -- and start on a storage unit boundary. This means that
1507 -- the Normalized_First_Bit value is zero in the previous
1508 -- component, and the new value is also set to zero.
1512 -- In this case, the new position is given by an expression
1513 -- that is the sum of old normalized position and old size.
1519 Expr_From_SO_Ref
(Loc
, Old_Npos
),
1521 Expr_From_SO_Ref
(Loc
, Old_Esiz
, Prev_Comp
)),
1525 -- Get maximum size of previous component
1527 if Size_Depends_On_Discriminant
(Etype
(Prev_Comp
)) then
1528 Old_Maxsz
:= Get_Max_SU_Size
(Etype
(Prev_Comp
));
1530 Old_Maxsz
:= Expr_From_SO_Ref
(Loc
, Old_Esiz
, Prev_Comp
);
1533 -- Now we can compute the new max position. If the max size
1534 -- is static and the old position is static, then we can
1535 -- compute the new position statically.
1537 if Nkind
(Old_Maxsz
) = N_Integer_Literal
1538 and then Known_Static_Normalized_Position_Max
(Prev_Comp
)
1540 New_NPMax
:= Old_NPMax
+ Intval
(Old_Maxsz
);
1542 -- Otherwise new max position is dynamic
1548 Left_Opnd
=> Expr_From_SO_Ref
(Loc
, Old_NPMax
),
1549 Right_Opnd
=> Old_Maxsz
),
1554 -- Previous field has known static Esize
1557 New_Fbit
:= Old_Fbit
+ Old_Esiz
;
1559 -- Bump New_Fbit to storage unit boundary if required
1561 if New_Fbit
/= 0 and then Force_SU
then
1562 New_Fbit
:= (New_Fbit
+ SSU
- 1) / SSU
* SSU
;
1565 -- If old normalized position is static, we can go ahead and
1566 -- compute the new normalized position directly.
1568 if Known_Static_Normalized_Position
(Prev_Comp
) then
1569 New_Npos
:= Old_Npos
;
1571 if New_Fbit
>= SSU
then
1572 New_Npos
:= New_Npos
+ New_Fbit
/ SSU
;
1573 New_Fbit
:= New_Fbit
mod SSU
;
1576 -- Bump alignment if stricter than prev
1578 if Align
> Alignment
(Etype
(Prev_Comp
)) then
1579 New_Npos
:= (New_Npos
+ Align
- 1) / Align
* Align
;
1582 -- The max position is always equal to the position if
1583 -- the latter is static, since arrays depending on the
1584 -- values of discriminants never have static sizes.
1586 New_NPMax
:= New_Npos
;
1589 -- Case of old normalized position is dynamic
1592 -- If new bit position is within the current storage unit,
1593 -- we can just copy the old position as the result position
1594 -- (we have already set the new first bit value).
1596 if New_Fbit
< SSU
then
1597 New_Npos
:= Old_Npos
;
1598 New_NPMax
:= Old_NPMax
;
1600 -- If new bit position is past the current storage unit, we
1601 -- need to generate a new dynamic value for the position
1602 -- ??? need to deal with alignment
1608 Left_Opnd
=> Expr_From_SO_Ref
(Loc
, Old_Npos
),
1610 Make_Integer_Literal
(Loc
,
1611 Intval
=> New_Fbit
/ SSU
)),
1618 Left_Opnd
=> Expr_From_SO_Ref
(Loc
, Old_NPMax
),
1620 Make_Integer_Literal
(Loc
,
1621 Intval
=> New_Fbit
/ SSU
)),
1624 New_Fbit
:= New_Fbit
mod SSU
;
1629 end Get_Next_Component_Location
;
1631 ----------------------
1632 -- Layout_Component --
1633 ----------------------
1635 procedure Layout_Component
(Comp
: Entity_Id
; Prev_Comp
: Entity_Id
) is
1636 Ctyp
: constant Entity_Id
:= Etype
(Comp
);
1637 ORC
: constant Entity_Id
:= Original_Record_Component
(Comp
);
1644 -- Increase alignment of record if necessary. Note that we do not
1645 -- do this for packed records, which have an alignment of one by
1646 -- default, or for records for which an explicit alignment was
1647 -- specified with an alignment clause.
1649 if not Is_Packed
(E
)
1650 and then not Has_Alignment_Clause
(E
)
1651 and then Alignment
(Ctyp
) > Alignment
(E
)
1653 Set_Alignment
(E
, Alignment
(Ctyp
));
1656 -- If original component set, then use same layout
1658 if Present
(ORC
) and then ORC
/= Comp
then
1659 Set_Normalized_Position
(Comp
, Normalized_Position
(ORC
));
1660 Set_Normalized_First_Bit
(Comp
, Normalized_First_Bit
(ORC
));
1661 Set_Normalized_Position_Max
(Comp
, Normalized_Position_Max
(ORC
));
1662 Set_Component_Bit_Offset
(Comp
, Component_Bit_Offset
(ORC
));
1663 Set_Esize
(Comp
, Esize
(ORC
));
1667 -- Parent field is always at start of record, this will overlap
1668 -- the actual fields that are part of the parent, and that's fine
1670 if Chars
(Comp
) = Name_uParent
then
1671 Set_Normalized_Position
(Comp
, Uint_0
);
1672 Set_Normalized_First_Bit
(Comp
, Uint_0
);
1673 Set_Normalized_Position_Max
(Comp
, Uint_0
);
1674 Set_Component_Bit_Offset
(Comp
, Uint_0
);
1675 Set_Esize
(Comp
, Esize
(Ctyp
));
1679 -- Check case of type of component has a scope of the record we are
1680 -- laying out. When this happens, the type in question is an Itype
1681 -- that has not yet been laid out (that's because such types do not
1682 -- get frozen in the normal manner, because there is no place for
1683 -- the freeze nodes).
1685 if Scope
(Ctyp
) = E
then
1689 -- If component already laid out, then we are done
1691 if Known_Normalized_Position
(Comp
) then
1695 -- Set size of component from type. We use the Esize except in a
1696 -- packed record, where we use the RM_Size (since that is what the
1697 -- RM_Size value, as distinct from the Object_Size is useful for).
1699 if Is_Packed
(E
) then
1700 Set_Esize
(Comp
, RM_Size
(Ctyp
));
1702 Set_Esize
(Comp
, Esize
(Ctyp
));
1705 -- Compute the component position from the previous one. See if
1706 -- current component requires being on a storage unit boundary.
1708 -- If record is not packed, we always go to a storage unit boundary
1710 if not Is_Packed
(E
) then
1716 -- Elementary types do not need SU boundary in packed record
1718 if Is_Elementary_Type
(Ctyp
) then
1721 -- Packed array types with a modular packed array type do not
1722 -- force a storage unit boundary (since the code generation
1723 -- treats these as equivalent to the underlying modular type),
1725 elsif Is_Array_Type
(Ctyp
)
1726 and then Is_Bit_Packed_Array
(Ctyp
)
1727 and then Is_Modular_Integer_Type
(Packed_Array_Impl_Type
(Ctyp
))
1731 -- Record types with known length less than or equal to the length
1732 -- of long long integer can also be unaligned, since they can be
1733 -- treated as scalars.
1735 elsif Is_Record_Type
(Ctyp
)
1736 and then not Is_Dynamic_SO_Ref
(Esize
(Ctyp
))
1737 and then Esize
(Ctyp
) <= Esize
(Standard_Long_Long_Integer
)
1741 -- All other cases force a storage unit boundary, even when packed
1748 -- Now get the next component location
1750 Get_Next_Component_Location
1751 (Prev_Comp
, Alignment
(Ctyp
), Npos
, Fbit
, NPMax
, Forc
);
1752 Set_Normalized_Position
(Comp
, Npos
);
1753 Set_Normalized_First_Bit
(Comp
, Fbit
);
1754 Set_Normalized_Position_Max
(Comp
, NPMax
);
1756 -- Set Component_Bit_Offset in the static case
1758 if Known_Static_Normalized_Position
(Comp
)
1759 and then Known_Normalized_First_Bit
(Comp
)
1761 Set_Component_Bit_Offset
(Comp
, SSU
* Npos
+ Fbit
);
1763 end Layout_Component
;
1765 -----------------------
1766 -- Layout_Components --
1767 -----------------------
1769 procedure Layout_Components
1773 RM_Siz
: out SO_Ref
)
1780 -- Only lay out components if there are some to lay out
1782 if Present
(From
) then
1784 -- Lay out components with no component clauses
1788 if Ekind
(Comp
) = E_Component
1789 or else Ekind
(Comp
) = E_Discriminant
1791 -- The compatibility of component clauses with composite
1792 -- types isn't checked in Sem_Ch13, so we check it here.
1794 if Present
(Component_Clause
(Comp
)) then
1795 if Is_Composite_Type
(Etype
(Comp
))
1796 and then Esize
(Comp
) < RM_Size
(Etype
(Comp
))
1798 Error_Msg_Uint_1
:= RM_Size
(Etype
(Comp
));
1800 ("size for & too small, minimum allowed is ^",
1801 Component_Clause
(Comp
),
1806 Layout_Component
(Comp
, Prev_Comp
);
1811 exit when Comp
= To
;
1816 -- Set size fields, both are zero if no components
1818 if No
(Prev_Comp
) then
1822 -- If record subtype with non-static discriminants, then we don't
1823 -- know which variant will be the one which gets chosen. We don't
1824 -- just want to set the maximum size from the base, because the
1825 -- size should depend on the particular variant.
1827 -- What we do is to use the RM_Size of the base type, which has
1828 -- the necessary conditional computation of the size, using the
1829 -- size information for the particular variant chosen. Records
1830 -- with default discriminants for example have an Esize that is
1831 -- set to the maximum of all variants, but that's not what we
1832 -- want for a constrained subtype.
1834 elsif Ekind
(E
) = E_Record_Subtype
1835 and then not Has_Static_Discriminants
(E
)
1838 BT
: constant Node_Id
:= Base_Type
(E
);
1840 Esiz
:= RM_Size
(BT
);
1841 RM_Siz
:= RM_Size
(BT
);
1842 Set_Alignment
(E
, Alignment
(BT
));
1846 -- First the object size, for which we align past the last field
1847 -- to the alignment of the record (the object size is required to
1848 -- be a multiple of the alignment).
1850 Get_Next_Component_Location
1858 -- If the resulting normalized position is a dynamic reference,
1859 -- then the size is dynamic, and is stored in storage units. In
1860 -- this case, we set the RM_Size to the same value, it is simply
1861 -- not worth distinguishing Esize and RM_Size values in the
1862 -- dynamic case, since the RM has nothing to say about them.
1864 -- Note that a size cannot have been given in this case, since
1865 -- size specifications cannot be given for variable length types.
1868 Align
: constant Uint
:= Alignment
(E
);
1871 if Is_Dynamic_SO_Ref
(End_Npos
) then
1874 -- Set the Object_Size allowing for the alignment. In the
1875 -- dynamic case, we must do the actual runtime computation.
1876 -- We can skip this in the non-packed record case if the
1877 -- last component has a smaller alignment than the overall
1878 -- record alignment.
1880 if Is_Dynamic_SO_Ref
(End_NPMax
) then
1884 or else Alignment
(Etype
(Prev_Comp
)) < Align
1886 -- The expression we build is:
1887 -- (expr + align - 1) / align * align
1892 Make_Op_Multiply
(Loc
,
1894 Make_Op_Divide
(Loc
,
1898 Expr_From_SO_Ref
(Loc
, Esiz
),
1900 Make_Integer_Literal
(Loc
,
1901 Intval
=> Align
- 1)),
1903 Make_Integer_Literal
(Loc
, Align
)),
1905 Make_Integer_Literal
(Loc
, Align
)),
1910 -- Here Esiz is static, so we can adjust the alignment
1911 -- directly go give the required aligned value.
1914 Esiz
:= (End_NPMax
+ Align
- 1) / Align
* Align
* SSU
;
1917 -- Case where computed size is static
1920 -- The ending size was computed in Npos in storage units,
1921 -- but the actual size is stored in bits, so adjust
1922 -- accordingly. We also adjust the size to match the
1925 Esiz
:= (End_NPMax
+ Align
- 1) / Align
* Align
* SSU
;
1927 -- Compute the resulting Value_Size (RM_Size). For this
1928 -- purpose we do not force alignment of the record or
1929 -- storage size alignment of the result.
1931 Get_Next_Component_Location
1939 RM_Siz
:= End_Npos
* SSU
+ End_Fbit
;
1940 Set_And_Check_Static_Size
(E
, Esiz
, RM_Siz
);
1944 end Layout_Components
;
1946 -------------------------------
1947 -- Layout_Non_Variant_Record --
1948 -------------------------------
1950 procedure Layout_Non_Variant_Record
is
1954 Layout_Components
(First_Entity
(E
), Last_Entity
(E
), Esiz
, RM_Siz
);
1955 Set_Esize
(E
, Esiz
);
1956 Set_RM_Size
(E
, RM_Siz
);
1957 end Layout_Non_Variant_Record
;
1959 ---------------------------
1960 -- Layout_Variant_Record --
1961 ---------------------------
1963 procedure Layout_Variant_Record
is
1964 Tdef
: constant Node_Id
:= Type_Definition
(Decl
);
1965 First_Discr
: Entity_Id
;
1966 Last_Discr
: Entity_Id
;
1970 pragma Warnings
(Off
, SO_Ref
);
1972 RM_Siz_Expr
: Node_Id
:= Empty
;
1973 -- Expression for the evolving RM_Siz value. This is typically an if
1974 -- expression which involves tests of discriminant values that are
1975 -- formed as references to the entity V. At the end of scanning all
1976 -- the components, a suitable function is constructed in which V is
1979 -----------------------
1980 -- Local Subprograms --
1981 -----------------------
1983 procedure Layout_Component_List
1986 RM_Siz_Expr
: out Node_Id
);
1987 -- Recursive procedure, called to lay out one component list Esiz
1988 -- and RM_Siz_Expr are set to the Object_Size and Value_Size values
1989 -- respectively representing the record size up to and including the
1990 -- last component in the component list (including any variants in
1991 -- this component list). RM_Siz_Expr is returned as an expression
1992 -- which may in the general case involve some references to the
1993 -- discriminants of the current record value, referenced by selecting
1994 -- from the entity V.
1996 ---------------------------
1997 -- Layout_Component_List --
1998 ---------------------------
2000 procedure Layout_Component_List
2003 RM_Siz_Expr
: out Node_Id
)
2005 Citems
: constant List_Id
:= Component_Items
(Clist
);
2006 Vpart
: constant Node_Id
:= Variant_Part
(Clist
);
2010 RMS_Ent
: Entity_Id
;
2013 if Is_Non_Empty_List
(Citems
) then
2015 (From
=> Defining_Identifier
(First
(Citems
)),
2016 To
=> Defining_Identifier
(Last
(Citems
)),
2020 Layout_Components
(Empty
, Empty
, Esiz
, RM_Siz
);
2023 -- Case where no variants are present in the component list
2027 -- The Esiz value has been correctly set by the call to
2028 -- Layout_Components, so there is nothing more to be done.
2030 -- For RM_Siz, we have an SO_Ref value, which we must convert
2031 -- to an appropriate expression.
2033 if Is_Static_SO_Ref
(RM_Siz
) then
2035 Make_Integer_Literal
(Loc
,
2039 RMS_Ent
:= Get_Dynamic_SO_Entity
(RM_Siz
);
2041 -- If the size is represented by a function, then we create
2042 -- an appropriate function call using V as the parameter to
2045 if Is_Discrim_SO_Function
(RMS_Ent
) then
2047 Make_Function_Call
(Loc
,
2048 Name
=> New_Occurrence_Of
(RMS_Ent
, Loc
),
2049 Parameter_Associations
=> New_List
(
2050 Make_Identifier
(Loc
, Vname
)));
2052 -- If the size is represented by a constant, then the
2053 -- expression we want is a reference to this constant
2056 RM_Siz_Expr
:= New_Occurrence_Of
(RMS_Ent
, Loc
);
2060 -- Case where variants are present in this component list
2070 D_Entity
: Entity_Id
;
2073 RM_Siz_Expr
:= Empty
;
2076 Var
:= Last
(Variants
(Vpart
));
2077 while Present
(Var
) loop
2079 Layout_Component_List
2080 (Component_List
(Var
), EsizV
, RM_SizV
);
2082 -- Set the Object_Size. If this is the first variant,
2083 -- we just set the size of this first variant.
2085 if Var
= Last
(Variants
(Vpart
)) then
2088 -- Otherwise the Object_Size is formed as a maximum
2089 -- of Esiz so far from previous variants, and the new
2090 -- Esiz value from the variant we just processed.
2092 -- If both values are static, we can just compute the
2093 -- maximum directly to save building junk nodes.
2095 elsif not Is_Dynamic_SO_Ref
(Esiz
)
2096 and then not Is_Dynamic_SO_Ref
(EsizV
)
2098 Esiz
:= UI_Max
(Esiz
, EsizV
);
2100 -- If either value is dynamic, then we have to generate
2101 -- an appropriate Standard_Unsigned'Max attribute call.
2102 -- If one of the values is static then it needs to be
2103 -- converted from bits to storage units to be compatible
2104 -- with the dynamic value.
2107 if Is_Static_SO_Ref
(Esiz
) then
2108 Esiz
:= (Esiz
+ SSU
- 1) / SSU
;
2111 if Is_Static_SO_Ref
(EsizV
) then
2112 EsizV
:= (EsizV
+ SSU
- 1) / SSU
;
2117 (Make_Attribute_Reference
(Loc
,
2118 Attribute_Name
=> Name_Max
,
2120 New_Occurrence_Of
(Standard_Unsigned
, Loc
),
2121 Expressions
=> New_List
(
2122 Expr_From_SO_Ref
(Loc
, Esiz
),
2123 Expr_From_SO_Ref
(Loc
, EsizV
))),
2128 -- Now deal with Value_Size (RM_Siz). We are aiming at
2129 -- an expression that looks like:
2131 -- if xxDx (V.disc) then rmsiz1
2132 -- else if xxDx (V.disc) then rmsiz2
2135 -- Where rmsiz1, rmsiz2... are the RM_Siz values for the
2136 -- individual variants, and xxDx are the discriminant
2137 -- checking functions generated for the variant type.
2139 -- If this is the first variant, we simply set the result
2140 -- as the expression. Note that this takes care of the
2143 if No
(RM_Siz_Expr
) then
2145 -- If this is the only variant and the size is a
2146 -- literal, then use bit size as is, otherwise convert
2147 -- to storage units and continue to the next variant.
2150 and then Nkind
(RM_SizV
) = N_Integer_Literal
2152 RM_Siz_Expr
:= RM_SizV
;
2154 RM_Siz_Expr
:= Bits_To_SU
(RM_SizV
);
2157 -- Otherwise construct the appropriate test
2160 -- The test to be used in general is a call to the
2161 -- discriminant checking function. However, it is
2162 -- definitely worth special casing the very common
2163 -- case where a single value is involved.
2165 Dchoice
:= First
(Discrete_Choices
(Var
));
2167 if No
(Next
(Dchoice
))
2168 and then Nkind
(Dchoice
) /= N_Range
2170 -- Discriminant to be tested
2173 Make_Selected_Component
(Loc
,
2175 Make_Identifier
(Loc
, Vname
),
2178 (Entity
(Name
(Vpart
)), Loc
));
2182 Left_Opnd
=> Discrim
,
2183 Right_Opnd
=> New_Copy
(Dchoice
));
2185 -- Generate a call to the discriminant-checking
2186 -- function for the variant. Note that the result
2187 -- has to be complemented since the function returns
2188 -- False when the passed discriminant value matches.
2191 -- The checking function takes all of the type's
2192 -- discriminants as parameters, so a list of all
2193 -- the selected discriminants must be constructed.
2196 D_Entity
:= First_Discriminant
(E
);
2197 while Present
(D_Entity
) loop
2199 Make_Selected_Component
(Loc
,
2201 Make_Identifier
(Loc
, Vname
),
2203 New_Occurrence_Of
(D_Entity
, Loc
)));
2205 D_Entity
:= Next_Discriminant
(D_Entity
);
2211 Make_Function_Call
(Loc
,
2214 (Dcheck_Function
(Var
), Loc
),
2215 Parameter_Associations
=>
2220 Make_If_Expression
(Loc
,
2223 (Dtest
, Bits_To_SU
(RM_SizV
), RM_Siz_Expr
));
2230 end Layout_Component_List
;
2232 Others_Present
: Boolean;
2233 pragma Warnings
(Off
, Others_Present
);
2234 -- Indicates others present, not used in this case
2236 procedure Non_Static_Choice_Error
(Choice
: Node_Id
);
2237 -- Error routine invoked by the generic instantiation below when
2238 -- the variant part has a nonstatic choice.
2240 package Variant_Choices_Processing
is new
2241 Generic_Check_Choices
2242 (Process_Empty_Choice
=> No_OP
,
2243 Process_Non_Static_Choice
=> Non_Static_Choice_Error
,
2244 Process_Associated_Node
=> No_OP
);
2245 use Variant_Choices_Processing
;
2247 -----------------------------
2248 -- Non_Static_Choice_Error --
2249 -----------------------------
2251 procedure Non_Static_Choice_Error
(Choice
: Node_Id
) is
2253 Flag_Non_Static_Expr
2254 ("choice given in case expression is not static!", Choice
);
2255 end Non_Static_Choice_Error
;
2257 -- Start of processing for Layout_Variant_Record
2260 -- Call Check_Choices here to ensure that Others_Discrete_Choices
2261 -- gets set on any 'others' choice before the discriminant-checking
2262 -- functions are generated. Otherwise the function for the 'others'
2263 -- alternative will unconditionally return True, causing discriminant
2264 -- checks to fail. However, Check_Choices is now normally delayed
2265 -- until the type's freeze entity is processed, due to requirements
2266 -- coming from subtype predicates, so doing it at this point is
2267 -- probably not right in general, but it's not clear how else to deal
2268 -- with this situation. Perhaps we should only generate declarations
2269 -- for the checking functions here, and somehow delay generation of
2270 -- their bodies, but that would be a nontrivial change. ???
2273 VP
: constant Node_Id
:=
2274 Variant_Part
(Component_List
(Type_Definition
(Decl
)));
2277 (VP
, Variants
(VP
), Etype
(Name
(VP
)), Others_Present
);
2280 -- We need the discriminant checking functions, since we generate
2281 -- calls to these functions for the RM_Size expression, so make
2282 -- sure that these functions have been constructed in time.
2284 Build_Discr_Checking_Funcs
(Decl
);
2286 -- Lay out the discriminants
2288 First_Discr
:= First_Discriminant
(E
);
2289 Last_Discr
:= First_Discr
;
2290 while Present
(Next_Discriminant
(Last_Discr
)) loop
2291 Next_Discriminant
(Last_Discr
);
2295 (From
=> First_Discr
,
2300 -- Lay out the main component list (this will make recursive calls
2301 -- to lay out all component lists nested within variants).
2303 Layout_Component_List
(Component_List
(Tdef
), Esiz
, RM_Siz_Expr
);
2304 Set_Esize
(E
, Esiz
);
2306 -- If the RM_Size is a literal, set its value
2308 if Nkind
(RM_Siz_Expr
) = N_Integer_Literal
then
2309 Set_RM_Size
(E
, Intval
(RM_Siz_Expr
));
2311 -- Otherwise we construct a dynamic SO_Ref
2320 end Layout_Variant_Record
;
2322 -- Start of processing for Layout_Record_Type
2325 -- If this is a cloned subtype, just copy the size fields from the
2326 -- original, nothing else needs to be done in this case, since the
2327 -- components themselves are all shared.
2329 if Ekind_In
(E
, E_Record_Subtype
, E_Class_Wide_Subtype
)
2330 and then Present
(Cloned_Subtype
(E
))
2332 Set_Esize
(E
, Esize
(Cloned_Subtype
(E
)));
2333 Set_RM_Size
(E
, RM_Size
(Cloned_Subtype
(E
)));
2334 Set_Alignment
(E
, Alignment
(Cloned_Subtype
(E
)));
2336 -- Another special case, class-wide types. The RM says that the size
2337 -- of such types is implementation defined (RM 13.3(48)). What we do
2338 -- here is to leave the fields set as unknown values, and the backend
2339 -- determines the actual behavior.
2341 elsif Ekind
(E
) = E_Class_Wide_Type
then
2347 -- Initialize alignment conservatively to 1. This value will be
2348 -- increased as necessary during processing of the record.
2350 if Unknown_Alignment
(E
) then
2351 Set_Alignment
(E
, Uint_1
);
2354 -- Initialize previous component. This is Empty unless there are
2355 -- components which have already been laid out by component clauses.
2356 -- If there are such components, we start our lay out of the
2357 -- remaining components following the last such component.
2361 Comp
:= First_Component_Or_Discriminant
(E
);
2362 while Present
(Comp
) loop
2363 if Present
(Component_Clause
(Comp
)) then
2366 Component_Bit_Offset
(Comp
) >
2367 Component_Bit_Offset
(Prev_Comp
)
2373 Next_Component_Or_Discriminant
(Comp
);
2376 -- We have two separate circuits, one for non-variant records and
2377 -- one for variant records. For non-variant records, we simply go
2378 -- through the list of components. This handles all the non-variant
2379 -- cases including those cases of subtypes where there is no full
2380 -- type declaration, so the tree cannot be used to drive the layout.
2381 -- For variant records, we have to drive the layout from the tree
2382 -- since we need to understand the variant structure in this case.
2384 if Present
(Full_View
(E
)) then
2385 Decl
:= Declaration_Node
(Full_View
(E
));
2387 Decl
:= Declaration_Node
(E
);
2390 -- Scan all the components
2392 if Nkind
(Decl
) = N_Full_Type_Declaration
2393 and then Has_Discriminants
(E
)
2394 and then Nkind
(Type_Definition
(Decl
)) = N_Record_Definition
2395 and then Present
(Component_List
(Type_Definition
(Decl
)))
2397 Present
(Variant_Part
(Component_List
(Type_Definition
(Decl
))))
2399 Layout_Variant_Record
;
2401 Layout_Non_Variant_Record
;
2404 end Layout_Record_Type
;
2410 procedure Layout_Type
(E
: Entity_Id
) is
2411 Desig_Type
: Entity_Id
;
2414 -- For string literal types, for now, kill the size always, this is
2415 -- because gigi does not like or need the size to be set ???
2417 if Ekind
(E
) = E_String_Literal_Subtype
then
2418 Set_Esize
(E
, Uint_0
);
2419 Set_RM_Size
(E
, Uint_0
);
2423 -- For access types, set size/alignment. This is system address size,
2424 -- except for fat pointers (unconstrained array access types), where the
2425 -- size is two times the address size, to accommodate the two pointers
2426 -- that are required for a fat pointer (data and template). Note that
2427 -- E_Access_Protected_Subprogram_Type is not an access type for this
2428 -- purpose since it is not a pointer but is equivalent to a record. For
2429 -- access subtypes, copy the size from the base type since Gigi
2430 -- represents them the same way.
2432 if Is_Access_Type
(E
) then
2433 Desig_Type
:= Underlying_Type
(Designated_Type
(E
));
2435 -- If we only have a limited view of the type, see whether the
2436 -- non-limited view is available.
2438 if From_Limited_With
(Designated_Type
(E
))
2439 and then Ekind
(Designated_Type
(E
)) = E_Incomplete_Type
2440 and then Present
(Non_Limited_View
(Designated_Type
(E
)))
2442 Desig_Type
:= Non_Limited_View
(Designated_Type
(E
));
2445 -- If Esize already set (e.g. by a size clause), then nothing further
2448 if Known_Esize
(E
) then
2451 -- Access to subprogram is a strange beast, and we let the backend
2452 -- figure out what is needed (it may be some kind of fat pointer,
2453 -- including the static link for example.
2455 elsif Is_Access_Protected_Subprogram_Type
(E
) then
2458 -- For access subtypes, copy the size information from base type
2460 elsif Ekind
(E
) = E_Access_Subtype
then
2461 Set_Size_Info
(E
, Base_Type
(E
));
2462 Set_RM_Size
(E
, RM_Size
(Base_Type
(E
)));
2464 -- For other access types, we use either address size, or, if a fat
2465 -- pointer is used (pointer-to-unconstrained array case), twice the
2466 -- address size to accommodate a fat pointer.
2468 elsif Present
(Desig_Type
)
2469 and then Is_Array_Type
(Desig_Type
)
2470 and then not Is_Constrained
(Desig_Type
)
2471 and then not Has_Completion_In_Body
(Desig_Type
)
2473 -- Debug Flag -gnatd6 says make all pointers to unconstrained thin
2475 and then not Debug_Flag_6
2477 Init_Size
(E
, 2 * System_Address_Size
);
2479 -- Check for bad convention set
2481 if Warn_On_Export_Import
2483 (Convention
(E
) = Convention_C
2485 Convention
(E
) = Convention_CPP
)
2488 ("?x?this access type does not correspond to C pointer", E
);
2491 -- If the designated type is a limited view it is unanalyzed. We can
2492 -- examine the declaration itself to determine whether it will need a
2495 elsif Present
(Desig_Type
)
2496 and then Present
(Parent
(Desig_Type
))
2497 and then Nkind
(Parent
(Desig_Type
)) = N_Full_Type_Declaration
2498 and then Nkind
(Type_Definition
(Parent
(Desig_Type
))) =
2499 N_Unconstrained_Array_Definition
2500 and then not Debug_Flag_6
2502 Init_Size
(E
, 2 * System_Address_Size
);
2504 -- When the target is AAMP, access-to-subprogram types are fat
2505 -- pointers consisting of the subprogram address and a static link,
2506 -- with the exception of library-level access types (including
2507 -- library-level anonymous access types, such as for components),
2508 -- where a simple subprogram address is used.
2510 elsif AAMP_On_Target
2512 ((Ekind
(E
) = E_Access_Subprogram_Type
2513 and then Present
(Enclosing_Subprogram
(E
)))
2515 (Ekind
(E
) = E_Anonymous_Access_Subprogram_Type
2517 (not Is_Local_Anonymous_Access
(E
)
2518 or else Present
(Enclosing_Subprogram
(E
)))))
2520 Init_Size
(E
, 2 * System_Address_Size
);
2522 -- Normal case of thin pointer
2525 Init_Size
(E
, System_Address_Size
);
2528 Set_Elem_Alignment
(E
);
2530 -- Scalar types: set size and alignment
2532 elsif Is_Scalar_Type
(E
) then
2534 -- For discrete types, the RM_Size and Esize must be set already,
2535 -- since this is part of the earlier processing and the front end is
2536 -- always required to lay out the sizes of such types (since they are
2537 -- available as static attributes). All we do is to check that this
2538 -- rule is indeed obeyed.
2540 if Is_Discrete_Type
(E
) then
2542 -- If the RM_Size is not set, then here is where we set it
2544 -- Note: an RM_Size of zero looks like not set here, but this
2545 -- is a rare case, and we can simply reset it without any harm.
2547 if not Known_RM_Size
(E
) then
2548 Set_Discrete_RM_Size
(E
);
2551 -- If Esize for a discrete type is not set then set it
2553 if not Known_Esize
(E
) then
2559 -- If size is big enough, set it and exit
2561 if S
>= RM_Size
(E
) then
2565 -- If the RM_Size is greater than 64 (happens only when
2566 -- strange values are specified by the user, then Esize
2567 -- is simply a copy of RM_Size, it will be further
2568 -- refined later on)
2571 Set_Esize
(E
, RM_Size
(E
));
2574 -- Otherwise double possible size and keep trying
2583 -- For non-discrete scalar types, if the RM_Size is not set, then set
2584 -- it now to a copy of the Esize if the Esize is set.
2587 if Known_Esize
(E
) and then Unknown_RM_Size
(E
) then
2588 Set_RM_Size
(E
, Esize
(E
));
2592 Set_Elem_Alignment
(E
);
2594 -- Non-elementary (composite) types
2597 -- For packed arrays, take size and alignment values from the packed
2598 -- array type if a packed array type has been created and the fields
2599 -- are not currently set.
2601 if Is_Array_Type
(E
)
2602 and then Present
(Packed_Array_Impl_Type
(E
))
2605 PAT
: constant Entity_Id
:= Packed_Array_Impl_Type
(E
);
2608 if Unknown_Esize
(E
) then
2609 Set_Esize
(E
, Esize
(PAT
));
2612 if Unknown_RM_Size
(E
) then
2613 Set_RM_Size
(E
, RM_Size
(PAT
));
2616 if Unknown_Alignment
(E
) then
2617 Set_Alignment
(E
, Alignment
(PAT
));
2622 -- If Esize is set, and RM_Size is not, RM_Size is copied from Esize.
2623 -- At least for now this seems reasonable, and is in any case needed
2624 -- for compatibility with old versions of gigi.
2626 if Known_Esize
(E
) and then Unknown_RM_Size
(E
) then
2627 Set_RM_Size
(E
, Esize
(E
));
2630 -- For array base types, set component size if object size of the
2631 -- component type is known and is a small power of 2 (8, 16, 32, 64),
2632 -- since this is what will always be used.
2634 if Ekind
(E
) = E_Array_Type
and then Unknown_Component_Size
(E
) then
2636 CT
: constant Entity_Id
:= Component_Type
(E
);
2639 -- For some reason, access types can cause trouble, So let's
2640 -- just do this for scalar types ???
2643 and then Is_Scalar_Type
(CT
)
2644 and then Known_Static_Esize
(CT
)
2647 S
: constant Uint
:= Esize
(CT
);
2649 if Addressable
(S
) then
2650 Set_Component_Size
(E
, S
);
2658 -- Lay out array and record types if front end layout set
2660 if Frontend_Layout_On_Target
then
2661 if Is_Array_Type
(E
) and then not Is_Bit_Packed_Array
(E
) then
2662 Layout_Array_Type
(E
);
2663 elsif Is_Record_Type
(E
) then
2664 Layout_Record_Type
(E
);
2667 -- Case of backend layout, we still do a little in the front end
2670 -- Processing for record types
2672 if Is_Record_Type
(E
) then
2674 -- Special remaining processing for record types with a known
2675 -- size of 16, 32, or 64 bits whose alignment is not yet set.
2676 -- For these types, we set a corresponding alignment matching
2677 -- the size if possible, or as large as possible if not.
2679 if Convention
(E
) = Convention_Ada
and then not Debug_Flag_Q
then
2680 Set_Composite_Alignment
(E
);
2683 -- Processing for array types
2685 elsif Is_Array_Type
(E
) then
2687 -- For arrays that are required to be atomic, we do the same
2688 -- processing as described above for short records, since we
2689 -- really need to have the alignment set for the whole array.
2691 if Is_Atomic
(E
) and then not Debug_Flag_Q
then
2692 Set_Composite_Alignment
(E
);
2695 -- For unpacked array types, set an alignment of 1 if we know
2696 -- that the component alignment is not greater than 1. The reason
2697 -- we do this is to avoid unnecessary copying of slices of such
2698 -- arrays when passed to subprogram parameters (see special test
2699 -- in Exp_Ch6.Expand_Actuals).
2701 if not Is_Packed
(E
) and then Unknown_Alignment
(E
) then
2702 if Known_Static_Component_Size
(E
)
2703 and then Component_Size
(E
) = 1
2705 Set_Alignment
(E
, Uint_1
);
2709 -- We need to know whether the size depends on the value of one
2710 -- or more discriminants to select the return mechanism. Skip if
2711 -- errors are present, to prevent cascaded messages.
2713 if Serious_Errors_Detected
= 0 then
2714 Compute_Size_Depends_On_Discriminant
(E
);
2720 -- Final step is to check that Esize and RM_Size are compatible
2722 if Known_Static_Esize
(E
) and then Known_Static_RM_Size
(E
) then
2723 if Esize
(E
) < RM_Size
(E
) then
2725 -- Esize is less than RM_Size. That's not good. First we test
2726 -- whether this was set deliberately with an Object_Size clause
2727 -- and if so, object to the clause.
2729 if Has_Object_Size_Clause
(E
) then
2730 Error_Msg_Uint_1
:= RM_Size
(E
);
2732 ("object size is too small, minimum allowed is ^",
2733 Expression
(Get_Attribute_Definition_Clause
2734 (E
, Attribute_Object_Size
)));
2737 -- Adjust Esize up to RM_Size value
2740 Size
: constant Uint
:= RM_Size
(E
);
2743 Set_Esize
(E
, RM_Size
(E
));
2745 -- For scalar types, increase Object_Size to power of 2, but
2746 -- not less than a storage unit in any case (i.e., normally
2747 -- this means it will be storage-unit addressable).
2749 if Is_Scalar_Type
(E
) then
2750 if Size
<= System_Storage_Unit
then
2751 Init_Esize
(E
, System_Storage_Unit
);
2752 elsif Size
<= 16 then
2754 elsif Size
<= 32 then
2757 Set_Esize
(E
, (Size
+ 63) / 64 * 64);
2760 -- Finally, make sure that alignment is consistent with
2761 -- the newly assigned size.
2763 while Alignment
(E
) * System_Storage_Unit
< Esize
(E
)
2764 and then Alignment
(E
) < Maximum_Alignment
2766 Set_Alignment
(E
, 2 * Alignment
(E
));
2774 ---------------------
2775 -- Rewrite_Integer --
2776 ---------------------
2778 procedure Rewrite_Integer
(N
: Node_Id
; V
: Uint
) is
2779 Loc
: constant Source_Ptr
:= Sloc
(N
);
2780 Typ
: constant Entity_Id
:= Etype
(N
);
2782 Rewrite
(N
, Make_Integer_Literal
(Loc
, Intval
=> V
));
2784 end Rewrite_Integer
;
2786 -------------------------------
2787 -- Set_And_Check_Static_Size --
2788 -------------------------------
2790 procedure Set_And_Check_Static_Size
2797 procedure Check_Size_Too_Small
(Spec
: Uint
; Min
: Uint
);
2798 -- Spec is the number of bit specified in the size clause, and Min is
2799 -- the minimum computed size. An error is given that the specified size
2800 -- is too small if Spec < Min, and in this case both Esize and RM_Size
2801 -- are set to unknown in E. The error message is posted on node SC.
2803 procedure Check_Unused_Bits
(Spec
: Uint
; Max
: Uint
);
2804 -- Spec is the number of bits specified in the size clause, and Max is
2805 -- the maximum computed size. A warning is given about unused bits if
2806 -- Spec > Max. This warning is posted on node SC.
2808 --------------------------
2809 -- Check_Size_Too_Small --
2810 --------------------------
2812 procedure Check_Size_Too_Small
(Spec
: Uint
; Min
: Uint
) is
2815 Error_Msg_Uint_1
:= Min
;
2816 Error_Msg_NE
("size for & too small, minimum allowed is ^", SC
, E
);
2820 end Check_Size_Too_Small
;
2822 -----------------------
2823 -- Check_Unused_Bits --
2824 -----------------------
2826 procedure Check_Unused_Bits
(Spec
: Uint
; Max
: Uint
) is
2829 Error_Msg_Uint_1
:= Spec
- Max
;
2830 Error_Msg_NE
("??^ bits of & unused", SC
, E
);
2832 end Check_Unused_Bits
;
2834 -- Start of processing for Set_And_Check_Static_Size
2837 -- Case where Object_Size (Esize) is already set by a size clause
2839 if Known_Static_Esize
(E
) then
2840 SC
:= Size_Clause
(E
);
2843 SC
:= Get_Attribute_Definition_Clause
(E
, Attribute_Object_Size
);
2846 -- Perform checks on specified size against computed sizes
2848 if Present
(SC
) then
2849 Check_Unused_Bits
(Esize
(E
), Esiz
);
2850 Check_Size_Too_Small
(Esize
(E
), RM_Siz
);
2854 -- Case where Value_Size (RM_Size) is set by specific Value_Size clause
2855 -- (we do not need to worry about Value_Size being set by a Size clause,
2856 -- since that will have set Esize as well, and we already took care of
2859 if Known_Static_RM_Size
(E
) then
2860 SC
:= Get_Attribute_Definition_Clause
(E
, Attribute_Value_Size
);
2862 -- Perform checks on specified size against computed sizes
2864 if Present
(SC
) then
2865 Check_Unused_Bits
(RM_Size
(E
), Esiz
);
2866 Check_Size_Too_Small
(RM_Size
(E
), RM_Siz
);
2870 -- Set sizes if unknown
2872 if Unknown_Esize
(E
) then
2873 Set_Esize
(E
, Esiz
);
2876 if Unknown_RM_Size
(E
) then
2877 Set_RM_Size
(E
, RM_Siz
);
2879 end Set_And_Check_Static_Size
;
2881 -----------------------------
2882 -- Set_Composite_Alignment --
2883 -----------------------------
2885 procedure Set_Composite_Alignment
(E
: Entity_Id
) is
2890 -- If alignment is already set, then nothing to do
2892 if Known_Alignment
(E
) then
2896 -- Alignment is not known, see if we can set it, taking into account
2897 -- the setting of the Optimize_Alignment mode.
2899 -- If Optimize_Alignment is set to Space, then we try to give packed
2900 -- records an aligmment of 1, unless there is some reason we can't.
2902 if Optimize_Alignment_Space
(E
)
2903 and then Is_Record_Type
(E
)
2904 and then Is_Packed
(E
)
2906 -- No effect for record with atomic components
2908 if Is_Atomic
(E
) then
2909 Error_Msg_N
("Optimize_Alignment has no effect for &??", E
);
2910 Error_Msg_N
("\pragma ignored for atomic record??", E
);
2914 -- No effect if independent components
2916 if Has_Independent_Components
(E
) then
2917 Error_Msg_N
("Optimize_Alignment has no effect for &??", E
);
2919 ("\pragma ignored for record with independent components??", E
);
2923 -- No effect if any component is atomic or is a by reference type
2928 Ent
:= First_Component_Or_Discriminant
(E
);
2929 while Present
(Ent
) loop
2930 if Is_By_Reference_Type
(Etype
(Ent
))
2931 or else Is_Atomic
(Etype
(Ent
))
2932 or else Is_Atomic
(Ent
)
2934 Error_Msg_N
("Optimize_Alignment has no effect for &??", E
);
2936 ("\pragma is ignored if atomic components present??", E
);
2939 Next_Component_Or_Discriminant
(Ent
);
2944 -- Optimize_Alignment has no effect on variable length record
2946 if not Size_Known_At_Compile_Time
(E
) then
2947 Error_Msg_N
("Optimize_Alignment has no effect for &??", E
);
2948 Error_Msg_N
("\pragma is ignored for variable length record??", E
);
2952 -- All tests passed, we can set alignment to 1
2956 -- Not a record, or not packed
2959 -- The only other cases we worry about here are where the size is
2960 -- statically known at compile time.
2962 if Known_Static_Esize
(E
) then
2964 elsif Unknown_Esize
(E
) and then Known_Static_RM_Size
(E
) then
2970 -- Size is known, alignment is not set
2972 -- Reset alignment to match size if the known size is exactly 2, 4,
2973 -- or 8 storage units.
2975 if Siz
= 2 * System_Storage_Unit
then
2977 elsif Siz
= 4 * System_Storage_Unit
then
2979 elsif Siz
= 8 * System_Storage_Unit
then
2982 -- If Optimize_Alignment is set to Space, then make sure the
2983 -- alignment matches the size, for example, if the size is 17
2984 -- bytes then we want an alignment of 1 for the type.
2986 elsif Optimize_Alignment_Space
(E
) then
2987 if Siz
mod (8 * System_Storage_Unit
) = 0 then
2989 elsif Siz
mod (4 * System_Storage_Unit
) = 0 then
2991 elsif Siz
mod (2 * System_Storage_Unit
) = 0 then
2997 -- If Optimize_Alignment is set to Time, then we reset for odd
2998 -- "in between sizes", for example a 17 bit record is given an
3001 elsif Optimize_Alignment_Time
(E
)
3002 and then Siz
> System_Storage_Unit
3003 and then Siz
<= 8 * System_Storage_Unit
3005 if Siz
<= 2 * System_Storage_Unit
then
3007 elsif Siz
<= 4 * System_Storage_Unit
then
3009 else -- Siz <= 8 * System_Storage_Unit then
3013 -- No special alignment fiddling needed
3020 -- Here we have Set Align to the proposed improved value. Make sure the
3021 -- value set does not exceed Maximum_Alignment for the target.
3023 if Align
> Maximum_Alignment
then
3024 Align
:= Maximum_Alignment
;
3027 -- Further processing for record types only to reduce the alignment
3028 -- set by the above processing in some specific cases. We do not
3029 -- do this for atomic records, since we need max alignment there,
3031 if Is_Record_Type
(E
) and then not Is_Atomic
(E
) then
3033 -- For records, there is generally no point in setting alignment
3034 -- higher than word size since we cannot do better than move by
3035 -- words in any case. Omit this if we are optimizing for time,
3036 -- since conceivably we may be able to do better.
3038 if Align
> System_Word_Size
/ System_Storage_Unit
3039 and then not Optimize_Alignment_Time
(E
)
3041 Align
:= System_Word_Size
/ System_Storage_Unit
;
3044 -- Check components. If any component requires a higher alignment,
3045 -- then we set that higher alignment in any case. Don't do this if
3046 -- we have Optimize_Alignment set to Space. Note that that covers
3047 -- the case of packed records, where we already set alignment to 1.
3049 if not Optimize_Alignment_Space
(E
) then
3054 Comp
:= First_Component
(E
);
3055 while Present
(Comp
) loop
3056 if Known_Alignment
(Etype
(Comp
)) then
3058 Calign
: constant Uint
:= Alignment
(Etype
(Comp
));
3061 -- The cases to process are when the alignment of the
3062 -- component type is larger than the alignment we have
3063 -- so far, and either there is no component clause for
3064 -- the component, or the length set by the component
3065 -- clause matches the length of the component type.
3069 (Unknown_Esize
(Comp
)
3070 or else (Known_Static_Esize
(Comp
)
3073 Calign
* System_Storage_Unit
))
3075 Align
:= UI_To_Int
(Calign
);
3080 Next_Component
(Comp
);
3086 -- Set chosen alignment, and increase Esize if necessary to match the
3087 -- chosen alignment.
3089 Set_Alignment
(E
, UI_From_Int
(Align
));
3091 if Known_Static_Esize
(E
)
3092 and then Esize
(E
) < Align
* System_Storage_Unit
3094 Set_Esize
(E
, UI_From_Int
(Align
* System_Storage_Unit
));
3096 end Set_Composite_Alignment
;
3098 --------------------------
3099 -- Set_Discrete_RM_Size --
3100 --------------------------
3102 procedure Set_Discrete_RM_Size
(Def_Id
: Entity_Id
) is
3103 FST
: constant Entity_Id
:= First_Subtype
(Def_Id
);
3106 -- All discrete types except for the base types in standard are
3107 -- constrained, so indicate this by setting Is_Constrained.
3109 Set_Is_Constrained
(Def_Id
);
3111 -- Set generic types to have an unknown size, since the representation
3112 -- of a generic type is irrelevant, in view of the fact that they have
3113 -- nothing to do with code.
3115 if Is_Generic_Type
(Root_Type
(FST
)) then
3116 Set_RM_Size
(Def_Id
, Uint_0
);
3118 -- If the subtype statically matches the first subtype, then it is
3119 -- required to have exactly the same layout. This is required by
3120 -- aliasing considerations.
3122 elsif Def_Id
/= FST
and then
3123 Subtypes_Statically_Match
(Def_Id
, FST
)
3125 Set_RM_Size
(Def_Id
, RM_Size
(FST
));
3126 Set_Size_Info
(Def_Id
, FST
);
3128 -- In all other cases the RM_Size is set to the minimum size. Note that
3129 -- this routine is never called for subtypes for which the RM_Size is
3130 -- set explicitly by an attribute clause.
3133 Set_RM_Size
(Def_Id
, UI_From_Int
(Minimum_Size
(Def_Id
)));
3135 end Set_Discrete_RM_Size
;
3137 ------------------------
3138 -- Set_Elem_Alignment --
3139 ------------------------
3141 procedure Set_Elem_Alignment
(E
: Entity_Id
) is
3143 -- Do not set alignment for packed array types, unless we are doing
3144 -- front end layout, because otherwise this is always handled in the
3147 if Is_Packed_Array_Impl_Type
(E
)
3148 and then not Frontend_Layout_On_Target
3152 -- If there is an alignment clause, then we respect it
3154 elsif Has_Alignment_Clause
(E
) then
3157 -- If the size is not set, then don't attempt to set the alignment. This
3158 -- happens in the backend layout case for access-to-subprogram types.
3160 elsif not Known_Static_Esize
(E
) then
3163 -- For access types, do not set the alignment if the size is less than
3164 -- the allowed minimum size. This avoids cascaded error messages.
3166 elsif Is_Access_Type
(E
) and then Esize
(E
) < System_Address_Size
then
3170 -- Here we calculate the alignment as the largest power of two multiple
3171 -- of System.Storage_Unit that does not exceed either the object size of
3172 -- the type, or the maximum allowed alignment.
3178 Max_Alignment
: Nat
;
3181 -- The given Esize may be larger that int'last because of a previous
3182 -- error, and the call to UI_To_Int will fail, so use default.
3184 if Esize
(E
) / SSU
> Ttypes
.Maximum_Alignment
then
3185 S
:= Ttypes
.Maximum_Alignment
;
3187 -- If this is an access type and the target doesn't have strict
3188 -- alignment and we are not doing front end layout, then cap the
3189 -- alignment to that of a regular access type. This will avoid
3190 -- giving fat pointers twice the usual alignment for no practical
3191 -- benefit since the misalignment doesn't really matter.
3193 elsif Is_Access_Type
(E
)
3194 and then not Target_Strict_Alignment
3195 and then not Frontend_Layout_On_Target
3197 S
:= System_Address_Size
/ SSU
;
3200 S
:= UI_To_Int
(Esize
(E
)) / SSU
;
3203 -- If the default alignment of "double" floating-point types is
3204 -- specifically capped, enforce the cap.
3206 if Ttypes
.Target_Double_Float_Alignment
> 0
3208 and then Is_Floating_Point_Type
(E
)
3210 Max_Alignment
:= Ttypes
.Target_Double_Float_Alignment
;
3212 -- If the default alignment of "double" or larger scalar types is
3213 -- specifically capped, enforce the cap.
3215 elsif Ttypes
.Target_Double_Scalar_Alignment
> 0
3217 and then Is_Scalar_Type
(E
)
3219 Max_Alignment
:= Ttypes
.Target_Double_Scalar_Alignment
;
3221 -- Otherwise enforce the overall alignment cap
3224 Max_Alignment
:= Ttypes
.Maximum_Alignment
;
3228 while 2 * A
<= Max_Alignment
and then 2 * A
<= S
loop
3232 -- If alignment is currently not set, then we can safetly set it to
3233 -- this new calculated value.
3235 if Unknown_Alignment
(E
) then
3236 Init_Alignment
(E
, A
);
3238 -- Cases where we have inherited an alignment
3240 -- For constructed types, always reset the alignment, these are
3241 -- Generally invisible to the user anyway, and that way we are
3242 -- sure that no constructed types have weird alignments.
3244 elsif not Comes_From_Source
(E
) then
3245 Init_Alignment
(E
, A
);
3247 -- If this inherited alignment is the same as the one we computed,
3248 -- then obviously everything is fine, and we do not need to reset it.
3250 elsif Alignment
(E
) = A
then
3253 -- Now we come to the difficult cases where we have inherited an
3254 -- alignment and size, but overridden the size but not the alignment.
3256 elsif Has_Size_Clause
(E
) or else Has_Object_Size_Clause
(E
) then
3258 -- This is tricky, it might be thought that we should try to
3259 -- inherit the alignment, since that's what the RM implies, but
3260 -- that leads to complex rules and oddities. Consider for example:
3262 -- type R is new Character;
3263 -- for R'Size use 16;
3265 -- It seems quite bogus in this case to inherit an alignment of 1
3266 -- from the parent type Character. Furthermore, if that's what the
3267 -- programmer really wanted for some odd reason, then they could
3268 -- specify the alignment they wanted.
3270 -- Furthermore we really don't want to inherit the alignment in
3271 -- the case of a specified Object_Size for a subtype, since then
3272 -- there would be no way of overriding to give a reasonable value
3273 -- (we don't have an Object_Subtype attribute). Consider:
3275 -- subtype R is new Character;
3276 -- for R'Object_Size use 16;
3278 -- If we inherit the alignment of 1, then we have an odd
3279 -- inefficient alignment for the subtype, which cannot be fixed.
3281 -- So we make the decision that if Size (or Object_Size) is given
3282 -- (and, in the case of a first subtype, the alignment is not set
3283 -- with a specific alignment clause). We reset the alignment to
3284 -- the appropriate value for the specified size. This is a nice
3285 -- simple rule to implement and document.
3287 -- There is one slight glitch, which is that a confirming size
3288 -- clause can now change the alignment, which, if we really think
3289 -- that confirming rep clauses should have no effect, is a no-no.
3291 -- type R is new Character;
3292 -- for R'Alignment use 2;
3294 -- for S'Size use Character'Size;
3296 -- Now the alignment of S is 1 instead of 2, as a result of
3297 -- applying the above rule to the confirming rep clause for S. Not
3298 -- clear this is worth worrying about. If we recorded whether a
3299 -- size clause was confirming we could avoid this, but right now
3300 -- we have no way of doing that or easily figuring it out, so we
3303 -- Historical note. In versions of GNAT prior to Nov 6th, 2010, an
3304 -- odd distinction was made between inherited alignments greater
3305 -- than the computed alignment (where the larger alignment was
3306 -- inherited) and inherited alignments smaller than the computed
3307 -- alignment (where the smaller alignment was overridden). This
3308 -- was a dubious fix to get around an ACATS problem which seems
3309 -- to have disappeared anyway, and in any case, this peculiarity
3310 -- was never documented.
3312 Init_Alignment
(E
, A
);
3314 -- If no Size (or Object_Size) was specified, then we inherited the
3315 -- object size, so we should inherit the alignment as well and not
3316 -- modify it. This takes care of cases like:
3318 -- type R is new Integer;
3319 -- for R'Alignment use 1;
3322 -- Here we have R has a default Object_Size of 32, and a specified
3323 -- alignment of 1, and it seeems right for S to inherit both values.
3329 end Set_Elem_Alignment
;
3331 ----------------------
3332 -- SO_Ref_From_Expr --
3333 ----------------------
3335 function SO_Ref_From_Expr
3337 Ins_Type
: Entity_Id
;
3338 Vtype
: Entity_Id
:= Empty
;
3339 Make_Func
: Boolean := False) return Dynamic_SO_Ref
3341 Loc
: constant Source_Ptr
:= Sloc
(Ins_Type
);
3342 K
: constant Entity_Id
:= Make_Temporary
(Loc
, 'K');
3345 Vtype_Primary_View
: Entity_Id
;
3347 function Check_Node_V_Ref
(N
: Node_Id
) return Traverse_Result
;
3348 -- Function used to check one node for reference to V
3350 function Has_V_Ref
is new Traverse_Func
(Check_Node_V_Ref
);
3351 -- Function used to traverse tree to check for reference to V
3353 ----------------------
3354 -- Check_Node_V_Ref --
3355 ----------------------
3357 function Check_Node_V_Ref
(N
: Node_Id
) return Traverse_Result
is
3359 if Nkind
(N
) = N_Identifier
then
3360 if Chars
(N
) = Vname
then
3369 end Check_Node_V_Ref
;
3371 -- Start of processing for SO_Ref_From_Expr
3374 -- Case of expression is an integer literal, in this case we just
3375 -- return the value (which must always be non-negative, since size
3376 -- and offset values can never be negative).
3378 if Nkind
(Expr
) = N_Integer_Literal
then
3379 pragma Assert
(Intval
(Expr
) >= 0);
3380 return Intval
(Expr
);
3383 -- Case where there is a reference to V, create function
3385 if Has_V_Ref
(Expr
) = Abandon
then
3387 pragma Assert
(Present
(Vtype
));
3389 -- Check whether Vtype is a view of a private type and ensure that
3390 -- we use the primary view of the type (which is denoted by its
3391 -- Etype, whether it's the type's partial or full view entity).
3392 -- This is needed to make sure that we use the same (primary) view
3393 -- of the type for all V formals, whether the current view of the
3394 -- type is the partial or full view, so that types will always
3395 -- match on calls from one size function to another.
3397 if Has_Private_Declaration
(Vtype
) then
3398 Vtype_Primary_View
:= Etype
(Vtype
);
3400 Vtype_Primary_View
:= Vtype
;
3403 Set_Is_Discrim_SO_Function
(K
);
3406 Make_Subprogram_Body
(Loc
,
3409 Make_Function_Specification
(Loc
,
3410 Defining_Unit_Name
=> K
,
3411 Parameter_Specifications
=> New_List
(
3412 Make_Parameter_Specification
(Loc
,
3413 Defining_Identifier
=>
3414 Make_Defining_Identifier
(Loc
, Chars
=> Vname
),
3416 New_Occurrence_Of
(Vtype_Primary_View
, Loc
))),
3417 Result_Definition
=>
3418 New_Occurrence_Of
(Standard_Unsigned
, Loc
)),
3420 Declarations
=> Empty_List
,
3422 Handled_Statement_Sequence
=>
3423 Make_Handled_Sequence_Of_Statements
(Loc
,
3424 Statements
=> New_List
(
3425 Make_Simple_Return_Statement
(Loc
,
3426 Expression
=> Expr
))));
3428 -- The caller requests that the expression be encapsulated in a
3429 -- parameterless function.
3431 elsif Make_Func
then
3433 Make_Subprogram_Body
(Loc
,
3436 Make_Function_Specification
(Loc
,
3437 Defining_Unit_Name
=> K
,
3438 Parameter_Specifications
=> Empty_List
,
3439 Result_Definition
=>
3440 New_Occurrence_Of
(Standard_Unsigned
, Loc
)),
3442 Declarations
=> Empty_List
,
3444 Handled_Statement_Sequence
=>
3445 Make_Handled_Sequence_Of_Statements
(Loc
,
3446 Statements
=> New_List
(
3447 Make_Simple_Return_Statement
(Loc
, Expression
=> Expr
))));
3449 -- No reference to V and function not requested, so create a constant
3453 Make_Object_Declaration
(Loc
,
3454 Defining_Identifier
=> K
,
3455 Object_Definition
=>
3456 New_Occurrence_Of
(Standard_Unsigned
, Loc
),
3457 Constant_Present
=> True,
3458 Expression
=> Expr
);
3461 Append_Freeze_Action
(Ins_Type
, Decl
);
3463 return Create_Dynamic_SO_Ref
(K
);
3464 end SO_Ref_From_Expr
;