1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1992-2005, Free Software Foundation, Inc. --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 2, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING. If not, write --
19 -- to the Free Software Foundation, 51 Franklin Street, Fifth Floor, --
20 -- Boston, MA 02110-1301, USA. --
22 -- GNAT was originally developed by the GNAT team at New York University. --
23 -- Extensive contributions were provided by Ada Core Technologies Inc. --
25 ------------------------------------------------------------------------------
27 with Atree
; use Atree
;
28 with Debug
; use Debug
;
29 with Einfo
; use Einfo
;
30 with Elists
; use Elists
;
31 with Errout
; use Errout
;
32 with Exp_Ch7
; use Exp_Ch7
;
33 with Exp_Pakd
; use Exp_Pakd
;
34 with Exp_Util
; use Exp_Util
;
35 with Exp_Tss
; use Exp_Tss
;
36 with Layout
; use Layout
;
37 with Lib
.Xref
; use Lib
.Xref
;
38 with Nlists
; use Nlists
;
39 with Nmake
; use Nmake
;
41 with Restrict
; use Restrict
;
42 with Rident
; use Rident
;
44 with Sem_Cat
; use Sem_Cat
;
45 with Sem_Ch6
; use Sem_Ch6
;
46 with Sem_Ch7
; use Sem_Ch7
;
47 with Sem_Ch8
; use Sem_Ch8
;
48 with Sem_Ch13
; use Sem_Ch13
;
49 with Sem_Eval
; use Sem_Eval
;
50 with Sem_Mech
; use Sem_Mech
;
51 with Sem_Prag
; use Sem_Prag
;
52 with Sem_Res
; use Sem_Res
;
53 with Sem_Util
; use Sem_Util
;
54 with Sinfo
; use Sinfo
;
55 with Snames
; use Snames
;
56 with Stand
; use Stand
;
57 with Targparm
; use Targparm
;
58 with Tbuild
; use Tbuild
;
59 with Ttypes
; use Ttypes
;
60 with Uintp
; use Uintp
;
61 with Urealp
; use Urealp
;
63 package body Freeze
is
65 -----------------------
66 -- Local Subprograms --
67 -----------------------
69 procedure Adjust_Esize_For_Alignment
(Typ
: Entity_Id
);
70 -- Typ is a type that is being frozen. If no size clause is given,
71 -- but a default Esize has been computed, then this default Esize is
72 -- adjusted up if necessary to be consistent with a given alignment,
73 -- but never to a value greater than Long_Long_Integer'Size. This
74 -- is used for all discrete types and for fixed-point types.
76 procedure Build_And_Analyze_Renamed_Body
79 After
: in out Node_Id
);
80 -- Build body for a renaming declaration, insert in tree and analyze
82 procedure Check_Address_Clause
(E
: Entity_Id
);
83 -- Apply legality checks to address clauses for object declarations,
84 -- at the point the object is frozen.
86 procedure Check_Strict_Alignment
(E
: Entity_Id
);
87 -- E is a base type. If E is tagged or has a component that is aliased
88 -- or tagged or contains something this is aliased or tagged, set
91 procedure Check_Unsigned_Type
(E
: Entity_Id
);
92 pragma Inline
(Check_Unsigned_Type
);
93 -- If E is a fixed-point or discrete type, then all the necessary work
94 -- to freeze it is completed except for possible setting of the flag
95 -- Is_Unsigned_Type, which is done by this procedure. The call has no
96 -- effect if the entity E is not a discrete or fixed-point type.
98 procedure Freeze_And_Append
101 Result
: in out List_Id
);
102 -- Freezes Ent using Freeze_Entity, and appends the resulting list of
103 -- nodes to Result, modifying Result from No_List if necessary.
105 procedure Freeze_Enumeration_Type
(Typ
: Entity_Id
);
106 -- Freeze enumeration type. The Esize field is set as processing
107 -- proceeds (i.e. set by default when the type is declared and then
108 -- adjusted by rep clauses. What this procedure does is to make sure
109 -- that if a foreign convention is specified, and no specific size
110 -- is given, then the size must be at least Integer'Size.
112 procedure Freeze_Static_Object
(E
: Entity_Id
);
113 -- If an object is frozen which has Is_Statically_Allocated set, then
114 -- all referenced types must also be marked with this flag. This routine
115 -- is in charge of meeting this requirement for the object entity E.
117 procedure Freeze_Subprogram
(E
: Entity_Id
);
118 -- Perform freezing actions for a subprogram (create extra formals,
119 -- and set proper default mechanism values). Note that this routine
120 -- is not called for internal subprograms, for which neither of these
121 -- actions is needed (or desirable, we do not want for example to have
122 -- these extra formals present in initialization procedures, where they
123 -- would serve no purpose). In this call E is either a subprogram or
124 -- a subprogram type (i.e. an access to a subprogram).
126 function Is_Fully_Defined
(T
: Entity_Id
) return Boolean;
127 -- True if T is not private and has no private components, or has a full
128 -- view. Used to determine whether the designated type of an access type
129 -- should be frozen when the access type is frozen. This is done when an
130 -- allocator is frozen, or an expression that may involve attributes of
131 -- the designated type. Otherwise freezing the access type does not freeze
132 -- the designated type.
134 procedure Process_Default_Expressions
136 After
: in out Node_Id
);
137 -- This procedure is called for each subprogram to complete processing
138 -- of default expressions at the point where all types are known to be
139 -- frozen. The expressions must be analyzed in full, to make sure that
140 -- all error processing is done (they have only been pre-analyzed). If
141 -- the expression is not an entity or literal, its analysis may generate
142 -- code which must not be executed. In that case we build a function
143 -- body to hold that code. This wrapper function serves no other purpose
144 -- (it used to be called to evaluate the default, but now the default is
145 -- inlined at each point of call).
147 procedure Set_Component_Alignment_If_Not_Set
(Typ
: Entity_Id
);
148 -- Typ is a record or array type that is being frozen. This routine
149 -- sets the default component alignment from the scope stack values
150 -- if the alignment is otherwise not specified.
152 procedure Check_Debug_Info_Needed
(T
: Entity_Id
);
153 -- As each entity is frozen, this routine is called to deal with the
154 -- setting of Debug_Info_Needed for the entity. This flag is set if
155 -- the entity comes from source, or if we are in Debug_Generated_Code
156 -- mode or if the -gnatdV debug flag is set. However, it never sets
157 -- the flag if Debug_Info_Off is set.
159 procedure Set_Debug_Info_Needed
(T
: Entity_Id
);
160 -- Sets the Debug_Info_Needed flag on entity T if not already set, and
161 -- also on any entities that are needed by T (for an object, the type
162 -- of the object is needed, and for a type, the subsidiary types are
163 -- needed -- see body for details). Never has any effect on T if the
164 -- Debug_Info_Off flag is set.
166 procedure Undelay_Type
(T
: Entity_Id
);
167 -- T is a type of a component that we know to be an Itype.
168 -- We don't want this to have a Freeze_Node, so ensure it doesn't.
169 -- Do the same for any Full_View or Corresponding_Record_Type.
171 procedure Warn_Overlay
175 -- Expr is the expression for an address clause for entity Nam whose type
176 -- is Typ. If Typ has a default initialization, and there is no explicit
177 -- initialization in the source declaration, check whether the address
178 -- clause might cause overlaying of an entity, and emit a warning on the
179 -- side effect that the initialization will cause.
181 -------------------------------
182 -- Adjust_Esize_For_Alignment --
183 -------------------------------
185 procedure Adjust_Esize_For_Alignment
(Typ
: Entity_Id
) is
189 if Known_Esize
(Typ
) and then Known_Alignment
(Typ
) then
190 Align
:= Alignment_In_Bits
(Typ
);
192 if Align
> Esize
(Typ
)
193 and then Align
<= Standard_Long_Long_Integer_Size
195 Set_Esize
(Typ
, Align
);
198 end Adjust_Esize_For_Alignment
;
200 ------------------------------------
201 -- Build_And_Analyze_Renamed_Body --
202 ------------------------------------
204 procedure Build_And_Analyze_Renamed_Body
207 After
: in out Node_Id
)
209 Body_Node
: constant Node_Id
:= Build_Renamed_Body
(Decl
, New_S
);
211 Insert_After
(After
, Body_Node
);
212 Mark_Rewrite_Insertion
(Body_Node
);
215 end Build_And_Analyze_Renamed_Body
;
217 ------------------------
218 -- Build_Renamed_Body --
219 ------------------------
221 function Build_Renamed_Body
223 New_S
: Entity_Id
) return Node_Id
225 Loc
: constant Source_Ptr
:= Sloc
(New_S
);
226 -- We use for the source location of the renamed body, the location
227 -- of the spec entity. It might seem more natural to use the location
228 -- of the renaming declaration itself, but that would be wrong, since
229 -- then the body we create would look as though it was created far
230 -- too late, and this could cause problems with elaboration order
231 -- analysis, particularly in connection with instantiations.
233 N
: constant Node_Id
:= Unit_Declaration_Node
(New_S
);
234 Nam
: constant Node_Id
:= Name
(N
);
236 Spec
: constant Node_Id
:= New_Copy_Tree
(Specification
(Decl
));
237 Actuals
: List_Id
:= No_List
;
242 O_Formal
: Entity_Id
;
243 Param_Spec
: Node_Id
;
246 -- Determine the entity being renamed, which is the target of the
247 -- call statement. If the name is an explicit dereference, this is
248 -- a renaming of a subprogram type rather than a subprogram. The
249 -- name itself is fully analyzed.
251 if Nkind
(Nam
) = N_Selected_Component
then
252 Old_S
:= Entity
(Selector_Name
(Nam
));
254 elsif Nkind
(Nam
) = N_Explicit_Dereference
then
255 Old_S
:= Etype
(Nam
);
257 elsif Nkind
(Nam
) = N_Indexed_Component
then
258 if Is_Entity_Name
(Prefix
(Nam
)) then
259 Old_S
:= Entity
(Prefix
(Nam
));
261 Old_S
:= Entity
(Selector_Name
(Prefix
(Nam
)));
264 elsif Nkind
(Nam
) = N_Character_Literal
then
265 Old_S
:= Etype
(New_S
);
268 Old_S
:= Entity
(Nam
);
271 if Is_Entity_Name
(Nam
) then
273 -- If the renamed entity is a predefined operator, retain full
274 -- name to ensure its visibility.
276 if Ekind
(Old_S
) = E_Operator
277 and then Nkind
(Nam
) = N_Expanded_Name
279 Call_Name
:= New_Copy
(Name
(N
));
281 Call_Name
:= New_Reference_To
(Old_S
, Loc
);
285 Call_Name
:= New_Copy
(Name
(N
));
287 -- The original name may have been overloaded, but
288 -- is fully resolved now.
290 Set_Is_Overloaded
(Call_Name
, False);
293 -- For simple renamings, subsequent calls can be expanded directly
294 -- as called to the renamed entity. The body must be generated in
295 -- any case for calls they may appear elsewhere.
297 if (Ekind
(Old_S
) = E_Function
298 or else Ekind
(Old_S
) = E_Procedure
)
299 and then Nkind
(Decl
) = N_Subprogram_Declaration
301 Set_Body_To_Inline
(Decl
, Old_S
);
304 -- The body generated for this renaming is an internal artifact, and
305 -- does not constitute a freeze point for the called entity.
307 Set_Must_Not_Freeze
(Call_Name
);
309 Formal
:= First_Formal
(Defining_Entity
(Decl
));
311 if Present
(Formal
) then
314 while Present
(Formal
) loop
315 Append
(New_Reference_To
(Formal
, Loc
), Actuals
);
316 Next_Formal
(Formal
);
320 -- If the renamed entity is an entry, inherit its profile. For
321 -- other renamings as bodies, both profiles must be subtype
322 -- conformant, so it is not necessary to replace the profile given
323 -- in the declaration. However, default values that are aggregates
324 -- are rewritten when partially analyzed, so we recover the original
325 -- aggregate to insure that subsequent conformity checking works.
326 -- Similarly, if the default expression was constant-folded, recover
327 -- the original expression.
329 Formal
:= First_Formal
(Defining_Entity
(Decl
));
331 if Present
(Formal
) then
332 O_Formal
:= First_Formal
(Old_S
);
333 Param_Spec
:= First
(Parameter_Specifications
(Spec
));
335 while Present
(Formal
) loop
336 if Is_Entry
(Old_S
) then
338 if Nkind
(Parameter_Type
(Param_Spec
)) /=
341 Set_Etype
(Formal
, Etype
(O_Formal
));
342 Set_Entity
(Parameter_Type
(Param_Spec
), Etype
(O_Formal
));
345 elsif Nkind
(Default_Value
(O_Formal
)) = N_Aggregate
346 or else Nkind
(Original_Node
(Default_Value
(O_Formal
))) /=
347 Nkind
(Default_Value
(O_Formal
))
349 Set_Expression
(Param_Spec
,
350 New_Copy_Tree
(Original_Node
(Default_Value
(O_Formal
))));
353 Next_Formal
(Formal
);
354 Next_Formal
(O_Formal
);
359 -- If the renamed entity is a function, the generated body contains a
360 -- return statement. Otherwise, build a procedure call. If the entity is
361 -- an entry, subsequent analysis of the call will transform it into the
362 -- proper entry or protected operation call. If the renamed entity is
363 -- a character literal, return it directly.
365 if Ekind
(Old_S
) = E_Function
366 or else Ekind
(Old_S
) = E_Operator
367 or else (Ekind
(Old_S
) = E_Subprogram_Type
368 and then Etype
(Old_S
) /= Standard_Void_Type
)
371 Make_Return_Statement
(Loc
,
373 Make_Function_Call
(Loc
,
375 Parameter_Associations
=> Actuals
));
377 elsif Ekind
(Old_S
) = E_Enumeration_Literal
then
379 Make_Return_Statement
(Loc
,
380 Expression
=> New_Occurrence_Of
(Old_S
, Loc
));
382 elsif Nkind
(Nam
) = N_Character_Literal
then
384 Make_Return_Statement
(Loc
,
385 Expression
=> Call_Name
);
389 Make_Procedure_Call_Statement
(Loc
,
391 Parameter_Associations
=> Actuals
);
394 -- Create entities for subprogram body and formals
396 Set_Defining_Unit_Name
(Spec
,
397 Make_Defining_Identifier
(Loc
, Chars
=> Chars
(New_S
)));
399 Param_Spec
:= First
(Parameter_Specifications
(Spec
));
401 while Present
(Param_Spec
) loop
402 Set_Defining_Identifier
(Param_Spec
,
403 Make_Defining_Identifier
(Loc
,
404 Chars
=> Chars
(Defining_Identifier
(Param_Spec
))));
409 Make_Subprogram_Body
(Loc
,
410 Specification
=> Spec
,
411 Declarations
=> New_List
,
412 Handled_Statement_Sequence
=>
413 Make_Handled_Sequence_Of_Statements
(Loc
,
414 Statements
=> New_List
(Call_Node
)));
416 if Nkind
(Decl
) /= N_Subprogram_Declaration
then
418 Make_Subprogram_Declaration
(Loc
,
419 Specification
=> Specification
(N
)));
422 -- Link the body to the entity whose declaration it completes. If
423 -- the body is analyzed when the renamed entity is frozen, it may be
424 -- necessary to restore the proper scope (see package Exp_Ch13).
426 if Nkind
(N
) = N_Subprogram_Renaming_Declaration
427 and then Present
(Corresponding_Spec
(N
))
429 Set_Corresponding_Spec
(Body_Node
, Corresponding_Spec
(N
));
431 Set_Corresponding_Spec
(Body_Node
, New_S
);
435 end Build_Renamed_Body
;
437 --------------------------
438 -- Check_Address_Clause --
439 --------------------------
441 procedure Check_Address_Clause
(E
: Entity_Id
) is
442 Addr
: constant Node_Id
:= Address_Clause
(E
);
444 Decl
: constant Node_Id
:= Declaration_Node
(E
);
445 Typ
: constant Entity_Id
:= Etype
(E
);
448 if Present
(Addr
) then
449 Expr
:= Expression
(Addr
);
451 -- If we have no initialization of any kind, then we don't
452 -- need to place any restrictions on the address clause, because
453 -- the object will be elaborated after the address clause is
454 -- evaluated. This happens if the declaration has no initial
455 -- expression, or the type has no implicit initialization, or
456 -- the object is imported.
458 -- The same holds for all initialized scalar types and all
459 -- access types. Packed bit arrays of size up to 64 are
460 -- represented using a modular type with an initialization
461 -- (to zero) and can be processed like other initialized
464 -- If the type is controlled, code to attach the object to a
465 -- finalization chain is generated at the point of declaration,
466 -- and therefore the elaboration of the object cannot be delayed:
467 -- the address expression must be a constant.
469 if (No
(Expression
(Decl
))
470 and then not Controlled_Type
(Typ
)
472 (not Has_Non_Null_Base_Init_Proc
(Typ
)
473 or else Is_Imported
(E
)))
476 (Present
(Expression
(Decl
))
477 and then Is_Scalar_Type
(Typ
))
483 (Is_Bit_Packed_Array
(Typ
)
485 Is_Modular_Integer_Type
(Packed_Array_Type
(Typ
)))
489 -- Otherwise, we require the address clause to be constant
490 -- because the call to the initialization procedure (or the
491 -- attach code) has to happen at the point of the declaration.
494 Check_Constant_Address_Clause
(Expr
, E
);
495 Set_Has_Delayed_Freeze
(E
, False);
498 if not Error_Posted
(Expr
)
499 and then not Controlled_Type
(Typ
)
501 Warn_Overlay
(Expr
, Typ
, Name
(Addr
));
504 end Check_Address_Clause
;
506 -----------------------------
507 -- Check_Compile_Time_Size --
508 -----------------------------
510 procedure Check_Compile_Time_Size
(T
: Entity_Id
) is
512 procedure Set_Small_Size
(T
: Entity_Id
; S
: Uint
);
513 -- Sets the compile time known size (32 bits or less) in the Esize
514 -- field, of T checking for a size clause that was given which attempts
515 -- to give a smaller size.
517 function Size_Known
(T
: Entity_Id
) return Boolean;
518 -- Recursive function that does all the work
520 function Static_Discriminated_Components
(T
: Entity_Id
) return Boolean;
521 -- If T is a constrained subtype, its size is not known if any of its
522 -- discriminant constraints is not static and it is not a null record.
523 -- The test is conservative and doesn't check that the components are
524 -- in fact constrained by non-static discriminant values. Could be made
531 procedure Set_Small_Size
(T
: Entity_Id
; S
: Uint
) is
536 elsif Has_Size_Clause
(T
) then
537 if RM_Size
(T
) < S
then
538 Error_Msg_Uint_1
:= S
;
540 ("size for & is too small, minimum is ^",
543 elsif Unknown_Esize
(T
) then
547 -- Set sizes if not set already
550 if Unknown_Esize
(T
) then
554 if Unknown_RM_Size
(T
) then
564 function Size_Known
(T
: Entity_Id
) return Boolean is
572 if Size_Known_At_Compile_Time
(T
) then
575 elsif Is_Scalar_Type
(T
)
576 or else Is_Task_Type
(T
)
578 return not Is_Generic_Type
(T
);
580 elsif Is_Array_Type
(T
) then
581 if Ekind
(T
) = E_String_Literal_Subtype
then
582 Set_Small_Size
(T
, Component_Size
(T
)
583 * String_Literal_Length
(T
));
586 elsif not Is_Constrained
(T
) then
589 -- Don't do any recursion on type with error posted, since
590 -- we may have a malformed type that leads us into a loop
592 elsif Error_Posted
(T
) then
595 elsif not Size_Known
(Component_Type
(T
)) then
599 -- Check for all indexes static, and also compute possible
600 -- size (in case it is less than 32 and may be packable).
603 Esiz
: Uint
:= Component_Size
(T
);
607 Index
:= First_Index
(T
);
608 while Present
(Index
) loop
609 if Nkind
(Index
) = N_Range
then
610 Get_Index_Bounds
(Index
, Low
, High
);
612 elsif Error_Posted
(Scalar_Range
(Etype
(Index
))) then
616 Low
:= Type_Low_Bound
(Etype
(Index
));
617 High
:= Type_High_Bound
(Etype
(Index
));
620 if not Compile_Time_Known_Value
(Low
)
621 or else not Compile_Time_Known_Value
(High
)
622 or else Etype
(Index
) = Any_Type
627 Dim
:= Expr_Value
(High
) - Expr_Value
(Low
) + 1;
639 Set_Small_Size
(T
, Esiz
);
643 elsif Is_Access_Type
(T
) then
646 elsif Is_Private_Type
(T
)
647 and then not Is_Generic_Type
(T
)
648 and then Present
(Underlying_Type
(T
))
650 -- Don't do any recursion on type with error posted, since
651 -- we may have a malformed type that leads us into a loop
653 if Error_Posted
(T
) then
656 return Size_Known
(Underlying_Type
(T
));
659 elsif Is_Record_Type
(T
) then
661 -- A class-wide type is never considered to have a known size
663 if Is_Class_Wide_Type
(T
) then
666 -- A subtype of a variant record must not have non-static
667 -- discriminanted components.
669 elsif T
/= Base_Type
(T
)
670 and then not Static_Discriminated_Components
(T
)
674 -- Don't do any recursion on type with error posted, since
675 -- we may have a malformed type that leads us into a loop
677 elsif Error_Posted
(T
) then
681 -- Now look at the components of the record
684 -- The following two variables are used to keep track of
685 -- the size of packed records if we can tell the size of
686 -- the packed record in the front end. Packed_Size_Known
687 -- is True if so far we can figure out the size. It is
688 -- initialized to True for a packed record, unless the
689 -- record has discriminants. The reason we eliminate the
690 -- discriminated case is that we don't know the way the
691 -- back end lays out discriminated packed records. If
692 -- Packed_Size_Known is True, then Packed_Size is the
693 -- size in bits so far.
695 Packed_Size_Known
: Boolean :=
697 and then not Has_Discriminants
(T
);
699 Packed_Size
: Uint
:= Uint_0
;
702 -- Test for variant part present
704 if Has_Discriminants
(T
)
705 and then Present
(Parent
(T
))
706 and then Nkind
(Parent
(T
)) = N_Full_Type_Declaration
707 and then Nkind
(Type_Definition
(Parent
(T
))) =
709 and then not Null_Present
(Type_Definition
(Parent
(T
)))
710 and then Present
(Variant_Part
711 (Component_List
(Type_Definition
(Parent
(T
)))))
713 -- If variant part is present, and type is unconstrained,
714 -- then we must have defaulted discriminants, or a size
715 -- clause must be present for the type, or else the size
716 -- is definitely not known at compile time.
718 if not Is_Constrained
(T
)
720 No
(Discriminant_Default_Value
721 (First_Discriminant
(T
)))
722 and then Unknown_Esize
(T
)
728 -- Loop through components
730 Comp
:= First_Entity
(T
);
731 while Present
(Comp
) loop
732 if Ekind
(Comp
) = E_Component
734 Ekind
(Comp
) = E_Discriminant
736 Ctyp
:= Etype
(Comp
);
738 -- We do not know the packed size if there is a
739 -- component clause present (we possibly could,
740 -- but this would only help in the case of a record
741 -- with partial rep clauses. That's because in the
742 -- case of full rep clauses, the size gets figured
743 -- out anyway by a different circuit).
745 if Present
(Component_Clause
(Comp
)) then
746 Packed_Size_Known
:= False;
749 -- We need to identify a component that is an array
750 -- where the index type is an enumeration type with
751 -- non-standard representation, and some bound of the
752 -- type depends on a discriminant.
754 -- This is because gigi computes the size by doing a
755 -- substituation of the appropriate discriminant value
756 -- in the size expression for the base type, and gigi
757 -- is not clever enough to evaluate the resulting
758 -- expression (which involves a call to rep_to_pos)
761 -- It would be nice if gigi would either recognize that
762 -- this expression can be computed at compile time, or
763 -- alternatively figured out the size from the subtype
764 -- directly, where all the information is at hand ???
766 if Is_Array_Type
(Etype
(Comp
))
767 and then Present
(Packed_Array_Type
(Etype
(Comp
)))
770 Ocomp
: constant Entity_Id
:=
771 Original_Record_Component
(Comp
);
772 OCtyp
: constant Entity_Id
:= Etype
(Ocomp
);
778 Ind
:= First_Index
(OCtyp
);
779 while Present
(Ind
) loop
780 Indtyp
:= Etype
(Ind
);
782 if Is_Enumeration_Type
(Indtyp
)
783 and then Has_Non_Standard_Rep
(Indtyp
)
785 Lo
:= Type_Low_Bound
(Indtyp
);
786 Hi
:= Type_High_Bound
(Indtyp
);
788 if Is_Entity_Name
(Lo
)
790 Ekind
(Entity
(Lo
)) = E_Discriminant
794 elsif Is_Entity_Name
(Hi
)
796 Ekind
(Entity
(Hi
)) = E_Discriminant
807 -- Clearly size of record is not known if the size of
808 -- one of the components is not known.
810 if not Size_Known
(Ctyp
) then
814 -- Accumulate packed size if possible
816 if Packed_Size_Known
then
818 -- We can only deal with elementary types, since for
819 -- non-elementary components, alignment enters into
820 -- the picture, and we don't know enough to handle
821 -- proper alignment in this context. Packed arrays
822 -- count as elementary if the representation is a
825 if Is_Elementary_Type
(Ctyp
)
826 or else (Is_Array_Type
(Ctyp
)
828 Present
(Packed_Array_Type
(Ctyp
))
830 Is_Modular_Integer_Type
831 (Packed_Array_Type
(Ctyp
)))
833 -- If RM_Size is known and static, then we can
834 -- keep accumulating the packed size.
836 if Known_Static_RM_Size
(Ctyp
) then
838 -- A little glitch, to be removed sometime ???
839 -- gigi does not understand zero sizes yet.
841 if RM_Size
(Ctyp
) = Uint_0
then
842 Packed_Size_Known
:= False;
844 -- Normal case where we can keep accumulating
845 -- the packed array size.
848 Packed_Size
:= Packed_Size
+ RM_Size
(Ctyp
);
851 -- If we have a field whose RM_Size is not known
852 -- then we can't figure out the packed size here.
855 Packed_Size_Known
:= False;
858 -- If we have a non-elementary type we can't figure
859 -- out the packed array size (alignment issues).
862 Packed_Size_Known
:= False;
870 if Packed_Size_Known
then
871 Set_Small_Size
(T
, Packed_Size
);
882 -------------------------------------
883 -- Static_Discriminated_Components --
884 -------------------------------------
886 function Static_Discriminated_Components
887 (T
: Entity_Id
) return Boolean
889 Constraint
: Elmt_Id
;
892 if Has_Discriminants
(T
)
893 and then Present
(Discriminant_Constraint
(T
))
894 and then Present
(First_Component
(T
))
896 Constraint
:= First_Elmt
(Discriminant_Constraint
(T
));
897 while Present
(Constraint
) loop
898 if not Compile_Time_Known_Value
(Node
(Constraint
)) then
902 Next_Elmt
(Constraint
);
907 end Static_Discriminated_Components
;
909 -- Start of processing for Check_Compile_Time_Size
912 Set_Size_Known_At_Compile_Time
(T
, Size_Known
(T
));
913 end Check_Compile_Time_Size
;
915 -----------------------------
916 -- Check_Debug_Info_Needed --
917 -----------------------------
919 procedure Check_Debug_Info_Needed
(T
: Entity_Id
) is
921 if Needs_Debug_Info
(T
) or else Debug_Info_Off
(T
) then
924 elsif Comes_From_Source
(T
)
925 or else Debug_Generated_Code
926 or else Debug_Flag_VV
928 Set_Debug_Info_Needed
(T
);
930 end Check_Debug_Info_Needed
;
932 ----------------------------
933 -- Check_Strict_Alignment --
934 ----------------------------
936 procedure Check_Strict_Alignment
(E
: Entity_Id
) is
940 if Is_Tagged_Type
(E
) or else Is_Concurrent_Type
(E
) then
941 Set_Strict_Alignment
(E
);
943 elsif Is_Array_Type
(E
) then
944 Set_Strict_Alignment
(E
, Strict_Alignment
(Component_Type
(E
)));
946 elsif Is_Record_Type
(E
) then
947 if Is_Limited_Record
(E
) then
948 Set_Strict_Alignment
(E
);
952 Comp
:= First_Component
(E
);
954 while Present
(Comp
) loop
955 if not Is_Type
(Comp
)
956 and then (Strict_Alignment
(Etype
(Comp
))
957 or else Is_Aliased
(Comp
))
959 Set_Strict_Alignment
(E
);
963 Next_Component
(Comp
);
966 end Check_Strict_Alignment
;
968 -------------------------
969 -- Check_Unsigned_Type --
970 -------------------------
972 procedure Check_Unsigned_Type
(E
: Entity_Id
) is
973 Ancestor
: Entity_Id
;
978 if not Is_Discrete_Or_Fixed_Point_Type
(E
) then
982 -- Do not attempt to analyze case where range was in error
984 if Error_Posted
(Scalar_Range
(E
)) then
988 -- The situation that is non trivial is something like
990 -- subtype x1 is integer range -10 .. +10;
991 -- subtype x2 is x1 range 0 .. V1;
992 -- subtype x3 is x2 range V2 .. V3;
993 -- subtype x4 is x3 range V4 .. V5;
995 -- where Vn are variables. Here the base type is signed, but we still
996 -- know that x4 is unsigned because of the lower bound of x2.
998 -- The only way to deal with this is to look up the ancestor chain
1002 if Ancestor
= Any_Type
or else Etype
(Ancestor
) = Any_Type
then
1006 Lo_Bound
:= Type_Low_Bound
(Ancestor
);
1008 if Compile_Time_Known_Value
(Lo_Bound
) then
1010 if Expr_Rep_Value
(Lo_Bound
) >= 0 then
1011 Set_Is_Unsigned_Type
(E
, True);
1017 Ancestor
:= Ancestor_Subtype
(Ancestor
);
1019 -- If no ancestor had a static lower bound, go to base type
1021 if No
(Ancestor
) then
1023 -- Note: the reason we still check for a compile time known
1024 -- value for the base type is that at least in the case of
1025 -- generic formals, we can have bounds that fail this test,
1026 -- and there may be other cases in error situations.
1028 Btyp
:= Base_Type
(E
);
1030 if Btyp
= Any_Type
or else Etype
(Btyp
) = Any_Type
then
1034 Lo_Bound
:= Type_Low_Bound
(Base_Type
(E
));
1036 if Compile_Time_Known_Value
(Lo_Bound
)
1037 and then Expr_Rep_Value
(Lo_Bound
) >= 0
1039 Set_Is_Unsigned_Type
(E
, True);
1046 end Check_Unsigned_Type
;
1048 -----------------------------
1049 -- Expand_Atomic_Aggregate --
1050 -----------------------------
1052 procedure Expand_Atomic_Aggregate
(E
: Entity_Id
; Typ
: Entity_Id
) is
1053 Loc
: constant Source_Ptr
:= Sloc
(E
);
1058 if (Nkind
(Parent
(E
)) = N_Object_Declaration
1059 or else Nkind
(Parent
(E
)) = N_Assignment_Statement
)
1060 and then Comes_From_Source
(Parent
(E
))
1061 and then Nkind
(E
) = N_Aggregate
1064 Make_Defining_Identifier
(Loc
,
1065 New_Internal_Name
('T'));
1068 Make_Object_Declaration
(Loc
,
1069 Defining_Identifier
=> Temp
,
1070 Object_definition
=> New_Occurrence_Of
(Typ
, Loc
),
1071 Expression
=> Relocate_Node
(E
));
1072 Insert_Before
(Parent
(E
), New_N
);
1075 Set_Expression
(Parent
(E
), New_Occurrence_Of
(Temp
, Loc
));
1077 -- To prevent the temporary from being constant-folded (which
1078 -- would lead to the same piecemeal assignment on the original
1079 -- target) indicate to the back-end that the temporary is a
1080 -- variable with real storage. See description of this flag
1081 -- in Einfo, and the notes on N_Assignment_Statement and
1082 -- N_Object_Declaration in Sinfo.
1084 Set_Is_True_Constant
(Temp
, False);
1086 end Expand_Atomic_Aggregate
;
1092 -- Note: the easy coding for this procedure would be to just build a
1093 -- single list of freeze nodes and then insert them and analyze them
1094 -- all at once. This won't work, because the analysis of earlier freeze
1095 -- nodes may recursively freeze types which would otherwise appear later
1096 -- on in the freeze list. So we must analyze and expand the freeze nodes
1097 -- as they are generated.
1099 procedure Freeze_All
(From
: Entity_Id
; After
: in out Node_Id
) is
1100 Loc
: constant Source_Ptr
:= Sloc
(After
);
1104 procedure Freeze_All_Ent
(From
: Entity_Id
; After
: in out Node_Id
);
1105 -- This is the internal recursive routine that does freezing of
1106 -- entities (but NOT the analysis of default expressions, which
1107 -- should not be recursive, we don't want to analyze those till
1108 -- we are sure that ALL the types are frozen).
1110 --------------------
1111 -- Freeze_All_Ent --
1112 --------------------
1114 procedure Freeze_All_Ent
1116 After
: in out Node_Id
)
1122 procedure Process_Flist
;
1123 -- If freeze nodes are present, insert and analyze, and reset
1124 -- cursor for next insertion.
1130 procedure Process_Flist
is
1132 if Is_Non_Empty_List
(Flist
) then
1133 Lastn
:= Next
(After
);
1134 Insert_List_After_And_Analyze
(After
, Flist
);
1136 if Present
(Lastn
) then
1137 After
:= Prev
(Lastn
);
1139 After
:= Last
(List_Containing
(After
));
1144 -- Start or processing for Freeze_All_Ent
1148 while Present
(E
) loop
1150 -- If the entity is an inner package which is not a package
1151 -- renaming, then its entities must be frozen at this point.
1152 -- Note that such entities do NOT get frozen at the end of
1153 -- the nested package itself (only library packages freeze).
1155 -- Same is true for task declarations, where anonymous records
1156 -- created for entry parameters must be frozen.
1158 if Ekind
(E
) = E_Package
1159 and then No
(Renamed_Object
(E
))
1160 and then not Is_Child_Unit
(E
)
1161 and then not Is_Frozen
(E
)
1164 Install_Visible_Declarations
(E
);
1165 Install_Private_Declarations
(E
);
1167 Freeze_All
(First_Entity
(E
), After
);
1169 End_Package_Scope
(E
);
1171 elsif Ekind
(E
) in Task_Kind
1173 (Nkind
(Parent
(E
)) = N_Task_Type_Declaration
1175 Nkind
(Parent
(E
)) = N_Single_Task_Declaration
)
1178 Freeze_All
(First_Entity
(E
), After
);
1181 -- For a derived tagged type, we must ensure that all the
1182 -- primitive operations of the parent have been frozen, so
1183 -- that their addresses will be in the parent's dispatch table
1184 -- at the point it is inherited.
1186 elsif Ekind
(E
) = E_Record_Type
1187 and then Is_Tagged_Type
(E
)
1188 and then Is_Tagged_Type
(Etype
(E
))
1189 and then Is_Derived_Type
(E
)
1192 Prim_List
: constant Elist_Id
:=
1193 Primitive_Operations
(Etype
(E
));
1199 Prim
:= First_Elmt
(Prim_List
);
1201 while Present
(Prim
) loop
1202 Subp
:= Node
(Prim
);
1204 if Comes_From_Source
(Subp
)
1205 and then not Is_Frozen
(Subp
)
1207 Flist
:= Freeze_Entity
(Subp
, Loc
);
1216 if not Is_Frozen
(E
) then
1217 Flist
:= Freeze_Entity
(E
, Loc
);
1221 -- If an incomplete type is still not frozen, this may be
1222 -- a premature freezing because of a body declaration that
1223 -- follows. Indicate where the freezing took place.
1225 -- If the freezing is caused by the end of the current
1226 -- declarative part, it is a Taft Amendment type, and there
1229 if not Is_Frozen
(E
)
1230 and then Ekind
(E
) = E_Incomplete_Type
1233 Bod
: constant Node_Id
:= Next
(After
);
1236 if (Nkind
(Bod
) = N_Subprogram_Body
1237 or else Nkind
(Bod
) = N_Entry_Body
1238 or else Nkind
(Bod
) = N_Package_Body
1239 or else Nkind
(Bod
) = N_Protected_Body
1240 or else Nkind
(Bod
) = N_Task_Body
1241 or else Nkind
(Bod
) in N_Body_Stub
)
1243 List_Containing
(After
) = List_Containing
(Parent
(E
))
1245 Error_Msg_Sloc
:= Sloc
(Next
(After
));
1247 ("type& is frozen# before its full declaration",
1257 -- Start of processing for Freeze_All
1260 Freeze_All_Ent
(From
, After
);
1262 -- Now that all types are frozen, we can deal with default expressions
1263 -- that require us to build a default expression functions. This is the
1264 -- point at which such functions are constructed (after all types that
1265 -- might be used in such expressions have been frozen).
1267 -- We also add finalization chains to access types whose designated
1268 -- types are controlled. This is normally done when freezing the type,
1269 -- but this misses recursive type definitions where the later members
1270 -- of the recursion introduce controlled components (e.g. 5624-001).
1272 -- Loop through entities
1275 while Present
(E
) loop
1276 if Is_Subprogram
(E
) then
1278 if not Default_Expressions_Processed
(E
) then
1279 Process_Default_Expressions
(E
, After
);
1282 if not Has_Completion
(E
) then
1283 Decl
:= Unit_Declaration_Node
(E
);
1285 if Nkind
(Decl
) = N_Subprogram_Renaming_Declaration
then
1286 Build_And_Analyze_Renamed_Body
(Decl
, E
, After
);
1288 elsif Nkind
(Decl
) = N_Subprogram_Declaration
1289 and then Present
(Corresponding_Body
(Decl
))
1291 Nkind
(Unit_Declaration_Node
(Corresponding_Body
(Decl
)))
1292 = N_Subprogram_Renaming_Declaration
1294 Build_And_Analyze_Renamed_Body
1295 (Decl
, Corresponding_Body
(Decl
), After
);
1299 elsif Ekind
(E
) in Task_Kind
1301 (Nkind
(Parent
(E
)) = N_Task_Type_Declaration
1303 Nkind
(Parent
(E
)) = N_Single_Task_Declaration
)
1308 Ent
:= First_Entity
(E
);
1310 while Present
(Ent
) loop
1313 and then not Default_Expressions_Processed
(Ent
)
1315 Process_Default_Expressions
(Ent
, After
);
1322 elsif Is_Access_Type
(E
)
1323 and then Comes_From_Source
(E
)
1324 and then Ekind
(Directly_Designated_Type
(E
)) = E_Incomplete_Type
1325 and then Controlled_Type
(Designated_Type
(E
))
1326 and then No
(Associated_Final_Chain
(E
))
1328 Build_Final_List
(Parent
(E
), E
);
1335 -----------------------
1336 -- Freeze_And_Append --
1337 -----------------------
1339 procedure Freeze_And_Append
1342 Result
: in out List_Id
)
1344 L
: constant List_Id
:= Freeze_Entity
(Ent
, Loc
);
1346 if Is_Non_Empty_List
(L
) then
1347 if Result
= No_List
then
1350 Append_List
(L
, Result
);
1353 end Freeze_And_Append
;
1359 procedure Freeze_Before
(N
: Node_Id
; T
: Entity_Id
) is
1360 Freeze_Nodes
: constant List_Id
:= Freeze_Entity
(T
, Sloc
(N
));
1362 if Is_Non_Empty_List
(Freeze_Nodes
) then
1363 Insert_Actions
(N
, Freeze_Nodes
);
1371 function Freeze_Entity
(E
: Entity_Id
; Loc
: Source_Ptr
) return List_Id
is
1372 Test_E
: Entity_Id
:= E
;
1380 procedure Check_Current_Instance
(Comp_Decl
: Node_Id
);
1381 -- Check that an Access or Unchecked_Access attribute with a prefix
1382 -- which is the current instance type can only be applied when the type
1385 function After_Last_Declaration
return Boolean;
1386 -- If Loc is a freeze_entity that appears after the last declaration
1387 -- in the scope, inhibit error messages on late completion.
1389 procedure Freeze_Record_Type
(Rec
: Entity_Id
);
1390 -- Freeze each component, handle some representation clauses, and freeze
1391 -- primitive operations if this is a tagged type.
1393 ----------------------------
1394 -- After_Last_Declaration --
1395 ----------------------------
1397 function After_Last_Declaration
return Boolean is
1398 Spec
: constant Node_Id
:= Parent
(Current_Scope
);
1401 if Nkind
(Spec
) = N_Package_Specification
then
1402 if Present
(Private_Declarations
(Spec
)) then
1403 return Loc
>= Sloc
(Last
(Private_Declarations
(Spec
)));
1405 elsif Present
(Visible_Declarations
(Spec
)) then
1406 return Loc
>= Sloc
(Last
(Visible_Declarations
(Spec
)));
1414 end After_Last_Declaration
;
1416 ----------------------------
1417 -- Check_Current_Instance --
1418 ----------------------------
1420 procedure Check_Current_Instance
(Comp_Decl
: Node_Id
) is
1422 function Process
(N
: Node_Id
) return Traverse_Result
;
1423 -- Process routine to apply check to given node
1429 function Process
(N
: Node_Id
) return Traverse_Result
is
1432 when N_Attribute_Reference
=>
1433 if (Attribute_Name
(N
) = Name_Access
1435 Attribute_Name
(N
) = Name_Unchecked_Access
)
1436 and then Is_Entity_Name
(Prefix
(N
))
1437 and then Is_Type
(Entity
(Prefix
(N
)))
1438 and then Entity
(Prefix
(N
)) = E
1441 ("current instance must be a limited type", Prefix
(N
));
1447 when others => return OK
;
1451 procedure Traverse
is new Traverse_Proc
(Process
);
1453 -- Start of processing for Check_Current_Instance
1456 Traverse
(Comp_Decl
);
1457 end Check_Current_Instance
;
1459 ------------------------
1460 -- Freeze_Record_Type --
1461 ------------------------
1463 procedure Freeze_Record_Type
(Rec
: Entity_Id
) is
1470 Unplaced_Component
: Boolean := False;
1471 -- Set True if we find at least one component with no component
1472 -- clause (used to warn about useless Pack pragmas).
1474 Placed_Component
: Boolean := False;
1475 -- Set True if we find at least one component with a component
1476 -- clause (used to warn about useless Bit_Order pragmas).
1478 procedure Check_Itype
(Desig
: Entity_Id
);
1479 -- If the component subtype is an access to a constrained subtype
1480 -- of an already frozen type, make the subtype frozen as well. It
1481 -- might otherwise be frozen in the wrong scope, and a freeze node
1482 -- on subtype has no effect.
1488 procedure Check_Itype
(Desig
: Entity_Id
) is
1490 if not Is_Frozen
(Desig
)
1491 and then Is_Frozen
(Base_Type
(Desig
))
1493 Set_Is_Frozen
(Desig
);
1495 -- In addition, add an Itype_Reference to ensure that the
1496 -- access subtype is elaborated early enough. This cannot
1497 -- be done if the subtype may depend on discriminants.
1499 if Ekind
(Comp
) = E_Component
1500 and then Is_Itype
(Etype
(Comp
))
1501 and then not Has_Discriminants
(Rec
)
1503 IR
:= Make_Itype_Reference
(Sloc
(Comp
));
1504 Set_Itype
(IR
, Desig
);
1507 Result
:= New_List
(IR
);
1509 Append
(IR
, Result
);
1515 -- Start of processing for Freeze_Record_Type
1518 -- If this is a subtype of a controlled type, declared without
1519 -- a constraint, the _controller may not appear in the component
1520 -- list if the parent was not frozen at the point of subtype
1521 -- declaration. Inherit the _controller component now.
1523 if Rec
/= Base_Type
(Rec
)
1524 and then Has_Controlled_Component
(Rec
)
1526 if Nkind
(Parent
(Rec
)) = N_Subtype_Declaration
1527 and then Is_Entity_Name
(Subtype_Indication
(Parent
(Rec
)))
1529 Set_First_Entity
(Rec
, First_Entity
(Base_Type
(Rec
)));
1531 -- If this is an internal type without a declaration, as for
1532 -- record component, the base type may not yet be frozen, and its
1533 -- controller has not been created. Add an explicit freeze node
1534 -- for the itype, so it will be frozen after the base type. This
1535 -- freeze node is used to communicate with the expander, in order
1536 -- to create the controller for the enclosing record, and it is
1537 -- deleted afterwards (see exp_ch3). It must not be created when
1538 -- expansion is off, because it might appear in the wrong context
1539 -- for the back end.
1541 elsif Is_Itype
(Rec
)
1542 and then Has_Delayed_Freeze
(Base_Type
(Rec
))
1544 Nkind
(Associated_Node_For_Itype
(Rec
)) =
1545 N_Component_Declaration
1546 and then Expander_Active
1548 Ensure_Freeze_Node
(Rec
);
1552 -- Freeze components and embedded subtypes
1554 Comp
:= First_Entity
(Rec
);
1556 while Present
(Comp
) loop
1558 -- First handle the (real) component case
1560 if Ekind
(Comp
) = E_Component
1561 or else Ekind
(Comp
) = E_Discriminant
1564 CC
: constant Node_Id
:= Component_Clause
(Comp
);
1567 -- Freezing a record type freezes the type of each of its
1568 -- components. However, if the type of the component is
1569 -- part of this record, we do not want or need a separate
1570 -- Freeze_Node. Note that Is_Itype is wrong because that's
1571 -- also set in private type cases. We also can't check for
1572 -- the Scope being exactly Rec because of private types and
1573 -- record extensions.
1575 if Is_Itype
(Etype
(Comp
))
1576 and then Is_Record_Type
(Underlying_Type
1577 (Scope
(Etype
(Comp
))))
1579 Undelay_Type
(Etype
(Comp
));
1582 Freeze_And_Append
(Etype
(Comp
), Loc
, Result
);
1584 -- Check for error of component clause given for variable
1585 -- sized type. We have to delay this test till this point,
1586 -- since the component type has to be frozen for us to know
1587 -- if it is variable length. We omit this test in a generic
1588 -- context, it will be applied at instantiation time.
1590 if Present
(CC
) then
1591 Placed_Component
:= True;
1593 if Inside_A_Generic
then
1596 elsif not Size_Known_At_Compile_Time
1597 (Underlying_Type
(Etype
(Comp
)))
1600 ("component clause not allowed for variable " &
1601 "length component", CC
);
1605 Unplaced_Component
:= True;
1608 -- Case of component requires byte alignment
1610 if Must_Be_On_Byte_Boundary
(Etype
(Comp
)) then
1612 -- Set the enclosing record to also require byte align
1614 Set_Must_Be_On_Byte_Boundary
(Rec
);
1616 -- Check for component clause that is inconsistent
1617 -- with the required byte boundary alignment.
1620 and then Normalized_First_Bit
(Comp
) mod
1621 System_Storage_Unit
/= 0
1624 ("component & must be byte aligned",
1625 Component_Name
(Component_Clause
(Comp
)));
1629 -- If component clause is present, then deal with the
1630 -- non-default bit order case. We cannot do this before
1631 -- the freeze point, because there is no required order
1632 -- for the component clause and the bit_order clause.
1634 -- We only do this processing for the base type, and in
1635 -- fact that's important, since otherwise if there are
1636 -- record subtypes, we could reverse the bits once for
1637 -- each subtype, which would be incorrect.
1640 and then Reverse_Bit_Order
(Rec
)
1641 and then Ekind
(E
) = E_Record_Type
1644 CFB
: constant Uint
:= Component_Bit_Offset
(Comp
);
1645 CSZ
: constant Uint
:= Esize
(Comp
);
1646 CLC
: constant Node_Id
:= Component_Clause
(Comp
);
1647 Pos
: constant Node_Id
:= Position
(CLC
);
1648 FB
: constant Node_Id
:= First_Bit
(CLC
);
1650 Storage_Unit_Offset
: constant Uint
:=
1651 CFB
/ System_Storage_Unit
;
1653 Start_Bit
: constant Uint
:=
1654 CFB
mod System_Storage_Unit
;
1657 -- Cases where field goes over storage unit boundary
1659 if Start_Bit
+ CSZ
> System_Storage_Unit
then
1661 -- Allow multi-byte field but generate warning
1663 if Start_Bit
mod System_Storage_Unit
= 0
1664 and then CSZ
mod System_Storage_Unit
= 0
1667 ("multi-byte field specified with non-standard"
1668 & " Bit_Order?", CLC
);
1670 if Bytes_Big_Endian
then
1672 ("bytes are not reversed "
1673 & "(component is big-endian)?", CLC
);
1676 ("bytes are not reversed "
1677 & "(component is little-endian)?", CLC
);
1680 -- Do not allow non-contiguous field
1684 ("attempt to specify non-contiguous field"
1685 & " not permitted", CLC
);
1687 ("\(caused by non-standard Bit_Order "
1688 & "specified)", CLC
);
1691 -- Case where field fits in one storage unit
1694 -- Give warning if suspicious component clause
1696 if Intval
(FB
) >= System_Storage_Unit
then
1698 ("?Bit_Order clause does not affect " &
1699 "byte ordering", Pos
);
1701 Intval
(Pos
) + Intval
(FB
) /
1702 System_Storage_Unit
;
1704 ("?position normalized to ^ before bit " &
1705 "order interpreted", Pos
);
1708 -- Here is where we fix up the Component_Bit_Offset
1709 -- value to account for the reverse bit order.
1710 -- Some examples of what needs to be done are:
1712 -- First_Bit .. Last_Bit Component_Bit_Offset
1715 -- 0 .. 0 7 .. 7 0 7
1716 -- 0 .. 1 6 .. 7 0 6
1717 -- 0 .. 2 5 .. 7 0 5
1718 -- 0 .. 7 0 .. 7 0 4
1720 -- 1 .. 1 6 .. 6 1 6
1721 -- 1 .. 4 3 .. 6 1 3
1722 -- 4 .. 7 0 .. 3 4 0
1724 -- The general rule is that the first bit is
1725 -- is obtained by subtracting the old ending bit
1726 -- from storage_unit - 1.
1728 Set_Component_Bit_Offset
1730 (Storage_Unit_Offset
* System_Storage_Unit
) +
1731 (System_Storage_Unit
- 1) -
1732 (Start_Bit
+ CSZ
- 1));
1734 Set_Normalized_First_Bit
1736 Component_Bit_Offset
(Comp
) mod
1737 System_Storage_Unit
);
1744 -- If the component is an Itype with Delayed_Freeze and is either
1745 -- a record or array subtype and its base type has not yet been
1746 -- frozen, we must remove this from the entity list of this
1747 -- record and put it on the entity list of the scope of its base
1748 -- type. Note that we know that this is not the type of a
1749 -- component since we cleared Has_Delayed_Freeze for it in the
1750 -- previous loop. Thus this must be the Designated_Type of an
1751 -- access type, which is the type of a component.
1754 and then Is_Type
(Scope
(Comp
))
1755 and then Is_Composite_Type
(Comp
)
1756 and then Base_Type
(Comp
) /= Comp
1757 and then Has_Delayed_Freeze
(Comp
)
1758 and then not Is_Frozen
(Base_Type
(Comp
))
1761 Will_Be_Frozen
: Boolean := False;
1762 S
: Entity_Id
:= Scope
(Rec
);
1765 -- We have a pretty bad kludge here. Suppose Rec is a
1766 -- subtype being defined in a subprogram that's created
1767 -- as part of the freezing of Rec'Base. In that case,
1768 -- we know that Comp'Base must have already been frozen by
1769 -- the time we get to elaborate this because Gigi doesn't
1770 -- elaborate any bodies until it has elaborated all of the
1771 -- declarative part. But Is_Frozen will not be set at this
1772 -- point because we are processing code in lexical order.
1774 -- We detect this case by going up the Scope chain of
1775 -- Rec and seeing if we have a subprogram scope before
1776 -- reaching the top of the scope chain or that of Comp'Base.
1777 -- If we do, then mark that Comp'Base will actually be
1778 -- frozen. If so, we merely undelay it.
1780 while Present
(S
) loop
1781 if Is_Subprogram
(S
) then
1782 Will_Be_Frozen
:= True;
1784 elsif S
= Scope
(Base_Type
(Comp
)) then
1791 if Will_Be_Frozen
then
1792 Undelay_Type
(Comp
);
1794 if Present
(Prev
) then
1795 Set_Next_Entity
(Prev
, Next_Entity
(Comp
));
1797 Set_First_Entity
(Rec
, Next_Entity
(Comp
));
1800 -- Insert in entity list of scope of base type (which
1801 -- must be an enclosing scope, because still unfrozen).
1803 Append_Entity
(Comp
, Scope
(Base_Type
(Comp
)));
1807 -- If the component is an access type with an allocator as
1808 -- default value, the designated type will be frozen by the
1809 -- corresponding expression in init_proc. In order to place the
1810 -- freeze node for the designated type before that for the
1811 -- current record type, freeze it now.
1813 -- Same process if the component is an array of access types,
1814 -- initialized with an aggregate. If the designated type is
1815 -- private, it cannot contain allocators, and it is premature to
1816 -- freeze the type, so we check for this as well.
1818 elsif Is_Access_Type
(Etype
(Comp
))
1819 and then Present
(Parent
(Comp
))
1820 and then Present
(Expression
(Parent
(Comp
)))
1821 and then Nkind
(Expression
(Parent
(Comp
))) = N_Allocator
1824 Alloc
: constant Node_Id
:= Expression
(Parent
(Comp
));
1827 -- If component is pointer to a classwide type, freeze
1828 -- the specific type in the expression being allocated.
1829 -- The expression may be a subtype indication, in which
1830 -- case freeze the subtype mark.
1832 if Is_Class_Wide_Type
(Designated_Type
(Etype
(Comp
))) then
1833 if Is_Entity_Name
(Expression
(Alloc
)) then
1835 (Entity
(Expression
(Alloc
)), Loc
, Result
);
1837 Nkind
(Expression
(Alloc
)) = N_Subtype_Indication
1840 (Entity
(Subtype_Mark
(Expression
(Alloc
))),
1844 elsif Is_Itype
(Designated_Type
(Etype
(Comp
))) then
1845 Check_Itype
(Designated_Type
(Etype
(Comp
)));
1849 (Designated_Type
(Etype
(Comp
)), Loc
, Result
);
1853 elsif Is_Access_Type
(Etype
(Comp
))
1854 and then Is_Itype
(Designated_Type
(Etype
(Comp
)))
1856 Check_Itype
(Designated_Type
(Etype
(Comp
)));
1858 elsif Is_Array_Type
(Etype
(Comp
))
1859 and then Is_Access_Type
(Component_Type
(Etype
(Comp
)))
1860 and then Present
(Parent
(Comp
))
1861 and then Nkind
(Parent
(Comp
)) = N_Component_Declaration
1862 and then Present
(Expression
(Parent
(Comp
)))
1863 and then Nkind
(Expression
(Parent
(Comp
))) = N_Aggregate
1864 and then Is_Fully_Defined
1865 (Designated_Type
(Component_Type
(Etype
(Comp
))))
1869 (Component_Type
(Etype
(Comp
))), Loc
, Result
);
1876 -- Check for useless pragma Bit_Order
1878 if not Placed_Component
and then Reverse_Bit_Order
(Rec
) then
1879 ADC
:= Get_Attribute_Definition_Clause
(Rec
, Attribute_Bit_Order
);
1880 Error_Msg_N
("?Bit_Order specification has no effect", ADC
);
1881 Error_Msg_N
("\?since no component clauses were specified", ADC
);
1884 -- Check for useless pragma Pack when all components placed. We only
1885 -- do this check for record types, not subtypes, since a subtype may
1886 -- have all its components placed, and it still makes perfectly good
1887 -- sense to pack other subtypes or the parent type.
1889 if Ekind
(Rec
) = E_Record_Type
1890 and then Is_Packed
(Rec
)
1891 and then not Unplaced_Component
1893 -- Reset packed status. Probably not necessary, but we do it
1894 -- so that there is no chance of the back end doing something
1895 -- strange with this redundant indication of packing.
1897 Set_Is_Packed
(Rec
, False);
1899 -- Give warning if redundant constructs warnings on
1901 if Warn_On_Redundant_Constructs
then
1903 ("?pragma Pack has no effect, no unplaced components",
1904 Get_Rep_Pragma
(Rec
, Name_Pack
));
1908 -- If this is the record corresponding to a remote type, freeze the
1909 -- remote type here since that is what we are semantically freezing.
1910 -- This prevents the freeze node for that type in an inner scope.
1912 -- Also, Check for controlled components and unchecked unions.
1913 -- Finally, enforce the restriction that access attributes with a
1914 -- current instance prefix can only apply to limited types.
1916 if Ekind
(Rec
) = E_Record_Type
then
1917 if Present
(Corresponding_Remote_Type
(Rec
)) then
1919 (Corresponding_Remote_Type
(Rec
), Loc
, Result
);
1922 Comp
:= First_Component
(Rec
);
1923 while Present
(Comp
) loop
1924 if Has_Controlled_Component
(Etype
(Comp
))
1925 or else (Chars
(Comp
) /= Name_uParent
1926 and then Is_Controlled
(Etype
(Comp
)))
1927 or else (Is_Protected_Type
(Etype
(Comp
))
1929 (Corresponding_Record_Type
(Etype
(Comp
)))
1930 and then Has_Controlled_Component
1931 (Corresponding_Record_Type
(Etype
(Comp
))))
1933 Set_Has_Controlled_Component
(Rec
);
1937 if Has_Unchecked_Union
(Etype
(Comp
)) then
1938 Set_Has_Unchecked_Union
(Rec
);
1941 if Has_Per_Object_Constraint
(Comp
)
1942 and then not Is_Limited_Type
(Rec
)
1944 -- Scan component declaration for likely misuses of current
1945 -- instance, either in a constraint or a default expression.
1947 Check_Current_Instance
(Parent
(Comp
));
1950 Next_Component
(Comp
);
1954 Set_Component_Alignment_If_Not_Set
(Rec
);
1956 -- For first subtypes, check if there are any fixed-point fields with
1957 -- component clauses, where we must check the size. This is not done
1958 -- till the freeze point, since for fixed-point types, we do not know
1959 -- the size until the type is frozen. Similar processing applies to
1960 -- bit packed arrays.
1962 if Is_First_Subtype
(Rec
) then
1963 Comp
:= First_Component
(Rec
);
1965 while Present
(Comp
) loop
1966 if Present
(Component_Clause
(Comp
))
1967 and then (Is_Fixed_Point_Type
(Etype
(Comp
))
1969 Is_Bit_Packed_Array
(Etype
(Comp
)))
1972 (Component_Name
(Component_Clause
(Comp
)),
1978 Next_Component
(Comp
);
1981 end Freeze_Record_Type
;
1983 -- Start of processing for Freeze_Entity
1986 -- We are going to test for various reasons why this entity need not be
1987 -- frozen here, but in the case of an Itype that's defined within a
1988 -- record, that test actually applies to the record.
1990 if Is_Itype
(E
) and then Is_Record_Type
(Scope
(E
)) then
1991 Test_E
:= Scope
(E
);
1992 elsif Is_Itype
(E
) and then Present
(Underlying_Type
(Scope
(E
)))
1993 and then Is_Record_Type
(Underlying_Type
(Scope
(E
)))
1995 Test_E
:= Underlying_Type
(Scope
(E
));
1998 -- Do not freeze if already frozen since we only need one freeze node
2000 if Is_Frozen
(E
) then
2003 -- It is improper to freeze an external entity within a generic because
2004 -- its freeze node will appear in a non-valid context. The entity will
2005 -- be frozen in the proper scope after the current generic is analyzed.
2007 elsif Inside_A_Generic
and then External_Ref_In_Generic
(Test_E
) then
2010 -- Do not freeze a global entity within an inner scope created during
2011 -- expansion. A call to subprogram E within some internal procedure
2012 -- (a stream attribute for example) might require freezing E, but the
2013 -- freeze node must appear in the same declarative part as E itself.
2014 -- The two-pass elaboration mechanism in gigi guarantees that E will
2015 -- be frozen before the inner call is elaborated. We exclude constants
2016 -- from this test, because deferred constants may be frozen early, and
2017 -- must be diagnosed (see e.g. 1522-005). If the enclosing subprogram
2018 -- comes from source, or is a generic instance, then the freeze point
2019 -- is the one mandated by the language. and we freze the entity.
2021 elsif In_Open_Scopes
(Scope
(Test_E
))
2022 and then Scope
(Test_E
) /= Current_Scope
2023 and then Ekind
(Test_E
) /= E_Constant
2026 S
: Entity_Id
:= Current_Scope
;
2029 while Present
(S
) loop
2030 if Is_Overloadable
(S
) then
2031 if Comes_From_Source
(S
)
2032 or else Is_Generic_Instance
(S
)
2044 -- Similarly, an inlined instance body may make reference to global
2045 -- entities, but these references cannot be the proper freezing point
2046 -- for them, and the the absence of inlining freezing will take place
2047 -- in their own scope. Normally instance bodies are analyzed after
2048 -- the enclosing compilation, and everything has been frozen at the
2049 -- proper place, but with front-end inlining an instance body is
2050 -- compiled before the end of the enclosing scope, and as a result
2051 -- out-of-order freezing must be prevented.
2053 elsif Front_End_Inlining
2054 and then In_Instance_Body
2055 and then Present
(Scope
(Test_E
))
2058 S
: Entity_Id
:= Scope
(Test_E
);
2061 while Present
(S
) loop
2062 if Is_Generic_Instance
(S
) then
2075 -- Here to freeze the entity
2080 -- Case of entity being frozen is other than a type
2082 if not Is_Type
(E
) then
2084 -- If entity is exported or imported and does not have an external
2085 -- name, now is the time to provide the appropriate default name.
2086 -- Skip this if the entity is stubbed, since we don't need a name
2087 -- for any stubbed routine.
2089 if (Is_Imported
(E
) or else Is_Exported
(E
))
2090 and then No
(Interface_Name
(E
))
2091 and then Convention
(E
) /= Convention_Stubbed
2093 Set_Encoded_Interface_Name
2094 (E
, Get_Default_External_Name
(E
));
2096 -- Special processing for atomic objects appearing in object decls
2099 and then Nkind
(Parent
(E
)) = N_Object_Declaration
2100 and then Present
(Expression
(Parent
(E
)))
2103 Expr
: constant Node_Id
:= Expression
(Parent
(E
));
2106 -- If expression is an aggregate, assign to a temporary to
2107 -- ensure that the actual assignment is done atomically rather
2108 -- than component-wise (the assignment to the temp may be done
2109 -- component-wise, but that is harmless.
2111 if Nkind
(Expr
) = N_Aggregate
then
2112 Expand_Atomic_Aggregate
(Expr
, Etype
(E
));
2114 -- If the expression is a reference to a record or array object
2115 -- entity, then reset Is_True_Constant to False so that the
2116 -- compiler will not optimize away the intermediate object,
2117 -- which we need in this case for the same reason (to ensure
2118 -- that the actual assignment is atomic, rather than
2121 elsif Is_Entity_Name
(Expr
)
2122 and then (Is_Record_Type
(Etype
(Expr
))
2124 Is_Array_Type
(Etype
(Expr
)))
2126 Set_Is_True_Constant
(Entity
(Expr
), False);
2131 -- For a subprogram, freeze all parameter types and also the return
2132 -- type (RM 13.14(14)). However skip this for internal subprograms.
2133 -- This is also the point where any extra formal parameters are
2134 -- created since we now know whether the subprogram will use
2135 -- a foreign convention.
2137 if Is_Subprogram
(E
) then
2138 if not Is_Internal
(E
) then
2141 Warn_Node
: Node_Id
;
2143 function Is_Fat_C_Ptr_Type
(T
: Entity_Id
) return Boolean;
2144 -- Determines if given type entity is a fat pointer type
2145 -- used as an argument type or return type to a subprogram
2146 -- with C or C++ convention set.
2148 --------------------------
2149 -- Is_Fat_C_Access_Type --
2150 --------------------------
2152 function Is_Fat_C_Ptr_Type
(T
: Entity_Id
) return Boolean is
2154 return (Convention
(E
) = Convention_C
2156 Convention
(E
) = Convention_CPP
)
2157 and then Is_Access_Type
(T
)
2158 and then Esize
(T
) > Ttypes
.System_Address_Size
;
2159 end Is_Fat_C_Ptr_Type
;
2162 -- Loop through formals
2164 Formal
:= First_Formal
(E
);
2165 while Present
(Formal
) loop
2166 F_Type
:= Etype
(Formal
);
2167 Freeze_And_Append
(F_Type
, Loc
, Result
);
2169 if Is_Private_Type
(F_Type
)
2170 and then Is_Private_Type
(Base_Type
(F_Type
))
2171 and then No
(Full_View
(Base_Type
(F_Type
)))
2172 and then not Is_Generic_Type
(F_Type
)
2173 and then not Is_Derived_Type
(F_Type
)
2175 -- If the type of a formal is incomplete, subprogram
2176 -- is being frozen prematurely. Within an instance
2177 -- (but not within a wrapper package) this is an
2178 -- an artifact of our need to regard the end of an
2179 -- instantiation as a freeze point. Otherwise it is
2180 -- a definite error.
2182 -- and then not Is_Wrapper_Package (Current_Scope) ???
2185 Set_Is_Frozen
(E
, False);
2188 elsif not After_Last_Declaration
then
2189 Error_Msg_Node_1
:= F_Type
;
2191 ("type& must be fully defined before this point",
2196 -- Check bad use of fat C pointer
2198 if Warn_On_Export_Import
and then
2199 Is_Fat_C_Ptr_Type
(F_Type
)
2201 Error_Msg_Qual_Level
:= 1;
2203 ("?type of & does not correspond to C pointer",
2205 Error_Msg_Qual_Level
:= 0;
2208 -- Check for unconstrained array in exported foreign
2211 if Convention
(E
) in Foreign_Convention
2212 and then not Is_Imported
(E
)
2213 and then Is_Array_Type
(F_Type
)
2214 and then not Is_Constrained
(F_Type
)
2215 and then Warn_On_Export_Import
2217 Error_Msg_Qual_Level
:= 1;
2219 -- If this is an inherited operation, place the
2220 -- warning on the derived type declaration, rather
2221 -- than on the original subprogram.
2223 if Nkind
(Original_Node
(Parent
(E
))) =
2224 N_Full_Type_Declaration
2226 Warn_Node
:= Parent
(E
);
2228 if Formal
= First_Formal
(E
) then
2230 ("?in inherited operation&!", Warn_Node
, E
);
2233 Warn_Node
:= Formal
;
2237 ("?type of argument& is unconstrained array",
2240 ("?foreign caller must pass bounds explicitly",
2242 Error_Msg_Qual_Level
:= 0;
2245 -- Ada 2005 (AI-326): Check wrong use of tag incomplete
2246 -- types with unknown discriminants. For example:
2248 -- type T (<>) is tagged;
2249 -- procedure P (X : access T); -- ERROR
2250 -- procedure P (X : T); -- ERROR
2252 if not From_With_Type
(F_Type
) then
2253 if Is_Access_Type
(F_Type
) then
2254 F_Type
:= Designated_Type
(F_Type
);
2257 if Ekind
(F_Type
) = E_Incomplete_Type
2258 and then Is_Tagged_Type
(F_Type
)
2259 and then not Is_Class_Wide_Type
(F_Type
)
2260 and then No
(Full_View
(F_Type
))
2261 and then Unknown_Discriminants_Present
2263 and then No
(Stored_Constraint
(F_Type
))
2266 ("(Ada 2005): invalid use of unconstrained tagged"
2267 & " incomplete type", E
);
2269 elsif Ekind
(F_Type
) = E_Subprogram_Type
then
2270 Freeze_And_Append
(F_Type
, Loc
, Result
);
2274 Next_Formal
(Formal
);
2277 -- Check return type
2279 if Ekind
(E
) = E_Function
then
2280 Freeze_And_Append
(Etype
(E
), Loc
, Result
);
2282 if Warn_On_Export_Import
2283 and then Is_Fat_C_Ptr_Type
(Etype
(E
))
2286 ("?return type of& does not correspond to C pointer",
2289 elsif Is_Array_Type
(Etype
(E
))
2290 and then not Is_Constrained
(Etype
(E
))
2291 and then not Is_Imported
(E
)
2292 and then Convention
(E
) in Foreign_Convention
2293 and then Warn_On_Export_Import
2296 ("?foreign convention function& should not " &
2297 "return unconstrained array", E
);
2299 -- Ada 2005 (AI-326): Check wrong use of tagged
2302 -- type T is tagged;
2303 -- function F (X : Boolean) return T; -- ERROR
2305 elsif Ekind
(Etype
(E
)) = E_Incomplete_Type
2306 and then Is_Tagged_Type
(Etype
(E
))
2307 and then No
(Full_View
(Etype
(E
)))
2310 ("(Ada 2005): invalid use of tagged incomplete type",
2317 -- Must freeze its parent first if it is a derived subprogram
2319 if Present
(Alias
(E
)) then
2320 Freeze_And_Append
(Alias
(E
), Loc
, Result
);
2323 -- If the return type requires a transient scope, and we are on
2324 -- a target allowing functions to return with a depressed stack
2325 -- pointer, then we mark the function as requiring this treatment.
2327 if Ekind
(E
) = E_Function
2328 and then Functions_Return_By_DSP_On_Target
2329 and then Requires_Transient_Scope
(Etype
(E
))
2331 Set_Function_Returns_With_DSP
(E
);
2334 if not Is_Internal
(E
) then
2335 Freeze_Subprogram
(E
);
2338 -- Here for other than a subprogram or type
2341 -- If entity has a type, and it is not a generic unit, then
2342 -- freeze it first (RM 13.14(10))
2344 if Present
(Etype
(E
))
2345 and then Ekind
(E
) /= E_Generic_Function
2347 Freeze_And_Append
(Etype
(E
), Loc
, Result
);
2350 -- Special processing for objects created by object declaration
2352 if Nkind
(Declaration_Node
(E
)) = N_Object_Declaration
then
2354 -- For object created by object declaration, perform required
2355 -- categorization (preelaborate and pure) checks. Defer these
2356 -- checks to freeze time since pragma Import inhibits default
2357 -- initialization and thus pragma Import affects these checks.
2359 Validate_Object_Declaration
(Declaration_Node
(E
));
2361 -- If there is an address clause, check it is valid
2363 Check_Address_Clause
(E
);
2365 -- For imported objects, set Is_Public unless there is also
2366 -- an address clause, which means that there is no external
2367 -- symbol needed for the Import (Is_Public may still be set
2368 -- for other unrelated reasons). Note that we delayed this
2369 -- processing till freeze time so that we can be sure not
2370 -- to set the flag if there is an address clause. If there
2371 -- is such a clause, then the only purpose of the import
2372 -- pragma is to suppress implicit initialization.
2375 and then not Present
(Address_Clause
(E
))
2381 -- Check that a constant which has a pragma Volatile[_Components]
2382 -- or Atomic[_Components] also has a pragma Import (RM C.6(13))
2384 -- Note: Atomic[_Components] also sets Volatile[_Components]
2386 if Ekind
(E
) = E_Constant
2387 and then (Has_Volatile_Components
(E
) or else Is_Volatile
(E
))
2388 and then not Is_Imported
(E
)
2390 -- Make sure we actually have a pragma, and have not merely
2391 -- inherited the indication from elsewhere (e.g. an address
2392 -- clause, which is not good enough in RM terms!)
2394 if Has_Rep_Pragma
(E
, Name_Atomic
)
2396 Has_Rep_Pragma
(E
, Name_Atomic_Components
)
2399 ("stand alone atomic constant must be " &
2400 "imported ('R'M 'C.6(13))", E
);
2402 elsif Has_Rep_Pragma
(E
, Name_Volatile
)
2404 Has_Rep_Pragma
(E
, Name_Volatile_Components
)
2407 ("stand alone volatile constant must be " &
2408 "imported ('R'M 'C.6(13))", E
);
2412 -- Static objects require special handling
2414 if (Ekind
(E
) = E_Constant
or else Ekind
(E
) = E_Variable
)
2415 and then Is_Statically_Allocated
(E
)
2417 Freeze_Static_Object
(E
);
2420 -- Remaining step is to layout objects
2422 if Ekind
(E
) = E_Variable
2424 Ekind
(E
) = E_Constant
2426 Ekind
(E
) = E_Loop_Parameter
2434 -- Case of a type or subtype being frozen
2437 -- The type may be defined in a generic unit. This can occur when
2438 -- freezing a generic function that returns the type (which is
2439 -- defined in a parent unit). It is clearly meaningless to freeze
2440 -- this type. However, if it is a subtype, its size may be determi-
2441 -- nable and used in subsequent checks, so might as well try to
2444 if Present
(Scope
(E
))
2445 and then Is_Generic_Unit
(Scope
(E
))
2447 Check_Compile_Time_Size
(E
);
2451 -- Deal with special cases of freezing for subtype
2453 if E
/= Base_Type
(E
) then
2455 -- If ancestor subtype present, freeze that first.
2456 -- Note that this will also get the base type frozen.
2458 Atype
:= Ancestor_Subtype
(E
);
2460 if Present
(Atype
) then
2461 Freeze_And_Append
(Atype
, Loc
, Result
);
2463 -- Otherwise freeze the base type of the entity before
2464 -- freezing the entity itself, (RM 13.14(15)).
2466 elsif E
/= Base_Type
(E
) then
2467 Freeze_And_Append
(Base_Type
(E
), Loc
, Result
);
2470 -- For a derived type, freeze its parent type first (RM 13.14(15))
2472 elsif Is_Derived_Type
(E
) then
2473 Freeze_And_Append
(Etype
(E
), Loc
, Result
);
2474 Freeze_And_Append
(First_Subtype
(Etype
(E
)), Loc
, Result
);
2477 -- For array type, freeze index types and component type first
2478 -- before freezing the array (RM 13.14(15)).
2480 if Is_Array_Type
(E
) then
2482 Ctyp
: constant Entity_Id
:= Component_Type
(E
);
2485 Non_Standard_Enum
: Boolean := False;
2486 -- Set true if any of the index types is an enumeration
2487 -- type with a non-standard representation.
2490 Freeze_And_Append
(Ctyp
, Loc
, Result
);
2492 Indx
:= First_Index
(E
);
2493 while Present
(Indx
) loop
2494 Freeze_And_Append
(Etype
(Indx
), Loc
, Result
);
2496 if Is_Enumeration_Type
(Etype
(Indx
))
2497 and then Has_Non_Standard_Rep
(Etype
(Indx
))
2499 Non_Standard_Enum
:= True;
2505 -- Processing that is done only for base types
2507 if Ekind
(E
) = E_Array_Type
then
2509 -- Propagate flags for component type
2511 if Is_Controlled
(Component_Type
(E
))
2512 or else Has_Controlled_Component
(Ctyp
)
2514 Set_Has_Controlled_Component
(E
);
2517 if Has_Unchecked_Union
(Component_Type
(E
)) then
2518 Set_Has_Unchecked_Union
(E
);
2521 -- If packing was requested or if the component size was set
2522 -- explicitly, then see if bit packing is required. This
2523 -- processing is only done for base types, since all the
2524 -- representation aspects involved are type-related. This
2525 -- is not just an optimization, if we start processing the
2526 -- subtypes, they intefere with the settings on the base
2527 -- type (this is because Is_Packed has a slightly different
2528 -- meaning before and after freezing).
2535 if (Is_Packed
(E
) or else Has_Pragma_Pack
(E
))
2536 and then not Has_Atomic_Components
(E
)
2537 and then Known_Static_RM_Size
(Ctyp
)
2539 Csiz
:= UI_Max
(RM_Size
(Ctyp
), 1);
2541 elsif Known_Component_Size
(E
) then
2542 Csiz
:= Component_Size
(E
);
2544 elsif not Known_Static_Esize
(Ctyp
) then
2548 Esiz
:= Esize
(Ctyp
);
2550 -- We can set the component size if it is less than
2551 -- 16, rounding it up to the next storage unit size.
2555 elsif Esiz
<= 16 then
2561 -- Set component size up to match alignment if
2562 -- it would otherwise be less than the alignment.
2563 -- This deals with cases of types whose alignment
2564 -- exceeds their sizes (padded types).
2568 A
: constant Uint
:= Alignment_In_Bits
(Ctyp
);
2579 if 1 <= Csiz
and then Csiz
<= 64 then
2581 -- We set the component size for all cases 1-64
2583 Set_Component_Size
(Base_Type
(E
), Csiz
);
2585 -- Check for base type of 8,16,32 bits, where the
2586 -- subtype has a length one less than the base type
2587 -- and is unsigned (e.g. Natural subtype of Integer)
2589 -- In such cases, if a component size was not set
2590 -- explicitly, then generate a warning.
2592 if Has_Pragma_Pack
(E
)
2593 and then not Has_Component_Size_Clause
(E
)
2595 (Csiz
= 7 or else Csiz
= 15 or else Csiz
= 31)
2596 and then Esize
(Base_Type
(Ctyp
)) = Csiz
+ 1
2598 Error_Msg_Uint_1
:= Csiz
;
2600 Get_Rep_Pragma
(First_Subtype
(E
), Name_Pack
);
2602 if Present
(Pnod
) then
2604 ("pragma Pack causes component size to be ^?",
2607 ("\use Component_Size to set desired value",
2612 -- Actual packing is not needed for 8,16,32,64
2613 -- Also not needed for 24 if alignment is 1
2619 or else (Csiz
= 24 and then Alignment
(Ctyp
) = 1)
2621 -- Here the array was requested to be packed, but
2622 -- the packing request had no effect, so Is_Packed
2625 -- Note: semantically this means that we lose
2626 -- track of the fact that a derived type inherited
2627 -- a pack pragma that was non-effective, but that
2630 -- We regard a Pack pragma as a request to set a
2631 -- representation characteristic, and this request
2634 Set_Is_Packed
(Base_Type
(E
), False);
2636 -- In all other cases, packing is indeed needed
2639 Set_Has_Non_Standard_Rep
(Base_Type
(E
));
2640 Set_Is_Bit_Packed_Array
(Base_Type
(E
));
2641 Set_Is_Packed
(Base_Type
(E
));
2646 -- Processing that is done only for subtypes
2649 -- Acquire alignment from base type
2651 if Unknown_Alignment
(E
) then
2652 Set_Alignment
(E
, Alignment
(Base_Type
(E
)));
2656 -- For bit-packed arrays, check the size
2658 if Is_Bit_Packed_Array
(E
)
2659 and then Known_Esize
(E
)
2663 SizC
: constant Node_Id
:= Size_Clause
(E
);
2666 -- It is not clear if it is possible to have no size
2667 -- clause at this stage, but this is not worth worrying
2668 -- about. Post the error on the entity name in the size
2669 -- clause if present, else on the type entity itself.
2671 if Present
(SizC
) then
2672 Check_Size
(Name
(SizC
), E
, Esize
(E
), Discard
);
2674 Check_Size
(E
, E
, Esize
(E
), Discard
);
2679 -- Check one common case of a size given where the array
2680 -- needs to be packed, but was not so the size cannot be
2681 -- honored. This would of course be caught by the backend,
2682 -- and indeed we don't catch all cases. The point is that
2683 -- we can give a better error message in those cases that
2684 -- we do catch with the circuitry here.
2688 Ctyp
: constant Entity_Id
:= Component_Type
(E
);
2691 if Present
(Size_Clause
(E
))
2692 and then Known_Static_Esize
(E
)
2693 and then not Is_Bit_Packed_Array
(E
)
2694 and then not Has_Pragma_Pack
(E
)
2695 and then Number_Dimensions
(E
) = 1
2696 and then not Has_Component_Size_Clause
(E
)
2697 and then Known_Static_Esize
(Ctyp
)
2699 Get_Index_Bounds
(First_Index
(E
), Lo
, Hi
);
2701 if Compile_Time_Known_Value
(Lo
)
2702 and then Compile_Time_Known_Value
(Hi
)
2703 and then Known_Static_RM_Size
(Ctyp
)
2704 and then RM_Size
(Ctyp
) < 64
2707 Lov
: constant Uint
:= Expr_Value
(Lo
);
2708 Hiv
: constant Uint
:= Expr_Value
(Hi
);
2709 Len
: constant Uint
:=
2710 UI_Max
(Uint_0
, Hiv
- Lov
+ 1);
2711 Rsiz
: constant Uint
:= RM_Size
(Ctyp
);
2713 -- What we are looking for here is the situation
2714 -- where the Esize given would be exactly right
2715 -- if there was a pragma Pack (resulting in the
2716 -- component size being the same as the RM_Size).
2717 -- Furthermore, the component type size must be
2718 -- an odd size (not a multiple of storage unit)
2721 if Esize
(E
) = Len
* Rsiz
2722 and then Rsiz
mod System_Storage_Unit
/= 0
2725 ("size given for& too small",
2726 Size_Clause
(E
), E
);
2728 ("\explicit pragma Pack is required",
2736 -- If any of the index types was an enumeration type with
2737 -- a non-standard rep clause, then we indicate that the
2738 -- array type is always packed (even if it is not bit packed).
2740 if Non_Standard_Enum
then
2741 Set_Has_Non_Standard_Rep
(Base_Type
(E
));
2742 Set_Is_Packed
(Base_Type
(E
));
2745 Set_Component_Alignment_If_Not_Set
(E
);
2747 -- If the array is packed, we must create the packed array
2748 -- type to be used to actually implement the type. This is
2749 -- only needed for real array types (not for string literal
2750 -- types, since they are present only for the front end).
2753 and then Ekind
(E
) /= E_String_Literal_Subtype
2755 Create_Packed_Array_Type
(E
);
2756 Freeze_And_Append
(Packed_Array_Type
(E
), Loc
, Result
);
2758 -- Size information of packed array type is copied to the
2759 -- array type, since this is really the representation.
2761 Set_Size_Info
(E
, Packed_Array_Type
(E
));
2762 Set_RM_Size
(E
, RM_Size
(Packed_Array_Type
(E
)));
2765 -- For non-packed arrays set the alignment of the array
2766 -- to the alignment of the component type if it is unknown.
2767 -- Skip this in the atomic case, since atomic arrays may
2768 -- need larger alignments.
2770 if not Is_Packed
(E
)
2771 and then Unknown_Alignment
(E
)
2772 and then Known_Alignment
(Ctyp
)
2773 and then Known_Static_Component_Size
(E
)
2774 and then Known_Static_Esize
(Ctyp
)
2775 and then Esize
(Ctyp
) = Component_Size
(E
)
2776 and then not Is_Atomic
(E
)
2778 Set_Alignment
(E
, Alignment
(Component_Type
(E
)));
2782 -- For a class-wide type, the corresponding specific type is
2783 -- frozen as well (RM 13.14(15))
2785 elsif Is_Class_Wide_Type
(E
) then
2786 Freeze_And_Append
(Root_Type
(E
), Loc
, Result
);
2788 -- If the Class_Wide_Type is an Itype (when type is the anonymous
2789 -- parent of a derived type) and it is a library-level entity,
2790 -- generate an itype reference for it. Otherwise, its first
2791 -- explicit reference may be in an inner scope, which will be
2792 -- rejected by the back-end.
2795 and then Is_Compilation_Unit
(Scope
(E
))
2798 Ref
: constant Node_Id
:= Make_Itype_Reference
(Loc
);
2803 Result
:= New_List
(Ref
);
2805 Append
(Ref
, Result
);
2810 -- The equivalent type associated with a class-wide subtype
2811 -- needs to be frozen to ensure that its layout is done.
2812 -- Class-wide subtypes are currently only frozen on targets
2813 -- requiring front-end layout (see New_Class_Wide_Subtype
2814 -- and Make_CW_Equivalent_Type in exp_util.adb).
2816 if Ekind
(E
) = E_Class_Wide_Subtype
2817 and then Present
(Equivalent_Type
(E
))
2819 Freeze_And_Append
(Equivalent_Type
(E
), Loc
, Result
);
2822 -- For a record (sub)type, freeze all the component types (RM
2823 -- 13.14(15). We test for E_Record_(sub)Type here, rather than
2824 -- using Is_Record_Type, because we don't want to attempt the
2825 -- freeze for the case of a private type with record extension
2826 -- (we will do that later when the full type is frozen).
2828 elsif Ekind
(E
) = E_Record_Type
2829 or else Ekind
(E
) = E_Record_Subtype
2831 Freeze_Record_Type
(E
);
2833 -- For a concurrent type, freeze corresponding record type. This
2834 -- does not correpond to any specific rule in the RM, but the
2835 -- record type is essentially part of the concurrent type.
2836 -- Freeze as well all local entities. This includes record types
2837 -- created for entry parameter blocks, and whatever local entities
2838 -- may appear in the private part.
2840 elsif Is_Concurrent_Type
(E
) then
2841 if Present
(Corresponding_Record_Type
(E
)) then
2843 (Corresponding_Record_Type
(E
), Loc
, Result
);
2846 Comp
:= First_Entity
(E
);
2848 while Present
(Comp
) loop
2849 if Is_Type
(Comp
) then
2850 Freeze_And_Append
(Comp
, Loc
, Result
);
2852 elsif (Ekind
(Comp
)) /= E_Function
then
2853 if Is_Itype
(Etype
(Comp
))
2854 and then Underlying_Type
(Scope
(Etype
(Comp
))) = E
2856 Undelay_Type
(Etype
(Comp
));
2859 Freeze_And_Append
(Etype
(Comp
), Loc
, Result
);
2865 -- Private types are required to point to the same freeze node as
2866 -- their corresponding full views. The freeze node itself has to
2867 -- point to the partial view of the entity (because from the partial
2868 -- view, we can retrieve the full view, but not the reverse).
2869 -- However, in order to freeze correctly, we need to freeze the full
2870 -- view. If we are freezing at the end of a scope (or within the
2871 -- scope of the private type), the partial and full views will have
2872 -- been swapped, the full view appears first in the entity chain and
2873 -- the swapping mechanism ensures that the pointers are properly set
2876 -- If we encounter the partial view before the full view (e.g. when
2877 -- freezing from another scope), we freeze the full view, and then
2878 -- set the pointers appropriately since we cannot rely on swapping to
2879 -- fix things up (subtypes in an outer scope might not get swapped).
2881 elsif Is_Incomplete_Or_Private_Type
(E
)
2882 and then not Is_Generic_Type
(E
)
2884 -- Case of full view present
2886 if Present
(Full_View
(E
)) then
2888 -- If full view has already been frozen, then no further
2889 -- processing is required
2891 if Is_Frozen
(Full_View
(E
)) then
2893 Set_Has_Delayed_Freeze
(E
, False);
2894 Set_Freeze_Node
(E
, Empty
);
2895 Check_Debug_Info_Needed
(E
);
2897 -- Otherwise freeze full view and patch the pointers so that
2898 -- the freeze node will elaborate both views in the back-end.
2902 Full
: constant Entity_Id
:= Full_View
(E
);
2905 if Is_Private_Type
(Full
)
2906 and then Present
(Underlying_Full_View
(Full
))
2909 (Underlying_Full_View
(Full
), Loc
, Result
);
2912 Freeze_And_Append
(Full
, Loc
, Result
);
2914 if Has_Delayed_Freeze
(E
) then
2915 F_Node
:= Freeze_Node
(Full
);
2917 if Present
(F_Node
) then
2918 Set_Freeze_Node
(E
, F_Node
);
2919 Set_Entity
(F_Node
, E
);
2922 -- {Incomplete,Private}_Subtypes
2923 -- with Full_Views constrained by discriminants
2925 Set_Has_Delayed_Freeze
(E
, False);
2926 Set_Freeze_Node
(E
, Empty
);
2931 Check_Debug_Info_Needed
(E
);
2934 -- AI-117 requires that the convention of a partial view be the
2935 -- same as the convention of the full view. Note that this is a
2936 -- recognized breach of privacy, but it's essential for logical
2937 -- consistency of representation, and the lack of a rule in
2938 -- RM95 was an oversight.
2940 Set_Convention
(E
, Convention
(Full_View
(E
)));
2942 Set_Size_Known_At_Compile_Time
(E
,
2943 Size_Known_At_Compile_Time
(Full_View
(E
)));
2945 -- Size information is copied from the full view to the
2946 -- incomplete or private view for consistency
2948 -- We skip this is the full view is not a type. This is very
2949 -- strange of course, and can only happen as a result of
2950 -- certain illegalities, such as a premature attempt to derive
2951 -- from an incomplete type.
2953 if Is_Type
(Full_View
(E
)) then
2954 Set_Size_Info
(E
, Full_View
(E
));
2955 Set_RM_Size
(E
, RM_Size
(Full_View
(E
)));
2960 -- Case of no full view present. If entity is derived or subtype,
2961 -- it is safe to freeze, correctness depends on the frozen status
2962 -- of parent. Otherwise it is either premature usage, or a Taft
2963 -- amendment type, so diagnosis is at the point of use and the
2964 -- type might be frozen later.
2966 elsif E
/= Base_Type
(E
)
2967 or else Is_Derived_Type
(E
)
2972 Set_Is_Frozen
(E
, False);
2976 -- For access subprogram, freeze types of all formals, the return
2977 -- type was already frozen, since it is the Etype of the function.
2979 elsif Ekind
(E
) = E_Subprogram_Type
then
2980 Formal
:= First_Formal
(E
);
2981 while Present
(Formal
) loop
2982 Freeze_And_Append
(Etype
(Formal
), Loc
, Result
);
2983 Next_Formal
(Formal
);
2986 -- If the return type requires a transient scope, and we are on
2987 -- a target allowing functions to return with a depressed stack
2988 -- pointer, then we mark the function as requiring this treatment.
2990 if Functions_Return_By_DSP_On_Target
2991 and then Requires_Transient_Scope
(Etype
(E
))
2993 Set_Function_Returns_With_DSP
(E
);
2996 Freeze_Subprogram
(E
);
2998 -- AI-326: Check wrong use of tag incomplete type
3000 -- type T is tagged;
3001 -- type Acc is access function (X : T) return T; -- ERROR
3003 if Ekind
(Etype
(E
)) = E_Incomplete_Type
3004 and then Is_Tagged_Type
(Etype
(E
))
3005 and then No
(Full_View
(Etype
(E
)))
3008 ("(Ada 2005): invalid use of tagged incomplete type", E
);
3011 -- For access to a protected subprogram, freeze the equivalent type
3012 -- (however this is not set if we are not generating code or if this
3013 -- is an anonymous type used just for resolution).
3015 elsif Ekind
(E
) = E_Access_Protected_Subprogram_Type
then
3017 -- AI-326: Check wrong use of tagged incomplete types
3019 -- type T is tagged;
3020 -- type As3D is access protected
3021 -- function (X : Float) return T; -- ERROR
3027 Etyp
:= Etype
(Directly_Designated_Type
(E
));
3029 if Is_Class_Wide_Type
(Etyp
) then
3030 Etyp
:= Etype
(Etyp
);
3033 if Ekind
(Etyp
) = E_Incomplete_Type
3034 and then Is_Tagged_Type
(Etyp
)
3035 and then No
(Full_View
(Etyp
))
3038 ("(Ada 2005): invalid use of tagged incomplete type", E
);
3042 if Present
(Equivalent_Type
(E
)) then
3043 Freeze_And_Append
(Equivalent_Type
(E
), Loc
, Result
);
3047 -- Generic types are never seen by the back-end, and are also not
3048 -- processed by the expander (since the expander is turned off for
3049 -- generic processing), so we never need freeze nodes for them.
3051 if Is_Generic_Type
(E
) then
3055 -- Some special processing for non-generic types to complete
3056 -- representation details not known till the freeze point.
3058 if Is_Fixed_Point_Type
(E
) then
3059 Freeze_Fixed_Point_Type
(E
);
3061 -- Some error checks required for ordinary fixed-point type. Defer
3062 -- these till the freeze-point since we need the small and range
3063 -- values. We only do these checks for base types
3065 if Is_Ordinary_Fixed_Point_Type
(E
)
3066 and then E
= Base_Type
(E
)
3068 if Small_Value
(E
) < Ureal_2_M_80
then
3069 Error_Msg_Name_1
:= Name_Small
;
3071 ("`&''%` is too small, minimum is 2.0'*'*(-80)", E
);
3073 elsif Small_Value
(E
) > Ureal_2_80
then
3074 Error_Msg_Name_1
:= Name_Small
;
3076 ("`&''%` is too large, maximum is 2.0'*'*80", E
);
3079 if Expr_Value_R
(Type_Low_Bound
(E
)) < Ureal_M_10_36
then
3080 Error_Msg_Name_1
:= Name_First
;
3082 ("`&''%` is too small, minimum is -10.0'*'*36", E
);
3085 if Expr_Value_R
(Type_High_Bound
(E
)) > Ureal_10_36
then
3086 Error_Msg_Name_1
:= Name_Last
;
3088 ("`&''%` is too large, maximum is 10.0'*'*36", E
);
3092 elsif Is_Enumeration_Type
(E
) then
3093 Freeze_Enumeration_Type
(E
);
3095 elsif Is_Integer_Type
(E
) then
3096 Adjust_Esize_For_Alignment
(E
);
3098 elsif Is_Access_Type
(E
) then
3100 -- Check restriction for standard storage pool
3102 if No
(Associated_Storage_Pool
(E
)) then
3103 Check_Restriction
(No_Standard_Storage_Pools
, E
);
3106 -- Deal with error message for pure access type. This is not an
3107 -- error in Ada 2005 if there is no pool (see AI-366).
3109 if Is_Pure_Unit_Access_Type
(E
)
3110 and then (Ada_Version
< Ada_05
3111 or else not No_Pool_Assigned
(E
))
3113 Error_Msg_N
("named access type not allowed in pure unit", E
);
3117 -- Case of composite types
3119 if Is_Composite_Type
(E
) then
3121 -- AI-117 requires that all new primitives of a tagged type must
3122 -- inherit the convention of the full view of the type. Inherited
3123 -- and overriding operations are defined to inherit the convention
3124 -- of their parent or overridden subprogram (also specified in
3125 -- AI-117), which will have occurred earlier (in Derive_Subprogram
3126 -- and New_Overloaded_Entity). Here we set the convention of
3127 -- primitives that are still convention Ada, which will ensure
3128 -- that any new primitives inherit the type's convention.
3129 -- Class-wide types can have a foreign convention inherited from
3130 -- their specific type, but are excluded from this since they
3131 -- don't have any associated primitives.
3133 if Is_Tagged_Type
(E
)
3134 and then not Is_Class_Wide_Type
(E
)
3135 and then Convention
(E
) /= Convention_Ada
3138 Prim_List
: constant Elist_Id
:= Primitive_Operations
(E
);
3141 Prim
:= First_Elmt
(Prim_List
);
3142 while Present
(Prim
) loop
3143 if Convention
(Node
(Prim
)) = Convention_Ada
then
3144 Set_Convention
(Node
(Prim
), Convention
(E
));
3153 -- Generate primitive operation references for a tagged type
3155 if Is_Tagged_Type
(E
)
3156 and then not Is_Class_Wide_Type
(E
)
3159 Prim_List
: Elist_Id
;
3164 -- Ada 2005 (AI-345): In case of concurrent type generate
3165 -- reference to the wrapper that allow us to dispatch calls
3166 -- through their implemented abstract interface types.
3168 -- The check for Present here is to protect against previously
3169 -- reported critical errors.
3171 if Is_Concurrent_Type
(E
)
3172 and then Present
(Corresponding_Record_Type
(E
))
3174 pragma Assert
(not Is_Empty_Elmt_List
3175 (Abstract_Interfaces
3176 (Corresponding_Record_Type
(E
))));
3178 Prim_List
:= Primitive_Operations
3179 (Corresponding_Record_Type
(E
));
3181 Prim_List
:= Primitive_Operations
(E
);
3184 -- Loop to generate references for primitive operations
3186 if Present
(Prim_List
) then
3187 Prim
:= First_Elmt
(Prim_List
);
3188 while Present
(Prim
) loop
3190 -- If the operation is derived, get the original for
3191 -- cross-reference purposes (it is the original for
3192 -- which we want the xref, and for which the comes
3193 -- from source test needs to be performed).
3196 while Present
(Alias
(Ent
)) loop
3200 Generate_Reference
(E
, Ent
, 'p', Set_Ref
=> False);
3207 -- Now that all types from which E may depend are frozen, see if the
3208 -- size is known at compile time, if it must be unsigned, or if
3209 -- strict alignent is required
3211 Check_Compile_Time_Size
(E
);
3212 Check_Unsigned_Type
(E
);
3214 if Base_Type
(E
) = E
then
3215 Check_Strict_Alignment
(E
);
3218 -- Do not allow a size clause for a type which does not have a size
3219 -- that is known at compile time
3221 if Has_Size_Clause
(E
)
3222 and then not Size_Known_At_Compile_Time
(E
)
3224 -- Supress this message if errors posted on E, even if we are
3225 -- in all errors mode, since this is often a junk message
3227 if not Error_Posted
(E
) then
3229 ("size clause not allowed for variable length type",
3234 -- Remaining process is to set/verify the representation information,
3235 -- in particular the size and alignment values. This processing is
3236 -- not required for generic types, since generic types do not play
3237 -- any part in code generation, and so the size and alignment values
3238 -- for such types are irrelevant.
3240 if Is_Generic_Type
(E
) then
3243 -- Otherwise we call the layout procedure
3249 -- End of freeze processing for type entities
3252 -- Here is where we logically freeze the current entity. If it has a
3253 -- freeze node, then this is the point at which the freeze node is
3254 -- linked into the result list.
3256 if Has_Delayed_Freeze
(E
) then
3258 -- If a freeze node is already allocated, use it, otherwise allocate
3259 -- a new one. The preallocation happens in the case of anonymous base
3260 -- types, where we preallocate so that we can set First_Subtype_Link.
3261 -- Note that we reset the Sloc to the current freeze location.
3263 if Present
(Freeze_Node
(E
)) then
3264 F_Node
:= Freeze_Node
(E
);
3265 Set_Sloc
(F_Node
, Loc
);
3268 F_Node
:= New_Node
(N_Freeze_Entity
, Loc
);
3269 Set_Freeze_Node
(E
, F_Node
);
3270 Set_Access_Types_To_Process
(F_Node
, No_Elist
);
3271 Set_TSS_Elist
(F_Node
, No_Elist
);
3272 Set_Actions
(F_Node
, No_List
);
3275 Set_Entity
(F_Node
, E
);
3277 if Result
= No_List
then
3278 Result
:= New_List
(F_Node
);
3280 Append
(F_Node
, Result
);
3283 -- A final pass over record types with discriminants. If the type
3284 -- has an incomplete declaration, there may be constrained access
3285 -- subtypes declared elsewhere, which do not depend on the discrimi-
3286 -- nants of the type, and which are used as component types (i.e.
3287 -- the full view is a recursive type). The designated types of these
3288 -- subtypes can only be elaborated after the type itself, and they
3289 -- need an itype reference.
3291 if Ekind
(E
) = E_Record_Type
3292 and then Has_Discriminants
(E
)
3300 Comp
:= First_Component
(E
);
3302 while Present
(Comp
) loop
3303 Typ
:= Etype
(Comp
);
3305 if Ekind
(Comp
) = E_Component
3306 and then Is_Access_Type
(Typ
)
3307 and then Scope
(Typ
) /= E
3308 and then Base_Type
(Designated_Type
(Typ
)) = E
3309 and then Is_Itype
(Designated_Type
(Typ
))
3311 IR
:= Make_Itype_Reference
(Sloc
(Comp
));
3312 Set_Itype
(IR
, Designated_Type
(Typ
));
3313 Append
(IR
, Result
);
3316 Next_Component
(Comp
);
3322 -- When a type is frozen, the first subtype of the type is frozen as
3323 -- well (RM 13.14(15)). This has to be done after freezing the type,
3324 -- since obviously the first subtype depends on its own base type.
3327 Freeze_And_Append
(First_Subtype
(E
), Loc
, Result
);
3329 -- If we just froze a tagged non-class wide record, then freeze the
3330 -- corresponding class-wide type. This must be done after the tagged
3331 -- type itself is frozen, because the class-wide type refers to the
3332 -- tagged type which generates the class.
3334 if Is_Tagged_Type
(E
)
3335 and then not Is_Class_Wide_Type
(E
)
3336 and then Present
(Class_Wide_Type
(E
))
3338 Freeze_And_Append
(Class_Wide_Type
(E
), Loc
, Result
);
3342 Check_Debug_Info_Needed
(E
);
3344 -- Special handling for subprograms
3346 if Is_Subprogram
(E
) then
3348 -- If subprogram has address clause then reset Is_Public flag, since
3349 -- we do not want the backend to generate external references.
3351 if Present
(Address_Clause
(E
))
3352 and then not Is_Library_Level_Entity
(E
)
3354 Set_Is_Public
(E
, False);
3356 -- If no address clause and not intrinsic, then for imported
3357 -- subprogram in main unit, generate descriptor if we are in
3358 -- Propagate_Exceptions mode.
3360 elsif Propagate_Exceptions
3361 and then Is_Imported
(E
)
3362 and then not Is_Intrinsic_Subprogram
(E
)
3363 and then Convention
(E
) /= Convention_Stubbed
3365 if Result
= No_List
then
3366 Result
:= Empty_List
;
3374 -----------------------------
3375 -- Freeze_Enumeration_Type --
3376 -----------------------------
3378 procedure Freeze_Enumeration_Type
(Typ
: Entity_Id
) is
3380 if Has_Foreign_Convention
(Typ
)
3381 and then not Has_Size_Clause
(Typ
)
3382 and then Esize
(Typ
) < Standard_Integer_Size
3384 Init_Esize
(Typ
, Standard_Integer_Size
);
3386 Adjust_Esize_For_Alignment
(Typ
);
3388 end Freeze_Enumeration_Type
;
3390 -----------------------
3391 -- Freeze_Expression --
3392 -----------------------
3394 procedure Freeze_Expression
(N
: Node_Id
) is
3395 In_Def_Exp
: constant Boolean := In_Default_Expression
;
3398 Desig_Typ
: Entity_Id
;
3402 Freeze_Outside
: Boolean := False;
3403 -- This flag is set true if the entity must be frozen outside the
3404 -- current subprogram. This happens in the case of expander generated
3405 -- subprograms (_Init_Proc, _Input, _Output, _Read, _Write) which do
3406 -- not freeze all entities like other bodies, but which nevertheless
3407 -- may reference entities that have to be frozen before the body and
3408 -- obviously cannot be frozen inside the body.
3410 function In_Exp_Body
(N
: Node_Id
) return Boolean;
3411 -- Given an N_Handled_Sequence_Of_Statements node N, determines whether
3412 -- it is the handled statement sequence of an expander-generated
3413 -- subprogram (init proc, or stream subprogram). If so, it returns
3414 -- True, otherwise False.
3420 function In_Exp_Body
(N
: Node_Id
) return Boolean is
3424 if Nkind
(N
) = N_Subprogram_Body
then
3430 if Nkind
(P
) /= N_Subprogram_Body
then
3434 P
:= Defining_Unit_Name
(Specification
(P
));
3436 if Nkind
(P
) = N_Defining_Identifier
3437 and then (Is_Init_Proc
(P
) or else
3438 Is_TSS
(P
, TSS_Stream_Input
) or else
3439 Is_TSS
(P
, TSS_Stream_Output
) or else
3440 Is_TSS
(P
, TSS_Stream_Read
) or else
3441 Is_TSS
(P
, TSS_Stream_Write
))
3450 -- Start of processing for Freeze_Expression
3453 -- Immediate return if freezing is inhibited. This flag is set by the
3454 -- analyzer to stop freezing on generated expressions that would cause
3455 -- freezing if they were in the source program, but which are not
3456 -- supposed to freeze, since they are created.
3458 if Must_Not_Freeze
(N
) then
3462 -- If expression is non-static, then it does not freeze in a default
3463 -- expression, see section "Handling of Default Expressions" in the
3464 -- spec of package Sem for further details. Note that we have to
3465 -- make sure that we actually have a real expression (if we have
3466 -- a subtype indication, we can't test Is_Static_Expression!)
3469 and then Nkind
(N
) in N_Subexpr
3470 and then not Is_Static_Expression
(N
)
3475 -- Freeze type of expression if not frozen already
3479 if Nkind
(N
) in N_Has_Etype
then
3480 if not Is_Frozen
(Etype
(N
)) then
3483 -- Base type may be an derived numeric type that is frozen at
3484 -- the point of declaration, but first_subtype is still unfrozen.
3486 elsif not Is_Frozen
(First_Subtype
(Etype
(N
))) then
3487 Typ
:= First_Subtype
(Etype
(N
));
3491 -- For entity name, freeze entity if not frozen already. A special
3492 -- exception occurs for an identifier that did not come from source.
3493 -- We don't let such identifiers freeze a non-internal entity, i.e.
3494 -- an entity that did come from source, since such an identifier was
3495 -- generated by the expander, and cannot have any semantic effect on
3496 -- the freezing semantics. For example, this stops the parameter of
3497 -- an initialization procedure from freezing the variable.
3499 if Is_Entity_Name
(N
)
3500 and then not Is_Frozen
(Entity
(N
))
3501 and then (Nkind
(N
) /= N_Identifier
3502 or else Comes_From_Source
(N
)
3503 or else not Comes_From_Source
(Entity
(N
)))
3510 -- For an allocator freeze designated type if not frozen already
3512 -- For an aggregate whose component type is an access type, freeze the
3513 -- designated type now, so that its freeze does not appear within the
3514 -- loop that might be created in the expansion of the aggregate. If the
3515 -- designated type is a private type without full view, the expression
3516 -- cannot contain an allocator, so the type is not frozen.
3522 Desig_Typ
:= Designated_Type
(Etype
(N
));
3525 if Is_Array_Type
(Etype
(N
))
3526 and then Is_Access_Type
(Component_Type
(Etype
(N
)))
3528 Desig_Typ
:= Designated_Type
(Component_Type
(Etype
(N
)));
3531 when N_Selected_Component |
3532 N_Indexed_Component |
3535 if Is_Access_Type
(Etype
(Prefix
(N
))) then
3536 Desig_Typ
:= Designated_Type
(Etype
(Prefix
(N
)));
3543 if Desig_Typ
/= Empty
3544 and then (Is_Frozen
(Desig_Typ
)
3545 or else (not Is_Fully_Defined
(Desig_Typ
)))
3550 -- All done if nothing needs freezing
3554 and then No
(Desig_Typ
)
3559 -- Loop for looking at the right place to insert the freeze nodes
3560 -- exiting from the loop when it is appropriate to insert the freeze
3561 -- node before the current node P.
3563 -- Also checks some special exceptions to the freezing rules. These
3564 -- cases result in a direct return, bypassing the freeze action.
3568 Parent_P
:= Parent
(P
);
3570 -- If we don't have a parent, then we are not in a well-formed tree.
3571 -- This is an unusual case, but there are some legitimate situations
3572 -- in which this occurs, notably when the expressions in the range of
3573 -- a type declaration are resolved. We simply ignore the freeze
3574 -- request in this case. Is this right ???
3576 if No
(Parent_P
) then
3580 -- See if we have got to an appropriate point in the tree
3582 case Nkind
(Parent_P
) is
3584 -- A special test for the exception of (RM 13.14(8)) for the case
3585 -- of per-object expressions (RM 3.8(18)) occurring in component
3586 -- definition or a discrete subtype definition. Note that we test
3587 -- for a component declaration which includes both cases we are
3588 -- interested in, and furthermore the tree does not have explicit
3589 -- nodes for either of these two constructs.
3591 when N_Component_Declaration
=>
3593 -- The case we want to test for here is an identifier that is
3594 -- a per-object expression, this is either a discriminant that
3595 -- appears in a context other than the component declaration
3596 -- or it is a reference to the type of the enclosing construct.
3598 -- For either of these cases, we skip the freezing
3600 if not In_Default_Expression
3601 and then Nkind
(N
) = N_Identifier
3602 and then (Present
(Entity
(N
)))
3604 -- We recognize the discriminant case by just looking for
3605 -- a reference to a discriminant. It can only be one for
3606 -- the enclosing construct. Skip freezing in this case.
3608 if Ekind
(Entity
(N
)) = E_Discriminant
then
3611 -- For the case of a reference to the enclosing record,
3612 -- (or task or protected type), we look for a type that
3613 -- matches the current scope.
3615 elsif Entity
(N
) = Current_Scope
then
3620 -- If we have an enumeration literal that appears as the choice in
3621 -- the aggregate of an enumeration representation clause, then
3622 -- freezing does not occur (RM 13.14(10)).
3624 when N_Enumeration_Representation_Clause
=>
3626 -- The case we are looking for is an enumeration literal
3628 if (Nkind
(N
) = N_Identifier
or Nkind
(N
) = N_Character_Literal
)
3629 and then Is_Enumeration_Type
(Etype
(N
))
3631 -- If enumeration literal appears directly as the choice,
3632 -- do not freeze (this is the normal non-overloade case)
3634 if Nkind
(Parent
(N
)) = N_Component_Association
3635 and then First
(Choices
(Parent
(N
))) = N
3639 -- If enumeration literal appears as the name of function
3640 -- which is the choice, then also do not freeze. This
3641 -- happens in the overloaded literal case, where the
3642 -- enumeration literal is temporarily changed to a function
3643 -- call for overloading analysis purposes.
3645 elsif Nkind
(Parent
(N
)) = N_Function_Call
3647 Nkind
(Parent
(Parent
(N
))) = N_Component_Association
3649 First
(Choices
(Parent
(Parent
(N
)))) = Parent
(N
)
3655 -- Normally if the parent is a handled sequence of statements,
3656 -- then the current node must be a statement, and that is an
3657 -- appropriate place to insert a freeze node.
3659 when N_Handled_Sequence_Of_Statements
=>
3661 -- An exception occurs when the sequence of statements is for
3662 -- an expander generated body that did not do the usual freeze
3663 -- all operation. In this case we usually want to freeze
3664 -- outside this body, not inside it, and we skip past the
3665 -- subprogram body that we are inside.
3667 if In_Exp_Body
(Parent_P
) then
3669 -- However, we *do* want to freeze at this point if we have
3670 -- an entity to freeze, and that entity is declared *inside*
3671 -- the body of the expander generated procedure. This case
3672 -- is recognized by the scope of the type, which is either
3673 -- the spec for some enclosing body, or (in the case of
3674 -- init_procs, for which there are no separate specs) the
3678 Subp
: constant Node_Id
:= Parent
(Parent_P
);
3682 if Nkind
(Subp
) = N_Subprogram_Body
then
3683 Cspc
:= Corresponding_Spec
(Subp
);
3685 if (Present
(Typ
) and then Scope
(Typ
) = Cspc
)
3687 (Present
(Nam
) and then Scope
(Nam
) = Cspc
)
3692 and then Scope
(Typ
) = Current_Scope
3693 and then Current_Scope
= Defining_Entity
(Subp
)
3700 -- If not that exception to the exception, then this is
3701 -- where we delay the freeze till outside the body.
3703 Parent_P
:= Parent
(Parent_P
);
3704 Freeze_Outside
:= True;
3706 -- Here if normal case where we are in handled statement
3707 -- sequence and want to do the insertion right there.
3713 -- If parent is a body or a spec or a block, then the current node
3714 -- is a statement or declaration and we can insert the freeze node
3717 when N_Package_Specification |
3723 N_Block_Statement
=> exit;
3725 -- The expander is allowed to define types in any statements list,
3726 -- so any of the following parent nodes also mark a freezing point
3727 -- if the actual node is in a list of statements or declarations.
3729 when N_Exception_Handler |
3732 N_Case_Statement_Alternative |
3733 N_Compilation_Unit_Aux |
3734 N_Selective_Accept |
3735 N_Accept_Alternative |
3736 N_Delay_Alternative |
3737 N_Conditional_Entry_Call |
3738 N_Entry_Call_Alternative |
3739 N_Triggering_Alternative |
3743 exit when Is_List_Member
(P
);
3745 -- Note: The N_Loop_Statement is a special case. A type that
3746 -- appears in the source can never be frozen in a loop (this
3747 -- occurs only because of a loop expanded by the expander), so we
3748 -- keep on going. Otherwise we terminate the search. Same is true
3749 -- of any entity which comes from source. (if they have predefined
3750 -- type, that type does not appear to come from source, but the
3751 -- entity should not be frozen here).
3753 when N_Loop_Statement
=>
3754 exit when not Comes_From_Source
(Etype
(N
))
3755 and then (No
(Nam
) or else not Comes_From_Source
(Nam
));
3757 -- For all other cases, keep looking at parents
3763 -- We fall through the case if we did not yet find the proper
3764 -- place in the free for inserting the freeze node, so climb!
3769 -- If the expression appears in a record or an initialization procedure,
3770 -- the freeze nodes are collected and attached to the current scope, to
3771 -- be inserted and analyzed on exit from the scope, to insure that
3772 -- generated entities appear in the correct scope. If the expression is
3773 -- a default for a discriminant specification, the scope is still void.
3774 -- The expression can also appear in the discriminant part of a private
3775 -- or concurrent type.
3777 -- If the expression appears in a constrained subcomponent of an
3778 -- enclosing record declaration, the freeze nodes must be attached to
3779 -- the outer record type so they can eventually be placed in the
3780 -- enclosing declaration list.
3782 -- The other case requiring this special handling is if we are in a
3783 -- default expression, since in that case we are about to freeze a
3784 -- static type, and the freeze scope needs to be the outer scope, not
3785 -- the scope of the subprogram with the default parameter.
3787 -- For default expressions in generic units, the Move_Freeze_Nodes
3788 -- mechanism (see sem_ch12.adb) takes care of placing them at the proper
3789 -- place, after the generic unit.
3791 if (In_Def_Exp
and not Inside_A_Generic
)
3792 or else Freeze_Outside
3793 or else (Is_Type
(Current_Scope
)
3794 and then (not Is_Concurrent_Type
(Current_Scope
)
3795 or else not Has_Completion
(Current_Scope
)))
3796 or else Ekind
(Current_Scope
) = E_Void
3799 Loc
: constant Source_Ptr
:= Sloc
(Current_Scope
);
3800 Freeze_Nodes
: List_Id
:= No_List
;
3801 Pos
: Int
:= Scope_Stack
.Last
;
3804 if Present
(Desig_Typ
) then
3805 Freeze_And_Append
(Desig_Typ
, Loc
, Freeze_Nodes
);
3808 if Present
(Typ
) then
3809 Freeze_And_Append
(Typ
, Loc
, Freeze_Nodes
);
3812 if Present
(Nam
) then
3813 Freeze_And_Append
(Nam
, Loc
, Freeze_Nodes
);
3816 -- The current scope may be that of a constrained component of
3817 -- an enclosing record declaration, which is above the current
3818 -- scope in the scope stack.
3820 if Is_Record_Type
(Scope
(Current_Scope
)) then
3824 if Is_Non_Empty_List
(Freeze_Nodes
) then
3825 if No
(Scope_Stack
.Table
(Pos
).Pending_Freeze_Actions
) then
3826 Scope_Stack
.Table
(Pos
).Pending_Freeze_Actions
:=
3829 Append_List
(Freeze_Nodes
, Scope_Stack
.Table
3830 (Pos
).Pending_Freeze_Actions
);
3838 -- Now we have the right place to do the freezing. First, a special
3839 -- adjustment, if we are in default expression analysis mode, these
3840 -- freeze actions must not be thrown away (normally all inserted actions
3841 -- are thrown away in this mode. However, the freeze actions are from
3842 -- static expressions and one of the important reasons we are doing this
3843 -- special analysis is to get these freeze actions. Therefore we turn
3844 -- off the In_Default_Expression mode to propagate these freeze actions.
3845 -- This also means they get properly analyzed and expanded.
3847 In_Default_Expression
:= False;
3849 -- Freeze the designated type of an allocator (RM 13.14(13))
3851 if Present
(Desig_Typ
) then
3852 Freeze_Before
(P
, Desig_Typ
);
3855 -- Freeze type of expression (RM 13.14(10)). Note that we took care of
3856 -- the enumeration representation clause exception in the loop above.
3858 if Present
(Typ
) then
3859 Freeze_Before
(P
, Typ
);
3862 -- Freeze name if one is present (RM 13.14(11))
3864 if Present
(Nam
) then
3865 Freeze_Before
(P
, Nam
);
3868 In_Default_Expression
:= In_Def_Exp
;
3869 end Freeze_Expression
;
3871 -----------------------------
3872 -- Freeze_Fixed_Point_Type --
3873 -----------------------------
3875 -- Certain fixed-point types and subtypes, including implicit base types
3876 -- and declared first subtypes, have not yet set up a range. This is
3877 -- because the range cannot be set until the Small and Size values are
3878 -- known, and these are not known till the type is frozen.
3880 -- To signal this case, Scalar_Range contains an unanalyzed syntactic range
3881 -- whose bounds are unanalyzed real literals. This routine will recognize
3882 -- this case, and transform this range node into a properly typed range
3883 -- with properly analyzed and resolved values.
3885 procedure Freeze_Fixed_Point_Type
(Typ
: Entity_Id
) is
3886 Rng
: constant Node_Id
:= Scalar_Range
(Typ
);
3887 Lo
: constant Node_Id
:= Low_Bound
(Rng
);
3888 Hi
: constant Node_Id
:= High_Bound
(Rng
);
3889 Btyp
: constant Entity_Id
:= Base_Type
(Typ
);
3890 Brng
: constant Node_Id
:= Scalar_Range
(Btyp
);
3891 BLo
: constant Node_Id
:= Low_Bound
(Brng
);
3892 BHi
: constant Node_Id
:= High_Bound
(Brng
);
3893 Small
: constant Ureal
:= Small_Value
(Typ
);
3900 function Fsize
(Lov
, Hiv
: Ureal
) return Nat
;
3901 -- Returns size of type with given bounds. Also leaves these
3902 -- bounds set as the current bounds of the Typ.
3908 function Fsize
(Lov
, Hiv
: Ureal
) return Nat
is
3910 Set_Realval
(Lo
, Lov
);
3911 Set_Realval
(Hi
, Hiv
);
3912 return Minimum_Size
(Typ
);
3915 -- Start of processing for Freeze_Fixed_Point_Type
3918 -- If Esize of a subtype has not previously been set, set it now
3920 if Unknown_Esize
(Typ
) then
3921 Atype
:= Ancestor_Subtype
(Typ
);
3923 if Present
(Atype
) then
3924 Set_Esize
(Typ
, Esize
(Atype
));
3926 Set_Esize
(Typ
, Esize
(Base_Type
(Typ
)));
3930 -- Immediate return if the range is already analyzed. This means that
3931 -- the range is already set, and does not need to be computed by this
3934 if Analyzed
(Rng
) then
3938 -- Immediate return if either of the bounds raises Constraint_Error
3940 if Raises_Constraint_Error
(Lo
)
3941 or else Raises_Constraint_Error
(Hi
)
3946 Loval
:= Realval
(Lo
);
3947 Hival
:= Realval
(Hi
);
3949 -- Ordinary fixed-point case
3951 if Is_Ordinary_Fixed_Point_Type
(Typ
) then
3953 -- For the ordinary fixed-point case, we are allowed to fudge the
3954 -- end-points up or down by small. Generally we prefer to fudge up,
3955 -- i.e. widen the bounds for non-model numbers so that the end points
3956 -- are included. However there are cases in which this cannot be
3957 -- done, and indeed cases in which we may need to narrow the bounds.
3958 -- The following circuit makes the decision.
3960 -- Note: our terminology here is that Incl_EP means that the bounds
3961 -- are widened by Small if necessary to include the end points, and
3962 -- Excl_EP means that the bounds are narrowed by Small to exclude the
3963 -- end-points if this reduces the size.
3965 -- Note that in the Incl case, all we care about is including the
3966 -- end-points. In the Excl case, we want to narrow the bounds as
3967 -- much as permitted by the RM, to give the smallest possible size.
3970 Loval_Incl_EP
: Ureal
;
3971 Hival_Incl_EP
: Ureal
;
3973 Loval_Excl_EP
: Ureal
;
3974 Hival_Excl_EP
: Ureal
;
3980 First_Subt
: Entity_Id
;
3985 -- First step. Base types are required to be symmetrical. Right
3986 -- now, the base type range is a copy of the first subtype range.
3987 -- This will be corrected before we are done, but right away we
3988 -- need to deal with the case where both bounds are non-negative.
3989 -- In this case, we set the low bound to the negative of the high
3990 -- bound, to make sure that the size is computed to include the
3991 -- required sign. Note that we do not need to worry about the
3992 -- case of both bounds negative, because the sign will be dealt
3993 -- with anyway. Furthermore we can't just go making such a bound
3994 -- symmetrical, since in a twos-complement system, there is an
3995 -- extra negative value which could not be accomodated on the
3999 and then not UR_Is_Negative
(Loval
)
4000 and then Hival
> Loval
4003 Set_Realval
(Lo
, Loval
);
4006 -- Compute the fudged bounds. If the number is a model number,
4007 -- then we do nothing to include it, but we are allowed to backoff
4008 -- to the next adjacent model number when we exclude it. If it is
4009 -- not a model number then we straddle the two values with the
4010 -- model numbers on either side.
4012 Model_Num
:= UR_Trunc
(Loval
/ Small
) * Small
;
4014 if Loval
= Model_Num
then
4015 Loval_Incl_EP
:= Model_Num
;
4017 Loval_Incl_EP
:= Model_Num
- Small
;
4020 -- The low value excluding the end point is Small greater, but
4021 -- we do not do this exclusion if the low value is positive,
4022 -- since it can't help the size and could actually hurt by
4023 -- crossing the high bound.
4025 if UR_Is_Negative
(Loval_Incl_EP
) then
4026 Loval_Excl_EP
:= Loval_Incl_EP
+ Small
;
4028 Loval_Excl_EP
:= Loval_Incl_EP
;
4031 -- Similar processing for upper bound and high value
4033 Model_Num
:= UR_Trunc
(Hival
/ Small
) * Small
;
4035 if Hival
= Model_Num
then
4036 Hival_Incl_EP
:= Model_Num
;
4038 Hival_Incl_EP
:= Model_Num
+ Small
;
4041 if UR_Is_Positive
(Hival_Incl_EP
) then
4042 Hival_Excl_EP
:= Hival_Incl_EP
- Small
;
4044 Hival_Excl_EP
:= Hival_Incl_EP
;
4047 -- One further adjustment is needed. In the case of subtypes, we
4048 -- cannot go outside the range of the base type, or we get
4049 -- peculiarities, and the base type range is already set. This
4050 -- only applies to the Incl values, since clearly the Excl values
4051 -- are already as restricted as they are allowed to be.
4054 Loval_Incl_EP
:= UR_Max
(Loval_Incl_EP
, Realval
(BLo
));
4055 Hival_Incl_EP
:= UR_Min
(Hival_Incl_EP
, Realval
(BHi
));
4058 -- Get size including and excluding end points
4060 Size_Incl_EP
:= Fsize
(Loval_Incl_EP
, Hival_Incl_EP
);
4061 Size_Excl_EP
:= Fsize
(Loval_Excl_EP
, Hival_Excl_EP
);
4063 -- No need to exclude end-points if it does not reduce size
4065 if Fsize
(Loval_Incl_EP
, Hival_Excl_EP
) = Size_Excl_EP
then
4066 Loval_Excl_EP
:= Loval_Incl_EP
;
4069 if Fsize
(Loval_Excl_EP
, Hival_Incl_EP
) = Size_Excl_EP
then
4070 Hival_Excl_EP
:= Hival_Incl_EP
;
4073 -- Now we set the actual size to be used. We want to use the
4074 -- bounds fudged up to include the end-points but only if this
4075 -- can be done without violating a specifically given size
4076 -- size clause or causing an unacceptable increase in size.
4078 -- Case of size clause given
4080 if Has_Size_Clause
(Typ
) then
4082 -- Use the inclusive size only if it is consistent with
4083 -- the explicitly specified size.
4085 if Size_Incl_EP
<= RM_Size
(Typ
) then
4086 Actual_Lo
:= Loval_Incl_EP
;
4087 Actual_Hi
:= Hival_Incl_EP
;
4088 Actual_Size
:= Size_Incl_EP
;
4090 -- If the inclusive size is too large, we try excluding
4091 -- the end-points (will be caught later if does not work).
4094 Actual_Lo
:= Loval_Excl_EP
;
4095 Actual_Hi
:= Hival_Excl_EP
;
4096 Actual_Size
:= Size_Excl_EP
;
4099 -- Case of size clause not given
4102 -- If we have a base type whose corresponding first subtype
4103 -- has an explicit size that is large enough to include our
4104 -- end-points, then do so. There is no point in working hard
4105 -- to get a base type whose size is smaller than the specified
4106 -- size of the first subtype.
4108 First_Subt
:= First_Subtype
(Typ
);
4110 if Has_Size_Clause
(First_Subt
)
4111 and then Size_Incl_EP
<= Esize
(First_Subt
)
4113 Actual_Size
:= Size_Incl_EP
;
4114 Actual_Lo
:= Loval_Incl_EP
;
4115 Actual_Hi
:= Hival_Incl_EP
;
4117 -- If excluding the end-points makes the size smaller and
4118 -- results in a size of 8,16,32,64, then we take the smaller
4119 -- size. For the 64 case, this is compulsory. For the other
4120 -- cases, it seems reasonable. We like to include end points
4121 -- if we can, but not at the expense of moving to the next
4122 -- natural boundary of size.
4124 elsif Size_Incl_EP
/= Size_Excl_EP
4126 (Size_Excl_EP
= 8 or else
4127 Size_Excl_EP
= 16 or else
4128 Size_Excl_EP
= 32 or else
4131 Actual_Size
:= Size_Excl_EP
;
4132 Actual_Lo
:= Loval_Excl_EP
;
4133 Actual_Hi
:= Hival_Excl_EP
;
4135 -- Otherwise we can definitely include the end points
4138 Actual_Size
:= Size_Incl_EP
;
4139 Actual_Lo
:= Loval_Incl_EP
;
4140 Actual_Hi
:= Hival_Incl_EP
;
4143 -- One pathological case: normally we never fudge a low bound
4144 -- down, since it would seem to increase the size (if it has
4145 -- any effect), but for ranges containing single value, or no
4146 -- values, the high bound can be small too large. Consider:
4148 -- type t is delta 2.0**(-14)
4149 -- range 131072.0 .. 0;
4151 -- That lower bound is *just* outside the range of 32 bits, and
4152 -- does need fudging down in this case. Note that the bounds
4153 -- will always have crossed here, since the high bound will be
4154 -- fudged down if necessary, as in the case of:
4156 -- type t is delta 2.0**(-14)
4157 -- range 131072.0 .. 131072.0;
4159 -- So we detect the situation by looking for crossed bounds,
4160 -- and if the bounds are crossed, and the low bound is greater
4161 -- than zero, we will always back it off by small, since this
4162 -- is completely harmless.
4164 if Actual_Lo
> Actual_Hi
then
4165 if UR_Is_Positive
(Actual_Lo
) then
4166 Actual_Lo
:= Loval_Incl_EP
- Small
;
4167 Actual_Size
:= Fsize
(Actual_Lo
, Actual_Hi
);
4169 -- And of course, we need to do exactly the same parallel
4170 -- fudge for flat ranges in the negative region.
4172 elsif UR_Is_Negative
(Actual_Hi
) then
4173 Actual_Hi
:= Hival_Incl_EP
+ Small
;
4174 Actual_Size
:= Fsize
(Actual_Lo
, Actual_Hi
);
4179 Set_Realval
(Lo
, Actual_Lo
);
4180 Set_Realval
(Hi
, Actual_Hi
);
4183 -- For the decimal case, none of this fudging is required, since there
4184 -- are no end-point problems in the decimal case (the end-points are
4185 -- always included).
4188 Actual_Size
:= Fsize
(Loval
, Hival
);
4191 -- At this stage, the actual size has been calculated and the proper
4192 -- required bounds are stored in the low and high bounds.
4194 if Actual_Size
> 64 then
4195 Error_Msg_Uint_1
:= UI_From_Int
(Actual_Size
);
4197 ("size required (^) for type& too large, maximum is 64", Typ
);
4201 -- Check size against explicit given size
4203 if Has_Size_Clause
(Typ
) then
4204 if Actual_Size
> RM_Size
(Typ
) then
4205 Error_Msg_Uint_1
:= RM_Size
(Typ
);
4206 Error_Msg_Uint_2
:= UI_From_Int
(Actual_Size
);
4208 ("size given (^) for type& too small, minimum is ^",
4209 Size_Clause
(Typ
), Typ
);
4212 Actual_Size
:= UI_To_Int
(Esize
(Typ
));
4215 -- Increase size to next natural boundary if no size clause given
4218 if Actual_Size
<= 8 then
4220 elsif Actual_Size
<= 16 then
4222 elsif Actual_Size
<= 32 then
4228 Init_Esize
(Typ
, Actual_Size
);
4229 Adjust_Esize_For_Alignment
(Typ
);
4232 -- If we have a base type, then expand the bounds so that they extend to
4233 -- the full width of the allocated size in bits, to avoid junk range
4234 -- checks on intermediate computations.
4236 if Base_Type
(Typ
) = Typ
then
4237 Set_Realval
(Lo
, -(Small
* (Uint_2
** (Actual_Size
- 1))));
4238 Set_Realval
(Hi
, (Small
* (Uint_2
** (Actual_Size
- 1) - 1)));
4241 -- Final step is to reanalyze the bounds using the proper type
4242 -- and set the Corresponding_Integer_Value fields of the literals.
4244 Set_Etype
(Lo
, Empty
);
4245 Set_Analyzed
(Lo
, False);
4248 -- Resolve with universal fixed if the base type, and the base type if
4249 -- it is a subtype. Note we can't resolve the base type with itself,
4250 -- that would be a reference before definition.
4253 Resolve
(Lo
, Universal_Fixed
);
4258 -- Set corresponding integer value for bound
4260 Set_Corresponding_Integer_Value
4261 (Lo
, UR_To_Uint
(Realval
(Lo
) / Small
));
4263 -- Similar processing for high bound
4265 Set_Etype
(Hi
, Empty
);
4266 Set_Analyzed
(Hi
, False);
4270 Resolve
(Hi
, Universal_Fixed
);
4275 Set_Corresponding_Integer_Value
4276 (Hi
, UR_To_Uint
(Realval
(Hi
) / Small
));
4278 -- Set type of range to correspond to bounds
4280 Set_Etype
(Rng
, Etype
(Lo
));
4282 -- Set Esize to calculated size if not set already
4284 if Unknown_Esize
(Typ
) then
4285 Init_Esize
(Typ
, Actual_Size
);
4288 -- Set RM_Size if not already set. If already set, check value
4291 Minsiz
: constant Uint
:= UI_From_Int
(Minimum_Size
(Typ
));
4294 if RM_Size
(Typ
) /= Uint_0
then
4295 if RM_Size
(Typ
) < Minsiz
then
4296 Error_Msg_Uint_1
:= RM_Size
(Typ
);
4297 Error_Msg_Uint_2
:= Minsiz
;
4299 ("size given (^) for type& too small, minimum is ^",
4300 Size_Clause
(Typ
), Typ
);
4304 Set_RM_Size
(Typ
, Minsiz
);
4307 end Freeze_Fixed_Point_Type
;
4313 procedure Freeze_Itype
(T
: Entity_Id
; N
: Node_Id
) is
4317 Set_Has_Delayed_Freeze
(T
);
4318 L
:= Freeze_Entity
(T
, Sloc
(N
));
4320 if Is_Non_Empty_List
(L
) then
4321 Insert_Actions
(N
, L
);
4325 --------------------------
4326 -- Freeze_Static_Object --
4327 --------------------------
4329 procedure Freeze_Static_Object
(E
: Entity_Id
) is
4331 Cannot_Be_Static
: exception;
4332 -- Exception raised if the type of a static object cannot be made
4333 -- static. This happens if the type depends on non-global objects.
4335 procedure Ensure_Expression_Is_SA
(N
: Node_Id
);
4336 -- Called to ensure that an expression used as part of a type definition
4337 -- is statically allocatable, which means that the expression type is
4338 -- statically allocatable, and the expression is either static, or a
4339 -- reference to a library level constant.
4341 procedure Ensure_Type_Is_SA
(Typ
: Entity_Id
);
4342 -- Called to mark a type as static, checking that it is possible
4343 -- to set the type as static. If it is not possible, then the
4344 -- exception Cannot_Be_Static is raised.
4346 -----------------------------
4347 -- Ensure_Expression_Is_SA --
4348 -----------------------------
4350 procedure Ensure_Expression_Is_SA
(N
: Node_Id
) is
4354 Ensure_Type_Is_SA
(Etype
(N
));
4356 if Is_Static_Expression
(N
) then
4359 elsif Nkind
(N
) = N_Identifier
then
4363 and then Ekind
(Ent
) = E_Constant
4364 and then Is_Library_Level_Entity
(Ent
)
4370 raise Cannot_Be_Static
;
4371 end Ensure_Expression_Is_SA
;
4373 -----------------------
4374 -- Ensure_Type_Is_SA --
4375 -----------------------
4377 procedure Ensure_Type_Is_SA
(Typ
: Entity_Id
) is
4382 -- If type is library level, we are all set
4384 if Is_Library_Level_Entity
(Typ
) then
4388 -- We are also OK if the type already marked as statically allocated,
4389 -- which means we processed it before.
4391 if Is_Statically_Allocated
(Typ
) then
4395 -- Mark type as statically allocated
4397 Set_Is_Statically_Allocated
(Typ
);
4399 -- Check that it is safe to statically allocate this type
4401 if Is_Scalar_Type
(Typ
) or else Is_Real_Type
(Typ
) then
4402 Ensure_Expression_Is_SA
(Type_Low_Bound
(Typ
));
4403 Ensure_Expression_Is_SA
(Type_High_Bound
(Typ
));
4405 elsif Is_Array_Type
(Typ
) then
4406 N
:= First_Index
(Typ
);
4407 while Present
(N
) loop
4408 Ensure_Type_Is_SA
(Etype
(N
));
4412 Ensure_Type_Is_SA
(Component_Type
(Typ
));
4414 elsif Is_Access_Type
(Typ
) then
4415 if Ekind
(Designated_Type
(Typ
)) = E_Subprogram_Type
then
4419 T
: constant Entity_Id
:= Etype
(Designated_Type
(Typ
));
4422 if T
/= Standard_Void_Type
then
4423 Ensure_Type_Is_SA
(T
);
4426 F
:= First_Formal
(Designated_Type
(Typ
));
4428 while Present
(F
) loop
4429 Ensure_Type_Is_SA
(Etype
(F
));
4435 Ensure_Type_Is_SA
(Designated_Type
(Typ
));
4438 elsif Is_Record_Type
(Typ
) then
4439 C
:= First_Entity
(Typ
);
4441 while Present
(C
) loop
4442 if Ekind
(C
) = E_Discriminant
4443 or else Ekind
(C
) = E_Component
4445 Ensure_Type_Is_SA
(Etype
(C
));
4447 elsif Is_Type
(C
) then
4448 Ensure_Type_Is_SA
(C
);
4454 elsif Ekind
(Typ
) = E_Subprogram_Type
then
4455 Ensure_Type_Is_SA
(Etype
(Typ
));
4457 C
:= First_Formal
(Typ
);
4458 while Present
(C
) loop
4459 Ensure_Type_Is_SA
(Etype
(C
));
4464 raise Cannot_Be_Static
;
4466 end Ensure_Type_Is_SA
;
4468 -- Start of processing for Freeze_Static_Object
4471 Ensure_Type_Is_SA
(Etype
(E
));
4473 -- Reset True_Constant flag, since something strange is going on with
4474 -- the scoping here, and our simple value tracing may not be sufficient
4475 -- for this indication to be reliable. We kill the Constant_Value
4476 -- indication for the same reason.
4478 Set_Is_True_Constant
(E
, False);
4479 Set_Current_Value
(E
, Empty
);
4482 when Cannot_Be_Static
=>
4484 -- If the object that cannot be static is imported or exported,
4485 -- then we give an error message saying that this object cannot
4486 -- be imported or exported.
4488 if Is_Imported
(E
) then
4490 ("& cannot be imported (local type is not constant)", E
);
4492 -- Otherwise must be exported, something is wrong if compiler
4493 -- is marking something as statically allocated which cannot be).
4495 else pragma Assert
(Is_Exported
(E
));
4497 ("& cannot be exported (local type is not constant)", E
);
4499 end Freeze_Static_Object
;
4501 -----------------------
4502 -- Freeze_Subprogram --
4503 -----------------------
4505 procedure Freeze_Subprogram
(E
: Entity_Id
) is
4510 -- Subprogram may not have an address clause unless it is imported
4512 if Present
(Address_Clause
(E
)) then
4513 if not Is_Imported
(E
) then
4515 ("address clause can only be given " &
4516 "for imported subprogram",
4517 Name
(Address_Clause
(E
)));
4521 -- Reset the Pure indication on an imported subprogram unless an
4522 -- explicit Pure_Function pragma was present. We do this because
4523 -- otherwise it is an insidious error to call a non-pure function from
4524 -- pure unit and have calls mysteriously optimized away. What happens
4525 -- here is that the Import can bypass the normal check to ensure that
4526 -- pure units call only pure subprograms.
4529 and then Is_Pure
(E
)
4530 and then not Has_Pragma_Pure_Function
(E
)
4532 Set_Is_Pure
(E
, False);
4535 -- For non-foreign convention subprograms, this is where we create
4536 -- the extra formals (for accessibility level and constrained bit
4537 -- information). We delay this till the freeze point precisely so
4538 -- that we know the convention!
4540 if not Has_Foreign_Convention
(E
) then
4541 Create_Extra_Formals
(E
);
4544 -- If this is convention Ada and a Valued_Procedure, that's odd
4546 if Ekind
(E
) = E_Procedure
4547 and then Is_Valued_Procedure
(E
)
4548 and then Convention
(E
) = Convention_Ada
4549 and then Warn_On_Export_Import
4552 ("?Valued_Procedure has no effect for convention Ada", E
);
4553 Set_Is_Valued_Procedure
(E
, False);
4556 -- Case of foreign convention
4561 -- For foreign conventions, warn about return of an
4562 -- unconstrained array.
4564 -- Note: we *do* allow a return by descriptor for the VMS case,
4565 -- though here there is probably more to be done ???
4567 if Ekind
(E
) = E_Function
then
4568 Retype
:= Underlying_Type
(Etype
(E
));
4570 -- If no return type, probably some other error, e.g. a
4571 -- missing full declaration, so ignore.
4576 -- If the return type is generic, we have emitted a warning
4577 -- earlier on, and there is nothing else to check here. Specific
4578 -- instantiations may lead to erroneous behavior.
4580 elsif Is_Generic_Type
(Etype
(E
)) then
4583 elsif Is_Array_Type
(Retype
)
4584 and then not Is_Constrained
(Retype
)
4585 and then Mechanism
(E
) not in Descriptor_Codes
4586 and then Warn_On_Export_Import
4589 ("?foreign convention function& should not return " &
4590 "unconstrained array", E
);
4595 -- If any of the formals for an exported foreign convention
4596 -- subprogram have defaults, then emit an appropriate warning since
4597 -- this is odd (default cannot be used from non-Ada code)
4599 if Is_Exported
(E
) then
4600 F
:= First_Formal
(E
);
4601 while Present
(F
) loop
4602 if Warn_On_Export_Import
4603 and then Present
(Default_Value
(F
))
4606 ("?parameter cannot be defaulted in non-Ada call",
4615 -- For VMS, descriptor mechanisms for parameters are allowed only
4616 -- for imported subprograms.
4618 if OpenVMS_On_Target
then
4619 if not Is_Imported
(E
) then
4620 F
:= First_Formal
(E
);
4621 while Present
(F
) loop
4622 if Mechanism
(F
) in Descriptor_Codes
then
4624 ("descriptor mechanism for parameter not permitted", F
);
4626 ("\can only be used for imported subprogram", F
);
4634 -- Pragma Inline_Always is disallowed for dispatching subprograms
4635 -- because the address of such subprograms is saved in the dispatch
4636 -- table to support dispatching calls, and dispatching calls cannot
4637 -- be inlined. This is consistent with the restriction against using
4638 -- 'Access or 'Address on an Inline_Always subprogram.
4640 if Is_Dispatching_Operation
(E
) and then Is_Always_Inlined
(E
) then
4642 ("pragma Inline_Always not allowed for dispatching subprograms", E
);
4644 end Freeze_Subprogram
;
4646 ----------------------
4647 -- Is_Fully_Defined --
4648 ----------------------
4650 function Is_Fully_Defined
(T
: Entity_Id
) return Boolean is
4652 if Ekind
(T
) = E_Class_Wide_Type
then
4653 return Is_Fully_Defined
(Etype
(T
));
4655 elsif Is_Array_Type
(T
) then
4656 return Is_Fully_Defined
(Component_Type
(T
));
4658 elsif Is_Record_Type
(T
)
4659 and not Is_Private_Type
(T
)
4661 -- Verify that the record type has no components with private types
4662 -- without completion.
4668 Comp
:= First_Component
(T
);
4670 while Present
(Comp
) loop
4671 if not Is_Fully_Defined
(Etype
(Comp
)) then
4675 Next_Component
(Comp
);
4680 else return not Is_Private_Type
(T
)
4681 or else Present
(Full_View
(Base_Type
(T
)));
4683 end Is_Fully_Defined
;
4685 ---------------------------------
4686 -- Process_Default_Expressions --
4687 ---------------------------------
4689 procedure Process_Default_Expressions
4691 After
: in out Node_Id
)
4693 Loc
: constant Source_Ptr
:= Sloc
(E
);
4700 Set_Default_Expressions_Processed
(E
);
4702 -- A subprogram instance and its associated anonymous subprogram share
4703 -- their signature. The default expression functions are defined in the
4704 -- wrapper packages for the anonymous subprogram, and should not be
4705 -- generated again for the instance.
4707 if Is_Generic_Instance
(E
)
4708 and then Present
(Alias
(E
))
4709 and then Default_Expressions_Processed
(Alias
(E
))
4714 Formal
:= First_Formal
(E
);
4716 while Present
(Formal
) loop
4717 if Present
(Default_Value
(Formal
)) then
4719 -- We work with a copy of the default expression because we
4720 -- do not want to disturb the original, since this would mess
4721 -- up the conformance checking.
4723 Dcopy
:= New_Copy_Tree
(Default_Value
(Formal
));
4725 -- The analysis of the expression may generate insert actions,
4726 -- which of course must not be executed. We wrap those actions
4727 -- in a procedure that is not called, and later on eliminated.
4728 -- The following cases have no side-effects, and are analyzed
4731 if Nkind
(Dcopy
) = N_Identifier
4732 or else Nkind
(Dcopy
) = N_Expanded_Name
4733 or else Nkind
(Dcopy
) = N_Integer_Literal
4734 or else (Nkind
(Dcopy
) = N_Real_Literal
4735 and then not Vax_Float
(Etype
(Dcopy
)))
4736 or else Nkind
(Dcopy
) = N_Character_Literal
4737 or else Nkind
(Dcopy
) = N_String_Literal
4738 or else Nkind
(Dcopy
) = N_Null
4739 or else (Nkind
(Dcopy
) = N_Attribute_Reference
4741 Attribute_Name
(Dcopy
) = Name_Null_Parameter
)
4744 -- If there is no default function, we must still do a full
4745 -- analyze call on the default value, to ensure that all error
4746 -- checks are performed, e.g. those associated with static
4747 -- evaluation. Note: this branch will always be taken if the
4748 -- analyzer is turned off (but we still need the error checks).
4750 -- Note: the setting of parent here is to meet the requirement
4751 -- that we can only analyze the expression while attached to
4752 -- the tree. Really the requirement is that the parent chain
4753 -- be set, we don't actually need to be in the tree.
4755 Set_Parent
(Dcopy
, Declaration_Node
(Formal
));
4758 -- Default expressions are resolved with their own type if the
4759 -- context is generic, to avoid anomalies with private types.
4761 if Ekind
(Scope
(E
)) = E_Generic_Package
then
4764 Resolve
(Dcopy
, Etype
(Formal
));
4767 -- If that resolved expression will raise constraint error,
4768 -- then flag the default value as raising constraint error.
4769 -- This allows a proper error message on the calls.
4771 if Raises_Constraint_Error
(Dcopy
) then
4772 Set_Raises_Constraint_Error
(Default_Value
(Formal
));
4775 -- If the default is a parameterless call, we use the name of
4776 -- the called function directly, and there is no body to build.
4778 elsif Nkind
(Dcopy
) = N_Function_Call
4779 and then No
(Parameter_Associations
(Dcopy
))
4783 -- Else construct and analyze the body of a wrapper procedure
4784 -- that contains an object declaration to hold the expression.
4785 -- Given that this is done only to complete the analysis, it
4786 -- simpler to build a procedure than a function which might
4787 -- involve secondary stack expansion.
4791 Make_Defining_Identifier
(Loc
, New_Internal_Name
('D'));
4794 Make_Subprogram_Body
(Loc
,
4796 Make_Procedure_Specification
(Loc
,
4797 Defining_Unit_Name
=> Dnam
),
4799 Declarations
=> New_List
(
4800 Make_Object_Declaration
(Loc
,
4801 Defining_Identifier
=>
4802 Make_Defining_Identifier
(Loc
,
4803 New_Internal_Name
('T')),
4804 Object_Definition
=>
4805 New_Occurrence_Of
(Etype
(Formal
), Loc
),
4806 Expression
=> New_Copy_Tree
(Dcopy
))),
4808 Handled_Statement_Sequence
=>
4809 Make_Handled_Sequence_Of_Statements
(Loc
,
4810 Statements
=> New_List
));
4812 Set_Scope
(Dnam
, Scope
(E
));
4813 Set_Assignment_OK
(First
(Declarations
(Dbody
)));
4814 Set_Is_Eliminated
(Dnam
);
4815 Insert_After
(After
, Dbody
);
4821 Next_Formal
(Formal
);
4824 end Process_Default_Expressions
;
4826 ----------------------------------------
4827 -- Set_Component_Alignment_If_Not_Set --
4828 ----------------------------------------
4830 procedure Set_Component_Alignment_If_Not_Set
(Typ
: Entity_Id
) is
4832 -- Ignore if not base type, subtypes don't need anything
4834 if Typ
/= Base_Type
(Typ
) then
4838 -- Do not override existing representation
4840 if Is_Packed
(Typ
) then
4843 elsif Has_Specified_Layout
(Typ
) then
4846 elsif Component_Alignment
(Typ
) /= Calign_Default
then
4850 Set_Component_Alignment
4851 (Typ
, Scope_Stack
.Table
4852 (Scope_Stack
.Last
).Component_Alignment_Default
);
4854 end Set_Component_Alignment_If_Not_Set
;
4856 ---------------------------
4857 -- Set_Debug_Info_Needed --
4858 ---------------------------
4860 procedure Set_Debug_Info_Needed
(T
: Entity_Id
) is
4863 or else Needs_Debug_Info
(T
)
4864 or else Debug_Info_Off
(T
)
4868 Set_Needs_Debug_Info
(T
);
4871 if Is_Object
(T
) then
4872 Set_Debug_Info_Needed
(Etype
(T
));
4874 elsif Is_Type
(T
) then
4875 Set_Debug_Info_Needed
(Etype
(T
));
4877 if Is_Record_Type
(T
) then
4879 Ent
: Entity_Id
:= First_Entity
(T
);
4881 while Present
(Ent
) loop
4882 Set_Debug_Info_Needed
(Ent
);
4887 elsif Is_Array_Type
(T
) then
4888 Set_Debug_Info_Needed
(Component_Type
(T
));
4891 Indx
: Node_Id
:= First_Index
(T
);
4893 while Present
(Indx
) loop
4894 Set_Debug_Info_Needed
(Etype
(Indx
));
4895 Indx
:= Next_Index
(Indx
);
4899 if Is_Packed
(T
) then
4900 Set_Debug_Info_Needed
(Packed_Array_Type
(T
));
4903 elsif Is_Access_Type
(T
) then
4904 Set_Debug_Info_Needed
(Directly_Designated_Type
(T
));
4906 elsif Is_Private_Type
(T
) then
4907 Set_Debug_Info_Needed
(Full_View
(T
));
4909 elsif Is_Protected_Type
(T
) then
4910 Set_Debug_Info_Needed
(Corresponding_Record_Type
(T
));
4913 end Set_Debug_Info_Needed
;
4919 procedure Undelay_Type
(T
: Entity_Id
) is
4921 Set_Has_Delayed_Freeze
(T
, False);
4922 Set_Freeze_Node
(T
, Empty
);
4924 -- Since we don't want T to have a Freeze_Node, we don't want its
4925 -- Full_View or Corresponding_Record_Type to have one either.
4927 -- ??? Fundamentally, this whole handling is a kludge. What we really
4928 -- want is to be sure that for an Itype that's part of record R and is a
4929 -- subtype of type T, that it's frozen after the later of the freeze
4930 -- points of R and T. We have no way of doing that directly, so what we
4931 -- do is force most such Itypes to be frozen as part of freezing R via
4932 -- this procedure and only delay the ones that need to be delayed
4933 -- (mostly the designated types of access types that are defined as part
4936 if Is_Private_Type
(T
)
4937 and then Present
(Full_View
(T
))
4938 and then Is_Itype
(Full_View
(T
))
4939 and then Is_Record_Type
(Scope
(Full_View
(T
)))
4941 Undelay_Type
(Full_View
(T
));
4944 if Is_Concurrent_Type
(T
)
4945 and then Present
(Corresponding_Record_Type
(T
))
4946 and then Is_Itype
(Corresponding_Record_Type
(T
))
4947 and then Is_Record_Type
(Scope
(Corresponding_Record_Type
(T
)))
4949 Undelay_Type
(Corresponding_Record_Type
(T
));
4957 procedure Warn_Overlay
4962 Ent
: constant Entity_Id
:= Entity
(Nam
);
4963 -- The object to which the address clause applies
4966 Old
: Entity_Id
:= Empty
;
4970 -- No warning if address clause overlay warnings are off
4972 if not Address_Clause_Overlay_Warnings
then
4976 -- No warning if there is an explicit initialization
4978 Init
:= Original_Node
(Expression
(Declaration_Node
(Ent
)));
4980 if Present
(Init
) and then Comes_From_Source
(Init
) then
4984 -- We only give the warning for non-imported entities of a type for
4985 -- which a non-null base init proc is defined (or for access types which
4986 -- have implicit null initialization).
4989 and then (Has_Non_Null_Base_Init_Proc
(Typ
)
4990 or else Is_Access_Type
(Typ
))
4991 and then not Is_Imported
(Ent
)
4993 if Nkind
(Expr
) = N_Attribute_Reference
4994 and then Is_Entity_Name
(Prefix
(Expr
))
4996 Old
:= Entity
(Prefix
(Expr
));
4998 elsif Is_Entity_Name
(Expr
)
4999 and then Ekind
(Entity
(Expr
)) = E_Constant
5001 Decl
:= Declaration_Node
(Entity
(Expr
));
5003 if Nkind
(Decl
) = N_Object_Declaration
5004 and then Present
(Expression
(Decl
))
5005 and then Nkind
(Expression
(Decl
)) = N_Attribute_Reference
5006 and then Is_Entity_Name
(Prefix
(Expression
(Decl
)))
5008 Old
:= Entity
(Prefix
(Expression
(Decl
)));
5010 elsif Nkind
(Expr
) = N_Function_Call
then
5014 -- A function call (most likely to To_Address) is probably not an
5015 -- overlay, so skip warning. Ditto if the function call was inlined
5016 -- and transformed into an entity.
5018 elsif Nkind
(Original_Node
(Expr
)) = N_Function_Call
then
5022 Decl
:= Next
(Parent
(Expr
));
5024 -- If a pragma Import follows, we assume that it is for the current
5025 -- target of the address clause, and skip the warning.
5028 and then Nkind
(Decl
) = N_Pragma
5029 and then Chars
(Decl
) = Name_Import
5034 if Present
(Old
) then
5035 Error_Msg_Node_2
:= Old
;
5037 ("default initialization of & may modify &?",
5041 ("default initialization of & may modify overlaid storage?",
5045 -- Add friendly warning if initialization comes from a packed array
5048 if Is_Record_Type
(Typ
) then
5053 Comp
:= First_Component
(Typ
);
5055 while Present
(Comp
) loop
5056 if Nkind
(Parent
(Comp
)) = N_Component_Declaration
5057 and then Present
(Expression
(Parent
(Comp
)))
5060 elsif Is_Array_Type
(Etype
(Comp
))
5061 and then Present
(Packed_Array_Type
(Etype
(Comp
)))
5064 ("packed array component& will be initialized to zero?",
5068 Next_Component
(Comp
);
5075 ("use pragma Import for & to " &
5076 "suppress initialization ('R'M B.1(24))?",