1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1992-2023, Free Software Foundation, Inc. --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 3, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING3. If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license. --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
24 ------------------------------------------------------------------------------
26 with Accessibility
; use Accessibility
;
27 with Aspects
; use Aspects
;
28 with Atree
; use Atree
;
29 with Checks
; use Checks
;
30 with Contracts
; use Contracts
;
31 with Debug
; use Debug
;
32 with Elists
; use Elists
;
33 with Einfo
; use Einfo
;
34 with Einfo
.Entities
; use Einfo
.Entities
;
35 with Einfo
.Utils
; use Einfo
.Utils
;
36 with Errout
; use Errout
;
37 with Eval_Fat
; use Eval_Fat
;
38 with Exp_Ch3
; use Exp_Ch3
;
39 with Exp_Ch9
; use Exp_Ch9
;
40 with Exp_Disp
; use Exp_Disp
;
41 with Exp_Dist
; use Exp_Dist
;
42 with Exp_Tss
; use Exp_Tss
;
43 with Exp_Util
; use Exp_Util
;
44 with Expander
; use Expander
;
45 with Freeze
; use Freeze
;
46 with Ghost
; use Ghost
;
47 with Itypes
; use Itypes
;
48 with Layout
; use Layout
;
50 with Lib
.Xref
; use Lib
.Xref
;
51 with Namet
; use Namet
;
52 with Nlists
; use Nlists
;
53 with Nmake
; use Nmake
;
55 with Restrict
; use Restrict
;
56 with Rident
; use Rident
;
57 with Rtsfind
; use Rtsfind
;
59 with Sem_Aux
; use Sem_Aux
;
60 with Sem_Case
; use Sem_Case
;
61 with Sem_Cat
; use Sem_Cat
;
62 with Sem_Ch6
; use Sem_Ch6
;
63 with Sem_Ch7
; use Sem_Ch7
;
64 with Sem_Ch8
; use Sem_Ch8
;
65 with Sem_Ch10
; use Sem_Ch10
;
66 with Sem_Ch13
; use Sem_Ch13
;
67 with Sem_Dim
; use Sem_Dim
;
68 with Sem_Disp
; use Sem_Disp
;
69 with Sem_Dist
; use Sem_Dist
;
70 with Sem_Elab
; use Sem_Elab
;
71 with Sem_Elim
; use Sem_Elim
;
72 with Sem_Eval
; use Sem_Eval
;
73 with Sem_Mech
; use Sem_Mech
;
74 with Sem_Res
; use Sem_Res
;
75 with Sem_Smem
; use Sem_Smem
;
76 with Sem_Type
; use Sem_Type
;
77 with Sem_Util
; use Sem_Util
;
78 with Sem_Warn
; use Sem_Warn
;
79 with Stand
; use Stand
;
80 with Sinfo
; use Sinfo
;
81 with Sinfo
.Nodes
; use Sinfo
.Nodes
;
82 with Sinfo
.Utils
; use Sinfo
.Utils
;
83 with Sinput
; use Sinput
;
84 with Snames
; use Snames
;
85 with Strub
; use Strub
;
86 with Targparm
; use Targparm
;
87 with Tbuild
; use Tbuild
;
88 with Ttypes
; use Ttypes
;
89 with Uintp
; use Uintp
;
90 with Urealp
; use Urealp
;
91 with Warnsw
; use Warnsw
;
93 package body Sem_Ch3
is
95 -----------------------
96 -- Local Subprograms --
97 -----------------------
99 procedure Add_Interface_Tag_Components
(N
: Node_Id
; Typ
: Entity_Id
);
100 -- Ada 2005 (AI-251): Add the tag components corresponding to all the
101 -- abstract interface types implemented by a record type or a derived
104 procedure Build_Access_Subprogram_Wrapper
(Decl
: Node_Id
);
105 -- When an access-to-subprogram type has pre/postconditions, we build a
106 -- subprogram that includes these contracts and is invoked by an indirect
107 -- call through the corresponding access type.
109 procedure Build_Derived_Type
111 Parent_Type
: Entity_Id
;
112 Derived_Type
: Entity_Id
;
113 Is_Completion
: Boolean;
114 Derive_Subps
: Boolean := True);
115 -- Create and decorate a Derived_Type given the Parent_Type entity. N is
116 -- the N_Full_Type_Declaration node containing the derived type definition.
117 -- Parent_Type is the entity for the parent type in the derived type
118 -- definition and Derived_Type the actual derived type. Is_Completion must
119 -- be set to False if Derived_Type is the N_Defining_Identifier node in N
120 -- (i.e. Derived_Type = Defining_Identifier (N)). In this case N is not the
121 -- completion of a private type declaration. If Is_Completion is set to
122 -- True, N is the completion of a private type declaration and Derived_Type
123 -- is different from the defining identifier inside N (i.e. Derived_Type /=
124 -- Defining_Identifier (N)). Derive_Subps indicates whether the parent
125 -- subprograms should be derived. The only case where this parameter is
126 -- False is when Build_Derived_Type is recursively called to process an
127 -- implicit derived full type for a type derived from a private type (in
128 -- that case the subprograms must only be derived for the private view of
131 -- ??? These flags need a bit of re-examination and re-documentation:
132 -- ??? are they both necessary (both seem related to the recursion)?
134 procedure Build_Derived_Access_Type
136 Parent_Type
: Entity_Id
;
137 Derived_Type
: Entity_Id
);
138 -- Subsidiary procedure to Build_Derived_Type. For a derived access type,
139 -- create an implicit base if the parent type is constrained or if the
140 -- subtype indication has a constraint.
142 procedure Build_Derived_Array_Type
144 Parent_Type
: Entity_Id
;
145 Derived_Type
: Entity_Id
);
146 -- Subsidiary procedure to Build_Derived_Type. For a derived array type,
147 -- create an implicit base if the parent type is constrained or if the
148 -- subtype indication has a constraint.
150 procedure Build_Derived_Concurrent_Type
152 Parent_Type
: Entity_Id
;
153 Derived_Type
: Entity_Id
);
154 -- Subsidiary procedure to Build_Derived_Type. For a derived task or
155 -- protected type, inherit entries and protected subprograms, check
156 -- legality of discriminant constraints if any.
158 procedure Build_Derived_Enumeration_Type
160 Parent_Type
: Entity_Id
;
161 Derived_Type
: Entity_Id
);
162 -- Subsidiary procedure to Build_Derived_Type. For a derived enumeration
163 -- type, we must create a new list of literals. Types derived from
164 -- Character and [Wide_]Wide_Character are special-cased.
166 procedure Build_Derived_Numeric_Type
168 Parent_Type
: Entity_Id
;
169 Derived_Type
: Entity_Id
);
170 -- Subsidiary procedure to Build_Derived_Type. For numeric types, create
171 -- an anonymous base type, and propagate constraint to subtype if needed.
173 procedure Build_Derived_Private_Type
175 Parent_Type
: Entity_Id
;
176 Derived_Type
: Entity_Id
;
177 Is_Completion
: Boolean;
178 Derive_Subps
: Boolean := True);
179 -- Subsidiary procedure to Build_Derived_Type. This procedure is complex
180 -- because the parent may or may not have a completion, and the derivation
181 -- may itself be a completion.
183 procedure Build_Derived_Record_Type
185 Parent_Type
: Entity_Id
;
186 Derived_Type
: Entity_Id
;
187 Derive_Subps
: Boolean := True);
188 -- Subsidiary procedure used for tagged and untagged record types
189 -- by Build_Derived_Type and Analyze_Private_Extension_Declaration.
190 -- All parameters are as in Build_Derived_Type except that N, in
191 -- addition to being an N_Full_Type_Declaration node, can also be an
192 -- N_Private_Extension_Declaration node. See the definition of this routine
193 -- for much more info. Derive_Subps indicates whether subprograms should be
194 -- derived from the parent type. The only case where Derive_Subps is False
195 -- is for an implicit derived full type for a type derived from a private
196 -- type (see Build_Derived_Type).
198 procedure Build_Discriminal
(Discrim
: Entity_Id
);
199 -- Create the discriminal corresponding to discriminant Discrim, that is
200 -- the parameter corresponding to Discrim to be used in initialization
201 -- procedures for the type where Discrim is a discriminant. Discriminals
202 -- are not used during semantic analysis, and are not fully defined
203 -- entities until expansion. Thus they are not given a scope until
204 -- initialization procedures are built.
206 function Build_Discriminant_Constraints
209 Derived_Def
: Boolean := False) return Elist_Id
;
210 -- Validate discriminant constraints and return the list of the constraints
211 -- in order of discriminant declarations, where T is the discriminated
212 -- unconstrained type. Def is the N_Subtype_Indication node where the
213 -- discriminants constraints for T are specified. Derived_Def is True
214 -- when building the discriminant constraints in a derived type definition
215 -- of the form "type D (...) is new T (xxx)". In this case T is the parent
216 -- type and Def is the constraint "(xxx)" on T and this routine sets the
217 -- Corresponding_Discriminant field of the discriminants in the derived
218 -- type D to point to the corresponding discriminants in the parent type T.
220 procedure Build_Discriminated_Subtype
224 Related_Nod
: Node_Id
;
225 For_Access
: Boolean := False);
226 -- Subsidiary procedure to Constrain_Discriminated_Type and to
227 -- Process_Incomplete_Dependents. Given
229 -- T (a possibly discriminated base type)
230 -- Def_Id (a very partially built subtype for T),
232 -- the call completes Def_Id to be the appropriate E_*_Subtype.
234 -- The Elist is the list of discriminant constraints if any (it is set
235 -- to No_Elist if T is not a discriminated type, and to an empty list if
236 -- T has discriminants but there are no discriminant constraints). The
237 -- Related_Nod is the same as Decl_Node in Create_Constrained_Components.
238 -- The For_Access says whether or not this subtype is really constraining
241 function Build_Scalar_Bound
244 Der_T
: Entity_Id
) return Node_Id
;
245 -- The bounds of a derived scalar type are conversions of the bounds of
246 -- the parent type. Optimize the representation if the bounds are literals.
247 -- Needs a more complete spec--what are the parameters exactly, and what
248 -- exactly is the returned value, and how is Bound affected???
250 procedure Check_Access_Discriminant_Requires_Limited
253 -- Check the restriction that the type to which an access discriminant
254 -- belongs must be a concurrent type or a descendant of a type with
255 -- the reserved word 'limited' in its declaration.
257 procedure Check_Anonymous_Access_Component
262 Access_Def
: Node_Id
);
263 -- Ada 2005 AI-382: an access component in a record definition can refer to
264 -- the enclosing record, in which case it denotes the type itself, and not
265 -- the current instance of the type. We create an anonymous access type for
266 -- the component, and flag it as an access to a component, so accessibility
267 -- checks are properly performed on it. The declaration of the access type
268 -- is placed ahead of that of the record to prevent order-of-elaboration
269 -- circularity issues in Gigi. We create an incomplete type for the record
270 -- declaration, which is the designated type of the anonymous access.
272 procedure Check_Anonymous_Access_Components
276 Comp_List
: Node_Id
);
277 -- Call Check_Anonymous_Access_Component on Comp_List
279 procedure Check_Constraining_Discriminant
(New_Disc
, Old_Disc
: Entity_Id
);
280 -- Check that, if a new discriminant is used in a constraint defining the
281 -- parent subtype of a derivation, its subtype is statically compatible
282 -- with the subtype of the corresponding parent discriminant (RM 3.7(15)).
284 procedure Check_Delta_Expression
(E
: Node_Id
);
285 -- Check that the expression represented by E is suitable for use as a
286 -- delta expression, i.e. it is of real type and is static.
288 procedure Check_Digits_Expression
(E
: Node_Id
);
289 -- Check that the expression represented by E is suitable for use as a
290 -- digits expression, i.e. it is of integer type, positive and static.
292 procedure Check_Initialization
(T
: Entity_Id
; Exp
: Node_Id
);
293 -- Validate the initialization of an object declaration. T is the required
294 -- type, and Exp is the initialization expression.
296 procedure Check_Interfaces
(N
: Node_Id
; Def
: Node_Id
);
297 -- Check ARM rules 3.9.4 (15/2), 9.1 (9.d/2) and 9.4 (11.d/2)
299 procedure Check_Or_Process_Discriminants
302 Prev
: Entity_Id
:= Empty
);
303 -- If N is the full declaration of the completion T of an incomplete or
304 -- private type, check its discriminants (which are already known to be
305 -- conformant with those of the partial view, see Find_Type_Name),
306 -- otherwise process them. Prev is the entity of the partial declaration,
309 procedure Check_Real_Bound
(Bound
: Node_Id
);
310 -- Check given bound for being of real type and static. If not, post an
311 -- appropriate message, and rewrite the bound with the real literal zero.
313 procedure Constant_Redeclaration
317 -- Various checks on legality of full declaration of deferred constant.
318 -- Id is the entity for the redeclaration, N is the N_Object_Declaration,
319 -- node. The caller has not yet set any attributes of this entity.
321 function Contain_Interface
323 Ifaces
: Elist_Id
) return Boolean;
324 -- Ada 2005: Determine whether Iface is present in the list Ifaces
326 procedure Convert_Scalar_Bounds
328 Parent_Type
: Entity_Id
;
329 Derived_Type
: Entity_Id
;
331 -- For derived scalar types, convert the bounds in the type definition to
332 -- the derived type, and complete their analysis. Given a constraint of the
333 -- form ".. new T range Lo .. Hi", Lo and Hi are analyzed and resolved with
334 -- T'Base, the parent_type. The bounds of the derived type (the anonymous
335 -- base) are copies of Lo and Hi. Finally, the bounds of the derived
336 -- subtype are conversions of those bounds to the derived_type, so that
337 -- their typing is consistent.
339 procedure Copy_Array_Base_Type_Attributes
(T1
, T2
: Entity_Id
);
340 -- Copies attributes from array base type T2 to array base type T1. Copies
341 -- only attributes that apply to base types, but not subtypes.
343 procedure Copy_Array_Subtype_Attributes
(T1
, T2
: Entity_Id
);
344 -- Copies attributes from array subtype T2 to array subtype T1. Copies
345 -- attributes that apply to both subtypes and base types.
347 procedure Create_Constrained_Components
351 Constraints
: Elist_Id
);
352 -- Build the list of entities for a constrained discriminated record
353 -- subtype. If a component depends on a discriminant, replace its subtype
354 -- using the discriminant values in the discriminant constraint. Subt
355 -- is the defining identifier for the subtype whose list of constrained
356 -- entities we will create. Decl_Node is the type declaration node where
357 -- we will attach all the itypes created. Typ is the base discriminated
358 -- type for the subtype Subt. Constraints is the list of discriminant
359 -- constraints for Typ.
361 function Constrain_Component_Type
363 Constrained_Typ
: Entity_Id
;
364 Related_Node
: Node_Id
;
366 Constraints
: Elist_Id
) return Entity_Id
;
367 -- Given a discriminated base type Typ, a list of discriminant constraints,
368 -- Constraints, for Typ and a component Comp of Typ, create and return the
369 -- type corresponding to Etype (Comp) where all discriminant references
370 -- are replaced with the corresponding constraint. If Etype (Comp) contains
371 -- no discriminant references then it is returned as-is. Constrained_Typ
372 -- is the final constrained subtype to which the constrained component
373 -- belongs. Related_Node is the node where we attach all created itypes.
375 procedure Constrain_Access
376 (Def_Id
: in out Entity_Id
;
378 Related_Nod
: Node_Id
);
379 -- Apply a list of constraints to an access type. If Def_Id is empty, it is
380 -- an anonymous type created for a subtype indication. In that case it is
381 -- created in the procedure and attached to Related_Nod.
383 procedure Constrain_Array
384 (Def_Id
: in out Entity_Id
;
386 Related_Nod
: Node_Id
;
387 Related_Id
: Entity_Id
;
389 -- Apply a list of index constraints to an unconstrained array type. The
390 -- first parameter is the entity for the resulting subtype. A value of
391 -- Empty for Def_Id indicates that an implicit type must be created, but
392 -- creation is delayed (and must be done by this procedure) because other
393 -- subsidiary implicit types must be created first (which is why Def_Id
394 -- is an in/out parameter). The second parameter is a subtype indication
395 -- node for the constrained array to be created (e.g. something of the
396 -- form string (1 .. 10)). Related_Nod gives the place where this type
397 -- has to be inserted in the tree. The Related_Id and Suffix parameters
398 -- are used to build the associated Implicit type name.
400 procedure Constrain_Concurrent
401 (Def_Id
: in out Entity_Id
;
403 Related_Nod
: Node_Id
;
404 Related_Id
: Entity_Id
;
406 -- Apply list of discriminant constraints to an unconstrained concurrent
409 -- SI is the N_Subtype_Indication node containing the constraint and
410 -- the unconstrained type to constrain.
412 -- Def_Id is the entity for the resulting constrained subtype. A value
413 -- of Empty for Def_Id indicates that an implicit type must be created,
414 -- but creation is delayed (and must be done by this procedure) because
415 -- other subsidiary implicit types must be created first (which is why
416 -- Def_Id is an in/out parameter).
418 -- Related_Nod gives the place where this type has to be inserted
421 -- The last two arguments are used to create its external name if needed.
423 function Constrain_Corresponding_Record
424 (Prot_Subt
: Entity_Id
;
425 Corr_Rec
: Entity_Id
;
426 Related_Nod
: Node_Id
) return Entity_Id
;
427 -- When constraining a protected type or task type with discriminants,
428 -- constrain the corresponding record with the same discriminant values.
430 procedure Constrain_Decimal
(Def_Id
: Entity_Id
; S
: Node_Id
);
431 -- Constrain a decimal fixed point type with a digits constraint and/or a
432 -- range constraint, and build E_Decimal_Fixed_Point_Subtype entity.
434 procedure Constrain_Discriminated_Type
437 Related_Nod
: Node_Id
;
438 For_Access
: Boolean := False);
439 -- Process discriminant constraints of composite type. Verify that values
440 -- have been provided for all discriminants, that the original type is
441 -- unconstrained, and that the types of the supplied expressions match
442 -- the discriminant types. The first three parameters are like in routine
443 -- Constrain_Concurrent. See Build_Discriminated_Subtype for an explanation
446 procedure Constrain_Enumeration
(Def_Id
: Entity_Id
; S
: Node_Id
);
447 -- Constrain an enumeration type with a range constraint. This is identical
448 -- to Constrain_Integer, but for the Ekind of the resulting subtype.
450 procedure Constrain_Float
(Def_Id
: Entity_Id
; S
: Node_Id
);
451 -- Constrain a floating point type with either a digits constraint
452 -- and/or a range constraint, building a E_Floating_Point_Subtype.
454 procedure Constrain_Index
457 Related_Nod
: Node_Id
;
458 Related_Id
: Entity_Id
;
461 -- Process an index constraint S in a constrained array declaration. The
462 -- constraint can be a subtype name, or a range with or without an explicit
463 -- subtype mark. The index is the corresponding index of the unconstrained
464 -- array. The Related_Id and Suffix parameters are used to build the
465 -- associated Implicit type name.
467 procedure Constrain_Integer
(Def_Id
: Entity_Id
; S
: Node_Id
);
468 -- Build subtype of a signed or modular integer type
470 procedure Constrain_Ordinary_Fixed
(Def_Id
: Entity_Id
; S
: Node_Id
);
471 -- Constrain an ordinary fixed point type with a range constraint, and
472 -- build an E_Ordinary_Fixed_Point_Subtype entity.
474 procedure Copy_And_Swap
(Priv
, Full
: Entity_Id
);
475 -- Copy the Priv entity into the entity of its full declaration then swap
476 -- the two entities in such a manner that the former private type is now
477 -- seen as a full type.
479 procedure Decimal_Fixed_Point_Type_Declaration
482 -- Create a new decimal fixed point type, and apply the constraint to
483 -- obtain a subtype of this new type.
485 procedure Complete_Private_Subtype
488 Full_Base
: Entity_Id
;
489 Related_Nod
: Node_Id
);
490 -- Complete the implicit full view of a private subtype by setting the
491 -- appropriate semantic fields. If the full view of the parent is a record
492 -- type, build constrained components of subtype.
494 procedure Derive_Progenitor_Subprograms
495 (Parent_Type
: Entity_Id
;
496 Tagged_Type
: Entity_Id
);
497 -- Ada 2005 (AI-251): To complete type derivation, collect the primitive
498 -- operations of progenitors of Tagged_Type, and replace the subsidiary
499 -- subtypes with Tagged_Type, to build the specs of the inherited interface
500 -- primitives. The derived primitives are aliased to those of the
501 -- interface. This routine takes care also of transferring to the full view
502 -- subprograms associated with the partial view of Tagged_Type that cover
503 -- interface primitives.
505 procedure Derived_Standard_Character
507 Parent_Type
: Entity_Id
;
508 Derived_Type
: Entity_Id
);
509 -- Subsidiary procedure to Build_Derived_Enumeration_Type which handles
510 -- derivations from types Standard.Character and Standard.Wide_Character.
512 procedure Derived_Type_Declaration
515 Is_Completion
: Boolean);
516 -- Process a derived type declaration. Build_Derived_Type is invoked
517 -- to process the actual derived type definition. Parameters N and
518 -- Is_Completion have the same meaning as in Build_Derived_Type.
519 -- T is the N_Defining_Identifier for the entity defined in the
520 -- N_Full_Type_Declaration node N, that is T is the derived type.
522 procedure Enumeration_Type_Declaration
(T
: Entity_Id
; Def
: Node_Id
);
523 -- Insert each literal in symbol table, as an overloadable identifier. Each
524 -- enumeration type is mapped into a sequence of integers, and each literal
525 -- is defined as a constant with integer value. If any of the literals are
526 -- character literals, the type is a character type, which means that
527 -- strings are legal aggregates for arrays of components of the type.
529 function Expand_To_Stored_Constraint
531 Constraint
: Elist_Id
) return Elist_Id
;
532 -- Given a constraint (i.e. a list of expressions) on the discriminants of
533 -- Typ, expand it into a constraint on the stored discriminants and return
534 -- the new list of expressions constraining the stored discriminants.
536 function Find_Type_Of_Object
538 Related_Nod
: Node_Id
) return Entity_Id
;
539 -- Get type entity for object referenced by Obj_Def, attaching the implicit
540 -- types generated to Related_Nod.
542 procedure Floating_Point_Type_Declaration
(T
: Entity_Id
; Def
: Node_Id
);
543 -- Create a new float and apply the constraint to obtain subtype of it
545 function Has_Range_Constraint
(N
: Node_Id
) return Boolean;
546 -- Given an N_Subtype_Indication node N, return True if a range constraint
547 -- is present, either directly, or as part of a digits or delta constraint.
548 -- In addition, a digits constraint in the decimal case returns True, since
549 -- it establishes a default range if no explicit range is present.
551 function Inherit_Components
553 Parent_Base
: Entity_Id
;
554 Derived_Base
: Entity_Id
;
556 Inherit_Discr
: Boolean;
557 Discs
: Elist_Id
) return Elist_Id
;
558 -- Called from Build_Derived_Record_Type to inherit the components of
559 -- Parent_Base (a base type) into the Derived_Base (the derived base type).
560 -- For more information on derived types and component inheritance please
561 -- consult the comment above the body of Build_Derived_Record_Type.
563 -- N is the original derived type declaration
565 -- Is_Tagged is set if we are dealing with tagged types
567 -- If Inherit_Discr is set, Derived_Base inherits its discriminants from
568 -- Parent_Base, otherwise no discriminants are inherited.
570 -- Discs gives the list of constraints that apply to Parent_Base in the
571 -- derived type declaration. If Discs is set to No_Elist, then we have
572 -- the following situation:
574 -- type Parent (D1..Dn : ..) is [tagged] record ...;
575 -- type Derived is new Parent [with ...];
577 -- which gets treated as
579 -- type Derived (D1..Dn : ..) is new Parent (D1,..,Dn) [with ...];
581 -- For untagged types the returned value is an association list. The list
582 -- starts from the association (Parent_Base => Derived_Base), and then it
583 -- contains a sequence of the associations of the form
585 -- (Old_Component => New_Component),
587 -- where Old_Component is the Entity_Id of a component in Parent_Base and
588 -- New_Component is the Entity_Id of the corresponding component in
589 -- Derived_Base. For untagged records, this association list is needed when
590 -- copying the record declaration for the derived base. In the tagged case
591 -- the value returned is irrelevant.
593 function Is_EVF_Procedure
(Subp
: Entity_Id
) return Boolean;
594 -- Subsidiary to Check_Abstract_Overriding and Derive_Subprogram.
595 -- Determine whether subprogram Subp is a procedure subject to pragma
596 -- Extensions_Visible with value False and has at least one controlling
597 -- parameter of mode OUT.
599 function Is_Private_Primitive
(Prim
: Entity_Id
) return Boolean;
600 -- Subsidiary to Check_Abstract_Overriding and Derive_Subprogram.
601 -- When applied to a primitive subprogram Prim, returns True if Prim is
602 -- declared as a private operation within a package or generic package,
603 -- and returns False otherwise.
605 function Is_Valid_Constraint_Kind
607 Constraint_Kind
: Node_Kind
) return Boolean;
608 -- Returns True if it is legal to apply the given kind of constraint to the
609 -- given kind of type (index constraint to an array type, for example).
611 procedure Modular_Type_Declaration
(T
: Entity_Id
; Def
: Node_Id
);
612 -- Create new modular type. Verify that modulus is in bounds
614 procedure New_Concatenation_Op
(Typ
: Entity_Id
);
615 -- Create an abbreviated declaration for an operator in order to
616 -- materialize concatenation on array types.
618 procedure Ordinary_Fixed_Point_Type_Declaration
621 -- Create a new ordinary fixed point type, and apply the constraint to
622 -- obtain subtype of it.
624 procedure Preanalyze_Default_Expression
(N
: Node_Id
; T
: Entity_Id
);
625 -- Wrapper on Preanalyze_Spec_Expression for default expressions, so that
626 -- In_Default_Expr can be properly adjusted.
628 procedure Prepare_Private_Subtype_Completion
630 Related_Nod
: Node_Id
);
631 -- Id is a subtype of some private type. Creates the full declaration
632 -- associated with Id whenever possible, i.e. when the full declaration
633 -- of the base type is already known. Records each subtype into
634 -- Private_Dependents of the base type.
636 procedure Process_Incomplete_Dependents
640 -- Process all entities that depend on an incomplete type. There include
641 -- subtypes, subprogram types that mention the incomplete type in their
642 -- profiles, and subprogram with access parameters that designate the
645 -- Inc_T is the defining identifier of an incomplete type declaration, its
646 -- Ekind is E_Incomplete_Type.
648 -- N is the corresponding N_Full_Type_Declaration for Inc_T.
650 -- Full_T is N's defining identifier.
652 -- Subtypes of incomplete types with discriminants are completed when the
653 -- parent type is. This is simpler than private subtypes, because they can
654 -- only appear in the same scope, and there is no need to exchange views.
655 -- Similarly, access_to_subprogram types may have a parameter or a return
656 -- type that is an incomplete type, and that must be replaced with the
659 -- If the full type is tagged, subprogram with access parameters that
660 -- designated the incomplete may be primitive operations of the full type,
661 -- and have to be processed accordingly.
663 procedure Process_Real_Range_Specification
(Def
: Node_Id
);
664 -- Given the type definition for a real type, this procedure processes and
665 -- checks the real range specification of this type definition if one is
666 -- present. If errors are found, error messages are posted, and the
667 -- Real_Range_Specification of Def is reset to Empty.
669 procedure Record_Type_Declaration
673 -- Process a record type declaration (for both untagged and tagged
674 -- records). Parameters T and N are exactly like in procedure
675 -- Derived_Type_Declaration, except that no flag Is_Completion is needed
676 -- for this routine. If this is the completion of an incomplete type
677 -- declaration, Prev is the entity of the incomplete declaration, used for
678 -- cross-referencing. Otherwise Prev = T.
680 procedure Record_Type_Definition
(Def
: Node_Id
; Prev_T
: Entity_Id
);
681 -- This routine is used to process the actual record type definition (both
682 -- for untagged and tagged records). Def is a record type definition node.
683 -- This procedure analyzes the components in this record type definition.
684 -- Prev_T is the entity for the enclosing record type. It is provided so
685 -- that its Has_Task flag can be set if any of the component have Has_Task
686 -- set. If the declaration is the completion of an incomplete type
687 -- declaration, Prev_T is the original incomplete type, whose full view is
690 procedure Replace_Discriminants
(Typ
: Entity_Id
; Decl
: Node_Id
);
691 -- Subsidiary to Build_Derived_Record_Type. For untagged record types, we
692 -- first create the list of components for the derived type from that of
693 -- the parent by means of Inherit_Components and then build a copy of the
694 -- declaration tree of the parent with the help of the mapping returned by
695 -- Inherit_Components, which will for example be used to validate record
696 -- representation clauses given for the derived type. If the parent type
697 -- is private and has discriminants, the ancestor discriminants used in the
698 -- inheritance are that of the private declaration, whereas the ancestor
699 -- discriminants present in the declaration tree of the parent are that of
700 -- the full declaration; as a consequence, the remapping done during the
701 -- copy will leave the references to the ancestor discriminants unchanged
702 -- in the declaration tree and they need to be fixed up. If the derived
703 -- type has a known discriminant part, then the remapping done during the
704 -- copy will only create references to the stored discriminants and they
705 -- need to be replaced with references to the non-stored discriminants.
707 procedure Set_Fixed_Range
712 -- Build a range node with the given bounds and set it as the Scalar_Range
713 -- of the given fixed-point type entity. Loc is the source location used
714 -- for the constructed range. See body for further details.
716 procedure Set_Scalar_Range_For_Subtype
720 -- This routine is used to set the scalar range field for a subtype given
721 -- Def_Id, the entity for the subtype, and R, the range expression for the
722 -- scalar range. Subt provides the parent subtype to be used to analyze,
723 -- resolve, and check the given range.
725 procedure Set_Default_SSO
(T
: Entity_Id
);
726 -- T is the entity for an array or record being declared. This procedure
727 -- sets the flags SSO_Set_Low_By_Default/SSO_Set_High_By_Default according
728 -- to the setting of Opt.Default_SSO.
730 procedure Signed_Integer_Type_Declaration
(T
: Entity_Id
; Def
: Node_Id
);
731 -- Create a new signed integer entity, and apply the constraint to obtain
732 -- the required first named subtype of this type.
734 procedure Set_Stored_Constraint_From_Discriminant_Constraint
736 -- E is some record type. This routine computes E's Stored_Constraint
737 -- from its Discriminant_Constraint.
739 procedure Diagnose_Interface
(N
: Node_Id
; E
: Entity_Id
);
740 -- Check that an entity in a list of progenitors is an interface,
741 -- emit error otherwise.
743 -----------------------
744 -- Access_Definition --
745 -----------------------
747 function Access_Definition
748 (Related_Nod
: Node_Id
;
749 N
: Node_Id
) return Entity_Id
751 Anon_Type
: Entity_Id
;
752 Anon_Scope
: Entity_Id
;
753 Desig_Type
: Entity_Id
;
754 Enclosing_Prot_Type
: Entity_Id
:= Empty
;
757 if Is_Entry
(Current_Scope
)
758 and then Is_Task_Type
(Etype
(Scope
(Current_Scope
)))
760 Error_Msg_N
("task entries cannot have access parameters", N
);
764 -- Ada 2005: For an object declaration the corresponding anonymous
765 -- type is declared in the current scope.
767 -- If the access definition is the return type of another access to
768 -- function, scope is the current one, because it is the one of the
769 -- current type declaration, except for the pathological case below.
771 if Nkind
(Related_Nod
) in
772 N_Object_Declaration | N_Access_Function_Definition
774 Anon_Scope
:= Current_Scope
;
776 -- A pathological case: function returning access functions that
777 -- return access functions, etc. Each anonymous access type created
778 -- is in the enclosing scope of the outermost function.
786 N_Access_Function_Definition | N_Access_Definition
791 if Nkind
(Par
) = N_Function_Specification
then
792 Anon_Scope
:= Scope
(Defining_Entity
(Par
));
796 -- For the anonymous function result case, retrieve the scope of the
797 -- function specification's associated entity rather than using the
798 -- current scope. The current scope will be the function itself if the
799 -- formal part is currently being analyzed, but will be the parent scope
800 -- in the case of a parameterless function, and we always want to use
801 -- the function's parent scope. Finally, if the function is a child
802 -- unit, we must traverse the tree to retrieve the proper entity.
804 elsif Nkind
(Related_Nod
) = N_Function_Specification
805 and then Nkind
(Parent
(N
)) /= N_Parameter_Specification
807 -- If the current scope is a protected type, the anonymous access
808 -- is associated with one of the protected operations, and must
809 -- be available in the scope that encloses the protected declaration.
810 -- Otherwise the type is in the scope enclosing the subprogram.
812 -- If the function has formals, the return type of a subprogram
813 -- declaration is analyzed in the scope of the subprogram (see
814 -- Process_Formals) and thus the protected type, if present, is
815 -- the scope of the current function scope.
817 if Ekind
(Current_Scope
) = E_Protected_Type
then
818 Enclosing_Prot_Type
:= Current_Scope
;
820 elsif Ekind
(Current_Scope
) = E_Function
821 and then Ekind
(Scope
(Current_Scope
)) = E_Protected_Type
823 Enclosing_Prot_Type
:= Scope
(Current_Scope
);
826 if Present
(Enclosing_Prot_Type
) then
827 Anon_Scope
:= Scope
(Enclosing_Prot_Type
);
830 Anon_Scope
:= Scope
(Defining_Entity
(Related_Nod
));
833 -- For an access type definition, if the current scope is a child
834 -- unit it is the scope of the type.
836 elsif Is_Compilation_Unit
(Current_Scope
) then
837 Anon_Scope
:= Current_Scope
;
839 -- For access formals, access components, and access discriminants, the
840 -- scope is that of the enclosing declaration,
843 Anon_Scope
:= Scope
(Current_Scope
);
848 (E_Anonymous_Access_Type
, Related_Nod
, Scope_Id
=> Anon_Scope
);
851 and then Ada_Version
>= Ada_2005
853 Error_Msg_N
("ALL not permitted for anonymous access types", N
);
856 -- Ada 2005 (AI-254): In case of anonymous access to subprograms call
857 -- the corresponding semantic routine
859 if Present
(Access_To_Subprogram_Definition
(N
)) then
860 Access_Subprogram_Declaration
861 (T_Name
=> Anon_Type
,
862 T_Def
=> Access_To_Subprogram_Definition
(N
));
864 if Ekind
(Anon_Type
) = E_Access_Protected_Subprogram_Type
then
866 (Anon_Type
, E_Anonymous_Access_Protected_Subprogram_Type
);
868 Mutate_Ekind
(Anon_Type
, E_Anonymous_Access_Subprogram_Type
);
871 -- If the anonymous access is associated with a protected operation,
872 -- create a reference to it after the enclosing protected definition
873 -- because the itype will be used in the subsequent bodies.
875 -- If the anonymous access itself is protected, a full type
876 -- declaratiton will be created for it, so that the equivalent
877 -- record type can be constructed. For further details, see
878 -- Replace_Anonymous_Access_To_Protected-Subprogram.
880 if Ekind
(Current_Scope
) = E_Protected_Type
881 and then not Protected_Present
(Access_To_Subprogram_Definition
(N
))
883 Build_Itype_Reference
(Anon_Type
, Parent
(Current_Scope
));
889 Find_Type
(Subtype_Mark
(N
));
890 Desig_Type
:= Entity
(Subtype_Mark
(N
));
892 Set_Directly_Designated_Type
(Anon_Type
, Desig_Type
);
893 Set_Etype
(Anon_Type
, Anon_Type
);
895 -- Make sure the anonymous access type has size and alignment fields
896 -- set, as required by gigi. This is necessary in the case of the
897 -- Task_Body_Procedure.
899 if not Has_Private_Component
(Desig_Type
) then
900 Layout_Type
(Anon_Type
);
903 -- Ada 2005 (AI-231): Ada 2005 semantics for anonymous access differs
904 -- from Ada 95 semantics. In Ada 2005, anonymous access must specify if
905 -- the null value is allowed. In Ada 95 the null value is never allowed.
907 if Ada_Version
>= Ada_2005
then
908 Set_Can_Never_Be_Null
(Anon_Type
, Null_Exclusion_Present
(N
));
910 Set_Can_Never_Be_Null
(Anon_Type
, True);
913 -- The anonymous access type is as public as the discriminated type or
914 -- subprogram that defines it. It is imported (for back-end purposes)
915 -- if the designated type is.
917 Set_Is_Public
(Anon_Type
, Is_Public
(Scope
(Anon_Type
)));
919 -- Ada 2005 (AI-231): Propagate the access-constant attribute
921 Set_Is_Access_Constant
(Anon_Type
, Constant_Present
(N
));
923 -- The context is either a subprogram declaration, object declaration,
924 -- or an access discriminant, in a private or a full type declaration.
925 -- In the case of a subprogram, if the designated type is incomplete,
926 -- the operation will be a primitive operation of the full type, to be
927 -- updated subsequently. If the type is imported through a limited_with
928 -- clause, the subprogram is not a primitive operation of the type
929 -- (which is declared elsewhere in some other scope).
931 if Ekind
(Desig_Type
) = E_Incomplete_Type
932 and then not From_Limited_With
(Desig_Type
)
933 and then Is_Overloadable
(Current_Scope
)
935 Append_Elmt
(Current_Scope
, Private_Dependents
(Desig_Type
));
936 Set_Has_Delayed_Freeze
(Current_Scope
);
939 -- If the designated type is limited and class-wide, the object might
940 -- contain tasks, so we create a Master entity for the declaration. This
941 -- must be done before expansion of the full declaration, because the
942 -- declaration may include an expression that is an allocator, whose
943 -- expansion needs the proper Master for the created tasks.
946 and then Nkind
(Related_Nod
) = N_Object_Declaration
948 if Is_Limited_Record
(Desig_Type
)
949 and then Is_Class_Wide_Type
(Desig_Type
)
951 Build_Class_Wide_Master
(Anon_Type
);
953 -- Similarly, if the type is an anonymous access that designates
954 -- tasks, create a master entity for it in the current context.
956 elsif Has_Task
(Desig_Type
)
957 and then Comes_From_Source
(Related_Nod
)
959 Build_Master_Entity
(Defining_Identifier
(Related_Nod
));
960 Build_Master_Renaming
(Anon_Type
);
964 -- For a private component of a protected type, it is imperative that
965 -- the back-end elaborate the type immediately after the protected
966 -- declaration, because this type will be used in the declarations
967 -- created for the component within each protected body, so we must
968 -- create an itype reference for it now.
970 if Nkind
(Parent
(Related_Nod
)) = N_Protected_Definition
then
971 Build_Itype_Reference
(Anon_Type
, Parent
(Parent
(Related_Nod
)));
973 -- Similarly, if the access definition is the return result of a
974 -- function, create an itype reference for it because it will be used
975 -- within the function body. For a regular function that is not a
976 -- compilation unit, insert reference after the declaration. For a
977 -- protected operation, insert it after the enclosing protected type
978 -- declaration. In either case, do not create a reference for a type
979 -- obtained through a limited_with clause, because this would introduce
980 -- semantic dependencies.
982 -- Similarly, do not create a reference if the designated type is a
983 -- generic formal, because no use of it will reach the backend.
985 elsif Nkind
(Related_Nod
) = N_Function_Specification
986 and then not From_Limited_With
(Desig_Type
)
987 and then not Is_Generic_Type
(Desig_Type
)
989 if Present
(Enclosing_Prot_Type
) then
990 Build_Itype_Reference
(Anon_Type
, Parent
(Enclosing_Prot_Type
));
992 elsif Is_List_Member
(Parent
(Related_Nod
))
993 and then Nkind
(Parent
(N
)) /= N_Parameter_Specification
995 Build_Itype_Reference
(Anon_Type
, Parent
(Related_Nod
));
998 -- Finally, create an itype reference for an object declaration of an
999 -- anonymous access type. This is strictly necessary only for deferred
1000 -- constants, but in any case will avoid out-of-scope problems in the
1003 elsif Nkind
(Related_Nod
) = N_Object_Declaration
then
1004 Build_Itype_Reference
(Anon_Type
, Related_Nod
);
1008 end Access_Definition
;
1010 -----------------------------------
1011 -- Access_Subprogram_Declaration --
1012 -----------------------------------
1014 procedure Access_Subprogram_Declaration
1015 (T_Name
: Entity_Id
;
1018 procedure Check_For_Premature_Usage
(Def
: Node_Id
);
1019 -- Check that type T_Name is not used, directly or recursively, as a
1020 -- parameter or a return type in Def. Def is either a subtype, an
1021 -- access_definition, or an access_to_subprogram_definition.
1023 -------------------------------
1024 -- Check_For_Premature_Usage --
1025 -------------------------------
1027 procedure Check_For_Premature_Usage
(Def
: Node_Id
) is
1031 -- Check for a subtype mark
1033 if Nkind
(Def
) in N_Has_Etype
then
1034 if Etype
(Def
) = T_Name
then
1036 ("type& cannot be used before the end of its declaration",
1040 -- If this is not a subtype, then this is an access_definition
1042 elsif Nkind
(Def
) = N_Access_Definition
then
1043 if Present
(Access_To_Subprogram_Definition
(Def
)) then
1044 Check_For_Premature_Usage
1045 (Access_To_Subprogram_Definition
(Def
));
1047 Check_For_Premature_Usage
(Subtype_Mark
(Def
));
1050 -- The only cases left are N_Access_Function_Definition and
1051 -- N_Access_Procedure_Definition.
1054 if Present
(Parameter_Specifications
(Def
)) then
1055 Param
:= First
(Parameter_Specifications
(Def
));
1056 while Present
(Param
) loop
1057 Check_For_Premature_Usage
(Parameter_Type
(Param
));
1062 if Nkind
(Def
) = N_Access_Function_Definition
then
1063 Check_For_Premature_Usage
(Result_Definition
(Def
));
1066 end Check_For_Premature_Usage
;
1070 Formals
: constant List_Id
:= Parameter_Specifications
(T_Def
);
1073 Desig_Type
: constant Entity_Id
:=
1074 Create_Itype
(E_Subprogram_Type
, Parent
(T_Def
));
1076 -- Start of processing for Access_Subprogram_Declaration
1079 -- Associate the Itype node with the inner full-type declaration or
1080 -- subprogram spec or entry body. This is required to handle nested
1081 -- anonymous declarations. For example:
1084 -- (X : access procedure
1085 -- (Y : access procedure
1088 D_Ityp
:= Associated_Node_For_Itype
(Desig_Type
);
1089 while Nkind
(D_Ityp
) not in N_Full_Type_Declaration
1090 | N_Private_Type_Declaration
1091 | N_Private_Extension_Declaration
1092 | N_Procedure_Specification
1093 | N_Function_Specification
1095 | N_Object_Declaration
1096 | N_Object_Renaming_Declaration
1097 | N_Formal_Object_Declaration
1098 | N_Formal_Type_Declaration
1099 | N_Task_Type_Declaration
1100 | N_Protected_Type_Declaration
1102 D_Ityp
:= Parent
(D_Ityp
);
1103 pragma Assert
(D_Ityp
/= Empty
);
1106 Set_Associated_Node_For_Itype
(Desig_Type
, D_Ityp
);
1108 if Nkind
(D_Ityp
) in N_Procedure_Specification | N_Function_Specification
1110 Set_Scope
(Desig_Type
, Scope
(Defining_Entity
(D_Ityp
)));
1112 elsif Nkind
(D_Ityp
) in N_Full_Type_Declaration
1113 | N_Object_Declaration
1114 | N_Object_Renaming_Declaration
1115 | N_Formal_Type_Declaration
1117 Set_Scope
(Desig_Type
, Scope
(Defining_Identifier
(D_Ityp
)));
1120 if Nkind
(T_Def
) = N_Access_Function_Definition
then
1121 if Nkind
(Result_Definition
(T_Def
)) = N_Access_Definition
then
1123 Acc
: constant Node_Id
:= Result_Definition
(T_Def
);
1126 if Present
(Access_To_Subprogram_Definition
(Acc
))
1128 Protected_Present
(Access_To_Subprogram_Definition
(Acc
))
1132 Replace_Anonymous_Access_To_Protected_Subprogram
1138 Access_Definition
(T_Def
, Result_Definition
(T_Def
)));
1143 Analyze
(Result_Definition
(T_Def
));
1146 Typ
: constant Entity_Id
:= Entity
(Result_Definition
(T_Def
));
1149 -- If a null exclusion is imposed on the result type, then
1150 -- create a null-excluding itype (an access subtype) and use
1151 -- it as the function's Etype.
1153 if Is_Access_Type
(Typ
)
1154 and then Null_Exclusion_In_Return_Present
(T_Def
)
1156 Set_Etype
(Desig_Type
,
1157 Create_Null_Excluding_Itype
1159 Related_Nod
=> T_Def
,
1160 Scope_Id
=> Current_Scope
));
1163 if From_Limited_With
(Typ
) then
1165 -- AI05-151: Incomplete types are allowed in all basic
1166 -- declarations, including access to subprograms.
1168 if Ada_Version
>= Ada_2012
then
1173 ("illegal use of incomplete type&",
1174 Result_Definition
(T_Def
), Typ
);
1177 elsif Ekind
(Current_Scope
) = E_Package
1178 and then In_Private_Part
(Current_Scope
)
1180 if Ekind
(Typ
) = E_Incomplete_Type
then
1181 Append_Elmt
(Desig_Type
, Private_Dependents
(Typ
));
1183 elsif Is_Class_Wide_Type
(Typ
)
1184 and then Ekind
(Etype
(Typ
)) = E_Incomplete_Type
1187 (Desig_Type
, Private_Dependents
(Etype
(Typ
)));
1191 Set_Etype
(Desig_Type
, Typ
);
1196 if not Is_Type
(Etype
(Desig_Type
)) then
1198 ("expect type in function specification",
1199 Result_Definition
(T_Def
));
1203 Set_Etype
(Desig_Type
, Standard_Void_Type
);
1206 if Present
(Formals
) then
1207 Push_Scope
(Desig_Type
);
1209 -- Some special tests here. These special tests can be removed
1210 -- if and when Itypes always have proper parent pointers to their
1213 -- Special test 1) Link defining_identifier of formals. Required by
1214 -- First_Formal to provide its functionality.
1220 F
:= First
(Formals
);
1222 while Present
(F
) loop
1223 if No
(Parent
(Defining_Identifier
(F
))) then
1224 Set_Parent
(Defining_Identifier
(F
), F
);
1231 Process_Formals
(Formals
, Parent
(T_Def
));
1233 -- Special test 2) End_Scope requires that the parent pointer be set
1234 -- to something reasonable, but Itypes don't have parent pointers. So
1235 -- we set it and then unset it ???
1237 Set_Parent
(Desig_Type
, T_Name
);
1239 Set_Parent
(Desig_Type
, Empty
);
1242 -- Check for premature usage of the type being defined
1244 Check_For_Premature_Usage
(T_Def
);
1246 -- The return type and/or any parameter type may be incomplete. Mark the
1247 -- subprogram_type as depending on the incomplete type, so that it can
1248 -- be updated when the full type declaration is seen. This only applies
1249 -- to incomplete types declared in some enclosing scope, not to limited
1250 -- views from other packages.
1252 -- Prior to Ada 2012, access to functions can only have in_parameters.
1254 if Present
(Formals
) then
1255 Formal
:= First_Formal
(Desig_Type
);
1256 while Present
(Formal
) loop
1257 if Ekind
(Formal
) /= E_In_Parameter
1258 and then Nkind
(T_Def
) = N_Access_Function_Definition
1259 and then Ada_Version
< Ada_2012
1261 Error_Msg_N
("functions can only have IN parameters", Formal
);
1264 if Ekind
(Etype
(Formal
)) = E_Incomplete_Type
1265 and then In_Open_Scopes
(Scope
(Etype
(Formal
)))
1267 Append_Elmt
(Desig_Type
, Private_Dependents
(Etype
(Formal
)));
1268 Set_Has_Delayed_Freeze
(Desig_Type
);
1271 Next_Formal
(Formal
);
1275 -- Check whether an indirect call without actuals may be possible. This
1276 -- is used when resolving calls whose result is then indexed.
1278 May_Need_Actuals
(Desig_Type
);
1280 -- If the return type is incomplete, this is legal as long as the type
1281 -- is declared in the current scope and will be completed in it (rather
1282 -- than being part of limited view).
1284 if Ekind
(Etype
(Desig_Type
)) = E_Incomplete_Type
1285 and then not Has_Delayed_Freeze
(Desig_Type
)
1286 and then In_Open_Scopes
(Scope
(Etype
(Desig_Type
)))
1288 Append_Elmt
(Desig_Type
, Private_Dependents
(Etype
(Desig_Type
)));
1289 Set_Has_Delayed_Freeze
(Desig_Type
);
1292 Check_Delayed_Subprogram
(Desig_Type
);
1294 if Protected_Present
(T_Def
) then
1295 Mutate_Ekind
(T_Name
, E_Access_Protected_Subprogram_Type
);
1296 Set_Convention
(Desig_Type
, Convention_Protected
);
1298 Mutate_Ekind
(T_Name
, E_Access_Subprogram_Type
);
1301 Set_Can_Use_Internal_Rep
(T_Name
,
1302 not Always_Compatible_Rep_On_Target
);
1303 Set_Etype
(T_Name
, T_Name
);
1304 Reinit_Size_Align
(T_Name
);
1305 Set_Directly_Designated_Type
(T_Name
, Desig_Type
);
1307 -- If the access_to_subprogram is not declared at the library level,
1308 -- it can only point to subprograms that are at the same or deeper
1309 -- accessibility level. The corresponding subprogram type might
1310 -- require an activation record when compiling for C.
1312 Set_Needs_Activation_Record
(Desig_Type
,
1313 not Is_Library_Level_Entity
(T_Name
));
1315 Generate_Reference_To_Formals
(T_Name
);
1317 -- Ada 2005 (AI-231): Propagate the null-excluding attribute
1319 Set_Can_Never_Be_Null
(T_Name
, Null_Exclusion_Present
(T_Def
));
1321 Check_Restriction
(No_Access_Subprograms
, T_Def
);
1323 -- Addition of extra formals must be delayed till the freeze point so
1324 -- that we know the convention.
1325 end Access_Subprogram_Declaration
;
1327 ----------------------------
1328 -- Access_Type_Declaration --
1329 ----------------------------
1331 procedure Access_Type_Declaration
(T
: Entity_Id
; Def
: Node_Id
) is
1333 procedure Setup_Access_Type
(Desig_Typ
: Entity_Id
);
1334 -- After type declaration is analysed with T being an incomplete type,
1335 -- this routine will mutate the kind of T to the appropriate access type
1336 -- and set its directly designated type to Desig_Typ.
1338 -----------------------
1339 -- Setup_Access_Type --
1340 -----------------------
1342 procedure Setup_Access_Type
(Desig_Typ
: Entity_Id
) is
1344 if All_Present
(Def
) or else Constant_Present
(Def
) then
1345 Mutate_Ekind
(T
, E_General_Access_Type
);
1347 Mutate_Ekind
(T
, E_Access_Type
);
1350 Set_Directly_Designated_Type
(T
, Desig_Typ
);
1351 end Setup_Access_Type
;
1355 P
: constant Node_Id
:= Parent
(Def
);
1356 S
: constant Node_Id
:= Subtype_Indication
(Def
);
1358 Full_Desig
: Entity_Id
;
1360 -- Start of processing for Access_Type_Declaration
1363 -- Check for permissible use of incomplete type
1365 if Nkind
(S
) /= N_Subtype_Indication
then
1369 if Nkind
(S
) in N_Has_Entity
1370 and then Present
(Entity
(S
))
1371 and then Ekind
(Root_Type
(Entity
(S
))) = E_Incomplete_Type
1373 Setup_Access_Type
(Desig_Typ
=> Entity
(S
));
1375 -- If the designated type is a limited view, we cannot tell if
1376 -- the full view contains tasks, and there is no way to handle
1377 -- that full view in a client. We create a master entity for the
1378 -- scope, which will be used when a client determines that one
1381 if From_Limited_With
(Entity
(S
))
1382 and then not Is_Class_Wide_Type
(Entity
(S
))
1384 Build_Master_Entity
(T
);
1385 Build_Master_Renaming
(T
);
1389 Setup_Access_Type
(Desig_Typ
=> Process_Subtype
(S
, P
, T
, 'P'));
1392 -- If the access definition is of the form: ACCESS NOT NULL ..
1393 -- the subtype indication must be of an access type. Create
1394 -- a null-excluding subtype of it.
1396 if Null_Excluding_Subtype
(Def
) then
1397 if not Is_Access_Type
(Entity
(S
)) then
1398 Error_Msg_N
("null exclusion must apply to access type", Def
);
1402 Loc
: constant Source_Ptr
:= Sloc
(S
);
1404 Nam
: constant Entity_Id
:= Make_Temporary
(Loc
, 'S');
1408 Make_Subtype_Declaration
(Loc
,
1409 Defining_Identifier
=> Nam
,
1410 Subtype_Indication
=>
1411 New_Occurrence_Of
(Entity
(S
), Loc
));
1412 Set_Null_Exclusion_Present
(Decl
);
1413 Insert_Before
(Parent
(Def
), Decl
);
1415 Set_Entity
(S
, Nam
);
1421 Setup_Access_Type
(Desig_Typ
=> Process_Subtype
(S
, P
, T
, 'P'));
1424 if not Error_Posted
(T
) then
1425 Full_Desig
:= Designated_Type
(T
);
1427 if Base_Type
(Full_Desig
) = T
then
1428 Error_Msg_N
("access type cannot designate itself", S
);
1430 -- In Ada 2005, the type may have a limited view through some unit in
1431 -- its own context, allowing the following circularity that cannot be
1432 -- detected earlier.
1434 elsif Is_Class_Wide_Type
(Full_Desig
) and then Etype
(Full_Desig
) = T
1437 ("access type cannot designate its own class-wide type", S
);
1439 -- Clean up indication of tagged status to prevent cascaded errors
1441 Set_Is_Tagged_Type
(T
, False);
1446 -- For SPARK, check that the designated type is compatible with
1447 -- respect to volatility with the access type.
1449 if SPARK_Mode
/= Off
1450 and then Comes_From_Source
(T
)
1452 -- ??? UNIMPLEMENTED
1453 -- In the case where the designated type is incomplete at this
1454 -- point, performing this check here is harmless but the check
1455 -- will need to be repeated when the designated type is complete.
1457 -- The preceding call to Comes_From_Source is needed because the
1458 -- FE sometimes introduces implicitly declared access types. See,
1459 -- for example, the expansion of nested_po.ads in OA28-015.
1461 Check_Volatility_Compatibility
1462 (Full_Desig
, T
, "designated type", "access type",
1463 Srcpos_Bearer
=> T
);
1467 -- If the type has appeared already in a with_type clause, it is frozen
1468 -- and the pointer size is already set. Else, initialize.
1470 if not From_Limited_With
(T
) then
1471 Reinit_Size_Align
(T
);
1474 -- Note that Has_Task is always false, since the access type itself
1475 -- is not a task type. See Einfo for more description on this point.
1476 -- Exactly the same consideration applies to Has_Controlled_Component
1477 -- and to Has_Protected.
1479 Set_Has_Task
(T
, False);
1480 Set_Has_Protected
(T
, False);
1481 Set_Has_Timing_Event
(T
, False);
1482 Set_Has_Controlled_Component
(T
, False);
1484 -- Initialize field Finalization_Master explicitly to Empty, to avoid
1485 -- problems where an incomplete view of this entity has been previously
1486 -- established by a limited with and an overlaid version of this field
1487 -- (Stored_Constraint) was initialized for the incomplete view.
1489 -- This reset is performed in most cases except where the access type
1490 -- has been created for the purposes of allocating or deallocating a
1491 -- build-in-place object. Such access types have explicitly set pools
1492 -- and finalization masters.
1494 if No
(Associated_Storage_Pool
(T
)) then
1495 Set_Finalization_Master
(T
, Empty
);
1498 -- Ada 2005 (AI-231): Propagate the null-excluding and access-constant
1501 Set_Can_Never_Be_Null
(T
, Null_Exclusion_Present
(Def
));
1502 Set_Is_Access_Constant
(T
, Constant_Present
(Def
));
1503 end Access_Type_Declaration
;
1505 ----------------------------------
1506 -- Add_Interface_Tag_Components --
1507 ----------------------------------
1509 procedure Add_Interface_Tag_Components
(N
: Node_Id
; Typ
: Entity_Id
) is
1510 Loc
: constant Source_Ptr
:= Sloc
(N
);
1514 procedure Add_Tag
(Iface
: Entity_Id
);
1515 -- Add tag for one of the progenitor interfaces
1521 procedure Add_Tag
(Iface
: Entity_Id
) is
1528 pragma Assert
(Is_Tagged_Type
(Iface
) and then Is_Interface
(Iface
));
1530 -- This is a reasonable place to propagate predicates
1532 if Has_Predicates
(Iface
) then
1533 Set_Has_Predicates
(Typ
);
1537 Make_Component_Definition
(Loc
,
1538 Aliased_Present
=> True,
1539 Subtype_Indication
=>
1540 New_Occurrence_Of
(RTE
(RE_Interface_Tag
), Loc
));
1542 Tag
:= Make_Temporary
(Loc
, 'V');
1545 Make_Component_Declaration
(Loc
,
1546 Defining_Identifier
=> Tag
,
1547 Component_Definition
=> Def
);
1549 Analyze_Component_Declaration
(Decl
);
1551 Set_Analyzed
(Decl
);
1552 Mutate_Ekind
(Tag
, E_Component
);
1554 Set_Is_Aliased
(Tag
);
1555 Set_Is_Independent
(Tag
);
1556 Set_Related_Type
(Tag
, Iface
);
1557 Reinit_Component_Location
(Tag
);
1559 pragma Assert
(Is_Frozen
(Iface
));
1561 Set_DT_Entry_Count
(Tag
,
1562 DT_Entry_Count
(First_Entity
(Iface
)));
1564 if No
(Last_Tag
) then
1567 Insert_After
(Last_Tag
, Decl
);
1572 -- If the ancestor has discriminants we need to give special support
1573 -- to store the offset_to_top value of the secondary dispatch tables.
1574 -- For this purpose we add a supplementary component just after the
1575 -- field that contains the tag associated with each secondary DT.
1577 if Typ
/= Etype
(Typ
) and then Has_Discriminants
(Etype
(Typ
)) then
1579 Make_Component_Definition
(Loc
,
1580 Subtype_Indication
=>
1581 New_Occurrence_Of
(RTE
(RE_Storage_Offset
), Loc
));
1583 Offset
:= Make_Temporary
(Loc
, 'V');
1586 Make_Component_Declaration
(Loc
,
1587 Defining_Identifier
=> Offset
,
1588 Component_Definition
=> Def
);
1590 Analyze_Component_Declaration
(Decl
);
1592 Set_Analyzed
(Decl
);
1593 Mutate_Ekind
(Offset
, E_Component
);
1594 Set_Is_Aliased
(Offset
);
1595 Set_Is_Independent
(Offset
);
1596 Set_Related_Type
(Offset
, Iface
);
1597 Reinit_Component_Location
(Offset
);
1598 Insert_After
(Last_Tag
, Decl
);
1609 -- Start of processing for Add_Interface_Tag_Components
1612 if not RTE_Available
(RE_Interface_Tag
) then
1614 ("(Ada 2005) interface types not supported by this run-time!", N
);
1618 if Ekind
(Typ
) /= E_Record_Type
1619 or else (Is_Concurrent_Record_Type
(Typ
)
1620 and then Is_Empty_List
(Abstract_Interface_List
(Typ
)))
1621 or else (not Is_Concurrent_Record_Type
(Typ
)
1622 and then No
(Interfaces
(Typ
))
1623 and then Is_Empty_Elmt_List
(Interfaces
(Typ
)))
1628 -- Find the current last tag
1630 if Nkind
(Type_Definition
(N
)) = N_Derived_Type_Definition
then
1631 Ext
:= Record_Extension_Part
(Type_Definition
(N
));
1633 pragma Assert
(Nkind
(Type_Definition
(N
)) = N_Record_Definition
);
1634 Ext
:= Type_Definition
(N
);
1639 if not (Present
(Component_List
(Ext
))) then
1640 Set_Null_Present
(Ext
, False);
1642 Set_Component_List
(Ext
,
1643 Make_Component_List
(Loc
,
1644 Component_Items
=> L
,
1645 Null_Present
=> False));
1647 if Nkind
(Type_Definition
(N
)) = N_Derived_Type_Definition
then
1648 L
:= Component_Items
1650 (Record_Extension_Part
1651 (Type_Definition
(N
))));
1653 L
:= Component_Items
1655 (Type_Definition
(N
)));
1658 -- Find the last tag component
1661 while Present
(Comp
) loop
1662 if Nkind
(Comp
) = N_Component_Declaration
1663 and then Is_Tag
(Defining_Identifier
(Comp
))
1672 -- At this point L references the list of components and Last_Tag
1673 -- references the current last tag (if any). Now we add the tag
1674 -- corresponding with all the interfaces that are not implemented
1677 if Present
(Interfaces
(Typ
)) then
1678 Elmt
:= First_Elmt
(Interfaces
(Typ
));
1679 while Present
(Elmt
) loop
1680 Add_Tag
(Node
(Elmt
));
1684 end Add_Interface_Tag_Components
;
1686 -------------------------------------
1687 -- Add_Internal_Interface_Entities --
1688 -------------------------------------
1690 procedure Add_Internal_Interface_Entities
(Tagged_Type
: Entity_Id
) is
1693 Iface_Elmt
: Elmt_Id
;
1694 Iface_Prim
: Entity_Id
;
1695 Ifaces_List
: Elist_Id
;
1696 New_Subp
: Entity_Id
:= Empty
;
1698 Restore_Scope
: Boolean := False;
1701 pragma Assert
(Ada_Version
>= Ada_2005
1702 and then Is_Record_Type
(Tagged_Type
)
1703 and then Is_Tagged_Type
(Tagged_Type
)
1704 and then Has_Interfaces
(Tagged_Type
)
1705 and then not Is_Interface
(Tagged_Type
));
1707 -- Ensure that the internal entities are added to the scope of the type
1709 if Scope
(Tagged_Type
) /= Current_Scope
then
1710 Push_Scope
(Scope
(Tagged_Type
));
1711 Restore_Scope
:= True;
1714 Collect_Interfaces
(Tagged_Type
, Ifaces_List
);
1716 Iface_Elmt
:= First_Elmt
(Ifaces_List
);
1717 while Present
(Iface_Elmt
) loop
1718 Iface
:= Node
(Iface_Elmt
);
1720 -- Originally we excluded here from this processing interfaces that
1721 -- are parents of Tagged_Type because their primitives are located
1722 -- in the primary dispatch table (and hence no auxiliary internal
1723 -- entities are required to handle secondary dispatch tables in such
1724 -- case). However, these auxiliary entities are also required to
1725 -- handle derivations of interfaces in formals of generics (see
1726 -- Derive_Subprograms).
1728 Elmt
:= First_Elmt
(Primitive_Operations
(Iface
));
1729 while Present
(Elmt
) loop
1730 Iface_Prim
:= Node
(Elmt
);
1732 if not Is_Predefined_Dispatching_Operation
(Iface_Prim
) then
1734 Find_Primitive_Covering_Interface
1735 (Tagged_Type
=> Tagged_Type
,
1736 Iface_Prim
=> Iface_Prim
);
1738 if No
(Prim
) and then Serious_Errors_Detected
> 0 then
1742 pragma Assert
(Present
(Prim
));
1744 -- Ada 2012 (AI05-0197): If the name of the covering primitive
1745 -- differs from the name of the interface primitive then it is
1746 -- a private primitive inherited from a parent type. In such
1747 -- case, given that Tagged_Type covers the interface, the
1748 -- inherited private primitive becomes visible. For such
1749 -- purpose we add a new entity that renames the inherited
1750 -- private primitive.
1752 if Chars
(Prim
) /= Chars
(Iface_Prim
) then
1753 pragma Assert
(Has_Suffix
(Prim
, 'P'));
1755 (New_Subp
=> New_Subp
,
1756 Parent_Subp
=> Iface_Prim
,
1757 Derived_Type
=> Tagged_Type
,
1758 Parent_Type
=> Iface
);
1759 Set_Alias
(New_Subp
, Prim
);
1760 Set_Is_Abstract_Subprogram
1761 (New_Subp
, Is_Abstract_Subprogram
(Prim
));
1765 (New_Subp
=> New_Subp
,
1766 Parent_Subp
=> Iface_Prim
,
1767 Derived_Type
=> Tagged_Type
,
1768 Parent_Type
=> Iface
);
1773 if Is_Inherited_Operation
(Prim
)
1774 and then Present
(Alias
(Prim
))
1776 Anc
:= Alias
(Prim
);
1778 Anc
:= Overridden_Operation
(Prim
);
1781 -- Apply legality checks in RM 6.1.1 (10-13) concerning
1782 -- nonconforming preconditions in both an ancestor and
1783 -- a progenitor operation.
1785 -- If the operation is a primitive wrapper it is an explicit
1786 -- (overriding) operqtion and all is fine.
1789 and then Has_Non_Trivial_Precondition
(Anc
)
1790 and then Has_Non_Trivial_Precondition
(Iface_Prim
)
1792 if Is_Abstract_Subprogram
(Prim
)
1794 (Ekind
(Prim
) = E_Procedure
1795 and then Nkind
(Parent
(Prim
)) =
1796 N_Procedure_Specification
1797 and then Null_Present
(Parent
(Prim
)))
1798 or else Is_Primitive_Wrapper
(Prim
)
1802 -- The operation is inherited and must be overridden
1804 elsif not Comes_From_Source
(Prim
) then
1806 ("&inherits non-conforming preconditions and must "
1807 & "be overridden (RM 6.1.1 (10-16))",
1808 Parent
(Tagged_Type
), Prim
);
1813 -- Ada 2005 (AI-251): Decorate internal entity Iface_Subp
1814 -- associated with interface types. These entities are
1815 -- only registered in the list of primitives of its
1816 -- corresponding tagged type because they are only used
1817 -- to fill the contents of the secondary dispatch tables.
1818 -- Therefore they are removed from the homonym chains.
1820 Set_Is_Hidden
(New_Subp
);
1821 Set_Is_Internal
(New_Subp
);
1822 Set_Alias
(New_Subp
, Prim
);
1823 Set_Is_Abstract_Subprogram
1824 (New_Subp
, Is_Abstract_Subprogram
(Prim
));
1825 Set_Interface_Alias
(New_Subp
, Iface_Prim
);
1827 -- If the returned type is an interface then propagate it to
1828 -- the returned type. Needed by the thunk to generate the code
1829 -- which displaces "this" to reference the corresponding
1830 -- secondary dispatch table in the returned object.
1832 if Is_Interface
(Etype
(Iface_Prim
)) then
1833 Set_Etype
(New_Subp
, Etype
(Iface_Prim
));
1836 -- Internal entities associated with interface types are only
1837 -- registered in the list of primitives of the tagged type.
1838 -- They are only used to fill the contents of the secondary
1839 -- dispatch tables. Therefore they are not needed in the
1842 Remove_Homonym
(New_Subp
);
1844 -- Hidden entities associated with interfaces must have set
1845 -- the Has_Delay_Freeze attribute to ensure that, in case
1846 -- of locally defined tagged types (or compiling with static
1847 -- dispatch tables generation disabled) the corresponding
1848 -- entry of the secondary dispatch table is filled when such
1849 -- an entity is frozen.
1851 Set_Has_Delayed_Freeze
(New_Subp
);
1858 Next_Elmt
(Iface_Elmt
);
1861 if Restore_Scope
then
1864 end Add_Internal_Interface_Entities
;
1866 -----------------------------------
1867 -- Analyze_Component_Declaration --
1868 -----------------------------------
1870 procedure Analyze_Component_Declaration
(N
: Node_Id
) is
1871 Loc
: constant Source_Ptr
:= Sloc
(Component_Definition
(N
));
1872 Id
: constant Entity_Id
:= Defining_Identifier
(N
);
1873 E
: constant Node_Id
:= Expression
(N
);
1874 Typ
: constant Node_Id
:=
1875 Subtype_Indication
(Component_Definition
(N
));
1879 function Contains_POC
(Constr
: Node_Id
) return Boolean;
1880 -- Determines whether a constraint uses the discriminant of a record
1881 -- type thus becoming a per-object constraint (POC).
1883 function Is_Known_Limited
(Typ
: Entity_Id
) return Boolean;
1884 -- Typ is the type of the current component, check whether this type is
1885 -- a limited type. Used to validate declaration against that of
1886 -- enclosing record.
1892 function Contains_POC
(Constr
: Node_Id
) return Boolean is
1894 -- Prevent cascaded errors
1896 if Error_Posted
(Constr
) then
1900 case Nkind
(Constr
) is
1901 when N_Attribute_Reference
=>
1902 return Attribute_Name
(Constr
) = Name_Access
1903 and then Prefix
(Constr
) = Scope
(Entity
(Prefix
(Constr
)));
1905 when N_Discriminant_Association
=>
1906 return Denotes_Discriminant
(Expression
(Constr
));
1908 when N_Identifier
=>
1909 return Denotes_Discriminant
(Constr
);
1911 when N_Index_Or_Discriminant_Constraint
=>
1916 IDC
:= First
(Constraints
(Constr
));
1917 while Present
(IDC
) loop
1919 -- One per-object constraint is sufficient
1921 if Contains_POC
(IDC
) then
1932 return Denotes_Discriminant
(Low_Bound
(Constr
))
1934 Denotes_Discriminant
(High_Bound
(Constr
));
1936 when N_Range_Constraint
=>
1937 return Denotes_Discriminant
(Range_Expression
(Constr
));
1944 ----------------------
1945 -- Is_Known_Limited --
1946 ----------------------
1948 function Is_Known_Limited
(Typ
: Entity_Id
) return Boolean is
1949 P
: constant Entity_Id
:= Etype
(Typ
);
1950 R
: constant Entity_Id
:= Root_Type
(Typ
);
1953 if Is_Limited_Record
(Typ
) then
1956 -- If the root type is limited (and not a limited interface) so is
1957 -- the current type.
1959 elsif Is_Limited_Record
(R
)
1960 and then (not Is_Interface
(R
) or else not Is_Limited_Interface
(R
))
1964 -- Else the type may have a limited interface progenitor, but a
1965 -- limited record parent that is not an interface.
1968 and then Is_Limited_Record
(P
)
1969 and then not Is_Interface
(P
)
1976 end Is_Known_Limited
;
1978 -- Start of processing for Analyze_Component_Declaration
1981 Generate_Definition
(Id
);
1984 if Present
(Typ
) then
1985 T
:= Find_Type_Of_Object
1986 (Subtype_Indication
(Component_Definition
(N
)), N
);
1988 -- Ada 2005 (AI-230): Access Definition case
1991 pragma Assert
(Present
1992 (Access_Definition
(Component_Definition
(N
))));
1994 T
:= Access_Definition
1996 N
=> Access_Definition
(Component_Definition
(N
)));
1997 Set_Is_Local_Anonymous_Access
(T
);
1999 -- Ada 2005 (AI-254)
2001 if Present
(Access_To_Subprogram_Definition
2002 (Access_Definition
(Component_Definition
(N
))))
2003 and then Protected_Present
(Access_To_Subprogram_Definition
2005 (Component_Definition
(N
))))
2007 T
:= Replace_Anonymous_Access_To_Protected_Subprogram
(N
);
2011 -- If the subtype is a constrained subtype of the enclosing record,
2012 -- (which must have a partial view) the back-end does not properly
2013 -- handle the recursion. Rewrite the component declaration with an
2014 -- explicit subtype indication, which is acceptable to Gigi. We can copy
2015 -- the tree directly because side effects have already been removed from
2016 -- discriminant constraints.
2018 if Ekind
(T
) = E_Access_Subtype
2019 and then Is_Entity_Name
(Subtype_Indication
(Component_Definition
(N
)))
2020 and then Comes_From_Source
(T
)
2021 and then Nkind
(Parent
(T
)) = N_Subtype_Declaration
2022 and then Etype
(Directly_Designated_Type
(T
)) = Current_Scope
2025 (Subtype_Indication
(Component_Definition
(N
)),
2026 New_Copy_Tree
(Subtype_Indication
(Parent
(T
))));
2027 T
:= Find_Type_Of_Object
2028 (Subtype_Indication
(Component_Definition
(N
)), N
);
2031 -- If the component declaration includes a default expression, then we
2032 -- check that the component is not of a limited type (RM 3.7(5)),
2033 -- and do the special preanalysis of the expression (see section on
2034 -- "Handling of Default and Per-Object Expressions" in the spec of
2038 Preanalyze_Default_Expression
(E
, T
);
2039 Check_Initialization
(T
, E
);
2041 if Ada_Version
>= Ada_2005
2042 and then Ekind
(T
) = E_Anonymous_Access_Type
2043 and then Etype
(E
) /= Any_Type
2045 -- Check RM 3.9.2(9): "if the expected type for an expression is
2046 -- an anonymous access-to-specific tagged type, then the object
2047 -- designated by the expression shall not be dynamically tagged
2048 -- unless it is a controlling operand in a call on a dispatching
2051 if Is_Tagged_Type
(Directly_Designated_Type
(T
))
2053 Ekind
(Directly_Designated_Type
(T
)) /= E_Class_Wide_Type
2055 Ekind
(Directly_Designated_Type
(Etype
(E
))) =
2059 ("access to specific tagged type required (RM 3.9.2(9))", E
);
2062 -- (Ada 2005: AI-230): Accessibility check for anonymous
2065 if Type_Access_Level
(Etype
(E
)) >
2066 Deepest_Type_Access_Level
(T
)
2069 ("expression has deeper access level than component " &
2070 "(RM 3.10.2 (12.2))", E
);
2073 -- The initialization expression is a reference to an access
2074 -- discriminant. The type of the discriminant is always deeper
2075 -- than any access type.
2077 if Ekind
(Etype
(E
)) = E_Anonymous_Access_Type
2078 and then Is_Entity_Name
(E
)
2079 and then Ekind
(Entity
(E
)) = E_In_Parameter
2080 and then Present
(Discriminal_Link
(Entity
(E
)))
2083 ("discriminant has deeper accessibility level than target",
2089 -- The parent type may be a private view with unknown discriminants,
2090 -- and thus unconstrained. Regular components must be constrained.
2092 if not Is_Definite_Subtype
(T
)
2093 and then Chars
(Id
) /= Name_uParent
2095 if Is_Class_Wide_Type
(T
) then
2097 ("class-wide subtype with unknown discriminants" &
2098 " in component declaration",
2099 Subtype_Indication
(Component_Definition
(N
)));
2102 ("unconstrained subtype in component declaration",
2103 Subtype_Indication
(Component_Definition
(N
)));
2106 -- Components cannot be abstract, except for the special case of
2107 -- the _Parent field (case of extending an abstract tagged type)
2109 elsif Is_Abstract_Type
(T
) and then Chars
(Id
) /= Name_uParent
then
2110 Error_Msg_N
("type of a component cannot be abstract", N
);
2115 if Aliased_Present
(Component_Definition
(N
)) then
2116 Set_Is_Aliased
(Id
);
2118 -- AI12-001: All aliased objects are considered to be specified as
2119 -- independently addressable (RM C.6(8.1/4)).
2121 Set_Is_Independent
(Id
);
2124 -- The component declaration may have a per-object constraint, set
2125 -- the appropriate flag in the defining identifier of the subtype.
2127 if Present
(Subtype_Indication
(Component_Definition
(N
))) then
2129 Sindic
: constant Node_Id
:=
2130 Subtype_Indication
(Component_Definition
(N
));
2132 if Nkind
(Sindic
) = N_Subtype_Indication
2133 and then Present
(Constraint
(Sindic
))
2134 and then Contains_POC
(Constraint
(Sindic
))
2136 Set_Has_Per_Object_Constraint
(Id
);
2141 -- Ada 2005 (AI-231): Propagate the null-excluding attribute and carry
2142 -- out some static checks.
2144 if Ada_Version
>= Ada_2005
and then Can_Never_Be_Null
(T
) then
2145 Null_Exclusion_Static_Checks
(N
);
2148 -- If this component is private (or depends on a private type), flag the
2149 -- record type to indicate that some operations are not available.
2151 P
:= Private_Component
(T
);
2155 -- Check for circular definitions
2157 if P
= Any_Type
then
2158 Set_Etype
(Id
, Any_Type
);
2160 -- There is a gap in the visibility of operations only if the
2161 -- component type is not defined in the scope of the record type.
2163 elsif Scope
(P
) = Scope
(Current_Scope
) then
2166 elsif Is_Limited_Type
(P
) then
2167 Set_Is_Limited_Composite
(Current_Scope
);
2170 Set_Is_Private_Composite
(Current_Scope
);
2175 and then Is_Limited_Type
(T
)
2176 and then Chars
(Id
) /= Name_uParent
2177 and then Is_Tagged_Type
(Current_Scope
)
2179 if Is_Derived_Type
(Current_Scope
)
2180 and then not Is_Known_Limited
(Current_Scope
)
2183 ("extension of nonlimited type cannot have limited components",
2186 if Is_Interface
(Root_Type
(Current_Scope
)) then
2188 ("\limitedness is not inherited from limited interface", N
);
2189 Error_Msg_N
("\add LIMITED to type indication", N
);
2192 Explain_Limited_Type
(T
, N
);
2193 Set_Etype
(Id
, Any_Type
);
2194 Set_Is_Limited_Composite
(Current_Scope
, False);
2196 elsif not Is_Derived_Type
(Current_Scope
)
2197 and then not Is_Limited_Record
(Current_Scope
)
2198 and then not Is_Concurrent_Type
(Current_Scope
)
2201 ("nonlimited tagged type cannot have limited components", N
);
2202 Explain_Limited_Type
(T
, N
);
2203 Set_Etype
(Id
, Any_Type
);
2204 Set_Is_Limited_Composite
(Current_Scope
, False);
2208 -- When possible, build the default subtype
2210 if Build_Default_Subtype_OK
(T
) then
2212 Act_T
: constant Entity_Id
:= Build_Default_Subtype
(T
, N
);
2215 Set_Etype
(Id
, Act_T
);
2217 -- Rewrite component definition to use the constrained subtype
2219 Rewrite
(Component_Definition
(N
),
2220 Make_Component_Definition
(Loc
,
2221 Subtype_Indication
=> New_Occurrence_Of
(Act_T
, Loc
)));
2225 Set_Original_Record_Component
(Id
, Id
);
2227 if Has_Aspects
(N
) then
2228 Analyze_Aspect_Specifications
(N
, Id
);
2231 Analyze_Dimension
(N
);
2232 end Analyze_Component_Declaration
;
2234 --------------------------
2235 -- Analyze_Declarations --
2236 --------------------------
2238 procedure Analyze_Declarations
(L
: List_Id
) is
2241 procedure Adjust_Decl
;
2242 -- Adjust Decl not to include implicit label declarations, since these
2243 -- have strange Sloc values that result in elaboration check problems.
2244 -- (They have the sloc of the label as found in the source, and that
2245 -- is ahead of the current declarative part).
2247 procedure Build_Assertion_Bodies
(Decls
: List_Id
; Context
: Node_Id
);
2248 -- Create the subprogram bodies which verify the run-time semantics of
2249 -- the pragmas listed below for each elibigle type found in declarative
2250 -- list Decls. The pragmas are:
2252 -- Default_Initial_Condition
2256 -- Context denotes the owner of the declarative list.
2258 procedure Check_Entry_Contracts
;
2259 -- Perform a preanalysis of the pre- and postconditions of an entry
2260 -- declaration. This must be done before full resolution and creation
2261 -- of the parameter block, etc. to catch illegal uses within the
2262 -- contract expression. Full analysis of the expression is done when
2263 -- the contract is processed.
2265 function Contains_Lib_Incomplete_Type
(Pkg
: Entity_Id
) return Boolean;
2266 -- Check if a nested package has entities within it that rely on library
2267 -- level private types where the full view has not been completed for
2268 -- the purposes of checking if it is acceptable to freeze an expression
2269 -- function at the point of declaration.
2271 procedure Handle_Late_Controlled_Primitive
(Body_Decl
: Node_Id
);
2272 -- Determine whether Body_Decl denotes the body of a late controlled
2273 -- primitive (either Initialize, Adjust or Finalize). If this is the
2274 -- case, add a proper spec if the body lacks one. The spec is inserted
2275 -- before Body_Decl and immediately analyzed.
2277 procedure Remove_Partial_Visible_Refinements
(Spec_Id
: Entity_Id
);
2278 -- Spec_Id is the entity of a package that may define abstract states,
2279 -- and in the case of a child unit, whose ancestors may define abstract
2280 -- states. If the states have partial visible refinement, remove the
2281 -- partial visibility of each constituent at the end of the package
2282 -- spec and body declarations.
2284 procedure Remove_Visible_Refinements
(Spec_Id
: Entity_Id
);
2285 -- Spec_Id is the entity of a package that may define abstract states.
2286 -- If the states have visible refinement, remove the visibility of each
2287 -- constituent at the end of the package body declaration.
2289 procedure Resolve_Aspects
;
2290 -- Utility to resolve the expressions of aspects at the end of a list of
2291 -- declarations, or before a declaration that freezes previous entities,
2292 -- such as in a subprogram body.
2298 procedure Adjust_Decl
is
2300 while Present
(Prev
(Decl
))
2301 and then Nkind
(Decl
) = N_Implicit_Label_Declaration
2307 ----------------------------
2308 -- Build_Assertion_Bodies --
2309 ----------------------------
2311 procedure Build_Assertion_Bodies
(Decls
: List_Id
; Context
: Node_Id
) is
2312 procedure Build_Assertion_Bodies_For_Type
(Typ
: Entity_Id
);
2313 -- Create the subprogram bodies which verify the run-time semantics
2314 -- of the pragmas listed below for type Typ. The pragmas are:
2316 -- Default_Initial_Condition
2320 -------------------------------------
2321 -- Build_Assertion_Bodies_For_Type --
2322 -------------------------------------
2324 procedure Build_Assertion_Bodies_For_Type
(Typ
: Entity_Id
) is
2326 if Nkind
(Context
) = N_Package_Specification
then
2328 -- Preanalyze and resolve the class-wide invariants of an
2329 -- interface at the end of whichever declarative part has the
2330 -- interface type. Note that an interface may be declared in
2331 -- any non-package declarative part, but reaching the end of
2332 -- such a declarative part will always freeze the type and
2333 -- generate the invariant procedure (see Freeze_Type).
2335 if Is_Interface
(Typ
) then
2337 -- Interfaces are treated as the partial view of a private
2338 -- type, in order to achieve uniformity with the general
2339 -- case. As a result, an interface receives only a "partial"
2340 -- invariant procedure, which is never called.
2342 if Has_Own_Invariants
(Typ
) then
2343 Build_Invariant_Procedure_Body
2345 Partial_Invariant
=> True);
2348 elsif Decls
= Visible_Declarations
(Context
) then
2349 -- Preanalyze and resolve the invariants of a private type
2350 -- at the end of the visible declarations to catch potential
2351 -- errors. Inherited class-wide invariants are not included
2352 -- because they have already been resolved.
2354 if Ekind
(Typ
) in E_Limited_Private_Type
2356 | E_Record_Type_With_Private
2357 and then Has_Own_Invariants
(Typ
)
2359 Build_Invariant_Procedure_Body
2361 Partial_Invariant
=> True);
2364 -- Preanalyze and resolve the Default_Initial_Condition
2365 -- assertion expression at the end of the declarations to
2366 -- catch any errors.
2368 if Ekind
(Typ
) in E_Limited_Private_Type
2370 | E_Record_Type_With_Private
2371 and then Has_Own_DIC
(Typ
)
2373 Build_DIC_Procedure_Body
2375 Partial_DIC
=> True);
2378 elsif Decls
= Private_Declarations
(Context
) then
2380 -- Preanalyze and resolve the invariants of a private type's
2381 -- full view at the end of the private declarations to catch
2382 -- potential errors.
2384 if (not Is_Private_Type
(Typ
)
2385 or else Present
(Underlying_Full_View
(Typ
)))
2386 and then Has_Private_Declaration
(Typ
)
2387 and then Has_Invariants
(Typ
)
2389 Build_Invariant_Procedure_Body
(Typ
);
2392 if (not Is_Private_Type
(Typ
)
2393 or else Present
(Underlying_Full_View
(Typ
)))
2394 and then Has_Private_Declaration
(Typ
)
2395 and then Has_DIC
(Typ
)
2397 Build_DIC_Procedure_Body
(Typ
);
2401 end Build_Assertion_Bodies_For_Type
;
2406 Decl_Id
: Entity_Id
;
2408 -- Start of processing for Build_Assertion_Bodies
2411 Decl
:= First
(Decls
);
2412 while Present
(Decl
) loop
2413 if Is_Declaration
(Decl
) then
2414 Decl_Id
:= Defining_Entity
(Decl
);
2416 if Is_Type
(Decl_Id
) then
2417 Build_Assertion_Bodies_For_Type
(Decl_Id
);
2423 end Build_Assertion_Bodies
;
2425 ---------------------------
2426 -- Check_Entry_Contracts --
2427 ---------------------------
2429 procedure Check_Entry_Contracts
is
2435 Ent
:= First_Entity
(Current_Scope
);
2436 while Present
(Ent
) loop
2438 -- This only concerns entries with pre/postconditions
2440 if Ekind
(Ent
) = E_Entry
2441 and then Present
(Contract
(Ent
))
2442 and then Present
(Pre_Post_Conditions
(Contract
(Ent
)))
2444 ASN
:= Pre_Post_Conditions
(Contract
(Ent
));
2446 Install_Formals
(Ent
);
2448 -- Pre/postconditions are rewritten as Check pragmas. Analysis
2449 -- is performed on a copy of the pragma expression, to prevent
2450 -- modifying the original expression.
2452 while Present
(ASN
) loop
2453 if Nkind
(ASN
) = N_Pragma
then
2457 (First
(Pragma_Argument_Associations
(ASN
))));
2458 Set_Parent
(Exp
, ASN
);
2460 Preanalyze_Assert_Expression
(Exp
, Standard_Boolean
);
2463 ASN
:= Next_Pragma
(ASN
);
2471 end Check_Entry_Contracts
;
2473 ----------------------------------
2474 -- Contains_Lib_Incomplete_Type --
2475 ----------------------------------
2477 function Contains_Lib_Incomplete_Type
(Pkg
: Entity_Id
) return Boolean is
2481 -- Avoid looking through scopes that do not meet the precondition of
2482 -- Pkg not being within a library unit spec.
2484 if not Is_Compilation_Unit
(Pkg
)
2485 and then not Is_Generic_Instance
(Pkg
)
2486 and then not In_Package_Body
(Enclosing_Lib_Unit_Entity
(Pkg
))
2488 -- Loop through all entities in the current scope to identify
2489 -- an entity that depends on a private type.
2491 Curr
:= First_Entity
(Pkg
);
2493 if Nkind
(Curr
) in N_Entity
2494 and then Depends_On_Private
(Curr
)
2499 exit when Last_Entity
(Current_Scope
) = Curr
;
2505 end Contains_Lib_Incomplete_Type
;
2507 --------------------------------------
2508 -- Handle_Late_Controlled_Primitive --
2509 --------------------------------------
2511 procedure Handle_Late_Controlled_Primitive
(Body_Decl
: Node_Id
) is
2512 Body_Spec
: constant Node_Id
:= Specification
(Body_Decl
);
2513 Body_Id
: constant Entity_Id
:= Defining_Entity
(Body_Spec
);
2514 Loc
: constant Source_Ptr
:= Sloc
(Body_Id
);
2515 Params
: constant List_Id
:=
2516 Parameter_Specifications
(Body_Spec
);
2518 Spec_Id
: Entity_Id
;
2522 -- Consider only procedure bodies whose name matches one of the three
2523 -- controlled primitives.
2525 if Nkind
(Body_Spec
) /= N_Procedure_Specification
2526 or else Chars
(Body_Id
) not in Name_Adjust
2532 -- A controlled primitive must have exactly one formal which is not
2533 -- an anonymous access type.
2535 elsif List_Length
(Params
) /= 1 then
2539 Typ
:= Parameter_Type
(First
(Params
));
2541 if Nkind
(Typ
) = N_Access_Definition
then
2547 -- The type of the formal must be derived from [Limited_]Controlled
2549 if not Is_Controlled
(Entity
(Typ
)) then
2553 -- Check whether a specification exists for this body. We do not
2554 -- analyze the spec of the body in full, because it will be analyzed
2555 -- again when the body is properly analyzed, and we cannot create
2556 -- duplicate entries in the formals chain. We look for an explicit
2557 -- specification because the body may be an overriding operation and
2558 -- an inherited spec may be present.
2560 Spec_Id
:= Current_Entity
(Body_Id
);
2562 while Present
(Spec_Id
) loop
2563 if Ekind
(Spec_Id
) in E_Procedure | E_Generic_Procedure
2564 and then Scope
(Spec_Id
) = Current_Scope
2565 and then Present
(First_Formal
(Spec_Id
))
2566 and then No
(Next_Formal
(First_Formal
(Spec_Id
)))
2567 and then Etype
(First_Formal
(Spec_Id
)) = Entity
(Typ
)
2568 and then Comes_From_Source
(Spec_Id
)
2573 Spec_Id
:= Homonym
(Spec_Id
);
2576 -- At this point the body is known to be a late controlled primitive.
2577 -- Generate a matching spec and insert it before the body. Note the
2578 -- use of Copy_Separate_Tree - we want an entirely separate semantic
2579 -- tree in this case.
2581 Spec
:= Copy_Separate_Tree
(Body_Spec
);
2583 -- Ensure that the subprogram declaration does not inherit the null
2584 -- indicator from the body as we now have a proper spec/body pair.
2586 Set_Null_Present
(Spec
, False);
2588 -- Ensure that the freeze node is inserted after the declaration of
2589 -- the primitive since its expansion will freeze the primitive.
2591 Decl
:= Make_Subprogram_Declaration
(Loc
, Specification
=> Spec
);
2593 Insert_Before_And_Analyze
(Body_Decl
, Decl
);
2594 end Handle_Late_Controlled_Primitive
;
2596 ----------------------------------------
2597 -- Remove_Partial_Visible_Refinements --
2598 ----------------------------------------
2600 procedure Remove_Partial_Visible_Refinements
(Spec_Id
: Entity_Id
) is
2601 State_Elmt
: Elmt_Id
;
2603 if Present
(Abstract_States
(Spec_Id
)) then
2604 State_Elmt
:= First_Elmt
(Abstract_States
(Spec_Id
));
2605 while Present
(State_Elmt
) loop
2606 Set_Has_Partial_Visible_Refinement
(Node
(State_Elmt
), False);
2607 Next_Elmt
(State_Elmt
);
2611 -- For a child unit, also hide the partial state refinement from
2612 -- ancestor packages.
2614 if Is_Child_Unit
(Spec_Id
) then
2615 Remove_Partial_Visible_Refinements
(Scope
(Spec_Id
));
2617 end Remove_Partial_Visible_Refinements
;
2619 --------------------------------
2620 -- Remove_Visible_Refinements --
2621 --------------------------------
2623 procedure Remove_Visible_Refinements
(Spec_Id
: Entity_Id
) is
2624 State_Elmt
: Elmt_Id
;
2626 if Present
(Abstract_States
(Spec_Id
)) then
2627 State_Elmt
:= First_Elmt
(Abstract_States
(Spec_Id
));
2628 while Present
(State_Elmt
) loop
2629 Set_Has_Visible_Refinement
(Node
(State_Elmt
), False);
2630 Next_Elmt
(State_Elmt
);
2633 end Remove_Visible_Refinements
;
2635 ---------------------
2636 -- Resolve_Aspects --
2637 ---------------------
2639 procedure Resolve_Aspects
is
2643 E
:= First_Entity
(Current_Scope
);
2644 while Present
(E
) loop
2645 Resolve_Aspect_Expressions
(E
);
2647 -- Now that the aspect expressions have been resolved, if this is
2648 -- at the end of the visible declarations, we can set the flag
2649 -- Known_To_Have_Preelab_Init properly on types declared in the
2650 -- visible part, which is needed for checking whether full types
2651 -- in the private part satisfy the Preelaborable_Initialization
2652 -- aspect of the partial view. We can't wait for the creation of
2653 -- the pragma by Analyze_Aspects_At_Freeze_Point, because the
2654 -- freeze point may occur after the end of the package declaration
2655 -- (in the case of nested packages).
2658 and then L
= Visible_Declarations
(Parent
(L
))
2659 and then Has_Aspect
(E
, Aspect_Preelaborable_Initialization
)
2662 ASN
: constant Node_Id
:=
2663 Find_Aspect
(E
, Aspect_Preelaborable_Initialization
);
2664 Expr
: constant Node_Id
:= Expression
(ASN
);
2666 -- Set Known_To_Have_Preelab_Init to True if aspect has no
2667 -- expression, or if the expression is True (or was folded
2668 -- to True), or if the expression is a conjunction of one or
2669 -- more Preelaborable_Initialization attributes applied to
2670 -- formal types and wasn't folded to False. (Note that
2671 -- Is_Conjunction_Of_Formal_Preelab_Init_Attributes goes to
2672 -- Original_Node if needed, hence test for Standard_False.)
2675 or else (Is_Entity_Name
(Expr
)
2676 and then Entity
(Expr
) = Standard_True
)
2678 (Is_Conjunction_Of_Formal_Preelab_Init_Attributes
(Expr
)
2680 not (Is_Entity_Name
(Expr
)
2681 and then Entity
(Expr
) = Standard_False
))
2683 Set_Known_To_Have_Preelab_Init
(E
);
2690 end Resolve_Aspects
;
2694 Context
: Node_Id
:= Empty
;
2695 Ctrl_Typ
: Entity_Id
:= Empty
;
2696 Freeze_From
: Entity_Id
:= Empty
;
2697 Next_Decl
: Node_Id
;
2699 -- Start of processing for Analyze_Declarations
2703 while Present
(Decl
) loop
2705 -- Complete analysis of declaration
2708 Next_Decl
:= Next
(Decl
);
2710 if No
(Freeze_From
) then
2711 Freeze_From
:= First_Entity
(Current_Scope
);
2714 -- Remember if the declaration we just processed is the full type
2715 -- declaration of a controlled type (to handle late overriding of
2716 -- initialize, adjust or finalize).
2718 if Nkind
(Decl
) = N_Full_Type_Declaration
2719 and then Is_Controlled
(Defining_Identifier
(Decl
))
2721 Ctrl_Typ
:= Defining_Identifier
(Decl
);
2724 -- At the end of a declarative part, freeze remaining entities
2725 -- declared in it. The end of the visible declarations of package
2726 -- specification is not the end of a declarative part if private
2727 -- declarations are present. The end of a package declaration is a
2728 -- freezing point only if it a library package. A task definition or
2729 -- protected type definition is not a freeze point either. Finally,
2730 -- we do not freeze entities in generic scopes, because there is no
2731 -- code generated for them and freeze nodes will be generated for
2734 -- The end of a package instantiation is not a freeze point, but
2735 -- for now we make it one, because the generic body is inserted
2736 -- (currently) immediately after. Generic instantiations will not
2737 -- be a freeze point once delayed freezing of bodies is implemented.
2738 -- (This is needed in any case for early instantiations ???).
2740 if No
(Next_Decl
) then
2741 if Nkind
(Parent
(L
)) = N_Component_List
then
2744 elsif Nkind
(Parent
(L
)) in
2745 N_Protected_Definition | N_Task_Definition
2747 Check_Entry_Contracts
;
2749 elsif Nkind
(Parent
(L
)) /= N_Package_Specification
then
2750 if Nkind
(Parent
(L
)) = N_Package_Body
then
2751 Freeze_From
:= First_Entity
(Current_Scope
);
2754 -- There may have been several freezing points previously,
2755 -- for example object declarations or subprogram bodies, but
2756 -- at the end of a declarative part we check freezing from
2757 -- the beginning, even though entities may already be frozen,
2758 -- in order to perform visibility checks on delayed aspects.
2762 -- If the current scope is a generic subprogram body. Skip the
2763 -- generic formal parameters that are not frozen here.
2765 if Is_Subprogram
(Current_Scope
)
2766 and then Nkind
(Unit_Declaration_Node
(Current_Scope
)) =
2767 N_Generic_Subprogram_Declaration
2768 and then Present
(First_Entity
(Current_Scope
))
2770 while Is_Generic_Formal
(Freeze_From
) loop
2771 Next_Entity
(Freeze_From
);
2774 Freeze_All
(Freeze_From
, Decl
);
2775 Freeze_From
:= Last_Entity
(Current_Scope
);
2778 -- For declarations in a subprogram body there is no issue
2779 -- with name resolution in aspect specifications.
2781 Freeze_All
(First_Entity
(Current_Scope
), Decl
);
2782 Freeze_From
:= Last_Entity
(Current_Scope
);
2785 -- Current scope is a package specification
2787 elsif Scope
(Current_Scope
) /= Standard_Standard
2788 and then not Is_Child_Unit
(Current_Scope
)
2789 and then No
(Generic_Parent
(Parent
(L
)))
2791 -- ARM rule 13.1.1(11/3): usage names in aspect definitions are
2792 -- resolved at the end of the immediately enclosing declaration
2793 -- list (AI05-0183-1).
2797 elsif L
/= Visible_Declarations
(Parent
(L
))
2798 or else Is_Empty_List
(Private_Declarations
(Parent
(L
)))
2802 -- End of a package declaration
2804 -- This is a freeze point because it is the end of a
2805 -- compilation unit.
2807 Freeze_All
(First_Entity
(Current_Scope
), Decl
);
2808 Freeze_From
:= Last_Entity
(Current_Scope
);
2810 -- At the end of the visible declarations the expressions in
2811 -- aspects of all entities declared so far must be resolved.
2812 -- The entities themselves might be frozen later, and the
2813 -- generated pragmas and attribute definition clauses analyzed
2814 -- in full at that point, but name resolution must take place
2816 -- In addition to being the proper semantics, this is mandatory
2817 -- within generic units, because global name capture requires
2818 -- those expressions to be analyzed, given that the generated
2819 -- pragmas do not appear in the original generic tree.
2821 elsif Serious_Errors_Detected
= 0 then
2825 -- If next node is a body then freeze all types before the body.
2826 -- An exception occurs for some expander-generated bodies. If these
2827 -- are generated at places where in general language rules would not
2828 -- allow a freeze point, then we assume that the expander has
2829 -- explicitly checked that all required types are properly frozen,
2830 -- and we do not cause general freezing here. This special circuit
2831 -- is used when the encountered body is marked as having already
2834 -- In all other cases (bodies that come from source, and expander
2835 -- generated bodies that have not been analyzed yet), freeze all
2836 -- types now. Note that in the latter case, the expander must take
2837 -- care to attach the bodies at a proper place in the tree so as to
2838 -- not cause unwanted freezing at that point.
2840 -- It is also necessary to check for a case where both an expression
2841 -- function is used and the current scope depends on an incomplete
2842 -- private type from a library unit, otherwise premature freezing of
2843 -- the private type will occur.
2845 elsif not Analyzed
(Next_Decl
) and then Is_Body
(Next_Decl
)
2846 and then ((Nkind
(Next_Decl
) /= N_Subprogram_Body
2847 or else not Was_Expression_Function
(Next_Decl
))
2848 or else (not Is_Ignored_Ghost_Entity
(Current_Scope
)
2849 and then not Contains_Lib_Incomplete_Type
2852 -- When a controlled type is frozen, the expander generates stream
2853 -- and controlled-type support routines. If the freeze is caused
2854 -- by the stand-alone body of Initialize, Adjust, or Finalize, the
2855 -- expander will end up using the wrong version of these routines,
2856 -- as the body has not been processed yet. To remedy this, detect
2857 -- a late controlled primitive and create a proper spec for it.
2858 -- This ensures that the primitive will override its inherited
2859 -- counterpart before the freeze takes place.
2861 -- If the declaration we just processed is a body, do not attempt
2862 -- to examine Next_Decl as the late primitive idiom can only apply
2863 -- to the first encountered body.
2865 -- ??? A cleaner approach may be possible and/or this solution
2866 -- could be extended to general-purpose late primitives.
2868 if Present
(Ctrl_Typ
) then
2870 -- No need to continue searching for late body overriding if
2871 -- the controlled type is already frozen.
2873 if Is_Frozen
(Ctrl_Typ
) then
2876 elsif Nkind
(Next_Decl
) = N_Subprogram_Body
then
2877 Handle_Late_Controlled_Primitive
(Next_Decl
);
2883 -- The generated body of an expression function does not freeze,
2884 -- unless it is a completion, in which case only the expression
2885 -- itself freezes. This is handled when the body itself is
2886 -- analyzed (see Freeze_Expr_Types, sem_ch6.adb).
2888 Freeze_All
(Freeze_From
, Decl
);
2889 Freeze_From
:= Last_Entity
(Current_Scope
);
2895 -- Post-freezing actions
2898 Context
:= Parent
(L
);
2900 -- Certain contract annotations have forward visibility semantics and
2901 -- must be analyzed after all declarative items have been processed.
2902 -- This timing ensures that entities referenced by such contracts are
2905 -- Analyze the contract of an immediately enclosing package spec or
2906 -- body first because other contracts may depend on its information.
2908 if Nkind
(Context
) = N_Package_Body
then
2909 Analyze_Package_Body_Contract
(Defining_Entity
(Context
));
2911 elsif Nkind
(Context
) = N_Package_Specification
then
2912 Analyze_Package_Contract
(Defining_Entity
(Context
));
2915 -- Analyze the contracts of various constructs in the declarative
2918 Analyze_Contracts
(L
);
2920 if Nkind
(Context
) = N_Package_Body
then
2922 -- Ensure that all abstract states and objects declared in the
2923 -- state space of a package body are utilized as constituents.
2925 Check_Unused_Body_States
(Defining_Entity
(Context
));
2927 -- State refinements are visible up to the end of the package body
2928 -- declarations. Hide the state refinements from visibility to
2929 -- restore the original state conditions.
2931 Remove_Visible_Refinements
(Corresponding_Spec
(Context
));
2932 Remove_Partial_Visible_Refinements
(Corresponding_Spec
(Context
));
2934 elsif Nkind
(Context
) = N_Package_Specification
then
2936 -- Partial state refinements are visible up to the end of the
2937 -- package spec declarations. Hide the partial state refinements
2938 -- from visibility to restore the original state conditions.
2940 Remove_Partial_Visible_Refinements
(Defining_Entity
(Context
));
2943 -- Verify that all abstract states found in any package declared in
2944 -- the input declarative list have proper refinements. The check is
2945 -- performed only when the context denotes a block, entry, package,
2946 -- protected, subprogram, or task body (SPARK RM 7.1.4(4) and SPARK
2949 Check_State_Refinements
(Context
);
2951 -- Create the subprogram bodies which verify the run-time semantics
2952 -- of pragmas Default_Initial_Condition and [Type_]Invariant for all
2953 -- types within the current declarative list. This ensures that all
2954 -- assertion expressions are preanalyzed and resolved at the end of
2955 -- the declarative part. Note that the resolution happens even when
2956 -- freezing does not take place.
2958 Build_Assertion_Bodies
(L
, Context
);
2960 end Analyze_Declarations
;
2962 -----------------------------------
2963 -- Analyze_Full_Type_Declaration --
2964 -----------------------------------
2966 procedure Analyze_Full_Type_Declaration
(N
: Node_Id
) is
2967 Def
: constant Node_Id
:= Type_Definition
(N
);
2968 Def_Id
: constant Entity_Id
:= Defining_Identifier
(N
);
2972 Is_Remote
: constant Boolean :=
2973 (Is_Remote_Types
(Current_Scope
)
2974 or else Is_Remote_Call_Interface
(Current_Scope
))
2975 and then not (In_Private_Part
(Current_Scope
)
2976 or else In_Package_Body
(Current_Scope
));
2978 procedure Check_Nonoverridable_Aspects
;
2979 -- Apply the rule in RM 13.1.1(18.4/4) on iterator aspects that cannot
2980 -- be overridden, and can only be confirmed on derivation.
2982 procedure Check_Ops_From_Incomplete_Type
;
2983 -- If there is a tagged incomplete partial view of the type, traverse
2984 -- the primitives of the incomplete view and change the type of any
2985 -- controlling formals and result to indicate the full view. The
2986 -- primitives will be added to the full type's primitive operations
2987 -- list later in Sem_Disp.Check_Operation_From_Incomplete_Type (which
2988 -- is called from Process_Incomplete_Dependents).
2990 ----------------------------------
2991 -- Check_Nonoverridable_Aspects --
2992 ----------------------------------
2994 procedure Check_Nonoverridable_Aspects
is
2995 function Get_Aspect_Spec
2997 Aspect_Name
: Name_Id
) return Node_Id
;
2998 -- Check whether a list of aspect specifications includes an entry
2999 -- for a specific aspect. The list is either that of a partial or
3002 ---------------------
3003 -- Get_Aspect_Spec --
3004 ---------------------
3006 function Get_Aspect_Spec
3008 Aspect_Name
: Name_Id
) return Node_Id
3013 Spec
:= First
(Specs
);
3014 while Present
(Spec
) loop
3015 if Chars
(Identifier
(Spec
)) = Aspect_Name
then
3022 end Get_Aspect_Spec
;
3026 Prev_Aspects
: constant List_Id
:=
3027 Aspect_Specifications
(Parent
(Def_Id
));
3028 Par_Type
: Entity_Id
;
3029 Prev_Aspect
: Node_Id
;
3031 -- Start of processing for Check_Nonoverridable_Aspects
3034 -- Get parent type of derived type. Note that Prev is the entity in
3035 -- the partial declaration, but its contents are now those of full
3036 -- view, while Def_Id reflects the partial view.
3038 if Is_Private_Type
(Def_Id
) then
3039 Par_Type
:= Etype
(Full_View
(Def_Id
));
3041 Par_Type
:= Etype
(Def_Id
);
3044 -- If there is an inherited Implicit_Dereference, verify that it is
3045 -- made explicit in the partial view.
3047 if Has_Discriminants
(Base_Type
(Par_Type
))
3048 and then Nkind
(Parent
(Prev
)) = N_Full_Type_Declaration
3049 and then Present
(Discriminant_Specifications
(Parent
(Prev
)))
3050 and then Present
(Get_Reference_Discriminant
(Par_Type
))
3053 Get_Aspect_Spec
(Prev_Aspects
, Name_Implicit_Dereference
);
3057 (Discriminant_Specifications
3058 (Original_Node
(Parent
(Prev
))))
3061 ("type does not inherit implicit dereference", Prev
);
3064 -- If one of the views has the aspect specified, verify that it
3065 -- is consistent with that of the parent.
3068 Cur_Discr
: constant Entity_Id
:=
3069 Get_Reference_Discriminant
(Prev
);
3070 Par_Discr
: constant Entity_Id
:=
3071 Get_Reference_Discriminant
(Par_Type
);
3074 if Corresponding_Discriminant
(Cur_Discr
) /= Par_Discr
then
3076 ("aspect inconsistent with that of parent", N
);
3079 -- Check that specification in partial view matches the
3080 -- inherited aspect. Compare names directly because aspect
3081 -- expression may not be analyzed.
3083 if Present
(Prev_Aspect
)
3084 and then Nkind
(Expression
(Prev_Aspect
)) = N_Identifier
3085 and then Chars
(Expression
(Prev_Aspect
)) /=
3089 ("aspect inconsistent with that of parent", N
);
3095 -- What about other nonoverridable aspects???
3096 end Check_Nonoverridable_Aspects
;
3098 ------------------------------------
3099 -- Check_Ops_From_Incomplete_Type --
3100 ------------------------------------
3102 procedure Check_Ops_From_Incomplete_Type
is
3109 and then Ekind
(Prev
) = E_Incomplete_Type
3110 and then Is_Tagged_Type
(Prev
)
3111 and then Is_Tagged_Type
(T
)
3112 and then Present
(Primitive_Operations
(Prev
))
3114 Elmt
:= First_Elmt
(Primitive_Operations
(Prev
));
3115 while Present
(Elmt
) loop
3118 Formal
:= First_Formal
(Op
);
3119 while Present
(Formal
) loop
3120 if Etype
(Formal
) = Prev
then
3121 Set_Etype
(Formal
, T
);
3124 Next_Formal
(Formal
);
3127 if Etype
(Op
) = Prev
then
3134 end Check_Ops_From_Incomplete_Type
;
3136 -- Start of processing for Analyze_Full_Type_Declaration
3139 Prev
:= Find_Type_Name
(N
);
3141 -- The full view, if present, now points to the current type. If there
3142 -- is an incomplete partial view, set a link to it, to simplify the
3143 -- retrieval of primitive operations of the type.
3145 -- Ada 2005 (AI-50217): If the type was previously decorated when
3146 -- imported through a LIMITED WITH clause, it appears as incomplete
3147 -- but has no full view.
3149 if Ekind
(Prev
) = E_Incomplete_Type
3150 and then Present
(Full_View
(Prev
))
3152 T
:= Full_View
(Prev
);
3153 Set_Incomplete_View
(N
, Prev
);
3158 Set_Is_Pure
(T
, Is_Pure
(Current_Scope
));
3160 -- We set the flag Is_First_Subtype here. It is needed to set the
3161 -- corresponding flag for the Implicit class-wide-type created
3162 -- during tagged types processing.
3164 Set_Is_First_Subtype
(T
, True);
3166 -- Only composite types other than array types are allowed to have
3171 -- For derived types, the rule will be checked once we've figured
3172 -- out the parent type.
3174 when N_Derived_Type_Definition
=>
3177 -- For record types, discriminants are allowed.
3179 when N_Record_Definition
=>
3183 if Present
(Discriminant_Specifications
(N
)) then
3185 ("elementary or array type cannot have discriminants",
3187 (First
(Discriminant_Specifications
(N
))));
3191 -- Elaborate the type definition according to kind, and generate
3192 -- subsidiary (implicit) subtypes where needed. We skip this if it was
3193 -- already done (this happens during the reanalysis that follows a call
3194 -- to the high level optimizer).
3196 if not Analyzed
(T
) then
3199 -- Set the SPARK mode from the current context
3201 Set_SPARK_Pragma
(T
, SPARK_Mode_Pragma
);
3202 Set_SPARK_Pragma_Inherited
(T
);
3205 when N_Access_To_Subprogram_Definition
=>
3206 Access_Subprogram_Declaration
(T
, Def
);
3208 -- If this is a remote access to subprogram, we must create the
3209 -- equivalent fat pointer type, and related subprograms.
3212 Process_Remote_AST_Declaration
(N
);
3215 -- Validate categorization rule against access type declaration
3216 -- usually a violation in Pure unit, Shared_Passive unit.
3218 Validate_Access_Type_Declaration
(T
, N
);
3220 -- If the type has contracts, we create the corresponding
3221 -- wrapper at once, before analyzing the aspect specifications,
3222 -- so that pre/postconditions can be handled directly on the
3223 -- generated wrapper.
3225 if Ada_Version
>= Ada_2022
3226 and then Present
(Aspect_Specifications
(N
))
3227 and then Expander_Active
3229 Build_Access_Subprogram_Wrapper
(N
);
3232 when N_Access_To_Object_Definition
=>
3233 Access_Type_Declaration
(T
, Def
);
3235 -- Validate categorization rule against access type declaration
3236 -- usually a violation in Pure unit, Shared_Passive unit.
3238 Validate_Access_Type_Declaration
(T
, N
);
3240 -- If we are in a Remote_Call_Interface package and define a
3241 -- RACW, then calling stubs and specific stream attributes
3245 and then Is_Remote_Access_To_Class_Wide_Type
(Def_Id
)
3247 Add_RACW_Features
(Def_Id
);
3250 when N_Array_Type_Definition
=>
3251 Array_Type_Declaration
(T
, Def
);
3253 when N_Derived_Type_Definition
=>
3254 Derived_Type_Declaration
(T
, N
, T
/= Def_Id
);
3256 -- Save the scenario for examination by the ABE Processing
3259 Record_Elaboration_Scenario
(N
);
3261 when N_Enumeration_Type_Definition
=>
3262 Enumeration_Type_Declaration
(T
, Def
);
3264 when N_Floating_Point_Definition
=>
3265 Floating_Point_Type_Declaration
(T
, Def
);
3267 when N_Decimal_Fixed_Point_Definition
=>
3268 Decimal_Fixed_Point_Type_Declaration
(T
, Def
);
3270 when N_Ordinary_Fixed_Point_Definition
=>
3271 Ordinary_Fixed_Point_Type_Declaration
(T
, Def
);
3273 when N_Signed_Integer_Type_Definition
=>
3274 Signed_Integer_Type_Declaration
(T
, Def
);
3276 when N_Modular_Type_Definition
=>
3277 Modular_Type_Declaration
(T
, Def
);
3279 when N_Record_Definition
=>
3280 Record_Type_Declaration
(T
, N
, Prev
);
3282 -- If declaration has a parse error, nothing to elaborate.
3288 raise Program_Error
;
3292 if Etype
(T
) = Any_Type
then
3296 -- Set the primitives list of the full type and its base type when
3297 -- needed. T may be E_Void in cases of earlier errors, and in that
3298 -- case we bypass this.
3300 if Ekind
(T
) /= E_Void
then
3301 if not Present
(Direct_Primitive_Operations
(T
)) then
3302 if Etype
(T
) = T
then
3303 Set_Direct_Primitive_Operations
(T
, New_Elmt_List
);
3305 -- If Etype of T is the base type (as opposed to a parent type)
3306 -- and already has an associated list of primitive operations,
3307 -- then set T's primitive list to the base type's list. Otherwise,
3308 -- create a new empty primitives list and share the list between
3309 -- T and its base type. The lists need to be shared in common.
3311 elsif Etype
(T
) = Base_Type
(T
) then
3313 if not Present
(Direct_Primitive_Operations
(Base_Type
(T
)))
3315 Set_Direct_Primitive_Operations
3316 (Base_Type
(T
), New_Elmt_List
);
3319 Set_Direct_Primitive_Operations
3320 (T
, Direct_Primitive_Operations
(Base_Type
(T
)));
3322 -- Case where the Etype is a parent type, so we need a new
3323 -- primitives list for T.
3326 Set_Direct_Primitive_Operations
(T
, New_Elmt_List
);
3329 -- If T already has a Direct_Primitive_Operations list but its
3330 -- base type doesn't then set the base type's list to T's list.
3332 elsif not Present
(Direct_Primitive_Operations
(Base_Type
(T
))) then
3333 Set_Direct_Primitive_Operations
3334 (Base_Type
(T
), Direct_Primitive_Operations
(T
));
3338 -- Some common processing for all types
3340 Set_Depends_On_Private
(T
, Has_Private_Component
(T
));
3341 Check_Ops_From_Incomplete_Type
;
3343 -- Both the declared entity, and its anonymous base type if one was
3344 -- created, need freeze nodes allocated.
3347 B
: constant Entity_Id
:= Base_Type
(T
);
3350 -- In the case where the base type differs from the first subtype, we
3351 -- pre-allocate a freeze node, and set the proper link to the first
3352 -- subtype. Freeze_Entity will use this preallocated freeze node when
3353 -- it freezes the entity.
3355 -- This does not apply if the base type is a generic type, whose
3356 -- declaration is independent of the current derived definition.
3358 if B
/= T
and then not Is_Generic_Type
(B
) then
3359 Ensure_Freeze_Node
(B
);
3360 Set_First_Subtype_Link
(Freeze_Node
(B
), T
);
3363 -- A type that is imported through a limited_with clause cannot
3364 -- generate any code, and thus need not be frozen. However, an access
3365 -- type with an imported designated type needs a finalization list,
3366 -- which may be referenced in some other package that has non-limited
3367 -- visibility on the designated type. Thus we must create the
3368 -- finalization list at the point the access type is frozen, to
3369 -- prevent unsatisfied references at link time.
3371 if not From_Limited_With
(T
) or else Is_Access_Type
(T
) then
3372 Set_Has_Delayed_Freeze
(T
);
3376 -- Case where T is the full declaration of some private type which has
3377 -- been swapped in Defining_Identifier (N).
3379 if T
/= Def_Id
and then Is_Private_Type
(Def_Id
) then
3380 Process_Full_View
(N
, T
, Def_Id
);
3382 -- Record the reference. The form of this is a little strange, since
3383 -- the full declaration has been swapped in. So the first parameter
3384 -- here represents the entity to which a reference is made which is
3385 -- the "real" entity, i.e. the one swapped in, and the second
3386 -- parameter provides the reference location.
3388 -- Also, we want to kill Has_Pragma_Unreferenced temporarily here
3389 -- since we don't want a complaint about the full type being an
3390 -- unwanted reference to the private type
3393 B
: constant Boolean := Has_Pragma_Unreferenced
(T
);
3395 Set_Has_Pragma_Unreferenced
(T
, False);
3396 Generate_Reference
(T
, T
, 'c');
3397 Set_Has_Pragma_Unreferenced
(T
, B
);
3400 Set_Completion_Referenced
(Def_Id
);
3402 -- For completion of incomplete type, process incomplete dependents
3403 -- and always mark the full type as referenced (it is the incomplete
3404 -- type that we get for any real reference).
3406 elsif Ekind
(Prev
) = E_Incomplete_Type
then
3407 Process_Incomplete_Dependents
(N
, T
, Prev
);
3408 Generate_Reference
(Prev
, Def_Id
, 'c');
3409 Set_Completion_Referenced
(Def_Id
);
3411 -- If not private type or incomplete type completion, this is a real
3412 -- definition of a new entity, so record it.
3415 Generate_Definition
(Def_Id
);
3418 -- Propagate any pending access types whose finalization masters need to
3419 -- be fully initialized from the partial to the full view. Guard against
3420 -- an illegal full view that remains unanalyzed.
3422 if Is_Type
(Def_Id
) and then Is_Incomplete_Or_Private_Type
(Prev
) then
3423 Set_Pending_Access_Types
(Def_Id
, Pending_Access_Types
(Prev
));
3426 if Chars
(Scope
(Def_Id
)) = Name_System
3427 and then Chars
(Def_Id
) = Name_Address
3428 and then In_Predefined_Unit
(N
)
3430 Set_Is_Descendant_Of_Address
(Def_Id
);
3431 Set_Is_Descendant_Of_Address
(Base_Type
(Def_Id
));
3432 Set_Is_Descendant_Of_Address
(Prev
);
3435 Set_Optimize_Alignment_Flags
(Def_Id
);
3436 Check_Eliminated
(Def_Id
);
3438 -- If the declaration is a completion and aspects are present, apply
3439 -- them to the entity for the type which is currently the partial
3440 -- view, but which is the one that will be frozen.
3442 if Has_Aspects
(N
) then
3444 -- In most cases the partial view is a private type, and both views
3445 -- appear in different declarative parts. In the unusual case where
3446 -- the partial view is incomplete, perform the analysis on the
3447 -- full view, to prevent freezing anomalies with the corresponding
3448 -- class-wide type, which otherwise might be frozen before the
3449 -- dispatch table is built.
3452 and then Ekind
(Prev
) /= E_Incomplete_Type
3454 Analyze_Aspect_Specifications
(N
, Prev
);
3459 Analyze_Aspect_Specifications
(N
, Def_Id
);
3463 if Is_Derived_Type
(Prev
)
3464 and then Def_Id
/= Prev
3466 Check_Nonoverridable_Aspects
;
3469 -- Check for tagged type declaration at library level
3471 if Is_Tagged_Type
(T
)
3472 and then not Is_Library_Level_Entity
(T
)
3474 Check_Restriction
(No_Local_Tagged_Types
, T
);
3476 end Analyze_Full_Type_Declaration
;
3478 ----------------------------------
3479 -- Analyze_Incomplete_Type_Decl --
3480 ----------------------------------
3482 procedure Analyze_Incomplete_Type_Decl
(N
: Node_Id
) is
3483 F
: constant Boolean := Is_Pure
(Current_Scope
);
3487 Generate_Definition
(Defining_Identifier
(N
));
3489 -- Process an incomplete declaration. The identifier must not have been
3490 -- declared already in the scope. However, an incomplete declaration may
3491 -- appear in the private part of a package, for a private type that has
3492 -- already been declared.
3494 -- In this case, the discriminants (if any) must match
3496 T
:= Find_Type_Name
(N
);
3498 Mutate_Ekind
(T
, E_Incomplete_Type
);
3500 Set_Is_First_Subtype
(T
);
3501 Reinit_Size_Align
(T
);
3503 -- Set the SPARK mode from the current context
3505 Set_SPARK_Pragma
(T
, SPARK_Mode_Pragma
);
3506 Set_SPARK_Pragma_Inherited
(T
);
3508 -- Ada 2005 (AI-326): Minimum decoration to give support to tagged
3509 -- incomplete types.
3511 if Tagged_Present
(N
) then
3512 Set_Is_Tagged_Type
(T
, True);
3513 Set_No_Tagged_Streams_Pragma
(T
, No_Tagged_Streams
);
3514 Make_Class_Wide_Type
(T
);
3517 -- Initialize the list of primitive operations to an empty list,
3518 -- to cover tagged types as well as untagged types. For untagged
3519 -- types this is used either to analyze the call as legal when
3520 -- Core_Extensions_Allowed is True, or to issue a better error message
3523 Set_Direct_Primitive_Operations
(T
, New_Elmt_List
);
3525 Set_Stored_Constraint
(T
, No_Elist
);
3527 if Present
(Discriminant_Specifications
(N
)) then
3529 Process_Discriminants
(N
);
3533 -- If the type has discriminants, nontrivial subtypes may be declared
3534 -- before the full view of the type. The full views of those subtypes
3535 -- will be built after the full view of the type.
3537 Set_Private_Dependents
(T
, New_Elmt_List
);
3539 end Analyze_Incomplete_Type_Decl
;
3541 -----------------------------------
3542 -- Analyze_Interface_Declaration --
3543 -----------------------------------
3545 procedure Analyze_Interface_Declaration
(T
: Entity_Id
; Def
: Node_Id
) is
3546 CW
: constant Entity_Id
:= Class_Wide_Type
(T
);
3549 Set_Is_Tagged_Type
(T
);
3550 Set_No_Tagged_Streams_Pragma
(T
, No_Tagged_Streams
);
3552 Set_Is_Limited_Record
(T
, Limited_Present
(Def
)
3553 or else Task_Present
(Def
)
3554 or else Protected_Present
(Def
)
3555 or else Synchronized_Present
(Def
));
3557 -- Type is abstract if full declaration carries keyword, or if previous
3558 -- partial view did.
3560 Set_Is_Abstract_Type
(T
);
3561 Set_Is_Interface
(T
);
3563 -- Type is a limited interface if it includes the keyword limited, task,
3564 -- protected, or synchronized.
3566 Set_Is_Limited_Interface
3567 (T
, Limited_Present
(Def
)
3568 or else Protected_Present
(Def
)
3569 or else Synchronized_Present
(Def
)
3570 or else Task_Present
(Def
));
3572 Set_Interfaces
(T
, New_Elmt_List
);
3573 Set_Direct_Primitive_Operations
(T
, New_Elmt_List
);
3575 -- Complete the decoration of the class-wide entity if it was already
3576 -- built (i.e. during the creation of the limited view)
3578 if Present
(CW
) then
3579 Set_Is_Interface
(CW
);
3580 Set_Is_Limited_Interface
(CW
, Is_Limited_Interface
(T
));
3583 -- Check runtime support for synchronized interfaces
3585 if Is_Concurrent_Interface
(T
)
3586 and then not RTE_Available
(RE_Select_Specific_Data
)
3588 Error_Msg_CRT
("synchronized interfaces", T
);
3590 end Analyze_Interface_Declaration
;
3592 -----------------------------
3593 -- Analyze_Itype_Reference --
3594 -----------------------------
3596 -- Nothing to do. This node is placed in the tree only for the benefit of
3597 -- back end processing, and has no effect on the semantic processing.
3599 procedure Analyze_Itype_Reference
(N
: Node_Id
) is
3601 pragma Assert
(Is_Itype
(Itype
(N
)));
3603 end Analyze_Itype_Reference
;
3605 --------------------------------
3606 -- Analyze_Number_Declaration --
3607 --------------------------------
3609 procedure Analyze_Number_Declaration
(N
: Node_Id
) is
3610 E
: constant Node_Id
:= Expression
(N
);
3611 Id
: constant Entity_Id
:= Defining_Identifier
(N
);
3612 Index
: Interp_Index
;
3617 Generate_Definition
(Id
);
3620 -- This is an optimization of a common case of an integer literal
3622 if Nkind
(E
) = N_Integer_Literal
then
3623 Set_Is_Static_Expression
(E
, True);
3624 Set_Etype
(E
, Universal_Integer
);
3626 Set_Etype
(Id
, Universal_Integer
);
3627 Mutate_Ekind
(Id
, E_Named_Integer
);
3628 Set_Is_Frozen
(Id
, True);
3630 Set_Debug_Info_Needed
(Id
);
3634 Set_Is_Pure
(Id
, Is_Pure
(Current_Scope
));
3636 -- Process expression, replacing error by integer zero, to avoid
3637 -- cascaded errors or aborts further along in the processing
3639 -- Replace Error by integer zero, which seems least likely to cause
3643 Rewrite
(E
, Make_Integer_Literal
(Sloc
(E
), Uint_0
));
3644 Set_Error_Posted
(E
);
3649 -- Verify that the expression is static and numeric. If
3650 -- the expression is overloaded, we apply the preference
3651 -- rule that favors root numeric types.
3653 if not Is_Overloaded
(E
) then
3655 if Has_Dynamic_Predicate_Aspect
(T
)
3656 or else Has_Ghost_Predicate_Aspect
(T
)
3659 ("subtype has non-static predicate, "
3660 & "not allowed in number declaration", N
);
3666 Get_First_Interp
(E
, Index
, It
);
3667 while Present
(It
.Typ
) loop
3668 if (Is_Integer_Type
(It
.Typ
) or else Is_Real_Type
(It
.Typ
))
3669 and then (Scope
(Base_Type
(It
.Typ
))) = Standard_Standard
3671 if T
= Any_Type
then
3674 elsif Is_Universal_Numeric_Type
(It
.Typ
) then
3675 -- Choose universal interpretation over any other
3682 Get_Next_Interp
(Index
, It
);
3686 if Is_Integer_Type
(T
) then
3688 Set_Etype
(Id
, Universal_Integer
);
3689 Mutate_Ekind
(Id
, E_Named_Integer
);
3691 elsif Is_Real_Type
(T
) then
3693 -- Because the real value is converted to universal_real, this is a
3694 -- legal context for a universal fixed expression.
3696 if T
= Universal_Fixed
then
3698 Loc
: constant Source_Ptr
:= Sloc
(N
);
3699 Conv
: constant Node_Id
:= Make_Type_Conversion
(Loc
,
3701 New_Occurrence_Of
(Universal_Real
, Loc
),
3702 Expression
=> Relocate_Node
(E
));
3709 elsif T
= Any_Fixed
then
3710 Error_Msg_N
("illegal context for mixed mode operation", E
);
3712 -- Expression is of the form : universal_fixed * integer. Try to
3713 -- resolve as universal_real.
3715 T
:= Universal_Real
;
3720 Set_Etype
(Id
, Universal_Real
);
3721 Mutate_Ekind
(Id
, E_Named_Real
);
3724 Wrong_Type
(E
, Any_Numeric
);
3728 Mutate_Ekind
(Id
, E_Constant
);
3729 Set_Never_Set_In_Source
(Id
, True);
3730 Set_Is_True_Constant
(Id
, True);
3734 if Nkind
(E
) in N_Integer_Literal | N_Real_Literal
then
3735 Set_Etype
(E
, Etype
(Id
));
3738 if not Is_OK_Static_Expression
(E
) then
3739 Flag_Non_Static_Expr
3740 ("non-static expression used in number declaration!", E
);
3741 Rewrite
(E
, Make_Integer_Literal
(Sloc
(N
), 1));
3742 Set_Etype
(E
, Any_Type
);
3745 Analyze_Dimension
(N
);
3746 end Analyze_Number_Declaration
;
3748 --------------------------------
3749 -- Analyze_Object_Declaration --
3750 --------------------------------
3752 -- WARNING: This routine manages Ghost regions. Return statements must be
3753 -- replaced by gotos which jump to the end of the routine and restore the
3756 procedure Analyze_Object_Declaration
(N
: Node_Id
) is
3757 Loc
: constant Source_Ptr
:= Sloc
(N
);
3758 Id
: constant Entity_Id
:= Defining_Identifier
(N
);
3759 Next_Decl
: constant Node_Id
:= Next
(N
);
3764 E
: Node_Id
:= Expression
(N
);
3765 -- E is set to Expression (N) throughout this routine. When Expression
3766 -- (N) is modified, E is changed accordingly.
3768 procedure Check_Dynamic_Object
(Typ
: Entity_Id
);
3769 -- A library-level object with nonstatic discriminant constraints may
3770 -- require dynamic allocation. The declaration is illegal if the
3771 -- profile includes the restriction No_Implicit_Heap_Allocations.
3773 procedure Check_For_Null_Excluding_Components
3774 (Obj_Typ
: Entity_Id
;
3775 Obj_Decl
: Node_Id
);
3776 -- Verify that each null-excluding component of object declaration
3777 -- Obj_Decl carrying type Obj_Typ has explicit initialization. Emit
3778 -- a compile-time warning if this is not the case.
3780 procedure Check_Return_Subtype_Indication
(Obj_Decl
: Node_Id
);
3781 -- Check that the return subtype indication properly matches the result
3782 -- subtype of the function in an extended return object declaration, as
3783 -- required by RM 6.5(5.1/2-5.3/2).
3785 function Count_Tasks
(T
: Entity_Id
) return Uint
;
3786 -- This function is called when a non-generic library level object of a
3787 -- task type is declared. Its function is to count the static number of
3788 -- tasks declared within the type (it is only called if Has_Task is set
3789 -- for T). As a side effect, if an array of tasks with nonstatic bounds
3790 -- or a variant record type is encountered, Check_Restriction is called
3791 -- indicating the count is unknown.
3793 function Delayed_Aspect_Present
return Boolean;
3794 -- If the declaration has an expression that is an aggregate, and it
3795 -- has aspects that require delayed analysis, the resolution of the
3796 -- aggregate must be deferred to the freeze point of the object. This
3797 -- special processing was created for address clauses, but it must
3798 -- also apply to address aspects. This must be done before the aspect
3799 -- specifications are analyzed because we must handle the aggregate
3800 -- before the analysis of the object declaration is complete.
3802 -- Any other relevant delayed aspects on object declarations ???
3804 --------------------------
3805 -- Check_Dynamic_Object --
3806 --------------------------
3808 procedure Check_Dynamic_Object
(Typ
: Entity_Id
) is
3810 Obj_Type
: Entity_Id
;
3815 if Is_Private_Type
(Obj_Type
)
3816 and then Present
(Full_View
(Obj_Type
))
3818 Obj_Type
:= Full_View
(Obj_Type
);
3821 if Known_Static_Esize
(Obj_Type
) then
3825 if Restriction_Active
(No_Implicit_Heap_Allocations
)
3826 and then Expander_Active
3827 and then Has_Discriminants
(Obj_Type
)
3829 Comp
:= First_Component
(Obj_Type
);
3830 while Present
(Comp
) loop
3831 if Known_Static_Esize
(Etype
(Comp
))
3832 or else Size_Known_At_Compile_Time
(Etype
(Comp
))
3836 elsif Is_Record_Type
(Etype
(Comp
)) then
3837 Check_Dynamic_Object
(Etype
(Comp
));
3839 elsif not Discriminated_Size
(Comp
)
3840 and then Comes_From_Source
(Comp
)
3843 ("component& of non-static size will violate restriction "
3844 & "No_Implicit_Heap_Allocation?", N
, Comp
);
3848 Next_Component
(Comp
);
3851 end Check_Dynamic_Object
;
3853 -----------------------------------------
3854 -- Check_For_Null_Excluding_Components --
3855 -----------------------------------------
3857 procedure Check_For_Null_Excluding_Components
3858 (Obj_Typ
: Entity_Id
;
3861 procedure Check_Component
3862 (Comp_Typ
: Entity_Id
;
3863 Comp_Decl
: Node_Id
:= Empty
;
3864 Array_Comp
: Boolean := False);
3865 -- Apply a compile-time null-exclusion check on a component denoted
3866 -- by its declaration Comp_Decl and type Comp_Typ, and all of its
3867 -- subcomponents (if any).
3869 ---------------------
3870 -- Check_Component --
3871 ---------------------
3873 procedure Check_Component
3874 (Comp_Typ
: Entity_Id
;
3875 Comp_Decl
: Node_Id
:= Empty
;
3876 Array_Comp
: Boolean := False)
3882 -- Do not consider internally-generated components or those that
3883 -- are already initialized.
3885 if Present
(Comp_Decl
)
3886 and then (not Comes_From_Source
(Comp_Decl
)
3887 or else Present
(Expression
(Comp_Decl
)))
3892 if Is_Incomplete_Or_Private_Type
(Comp_Typ
)
3893 and then Present
(Full_View
(Comp_Typ
))
3895 T
:= Full_View
(Comp_Typ
);
3900 -- Verify a component of a null-excluding access type
3902 if Is_Access_Type
(T
)
3903 and then Can_Never_Be_Null
(T
)
3905 if Comp_Decl
= Obj_Decl
then
3906 Null_Exclusion_Static_Checks
3909 Array_Comp
=> Array_Comp
);
3912 Null_Exclusion_Static_Checks
3915 Array_Comp
=> Array_Comp
);
3918 -- Check array components
3920 elsif Is_Array_Type
(T
) then
3922 -- There is no suitable component when the object is of an
3923 -- array type. However, a namable component may appear at some
3924 -- point during the recursive inspection, but not at the top
3925 -- level. At the top level just indicate array component case.
3927 if Comp_Decl
= Obj_Decl
then
3928 Check_Component
(Component_Type
(T
), Array_Comp
=> True);
3930 Check_Component
(Component_Type
(T
), Comp_Decl
);
3933 -- Verify all components of type T
3935 -- Note: No checks are performed on types with discriminants due
3936 -- to complexities involving variants. ???
3938 elsif (Is_Concurrent_Type
(T
)
3939 or else Is_Incomplete_Or_Private_Type
(T
)
3940 or else Is_Record_Type
(T
))
3941 and then not Has_Discriminants
(T
)
3943 Comp
:= First_Component
(T
);
3944 while Present
(Comp
) loop
3945 Check_Component
(Etype
(Comp
), Parent
(Comp
));
3947 Next_Component
(Comp
);
3950 end Check_Component
;
3952 -- Start processing for Check_For_Null_Excluding_Components
3955 Check_Component
(Obj_Typ
, Obj_Decl
);
3956 end Check_For_Null_Excluding_Components
;
3958 -------------------------------------
3959 -- Check_Return_Subtype_Indication --
3960 -------------------------------------
3962 procedure Check_Return_Subtype_Indication
(Obj_Decl
: Node_Id
) is
3963 Obj_Id
: constant Entity_Id
:= Defining_Identifier
(Obj_Decl
);
3964 Obj_Typ
: constant Entity_Id
:= Etype
(Obj_Id
);
3965 Func_Id
: constant Entity_Id
:= Return_Applies_To
(Scope
(Obj_Id
));
3966 R_Typ
: constant Entity_Id
:= Etype
(Func_Id
);
3967 Indic
: constant Node_Id
:=
3968 Object_Definition
(Original_Node
(Obj_Decl
));
3970 procedure Error_No_Match
(N
: Node_Id
);
3971 -- Output error messages for case where types do not statically
3972 -- match. N is the location for the messages.
3974 --------------------
3975 -- Error_No_Match --
3976 --------------------
3978 procedure Error_No_Match
(N
: Node_Id
) is
3981 ("subtype must statically match function result subtype", N
);
3983 if not Predicates_Match
(Obj_Typ
, R_Typ
) then
3984 Error_Msg_Node_2
:= R_Typ
;
3986 ("\predicate of& does not match predicate of&",
3991 -- Start of processing for Check_Return_Subtype_Indication
3994 -- First, avoid cascaded errors
3996 if Error_Posted
(Obj_Decl
) or else Error_Posted
(Indic
) then
4000 -- "return access T" case; check that the return statement also has
4001 -- "access T", and that the subtypes statically match:
4002 -- if this is an access to subprogram the signatures must match.
4004 if Is_Anonymous_Access_Type
(R_Typ
) then
4005 if Is_Anonymous_Access_Type
(Obj_Typ
) then
4006 if Ekind
(Designated_Type
(Obj_Typ
)) /= E_Subprogram_Type
4008 if Base_Type
(Designated_Type
(Obj_Typ
)) /=
4009 Base_Type
(Designated_Type
(R_Typ
))
4010 or else not Subtypes_Statically_Match
(Obj_Typ
, R_Typ
)
4012 Error_No_Match
(Subtype_Mark
(Indic
));
4016 -- For two anonymous access to subprogram types, the types
4017 -- themselves must be type conformant.
4019 if not Conforming_Types
4020 (Obj_Typ
, R_Typ
, Fully_Conformant
)
4022 Error_No_Match
(Indic
);
4027 Error_Msg_N
("must use anonymous access type", Indic
);
4030 -- If the return object is of an anonymous access type, then report
4031 -- an error if the function's result type is not also anonymous.
4033 elsif Is_Anonymous_Access_Type
(Obj_Typ
) then
4034 pragma Assert
(not Is_Anonymous_Access_Type
(R_Typ
));
4036 ("anonymous access not allowed for function with named access "
4039 -- Subtype indication case: check that the return object's type is
4040 -- covered by the result type, and that the subtypes statically match
4041 -- when the result subtype is constrained. Also handle record types
4042 -- with unknown discriminants for which we have built the underlying
4043 -- record view. Coverage is needed to allow specific-type return
4044 -- objects when the result type is class-wide (see AI05-32).
4046 elsif Covers
(Base_Type
(R_Typ
), Base_Type
(Obj_Typ
))
4047 or else (Is_Underlying_Record_View
(Base_Type
(Obj_Typ
))
4051 Underlying_Record_View
(Base_Type
(Obj_Typ
))))
4053 -- A null exclusion may be present on the return type, on the
4054 -- function specification, on the object declaration or on the
4057 if Is_Access_Type
(R_Typ
)
4059 (Can_Never_Be_Null
(R_Typ
)
4060 or else Null_Exclusion_Present
(Parent
(Func_Id
))) /=
4061 Can_Never_Be_Null
(Obj_Typ
)
4063 Error_No_Match
(Indic
);
4066 -- AI05-103: for elementary types, subtypes must statically match
4068 if Is_Constrained
(R_Typ
) or else Is_Access_Type
(R_Typ
) then
4069 if not Subtypes_Statically_Match
(Obj_Typ
, R_Typ
) then
4070 Error_No_Match
(Indic
);
4074 -- All remaining cases are illegal
4076 -- Note: previous versions of this subprogram allowed the return
4077 -- value to be the ancestor of the return type if the return type
4078 -- was a null extension. This was plainly incorrect.
4082 ("wrong type for return_subtype_indication", Indic
);
4084 end Check_Return_Subtype_Indication
;
4090 function Count_Tasks
(T
: Entity_Id
) return Uint
is
4096 if Is_Task_Type
(T
) then
4099 elsif Is_Record_Type
(T
) then
4100 if Has_Discriminants
(T
) then
4101 Check_Restriction
(Max_Tasks
, N
);
4106 C
:= First_Component
(T
);
4107 while Present
(C
) loop
4108 V
:= V
+ Count_Tasks
(Etype
(C
));
4115 elsif Is_Array_Type
(T
) then
4116 X
:= First_Index
(T
);
4117 V
:= Count_Tasks
(Component_Type
(T
));
4118 while Present
(X
) loop
4121 if not Is_OK_Static_Subtype
(C
) then
4122 Check_Restriction
(Max_Tasks
, N
);
4125 V
:= V
* (UI_Max
(Uint_0
,
4126 Expr_Value
(Type_High_Bound
(C
)) -
4127 Expr_Value
(Type_Low_Bound
(C
)) + Uint_1
));
4140 ----------------------------
4141 -- Delayed_Aspect_Present --
4142 ----------------------------
4144 function Delayed_Aspect_Present
return Boolean is
4149 if Present
(Aspect_Specifications
(N
)) then
4150 A
:= First
(Aspect_Specifications
(N
));
4152 while Present
(A
) loop
4153 A_Id
:= Get_Aspect_Id
(Chars
(Identifier
(A
)));
4155 if A_Id
= Aspect_Address
then
4157 -- Set flag on object entity, for later processing at
4158 -- the freeze point.
4160 Set_Has_Delayed_Aspects
(Id
);
4169 end Delayed_Aspect_Present
;
4173 Saved_GM
: constant Ghost_Mode_Type
:= Ghost_Mode
;
4174 Saved_IGR
: constant Node_Id
:= Ignored_Ghost_Region
;
4175 -- Save the Ghost-related attributes to restore on exit
4177 Prev_Entity
: Entity_Id
:= Empty
;
4178 Related_Id
: Entity_Id
;
4180 -- Start of processing for Analyze_Object_Declaration
4183 -- There are three kinds of implicit types generated by an
4184 -- object declaration:
4186 -- 1. Those generated by the original Object Definition
4188 -- 2. Those generated by the Expression
4190 -- 3. Those used to constrain the Object Definition with the
4191 -- expression constraints when the definition is unconstrained.
4193 -- They must be generated in this order to avoid order of elaboration
4194 -- issues. Thus the first step (after entering the name) is to analyze
4195 -- the object definition.
4197 if Constant_Present
(N
) then
4198 Prev_Entity
:= Current_Entity_In_Scope
(Id
);
4200 if Present
(Prev_Entity
)
4202 -- If the homograph is an implicit subprogram, it is overridden
4203 -- by the current declaration.
4205 ((Is_Overloadable
(Prev_Entity
)
4206 and then Is_Inherited_Operation
(Prev_Entity
))
4208 -- The current object is a discriminal generated for an entry
4209 -- family index. Even though the index is a constant, in this
4210 -- particular context there is no true constant redeclaration.
4211 -- Enter_Name will handle the visibility.
4214 (Is_Discriminal
(Id
)
4215 and then Ekind
(Discriminal_Link
(Id
)) =
4216 E_Entry_Index_Parameter
)
4218 -- The current object is the renaming for a generic declared
4219 -- within the instance.
4222 (Ekind
(Prev_Entity
) = E_Package
4223 and then Nkind
(Parent
(Prev_Entity
)) =
4224 N_Package_Renaming_Declaration
4225 and then not Comes_From_Source
(Prev_Entity
)
4227 Is_Generic_Instance
(Renamed_Entity
(Prev_Entity
)))
4229 -- The entity may be a homonym of a private component of the
4230 -- enclosing protected object, for which we create a local
4231 -- renaming declaration. The declaration is legal, even if
4232 -- useless when it just captures that component.
4235 (Ekind
(Scope
(Current_Scope
)) = E_Protected_Type
4236 and then Nkind
(Parent
(Prev_Entity
)) =
4237 N_Object_Renaming_Declaration
))
4239 Prev_Entity
:= Empty
;
4243 if Present
(Prev_Entity
) then
4245 -- The object declaration is Ghost when it completes a deferred Ghost
4248 Mark_And_Set_Ghost_Completion
(N
, Prev_Entity
);
4250 Constant_Redeclaration
(Id
, N
, T
);
4252 Generate_Reference
(Prev_Entity
, Id
, 'c');
4253 Set_Completion_Referenced
(Id
);
4255 if Error_Posted
(N
) then
4257 -- Type mismatch or illegal redeclaration; do not analyze
4258 -- expression to avoid cascaded errors.
4260 T
:= Find_Type_Of_Object
(Object_Definition
(N
), N
);
4262 Mutate_Ekind
(Id
, E_Variable
);
4266 -- In the normal case, enter identifier at the start to catch premature
4267 -- usage in the initialization expression.
4270 Generate_Definition
(Id
);
4273 Mark_Coextensions
(N
, Object_Definition
(N
));
4275 T
:= Find_Type_Of_Object
(Object_Definition
(N
), N
);
4277 if Nkind
(Object_Definition
(N
)) = N_Access_Definition
4279 (Access_To_Subprogram_Definition
(Object_Definition
(N
)))
4280 and then Protected_Present
4281 (Access_To_Subprogram_Definition
(Object_Definition
(N
)))
4283 T
:= Replace_Anonymous_Access_To_Protected_Subprogram
(N
);
4286 if Error_Posted
(Id
) then
4288 Mutate_Ekind
(Id
, E_Variable
);
4293 -- Ada 2005 (AI-231): Propagate the null-excluding attribute and carry
4294 -- out some static checks.
4296 if Ada_Version
>= Ada_2005
then
4298 -- In case of aggregates we must also take care of the correct
4299 -- initialization of nested aggregates bug this is done at the
4300 -- point of the analysis of the aggregate (see sem_aggr.adb) ???
4302 if Can_Never_Be_Null
(T
) then
4303 if Present
(Expression
(N
))
4304 and then Nkind
(Expression
(N
)) = N_Aggregate
4308 elsif Comes_From_Source
(Id
) then
4310 Save_Typ
: constant Entity_Id
:= Etype
(Id
);
4312 Set_Etype
(Id
, T
); -- Temp. decoration for static checks
4313 Null_Exclusion_Static_Checks
(N
);
4314 Set_Etype
(Id
, Save_Typ
);
4318 -- We might be dealing with an object of a composite type containing
4319 -- null-excluding components without an aggregate, so we must verify
4320 -- that such components have default initialization.
4323 Check_For_Null_Excluding_Components
(T
, N
);
4327 -- Object is marked pure if it is in a pure scope
4329 Set_Is_Pure
(Id
, Is_Pure
(Current_Scope
));
4331 -- If deferred constant, make sure context is appropriate. We detect
4332 -- a deferred constant as a constant declaration with no expression.
4333 -- A deferred constant can appear in a package body if its completion
4334 -- is by means of an interface pragma.
4336 if Constant_Present
(N
) and then No
(E
) then
4338 -- A deferred constant may appear in the declarative part of the
4339 -- following constructs:
4343 -- extended return statements
4346 -- subprogram bodies
4349 -- When declared inside a package spec, a deferred constant must be
4350 -- completed by a full constant declaration or pragma Import. In all
4351 -- other cases, the only proper completion is pragma Import. Extended
4352 -- return statements are flagged as invalid contexts because they do
4353 -- not have a declarative part and so cannot accommodate the pragma.
4355 if Ekind
(Current_Scope
) = E_Return_Statement
then
4357 ("invalid context for deferred constant declaration (RM 7.4)",
4360 ("\declaration requires an initialization expression",
4362 Set_Constant_Present
(N
, False);
4364 -- In Ada 83, deferred constant must be of private type
4366 elsif not Is_Private_Type
(T
) then
4367 if Ada_Version
= Ada_83
and then Comes_From_Source
(N
) then
4369 ("(Ada 83) deferred constant must be private type", N
);
4373 -- If not a deferred constant, then the object declaration freezes
4374 -- its type, unless the object is of an anonymous type and has delayed
4375 -- aspects. In that case the type is frozen when the object itself is.
4378 Check_Fully_Declared
(T
, N
);
4380 if Has_Delayed_Aspects
(Id
)
4381 and then Is_Array_Type
(T
)
4382 and then Is_Itype
(T
)
4384 Set_Has_Delayed_Freeze
(T
);
4386 Freeze_Before
(N
, T
);
4390 -- If the object was created by a constrained array definition, then
4391 -- set the link in both the anonymous base type and anonymous subtype
4392 -- that are built to represent the array type to point to the object.
4394 if Nkind
(Object_Definition
(Declaration_Node
(Id
))) =
4395 N_Constrained_Array_Definition
4397 Set_Related_Array_Object
(T
, Id
);
4398 Set_Related_Array_Object
(Base_Type
(T
), Id
);
4401 -- Check for protected objects not at library level
4403 if Has_Protected
(T
) and then not Is_Library_Level_Entity
(Id
) then
4404 Check_Restriction
(No_Local_Protected_Objects
, Id
);
4407 -- Check for violation of No_Local_Timing_Events
4409 if Has_Timing_Event
(T
) and then not Is_Library_Level_Entity
(Id
) then
4410 Check_Restriction
(No_Local_Timing_Events
, Id
);
4413 -- The actual subtype of the object is the nominal subtype, unless
4414 -- the nominal one is unconstrained and obtained from the expression.
4418 if Is_Library_Level_Entity
(Id
) then
4419 Check_Dynamic_Object
(T
);
4422 -- Process initialization expression if present and not in error
4424 if Present
(E
) and then E
/= Error
then
4426 -- Generate an error in case of CPP class-wide object initialization.
4427 -- Required because otherwise the expansion of the class-wide
4428 -- assignment would try to use 'size to initialize the object
4429 -- (primitive that is not available in CPP tagged types).
4431 if Is_Class_Wide_Type
(Act_T
)
4433 (Is_CPP_Class
(Root_Type
(Etype
(Act_T
)))
4435 (Present
(Full_View
(Root_Type
(Etype
(Act_T
))))
4437 Is_CPP_Class
(Full_View
(Root_Type
(Etype
(Act_T
))))))
4440 ("predefined assignment not available for 'C'P'P tagged types",
4444 Mark_Coextensions
(N
, E
);
4447 -- In case of errors detected in the analysis of the expression,
4448 -- decorate it with the expected type to avoid cascaded errors.
4450 if No
(Etype
(E
)) then
4454 -- If an initialization expression is present, then we set the
4455 -- Is_True_Constant flag. It will be reset if this is a variable
4456 -- and it is indeed modified.
4458 Set_Is_True_Constant
(Id
, True);
4460 -- If we are analyzing a constant declaration, set its completion
4461 -- flag after analyzing and resolving the expression.
4463 if Constant_Present
(N
) then
4464 Set_Has_Completion
(Id
);
4467 -- Set type and resolve (type may be overridden later on). Note:
4468 -- Ekind (Id) must still be E_Void at this point so that incorrect
4469 -- early usage within E is properly diagnosed.
4473 -- If the expression is an aggregate we must look ahead to detect
4474 -- the possible presence of an address clause, and defer resolution
4475 -- and expansion of the aggregate to the freeze point of the entity.
4477 -- This is not always legal because the aggregate may contain other
4478 -- references that need freezing, e.g. references to other entities
4479 -- with address clauses. In any case, when compiling with -gnatI the
4480 -- presence of the address clause must be ignored.
4482 if Comes_From_Source
(N
)
4483 and then Expander_Active
4484 and then Nkind
(E
) = N_Aggregate
4486 ((Present
(Following_Address_Clause
(N
))
4487 and then not Ignore_Rep_Clauses
)
4488 or else Delayed_Aspect_Present
)
4492 -- If the aggregate is limited it will be built in place, and its
4493 -- expansion is deferred until the object declaration is expanded.
4495 -- This is also required when generating C code to ensure that an
4496 -- object with an alignment or address clause can be initialized
4497 -- by means of component by component assignments.
4499 if Is_Limited_Type
(T
) or else Modify_Tree_For_C
then
4500 Set_Expansion_Delayed
(E
);
4504 -- If the expression is a formal that is a "subprogram pointer"
4505 -- this is illegal in accessibility terms (see RM 3.10.2 (13.1/2)
4506 -- and AARM 3.10.2 (13.b/2)). Add an explicit conversion to force
4507 -- the corresponding check, as is done for assignments.
4509 if Is_Entity_Name
(E
)
4510 and then Present
(Entity
(E
))
4511 and then Is_Formal
(Entity
(E
))
4513 Ekind
(Etype
(Entity
(E
))) = E_Anonymous_Access_Subprogram_Type
4514 and then Ekind
(T
) /= E_Anonymous_Access_Subprogram_Type
4516 Rewrite
(E
, Convert_To
(T
, Relocate_Node
(E
)));
4522 -- No further action needed if E is a call to an inlined function
4523 -- which returns an unconstrained type and it has been expanded into
4524 -- a procedure call. In that case N has been replaced by an object
4525 -- declaration without initializing expression and it has been
4526 -- analyzed (see Expand_Inlined_Call).
4528 if Back_End_Inlining
4529 and then Expander_Active
4530 and then Nkind
(E
) = N_Function_Call
4531 and then Nkind
(Name
(E
)) in N_Has_Entity
4532 and then Is_Inlined
(Entity
(Name
(E
)))
4533 and then not Is_Constrained
(Etype
(E
))
4534 and then Analyzed
(N
)
4535 and then No
(Expression
(N
))
4540 -- If E is null and has been replaced by an N_Raise_Constraint_Error
4541 -- node (which was marked already-analyzed), we need to set the type
4542 -- to something else than Universal_Access to keep gigi happy.
4544 if Etype
(E
) = Universal_Access
then
4548 -- If the object is an access to variable, the initialization
4549 -- expression cannot be an access to constant.
4551 if Is_Access_Type
(T
)
4552 and then not Is_Access_Constant
(T
)
4553 and then Is_Access_Type
(Etype
(E
))
4554 and then Is_Access_Constant
(Etype
(E
))
4557 ("access to variable cannot be initialized with an "
4558 & "access-to-constant expression", E
);
4561 if not Assignment_OK
(N
) then
4562 Check_Initialization
(T
, E
);
4565 Check_Unset_Reference
(E
);
4567 -- If this is a variable, then set current value. If this is a
4568 -- declared constant of a scalar type with a static expression,
4569 -- indicate that it is always valid.
4571 if not Constant_Present
(N
) then
4572 if Compile_Time_Known_Value
(E
) then
4573 Set_Current_Value
(Id
, E
);
4576 elsif Is_Scalar_Type
(T
) and then Is_OK_Static_Expression
(E
) then
4577 Set_Is_Known_Valid
(Id
);
4579 -- If it is a constant initialized with a valid nonstatic entity,
4580 -- the constant is known valid as well, and can inherit the subtype
4581 -- of the entity if it is a subtype of the given type. This info
4582 -- is preserved on the actual subtype of the constant.
4584 elsif Is_Scalar_Type
(T
)
4585 and then Is_Entity_Name
(E
)
4586 and then Is_Known_Valid
(Entity
(E
))
4587 and then In_Subrange_Of
(Etype
(Entity
(E
)), T
)
4589 Set_Is_Known_Valid
(Id
);
4590 Mutate_Ekind
(Id
, E_Constant
);
4591 Set_Actual_Subtype
(Id
, Etype
(Entity
(E
)));
4594 -- Deal with setting of null flags
4596 if Is_Access_Type
(T
) then
4597 if Known_Non_Null
(E
) then
4598 Set_Is_Known_Non_Null
(Id
, True);
4599 elsif Known_Null
(E
) and then not Can_Never_Be_Null
(Id
) then
4600 Set_Is_Known_Null
(Id
, True);
4604 -- Check incorrect use of dynamically tagged expressions
4606 if Is_Tagged_Type
(T
) then
4607 Check_Dynamically_Tagged_Expression
4613 Apply_Scalar_Range_Check
(E
, T
);
4614 Apply_Static_Length_Check
(E
, T
);
4616 -- A formal parameter of a specific tagged type whose related
4617 -- subprogram is subject to pragma Extensions_Visible with value
4618 -- "False" cannot be implicitly converted to a class-wide type by
4619 -- means of an initialization expression (SPARK RM 6.1.7(3)). Do
4620 -- not consider internally generated expressions.
4622 if Is_Class_Wide_Type
(T
)
4623 and then Comes_From_Source
(E
)
4624 and then Is_EVF_Expression
(E
)
4627 ("formal parameter cannot be implicitly converted to "
4628 & "class-wide type when Extensions_Visible is False", E
);
4632 -- If the No_Streams restriction is set, check that the type of the
4633 -- object is not, and does not contain, any subtype derived from
4634 -- Ada.Streams.Root_Stream_Type. Note that we guard the call to
4635 -- Has_Stream just for efficiency reasons. There is no point in
4636 -- spending time on a Has_Stream check if the restriction is not set.
4638 if Restriction_Check_Required
(No_Streams
) then
4639 if Has_Stream
(T
) then
4640 Check_Restriction
(No_Streams
, N
);
4644 -- Deal with predicate check before we start to do major rewriting. It
4645 -- is OK to initialize and then check the initialized value, since the
4646 -- object goes out of scope if we get a predicate failure. Note that we
4647 -- do this in the analyzer and not the expander because the analyzer
4648 -- does some substantial rewriting in some cases.
4650 -- We need a predicate check if the type has predicates that are not
4651 -- ignored, and if either there is an initializing expression, or for
4652 -- default initialization when we have at least one case of an explicit
4653 -- default initial value (including via a Default_Value or
4654 -- Default_Component_Value aspect, see AI12-0301) and then this is not
4655 -- an internal declaration whose initialization comes later (as for an
4656 -- aggregate expansion) or a deferred constant.
4657 -- If expression is an aggregate it may be expanded into assignments
4658 -- and the declaration itself is marked with No_Initialization, but
4659 -- the predicate still applies.
4661 if not Suppress_Assignment_Checks
(N
)
4662 and then (Predicate_Enabled
(T
) or else Has_Static_Predicate
(T
))
4664 (not No_Initialization
(N
)
4665 or else (Present
(E
) and then Nkind
(E
) = N_Aggregate
))
4669 Is_Partially_Initialized_Type
(T
, Include_Implicit
=> False))
4670 and then not (Constant_Present
(N
) and then No
(E
))
4672 -- If the type has a static predicate and the expression is known at
4673 -- compile time, see if the expression satisfies the predicate.
4674 -- In the case of a static expression, this must be done even if
4675 -- the predicate is not enabled (as per static expression rules).
4678 Check_Expression_Against_Static_Predicate
(E
, T
);
4681 -- Do not perform further predicate-related checks unless
4682 -- predicates are enabled for the subtype.
4684 if not Predicate_Enabled
(T
) then
4687 -- If the type is a null record and there is no explicit initial
4688 -- expression, no predicate check applies.
4690 elsif No
(E
) and then Is_Null_Record_Type
(T
) then
4693 -- If there is an address clause for this object, do not generate a
4694 -- predicate check here. It will be generated later, at the freezng
4695 -- point. It would be wrong to generate references to the object
4696 -- here, before the address has been determined.
4698 elsif Has_Aspect
(Id
, Aspect_Address
)
4699 or else Present
(Following_Address_Clause
(N
))
4703 -- Do not generate a predicate check if the initialization expression
4704 -- is a type conversion whose target subtype statically matches the
4705 -- object's subtype because the conversion has been subjected to the
4706 -- same check. This is a small optimization which avoids redundant
4710 and then Nkind
(E
) in N_Type_Conversion
4711 and then Subtypes_Statically_Match
(Etype
(Subtype_Mark
(E
)), T
)
4716 -- The check must be inserted after the expanded aggregate
4717 -- expansion code, if any.
4720 Check
: constant Node_Id
:=
4721 Make_Predicate_Check
(T
, New_Occurrence_Of
(Id
, Loc
));
4723 if No
(Next_Decl
) then
4724 Append_To
(List_Containing
(N
), Check
);
4726 Insert_Before
(Next_Decl
, Check
);
4732 -- Case of unconstrained type
4734 if not Is_Definite_Subtype
(T
) then
4736 -- Nothing to do in deferred constant case
4738 if Constant_Present
(N
) and then No
(E
) then
4741 -- Case of no initialization present
4744 if No_Initialization
(N
) then
4747 elsif Is_Class_Wide_Type
(T
) then
4749 ("initialization required in class-wide declaration", N
);
4753 ("unconstrained subtype not allowed (need initialization)",
4754 Object_Definition
(N
));
4756 if Is_Record_Type
(T
) and then Has_Discriminants
(T
) then
4758 ("\provide initial value or explicit discriminant values",
4759 Object_Definition
(N
));
4762 ("\or give default discriminant values for type&",
4763 Object_Definition
(N
), T
);
4765 elsif Is_Array_Type
(T
) then
4767 ("\provide initial value or explicit array bounds",
4768 Object_Definition
(N
));
4772 -- Case of initialization present but in error. Set initial
4773 -- expression as absent (but do not make above complaints).
4775 elsif E
= Error
then
4776 Set_Expression
(N
, Empty
);
4779 -- Case of initialization present
4782 -- Unconstrained variables not allowed in Ada 83
4784 if Ada_Version
= Ada_83
4785 and then not Constant_Present
(N
)
4786 and then Comes_From_Source
(Object_Definition
(N
))
4789 ("(Ada 83) unconstrained variable not allowed",
4790 Object_Definition
(N
));
4793 -- Now we constrain the variable from the initializing expression
4795 -- If the expression is an aggregate, it has been expanded into
4796 -- individual assignments. Retrieve the actual type from the
4797 -- expanded construct.
4799 if Is_Array_Type
(T
)
4800 and then No_Initialization
(N
)
4801 and then Nkind
(Original_Node
(E
)) = N_Aggregate
4805 -- In case of class-wide interface object declarations we delay
4806 -- the generation of the equivalent record type declarations until
4807 -- its expansion because there are cases in they are not required.
4809 elsif Is_Interface
(T
) then
4812 -- If the type is an unchecked union, no subtype can be built from
4813 -- the expression. Rewrite declaration as a renaming, which the
4814 -- back-end can handle properly. This is a rather unusual case,
4815 -- because most unchecked_union declarations have default values
4816 -- for discriminants and are thus not indefinite.
4818 elsif Is_Unchecked_Union
(T
) then
4819 if Constant_Present
(N
) or else Nkind
(E
) = N_Function_Call
then
4820 Mutate_Ekind
(Id
, E_Constant
);
4822 Mutate_Ekind
(Id
, E_Variable
);
4825 -- If the expression is an aggregate it contains the required
4826 -- discriminant values but it has not been resolved yet, so do
4827 -- it now, and treat it as the initial expression of an object
4828 -- declaration, rather than a renaming.
4830 if Nkind
(E
) = N_Aggregate
then
4831 Analyze_And_Resolve
(E
, T
);
4835 Make_Object_Renaming_Declaration
(Loc
,
4836 Defining_Identifier
=> Id
,
4837 Subtype_Mark
=> New_Occurrence_Of
(T
, Loc
),
4840 Set_Renamed_Object
(Id
, E
);
4841 Freeze_Before
(N
, T
);
4847 -- Ensure that the generated subtype has a unique external name
4848 -- when the related object is public. This guarantees that the
4849 -- subtype and its bounds will not be affected by switches or
4850 -- pragmas that may offset the internal counter due to extra
4853 if Is_Public
(Id
) then
4856 Related_Id
:= Empty
;
4859 -- If the object has an unconstrained array subtype with fixed
4860 -- lower bound, then sliding to that bound may be needed.
4862 if Is_Fixed_Lower_Bound_Array_Subtype
(T
) then
4863 Expand_Sliding_Conversion
(E
, T
);
4866 if In_Spec_Expression
and then In_Declare_Expr
> 0 then
4867 -- It is too early to be doing expansion-ish things,
4868 -- so exit early. But we have to set Ekind (Id) now so
4869 -- that subsequent uses of this entity are not rejected
4870 -- via the same mechanism that (correctly) rejects
4871 -- "X : Integer := X;".
4873 if Constant_Present
(N
) then
4874 Mutate_Ekind
(Id
, E_Constant
);
4875 Set_Is_True_Constant
(Id
);
4877 Mutate_Ekind
(Id
, E_Variable
);
4879 Set_Has_Initial_Value
(Id
);
4886 Expand_Subtype_From_Expr
4889 Subtype_Indic
=> Object_Definition
(N
),
4891 Related_Id
=> Related_Id
);
4893 Act_T
:= Find_Type_Of_Object
(Object_Definition
(N
), N
);
4898 Full_View_Present
: constant Boolean :=
4899 Is_Private_Type
(Act_T
)
4900 and then Present
(Full_View
(Act_T
));
4901 -- Propagate attributes to full view when needed
4904 Set_Is_Constr_Subt_For_U_Nominal
(Act_T
);
4906 if Full_View_Present
then
4907 Set_Is_Constr_Subt_For_U_Nominal
(Full_View
(Act_T
));
4910 if Aliased_Present
(N
) then
4911 Set_Is_Constr_Subt_For_UN_Aliased
(Act_T
);
4913 if Full_View_Present
then
4914 Set_Is_Constr_Subt_For_UN_Aliased
(Full_View
(Act_T
));
4918 Freeze_Before
(N
, Act_T
);
4922 Freeze_Before
(N
, T
);
4925 elsif Is_Array_Type
(T
)
4926 and then No_Initialization
(N
)
4927 and then (Nkind
(Original_Node
(E
)) = N_Aggregate
4928 or else (Nkind
(Original_Node
(E
)) = N_Qualified_Expression
4929 and then Nkind
(Original_Node
(Expression
4930 (Original_Node
(E
)))) = N_Aggregate
))
4932 if not Is_Entity_Name
(Object_Definition
(N
)) then
4934 Check_Compile_Time_Size
(Act_T
);
4937 -- When the given object definition and the aggregate are specified
4938 -- independently, and their lengths might differ do a length check.
4939 -- This cannot happen if the aggregate is of the form (others =>...)
4941 if Nkind
(E
) = N_Raise_Constraint_Error
then
4943 -- Aggregate is statically illegal. Place back in declaration
4945 Set_Expression
(N
, E
);
4946 Set_No_Initialization
(N
, False);
4948 elsif T
= Etype
(E
) then
4951 elsif Nkind
(E
) = N_Aggregate
4952 and then Present
(Component_Associations
(E
))
4953 and then Present
(Choice_List
(First
(Component_Associations
(E
))))
4955 Nkind
(First
(Choice_List
(First
(Component_Associations
(E
))))) =
4961 Apply_Length_Check
(E
, T
);
4964 -- When possible, build the default subtype
4966 elsif Build_Default_Subtype_OK
(T
) then
4968 Act_T
:= Build_Default_Subtype
(T
, N
);
4970 -- Ada 2005: A limited object may be initialized by means of an
4971 -- aggregate. If the type has default discriminants it has an
4972 -- unconstrained nominal type, Its actual subtype will be obtained
4973 -- from the aggregate, and not from the default discriminants.
4978 Rewrite
(Object_Definition
(N
), New_Occurrence_Of
(Act_T
, Loc
));
4979 Freeze_Before
(N
, Act_T
);
4981 elsif Nkind
(E
) = N_Function_Call
4982 and then Constant_Present
(N
)
4983 and then Has_Unconstrained_Elements
(Etype
(E
))
4985 -- The back-end has problems with constants of a discriminated type
4986 -- with defaults, if the initial value is a function call. We
4987 -- generate an intermediate temporary that will receive a reference
4988 -- to the result of the call. The initialization expression then
4989 -- becomes a dereference of that temporary.
4991 Remove_Side_Effects
(E
);
4993 -- If this is a constant declaration of an unconstrained type and
4994 -- the initialization is an aggregate, we can use the subtype of the
4995 -- aggregate for the declared entity because it is immutable.
4997 elsif not Is_Constrained
(T
)
4998 and then Has_Discriminants
(T
)
4999 and then Constant_Present
(N
)
5000 and then not Has_Unchecked_Union
(T
)
5001 and then Nkind
(E
) = N_Aggregate
5006 -- Check No_Wide_Characters restriction
5008 Check_Wide_Character_Restriction
(T
, Object_Definition
(N
));
5010 -- Indicate this is not set in source. Certainly true for constants, and
5011 -- true for variables so far (will be reset for a variable if and when
5012 -- we encounter a modification in the source).
5014 Set_Never_Set_In_Source
(Id
);
5016 -- Now establish the proper kind and type of the object
5018 if Ekind
(Id
) = E_Void
then
5019 Reinit_Field_To_Zero
(Id
, F_Next_Inlined_Subprogram
);
5022 if Constant_Present
(N
) then
5023 Mutate_Ekind
(Id
, E_Constant
);
5024 Set_Is_True_Constant
(Id
);
5027 Mutate_Ekind
(Id
, E_Variable
);
5029 -- A variable is set as shared passive if it appears in a shared
5030 -- passive package, and is at the outer level. This is not done for
5031 -- entities generated during expansion, because those are always
5032 -- manipulated locally.
5034 if Is_Shared_Passive
(Current_Scope
)
5035 and then Is_Library_Level_Entity
(Id
)
5036 and then Comes_From_Source
(Id
)
5038 Set_Is_Shared_Passive
(Id
);
5039 Check_Shared_Var
(Id
, T
, N
);
5042 -- Set Has_Initial_Value if initializing expression present. Note
5043 -- that if there is no initializing expression, we leave the state
5044 -- of this flag unchanged (usually it will be False, but notably in
5045 -- the case of exception choice variables, it will already be true).
5048 Set_Has_Initial_Value
(Id
);
5052 -- Set the SPARK mode from the current context (may be overwritten later
5053 -- with explicit pragma).
5055 Set_SPARK_Pragma
(Id
, SPARK_Mode_Pragma
);
5056 Set_SPARK_Pragma_Inherited
(Id
);
5058 -- Preserve relevant elaboration-related attributes of the context which
5059 -- are no longer available or very expensive to recompute once analysis,
5060 -- resolution, and expansion are over.
5062 Mark_Elaboration_Attributes
5067 -- Initialize alignment and size and capture alignment setting
5069 Reinit_Alignment
(Id
);
5071 Set_Optimize_Alignment_Flags
(Id
);
5073 -- Deal with aliased case
5075 if Aliased_Present
(N
) then
5076 Set_Is_Aliased
(Id
);
5078 -- AI12-001: All aliased objects are considered to be specified as
5079 -- independently addressable (RM C.6(8.1/4)).
5081 Set_Is_Independent
(Id
);
5083 -- If the object is aliased and the type is unconstrained with
5084 -- defaulted discriminants and there is no expression, then the
5085 -- object is constrained by the defaults, so it is worthwhile
5086 -- building the corresponding subtype.
5088 -- Ada 2005 (AI-363): If the aliased object is discriminated and
5089 -- unconstrained, then only establish an actual subtype if the
5090 -- nominal subtype is indefinite. In definite cases the object is
5091 -- unconstrained in Ada 2005.
5094 and then Is_Record_Type
(T
)
5095 and then not Is_Constrained
(T
)
5096 and then Has_Discriminants
(T
)
5097 and then (Ada_Version
< Ada_2005
5098 or else not Is_Definite_Subtype
(T
))
5100 Set_Actual_Subtype
(Id
, Build_Default_Subtype
(T
, N
));
5104 -- Now we can set the type of the object
5106 Set_Etype
(Id
, Act_T
);
5108 -- Non-constant object is marked to be treated as volatile if type is
5109 -- volatile and we clear the Current_Value setting that may have been
5110 -- set above. Doing so for constants isn't required and might interfere
5111 -- with possible uses of the object as a static expression in contexts
5112 -- incompatible with volatility (e.g. as a case-statement alternative).
5114 if Ekind
(Id
) /= E_Constant
and then Treat_As_Volatile
(Etype
(Id
)) then
5115 Set_Treat_As_Volatile
(Id
);
5116 Set_Current_Value
(Id
, Empty
);
5119 -- Deal with controlled types
5121 if Has_Controlled_Component
(Etype
(Id
))
5122 or else Is_Controlled
(Etype
(Id
))
5124 if not Is_Library_Level_Entity
(Id
) then
5125 Check_Restriction
(No_Nested_Finalization
, N
);
5127 Validate_Controlled_Object
(Id
);
5131 if Has_Task
(Etype
(Id
)) then
5132 Check_Restriction
(No_Tasking
, N
);
5134 -- Deal with counting max tasks
5136 -- Nothing to do if inside a generic
5138 if Inside_A_Generic
then
5141 -- If library level entity, then count tasks
5143 elsif Is_Library_Level_Entity
(Id
) then
5144 Check_Restriction
(Max_Tasks
, N
, Count_Tasks
(Etype
(Id
)));
5146 -- If not library level entity, then indicate we don't know max
5147 -- tasks and also check task hierarchy restriction and blocking
5148 -- operation (since starting a task is definitely blocking).
5151 Check_Restriction
(Max_Tasks
, N
);
5152 Check_Restriction
(No_Task_Hierarchy
, N
);
5153 Check_Potentially_Blocking_Operation
(N
);
5156 -- A rather specialized test. If we see two tasks being declared
5157 -- of the same type in the same object declaration, and the task
5158 -- has an entry with an address clause, we know that program error
5159 -- will be raised at run time since we can't have two tasks with
5160 -- entries at the same address.
5162 if Is_Task_Type
(Etype
(Id
)) and then More_Ids
(N
) then
5167 E
:= First_Entity
(Etype
(Id
));
5168 while Present
(E
) loop
5169 if Ekind
(E
) = E_Entry
5170 and then Present
(Get_Attribute_Definition_Clause
5171 (E
, Attribute_Address
))
5173 Error_Msg_Warn
:= SPARK_Mode
/= On
;
5175 ("more than one task with same entry address<<", N
);
5176 Error_Msg_N
("\Program_Error [<<", N
);
5178 Make_Raise_Program_Error
(Loc
,
5179 Reason
=> PE_Duplicated_Entry_Address
));
5189 -- Check specific legality rules for a return object
5191 if Is_Return_Object
(Id
) then
5192 Check_Return_Subtype_Indication
(N
);
5195 -- Some simple constant-propagation: if the expression is a constant
5196 -- string initialized with a literal, share the literal. This avoids
5200 and then Is_Entity_Name
(E
)
5201 and then Ekind
(Entity
(E
)) = E_Constant
5202 and then Base_Type
(Etype
(E
)) = Standard_String
5205 Val
: constant Node_Id
:= Constant_Value
(Entity
(E
));
5207 if Present
(Val
) and then Nkind
(Val
) = N_String_Literal
then
5208 Rewrite
(E
, New_Copy
(Val
));
5213 if Present
(Prev_Entity
)
5214 and then Is_Frozen
(Prev_Entity
)
5215 and then not Error_Posted
(Id
)
5217 Error_Msg_N
("full constant declaration appears too late", N
);
5220 Check_Eliminated
(Id
);
5222 -- Deal with setting In_Private_Part flag if in private part
5224 if Ekind
(Scope
(Id
)) = E_Package
5225 and then In_Private_Part
(Scope
(Id
))
5227 Set_In_Private_Part
(Id
);
5231 -- Initialize the refined state of a variable here because this is a
5232 -- common destination for legal and illegal object declarations.
5234 if Ekind
(Id
) = E_Variable
then
5235 Set_Encapsulating_State
(Id
, Empty
);
5238 if Has_Aspects
(N
) then
5239 Analyze_Aspect_Specifications
(N
, Id
);
5242 Analyze_Dimension
(N
);
5244 -- Verify whether the object declaration introduces an illegal hidden
5245 -- state within a package subject to a null abstract state.
5247 if Ekind
(Id
) = E_Variable
then
5248 Check_No_Hidden_State
(Id
);
5251 Restore_Ghost_Region
(Saved_GM
, Saved_IGR
);
5252 end Analyze_Object_Declaration
;
5254 ---------------------------
5255 -- Analyze_Others_Choice --
5256 ---------------------------
5258 -- Nothing to do for the others choice node itself, the semantic analysis
5259 -- of the others choice will occur as part of the processing of the parent
5261 procedure Analyze_Others_Choice
(N
: Node_Id
) is
5262 pragma Warnings
(Off
, N
);
5265 end Analyze_Others_Choice
;
5267 -------------------------------------------
5268 -- Analyze_Private_Extension_Declaration --
5269 -------------------------------------------
5271 procedure Analyze_Private_Extension_Declaration
(N
: Node_Id
) is
5272 Indic
: constant Node_Id
:= Subtype_Indication
(N
);
5273 T
: constant Entity_Id
:= Defining_Identifier
(N
);
5275 Iface_Elmt
: Elmt_Id
;
5276 Parent_Base
: Entity_Id
;
5277 Parent_Type
: Entity_Id
;
5280 -- Ada 2005 (AI-251): Decorate all names in list of ancestor interfaces
5282 if Is_Non_Empty_List
(Interface_List
(N
)) then
5288 Intf
:= First
(Interface_List
(N
));
5289 while Present
(Intf
) loop
5290 T
:= Find_Type_Of_Subtype_Indic
(Intf
);
5292 Diagnose_Interface
(Intf
, T
);
5298 Generate_Definition
(T
);
5300 -- For other than Ada 2012, just enter the name in the current scope
5302 if Ada_Version
< Ada_2012
then
5305 -- Ada 2012 (AI05-0162): Enter the name in the current scope handling
5306 -- case of private type that completes an incomplete type.
5313 Prev
:= Find_Type_Name
(N
);
5315 pragma Assert
(Prev
= T
5316 or else (Ekind
(Prev
) = E_Incomplete_Type
5317 and then Present
(Full_View
(Prev
))
5318 and then Full_View
(Prev
) = T
));
5322 Parent_Type
:= Find_Type_Of_Subtype_Indic
(Indic
);
5323 Parent_Base
:= Base_Type
(Parent_Type
);
5325 if Parent_Type
= Any_Type
or else Etype
(Parent_Type
) = Any_Type
then
5326 Mutate_Ekind
(T
, Ekind
(Parent_Type
));
5327 Set_Etype
(T
, Any_Type
);
5330 elsif not Is_Tagged_Type
(Parent_Type
) then
5332 ("parent of type extension must be a tagged type", Indic
);
5335 elsif Ekind
(Parent_Type
) in E_Void | E_Incomplete_Type
then
5336 Error_Msg_N
("premature derivation of incomplete type", Indic
);
5339 elsif Is_Concurrent_Type
(Parent_Type
) then
5341 ("parent type of a private extension cannot be a synchronized "
5342 & "tagged type (RM 3.9.1 (3/1))", N
);
5344 Set_Etype
(T
, Any_Type
);
5345 Mutate_Ekind
(T
, E_Limited_Private_Type
);
5346 Set_Private_Dependents
(T
, New_Elmt_List
);
5347 Set_Error_Posted
(T
);
5351 Check_Wide_Character_Restriction
(Parent_Type
, Indic
);
5353 -- Perhaps the parent type should be changed to the class-wide type's
5354 -- specific type in this case to prevent cascading errors ???
5356 if Is_Class_Wide_Type
(Parent_Type
) then
5358 ("parent of type extension must not be a class-wide type", Indic
);
5362 if (not Is_Package_Or_Generic_Package
(Current_Scope
)
5363 and then Nkind
(Parent
(N
)) /= N_Generic_Subprogram_Declaration
)
5364 or else In_Private_Part
(Current_Scope
)
5366 Error_Msg_N
("invalid context for private extension", N
);
5369 -- Set common attributes
5371 Set_Is_Pure
(T
, Is_Pure
(Current_Scope
));
5372 Set_Scope
(T
, Current_Scope
);
5373 Mutate_Ekind
(T
, E_Record_Type_With_Private
);
5374 Reinit_Size_Align
(T
);
5375 Set_Default_SSO
(T
);
5376 Set_No_Reordering
(T
, No_Component_Reordering
);
5378 Set_Etype
(T
, Parent_Base
);
5379 Propagate_Concurrent_Flags
(T
, Parent_Base
);
5381 Set_Convention
(T
, Convention
(Parent_Type
));
5382 Set_First_Rep_Item
(T
, First_Rep_Item
(Parent_Type
));
5383 Set_Is_First_Subtype
(T
);
5385 -- Set the SPARK mode from the current context
5387 Set_SPARK_Pragma
(T
, SPARK_Mode_Pragma
);
5388 Set_SPARK_Pragma_Inherited
(T
);
5390 if Unknown_Discriminants_Present
(N
) then
5391 Set_Discriminant_Constraint
(T
, No_Elist
);
5394 Build_Derived_Record_Type
(N
, Parent_Type
, T
);
5396 -- A private extension inherits the Default_Initial_Condition pragma
5397 -- coming from any parent type within the derivation chain.
5399 if Has_DIC
(Parent_Type
) then
5400 Set_Has_Inherited_DIC
(T
);
5403 -- A private extension inherits any class-wide invariants coming from a
5404 -- parent type or an interface. Note that the invariant procedure of the
5405 -- parent type should not be inherited because the private extension may
5406 -- define invariants of its own.
5408 if Has_Inherited_Invariants
(Parent_Type
)
5409 or else Has_Inheritable_Invariants
(Parent_Type
)
5411 Set_Has_Inherited_Invariants
(T
);
5413 elsif Present
(Interfaces
(T
)) then
5414 Iface_Elmt
:= First_Elmt
(Interfaces
(T
));
5415 while Present
(Iface_Elmt
) loop
5416 Iface
:= Node
(Iface_Elmt
);
5418 if Has_Inheritable_Invariants
(Iface
) then
5419 Set_Has_Inherited_Invariants
(T
);
5423 Next_Elmt
(Iface_Elmt
);
5427 -- Ada 2005 (AI-443): Synchronized private extension or a rewritten
5428 -- synchronized formal derived type.
5430 if Ada_Version
>= Ada_2005
and then Synchronized_Present
(N
) then
5431 Set_Is_Limited_Record
(T
);
5433 -- Formal derived type case
5435 if Is_Generic_Type
(T
) then
5437 -- The parent must be a tagged limited type or a synchronized
5440 if (not Is_Tagged_Type
(Parent_Type
)
5441 or else not Is_Limited_Type
(Parent_Type
))
5443 (not Is_Interface
(Parent_Type
)
5444 or else not Is_Synchronized_Interface
(Parent_Type
))
5447 ("parent type of & must be tagged limited or synchronized",
5451 -- The progenitors (if any) must be limited or synchronized
5454 if Present
(Interfaces
(T
)) then
5455 Iface_Elmt
:= First_Elmt
(Interfaces
(T
));
5456 while Present
(Iface_Elmt
) loop
5457 Iface
:= Node
(Iface_Elmt
);
5459 if not Is_Limited_Interface
(Iface
)
5460 and then not Is_Synchronized_Interface
(Iface
)
5463 ("progenitor & must be limited or synchronized",
5467 Next_Elmt
(Iface_Elmt
);
5471 -- Regular derived extension, the parent must be a limited or
5472 -- synchronized interface.
5475 if not Is_Interface
(Parent_Type
)
5476 or else (not Is_Limited_Interface
(Parent_Type
)
5477 and then not Is_Synchronized_Interface
(Parent_Type
))
5480 ("parent type of & must be limited interface", N
, T
);
5484 -- A consequence of 3.9.4 (6/2) and 7.3 (7.2/2) is that a private
5485 -- extension with a synchronized parent must be explicitly declared
5486 -- synchronized, because the full view will be a synchronized type.
5487 -- This must be checked before the check for limited types below,
5488 -- to ensure that types declared limited are not allowed to extend
5489 -- synchronized interfaces.
5491 elsif Is_Interface
(Parent_Type
)
5492 and then Is_Synchronized_Interface
(Parent_Type
)
5493 and then not Synchronized_Present
(N
)
5496 ("private extension of& must be explicitly synchronized",
5499 elsif Limited_Present
(N
) then
5500 Set_Is_Limited_Record
(T
);
5502 if not Is_Limited_Type
(Parent_Type
)
5504 (not Is_Interface
(Parent_Type
)
5505 or else not Is_Limited_Interface
(Parent_Type
))
5507 Error_Msg_NE
("parent type& of limited extension must be limited",
5512 -- Remember that its parent type has a private extension. Used to warn
5513 -- on public primitives of the parent type defined after its private
5514 -- extensions (see Check_Dispatching_Operation).
5516 Set_Has_Private_Extension
(Parent_Type
);
5519 if Has_Aspects
(N
) then
5520 Analyze_Aspect_Specifications
(N
, T
);
5522 end Analyze_Private_Extension_Declaration
;
5524 ---------------------------------
5525 -- Analyze_Subtype_Declaration --
5526 ---------------------------------
5528 procedure Analyze_Subtype_Declaration
5530 Skip
: Boolean := False)
5532 Id
: constant Entity_Id
:= Defining_Identifier
(N
);
5536 Generate_Definition
(Id
);
5537 Set_Is_Pure
(Id
, Is_Pure
(Current_Scope
));
5538 Reinit_Size_Align
(Id
);
5540 -- The following guard condition on Enter_Name is to handle cases where
5541 -- the defining identifier has already been entered into the scope but
5542 -- the declaration as a whole needs to be analyzed.
5544 -- This case in particular happens for derived enumeration types. The
5545 -- derived enumeration type is processed as an inserted enumeration type
5546 -- declaration followed by a rewritten subtype declaration. The defining
5547 -- identifier, however, is entered into the name scope very early in the
5548 -- processing of the original type declaration and therefore needs to be
5549 -- avoided here, when the created subtype declaration is analyzed. (See
5550 -- Build_Derived_Types)
5552 -- This also happens when the full view of a private type is a derived
5553 -- type with constraints. In this case the entity has been introduced
5554 -- in the private declaration.
5556 -- Finally this happens in some complex cases when validity checks are
5557 -- enabled, where the same subtype declaration may be analyzed twice.
5558 -- This can happen if the subtype is created by the preanalysis of
5559 -- an attribute that gives the range of a loop statement, and the loop
5560 -- itself appears within an if_statement that will be rewritten during
5564 or else (Present
(Etype
(Id
))
5565 and then (Is_Private_Type
(Etype
(Id
))
5566 or else Is_Task_Type
(Etype
(Id
))
5567 or else Is_Rewrite_Substitution
(N
)))
5571 elsif Current_Entity
(Id
) = Id
then
5578 T
:= Process_Subtype
(Subtype_Indication
(N
), N
, Id
, 'P');
5580 -- Class-wide equivalent types of records with unknown discriminants
5581 -- involve the generation of an itype which serves as the private view
5582 -- of a constrained record subtype. In such cases the base type of the
5583 -- current subtype we are processing is the private itype. Use the full
5584 -- of the private itype when decorating various attributes.
5587 and then Is_Private_Type
(T
)
5588 and then Present
(Full_View
(T
))
5593 -- Inherit common attributes
5595 Set_Is_Volatile
(Id
, Is_Volatile
(T
));
5596 Set_Treat_As_Volatile
(Id
, Treat_As_Volatile
(T
));
5597 Set_Is_Generic_Type
(Id
, Is_Generic_Type
(Base_Type
(T
)));
5598 Set_Convention
(Id
, Convention
(T
));
5600 -- If ancestor has predicates then so does the subtype, and in addition
5601 -- we must delay the freeze to properly arrange predicate inheritance.
5603 -- The Ancestor_Type test is really unpleasant, there seem to be cases
5604 -- in which T = ID, so the above tests and assignments do nothing???
5606 if Has_Predicates
(T
)
5607 or else (Present
(Ancestor_Subtype
(T
))
5608 and then Has_Predicates
(Ancestor_Subtype
(T
)))
5610 Set_Has_Predicates
(Id
);
5611 Set_Has_Delayed_Freeze
(Id
);
5613 -- Generated subtypes inherit the predicate function from the parent
5614 -- (no aspects to examine on the generated declaration).
5616 if not Comes_From_Source
(N
) then
5617 Mutate_Ekind
(Id
, Ekind
(T
));
5619 if Present
(Predicate_Function
(Id
)) then
5622 elsif Present
(Predicate_Function
(T
)) then
5623 Set_Predicate_Function
(Id
, Predicate_Function
(T
));
5625 elsif Present
(Ancestor_Subtype
(T
))
5626 and then Present
(Predicate_Function
(Ancestor_Subtype
(T
)))
5628 Set_Predicate_Function
(Id
,
5629 Predicate_Function
(Ancestor_Subtype
(T
)));
5634 -- In the case where there is no constraint given in the subtype
5635 -- indication, Process_Subtype just returns the Subtype_Mark, so its
5636 -- semantic attributes must be established here.
5638 if Nkind
(Subtype_Indication
(N
)) /= N_Subtype_Indication
then
5639 Set_Etype
(Id
, Base_Type
(T
));
5643 Mutate_Ekind
(Id
, E_Array_Subtype
);
5644 Copy_Array_Subtype_Attributes
(Id
, T
);
5645 Set_Packed_Array_Impl_Type
(Id
, Packed_Array_Impl_Type
(T
));
5647 when Decimal_Fixed_Point_Kind
=>
5648 Mutate_Ekind
(Id
, E_Decimal_Fixed_Point_Subtype
);
5649 Set_Digits_Value
(Id
, Digits_Value
(T
));
5650 Set_Delta_Value
(Id
, Delta_Value
(T
));
5651 Set_Scale_Value
(Id
, Scale_Value
(T
));
5652 Set_Small_Value
(Id
, Small_Value
(T
));
5653 Set_Scalar_Range
(Id
, Scalar_Range
(T
));
5654 Set_Machine_Radix_10
(Id
, Machine_Radix_10
(T
));
5655 Set_Is_Constrained
(Id
, Is_Constrained
(T
));
5656 Set_Is_Known_Valid
(Id
, Is_Known_Valid
(T
));
5657 Copy_RM_Size
(To
=> Id
, From
=> T
);
5659 when Enumeration_Kind
=>
5660 Mutate_Ekind
(Id
, E_Enumeration_Subtype
);
5661 Set_First_Literal
(Id
, First_Literal
(Base_Type
(T
)));
5662 Set_Scalar_Range
(Id
, Scalar_Range
(T
));
5663 Set_Is_Character_Type
(Id
, Is_Character_Type
(T
));
5664 Set_Is_Constrained
(Id
, Is_Constrained
(T
));
5665 Set_Is_Known_Valid
(Id
, Is_Known_Valid
(T
));
5666 Copy_RM_Size
(To
=> Id
, From
=> T
);
5668 when Ordinary_Fixed_Point_Kind
=>
5669 Mutate_Ekind
(Id
, E_Ordinary_Fixed_Point_Subtype
);
5670 Set_Scalar_Range
(Id
, Scalar_Range
(T
));
5671 Set_Small_Value
(Id
, Small_Value
(T
));
5672 Set_Delta_Value
(Id
, Delta_Value
(T
));
5673 Set_Is_Constrained
(Id
, Is_Constrained
(T
));
5674 Set_Is_Known_Valid
(Id
, Is_Known_Valid
(T
));
5675 Copy_RM_Size
(To
=> Id
, From
=> T
);
5678 Mutate_Ekind
(Id
, E_Floating_Point_Subtype
);
5679 Set_Scalar_Range
(Id
, Scalar_Range
(T
));
5680 Set_Digits_Value
(Id
, Digits_Value
(T
));
5681 Set_Is_Constrained
(Id
, Is_Constrained
(T
));
5683 -- If the floating point type has dimensions, these will be
5684 -- inherited subsequently when Analyze_Dimensions is called.
5686 when Signed_Integer_Kind
=>
5687 Mutate_Ekind
(Id
, E_Signed_Integer_Subtype
);
5688 Set_Scalar_Range
(Id
, Scalar_Range
(T
));
5689 Set_Is_Constrained
(Id
, Is_Constrained
(T
));
5690 Set_Is_Known_Valid
(Id
, Is_Known_Valid
(T
));
5691 Copy_RM_Size
(To
=> Id
, From
=> T
);
5693 when Modular_Integer_Kind
=>
5694 Mutate_Ekind
(Id
, E_Modular_Integer_Subtype
);
5695 Set_Scalar_Range
(Id
, Scalar_Range
(T
));
5696 Set_Is_Constrained
(Id
, Is_Constrained
(T
));
5697 Set_Is_Known_Valid
(Id
, Is_Known_Valid
(T
));
5698 Copy_RM_Size
(To
=> Id
, From
=> T
);
5700 when Class_Wide_Kind
=>
5701 Mutate_Ekind
(Id
, E_Class_Wide_Subtype
);
5702 Set_Class_Wide_Type
(Id
, Class_Wide_Type
(T
));
5703 Set_Cloned_Subtype
(Id
, T
);
5704 Set_Is_Tagged_Type
(Id
, True);
5705 Set_Is_Limited_Record
(Id
, Is_Limited_Record
(T
));
5706 Set_Has_Unknown_Discriminants
5708 Set_No_Tagged_Streams_Pragma
5709 (Id
, No_Tagged_Streams_Pragma
(T
));
5711 if Ekind
(T
) = E_Class_Wide_Subtype
then
5712 Set_Equivalent_Type
(Id
, Equivalent_Type
(T
));
5715 when E_Record_Subtype
5718 Mutate_Ekind
(Id
, E_Record_Subtype
);
5720 -- Subtype declarations introduced for formal type parameters
5721 -- in generic instantiations should inherit the Size value of
5722 -- the type they rename.
5724 if Present
(Generic_Parent_Type
(N
)) then
5725 Copy_RM_Size
(To
=> Id
, From
=> T
);
5728 if Ekind
(T
) = E_Record_Subtype
5729 and then Present
(Cloned_Subtype
(T
))
5731 Set_Cloned_Subtype
(Id
, Cloned_Subtype
(T
));
5733 Set_Cloned_Subtype
(Id
, T
);
5736 Set_First_Entity
(Id
, First_Entity
(T
));
5737 Set_Last_Entity
(Id
, Last_Entity
(T
));
5738 Set_Has_Discriminants
(Id
, Has_Discriminants
(T
));
5739 Set_Is_Constrained
(Id
, Is_Constrained
(T
));
5740 Set_Is_Limited_Record
(Id
, Is_Limited_Record
(T
));
5741 Set_Has_Implicit_Dereference
5742 (Id
, Has_Implicit_Dereference
(T
));
5743 Set_Has_Unknown_Discriminants
5744 (Id
, Has_Unknown_Discriminants
(T
));
5746 if Has_Discriminants
(T
) then
5747 Set_Discriminant_Constraint
5748 (Id
, Discriminant_Constraint
(T
));
5749 Set_Stored_Constraint_From_Discriminant_Constraint
(Id
);
5751 elsif Has_Unknown_Discriminants
(Id
) then
5752 Set_Discriminant_Constraint
(Id
, No_Elist
);
5755 if Is_Tagged_Type
(T
) then
5756 Set_Is_Tagged_Type
(Id
, True);
5757 Set_No_Tagged_Streams_Pragma
5758 (Id
, No_Tagged_Streams_Pragma
(T
));
5759 Set_Is_Abstract_Type
(Id
, Is_Abstract_Type
(T
));
5760 Set_Direct_Primitive_Operations
5761 (Id
, Direct_Primitive_Operations
(T
));
5762 Set_Class_Wide_Type
(Id
, Class_Wide_Type
(T
));
5764 if Is_Interface
(T
) then
5765 Set_Is_Interface
(Id
);
5766 Set_Is_Limited_Interface
(Id
, Is_Limited_Interface
(T
));
5770 when Private_Kind
=>
5771 Mutate_Ekind
(Id
, Subtype_Kind
(Ekind
(T
)));
5772 Set_Has_Discriminants
(Id
, Has_Discriminants
(T
));
5773 Set_Is_Constrained
(Id
, Is_Constrained
(T
));
5774 Set_First_Entity
(Id
, First_Entity
(T
));
5775 Set_Last_Entity
(Id
, Last_Entity
(T
));
5776 Set_Private_Dependents
(Id
, New_Elmt_List
);
5777 Set_Is_Limited_Record
(Id
, Is_Limited_Record
(T
));
5778 Set_Has_Implicit_Dereference
5779 (Id
, Has_Implicit_Dereference
(T
));
5780 Set_Has_Unknown_Discriminants
5781 (Id
, Has_Unknown_Discriminants
(T
));
5782 Set_Known_To_Have_Preelab_Init
5783 (Id
, Known_To_Have_Preelab_Init
(T
));
5785 if Is_Tagged_Type
(T
) then
5786 Set_Is_Tagged_Type
(Id
);
5787 Set_No_Tagged_Streams_Pragma
(Id
,
5788 No_Tagged_Streams_Pragma
(T
));
5789 Set_Is_Abstract_Type
(Id
, Is_Abstract_Type
(T
));
5790 Set_Class_Wide_Type
(Id
, Class_Wide_Type
(T
));
5791 Set_Direct_Primitive_Operations
(Id
,
5792 Direct_Primitive_Operations
(T
));
5795 -- In general the attributes of the subtype of a private type
5796 -- are the attributes of the partial view of parent. However,
5797 -- the full view may be a discriminated type, and the subtype
5798 -- must share the discriminant constraint to generate correct
5799 -- calls to initialization procedures.
5801 if Has_Discriminants
(T
) then
5802 Set_Discriminant_Constraint
5803 (Id
, Discriminant_Constraint
(T
));
5804 Set_Stored_Constraint_From_Discriminant_Constraint
(Id
);
5806 elsif Present
(Full_View
(T
))
5807 and then Has_Discriminants
(Full_View
(T
))
5809 Set_Discriminant_Constraint
5810 (Id
, Discriminant_Constraint
(Full_View
(T
)));
5811 Set_Stored_Constraint_From_Discriminant_Constraint
(Id
);
5813 -- This would seem semantically correct, but apparently
5814 -- generates spurious errors about missing components ???
5816 -- Set_Has_Discriminants (Id);
5819 Prepare_Private_Subtype_Completion
(Id
, N
);
5821 -- If this is the subtype of a constrained private type with
5822 -- discriminants that has got a full view and we also have
5823 -- built a completion just above, show that the completion
5824 -- is a clone of the full view to the back-end.
5826 if Has_Discriminants
(T
)
5827 and then not Has_Unknown_Discriminants
(T
)
5828 and then not Is_Empty_Elmt_List
(Discriminant_Constraint
(T
))
5829 and then Present
(Full_View
(T
))
5830 and then Present
(Full_View
(Id
))
5832 Set_Cloned_Subtype
(Full_View
(Id
), Full_View
(T
));
5836 Mutate_Ekind
(Id
, E_Access_Subtype
);
5837 Set_Is_Constrained
(Id
, Is_Constrained
(T
));
5838 Set_Is_Access_Constant
5839 (Id
, Is_Access_Constant
(T
));
5840 Set_Directly_Designated_Type
5841 (Id
, Designated_Type
(T
));
5842 Set_Can_Never_Be_Null
(Id
, Can_Never_Be_Null
(T
));
5844 -- A Pure library_item must not contain the declaration of a
5845 -- named access type, except within a subprogram, generic
5846 -- subprogram, task unit, or protected unit, or if it has
5847 -- a specified Storage_Size of zero (RM05-10.2.1(15.4-15.5)).
5849 if Comes_From_Source
(Id
)
5850 and then In_Pure_Unit
5851 and then not In_Subprogram_Task_Protected_Unit
5852 and then not No_Pool_Assigned
(Id
)
5855 ("named access types not allowed in pure unit", N
);
5858 when Concurrent_Kind
=>
5859 Mutate_Ekind
(Id
, Subtype_Kind
(Ekind
(T
)));
5860 Set_Corresponding_Record_Type
(Id
,
5861 Corresponding_Record_Type
(T
));
5862 Set_First_Entity
(Id
, First_Entity
(T
));
5863 Set_First_Private_Entity
(Id
, First_Private_Entity
(T
));
5864 Set_Has_Discriminants
(Id
, Has_Discriminants
(T
));
5865 Set_Is_Constrained
(Id
, Is_Constrained
(T
));
5866 Set_Is_Tagged_Type
(Id
, Is_Tagged_Type
(T
));
5867 Set_Last_Entity
(Id
, Last_Entity
(T
));
5869 if Is_Tagged_Type
(T
) then
5870 Set_No_Tagged_Streams_Pragma
5871 (Id
, No_Tagged_Streams_Pragma
(T
));
5874 if Has_Discriminants
(T
) then
5875 Set_Discriminant_Constraint
5876 (Id
, Discriminant_Constraint
(T
));
5877 Set_Stored_Constraint_From_Discriminant_Constraint
(Id
);
5880 when Incomplete_Kind
=>
5881 if Ada_Version
>= Ada_2005
then
5883 -- In Ada 2005 an incomplete type can be explicitly tagged:
5884 -- propagate indication. Note that we also have to include
5885 -- subtypes for Ada 2012 extended use of incomplete types.
5887 Mutate_Ekind
(Id
, E_Incomplete_Subtype
);
5888 Set_Is_Tagged_Type
(Id
, Is_Tagged_Type
(T
));
5889 Set_Private_Dependents
(Id
, New_Elmt_List
);
5891 if Is_Tagged_Type
(Id
) then
5892 Set_No_Tagged_Streams_Pragma
5893 (Id
, No_Tagged_Streams_Pragma
(T
));
5896 -- For tagged types, or when prefixed-call syntax is allowed
5897 -- for untagged types, initialize the list of primitive
5898 -- operations to an empty list.
5900 if Is_Tagged_Type
(Id
)
5901 or else Core_Extensions_Allowed
5903 Set_Direct_Primitive_Operations
(Id
, New_Elmt_List
);
5906 -- Ada 2005 (AI-412): Decorate an incomplete subtype of an
5907 -- incomplete type visible through a limited with clause.
5909 if From_Limited_With
(T
)
5910 and then Present
(Non_Limited_View
(T
))
5912 Set_From_Limited_With
(Id
);
5913 Set_Non_Limited_View
(Id
, Non_Limited_View
(T
));
5915 -- Ada 2005 (AI-412): Add the regular incomplete subtype
5916 -- to the private dependents of the original incomplete
5917 -- type for future transformation.
5920 Append_Elmt
(Id
, Private_Dependents
(T
));
5923 -- If the subtype name denotes an incomplete type an error
5924 -- was already reported by Process_Subtype.
5927 Set_Etype
(Id
, Any_Type
);
5931 raise Program_Error
;
5934 -- If there is no constraint in the subtype indication, the
5935 -- declared entity inherits predicates from the parent.
5937 Inherit_Predicate_Flags
(Id
, T
);
5940 if Etype
(Id
) = Any_Type
then
5944 -- When prefixed calls are enabled for untagged types, the subtype
5945 -- shares the primitive operations of its base type. Do this even
5946 -- when Extensions_Allowed is False to issue better error messages.
5948 Set_Direct_Primitive_Operations
5949 (Id
, Direct_Primitive_Operations
(Base_Type
(T
)));
5951 -- Some common processing on all types
5953 Set_Size_Info
(Id
, T
);
5954 Set_First_Rep_Item
(Id
, First_Rep_Item
(T
));
5956 -- If the parent type is a generic actual, so is the subtype. This may
5957 -- happen in a nested instance. Why Comes_From_Source test???
5959 if not Comes_From_Source
(N
) then
5960 Set_Is_Generic_Actual_Type
(Id
, Is_Generic_Actual_Type
(T
));
5963 -- If this is a subtype declaration for an actual in an instance,
5964 -- inherit static and dynamic predicates if any.
5966 -- If declaration has no aspect specifications, inherit predicate
5967 -- info as well. Unclear how to handle the case of both specified
5968 -- and inherited predicates ??? Other inherited aspects, such as
5969 -- invariants, should be OK, but the combination with later pragmas
5970 -- may also require special merging.
5972 if Has_Predicates
(T
)
5973 and then Present
(Predicate_Function
(T
))
5975 ((In_Instance
and then not Comes_From_Source
(N
))
5976 or else No
(Aspect_Specifications
(N
)))
5978 -- Inherit Subprograms_For_Type from the full view, if present
5980 if Present
(Full_View
(T
))
5981 and then Present
(Subprograms_For_Type
(Full_View
(T
)))
5983 Set_Subprograms_For_Type
5984 (Id
, Subprograms_For_Type
(Full_View
(T
)));
5986 Set_Subprograms_For_Type
(Id
, Subprograms_For_Type
(T
));
5989 -- If the current declaration created both a private and a full view,
5990 -- then propagate Predicate_Function to the latter as well.
5992 if Present
(Full_View
(Id
))
5993 and then No
(Predicate_Function
(Full_View
(Id
)))
5995 Set_Subprograms_For_Type
5996 (Full_View
(Id
), Subprograms_For_Type
(Id
));
5999 if Has_Static_Predicate
(T
) then
6000 Set_Has_Static_Predicate
(Id
);
6001 Set_Static_Discrete_Predicate
(Id
, Static_Discrete_Predicate
(T
));
6005 -- If the base type is a scalar type, or else if there is no
6006 -- constraint, the atomic flag is inherited by the subtype.
6007 -- Ditto for the Independent aspect.
6009 if Is_Scalar_Type
(Id
)
6010 or else Is_Entity_Name
(Subtype_Indication
(N
))
6012 Set_Is_Atomic
(Id
, Is_Atomic
(T
));
6013 Set_Is_Independent
(Id
, Is_Independent
(T
));
6016 -- Remaining processing depends on characteristics of base type
6020 Set_Is_Immediately_Visible
(Id
, True);
6021 Set_Depends_On_Private
(Id
, Has_Private_Component
(T
));
6022 Set_Is_Descendant_Of_Address
(Id
, Is_Descendant_Of_Address
(T
));
6024 if Is_Interface
(T
) then
6025 Set_Is_Interface
(Id
);
6026 Set_Is_Limited_Interface
(Id
, Is_Limited_Interface
(T
));
6029 if Present
(Generic_Parent_Type
(N
))
6031 (Nkind
(Parent
(Generic_Parent_Type
(N
))) /=
6032 N_Formal_Type_Declaration
6033 or else Nkind
(Formal_Type_Definition
6034 (Parent
(Generic_Parent_Type
(N
)))) /=
6035 N_Formal_Private_Type_Definition
)
6037 if Is_Tagged_Type
(Id
) then
6039 -- If this is a generic actual subtype for a synchronized type,
6040 -- the primitive operations are those of the corresponding record
6041 -- for which there is a separate subtype declaration.
6043 if Is_Concurrent_Type
(Id
) then
6045 elsif Is_Class_Wide_Type
(Id
) then
6046 Derive_Subprograms
(Generic_Parent_Type
(N
), Id
, Etype
(T
));
6048 Derive_Subprograms
(Generic_Parent_Type
(N
), Id
, T
);
6051 elsif Scope
(Etype
(Id
)) /= Standard_Standard
then
6052 Derive_Subprograms
(Generic_Parent_Type
(N
), Id
);
6056 if Is_Private_Type
(T
) and then Present
(Full_View
(T
)) then
6057 Conditional_Delay
(Id
, Full_View
(T
));
6059 -- The subtypes of components or subcomponents of protected types
6060 -- do not need freeze nodes, which would otherwise appear in the
6061 -- wrong scope (before the freeze node for the protected type). The
6062 -- proper subtypes are those of the subcomponents of the corresponding
6065 elsif Ekind
(Scope
(Id
)) /= E_Protected_Type
6066 and then Present
(Scope
(Scope
(Id
))) -- error defense
6067 and then Ekind
(Scope
(Scope
(Id
))) /= E_Protected_Type
6069 Conditional_Delay
(Id
, T
);
6072 -- If we have a subtype of an incomplete type whose full type is a
6073 -- derived numeric type, we need to have a freeze node for the subtype.
6074 -- Otherwise gigi will complain while computing the (static) bounds of
6078 and then Is_Elementary_Type
(Id
)
6079 and then Etype
(Id
) /= Id
6082 Partial
: constant Entity_Id
:=
6083 Incomplete_Or_Partial_View
(First_Subtype
(Id
));
6085 if Present
(Partial
)
6086 and then Ekind
(Partial
) = E_Incomplete_Type
6088 Set_Has_Delayed_Freeze
(Id
);
6093 -- Check that Constraint_Error is raised for a scalar subtype indication
6094 -- when the lower or upper bound of a non-null range lies outside the
6095 -- range of the type mark. Likewise for an array subtype, but check the
6096 -- compatibility for each index.
6098 if Nkind
(Subtype_Indication
(N
)) = N_Subtype_Indication
then
6100 Indic_Typ
: constant Entity_Id
:=
6101 Underlying_Type
(Etype
(Subtype_Mark
(Subtype_Indication
(N
))));
6102 Subt_Index
: Node_Id
;
6103 Target_Index
: Node_Id
;
6106 if Is_Scalar_Type
(Etype
(Id
))
6107 and then Scalar_Range
(Id
) /= Scalar_Range
(Indic_Typ
)
6109 Apply_Range_Check
(Scalar_Range
(Id
), Indic_Typ
);
6111 elsif Is_Array_Type
(Etype
(Id
))
6112 and then Present
(First_Index
(Id
))
6114 Subt_Index
:= First_Index
(Id
);
6115 Target_Index
:= First_Index
(Indic_Typ
);
6117 while Present
(Subt_Index
) loop
6118 if ((Nkind
(Subt_Index
) in N_Expanded_Name | N_Identifier
6119 and then Is_Scalar_Type
(Entity
(Subt_Index
)))
6120 or else Nkind
(Subt_Index
) = N_Subtype_Indication
)
6122 Nkind
(Scalar_Range
(Etype
(Subt_Index
))) = N_Range
6125 (Scalar_Range
(Etype
(Subt_Index
)),
6126 Etype
(Target_Index
),
6130 Next_Index
(Subt_Index
);
6131 Next_Index
(Target_Index
);
6137 Set_Optimize_Alignment_Flags
(Id
);
6138 Check_Eliminated
(Id
);
6141 if Has_Aspects
(N
) then
6142 Analyze_Aspect_Specifications
(N
, Id
);
6145 Analyze_Dimension
(N
);
6147 -- Check No_Dynamic_Sized_Objects restriction, which disallows subtype
6148 -- indications on composite types where the constraints are dynamic.
6149 -- Note that object declarations and aggregates generate implicit
6150 -- subtype declarations, which this covers. One special case is that the
6151 -- implicitly generated "=" for discriminated types includes an
6152 -- offending subtype declaration, which is harmless, so we ignore it
6155 if Nkind
(Subtype_Indication
(N
)) = N_Subtype_Indication
then
6157 Cstr
: constant Node_Id
:= Constraint
(Subtype_Indication
(N
));
6159 if Nkind
(Cstr
) = N_Index_Or_Discriminant_Constraint
6160 and then not (Is_Internal
(Id
)
6161 and then Is_TSS
(Scope
(Id
),
6162 TSS_Composite_Equality
))
6163 and then not Within_Init_Proc
6164 and then not All_Composite_Constraints_Static
(Cstr
)
6166 Check_Restriction
(No_Dynamic_Sized_Objects
, Cstr
);
6170 end Analyze_Subtype_Declaration
;
6172 --------------------------------
6173 -- Analyze_Subtype_Indication --
6174 --------------------------------
6176 procedure Analyze_Subtype_Indication
(N
: Node_Id
) is
6177 T
: constant Entity_Id
:= Subtype_Mark
(N
);
6178 R
: constant Node_Id
:= Range_Expression
(Constraint
(N
));
6184 Set_Error_Posted
(R
);
6185 Set_Error_Posted
(T
);
6188 Set_Etype
(N
, Etype
(R
));
6189 Resolve
(R
, Entity
(T
));
6191 end Analyze_Subtype_Indication
;
6193 --------------------------
6194 -- Analyze_Variant_Part --
6195 --------------------------
6197 procedure Analyze_Variant_Part
(N
: Node_Id
) is
6198 Discr_Name
: Node_Id
;
6199 Discr_Type
: Entity_Id
;
6201 procedure Process_Variant
(A
: Node_Id
);
6202 -- Analyze declarations for a single variant
6204 package Analyze_Variant_Choices
is
6205 new Generic_Analyze_Choices
(Process_Variant
);
6206 use Analyze_Variant_Choices
;
6208 ---------------------
6209 -- Process_Variant --
6210 ---------------------
6212 procedure Process_Variant
(A
: Node_Id
) is
6213 CL
: constant Node_Id
:= Component_List
(A
);
6215 if not Null_Present
(CL
) then
6216 Analyze_Declarations
(Component_Items
(CL
));
6218 if Present
(Variant_Part
(CL
)) then
6219 Analyze
(Variant_Part
(CL
));
6222 end Process_Variant
;
6224 -- Start of processing for Analyze_Variant_Part
6227 Discr_Name
:= Name
(N
);
6228 Analyze
(Discr_Name
);
6230 -- If Discr_Name bad, get out (prevent cascaded errors)
6232 if Etype
(Discr_Name
) = Any_Type
then
6236 -- Check invalid discriminant in variant part
6238 if Ekind
(Entity
(Discr_Name
)) /= E_Discriminant
then
6239 Error_Msg_N
("invalid discriminant name in variant part", Discr_Name
);
6242 Discr_Type
:= Etype
(Entity
(Discr_Name
));
6244 if not Is_Discrete_Type
(Discr_Type
) then
6246 ("discriminant in a variant part must be of a discrete type",
6251 -- Now analyze the choices, which also analyzes the declarations that
6252 -- are associated with each choice.
6254 Analyze_Choices
(Variants
(N
), Discr_Type
);
6256 -- Note: we used to instantiate and call Check_Choices here to check
6257 -- that the choices covered the discriminant, but it's too early to do
6258 -- that because of statically predicated subtypes, whose analysis may
6259 -- be deferred to their freeze point which may be as late as the freeze
6260 -- point of the containing record. So this call is now to be found in
6261 -- Freeze_Record_Declaration.
6263 end Analyze_Variant_Part
;
6265 ----------------------------
6266 -- Array_Type_Declaration --
6267 ----------------------------
6269 procedure Array_Type_Declaration
(T
: in out Entity_Id
; Def
: Node_Id
) is
6270 Component_Def
: constant Node_Id
:= Component_Definition
(Def
);
6271 Component_Typ
: constant Node_Id
:= Subtype_Indication
(Component_Def
);
6272 P
: constant Node_Id
:= Parent
(Def
);
6273 Element_Type
: Entity_Id
;
6274 Implicit_Base
: Entity_Id
;
6278 Related_Id
: Entity_Id
;
6279 Has_FLB_Index
: Boolean := False;
6282 if Nkind
(Def
) = N_Constrained_Array_Definition
then
6283 Index
:= First
(Discrete_Subtype_Definitions
(Def
));
6285 Index
:= First
(Subtype_Marks
(Def
));
6288 -- Find proper names for the implicit types which may be public. In case
6289 -- of anonymous arrays we use the name of the first object of that type
6293 Related_Id
:= Defining_Identifier
(P
);
6299 while Present
(Index
) loop
6302 -- Test for odd case of trying to index a type by the type itself
6304 if Is_Entity_Name
(Index
) and then Entity
(Index
) = T
then
6305 Error_Msg_N
("type& cannot be indexed by itself", Index
);
6306 Set_Entity
(Index
, Standard_Boolean
);
6307 Set_Etype
(Index
, Standard_Boolean
);
6310 -- Add a subtype declaration for each index of private array type
6311 -- declaration whose type is also private. For example:
6314 -- type Index is private;
6316 -- type Table is array (Index) of ...
6319 -- This is currently required by the expander for the internally
6320 -- generated equality subprogram of records with variant parts in
6321 -- which the type of some component is such a private type. And it
6322 -- also helps semantic analysis in peculiar cases where the array
6323 -- type is referenced from an instance but not the index directly.
6325 if Is_Package_Or_Generic_Package
(Current_Scope
)
6326 and then In_Private_Part
(Current_Scope
)
6327 and then Has_Private_Declaration
(Etype
(Index
))
6328 and then Scope
(Etype
(Index
)) = Current_Scope
6331 Loc
: constant Source_Ptr
:= Sloc
(Def
);
6336 New_E
:= Make_Temporary
(Loc
, 'T');
6337 Set_Is_Internal
(New_E
);
6340 Make_Subtype_Declaration
(Loc
,
6341 Defining_Identifier
=> New_E
,
6342 Subtype_Indication
=>
6343 New_Occurrence_Of
(Etype
(Index
), Loc
));
6345 Insert_Before
(Parent
(Def
), Decl
);
6347 Set_Etype
(Index
, New_E
);
6349 -- If the index is a range or a subtype indication it carries
6350 -- no entity. Example:
6353 -- type T is private;
6355 -- type T is new Natural;
6356 -- Table : array (T(1) .. T(10)) of Boolean;
6359 -- Otherwise the type of the reference is its entity.
6361 if Is_Entity_Name
(Index
) then
6362 Set_Entity
(Index
, New_E
);
6367 Make_Index
(Index
, P
, Related_Id
, Nb_Index
);
6369 -- In the case where we have an unconstrained array with an index
6370 -- given by a subtype_indication, this is necessarily a "fixed lower
6371 -- bound" index. We change the upper bound of that index to the upper
6372 -- bound of the index's subtype (denoted by the subtype_mark), since
6373 -- that upper bound was originally set by the parser to be the same
6374 -- as the lower bound. In truth, that upper bound corresponds to
6375 -- a box ("<>"), and could be set to Empty, but it's convenient to
6376 -- set it to the upper bound to avoid needing to add special tests
6377 -- in various places for an Empty upper bound, and in any case that
6378 -- accurately characterizes the index's range of values.
6380 if Nkind
(Def
) = N_Unconstrained_Array_Definition
6381 and then Nkind
(Index
) = N_Subtype_Indication
6384 Index_Subtype_High_Bound
: constant Entity_Id
:=
6385 Type_High_Bound
(Entity
(Subtype_Mark
(Index
)));
6387 Set_High_Bound
(Range_Expression
(Constraint
(Index
)),
6388 Index_Subtype_High_Bound
);
6390 -- Record that the array type has one or more indexes with
6391 -- a fixed lower bound.
6393 Has_FLB_Index
:= True;
6395 -- Mark the index as belonging to an array type with a fixed
6398 Set_Is_Fixed_Lower_Bound_Index_Subtype
(Etype
(Index
));
6402 -- Check error of subtype with predicate for index type
6404 Bad_Predicated_Subtype_Use
6405 ("subtype& has predicate, not allowed as index subtype",
6406 Index
, Etype
(Index
));
6408 -- Move to next index
6411 Nb_Index
:= Nb_Index
+ 1;
6414 -- Process subtype indication if one is present
6416 if Present
(Component_Typ
) then
6417 Element_Type
:= Process_Subtype
(Component_Typ
, P
, Related_Id
, 'C');
6418 Set_Etype
(Component_Typ
, Element_Type
);
6420 -- Ada 2005 (AI-230): Access Definition case
6422 else pragma Assert
(Present
(Access_Definition
(Component_Def
)));
6424 -- Indicate that the anonymous access type is created by the
6425 -- array type declaration.
6427 Element_Type
:= Access_Definition
6429 N
=> Access_Definition
(Component_Def
));
6430 Set_Is_Local_Anonymous_Access
(Element_Type
);
6432 -- Propagate the parent. This field is needed if we have to generate
6433 -- the master_id associated with an anonymous access to task type
6434 -- component (see Expand_N_Full_Type_Declaration.Build_Master)
6436 Copy_Parent
(To
=> Element_Type
, From
=> T
);
6438 -- Ada 2005 (AI-230): In case of components that are anonymous access
6439 -- types the level of accessibility depends on the enclosing type
6442 Set_Scope
(Element_Type
, Current_Scope
); -- Ada 2005 (AI-230)
6444 -- Ada 2005 (AI-254)
6447 CD
: constant Node_Id
:=
6448 Access_To_Subprogram_Definition
6449 (Access_Definition
(Component_Def
));
6451 if Present
(CD
) and then Protected_Present
(CD
) then
6453 Replace_Anonymous_Access_To_Protected_Subprogram
(Def
);
6458 -- Constrained array case
6461 -- We might be creating more than one itype with the same Related_Id,
6462 -- e.g. for an array object definition and its initial value. Give
6463 -- them unique suffixes, because GNATprove require distinct types to
6464 -- have different names.
6466 T
:= Create_Itype
(E_Void
, P
, Related_Id
, 'T', Suffix_Index
=> -1);
6469 if Nkind
(Def
) = N_Constrained_Array_Definition
then
6470 -- Establish Implicit_Base as unconstrained base type
6472 Implicit_Base
:= Create_Itype
(E_Array_Type
, P
, Related_Id
, 'B');
6474 Set_Etype
(Implicit_Base
, Implicit_Base
);
6475 Set_Scope
(Implicit_Base
, Current_Scope
);
6476 Set_Has_Delayed_Freeze
(Implicit_Base
);
6477 Set_Default_SSO
(Implicit_Base
);
6479 -- The constrained array type is a subtype of the unconstrained one
6481 Mutate_Ekind
(T
, E_Array_Subtype
);
6482 Reinit_Size_Align
(T
);
6483 Set_Etype
(T
, Implicit_Base
);
6484 Set_Scope
(T
, Current_Scope
);
6485 Set_Is_Constrained
(T
);
6487 First
(Discrete_Subtype_Definitions
(Def
)));
6488 Set_Has_Delayed_Freeze
(T
);
6490 -- Complete setup of implicit base type
6492 pragma Assert
(not Known_Component_Size
(Implicit_Base
));
6493 Set_Component_Type
(Implicit_Base
, Element_Type
);
6494 Set_Finalize_Storage_Only
6496 Finalize_Storage_Only
(Element_Type
));
6497 Set_First_Index
(Implicit_Base
, First_Index
(T
));
6498 Set_Has_Controlled_Component
6500 Has_Controlled_Component
(Element_Type
)
6501 or else Is_Controlled
(Element_Type
));
6502 Set_Packed_Array_Impl_Type
6503 (Implicit_Base
, Empty
);
6505 Propagate_Concurrent_Flags
(Implicit_Base
, Element_Type
);
6507 -- Unconstrained array case
6509 else pragma Assert
(Nkind
(Def
) = N_Unconstrained_Array_Definition
);
6510 Mutate_Ekind
(T
, E_Array_Type
);
6511 Reinit_Size_Align
(T
);
6513 Set_Scope
(T
, Current_Scope
);
6514 pragma Assert
(not Known_Component_Size
(T
));
6515 Set_Is_Constrained
(T
, False);
6516 Set_Is_Fixed_Lower_Bound_Array_Subtype
6518 Set_First_Index
(T
, First
(Subtype_Marks
(Def
)));
6519 Set_Has_Delayed_Freeze
(T
, True);
6520 Propagate_Concurrent_Flags
(T
, Element_Type
);
6521 Set_Has_Controlled_Component
(T
, Has_Controlled_Component
6524 Is_Controlled
(Element_Type
));
6525 Set_Finalize_Storage_Only
(T
, Finalize_Storage_Only
6527 Set_Default_SSO
(T
);
6530 -- Common attributes for both cases
6532 Set_Component_Type
(Base_Type
(T
), Element_Type
);
6533 Set_Packed_Array_Impl_Type
(T
, Empty
);
6535 if Aliased_Present
(Component_Definition
(Def
)) then
6536 Set_Has_Aliased_Components
(Etype
(T
));
6538 -- AI12-001: All aliased objects are considered to be specified as
6539 -- independently addressable (RM C.6(8.1/4)).
6541 Set_Has_Independent_Components
(Etype
(T
));
6544 -- Ada 2005 (AI-231): Propagate the null-excluding attribute to the
6545 -- array type to ensure that objects of this type are initialized.
6547 if Ada_Version
>= Ada_2005
and then Can_Never_Be_Null
(Element_Type
) then
6548 Set_Can_Never_Be_Null
(T
);
6550 if Null_Exclusion_Present
(Component_Definition
(Def
))
6552 -- No need to check itypes because in their case this check was
6553 -- done at their point of creation
6555 and then not Is_Itype
(Element_Type
)
6558 ("`NOT NULL` not allowed (null already excluded)",
6559 Subtype_Indication
(Component_Definition
(Def
)));
6563 Priv
:= Private_Component
(Element_Type
);
6565 if Present
(Priv
) then
6567 -- Check for circular definitions
6569 if Priv
= Any_Type
then
6570 Set_Component_Type
(Etype
(T
), Any_Type
);
6572 -- There is a gap in the visibility of operations on the composite
6573 -- type only if the component type is defined in a different scope.
6575 elsif Scope
(Priv
) = Current_Scope
then
6578 elsif Is_Limited_Type
(Priv
) then
6579 Set_Is_Limited_Composite
(Etype
(T
));
6580 Set_Is_Limited_Composite
(T
);
6582 Set_Is_Private_Composite
(Etype
(T
));
6583 Set_Is_Private_Composite
(T
);
6587 -- A syntax error in the declaration itself may lead to an empty index
6588 -- list, in which case do a minimal patch.
6590 if No
(First_Index
(T
)) then
6591 Error_Msg_N
("missing index definition in array type declaration", T
);
6594 Indexes
: constant List_Id
:=
6595 New_List
(New_Occurrence_Of
(Any_Id
, Sloc
(T
)));
6597 Set_Discrete_Subtype_Definitions
(Def
, Indexes
);
6598 Set_First_Index
(T
, First
(Indexes
));
6603 -- Create a concatenation operator for the new type. Internal array
6604 -- types created for packed entities do not need such, they are
6605 -- compatible with the user-defined type.
6607 if Number_Dimensions
(T
) = 1
6608 and then not Is_Packed_Array_Impl_Type
(T
)
6610 New_Concatenation_Op
(T
);
6613 -- In the case of an unconstrained array the parser has already verified
6614 -- that all the indexes are unconstrained but we still need to make sure
6615 -- that the element type is constrained.
6617 if not Is_Definite_Subtype
(Element_Type
) then
6619 ("unconstrained element type in array declaration",
6620 Subtype_Indication
(Component_Def
));
6622 elsif Is_Abstract_Type
(Element_Type
) then
6624 ("the type of a component cannot be abstract",
6625 Subtype_Indication
(Component_Def
));
6628 -- There may be an invariant declared for the component type, but
6629 -- the construction of the component invariant checking procedure
6630 -- takes place during expansion.
6631 end Array_Type_Declaration
;
6633 ------------------------------------------------------
6634 -- Replace_Anonymous_Access_To_Protected_Subprogram --
6635 ------------------------------------------------------
6637 function Replace_Anonymous_Access_To_Protected_Subprogram
6638 (N
: Node_Id
) return Entity_Id
6640 Loc
: constant Source_Ptr
:= Sloc
(N
);
6642 Curr_Scope
: constant Scope_Stack_Entry
:=
6643 Scope_Stack
.Table
(Scope_Stack
.Last
);
6645 Anon
: constant Entity_Id
:= Make_Temporary
(Loc
, 'S');
6648 -- Access definition in declaration
6651 -- Object definition or formal definition with an access definition
6654 -- Declaration of anonymous access to subprogram type
6657 -- Original specification in access to subprogram
6662 Set_Is_Internal
(Anon
);
6665 when N_Constrained_Array_Definition
6666 | N_Component_Declaration
6667 | N_Unconstrained_Array_Definition
6669 Comp
:= Component_Definition
(N
);
6670 Acc
:= Access_Definition
(Comp
);
6672 when N_Discriminant_Specification
=>
6673 Comp
:= Discriminant_Type
(N
);
6676 when N_Parameter_Specification
=>
6677 Comp
:= Parameter_Type
(N
);
6680 when N_Access_Function_Definition
=>
6681 Comp
:= Result_Definition
(N
);
6684 when N_Object_Declaration
=>
6685 Comp
:= Object_Definition
(N
);
6688 when N_Function_Specification
=>
6689 Comp
:= Result_Definition
(N
);
6693 raise Program_Error
;
6696 Spec
:= Access_To_Subprogram_Definition
(Acc
);
6699 Make_Full_Type_Declaration
(Loc
,
6700 Defining_Identifier
=> Anon
,
6701 Type_Definition
=> Copy_Separate_Tree
(Spec
));
6703 Mark_Rewrite_Insertion
(Decl
);
6705 -- Insert the new declaration in the nearest enclosing scope. If the
6706 -- parent is a body and N is its return type, the declaration belongs
6707 -- in the enclosing scope. Likewise if N is the type of a parameter.
6711 if Nkind
(N
) = N_Function_Specification
6712 and then Nkind
(P
) = N_Subprogram_Body
6715 elsif Nkind
(N
) = N_Parameter_Specification
6716 and then Nkind
(P
) in N_Subprogram_Specification
6717 and then Nkind
(Parent
(P
)) = N_Subprogram_Body
6719 P
:= Parent
(Parent
(P
));
6722 while Present
(P
) and then not Has_Declarations
(P
) loop
6726 pragma Assert
(Present
(P
));
6728 if Nkind
(P
) = N_Package_Specification
then
6729 Prepend
(Decl
, Visible_Declarations
(P
));
6731 Prepend
(Decl
, Declarations
(P
));
6734 -- Replace the anonymous type with an occurrence of the new declaration.
6735 -- In all cases the rewritten node does not have the null-exclusion
6736 -- attribute because (if present) it was already inherited by the
6737 -- anonymous entity (Anon). Thus, in case of components we do not
6738 -- inherit this attribute.
6740 if Nkind
(N
) = N_Parameter_Specification
then
6741 Rewrite
(Comp
, New_Occurrence_Of
(Anon
, Loc
));
6742 Set_Etype
(Defining_Identifier
(N
), Anon
);
6743 Set_Null_Exclusion_Present
(N
, False);
6745 elsif Nkind
(N
) = N_Object_Declaration
then
6746 Rewrite
(Comp
, New_Occurrence_Of
(Anon
, Loc
));
6747 Set_Etype
(Defining_Identifier
(N
), Anon
);
6749 elsif Nkind
(N
) = N_Access_Function_Definition
then
6750 Rewrite
(Comp
, New_Occurrence_Of
(Anon
, Loc
));
6752 elsif Nkind
(N
) = N_Function_Specification
then
6753 Rewrite
(Comp
, New_Occurrence_Of
(Anon
, Loc
));
6754 Set_Etype
(Defining_Unit_Name
(N
), Anon
);
6758 Make_Component_Definition
(Loc
,
6759 Subtype_Indication
=> New_Occurrence_Of
(Anon
, Loc
)));
6762 Mark_Rewrite_Insertion
(Comp
);
6764 if Nkind
(N
) in N_Object_Declaration | N_Access_Function_Definition
6765 or else (Nkind
(Parent
(N
)) = N_Full_Type_Declaration
6766 and then not Is_Type
(Current_Scope
))
6769 -- Declaration can be analyzed in the current scope.
6774 -- Temporarily remove the current scope (record or subprogram) from
6775 -- the stack to add the new declarations to the enclosing scope.
6776 -- The anonymous entity is an Itype with the proper attributes.
6778 Scope_Stack
.Decrement_Last
;
6780 Set_Is_Itype
(Anon
);
6781 Set_Associated_Node_For_Itype
(Anon
, N
);
6782 Scope_Stack
.Append
(Curr_Scope
);
6785 Mutate_Ekind
(Anon
, E_Anonymous_Access_Protected_Subprogram_Type
);
6786 Set_Can_Use_Internal_Rep
(Anon
, not Always_Compatible_Rep_On_Target
);
6788 end Replace_Anonymous_Access_To_Protected_Subprogram
;
6790 -------------------------------------
6791 -- Build_Access_Subprogram_Wrapper --
6792 -------------------------------------
6794 procedure Build_Access_Subprogram_Wrapper
(Decl
: Node_Id
) is
6795 Loc
: constant Source_Ptr
:= Sloc
(Decl
);
6796 Id
: constant Entity_Id
:= Defining_Identifier
(Decl
);
6797 Type_Def
: constant Node_Id
:= Type_Definition
(Decl
);
6798 Specs
: constant List_Id
:=
6799 Parameter_Specifications
(Type_Def
);
6800 Profile
: constant List_Id
:= New_List
;
6801 Subp
: constant Entity_Id
:= Make_Temporary
(Loc
, 'A');
6803 Contracts
: constant List_Id
:= New_List
;
6809 procedure Replace_Type_Name
(Expr
: Node_Id
);
6810 -- In the expressions for contract aspects, replace occurrences of the
6811 -- access type with the name of the subprogram entity, as needed, e.g.
6812 -- for 'Result. Aspects that are not contracts, e.g. Size or Alignment)
6813 -- remain on the original access type declaration. What about expanded
6814 -- names denoting formals, whose prefix in source is the type name ???
6816 -----------------------
6817 -- Replace_Type_Name --
6818 -----------------------
6820 procedure Replace_Type_Name
(Expr
: Node_Id
) is
6821 function Process
(N
: Node_Id
) return Traverse_Result
;
6822 function Process
(N
: Node_Id
) return Traverse_Result
is
6824 if Nkind
(N
) = N_Attribute_Reference
6825 and then Is_Entity_Name
(Prefix
(N
))
6826 and then Chars
(Prefix
(N
)) = Chars
(Id
)
6828 Set_Prefix
(N
, Make_Identifier
(Sloc
(N
), Chars
(Subp
)));
6834 procedure Traverse
is new Traverse_Proc
(Process
);
6837 end Replace_Type_Name
;
6840 if Ekind
(Id
) in E_Access_Subprogram_Type
6841 | E_Access_Protected_Subprogram_Type
6842 | E_Anonymous_Access_Protected_Subprogram_Type
6843 | E_Anonymous_Access_Subprogram_Type
6849 ("illegal pre/postcondition on access type", Decl
);
6858 Asp
:= First
(Aspect_Specifications
(Decl
));
6859 while Present
(Asp
) loop
6860 A_Id
:= Get_Aspect_Id
(Chars
(Identifier
(Asp
)));
6861 if A_Id
= Aspect_Pre
or else A_Id
= Aspect_Post
then
6862 Append
(New_Copy_Tree
(Asp
), Contracts
);
6863 Replace_Type_Name
(Expression
(Last
(Contracts
)));
6869 -- If there are no contract aspects, no need for a wrapper.
6871 if Is_Empty_List
(Contracts
) then
6875 Form_P
:= First
(Specs
);
6877 while Present
(Form_P
) loop
6878 New_P
:= New_Copy_Tree
(Form_P
);
6879 Set_Defining_Identifier
(New_P
,
6880 Make_Defining_Identifier
6881 (Loc
, Chars
(Defining_Identifier
(Form_P
))));
6882 Append
(New_P
, Profile
);
6886 -- Add to parameter specifications the access parameter that is passed
6887 -- in from an indirect call.
6890 Make_Parameter_Specification
(Loc
,
6891 Defining_Identifier
=> Make_Temporary
(Loc
, 'P'),
6892 Parameter_Type
=> New_Occurrence_Of
(Id
, Loc
)),
6895 if Nkind
(Type_Def
) = N_Access_Procedure_Definition
then
6897 Make_Procedure_Specification
(Loc
,
6898 Defining_Unit_Name
=> Subp
,
6899 Parameter_Specifications
=> Profile
);
6900 Mutate_Ekind
(Subp
, E_Procedure
);
6903 Make_Function_Specification
(Loc
,
6904 Defining_Unit_Name
=> Subp
,
6905 Parameter_Specifications
=> Profile
,
6906 Result_Definition
=>
6908 (Result_Definition
(Type_Definition
(Decl
))));
6909 Mutate_Ekind
(Subp
, E_Function
);
6913 Make_Subprogram_Declaration
(Loc
, Specification
=> Spec
);
6914 Set_Aspect_Specifications
(New_Decl
, Contracts
);
6915 Set_Is_Wrapper
(Subp
);
6917 -- The wrapper is declared in the freezing actions to facilitate its
6918 -- identification and thus avoid handling it as a primitive operation
6919 -- of a tagged type (see Is_Access_To_Subprogram_Wrapper); otherwise it
6920 -- may be handled as a dispatching operation and erroneously registered
6921 -- in a dispatch table.
6923 Append_Freeze_Action
(Id
, New_Decl
);
6925 Set_Access_Subprogram_Wrapper
(Designated_Type
(Id
), Subp
);
6926 Build_Access_Subprogram_Wrapper_Body
(Decl
, New_Decl
);
6927 end Build_Access_Subprogram_Wrapper
;
6929 -------------------------------
6930 -- Build_Derived_Access_Type --
6931 -------------------------------
6933 procedure Build_Derived_Access_Type
6935 Parent_Type
: Entity_Id
;
6936 Derived_Type
: Entity_Id
)
6938 S
: constant Node_Id
:= Subtype_Indication
(Type_Definition
(N
));
6940 Desig_Type
: Entity_Id
;
6942 Discr_Con_Elist
: Elist_Id
;
6943 Discr_Con_El
: Elmt_Id
;
6947 -- Set the designated type so it is available in case this is an access
6948 -- to a self-referential type, e.g. a standard list type with a next
6949 -- pointer. Will be reset after subtype is built.
6951 Set_Directly_Designated_Type
6952 (Derived_Type
, Designated_Type
(Parent_Type
));
6954 Subt
:= Process_Subtype
(S
, N
);
6956 if Nkind
(S
) /= N_Subtype_Indication
6957 and then Subt
/= Base_Type
(Subt
)
6959 Mutate_Ekind
(Derived_Type
, E_Access_Subtype
);
6962 if Ekind
(Derived_Type
) = E_Access_Subtype
then
6964 Pbase
: constant Entity_Id
:= Base_Type
(Parent_Type
);
6965 Ibase
: constant Entity_Id
:=
6966 Create_Itype
(Ekind
(Pbase
), N
, Derived_Type
, 'B');
6967 Svg_Chars
: constant Name_Id
:= Chars
(Ibase
);
6968 Svg_Next_E
: constant Entity_Id
:= Next_Entity
(Ibase
);
6969 Svg_Prev_E
: constant Entity_Id
:= Prev_Entity
(Ibase
);
6972 Copy_Node
(Pbase
, Ibase
);
6974 -- Restore Itype status after Copy_Node
6976 Set_Is_Itype
(Ibase
);
6977 Set_Associated_Node_For_Itype
(Ibase
, N
);
6979 Set_Chars
(Ibase
, Svg_Chars
);
6980 Set_Prev_Entity
(Ibase
, Svg_Prev_E
);
6981 Set_Next_Entity
(Ibase
, Svg_Next_E
);
6982 Set_Sloc
(Ibase
, Sloc
(Derived_Type
));
6983 Set_Scope
(Ibase
, Scope
(Derived_Type
));
6984 Set_Freeze_Node
(Ibase
, Empty
);
6985 Set_Is_Frozen
(Ibase
, False);
6986 Set_Comes_From_Source
(Ibase
, False);
6987 Set_Is_First_Subtype
(Ibase
, False);
6989 Set_Etype
(Ibase
, Pbase
);
6990 Set_Etype
(Derived_Type
, Ibase
);
6994 Set_Directly_Designated_Type
6995 (Derived_Type
, Designated_Type
(Subt
));
6997 Set_Is_Constrained
(Derived_Type
, Is_Constrained
(Subt
));
6998 Set_Is_Access_Constant
(Derived_Type
, Is_Access_Constant
(Parent_Type
));
6999 Set_Size_Info
(Derived_Type
, Parent_Type
);
7000 Copy_RM_Size
(To
=> Derived_Type
, From
=> Parent_Type
);
7001 Set_Depends_On_Private
(Derived_Type
,
7002 Has_Private_Component
(Derived_Type
));
7003 Conditional_Delay
(Derived_Type
, Subt
);
7005 if Is_Access_Subprogram_Type
(Derived_Type
)
7006 and then Is_Base_Type
(Derived_Type
)
7008 Set_Can_Use_Internal_Rep
7009 (Derived_Type
, Can_Use_Internal_Rep
(Parent_Type
));
7012 -- Ada 2005 (AI-231): Set the null-exclusion attribute, and verify
7013 -- that it is not redundant.
7015 if Null_Exclusion_Present
(Type_Definition
(N
)) then
7016 Set_Can_Never_Be_Null
(Derived_Type
);
7018 elsif Can_Never_Be_Null
(Parent_Type
) then
7019 Set_Can_Never_Be_Null
(Derived_Type
);
7022 -- Note: we do not copy the Storage_Size_Variable, since we always go to
7023 -- the root type for this information.
7025 -- Apply range checks to discriminants for derived record case
7026 -- ??? THIS CODE SHOULD NOT BE HERE REALLY.
7028 Desig_Type
:= Designated_Type
(Derived_Type
);
7030 if Is_Composite_Type
(Desig_Type
)
7031 and then not Is_Array_Type
(Desig_Type
)
7032 and then Has_Discriminants
(Desig_Type
)
7033 and then Base_Type
(Desig_Type
) /= Desig_Type
7035 Discr_Con_Elist
:= Discriminant_Constraint
(Desig_Type
);
7036 Discr_Con_El
:= First_Elmt
(Discr_Con_Elist
);
7038 Discr
:= First_Discriminant
(Base_Type
(Desig_Type
));
7039 while Present
(Discr_Con_El
) loop
7040 Apply_Range_Check
(Node
(Discr_Con_El
), Etype
(Discr
));
7041 Next_Elmt
(Discr_Con_El
);
7042 Next_Discriminant
(Discr
);
7045 end Build_Derived_Access_Type
;
7047 ------------------------------
7048 -- Build_Derived_Array_Type --
7049 ------------------------------
7051 procedure Build_Derived_Array_Type
7053 Parent_Type
: Entity_Id
;
7054 Derived_Type
: Entity_Id
)
7056 Loc
: constant Source_Ptr
:= Sloc
(N
);
7057 Tdef
: constant Node_Id
:= Type_Definition
(N
);
7058 Indic
: constant Node_Id
:= Subtype_Indication
(Tdef
);
7059 Parent_Base
: constant Entity_Id
:= Base_Type
(Parent_Type
);
7060 Implicit_Base
: Entity_Id
:= Empty
;
7061 New_Indic
: Node_Id
;
7063 procedure Make_Implicit_Base
;
7064 -- If the parent subtype is constrained, the derived type is a subtype
7065 -- of an implicit base type derived from the parent base.
7067 ------------------------
7068 -- Make_Implicit_Base --
7069 ------------------------
7071 procedure Make_Implicit_Base
is
7074 Create_Itype
(Ekind
(Parent_Base
), N
, Derived_Type
, 'B');
7076 Mutate_Ekind
(Implicit_Base
, Ekind
(Parent_Base
));
7077 Set_Etype
(Implicit_Base
, Parent_Base
);
7079 Copy_Array_Subtype_Attributes
(Implicit_Base
, Parent_Base
);
7080 Copy_Array_Base_Type_Attributes
(Implicit_Base
, Parent_Base
);
7082 Set_Has_Delayed_Freeze
(Implicit_Base
, True);
7083 end Make_Implicit_Base
;
7085 -- Start of processing for Build_Derived_Array_Type
7088 if not Is_Constrained
(Parent_Type
) then
7089 if Nkind
(Indic
) /= N_Subtype_Indication
then
7090 Mutate_Ekind
(Derived_Type
, E_Array_Type
);
7092 Copy_Array_Subtype_Attributes
(Derived_Type
, Parent_Type
);
7093 Copy_Array_Base_Type_Attributes
(Derived_Type
, Parent_Type
);
7095 Set_Has_Delayed_Freeze
(Derived_Type
, True);
7099 Set_Etype
(Derived_Type
, Implicit_Base
);
7102 Make_Subtype_Declaration
(Loc
,
7103 Defining_Identifier
=> Derived_Type
,
7104 Subtype_Indication
=>
7105 Make_Subtype_Indication
(Loc
,
7106 Subtype_Mark
=> New_Occurrence_Of
(Implicit_Base
, Loc
),
7107 Constraint
=> Constraint
(Indic
)));
7109 Rewrite
(N
, New_Indic
);
7114 if Nkind
(Indic
) /= N_Subtype_Indication
then
7117 Mutate_Ekind
(Derived_Type
, Ekind
(Parent_Type
));
7118 Set_Etype
(Derived_Type
, Implicit_Base
);
7119 Copy_Array_Subtype_Attributes
(Derived_Type
, Parent_Type
);
7122 Error_Msg_N
("illegal constraint on constrained type", Indic
);
7126 -- If parent type is not a derived type itself, and is declared in
7127 -- closed scope (e.g. a subprogram), then we must explicitly introduce
7128 -- the new type's concatenation operator since Derive_Subprograms
7129 -- will not inherit the parent's operator. If the parent type is
7130 -- unconstrained, the operator is of the unconstrained base type.
7132 if Number_Dimensions
(Parent_Type
) = 1
7133 and then not Is_Limited_Type
(Parent_Type
)
7134 and then not Is_Derived_Type
(Parent_Type
)
7135 and then not Is_Package_Or_Generic_Package
7136 (Scope
(Base_Type
(Parent_Type
)))
7138 if not Is_Constrained
(Parent_Type
)
7139 and then Is_Constrained
(Derived_Type
)
7141 New_Concatenation_Op
(Implicit_Base
);
7143 New_Concatenation_Op
(Derived_Type
);
7146 end Build_Derived_Array_Type
;
7148 -----------------------------------
7149 -- Build_Derived_Concurrent_Type --
7150 -----------------------------------
7152 procedure Build_Derived_Concurrent_Type
7154 Parent_Type
: Entity_Id
;
7155 Derived_Type
: Entity_Id
)
7157 Loc
: constant Source_Ptr
:= Sloc
(N
);
7158 Def
: constant Node_Id
:= Type_Definition
(N
);
7159 Indic
: constant Node_Id
:= Subtype_Indication
(Def
);
7161 Corr_Record
: constant Entity_Id
:= Make_Temporary
(Loc
, 'C');
7162 Corr_Decl
: Node_Id
:= Empty
;
7163 Corr_Decl_Needed
: Boolean;
7164 -- If the derived type has fewer discriminants than its parent, the
7165 -- corresponding record is also a derived type, in order to account for
7166 -- the bound discriminants. We create a full type declaration for it in
7169 Constraint_Present
: constant Boolean :=
7170 Nkind
(Indic
) = N_Subtype_Indication
;
7172 D_Constraint
: Node_Id
;
7173 New_Constraint
: Elist_Id
:= No_Elist
;
7174 Old_Disc
: Entity_Id
;
7175 New_Disc
: Entity_Id
;
7179 Set_Stored_Constraint
(Derived_Type
, No_Elist
);
7180 Corr_Decl_Needed
:= False;
7183 if Present
(Discriminant_Specifications
(N
))
7184 and then Constraint_Present
7186 Old_Disc
:= First_Discriminant
(Parent_Type
);
7187 New_Disc
:= First
(Discriminant_Specifications
(N
));
7188 while Present
(New_Disc
) and then Present
(Old_Disc
) loop
7189 Next_Discriminant
(Old_Disc
);
7194 if Present
(Old_Disc
) and then Expander_Active
then
7196 -- The new type has fewer discriminants, so we need to create a new
7197 -- corresponding record, which is derived from the corresponding
7198 -- record of the parent, and has a stored constraint that captures
7199 -- the values of the discriminant constraints. The corresponding
7200 -- record is needed only if expander is active and code generation is
7203 -- The type declaration for the derived corresponding record has the
7204 -- same discriminant part and constraints as the current declaration.
7205 -- Copy the unanalyzed tree to build declaration.
7207 Corr_Decl_Needed
:= True;
7208 New_N
:= Copy_Separate_Tree
(N
);
7211 Make_Full_Type_Declaration
(Loc
,
7212 Defining_Identifier
=> Corr_Record
,
7213 Discriminant_Specifications
=>
7214 Discriminant_Specifications
(New_N
),
7216 Make_Derived_Type_Definition
(Loc
,
7217 Subtype_Indication
=>
7218 Make_Subtype_Indication
(Loc
,
7221 (Corresponding_Record_Type
(Parent_Type
), Loc
),
7224 (Subtype_Indication
(Type_Definition
(New_N
))))));
7227 -- Copy Storage_Size and Relative_Deadline variables if task case
7229 if Is_Task_Type
(Parent_Type
) then
7230 Set_Storage_Size_Variable
(Derived_Type
,
7231 Storage_Size_Variable
(Parent_Type
));
7232 Set_Relative_Deadline_Variable
(Derived_Type
,
7233 Relative_Deadline_Variable
(Parent_Type
));
7236 if Present
(Discriminant_Specifications
(N
)) then
7237 Push_Scope
(Derived_Type
);
7238 Check_Or_Process_Discriminants
(N
, Derived_Type
);
7240 if Constraint_Present
then
7242 Expand_To_Stored_Constraint
7244 Build_Discriminant_Constraints
7245 (Parent_Type
, Indic
, True));
7250 elsif Constraint_Present
then
7252 -- Build an unconstrained derived type and rewrite the derived type
7253 -- as a subtype of this new base type.
7256 Parent_Base
: constant Entity_Id
:= Base_Type
(Parent_Type
);
7257 New_Base
: Entity_Id
;
7259 New_Indic
: Node_Id
;
7263 Create_Itype
(Ekind
(Derived_Type
), N
, Derived_Type
, 'B');
7266 Make_Full_Type_Declaration
(Loc
,
7267 Defining_Identifier
=> New_Base
,
7269 Make_Derived_Type_Definition
(Loc
,
7270 Abstract_Present
=> Abstract_Present
(Def
),
7271 Limited_Present
=> Limited_Present
(Def
),
7272 Subtype_Indication
=>
7273 New_Occurrence_Of
(Parent_Base
, Loc
)));
7275 Mark_Rewrite_Insertion
(New_Decl
);
7276 Insert_Before
(N
, New_Decl
);
7280 Make_Subtype_Indication
(Loc
,
7281 Subtype_Mark
=> New_Occurrence_Of
(New_Base
, Loc
),
7282 Constraint
=> Relocate_Node
(Constraint
(Indic
)));
7285 Make_Subtype_Declaration
(Loc
,
7286 Defining_Identifier
=> Derived_Type
,
7287 Subtype_Indication
=> New_Indic
));
7294 -- By default, operations and private data are inherited from parent.
7295 -- However, in the presence of bound discriminants, a new corresponding
7296 -- record will be created, see below.
7298 Set_Has_Discriminants
7299 (Derived_Type
, Has_Discriminants
(Parent_Type
));
7300 Set_Corresponding_Record_Type
7301 (Derived_Type
, Corresponding_Record_Type
(Parent_Type
));
7303 -- Is_Constrained is set according the parent subtype, but is set to
7304 -- False if the derived type is declared with new discriminants.
7308 (Is_Constrained
(Parent_Type
) or else Constraint_Present
)
7309 and then not Present
(Discriminant_Specifications
(N
)));
7311 if Constraint_Present
then
7312 if not Has_Discriminants
(Parent_Type
) then
7313 Error_Msg_N
("untagged parent must have discriminants", N
);
7315 elsif Present
(Discriminant_Specifications
(N
)) then
7317 -- Verify that new discriminants are used to constrain old ones
7319 D_Constraint
:= First
(Constraints
(Constraint
(Indic
)));
7321 Old_Disc
:= First_Discriminant
(Parent_Type
);
7323 while Present
(D_Constraint
) loop
7324 if Nkind
(D_Constraint
) /= N_Discriminant_Association
then
7326 -- Positional constraint. If it is a reference to a new
7327 -- discriminant, it constrains the corresponding old one.
7329 if Nkind
(D_Constraint
) = N_Identifier
then
7330 New_Disc
:= First_Discriminant
(Derived_Type
);
7331 while Present
(New_Disc
) loop
7332 exit when Chars
(New_Disc
) = Chars
(D_Constraint
);
7333 Next_Discriminant
(New_Disc
);
7336 if Present
(New_Disc
) then
7337 Set_Corresponding_Discriminant
(New_Disc
, Old_Disc
);
7341 Next_Discriminant
(Old_Disc
);
7343 -- if this is a named constraint, search by name for the old
7344 -- discriminants constrained by the new one.
7346 elsif Nkind
(Expression
(D_Constraint
)) = N_Identifier
then
7348 -- Find new discriminant with that name
7350 New_Disc
:= First_Discriminant
(Derived_Type
);
7351 while Present
(New_Disc
) loop
7353 Chars
(New_Disc
) = Chars
(Expression
(D_Constraint
));
7354 Next_Discriminant
(New_Disc
);
7357 if Present
(New_Disc
) then
7359 -- Verify that new discriminant renames some discriminant
7360 -- of the parent type, and associate the new discriminant
7361 -- with one or more old ones that it renames.
7367 Selector
:= First
(Selector_Names
(D_Constraint
));
7368 while Present
(Selector
) loop
7369 Old_Disc
:= First_Discriminant
(Parent_Type
);
7370 while Present
(Old_Disc
) loop
7371 exit when Chars
(Old_Disc
) = Chars
(Selector
);
7372 Next_Discriminant
(Old_Disc
);
7375 if Present
(Old_Disc
) then
7376 Set_Corresponding_Discriminant
7377 (New_Disc
, Old_Disc
);
7386 Next
(D_Constraint
);
7389 New_Disc
:= First_Discriminant
(Derived_Type
);
7390 while Present
(New_Disc
) loop
7391 if No
(Corresponding_Discriminant
(New_Disc
)) then
7393 ("new discriminant& must constrain old one", N
, New_Disc
);
7395 -- If a new discriminant is used in the constraint, then its
7396 -- subtype must be statically compatible with the subtype of
7397 -- the parent discriminant (RM 3.7(15)).
7400 Check_Constraining_Discriminant
7401 (New_Disc
, Corresponding_Discriminant
(New_Disc
));
7404 Next_Discriminant
(New_Disc
);
7408 elsif Present
(Discriminant_Specifications
(N
)) then
7410 ("missing discriminant constraint in untagged derivation", N
);
7413 -- The entity chain of the derived type includes the new discriminants
7414 -- but shares operations with the parent.
7416 if Present
(Discriminant_Specifications
(N
)) then
7417 Old_Disc
:= First_Discriminant
(Parent_Type
);
7418 while Present
(Old_Disc
) loop
7419 if No
(Next_Entity
(Old_Disc
))
7420 or else Ekind
(Next_Entity
(Old_Disc
)) /= E_Discriminant
7423 (Last_Entity
(Derived_Type
), Next_Entity
(Old_Disc
));
7427 Next_Discriminant
(Old_Disc
);
7431 Set_First_Entity
(Derived_Type
, First_Entity
(Parent_Type
));
7432 if Has_Discriminants
(Parent_Type
) then
7433 Set_Is_Constrained
(Derived_Type
, Is_Constrained
(Parent_Type
));
7434 Set_Discriminant_Constraint
(
7435 Derived_Type
, Discriminant_Constraint
(Parent_Type
));
7439 Set_Last_Entity
(Derived_Type
, Last_Entity
(Parent_Type
));
7441 Set_Has_Completion
(Derived_Type
);
7443 if Corr_Decl_Needed
then
7444 Set_Stored_Constraint
(Derived_Type
, New_Constraint
);
7445 Insert_After
(N
, Corr_Decl
);
7446 Analyze
(Corr_Decl
);
7447 Set_Corresponding_Record_Type
(Derived_Type
, Corr_Record
);
7449 end Build_Derived_Concurrent_Type
;
7451 ------------------------------------
7452 -- Build_Derived_Enumeration_Type --
7453 ------------------------------------
7455 procedure Build_Derived_Enumeration_Type
7457 Parent_Type
: Entity_Id
;
7458 Derived_Type
: Entity_Id
)
7460 function Bound_Belongs_To_Type
(B
: Node_Id
) return Boolean;
7461 -- When the type declaration includes a constraint, we generate
7462 -- a subtype declaration of an anonymous base type, with the constraint
7463 -- given in the original type declaration. Conceptually, the bounds
7464 -- are converted to the new base type, and this conversion freezes
7465 -- (prematurely) that base type, when the bounds are simply literals.
7466 -- As a result, a representation clause for the derived type is then
7467 -- rejected or ignored. This procedure recognizes the simple case of
7468 -- literal bounds, which allows us to indicate that the conversions
7469 -- are not freeze points, and the subsequent representation clause
7471 -- A similar approach might be used to resolve the long-standing
7472 -- problem of premature freezing of derived numeric types ???
7474 function Bound_Belongs_To_Type
(B
: Node_Id
) return Boolean is
7476 return Nkind
(B
) = N_Type_Conversion
7477 and then Is_Entity_Name
(Expression
(B
))
7478 and then Ekind
(Entity
(Expression
(B
))) = E_Enumeration_Literal
;
7479 end Bound_Belongs_To_Type
;
7481 Loc
: constant Source_Ptr
:= Sloc
(N
);
7482 Def
: constant Node_Id
:= Type_Definition
(N
);
7483 Indic
: constant Node_Id
:= Subtype_Indication
(Def
);
7484 Implicit_Base
: Entity_Id
;
7485 Literal
: Entity_Id
;
7486 New_Lit
: Entity_Id
;
7487 Literals_List
: List_Id
;
7488 Type_Decl
: Node_Id
;
7490 Rang_Expr
: Node_Id
;
7493 -- Since types Standard.Character and Standard.[Wide_]Wide_Character do
7494 -- not have explicit literals lists we need to process types derived
7495 -- from them specially. This is handled by Derived_Standard_Character.
7496 -- If the parent type is a generic type, there are no literals either,
7497 -- and we construct the same skeletal representation as for the generic
7500 if Is_Standard_Character_Type
(Parent_Type
) then
7501 Derived_Standard_Character
(N
, Parent_Type
, Derived_Type
);
7503 elsif Is_Generic_Type
(Root_Type
(Parent_Type
)) then
7509 if Nkind
(Indic
) /= N_Subtype_Indication
then
7511 Make_Attribute_Reference
(Loc
,
7512 Attribute_Name
=> Name_First
,
7513 Prefix
=> New_Occurrence_Of
(Derived_Type
, Loc
));
7514 Set_Etype
(Lo
, Derived_Type
);
7517 Make_Attribute_Reference
(Loc
,
7518 Attribute_Name
=> Name_Last
,
7519 Prefix
=> New_Occurrence_Of
(Derived_Type
, Loc
));
7520 Set_Etype
(Hi
, Derived_Type
);
7522 Set_Scalar_Range
(Derived_Type
,
7528 -- Analyze subtype indication and verify compatibility
7529 -- with parent type.
7531 if Base_Type
(Process_Subtype
(Indic
, N
)) /=
7532 Base_Type
(Parent_Type
)
7535 ("illegal constraint for formal discrete type", N
);
7541 -- If a constraint is present, analyze the bounds to catch
7542 -- premature usage of the derived literals.
7544 if Nkind
(Indic
) = N_Subtype_Indication
7545 and then Nkind
(Range_Expression
(Constraint
(Indic
))) = N_Range
7547 Analyze
(Low_Bound
(Range_Expression
(Constraint
(Indic
))));
7548 Analyze
(High_Bound
(Range_Expression
(Constraint
(Indic
))));
7551 -- Create an implicit base type for the derived type even if there
7552 -- is no constraint attached to it, since this seems closer to the
7553 -- Ada semantics. Use an Itype like for the implicit base type of
7554 -- other kinds of derived type, but build a full type declaration
7555 -- for it so as to analyze the new literals properly. Then build a
7556 -- subtype declaration tree which applies the constraint (if any)
7557 -- and have it replace the derived type declaration.
7559 Literal
:= First_Literal
(Parent_Type
);
7560 Literals_List
:= New_List
;
7561 while Present
(Literal
)
7562 and then Ekind
(Literal
) = E_Enumeration_Literal
7564 -- Literals of the derived type have the same representation as
7565 -- those of the parent type, but this representation can be
7566 -- overridden by an explicit representation clause. Indicate
7567 -- that there is no explicit representation given yet. These
7568 -- derived literals are implicit operations of the new type,
7569 -- and can be overridden by explicit ones.
7571 if Nkind
(Literal
) = N_Defining_Character_Literal
then
7573 Make_Defining_Character_Literal
(Loc
, Chars
(Literal
));
7575 New_Lit
:= Make_Defining_Identifier
(Loc
, Chars
(Literal
));
7578 Mutate_Ekind
(New_Lit
, E_Enumeration_Literal
);
7579 Set_Is_Not_Self_Hidden
(New_Lit
);
7580 Set_Enumeration_Pos
(New_Lit
, Enumeration_Pos
(Literal
));
7581 Set_Enumeration_Rep
(New_Lit
, Enumeration_Rep
(Literal
));
7582 Set_Enumeration_Rep_Expr
(New_Lit
, Empty
);
7583 Set_Alias
(New_Lit
, Literal
);
7584 Set_Is_Known_Valid
(New_Lit
, True);
7586 Append
(New_Lit
, Literals_List
);
7587 Next_Literal
(Literal
);
7591 Create_Itype
(E_Enumeration_Type
, N
, Derived_Type
, 'B');
7593 -- Indicate the proper nature of the derived type. This must be done
7594 -- before analysis of the literals, to recognize cases when a literal
7595 -- may be hidden by a previous explicit function definition (cf.
7598 Mutate_Ekind
(Derived_Type
, E_Enumeration_Subtype
);
7599 Set_Etype
(Derived_Type
, Implicit_Base
);
7602 Make_Full_Type_Declaration
(Loc
,
7603 Defining_Identifier
=> Implicit_Base
,
7605 Make_Enumeration_Type_Definition
(Loc
, Literals_List
));
7607 -- Do not insert the declarationn, just analyze it in the context
7609 Set_Parent
(Type_Decl
, Parent
(N
));
7610 Analyze
(Type_Decl
);
7612 -- The anonymous base now has a full declaration, but this base
7613 -- is not a first subtype.
7615 Set_Is_First_Subtype
(Implicit_Base
, False);
7617 -- After the implicit base is analyzed its Etype needs to be changed
7618 -- to reflect the fact that it is derived from the parent type which
7619 -- was ignored during analysis. We also set the size at this point.
7621 Set_Etype
(Implicit_Base
, Parent_Type
);
7623 Set_Size_Info
(Implicit_Base
, Parent_Type
);
7624 Set_RM_Size
(Implicit_Base
, RM_Size
(Parent_Type
));
7625 Set_First_Rep_Item
(Implicit_Base
, First_Rep_Item
(Parent_Type
));
7627 -- Copy other flags from parent type
7629 Set_Has_Non_Standard_Rep
7630 (Implicit_Base
, Has_Non_Standard_Rep
7632 Set_Has_Pragma_Ordered
7633 (Implicit_Base
, Has_Pragma_Ordered
7635 Set_Has_Delayed_Freeze
(Implicit_Base
);
7637 -- Process the subtype indication including a validation check on the
7638 -- constraint, if any. If a constraint is given, its bounds must be
7639 -- implicitly converted to the new type.
7641 if Nkind
(Indic
) = N_Subtype_Indication
then
7643 R
: constant Node_Id
:=
7644 Range_Expression
(Constraint
(Indic
));
7647 if Nkind
(R
) = N_Range
then
7648 Hi
:= Build_Scalar_Bound
7649 (High_Bound
(R
), Parent_Type
, Implicit_Base
);
7650 Lo
:= Build_Scalar_Bound
7651 (Low_Bound
(R
), Parent_Type
, Implicit_Base
);
7654 -- Constraint is a Range attribute. Replace with explicit
7655 -- mention of the bounds of the prefix, which must be a
7658 Analyze
(Prefix
(R
));
7660 Convert_To
(Implicit_Base
,
7661 Make_Attribute_Reference
(Loc
,
7662 Attribute_Name
=> Name_Last
,
7664 New_Occurrence_Of
(Entity
(Prefix
(R
)), Loc
)));
7667 Convert_To
(Implicit_Base
,
7668 Make_Attribute_Reference
(Loc
,
7669 Attribute_Name
=> Name_First
,
7671 New_Occurrence_Of
(Entity
(Prefix
(R
)), Loc
)));
7678 (Type_High_Bound
(Parent_Type
),
7679 Parent_Type
, Implicit_Base
);
7682 (Type_Low_Bound
(Parent_Type
),
7683 Parent_Type
, Implicit_Base
);
7691 -- If we constructed a default range for the case where no range
7692 -- was given, then the expressions in the range must not freeze
7693 -- since they do not correspond to expressions in the source.
7694 -- However, if the type inherits predicates the expressions will
7695 -- be elaborated earlier and must freeze.
7697 if (Nkind
(Indic
) /= N_Subtype_Indication
7699 (Bound_Belongs_To_Type
(Lo
) and then Bound_Belongs_To_Type
(Hi
)))
7700 and then not Has_Predicates
(Derived_Type
)
7702 Set_Must_Not_Freeze
(Lo
);
7703 Set_Must_Not_Freeze
(Hi
);
7704 Set_Must_Not_Freeze
(Rang_Expr
);
7708 Make_Subtype_Declaration
(Loc
,
7709 Defining_Identifier
=> Derived_Type
,
7710 Subtype_Indication
=>
7711 Make_Subtype_Indication
(Loc
,
7712 Subtype_Mark
=> New_Occurrence_Of
(Implicit_Base
, Loc
),
7714 Make_Range_Constraint
(Loc
,
7715 Range_Expression
=> Rang_Expr
))));
7719 -- Propagate the aspects from the original type declaration to the
7720 -- declaration of the implicit base.
7722 Move_Aspects
(From
=> Original_Node
(N
), To
=> Type_Decl
);
7724 -- Apply a range check. Since this range expression doesn't have an
7725 -- Etype, we have to specifically pass the Source_Typ parameter. Is
7728 if Nkind
(Indic
) = N_Subtype_Indication
then
7730 (Range_Expression
(Constraint
(Indic
)), Parent_Type
,
7731 Source_Typ
=> Entity
(Subtype_Mark
(Indic
)));
7734 end Build_Derived_Enumeration_Type
;
7736 --------------------------------
7737 -- Build_Derived_Numeric_Type --
7738 --------------------------------
7740 procedure Build_Derived_Numeric_Type
7742 Parent_Type
: Entity_Id
;
7743 Derived_Type
: Entity_Id
)
7745 Loc
: constant Source_Ptr
:= Sloc
(N
);
7746 Tdef
: constant Node_Id
:= Type_Definition
(N
);
7747 Indic
: constant Node_Id
:= Subtype_Indication
(Tdef
);
7748 Parent_Base
: constant Entity_Id
:= Base_Type
(Parent_Type
);
7749 No_Constraint
: constant Boolean := Nkind
(Indic
) /=
7750 N_Subtype_Indication
;
7751 Implicit_Base
: Entity_Id
;
7757 -- Process the subtype indication including a validation check on
7758 -- the constraint if any.
7760 Discard_Node
(Process_Subtype
(Indic
, N
));
7762 -- Introduce an implicit base type for the derived type even if there
7763 -- is no constraint attached to it, since this seems closer to the Ada
7767 Create_Itype
(Ekind
(Parent_Base
), N
, Derived_Type
, 'B');
7769 Set_Etype
(Implicit_Base
, Parent_Base
);
7770 Mutate_Ekind
(Implicit_Base
, Ekind
(Parent_Base
));
7771 Set_Size_Info
(Implicit_Base
, Parent_Base
);
7772 Set_First_Rep_Item
(Implicit_Base
, First_Rep_Item
(Parent_Base
));
7773 Set_Parent
(Implicit_Base
, Parent
(Derived_Type
));
7774 Set_Is_Known_Valid
(Implicit_Base
, Is_Known_Valid
(Parent_Base
));
7775 Set_Is_Volatile
(Implicit_Base
, Is_Volatile
(Parent_Base
));
7777 -- Set RM Size for discrete type or decimal fixed-point type
7778 -- Ordinary fixed-point is excluded, why???
7780 if Is_Discrete_Type
(Parent_Base
)
7781 or else Is_Decimal_Fixed_Point_Type
(Parent_Base
)
7783 Set_RM_Size
(Implicit_Base
, RM_Size
(Parent_Base
));
7786 Set_Has_Delayed_Freeze
(Implicit_Base
);
7788 Lo
:= New_Copy_Tree
(Type_Low_Bound
(Parent_Base
));
7789 Hi
:= New_Copy_Tree
(Type_High_Bound
(Parent_Base
));
7791 Set_Scalar_Range
(Implicit_Base
,
7796 if Has_Infinities
(Parent_Base
) then
7797 Set_Includes_Infinities
(Scalar_Range
(Implicit_Base
));
7800 -- The Derived_Type, which is the entity of the declaration, is a
7801 -- subtype of the implicit base. Its Ekind is a subtype, even in the
7802 -- absence of an explicit constraint.
7804 Set_Etype
(Derived_Type
, Implicit_Base
);
7806 -- If we did not have a constraint, then the Ekind is set from the
7807 -- parent type (otherwise Process_Subtype has set the bounds)
7809 if No_Constraint
then
7810 Mutate_Ekind
(Derived_Type
, Subtype_Kind
(Ekind
(Parent_Type
)));
7813 -- If we did not have a range constraint, then set the range from the
7814 -- parent type. Otherwise, the Process_Subtype call has set the bounds.
7816 if No_Constraint
or else not Has_Range_Constraint
(Indic
) then
7817 Set_Scalar_Range
(Derived_Type
,
7819 Low_Bound
=> New_Copy_Tree
(Type_Low_Bound
(Parent_Type
)),
7820 High_Bound
=> New_Copy_Tree
(Type_High_Bound
(Parent_Type
))));
7821 Set_Is_Constrained
(Derived_Type
, Is_Constrained
(Parent_Type
));
7823 if Has_Infinities
(Parent_Type
) then
7824 Set_Includes_Infinities
(Scalar_Range
(Derived_Type
));
7827 Set_Is_Known_Valid
(Derived_Type
, Is_Known_Valid
(Parent_Type
));
7830 Set_Is_Descendant_Of_Address
(Derived_Type
,
7831 Is_Descendant_Of_Address
(Parent_Type
));
7832 Set_Is_Descendant_Of_Address
(Implicit_Base
,
7833 Is_Descendant_Of_Address
(Parent_Type
));
7835 -- Set remaining type-specific fields, depending on numeric type
7837 if Is_Modular_Integer_Type
(Parent_Type
) then
7838 Set_Modulus
(Implicit_Base
, Modulus
(Parent_Base
));
7840 Set_Non_Binary_Modulus
7841 (Implicit_Base
, Non_Binary_Modulus
(Parent_Base
));
7844 (Implicit_Base
, Is_Known_Valid
(Parent_Base
));
7846 elsif Is_Floating_Point_Type
(Parent_Type
) then
7848 -- Digits of base type is always copied from the digits value of
7849 -- the parent base type, but the digits of the derived type will
7850 -- already have been set if there was a constraint present.
7852 Set_Digits_Value
(Implicit_Base
, Digits_Value
(Parent_Base
));
7853 Set_Float_Rep
(Implicit_Base
, Float_Rep
(Parent_Base
));
7855 if No_Constraint
then
7856 Set_Digits_Value
(Derived_Type
, Digits_Value
(Parent_Type
));
7859 elsif Is_Fixed_Point_Type
(Parent_Type
) then
7861 -- Small of base type and derived type are always copied from the
7862 -- parent base type, since smalls never change. The delta of the
7863 -- base type is also copied from the parent base type. However the
7864 -- delta of the derived type will have been set already if a
7865 -- constraint was present.
7867 Set_Small_Value
(Derived_Type
, Small_Value
(Parent_Base
));
7868 Set_Small_Value
(Implicit_Base
, Small_Value
(Parent_Base
));
7869 Set_Delta_Value
(Implicit_Base
, Delta_Value
(Parent_Base
));
7871 if No_Constraint
then
7872 Set_Delta_Value
(Derived_Type
, Delta_Value
(Parent_Type
));
7875 -- The scale and machine radix in the decimal case are always
7876 -- copied from the parent base type.
7878 if Is_Decimal_Fixed_Point_Type
(Parent_Type
) then
7879 Set_Scale_Value
(Derived_Type
, Scale_Value
(Parent_Base
));
7880 Set_Scale_Value
(Implicit_Base
, Scale_Value
(Parent_Base
));
7882 Set_Machine_Radix_10
7883 (Derived_Type
, Machine_Radix_10
(Parent_Base
));
7884 Set_Machine_Radix_10
7885 (Implicit_Base
, Machine_Radix_10
(Parent_Base
));
7887 Set_Digits_Value
(Implicit_Base
, Digits_Value
(Parent_Base
));
7889 if No_Constraint
then
7890 Set_Digits_Value
(Derived_Type
, Digits_Value
(Parent_Base
));
7893 -- the analysis of the subtype_indication sets the
7894 -- digits value of the derived type.
7901 if Is_Integer_Type
(Parent_Type
) then
7902 Set_Has_Shift_Operator
7903 (Implicit_Base
, Has_Shift_Operator
(Parent_Type
));
7906 -- The type of the bounds is that of the parent type, and they
7907 -- must be converted to the derived type.
7909 Convert_Scalar_Bounds
(N
, Parent_Type
, Derived_Type
, Loc
);
7910 end Build_Derived_Numeric_Type
;
7912 --------------------------------
7913 -- Build_Derived_Private_Type --
7914 --------------------------------
7916 procedure Build_Derived_Private_Type
7918 Parent_Type
: Entity_Id
;
7919 Derived_Type
: Entity_Id
;
7920 Is_Completion
: Boolean;
7921 Derive_Subps
: Boolean := True)
7923 Loc
: constant Source_Ptr
:= Sloc
(N
);
7924 Par_Base
: constant Entity_Id
:= Base_Type
(Parent_Type
);
7925 Par_Scope
: constant Entity_Id
:= Scope
(Par_Base
);
7926 Full_N
: constant Node_Id
:= New_Copy_Tree
(N
);
7927 Full_Der
: Entity_Id
:= New_Copy
(Derived_Type
);
7930 function Available_Full_View
(Typ
: Entity_Id
) return Entity_Id
;
7931 -- Return the Full_View or Underlying_Full_View of Typ, whichever is
7932 -- present (they cannot be both present for the same type), or Empty.
7934 procedure Build_Full_Derivation
;
7935 -- Build full derivation, i.e. derive from the full view
7937 procedure Copy_And_Build
;
7938 -- Copy derived type declaration, replace parent with its full view,
7939 -- and build derivation
7941 -------------------------
7942 -- Available_Full_View --
7943 -------------------------
7945 function Available_Full_View
(Typ
: Entity_Id
) return Entity_Id
is
7947 if Present
(Full_View
(Typ
)) then
7948 return Full_View
(Typ
);
7950 elsif Present
(Underlying_Full_View
(Typ
)) then
7952 -- We should be called on a type with an underlying full view
7953 -- only by means of the recursive call made in Copy_And_Build
7954 -- through the first call to Build_Derived_Type, or else if
7955 -- the parent scope is being analyzed because we are deriving
7958 pragma Assert
(Is_Completion
or else In_Private_Part
(Par_Scope
));
7960 return Underlying_Full_View
(Typ
);
7965 end Available_Full_View
;
7967 ---------------------------
7968 -- Build_Full_Derivation --
7969 ---------------------------
7971 procedure Build_Full_Derivation
is
7973 -- If parent scope is not open, install the declarations
7975 if not In_Open_Scopes
(Par_Scope
) then
7976 Install_Private_Declarations
(Par_Scope
);
7977 Install_Visible_Declarations
(Par_Scope
);
7979 Uninstall_Declarations
(Par_Scope
);
7981 -- If parent scope is open and in another unit, and parent has a
7982 -- completion, then the derivation is taking place in the visible
7983 -- part of a child unit. In that case retrieve the full view of
7984 -- the parent momentarily.
7986 elsif not In_Same_Source_Unit
(N
, Parent_Type
)
7987 and then Present
(Full_View
(Parent_Type
))
7989 Full_P
:= Full_View
(Parent_Type
);
7990 Exchange_Declarations
(Parent_Type
);
7992 Exchange_Declarations
(Full_P
);
7994 -- Otherwise it is a local derivation
7999 end Build_Full_Derivation
;
8001 --------------------
8002 -- Copy_And_Build --
8003 --------------------
8005 procedure Copy_And_Build
is
8006 Full_Parent
: Entity_Id
:= Parent_Type
;
8009 -- If the parent is itself derived from another private type,
8010 -- installing the private declarations has not affected its
8011 -- privacy status, so use its own full view explicitly.
8013 if Is_Private_Type
(Full_Parent
)
8014 and then Present
(Full_View
(Full_Parent
))
8016 Full_Parent
:= Full_View
(Full_Parent
);
8019 -- If the full view is itself derived from another private type
8020 -- and has got an underlying full view, and this is done for a
8021 -- completion, i.e. to build the underlying full view of the type,
8022 -- then use this underlying full view. We cannot do that if this
8023 -- is not a completion, i.e. to build the full view of the type,
8024 -- because this would break the privacy of the parent type, except
8025 -- if the parent scope is being analyzed because we are deriving a
8028 if Is_Private_Type
(Full_Parent
)
8029 and then Present
(Underlying_Full_View
(Full_Parent
))
8030 and then (Is_Completion
or else In_Private_Part
(Par_Scope
))
8032 Full_Parent
:= Underlying_Full_View
(Full_Parent
);
8035 -- For private, record, concurrent, access and almost all enumeration
8036 -- types, the derivation from the full view requires a fully-fledged
8037 -- declaration. In the other cases, just use an itype.
8039 if Is_Private_Type
(Full_Parent
)
8040 or else Is_Record_Type
(Full_Parent
)
8041 or else Is_Concurrent_Type
(Full_Parent
)
8042 or else Is_Access_Type
(Full_Parent
)
8044 (Is_Enumeration_Type
(Full_Parent
)
8045 and then not Is_Standard_Character_Type
(Full_Parent
)
8046 and then not Is_Generic_Type
(Root_Type
(Full_Parent
)))
8048 -- Copy and adjust declaration to provide a completion for what
8049 -- is originally a private declaration. Indicate that full view
8050 -- is internally generated.
8052 Set_Comes_From_Source
(Full_N
, False);
8053 Set_Comes_From_Source
(Full_Der
, False);
8054 Set_Parent
(Full_Der
, Full_N
);
8055 Set_Defining_Identifier
(Full_N
, Full_Der
);
8057 -- If there are no constraints, adjust the subtype mark
8059 if Nkind
(Subtype_Indication
(Type_Definition
(Full_N
))) /=
8060 N_Subtype_Indication
8062 Set_Subtype_Indication
8063 (Type_Definition
(Full_N
),
8064 New_Occurrence_Of
(Full_Parent
, Sloc
(Full_N
)));
8067 Insert_After
(N
, Full_N
);
8069 -- Build full view of derived type from full view of parent which
8070 -- is now installed. Subprograms have been derived on the partial
8071 -- view, the completion does not derive them anew.
8073 if Is_Record_Type
(Full_Parent
) then
8075 -- If parent type is tagged, the completion inherits the proper
8076 -- primitive operations.
8078 if Is_Tagged_Type
(Parent_Type
) then
8079 Build_Derived_Record_Type
8080 (Full_N
, Full_Parent
, Full_Der
, Derive_Subps
);
8082 Build_Derived_Record_Type
8083 (Full_N
, Full_Parent
, Full_Der
, Derive_Subps
=> False);
8087 -- If the parent type is private, this is not a completion and
8088 -- we build the full derivation recursively as a completion.
8091 (Full_N
, Full_Parent
, Full_Der
,
8092 Is_Completion
=> Is_Private_Type
(Full_Parent
),
8093 Derive_Subps
=> False);
8096 -- The full declaration has been introduced into the tree and
8097 -- processed in the step above. It should not be analyzed again
8098 -- (when encountered later in the current list of declarations)
8099 -- to prevent spurious name conflicts. The full entity remains
8102 Set_Analyzed
(Full_N
);
8106 Make_Defining_Identifier
(Sloc
(Derived_Type
),
8107 Chars
=> Chars
(Derived_Type
));
8108 Set_Is_Itype
(Full_Der
);
8109 Set_Associated_Node_For_Itype
(Full_Der
, N
);
8110 Set_Parent
(Full_Der
, N
);
8112 (N
, Full_Parent
, Full_Der
,
8113 Is_Completion
=> False, Derive_Subps
=> False);
8114 Set_Is_Not_Self_Hidden
(Full_Der
);
8117 Set_Has_Private_Declaration
(Full_Der
);
8118 Set_Has_Private_Declaration
(Derived_Type
);
8120 Set_Scope
(Full_Der
, Scope
(Derived_Type
));
8121 Set_Is_First_Subtype
(Full_Der
, Is_First_Subtype
(Derived_Type
));
8122 Set_Has_Size_Clause
(Full_Der
, False);
8123 Set_Has_Alignment_Clause
(Full_Der
, False);
8124 Set_Has_Delayed_Freeze
(Full_Der
);
8125 Set_Is_Frozen
(Full_Der
, False);
8126 Set_Freeze_Node
(Full_Der
, Empty
);
8127 Set_Depends_On_Private
(Full_Der
, Has_Private_Component
(Full_Der
));
8128 Set_Is_Public
(Full_Der
, Is_Public
(Derived_Type
));
8130 -- The convention on the base type may be set in the private part
8131 -- and not propagated to the subtype until later, so we obtain the
8132 -- convention from the base type of the parent.
8134 Set_Convention
(Full_Der
, Convention
(Base_Type
(Full_Parent
)));
8137 -- Start of processing for Build_Derived_Private_Type
8140 if Is_Tagged_Type
(Parent_Type
) then
8141 Full_P
:= Full_View
(Parent_Type
);
8143 -- A type extension of a type with unknown discriminants is an
8144 -- indefinite type that the back-end cannot handle directly.
8145 -- We treat it as a private type, and build a completion that is
8146 -- derived from the full view of the parent, and hopefully has
8147 -- known discriminants.
8149 -- If the full view of the parent type has an underlying record view,
8150 -- use it to generate the underlying record view of this derived type
8151 -- (required for chains of derivations with unknown discriminants).
8153 -- Minor optimization: we avoid the generation of useless underlying
8154 -- record view entities if the private type declaration has unknown
8155 -- discriminants but its corresponding full view has no
8158 if Has_Unknown_Discriminants
(Parent_Type
)
8159 and then Present
(Full_P
)
8160 and then (Has_Discriminants
(Full_P
)
8161 or else Present
(Underlying_Record_View
(Full_P
)))
8162 and then not In_Open_Scopes
(Par_Scope
)
8163 and then Expander_Active
8166 Full_Der
: constant Entity_Id
:= Make_Temporary
(Loc
, 'T');
8167 New_Ext
: constant Node_Id
:=
8169 (Record_Extension_Part
(Type_Definition
(N
)));
8173 Build_Derived_Record_Type
8174 (N
, Parent_Type
, Derived_Type
, Derive_Subps
);
8176 -- Build anonymous completion, as a derivation from the full
8177 -- view of the parent. This is not a completion in the usual
8178 -- sense, because the current type is not private.
8181 Make_Full_Type_Declaration
(Loc
,
8182 Defining_Identifier
=> Full_Der
,
8184 Make_Derived_Type_Definition
(Loc
,
8185 Subtype_Indication
=>
8187 (Subtype_Indication
(Type_Definition
(N
))),
8188 Record_Extension_Part
=> New_Ext
));
8190 -- If the parent type has an underlying record view, use it
8191 -- here to build the new underlying record view.
8193 if Present
(Underlying_Record_View
(Full_P
)) then
8195 (Nkind
(Subtype_Indication
(Type_Definition
(Decl
)))
8197 Set_Entity
(Subtype_Indication
(Type_Definition
(Decl
)),
8198 Underlying_Record_View
(Full_P
));
8201 Install_Private_Declarations
(Par_Scope
);
8202 Install_Visible_Declarations
(Par_Scope
);
8203 Insert_Before
(N
, Decl
);
8205 -- Mark entity as an underlying record view before analysis,
8206 -- to avoid generating the list of its primitive operations
8207 -- (which is not really required for this entity) and thus
8208 -- prevent spurious errors associated with missing overriding
8209 -- of abstract primitives (overridden only for Derived_Type).
8211 Mutate_Ekind
(Full_Der
, E_Record_Type
);
8212 Set_Is_Underlying_Record_View
(Full_Der
);
8213 Set_Default_SSO
(Full_Der
);
8214 Set_No_Reordering
(Full_Der
, No_Component_Reordering
);
8218 pragma Assert
(Has_Discriminants
(Full_Der
)
8219 and then not Has_Unknown_Discriminants
(Full_Der
));
8221 Uninstall_Declarations
(Par_Scope
);
8223 -- Freeze the underlying record view, to prevent generation of
8224 -- useless dispatching information, which is simply shared with
8225 -- the real derived type.
8227 Set_Is_Frozen
(Full_Der
);
8229 -- If the derived type has access discriminants, create
8230 -- references to their anonymous types now, to prevent
8231 -- back-end problems when their first use is in generated
8232 -- bodies of primitives.
8238 E
:= First_Entity
(Full_Der
);
8240 while Present
(E
) loop
8241 if Ekind
(E
) = E_Discriminant
8242 and then Ekind
(Etype
(E
)) = E_Anonymous_Access_Type
8244 Build_Itype_Reference
(Etype
(E
), Decl
);
8251 -- Set up links between real entity and underlying record view
8253 Set_Underlying_Record_View
(Derived_Type
, Base_Type
(Full_Der
));
8254 Set_Underlying_Record_View
(Base_Type
(Full_Der
), Derived_Type
);
8257 -- If discriminants are known, build derived record
8260 Build_Derived_Record_Type
8261 (N
, Parent_Type
, Derived_Type
, Derive_Subps
);
8266 elsif Has_Discriminants
(Parent_Type
) then
8268 -- Build partial view of derived type from partial view of parent.
8269 -- This must be done before building the full derivation because the
8270 -- second derivation will modify the discriminants of the first and
8271 -- the discriminants are chained with the rest of the components in
8272 -- the full derivation.
8274 Build_Derived_Record_Type
8275 (N
, Parent_Type
, Derived_Type
, Derive_Subps
);
8277 -- Build the full derivation if this is not the anonymous derived
8278 -- base type created by Build_Derived_Record_Type in the constrained
8279 -- case (see point 5. of its head comment) since we build it for the
8282 if Present
(Available_Full_View
(Parent_Type
))
8283 and then not Is_Itype
(Derived_Type
)
8286 Der_Base
: constant Entity_Id
:= Base_Type
(Derived_Type
);
8288 Last_Discr
: Entity_Id
;
8291 -- If this is not a completion, construct the implicit full
8292 -- view by deriving from the full view of the parent type.
8293 -- But if this is a completion, the derived private type
8294 -- being built is a full view and the full derivation can
8295 -- only be its underlying full view.
8297 Build_Full_Derivation
;
8299 if not Is_Completion
then
8300 Set_Full_View
(Derived_Type
, Full_Der
);
8302 Set_Underlying_Full_View
(Derived_Type
, Full_Der
);
8303 Set_Is_Underlying_Full_View
(Full_Der
);
8306 if not Is_Base_Type
(Derived_Type
) then
8307 Set_Full_View
(Der_Base
, Base_Type
(Full_Der
));
8310 -- Copy the discriminant list from full view to the partial
8311 -- view (base type and its subtype). Gigi requires that the
8312 -- partial and full views have the same discriminants.
8314 -- Note that since the partial view points to discriminants
8315 -- in the full view, their scope will be that of the full
8316 -- view. This might cause some front end problems and need
8319 Discr
:= First_Discriminant
(Base_Type
(Full_Der
));
8320 Set_First_Entity
(Der_Base
, Discr
);
8323 Last_Discr
:= Discr
;
8324 Next_Discriminant
(Discr
);
8325 exit when No
(Discr
);
8328 Set_Last_Entity
(Der_Base
, Last_Discr
);
8329 Set_First_Entity
(Derived_Type
, First_Entity
(Der_Base
));
8330 Set_Last_Entity
(Derived_Type
, Last_Entity
(Der_Base
));
8334 elsif Present
(Available_Full_View
(Parent_Type
))
8335 and then Has_Discriminants
(Available_Full_View
(Parent_Type
))
8337 if Has_Unknown_Discriminants
(Parent_Type
)
8338 and then Nkind
(Subtype_Indication
(Type_Definition
(N
))) =
8339 N_Subtype_Indication
8342 ("cannot constrain type with unknown discriminants",
8343 Subtype_Indication
(Type_Definition
(N
)));
8347 -- If this is not a completion, construct the implicit full view by
8348 -- deriving from the full view of the parent type. But if this is a
8349 -- completion, the derived private type being built is a full view
8350 -- and the full derivation can only be its underlying full view.
8352 Build_Full_Derivation
;
8354 if not Is_Completion
then
8355 Set_Full_View
(Derived_Type
, Full_Der
);
8357 Set_Underlying_Full_View
(Derived_Type
, Full_Der
);
8358 Set_Is_Underlying_Full_View
(Full_Der
);
8361 -- In any case, the primitive operations are inherited from the
8362 -- parent type, not from the internal full view.
8364 Set_Etype
(Base_Type
(Derived_Type
), Base_Type
(Parent_Type
));
8366 if Derive_Subps
then
8367 -- Initialize the list of primitive operations to an empty list,
8368 -- to cover tagged types as well as untagged types. For untagged
8369 -- types this is used either to analyze the call as legal when
8370 -- Extensions_Allowed is True, or to issue a better error message
8373 Set_Direct_Primitive_Operations
(Derived_Type
, New_Elmt_List
);
8375 Derive_Subprograms
(Parent_Type
, Derived_Type
);
8378 Set_Stored_Constraint
(Derived_Type
, No_Elist
);
8380 (Derived_Type
, Is_Constrained
(Available_Full_View
(Parent_Type
)));
8383 -- Untagged type, No discriminants on either view
8385 if Nkind
(Subtype_Indication
(Type_Definition
(N
))) =
8386 N_Subtype_Indication
8389 ("illegal constraint on type without discriminants", N
);
8392 if Present
(Discriminant_Specifications
(N
))
8393 and then Present
(Available_Full_View
(Parent_Type
))
8394 and then not Is_Tagged_Type
(Available_Full_View
(Parent_Type
))
8396 Error_Msg_N
("cannot add discriminants to untagged type", N
);
8399 Set_Stored_Constraint
(Derived_Type
, No_Elist
);
8400 Set_Is_Constrained
(Derived_Type
, Is_Constrained
(Parent_Type
));
8402 Set_Is_Controlled_Active
8403 (Derived_Type
, Is_Controlled_Active
(Parent_Type
));
8405 Set_Disable_Controlled
8406 (Derived_Type
, Disable_Controlled
(Parent_Type
));
8408 Set_Has_Controlled_Component
8409 (Derived_Type
, Has_Controlled_Component
(Parent_Type
));
8411 -- Direct controlled types do not inherit Finalize_Storage_Only flag
8413 if not Is_Controlled
(Parent_Type
) then
8414 Set_Finalize_Storage_Only
8415 (Base_Type
(Derived_Type
), Finalize_Storage_Only
(Parent_Type
));
8418 -- If this is not a completion, construct the implicit full view by
8419 -- deriving from the full view of the parent type. But if this is a
8420 -- completion, the derived private type being built is a full view
8421 -- and the full derivation can only be its underlying full view.
8423 -- ??? If the parent type is untagged private and its completion is
8424 -- tagged, this mechanism will not work because we cannot derive from
8425 -- the tagged full view unless we have an extension.
8427 if Present
(Available_Full_View
(Parent_Type
))
8428 and then not Is_Tagged_Type
(Available_Full_View
(Parent_Type
))
8429 and then not Error_Posted
(N
)
8431 Build_Full_Derivation
;
8433 if not Is_Completion
then
8434 Set_Full_View
(Derived_Type
, Full_Der
);
8436 Set_Underlying_Full_View
(Derived_Type
, Full_Der
);
8437 Set_Is_Underlying_Full_View
(Full_Der
);
8442 Set_Has_Unknown_Discriminants
(Derived_Type
,
8443 Has_Unknown_Discriminants
(Parent_Type
));
8445 if Is_Private_Type
(Derived_Type
) then
8446 Set_Private_Dependents
(Derived_Type
, New_Elmt_List
);
8449 -- If the parent base type is in scope, add the derived type to its
8450 -- list of private dependents, because its full view may become
8451 -- visible subsequently (in a nested private part, a body, or in a
8452 -- further child unit).
8454 if Is_Private_Type
(Par_Base
) and then In_Open_Scopes
(Par_Scope
) then
8455 Append_Elmt
(Derived_Type
, Private_Dependents
(Parent_Type
));
8457 -- Check for unusual case where a type completed by a private
8458 -- derivation occurs within a package nested in a child unit, and
8459 -- the parent is declared in an ancestor.
8461 if Is_Child_Unit
(Scope
(Current_Scope
))
8462 and then Is_Completion
8463 and then In_Private_Part
(Current_Scope
)
8464 and then Scope
(Parent_Type
) /= Current_Scope
8466 -- Note that if the parent has a completion in the private part,
8467 -- (which is itself a derivation from some other private type)
8468 -- it is that completion that is visible, there is no full view
8469 -- available, and no special processing is needed.
8471 and then Present
(Full_View
(Parent_Type
))
8473 -- In this case, the full view of the parent type will become
8474 -- visible in the body of the enclosing child, and only then will
8475 -- the current type be possibly non-private. Build an underlying
8476 -- full view that will be installed when the enclosing child body
8479 if Present
(Underlying_Full_View
(Derived_Type
)) then
8480 Full_Der
:= Underlying_Full_View
(Derived_Type
);
8482 Build_Full_Derivation
;
8483 Set_Underlying_Full_View
(Derived_Type
, Full_Der
);
8484 Set_Is_Underlying_Full_View
(Full_Der
);
8487 -- The full view will be used to swap entities on entry/exit to
8488 -- the body, and must appear in the entity list for the package.
8490 Append_Entity
(Full_Der
, Scope
(Derived_Type
));
8493 end Build_Derived_Private_Type
;
8495 -------------------------------
8496 -- Build_Derived_Record_Type --
8497 -------------------------------
8501 -- Ideally we would like to use the same model of type derivation for
8502 -- tagged and untagged record types. Unfortunately this is not quite
8503 -- possible because the semantics of representation clauses is different
8504 -- for tagged and untagged records under inheritance. Consider the
8507 -- type R (...) is [tagged] record ... end record;
8508 -- type T (...) is new R (...) [with ...];
8510 -- The representation clauses for T can specify a completely different
8511 -- record layout from R's. Hence the same component can be placed in two
8512 -- very different positions in objects of type T and R. If R and T are
8513 -- tagged types, representation clauses for T can only specify the layout
8514 -- of non inherited components, thus components that are common in R and T
8515 -- have the same position in objects of type R and T.
8517 -- This has two implications. The first is that the entire tree for R's
8518 -- declaration needs to be copied for T in the untagged case, so that T
8519 -- can be viewed as a record type of its own with its own representation
8520 -- clauses. The second implication is the way we handle discriminants.
8521 -- Specifically, in the untagged case we need a way to communicate to Gigi
8522 -- what are the real discriminants in the record, while for the semantics
8523 -- we need to consider those introduced by the user to rename the
8524 -- discriminants in the parent type. This is handled by introducing the
8525 -- notion of stored discriminants. See below for more.
8527 -- Fortunately the way regular components are inherited can be handled in
8528 -- the same way in tagged and untagged types.
8530 -- To complicate things a bit more the private view of a private extension
8531 -- cannot be handled in the same way as the full view (for one thing the
8532 -- semantic rules are somewhat different). We will explain what differs
8535 -- 2. DISCRIMINANTS UNDER INHERITANCE
8537 -- The semantic rules governing the discriminants of derived types are
8540 -- type Derived_Type_Name [KNOWN_DISCRIMINANT_PART] is new
8541 -- [abstract] Parent_Type_Name [CONSTRAINT] [RECORD_EXTENSION_PART]
8543 -- If parent type has discriminants, then the discriminants that are
8544 -- declared in the derived type are [3.4 (11)]:
8546 -- o The discriminants specified by a new KNOWN_DISCRIMINANT_PART, if
8549 -- o Otherwise, each discriminant of the parent type (implicitly declared
8550 -- in the same order with the same specifications). In this case, the
8551 -- discriminants are said to be "inherited", or if unknown in the parent
8552 -- are also unknown in the derived type.
8554 -- Furthermore if a KNOWN_DISCRIMINANT_PART is provided, then [3.7(13-18)]:
8556 -- o The parent subtype must be constrained;
8558 -- o If the parent type is not a tagged type, then each discriminant of
8559 -- the derived type must be used in the constraint defining a parent
8560 -- subtype. [Implementation note: This ensures that the new discriminant
8561 -- can share storage with an existing discriminant.]
8563 -- For the derived type each discriminant of the parent type is either
8564 -- inherited, constrained to equal some new discriminant of the derived
8565 -- type, or constrained to the value of an expression.
8567 -- When inherited or constrained to equal some new discriminant, the
8568 -- parent discriminant and the discriminant of the derived type are said
8571 -- If a discriminant of the parent type is constrained to a specific value
8572 -- in the derived type definition, then the discriminant is said to be
8573 -- "specified" by that derived type definition.
8575 -- 3. DISCRIMINANTS IN DERIVED UNTAGGED RECORD TYPES
8577 -- We have spoken about stored discriminants in point 1 (introduction)
8578 -- above. There are two sorts of stored discriminants: implicit and
8579 -- explicit. As long as the derived type inherits the same discriminants as
8580 -- the root record type, stored discriminants are the same as regular
8581 -- discriminants, and are said to be implicit. However, if any discriminant
8582 -- in the root type was renamed in the derived type, then the derived
8583 -- type will contain explicit stored discriminants. Explicit stored
8584 -- discriminants are discriminants in addition to the semantically visible
8585 -- discriminants defined for the derived type. Stored discriminants are
8586 -- used by Gigi to figure out what are the physical discriminants in
8587 -- objects of the derived type (see precise definition in einfo.ads).
8588 -- As an example, consider the following:
8590 -- type R (D1, D2, D3 : Int) is record ... end record;
8591 -- type T1 is new R;
8592 -- type T2 (X1, X2: Int) is new T1 (X2, 88, X1);
8593 -- type T3 is new T2;
8594 -- type T4 (Y : Int) is new T3 (Y, 99);
8596 -- The following table summarizes the discriminants and stored
8597 -- discriminants in R and T1 through T4:
8599 -- Type Discrim Stored Discrim Comment
8600 -- R (D1, D2, D3) (D1, D2, D3) Stored discrims implicit in R
8601 -- T1 (D1, D2, D3) (D1, D2, D3) Stored discrims implicit in T1
8602 -- T2 (X1, X2) (D1, D2, D3) Stored discrims EXPLICIT in T2
8603 -- T3 (X1, X2) (D1, D2, D3) Stored discrims EXPLICIT in T3
8604 -- T4 (Y) (D1, D2, D3) Stored discrims EXPLICIT in T4
8606 -- Field Corresponding_Discriminant (abbreviated CD below) allows us to
8607 -- find the corresponding discriminant in the parent type, while
8608 -- Original_Record_Component (abbreviated ORC below) the actual physical
8609 -- component that is renamed. Finally the field Is_Completely_Hidden
8610 -- (abbreviated ICH below) is set for all explicit stored discriminants
8611 -- (see einfo.ads for more info). For the above example this gives:
8613 -- Discrim CD ORC ICH
8614 -- ^^^^^^^ ^^ ^^^ ^^^
8615 -- D1 in R empty itself no
8616 -- D2 in R empty itself no
8617 -- D3 in R empty itself no
8619 -- D1 in T1 D1 in R itself no
8620 -- D2 in T1 D2 in R itself no
8621 -- D3 in T1 D3 in R itself no
8623 -- X1 in T2 D3 in T1 D3 in T2 no
8624 -- X2 in T2 D1 in T1 D1 in T2 no
8625 -- D1 in T2 empty itself yes
8626 -- D2 in T2 empty itself yes
8627 -- D3 in T2 empty itself yes
8629 -- X1 in T3 X1 in T2 D3 in T3 no
8630 -- X2 in T3 X2 in T2 D1 in T3 no
8631 -- D1 in T3 empty itself yes
8632 -- D2 in T3 empty itself yes
8633 -- D3 in T3 empty itself yes
8635 -- Y in T4 X1 in T3 D3 in T4 no
8636 -- D1 in T4 empty itself yes
8637 -- D2 in T4 empty itself yes
8638 -- D3 in T4 empty itself yes
8640 -- 4. DISCRIMINANTS IN DERIVED TAGGED RECORD TYPES
8642 -- Type derivation for tagged types is fairly straightforward. If no
8643 -- discriminants are specified by the derived type, these are inherited
8644 -- from the parent. No explicit stored discriminants are ever necessary.
8645 -- The only manipulation that is done to the tree is that of adding a
8646 -- _parent field with parent type and constrained to the same constraint
8647 -- specified for the parent in the derived type definition. For instance:
8649 -- type R (D1, D2, D3 : Int) is tagged record ... end record;
8650 -- type T1 is new R with null record;
8651 -- type T2 (X1, X2: Int) is new T1 (X2, 88, X1) with null record;
8653 -- are changed into:
8655 -- type T1 (D1, D2, D3 : Int) is new R (D1, D2, D3) with record
8656 -- _parent : R (D1, D2, D3);
8659 -- type T2 (X1, X2: Int) is new T1 (X2, 88, X1) with record
8660 -- _parent : T1 (X2, 88, X1);
8663 -- The discriminants actually present in R, T1 and T2 as well as their CD,
8664 -- ORC and ICH fields are:
8666 -- Discrim CD ORC ICH
8667 -- ^^^^^^^ ^^ ^^^ ^^^
8668 -- D1 in R empty itself no
8669 -- D2 in R empty itself no
8670 -- D3 in R empty itself no
8672 -- D1 in T1 D1 in R D1 in R no
8673 -- D2 in T1 D2 in R D2 in R no
8674 -- D3 in T1 D3 in R D3 in R no
8676 -- X1 in T2 D3 in T1 D3 in R no
8677 -- X2 in T2 D1 in T1 D1 in R no
8679 -- 5. FIRST TRANSFORMATION FOR DERIVED RECORDS
8681 -- Regardless of whether we are dealing with a tagged or untagged type
8682 -- we will transform all derived type declarations of the form
8684 -- type T is new R (...) [with ...];
8686 -- subtype S is R (...);
8687 -- type T is new S [with ...];
8689 -- type BT is new R [with ...];
8690 -- subtype T is BT (...);
8692 -- That is, the base derived type is constrained only if it has no
8693 -- discriminants. The reason for doing this is that GNAT's semantic model
8694 -- assumes that a base type with discriminants is unconstrained.
8696 -- Note that, strictly speaking, the above transformation is not always
8697 -- correct. Consider for instance the following excerpt from ACVC b34011a:
8699 -- procedure B34011A is
8700 -- type REC (D : integer := 0) is record
8705 -- type T6 is new Rec;
8706 -- function F return T6;
8711 -- type U is new T6 (Q6.F.I); -- ERROR: Q6.F.
8714 -- The definition of Q6.U is illegal. However transforming Q6.U into
8716 -- type BaseU is new T6;
8717 -- subtype U is BaseU (Q6.F.I)
8719 -- turns U into a legal subtype, which is incorrect. To avoid this problem
8720 -- we always analyze the constraint (in this case (Q6.F.I)) before applying
8721 -- the transformation described above.
8723 -- There is another instance where the above transformation is incorrect.
8727 -- type Base (D : Integer) is tagged null record;
8728 -- procedure P (X : Base);
8730 -- type Der is new Base (2) with null record;
8731 -- procedure P (X : Der);
8734 -- Then the above transformation turns this into
8736 -- type Der_Base is new Base with null record;
8737 -- -- procedure P (X : Base) is implicitly inherited here
8738 -- -- as procedure P (X : Der_Base).
8740 -- subtype Der is Der_Base (2);
8741 -- procedure P (X : Der);
8742 -- -- The overriding of P (X : Der_Base) is illegal since we
8743 -- -- have a parameter conformance problem.
8745 -- To get around this problem, after having semantically processed Der_Base
8746 -- and the rewritten subtype declaration for Der, we copy Der_Base field
8747 -- Discriminant_Constraint from Der so that when parameter conformance is
8748 -- checked when P is overridden, no semantic errors are flagged.
8750 -- 6. SECOND TRANSFORMATION FOR DERIVED RECORDS
8752 -- Regardless of whether we are dealing with a tagged or untagged type
8753 -- we will transform all derived type declarations of the form
8755 -- type R (D1, .., Dn : ...) is [tagged] record ...;
8756 -- type T is new R [with ...];
8758 -- type T (D1, .., Dn : ...) is new R (D1, .., Dn) [with ...];
8760 -- The reason for such transformation is that it allows us to implement a
8761 -- very clean form of component inheritance as explained below.
8763 -- Note that this transformation is not achieved by direct tree rewriting
8764 -- and manipulation, but rather by redoing the semantic actions that the
8765 -- above transformation will entail. This is done directly in routine
8766 -- Inherit_Components.
8768 -- 7. TYPE DERIVATION AND COMPONENT INHERITANCE
8770 -- In both tagged and untagged derived types, regular non discriminant
8771 -- components are inherited in the derived type from the parent type. In
8772 -- the absence of discriminants component, inheritance is straightforward
8773 -- as components can simply be copied from the parent.
8775 -- If the parent has discriminants, inheriting components constrained with
8776 -- these discriminants requires caution. Consider the following example:
8778 -- type R (D1, D2 : Positive) is [tagged] record
8779 -- S : String (D1 .. D2);
8782 -- type T1 is new R [with null record];
8783 -- type T2 (X : positive) is new R (1, X) [with null record];
8785 -- As explained in 6. above, T1 is rewritten as
8786 -- type T1 (D1, D2 : Positive) is new R (D1, D2) [with null record];
8787 -- which makes the treatment for T1 and T2 identical.
8789 -- What we want when inheriting S, is that references to D1 and D2 in R are
8790 -- replaced with references to their correct constraints, i.e. D1 and D2 in
8791 -- T1 and 1 and X in T2. So all R's discriminant references are replaced
8792 -- with either discriminant references in the derived type or expressions.
8793 -- This replacement is achieved as follows: before inheriting R's
8794 -- components, a subtype R (D1, D2) for T1 (resp. R (1, X) for T2) is
8795 -- created in the scope of T1 (resp. scope of T2) so that discriminants D1
8796 -- and D2 of T1 are visible (resp. discriminant X of T2 is visible).
8797 -- For T2, for instance, this has the effect of replacing String (D1 .. D2)
8798 -- by String (1 .. X).
8800 -- 8. TYPE DERIVATION IN PRIVATE TYPE EXTENSIONS
8802 -- We explain here the rules governing private type extensions relevant to
8803 -- type derivation. These rules are explained on the following example:
8805 -- type D [(...)] is new A [(...)] with private; <-- partial view
8806 -- type D [(...)] is new P [(...)] with null record; <-- full view
8808 -- Type A is called the ancestor subtype of the private extension.
8809 -- Type P is the parent type of the full view of the private extension. It
8810 -- must be A or a type derived from A.
8812 -- The rules concerning the discriminants of private type extensions are
8815 -- o If a private extension inherits known discriminants from the ancestor
8816 -- subtype, then the full view must also inherit its discriminants from
8817 -- the ancestor subtype and the parent subtype of the full view must be
8818 -- constrained if and only if the ancestor subtype is constrained.
8820 -- o If a partial view has unknown discriminants, then the full view may
8821 -- define a definite or an indefinite subtype, with or without
8824 -- o If a partial view has neither known nor unknown discriminants, then
8825 -- the full view must define a definite subtype.
8827 -- o If the ancestor subtype of a private extension has constrained
8828 -- discriminants, then the parent subtype of the full view must impose a
8829 -- statically matching constraint on those discriminants.
8831 -- This means that only the following forms of private extensions are
8834 -- type D is new A with private; <-- partial view
8835 -- type D is new P with null record; <-- full view
8837 -- If A has no discriminants than P has no discriminants, otherwise P must
8838 -- inherit A's discriminants.
8840 -- type D is new A (...) with private; <-- partial view
8841 -- type D is new P (:::) with null record; <-- full view
8843 -- P must inherit A's discriminants and (...) and (:::) must statically
8846 -- subtype A is R (...);
8847 -- type D is new A with private; <-- partial view
8848 -- type D is new P with null record; <-- full view
8850 -- P must have inherited R's discriminants and must be derived from A or
8851 -- any of its subtypes.
8853 -- type D (..) is new A with private; <-- partial view
8854 -- type D (..) is new P [(:::)] with null record; <-- full view
8856 -- No specific constraints on P's discriminants or constraint (:::).
8857 -- Note that A can be unconstrained, but the parent subtype P must either
8858 -- be constrained or (:::) must be present.
8860 -- type D (..) is new A [(...)] with private; <-- partial view
8861 -- type D (..) is new P [(:::)] with null record; <-- full view
8863 -- P's constraints on A's discriminants must statically match those
8864 -- imposed by (...).
8866 -- 9. IMPLEMENTATION OF TYPE DERIVATION FOR PRIVATE EXTENSIONS
8868 -- The full view of a private extension is handled exactly as described
8869 -- above. The model chose for the private view of a private extension is
8870 -- the same for what concerns discriminants (i.e. they receive the same
8871 -- treatment as in the tagged case). However, the private view of the
8872 -- private extension always inherits the components of the parent base,
8873 -- without replacing any discriminant reference. Strictly speaking this is
8874 -- incorrect. However, Gigi never uses this view to generate code so this
8875 -- is a purely semantic issue. In theory, a set of transformations similar
8876 -- to those given in 5. and 6. above could be applied to private views of
8877 -- private extensions to have the same model of component inheritance as
8878 -- for non private extensions. However, this is not done because it would
8879 -- further complicate private type processing. Semantically speaking, this
8880 -- leaves us in an uncomfortable situation. As an example consider:
8883 -- type R (D : integer) is tagged record
8884 -- S : String (1 .. D);
8886 -- procedure P (X : R);
8887 -- type T is new R (1) with private;
8889 -- type T is new R (1) with null record;
8892 -- This is transformed into:
8895 -- type R (D : integer) is tagged record
8896 -- S : String (1 .. D);
8898 -- procedure P (X : R);
8899 -- type T is new R (1) with private;
8901 -- type BaseT is new R with null record;
8902 -- subtype T is BaseT (1);
8905 -- (strictly speaking the above is incorrect Ada)
8907 -- From the semantic standpoint the private view of private extension T
8908 -- should be flagged as constrained since one can clearly have
8912 -- in a unit withing Pack. However, when deriving subprograms for the
8913 -- private view of private extension T, T must be seen as unconstrained
8914 -- since T has discriminants (this is a constraint of the current
8915 -- subprogram derivation model). Thus, when processing the private view of
8916 -- a private extension such as T, we first mark T as unconstrained, we
8917 -- process it, we perform program derivation and just before returning from
8918 -- Build_Derived_Record_Type we mark T as constrained.
8920 -- ??? Are there are other uncomfortable cases that we will have to
8923 -- 10. RECORD_TYPE_WITH_PRIVATE complications
8925 -- Types that are derived from a visible record type and have a private
8926 -- extension present other peculiarities. They behave mostly like private
8927 -- types, but if they have primitive operations defined, these will not
8928 -- have the proper signatures for further inheritance, because other
8929 -- primitive operations will use the implicit base that we define for
8930 -- private derivations below. This affect subprogram inheritance (see
8931 -- Derive_Subprograms for details). We also derive the implicit base from
8932 -- the base type of the full view, so that the implicit base is a record
8933 -- type and not another private type, This avoids infinite loops.
8935 procedure Build_Derived_Record_Type
8937 Parent_Type
: Entity_Id
;
8938 Derived_Type
: Entity_Id
;
8939 Derive_Subps
: Boolean := True)
8941 Discriminant_Specs
: constant Boolean :=
8942 Present
(Discriminant_Specifications
(N
));
8943 Is_Tagged
: constant Boolean := Is_Tagged_Type
(Parent_Type
);
8944 Loc
: constant Source_Ptr
:= Sloc
(N
);
8945 Private_Extension
: constant Boolean :=
8946 Nkind
(N
) = N_Private_Extension_Declaration
;
8947 Assoc_List
: Elist_Id
;
8948 Constraint_Present
: Boolean;
8950 Discrim
: Entity_Id
;
8952 Inherit_Discrims
: Boolean := False;
8953 Last_Discrim
: Entity_Id
;
8954 New_Base
: Entity_Id
;
8956 New_Discrs
: Elist_Id
;
8957 New_Indic
: Node_Id
;
8958 Parent_Base
: Entity_Id
;
8959 Save_Etype
: Entity_Id
;
8960 Save_Discr_Constr
: Elist_Id
;
8961 Save_Next_Entity
: Entity_Id
;
8964 Discs
: Elist_Id
:= New_Elmt_List
;
8965 -- An empty Discs list means that there were no constraints in the
8966 -- subtype indication or that there was an error processing it.
8968 procedure Check_Generic_Ancestors
;
8969 -- In Ada 2005 (AI-344), the restriction that a derived tagged type
8970 -- cannot be declared at a deeper level than its parent type is
8971 -- removed. The check on derivation within a generic body is also
8972 -- relaxed, but there's a restriction that a derived tagged type
8973 -- cannot be declared in a generic body if it's derived directly
8974 -- or indirectly from a formal type of that generic. This applies
8975 -- to progenitors as well.
8977 -----------------------------
8978 -- Check_Generic_Ancestors --
8979 -----------------------------
8981 procedure Check_Generic_Ancestors
is
8982 Ancestor_Type
: Entity_Id
;
8983 Intf_List
: List_Id
;
8984 Intf_Name
: Node_Id
;
8986 procedure Check_Ancestor
;
8987 -- For parent and progenitors.
8989 --------------------
8990 -- Check_Ancestor --
8991 --------------------
8993 procedure Check_Ancestor
is
8995 -- If the derived type does have a formal type as an ancestor
8996 -- then it's an error if the derived type is declared within
8997 -- the body of the generic unit that declares the formal type
8998 -- in its generic formal part. It's sufficient to check whether
8999 -- the ancestor type is declared inside the same generic body
9000 -- as the derived type (such as within a nested generic spec),
9001 -- in which case the derivation is legal. If the formal type is
9002 -- declared outside of that generic body, then it's certain
9003 -- that the derived type is declared within the generic body
9004 -- of the generic unit declaring the formal type.
9006 if Is_Generic_Type
(Ancestor_Type
)
9007 and then Enclosing_Generic_Body
(Ancestor_Type
) /=
9008 Enclosing_Generic_Body
(Derived_Type
)
9011 ("ancestor type& is formal type of enclosing"
9012 & " generic unit (RM 3.9.1 (4/2))",
9013 Indic
, Ancestor_Type
);
9018 if Nkind
(N
) = N_Private_Extension_Declaration
then
9019 Intf_List
:= Interface_List
(N
);
9021 Intf_List
:= Interface_List
(Type_Definition
(N
));
9024 if Present
(Enclosing_Generic_Body
(Derived_Type
)) then
9025 Ancestor_Type
:= Parent_Type
;
9027 while not Is_Generic_Type
(Ancestor_Type
)
9028 and then Etype
(Ancestor_Type
) /= Ancestor_Type
9030 Ancestor_Type
:= Etype
(Ancestor_Type
);
9035 if Present
(Intf_List
) then
9036 Intf_Name
:= First
(Intf_List
);
9037 while Present
(Intf_Name
) loop
9038 Ancestor_Type
:= Entity
(Intf_Name
);
9044 end Check_Generic_Ancestors
;
9046 -- Start of processing for Build_Derived_Record_Type
9049 -- If the parent type is a private extension with discriminants, we
9050 -- need to have an unconstrained type on which to apply the inherited
9051 -- constraint, so we get to the full view. However, this means that the
9052 -- derived type and its implicit base type created below will not point
9053 -- to the same view of their respective parent type and, thus, special
9054 -- glue code like Exp_Ch7.Convert_View is needed to bridge this gap.
9056 if Ekind
(Parent_Type
) = E_Record_Type_With_Private
9057 and then Has_Discriminants
(Parent_Type
)
9058 and then Present
(Full_View
(Parent_Type
))
9060 Parent_Base
:= Base_Type
(Full_View
(Parent_Type
));
9062 Parent_Base
:= Base_Type
(Parent_Type
);
9065 -- If the parent type is declared as a subtype of another private
9066 -- type with inherited discriminants, its generated base type is
9067 -- itself a record subtype. To further inherit the constraint we
9068 -- need to use its own base to have an unconstrained type on which
9069 -- to apply the inherited constraint.
9071 if Ekind
(Parent_Base
) = E_Record_Subtype
then
9072 Parent_Base
:= Base_Type
(Parent_Base
);
9075 -- If the parent base is a private type and only its full view has
9076 -- discriminants, use the full view's base type.
9078 -- This can happen when we are deriving from a subtype of a derived type
9079 -- of a private type derived from a discriminated type with known
9083 -- type Root_Type(I: Positive) is record
9086 -- type Bounded_Root_Type is private;
9088 -- type Bounded_Root_Type is new Root_Type(10);
9092 -- type Constrained_Root_Type is new Pkg.Bounded_Root_Type;
9094 -- subtype Sub_Base is Pkg2.Constrained_Root_Type;
9095 -- type New_Der_Type is new Sub_Base;
9097 if Is_Private_Type
(Parent_Base
)
9098 and then Present
(Full_View
(Parent_Base
))
9099 and then not Has_Discriminants
(Parent_Base
)
9100 and then Has_Discriminants
(Full_View
(Parent_Base
))
9102 Parent_Base
:= Base_Type
(Full_View
(Parent_Base
));
9105 -- AI05-0115: if this is a derivation from a private type in some
9106 -- other scope that may lead to invisible components for the derived
9107 -- type, mark it accordingly.
9109 if Is_Private_Type
(Parent_Type
) then
9110 if Scope
(Parent_Base
) = Scope
(Derived_Type
) then
9113 elsif In_Open_Scopes
(Scope
(Parent_Base
))
9114 and then In_Private_Part
(Scope
(Parent_Base
))
9119 Set_Has_Private_Ancestor
(Derived_Type
);
9123 Set_Has_Private_Ancestor
9124 (Derived_Type
, Has_Private_Ancestor
(Parent_Type
));
9127 -- Before we start the previously documented transformations, here is
9128 -- little fix for size and alignment of tagged types. Normally when we
9129 -- derive type D from type P, we copy the size and alignment of P as the
9130 -- default for D, and in the absence of explicit representation clauses
9131 -- for D, the size and alignment are indeed the same as the parent.
9133 -- But this is wrong for tagged types, since fields may be added, and
9134 -- the default size may need to be larger, and the default alignment may
9135 -- need to be larger.
9137 -- We therefore reset the size and alignment fields in the tagged case.
9138 -- Note that the size and alignment will in any case be at least as
9139 -- large as the parent type (since the derived type has a copy of the
9140 -- parent type in the _parent field)
9142 -- The type is also marked as being tagged here, which is needed when
9143 -- processing components with a self-referential anonymous access type
9144 -- in the call to Check_Anonymous_Access_Components below. Note that
9145 -- this flag is also set later on for completeness.
9148 Set_Is_Tagged_Type
(Derived_Type
);
9149 Reinit_Size_Align
(Derived_Type
);
9152 -- STEP 0a: figure out what kind of derived type declaration we have
9154 if Private_Extension
then
9156 Mutate_Ekind
(Derived_Type
, E_Record_Type_With_Private
);
9157 Set_Default_SSO
(Derived_Type
);
9158 Set_No_Reordering
(Derived_Type
, No_Component_Reordering
);
9161 Type_Def
:= Type_Definition
(N
);
9163 -- Ekind (Parent_Base) is not necessarily E_Record_Type since
9164 -- Parent_Base can be a private type or private extension. However,
9165 -- for tagged types with an extension the newly added fields are
9166 -- visible and hence the Derived_Type is always an E_Record_Type.
9167 -- (except that the parent may have its own private fields).
9168 -- For untagged types we preserve the Ekind of the Parent_Base.
9170 if Present
(Record_Extension_Part
(Type_Def
)) then
9171 Mutate_Ekind
(Derived_Type
, E_Record_Type
);
9172 Set_Default_SSO
(Derived_Type
);
9173 Set_No_Reordering
(Derived_Type
, No_Component_Reordering
);
9175 -- Create internal access types for components with anonymous
9178 if Ada_Version
>= Ada_2005
then
9179 Check_Anonymous_Access_Components
9180 (N
, Derived_Type
, Derived_Type
,
9181 Component_List
(Record_Extension_Part
(Type_Def
)));
9185 Mutate_Ekind
(Derived_Type
, Ekind
(Parent_Base
));
9189 -- Indic can either be an N_Identifier if the subtype indication
9190 -- contains no constraint or an N_Subtype_Indication if the subtype
9191 -- indication has a constraint. In either case it can include an
9194 Indic
:= Subtype_Indication
(Type_Def
);
9195 Constraint_Present
:= (Nkind
(Indic
) = N_Subtype_Indication
);
9197 -- Check that the type has visible discriminants. The type may be
9198 -- a private type with unknown discriminants whose full view has
9199 -- discriminants which are invisible.
9201 if Constraint_Present
then
9202 if not Has_Discriminants
(Parent_Base
)
9204 (Has_Unknown_Discriminants
(Parent_Base
)
9205 and then Is_Private_Type
(Parent_Base
))
9208 ("invalid constraint: type has no discriminant",
9209 Constraint
(Indic
));
9211 Constraint_Present
:= False;
9212 Rewrite
(Indic
, New_Copy_Tree
(Subtype_Mark
(Indic
)));
9214 elsif Is_Constrained
(Parent_Type
) then
9216 ("invalid constraint: parent type is already constrained",
9217 Constraint
(Indic
));
9219 Constraint_Present
:= False;
9220 Rewrite
(Indic
, New_Copy_Tree
(Subtype_Mark
(Indic
)));
9224 -- STEP 0b: If needed, apply transformation given in point 5. above
9226 if not Private_Extension
9227 and then Has_Discriminants
(Parent_Type
)
9228 and then not Discriminant_Specs
9229 and then (Is_Constrained
(Parent_Type
) or else Constraint_Present
)
9231 -- First, we must analyze the constraint (see comment in point 5.)
9232 -- The constraint may come from the subtype indication of the full
9233 -- declaration. Temporarily set the state of the Derived_Type to
9234 -- "self-hidden" (see RM-8.3(17)).
9236 if Constraint_Present
then
9237 pragma Assert
(Is_Not_Self_Hidden
(Derived_Type
));
9238 Set_Is_Not_Self_Hidden
(Derived_Type
, False);
9239 New_Discrs
:= Build_Discriminant_Constraints
(Parent_Type
, Indic
);
9240 Set_Is_Not_Self_Hidden
(Derived_Type
);
9242 -- If there is no explicit constraint, there might be one that is
9243 -- inherited from a constrained parent type. In that case verify that
9244 -- it conforms to the constraint in the partial view. In perverse
9245 -- cases the parent subtypes of the partial and full view can have
9246 -- different constraints.
9248 elsif Present
(Stored_Constraint
(Parent_Type
)) then
9249 New_Discrs
:= Stored_Constraint
(Parent_Type
);
9252 New_Discrs
:= No_Elist
;
9255 if Has_Discriminants
(Derived_Type
)
9256 and then Has_Private_Declaration
(Derived_Type
)
9257 and then Present
(Discriminant_Constraint
(Derived_Type
))
9258 and then Present
(New_Discrs
)
9260 -- Verify that constraints of the full view statically match
9261 -- those given in the partial view.
9267 C1
:= First_Elmt
(New_Discrs
);
9268 C2
:= First_Elmt
(Discriminant_Constraint
(Derived_Type
));
9269 while Present
(C1
) and then Present
(C2
) loop
9270 if Fully_Conformant_Expressions
(Node
(C1
), Node
(C2
))
9272 (Is_OK_Static_Expression
(Node
(C1
))
9273 and then Is_OK_Static_Expression
(Node
(C2
))
9275 Expr_Value
(Node
(C1
)) = Expr_Value
(Node
(C2
)))
9280 if Constraint_Present
then
9282 ("constraint not conformant to previous declaration",
9286 ("constraint of full view is incompatible "
9287 & "with partial view", N
);
9297 -- Insert and analyze the declaration for the unconstrained base type
9299 New_Base
:= Create_Itype
(Ekind
(Derived_Type
), N
, Derived_Type
, 'B');
9302 Make_Full_Type_Declaration
(Loc
,
9303 Defining_Identifier
=> New_Base
,
9305 Make_Derived_Type_Definition
(Loc
,
9306 Abstract_Present
=> Abstract_Present
(Type_Def
),
9307 Limited_Present
=> Limited_Present
(Type_Def
),
9308 Subtype_Indication
=>
9309 New_Occurrence_Of
(Parent_Base
, Loc
),
9310 Record_Extension_Part
=>
9311 Relocate_Node
(Record_Extension_Part
(Type_Def
)),
9312 Interface_List
=> Interface_List
(Type_Def
)));
9314 Set_Parent
(New_Decl
, Parent
(N
));
9315 Mark_Rewrite_Insertion
(New_Decl
);
9316 Insert_Before
(N
, New_Decl
);
9318 -- In the extension case, make sure ancestor is frozen appropriately
9319 -- (see also non-discriminated case below).
9321 if Present
(Record_Extension_Part
(Type_Def
))
9322 or else Is_Interface
(Parent_Base
)
9324 Freeze_Before
(New_Decl
, Parent_Type
);
9327 -- Note that this call passes False for the Derive_Subps parameter
9328 -- because subprogram derivation is deferred until after creating
9329 -- the subtype (see below).
9332 (New_Decl
, Parent_Base
, New_Base
,
9333 Is_Completion
=> False, Derive_Subps
=> False);
9335 -- ??? This needs re-examination to determine whether the
9336 -- following call can simply be replaced by a call to Analyze.
9338 Set_Analyzed
(New_Decl
);
9340 -- Insert and analyze the declaration for the constrained subtype
9342 if Constraint_Present
then
9344 Make_Subtype_Indication
(Loc
,
9345 Subtype_Mark
=> New_Occurrence_Of
(New_Base
, Loc
),
9346 Constraint
=> Relocate_Node
(Constraint
(Indic
)));
9350 Constr_List
: constant List_Id
:= New_List
;
9355 C
:= First_Elmt
(Discriminant_Constraint
(Parent_Type
));
9356 while Present
(C
) loop
9359 -- It is safe here to call New_Copy_Tree since we called
9360 -- Force_Evaluation on each constraint previously
9361 -- in Build_Discriminant_Constraints.
9363 Append
(New_Copy_Tree
(Expr
), To
=> Constr_List
);
9369 Make_Subtype_Indication
(Loc
,
9370 Subtype_Mark
=> New_Occurrence_Of
(New_Base
, Loc
),
9372 Make_Index_Or_Discriminant_Constraint
(Loc
, Constr_List
));
9377 Make_Subtype_Declaration
(Loc
,
9378 Defining_Identifier
=> Derived_Type
,
9379 Subtype_Indication
=> New_Indic
));
9383 -- Derivation of subprograms must be delayed until the full subtype
9384 -- has been established, to ensure proper overriding of subprograms
9385 -- inherited by full types. If the derivations occurred as part of
9386 -- the call to Build_Derived_Type above, then the check for type
9387 -- conformance would fail because earlier primitive subprograms
9388 -- could still refer to the full type prior the change to the new
9389 -- subtype and hence would not match the new base type created here.
9390 -- Subprograms are not derived, however, when Derive_Subps is False
9391 -- (since otherwise there could be redundant derivations).
9393 if Derive_Subps
then
9394 Derive_Subprograms
(Parent_Type
, Derived_Type
);
9397 -- For tagged types the Discriminant_Constraint of the new base itype
9398 -- is inherited from the first subtype so that no subtype conformance
9399 -- problem arise when the first subtype overrides primitive
9400 -- operations inherited by the implicit base type.
9403 Set_Discriminant_Constraint
9404 (New_Base
, Discriminant_Constraint
(Derived_Type
));
9410 -- If we get here Derived_Type will have no discriminants or it will be
9411 -- a discriminated unconstrained base type.
9413 -- STEP 1a: perform preliminary actions/checks for derived tagged types
9417 -- The parent type is frozen for non-private extensions (RM 13.14(7))
9418 -- The declaration of a specific descendant of an interface type
9419 -- freezes the interface type (RM 13.14).
9421 if not Private_Extension
or else Is_Interface
(Parent_Base
) then
9422 Freeze_Before
(N
, Parent_Type
);
9425 if Ada_Version
>= Ada_2005
then
9426 Check_Generic_Ancestors
;
9428 elsif Type_Access_Level
(Derived_Type
) /=
9429 Type_Access_Level
(Parent_Type
)
9430 and then not Is_Generic_Type
(Derived_Type
)
9432 if Is_Controlled
(Parent_Type
) then
9434 ("controlled type must be declared at the library level",
9438 ("type extension at deeper accessibility level than parent",
9444 GB
: constant Node_Id
:= Enclosing_Generic_Body
(Derived_Type
);
9447 and then GB
/= Enclosing_Generic_Body
(Parent_Base
)
9450 ("parent type of& must not be outside generic body"
9452 Indic
, Derived_Type
);
9458 -- Ada 2005 (AI-251)
9460 if Ada_Version
>= Ada_2005
and then Is_Tagged
then
9462 -- "The declaration of a specific descendant of an interface type
9463 -- freezes the interface type" (RM 13.14).
9468 Iface
:= First
(Interface_List
(Type_Def
));
9469 while Present
(Iface
) loop
9470 Freeze_Before
(N
, Etype
(Iface
));
9476 -- STEP 1b : preliminary cleanup of the full view of private types
9478 -- If the type is already marked as having discriminants, then it's the
9479 -- completion of a private type or private extension and we need to
9480 -- retain the discriminants from the partial view if the current
9481 -- declaration has Discriminant_Specifications so that we can verify
9482 -- conformance. However, we must remove any existing components that
9483 -- were inherited from the parent (and attached in Copy_And_Swap)
9484 -- because the full type inherits all appropriate components anyway, and
9485 -- we do not want the partial view's components interfering.
9487 if Has_Discriminants
(Derived_Type
) and then Discriminant_Specs
then
9488 Discrim
:= First_Discriminant
(Derived_Type
);
9490 Last_Discrim
:= Discrim
;
9491 Next_Discriminant
(Discrim
);
9492 exit when No
(Discrim
);
9495 Set_Last_Entity
(Derived_Type
, Last_Discrim
);
9497 -- In all other cases wipe out the list of inherited components (even
9498 -- inherited discriminants), it will be properly rebuilt here.
9501 Set_First_Entity
(Derived_Type
, Empty
);
9502 Set_Last_Entity
(Derived_Type
, Empty
);
9505 -- STEP 1c: Initialize some flags for the Derived_Type
9507 -- The following flags must be initialized here so that
9508 -- Process_Discriminants can check that discriminants of tagged types do
9509 -- not have a default initial value and that access discriminants are
9510 -- only specified for limited records. For completeness, these flags are
9511 -- also initialized along with all the other flags below.
9513 -- AI-419: Limitedness is not inherited from an interface parent, so to
9514 -- be limited in that case the type must be explicitly declared as
9515 -- limited. However, task and protected interfaces are always limited.
9517 if Limited_Present
(Type_Def
) then
9518 Set_Is_Limited_Record
(Derived_Type
);
9520 elsif Is_Limited_Record
(Parent_Type
)
9521 or else (Present
(Full_View
(Parent_Type
))
9522 and then Is_Limited_Record
(Full_View
(Parent_Type
)))
9524 if not Is_Interface
(Parent_Type
)
9525 or else Is_Concurrent_Interface
(Parent_Type
)
9527 Set_Is_Limited_Record
(Derived_Type
);
9531 -- STEP 2a: process discriminants of derived type if any
9533 Push_Scope
(Derived_Type
);
9535 if Discriminant_Specs
then
9536 Set_Has_Unknown_Discriminants
(Derived_Type
, False);
9538 -- The following call to Check_Or_Process_Discriminants initializes
9539 -- fields Has_Discriminants and Discriminant_Constraint, unless we
9540 -- are processing the completion of a private type declaration.
9541 -- Temporarily set the state of the Derived_Type to "self-hidden"
9542 -- (see RM-8.3(17)), unless it is already the case.
9544 if Is_Not_Self_Hidden
(Derived_Type
) then
9545 Set_Is_Not_Self_Hidden
(Derived_Type
, False);
9546 Check_Or_Process_Discriminants
(N
, Derived_Type
);
9547 Set_Is_Not_Self_Hidden
(Derived_Type
);
9549 Check_Or_Process_Discriminants
(N
, Derived_Type
);
9552 -- For untagged types, the constraint on the Parent_Type must be
9553 -- present and is used to rename the discriminants.
9555 if not Is_Tagged
and then not Has_Discriminants
(Parent_Type
) then
9556 Error_Msg_N
("untagged parent must have discriminants", Indic
);
9558 elsif not Is_Tagged
and then not Constraint_Present
then
9560 ("discriminant constraint needed for derived untagged records",
9563 -- Otherwise the parent subtype must be constrained unless we have a
9564 -- private extension.
9566 elsif not Constraint_Present
9567 and then not Private_Extension
9568 and then not Is_Constrained
(Parent_Type
)
9571 ("unconstrained type not allowed in this context", Indic
);
9573 elsif Constraint_Present
then
9574 -- The following call sets the field Corresponding_Discriminant
9575 -- for the discriminants in the Derived_Type.
9577 Discs
:= Build_Discriminant_Constraints
(Parent_Type
, Indic
, True);
9579 -- For untagged types all new discriminants must rename
9580 -- discriminants in the parent. For private extensions new
9581 -- discriminants cannot rename old ones (implied by [7.3(13)]).
9583 Discrim
:= First_Discriminant
(Derived_Type
);
9584 while Present
(Discrim
) loop
9586 and then No
(Corresponding_Discriminant
(Discrim
))
9589 ("new discriminants must constrain old ones", Discrim
);
9591 elsif Private_Extension
9592 and then Present
(Corresponding_Discriminant
(Discrim
))
9595 ("only static constraints allowed for parent"
9596 & " discriminants in the partial view", Indic
);
9600 -- If a new discriminant is used in the constraint, then its
9601 -- subtype must be statically compatible with the subtype of
9602 -- the parent discriminant (RM 3.7(15)).
9604 if Present
(Corresponding_Discriminant
(Discrim
)) then
9605 Check_Constraining_Discriminant
9606 (Discrim
, Corresponding_Discriminant
(Discrim
));
9609 Next_Discriminant
(Discrim
);
9612 -- Check whether the constraints of the full view statically
9613 -- match those imposed by the parent subtype [7.3(13)].
9615 if Present
(Stored_Constraint
(Derived_Type
)) then
9620 C1
:= First_Elmt
(Discs
);
9621 C2
:= First_Elmt
(Stored_Constraint
(Derived_Type
));
9622 while Present
(C1
) and then Present
(C2
) loop
9624 Fully_Conformant_Expressions
(Node
(C1
), Node
(C2
))
9627 ("not conformant with previous declaration",
9638 -- STEP 2b: No new discriminants, inherit discriminants if any
9641 if Private_Extension
then
9642 Set_Has_Unknown_Discriminants
9644 Has_Unknown_Discriminants
(Parent_Type
)
9645 or else Unknown_Discriminants_Present
(N
));
9647 -- The partial view of the parent may have unknown discriminants,
9648 -- but if the full view has discriminants and the parent type is
9649 -- in scope they must be inherited.
9651 elsif Has_Unknown_Discriminants
(Parent_Type
)
9653 (not Has_Discriminants
(Parent_Type
)
9654 or else not In_Open_Scopes
(Scope
(Parent_Base
)))
9656 Set_Has_Unknown_Discriminants
(Derived_Type
);
9659 if not Has_Unknown_Discriminants
(Derived_Type
)
9660 and then not Has_Unknown_Discriminants
(Parent_Base
)
9661 and then Has_Discriminants
(Parent_Type
)
9663 Inherit_Discrims
:= True;
9664 Set_Has_Discriminants
9665 (Derived_Type
, True);
9666 Set_Discriminant_Constraint
9667 (Derived_Type
, Discriminant_Constraint
(Parent_Base
));
9670 -- The following test is true for private types (remember
9671 -- transformation 5. is not applied to those) and in an error
9674 if Constraint_Present
then
9675 Discs
:= Build_Discriminant_Constraints
(Parent_Type
, Indic
);
9678 -- For now mark a new derived type as constrained only if it has no
9679 -- discriminants. At the end of Build_Derived_Record_Type we properly
9680 -- set this flag in the case of private extensions. See comments in
9681 -- point 9. just before body of Build_Derived_Record_Type.
9685 not (Inherit_Discrims
9686 or else Has_Unknown_Discriminants
(Derived_Type
)));
9689 -- STEP 3: initialize fields of derived type
9691 Set_Is_Tagged_Type
(Derived_Type
, Is_Tagged
);
9692 Set_Stored_Constraint
(Derived_Type
, No_Elist
);
9694 -- Ada 2005 (AI-251): Private type-declarations can implement interfaces
9695 -- but cannot be interfaces
9697 if not Private_Extension
9698 and then Ekind
(Derived_Type
) /= E_Private_Type
9699 and then Ekind
(Derived_Type
) /= E_Limited_Private_Type
9701 if Interface_Present
(Type_Def
) then
9702 Analyze_Interface_Declaration
(Derived_Type
, Type_Def
);
9705 Set_Interfaces
(Derived_Type
, No_Elist
);
9708 -- Fields inherited from the Parent_Type
9710 Set_Has_Specified_Layout
9711 (Derived_Type
, Has_Specified_Layout
(Parent_Type
));
9712 Set_Is_Limited_Composite
9713 (Derived_Type
, Is_Limited_Composite
(Parent_Type
));
9714 Set_Is_Private_Composite
9715 (Derived_Type
, Is_Private_Composite
(Parent_Type
));
9717 if Is_Tagged_Type
(Parent_Type
) then
9718 Set_No_Tagged_Streams_Pragma
9719 (Derived_Type
, No_Tagged_Streams_Pragma
(Parent_Type
));
9722 -- Fields inherited from the Parent_Base
9724 Set_Has_Controlled_Component
9725 (Derived_Type
, Has_Controlled_Component
(Parent_Base
));
9726 Set_Has_Non_Standard_Rep
9727 (Derived_Type
, Has_Non_Standard_Rep
(Parent_Base
));
9728 Set_Has_Primitive_Operations
9729 (Derived_Type
, Has_Primitive_Operations
(Parent_Base
));
9731 -- Set fields for private derived types
9733 if Is_Private_Type
(Derived_Type
) then
9734 Set_Depends_On_Private
(Derived_Type
, True);
9735 Set_Private_Dependents
(Derived_Type
, New_Elmt_List
);
9738 -- Inherit fields for non-private types. If this is the completion of a
9739 -- derivation from a private type, the parent itself is private and the
9740 -- attributes come from its full view, which must be present.
9742 if Is_Record_Type
(Derived_Type
) then
9744 Parent_Full
: Entity_Id
;
9747 if Is_Private_Type
(Parent_Base
)
9748 and then not Is_Record_Type
(Parent_Base
)
9750 Parent_Full
:= Full_View
(Parent_Base
);
9752 Parent_Full
:= Parent_Base
;
9755 Set_Component_Alignment
9756 (Derived_Type
, Component_Alignment
(Parent_Full
));
9758 (Derived_Type
, C_Pass_By_Copy
(Parent_Full
));
9759 Set_Has_Complex_Representation
9760 (Derived_Type
, Has_Complex_Representation
(Parent_Full
));
9762 -- For untagged types, inherit the layout by default to avoid
9763 -- costly changes of representation for type conversions.
9765 if not Is_Tagged
then
9766 Set_Is_Packed
(Derived_Type
, Is_Packed
(Parent_Full
));
9767 Set_No_Reordering
(Derived_Type
, No_Reordering
(Parent_Full
));
9772 -- Initialize the list of primitive operations to an empty list,
9773 -- to cover tagged types as well as untagged types. For untagged
9774 -- types this is used either to analyze the call as legal when
9775 -- Extensions_Allowed is True, or to issue a better error message
9778 Set_Direct_Primitive_Operations
(Derived_Type
, New_Elmt_List
);
9780 -- Set fields for tagged types
9783 -- All tagged types defined in Ada.Finalization are controlled
9785 if Chars
(Scope
(Derived_Type
)) = Name_Finalization
9786 and then Chars
(Scope
(Scope
(Derived_Type
))) = Name_Ada
9787 and then Scope
(Scope
(Scope
(Derived_Type
))) = Standard_Standard
9789 Set_Is_Controlled_Active
(Derived_Type
);
9791 Set_Is_Controlled_Active
9792 (Derived_Type
, Is_Controlled_Active
(Parent_Base
));
9795 -- Minor optimization: there is no need to generate the class-wide
9796 -- entity associated with an underlying record view.
9798 if not Is_Underlying_Record_View
(Derived_Type
) then
9799 Make_Class_Wide_Type
(Derived_Type
);
9802 Set_Is_Abstract_Type
(Derived_Type
, Abstract_Present
(Type_Def
));
9804 if Has_Discriminants
(Derived_Type
)
9805 and then Constraint_Present
9807 Set_Stored_Constraint
9808 (Derived_Type
, Expand_To_Stored_Constraint
(Parent_Base
, Discs
));
9811 if Ada_Version
>= Ada_2005
then
9813 Ifaces_List
: Elist_Id
;
9816 -- Checks rules 3.9.4 (13/2 and 14/2)
9818 if Comes_From_Source
(Derived_Type
)
9819 and then not Is_Private_Type
(Derived_Type
)
9820 and then Is_Interface
(Parent_Type
)
9821 and then not Is_Interface
(Derived_Type
)
9823 if Is_Task_Interface
(Parent_Type
) then
9825 ("(Ada 2005) task type required (RM 3.9.4 (13.2))",
9828 elsif Is_Protected_Interface
(Parent_Type
) then
9830 ("(Ada 2005) protected type required (RM 3.9.4 (14.2))",
9835 -- Check ARM rules 3.9.4 (15/2), 9.1 (9.d/2) and 9.4 (11.d/2)
9837 Check_Interfaces
(N
, Type_Def
);
9839 -- Ada 2005 (AI-251): Collect the list of progenitors that are
9840 -- not already in the parents.
9844 Ifaces_List
=> Ifaces_List
,
9845 Exclude_Parents
=> True);
9847 Set_Interfaces
(Derived_Type
, Ifaces_List
);
9849 -- If the derived type is the anonymous type created for
9850 -- a declaration whose parent has a constraint, propagate
9851 -- the interface list to the source type. This must be done
9852 -- prior to the completion of the analysis of the source type
9853 -- because the components in the extension may contain current
9854 -- instances whose legality depends on some ancestor.
9856 if Is_Itype
(Derived_Type
) then
9858 Def
: constant Node_Id
:=
9859 Associated_Node_For_Itype
(Derived_Type
);
9862 and then Nkind
(Def
) = N_Full_Type_Declaration
9865 (Defining_Identifier
(Def
), Ifaces_List
);
9870 -- A type extension is automatically Ghost when one of its
9871 -- progenitors is Ghost (SPARK RM 6.9(9)). This property is
9872 -- also inherited when the parent type is Ghost, but this is
9873 -- done in Build_Derived_Type as the mechanism also handles
9874 -- untagged derivations.
9876 if Implements_Ghost_Interface
(Derived_Type
) then
9877 Set_Is_Ghost_Entity
(Derived_Type
);
9883 -- STEP 4: Inherit components from the parent base and constrain them.
9884 -- Apply the second transformation described in point 6. above.
9886 if (not Is_Empty_Elmt_List
(Discs
) or else Inherit_Discrims
)
9887 or else not Has_Discriminants
(Parent_Type
)
9888 or else not Is_Constrained
(Parent_Type
)
9892 Constrs
:= Discriminant_Constraint
(Parent_Type
);
9897 (N
, Parent_Base
, Derived_Type
, Is_Tagged
, Inherit_Discrims
, Constrs
);
9899 -- STEP 5a: Copy the parent record declaration for untagged types
9901 Set_Has_Implicit_Dereference
9902 (Derived_Type
, Has_Implicit_Dereference
(Parent_Type
));
9904 if not Is_Tagged
then
9906 -- Discriminant_Constraint (Derived_Type) has been properly
9907 -- constructed. Save it and temporarily set it to Empty because we
9908 -- do not want the call to New_Copy_Tree below to mess this list.
9910 if Has_Discriminants
(Derived_Type
) then
9911 Save_Discr_Constr
:= Discriminant_Constraint
(Derived_Type
);
9912 Set_Discriminant_Constraint
(Derived_Type
, No_Elist
);
9914 Save_Discr_Constr
:= No_Elist
;
9917 -- Save the Etype field of Derived_Type. It is correctly set now,
9918 -- but the call to New_Copy tree may remap it to point to itself,
9919 -- which is not what we want. Ditto for the Next_Entity field.
9921 Save_Etype
:= Etype
(Derived_Type
);
9922 Save_Next_Entity
:= Next_Entity
(Derived_Type
);
9924 -- Assoc_List maps all stored discriminants in the Parent_Base to
9925 -- stored discriminants in the Derived_Type. It is fundamental that
9926 -- no types or itypes with discriminants other than the stored
9927 -- discriminants appear in the entities declared inside
9928 -- Derived_Type, since the back end cannot deal with it.
9932 (Parent
(Parent_Base
), Map
=> Assoc_List
, New_Sloc
=> Loc
);
9933 Copy_Dimensions_Of_Components
(Derived_Type
);
9935 -- Restore the fields saved prior to the New_Copy_Tree call
9936 -- and compute the stored constraint.
9938 Set_Etype
(Derived_Type
, Save_Etype
);
9939 Link_Entities
(Derived_Type
, Save_Next_Entity
);
9941 if Has_Discriminants
(Derived_Type
) then
9942 Set_Discriminant_Constraint
9943 (Derived_Type
, Save_Discr_Constr
);
9944 Set_Stored_Constraint
9945 (Derived_Type
, Expand_To_Stored_Constraint
(Parent_Type
, Discs
));
9947 Replace_Discriminants
(Derived_Type
, New_Decl
);
9950 -- Insert the new derived type declaration
9952 Rewrite
(N
, New_Decl
);
9954 -- STEP 5b: Complete the processing for record extensions in generics
9956 -- There is no completion for record extensions declared in the
9957 -- parameter part of a generic, so we need to complete processing for
9958 -- these generic record extensions here. Record_Type_Definition will
9959 -- set the Is_Not_Self_Hidden flag.
9961 elsif Private_Extension
and then Is_Generic_Type
(Derived_Type
) then
9962 Record_Type_Definition
(Empty
, Derived_Type
);
9964 -- STEP 5c: Process the record extension for non private tagged types
9966 elsif not Private_Extension
then
9967 Expand_Record_Extension
(Derived_Type
, Type_Def
);
9969 -- Ada 2005 (AI-251): Addition of the Tag corresponding to all the
9970 -- implemented interfaces if we are in expansion mode
9973 and then Has_Interfaces
(Derived_Type
)
9975 Add_Interface_Tag_Components
(N
, Derived_Type
);
9978 -- Analyze the record extension
9980 Record_Type_Definition
9981 (Record_Extension_Part
(Type_Def
), Derived_Type
);
9986 -- Nothing else to do if there is an error in the derivation.
9987 -- An unusual case: the full view may be derived from a type in an
9988 -- instance, when the partial view was used illegally as an actual
9989 -- in that instance, leading to a circular definition.
9991 if Etype
(Derived_Type
) = Any_Type
9992 or else Etype
(Parent_Type
) = Derived_Type
9997 -- Set delayed freeze and then derive subprograms, we need to do
9998 -- this in this order so that derived subprograms inherit the
9999 -- derived freeze if necessary.
10001 Set_Has_Delayed_Freeze
(Derived_Type
);
10003 if Derive_Subps
then
10004 Derive_Subprograms
(Parent_Type
, Derived_Type
);
10007 -- If we have a private extension which defines a constrained derived
10008 -- type mark as constrained here after we have derived subprograms. See
10009 -- comment on point 9. just above the body of Build_Derived_Record_Type.
10011 if Private_Extension
and then Inherit_Discrims
then
10012 if Constraint_Present
and then not Is_Empty_Elmt_List
(Discs
) then
10013 Set_Is_Constrained
(Derived_Type
, True);
10014 Set_Discriminant_Constraint
(Derived_Type
, Discs
);
10016 elsif Is_Constrained
(Parent_Type
) then
10018 (Derived_Type
, True);
10019 Set_Discriminant_Constraint
10020 (Derived_Type
, Discriminant_Constraint
(Parent_Type
));
10024 -- Update the class-wide type, which shares the now-completed entity
10025 -- list with its specific type. In case of underlying record views,
10026 -- we do not generate the corresponding class wide entity.
10029 and then not Is_Underlying_Record_View
(Derived_Type
)
10032 (Class_Wide_Type
(Derived_Type
), First_Entity
(Derived_Type
));
10034 (Class_Wide_Type
(Derived_Type
), Last_Entity
(Derived_Type
));
10037 Check_Function_Writable_Actuals
(N
);
10038 end Build_Derived_Record_Type
;
10040 ------------------------
10041 -- Build_Derived_Type --
10042 ------------------------
10044 procedure Build_Derived_Type
10046 Parent_Type
: Entity_Id
;
10047 Derived_Type
: Entity_Id
;
10048 Is_Completion
: Boolean;
10049 Derive_Subps
: Boolean := True)
10051 Parent_Base
: constant Entity_Id
:= Base_Type
(Parent_Type
);
10054 -- Set common attributes
10056 if Ekind
(Derived_Type
) in Incomplete_Or_Private_Kind
10057 and then Ekind
(Parent_Base
) in Elementary_Kind
10059 Reinit_Field_To_Zero
(Derived_Type
, F_Discriminant_Constraint
);
10062 Set_Scope
(Derived_Type
, Current_Scope
);
10063 Set_Etype
(Derived_Type
, Parent_Base
);
10064 Mutate_Ekind
(Derived_Type
, Ekind
(Parent_Base
));
10065 Propagate_Concurrent_Flags
(Derived_Type
, Parent_Base
);
10067 Set_Size_Info
(Derived_Type
, Parent_Type
);
10068 Copy_RM_Size
(To
=> Derived_Type
, From
=> Parent_Type
);
10070 Set_Is_Controlled_Active
10071 (Derived_Type
, Is_Controlled_Active
(Parent_Type
));
10073 Set_Disable_Controlled
(Derived_Type
, Disable_Controlled
(Parent_Type
));
10074 Set_Is_Tagged_Type
(Derived_Type
, Is_Tagged_Type
(Parent_Type
));
10075 Set_Is_Volatile
(Derived_Type
, Is_Volatile
(Parent_Type
));
10077 if Is_Tagged_Type
(Derived_Type
) then
10078 Set_No_Tagged_Streams_Pragma
10079 (Derived_Type
, No_Tagged_Streams_Pragma
(Parent_Type
));
10082 -- If the parent has primitive routines and may have not-seen-yet aspect
10083 -- specifications (e.g., a Pack pragma), then set the derived type link
10084 -- in order to later diagnose "early derivation" issues. If in different
10085 -- compilation units, then "early derivation" cannot be an issue (and we
10086 -- don't like interunit references that go in the opposite direction of
10087 -- semantic dependencies).
10089 if Has_Primitive_Operations
(Parent_Type
)
10090 and then Enclosing_Comp_Unit_Node
(Parent_Type
) =
10091 Enclosing_Comp_Unit_Node
(Derived_Type
)
10093 Set_Derived_Type_Link
(Parent_Base
, Derived_Type
);
10096 -- If the parent type is a private subtype, the convention on the base
10097 -- type may be set in the private part, and not propagated to the
10098 -- subtype until later, so we obtain the convention from the base type.
10100 Set_Convention
(Derived_Type
, Convention
(Parent_Base
));
10102 if Is_Tagged_Type
(Derived_Type
)
10103 and then Present
(Class_Wide_Type
(Derived_Type
))
10105 Set_Convention
(Class_Wide_Type
(Derived_Type
),
10106 Convention
(Class_Wide_Type
(Parent_Base
)));
10109 -- Set SSO default for record or array type
10111 if (Is_Array_Type
(Derived_Type
) or else Is_Record_Type
(Derived_Type
))
10112 and then Is_Base_Type
(Derived_Type
)
10114 Set_Default_SSO
(Derived_Type
);
10117 -- A derived type inherits the Default_Initial_Condition pragma coming
10118 -- from any parent type within the derivation chain.
10120 if Has_DIC
(Parent_Type
) then
10121 Set_Has_Inherited_DIC
(Derived_Type
);
10124 -- A derived type inherits any class-wide invariants coming from a
10125 -- parent type or an interface. Note that the invariant procedure of
10126 -- the parent type should not be inherited because the derived type may
10127 -- define invariants of its own.
10129 if not Is_Interface
(Derived_Type
) then
10130 if Has_Inherited_Invariants
(Parent_Type
)
10131 or else Has_Inheritable_Invariants
(Parent_Type
)
10133 Set_Has_Inherited_Invariants
(Derived_Type
);
10135 elsif Is_Concurrent_Type
(Derived_Type
)
10136 or else Is_Tagged_Type
(Derived_Type
)
10141 Iface_Elmt
: Elmt_Id
;
10145 (T
=> Derived_Type
,
10146 Ifaces_List
=> Ifaces
,
10147 Exclude_Parents
=> True);
10149 if Present
(Ifaces
) then
10150 Iface_Elmt
:= First_Elmt
(Ifaces
);
10151 while Present
(Iface_Elmt
) loop
10152 Iface
:= Node
(Iface_Elmt
);
10154 if Has_Inheritable_Invariants
(Iface
) then
10155 Set_Has_Inherited_Invariants
(Derived_Type
);
10159 Next_Elmt
(Iface_Elmt
);
10166 -- We similarly inherit predicates
10168 Inherit_Predicate_Flags
(Derived_Type
, Parent_Type
, Only_Flags
=> True);
10170 -- The derived type inherits representation clauses from the parent
10171 -- type, and from any interfaces.
10173 Inherit_Rep_Item_Chain
(Derived_Type
, Parent_Type
);
10176 Iface
: Node_Id
:= First
(Abstract_Interface_List
(Derived_Type
));
10178 while Present
(Iface
) loop
10179 Inherit_Rep_Item_Chain
(Derived_Type
, Entity
(Iface
));
10184 -- If the parent type has delayed rep aspects, then mark the derived
10185 -- type as possibly inheriting a delayed rep aspect.
10187 if Has_Delayed_Rep_Aspects
(Parent_Type
) then
10188 Set_May_Inherit_Delayed_Rep_Aspects
(Derived_Type
);
10191 -- A derived type becomes Ghost when its parent type is also Ghost
10192 -- (SPARK RM 6.9(9)). Note that the Ghost-related attributes are not
10193 -- directly inherited because the Ghost policy in effect may differ.
10195 if Is_Ghost_Entity
(Parent_Type
) then
10196 Set_Is_Ghost_Entity
(Derived_Type
);
10199 -- Type dependent processing
10201 case Ekind
(Parent_Type
) is
10202 when Numeric_Kind
=>
10203 Build_Derived_Numeric_Type
(N
, Parent_Type
, Derived_Type
);
10206 Build_Derived_Array_Type
(N
, Parent_Type
, Derived_Type
);
10208 when Class_Wide_Kind
10212 Build_Derived_Record_Type
10213 (N
, Parent_Type
, Derived_Type
, Derive_Subps
);
10216 when Enumeration_Kind
=>
10217 Build_Derived_Enumeration_Type
(N
, Parent_Type
, Derived_Type
);
10219 when Access_Kind
=>
10220 Build_Derived_Access_Type
(N
, Parent_Type
, Derived_Type
);
10222 when Incomplete_Or_Private_Kind
=>
10223 Build_Derived_Private_Type
10224 (N
, Parent_Type
, Derived_Type
, Is_Completion
, Derive_Subps
);
10226 -- For discriminated types, the derivation includes deriving
10227 -- primitive operations. For others it is done below.
10229 if Is_Tagged_Type
(Parent_Type
)
10230 or else Has_Discriminants
(Parent_Type
)
10231 or else (Present
(Full_View
(Parent_Type
))
10232 and then Has_Discriminants
(Full_View
(Parent_Type
)))
10237 when Concurrent_Kind
=>
10238 Build_Derived_Concurrent_Type
(N
, Parent_Type
, Derived_Type
);
10241 raise Program_Error
;
10244 -- Nothing more to do if some error occurred
10246 if Etype
(Derived_Type
) = Any_Type
then
10250 -- If not already set, initialize the derived type's list of primitive
10251 -- operations to an empty element list.
10253 if not Present
(Direct_Primitive_Operations
(Derived_Type
)) then
10254 Set_Direct_Primitive_Operations
(Derived_Type
, New_Elmt_List
);
10256 -- If Etype of the derived type is the base type (as opposed to
10257 -- a parent type) and doesn't have an associated list of primitive
10258 -- operations, then set the base type's primitive list to the
10259 -- derived type's list. The lists need to be shared in common
10260 -- between the two.
10262 if Etype
(Derived_Type
) = Base_Type
(Derived_Type
)
10264 not Present
(Direct_Primitive_Operations
(Etype
(Derived_Type
)))
10266 Set_Direct_Primitive_Operations
10267 (Etype
(Derived_Type
),
10268 Direct_Primitive_Operations
(Derived_Type
));
10272 -- Set delayed freeze and then derive subprograms, we need to do this
10273 -- in this order so that derived subprograms inherit the derived freeze
10276 Set_Has_Delayed_Freeze
(Derived_Type
);
10278 if Derive_Subps
then
10279 Derive_Subprograms
(Parent_Type
, Derived_Type
);
10282 Set_Has_Primitive_Operations
10283 (Base_Type
(Derived_Type
), Has_Primitive_Operations
(Parent_Type
));
10284 end Build_Derived_Type
;
10286 -----------------------
10287 -- Build_Discriminal --
10288 -----------------------
10290 procedure Build_Discriminal
(Discrim
: Entity_Id
) is
10291 D_Minal
: Entity_Id
;
10292 CR_Disc
: Entity_Id
;
10295 -- A discriminal has the same name as the discriminant
10297 D_Minal
:= Make_Defining_Identifier
(Sloc
(Discrim
), Chars
(Discrim
));
10299 Mutate_Ekind
(D_Minal
, E_In_Parameter
);
10300 Set_Mechanism
(D_Minal
, Default_Mechanism
);
10301 Set_Etype
(D_Minal
, Etype
(Discrim
));
10302 Set_Scope
(D_Minal
, Current_Scope
);
10303 Set_Parent
(D_Minal
, Parent
(Discrim
));
10305 Set_Discriminal
(Discrim
, D_Minal
);
10306 Set_Discriminal_Link
(D_Minal
, Discrim
);
10308 -- For task types, build at once the discriminants of the corresponding
10309 -- record, which are needed if discriminants are used in entry defaults
10310 -- and in family bounds.
10312 if Is_Concurrent_Type
(Current_Scope
)
10314 Is_Limited_Type
(Current_Scope
)
10316 CR_Disc
:= Make_Defining_Identifier
(Sloc
(Discrim
), Chars
(Discrim
));
10318 Mutate_Ekind
(CR_Disc
, E_In_Parameter
);
10319 Set_Mechanism
(CR_Disc
, Default_Mechanism
);
10320 Set_Etype
(CR_Disc
, Etype
(Discrim
));
10321 Set_Scope
(CR_Disc
, Current_Scope
);
10322 Set_Discriminal_Link
(CR_Disc
, Discrim
);
10323 Set_CR_Discriminant
(Discrim
, CR_Disc
);
10325 end Build_Discriminal
;
10327 ------------------------------------
10328 -- Build_Discriminant_Constraints --
10329 ------------------------------------
10331 function Build_Discriminant_Constraints
10334 Derived_Def
: Boolean := False) return Elist_Id
10336 C
: constant Node_Id
:= Constraint
(Def
);
10337 Nb_Discr
: constant Nat
:= Number_Discriminants
(T
);
10339 Discr_Expr
: array (1 .. Nb_Discr
) of Node_Id
:= (others => Empty
);
10340 -- Saves the expression corresponding to a given discriminant in T
10342 function Pos_Of_Discr
(T
: Entity_Id
; D
: Entity_Id
) return Nat
;
10343 -- Return the Position number within array Discr_Expr of a discriminant
10344 -- D within the discriminant list of the discriminated type T.
10346 procedure Process_Discriminant_Expression
10349 -- If this is a discriminant constraint on a partial view, do not
10350 -- generate an overflow check on the discriminant expression. The check
10351 -- will be generated when constraining the full view. Otherwise the
10352 -- backend creates duplicate symbols for the temporaries corresponding
10353 -- to the expressions to be checked, causing spurious assembler errors.
10359 function Pos_Of_Discr
(T
: Entity_Id
; D
: Entity_Id
) return Nat
is
10363 Disc
:= First_Discriminant
(T
);
10364 for J
in Discr_Expr
'Range loop
10369 Next_Discriminant
(Disc
);
10372 -- Note: Since this function is called on discriminants that are
10373 -- known to belong to the discriminated type, falling through the
10374 -- loop with no match signals an internal compiler error.
10376 raise Program_Error
;
10379 -------------------------------------
10380 -- Process_Discriminant_Expression --
10381 -------------------------------------
10383 procedure Process_Discriminant_Expression
10387 BDT
: constant Entity_Id
:= Base_Type
(Etype
(D
));
10390 -- If this is a discriminant constraint on a partial view, do
10391 -- not generate an overflow on the discriminant expression. The
10392 -- check will be generated when constraining the full view.
10394 if Is_Private_Type
(T
)
10395 and then Present
(Full_View
(T
))
10397 Analyze_And_Resolve
(Expr
, BDT
, Suppress
=> Overflow_Check
);
10399 Analyze_And_Resolve
(Expr
, BDT
);
10401 end Process_Discriminant_Expression
;
10403 -- Declarations local to Build_Discriminant_Constraints
10407 Elist
: constant Elist_Id
:= New_Elmt_List
;
10415 Discrim_Present
: Boolean := False;
10417 -- Start of processing for Build_Discriminant_Constraints
10420 -- The following loop will process positional associations only.
10421 -- For a positional association, the (single) discriminant is
10422 -- implicitly specified by position, in textual order (RM 3.7.2).
10424 Discr
:= First_Discriminant
(T
);
10425 Constr
:= First
(Constraints
(C
));
10426 for D
in Discr_Expr
'Range loop
10427 exit when Nkind
(Constr
) = N_Discriminant_Association
;
10429 if No
(Constr
) then
10430 Error_Msg_N
("too few discriminants given in constraint", C
);
10431 return New_Elmt_List
;
10433 elsif Nkind
(Constr
) = N_Range
10434 or else (Nkind
(Constr
) = N_Attribute_Reference
10435 and then Attribute_Name
(Constr
) = Name_Range
)
10438 ("a range is not a valid discriminant constraint", Constr
);
10439 Discr_Expr
(D
) := Error
;
10441 elsif Nkind
(Constr
) = N_Subtype_Indication
then
10443 ("a subtype indication is not a valid discriminant constraint",
10445 Discr_Expr
(D
) := Error
;
10448 Process_Discriminant_Expression
(Constr
, Discr
);
10449 Discr_Expr
(D
) := Constr
;
10452 Next_Discriminant
(Discr
);
10456 if No
(Discr
) and then Present
(Constr
) then
10457 Error_Msg_N
("too many discriminants given in constraint", Constr
);
10458 return New_Elmt_List
;
10461 -- Named associations can be given in any order, but if both positional
10462 -- and named associations are used in the same discriminant constraint,
10463 -- then positional associations must occur first, at their normal
10464 -- position. Hence once a named association is used, the rest of the
10465 -- discriminant constraint must use only named associations.
10467 while Present
(Constr
) loop
10469 -- Positional association forbidden after a named association
10471 if Nkind
(Constr
) /= N_Discriminant_Association
then
10472 Error_Msg_N
("positional association follows named one", Constr
);
10473 return New_Elmt_List
;
10475 -- Otherwise it is a named association
10478 -- E records the type of the discriminants in the named
10479 -- association. All the discriminants specified in the same name
10480 -- association must have the same type.
10484 -- Search the list of discriminants in T to see if the simple name
10485 -- given in the constraint matches any of them.
10487 Id
:= First
(Selector_Names
(Constr
));
10488 while Present
(Id
) loop
10491 -- If Original_Discriminant is present, we are processing a
10492 -- generic instantiation and this is an instance node. We need
10493 -- to find the name of the corresponding discriminant in the
10494 -- actual record type T and not the name of the discriminant in
10495 -- the generic formal. Example:
10498 -- type G (D : int) is private;
10500 -- subtype W is G (D => 1);
10502 -- type Rec (X : int) is record ... end record;
10503 -- package Q is new P (G => Rec);
10505 -- At the point of the instantiation, formal type G is Rec
10506 -- and therefore when reanalyzing "subtype W is G (D => 1);"
10507 -- which really looks like "subtype W is Rec (D => 1);" at
10508 -- the point of instantiation, we want to find the discriminant
10509 -- that corresponds to D in Rec, i.e. X.
10511 if Present
(Original_Discriminant
(Id
))
10512 and then In_Instance
10514 Discr
:= Find_Corresponding_Discriminant
(Id
, T
);
10518 Discr
:= First_Discriminant
(T
);
10519 while Present
(Discr
) loop
10520 if Chars
(Discr
) = Chars
(Id
) then
10525 Next_Discriminant
(Discr
);
10529 Error_Msg_N
("& does not match any discriminant", Id
);
10530 return New_Elmt_List
;
10532 -- If the parent type is a generic formal, preserve the
10533 -- name of the discriminant for subsequent instances.
10534 -- see comment at the beginning of this if statement.
10536 elsif Is_Generic_Type
(Root_Type
(T
)) then
10537 Set_Original_Discriminant
(Id
, Discr
);
10541 Position
:= Pos_Of_Discr
(T
, Discr
);
10543 if Present
(Discr_Expr
(Position
)) then
10544 Error_Msg_N
("duplicate constraint for discriminant&", Id
);
10547 -- Each discriminant specified in the same named association
10548 -- must be associated with a separate copy of the
10549 -- corresponding expression.
10551 if Present
(Next
(Id
)) then
10552 Expr
:= New_Copy_Tree
(Expression
(Constr
));
10553 Set_Parent
(Expr
, Parent
(Expression
(Constr
)));
10555 Expr
:= Expression
(Constr
);
10558 Discr_Expr
(Position
) := Expr
;
10559 Process_Discriminant_Expression
(Expr
, Discr
);
10562 -- A discriminant association with more than one discriminant
10563 -- name is only allowed if the named discriminants are all of
10564 -- the same type (RM 3.7.1(8)).
10567 E
:= Base_Type
(Etype
(Discr
));
10569 elsif Base_Type
(Etype
(Discr
)) /= E
then
10571 ("all discriminants in an association " &
10572 "must have the same type", Id
);
10582 -- A discriminant constraint must provide exactly one value for each
10583 -- discriminant of the type (RM 3.7.1(8)).
10585 for J
in Discr_Expr
'Range loop
10586 if No
(Discr_Expr
(J
)) then
10587 Error_Msg_N
("too few discriminants given in constraint", C
);
10588 return New_Elmt_List
;
10592 -- Determine if there are discriminant expressions in the constraint
10594 for J
in Discr_Expr
'Range loop
10595 if Denotes_Discriminant
10596 (Discr_Expr
(J
), Check_Concurrent
=> True)
10598 Discrim_Present
:= True;
10603 -- Build an element list consisting of the expressions given in the
10604 -- discriminant constraint and apply the appropriate checks. The list
10605 -- is constructed after resolving any named discriminant associations
10606 -- and therefore the expressions appear in the textual order of the
10609 Discr
:= First_Discriminant
(T
);
10610 for J
in Discr_Expr
'Range loop
10611 if Discr_Expr
(J
) /= Error
then
10612 Append_Elmt
(Discr_Expr
(J
), Elist
);
10614 -- If any of the discriminant constraints is given by a
10615 -- discriminant and we are in a derived type declaration we
10616 -- have a discriminant renaming. Establish link between new
10617 -- and old discriminant. The new discriminant has an implicit
10618 -- dereference if the old one does.
10620 if Denotes_Discriminant
(Discr_Expr
(J
)) then
10621 if Derived_Def
then
10623 New_Discr
: constant Entity_Id
:= Entity
(Discr_Expr
(J
));
10626 Set_Corresponding_Discriminant
(New_Discr
, Discr
);
10627 Set_Has_Implicit_Dereference
(New_Discr
,
10628 Has_Implicit_Dereference
(Discr
));
10632 -- Force the evaluation of non-discriminant expressions.
10633 -- If we have found a discriminant in the constraint 3.4(26)
10634 -- and 3.8(18) demand that no range checks are performed are
10635 -- after evaluation. If the constraint is for a component
10636 -- definition that has a per-object constraint, expressions are
10637 -- evaluated but not checked either. In all other cases perform
10641 if Discrim_Present
then
10644 elsif Parent_Kind
(Parent
(Def
)) = N_Component_Declaration
10645 and then Has_Per_Object_Constraint
10646 (Defining_Identifier
(Parent
(Parent
(Def
))))
10650 elsif Is_Access_Type
(Etype
(Discr
)) then
10651 Apply_Constraint_Check
(Discr_Expr
(J
), Etype
(Discr
));
10654 Apply_Range_Check
(Discr_Expr
(J
), Etype
(Discr
));
10657 -- If the value of the discriminant may be visible in
10658 -- another unit or child unit, create an external name
10659 -- for it. We use the name of the object or component
10660 -- that carries the discriminated subtype. The code
10661 -- below may generate external symbols for the discriminant
10662 -- expression when not strictly needed, which is harmless.
10665 and then Comes_From_Source
(Def
)
10666 and then not Is_Subprogram
(Current_Scope
)
10669 Id
: Entity_Id
:= Empty
;
10671 if Nkind
(Parent
(Def
)) = N_Object_Declaration
then
10672 Id
:= Defining_Identifier
(Parent
(Def
));
10674 elsif Nkind
(Parent
(Def
)) = N_Component_Definition
10676 Nkind
(Parent
(Parent
(Def
)))
10677 = N_Component_Declaration
10679 Id
:= Defining_Identifier
(Parent
(Parent
(Def
)));
10682 if Present
(Id
) then
10686 Discr_Number
=> J
);
10688 Force_Evaluation
(Discr_Expr
(J
));
10692 Force_Evaluation
(Discr_Expr
(J
));
10696 -- Check that the designated type of an access discriminant's
10697 -- expression is not a class-wide type unless the discriminant's
10698 -- designated type is also class-wide.
10700 if Ekind
(Etype
(Discr
)) = E_Anonymous_Access_Type
10701 and then not Is_Class_Wide_Type
10702 (Designated_Type
(Etype
(Discr
)))
10703 and then Etype
(Discr_Expr
(J
)) /= Any_Type
10704 and then Is_Class_Wide_Type
10705 (Designated_Type
(Etype
(Discr_Expr
(J
))))
10707 Wrong_Type
(Discr_Expr
(J
), Etype
(Discr
));
10709 elsif Is_Access_Type
(Etype
(Discr
))
10710 and then not Is_Access_Constant
(Etype
(Discr
))
10711 and then Is_Access_Type
(Etype
(Discr_Expr
(J
)))
10712 and then Is_Access_Constant
(Etype
(Discr_Expr
(J
)))
10715 ("constraint for discriminant& must be access to variable",
10720 Next_Discriminant
(Discr
);
10724 end Build_Discriminant_Constraints
;
10726 ---------------------------------
10727 -- Build_Discriminated_Subtype --
10728 ---------------------------------
10730 procedure Build_Discriminated_Subtype
10732 Def_Id
: Entity_Id
;
10734 Related_Nod
: Node_Id
;
10735 For_Access
: Boolean := False)
10737 Has_Discrs
: constant Boolean := Has_Discriminants
(T
);
10738 Constrained
: constant Boolean :=
10740 and then not Is_Empty_Elmt_List
(Elist
)
10741 and then not Is_Class_Wide_Type
(T
))
10742 or else Is_Constrained
(T
);
10745 if Ekind
(T
) = E_Record_Type
then
10746 Mutate_Ekind
(Def_Id
, E_Record_Subtype
);
10748 -- Inherit preelaboration flag from base, for types for which it
10749 -- may have been set: records, private types, protected types.
10751 Set_Known_To_Have_Preelab_Init
10752 (Def_Id
, Known_To_Have_Preelab_Init
(T
));
10754 elsif Ekind
(T
) = E_Task_Type
then
10755 Mutate_Ekind
(Def_Id
, E_Task_Subtype
);
10757 elsif Ekind
(T
) = E_Protected_Type
then
10758 Mutate_Ekind
(Def_Id
, E_Protected_Subtype
);
10759 Set_Known_To_Have_Preelab_Init
10760 (Def_Id
, Known_To_Have_Preelab_Init
(T
));
10762 elsif Is_Private_Type
(T
) then
10763 Mutate_Ekind
(Def_Id
, Subtype_Kind
(Ekind
(T
)));
10764 Set_Known_To_Have_Preelab_Init
10765 (Def_Id
, Known_To_Have_Preelab_Init
(T
));
10767 -- Private subtypes may have private dependents
10769 Set_Private_Dependents
(Def_Id
, New_Elmt_List
);
10771 elsif Is_Class_Wide_Type
(T
) then
10772 Mutate_Ekind
(Def_Id
, E_Class_Wide_Subtype
);
10775 -- Incomplete type. Attach subtype to list of dependents, to be
10776 -- completed with full view of parent type, unless is it the
10777 -- designated subtype of a record component within an init_proc.
10778 -- This last case arises for a component of an access type whose
10779 -- designated type is incomplete (e.g. a Taft Amendment type).
10780 -- The designated subtype is within an inner scope, and needs no
10781 -- elaboration, because only the access type is needed in the
10782 -- initialization procedure.
10784 if Ekind
(T
) = E_Incomplete_Type
then
10785 Mutate_Ekind
(Def_Id
, E_Incomplete_Subtype
);
10787 Mutate_Ekind
(Def_Id
, Ekind
(T
));
10790 if For_Access
and then Within_Init_Proc
then
10793 Append_Elmt
(Def_Id
, Private_Dependents
(T
));
10797 Set_Etype
(Def_Id
, T
);
10798 Reinit_Size_Align
(Def_Id
);
10799 Set_Has_Discriminants
(Def_Id
, Has_Discrs
);
10800 Set_Is_Constrained
(Def_Id
, Constrained
);
10802 Set_First_Entity
(Def_Id
, First_Entity
(T
));
10803 Set_Last_Entity
(Def_Id
, Last_Entity
(T
));
10804 Set_Has_Implicit_Dereference
10805 (Def_Id
, Has_Implicit_Dereference
(T
));
10806 Set_Has_Pragma_Unreferenced_Objects
10807 (Def_Id
, Has_Pragma_Unreferenced_Objects
(T
));
10809 -- If the subtype is the completion of a private declaration, there may
10810 -- have been representation clauses for the partial view, and they must
10811 -- be preserved. Build_Derived_Type chains the inherited clauses with
10812 -- the ones appearing on the extension. If this comes from a subtype
10813 -- declaration, all clauses are inherited.
10815 if No
(First_Rep_Item
(Def_Id
)) then
10816 Set_First_Rep_Item
(Def_Id
, First_Rep_Item
(T
));
10819 if Is_Tagged_Type
(T
) then
10820 Set_Is_Tagged_Type
(Def_Id
);
10821 Set_No_Tagged_Streams_Pragma
(Def_Id
, No_Tagged_Streams_Pragma
(T
));
10822 Make_Class_Wide_Type
(Def_Id
);
10825 Set_Stored_Constraint
(Def_Id
, No_Elist
);
10828 Set_Discriminant_Constraint
(Def_Id
, Elist
);
10829 Set_Stored_Constraint_From_Discriminant_Constraint
(Def_Id
);
10832 if Is_Tagged_Type
(T
) then
10834 -- Ada 2005 (AI-251): In case of concurrent types we inherit the
10835 -- concurrent record type (which has the list of primitive
10838 if Ada_Version
>= Ada_2005
10839 and then Is_Concurrent_Type
(T
)
10841 Set_Corresponding_Record_Type
(Def_Id
,
10842 Corresponding_Record_Type
(T
));
10844 Set_Direct_Primitive_Operations
(Def_Id
,
10845 Direct_Primitive_Operations
(T
));
10848 Set_Is_Abstract_Type
(Def_Id
, Is_Abstract_Type
(T
));
10851 -- Subtypes introduced by component declarations do not need to be
10852 -- marked as delayed, and do not get freeze nodes, because the semantics
10853 -- verifies that the parents of the subtypes are frozen before the
10854 -- enclosing record is frozen.
10856 if not Is_Type
(Scope
(Def_Id
)) then
10857 Set_Depends_On_Private
(Def_Id
, Depends_On_Private
(T
));
10859 if Is_Private_Type
(T
)
10860 and then Present
(Full_View
(T
))
10862 Conditional_Delay
(Def_Id
, Full_View
(T
));
10864 Conditional_Delay
(Def_Id
, T
);
10868 if Is_Record_Type
(T
) then
10869 Set_Is_Limited_Record
(Def_Id
, Is_Limited_Record
(T
));
10872 and then not Is_Empty_Elmt_List
(Elist
)
10873 and then not For_Access
10875 Create_Constrained_Components
(Def_Id
, Related_Nod
, T
, Elist
);
10877 elsif not Is_Private_Type
(T
) then
10878 Set_Cloned_Subtype
(Def_Id
, T
);
10881 end Build_Discriminated_Subtype
;
10883 ---------------------------
10884 -- Build_Itype_Reference --
10885 ---------------------------
10887 procedure Build_Itype_Reference
10891 IR
: constant Node_Id
:= Make_Itype_Reference
(Sloc
(Nod
));
10894 -- Itype references are only created for use by the back-end
10896 if Inside_A_Generic
then
10899 Set_Itype
(IR
, Ityp
);
10901 -- If Nod is a library unit entity, then Insert_After won't work,
10902 -- because Nod is not a member of any list. Therefore, we use
10903 -- Add_Global_Declaration in this case. This can happen if we have a
10904 -- build-in-place library function, child unit or not.
10906 if (Nkind
(Nod
) in N_Entity
and then Is_Compilation_Unit
(Nod
))
10907 or else (Nkind
(Nod
) in
10908 N_Defining_Program_Unit_Name | N_Subprogram_Declaration
10909 and then Is_Compilation_Unit
(Defining_Entity
(Nod
)))
10911 Add_Global_Declaration
(IR
);
10913 Insert_After
(Nod
, IR
);
10916 end Build_Itype_Reference
;
10918 ------------------------
10919 -- Build_Scalar_Bound --
10920 ------------------------
10922 function Build_Scalar_Bound
10925 Der_T
: Entity_Id
) return Node_Id
10927 New_Bound
: Entity_Id
;
10930 -- Note: not clear why this is needed, how can the original bound
10931 -- be unanalyzed at this point? and if it is, what business do we
10932 -- have messing around with it? and why is the base type of the
10933 -- parent type the right type for the resolution. It probably is
10934 -- not. It is OK for the new bound we are creating, but not for
10935 -- the old one??? Still if it never happens, no problem.
10937 Analyze_And_Resolve
(Bound
, Base_Type
(Par_T
));
10939 if Nkind
(Bound
) in N_Integer_Literal | N_Real_Literal
then
10940 New_Bound
:= New_Copy
(Bound
);
10941 Set_Etype
(New_Bound
, Der_T
);
10942 Set_Analyzed
(New_Bound
);
10944 elsif Is_Entity_Name
(Bound
) then
10945 New_Bound
:= OK_Convert_To
(Der_T
, New_Copy
(Bound
));
10947 -- The following is almost certainly wrong. What business do we have
10948 -- relocating a node (Bound) that is presumably still attached to
10949 -- the tree elsewhere???
10952 New_Bound
:= OK_Convert_To
(Der_T
, Relocate_Node
(Bound
));
10955 Set_Etype
(New_Bound
, Der_T
);
10957 end Build_Scalar_Bound
;
10959 -------------------------------
10960 -- Check_Abstract_Overriding --
10961 -------------------------------
10963 procedure Check_Abstract_Overriding
(T
: Entity_Id
) is
10964 Alias_Subp
: Entity_Id
;
10966 Op_List
: Elist_Id
;
10968 Type_Def
: Node_Id
;
10970 procedure Check_Pragma_Implemented
(Subp
: Entity_Id
);
10971 -- Ada 2012 (AI05-0030): Subprogram Subp overrides an interface routine
10972 -- which has pragma Implemented already set. Check whether Subp's entity
10973 -- kind conforms to the implementation kind of the overridden routine.
10975 procedure Check_Pragma_Implemented
10977 Iface_Subp
: Entity_Id
);
10978 -- Ada 2012 (AI05-0030): Subprogram Subp overrides interface routine
10979 -- Iface_Subp and both entities have pragma Implemented already set on
10980 -- them. Check whether the two implementation kinds are conforming.
10982 procedure Inherit_Pragma_Implemented
10984 Iface_Subp
: Entity_Id
);
10985 -- Ada 2012 (AI05-0030): Interface primitive Subp overrides interface
10986 -- subprogram Iface_Subp which has been marked by pragma Implemented.
10987 -- Propagate the implementation kind of Iface_Subp to Subp.
10989 ------------------------------
10990 -- Check_Pragma_Implemented --
10991 ------------------------------
10993 procedure Check_Pragma_Implemented
(Subp
: Entity_Id
) is
10994 Iface_Alias
: constant Entity_Id
:= Interface_Alias
(Subp
);
10995 Impl_Kind
: constant Name_Id
:= Implementation_Kind
(Iface_Alias
);
10996 Subp_Alias
: constant Entity_Id
:= Alias
(Subp
);
10997 Contr_Typ
: Entity_Id
;
10998 Impl_Subp
: Entity_Id
;
11001 -- Subp must have an alias since it is a hidden entity used to link
11002 -- an interface subprogram to its overriding counterpart.
11004 pragma Assert
(Present
(Subp_Alias
));
11006 -- Handle aliases to synchronized wrappers
11008 Impl_Subp
:= Subp_Alias
;
11010 if Is_Primitive_Wrapper
(Impl_Subp
) then
11011 Impl_Subp
:= Wrapped_Entity
(Impl_Subp
);
11014 -- Extract the type of the controlling formal
11016 Contr_Typ
:= Etype
(First_Formal
(Subp_Alias
));
11018 if Is_Concurrent_Record_Type
(Contr_Typ
) then
11019 Contr_Typ
:= Corresponding_Concurrent_Type
(Contr_Typ
);
11022 -- An interface subprogram whose implementation kind is By_Entry must
11023 -- be implemented by an entry.
11025 if Impl_Kind
= Name_By_Entry
11026 and then Ekind
(Impl_Subp
) /= E_Entry
11028 Error_Msg_Node_2
:= Iface_Alias
;
11030 ("type & must implement abstract subprogram & with an entry",
11031 Subp_Alias
, Contr_Typ
);
11033 elsif Impl_Kind
= Name_By_Protected_Procedure
then
11035 -- An interface subprogram whose implementation kind is By_
11036 -- Protected_Procedure cannot be implemented by a primitive
11037 -- procedure of a task type.
11039 if Ekind
(Contr_Typ
) /= E_Protected_Type
then
11040 Error_Msg_Node_2
:= Contr_Typ
;
11042 ("interface subprogram & cannot be implemented by a "
11043 & "primitive procedure of task type &",
11044 Subp_Alias
, Iface_Alias
);
11046 -- An interface subprogram whose implementation kind is By_
11047 -- Protected_Procedure must be implemented by a procedure.
11049 elsif Ekind
(Impl_Subp
) /= E_Procedure
then
11050 Error_Msg_Node_2
:= Iface_Alias
;
11052 ("type & must implement abstract subprogram & with a "
11053 & "procedure", Subp_Alias
, Contr_Typ
);
11055 elsif Present
(Get_Rep_Pragma
(Impl_Subp
, Name_Implemented
))
11056 and then Implementation_Kind
(Impl_Subp
) /= Impl_Kind
11058 Error_Msg_Name_1
:= Impl_Kind
;
11060 ("overriding operation& must have synchronization%",
11064 -- If primitive has Optional synchronization, overriding operation
11065 -- must match if it has an explicit synchronization.
11067 elsif Present
(Get_Rep_Pragma
(Impl_Subp
, Name_Implemented
))
11068 and then Implementation_Kind
(Impl_Subp
) /= Impl_Kind
11070 Error_Msg_Name_1
:= Impl_Kind
;
11072 ("overriding operation& must have synchronization%", Subp_Alias
);
11074 end Check_Pragma_Implemented
;
11076 ------------------------------
11077 -- Check_Pragma_Implemented --
11078 ------------------------------
11080 procedure Check_Pragma_Implemented
11082 Iface_Subp
: Entity_Id
)
11084 Iface_Kind
: constant Name_Id
:= Implementation_Kind
(Iface_Subp
);
11085 Subp_Kind
: constant Name_Id
:= Implementation_Kind
(Subp
);
11088 -- Ada 2012 (AI05-0030): The implementation kinds of an overridden
11089 -- and overriding subprogram are different. In general this is an
11090 -- error except when the implementation kind of the overridden
11091 -- subprograms is By_Any or Optional.
11093 if Iface_Kind
/= Subp_Kind
11094 and then Iface_Kind
/= Name_By_Any
11095 and then Iface_Kind
/= Name_Optional
11097 if Iface_Kind
= Name_By_Entry
then
11099 ("incompatible implementation kind, overridden subprogram " &
11100 "is marked By_Entry", Subp
);
11103 ("incompatible implementation kind, overridden subprogram " &
11104 "is marked By_Protected_Procedure", Subp
);
11107 end Check_Pragma_Implemented
;
11109 --------------------------------
11110 -- Inherit_Pragma_Implemented --
11111 --------------------------------
11113 procedure Inherit_Pragma_Implemented
11115 Iface_Subp
: Entity_Id
)
11117 Iface_Kind
: constant Name_Id
:= Implementation_Kind
(Iface_Subp
);
11118 Loc
: constant Source_Ptr
:= Sloc
(Subp
);
11119 Impl_Prag
: Node_Id
;
11122 -- Since the implementation kind is stored as a representation item
11123 -- rather than a flag, create a pragma node.
11127 Chars
=> Name_Implemented
,
11128 Pragma_Argument_Associations
=> New_List
(
11129 Make_Pragma_Argument_Association
(Loc
,
11130 Expression
=> New_Occurrence_Of
(Subp
, Loc
)),
11132 Make_Pragma_Argument_Association
(Loc
,
11133 Expression
=> Make_Identifier
(Loc
, Iface_Kind
))));
11135 -- The pragma doesn't need to be analyzed because it is internally
11136 -- built. It is safe to directly register it as a rep item since we
11137 -- are only interested in the characters of the implementation kind.
11139 Record_Rep_Item
(Subp
, Impl_Prag
);
11140 end Inherit_Pragma_Implemented
;
11142 -- Start of processing for Check_Abstract_Overriding
11145 Op_List
:= Primitive_Operations
(T
);
11147 -- Loop to check primitive operations
11149 Elmt
:= First_Elmt
(Op_List
);
11150 while Present
(Elmt
) loop
11151 Subp
:= Node
(Elmt
);
11152 Alias_Subp
:= Alias
(Subp
);
11154 -- If the parent type is untagged, then no overriding error checks
11155 -- are needed (such as in the case of an implicit full type for
11156 -- a derived type whose parent is an untagged private type with
11157 -- a tagged full type).
11159 if not Is_Tagged_Type
(Etype
(T
)) then
11162 -- Inherited subprograms are identified by the fact that they do not
11163 -- come from source, and the associated source location is the
11164 -- location of the first subtype of the derived type.
11166 -- Ada 2005 (AI-228): Apply the rules of RM-3.9.3(6/2) for
11167 -- subprograms that "require overriding".
11169 -- Special exception, do not complain about failure to override the
11170 -- stream routines _Input and _Output, as well as the primitive
11171 -- operations used in dispatching selects since we always provide
11172 -- automatic overridings for these subprograms.
11174 -- The partial view of T may have been a private extension, for
11175 -- which inherited functions dispatching on result are abstract.
11176 -- If the full view is a null extension, there is no need for
11177 -- overriding in Ada 2005, but wrappers need to be built for them
11178 -- (see exp_ch3, Build_Controlling_Function_Wrappers).
11180 elsif Is_Null_Extension
(T
)
11181 and then Has_Controlling_Result
(Subp
)
11182 and then Ada_Version
>= Ada_2005
11183 and then Present
(Alias_Subp
)
11184 and then not Comes_From_Source
(Subp
)
11185 and then not Is_Abstract_Subprogram
(Alias_Subp
)
11186 and then not Is_Access_Type
(Etype
(Subp
))
11190 -- Ada 2005 (AI-251): Internal entities of interfaces need no
11191 -- processing because this check is done with the aliased
11194 elsif Present
(Interface_Alias
(Subp
)) then
11197 -- AI12-0042: Test for rule in 7.3.2(6.1/4), that requires overriding
11198 -- of a visible private primitive inherited from an ancestor with
11199 -- the aspect Type_Invariant'Class, unless the inherited primitive
11202 elsif not Is_Abstract_Subprogram
(Subp
)
11203 and then not Comes_From_Source
(Subp
) -- An inherited subprogram
11204 and then Requires_Overriding
(Subp
)
11205 and then Present
(Alias_Subp
)
11206 and then Has_Invariants
(Etype
(T
))
11207 and then Present
(Get_Pragma
(Etype
(T
), Pragma_Invariant
))
11208 and then Class_Present
(Get_Pragma
(Etype
(T
), Pragma_Invariant
))
11209 and then Is_Private_Primitive
(Alias_Subp
)
11212 ("inherited private primitive & must be overridden", T
, Subp
);
11214 ("\because ancestor type has 'Type_'Invariant''Class " &
11215 "(RM 7.3.2(6.1))", T
);
11217 elsif (Is_Abstract_Subprogram
(Subp
)
11218 or else Requires_Overriding
(Subp
)
11220 (Has_Controlling_Result
(Subp
)
11221 and then Present
(Alias_Subp
)
11222 and then not Comes_From_Source
(Subp
)
11223 and then Sloc
(Subp
) = Sloc
(First_Subtype
(T
))))
11224 and then not Is_TSS
(Subp
, TSS_Stream_Input
)
11225 and then not Is_TSS
(Subp
, TSS_Stream_Output
)
11226 and then not Is_Abstract_Type
(T
)
11227 and then not Is_Predefined_Interface_Primitive
(Subp
)
11229 -- Ada 2005 (AI-251): Do not consider hidden entities associated
11230 -- with abstract interface types because the check will be done
11231 -- with the aliased entity (otherwise we generate a duplicated
11234 and then No
(Interface_Alias
(Subp
))
11236 if Present
(Alias_Subp
) then
11238 -- Only perform the check for a derived subprogram when the
11239 -- type has an explicit record extension. This avoids incorrect
11240 -- flagging of abstract subprograms for the case of a type
11241 -- without an extension that is derived from a formal type
11242 -- with a tagged actual (can occur within a private part).
11244 -- Ada 2005 (AI-391): In the case of an inherited function with
11245 -- a controlling result of the type, the rule does not apply if
11246 -- the type is a null extension (unless the parent function
11247 -- itself is abstract, in which case the function must still be
11248 -- be overridden). The expander will generate an overriding
11249 -- wrapper function calling the parent subprogram (see
11250 -- Exp_Ch3.Make_Controlling_Wrapper_Functions).
11252 Type_Def
:= Type_Definition
(Parent
(T
));
11254 if Nkind
(Type_Def
) = N_Derived_Type_Definition
11255 and then Present
(Record_Extension_Part
(Type_Def
))
11257 (Ada_Version
< Ada_2005
11258 or else not Is_Null_Extension
(T
)
11259 or else Ekind
(Subp
) = E_Procedure
11260 or else not Has_Controlling_Result
(Subp
)
11261 or else Is_Abstract_Subprogram
(Alias_Subp
)
11262 or else Requires_Overriding
(Subp
)
11263 or else Is_Access_Type
(Etype
(Subp
)))
11265 -- Avoid reporting error in case of abstract predefined
11266 -- primitive inherited from interface type because the
11267 -- body of internally generated predefined primitives
11268 -- of tagged types are generated later by Freeze_Type
11270 if Is_Interface
(Root_Type
(T
))
11271 and then Is_Abstract_Subprogram
(Subp
)
11272 and then Is_Predefined_Dispatching_Operation
(Subp
)
11273 and then not Comes_From_Source
(Ultimate_Alias
(Subp
))
11277 -- A null extension is not obliged to override an inherited
11278 -- procedure subject to pragma Extensions_Visible with value
11279 -- False and at least one controlling OUT parameter
11280 -- (SPARK RM 6.1.7(6)).
11282 elsif Is_Null_Extension
(T
)
11283 and then Is_EVF_Procedure
(Subp
)
11287 -- Subprogram renamings cannot be overridden
11289 elsif Comes_From_Source
(Subp
)
11290 and then Present
(Alias
(Subp
))
11294 -- Skip reporting the error on Ada 2022 only subprograms
11295 -- that require overriding if we are not in Ada 2022 mode.
11297 elsif Ada_Version
< Ada_2022
11298 and then Requires_Overriding
(Subp
)
11299 and then Is_Ada_2022_Only
(Ultimate_Alias
(Subp
))
11305 ("type must be declared abstract or & overridden",
11308 -- Traverse the whole chain of aliased subprograms to
11309 -- complete the error notification. This is especially
11310 -- useful for traceability of the chain of entities when
11311 -- the subprogram corresponds with an interface
11312 -- subprogram (which may be defined in another package).
11314 if Present
(Alias_Subp
) then
11320 while Present
(Alias
(E
)) loop
11322 -- Avoid reporting redundant errors on entities
11323 -- inherited from interfaces
11325 if Sloc
(E
) /= Sloc
(T
) then
11326 Error_Msg_Sloc
:= Sloc
(E
);
11328 ("\& has been inherited #", T
, Subp
);
11334 Error_Msg_Sloc
:= Sloc
(E
);
11336 -- AI05-0068: report if there is an overriding
11337 -- non-abstract subprogram that is invisible.
11340 and then not Is_Abstract_Subprogram
(E
)
11343 ("\& subprogram# is not visible",
11346 -- Clarify the case where a non-null extension must
11347 -- override inherited procedure subject to pragma
11348 -- Extensions_Visible with value False and at least
11349 -- one controlling OUT param.
11351 elsif Is_EVF_Procedure
(E
) then
11353 ("\& # is subject to Extensions_Visible False",
11358 ("\& has been inherited from subprogram #",
11365 -- Ada 2005 (AI-345): Protected or task type implementing
11366 -- abstract interfaces.
11368 elsif Is_Concurrent_Record_Type
(T
)
11369 and then Present
(Interfaces
(T
))
11371 -- There is no need to check here RM 9.4(11.9/3) since we
11372 -- are processing the corresponding record type and the
11373 -- mode of the overriding subprograms was verified by
11374 -- Check_Conformance when the corresponding concurrent
11375 -- type declaration was analyzed.
11378 ("interface subprogram & must be overridden", T
, Subp
);
11380 -- Examine primitive operations of synchronized type to find
11381 -- homonyms that have the wrong profile.
11387 Prim
:= First_Entity
(Corresponding_Concurrent_Type
(T
));
11388 while Present
(Prim
) loop
11389 if Chars
(Prim
) = Chars
(Subp
) then
11391 ("profile is not type conformant with prefixed "
11392 & "view profile of inherited operation&",
11396 Next_Entity
(Prim
);
11402 Error_Msg_Node_2
:= T
;
11404 ("abstract subprogram& not allowed for type&", Subp
);
11406 -- Also post unconditional warning on the type (unconditional
11407 -- so that if there are more than one of these cases, we get
11408 -- them all, and not just the first one).
11410 Error_Msg_Node_2
:= Subp
;
11411 Error_Msg_N
("nonabstract type& has abstract subprogram&!", T
);
11414 -- A subprogram subject to pragma Extensions_Visible with value
11415 -- "True" cannot override a subprogram subject to the same pragma
11416 -- with value "False" (SPARK RM 6.1.7(5)).
11418 elsif Extensions_Visible_Status
(Subp
) = Extensions_Visible_True
11419 and then Present
(Overridden_Operation
(Subp
))
11420 and then Extensions_Visible_Status
(Overridden_Operation
(Subp
)) =
11421 Extensions_Visible_False
11423 Error_Msg_Sloc
:= Sloc
(Overridden_Operation
(Subp
));
11425 ("subprogram & with Extensions_Visible True cannot override "
11426 & "subprogram # with Extensions_Visible False", Subp
);
11429 -- Ada 2012 (AI05-0030): Perform checks related to pragma Implemented
11431 -- Subp is an expander-generated procedure which maps an interface
11432 -- alias to a protected wrapper. The interface alias is flagged by
11433 -- pragma Implemented. Ensure that Subp is a procedure when the
11434 -- implementation kind is By_Protected_Procedure or an entry when
11437 if Ada_Version
>= Ada_2012
11438 and then Is_Hidden
(Subp
)
11439 and then Present
(Interface_Alias
(Subp
))
11440 and then Has_Rep_Pragma
(Interface_Alias
(Subp
), Name_Implemented
)
11442 Check_Pragma_Implemented
(Subp
);
11445 -- Subp is an interface primitive which overrides another interface
11446 -- primitive marked with pragma Implemented.
11448 if Ada_Version
>= Ada_2012
11449 and then Present
(Overridden_Operation
(Subp
))
11450 and then Has_Rep_Pragma
11451 (Overridden_Operation
(Subp
), Name_Implemented
)
11453 -- If the overriding routine is also marked by Implemented, check
11454 -- that the two implementation kinds are conforming.
11456 if Has_Rep_Pragma
(Subp
, Name_Implemented
) then
11457 Check_Pragma_Implemented
11459 Iface_Subp
=> Overridden_Operation
(Subp
));
11461 -- Otherwise the overriding routine inherits the implementation
11462 -- kind from the overridden subprogram.
11465 Inherit_Pragma_Implemented
11467 Iface_Subp
=> Overridden_Operation
(Subp
));
11471 -- Ada 2005 (AI95-0414) and Ada 2022 (AI12-0269): Diagnose failure to
11472 -- match No_Return in parent, but do it unconditionally in Ada 95 too
11473 -- for procedures, since this is our pragma.
11475 if Present
(Overridden_Operation
(Subp
))
11476 and then No_Return
(Overridden_Operation
(Subp
))
11479 -- If the subprogram is a renaming, check that the renamed
11480 -- subprogram is No_Return.
11482 if Present
(Renamed_Or_Alias
(Subp
)) then
11483 if not No_Return
(Renamed_Or_Alias
(Subp
)) then
11484 Error_Msg_NE
("subprogram & must be No_Return",
11486 Renamed_Or_Alias
(Subp
));
11487 Error_Msg_N
("\since renaming & overrides No_Return "
11488 & "subprogram (RM 6.5.1(6/2))",
11492 -- Make sure that the subprogram itself is No_Return.
11494 elsif not No_Return
(Subp
) then
11495 Error_Msg_N
("overriding subprogram & must be No_Return", Subp
);
11497 ("\since overridden subprogram is No_Return (RM 6.5.1(6/2))",
11502 -- If the operation is a wrapper for a synchronized primitive, it
11503 -- may be called indirectly through a dispatching select. We assume
11504 -- that it will be referenced elsewhere indirectly, and suppress
11505 -- warnings about an unused entity.
11507 if Is_Primitive_Wrapper
(Subp
)
11508 and then Present
(Wrapped_Entity
(Subp
))
11510 Set_Referenced
(Wrapped_Entity
(Subp
));
11515 end Check_Abstract_Overriding
;
11517 ------------------------------------------------
11518 -- Check_Access_Discriminant_Requires_Limited --
11519 ------------------------------------------------
11521 procedure Check_Access_Discriminant_Requires_Limited
11526 -- A discriminant_specification for an access discriminant shall appear
11527 -- only in the declaration for a task or protected type, or for a type
11528 -- with the reserved word 'limited' in its definition or in one of its
11529 -- ancestors (RM 3.7(10)).
11531 -- AI-0063: The proper condition is that type must be immutably limited,
11532 -- or else be a partial view.
11534 if Nkind
(Discriminant_Type
(D
)) = N_Access_Definition
then
11535 if Is_Limited_View
(Current_Scope
)
11537 (Nkind
(Parent
(Current_Scope
)) = N_Private_Type_Declaration
11538 and then Limited_Present
(Parent
(Current_Scope
)))
11544 ("access discriminants allowed only for limited types", Loc
);
11547 end Check_Access_Discriminant_Requires_Limited
;
11549 -----------------------------------
11550 -- Check_Aliased_Component_Types --
11551 -----------------------------------
11553 procedure Check_Aliased_Component_Types
(T
: Entity_Id
) is
11557 -- ??? Also need to check components of record extensions, but not
11558 -- components of protected types (which are always limited).
11560 -- Ada 2005: AI-363 relaxes this rule, to allow heap objects of such
11561 -- types to be unconstrained. This is safe because it is illegal to
11562 -- create access subtypes to such types with explicit discriminant
11565 if not Is_Limited_Type
(T
) then
11566 if Ekind
(T
) = E_Record_Type
then
11567 C
:= First_Component
(T
);
11568 while Present
(C
) loop
11570 and then Has_Discriminants
(Etype
(C
))
11571 and then not Is_Constrained
(Etype
(C
))
11572 and then not In_Instance_Body
11573 and then Ada_Version
< Ada_2005
11576 ("aliased component must be constrained (RM 3.6(11))",
11580 Next_Component
(C
);
11583 elsif Ekind
(T
) = E_Array_Type
then
11584 if Has_Aliased_Components
(T
)
11585 and then Has_Discriminants
(Component_Type
(T
))
11586 and then not Is_Constrained
(Component_Type
(T
))
11587 and then not In_Instance_Body
11588 and then Ada_Version
< Ada_2005
11591 ("aliased component type must be constrained (RM 3.6(11))",
11596 end Check_Aliased_Component_Types
;
11598 --------------------------------------
11599 -- Check_Anonymous_Access_Component --
11600 --------------------------------------
11602 procedure Check_Anonymous_Access_Component
11603 (Typ_Decl
: Node_Id
;
11606 Comp_Def
: Node_Id
;
11607 Access_Def
: Node_Id
)
11609 Loc
: constant Source_Ptr
:= Sloc
(Comp_Def
);
11610 Anon_Access
: Entity_Id
;
11613 Type_Def
: Node_Id
;
11615 procedure Build_Incomplete_Type_Declaration
;
11616 -- If the record type contains components that include an access to the
11617 -- current record, then create an incomplete type declaration for the
11618 -- record, to be used as the designated type of the anonymous access.
11619 -- This is done only once, and only if there is no previous partial
11620 -- view of the type.
11622 function Designates_T
(Subt
: Node_Id
) return Boolean;
11623 -- Check whether a node designates the enclosing record type, or 'Class
11626 function Mentions_T
(Acc_Def
: Node_Id
) return Boolean;
11627 -- Check whether an access definition includes a reference to
11628 -- the enclosing record type. The reference can be a subtype mark
11629 -- in the access definition itself, a 'Class attribute reference, or
11630 -- recursively a reference appearing in a parameter specification
11631 -- or result definition of an access_to_subprogram definition.
11633 --------------------------------------
11634 -- Build_Incomplete_Type_Declaration --
11635 --------------------------------------
11637 procedure Build_Incomplete_Type_Declaration
is
11642 -- Is_Tagged indicates whether the type is tagged. It is tagged if
11643 -- it's "is new ... with record" or else "is tagged record ...".
11645 Typ_Def
: constant Node_Id
:=
11646 (if Nkind
(Typ_Decl
) = N_Full_Type_Declaration
11647 then Type_Definition
(Typ_Decl
) else Empty
);
11648 Is_Tagged
: constant Boolean :=
11651 ((Nkind
(Typ_Def
) = N_Derived_Type_Definition
11653 Present
(Record_Extension_Part
(Typ_Def
)))
11655 (Nkind
(Typ_Def
) = N_Record_Definition
11656 and then Tagged_Present
(Typ_Def
)));
11659 -- If there is a previous partial view, no need to create a new one
11660 -- If the partial view, given by Prev, is incomplete, If Prev is
11661 -- a private declaration, full declaration is flagged accordingly.
11663 if Prev
/= Typ
then
11665 Make_Class_Wide_Type
(Prev
);
11666 Set_Class_Wide_Type
(Typ
, Class_Wide_Type
(Prev
));
11667 Set_Etype
(Class_Wide_Type
(Typ
), Typ
);
11672 elsif Has_Private_Declaration
(Typ
) then
11674 -- If we refer to T'Class inside T, and T is the completion of a
11675 -- private type, then make sure the class-wide type exists.
11678 Make_Class_Wide_Type
(Typ
);
11683 -- If there was a previous anonymous access type, the incomplete
11684 -- type declaration will have been created already.
11686 elsif Present
(Current_Entity
(Typ
))
11687 and then Ekind
(Current_Entity
(Typ
)) = E_Incomplete_Type
11688 and then Full_View
(Current_Entity
(Typ
)) = Typ
11691 and then Comes_From_Source
(Current_Entity
(Typ
))
11692 and then not Is_Tagged_Type
(Current_Entity
(Typ
))
11694 Make_Class_Wide_Type
(Typ
);
11696 ("incomplete view of tagged type should be declared tagged??",
11697 Parent
(Current_Entity
(Typ
)));
11702 Inc_T
:= Make_Defining_Identifier
(Loc
, Chars
(Typ
));
11703 Decl
:= Make_Incomplete_Type_Declaration
(Loc
, Inc_T
);
11705 -- Type has already been inserted into the current scope. Remove
11706 -- it, and add incomplete declaration for type, so that subsequent
11707 -- anonymous access types can use it. The entity is unchained from
11708 -- the homonym list and from immediate visibility. After analysis,
11709 -- the entity in the incomplete declaration becomes immediately
11710 -- visible in the record declaration that follows.
11712 H
:= Current_Entity
(Typ
);
11715 Set_Name_Entity_Id
(Chars
(Typ
), Homonym
(Typ
));
11718 while Present
(Homonym
(H
)) and then Homonym
(H
) /= Typ
loop
11719 H
:= Homonym
(Typ
);
11722 Set_Homonym
(H
, Homonym
(Typ
));
11725 Insert_Before
(Typ_Decl
, Decl
);
11727 Set_Full_View
(Inc_T
, Typ
);
11728 Set_Incomplete_View
(Typ_Decl
, Inc_T
);
11730 -- If the type is tagged, create a common class-wide type for
11731 -- both views, and set the Etype of the class-wide type to the
11735 Make_Class_Wide_Type
(Inc_T
);
11736 Set_Class_Wide_Type
(Typ
, Class_Wide_Type
(Inc_T
));
11737 Set_Etype
(Class_Wide_Type
(Typ
), Typ
);
11740 -- If the scope is a package with a limited view, create a shadow
11741 -- entity for the incomplete type like Build_Limited_Views, so as
11742 -- to make it possible for Remove_Limited_With_Unit to reinstall
11743 -- this incomplete type as the visible entity.
11745 if Ekind
(Scope
(Inc_T
)) = E_Package
11746 and then Present
(Limited_View
(Scope
(Inc_T
)))
11749 Shadow
: constant Entity_Id
:= Make_Temporary
(Loc
, 'Z');
11752 -- This is modeled on Build_Shadow_Entity
11754 Set_Chars
(Shadow
, Chars
(Inc_T
));
11755 Set_Parent
(Shadow
, Decl
);
11756 Decorate_Type
(Shadow
, Scope
(Inc_T
), Is_Tagged
);
11757 Set_Is_Internal
(Shadow
);
11758 Set_From_Limited_With
(Shadow
);
11759 Set_Non_Limited_View
(Shadow
, Inc_T
);
11760 Set_Private_Dependents
(Shadow
, New_Elmt_List
);
11763 Set_Non_Limited_View
11764 (Class_Wide_Type
(Shadow
), Class_Wide_Type
(Inc_T
));
11767 Append_Entity
(Shadow
, Limited_View
(Scope
(Inc_T
)));
11771 end Build_Incomplete_Type_Declaration
;
11777 function Designates_T
(Subt
: Node_Id
) return Boolean is
11778 Type_Id
: constant Name_Id
:= Chars
(Typ
);
11780 function Names_T
(Nam
: Node_Id
) return Boolean;
11781 -- The record type has not been introduced in the current scope
11782 -- yet, so we must examine the name of the type itself, either
11783 -- an identifier T, or an expanded name of the form P.T, where
11784 -- P denotes the current scope.
11790 function Names_T
(Nam
: Node_Id
) return Boolean is
11792 if Nkind
(Nam
) = N_Identifier
then
11793 return Chars
(Nam
) = Type_Id
;
11795 elsif Nkind
(Nam
) = N_Selected_Component
then
11796 if Chars
(Selector_Name
(Nam
)) = Type_Id
then
11797 if Nkind
(Prefix
(Nam
)) = N_Identifier
then
11798 return Chars
(Prefix
(Nam
)) = Chars
(Current_Scope
);
11800 elsif Nkind
(Prefix
(Nam
)) = N_Selected_Component
then
11801 return Chars
(Selector_Name
(Prefix
(Nam
))) =
11802 Chars
(Current_Scope
);
11816 -- Start of processing for Designates_T
11819 if Nkind
(Subt
) = N_Identifier
then
11820 return Chars
(Subt
) = Type_Id
;
11822 -- Reference can be through an expanded name which has not been
11823 -- analyzed yet, and which designates enclosing scopes.
11825 elsif Nkind
(Subt
) = N_Selected_Component
then
11826 if Names_T
(Subt
) then
11829 -- Otherwise it must denote an entity that is already visible.
11830 -- The access definition may name a subtype of the enclosing
11831 -- type, if there is a previous incomplete declaration for it.
11834 Find_Selected_Component
(Subt
);
11836 Is_Entity_Name
(Subt
)
11837 and then Scope
(Entity
(Subt
)) = Current_Scope
11839 (Chars
(Base_Type
(Entity
(Subt
))) = Type_Id
11841 (Is_Class_Wide_Type
(Entity
(Subt
))
11843 Chars
(Etype
(Base_Type
(Entity
(Subt
)))) =
11847 -- A reference to the current type may appear as the prefix of
11848 -- a 'Class attribute.
11850 elsif Nkind
(Subt
) = N_Attribute_Reference
11851 and then Attribute_Name
(Subt
) = Name_Class
11853 return Names_T
(Prefix
(Subt
));
11864 function Mentions_T
(Acc_Def
: Node_Id
) return Boolean is
11865 Param_Spec
: Node_Id
;
11867 Acc_Subprg
: constant Node_Id
:=
11868 Access_To_Subprogram_Definition
(Acc_Def
);
11871 if No
(Acc_Subprg
) then
11872 return Designates_T
(Subtype_Mark
(Acc_Def
));
11875 -- Component is an access_to_subprogram: examine its formals,
11876 -- and result definition in the case of an access_to_function.
11878 Param_Spec
:= First
(Parameter_Specifications
(Acc_Subprg
));
11879 while Present
(Param_Spec
) loop
11880 if Nkind
(Parameter_Type
(Param_Spec
)) = N_Access_Definition
11881 and then Mentions_T
(Parameter_Type
(Param_Spec
))
11885 elsif Designates_T
(Parameter_Type
(Param_Spec
)) then
11892 if Nkind
(Acc_Subprg
) = N_Access_Function_Definition
then
11893 if Nkind
(Result_Definition
(Acc_Subprg
)) =
11894 N_Access_Definition
11896 return Mentions_T
(Result_Definition
(Acc_Subprg
));
11898 return Designates_T
(Result_Definition
(Acc_Subprg
));
11905 -- Start of processing for Check_Anonymous_Access_Component
11908 if Present
(Access_Def
) and then Mentions_T
(Access_Def
) then
11909 Acc_Def
:= Access_To_Subprogram_Definition
(Access_Def
);
11911 Build_Incomplete_Type_Declaration
;
11912 Anon_Access
:= Make_Temporary
(Loc
, 'S');
11914 -- Create a declaration for the anonymous access type: either
11915 -- an access_to_object or an access_to_subprogram.
11917 if Present
(Acc_Def
) then
11918 if Nkind
(Acc_Def
) = N_Access_Function_Definition
then
11920 Make_Access_Function_Definition
(Loc
,
11921 Parameter_Specifications
=>
11922 Parameter_Specifications
(Acc_Def
),
11923 Result_Definition
=> Result_Definition
(Acc_Def
));
11926 Make_Access_Procedure_Definition
(Loc
,
11927 Parameter_Specifications
=>
11928 Parameter_Specifications
(Acc_Def
));
11933 Make_Access_To_Object_Definition
(Loc
,
11934 Subtype_Indication
=>
11935 Relocate_Node
(Subtype_Mark
(Access_Def
)));
11937 Set_Constant_Present
(Type_Def
, Constant_Present
(Access_Def
));
11938 Set_All_Present
(Type_Def
, All_Present
(Access_Def
));
11941 Set_Null_Exclusion_Present
11942 (Type_Def
, Null_Exclusion_Present
(Access_Def
));
11945 Make_Full_Type_Declaration
(Loc
,
11946 Defining_Identifier
=> Anon_Access
,
11947 Type_Definition
=> Type_Def
);
11949 Insert_Before
(Typ_Decl
, Decl
);
11952 -- At first sight we could add here the extra formals of an access to
11953 -- subprogram; however, it must delayed till the freeze point so that
11954 -- we know the convention.
11956 if Nkind
(Comp_Def
) = N_Component_Definition
then
11958 Make_Component_Definition
(Loc
,
11959 Subtype_Indication
=> New_Occurrence_Of
(Anon_Access
, Loc
)));
11961 pragma Assert
(Nkind
(Comp_Def
) = N_Discriminant_Specification
);
11963 Make_Discriminant_Specification
(Loc
,
11964 Defining_Identifier
=> Defining_Identifier
(Comp_Def
),
11965 Discriminant_Type
=> New_Occurrence_Of
(Anon_Access
, Loc
)));
11968 if Ekind
(Designated_Type
(Anon_Access
)) = E_Subprogram_Type
then
11969 Mutate_Ekind
(Anon_Access
, E_Anonymous_Access_Subprogram_Type
);
11971 Mutate_Ekind
(Anon_Access
, E_Anonymous_Access_Type
);
11974 Set_Is_Local_Anonymous_Access
(Anon_Access
);
11976 end Check_Anonymous_Access_Component
;
11978 ---------------------------------------
11979 -- Check_Anonymous_Access_Components --
11980 ---------------------------------------
11982 procedure Check_Anonymous_Access_Components
11983 (Typ_Decl
: Node_Id
;
11986 Comp_List
: Node_Id
)
11990 if No
(Comp_List
) then
11994 Set_Is_Not_Self_Hidden
(Typ
);
11996 Comp
:= First
(Component_Items
(Comp_List
));
11997 while Present
(Comp
) loop
11998 if Nkind
(Comp
) = N_Component_Declaration
then
11999 Check_Anonymous_Access_Component
12000 (Typ_Decl
, Typ
, Prev
,
12001 Component_Definition
(Comp
),
12002 Access_Definition
(Component_Definition
(Comp
)));
12008 if Present
(Variant_Part
(Comp_List
)) then
12012 V
:= First_Non_Pragma
(Variants
(Variant_Part
(Comp_List
)));
12013 while Present
(V
) loop
12014 Check_Anonymous_Access_Components
12015 (Typ_Decl
, Typ
, Prev
, Component_List
(V
));
12016 Next_Non_Pragma
(V
);
12020 end Check_Anonymous_Access_Components
;
12022 ----------------------
12023 -- Check_Completion --
12024 ----------------------
12026 procedure Check_Completion
(Body_Id
: Node_Id
:= Empty
) is
12029 procedure Post_Error
;
12030 -- Post error message for lack of completion for entity E
12036 procedure Post_Error
is
12037 procedure Missing_Body
;
12038 -- Output missing body message
12044 procedure Missing_Body
is
12046 -- Spec is in same unit, so we can post on spec
12048 if In_Same_Source_Unit
(Body_Id
, E
) then
12049 Error_Msg_N
("missing body for &", E
);
12051 -- Spec is in a separate unit, so we have to post on the body
12054 Error_Msg_NE
("missing body for & declared#!", Body_Id
, E
);
12058 -- Start of processing for Post_Error
12061 if not Comes_From_Source
(E
) then
12062 if Ekind
(E
) in E_Task_Type | E_Protected_Type
then
12064 -- It may be an anonymous protected type created for a
12065 -- single variable. Post error on variable, if present.
12071 Var
:= First_Entity
(Current_Scope
);
12072 while Present
(Var
) loop
12073 exit when Etype
(Var
) = E
12074 and then Comes_From_Source
(Var
);
12079 if Present
(Var
) then
12086 -- If a generated entity has no completion, then either previous
12087 -- semantic errors have disabled the expansion phase, or else we had
12088 -- missing subunits, or else we are compiling without expansion,
12089 -- or else something is very wrong.
12091 if not Comes_From_Source
(E
) then
12093 (Serious_Errors_Detected
> 0
12094 or else Configurable_Run_Time_Violations
> 0
12095 or else Subunits_Missing
12096 or else not Expander_Active
);
12099 -- Here for source entity
12102 -- Here if no body to post the error message, so we post the error
12103 -- on the declaration that has no completion. This is not really
12104 -- the right place to post it, think about this later ???
12106 if No
(Body_Id
) then
12107 if Is_Type
(E
) then
12109 ("missing full declaration for }", Parent
(E
), E
);
12111 Error_Msg_NE
("missing body for &", Parent
(E
), E
);
12114 -- Package body has no completion for a declaration that appears
12115 -- in the corresponding spec. Post error on the body, with a
12116 -- reference to the non-completed declaration.
12119 Error_Msg_Sloc
:= Sloc
(E
);
12121 if Is_Type
(E
) then
12122 Error_Msg_NE
("missing full declaration for }!", Body_Id
, E
);
12124 elsif Is_Overloadable
(E
)
12125 and then Current_Entity_In_Scope
(E
) /= E
12127 -- It may be that the completion is mistyped and appears as
12128 -- a distinct overloading of the entity.
12131 Candidate
: constant Entity_Id
:=
12132 Current_Entity_In_Scope
(E
);
12133 Decl
: constant Node_Id
:=
12134 Unit_Declaration_Node
(Candidate
);
12137 if Is_Overloadable
(Candidate
)
12138 and then Ekind
(Candidate
) = Ekind
(E
)
12139 and then Nkind
(Decl
) = N_Subprogram_Body
12140 and then Acts_As_Spec
(Decl
)
12142 Check_Type_Conformant
(Candidate
, E
);
12158 Pack_Id
: constant Entity_Id
:= Current_Scope
;
12160 -- Start of processing for Check_Completion
12163 E
:= First_Entity
(Pack_Id
);
12164 while Present
(E
) loop
12165 if Is_Intrinsic_Subprogram
(E
) then
12168 -- The following situation requires special handling: a child unit
12169 -- that appears in the context clause of the body of its parent:
12171 -- procedure Parent.Child (...);
12173 -- with Parent.Child;
12174 -- package body Parent is
12176 -- Here Parent.Child appears as a local entity, but should not be
12177 -- flagged as requiring completion, because it is a compilation
12180 -- Ignore missing completion for a subprogram that does not come from
12181 -- source (including the _Call primitive operation of RAS types,
12182 -- which has to have the flag Comes_From_Source for other purposes):
12183 -- we assume that the expander will provide the missing completion.
12184 -- In case of previous errors, other expansion actions that provide
12185 -- bodies for null procedures with not be invoked, so inhibit message
12188 -- Note that E_Operator is not in the list that follows, because
12189 -- this kind is reserved for predefined operators, that are
12190 -- intrinsic and do not need completion.
12192 elsif Ekind
(E
) in E_Function
12194 | E_Generic_Function
12195 | E_Generic_Procedure
12197 if Has_Completion
(E
) then
12200 elsif Is_Subprogram
(E
) and then Is_Abstract_Subprogram
(E
) then
12203 elsif Is_Subprogram
(E
)
12204 and then (not Comes_From_Source
(E
)
12205 or else Chars
(E
) = Name_uCall
)
12210 Nkind
(Parent
(Unit_Declaration_Node
(E
))) = N_Compilation_Unit
12214 elsif Nkind
(Parent
(E
)) = N_Procedure_Specification
12215 and then Null_Present
(Parent
(E
))
12216 and then Serious_Errors_Detected
> 0
12224 elsif Is_Entry
(E
) then
12225 if not Has_Completion
(E
)
12226 and then Ekind
(Scope
(E
)) = E_Protected_Type
12231 elsif Is_Package_Or_Generic_Package
(E
) then
12232 if Unit_Requires_Body
(E
) then
12233 if not Has_Completion
(E
)
12234 and then Nkind
(Parent
(Unit_Declaration_Node
(E
))) /=
12240 elsif not Is_Child_Unit
(E
) then
12241 May_Need_Implicit_Body
(E
);
12244 -- A formal incomplete type (Ada 2012) does not require a completion;
12245 -- other incomplete type declarations do.
12247 elsif Ekind
(E
) = E_Incomplete_Type
then
12248 if No
(Underlying_Type
(E
))
12249 and then not Is_Generic_Type
(E
)
12254 elsif Ekind
(E
) in E_Task_Type | E_Protected_Type
then
12255 if not Has_Completion
(E
) then
12259 -- A single task declared in the current scope is a constant, verify
12260 -- that the body of its anonymous type is in the same scope. If the
12261 -- task is defined elsewhere, this may be a renaming declaration for
12262 -- which no completion is needed.
12264 elsif Ekind
(E
) = E_Constant
then
12265 if Ekind
(Etype
(E
)) = E_Task_Type
12266 and then not Has_Completion
(Etype
(E
))
12267 and then Scope
(Etype
(E
)) = Current_Scope
12272 elsif Ekind
(E
) = E_Record_Type
then
12273 if Is_Tagged_Type
(E
) then
12274 Check_Abstract_Overriding
(E
);
12275 Check_Conventions
(E
);
12278 Check_Aliased_Component_Types
(E
);
12280 elsif Ekind
(E
) = E_Array_Type
then
12281 Check_Aliased_Component_Types
(E
);
12287 end Check_Completion
;
12289 -------------------------------------
12290 -- Check_Constraining_Discriminant --
12291 -------------------------------------
12293 procedure Check_Constraining_Discriminant
(New_Disc
, Old_Disc
: Entity_Id
)
12295 New_Type
: constant Entity_Id
:= Etype
(New_Disc
);
12296 Old_Type
: Entity_Id
;
12299 -- If the record type contains an array constrained by the discriminant
12300 -- but with some different bound, the compiler tries to create a smaller
12301 -- range for the discriminant type (see exp_ch3.Adjust_Discriminants).
12302 -- In this case, where the discriminant type is a scalar type, the check
12303 -- must use the original discriminant type in the parent declaration.
12305 if Is_Scalar_Type
(New_Type
) then
12306 Old_Type
:= Entity
(Discriminant_Type
(Parent
(Old_Disc
)));
12308 Old_Type
:= Etype
(Old_Disc
);
12311 if not Subtypes_Statically_Compatible
(New_Type
, Old_Type
) then
12313 ("subtype must be statically compatible with parent discriminant",
12316 if not Predicates_Compatible
(New_Type
, Old_Type
) then
12318 ("\subtype predicate is not compatible with parent discriminant",
12322 end Check_Constraining_Discriminant
;
12324 ------------------------------------
12325 -- Check_CPP_Type_Has_No_Defaults --
12326 ------------------------------------
12328 procedure Check_CPP_Type_Has_No_Defaults
(T
: Entity_Id
) is
12329 Tdef
: constant Node_Id
:= Type_Definition
(Declaration_Node
(T
));
12334 -- Obtain the component list
12336 if Nkind
(Tdef
) = N_Record_Definition
then
12337 Clist
:= Component_List
(Tdef
);
12338 else pragma Assert
(Nkind
(Tdef
) = N_Derived_Type_Definition
);
12339 Clist
:= Component_List
(Record_Extension_Part
(Tdef
));
12342 -- Check all components to ensure no default expressions
12344 if Present
(Clist
) then
12345 Comp
:= First_Non_Pragma
(Component_Items
(Clist
));
12346 while Present
(Comp
) loop
12347 if Present
(Expression
(Comp
)) then
12349 ("component of imported 'C'P'P type cannot have "
12350 & "default expression", Expression
(Comp
));
12353 Next_Non_Pragma
(Comp
);
12356 end Check_CPP_Type_Has_No_Defaults
;
12358 ----------------------------
12359 -- Check_Delta_Expression --
12360 ----------------------------
12362 procedure Check_Delta_Expression
(E
: Node_Id
) is
12364 if not (Is_Real_Type
(Etype
(E
))) then
12365 Wrong_Type
(E
, Any_Real
);
12367 elsif not Is_OK_Static_Expression
(E
) then
12368 Flag_Non_Static_Expr
12369 ("non-static expression used for delta value!", E
);
12371 elsif not UR_Is_Positive
(Expr_Value_R
(E
)) then
12372 Error_Msg_N
("delta expression must be positive", E
);
12378 -- If any of above errors occurred, then replace the incorrect
12379 -- expression by the real 0.1, which should prevent further errors.
12382 Make_Real_Literal
(Sloc
(E
), Ureal_Tenth
));
12383 Analyze_And_Resolve
(E
, Standard_Float
);
12384 end Check_Delta_Expression
;
12386 -----------------------------
12387 -- Check_Digits_Expression --
12388 -----------------------------
12390 procedure Check_Digits_Expression
(E
: Node_Id
) is
12392 if not (Is_Integer_Type
(Etype
(E
))) then
12393 Wrong_Type
(E
, Any_Integer
);
12395 elsif not Is_OK_Static_Expression
(E
) then
12396 Flag_Non_Static_Expr
12397 ("non-static expression used for digits value!", E
);
12399 elsif Expr_Value
(E
) <= 0 then
12400 Error_Msg_N
("digits value must be greater than zero", E
);
12406 -- If any of above errors occurred, then replace the incorrect
12407 -- expression by the integer 1, which should prevent further errors.
12409 Rewrite
(E
, Make_Integer_Literal
(Sloc
(E
), 1));
12410 Analyze_And_Resolve
(E
, Standard_Integer
);
12412 end Check_Digits_Expression
;
12414 --------------------------
12415 -- Check_Initialization --
12416 --------------------------
12418 procedure Check_Initialization
(T
: Entity_Id
; Exp
: Node_Id
) is
12420 -- Special processing for limited types
12422 if Is_Limited_Type
(T
)
12423 and then not In_Instance
12424 and then not In_Inlined_Body
12426 if not OK_For_Limited_Init
(T
, Exp
) then
12428 -- In GNAT mode, this is just a warning, to allow it to be evilly
12429 -- turned off. Otherwise it is a real error.
12433 ("??cannot initialize entities of limited type!", Exp
);
12435 elsif Ada_Version
< Ada_2005
then
12437 -- The side effect removal machinery may generate illegal Ada
12438 -- code to avoid the usage of access types and 'reference in
12439 -- SPARK mode. Since this is legal code with respect to theorem
12440 -- proving, do not emit the error.
12443 and then Nkind
(Exp
) = N_Function_Call
12444 and then Nkind
(Parent
(Exp
)) = N_Object_Declaration
12445 and then not Comes_From_Source
12446 (Defining_Identifier
(Parent
(Exp
)))
12452 ("cannot initialize entities of limited type", Exp
);
12453 Explain_Limited_Type
(T
, Exp
);
12457 -- Specialize error message according to kind of illegal
12458 -- initial expression. We check the Original_Node to cover
12459 -- cases where the initialization expression of an object
12460 -- declaration generated by the compiler has been rewritten
12461 -- (such as for dispatching calls).
12463 if Nkind
(Original_Node
(Exp
)) = N_Type_Conversion
12465 Nkind
(Expression
(Original_Node
(Exp
))) = N_Function_Call
12467 -- No error for internally-generated object declarations,
12468 -- which can come from build-in-place assignment statements.
12470 if Nkind
(Parent
(Exp
)) = N_Object_Declaration
12471 and then not Comes_From_Source
12472 (Defining_Identifier
(Parent
(Exp
)))
12478 ("illegal context for call to function with limited "
12484 ("initialization of limited object requires aggregate or "
12485 & "function call", Exp
);
12491 -- In gnatc or gnatprove mode, make sure set Do_Range_Check flag gets
12492 -- set unless we can be sure that no range check is required.
12494 if not Expander_Active
12495 and then Is_Scalar_Type
(T
)
12496 and then not Is_In_Range
(Exp
, T
, Assume_Valid
=> True)
12498 Set_Do_Range_Check
(Exp
);
12500 end Check_Initialization
;
12502 ----------------------
12503 -- Check_Interfaces --
12504 ----------------------
12506 procedure Check_Interfaces
(N
: Node_Id
; Def
: Node_Id
) is
12507 Parent_Type
: constant Entity_Id
:= Etype
(Defining_Identifier
(N
));
12510 Iface_Def
: Node_Id
;
12511 Iface_Typ
: Entity_Id
;
12512 Parent_Node
: Node_Id
;
12514 Is_Task
: Boolean := False;
12515 -- Set True if parent type or any progenitor is a task interface
12517 Is_Protected
: Boolean := False;
12518 -- Set True if parent type or any progenitor is a protected interface
12520 procedure Check_Ifaces
(Iface_Def
: Node_Id
; Error_Node
: Node_Id
);
12521 -- Check that a progenitor is compatible with declaration. If an error
12522 -- message is output, it is posted on Error_Node.
12528 procedure Check_Ifaces
(Iface_Def
: Node_Id
; Error_Node
: Node_Id
) is
12529 Iface_Id
: constant Entity_Id
:=
12530 Defining_Identifier
(Parent
(Iface_Def
));
12531 Type_Def
: Node_Id
;
12534 if Nkind
(N
) = N_Private_Extension_Declaration
then
12537 Type_Def
:= Type_Definition
(N
);
12540 if Is_Task_Interface
(Iface_Id
) then
12543 elsif Is_Protected_Interface
(Iface_Id
) then
12544 Is_Protected
:= True;
12547 if Is_Synchronized_Interface
(Iface_Id
) then
12549 -- A consequence of 3.9.4 (6/2) and 7.3 (7.2/2) is that a private
12550 -- extension derived from a synchronized interface must explicitly
12551 -- be declared synchronized, because the full view will be a
12552 -- synchronized type.
12554 if Nkind
(N
) = N_Private_Extension_Declaration
then
12555 if not Synchronized_Present
(N
) then
12557 ("private extension of& must be explicitly synchronized",
12561 -- However, by 3.9.4(16/2), a full type that is a record extension
12562 -- is never allowed to derive from a synchronized interface (note
12563 -- that interfaces must be excluded from this check, because those
12564 -- are represented by derived type definitions in some cases).
12566 elsif Nkind
(Type_Definition
(N
)) = N_Derived_Type_Definition
12567 and then not Interface_Present
(Type_Definition
(N
))
12569 Error_Msg_N
("record extension cannot derive from synchronized "
12570 & "interface", Error_Node
);
12574 -- Check that the characteristics of the progenitor are compatible
12575 -- with the explicit qualifier in the declaration.
12576 -- The check only applies to qualifiers that come from source.
12577 -- Limited_Present also appears in the declaration of corresponding
12578 -- records, and the check does not apply to them.
12580 if Limited_Present
(Type_Def
)
12582 Is_Concurrent_Record_Type
(Defining_Identifier
(N
))
12584 if Is_Limited_Interface
(Parent_Type
)
12585 and then not Is_Limited_Interface
(Iface_Id
)
12588 ("progenitor & must be limited interface",
12589 Error_Node
, Iface_Id
);
12592 (Task_Present
(Iface_Def
)
12593 or else Protected_Present
(Iface_Def
)
12594 or else Synchronized_Present
(Iface_Def
))
12595 and then Nkind
(N
) /= N_Private_Extension_Declaration
12596 and then not Error_Posted
(N
)
12599 ("progenitor & must be limited interface",
12600 Error_Node
, Iface_Id
);
12603 -- Protected interfaces can only inherit from limited, synchronized
12604 -- or protected interfaces.
12606 elsif Nkind
(N
) = N_Full_Type_Declaration
12607 and then Protected_Present
(Type_Def
)
12609 if Limited_Present
(Iface_Def
)
12610 or else Synchronized_Present
(Iface_Def
)
12611 or else Protected_Present
(Iface_Def
)
12615 elsif Task_Present
(Iface_Def
) then
12616 Error_Msg_N
("(Ada 2005) protected interface cannot inherit "
12617 & "from task interface", Error_Node
);
12620 Error_Msg_N
("(Ada 2005) protected interface cannot inherit "
12621 & "from non-limited interface", Error_Node
);
12624 -- Ada 2005 (AI-345): Synchronized interfaces can only inherit from
12625 -- limited and synchronized.
12627 elsif Synchronized_Present
(Type_Def
) then
12628 if Limited_Present
(Iface_Def
)
12629 or else Synchronized_Present
(Iface_Def
)
12633 elsif Protected_Present
(Iface_Def
)
12634 and then Nkind
(N
) /= N_Private_Extension_Declaration
12636 Error_Msg_N
("(Ada 2005) synchronized interface cannot inherit "
12637 & "from protected interface", Error_Node
);
12639 elsif Task_Present
(Iface_Def
)
12640 and then Nkind
(N
) /= N_Private_Extension_Declaration
12642 Error_Msg_N
("(Ada 2005) synchronized interface cannot inherit "
12643 & "from task interface", Error_Node
);
12645 elsif not Is_Limited_Interface
(Iface_Id
) then
12646 Error_Msg_N
("(Ada 2005) synchronized interface cannot inherit "
12647 & "from non-limited interface", Error_Node
);
12650 -- Ada 2005 (AI-345): Task interfaces can only inherit from limited,
12651 -- synchronized or task interfaces.
12653 elsif Nkind
(N
) = N_Full_Type_Declaration
12654 and then Task_Present
(Type_Def
)
12656 if Limited_Present
(Iface_Def
)
12657 or else Synchronized_Present
(Iface_Def
)
12658 or else Task_Present
(Iface_Def
)
12662 elsif Protected_Present
(Iface_Def
) then
12663 Error_Msg_N
("(Ada 2005) task interface cannot inherit from "
12664 & "protected interface", Error_Node
);
12667 Error_Msg_N
("(Ada 2005) task interface cannot inherit from "
12668 & "non-limited interface", Error_Node
);
12673 -- Start of processing for Check_Interfaces
12676 if Is_Interface
(Parent_Type
) then
12677 if Is_Task_Interface
(Parent_Type
) then
12680 elsif Is_Protected_Interface
(Parent_Type
) then
12681 Is_Protected
:= True;
12685 if Nkind
(N
) = N_Private_Extension_Declaration
then
12687 -- Check that progenitors are compatible with declaration
12689 Iface
:= First
(Interface_List
(Def
));
12690 while Present
(Iface
) loop
12691 Iface_Typ
:= Find_Type_Of_Subtype_Indic
(Iface
);
12693 Parent_Node
:= Parent
(Base_Type
(Iface_Typ
));
12694 Iface_Def
:= Type_Definition
(Parent_Node
);
12696 if not Is_Interface
(Iface_Typ
) then
12697 Diagnose_Interface
(Iface
, Iface_Typ
);
12699 Check_Ifaces
(Iface_Def
, Iface
);
12705 if Is_Task
and Is_Protected
then
12707 ("type cannot derive from task and protected interface", N
);
12713 -- Full type declaration of derived type.
12714 -- Check compatibility with parent if it is interface type
12716 if Nkind
(Type_Definition
(N
)) = N_Derived_Type_Definition
12717 and then Is_Interface
(Parent_Type
)
12719 Parent_Node
:= Parent
(Parent_Type
);
12721 -- More detailed checks for interface varieties
12724 (Iface_Def
=> Type_Definition
(Parent_Node
),
12725 Error_Node
=> Subtype_Indication
(Type_Definition
(N
)));
12728 Iface
:= First
(Interface_List
(Def
));
12729 while Present
(Iface
) loop
12730 Iface_Typ
:= Find_Type_Of_Subtype_Indic
(Iface
);
12732 Parent_Node
:= Parent
(Base_Type
(Iface_Typ
));
12733 Iface_Def
:= Type_Definition
(Parent_Node
);
12735 if not Is_Interface
(Iface_Typ
) then
12736 Diagnose_Interface
(Iface
, Iface_Typ
);
12739 -- "The declaration of a specific descendant of an interface
12740 -- type freezes the interface type" RM 13.14
12742 Freeze_Before
(N
, Iface_Typ
);
12743 Check_Ifaces
(Iface_Def
, Error_Node
=> Iface
);
12749 if Is_Task
and Is_Protected
then
12751 ("type cannot derive from task and protected interface", N
);
12753 end Check_Interfaces
;
12755 ------------------------------------
12756 -- Check_Or_Process_Discriminants --
12757 ------------------------------------
12759 -- If an incomplete or private type declaration was already given for the
12760 -- type, the discriminants may have already been processed if they were
12761 -- present on the incomplete declaration. In this case a full conformance
12762 -- check has been performed in Find_Type_Name, and we then recheck here
12763 -- some properties that can't be checked on the partial view alone.
12764 -- Otherwise we call Process_Discriminants.
12766 procedure Check_Or_Process_Discriminants
12769 Prev
: Entity_Id
:= Empty
)
12772 if Has_Discriminants
(T
) then
12774 -- Discriminants are already set on T if they were already present
12775 -- on the partial view. Make them visible to component declarations.
12779 -- Discriminant on T (full view) referencing expr on partial view
12781 Prev_D
: Entity_Id
;
12782 -- Entity of corresponding discriminant on partial view
12785 -- Discriminant specification for full view, expression is
12786 -- the syntactic copy on full view (which has been checked for
12787 -- conformance with partial view), only used here to post error
12791 D
:= First_Discriminant
(T
);
12792 New_D
:= First
(Discriminant_Specifications
(N
));
12793 while Present
(D
) loop
12794 Prev_D
:= Current_Entity
(D
);
12795 Set_Current_Entity
(D
);
12796 Set_Is_Immediately_Visible
(D
);
12797 Set_Homonym
(D
, Prev_D
);
12799 -- Handle the case where there is an untagged partial view and
12800 -- the full view is tagged: must disallow discriminants with
12801 -- defaults, unless compiling for Ada 2012, which allows a
12802 -- limited tagged type to have defaulted discriminants (see
12803 -- AI05-0214). However, suppress error here if it was already
12804 -- reported on the default expression of the partial view.
12806 if Is_Tagged_Type
(T
)
12807 and then Present
(Expression
(Parent
(D
)))
12808 and then (not Is_Limited_Type
(Current_Scope
)
12809 or else Ada_Version
< Ada_2012
)
12810 and then not Error_Posted
(Expression
(Parent
(D
)))
12812 if Ada_Version
>= Ada_2012
then
12814 ("discriminants of nonlimited tagged type cannot have "
12816 Expression
(New_D
));
12819 ("discriminants of tagged type cannot have defaults",
12820 Expression
(New_D
));
12824 -- Ada 2005 (AI-230): Access discriminant allowed in
12825 -- non-limited record types.
12827 if Ada_Version
< Ada_2005
then
12829 -- This restriction gets applied to the full type here. It
12830 -- has already been applied earlier to the partial view.
12832 Check_Access_Discriminant_Requires_Limited
(Parent
(D
), N
);
12835 Next_Discriminant
(D
);
12840 elsif Present
(Discriminant_Specifications
(N
)) then
12841 Process_Discriminants
(N
, Prev
);
12843 end Check_Or_Process_Discriminants
;
12845 ----------------------
12846 -- Check_Real_Bound --
12847 ----------------------
12849 procedure Check_Real_Bound
(Bound
: Node_Id
) is
12851 if not Is_Real_Type
(Etype
(Bound
)) then
12853 ("bound in real type definition must be of real type", Bound
);
12855 elsif not Is_OK_Static_Expression
(Bound
) then
12856 Flag_Non_Static_Expr
12857 ("non-static expression used for real type bound!", Bound
);
12864 (Bound
, Make_Real_Literal
(Sloc
(Bound
), Ureal_0
));
12866 Resolve
(Bound
, Standard_Float
);
12867 end Check_Real_Bound
;
12869 ------------------------------
12870 -- Complete_Private_Subtype --
12871 ------------------------------
12873 procedure Complete_Private_Subtype
12876 Full_Base
: Entity_Id
;
12877 Related_Nod
: Node_Id
)
12879 Save_Next_Entity
: Entity_Id
;
12880 Save_Homonym
: Entity_Id
;
12883 -- Set semantic attributes for (implicit) private subtype completion.
12884 -- If the full type has no discriminants, then it is a copy of the
12885 -- full view of the base. Otherwise, it is a subtype of the base with
12886 -- a possible discriminant constraint. Save and restore the original
12887 -- Next_Entity field of full to ensure that the calls to Copy_Node do
12888 -- not corrupt the entity chain.
12890 Save_Next_Entity
:= Next_Entity
(Full
);
12891 Save_Homonym
:= Homonym
(Priv
);
12893 if Is_Private_Type
(Full_Base
)
12894 or else Is_Record_Type
(Full_Base
)
12895 or else Is_Concurrent_Type
(Full_Base
)
12897 Copy_Node
(Priv
, Full
);
12899 -- Note that the Etype of the full view is the same as the Etype of
12900 -- the partial view. In this fashion, the subtype has access to the
12901 -- correct view of the parent.
12903 Set_Has_Discriminants
(Full
, Has_Discriminants
(Full_Base
));
12904 Set_Has_Unknown_Discriminants
12905 (Full
, Has_Unknown_Discriminants
(Full_Base
));
12906 Set_First_Entity
(Full
, First_Entity
(Full_Base
));
12907 Set_Last_Entity
(Full
, Last_Entity
(Full_Base
));
12909 -- If the underlying base type is constrained, we know that the
12910 -- full view of the subtype is constrained as well (the converse
12911 -- is not necessarily true).
12913 if Is_Constrained
(Full_Base
) then
12914 Set_Is_Constrained
(Full
);
12918 Copy_Node
(Full_Base
, Full
);
12920 -- The following subtlety with the Etype of the full view needs to be
12921 -- taken into account here. One could think that it must naturally be
12922 -- set to the base type of the full base:
12924 -- Set_Etype (Full, Base_Type (Full_Base));
12926 -- so that the full view becomes a subtype of the full base when the
12927 -- latter is a base type, which must for example happen when the full
12928 -- base is declared as derived type. That's also correct if the full
12929 -- base is declared as an array type, or a floating-point type, or a
12930 -- fixed-point type, or a signed integer type, as these declarations
12931 -- create an implicit base type and a first subtype so the Etype of
12932 -- the full views must be the implicit base type. But that's wrong
12933 -- if the full base is declared as an access type, or an enumeration
12934 -- type, or a modular integer type, as these declarations directly
12935 -- create a base type, i.e. with Etype pointing to itself. Moreover
12936 -- the full base being declared in the private part, i.e. when the
12937 -- views are swapped, the end result is that the Etype of the full
12938 -- base is set to its private view in this case and that we need to
12939 -- propagate this setting to the full view in order for the subtype
12940 -- to be compatible with the base type.
12942 if Is_Base_Type
(Full_Base
)
12943 and then (Is_Derived_Type
(Full_Base
)
12944 or else Ekind
(Full_Base
) in Array_Kind
12945 or else Ekind
(Full_Base
) in Fixed_Point_Kind
12946 or else Ekind
(Full_Base
) in Float_Kind
12947 or else Ekind
(Full_Base
) in Signed_Integer_Kind
)
12949 Set_Etype
(Full
, Full_Base
);
12952 Set_Chars
(Full
, Chars
(Priv
));
12953 Set_Sloc
(Full
, Sloc
(Priv
));
12954 Conditional_Delay
(Full
, Priv
);
12957 Link_Entities
(Full
, Save_Next_Entity
);
12958 Set_Homonym
(Full
, Save_Homonym
);
12959 Set_Associated_Node_For_Itype
(Full
, Related_Nod
);
12961 if Ekind
(Full
) in Incomplete_Or_Private_Kind
then
12962 Reinit_Field_To_Zero
(Full
, F_Private_Dependents
);
12965 -- Set common attributes for all subtypes: kind, convention, etc.
12967 Mutate_Ekind
(Full
, Subtype_Kind
(Ekind
(Full_Base
)));
12968 Set_Is_Not_Self_Hidden
(Full
);
12969 Set_Convention
(Full
, Convention
(Full_Base
));
12970 Set_Is_First_Subtype
(Full
, False);
12971 Set_Scope
(Full
, Scope
(Priv
));
12972 Set_Size_Info
(Full
, Full_Base
);
12973 Copy_RM_Size
(To
=> Full
, From
=> Full_Base
);
12974 Set_Is_Itype
(Full
);
12976 -- A subtype of a private-type-without-discriminants, whose full-view
12977 -- has discriminants with default expressions, is not constrained.
12979 if not Has_Discriminants
(Priv
) then
12980 Set_Is_Constrained
(Full
, Is_Constrained
(Full_Base
));
12982 if Has_Discriminants
(Full_Base
) then
12983 Set_Discriminant_Constraint
12984 (Full
, Discriminant_Constraint
(Full_Base
));
12986 -- The partial view may have been indefinite, the full view
12989 Set_Has_Unknown_Discriminants
12990 (Full
, Has_Unknown_Discriminants
(Full_Base
));
12994 Set_First_Rep_Item
(Full
, First_Rep_Item
(Full_Base
));
12995 Set_Depends_On_Private
(Full
, Has_Private_Component
(Full
));
12997 -- Freeze the private subtype entity if its parent is delayed, and not
12998 -- already frozen. We skip this processing if the type is an anonymous
12999 -- subtype of a record component, or is the corresponding record of a
13000 -- protected type, since these are processed when the enclosing type
13001 -- is frozen. If the parent type is declared in a nested package then
13002 -- the freezing of the private and full views also happens later.
13004 if not Is_Type
(Scope
(Full
)) then
13006 and then In_Same_Source_Unit
(Full
, Full_Base
)
13007 and then Scope
(Full_Base
) /= Scope
(Full
)
13009 Set_Has_Delayed_Freeze
(Full
);
13010 Set_Has_Delayed_Freeze
(Priv
);
13013 Set_Has_Delayed_Freeze
(Full
,
13014 Has_Delayed_Freeze
(Full_Base
)
13015 and then not Is_Frozen
(Full_Base
));
13019 Set_Freeze_Node
(Full
, Empty
);
13020 Set_Is_Frozen
(Full
, False);
13022 if Has_Discriminants
(Full
) then
13023 Set_Stored_Constraint_From_Discriminant_Constraint
(Full
);
13024 Set_Stored_Constraint
(Priv
, Stored_Constraint
(Full
));
13026 if Has_Unknown_Discriminants
(Full
) then
13027 Set_Discriminant_Constraint
(Full
, No_Elist
);
13031 if Ekind
(Full_Base
) = E_Record_Type
13032 and then Has_Discriminants
(Full_Base
)
13033 and then Has_Discriminants
(Priv
) -- might not, if errors
13034 and then not Has_Unknown_Discriminants
(Priv
)
13035 and then not Is_Empty_Elmt_List
(Discriminant_Constraint
(Priv
))
13037 Create_Constrained_Components
13038 (Full
, Related_Nod
, Full_Base
, Discriminant_Constraint
(Priv
));
13040 -- If the full base is itself derived from private, build a congruent
13041 -- subtype of its underlying full view, for use by the back end.
13043 elsif Is_Private_Type
(Full_Base
)
13044 and then Present
(Underlying_Full_View
(Full_Base
))
13047 Underlying_Full_Base
: constant Entity_Id
13048 := Underlying_Full_View
(Full_Base
);
13049 Underlying_Full
: constant Entity_Id
13050 := Make_Defining_Identifier
(Sloc
(Priv
), Chars
(Priv
));
13052 Set_Is_Itype
(Underlying_Full
);
13053 Set_Associated_Node_For_Itype
(Underlying_Full
, Related_Nod
);
13054 Complete_Private_Subtype
13055 (Priv
, Underlying_Full
, Underlying_Full_Base
, Related_Nod
);
13056 Set_Underlying_Full_View
(Full
, Underlying_Full
);
13057 Set_Is_Underlying_Full_View
(Underlying_Full
);
13060 elsif Is_Record_Type
(Full_Base
) then
13062 -- Show Full is simply a renaming of Full_Base
13064 Set_Cloned_Subtype
(Full
, Full_Base
);
13065 Set_Is_Limited_Record
(Full
, Is_Limited_Record
(Full_Base
));
13067 -- Propagate predicates
13069 Propagate_Predicate_Attributes
(Full
, Full_Base
);
13072 -- It is unsafe to share the bounds of a scalar type, because the Itype
13073 -- is elaborated on demand, and if a bound is nonstatic, then different
13074 -- orders of elaboration in different units will lead to different
13075 -- external symbols.
13077 if Is_Scalar_Type
(Full_Base
) then
13078 Set_Scalar_Range
(Full
,
13079 Make_Range
(Sloc
(Related_Nod
),
13081 Duplicate_Subexpr_No_Checks
(Type_Low_Bound
(Full_Base
)),
13083 Duplicate_Subexpr_No_Checks
(Type_High_Bound
(Full_Base
))));
13085 -- This completion inherits the bounds of the full parent, but if
13086 -- the parent is an unconstrained floating point type, so is the
13089 if Is_Floating_Point_Type
(Full_Base
) then
13090 Set_Includes_Infinities
13091 (Scalar_Range
(Full
), Has_Infinities
(Full_Base
));
13095 -- ??? It seems that a lot of fields are missing that should be copied
13096 -- from Full_Base to Full. Here are some that are introduced in a
13097 -- non-disruptive way but a cleanup is necessary.
13099 if Is_Tagged_Type
(Full_Base
) then
13100 Set_Is_Tagged_Type
(Full
);
13101 Set_Is_Limited_Record
(Full
, Is_Limited_Record
(Full_Base
));
13103 Set_Direct_Primitive_Operations
13104 (Full
, Direct_Primitive_Operations
(Full_Base
));
13105 Set_No_Tagged_Streams_Pragma
13106 (Full
, No_Tagged_Streams_Pragma
(Full_Base
));
13108 if Is_Interface
(Full_Base
) then
13109 Set_Is_Interface
(Full
);
13110 Set_Is_Limited_Interface
(Full
, Is_Limited_Interface
(Full_Base
));
13113 -- Inherit class_wide type of full_base in case the partial view was
13114 -- not tagged. Otherwise it has already been created when the private
13115 -- subtype was analyzed.
13117 if No
(Class_Wide_Type
(Full
)) then
13118 Set_Class_Wide_Type
(Full
, Class_Wide_Type
(Full_Base
));
13121 -- If this is a subtype of a protected or task type, constrain its
13122 -- corresponding record, unless this is a subtype without constraints,
13123 -- i.e. a simple renaming as with an actual subtype in an instance.
13125 elsif Is_Concurrent_Type
(Full_Base
) then
13126 if Has_Discriminants
(Full
)
13127 and then Present
(Corresponding_Record_Type
(Full_Base
))
13129 not Is_Empty_Elmt_List
(Discriminant_Constraint
(Full
))
13131 Set_Corresponding_Record_Type
(Full
,
13132 Constrain_Corresponding_Record
13133 (Full
, Corresponding_Record_Type
(Full_Base
), Related_Nod
));
13136 Set_Corresponding_Record_Type
(Full
,
13137 Corresponding_Record_Type
(Full_Base
));
13141 -- Link rep item chain, and also setting of Has_Predicates from private
13142 -- subtype to full subtype, since we will need these on the full subtype
13143 -- to create the predicate function. Note that the full subtype may
13144 -- already have rep items, inherited from the full view of the base
13145 -- type, so we must be sure not to overwrite these entries.
13150 Next_Item
: Node_Id
;
13151 Priv_Item
: Node_Id
;
13154 Item
:= First_Rep_Item
(Full
);
13155 Priv_Item
:= First_Rep_Item
(Priv
);
13157 -- If no existing rep items on full type, we can just link directly
13158 -- to the list of items on the private type, if any exist.. Same if
13159 -- the rep items are only those inherited from the base
13162 or else Nkind
(Item
) /= N_Aspect_Specification
13163 or else Entity
(Item
) = Full_Base
)
13164 and then Present
(First_Rep_Item
(Priv
))
13166 Set_First_Rep_Item
(Full
, Priv_Item
);
13168 -- Otherwise, search to the end of items currently linked to the full
13169 -- subtype and append the private items to the end. However, if Priv
13170 -- and Full already have the same list of rep items, then the append
13171 -- is not done, as that would create a circularity.
13173 -- The partial view may have a predicate and the rep item lists of
13174 -- both views agree when inherited from the same ancestor. In that
13175 -- case, simply propagate the list from one view to the other.
13176 -- A more complex analysis needed here ???
13178 elsif Present
(Priv_Item
)
13179 and then Item
= Next_Rep_Item
(Priv_Item
)
13181 Set_First_Rep_Item
(Full
, Priv_Item
);
13183 elsif Item
/= Priv_Item
then
13186 Next_Item
:= Next_Rep_Item
(Item
);
13187 exit when No
(Next_Item
);
13190 -- If the private view has aspect specifications, the full view
13191 -- inherits them. Since these aspects may already have been
13192 -- attached to the full view during derivation, do not append
13193 -- them if already present.
13195 if Item
= First_Rep_Item
(Priv
) then
13201 -- And link the private type items at the end of the chain
13204 Set_Next_Rep_Item
(Item
, First_Rep_Item
(Priv
));
13209 -- Make sure Has_Predicates is set on full type if it is set on the
13210 -- private type. Note that it may already be set on the full type and
13211 -- if so, we don't want to unset it. Similarly, propagate information
13212 -- about delayed aspects, because the corresponding pragmas must be
13213 -- analyzed when one of the views is frozen. This last step is needed
13214 -- in particular when the full type is a scalar type for which an
13215 -- anonymous base type is constructed.
13217 -- The predicate functions are generated either at the freeze point
13218 -- of the type or at the end of the visible part, and we must avoid
13219 -- generating them twice.
13221 Propagate_Predicate_Attributes
(Full
, Priv
);
13223 if Has_Delayed_Aspects
(Priv
) then
13224 Set_Has_Delayed_Aspects
(Full
);
13226 end Complete_Private_Subtype
;
13228 ----------------------------
13229 -- Constant_Redeclaration --
13230 ----------------------------
13232 procedure Constant_Redeclaration
13237 Prev
: constant Entity_Id
:= Current_Entity_In_Scope
(Id
);
13238 Obj_Def
: constant Node_Id
:= Object_Definition
(N
);
13241 procedure Check_Possible_Deferred_Completion
13242 (Prev_Id
: Entity_Id
;
13243 Curr_Obj_Def
: Node_Id
);
13244 -- Determine whether the two object definitions describe the partial
13245 -- and the full view of a constrained deferred constant. Generate
13246 -- a subtype for the full view and verify that it statically matches
13247 -- the subtype of the partial view.
13249 procedure Check_Recursive_Declaration
(Typ
: Entity_Id
);
13250 -- If deferred constant is an access type initialized with an allocator,
13251 -- check whether there is an illegal recursion in the definition,
13252 -- through a default value of some record subcomponent. This is normally
13253 -- detected when generating init procs, but requires this additional
13254 -- mechanism when expansion is disabled.
13256 ----------------------------------------
13257 -- Check_Possible_Deferred_Completion --
13258 ----------------------------------------
13260 procedure Check_Possible_Deferred_Completion
13261 (Prev_Id
: Entity_Id
;
13262 Curr_Obj_Def
: Node_Id
)
13264 Curr_Typ
: Entity_Id
;
13265 Prev_Typ
: constant Entity_Id
:= Etype
(Prev_Id
);
13266 Anon_Acc
: constant Boolean := Is_Anonymous_Access_Type
(Prev_Typ
);
13267 Mismatch
: Boolean := False;
13271 elsif Nkind
(Curr_Obj_Def
) = N_Subtype_Indication
then
13273 Loc
: constant Source_Ptr
:= Sloc
(N
);
13274 Def_Id
: constant Entity_Id
:= Make_Temporary
(Loc
, 'S');
13275 Decl
: constant Node_Id
:=
13276 Make_Subtype_Declaration
(Loc
,
13277 Defining_Identifier
=> Def_Id
,
13278 Subtype_Indication
=>
13279 Relocate_Node
(Curr_Obj_Def
));
13282 Insert_Before_And_Analyze
(N
, Decl
);
13283 Set_Etype
(Id
, Def_Id
);
13284 Curr_Typ
:= Def_Id
;
13287 Curr_Typ
:= Etype
(Curr_Obj_Def
);
13291 if Nkind
(Curr_Obj_Def
) /= N_Access_Definition
then
13293 elsif Has_Null_Exclusion
(Prev_Typ
)
13294 and then not Null_Exclusion_Present
(Curr_Obj_Def
)
13298 -- ??? Another check needed: mismatch if disagreement
13299 -- between designated types/profiles .
13302 Is_Constrained
(Prev_Typ
)
13303 and then not Subtypes_Statically_Match
(Prev_Typ
, Curr_Typ
);
13307 Error_Msg_Sloc
:= Sloc
(Prev_Id
);
13308 Error_Msg_N
("subtype does not statically match deferred "
13309 & "declaration #", N
);
13311 end Check_Possible_Deferred_Completion
;
13313 ---------------------------------
13314 -- Check_Recursive_Declaration --
13315 ---------------------------------
13317 procedure Check_Recursive_Declaration
(Typ
: Entity_Id
) is
13321 if Is_Record_Type
(Typ
) then
13322 Comp
:= First_Component
(Typ
);
13323 while Present
(Comp
) loop
13324 if Comes_From_Source
(Comp
) then
13325 if Present
(Expression
(Parent
(Comp
)))
13326 and then Is_Entity_Name
(Expression
(Parent
(Comp
)))
13327 and then Entity
(Expression
(Parent
(Comp
))) = Prev
13329 Error_Msg_Sloc
:= Sloc
(Parent
(Comp
));
13331 ("illegal circularity with declaration for & #",
13335 elsif Is_Record_Type
(Etype
(Comp
)) then
13336 Check_Recursive_Declaration
(Etype
(Comp
));
13340 Next_Component
(Comp
);
13343 end Check_Recursive_Declaration
;
13345 -- Start of processing for Constant_Redeclaration
13348 if Nkind
(Parent
(Prev
)) = N_Object_Declaration
then
13349 if Nkind
(Object_Definition
13350 (Parent
(Prev
))) = N_Subtype_Indication
13352 -- Find type of new declaration. The constraints of the two
13353 -- views must match statically, but there is no point in
13354 -- creating an itype for the full view.
13356 if Nkind
(Obj_Def
) = N_Subtype_Indication
then
13357 Find_Type
(Subtype_Mark
(Obj_Def
));
13358 New_T
:= Entity
(Subtype_Mark
(Obj_Def
));
13361 Find_Type
(Obj_Def
);
13362 New_T
:= Entity
(Obj_Def
);
13368 -- The full view may impose a constraint, even if the partial
13369 -- view does not, so construct the subtype.
13371 New_T
:= Find_Type_Of_Object
(Obj_Def
, N
);
13376 -- Current declaration is illegal, diagnosed below in Enter_Name
13382 -- If previous full declaration or a renaming declaration exists, or if
13383 -- a homograph is present, let Enter_Name handle it, either with an
13384 -- error or with the removal of an overridden implicit subprogram.
13385 -- The previous one is a full declaration if it has an expression
13386 -- (which in the case of an aggregate is indicated by the Init flag).
13388 if Ekind
(Prev
) /= E_Constant
13389 or else Nkind
(Parent
(Prev
)) = N_Object_Renaming_Declaration
13390 or else Present
(Expression
(Parent
(Prev
)))
13391 or else Has_Init_Expression
(Parent
(Prev
))
13392 or else Present
(Full_View
(Prev
))
13396 -- Verify that types of both declarations match, or else that both types
13397 -- are anonymous access types whose designated subtypes statically match
13398 -- (as allowed in Ada 2005 by AI-385).
13400 elsif Base_Type
(Etype
(Prev
)) /= Base_Type
(New_T
)
13402 (Ekind
(Etype
(Prev
)) /= E_Anonymous_Access_Type
13403 or else Ekind
(Etype
(New_T
)) /= E_Anonymous_Access_Type
13404 or else Is_Access_Constant
(Etype
(New_T
)) /=
13405 Is_Access_Constant
(Etype
(Prev
))
13406 or else Can_Never_Be_Null
(Etype
(New_T
)) /=
13407 Can_Never_Be_Null
(Etype
(Prev
))
13408 or else Null_Exclusion_Present
(Parent
(Prev
)) /=
13409 Null_Exclusion_Present
(Parent
(Id
))
13410 or else not Subtypes_Statically_Match
13411 (Designated_Type
(Etype
(Prev
)),
13412 Designated_Type
(Etype
(New_T
))))
13414 Error_Msg_Sloc
:= Sloc
(Prev
);
13415 Error_Msg_N
("type does not match declaration#", N
);
13416 Set_Full_View
(Prev
, Id
);
13417 Set_Etype
(Id
, Any_Type
);
13419 -- A deferred constant whose type is an anonymous array is always
13420 -- illegal (unless imported). A detailed error message might be
13421 -- helpful for Ada beginners.
13423 if Nkind
(Object_Definition
(Parent
(Prev
)))
13424 = N_Constrained_Array_Definition
13425 and then Nkind
(Object_Definition
(N
))
13426 = N_Constrained_Array_Definition
13428 Error_Msg_N
("\each anonymous array is a distinct type", N
);
13429 Error_Msg_N
("a deferred constant must have a named type",
13430 Object_Definition
(Parent
(Prev
)));
13434 Null_Exclusion_Present
(Parent
(Prev
))
13435 and then not Null_Exclusion_Present
(N
)
13437 Error_Msg_Sloc
:= Sloc
(Prev
);
13438 Error_Msg_N
("null-exclusion does not match declaration#", N
);
13439 Set_Full_View
(Prev
, Id
);
13440 Set_Etype
(Id
, Any_Type
);
13442 -- If so, process the full constant declaration
13445 -- RM 7.4 (6): If the subtype defined by the subtype_indication in
13446 -- the deferred declaration is constrained, then the subtype defined
13447 -- by the subtype_indication in the full declaration shall match it
13450 Check_Possible_Deferred_Completion
13452 Curr_Obj_Def
=> Obj_Def
);
13454 Set_Full_View
(Prev
, Id
);
13455 Set_Is_Public
(Id
, Is_Public
(Prev
));
13456 Set_Is_Internal
(Id
);
13457 Append_Entity
(Id
, Current_Scope
);
13459 -- Check ALIASED present if present before (RM 7.4(7))
13461 if Is_Aliased
(Prev
)
13462 and then not Aliased_Present
(N
)
13464 Error_Msg_Sloc
:= Sloc
(Prev
);
13465 Error_Msg_N
("ALIASED required (see declaration #)", N
);
13468 -- Check that placement is in private part and that the incomplete
13469 -- declaration appeared in the visible part.
13471 if Ekind
(Current_Scope
) = E_Package
13472 and then not In_Private_Part
(Current_Scope
)
13474 Error_Msg_Sloc
:= Sloc
(Prev
);
13476 ("full constant for declaration # must be in private part", N
);
13478 elsif Ekind
(Current_Scope
) = E_Package
13480 List_Containing
(Parent
(Prev
)) /=
13481 Visible_Declarations
(Package_Specification
(Current_Scope
))
13484 ("deferred constant must be declared in visible part",
13488 if Is_Access_Type
(T
)
13489 and then Nkind
(Expression
(N
)) = N_Allocator
13491 Check_Recursive_Declaration
(Designated_Type
(T
));
13494 -- A deferred constant is a visible entity. If type has invariants,
13495 -- verify that the initial value satisfies them. This is not done in
13496 -- GNATprove mode, as GNATprove handles invariant checks itself.
13498 if Has_Invariants
(T
)
13499 and then Present
(Invariant_Procedure
(T
))
13500 and then not GNATprove_Mode
13503 Make_Invariant_Call
(New_Occurrence_Of
(Prev
, Sloc
(N
))));
13506 end Constant_Redeclaration
;
13508 ----------------------
13509 -- Constrain_Access --
13510 ----------------------
13512 procedure Constrain_Access
13513 (Def_Id
: in out Entity_Id
;
13515 Related_Nod
: Node_Id
)
13517 T
: constant Entity_Id
:= Entity
(Subtype_Mark
(S
));
13518 Desig_Type
: constant Entity_Id
:= Designated_Type
(T
);
13519 Desig_Subtype
: Entity_Id
;
13520 Constraint_OK
: Boolean := True;
13523 if Is_Array_Type
(Desig_Type
) then
13524 Desig_Subtype
:= Create_Itype
(E_Void
, Related_Nod
);
13525 Constrain_Array
(Desig_Subtype
, S
, Related_Nod
, Def_Id
, 'P');
13527 elsif (Is_Record_Type
(Desig_Type
)
13528 or else Is_Incomplete_Or_Private_Type
(Desig_Type
))
13529 and then not Is_Constrained
(Desig_Type
)
13531 -- If this is a constrained access definition for a record
13532 -- component, we leave the type as an unconstrained access,
13533 -- and mark the component so that its actual type is built
13534 -- at a point of use (e.g., an assignment statement). This
13535 -- is handled in Sem_Util.Build_Actual_Subtype_Of_Component.
13537 if Desig_Type
= Current_Scope
13538 and then No
(Def_Id
)
13542 (E_Void
, Related_Nod
, Scope_Id
=> Scope
(Desig_Type
));
13543 Mutate_Ekind
(Desig_Subtype
, E_Record_Subtype
);
13544 Def_Id
:= Entity
(Subtype_Mark
(S
));
13546 -- We indicate that the component has a per-object constraint
13547 -- for treatment at a point of use, even though the constraint
13548 -- may be independent of discriminants of the enclosing type.
13550 if Nkind
(Related_Nod
) = N_Component_Declaration
then
13551 Set_Has_Per_Object_Constraint
13552 (Defining_Identifier
(Related_Nod
));
13555 -- This call added to ensure that the constraint is analyzed
13556 -- (needed for a B test). Note that we still return early from
13557 -- this procedure to avoid recursive processing.
13559 Constrain_Discriminated_Type
13560 (Desig_Subtype
, S
, Related_Nod
, For_Access
=> True);
13564 -- Enforce rule that the constraint is illegal if there is an
13565 -- unconstrained view of the designated type. This means that the
13566 -- partial view (either a private type declaration or a derivation
13567 -- from a private type) has no discriminants. (Defect Report
13568 -- 8652/0008, Technical Corrigendum 1, checked by ACATS B371001).
13570 -- Rule updated for Ada 2005: The private type is said to have
13571 -- a constrained partial view, given that objects of the type
13572 -- can be declared. Furthermore, the rule applies to all access
13573 -- types, unlike the rule concerning default discriminants (see
13576 if (Ekind
(T
) = E_General_Access_Type
or else Ada_Version
>= Ada_2005
)
13577 and then Has_Private_Declaration
(Desig_Type
)
13578 and then In_Open_Scopes
(Scope
(Desig_Type
))
13579 and then Has_Discriminants
(Desig_Type
)
13582 Pack
: constant Node_Id
:=
13583 Unit_Declaration_Node
(Scope
(Desig_Type
));
13588 if Nkind
(Pack
) = N_Package_Declaration
then
13589 Decls
:= Visible_Declarations
(Specification
(Pack
));
13590 Decl
:= First
(Decls
);
13591 while Present
(Decl
) loop
13592 if (Nkind
(Decl
) = N_Private_Type_Declaration
13593 and then Chars
(Defining_Identifier
(Decl
)) =
13594 Chars
(Desig_Type
))
13597 (Nkind
(Decl
) = N_Full_Type_Declaration
13599 Chars
(Defining_Identifier
(Decl
)) =
13601 and then Is_Derived_Type
(Desig_Type
)
13603 Has_Private_Declaration
(Etype
(Desig_Type
)))
13605 if No
(Discriminant_Specifications
(Decl
)) then
13607 ("cannot constrain access type if designated "
13608 & "type has constrained partial view", S
);
13620 Desig_Subtype
:= Create_Itype
(E_Void
, Related_Nod
);
13621 Constrain_Discriminated_Type
(Desig_Subtype
, S
, Related_Nod
,
13622 For_Access
=> True);
13624 elsif Is_Concurrent_Type
(Desig_Type
)
13625 and then not Is_Constrained
(Desig_Type
)
13627 Desig_Subtype
:= Create_Itype
(E_Void
, Related_Nod
);
13628 Constrain_Concurrent
(Desig_Subtype
, S
, Related_Nod
, Desig_Type
, ' ');
13631 Error_Msg_N
("invalid constraint on access type", S
);
13633 -- We simply ignore an invalid constraint
13635 Desig_Subtype
:= Desig_Type
;
13636 Constraint_OK
:= False;
13639 if No
(Def_Id
) then
13640 Def_Id
:= Create_Itype
(E_Access_Subtype
, Related_Nod
);
13642 Mutate_Ekind
(Def_Id
, E_Access_Subtype
);
13645 if Constraint_OK
then
13646 Set_Etype
(Def_Id
, Base_Type
(T
));
13648 if Is_Private_Type
(Desig_Type
) then
13649 Prepare_Private_Subtype_Completion
(Desig_Subtype
, Related_Nod
);
13652 Set_Etype
(Def_Id
, Any_Type
);
13655 Set_Size_Info
(Def_Id
, T
);
13656 Set_Is_Constrained
(Def_Id
, Constraint_OK
);
13657 Set_Directly_Designated_Type
(Def_Id
, Desig_Subtype
);
13658 Set_Depends_On_Private
(Def_Id
, Has_Private_Component
(Def_Id
));
13659 Set_Is_Access_Constant
(Def_Id
, Is_Access_Constant
(T
));
13660 Set_Can_Never_Be_Null
(Def_Id
, Can_Never_Be_Null
(T
));
13662 Conditional_Delay
(Def_Id
, T
);
13664 -- AI-363 : Subtypes of general access types whose designated types have
13665 -- default discriminants are disallowed. In instances, the rule has to
13666 -- be checked against the actual, of which T is the subtype. In a
13667 -- generic body, the rule is checked assuming that the actual type has
13668 -- defaulted discriminants.
13670 if Ada_Version
>= Ada_2005
or else Warn_On_Ada_2005_Compatibility
then
13671 if Ekind
(Base_Type
(T
)) = E_General_Access_Type
13672 and then Has_Defaulted_Discriminants
(Desig_Type
)
13674 if Ada_Version
< Ada_2005
then
13676 ("access subtype of general access type would not " &
13677 "be allowed in Ada 2005?y?", S
);
13680 ("access subtype of general access type not allowed", S
);
13683 Error_Msg_N
("\discriminants have defaults", S
);
13685 elsif Is_Access_Type
(T
)
13686 and then Is_Generic_Type
(Desig_Type
)
13687 and then Has_Discriminants
(Desig_Type
)
13688 and then In_Package_Body
(Current_Scope
)
13690 if Ada_Version
< Ada_2005
then
13692 ("access subtype would not be allowed in generic body "
13693 & "in Ada 2005?y?", S
);
13696 ("access subtype not allowed in generic body", S
);
13700 ("\designated type is a discriminated formal", S
);
13703 end Constrain_Access
;
13705 ---------------------
13706 -- Constrain_Array --
13707 ---------------------
13709 procedure Constrain_Array
13710 (Def_Id
: in out Entity_Id
;
13712 Related_Nod
: Node_Id
;
13713 Related_Id
: Entity_Id
;
13714 Suffix
: Character)
13716 C
: constant Node_Id
:= Constraint
(SI
);
13717 Number_Of_Constraints
: Nat
:= 0;
13720 Constraint_OK
: Boolean := True;
13721 Is_FLB_Array_Subtype
: Boolean := False;
13724 T
:= Entity
(Subtype_Mark
(SI
));
13726 if Is_Access_Type
(T
) then
13727 T
:= Designated_Type
(T
);
13730 T
:= Underlying_Type
(T
);
13732 -- If an index constraint follows a subtype mark in a subtype indication
13733 -- then the type or subtype denoted by the subtype mark must not already
13734 -- impose an index constraint. The subtype mark must denote either an
13735 -- unconstrained array type or an access type whose designated type
13736 -- is such an array type... (RM 3.6.1)
13738 if Is_Constrained
(T
) then
13739 Error_Msg_N
("array type is already constrained", Subtype_Mark
(SI
));
13740 Constraint_OK
:= False;
13743 S
:= First
(Constraints
(C
));
13744 while Present
(S
) loop
13745 Number_Of_Constraints
:= Number_Of_Constraints
+ 1;
13749 -- In either case, the index constraint must provide a discrete
13750 -- range for each index of the array type and the type of each
13751 -- discrete range must be the same as that of the corresponding
13752 -- index. (RM 3.6.1)
13754 if Number_Of_Constraints
/= Number_Dimensions
(T
) then
13755 Error_Msg_NE
("incorrect number of index constraints for }", C
, T
);
13756 Constraint_OK
:= False;
13759 S
:= First
(Constraints
(C
));
13760 Index
:= First_Index
(T
);
13763 -- Apply constraints to each index type
13765 for J
in 1 .. Number_Of_Constraints
loop
13766 Constrain_Index
(Index
, S
, Related_Nod
, Related_Id
, Suffix
, J
);
13768 -- If the subtype of the index has been set to indicate that
13769 -- it has a fixed lower bound, then record that the subtype's
13770 -- entity will need to be marked as being a fixed-lower-bound
13773 if S
= First
(Constraints
(C
)) then
13774 Is_FLB_Array_Subtype
:=
13775 Is_Fixed_Lower_Bound_Index_Subtype
(Etype
(S
));
13777 -- If the parent subtype (or should this be Etype of that?)
13778 -- is an FLB array subtype, we flag an error, because we
13779 -- don't currently allow subtypes of such subtypes to
13780 -- specify a fixed lower bound for any of their indexes,
13781 -- even if the index of the parent subtype is a "range <>"
13784 if Is_FLB_Array_Subtype
13785 and then Is_Fixed_Lower_Bound_Array_Subtype
(T
)
13788 ("index with fixed lower bound not allowed for subtype "
13789 & "of fixed-lower-bound }", S
, T
);
13791 Is_FLB_Array_Subtype
:= False;
13794 elsif Is_FLB_Array_Subtype
13795 and then not Is_Fixed_Lower_Bound_Index_Subtype
(Etype
(S
))
13798 ("constrained index not allowed for fixed-lower-bound "
13799 & "subtype of}", S
, T
);
13801 elsif not Is_FLB_Array_Subtype
13802 and then Is_Fixed_Lower_Bound_Index_Subtype
(Etype
(S
))
13805 ("index with fixed lower bound not allowed for "
13806 & "constrained subtype of}", S
, T
);
13816 if No
(Def_Id
) then
13818 Create_Itype
(E_Array_Subtype
, Related_Nod
, Related_Id
, Suffix
);
13819 Set_Parent
(Def_Id
, Related_Nod
);
13822 Mutate_Ekind
(Def_Id
, E_Array_Subtype
);
13825 Set_Size_Info
(Def_Id
, (T
));
13826 Set_First_Rep_Item
(Def_Id
, First_Rep_Item
(T
));
13827 Set_Etype
(Def_Id
, Base_Type
(T
));
13829 if Constraint_OK
then
13830 Set_First_Index
(Def_Id
, First
(Constraints
(C
)));
13832 Set_First_Index
(Def_Id
, First_Index
(T
));
13835 Set_Is_Constrained
(Def_Id
, not Is_FLB_Array_Subtype
);
13836 Set_Is_Fixed_Lower_Bound_Array_Subtype
13837 (Def_Id
, Is_FLB_Array_Subtype
);
13838 Set_Is_Aliased
(Def_Id
, Is_Aliased
(T
));
13839 Set_Is_Independent
(Def_Id
, Is_Independent
(T
));
13840 Set_Depends_On_Private
(Def_Id
, Has_Private_Component
(Def_Id
));
13842 Set_Is_Private_Composite
(Def_Id
, Is_Private_Composite
(T
));
13843 Set_Is_Limited_Composite
(Def_Id
, Is_Limited_Composite
(T
));
13845 -- A subtype does not inherit the Packed_Array_Impl_Type of is parent.
13846 -- We need to initialize the attribute because if Def_Id is previously
13847 -- analyzed through a limited_with clause, it will have the attributes
13848 -- of an incomplete type, one of which is an Elist that overlaps the
13849 -- Packed_Array_Impl_Type field.
13851 Set_Packed_Array_Impl_Type
(Def_Id
, Empty
);
13853 -- Build a freeze node if parent still needs one. Also make sure that
13854 -- the Depends_On_Private status is set because the subtype will need
13855 -- reprocessing at the time the base type does, and also we must set a
13856 -- conditional delay.
13858 Set_Depends_On_Private
(Def_Id
, Depends_On_Private
(T
));
13859 Conditional_Delay
(Def_Id
, T
);
13860 end Constrain_Array
;
13862 ------------------------------
13863 -- Constrain_Component_Type --
13864 ------------------------------
13866 function Constrain_Component_Type
13868 Constrained_Typ
: Entity_Id
;
13869 Related_Node
: Node_Id
;
13871 Constraints
: Elist_Id
) return Entity_Id
13873 Loc
: constant Source_Ptr
:= Sloc
(Constrained_Typ
);
13874 Compon_Type
: constant Entity_Id
:= Etype
(Comp
);
13876 function Build_Constrained_Array_Type
13877 (Old_Type
: Entity_Id
) return Entity_Id
;
13878 -- If Old_Type is an array type, one of whose indexes is constrained
13879 -- by a discriminant, build an Itype whose constraint replaces the
13880 -- discriminant with its value in the constraint.
13882 function Build_Constrained_Discriminated_Type
13883 (Old_Type
: Entity_Id
) return Entity_Id
;
13884 -- Ditto for record components. Handle the case where the constraint
13885 -- is a conversion of the discriminant value, introduced during
13888 function Build_Constrained_Access_Type
13889 (Old_Type
: Entity_Id
) return Entity_Id
;
13890 -- Ditto for access types. Makes use of previous two functions, to
13891 -- constrain designated type.
13893 function Is_Discriminant
(Expr
: Node_Id
) return Boolean;
13894 -- Returns True if Expr is a discriminant
13896 function Get_Discr_Value
(Discr_Expr
: Node_Id
) return Node_Id
;
13897 -- Find the value of a discriminant named by Discr_Expr in Constraints
13899 -----------------------------------
13900 -- Build_Constrained_Access_Type --
13901 -----------------------------------
13903 function Build_Constrained_Access_Type
13904 (Old_Type
: Entity_Id
) return Entity_Id
13906 Desig_Type
: constant Entity_Id
:= Designated_Type
(Old_Type
);
13908 Desig_Subtype
: Entity_Id
;
13912 -- If the original access type was not embedded in the enclosing
13913 -- type definition, there is no need to produce a new access
13914 -- subtype. In fact every access type with an explicit constraint
13915 -- generates an itype whose scope is the enclosing record.
13917 if not Is_Type
(Scope
(Old_Type
)) then
13920 elsif Is_Array_Type
(Desig_Type
) then
13921 Desig_Subtype
:= Build_Constrained_Array_Type
(Desig_Type
);
13923 elsif Has_Discriminants
(Desig_Type
) then
13925 -- This may be an access type to an enclosing record type for
13926 -- which we are constructing the constrained components. Return
13927 -- the enclosing record subtype. This is not always correct,
13928 -- but avoids infinite recursion. ???
13930 Desig_Subtype
:= Any_Type
;
13932 for J
in reverse 0 .. Scope_Stack
.Last
loop
13933 Scop
:= Scope_Stack
.Table
(J
).Entity
;
13936 and then Base_Type
(Scop
) = Base_Type
(Desig_Type
)
13938 Desig_Subtype
:= Scop
;
13941 exit when not Is_Type
(Scop
);
13944 if Desig_Subtype
= Any_Type
then
13946 Build_Constrained_Discriminated_Type
(Desig_Type
);
13953 if Desig_Subtype
/= Desig_Type
then
13955 -- The Related_Node better be here or else we won't be able
13956 -- to attach new itypes to a node in the tree.
13958 pragma Assert
(Present
(Related_Node
));
13960 Itype
:= Create_Itype
(E_Access_Subtype
, Related_Node
);
13962 Set_Etype
(Itype
, Base_Type
(Old_Type
));
13963 Set_Size_Info
(Itype
, (Old_Type
));
13964 Set_Directly_Designated_Type
(Itype
, Desig_Subtype
);
13965 Set_Depends_On_Private
(Itype
, Has_Private_Component
13967 Set_Is_Access_Constant
(Itype
, Is_Access_Constant
13970 -- The new itype needs freezing when it depends on a not frozen
13971 -- type and the enclosing subtype needs freezing.
13973 if Has_Delayed_Freeze
(Constrained_Typ
)
13974 and then not Is_Frozen
(Constrained_Typ
)
13976 Conditional_Delay
(Itype
, Base_Type
(Old_Type
));
13984 end Build_Constrained_Access_Type
;
13986 ----------------------------------
13987 -- Build_Constrained_Array_Type --
13988 ----------------------------------
13990 function Build_Constrained_Array_Type
13991 (Old_Type
: Entity_Id
) return Entity_Id
13995 Old_Index
: Node_Id
;
13996 Range_Node
: Node_Id
;
13997 Constr_List
: List_Id
;
13999 Need_To_Create_Itype
: Boolean := False;
14002 Old_Index
:= First_Index
(Old_Type
);
14003 while Present
(Old_Index
) loop
14004 Get_Index_Bounds
(Old_Index
, Lo_Expr
, Hi_Expr
);
14006 if Is_Discriminant
(Lo_Expr
)
14008 Is_Discriminant
(Hi_Expr
)
14010 Need_To_Create_Itype
:= True;
14014 Next_Index
(Old_Index
);
14017 if Need_To_Create_Itype
then
14018 Constr_List
:= New_List
;
14020 Old_Index
:= First_Index
(Old_Type
);
14021 while Present
(Old_Index
) loop
14022 Get_Index_Bounds
(Old_Index
, Lo_Expr
, Hi_Expr
);
14024 if Is_Discriminant
(Lo_Expr
) then
14025 Lo_Expr
:= Get_Discr_Value
(Lo_Expr
);
14028 if Is_Discriminant
(Hi_Expr
) then
14029 Hi_Expr
:= Get_Discr_Value
(Hi_Expr
);
14034 (Loc
, New_Copy_Tree
(Lo_Expr
), New_Copy_Tree
(Hi_Expr
));
14036 Append
(Range_Node
, To
=> Constr_List
);
14038 Next_Index
(Old_Index
);
14041 return Build_Subtype
(Related_Node
, Loc
, Old_Type
, Constr_List
);
14046 end Build_Constrained_Array_Type
;
14048 ------------------------------------------
14049 -- Build_Constrained_Discriminated_Type --
14050 ------------------------------------------
14052 function Build_Constrained_Discriminated_Type
14053 (Old_Type
: Entity_Id
) return Entity_Id
14056 Constr_List
: List_Id
;
14057 Old_Constraint
: Elmt_Id
;
14059 Need_To_Create_Itype
: Boolean := False;
14062 Old_Constraint
:= First_Elmt
(Discriminant_Constraint
(Old_Type
));
14063 while Present
(Old_Constraint
) loop
14064 Expr
:= Node
(Old_Constraint
);
14066 if Is_Discriminant
(Expr
) then
14067 Need_To_Create_Itype
:= True;
14070 -- After expansion of discriminated task types, the value
14071 -- of the discriminant may be converted to a run-time type
14072 -- for restricted run-times. Propagate the value of the
14073 -- discriminant as well, so that e.g. the secondary stack
14074 -- component has a static constraint. Necessary for LLVM.
14076 elsif Nkind
(Expr
) = N_Type_Conversion
14077 and then Is_Discriminant
(Expression
(Expr
))
14079 Need_To_Create_Itype
:= True;
14083 Next_Elmt
(Old_Constraint
);
14086 if Need_To_Create_Itype
then
14087 Constr_List
:= New_List
;
14089 Old_Constraint
:= First_Elmt
(Discriminant_Constraint
(Old_Type
));
14090 while Present
(Old_Constraint
) loop
14091 Expr
:= Node
(Old_Constraint
);
14093 if Is_Discriminant
(Expr
) then
14094 Expr
:= Get_Discr_Value
(Expr
);
14096 elsif Nkind
(Expr
) = N_Type_Conversion
14097 and then Is_Discriminant
(Expression
(Expr
))
14099 Expr
:= New_Copy_Tree
(Expr
);
14100 Set_Expression
(Expr
, Get_Discr_Value
(Expression
(Expr
)));
14103 Append
(New_Copy_Tree
(Expr
), To
=> Constr_List
);
14105 Next_Elmt
(Old_Constraint
);
14108 return Build_Subtype
(Related_Node
, Loc
, Old_Type
, Constr_List
);
14113 end Build_Constrained_Discriminated_Type
;
14115 ---------------------
14116 -- Get_Discr_Value --
14117 ---------------------
14119 function Get_Discr_Value
(Discr_Expr
: Node_Id
) return Node_Id
is
14120 Discr_Id
: constant Entity_Id
:= Entity
(Discr_Expr
);
14121 -- Entity of a discriminant that appear as a standalone expression in
14122 -- the constraint of a component.
14128 -- The discriminant may be declared for the type, in which case we
14129 -- find it by iterating over the list of discriminants. If the
14130 -- discriminant is inherited from a parent type, it appears as the
14131 -- corresponding discriminant of the current type. This will be the
14132 -- case when constraining an inherited component whose constraint is
14133 -- given by a discriminant of the parent.
14135 D
:= First_Discriminant
(Typ
);
14136 E
:= First_Elmt
(Constraints
);
14138 while Present
(D
) loop
14140 or else D
= CR_Discriminant
(Discr_Id
)
14141 or else Corresponding_Discriminant
(D
) = Discr_Id
14143 return New_Copy_Tree
(Node
(E
));
14146 Next_Discriminant
(D
);
14150 -- The Corresponding_Discriminant mechanism is incomplete, because
14151 -- the correspondence between new and old discriminants is not one
14152 -- to one: one new discriminant can constrain several old ones. In
14153 -- that case, scan sequentially the stored_constraint, the list of
14154 -- discriminants of the parents, and the constraints.
14156 -- Previous code checked for the present of the Stored_Constraint
14157 -- list for the derived type, but did not use it at all. Should it
14158 -- be present when the component is a discriminated task type?
14160 if Is_Derived_Type
(Typ
)
14161 and then Scope
(Discr_Id
) = Etype
(Typ
)
14163 D
:= First_Discriminant
(Etype
(Typ
));
14164 E
:= First_Elmt
(Constraints
);
14165 while Present
(D
) loop
14166 if D
= Discr_Id
then
14167 return New_Copy_Tree
(Node
(E
));
14170 Next_Discriminant
(D
);
14175 -- Something is wrong if we did not find the value
14177 raise Program_Error
;
14178 end Get_Discr_Value
;
14180 ---------------------
14181 -- Is_Discriminant --
14182 ---------------------
14184 function Is_Discriminant
(Expr
: Node_Id
) return Boolean is
14185 Discrim_Scope
: Entity_Id
;
14188 if Denotes_Discriminant
(Expr
) then
14189 Discrim_Scope
:= Scope
(Entity
(Expr
));
14191 -- Either we have a reference to one of Typ's discriminants,
14193 pragma Assert
(Discrim_Scope
= Typ
14195 -- or to the discriminants of the parent type, in the case
14196 -- of a derivation of a tagged type with variants.
14198 or else Discrim_Scope
= Etype
(Typ
)
14199 or else Full_View
(Discrim_Scope
) = Etype
(Typ
)
14201 -- or same as above for the case where the discriminants
14202 -- were declared in Typ's private view.
14204 or else (Is_Private_Type
(Discrim_Scope
)
14205 and then Chars
(Discrim_Scope
) = Chars
(Typ
))
14207 -- or else we are deriving from the full view and the
14208 -- discriminant is declared in the private entity.
14210 or else (Is_Private_Type
(Typ
)
14211 and then Chars
(Discrim_Scope
) = Chars
(Typ
))
14213 -- Or we are constrained the corresponding record of a
14214 -- synchronized type that completes a private declaration.
14216 or else (Is_Concurrent_Record_Type
(Typ
)
14218 Corresponding_Concurrent_Type
(Typ
) = Discrim_Scope
)
14220 -- or we have a class-wide type, in which case make sure the
14221 -- discriminant found belongs to the root type.
14223 or else (Is_Class_Wide_Type
(Typ
)
14224 and then Etype
(Typ
) = Discrim_Scope
));
14229 -- In all other cases we have something wrong
14232 end Is_Discriminant
;
14234 -- Start of processing for Constrain_Component_Type
14237 if Nkind
(Parent
(Comp
)) = N_Component_Declaration
14238 and then Comes_From_Source
(Parent
(Comp
))
14239 and then Comes_From_Source
14240 (Subtype_Indication
(Component_Definition
(Parent
(Comp
))))
14243 (Subtype_Indication
(Component_Definition
(Parent
(Comp
))))
14245 return Compon_Type
;
14247 elsif Is_Array_Type
(Compon_Type
) then
14248 return Build_Constrained_Array_Type
(Compon_Type
);
14250 elsif Has_Discriminants
(Compon_Type
) then
14251 return Build_Constrained_Discriminated_Type
(Compon_Type
);
14253 elsif Is_Access_Type
(Compon_Type
) then
14254 return Build_Constrained_Access_Type
(Compon_Type
);
14257 return Compon_Type
;
14259 end Constrain_Component_Type
;
14261 --------------------------
14262 -- Constrain_Concurrent --
14263 --------------------------
14265 -- For concurrent types, the associated record value type carries the same
14266 -- discriminants, so when we constrain a concurrent type, we must constrain
14267 -- the corresponding record type as well.
14269 procedure Constrain_Concurrent
14270 (Def_Id
: in out Entity_Id
;
14272 Related_Nod
: Node_Id
;
14273 Related_Id
: Entity_Id
;
14274 Suffix
: Character)
14276 -- Retrieve Base_Type to ensure getting to the concurrent type in the
14277 -- case of a private subtype (needed when only doing semantic analysis).
14279 T_Ent
: Entity_Id
:= Base_Type
(Entity
(Subtype_Mark
(SI
)));
14283 if Is_Access_Type
(T_Ent
) then
14284 T_Ent
:= Designated_Type
(T_Ent
);
14287 T_Val
:= Corresponding_Record_Type
(T_Ent
);
14289 if Present
(T_Val
) then
14291 if No
(Def_Id
) then
14292 Def_Id
:= Create_Itype
(E_Void
, Related_Nod
, Related_Id
, Suffix
);
14294 -- Elaborate itype now, as it may be used in a subsequent
14295 -- synchronized operation in another scope.
14297 if Nkind
(Related_Nod
) = N_Full_Type_Declaration
then
14298 Build_Itype_Reference
(Def_Id
, Related_Nod
);
14302 Constrain_Discriminated_Type
(Def_Id
, SI
, Related_Nod
);
14303 Set_First_Private_Entity
(Def_Id
, First_Private_Entity
(T_Ent
));
14305 Set_Depends_On_Private
(Def_Id
, Has_Private_Component
(Def_Id
));
14306 Set_Corresponding_Record_Type
(Def_Id
,
14307 Constrain_Corresponding_Record
(Def_Id
, T_Val
, Related_Nod
));
14310 -- If there is no associated record, expansion is disabled and this
14311 -- is a generic context. Create a subtype in any case, so that
14312 -- semantic analysis can proceed.
14314 if No
(Def_Id
) then
14315 Def_Id
:= Create_Itype
(E_Void
, Related_Nod
, Related_Id
, Suffix
);
14318 Constrain_Discriminated_Type
(Def_Id
, SI
, Related_Nod
);
14320 end Constrain_Concurrent
;
14322 ------------------------------------
14323 -- Constrain_Corresponding_Record --
14324 ------------------------------------
14326 function Constrain_Corresponding_Record
14327 (Prot_Subt
: Entity_Id
;
14328 Corr_Rec
: Entity_Id
;
14329 Related_Nod
: Node_Id
) return Entity_Id
14331 T_Sub
: constant Entity_Id
:=
14333 (Ekind
=> E_Record_Subtype
,
14334 Related_Nod
=> Related_Nod
,
14335 Related_Id
=> Corr_Rec
,
14337 Suffix_Index
=> -1);
14340 Set_Etype
(T_Sub
, Corr_Rec
);
14341 Set_Has_Discriminants
(T_Sub
, Has_Discriminants
(Prot_Subt
));
14342 Set_Is_Tagged_Type
(T_Sub
, Is_Tagged_Type
(Corr_Rec
));
14343 Set_Is_Constrained
(T_Sub
, True);
14344 Set_First_Entity
(T_Sub
, First_Entity
(Corr_Rec
));
14345 Set_Last_Entity
(T_Sub
, Last_Entity
(Corr_Rec
));
14347 if Has_Discriminants
(Prot_Subt
) then -- False only if errors.
14348 Set_Discriminant_Constraint
14349 (T_Sub
, Discriminant_Constraint
(Prot_Subt
));
14350 Set_Stored_Constraint_From_Discriminant_Constraint
(T_Sub
);
14351 Create_Constrained_Components
14352 (T_Sub
, Related_Nod
, Corr_Rec
, Discriminant_Constraint
(T_Sub
));
14355 Set_Depends_On_Private
(T_Sub
, Has_Private_Component
(T_Sub
));
14357 if Ekind
(Scope
(Prot_Subt
)) /= E_Record_Type
then
14358 Conditional_Delay
(T_Sub
, Corr_Rec
);
14361 -- This is a component subtype: it will be frozen in the context of
14362 -- the enclosing record's init_proc, so that discriminant references
14363 -- are resolved to discriminals. (Note: we used to skip freezing
14364 -- altogether in that case, which caused errors downstream for
14365 -- components of a bit packed array type).
14367 Set_Has_Delayed_Freeze
(T_Sub
);
14371 end Constrain_Corresponding_Record
;
14373 -----------------------
14374 -- Constrain_Decimal --
14375 -----------------------
14377 procedure Constrain_Decimal
(Def_Id
: Entity_Id
; S
: Node_Id
) is
14378 T
: constant Entity_Id
:= Entity
(Subtype_Mark
(S
));
14379 C
: constant Node_Id
:= Constraint
(S
);
14380 Loc
: constant Source_Ptr
:= Sloc
(C
);
14381 Range_Expr
: Node_Id
;
14382 Digits_Expr
: Node_Id
;
14387 Mutate_Ekind
(Def_Id
, E_Decimal_Fixed_Point_Subtype
);
14389 if Nkind
(C
) = N_Range_Constraint
then
14390 Range_Expr
:= Range_Expression
(C
);
14391 Digits_Val
:= Digits_Value
(T
);
14394 pragma Assert
(Nkind
(C
) = N_Digits_Constraint
);
14396 Digits_Expr
:= Digits_Expression
(C
);
14397 Analyze_And_Resolve
(Digits_Expr
, Any_Integer
);
14399 Check_Digits_Expression
(Digits_Expr
);
14400 Digits_Val
:= Expr_Value
(Digits_Expr
);
14402 if Digits_Val
> Digits_Value
(T
) then
14404 ("digits expression is incompatible with subtype", C
);
14405 Digits_Val
:= Digits_Value
(T
);
14408 if Present
(Range_Constraint
(C
)) then
14409 Range_Expr
:= Range_Expression
(Range_Constraint
(C
));
14411 Range_Expr
:= Empty
;
14415 Set_Etype
(Def_Id
, Base_Type
(T
));
14416 Set_Size_Info
(Def_Id
, (T
));
14417 Set_First_Rep_Item
(Def_Id
, First_Rep_Item
(T
));
14418 Set_Delta_Value
(Def_Id
, Delta_Value
(T
));
14419 Set_Scale_Value
(Def_Id
, Scale_Value
(T
));
14420 Set_Small_Value
(Def_Id
, Small_Value
(T
));
14421 Set_Machine_Radix_10
(Def_Id
, Machine_Radix_10
(T
));
14422 Set_Digits_Value
(Def_Id
, Digits_Val
);
14424 -- Manufacture range from given digits value if no range present
14426 if No
(Range_Expr
) then
14427 Bound_Val
:= (Ureal_10
** Digits_Val
- Ureal_1
) * Small_Value
(T
);
14431 Convert_To
(T
, Make_Real_Literal
(Loc
, (-Bound_Val
))),
14433 Convert_To
(T
, Make_Real_Literal
(Loc
, Bound_Val
)));
14436 Set_Scalar_Range_For_Subtype
(Def_Id
, Range_Expr
, T
);
14437 Set_Discrete_RM_Size
(Def_Id
);
14439 -- Unconditionally delay the freeze, since we cannot set size
14440 -- information in all cases correctly until the freeze point.
14442 Set_Has_Delayed_Freeze
(Def_Id
);
14443 end Constrain_Decimal
;
14445 ----------------------------------
14446 -- Constrain_Discriminated_Type --
14447 ----------------------------------
14449 procedure Constrain_Discriminated_Type
14450 (Def_Id
: Entity_Id
;
14452 Related_Nod
: Node_Id
;
14453 For_Access
: Boolean := False)
14455 E
: Entity_Id
:= Entity
(Subtype_Mark
(S
));
14458 procedure Fixup_Bad_Constraint
;
14459 -- Called after finding a bad constraint, and after having posted an
14460 -- appropriate error message. The goal is to leave type Def_Id in as
14461 -- reasonable state as possible.
14463 --------------------------
14464 -- Fixup_Bad_Constraint --
14465 --------------------------
14467 procedure Fixup_Bad_Constraint
is
14469 -- Set a reasonable Ekind for the entity, including incomplete types.
14471 Mutate_Ekind
(Def_Id
, Subtype_Kind
(Ekind
(T
)));
14473 -- Set Etype to the known type, to reduce chances of cascaded errors
14475 Set_Etype
(Def_Id
, E
);
14476 Set_Error_Posted
(Def_Id
);
14477 end Fixup_Bad_Constraint
;
14482 Constr
: Elist_Id
:= New_Elmt_List
;
14484 -- Start of processing for Constrain_Discriminated_Type
14487 C
:= Constraint
(S
);
14489 -- A discriminant constraint is only allowed in a subtype indication,
14490 -- after a subtype mark. This subtype mark must denote either a type
14491 -- with discriminants, or an access type whose designated type is a
14492 -- type with discriminants. A discriminant constraint specifies the
14493 -- values of these discriminants (RM 3.7.2(5)).
14495 T
:= Base_Type
(Entity
(Subtype_Mark
(S
)));
14497 if Is_Access_Type
(T
) then
14498 T
:= Designated_Type
(T
);
14501 -- In an instance it may be necessary to retrieve the full view of a
14502 -- type with unknown discriminants, or a full view with defaulted
14503 -- discriminants. In other contexts the constraint is illegal.
14506 and then Is_Private_Type
(T
)
14507 and then Present
(Full_View
(T
))
14509 (Has_Unknown_Discriminants
(T
)
14511 (not Has_Discriminants
(T
)
14512 and then Has_Defaulted_Discriminants
(Full_View
(T
))))
14514 T
:= Full_View
(T
);
14515 E
:= Full_View
(E
);
14518 -- Ada 2005 (AI-412): Constrained incomplete subtypes are illegal. Avoid
14519 -- generating an error for access-to-incomplete subtypes.
14521 if Ada_Version
>= Ada_2005
14522 and then Ekind
(T
) = E_Incomplete_Type
14523 and then Nkind
(Parent
(S
)) = N_Subtype_Declaration
14524 and then not Is_Itype
(Def_Id
)
14526 -- A little sanity check: emit an error message if the type has
14527 -- discriminants to begin with. Type T may be a regular incomplete
14528 -- type or imported via a limited with clause.
14530 if Has_Discriminants
(T
)
14531 or else (From_Limited_With
(T
)
14532 and then Present
(Non_Limited_View
(T
))
14533 and then Nkind
(Parent
(Non_Limited_View
(T
))) =
14534 N_Full_Type_Declaration
14535 and then Present
(Discriminant_Specifications
14536 (Parent
(Non_Limited_View
(T
)))))
14539 ("(Ada 2005) incomplete subtype may not be constrained", C
);
14541 Error_Msg_N
("invalid constraint: type has no discriminant", C
);
14544 Fixup_Bad_Constraint
;
14547 -- Check that the type has visible discriminants. The type may be
14548 -- a private type with unknown discriminants whose full view has
14549 -- discriminants which are invisible.
14551 elsif not Has_Discriminants
(T
)
14553 (Has_Unknown_Discriminants
(T
)
14554 and then Is_Private_Type
(T
))
14556 Error_Msg_N
("invalid constraint: type has no discriminant", C
);
14557 Fixup_Bad_Constraint
;
14560 elsif Is_Constrained
(E
)
14561 or else (Ekind
(E
) = E_Class_Wide_Subtype
14562 and then Present
(Discriminant_Constraint
(E
)))
14564 Error_Msg_N
("type is already constrained", Subtype_Mark
(S
));
14565 Fixup_Bad_Constraint
;
14569 -- T may be an unconstrained subtype (e.g. a generic actual). Constraint
14570 -- applies to the base type.
14572 T
:= Base_Type
(T
);
14574 Constr
:= Build_Discriminant_Constraints
(T
, S
);
14576 -- If the list returned was empty we had an error in building the
14577 -- discriminant constraint. We have also already signalled an error
14578 -- in the incomplete type case
14580 if Is_Empty_Elmt_List
(Constr
) then
14581 Fixup_Bad_Constraint
;
14585 Build_Discriminated_Subtype
(T
, Def_Id
, Constr
, Related_Nod
, For_Access
);
14586 end Constrain_Discriminated_Type
;
14588 ---------------------------
14589 -- Constrain_Enumeration --
14590 ---------------------------
14592 procedure Constrain_Enumeration
(Def_Id
: Entity_Id
; S
: Node_Id
) is
14593 T
: constant Entity_Id
:= Entity
(Subtype_Mark
(S
));
14594 C
: constant Node_Id
:= Constraint
(S
);
14597 Mutate_Ekind
(Def_Id
, E_Enumeration_Subtype
);
14599 Set_First_Literal
(Def_Id
, First_Literal
(Base_Type
(T
)));
14600 Set_Etype
(Def_Id
, Base_Type
(T
));
14601 Set_Size_Info
(Def_Id
, (T
));
14602 Set_Is_Character_Type
(Def_Id
, Is_Character_Type
(T
));
14603 Set_Scalar_Range_For_Subtype
(Def_Id
, Range_Expression
(C
), T
);
14605 -- Inherit the chain of representation items instead of replacing it
14606 -- because Build_Derived_Enumeration_Type rewrites the declaration of
14607 -- the derived type as a subtype declaration and the former needs to
14608 -- preserve existing representation items (see Build_Derived_Type).
14610 Inherit_Rep_Item_Chain
(Def_Id
, T
);
14612 Set_Discrete_RM_Size
(Def_Id
);
14613 end Constrain_Enumeration
;
14615 ----------------------
14616 -- Constrain_Float --
14617 ----------------------
14619 procedure Constrain_Float
(Def_Id
: Entity_Id
; S
: Node_Id
) is
14620 T
: constant Entity_Id
:= Entity
(Subtype_Mark
(S
));
14626 Mutate_Ekind
(Def_Id
, E_Floating_Point_Subtype
);
14628 Set_Etype
(Def_Id
, Base_Type
(T
));
14629 Set_Size_Info
(Def_Id
, (T
));
14630 Set_First_Rep_Item
(Def_Id
, First_Rep_Item
(T
));
14632 -- Process the constraint
14634 C
:= Constraint
(S
);
14636 -- Digits constraint present
14638 if Nkind
(C
) = N_Digits_Constraint
then
14639 Check_Restriction
(No_Obsolescent_Features
, C
);
14641 if Warn_On_Obsolescent_Feature
then
14643 ("subtype digits constraint is an " &
14644 "obsolescent feature (RM J.3(8))?j?", C
);
14647 D
:= Digits_Expression
(C
);
14648 Analyze_And_Resolve
(D
, Any_Integer
);
14649 Check_Digits_Expression
(D
);
14650 Set_Digits_Value
(Def_Id
, Expr_Value
(D
));
14652 -- Check that digits value is in range. Obviously we can do this
14653 -- at compile time, but it is strictly a runtime check, and of
14654 -- course there is an ACVC test that checks this.
14656 if Digits_Value
(Def_Id
) > Digits_Value
(T
) then
14657 Error_Msg_Uint_1
:= Digits_Value
(T
);
14658 Error_Msg_N
("??digits value is too large, maximum is ^", D
);
14660 Make_Raise_Constraint_Error
(Sloc
(D
),
14661 Reason
=> CE_Range_Check_Failed
);
14662 Insert_Action
(Declaration_Node
(Def_Id
), Rais
);
14665 C
:= Range_Constraint
(C
);
14667 -- No digits constraint present
14670 Set_Digits_Value
(Def_Id
, Digits_Value
(T
));
14673 -- Range constraint present
14675 if Nkind
(C
) = N_Range_Constraint
then
14676 Set_Scalar_Range_For_Subtype
(Def_Id
, Range_Expression
(C
), T
);
14678 -- No range constraint present
14681 pragma Assert
(No
(C
));
14682 Set_Scalar_Range
(Def_Id
, Scalar_Range
(T
));
14685 Set_Is_Constrained
(Def_Id
);
14686 end Constrain_Float
;
14688 ---------------------
14689 -- Constrain_Index --
14690 ---------------------
14692 procedure Constrain_Index
14695 Related_Nod
: Node_Id
;
14696 Related_Id
: Entity_Id
;
14697 Suffix
: Character;
14698 Suffix_Index
: Pos
)
14700 Def_Id
: Entity_Id
;
14701 R
: Node_Id
:= Empty
;
14702 T
: constant Entity_Id
:= Etype
(Index
);
14703 Is_FLB_Index
: Boolean := False;
14707 Create_Itype
(E_Void
, Related_Nod
, Related_Id
, Suffix
, Suffix_Index
);
14708 Set_Etype
(Def_Id
, Base_Type
(T
));
14710 if Nkind
(S
) = N_Range
14712 (Nkind
(S
) = N_Attribute_Reference
14713 and then Attribute_Name
(S
) = Name_Range
)
14715 -- A Range attribute will be transformed into N_Range by Resolve
14717 -- If a range has an Empty upper bound, then remember that for later
14718 -- setting of the index subtype's Is_Fixed_Lower_Bound_Index_Subtype
14719 -- flag, and also set the upper bound of the range to the index
14720 -- subtype's upper bound rather than leaving it Empty. In truth,
14721 -- that upper bound corresponds to a box ("<>"), but it's convenient
14722 -- to set it to the upper bound to avoid needing to add special tests
14723 -- in various places for an Empty upper bound, and in any case it
14724 -- accurately characterizes the index's range of values.
14726 if Nkind
(S
) = N_Range
and then No
(High_Bound
(S
)) then
14727 Is_FLB_Index
:= True;
14728 Set_High_Bound
(S
, Type_High_Bound
(T
));
14733 Process_Range_Expr_In_Decl
(R
, T
);
14735 if not Error_Posted
(S
)
14737 (Nkind
(S
) /= N_Range
14738 or else not Covers
(T
, (Etype
(Low_Bound
(S
))))
14739 or else not Covers
(T
, (Etype
(High_Bound
(S
)))))
14741 if Base_Type
(T
) /= Any_Type
14742 and then Etype
(Low_Bound
(S
)) /= Any_Type
14743 and then Etype
(High_Bound
(S
)) /= Any_Type
14745 Error_Msg_N
("range expected", S
);
14749 elsif Nkind
(S
) = N_Subtype_Indication
then
14751 -- The parser has verified that this is a discrete indication
14753 Resolve_Discrete_Subtype_Indication
(S
, T
);
14754 Bad_Predicated_Subtype_Use
14755 ("subtype& has predicate, not allowed in index constraint",
14756 S
, Entity
(Subtype_Mark
(S
)));
14758 R
:= Range_Expression
(Constraint
(S
));
14760 -- Capture values of bounds and generate temporaries for them if
14761 -- needed, since checks may cause duplication of the expressions
14762 -- which must not be reevaluated.
14764 -- The forced evaluation removes side effects from expressions, which
14765 -- should occur also in GNATprove mode. Otherwise, we end up with
14766 -- unexpected insertions of actions at places where this is not
14767 -- supposed to occur, e.g. on default parameters of a call.
14769 if Expander_Active
or GNATprove_Mode
then
14771 (Low_Bound
(R
), Related_Id
=> Def_Id
, Is_Low_Bound
=> True);
14773 (High_Bound
(R
), Related_Id
=> Def_Id
, Is_High_Bound
=> True);
14776 elsif Nkind
(S
) = N_Discriminant_Association
then
14778 -- Syntactically valid in subtype indication
14780 Error_Msg_N
("invalid index constraint", S
);
14781 Rewrite
(S
, New_Occurrence_Of
(T
, Sloc
(S
)));
14784 -- Subtype_Mark case, no anonymous subtypes to construct
14789 if Is_Entity_Name
(S
) then
14790 if not Is_Type
(Entity
(S
)) then
14791 Error_Msg_N
("expect subtype mark for index constraint", S
);
14793 elsif Base_Type
(Entity
(S
)) /= Base_Type
(T
) then
14794 Wrong_Type
(S
, Base_Type
(T
));
14796 -- Check error of subtype with predicate in index constraint
14799 Bad_Predicated_Subtype_Use
14800 ("subtype& has predicate, not allowed in index constraint",
14807 Error_Msg_N
("invalid index constraint", S
);
14808 Rewrite
(S
, New_Occurrence_Of
(T
, Sloc
(S
)));
14813 -- Complete construction of the Itype
14815 if Is_Modular_Integer_Type
(T
) then
14816 Mutate_Ekind
(Def_Id
, E_Modular_Integer_Subtype
);
14818 elsif Is_Integer_Type
(T
) then
14819 Mutate_Ekind
(Def_Id
, E_Signed_Integer_Subtype
);
14822 Mutate_Ekind
(Def_Id
, E_Enumeration_Subtype
);
14823 Set_Is_Character_Type
(Def_Id
, Is_Character_Type
(T
));
14824 Set_First_Literal
(Def_Id
, First_Literal
(T
));
14827 Set_Size_Info
(Def_Id
, (T
));
14828 Copy_RM_Size
(To
=> Def_Id
, From
=> T
);
14829 Set_First_Rep_Item
(Def_Id
, First_Rep_Item
(T
));
14831 -- If this is a range for a fixed-lower-bound subtype, then set the
14832 -- index itype's low bound to the FLB and the index itype's upper bound
14833 -- to the high bound of the parent array type's index subtype. Also,
14834 -- mark the itype as an FLB index subtype.
14836 if Nkind
(S
) = N_Range
and then Is_FLB_Index
then
14839 Make_Range
(Sloc
(S
),
14840 Low_Bound
=> Low_Bound
(S
),
14841 High_Bound
=> Type_High_Bound
(T
)));
14842 Set_Is_Fixed_Lower_Bound_Index_Subtype
(Def_Id
);
14845 Set_Scalar_Range
(Def_Id
, R
);
14848 Set_Etype
(S
, Def_Id
);
14849 Set_Discrete_RM_Size
(Def_Id
);
14850 end Constrain_Index
;
14852 -----------------------
14853 -- Constrain_Integer --
14854 -----------------------
14856 procedure Constrain_Integer
(Def_Id
: Entity_Id
; S
: Node_Id
) is
14857 T
: constant Entity_Id
:= Entity
(Subtype_Mark
(S
));
14858 C
: constant Node_Id
:= Constraint
(S
);
14861 Set_Scalar_Range_For_Subtype
(Def_Id
, Range_Expression
(C
), T
);
14863 if Is_Modular_Integer_Type
(T
) then
14864 Mutate_Ekind
(Def_Id
, E_Modular_Integer_Subtype
);
14866 Mutate_Ekind
(Def_Id
, E_Signed_Integer_Subtype
);
14869 Set_Etype
(Def_Id
, Base_Type
(T
));
14870 Set_Size_Info
(Def_Id
, (T
));
14871 Set_First_Rep_Item
(Def_Id
, First_Rep_Item
(T
));
14872 Set_Discrete_RM_Size
(Def_Id
);
14873 end Constrain_Integer
;
14875 ------------------------------
14876 -- Constrain_Ordinary_Fixed --
14877 ------------------------------
14879 procedure Constrain_Ordinary_Fixed
(Def_Id
: Entity_Id
; S
: Node_Id
) is
14880 T
: constant Entity_Id
:= Entity
(Subtype_Mark
(S
));
14886 Mutate_Ekind
(Def_Id
, E_Ordinary_Fixed_Point_Subtype
);
14887 Set_Etype
(Def_Id
, Base_Type
(T
));
14888 Set_Size_Info
(Def_Id
, (T
));
14889 Set_First_Rep_Item
(Def_Id
, First_Rep_Item
(T
));
14890 Set_Small_Value
(Def_Id
, Small_Value
(T
));
14892 -- Process the constraint
14894 C
:= Constraint
(S
);
14896 -- Delta constraint present
14898 if Nkind
(C
) = N_Delta_Constraint
then
14899 Check_Restriction
(No_Obsolescent_Features
, C
);
14901 if Warn_On_Obsolescent_Feature
then
14903 ("subtype delta constraint is an " &
14904 "obsolescent feature (RM J.3(7))?j?");
14907 D
:= Delta_Expression
(C
);
14908 Analyze_And_Resolve
(D
, Any_Real
);
14909 Check_Delta_Expression
(D
);
14910 Set_Delta_Value
(Def_Id
, Expr_Value_R
(D
));
14912 -- Check that delta value is in range. Obviously we can do this
14913 -- at compile time, but it is strictly a runtime check, and of
14914 -- course there is an ACVC test that checks this.
14916 if Delta_Value
(Def_Id
) < Delta_Value
(T
) then
14917 Error_Msg_N
("??delta value is too small", D
);
14919 Make_Raise_Constraint_Error
(Sloc
(D
),
14920 Reason
=> CE_Range_Check_Failed
);
14921 Insert_Action
(Declaration_Node
(Def_Id
), Rais
);
14924 C
:= Range_Constraint
(C
);
14926 -- No delta constraint present
14929 Set_Delta_Value
(Def_Id
, Delta_Value
(T
));
14932 -- Range constraint present
14934 if Nkind
(C
) = N_Range_Constraint
then
14935 Set_Scalar_Range_For_Subtype
(Def_Id
, Range_Expression
(C
), T
);
14937 -- No range constraint present
14940 pragma Assert
(No
(C
));
14941 Set_Scalar_Range
(Def_Id
, Scalar_Range
(T
));
14944 Set_Discrete_RM_Size
(Def_Id
);
14946 -- Unconditionally delay the freeze, since we cannot set size
14947 -- information in all cases correctly until the freeze point.
14949 Set_Has_Delayed_Freeze
(Def_Id
);
14950 end Constrain_Ordinary_Fixed
;
14952 -----------------------
14953 -- Contain_Interface --
14954 -----------------------
14956 function Contain_Interface
14957 (Iface
: Entity_Id
;
14958 Ifaces
: Elist_Id
) return Boolean
14960 Iface_Elmt
: Elmt_Id
;
14963 if Present
(Ifaces
) then
14964 Iface_Elmt
:= First_Elmt
(Ifaces
);
14965 while Present
(Iface_Elmt
) loop
14966 if Node
(Iface_Elmt
) = Iface
then
14970 Next_Elmt
(Iface_Elmt
);
14975 end Contain_Interface
;
14977 ---------------------------
14978 -- Convert_Scalar_Bounds --
14979 ---------------------------
14981 procedure Convert_Scalar_Bounds
14983 Parent_Type
: Entity_Id
;
14984 Derived_Type
: Entity_Id
;
14987 Implicit_Base
: constant Entity_Id
:= Base_Type
(Derived_Type
);
14994 -- Defend against previous errors
14996 if No
(Scalar_Range
(Derived_Type
)) then
14997 Check_Error_Detected
;
15001 Lo
:= Build_Scalar_Bound
15002 (Type_Low_Bound
(Derived_Type
),
15003 Parent_Type
, Implicit_Base
);
15005 Hi
:= Build_Scalar_Bound
15006 (Type_High_Bound
(Derived_Type
),
15007 Parent_Type
, Implicit_Base
);
15014 Set_Includes_Infinities
(Rng
, Has_Infinities
(Derived_Type
));
15016 Set_Parent
(Rng
, N
);
15017 Set_Scalar_Range
(Derived_Type
, Rng
);
15019 -- Analyze the bounds
15021 Analyze_And_Resolve
(Lo
, Implicit_Base
);
15022 Analyze_And_Resolve
(Hi
, Implicit_Base
);
15024 -- Analyze the range itself, except that we do not analyze it if
15025 -- the bounds are real literals, and we have a fixed-point type.
15026 -- The reason for this is that we delay setting the bounds in this
15027 -- case till we know the final Small and Size values (see circuit
15028 -- in Freeze.Freeze_Fixed_Point_Type for further details).
15030 if Is_Fixed_Point_Type
(Parent_Type
)
15031 and then Nkind
(Lo
) = N_Real_Literal
15032 and then Nkind
(Hi
) = N_Real_Literal
15036 -- Here we do the analysis of the range
15038 -- Note: we do this manually, since if we do a normal Analyze and
15039 -- Resolve call, there are problems with the conversions used for
15040 -- the derived type range.
15043 Set_Etype
(Rng
, Implicit_Base
);
15044 Set_Analyzed
(Rng
, True);
15046 end Convert_Scalar_Bounds
;
15048 -------------------
15049 -- Copy_And_Swap --
15050 -------------------
15052 procedure Copy_And_Swap
(Priv
, Full
: Entity_Id
) is
15054 -- Initialize new full declaration entity by copying the pertinent
15055 -- fields of the corresponding private declaration entity.
15057 -- We temporarily set Ekind to a value appropriate for a type to
15058 -- avoid assert failures in Einfo from checking for setting type
15059 -- attributes on something that is not a type. Ekind (Priv) is an
15060 -- appropriate choice, since it allowed the attributes to be set
15061 -- in the first place. This Ekind value will be modified later.
15063 Mutate_Ekind
(Full
, Ekind
(Priv
));
15065 -- Also set Etype temporarily to Any_Type, again, in the absence
15066 -- of errors, it will be properly reset, and if there are errors,
15067 -- then we want a value of Any_Type to remain.
15069 Set_Etype
(Full
, Any_Type
);
15071 -- Now start copying attributes
15073 Set_Has_Discriminants
(Full
, Has_Discriminants
(Priv
));
15075 if Has_Discriminants
(Full
) then
15076 Set_Discriminant_Constraint
(Full
, Discriminant_Constraint
(Priv
));
15077 Set_Stored_Constraint
(Full
, Stored_Constraint
(Priv
));
15080 Set_First_Rep_Item
(Full
, First_Rep_Item
(Priv
));
15081 Set_Homonym
(Full
, Homonym
(Priv
));
15082 Set_Is_Immediately_Visible
(Full
, Is_Immediately_Visible
(Priv
));
15083 Set_Is_Public
(Full
, Is_Public
(Priv
));
15084 Set_Is_Pure
(Full
, Is_Pure
(Priv
));
15085 Set_Is_Tagged_Type
(Full
, Is_Tagged_Type
(Priv
));
15086 Set_Has_Pragma_Unmodified
(Full
, Has_Pragma_Unmodified
(Priv
));
15087 Set_Has_Pragma_Unreferenced
(Full
, Has_Pragma_Unreferenced
(Priv
));
15088 Set_Has_Pragma_Unreferenced_Objects
15089 (Full
, Has_Pragma_Unreferenced_Objects
15092 Conditional_Delay
(Full
, Priv
);
15094 if Is_Tagged_Type
(Full
) then
15095 Set_Direct_Primitive_Operations
15096 (Full
, Direct_Primitive_Operations
(Priv
));
15097 Set_No_Tagged_Streams_Pragma
15098 (Full
, No_Tagged_Streams_Pragma
(Priv
));
15100 if Is_Base_Type
(Priv
) then
15101 Set_Class_Wide_Type
(Full
, Class_Wide_Type
(Priv
));
15105 Set_Is_Volatile
(Full
, Is_Volatile
(Priv
));
15106 Set_Treat_As_Volatile
(Full
, Treat_As_Volatile
(Priv
));
15107 Set_Scope
(Full
, Scope
(Priv
));
15108 Set_Prev_Entity
(Full
, Prev_Entity
(Priv
));
15109 Set_Next_Entity
(Full
, Next_Entity
(Priv
));
15110 Set_First_Entity
(Full
, First_Entity
(Priv
));
15111 Set_Last_Entity
(Full
, Last_Entity
(Priv
));
15113 -- If access types have been recorded for later handling, keep them in
15114 -- the full view so that they get handled when the full view freeze
15115 -- node is expanded.
15117 if Present
(Freeze_Node
(Priv
))
15118 and then Present
(Access_Types_To_Process
(Freeze_Node
(Priv
)))
15120 Ensure_Freeze_Node
(Full
);
15121 Set_Access_Types_To_Process
15122 (Freeze_Node
(Full
),
15123 Access_Types_To_Process
(Freeze_Node
(Priv
)));
15126 -- Swap the two entities. Now Private is the full type entity and Full
15127 -- is the private one. They will be swapped back at the end of the
15128 -- private part. This swapping ensures that the entity that is visible
15129 -- in the private part is the full declaration.
15131 Exchange_Entities
(Priv
, Full
);
15132 Set_Is_Not_Self_Hidden
(Priv
);
15133 Append_Entity
(Full
, Scope
(Full
));
15136 -------------------------------------
15137 -- Copy_Array_Base_Type_Attributes --
15138 -------------------------------------
15140 procedure Copy_Array_Base_Type_Attributes
(T1
, T2
: Entity_Id
) is
15142 Set_Component_Alignment
(T1
, Component_Alignment
(T2
));
15143 Set_Component_Type
(T1
, Component_Type
(T2
));
15144 Set_Component_Size
(T1
, Component_Size
(T2
));
15145 Set_Has_Controlled_Component
(T1
, Has_Controlled_Component
(T2
));
15146 Set_Has_Non_Standard_Rep
(T1
, Has_Non_Standard_Rep
(T2
));
15147 Propagate_Concurrent_Flags
(T1
, T2
);
15148 Set_Is_Packed
(T1
, Is_Packed
(T2
));
15149 Set_Has_Aliased_Components
(T1
, Has_Aliased_Components
(T2
));
15150 Set_Has_Atomic_Components
(T1
, Has_Atomic_Components
(T2
));
15151 Set_Has_Independent_Components
(T1
, Has_Independent_Components
(T2
));
15152 Set_Has_Volatile_Components
(T1
, Has_Volatile_Components
(T2
));
15153 end Copy_Array_Base_Type_Attributes
;
15155 -----------------------------------
15156 -- Copy_Array_Subtype_Attributes --
15157 -----------------------------------
15159 -- Note that we used to copy Packed_Array_Impl_Type too here, but we now
15160 -- let it be recreated during freezing for the sake of better debug info.
15162 procedure Copy_Array_Subtype_Attributes
(T1
, T2
: Entity_Id
) is
15164 Set_Size_Info
(T1
, T2
);
15166 Set_First_Index
(T1
, First_Index
(T2
));
15167 Set_Is_Aliased
(T1
, Is_Aliased
(T2
));
15168 Set_Is_Atomic
(T1
, Is_Atomic
(T2
));
15169 Set_Is_Independent
(T1
, Is_Independent
(T2
));
15170 Set_Is_Volatile
(T1
, Is_Volatile
(T2
));
15171 Set_Is_Volatile_Full_Access
(T1
, Is_Volatile_Full_Access
(T2
));
15172 Set_Treat_As_Volatile
(T1
, Treat_As_Volatile
(T2
));
15173 Set_Is_Constrained
(T1
, Is_Constrained
(T2
));
15174 Set_Depends_On_Private
(T1
, Has_Private_Component
(T2
));
15175 Inherit_Rep_Item_Chain
(T1
, T2
);
15176 Set_Convention
(T1
, Convention
(T2
));
15177 Set_Is_Limited_Composite
(T1
, Is_Limited_Composite
(T2
));
15178 Set_Is_Private_Composite
(T1
, Is_Private_Composite
(T2
));
15179 end Copy_Array_Subtype_Attributes
;
15181 -----------------------------------
15182 -- Create_Constrained_Components --
15183 -----------------------------------
15185 procedure Create_Constrained_Components
15187 Decl_Node
: Node_Id
;
15189 Constraints
: Elist_Id
)
15191 Loc
: constant Source_Ptr
:= Sloc
(Subt
);
15192 Comp_List
: constant Elist_Id
:= New_Elmt_List
;
15193 Parent_Type
: constant Entity_Id
:= Etype
(Typ
);
15195 Assoc_List
: List_Id
;
15196 Discr_Val
: Elmt_Id
;
15200 Is_Static
: Boolean := True;
15201 Is_Compile_Time_Known
: Boolean := True;
15203 procedure Collect_Fixed_Components
(Typ
: Entity_Id
);
15204 -- Collect parent type components that do not appear in a variant part
15206 procedure Create_All_Components
;
15207 -- Iterate over Comp_List to create the components of the subtype
15209 function Create_Component
(Old_Compon
: Entity_Id
) return Entity_Id
;
15210 -- Creates a new component from Old_Compon, copying all the fields from
15211 -- it, including its Etype, inserts the new component in the Subt entity
15212 -- chain and returns the new component.
15214 function Is_Variant_Record
(T
: Entity_Id
) return Boolean;
15215 -- If true, and discriminants are static, collect only components from
15216 -- variants selected by discriminant values.
15218 ------------------------------
15219 -- Collect_Fixed_Components --
15220 ------------------------------
15222 procedure Collect_Fixed_Components
(Typ
: Entity_Id
) is
15224 -- Build association list for discriminants, and find components of
15225 -- the variant part selected by the values of the discriminants.
15227 Assoc_List
:= New_List
;
15229 Old_C
:= First_Discriminant
(Typ
);
15230 Discr_Val
:= First_Elmt
(Constraints
);
15231 while Present
(Old_C
) loop
15232 Append_To
(Assoc_List
,
15233 Make_Component_Association
(Loc
,
15234 Choices
=> New_List
(New_Occurrence_Of
(Old_C
, Loc
)),
15235 Expression
=> New_Copy
(Node
(Discr_Val
))));
15237 Next_Elmt
(Discr_Val
);
15238 Next_Discriminant
(Old_C
);
15241 -- The tag and the possible parent component are unconditionally in
15244 if Is_Tagged_Type
(Typ
) or else Has_Controlled_Component
(Typ
) then
15245 Old_C
:= First_Component
(Typ
);
15246 while Present
(Old_C
) loop
15247 if Chars
(Old_C
) in Name_uTag | Name_uParent
then
15248 Append_Elmt
(Old_C
, Comp_List
);
15251 Next_Component
(Old_C
);
15254 end Collect_Fixed_Components
;
15256 ---------------------------
15257 -- Create_All_Components --
15258 ---------------------------
15260 procedure Create_All_Components
is
15264 Comp
:= First_Elmt
(Comp_List
);
15265 while Present
(Comp
) loop
15266 Old_C
:= Node
(Comp
);
15267 New_C
:= Create_Component
(Old_C
);
15271 Constrain_Component_Type
15272 (Old_C
, Subt
, Decl_Node
, Typ
, Constraints
));
15273 Set_Is_Public
(New_C
, Is_Public
(Subt
));
15277 end Create_All_Components
;
15279 ----------------------
15280 -- Create_Component --
15281 ----------------------
15283 function Create_Component
(Old_Compon
: Entity_Id
) return Entity_Id
is
15284 New_Compon
: constant Entity_Id
:= New_Copy
(Old_Compon
);
15287 if Ekind
(Old_Compon
) = E_Discriminant
15288 and then Is_Completely_Hidden
(Old_Compon
)
15290 -- This is a shadow discriminant created for a discriminant of
15291 -- the parent type, which needs to be present in the subtype.
15292 -- Give the shadow discriminant an internal name that cannot
15293 -- conflict with that of visible components.
15295 Set_Chars
(New_Compon
, New_Internal_Name
('C'));
15298 -- Set the parent so we have a proper link for freezing etc. This is
15299 -- not a real parent pointer, since of course our parent does not own
15300 -- up to us and reference us, we are an illegitimate child of the
15301 -- original parent.
15303 Set_Parent
(New_Compon
, Parent
(Old_Compon
));
15305 -- We do not want this node marked as Comes_From_Source, since
15306 -- otherwise it would get first class status and a separate cross-
15307 -- reference line would be generated. Illegitimate children do not
15308 -- rate such recognition.
15310 Set_Comes_From_Source
(New_Compon
, False);
15312 -- But it is a real entity, and a birth certificate must be properly
15313 -- registered by entering it into the entity list, and setting its
15314 -- scope to the given subtype. This turns out to be useful for the
15315 -- LLVM code generator, but that scope is not used otherwise.
15317 Enter_Name
(New_Compon
);
15318 Set_Scope
(New_Compon
, Subt
);
15321 end Create_Component
;
15323 -----------------------
15324 -- Is_Variant_Record --
15325 -----------------------
15327 function Is_Variant_Record
(T
: Entity_Id
) return Boolean is
15328 Decl
: constant Node_Id
:= Parent
(T
);
15330 return Nkind
(Decl
) = N_Full_Type_Declaration
15331 and then Nkind
(Type_Definition
(Decl
)) = N_Record_Definition
15332 and then Present
(Component_List
(Type_Definition
(Decl
)))
15334 Present
(Variant_Part
(Component_List
(Type_Definition
(Decl
))));
15335 end Is_Variant_Record
;
15337 -- Start of processing for Create_Constrained_Components
15340 pragma Assert
(Subt
/= Base_Type
(Subt
));
15341 pragma Assert
(Typ
= Base_Type
(Typ
));
15343 Set_First_Entity
(Subt
, Empty
);
15344 Set_Last_Entity
(Subt
, Empty
);
15346 -- Check whether constraint is fully static, in which case we can
15347 -- optimize the list of components.
15349 Discr_Val
:= First_Elmt
(Constraints
);
15350 while Present
(Discr_Val
) loop
15351 if not Is_OK_Static_Expression
(Node
(Discr_Val
)) then
15352 Is_Static
:= False;
15354 if not Compile_Time_Known_Value
(Node
(Discr_Val
)) then
15355 Is_Compile_Time_Known
:= False;
15360 Next_Elmt
(Discr_Val
);
15363 Set_Has_Static_Discriminants
(Subt
, Is_Static
);
15367 -- Inherit the discriminants of the parent type
15369 Add_Discriminants
: declare
15375 Old_C
:= First_Discriminant
(Typ
);
15377 while Present
(Old_C
) loop
15378 Num_Disc
:= Num_Disc
+ 1;
15379 New_C
:= Create_Component
(Old_C
);
15380 Set_Is_Public
(New_C
, Is_Public
(Subt
));
15381 Next_Discriminant
(Old_C
);
15384 -- For an untagged derived subtype, the number of discriminants may
15385 -- be smaller than the number of inherited discriminants, because
15386 -- several of them may be renamed by a single new discriminant or
15387 -- constrained. In this case, add the hidden discriminants back into
15388 -- the subtype, because they need to be present if the optimizer of
15389 -- the GCC 4.x back-end decides to break apart assignments between
15390 -- objects using the parent view into member-wise assignments.
15394 if Is_Derived_Type
(Typ
)
15395 and then not Is_Tagged_Type
(Typ
)
15397 Old_C
:= First_Stored_Discriminant
(Typ
);
15399 while Present
(Old_C
) loop
15400 Num_Stor
:= Num_Stor
+ 1;
15401 Next_Stored_Discriminant
(Old_C
);
15405 if Num_Stor
> Num_Disc
then
15407 -- Find out multiple uses of new discriminants, and add hidden
15408 -- components for the extra renamed discriminants. We recognize
15409 -- multiple uses through the Corresponding_Discriminant of a
15410 -- new discriminant: if it constrains several old discriminants,
15411 -- this field points to the last one in the parent type. The
15412 -- stored discriminants of the derived type have the same name
15413 -- as those of the parent.
15417 New_Discr
: Entity_Id
;
15418 Old_Discr
: Entity_Id
;
15421 Constr
:= First_Elmt
(Stored_Constraint
(Typ
));
15422 Old_Discr
:= First_Stored_Discriminant
(Typ
);
15423 while Present
(Constr
) loop
15424 if Is_Entity_Name
(Node
(Constr
))
15425 and then Ekind
(Entity
(Node
(Constr
))) = E_Discriminant
15427 New_Discr
:= Entity
(Node
(Constr
));
15429 if Chars
(Corresponding_Discriminant
(New_Discr
)) /=
15432 -- The new discriminant has been used to rename a
15433 -- subsequent old discriminant. Introduce a shadow
15434 -- component for the current old discriminant.
15436 New_C
:= Create_Component
(Old_Discr
);
15437 Set_Original_Record_Component
(New_C
, Old_Discr
);
15441 -- The constraint has eliminated the old discriminant.
15442 -- Introduce a shadow component.
15444 New_C
:= Create_Component
(Old_Discr
);
15445 Set_Original_Record_Component
(New_C
, Old_Discr
);
15448 Next_Elmt
(Constr
);
15449 Next_Stored_Discriminant
(Old_Discr
);
15453 end Add_Discriminants
;
15455 if Is_Compile_Time_Known
15456 and then Is_Variant_Record
(Typ
)
15458 Collect_Fixed_Components
(Typ
);
15461 Component_List
(Type_Definition
(Parent
(Typ
))),
15462 Governed_By
=> Assoc_List
,
15464 Report_Errors
=> Errors
,
15465 Allow_Compile_Time
=> True);
15466 pragma Assert
(not Errors
or else Serious_Errors_Detected
> 0);
15468 Create_All_Components
;
15470 -- If the subtype declaration is created for a tagged type derivation
15471 -- with constraints, we retrieve the record definition of the parent
15472 -- type to select the components of the proper variant.
15474 elsif Is_Compile_Time_Known
15475 and then Is_Tagged_Type
(Typ
)
15476 and then Nkind
(Parent
(Typ
)) = N_Full_Type_Declaration
15478 Nkind
(Type_Definition
(Parent
(Typ
))) = N_Derived_Type_Definition
15479 and then Is_Variant_Record
(Parent_Type
)
15481 Collect_Fixed_Components
(Typ
);
15484 Component_List
(Type_Definition
(Parent
(Parent_Type
))),
15485 Governed_By
=> Assoc_List
,
15487 Report_Errors
=> Errors
,
15488 Allow_Compile_Time
=> True);
15490 -- Note: previously there was a check at this point that no errors
15491 -- were detected. As a consequence of AI05-220 there may be an error
15492 -- if an inherited discriminant that controls a variant has a non-
15493 -- static constraint.
15495 -- If the tagged derivation has a type extension, collect all the
15496 -- new relevant components therein via Gather_Components.
15498 if Present
(Record_Extension_Part
(Type_Definition
(Parent
(Typ
))))
15503 (Record_Extension_Part
(Type_Definition
(Parent
(Typ
)))),
15504 Governed_By
=> Assoc_List
,
15506 Report_Errors
=> Errors
,
15507 Allow_Compile_Time
=> True,
15508 Include_Interface_Tag
=> True);
15511 Create_All_Components
;
15514 -- If discriminants are not static, or if this is a multi-level type
15515 -- extension, we have to include all components of the parent type.
15517 Old_C
:= First_Component
(Typ
);
15518 while Present
(Old_C
) loop
15519 New_C
:= Create_Component
(Old_C
);
15523 Constrain_Component_Type
15524 (Old_C
, Subt
, Decl_Node
, Typ
, Constraints
));
15525 Set_Is_Public
(New_C
, Is_Public
(Subt
));
15527 Next_Component
(Old_C
);
15532 end Create_Constrained_Components
;
15534 ------------------------------------------
15535 -- Decimal_Fixed_Point_Type_Declaration --
15536 ------------------------------------------
15538 procedure Decimal_Fixed_Point_Type_Declaration
15542 Loc
: constant Source_Ptr
:= Sloc
(Def
);
15543 Digs_Expr
: constant Node_Id
:= Digits_Expression
(Def
);
15544 Delta_Expr
: constant Node_Id
:= Delta_Expression
(Def
);
15545 Max_Digits
: constant Nat
:=
15546 (if System_Max_Integer_Size
= 128 then 38 else 18);
15547 -- Maximum number of digits that can be represented in an integer
15549 Implicit_Base
: Entity_Id
;
15556 Check_Restriction
(No_Fixed_Point
, Def
);
15558 -- Create implicit base type
15561 Create_Itype
(E_Decimal_Fixed_Point_Type
, Parent
(Def
), T
, 'B');
15562 Set_Etype
(Implicit_Base
, Implicit_Base
);
15564 -- Analyze and process delta expression
15566 Analyze_And_Resolve
(Delta_Expr
, Universal_Real
);
15568 Check_Delta_Expression
(Delta_Expr
);
15569 Delta_Val
:= Expr_Value_R
(Delta_Expr
);
15571 -- Check delta is power of 10, and determine scale value from it
15577 Scale_Val
:= Uint_0
;
15580 if Val
< Ureal_1
then
15581 while Val
< Ureal_1
loop
15582 Val
:= Val
* Ureal_10
;
15583 Scale_Val
:= Scale_Val
+ 1;
15586 if Scale_Val
> Max_Digits
then
15587 Error_Msg_Uint_1
:= UI_From_Int
(Max_Digits
);
15588 Error_Msg_N
("scale exceeds maximum value of ^", Def
);
15589 Scale_Val
:= UI_From_Int
(Max_Digits
);
15593 while Val
> Ureal_1
loop
15594 Val
:= Val
/ Ureal_10
;
15595 Scale_Val
:= Scale_Val
- 1;
15598 if Scale_Val
< -Max_Digits
then
15599 Error_Msg_Uint_1
:= UI_From_Int
(-Max_Digits
);
15600 Error_Msg_N
("scale is less than minimum value of ^", Def
);
15601 Scale_Val
:= UI_From_Int
(-Max_Digits
);
15605 if Val
/= Ureal_1
then
15606 Error_Msg_N
("delta expression must be a power of 10", Def
);
15607 Delta_Val
:= Ureal_10
** (-Scale_Val
);
15611 -- Set delta, scale and small (small = delta for decimal type)
15613 Set_Delta_Value
(Implicit_Base
, Delta_Val
);
15614 Set_Scale_Value
(Implicit_Base
, Scale_Val
);
15615 Set_Small_Value
(Implicit_Base
, Delta_Val
);
15617 -- Analyze and process digits expression
15619 Analyze_And_Resolve
(Digs_Expr
, Any_Integer
);
15620 Check_Digits_Expression
(Digs_Expr
);
15621 Digs_Val
:= Expr_Value
(Digs_Expr
);
15623 if Digs_Val
> Max_Digits
then
15624 Error_Msg_Uint_1
:= UI_From_Int
(Max_Digits
);
15625 Error_Msg_N
("digits value out of range, maximum is ^", Digs_Expr
);
15626 Digs_Val
:= UI_From_Int
(Max_Digits
);
15629 Set_Digits_Value
(Implicit_Base
, Digs_Val
);
15630 Bound_Val
:= UR_From_Uint
(10 ** Digs_Val
- 1) * Delta_Val
;
15632 -- Set range of base type from digits value for now. This will be
15633 -- expanded to represent the true underlying base range by Freeze.
15635 Set_Fixed_Range
(Implicit_Base
, Loc
, -Bound_Val
, Bound_Val
);
15637 -- Note: We leave Esize unset for now, size will be set at freeze
15638 -- time. We have to do this for ordinary fixed-point, because the size
15639 -- depends on the specified small, and we might as well do the same for
15640 -- decimal fixed-point.
15642 pragma Assert
(not Known_Esize
(Implicit_Base
));
15644 -- If there are bounds given in the declaration use them as the
15645 -- bounds of the first named subtype.
15647 if Present
(Real_Range_Specification
(Def
)) then
15649 RRS
: constant Node_Id
:= Real_Range_Specification
(Def
);
15650 Low
: constant Node_Id
:= Low_Bound
(RRS
);
15651 High
: constant Node_Id
:= High_Bound
(RRS
);
15656 Analyze_And_Resolve
(Low
, Any_Real
);
15657 Analyze_And_Resolve
(High
, Any_Real
);
15658 Check_Real_Bound
(Low
);
15659 Check_Real_Bound
(High
);
15660 Low_Val
:= Expr_Value_R
(Low
);
15661 High_Val
:= Expr_Value_R
(High
);
15663 if Low_Val
< (-Bound_Val
) then
15665 ("range low bound too small for digits value", Low
);
15666 Low_Val
:= -Bound_Val
;
15669 if High_Val
> Bound_Val
then
15671 ("range high bound too large for digits value", High
);
15672 High_Val
:= Bound_Val
;
15675 Set_Fixed_Range
(T
, Loc
, Low_Val
, High_Val
);
15678 -- If no explicit range, use range that corresponds to given
15679 -- digits value. This will end up as the final range for the
15683 Set_Fixed_Range
(T
, Loc
, -Bound_Val
, Bound_Val
);
15686 -- Complete entity for first subtype. The inheritance of the rep item
15687 -- chain ensures that SPARK-related pragmas are not clobbered when the
15688 -- decimal fixed point type acts as a full view of a private type.
15690 Mutate_Ekind
(T
, E_Decimal_Fixed_Point_Subtype
);
15691 Set_Etype
(T
, Implicit_Base
);
15692 Set_Size_Info
(T
, Implicit_Base
);
15693 Inherit_Rep_Item_Chain
(T
, Implicit_Base
);
15694 Set_Digits_Value
(T
, Digs_Val
);
15695 Set_Delta_Value
(T
, Delta_Val
);
15696 Set_Small_Value
(T
, Delta_Val
);
15697 Set_Scale_Value
(T
, Scale_Val
);
15698 Set_Is_Constrained
(T
);
15699 end Decimal_Fixed_Point_Type_Declaration
;
15701 -----------------------------------
15702 -- Derive_Progenitor_Subprograms --
15703 -----------------------------------
15705 procedure Derive_Progenitor_Subprograms
15706 (Parent_Type
: Entity_Id
;
15707 Tagged_Type
: Entity_Id
)
15712 Iface_Alias
: Entity_Id
;
15713 Iface_Elmt
: Elmt_Id
;
15714 Iface_Subp
: Entity_Id
;
15715 New_Subp
: Entity_Id
:= Empty
;
15716 Prim_Elmt
: Elmt_Id
;
15721 pragma Assert
(Ada_Version
>= Ada_2005
15722 and then Is_Record_Type
(Tagged_Type
)
15723 and then Is_Tagged_Type
(Tagged_Type
)
15724 and then Has_Interfaces
(Tagged_Type
));
15726 -- Step 1: Transfer to the full-view primitives associated with the
15727 -- partial-view that cover interface primitives. Conceptually this
15728 -- work should be done later by Process_Full_View; done here to
15729 -- simplify its implementation at later stages. It can be safely
15730 -- done here because interfaces must be visible in the partial and
15731 -- private view (RM 7.3(7.3/2)).
15733 -- Small optimization: This work is only required if the parent may
15734 -- have entities whose Alias attribute reference an interface primitive.
15735 -- Such a situation may occur if the parent is an abstract type and the
15736 -- primitive has not been yet overridden or if the parent is a generic
15737 -- formal type covering interfaces.
15739 -- If the tagged type is not abstract, it cannot have abstract
15740 -- primitives (the only entities in the list of primitives of
15741 -- non-abstract tagged types that can reference abstract primitives
15742 -- through its Alias attribute are the internal entities that have
15743 -- attribute Interface_Alias, and these entities are generated later
15744 -- by Add_Internal_Interface_Entities).
15746 if In_Private_Part
(Current_Scope
)
15747 and then (Is_Abstract_Type
(Parent_Type
)
15749 Is_Generic_Type
(Parent_Type
))
15751 Elmt
:= First_Elmt
(Primitive_Operations
(Tagged_Type
));
15752 while Present
(Elmt
) loop
15753 Subp
:= Node
(Elmt
);
15755 -- At this stage it is not possible to have entities in the list
15756 -- of primitives that have attribute Interface_Alias.
15758 pragma Assert
(No
(Interface_Alias
(Subp
)));
15760 Typ
:= Find_Dispatching_Type
(Ultimate_Alias
(Subp
));
15762 if Is_Interface
(Typ
) then
15763 E
:= Find_Primitive_Covering_Interface
15764 (Tagged_Type
=> Tagged_Type
,
15765 Iface_Prim
=> Subp
);
15768 and then Find_Dispatching_Type
(Ultimate_Alias
(E
)) /= Typ
15770 Replace_Elmt
(Elmt
, E
);
15771 Remove_Homonym
(Subp
);
15779 -- Step 2: Add primitives of progenitors that are not implemented by
15780 -- parents of Tagged_Type.
15782 if Present
(Interfaces
(Base_Type
(Tagged_Type
))) then
15783 Iface_Elmt
:= First_Elmt
(Interfaces
(Base_Type
(Tagged_Type
)));
15784 while Present
(Iface_Elmt
) loop
15785 Iface
:= Node
(Iface_Elmt
);
15787 Prim_Elmt
:= First_Elmt
(Primitive_Operations
(Iface
));
15788 while Present
(Prim_Elmt
) loop
15789 Iface_Subp
:= Node
(Prim_Elmt
);
15790 Iface_Alias
:= Ultimate_Alias
(Iface_Subp
);
15792 -- Exclude derivation of predefined primitives except those
15793 -- that come from source, or are inherited from one that comes
15794 -- from source. Required to catch declarations of equality
15795 -- operators of interfaces. For example:
15797 -- type Iface is interface;
15798 -- function "=" (Left, Right : Iface) return Boolean;
15800 if not Is_Predefined_Dispatching_Operation
(Iface_Subp
)
15801 or else Comes_From_Source
(Iface_Alias
)
15804 Find_Primitive_Covering_Interface
15805 (Tagged_Type
=> Tagged_Type
,
15806 Iface_Prim
=> Iface_Subp
);
15808 -- If not found we derive a new primitive leaving its alias
15809 -- attribute referencing the interface primitive.
15813 (New_Subp
, Iface_Subp
, Tagged_Type
, Iface
);
15815 -- Ada 2012 (AI05-0197): If the covering primitive's name
15816 -- differs from the name of the interface primitive then it
15817 -- is a private primitive inherited from a parent type. In
15818 -- such case, given that Tagged_Type covers the interface,
15819 -- the inherited private primitive becomes visible. For such
15820 -- purpose we add a new entity that renames the inherited
15821 -- private primitive.
15823 elsif Chars
(E
) /= Chars
(Iface_Subp
) then
15824 pragma Assert
(Has_Suffix
(E
, 'P'));
15826 (New_Subp
, Iface_Subp
, Tagged_Type
, Iface
);
15827 Set_Alias
(New_Subp
, E
);
15828 Set_Is_Abstract_Subprogram
(New_Subp
,
15829 Is_Abstract_Subprogram
(E
));
15831 -- Propagate to the full view interface entities associated
15832 -- with the partial view.
15834 elsif In_Private_Part
(Current_Scope
)
15835 and then Present
(Alias
(E
))
15836 and then Alias
(E
) = Iface_Subp
15838 List_Containing
(Parent
(E
)) /=
15839 Private_Declarations
15841 (Unit_Declaration_Node
(Current_Scope
)))
15843 Append_Elmt
(E
, Primitive_Operations
(Tagged_Type
));
15847 Next_Elmt
(Prim_Elmt
);
15850 Next_Elmt
(Iface_Elmt
);
15853 end Derive_Progenitor_Subprograms
;
15855 -----------------------
15856 -- Derive_Subprogram --
15857 -----------------------
15859 procedure Derive_Subprogram
15860 (New_Subp
: out Entity_Id
;
15861 Parent_Subp
: Entity_Id
;
15862 Derived_Type
: Entity_Id
;
15863 Parent_Type
: Entity_Id
;
15864 Actual_Subp
: Entity_Id
:= Empty
)
15866 Formal
: Entity_Id
;
15867 -- Formal parameter of parent primitive operation
15869 Formal_Of_Actual
: Entity_Id
;
15870 -- Formal parameter of actual operation, when the derivation is to
15871 -- create a renaming for a primitive operation of an actual in an
15874 New_Formal
: Entity_Id
;
15875 -- Formal of inherited operation
15877 Visible_Subp
: Entity_Id
:= Parent_Subp
;
15879 function Is_Private_Overriding
return Boolean;
15880 -- If Subp is a private overriding of a visible operation, the inherited
15881 -- operation derives from the overridden op (even though its body is the
15882 -- overriding one) and the inherited operation is visible now. See
15883 -- sem_disp to see the full details of the handling of the overridden
15884 -- subprogram, which is removed from the list of primitive operations of
15885 -- the type. The overridden subprogram is saved locally in Visible_Subp,
15886 -- and used to diagnose abstract operations that need overriding in the
15889 procedure Replace_Type
(Id
, New_Id
: Entity_Id
);
15890 -- Set the Etype of New_Id to the appropriate subtype determined from
15891 -- the Etype of Id, following (RM 3.4 (18, 19, 20, 21)). Id is either
15892 -- the parent type's primitive subprogram or one of its formals, and
15893 -- New_Id is the corresponding entity for the derived type. When the
15894 -- Etype of Id is an anonymous access type, create a new access type
15895 -- designating the derived type.
15897 procedure Set_Derived_Name
;
15898 -- This procedure sets the appropriate Chars name for New_Subp. This
15899 -- is normally just a copy of the parent name. An exception arises for
15900 -- type support subprograms, where the name is changed to reflect the
15901 -- name of the derived type, e.g. if type foo is derived from type bar,
15902 -- then a procedure barDA is derived with a name fooDA.
15904 ---------------------------
15905 -- Is_Private_Overriding --
15906 ---------------------------
15908 function Is_Private_Overriding
return Boolean is
15912 -- If the parent is not a dispatching operation there is no
15913 -- need to investigate overridings
15915 if not Is_Dispatching_Operation
(Parent_Subp
) then
15919 -- The visible operation that is overridden is a homonym of the
15920 -- parent subprogram. We scan the homonym chain to find the one
15921 -- whose alias is the subprogram we are deriving.
15923 Prev
:= Current_Entity
(Parent_Subp
);
15924 while Present
(Prev
) loop
15925 if Ekind
(Prev
) = Ekind
(Parent_Subp
)
15926 and then Alias
(Prev
) = Parent_Subp
15927 and then Scope
(Parent_Subp
) = Scope
(Prev
)
15928 and then not Is_Hidden
(Prev
)
15930 Visible_Subp
:= Prev
;
15934 Prev
:= Homonym
(Prev
);
15938 end Is_Private_Overriding
;
15944 procedure Replace_Type
(Id
, New_Id
: Entity_Id
) is
15945 Id_Type
: constant Entity_Id
:= Etype
(Id
);
15946 Par
: constant Node_Id
:= Parent
(Derived_Type
);
15949 -- When the type is an anonymous access type, create a new access
15950 -- type designating the derived type. This itype must be elaborated
15951 -- at the point of the derivation, not on subsequent calls that may
15952 -- be out of the proper scope for Gigi, so we insert a reference to
15953 -- it after the derivation.
15955 if Ekind
(Id_Type
) = E_Anonymous_Access_Type
then
15957 Acc_Type
: Entity_Id
;
15958 Desig_Typ
: Entity_Id
:= Designated_Type
(Id_Type
);
15961 if Ekind
(Desig_Typ
) = E_Record_Type_With_Private
15962 and then Present
(Full_View
(Desig_Typ
))
15963 and then not Is_Private_Type
(Parent_Type
)
15965 Desig_Typ
:= Full_View
(Desig_Typ
);
15968 if Base_Type
(Desig_Typ
) = Base_Type
(Parent_Type
)
15970 -- Ada 2005 (AI-251): Handle also derivations of abstract
15971 -- interface primitives.
15973 or else (Is_Interface
(Desig_Typ
)
15974 and then not Is_Class_Wide_Type
(Desig_Typ
))
15976 Acc_Type
:= New_Copy
(Id_Type
);
15977 Set_Etype
(Acc_Type
, Acc_Type
);
15978 Set_Scope
(Acc_Type
, New_Subp
);
15980 -- Set size of anonymous access type. If we have an access
15981 -- to an unconstrained array, this is a fat pointer, so it
15982 -- is sizes at twice addtress size.
15984 if Is_Array_Type
(Desig_Typ
)
15985 and then not Is_Constrained
(Desig_Typ
)
15987 Init_Size
(Acc_Type
, 2 * System_Address_Size
);
15989 -- Other cases use a thin pointer
15992 Init_Size
(Acc_Type
, System_Address_Size
);
15995 -- Set remaining characterstics of anonymous access type
15997 Reinit_Alignment
(Acc_Type
);
15998 Set_Directly_Designated_Type
(Acc_Type
, Derived_Type
);
16000 Set_Etype
(New_Id
, Acc_Type
);
16001 Set_Scope
(New_Id
, New_Subp
);
16003 -- Create a reference to it
16005 Build_Itype_Reference
(Acc_Type
, Parent
(Derived_Type
));
16008 Set_Etype
(New_Id
, Id_Type
);
16012 -- In Ada2012, a formal may have an incomplete type but the type
16013 -- derivation that inherits the primitive follows the full view.
16015 elsif Base_Type
(Id_Type
) = Base_Type
(Parent_Type
)
16017 (Ekind
(Id_Type
) = E_Record_Type_With_Private
16018 and then Present
(Full_View
(Id_Type
))
16020 Base_Type
(Full_View
(Id_Type
)) = Base_Type
(Parent_Type
))
16022 (Ada_Version
>= Ada_2012
16023 and then Ekind
(Id_Type
) = E_Incomplete_Type
16024 and then Full_View
(Id_Type
) = Parent_Type
)
16026 -- Constraint checks on formals are generated during expansion,
16027 -- based on the signature of the original subprogram. The bounds
16028 -- of the derived type are not relevant, and thus we can use
16029 -- the base type for the formals. However, the return type may be
16030 -- used in a context that requires that the proper static bounds
16031 -- be used (a case statement, for example) and for those cases
16032 -- we must use the derived type (first subtype), not its base.
16034 -- If the derived_type_definition has no constraints, we know that
16035 -- the derived type has the same constraints as the first subtype
16036 -- of the parent, and we can also use it rather than its base,
16037 -- which can lead to more efficient code.
16039 if Id_Type
= Parent_Type
then
16040 if Is_Scalar_Type
(Parent_Type
)
16042 Subtypes_Statically_Compatible
(Parent_Type
, Derived_Type
)
16044 Set_Etype
(New_Id
, Derived_Type
);
16046 elsif Nkind
(Par
) = N_Full_Type_Declaration
16048 Nkind
(Type_Definition
(Par
)) = N_Derived_Type_Definition
16051 (Subtype_Indication
(Type_Definition
(Par
)))
16053 Set_Etype
(New_Id
, Derived_Type
);
16056 Set_Etype
(New_Id
, Base_Type
(Derived_Type
));
16060 Set_Etype
(New_Id
, Base_Type
(Derived_Type
));
16064 Set_Etype
(New_Id
, Id_Type
);
16068 ----------------------
16069 -- Set_Derived_Name --
16070 ----------------------
16072 procedure Set_Derived_Name
is
16073 Nm
: constant TSS_Name_Type
:= Get_TSS_Name
(Parent_Subp
);
16075 if Nm
= TSS_Null
then
16076 Set_Chars
(New_Subp
, Chars
(Parent_Subp
));
16078 Set_Chars
(New_Subp
, Make_TSS_Name
(Base_Type
(Derived_Type
), Nm
));
16080 end Set_Derived_Name
;
16082 -- Start of processing for Derive_Subprogram
16085 New_Subp
:= New_Entity
(Nkind
(Parent_Subp
), Sloc
(Derived_Type
));
16086 Mutate_Ekind
(New_Subp
, Ekind
(Parent_Subp
));
16087 Set_Is_Not_Self_Hidden
(New_Subp
);
16089 -- Check whether the inherited subprogram is a private operation that
16090 -- should be inherited but not yet made visible. Such subprograms can
16091 -- become visible at a later point (e.g., the private part of a public
16092 -- child unit) via Declare_Inherited_Private_Subprograms. If the
16093 -- following predicate is true, then this is not such a private
16094 -- operation and the subprogram simply inherits the name of the parent
16095 -- subprogram. Note the special check for the names of controlled
16096 -- operations, which are currently exempted from being inherited with
16097 -- a hidden name because they must be findable for generation of
16098 -- implicit run-time calls.
16100 if not Is_Hidden
(Parent_Subp
)
16101 or else Is_Internal
(Parent_Subp
)
16102 or else Is_Private_Overriding
16103 or else Is_Internal_Name
(Chars
(Parent_Subp
))
16104 or else (Is_Controlled
(Parent_Type
)
16105 and then Chars
(Parent_Subp
) in Name_Adjust
16111 -- An inherited dispatching equality will be overridden by an internally
16112 -- generated one, or by an explicit one, so preserve its name and thus
16113 -- its entry in the dispatch table. Otherwise, if Parent_Subp is a
16114 -- private operation it may become invisible if the full view has
16115 -- progenitors, and the dispatch table will be malformed.
16116 -- We check that the type is limited to handle the anomalous declaration
16117 -- of Limited_Controlled, which is derived from a non-limited type, and
16118 -- which is handled specially elsewhere as well.
16120 elsif Chars
(Parent_Subp
) = Name_Op_Eq
16121 and then Is_Dispatching_Operation
(Parent_Subp
)
16122 and then Etype
(Parent_Subp
) = Standard_Boolean
16123 and then not Is_Limited_Type
(Etype
(First_Formal
(Parent_Subp
)))
16125 Etype
(First_Formal
(Parent_Subp
)) =
16126 Etype
(Next_Formal
(First_Formal
(Parent_Subp
)))
16130 -- If parent is hidden, this can be a regular derivation if the
16131 -- parent is immediately visible in a non-instantiating context,
16132 -- or if we are in the private part of an instance. This test
16133 -- should still be refined ???
16135 -- The test for In_Instance_Not_Visible avoids inheriting the derived
16136 -- operation as a non-visible operation in cases where the parent
16137 -- subprogram might not be visible now, but was visible within the
16138 -- original generic, so it would be wrong to make the inherited
16139 -- subprogram non-visible now. (Not clear if this test is fully
16140 -- correct; are there any cases where we should declare the inherited
16141 -- operation as not visible to avoid it being overridden, e.g., when
16142 -- the parent type is a generic actual with private primitives ???)
16144 -- (they should be treated the same as other private inherited
16145 -- subprograms, but it's not clear how to do this cleanly). ???
16147 elsif (In_Open_Scopes
(Scope
(Base_Type
(Parent_Type
)))
16148 and then Is_Immediately_Visible
(Parent_Subp
)
16149 and then not In_Instance
)
16150 or else In_Instance_Not_Visible
16154 -- Ada 2005 (AI-251): Regular derivation if the parent subprogram
16155 -- overrides an interface primitive because interface primitives
16156 -- must be visible in the partial view of the parent (RM 7.3 (7.3/2))
16158 elsif Ada_Version
>= Ada_2005
16159 and then Is_Dispatching_Operation
(Parent_Subp
)
16160 and then Present
(Covered_Interface_Op
(Parent_Subp
))
16164 -- Otherwise, the type is inheriting a private operation, so enter it
16165 -- with a special name so it can't be overridden. See also below, where
16166 -- we check for this case, and if so avoid setting Requires_Overriding.
16169 Set_Chars
(New_Subp
, New_External_Name
(Chars
(Parent_Subp
), 'P'));
16172 Set_Parent
(New_Subp
, Parent
(Derived_Type
));
16174 if Present
(Actual_Subp
) then
16175 Replace_Type
(Actual_Subp
, New_Subp
);
16177 Replace_Type
(Parent_Subp
, New_Subp
);
16180 Conditional_Delay
(New_Subp
, Parent_Subp
);
16182 -- If we are creating a renaming for a primitive operation of an
16183 -- actual of a generic derived type, we must examine the signature
16184 -- of the actual primitive, not that of the generic formal, which for
16185 -- example may be an interface. However the name and initial value
16186 -- of the inherited operation are those of the formal primitive.
16188 Formal
:= First_Formal
(Parent_Subp
);
16190 if Present
(Actual_Subp
) then
16191 Formal_Of_Actual
:= First_Formal
(Actual_Subp
);
16193 Formal_Of_Actual
:= Empty
;
16196 while Present
(Formal
) loop
16197 New_Formal
:= New_Copy
(Formal
);
16199 -- Extra formals are not inherited from a limited interface parent
16200 -- since limitedness is not inherited in such case (AI-419) and this
16201 -- affects the extra formals.
16203 if Is_Limited_Interface
(Parent_Type
) then
16204 Set_Extra_Formal
(New_Formal
, Empty
);
16205 Set_Extra_Accessibility
(New_Formal
, Empty
);
16208 -- Normally we do not go copying parents, but in the case of
16209 -- formals, we need to link up to the declaration (which is the
16210 -- parameter specification), and it is fine to link up to the
16211 -- original formal's parameter specification in this case.
16213 Set_Parent
(New_Formal
, Parent
(Formal
));
16214 Append_Entity
(New_Formal
, New_Subp
);
16216 if Present
(Formal_Of_Actual
) then
16217 Replace_Type
(Formal_Of_Actual
, New_Formal
);
16218 Next_Formal
(Formal_Of_Actual
);
16220 Replace_Type
(Formal
, New_Formal
);
16223 Next_Formal
(Formal
);
16226 -- Extra formals are shared between the parent subprogram and this
16227 -- internal entity built by Derive_Subprogram (implicit in the above
16228 -- copy of formals), unless the parent type is a limited interface type;
16229 -- hence we must inherit also the reference to the first extra formal.
16230 -- When the parent type is an interface, the extra formals will be added
16231 -- when the tagged type is frozen (see Expand_Freeze_Record_Type).
16233 if not Is_Limited_Interface
(Parent_Type
) then
16234 Set_Extra_Formals
(New_Subp
, Extra_Formals
(Parent_Subp
));
16236 if Ekind
(New_Subp
) = E_Function
then
16237 Set_Extra_Accessibility_Of_Result
(New_Subp
,
16238 Extra_Accessibility_Of_Result
(Parent_Subp
));
16242 -- If this derivation corresponds to a tagged generic actual, then
16243 -- primitive operations rename those of the actual. Otherwise the
16244 -- primitive operations rename those of the parent type, If the parent
16245 -- renames an intrinsic operator, so does the new subprogram. We except
16246 -- concatenation, which is always properly typed, and does not get
16247 -- expanded as other intrinsic operations.
16249 if No
(Actual_Subp
) then
16250 if Is_Intrinsic_Subprogram
(Parent_Subp
) then
16251 Set_Convention
(New_Subp
, Convention_Intrinsic
);
16252 Set_Is_Intrinsic_Subprogram
(New_Subp
);
16254 if Present
(Alias
(Parent_Subp
))
16255 and then Chars
(Parent_Subp
) /= Name_Op_Concat
16257 Set_Alias
(New_Subp
, Alias
(Parent_Subp
));
16259 Set_Alias
(New_Subp
, Parent_Subp
);
16263 Set_Alias
(New_Subp
, Parent_Subp
);
16267 Set_Alias
(New_Subp
, Actual_Subp
);
16270 Copy_Strub_Mode
(New_Subp
, Alias
(New_Subp
));
16272 -- Derived subprograms of a tagged type must inherit the convention
16273 -- of the parent subprogram (a requirement of AI95-117). Derived
16274 -- subprograms of untagged types simply get convention Ada by default.
16276 -- If the derived type is a tagged generic formal type with unknown
16277 -- discriminants, its convention is intrinsic (RM 6.3.1 (8)).
16279 -- However, if the type is derived from a generic formal, the further
16280 -- inherited subprogram has the convention of the non-generic ancestor.
16281 -- Otherwise there would be no way to override the operation.
16282 -- (This is subject to forthcoming ARG discussions).
16284 if Is_Tagged_Type
(Derived_Type
) then
16285 if Is_Generic_Type
(Derived_Type
)
16286 and then Has_Unknown_Discriminants
(Derived_Type
)
16288 Set_Convention
(New_Subp
, Convention_Intrinsic
);
16291 if Is_Generic_Type
(Parent_Type
)
16292 and then Has_Unknown_Discriminants
(Parent_Type
)
16294 Set_Convention
(New_Subp
, Convention
(Alias
(Parent_Subp
)));
16296 Set_Convention
(New_Subp
, Convention
(Parent_Subp
));
16301 -- Predefined controlled operations retain their name even if the parent
16302 -- is hidden (see above), but they are not primitive operations if the
16303 -- ancestor is not visible, for example if the parent is a private
16304 -- extension completed with a controlled extension. Note that a full
16305 -- type that is controlled can break privacy: the flag Is_Controlled is
16306 -- set on both views of the type.
16308 if Is_Controlled
(Parent_Type
)
16309 and then Chars
(Parent_Subp
) in Name_Initialize
16312 and then Is_Hidden
(Parent_Subp
)
16313 and then not Is_Visibly_Controlled
(Parent_Type
)
16315 Set_Is_Hidden
(New_Subp
);
16318 Set_Is_Imported
(New_Subp
, Is_Imported
(Parent_Subp
));
16319 Set_Is_Exported
(New_Subp
, Is_Exported
(Parent_Subp
));
16321 if Ekind
(Parent_Subp
) = E_Procedure
then
16322 Set_Is_Valued_Procedure
16323 (New_Subp
, Is_Valued_Procedure
(Parent_Subp
));
16325 Set_Has_Controlling_Result
16326 (New_Subp
, Has_Controlling_Result
(Parent_Subp
));
16329 -- No_Return must be inherited properly. If this is overridden in the
16330 -- case of a dispatching operation, then the check is made later in
16331 -- Check_Abstract_Overriding that the overriding operation is also
16332 -- No_Return (no such check is required for the nondispatching case).
16334 Set_No_Return
(New_Subp
, No_Return
(Parent_Subp
));
16336 -- If the parent subprogram is marked as Ghost, then so is the derived
16337 -- subprogram. The ghost policy for the derived subprogram is set from
16338 -- the effective ghost policy at the point of derived type declaration.
16340 if Is_Ghost_Entity
(Parent_Subp
) then
16341 Set_Is_Ghost_Entity
(New_Subp
);
16344 -- A derived function with a controlling result is abstract. If the
16345 -- Derived_Type is a nonabstract formal generic derived type, then
16346 -- inherited operations are not abstract: the required check is done at
16347 -- instantiation time. If the derivation is for a generic actual, the
16348 -- function is not abstract unless the actual is.
16350 if Is_Generic_Type
(Derived_Type
)
16351 and then not Is_Abstract_Type
(Derived_Type
)
16355 -- Ada 2005 (AI-228): Calculate the "require overriding" and "abstract"
16356 -- properties of the subprogram, as defined in RM-3.9.3(4/2-6/2). Note
16357 -- that functions with controlling access results of record extensions
16358 -- with a null extension part require overriding (AI95-00391/06).
16360 -- Ada 2022 (AI12-0042): Similarly, set those properties for
16361 -- implementing the rule of RM 7.3.2(6.1/4).
16363 -- A subprogram subject to pragma Extensions_Visible with value False
16364 -- requires overriding if the subprogram has at least one controlling
16365 -- OUT parameter (SPARK RM 6.1.7(6)).
16367 elsif Ada_Version
>= Ada_2005
16368 and then (Is_Abstract_Subprogram
(Alias
(New_Subp
))
16369 or else (Is_Tagged_Type
(Derived_Type
)
16370 and then Etype
(New_Subp
) = Derived_Type
16371 and then not Is_Null_Extension
(Derived_Type
))
16372 or else (Is_Tagged_Type
(Derived_Type
)
16373 and then Ekind
(Etype
(New_Subp
)) =
16374 E_Anonymous_Access_Type
16375 and then Designated_Type
(Etype
(New_Subp
)) =
16377 or else (Comes_From_Source
(Alias
(New_Subp
))
16378 and then Is_EVF_Procedure
(Alias
(New_Subp
)))
16380 -- AI12-0042: Set Requires_Overriding when a type extension
16381 -- inherits a private operation that is visible at the
16382 -- point of extension (Has_Private_Ancestor is False) from
16383 -- an ancestor that has Type_Invariant'Class, and when the
16384 -- type extension is in a visible part (the latter as
16385 -- clarified by AI12-0382).
16388 (not Has_Private_Ancestor
(Derived_Type
)
16389 and then Has_Invariants
(Parent_Type
)
16391 Present
(Get_Pragma
(Parent_Type
, Pragma_Invariant
))
16394 (Get_Pragma
(Parent_Type
, Pragma_Invariant
))
16395 and then Is_Private_Primitive
(Parent_Subp
)
16396 and then In_Visible_Part
(Scope
(Derived_Type
))))
16398 and then No
(Actual_Subp
)
16400 if not Is_Tagged_Type
(Derived_Type
)
16401 or else Is_Abstract_Type
(Derived_Type
)
16402 or else Is_Abstract_Subprogram
(Alias
(New_Subp
))
16404 Set_Is_Abstract_Subprogram
(New_Subp
);
16406 -- If the Chars of the new subprogram is different from that of the
16407 -- parent's one, it means that we entered it with a special name so
16408 -- it can't be overridden (see above). In that case we had better not
16409 -- *require* it to be overridden. This is the case where the parent
16410 -- type inherited the operation privately, so there's no danger of
16411 -- dangling dispatching.
16413 elsif Chars
(New_Subp
) = Chars
(Alias
(New_Subp
)) then
16414 Set_Requires_Overriding
(New_Subp
);
16417 elsif Ada_Version
< Ada_2005
16418 and then (Is_Abstract_Subprogram
(Alias
(New_Subp
))
16419 or else (Is_Tagged_Type
(Derived_Type
)
16420 and then Etype
(New_Subp
) = Derived_Type
16421 and then No
(Actual_Subp
)))
16423 Set_Is_Abstract_Subprogram
(New_Subp
);
16425 -- AI05-0097 : an inherited operation that dispatches on result is
16426 -- abstract if the derived type is abstract, even if the parent type
16427 -- is concrete and the derived type is a null extension.
16429 elsif Has_Controlling_Result
(Alias
(New_Subp
))
16430 and then Is_Abstract_Type
(Etype
(New_Subp
))
16432 Set_Is_Abstract_Subprogram
(New_Subp
);
16434 -- Finally, if the parent type is abstract we must verify that all
16435 -- inherited operations are either non-abstract or overridden, or that
16436 -- the derived type itself is abstract (this check is performed at the
16437 -- end of a package declaration, in Check_Abstract_Overriding). A
16438 -- private overriding in the parent type will not be visible in the
16439 -- derivation if we are not in an inner package or in a child unit of
16440 -- the parent type, in which case the abstractness of the inherited
16441 -- operation is carried to the new subprogram.
16443 elsif Is_Abstract_Type
(Parent_Type
)
16444 and then not In_Open_Scopes
(Scope
(Parent_Type
))
16445 and then Is_Private_Overriding
16446 and then Is_Abstract_Subprogram
(Visible_Subp
)
16448 if No
(Actual_Subp
) then
16449 Set_Alias
(New_Subp
, Visible_Subp
);
16450 Set_Is_Abstract_Subprogram
(New_Subp
, True);
16453 -- If this is a derivation for an instance of a formal derived
16454 -- type, abstractness comes from the primitive operation of the
16455 -- actual, not from the operation inherited from the ancestor.
16457 Set_Is_Abstract_Subprogram
16458 (New_Subp
, Is_Abstract_Subprogram
(Actual_Subp
));
16462 New_Overloaded_Entity
(New_Subp
, Derived_Type
);
16464 -- Ada RM 6.1.1 (15): If a subprogram inherits nonconforming class-wide
16465 -- preconditions and the derived type is abstract, the derived operation
16466 -- is abstract as well if parent subprogram is not abstract or null.
16468 if Is_Abstract_Type
(Derived_Type
)
16469 and then Has_Non_Trivial_Precondition
(Parent_Subp
)
16470 and then Present
(Interfaces
(Derived_Type
))
16473 -- Add useful attributes of subprogram before the freeze point,
16474 -- in case freezing is delayed or there are previous errors.
16476 Set_Is_Dispatching_Operation
(New_Subp
);
16479 Iface_Prim
: constant Entity_Id
:= Covered_Interface_Op
(New_Subp
);
16482 if Present
(Iface_Prim
)
16483 and then Has_Non_Trivial_Precondition
(Iface_Prim
)
16485 Set_Is_Abstract_Subprogram
(New_Subp
);
16490 -- Check for case of a derived subprogram for the instantiation of a
16491 -- formal derived tagged type, if so mark the subprogram as dispatching
16492 -- and inherit the dispatching attributes of the actual subprogram. The
16493 -- derived subprogram is effectively renaming of the actual subprogram,
16494 -- so it needs to have the same attributes as the actual.
16496 if Present
(Actual_Subp
)
16497 and then Is_Dispatching_Operation
(Actual_Subp
)
16499 Set_Is_Dispatching_Operation
(New_Subp
);
16501 if Present
(DTC_Entity
(Actual_Subp
)) then
16502 Set_DTC_Entity
(New_Subp
, DTC_Entity
(Actual_Subp
));
16503 Set_DT_Position_Value
(New_Subp
, DT_Position
(Actual_Subp
));
16507 -- Indicate that a derived subprogram does not require a body and that
16508 -- it does not require processing of default expressions.
16510 Set_Has_Completion
(New_Subp
);
16511 Set_Default_Expressions_Processed
(New_Subp
);
16513 if Ekind
(New_Subp
) = E_Function
then
16514 Set_Mechanism
(New_Subp
, Mechanism
(Parent_Subp
));
16515 Set_Returns_By_Ref
(New_Subp
, Returns_By_Ref
(Parent_Subp
));
16518 -- Ada 2022 (AI12-0279): If a Yield aspect is specified True for a
16519 -- primitive subprogram S of a type T, then the aspect is inherited
16520 -- by the corresponding primitive subprogram of each descendant of T.
16522 if Is_Tagged_Type
(Derived_Type
)
16523 and then Is_Dispatching_Operation
(New_Subp
)
16524 and then Has_Yield_Aspect
(Alias
(New_Subp
))
16526 Set_Has_Yield_Aspect
(New_Subp
, Has_Yield_Aspect
(Alias
(New_Subp
)));
16529 Set_Is_Ada_2022_Only
(New_Subp
, Is_Ada_2022_Only
(Parent_Subp
));
16530 end Derive_Subprogram
;
16532 ------------------------
16533 -- Derive_Subprograms --
16534 ------------------------
16536 procedure Derive_Subprograms
16537 (Parent_Type
: Entity_Id
;
16538 Derived_Type
: Entity_Id
;
16539 Generic_Actual
: Entity_Id
:= Empty
)
16541 Op_List
: constant Elist_Id
:=
16542 Collect_Primitive_Operations
(Parent_Type
);
16544 function Check_Derived_Type
return Boolean;
16545 -- Check that all the entities derived from Parent_Type are found in
16546 -- the list of primitives of Derived_Type exactly in the same order.
16548 procedure Derive_Interface_Subprogram
16549 (New_Subp
: out Entity_Id
;
16551 Actual_Subp
: Entity_Id
);
16552 -- Derive New_Subp from the ultimate alias of the parent subprogram Subp
16553 -- (which is an interface primitive). If Generic_Actual is present then
16554 -- Actual_Subp is the actual subprogram corresponding with the generic
16555 -- subprogram Subp.
16557 ------------------------
16558 -- Check_Derived_Type --
16559 ------------------------
16561 function Check_Derived_Type
return Boolean is
16563 Derived_Elmt
: Elmt_Id
;
16564 Derived_Op
: Entity_Id
;
16565 Derived_Ops
: Elist_Id
;
16566 Parent_Elmt
: Elmt_Id
;
16567 Parent_Op
: Entity_Id
;
16570 -- Traverse list of entities in the current scope searching for
16571 -- an incomplete type whose full-view is derived type.
16573 E
:= First_Entity
(Scope
(Derived_Type
));
16574 while Present
(E
) and then E
/= Derived_Type
loop
16575 if Ekind
(E
) = E_Incomplete_Type
16576 and then Present
(Full_View
(E
))
16577 and then Full_View
(E
) = Derived_Type
16579 -- Disable this test if Derived_Type completes an incomplete
16580 -- type because in such case more primitives can be added
16581 -- later to the list of primitives of Derived_Type by routine
16582 -- Process_Incomplete_Dependents.
16590 Derived_Ops
:= Collect_Primitive_Operations
(Derived_Type
);
16592 Derived_Elmt
:= First_Elmt
(Derived_Ops
);
16593 Parent_Elmt
:= First_Elmt
(Op_List
);
16594 while Present
(Parent_Elmt
) loop
16595 Parent_Op
:= Node
(Parent_Elmt
);
16596 Derived_Op
:= Node
(Derived_Elmt
);
16598 -- At this early stage Derived_Type has no entities with attribute
16599 -- Interface_Alias. In addition, such primitives are always
16600 -- located at the end of the list of primitives of Parent_Type.
16601 -- Therefore, if found we can safely stop processing pending
16604 exit when Present
(Interface_Alias
(Parent_Op
));
16606 -- Handle hidden entities
16608 if not Is_Predefined_Dispatching_Operation
(Parent_Op
)
16609 and then Is_Hidden
(Parent_Op
)
16611 if Present
(Derived_Op
)
16612 and then Primitive_Names_Match
(Parent_Op
, Derived_Op
)
16614 Next_Elmt
(Derived_Elmt
);
16619 or else Ekind
(Parent_Op
) /= Ekind
(Derived_Op
)
16620 or else not Primitive_Names_Match
(Parent_Op
, Derived_Op
)
16625 Next_Elmt
(Derived_Elmt
);
16628 Next_Elmt
(Parent_Elmt
);
16632 end Check_Derived_Type
;
16634 ---------------------------------
16635 -- Derive_Interface_Subprogram --
16636 ---------------------------------
16638 procedure Derive_Interface_Subprogram
16639 (New_Subp
: out Entity_Id
;
16641 Actual_Subp
: Entity_Id
)
16643 Iface_Subp
: constant Entity_Id
:= Ultimate_Alias
(Subp
);
16644 Iface_Type
: constant Entity_Id
:= Find_Dispatching_Type
(Iface_Subp
);
16647 pragma Assert
(Is_Interface
(Iface_Type
));
16650 (New_Subp
=> New_Subp
,
16651 Parent_Subp
=> Iface_Subp
,
16652 Derived_Type
=> Derived_Type
,
16653 Parent_Type
=> Iface_Type
,
16654 Actual_Subp
=> Actual_Subp
);
16656 -- Given that this new interface entity corresponds with a primitive
16657 -- of the parent that was not overridden we must leave it associated
16658 -- with its parent primitive to ensure that it will share the same
16659 -- dispatch table slot when overridden. We must set the Alias to Subp
16660 -- (instead of Iface_Subp), and we must fix Is_Abstract_Subprogram
16661 -- (in case we inherited Subp from Iface_Type via a nonabstract
16662 -- generic formal type).
16664 if No
(Actual_Subp
) then
16665 Set_Alias
(New_Subp
, Subp
);
16668 T
: Entity_Id
:= Find_Dispatching_Type
(Subp
);
16670 while Etype
(T
) /= T
loop
16671 if Is_Generic_Type
(T
) and then not Is_Abstract_Type
(T
) then
16672 Set_Is_Abstract_Subprogram
(New_Subp
, False);
16680 -- For instantiations this is not needed since the previous call to
16681 -- Derive_Subprogram leaves the entity well decorated.
16684 pragma Assert
(Alias
(New_Subp
) = Actual_Subp
);
16687 end Derive_Interface_Subprogram
;
16691 Alias_Subp
: Entity_Id
;
16692 Act_List
: Elist_Id
;
16693 Act_Elmt
: Elmt_Id
;
16694 Act_Subp
: Entity_Id
:= Empty
;
16696 Need_Search
: Boolean := False;
16697 New_Subp
: Entity_Id
;
16698 Parent_Base
: Entity_Id
;
16701 -- Start of processing for Derive_Subprograms
16704 if Ekind
(Parent_Type
) = E_Record_Type_With_Private
16705 and then Has_Discriminants
(Parent_Type
)
16706 and then Present
(Full_View
(Parent_Type
))
16708 Parent_Base
:= Full_View
(Parent_Type
);
16710 Parent_Base
:= Parent_Type
;
16713 if Present
(Generic_Actual
) then
16714 Act_List
:= Collect_Primitive_Operations
(Generic_Actual
);
16715 Act_Elmt
:= First_Elmt
(Act_List
);
16717 Act_List
:= No_Elist
;
16718 Act_Elmt
:= No_Elmt
;
16721 -- Derive primitives inherited from the parent. Note that if the generic
16722 -- actual is present, this is not really a type derivation, it is a
16723 -- completion within an instance.
16725 -- Case 1: Derived_Type does not implement interfaces
16727 if not Is_Tagged_Type
(Derived_Type
)
16728 or else (not Has_Interfaces
(Derived_Type
)
16729 and then not (Present
(Generic_Actual
)
16730 and then Has_Interfaces
(Generic_Actual
)))
16732 Elmt
:= First_Elmt
(Op_List
);
16733 while Present
(Elmt
) loop
16734 Subp
:= Node
(Elmt
);
16736 -- Literals are derived earlier in the process of building the
16737 -- derived type, and are skipped here.
16739 if Ekind
(Subp
) = E_Enumeration_Literal
then
16742 -- The actual is a direct descendant and the common primitive
16743 -- operations appear in the same order.
16745 -- If the generic parent type is present, the derived type is an
16746 -- instance of a formal derived type, and within the instance its
16747 -- operations are those of the actual. We derive from the formal
16748 -- type but make the inherited operations aliases of the
16749 -- corresponding operations of the actual.
16752 pragma Assert
(No
(Node
(Act_Elmt
))
16753 or else (Primitive_Names_Match
(Subp
, Node
(Act_Elmt
))
16756 (Subp
, Node
(Act_Elmt
),
16757 Skip_Controlling_Formals
=> True)));
16760 (New_Subp
, Subp
, Derived_Type
, Parent_Base
, Node
(Act_Elmt
));
16762 if Present
(Act_Elmt
) then
16763 Next_Elmt
(Act_Elmt
);
16770 -- Case 2: Derived_Type implements interfaces
16773 -- If the parent type has no predefined primitives we remove
16774 -- predefined primitives from the list of primitives of generic
16775 -- actual to simplify the complexity of this algorithm.
16777 if Present
(Generic_Actual
) then
16779 Has_Predefined_Primitives
: Boolean := False;
16782 -- Check if the parent type has predefined primitives
16784 Elmt
:= First_Elmt
(Op_List
);
16785 while Present
(Elmt
) loop
16786 Subp
:= Node
(Elmt
);
16788 if Is_Predefined_Dispatching_Operation
(Subp
)
16789 and then not Comes_From_Source
(Ultimate_Alias
(Subp
))
16791 Has_Predefined_Primitives
:= True;
16798 -- Remove predefined primitives of Generic_Actual. We must use
16799 -- an auxiliary list because in case of tagged types the value
16800 -- returned by Collect_Primitive_Operations is the value stored
16801 -- in its Primitive_Operations attribute (and we don't want to
16802 -- modify its current contents).
16804 if not Has_Predefined_Primitives
then
16806 Aux_List
: constant Elist_Id
:= New_Elmt_List
;
16809 Elmt
:= First_Elmt
(Act_List
);
16810 while Present
(Elmt
) loop
16811 Subp
:= Node
(Elmt
);
16813 if not Is_Predefined_Dispatching_Operation
(Subp
)
16814 or else Comes_From_Source
(Subp
)
16816 Append_Elmt
(Subp
, Aux_List
);
16822 Act_List
:= Aux_List
;
16826 Act_Elmt
:= First_Elmt
(Act_List
);
16827 Act_Subp
:= Node
(Act_Elmt
);
16831 -- Stage 1: If the generic actual is not present we derive the
16832 -- primitives inherited from the parent type. If the generic parent
16833 -- type is present, the derived type is an instance of a formal
16834 -- derived type, and within the instance its operations are those of
16835 -- the actual. We derive from the formal type but make the inherited
16836 -- operations aliases of the corresponding operations of the actual.
16838 Elmt
:= First_Elmt
(Op_List
);
16839 while Present
(Elmt
) loop
16840 Subp
:= Node
(Elmt
);
16841 Alias_Subp
:= Ultimate_Alias
(Subp
);
16843 -- Do not derive internal entities of the parent that link
16844 -- interface primitives with their covering primitive. These
16845 -- entities will be added to this type when frozen.
16847 if Present
(Interface_Alias
(Subp
)) then
16851 -- If the generic actual is present find the corresponding
16852 -- operation in the generic actual. If the parent type is a
16853 -- direct ancestor of the derived type then, even if it is an
16854 -- interface, the operations are inherited from the primary
16855 -- dispatch table and are in the proper order. If we detect here
16856 -- that primitives are not in the same order we traverse the list
16857 -- of primitive operations of the actual to find the one that
16858 -- implements the interface primitive.
16862 (Present
(Generic_Actual
)
16863 and then Present
(Act_Subp
)
16865 (Primitive_Names_Match
(Subp
, Act_Subp
)
16867 Type_Conformant
(Subp
, Act_Subp
,
16868 Skip_Controlling_Formals
=> True)))
16870 pragma Assert
(not Is_Ancestor
(Parent_Base
, Generic_Actual
,
16871 Use_Full_View
=> True));
16873 -- Remember that we need searching for all pending primitives
16875 Need_Search
:= True;
16877 -- Handle entities associated with interface primitives
16879 if Present
(Alias_Subp
)
16880 and then Is_Interface
(Find_Dispatching_Type
(Alias_Subp
))
16881 and then not Is_Predefined_Dispatching_Operation
(Subp
)
16883 -- Search for the primitive in the homonym chain
16886 Find_Primitive_Covering_Interface
16887 (Tagged_Type
=> Generic_Actual
,
16888 Iface_Prim
=> Alias_Subp
);
16890 -- Previous search may not locate primitives covering
16891 -- interfaces defined in generics units or instantiations.
16892 -- (it fails if the covering primitive has formals whose
16893 -- type is also defined in generics or instantiations).
16894 -- In such case we search in the list of primitives of the
16895 -- generic actual for the internal entity that links the
16896 -- interface primitive and the covering primitive.
16899 and then Is_Generic_Type
(Parent_Type
)
16901 -- This code has been designed to handle only generic
16902 -- formals that implement interfaces that are defined
16903 -- in a generic unit or instantiation. If this code is
16904 -- needed for other cases we must review it because
16905 -- (given that it relies on Original_Location to locate
16906 -- the primitive of Generic_Actual that covers the
16907 -- interface) it could leave linked through attribute
16908 -- Alias entities of unrelated instantiations).
16912 (Scope
(Find_Dispatching_Type
(Alias_Subp
)))
16914 Instantiation_Location
16915 (Sloc
(Find_Dispatching_Type
(Alias_Subp
)))
16918 Iface_Prim_Loc
: constant Source_Ptr
:=
16919 Original_Location
(Sloc
(Alias_Subp
));
16926 First_Elmt
(Primitive_Operations
(Generic_Actual
));
16928 Search
: while Present
(Elmt
) loop
16929 Prim
:= Node
(Elmt
);
16931 if Present
(Interface_Alias
(Prim
))
16932 and then Original_Location
16933 (Sloc
(Interface_Alias
(Prim
))) =
16936 Act_Subp
:= Alias
(Prim
);
16945 pragma Assert
(Present
(Act_Subp
)
16946 or else Is_Abstract_Type
(Generic_Actual
)
16947 or else Serious_Errors_Detected
> 0);
16949 -- Handle predefined primitives plus the rest of user-defined
16953 Act_Elmt
:= First_Elmt
(Act_List
);
16954 while Present
(Act_Elmt
) loop
16955 Act_Subp
:= Node
(Act_Elmt
);
16957 exit when Primitive_Names_Match
(Subp
, Act_Subp
)
16958 and then Type_Conformant
16960 Skip_Controlling_Formals
=> True)
16961 and then No
(Interface_Alias
(Act_Subp
));
16963 Next_Elmt
(Act_Elmt
);
16966 if No
(Act_Elmt
) then
16972 -- Case 1: If the parent is a limited interface then it has the
16973 -- predefined primitives of synchronized interfaces. However, the
16974 -- actual type may be a non-limited type and hence it does not
16975 -- have such primitives.
16977 if Present
(Generic_Actual
)
16978 and then No
(Act_Subp
)
16979 and then Is_Limited_Interface
(Parent_Base
)
16980 and then Is_Predefined_Interface_Primitive
(Subp
)
16984 -- Case 2: Inherit entities associated with interfaces that were
16985 -- not covered by the parent type. We exclude here null interface
16986 -- primitives because they do not need special management.
16988 -- We also exclude interface operations that are renamings. If the
16989 -- subprogram is an explicit renaming of an interface primitive,
16990 -- it is a regular primitive operation, and the presence of its
16991 -- alias is not relevant: it has to be derived like any other
16994 elsif Present
(Alias
(Subp
))
16995 and then Nkind
(Unit_Declaration_Node
(Subp
)) /=
16996 N_Subprogram_Renaming_Declaration
16997 and then Is_Interface
(Find_Dispatching_Type
(Alias_Subp
))
16999 (Nkind
(Parent
(Alias_Subp
)) = N_Procedure_Specification
17000 and then Null_Present
(Parent
(Alias_Subp
)))
17002 -- If this is an abstract private type then we transfer the
17003 -- derivation of the interface primitive from the partial view
17004 -- to the full view. This is safe because all the interfaces
17005 -- must be visible in the partial view. Done to avoid adding
17006 -- a new interface derivation to the private part of the
17007 -- enclosing package; otherwise this new derivation would be
17008 -- decorated as hidden when the analysis of the enclosing
17009 -- package completes.
17011 if Is_Abstract_Type
(Derived_Type
)
17012 and then In_Private_Part
(Current_Scope
)
17013 and then Has_Private_Declaration
(Derived_Type
)
17016 Partial_View
: Entity_Id
;
17021 Partial_View
:= First_Entity
(Current_Scope
);
17023 exit when No
(Partial_View
)
17024 or else (Has_Private_Declaration
(Partial_View
)
17026 Full_View
(Partial_View
) = Derived_Type
);
17028 Next_Entity
(Partial_View
);
17031 -- If the partial view was not found then the source code
17032 -- has errors and the derivation is not needed.
17034 if Present
(Partial_View
) then
17036 First_Elmt
(Primitive_Operations
(Partial_View
));
17037 while Present
(Elmt
) loop
17038 Ent
:= Node
(Elmt
);
17040 if Present
(Alias
(Ent
))
17041 and then Ultimate_Alias
(Ent
) = Alias
(Subp
)
17044 (Ent
, Primitive_Operations
(Derived_Type
));
17051 -- If the interface primitive was not found in the
17052 -- partial view then this interface primitive was
17053 -- overridden. We add a derivation to activate in
17054 -- Derive_Progenitor_Subprograms the machinery to
17058 Derive_Interface_Subprogram
17059 (New_Subp
=> New_Subp
,
17061 Actual_Subp
=> Act_Subp
);
17066 Derive_Interface_Subprogram
17067 (New_Subp
=> New_Subp
,
17069 Actual_Subp
=> Act_Subp
);
17072 -- Case 3: Common derivation
17076 (New_Subp
=> New_Subp
,
17077 Parent_Subp
=> Subp
,
17078 Derived_Type
=> Derived_Type
,
17079 Parent_Type
=> Parent_Base
,
17080 Actual_Subp
=> Act_Subp
);
17083 -- No need to update Act_Elm if we must search for the
17084 -- corresponding operation in the generic actual
17087 and then Present
(Act_Elmt
)
17089 Next_Elmt
(Act_Elmt
);
17090 Act_Subp
:= Node
(Act_Elmt
);
17097 -- Inherit additional operations from progenitors. If the derived
17098 -- type is a generic actual, there are not new primitive operations
17099 -- for the type because it has those of the actual, and therefore
17100 -- nothing needs to be done. The renamings generated above are not
17101 -- primitive operations, and their purpose is simply to make the
17102 -- proper operations visible within an instantiation.
17104 if No
(Generic_Actual
) then
17105 Derive_Progenitor_Subprograms
(Parent_Base
, Derived_Type
);
17109 -- Final check: Direct descendants must have their primitives in the
17110 -- same order. We exclude from this test untagged types and instances
17111 -- of formal derived types. We skip this test if we have already
17112 -- reported serious errors in the sources.
17114 pragma Assert
(not Is_Tagged_Type
(Derived_Type
)
17115 or else Present
(Generic_Actual
)
17116 or else Serious_Errors_Detected
> 0
17117 or else Check_Derived_Type
);
17118 end Derive_Subprograms
;
17120 --------------------------------
17121 -- Derived_Standard_Character --
17122 --------------------------------
17124 procedure Derived_Standard_Character
17126 Parent_Type
: Entity_Id
;
17127 Derived_Type
: Entity_Id
)
17129 Loc
: constant Source_Ptr
:= Sloc
(N
);
17130 Def
: constant Node_Id
:= Type_Definition
(N
);
17131 Indic
: constant Node_Id
:= Subtype_Indication
(Def
);
17132 Parent_Base
: constant Entity_Id
:= Base_Type
(Parent_Type
);
17133 Implicit_Base
: constant Entity_Id
:=
17135 (E_Enumeration_Type
, N
, Derived_Type
, 'B');
17141 Discard_Node
(Process_Subtype
(Indic
, N
));
17143 Set_Etype
(Implicit_Base
, Parent_Base
);
17144 Set_Size_Info
(Implicit_Base
, Root_Type
(Parent_Type
));
17145 Set_RM_Size
(Implicit_Base
, RM_Size
(Root_Type
(Parent_Type
)));
17147 Set_Is_Character_Type
(Implicit_Base
, True);
17148 Set_Has_Delayed_Freeze
(Implicit_Base
);
17150 -- The bounds of the implicit base are the bounds of the parent base.
17151 -- Note that their type is the parent base.
17153 Lo
:= New_Copy_Tree
(Type_Low_Bound
(Parent_Base
));
17154 Hi
:= New_Copy_Tree
(Type_High_Bound
(Parent_Base
));
17156 Set_Scalar_Range
(Implicit_Base
,
17159 High_Bound
=> Hi
));
17161 Mutate_Ekind
(Derived_Type
, E_Enumeration_Subtype
);
17162 Set_Etype
(Derived_Type
, Implicit_Base
);
17163 Set_Size_Info
(Derived_Type
, Parent_Type
);
17165 if not Known_RM_Size
(Derived_Type
) then
17166 Set_RM_Size
(Derived_Type
, RM_Size
(Parent_Type
));
17169 Set_Is_Character_Type
(Derived_Type
, True);
17171 if Nkind
(Indic
) /= N_Subtype_Indication
then
17173 -- If no explicit constraint, the bounds are those
17174 -- of the parent type.
17176 Lo
:= New_Copy_Tree
(Type_Low_Bound
(Parent_Type
));
17177 Hi
:= New_Copy_Tree
(Type_High_Bound
(Parent_Type
));
17178 Set_Scalar_Range
(Derived_Type
, Make_Range
(Loc
, Lo
, Hi
));
17181 Convert_Scalar_Bounds
(N
, Parent_Type
, Derived_Type
, Loc
);
17182 end Derived_Standard_Character
;
17184 ------------------------------
17185 -- Derived_Type_Declaration --
17186 ------------------------------
17188 procedure Derived_Type_Declaration
17191 Is_Completion
: Boolean)
17193 Parent_Type
: Entity_Id
;
17195 function Comes_From_Generic
(Typ
: Entity_Id
) return Boolean;
17196 -- Check whether the parent type is a generic formal, or derives
17197 -- directly or indirectly from one.
17199 ------------------------
17200 -- Comes_From_Generic --
17201 ------------------------
17203 function Comes_From_Generic
(Typ
: Entity_Id
) return Boolean is
17205 if Is_Generic_Type
(Typ
) then
17208 elsif Is_Generic_Type
(Root_Type
(Parent_Type
)) then
17211 elsif Is_Private_Type
(Typ
)
17212 and then Present
(Full_View
(Typ
))
17213 and then Is_Generic_Type
(Root_Type
(Full_View
(Typ
)))
17217 elsif Is_Generic_Actual_Type
(Typ
) then
17223 end Comes_From_Generic
;
17227 Def
: constant Node_Id
:= Type_Definition
(N
);
17228 Iface_Def
: Node_Id
;
17229 Indic
: constant Node_Id
:= Subtype_Indication
(Def
);
17230 Extension
: constant Node_Id
:= Record_Extension_Part
(Def
);
17231 Parent_Node
: Node_Id
;
17234 -- Start of processing for Derived_Type_Declaration
17237 Parent_Type
:= Find_Type_Of_Subtype_Indic
(Indic
);
17240 and then Is_Tagged_Type
(Parent_Type
)
17243 Partial_View
: constant Entity_Id
:=
17244 Incomplete_Or_Partial_View
(Parent_Type
);
17247 -- If the partial view was not found then the parent type is not
17248 -- a private type. Otherwise check if the partial view is a tagged
17251 if Present
(Partial_View
)
17252 and then Is_Private_Type
(Partial_View
)
17253 and then not Is_Tagged_Type
(Partial_View
)
17256 ("cannot derive from & declared as untagged private "
17257 & "(SPARK RM 3.4(1))", N
, Partial_View
);
17262 -- Ada 2005 (AI-251): In case of interface derivation check that the
17263 -- parent is also an interface.
17265 if Interface_Present
(Def
) then
17266 if not Is_Interface
(Parent_Type
) then
17267 Diagnose_Interface
(Indic
, Parent_Type
);
17270 Parent_Node
:= Parent
(Base_Type
(Parent_Type
));
17271 Iface_Def
:= Type_Definition
(Parent_Node
);
17273 -- Ada 2005 (AI-251): Limited interfaces can only inherit from
17274 -- other limited interfaces.
17276 if Limited_Present
(Def
) then
17277 if Limited_Present
(Iface_Def
) then
17280 elsif Protected_Present
(Iface_Def
) then
17282 ("descendant of & must be declared as a protected "
17283 & "interface", N
, Parent_Type
);
17285 elsif Synchronized_Present
(Iface_Def
) then
17287 ("descendant of & must be declared as a synchronized "
17288 & "interface", N
, Parent_Type
);
17290 elsif Task_Present
(Iface_Def
) then
17292 ("descendant of & must be declared as a task interface",
17297 ("(Ada 2005) limited interface cannot inherit from "
17298 & "non-limited interface", Indic
);
17301 -- Ada 2005 (AI-345): Non-limited interfaces can only inherit
17302 -- from non-limited or limited interfaces.
17304 elsif not Protected_Present
(Def
)
17305 and then not Synchronized_Present
(Def
)
17306 and then not Task_Present
(Def
)
17308 if Limited_Present
(Iface_Def
) then
17311 elsif Protected_Present
(Iface_Def
) then
17313 ("descendant of & must be declared as a protected "
17314 & "interface", N
, Parent_Type
);
17316 elsif Synchronized_Present
(Iface_Def
) then
17318 ("descendant of & must be declared as a synchronized "
17319 & "interface", N
, Parent_Type
);
17321 elsif Task_Present
(Iface_Def
) then
17323 ("descendant of & must be declared as a task interface",
17332 if Is_Tagged_Type
(Parent_Type
)
17333 and then Is_Concurrent_Type
(Parent_Type
)
17334 and then not Is_Interface
(Parent_Type
)
17337 ("parent type of a record extension cannot be a synchronized "
17338 & "tagged type (RM 3.9.1 (3/1))", N
);
17339 Set_Etype
(T
, Any_Type
);
17343 -- Ada 2005 (AI-251): Decorate all the names in the list of ancestor
17346 if Is_Tagged_Type
(Parent_Type
)
17347 and then Is_Non_Empty_List
(Interface_List
(Def
))
17354 Intf
:= First
(Interface_List
(Def
));
17355 while Present
(Intf
) loop
17356 T
:= Find_Type_Of_Subtype_Indic
(Intf
);
17358 if not Is_Interface
(T
) then
17359 Diagnose_Interface
(Intf
, T
);
17361 -- Check the rules of 3.9.4(12/2) and 7.5(2/2) that disallow
17362 -- a limited type from having a nonlimited progenitor.
17364 elsif (Limited_Present
(Def
)
17365 or else (not Is_Interface
(Parent_Type
)
17366 and then Is_Limited_Type
(Parent_Type
)))
17367 and then not Is_Limited_Interface
(T
)
17370 ("progenitor interface& of limited type must be limited",
17378 -- Check consistency of any nonoverridable aspects that are
17379 -- inherited from multiple sources.
17381 Check_Inherited_Nonoverridable_Aspects
17383 Interface_List
=> Interface_List
(Def
),
17384 Parent_Type
=> Parent_Type
);
17387 if Parent_Type
= Any_Type
17388 or else Etype
(Parent_Type
) = Any_Type
17389 or else (Is_Class_Wide_Type
(Parent_Type
)
17390 and then Etype
(Parent_Type
) = T
)
17392 -- If Parent_Type is undefined or illegal, make new type into a
17393 -- subtype of Any_Type, and set a few attributes to prevent cascaded
17394 -- errors. If this is a self-definition, emit error now.
17396 if T
= Parent_Type
or else T
= Etype
(Parent_Type
) then
17397 Error_Msg_N
("type cannot be used in its own definition", Indic
);
17400 Mutate_Ekind
(T
, Ekind
(Parent_Type
));
17401 Set_Etype
(T
, Any_Type
);
17402 Set_Scalar_Range
(T
, Scalar_Range
(Any_Type
));
17404 -- Initialize the list of primitive operations to an empty list,
17405 -- to cover tagged types as well as untagged types. For untagged
17406 -- types this is used either to analyze the call as legal when
17407 -- Extensions_Allowed is True, or to issue a better error message
17410 Set_Direct_Primitive_Operations
(T
, New_Elmt_List
);
17415 -- Ada 2005 (AI-251): The case in which the parent of the full-view is
17416 -- an interface is special because the list of interfaces in the full
17417 -- view can be given in any order. For example:
17419 -- type A is interface;
17420 -- type B is interface and A;
17421 -- type D is new B with private;
17423 -- type D is new A and B with null record; -- 1 --
17425 -- In this case we perform the following transformation of -1-:
17427 -- type D is new B and A with null record;
17429 -- If the parent of the full-view covers the parent of the partial-view
17430 -- we have two possible cases:
17432 -- 1) They have the same parent
17433 -- 2) The parent of the full-view implements some further interfaces
17435 -- In both cases we do not need to perform the transformation. In the
17436 -- first case the source program is correct and the transformation is
17437 -- not needed; in the second case the source program does not fulfill
17438 -- the no-hidden interfaces rule (AI-396) and the error will be reported
17441 -- This transformation not only simplifies the rest of the analysis of
17442 -- this type declaration but also simplifies the correct generation of
17443 -- the object layout to the expander.
17445 if In_Private_Part
(Current_Scope
)
17446 and then Is_Interface
(Parent_Type
)
17449 Partial_View
: Entity_Id
;
17450 Partial_View_Parent
: Entity_Id
;
17452 function Reorder_Interfaces
return Boolean;
17453 -- Look for an interface in the full view's interface list that
17454 -- matches the parent type of the partial view, and when found,
17455 -- rewrite the full view's parent with the partial view's parent,
17456 -- append the full view's original parent to the interface list,
17457 -- recursively call Derived_Type_Definition on the full type, and
17458 -- return True. If a match is not found, return False.
17460 ------------------------
17461 -- Reorder_Interfaces --
17462 ------------------------
17464 function Reorder_Interfaces
return Boolean is
17466 New_Iface
: Node_Id
;
17469 Iface
:= First
(Interface_List
(Def
));
17470 while Present
(Iface
) loop
17471 if Etype
(Iface
) = Etype
(Partial_View
) then
17472 Rewrite
(Subtype_Indication
(Def
),
17473 New_Copy
(Subtype_Indication
(Parent
(Partial_View
))));
17476 Make_Identifier
(Sloc
(N
), Chars
(Parent_Type
));
17477 Rewrite
(Iface
, New_Iface
);
17479 -- Analyze the transformed code
17481 Derived_Type_Declaration
(T
, N
, Is_Completion
);
17488 end Reorder_Interfaces
;
17491 -- Look for the associated private type declaration
17493 Partial_View
:= Incomplete_Or_Partial_View
(T
);
17495 -- If the partial view was not found then the source code has
17496 -- errors and the transformation is not needed.
17498 if Present
(Partial_View
) then
17499 Partial_View_Parent
:= Etype
(Partial_View
);
17501 -- If the parent of the full-view covers the parent of the
17502 -- partial-view we have nothing else to do.
17504 if Interface_Present_In_Ancestor
17505 (Parent_Type
, Partial_View_Parent
)
17509 -- Traverse the list of interfaces of the full view to look
17510 -- for the parent of the partial view and reorder the
17511 -- interfaces to match the order in the partial view,
17516 if Reorder_Interfaces
then
17517 -- Having the interfaces listed in any order is legal.
17518 -- However, the compiler does not properly handle
17519 -- different orders between partial and full views in
17520 -- generic units. We give a warning about the order
17521 -- mismatch, so the user can work around this problem.
17523 Error_Msg_N
("??full declaration does not respect " &
17524 "partial declaration order", T
);
17525 Error_Msg_N
("\??consider reordering", T
);
17534 -- Only composite types other than array types are allowed to have
17537 if Present
(Discriminant_Specifications
(N
)) then
17538 if (Is_Elementary_Type
(Parent_Type
)
17540 Is_Array_Type
(Parent_Type
))
17541 and then not Error_Posted
(N
)
17544 ("elementary or array type cannot have discriminants",
17545 Defining_Identifier
(First
(Discriminant_Specifications
(N
))));
17547 -- Unset Has_Discriminants flag to prevent cascaded errors, but
17548 -- only if we are not already processing a malformed syntax tree.
17550 if Is_Type
(T
) then
17551 Set_Has_Discriminants
(T
, False);
17556 -- In Ada 83, a derived type defined in a package specification cannot
17557 -- be used for further derivation until the end of its visible part.
17558 -- Note that derivation in the private part of the package is allowed.
17560 if Ada_Version
= Ada_83
17561 and then Is_Derived_Type
(Parent_Type
)
17562 and then In_Visible_Part
(Scope
(Parent_Type
))
17564 if Ada_Version
= Ada_83
and then Comes_From_Source
(Indic
) then
17566 ("(Ada 83) premature use of type for derivation", Indic
);
17570 -- Check for early use of incomplete or private type
17572 if Ekind
(Parent_Type
) in E_Void | E_Incomplete_Type
then
17573 Error_Msg_N
("premature derivation of incomplete type", Indic
);
17576 elsif (Is_Incomplete_Or_Private_Type
(Parent_Type
)
17577 and then not Comes_From_Generic
(Parent_Type
))
17578 or else Has_Private_Component
(Parent_Type
)
17580 -- The ancestor type of a formal type can be incomplete, in which
17581 -- case only the operations of the partial view are available in the
17582 -- generic. Subsequent checks may be required when the full view is
17583 -- analyzed to verify that a derivation from a tagged type has an
17586 if Nkind
(Original_Node
(N
)) = N_Formal_Type_Declaration
then
17589 elsif No
(Underlying_Type
(Parent_Type
))
17590 or else Has_Private_Component
(Parent_Type
)
17593 ("premature derivation of derived or private type", Indic
);
17595 -- Flag the type itself as being in error, this prevents some
17596 -- nasty problems with subsequent uses of the malformed type.
17598 Set_Error_Posted
(T
);
17600 -- Check that within the immediate scope of an untagged partial
17601 -- view it's illegal to derive from the partial view if the
17602 -- full view is tagged. (7.3(7))
17604 -- We verify that the Parent_Type is a partial view by checking
17605 -- that it is not a Full_Type_Declaration (i.e. a private type or
17606 -- private extension declaration), to distinguish a partial view
17607 -- from a derivation from a private type which also appears as
17608 -- E_Private_Type. If the parent base type is not declared in an
17609 -- enclosing scope there is no need to check.
17611 elsif Present
(Full_View
(Parent_Type
))
17612 and then Nkind
(Parent
(Parent_Type
)) /= N_Full_Type_Declaration
17613 and then not Is_Tagged_Type
(Parent_Type
)
17614 and then Is_Tagged_Type
(Full_View
(Parent_Type
))
17615 and then In_Open_Scopes
(Scope
(Base_Type
(Parent_Type
)))
17618 ("premature derivation from type with tagged full view",
17623 -- Check that form of derivation is appropriate
17625 Taggd
:= Is_Tagged_Type
(Parent_Type
);
17627 -- Set the parent type to the class-wide type's specific type in this
17628 -- case to prevent cascading errors
17630 if Present
(Extension
) and then Is_Class_Wide_Type
(Parent_Type
) then
17631 Error_Msg_N
("parent type must not be a class-wide type", Indic
);
17632 Set_Etype
(T
, Etype
(Parent_Type
));
17636 if Present
(Extension
) and then not Taggd
then
17638 ("type derived from untagged type cannot have extension", Indic
);
17640 elsif No
(Extension
) and then Taggd
then
17642 -- If this declaration is within a private part (or body) of a
17643 -- generic instantiation then the derivation is allowed (the parent
17644 -- type can only appear tagged in this case if it's a generic actual
17645 -- type, since it would otherwise have been rejected in the analysis
17646 -- of the generic template).
17648 if not Is_Generic_Actual_Type
(Parent_Type
)
17649 or else In_Visible_Part
(Scope
(Parent_Type
))
17651 if Is_Class_Wide_Type
(Parent_Type
) then
17653 ("parent type must not be a class-wide type", Indic
);
17655 -- Use specific type to prevent cascaded errors.
17657 Parent_Type
:= Etype
(Parent_Type
);
17661 ("type derived from tagged type must have extension", Indic
);
17666 -- AI-443: Synchronized formal derived types require a private
17667 -- extension. There is no point in checking the ancestor type or
17668 -- the progenitors since the construct is wrong to begin with.
17670 if Ada_Version
>= Ada_2005
17671 and then Is_Generic_Type
(T
)
17672 and then Present
(Original_Node
(N
))
17675 Decl
: constant Node_Id
:= Original_Node
(N
);
17678 if Nkind
(Decl
) = N_Formal_Type_Declaration
17679 and then Nkind
(Formal_Type_Definition
(Decl
)) =
17680 N_Formal_Derived_Type_Definition
17681 and then Synchronized_Present
(Formal_Type_Definition
(Decl
))
17682 and then No
(Extension
)
17684 -- Avoid emitting a duplicate error message
17686 and then not Error_Posted
(Indic
)
17689 ("synchronized derived type must have extension", N
);
17694 if Null_Exclusion_Present
(Def
)
17695 and then not Is_Access_Type
(Parent_Type
)
17697 Error_Msg_N
("null exclusion can only apply to an access type", N
);
17700 Check_Wide_Character_Restriction
(Parent_Type
, Indic
);
17702 -- Avoid deriving parent primitives of underlying record views
17704 Set_Is_Not_Self_Hidden
(T
);
17706 Build_Derived_Type
(N
, Parent_Type
, T
, Is_Completion
,
17707 Derive_Subps
=> not Is_Underlying_Record_View
(T
));
17709 -- AI-419: The parent type of an explicitly limited derived type must
17710 -- be a limited type or a limited interface.
17712 if Limited_Present
(Def
) then
17713 Set_Is_Limited_Record
(T
);
17715 if Is_Interface
(T
) then
17716 Set_Is_Limited_Interface
(T
);
17719 if not Is_Limited_Type
(Parent_Type
)
17721 (not Is_Interface
(Parent_Type
)
17722 or else not Is_Limited_Interface
(Parent_Type
))
17724 -- AI05-0096: a derivation in the private part of an instance is
17725 -- legal if the generic formal is untagged limited, and the actual
17728 if Is_Generic_Actual_Type
(Parent_Type
)
17729 and then In_Private_Part
(Current_Scope
)
17732 (Generic_Parent_Type
(Parent
(Parent_Type
)))
17738 ("parent type& of limited type must be limited",
17743 end Derived_Type_Declaration
;
17745 ------------------------
17746 -- Diagnose_Interface --
17747 ------------------------
17749 procedure Diagnose_Interface
(N
: Node_Id
; E
: Entity_Id
) is
17751 if not Is_Interface
(E
) and then E
/= Any_Type
then
17752 Error_Msg_NE
("(Ada 2005) & must be an interface", N
, E
);
17754 end Diagnose_Interface
;
17756 ----------------------------------
17757 -- Enumeration_Type_Declaration --
17758 ----------------------------------
17760 procedure Enumeration_Type_Declaration
(T
: Entity_Id
; Def
: Node_Id
) is
17767 -- Create identifier node representing lower bound
17769 B_Node
:= New_Node
(N_Identifier
, Sloc
(Def
));
17770 L
:= First
(Literals
(Def
));
17771 Set_Chars
(B_Node
, Chars
(L
));
17772 Set_Entity
(B_Node
, L
);
17773 Set_Etype
(B_Node
, T
);
17774 Set_Is_Static_Expression
(B_Node
, True);
17776 R_Node
:= New_Node
(N_Range
, Sloc
(Def
));
17777 Set_Low_Bound
(R_Node
, B_Node
);
17779 Mutate_Ekind
(T
, E_Enumeration_Type
);
17780 Set_First_Literal
(T
, L
);
17782 Set_Is_Constrained
(T
);
17786 -- Loop through literals of enumeration type setting pos and rep values
17787 -- except that if the Ekind is already set, then it means the literal
17788 -- was already constructed (case of a derived type declaration and we
17789 -- should not disturb the Pos and Rep values.
17791 while Present
(L
) loop
17792 if Ekind
(L
) /= E_Enumeration_Literal
then
17793 Mutate_Ekind
(L
, E_Enumeration_Literal
);
17794 Set_Is_Not_Self_Hidden
(L
);
17795 Set_Enumeration_Pos
(L
, Ev
);
17796 Set_Enumeration_Rep
(L
, Ev
);
17797 Set_Is_Known_Valid
(L
, True);
17801 New_Overloaded_Entity
(L
);
17802 Generate_Definition
(L
);
17803 Set_Convention
(L
, Convention_Intrinsic
);
17805 -- Case of character literal
17807 if Nkind
(L
) = N_Defining_Character_Literal
then
17808 Set_Is_Character_Type
(T
, True);
17810 -- Check violation of No_Wide_Characters
17812 if Restriction_Check_Required
(No_Wide_Characters
) then
17813 Get_Name_String
(Chars
(L
));
17815 if Name_Len
>= 3 and then Name_Buffer
(1 .. 2) = "QW" then
17816 Check_Restriction
(No_Wide_Characters
, L
);
17825 -- Now create a node representing upper bound
17827 B_Node
:= New_Node
(N_Identifier
, Sloc
(Def
));
17828 Set_Chars
(B_Node
, Chars
(Last
(Literals
(Def
))));
17829 Set_Entity
(B_Node
, Last
(Literals
(Def
)));
17830 Set_Etype
(B_Node
, T
);
17831 Set_Is_Static_Expression
(B_Node
, True);
17833 Set_High_Bound
(R_Node
, B_Node
);
17835 -- Initialize various fields of the type. Some of this information
17836 -- may be overwritten later through rep. clauses.
17838 Set_Scalar_Range
(T
, R_Node
);
17839 Set_RM_Size
(T
, UI_From_Int
(Minimum_Size
(T
)));
17840 Set_Enum_Esize
(T
);
17841 Set_Enum_Pos_To_Rep
(T
, Empty
);
17843 -- Set Discard_Names if configuration pragma set, or if there is
17844 -- a parameterless pragma in the current declarative region
17846 if Global_Discard_Names
or else Discard_Names
(Scope
(T
)) then
17847 Set_Discard_Names
(T
);
17850 -- Process end label if there is one
17852 if Present
(Def
) then
17853 Process_End_Label
(Def
, 'e', T
);
17855 end Enumeration_Type_Declaration
;
17857 ---------------------------------
17858 -- Expand_To_Stored_Constraint --
17859 ---------------------------------
17861 function Expand_To_Stored_Constraint
17863 Constraint
: Elist_Id
) return Elist_Id
17865 Explicitly_Discriminated_Type
: Entity_Id
;
17866 Expansion
: Elist_Id
;
17867 Discriminant
: Entity_Id
;
17869 function Type_With_Explicit_Discrims
(Id
: Entity_Id
) return Entity_Id
;
17870 -- Find the nearest type that actually specifies discriminants
17872 ---------------------------------
17873 -- Type_With_Explicit_Discrims --
17874 ---------------------------------
17876 function Type_With_Explicit_Discrims
(Id
: Entity_Id
) return Entity_Id
is
17877 Typ
: constant E
:= Base_Type
(Id
);
17880 if Ekind
(Typ
) in Incomplete_Or_Private_Kind
then
17881 if Present
(Full_View
(Typ
)) then
17882 return Type_With_Explicit_Discrims
(Full_View
(Typ
));
17886 if Has_Discriminants
(Typ
) then
17891 if Etype
(Typ
) = Typ
then
17893 elsif Has_Discriminants
(Typ
) then
17896 return Type_With_Explicit_Discrims
(Etype
(Typ
));
17899 end Type_With_Explicit_Discrims
;
17901 -- Start of processing for Expand_To_Stored_Constraint
17904 if No
(Constraint
) or else Is_Empty_Elmt_List
(Constraint
) then
17908 Explicitly_Discriminated_Type
:= Type_With_Explicit_Discrims
(Typ
);
17910 if No
(Explicitly_Discriminated_Type
) then
17914 Expansion
:= New_Elmt_List
;
17917 First_Stored_Discriminant
(Explicitly_Discriminated_Type
);
17918 while Present
(Discriminant
) loop
17920 (Get_Discriminant_Value
17921 (Discriminant
, Explicitly_Discriminated_Type
, Constraint
),
17923 Next_Stored_Discriminant
(Discriminant
);
17927 end Expand_To_Stored_Constraint
;
17929 ---------------------------
17930 -- Find_Hidden_Interface --
17931 ---------------------------
17933 function Find_Hidden_Interface
17935 Dest
: Elist_Id
) return Entity_Id
17938 Iface_Elmt
: Elmt_Id
;
17941 if Present
(Src
) and then Present
(Dest
) then
17942 Iface_Elmt
:= First_Elmt
(Src
);
17943 while Present
(Iface_Elmt
) loop
17944 Iface
:= Node
(Iface_Elmt
);
17946 if Is_Interface
(Iface
)
17947 and then not Contain_Interface
(Iface
, Dest
)
17952 Next_Elmt
(Iface_Elmt
);
17957 end Find_Hidden_Interface
;
17959 --------------------
17960 -- Find_Type_Name --
17961 --------------------
17963 function Find_Type_Name
(N
: Node_Id
) return Entity_Id
is
17964 Id
: constant Entity_Id
:= Defining_Identifier
(N
);
17965 New_Id
: Entity_Id
;
17967 Prev_Par
: Node_Id
;
17969 procedure Check_Duplicate_Aspects
;
17970 -- Check that aspects specified in a completion have not been specified
17971 -- already in the partial view.
17973 procedure Tag_Mismatch
;
17974 -- Diagnose a tagged partial view whose full view is untagged. We post
17975 -- the message on the full view, with a reference to the previous
17976 -- partial view. The partial view can be private or incomplete, and
17977 -- these are handled in a different manner, so we determine the position
17978 -- of the error message from the respective slocs of both.
17980 -----------------------------
17981 -- Check_Duplicate_Aspects --
17982 -----------------------------
17984 procedure Check_Duplicate_Aspects
is
17985 function Get_Partial_View_Aspect
(Asp
: Node_Id
) return Node_Id
;
17986 -- Return the corresponding aspect of the partial view which matches
17987 -- the aspect id of Asp. Return Empty is no such aspect exists.
17989 -----------------------------
17990 -- Get_Partial_View_Aspect --
17991 -----------------------------
17993 function Get_Partial_View_Aspect
(Asp
: Node_Id
) return Node_Id
is
17994 Asp_Id
: constant Aspect_Id
:= Get_Aspect_Id
(Asp
);
17995 Prev_Asps
: constant List_Id
:= Aspect_Specifications
(Prev_Par
);
17996 Prev_Asp
: Node_Id
;
17999 if Present
(Prev_Asps
) then
18000 Prev_Asp
:= First
(Prev_Asps
);
18001 while Present
(Prev_Asp
) loop
18002 if Get_Aspect_Id
(Prev_Asp
) = Asp_Id
then
18011 end Get_Partial_View_Aspect
;
18015 Full_Asps
: constant List_Id
:= Aspect_Specifications
(N
);
18016 Full_Asp
: Node_Id
;
18017 Part_Asp
: Node_Id
;
18019 -- Start of processing for Check_Duplicate_Aspects
18022 if Present
(Full_Asps
) then
18023 Full_Asp
:= First
(Full_Asps
);
18024 while Present
(Full_Asp
) loop
18025 Part_Asp
:= Get_Partial_View_Aspect
(Full_Asp
);
18027 -- An aspect and its class-wide counterpart are two distinct
18028 -- aspects and may apply to both views of an entity.
18030 if Present
(Part_Asp
)
18031 and then Class_Present
(Part_Asp
) = Class_Present
(Full_Asp
)
18034 ("aspect already specified in private declaration",
18041 if Has_Discriminants
(Prev
)
18042 and then not Has_Unknown_Discriminants
(Prev
)
18043 and then Get_Aspect_Id
(Full_Asp
) =
18044 Aspect_Implicit_Dereference
18047 ("cannot specify aspect if partial view has known "
18048 & "discriminants", Full_Asp
);
18054 end Check_Duplicate_Aspects
;
18060 procedure Tag_Mismatch
is
18062 if Sloc
(Prev
) < Sloc
(Id
) then
18063 if Ada_Version
>= Ada_2012
18064 and then Nkind
(N
) = N_Private_Type_Declaration
18067 ("declaration of private } must be a tagged type", Id
, Prev
);
18070 ("full declaration of } must be a tagged type", Id
, Prev
);
18074 if Ada_Version
>= Ada_2012
18075 and then Nkind
(N
) = N_Private_Type_Declaration
18078 ("declaration of private } must be a tagged type", Prev
, Id
);
18081 ("full declaration of } must be a tagged type", Prev
, Id
);
18086 -- Start of processing for Find_Type_Name
18089 -- Find incomplete declaration, if one was given
18091 Prev
:= Current_Entity_In_Scope
(Id
);
18093 -- New type declaration
18099 -- Previous declaration exists
18102 Prev_Par
:= Parent
(Prev
);
18104 -- Error if not incomplete/private case except if previous
18105 -- declaration is implicit, etc. Enter_Name will emit error if
18108 if not Is_Incomplete_Or_Private_Type
(Prev
) then
18112 -- Check invalid completion of private or incomplete type
18114 elsif Nkind
(N
) not in N_Full_Type_Declaration
18115 | N_Task_Type_Declaration
18116 | N_Protected_Type_Declaration
18118 (Ada_Version
< Ada_2012
18119 or else not Is_Incomplete_Type
(Prev
)
18120 or else Nkind
(N
) not in N_Private_Type_Declaration
18121 | N_Private_Extension_Declaration
)
18123 -- Completion must be a full type declarations (RM 7.3(4))
18125 Error_Msg_Sloc
:= Sloc
(Prev
);
18126 Error_Msg_NE
("invalid completion of }", Id
, Prev
);
18128 -- Set scope of Id to avoid cascaded errors. Entity is never
18129 -- examined again, except when saving globals in generics.
18131 Set_Scope
(Id
, Current_Scope
);
18134 -- If this is a repeated incomplete declaration, no further
18135 -- checks are possible.
18137 if Nkind
(N
) = N_Incomplete_Type_Declaration
then
18141 -- Case of full declaration of incomplete type
18143 elsif Ekind
(Prev
) = E_Incomplete_Type
18144 and then (Ada_Version
< Ada_2012
18145 or else No
(Full_View
(Prev
))
18146 or else not Is_Private_Type
(Full_View
(Prev
)))
18148 -- Indicate that the incomplete declaration has a matching full
18149 -- declaration. The defining occurrence of the incomplete
18150 -- declaration remains the visible one, and the procedure
18151 -- Get_Full_View dereferences it whenever the type is used.
18153 if Present
(Full_View
(Prev
)) then
18154 Error_Msg_NE
("invalid redeclaration of }", Id
, Prev
);
18157 Set_Full_View
(Prev
, Id
);
18158 Append_Entity
(Id
, Current_Scope
);
18159 Set_Is_Public
(Id
, Is_Public
(Prev
));
18160 Set_Is_Internal
(Id
);
18163 -- If the incomplete view is tagged, a class_wide type has been
18164 -- created already. Use it for the private type as well, in order
18165 -- to prevent multiple incompatible class-wide types that may be
18166 -- created for self-referential anonymous access components.
18168 if Is_Tagged_Type
(Prev
)
18169 and then Present
(Class_Wide_Type
(Prev
))
18171 Mutate_Ekind
(Id
, Ekind
(Prev
)); -- will be reset later
18172 Set_Class_Wide_Type
(Id
, Class_Wide_Type
(Prev
));
18174 -- Type of the class-wide type is the current Id. Previously
18175 -- this was not done for private declarations because of order-
18176 -- of-elaboration issues in the back end, but gigi now handles
18179 Set_Etype
(Class_Wide_Type
(Id
), Id
);
18182 -- Case of full declaration of private type
18185 -- If the private type was a completion of an incomplete type then
18186 -- update Prev to reference the private type
18188 if Ada_Version
>= Ada_2012
18189 and then Ekind
(Prev
) = E_Incomplete_Type
18190 and then Present
(Full_View
(Prev
))
18191 and then Is_Private_Type
(Full_View
(Prev
))
18193 Prev
:= Full_View
(Prev
);
18194 Prev_Par
:= Parent
(Prev
);
18197 if Nkind
(N
) = N_Full_Type_Declaration
18198 and then Nkind
(Type_Definition
(N
)) in
18199 N_Record_Definition | N_Derived_Type_Definition
18200 and then Interface_Present
(Type_Definition
(N
))
18203 ("completion of private type cannot be an interface", N
);
18206 if Nkind
(Parent
(Prev
)) /= N_Private_Extension_Declaration
then
18207 if Etype
(Prev
) /= Prev
then
18209 -- Prev is a private subtype or a derived type, and needs
18212 Error_Msg_NE
("invalid redeclaration of }", Id
, Prev
);
18215 elsif Ekind
(Prev
) = E_Private_Type
18216 and then Nkind
(N
) in N_Task_Type_Declaration
18217 | N_Protected_Type_Declaration
18220 ("completion of nonlimited type cannot be limited", N
);
18222 elsif Ekind
(Prev
) = E_Record_Type_With_Private
18223 and then Nkind
(N
) in N_Task_Type_Declaration
18224 | N_Protected_Type_Declaration
18226 if not Is_Limited_Record
(Prev
) then
18228 ("completion of nonlimited type cannot be limited", N
);
18230 elsif No
(Interface_List
(N
)) then
18232 ("completion of tagged private type must be tagged",
18237 -- Ada 2005 (AI-251): Private extension declaration of a task
18238 -- type or a protected type. This case arises when covering
18239 -- interface types.
18241 elsif Nkind
(N
) in N_Task_Type_Declaration
18242 | N_Protected_Type_Declaration
18246 elsif Nkind
(N
) /= N_Full_Type_Declaration
18247 or else Nkind
(Type_Definition
(N
)) /= N_Derived_Type_Definition
18250 ("full view of private extension must be an extension", N
);
18252 elsif not (Abstract_Present
(Parent
(Prev
)))
18253 and then Abstract_Present
(Type_Definition
(N
))
18256 ("full view of non-abstract extension cannot be abstract", N
);
18259 if not In_Private_Part
(Current_Scope
) then
18261 ("declaration of full view must appear in private part", N
);
18264 if Ada_Version
>= Ada_2012
then
18265 Check_Duplicate_Aspects
;
18268 Copy_And_Swap
(Prev
, Id
);
18269 Set_Has_Private_Declaration
(Prev
);
18270 Set_Has_Private_Declaration
(Id
);
18272 -- AI12-0133: Indicate whether we have a partial view with
18273 -- unknown discriminants, in which case initialization of objects
18274 -- of the type do not receive an invariant check.
18276 Set_Partial_View_Has_Unknown_Discr
18277 (Prev
, Has_Unknown_Discriminants
(Id
));
18279 -- Preserve aspect and iterator flags that may have been set on
18280 -- the partial view.
18282 Set_Has_Delayed_Aspects
(Prev
, Has_Delayed_Aspects
(Id
));
18283 Set_Has_Implicit_Dereference
(Prev
, Has_Implicit_Dereference
(Id
));
18285 -- If no error, propagate freeze_node from private to full view.
18286 -- It may have been generated for an early operational item.
18288 if Present
(Freeze_Node
(Id
))
18289 and then Serious_Errors_Detected
= 0
18290 and then No
(Full_View
(Id
))
18292 Set_Freeze_Node
(Prev
, Freeze_Node
(Id
));
18293 Set_Freeze_Node
(Id
, Empty
);
18294 Set_First_Rep_Item
(Prev
, First_Rep_Item
(Id
));
18297 Set_Full_View
(Id
, Prev
);
18301 -- Verify that full declaration conforms to partial one
18303 if Is_Incomplete_Or_Private_Type
(Prev
)
18304 and then Present
(Discriminant_Specifications
(Prev_Par
))
18306 if Present
(Discriminant_Specifications
(N
)) then
18307 if Ekind
(Prev
) = E_Incomplete_Type
then
18308 Check_Discriminant_Conformance
(N
, Prev
, Prev
);
18310 Check_Discriminant_Conformance
(N
, Prev
, Id
);
18315 ("missing discriminants in full type declaration", N
);
18317 -- To avoid cascaded errors on subsequent use, share the
18318 -- discriminants of the partial view.
18320 Set_Discriminant_Specifications
(N
,
18321 Discriminant_Specifications
(Prev_Par
));
18325 -- A prior untagged partial view can have an associated class-wide
18326 -- type due to use of the class attribute, and in this case the full
18327 -- type must also be tagged. This Ada 95 usage is deprecated in favor
18328 -- of incomplete tagged declarations, but we check for it.
18331 and then (Is_Tagged_Type
(Prev
)
18332 or else Present
(Class_Wide_Type
(Prev
)))
18334 -- Ada 2012 (AI05-0162): A private type may be the completion of
18335 -- an incomplete type.
18337 if Ada_Version
>= Ada_2012
18338 and then Is_Incomplete_Type
(Prev
)
18339 and then Nkind
(N
) in N_Private_Type_Declaration
18340 | N_Private_Extension_Declaration
18342 -- No need to check private extensions since they are tagged
18344 if Nkind
(N
) = N_Private_Type_Declaration
18345 and then not Tagged_Present
(N
)
18350 -- The full declaration is either a tagged type (including
18351 -- a synchronized type that implements interfaces) or a
18352 -- type extension, otherwise this is an error.
18354 elsif Nkind
(N
) in N_Task_Type_Declaration
18355 | N_Protected_Type_Declaration
18357 if No
(Interface_List
(N
)) and then not Error_Posted
(N
) then
18361 elsif Nkind
(Type_Definition
(N
)) = N_Record_Definition
then
18363 -- Indicate that the previous declaration (tagged incomplete
18364 -- or private declaration) requires the same on the full one.
18366 if not Tagged_Present
(Type_Definition
(N
)) then
18368 Set_Is_Tagged_Type
(Id
);
18371 elsif Nkind
(Type_Definition
(N
)) = N_Derived_Type_Definition
then
18372 if No
(Record_Extension_Part
(Type_Definition
(N
))) then
18374 ("full declaration of } must be a record extension",
18377 -- Set some attributes to produce a usable full view
18379 Set_Is_Tagged_Type
(Id
);
18388 and then Nkind
(Parent
(Prev
)) = N_Incomplete_Type_Declaration
18389 and then Present
(Premature_Use
(Parent
(Prev
)))
18391 Error_Msg_Sloc
:= Sloc
(N
);
18393 ("\full declaration #", Premature_Use
(Parent
(Prev
)));
18398 end Find_Type_Name
;
18400 -------------------------
18401 -- Find_Type_Of_Object --
18402 -------------------------
18404 function Find_Type_Of_Object
18405 (Obj_Def
: Node_Id
;
18406 Related_Nod
: Node_Id
) return Entity_Id
18408 Def_Kind
: constant Node_Kind
:= Nkind
(Obj_Def
);
18409 P
: Node_Id
:= Parent
(Obj_Def
);
18414 -- If the parent is a component_definition node we climb to the
18415 -- component_declaration node.
18417 if Nkind
(P
) = N_Component_Definition
then
18421 -- Case of an anonymous array subtype
18423 if Def_Kind
in N_Array_Type_Definition
then
18425 Array_Type_Declaration
(T
, Obj_Def
);
18427 -- Create an explicit subtype whenever possible
18429 elsif Nkind
(P
) /= N_Component_Declaration
18430 and then Def_Kind
= N_Subtype_Indication
18432 -- Base name of subtype on object name, which will be unique in
18433 -- the current scope.
18435 -- If this is a duplicate declaration, return base type, to avoid
18436 -- generating duplicate anonymous types.
18438 if Error_Posted
(P
) then
18439 Analyze
(Subtype_Mark
(Obj_Def
));
18440 return Entity
(Subtype_Mark
(Obj_Def
));
18445 (Chars
(Defining_Identifier
(Related_Nod
)), 'S', 0, 'T');
18447 T
:= Make_Defining_Identifier
(Sloc
(P
), Nam
);
18449 -- If In_Spec_Expression, for example within a pre/postcondition,
18450 -- provide enough information for use of the subtype without
18451 -- depending on full analysis and freezing, which will happen when
18452 -- building the corresponding subprogram.
18454 if In_Spec_Expression
then
18455 Analyze
(Subtype_Mark
(Obj_Def
));
18458 Base_T
: constant Entity_Id
:= Entity
(Subtype_Mark
(Obj_Def
));
18459 New_Def
: constant Node_Id
:= New_Copy_Tree
(Obj_Def
);
18460 Decl
: constant Node_Id
:=
18461 Make_Subtype_Declaration
(Sloc
(P
),
18462 Defining_Identifier
=> T
,
18463 Subtype_Indication
=> New_Def
);
18466 Set_Etype
(T
, Base_T
);
18467 Mutate_Ekind
(T
, Subtype_Kind
(Ekind
(Base_T
)));
18468 Set_Parent
(T
, Decl
);
18469 Set_Scope
(T
, Current_Scope
);
18471 if Ekind
(T
) = E_Array_Subtype
then
18472 Constrain_Array
(T
, New_Def
, Related_Nod
, T
, 'P');
18474 elsif Ekind
(T
) = E_Record_Subtype
then
18475 Set_First_Entity
(T
, First_Entity
(Base_T
));
18476 Set_Has_Discriminants
(T
, Has_Discriminants
(Base_T
));
18477 Set_Is_Constrained
(T
);
18480 Insert_Before
(Related_Nod
, Decl
);
18486 -- When generating code, insert subtype declaration ahead of
18487 -- declaration that generated it.
18489 Insert_Action
(Obj_Def
,
18490 Make_Subtype_Declaration
(Sloc
(P
),
18491 Defining_Identifier
=> T
,
18492 Subtype_Indication
=> Relocate_Node
(Obj_Def
)));
18494 -- This subtype may need freezing, and this will not be done
18495 -- automatically if the object declaration is not in declarative
18496 -- part. Since this is an object declaration, the type cannot always
18497 -- be frozen here. Deferred constants do not freeze their type
18498 -- (which often enough will be private).
18500 if Nkind
(P
) = N_Object_Declaration
18501 and then Constant_Present
(P
)
18502 and then No
(Expression
(P
))
18506 -- Here we freeze the base type of object type to catch premature use
18507 -- of discriminated private type without a full view.
18510 Insert_Actions
(Obj_Def
, Freeze_Entity
(Base_Type
(T
), P
));
18513 -- Ada 2005 AI-406: the object definition in an object declaration
18514 -- can be an access definition.
18516 elsif Def_Kind
= N_Access_Definition
then
18517 T
:= Access_Definition
(Related_Nod
, Obj_Def
);
18519 Set_Is_Local_Anonymous_Access
18520 (T
, Ada_Version
< Ada_2012
18521 or else Nkind
(P
) /= N_Object_Declaration
18522 or else Is_Library_Level_Entity
(Defining_Identifier
(P
)));
18524 -- Otherwise, the object definition is just a subtype_mark
18527 T
:= Process_Subtype
(Obj_Def
, Related_Nod
);
18531 end Find_Type_Of_Object
;
18533 --------------------------------
18534 -- Find_Type_Of_Subtype_Indic --
18535 --------------------------------
18537 function Find_Type_Of_Subtype_Indic
(S
: Node_Id
) return Entity_Id
is
18541 -- Case of subtype mark with a constraint
18543 if Nkind
(S
) = N_Subtype_Indication
then
18544 Find_Type
(Subtype_Mark
(S
));
18545 Typ
:= Entity
(Subtype_Mark
(S
));
18548 Is_Valid_Constraint_Kind
(Ekind
(Typ
), Nkind
(Constraint
(S
)))
18551 ("incorrect constraint for this kind of type", Constraint
(S
));
18552 Rewrite
(S
, New_Copy_Tree
(Subtype_Mark
(S
)));
18555 -- Otherwise we have a subtype mark without a constraint
18557 elsif Error_Posted
(S
) then
18558 Rewrite
(S
, New_Occurrence_Of
(Any_Id
, Sloc
(S
)));
18567 end Find_Type_Of_Subtype_Indic
;
18569 -------------------------------------
18570 -- Floating_Point_Type_Declaration --
18571 -------------------------------------
18573 procedure Floating_Point_Type_Declaration
(T
: Entity_Id
; Def
: Node_Id
) is
18574 Digs
: constant Node_Id
:= Digits_Expression
(Def
);
18575 Max_Digs_Val
: constant Uint
:= Digits_Value
(Standard_Long_Long_Float
);
18577 Base_Typ
: Entity_Id
;
18578 Implicit_Base
: Entity_Id
;
18580 function Can_Derive_From
(E
: Entity_Id
) return Boolean;
18581 -- Find if given digits value, and possibly a specified range, allows
18582 -- derivation from specified type
18584 procedure Convert_Bound
(B
: Node_Id
);
18585 -- If specified, the bounds must be static but may be of different
18586 -- types. They must be converted into machine numbers of the base type,
18587 -- in accordance with RM 4.9(38).
18589 function Find_Base_Type
return Entity_Id
;
18590 -- Find a predefined base type that Def can derive from, or generate
18591 -- an error and substitute Long_Long_Float if none exists.
18593 ---------------------
18594 -- Can_Derive_From --
18595 ---------------------
18597 function Can_Derive_From
(E
: Entity_Id
) return Boolean is
18598 Spec
: constant Entity_Id
:= Real_Range_Specification
(Def
);
18601 -- Check specified "digits" constraint
18603 if Digs_Val
> Digits_Value
(E
) then
18607 -- Check for matching range, if specified
18609 if Present
(Spec
) then
18610 if Expr_Value_R
(Type_Low_Bound
(E
)) >
18611 Expr_Value_R
(Low_Bound
(Spec
))
18616 if Expr_Value_R
(Type_High_Bound
(E
)) <
18617 Expr_Value_R
(High_Bound
(Spec
))
18624 end Can_Derive_From
;
18626 -------------------
18627 -- Convert_Bound --
18628 --------------------
18630 procedure Convert_Bound
(B
: Node_Id
) is
18632 -- If the bound is not a literal it can only be static if it is
18633 -- a static constant, possibly of a specified type.
18635 if Is_Entity_Name
(B
)
18636 and then Ekind
(Entity
(B
)) = E_Constant
18638 Rewrite
(B
, Constant_Value
(Entity
(B
)));
18641 if Nkind
(B
) = N_Real_Literal
then
18642 Set_Realval
(B
, Machine
(Base_Typ
, Realval
(B
), Round
, B
));
18643 Set_Is_Machine_Number
(B
);
18644 Set_Etype
(B
, Base_Typ
);
18648 --------------------
18649 -- Find_Base_Type --
18650 --------------------
18652 function Find_Base_Type
return Entity_Id
is
18653 Choice
: Elmt_Id
:= First_Elmt
(Predefined_Float_Types
);
18656 -- Iterate over the predefined types in order, returning the first
18657 -- one that Def can derive from.
18659 while Present
(Choice
) loop
18660 if Can_Derive_From
(Node
(Choice
)) then
18661 return Node
(Choice
);
18664 Next_Elmt
(Choice
);
18667 -- If we can't derive from any existing type, use Long_Long_Float
18668 -- and give appropriate message explaining the problem.
18670 if Digs_Val
> Max_Digs_Val
then
18671 -- It might be the case that there is a type with the requested
18672 -- range, just not the combination of digits and range.
18675 ("no predefined type has requested range and precision",
18676 Real_Range_Specification
(Def
));
18680 ("range too large for any predefined type",
18681 Real_Range_Specification
(Def
));
18684 return Standard_Long_Long_Float
;
18685 end Find_Base_Type
;
18687 -- Start of processing for Floating_Point_Type_Declaration
18690 Check_Restriction
(No_Floating_Point
, Def
);
18692 -- Create an implicit base type
18695 Create_Itype
(E_Floating_Point_Type
, Parent
(Def
), T
, 'B');
18697 -- Analyze and verify digits value
18699 Analyze_And_Resolve
(Digs
, Any_Integer
);
18700 Check_Digits_Expression
(Digs
);
18701 Digs_Val
:= Expr_Value
(Digs
);
18703 -- Process possible range spec and find correct type to derive from
18705 Process_Real_Range_Specification
(Def
);
18707 -- Check that requested number of digits is not too high.
18709 if Digs_Val
> Max_Digs_Val
then
18711 -- The check for Max_Base_Digits may be somewhat expensive, as it
18712 -- requires reading System, so only do it when necessary.
18715 Max_Base_Digits
: constant Uint
:=
18718 (Parent
(RTE
(RE_Max_Base_Digits
))));
18721 if Digs_Val
> Max_Base_Digits
then
18722 Error_Msg_Uint_1
:= Max_Base_Digits
;
18723 Error_Msg_N
("digits value out of range, maximum is ^", Digs
);
18725 elsif No
(Real_Range_Specification
(Def
)) then
18726 Error_Msg_Uint_1
:= Max_Digs_Val
;
18727 Error_Msg_N
("types with more than ^ digits need range spec "
18728 & "(RM 3.5.7(6))", Digs
);
18733 -- Find a suitable type to derive from or complain and use a substitute
18735 Base_Typ
:= Find_Base_Type
;
18737 -- If there are bounds given in the declaration use them as the bounds
18738 -- of the type, otherwise use the bounds of the predefined base type
18739 -- that was chosen based on the Digits value.
18741 if Present
(Real_Range_Specification
(Def
)) then
18742 Set_Scalar_Range
(T
, Real_Range_Specification
(Def
));
18743 Set_Is_Constrained
(T
);
18745 Convert_Bound
(Type_Low_Bound
(T
));
18746 Convert_Bound
(Type_High_Bound
(T
));
18749 Set_Scalar_Range
(T
, Scalar_Range
(Base_Typ
));
18752 -- Complete definition of implicit base and declared first subtype. The
18753 -- inheritance of the rep item chain ensures that SPARK-related pragmas
18754 -- are not clobbered when the floating point type acts as a full view of
18757 Set_Etype
(Implicit_Base
, Base_Typ
);
18758 Set_Scalar_Range
(Implicit_Base
, Scalar_Range
(Base_Typ
));
18759 Set_Size_Info
(Implicit_Base
, Base_Typ
);
18760 Set_RM_Size
(Implicit_Base
, RM_Size
(Base_Typ
));
18761 Set_First_Rep_Item
(Implicit_Base
, First_Rep_Item
(Base_Typ
));
18762 Set_Digits_Value
(Implicit_Base
, Digits_Value
(Base_Typ
));
18763 Set_Float_Rep
(Implicit_Base
, Float_Rep
(Base_Typ
));
18765 Mutate_Ekind
(T
, E_Floating_Point_Subtype
);
18766 Set_Etype
(T
, Implicit_Base
);
18767 Set_Size_Info
(T
, Implicit_Base
);
18768 Set_RM_Size
(T
, RM_Size
(Implicit_Base
));
18769 Inherit_Rep_Item_Chain
(T
, Implicit_Base
);
18771 if Digs_Val
>= Uint_1
then
18772 Set_Digits_Value
(T
, Digs_Val
);
18774 pragma Assert
(Serious_Errors_Detected
> 0); null;
18776 end Floating_Point_Type_Declaration
;
18778 ----------------------------
18779 -- Get_Discriminant_Value --
18780 ----------------------------
18782 -- This is the situation:
18784 -- There is a non-derived type
18786 -- type T0 (Dx, Dy, Dz...)
18788 -- There are zero or more levels of derivation, with each derivation
18789 -- either purely inheriting the discriminants, or defining its own.
18791 -- type Ti is new Ti-1
18793 -- type Ti (Dw) is new Ti-1(Dw, 1, X+Y)
18795 -- subtype Ti is ...
18797 -- The subtype issue is avoided by the use of Original_Record_Component,
18798 -- and the fact that derived subtypes also derive the constraints.
18800 -- This chain leads back from
18802 -- Typ_For_Constraint
18804 -- Typ_For_Constraint has discriminants, and the value for each
18805 -- discriminant is given by its corresponding Elmt of Constraints.
18807 -- Discriminant is some discriminant in this hierarchy
18809 -- We need to return its value
18811 -- We do this by recursively searching each level, and looking for
18812 -- Discriminant. Once we get to the bottom, we start backing up
18813 -- returning the value for it which may in turn be a discriminant
18814 -- further up, so on the backup we continue the substitution.
18816 function Get_Discriminant_Value
18817 (Discriminant
: Entity_Id
;
18818 Typ_For_Constraint
: Entity_Id
;
18819 Constraint
: Elist_Id
) return Node_Id
18821 function Root_Corresponding_Discriminant
18822 (Discr
: Entity_Id
) return Entity_Id
;
18823 -- Given a discriminant, traverse the chain of inherited discriminants
18824 -- and return the topmost discriminant.
18826 function Search_Derivation_Levels
18828 Discrim_Values
: Elist_Id
;
18829 Stored_Discrim_Values
: Boolean) return Node_Or_Entity_Id
;
18830 -- This is the routine that performs the recursive search of levels
18831 -- as described above.
18833 -------------------------------------
18834 -- Root_Corresponding_Discriminant --
18835 -------------------------------------
18837 function Root_Corresponding_Discriminant
18838 (Discr
: Entity_Id
) return Entity_Id
18844 while Present
(Corresponding_Discriminant
(D
)) loop
18845 D
:= Corresponding_Discriminant
(D
);
18849 end Root_Corresponding_Discriminant
;
18851 ------------------------------
18852 -- Search_Derivation_Levels --
18853 ------------------------------
18855 function Search_Derivation_Levels
18857 Discrim_Values
: Elist_Id
;
18858 Stored_Discrim_Values
: Boolean) return Node_Or_Entity_Id
18862 Result
: Node_Or_Entity_Id
;
18863 Result_Entity
: Node_Id
;
18866 -- If inappropriate type, return Error, this happens only in
18867 -- cascaded error situations, and we want to avoid a blow up.
18869 if not Is_Composite_Type
(Ti
) or else Is_Array_Type
(Ti
) then
18873 -- Look deeper if possible. Use Stored_Constraints only for
18874 -- untagged types. For tagged types use the given constraint.
18875 -- This asymmetry needs explanation???
18877 if not Stored_Discrim_Values
18878 and then Present
(Stored_Constraint
(Ti
))
18879 and then not Is_Tagged_Type
(Ti
)
18882 Search_Derivation_Levels
(Ti
, Stored_Constraint
(Ti
), True);
18886 Td
: Entity_Id
:= Etype
(Ti
);
18889 -- If the parent type is private, the full view may include
18890 -- renamed discriminants, and it is those stored values that
18891 -- may be needed (the partial view never has more information
18892 -- than the full view).
18894 if Is_Private_Type
(Td
) and then Present
(Full_View
(Td
)) then
18895 Td
:= Full_View
(Td
);
18899 Result
:= Discriminant
;
18902 if Present
(Stored_Constraint
(Ti
)) then
18904 Search_Derivation_Levels
18905 (Td
, Stored_Constraint
(Ti
), True);
18908 Search_Derivation_Levels
18909 (Td
, Discrim_Values
, Stored_Discrim_Values
);
18915 -- Extra underlying places to search, if not found above. For
18916 -- concurrent types, the relevant discriminant appears in the
18917 -- corresponding record. For a type derived from a private type
18918 -- without discriminant, the full view inherits the discriminants
18919 -- of the full view of the parent.
18921 if Result
= Discriminant
then
18922 if Is_Concurrent_Type
(Ti
)
18923 and then Present
(Corresponding_Record_Type
(Ti
))
18926 Search_Derivation_Levels
(
18927 Corresponding_Record_Type
(Ti
),
18929 Stored_Discrim_Values
);
18931 elsif Is_Private_Type
(Ti
)
18932 and then not Has_Discriminants
(Ti
)
18933 and then Present
(Full_View
(Ti
))
18934 and then Etype
(Full_View
(Ti
)) /= Ti
18937 Search_Derivation_Levels
(
18940 Stored_Discrim_Values
);
18944 -- If Result is not a (reference to a) discriminant, return it,
18945 -- otherwise set Result_Entity to the discriminant.
18947 if Nkind
(Result
) = N_Defining_Identifier
then
18948 pragma Assert
(Result
= Discriminant
);
18949 Result_Entity
:= Result
;
18952 if not Denotes_Discriminant
(Result
) then
18956 Result_Entity
:= Entity
(Result
);
18959 -- See if this level of derivation actually has discriminants because
18960 -- tagged derivations can add them, hence the lower levels need not
18963 if not Has_Discriminants
(Ti
) then
18967 -- Scan Ti's discriminants for Result_Entity, and return its
18968 -- corresponding value, if any.
18970 Result_Entity
:= Original_Record_Component
(Result_Entity
);
18972 Assoc
:= First_Elmt
(Discrim_Values
);
18974 if Stored_Discrim_Values
then
18975 Disc
:= First_Stored_Discriminant
(Ti
);
18977 Disc
:= First_Discriminant
(Ti
);
18980 while Present
(Disc
) loop
18982 -- If no further associations return the discriminant, value will
18983 -- be found on the second pass.
18989 if Original_Record_Component
(Disc
) = Result_Entity
then
18990 return Node
(Assoc
);
18995 if Stored_Discrim_Values
then
18996 Next_Stored_Discriminant
(Disc
);
18998 Next_Discriminant
(Disc
);
19002 -- Could not find it
19005 end Search_Derivation_Levels
;
19009 Result
: Node_Or_Entity_Id
;
19011 -- Start of processing for Get_Discriminant_Value
19014 -- ??? This routine is a gigantic mess and will be deleted. For the
19015 -- time being just test for the trivial case before calling recurse.
19017 -- We are now celebrating the 20th anniversary of this comment!
19019 if Base_Type
(Scope
(Discriminant
)) = Base_Type
(Typ_For_Constraint
) then
19025 D
:= First_Discriminant
(Typ_For_Constraint
);
19026 E
:= First_Elmt
(Constraint
);
19027 while Present
(D
) loop
19028 if Chars
(D
) = Chars
(Discriminant
) then
19032 Next_Discriminant
(D
);
19038 Result
:= Search_Derivation_Levels
19039 (Typ_For_Constraint
, Constraint
, False);
19041 -- ??? hack to disappear when this routine is gone
19043 if Nkind
(Result
) = N_Defining_Identifier
then
19049 D
:= First_Discriminant
(Typ_For_Constraint
);
19050 E
:= First_Elmt
(Constraint
);
19051 while Present
(D
) loop
19052 if Root_Corresponding_Discriminant
(D
) = Discriminant
then
19056 Next_Discriminant
(D
);
19062 pragma Assert
(Nkind
(Result
) /= N_Defining_Identifier
);
19064 end Get_Discriminant_Value
;
19066 --------------------------
19067 -- Has_Range_Constraint --
19068 --------------------------
19070 function Has_Range_Constraint
(N
: Node_Id
) return Boolean is
19071 C
: constant Node_Id
:= Constraint
(N
);
19074 if Nkind
(C
) = N_Range_Constraint
then
19077 elsif Nkind
(C
) = N_Digits_Constraint
then
19079 Is_Decimal_Fixed_Point_Type
(Entity
(Subtype_Mark
(N
)))
19080 or else Present
(Range_Constraint
(C
));
19082 elsif Nkind
(C
) = N_Delta_Constraint
then
19083 return Present
(Range_Constraint
(C
));
19088 end Has_Range_Constraint
;
19090 ------------------------
19091 -- Inherit_Components --
19092 ------------------------
19094 function Inherit_Components
19096 Parent_Base
: Entity_Id
;
19097 Derived_Base
: Entity_Id
;
19098 Is_Tagged
: Boolean;
19099 Inherit_Discr
: Boolean;
19100 Discs
: Elist_Id
) return Elist_Id
19102 Assoc_List
: constant Elist_Id
:= New_Elmt_List
;
19104 procedure Inherit_Component
19105 (Old_C
: Entity_Id
;
19106 Plain_Discrim
: Boolean := False;
19107 Stored_Discrim
: Boolean := False);
19108 -- Inherits component Old_C from Parent_Base to the Derived_Base. If
19109 -- Plain_Discrim is True, Old_C is a discriminant. If Stored_Discrim is
19110 -- True, Old_C is a stored discriminant. If they are both false then
19111 -- Old_C is a regular component.
19113 -----------------------
19114 -- Inherit_Component --
19115 -----------------------
19117 procedure Inherit_Component
19118 (Old_C
: Entity_Id
;
19119 Plain_Discrim
: Boolean := False;
19120 Stored_Discrim
: Boolean := False)
19122 procedure Set_Anonymous_Type
(Id
: Entity_Id
);
19123 -- Id denotes the entity of an access discriminant or anonymous
19124 -- access component. Set the type of Id to either the same type of
19125 -- Old_C or create a new one depending on whether the parent and
19126 -- the child types are in the same scope.
19128 ------------------------
19129 -- Set_Anonymous_Type --
19130 ------------------------
19132 procedure Set_Anonymous_Type
(Id
: Entity_Id
) is
19133 Old_Typ
: constant Entity_Id
:= Etype
(Old_C
);
19136 if Scope
(Parent_Base
) = Scope
(Derived_Base
) then
19137 Set_Etype
(Id
, Old_Typ
);
19139 -- The parent and the derived type are in two different scopes.
19140 -- Reuse the type of the original discriminant / component by
19141 -- copying it in order to preserve all attributes.
19145 Typ
: constant Entity_Id
:= New_Copy
(Old_Typ
);
19148 Set_Etype
(Id
, Typ
);
19150 -- Since we do not generate component declarations for
19151 -- inherited components, associate the itype with the
19154 Set_Associated_Node_For_Itype
(Typ
, Parent
(Derived_Base
));
19155 Set_Scope
(Typ
, Derived_Base
);
19158 end Set_Anonymous_Type
;
19160 -- Local variables and constants
19162 New_C
: constant Entity_Id
:= New_Copy
(Old_C
);
19164 Corr_Discrim
: Entity_Id
;
19165 Discrim
: Entity_Id
;
19167 -- Start of processing for Inherit_Component
19170 pragma Assert
(not Is_Tagged
or not Stored_Discrim
);
19172 Set_Parent
(New_C
, Parent
(Old_C
));
19174 -- Regular discriminants and components must be inserted in the scope
19175 -- of the Derived_Base. Do it here.
19177 if not Stored_Discrim
then
19178 Enter_Name
(New_C
);
19181 -- For tagged types the Original_Record_Component must point to
19182 -- whatever this field was pointing to in the parent type. This has
19183 -- already been achieved by the call to New_Copy above.
19185 if not Is_Tagged
then
19186 Set_Original_Record_Component
(New_C
, New_C
);
19187 Set_Corresponding_Record_Component
(New_C
, Old_C
);
19190 -- Set the proper type of an access discriminant
19192 if Ekind
(New_C
) = E_Discriminant
19193 and then Ekind
(Etype
(New_C
)) = E_Anonymous_Access_Type
19195 Set_Anonymous_Type
(New_C
);
19198 -- If we have inherited a component then see if its Etype contains
19199 -- references to Parent_Base discriminants. In this case, replace
19200 -- these references with the constraints given in Discs. We do not
19201 -- do this for the partial view of private types because this is
19202 -- not needed (only the components of the full view will be used
19203 -- for code generation) and cause problem. We also avoid this
19204 -- transformation in some error situations.
19206 if Ekind
(New_C
) = E_Component
then
19208 -- Set the proper type of an anonymous access component
19210 if Ekind
(Etype
(New_C
)) = E_Anonymous_Access_Type
then
19211 Set_Anonymous_Type
(New_C
);
19213 elsif (Is_Private_Type
(Derived_Base
)
19214 and then not Is_Generic_Type
(Derived_Base
))
19215 or else (Is_Empty_Elmt_List
(Discs
)
19216 and then not Expander_Active
)
19218 Set_Etype
(New_C
, Etype
(Old_C
));
19221 -- The current component introduces a circularity of the
19224 -- limited with Pack_2;
19225 -- package Pack_1 is
19226 -- type T_1 is tagged record
19227 -- Comp : access Pack_2.T_2;
19233 -- package Pack_2 is
19234 -- type T_2 is new Pack_1.T_1 with ...;
19239 Constrain_Component_Type
19240 (Old_C
, Derived_Base
, N
, Parent_Base
, Discs
));
19244 if Plain_Discrim
then
19245 Set_Corresponding_Discriminant
(New_C
, Old_C
);
19246 Build_Discriminal
(New_C
);
19248 -- If we are explicitly inheriting a stored discriminant it will be
19249 -- completely hidden.
19251 elsif Stored_Discrim
then
19252 Set_Corresponding_Discriminant
(New_C
, Empty
);
19253 Set_Discriminal
(New_C
, Empty
);
19254 Set_Is_Completely_Hidden
(New_C
);
19256 -- Set the Original_Record_Component of each discriminant in the
19257 -- derived base to point to the corresponding stored that we just
19260 Discrim
:= First_Discriminant
(Derived_Base
);
19261 while Present
(Discrim
) loop
19262 Corr_Discrim
:= Corresponding_Discriminant
(Discrim
);
19264 -- Corr_Discrim could be missing in an error situation
19266 if Present
(Corr_Discrim
)
19267 and then Original_Record_Component
(Corr_Discrim
) = Old_C
19269 Set_Original_Record_Component
(Discrim
, New_C
);
19270 Set_Corresponding_Record_Component
(Discrim
, Empty
);
19273 Next_Discriminant
(Discrim
);
19276 Append_Entity
(New_C
, Derived_Base
);
19279 if not Is_Tagged
then
19280 Append_Elmt
(Old_C
, Assoc_List
);
19281 Append_Elmt
(New_C
, Assoc_List
);
19283 end Inherit_Component
;
19285 -- Variables local to Inherit_Component
19287 Loc
: constant Source_Ptr
:= Sloc
(N
);
19289 Parent_Discrim
: Entity_Id
;
19290 Stored_Discrim
: Entity_Id
;
19292 Component
: Entity_Id
;
19294 -- Start of processing for Inherit_Components
19297 if not Is_Tagged
then
19298 Append_Elmt
(Parent_Base
, Assoc_List
);
19299 Append_Elmt
(Derived_Base
, Assoc_List
);
19302 -- Inherit parent discriminants if needed
19304 if Inherit_Discr
then
19305 Parent_Discrim
:= First_Discriminant
(Parent_Base
);
19306 while Present
(Parent_Discrim
) loop
19307 Inherit_Component
(Parent_Discrim
, Plain_Discrim
=> True);
19308 Next_Discriminant
(Parent_Discrim
);
19312 -- Create explicit stored discrims for untagged types when necessary
19314 if not Has_Unknown_Discriminants
(Derived_Base
)
19315 and then Has_Discriminants
(Parent_Base
)
19316 and then not Is_Tagged
19319 or else First_Discriminant
(Parent_Base
) /=
19320 First_Stored_Discriminant
(Parent_Base
))
19322 Stored_Discrim
:= First_Stored_Discriminant
(Parent_Base
);
19323 while Present
(Stored_Discrim
) loop
19324 Inherit_Component
(Stored_Discrim
, Stored_Discrim
=> True);
19325 Next_Stored_Discriminant
(Stored_Discrim
);
19329 -- See if we can apply the second transformation for derived types, as
19330 -- explained in point 6. in the comments above Build_Derived_Record_Type
19331 -- This is achieved by appending Derived_Base discriminants into Discs,
19332 -- which has the side effect of returning a non empty Discs list to the
19333 -- caller of Inherit_Components, which is what we want. This must be
19334 -- done for private derived types if there are explicit stored
19335 -- discriminants, to ensure that we can retrieve the values of the
19336 -- constraints provided in the ancestors.
19339 and then Is_Empty_Elmt_List
(Discs
)
19340 and then Present
(First_Discriminant
(Derived_Base
))
19342 (not Is_Private_Type
(Derived_Base
)
19343 or else Is_Completely_Hidden
19344 (First_Stored_Discriminant
(Derived_Base
))
19345 or else Is_Generic_Type
(Derived_Base
))
19347 D
:= First_Discriminant
(Derived_Base
);
19348 while Present
(D
) loop
19349 Append_Elmt
(New_Occurrence_Of
(D
, Loc
), Discs
);
19350 Next_Discriminant
(D
);
19354 -- Finally, inherit non-discriminant components unless they are not
19355 -- visible because defined or inherited from the full view of the
19356 -- parent. Don't inherit the _parent field of the parent type.
19358 Component
:= First_Entity
(Parent_Base
);
19359 while Present
(Component
) loop
19361 -- Ada 2005 (AI-251): Do not inherit components associated with
19362 -- secondary tags of the parent.
19364 if Ekind
(Component
) = E_Component
19365 and then Present
(Related_Type
(Component
))
19369 elsif Ekind
(Component
) /= E_Component
19370 or else Chars
(Component
) = Name_uParent
19374 -- If the derived type is within the parent type's declarative
19375 -- region, then the components can still be inherited even though
19376 -- they aren't visible at this point. This can occur for cases
19377 -- such as within public child units where the components must
19378 -- become visible upon entering the child unit's private part.
19380 elsif not Is_Visible_Component
(Component
)
19381 and then not In_Open_Scopes
(Scope
(Parent_Base
))
19385 elsif Ekind
(Derived_Base
) in E_Private_Type | E_Limited_Private_Type
19390 Inherit_Component
(Component
);
19393 Next_Entity
(Component
);
19396 -- For tagged derived types, inherited discriminants cannot be used in
19397 -- component declarations of the record extension part. To achieve this
19398 -- we mark the inherited discriminants as not visible.
19400 if Is_Tagged
and then Inherit_Discr
then
19401 D
:= First_Discriminant
(Derived_Base
);
19402 while Present
(D
) loop
19403 Set_Is_Immediately_Visible
(D
, False);
19404 Next_Discriminant
(D
);
19409 end Inherit_Components
;
19411 ----------------------
19412 -- Is_EVF_Procedure --
19413 ----------------------
19415 function Is_EVF_Procedure
(Subp
: Entity_Id
) return Boolean is
19416 Formal
: Entity_Id
;
19419 -- Examine the formals of an Extensions_Visible False procedure looking
19420 -- for a controlling OUT parameter.
19422 if Ekind
(Subp
) = E_Procedure
19423 and then Extensions_Visible_Status
(Subp
) = Extensions_Visible_False
19425 Formal
:= First_Formal
(Subp
);
19426 while Present
(Formal
) loop
19427 if Ekind
(Formal
) = E_Out_Parameter
19428 and then Is_Controlling_Formal
(Formal
)
19433 Next_Formal
(Formal
);
19438 end Is_EVF_Procedure
;
19440 --------------------------
19441 -- Is_Private_Primitive --
19442 --------------------------
19444 function Is_Private_Primitive
(Prim
: Entity_Id
) return Boolean is
19445 Prim_Scope
: constant Entity_Id
:= Scope
(Prim
);
19446 Priv_Entity
: Entity_Id
;
19448 if Is_Package_Or_Generic_Package
(Prim_Scope
) then
19449 Priv_Entity
:= First_Private_Entity
(Prim_Scope
);
19451 while Present
(Priv_Entity
) loop
19452 if Priv_Entity
= Prim
then
19456 Next_Entity
(Priv_Entity
);
19461 end Is_Private_Primitive
;
19463 ------------------------------
19464 -- Is_Valid_Constraint_Kind --
19465 ------------------------------
19467 function Is_Valid_Constraint_Kind
19468 (T_Kind
: Type_Kind
;
19469 Constraint_Kind
: Node_Kind
) return Boolean
19473 when Enumeration_Kind
19476 return Constraint_Kind
= N_Range_Constraint
;
19478 when Decimal_Fixed_Point_Kind
=>
19479 return Constraint_Kind
in N_Digits_Constraint | N_Range_Constraint
;
19481 when Ordinary_Fixed_Point_Kind
=>
19482 return Constraint_Kind
in N_Delta_Constraint | N_Range_Constraint
;
19485 return Constraint_Kind
in N_Digits_Constraint | N_Range_Constraint
;
19492 | E_Incomplete_Type
19496 return Constraint_Kind
= N_Index_Or_Discriminant_Constraint
;
19499 return True; -- Error will be detected later
19501 end Is_Valid_Constraint_Kind
;
19503 --------------------------
19504 -- Is_Visible_Component --
19505 --------------------------
19507 function Is_Visible_Component
19509 N
: Node_Id
:= Empty
) return Boolean
19511 Original_Comp
: Entity_Id
:= Empty
;
19512 Original_Type
: Entity_Id
;
19513 Type_Scope
: Entity_Id
;
19515 function Is_Local_Type
(Typ
: Entity_Id
) return Boolean;
19516 -- Check whether parent type of inherited component is declared locally,
19517 -- possibly within a nested package or instance. The current scope is
19518 -- the derived record itself.
19520 -------------------
19521 -- Is_Local_Type --
19522 -------------------
19524 function Is_Local_Type
(Typ
: Entity_Id
) return Boolean is
19526 return Scope_Within
(Inner
=> Typ
, Outer
=> Scope
(Current_Scope
));
19529 -- Start of processing for Is_Visible_Component
19532 if Ekind
(C
) in E_Component | E_Discriminant
then
19533 Original_Comp
:= Original_Record_Component
(C
);
19536 if No
(Original_Comp
) then
19538 -- Premature usage, or previous error
19543 Original_Type
:= Scope
(Original_Comp
);
19544 Type_Scope
:= Scope
(Base_Type
(Scope
(C
)));
19547 -- This test only concerns tagged types
19549 if not Is_Tagged_Type
(Original_Type
) then
19551 -- Check if this is a renamed discriminant (hidden either by the
19552 -- derived type or by some ancestor), unless we are analyzing code
19553 -- generated by the expander since it may reference such components
19554 -- (for example see the expansion of Deep_Adjust).
19556 if Ekind
(C
) = E_Discriminant
and then Present
(N
) then
19558 not Comes_From_Source
(N
)
19559 or else not Is_Completely_Hidden
(C
);
19564 -- If it is _Parent or _Tag, there is no visibility issue
19566 elsif not Comes_From_Source
(Original_Comp
) then
19569 -- Discriminants are visible unless the (private) type has unknown
19570 -- discriminants. If the discriminant reference is inserted for a
19571 -- discriminant check on a full view it is also visible.
19573 elsif Ekind
(Original_Comp
) = E_Discriminant
19575 (not Has_Unknown_Discriminants
(Original_Type
)
19576 or else (Present
(N
)
19577 and then Nkind
(N
) = N_Selected_Component
19578 and then Nkind
(Prefix
(N
)) = N_Type_Conversion
19579 and then not Comes_From_Source
(Prefix
(N
))))
19583 -- If the component has been declared in an ancestor which is currently
19584 -- a private type, then it is not visible. The same applies if the
19585 -- component's containing type is not in an open scope and the original
19586 -- component's enclosing type is a visible full view of a private type
19587 -- (which can occur in cases where an attempt is being made to reference
19588 -- a component in a sibling package that is inherited from a visible
19589 -- component of a type in an ancestor package; the component in the
19590 -- sibling package should not be visible even though the component it
19591 -- inherited from is visible), but instance bodies are not subject to
19592 -- this second case since they have the Has_Private_View mechanism to
19593 -- ensure proper visibility. This does not apply however in the case
19594 -- where the scope of the type is a private child unit, or when the
19595 -- parent comes from a local package in which the ancestor is currently
19596 -- visible. The latter suppression of visibility is needed for cases
19597 -- that are tested in B730006.
19599 elsif Is_Private_Type
(Original_Type
)
19601 (not Is_Private_Descendant
(Type_Scope
)
19602 and then not In_Open_Scopes
(Type_Scope
)
19603 and then Has_Private_Declaration
(Original_Type
)
19604 and then not In_Instance_Body
)
19606 -- If the type derives from an entity in a formal package, there
19607 -- are no additional visible components.
19609 if Nkind
(Original_Node
(Unit_Declaration_Node
(Type_Scope
))) =
19610 N_Formal_Package_Declaration
19614 -- if we are not in the private part of the current package, there
19615 -- are no additional visible components.
19617 elsif Ekind
(Scope
(Current_Scope
)) = E_Package
19618 and then not In_Private_Part
(Scope
(Current_Scope
))
19623 Is_Child_Unit
(Cunit_Entity
(Current_Sem_Unit
))
19624 and then In_Open_Scopes
(Scope
(Original_Type
))
19625 and then Is_Local_Type
(Type_Scope
);
19628 -- There is another weird way in which a component may be invisible when
19629 -- the private and the full view are not derived from the same ancestor.
19630 -- Here is an example :
19632 -- type A1 is tagged record F1 : integer; end record;
19633 -- type A2 is new A1 with record F2 : integer; end record;
19634 -- type T is new A1 with private;
19636 -- type T is new A2 with null record;
19638 -- In this case, the full view of T inherits F1 and F2 but the private
19639 -- view inherits only F1
19643 Ancestor
: Entity_Id
:= Scope
(C
);
19647 if Ancestor
= Original_Type
then
19650 -- The ancestor may have a partial view of the original type,
19651 -- but if the full view is in scope, as in a child body, the
19652 -- component is visible.
19654 elsif In_Private_Part
(Scope
(Original_Type
))
19655 and then Full_View
(Ancestor
) = Original_Type
19659 elsif Ancestor
= Etype
(Ancestor
) then
19661 -- No further ancestors to examine
19666 Ancestor
:= Etype
(Ancestor
);
19670 end Is_Visible_Component
;
19672 --------------------------
19673 -- Make_Class_Wide_Type --
19674 --------------------------
19676 procedure Make_Class_Wide_Type
(T
: Entity_Id
) is
19677 CW_Type
: Entity_Id
;
19679 Next_E
: Entity_Id
;
19680 Prev_E
: Entity_Id
;
19683 if Present
(Class_Wide_Type
(T
)) then
19685 -- The class-wide type is a partially decorated entity created for a
19686 -- unanalyzed tagged type referenced through a limited with clause.
19687 -- When the tagged type is analyzed, its class-wide type needs to be
19688 -- redecorated. Note that we reuse the entity created by Decorate_
19689 -- Tagged_Type in order to preserve all links.
19691 if Materialize_Entity
(Class_Wide_Type
(T
)) then
19692 CW_Type
:= Class_Wide_Type
(T
);
19693 Set_Materialize_Entity
(CW_Type
, False);
19695 -- The class wide type can have been defined by the partial view, in
19696 -- which case everything is already done.
19702 -- Default case, we need to create a new class-wide type
19706 New_External_Entity
(E_Void
, Scope
(T
), Sloc
(T
), T
, 'C', 0, 'T');
19709 -- Inherit root type characteristics
19711 CW_Name
:= Chars
(CW_Type
);
19712 Next_E
:= Next_Entity
(CW_Type
);
19713 Prev_E
:= Prev_Entity
(CW_Type
);
19714 Copy_Node
(T
, CW_Type
);
19715 Set_Comes_From_Source
(CW_Type
, False);
19716 Set_Chars
(CW_Type
, CW_Name
);
19717 Set_Parent
(CW_Type
, Parent
(T
));
19718 Set_Prev_Entity
(CW_Type
, Prev_E
);
19719 Set_Next_Entity
(CW_Type
, Next_E
);
19721 -- Ensure we have a new freeze node for the class-wide type. The partial
19722 -- view may have freeze action of its own, requiring a proper freeze
19723 -- node, and the same freeze node cannot be shared between the two
19726 Set_Has_Delayed_Freeze
(CW_Type
);
19727 Set_Freeze_Node
(CW_Type
, Empty
);
19729 -- Customize the class-wide type: It has no prim. op., it cannot be
19730 -- abstract, its Etype points back to the specific root type, and it
19731 -- cannot have any invariants.
19733 if Ekind
(CW_Type
) in Incomplete_Or_Private_Kind
then
19734 Reinit_Field_To_Zero
(CW_Type
, F_Private_Dependents
);
19736 elsif Ekind
(CW_Type
) in Concurrent_Kind
then
19737 Reinit_Field_To_Zero
(CW_Type
, F_First_Private_Entity
);
19738 Reinit_Field_To_Zero
(CW_Type
, F_Scope_Depth_Value
);
19740 if Ekind
(CW_Type
) in Task_Kind
then
19741 Reinit_Field_To_Zero
(CW_Type
, F_Is_Elaboration_Checks_OK_Id
);
19742 Reinit_Field_To_Zero
(CW_Type
, F_Is_Elaboration_Warnings_OK_Id
);
19745 if Ekind
(CW_Type
) in E_Task_Type | E_Protected_Type
then
19746 Reinit_Field_To_Zero
(CW_Type
, F_SPARK_Aux_Pragma_Inherited
);
19749 elsif Ekind
(CW_Type
) = E_Record_Type
then
19750 Reinit_Field_To_Zero
(CW_Type
, F_Corresponding_Concurrent_Type
);
19753 Mutate_Ekind
(CW_Type
, E_Class_Wide_Type
);
19754 Set_Is_Tagged_Type
(CW_Type
, True);
19755 Set_Direct_Primitive_Operations
(CW_Type
, New_Elmt_List
);
19756 Set_Is_Abstract_Type
(CW_Type
, False);
19757 Set_Is_Constrained
(CW_Type
, False);
19758 Set_Is_First_Subtype
(CW_Type
, Is_First_Subtype
(T
));
19759 Set_Default_SSO
(CW_Type
);
19760 Set_Has_Inheritable_Invariants
(CW_Type
, False);
19761 Set_Has_Inherited_Invariants
(CW_Type
, False);
19762 Set_Has_Own_Invariants
(CW_Type
, False);
19764 if Ekind
(T
) = E_Class_Wide_Subtype
then
19765 Set_Etype
(CW_Type
, Etype
(Base_Type
(T
)));
19767 Set_Etype
(CW_Type
, T
);
19770 Set_No_Tagged_Streams_Pragma
(CW_Type
, No_Tagged_Streams
);
19772 -- If this is the class_wide type of a constrained subtype, it does
19773 -- not have discriminants.
19775 Set_Has_Discriminants
(CW_Type
,
19776 Has_Discriminants
(T
) and then not Is_Constrained
(T
));
19778 Set_Has_Unknown_Discriminants
(CW_Type
, True);
19779 Set_Class_Wide_Type
(T
, CW_Type
);
19780 Set_Equivalent_Type
(CW_Type
, Empty
);
19782 -- The class-wide type of a class-wide type is itself (RM 3.9(14))
19784 Set_Class_Wide_Type
(CW_Type
, CW_Type
);
19785 end Make_Class_Wide_Type
;
19791 procedure Make_Index
19793 Related_Nod
: Node_Id
;
19794 Related_Id
: Entity_Id
:= Empty
;
19795 Suffix_Index
: Pos
:= 1)
19799 Def_Id
: Entity_Id
:= Empty
;
19800 Found
: Boolean := False;
19803 -- For a discrete range used in a constrained array definition and
19804 -- defined by a range, an implicit conversion to the predefined type
19805 -- INTEGER is assumed if each bound is either a numeric literal, a named
19806 -- number, or an attribute, and the type of both bounds (prior to the
19807 -- implicit conversion) is the type universal_integer. Otherwise, both
19808 -- bounds must be of the same discrete type, other than universal
19809 -- integer; this type must be determinable independently of the
19810 -- context, but using the fact that the type must be discrete and that
19811 -- both bounds must have the same type.
19813 -- Character literals also have a universal type in the absence of
19814 -- of additional context, and are resolved to Standard_Character.
19816 if Nkind
(N
) = N_Range
then
19818 -- The index is given by a range constraint. The bounds are known
19819 -- to be of a consistent type.
19821 if not Is_Overloaded
(N
) then
19824 -- For universal bounds, choose the specific predefined type
19826 if T
= Universal_Integer
then
19827 T
:= Standard_Integer
;
19829 elsif T
= Any_Character
then
19830 Ambiguous_Character
(Low_Bound
(N
));
19832 T
:= Standard_Character
;
19835 -- The node may be overloaded because some user-defined operators
19836 -- are available, but if a universal interpretation exists it is
19837 -- also the selected one.
19839 elsif Universal_Interpretation
(N
) = Universal_Integer
then
19840 T
:= Standard_Integer
;
19846 Ind
: Interp_Index
;
19850 Get_First_Interp
(N
, Ind
, It
);
19851 while Present
(It
.Typ
) loop
19852 if Is_Discrete_Type
(It
.Typ
) then
19855 and then not Covers
(It
.Typ
, T
)
19856 and then not Covers
(T
, It
.Typ
)
19858 Error_Msg_N
("ambiguous bounds in discrete range", N
);
19866 Get_Next_Interp
(Ind
, It
);
19869 if T
= Any_Type
then
19870 Error_Msg_N
("discrete type required for range", N
);
19871 Set_Etype
(N
, Any_Type
);
19874 elsif T
= Universal_Integer
then
19875 T
:= Standard_Integer
;
19880 if not Is_Discrete_Type
(T
) then
19881 Error_Msg_N
("discrete type required for range", N
);
19882 Set_Etype
(N
, Any_Type
);
19886 -- If the range bounds are "T'First .. T'Last" where T is a name of a
19887 -- discrete type, then use T as the type of the index.
19889 if Nkind
(Low_Bound
(N
)) = N_Attribute_Reference
19890 and then Attribute_Name
(Low_Bound
(N
)) = Name_First
19891 and then Is_Entity_Name
(Prefix
(Low_Bound
(N
)))
19892 and then Is_Discrete_Type
(Entity
(Prefix
(Low_Bound
(N
))))
19894 and then Nkind
(High_Bound
(N
)) = N_Attribute_Reference
19895 and then Attribute_Name
(High_Bound
(N
)) = Name_Last
19896 and then Is_Entity_Name
(Prefix
(High_Bound
(N
)))
19897 and then Entity
(Prefix
(High_Bound
(N
))) = Def_Id
19899 Def_Id
:= Entity
(Prefix
(Low_Bound
(N
)));
19903 Process_Range_Expr_In_Decl
(R
, T
);
19905 elsif Nkind
(N
) = N_Subtype_Indication
then
19907 -- The index is given by a subtype with a range constraint
19909 T
:= Base_Type
(Entity
(Subtype_Mark
(N
)));
19911 if not Is_Discrete_Type
(T
) then
19912 Error_Msg_N
("discrete type required for range", N
);
19913 Set_Etype
(N
, Any_Type
);
19917 R
:= Range_Expression
(Constraint
(N
));
19920 Process_Range_Expr_In_Decl
(R
, Entity
(Subtype_Mark
(N
)));
19922 elsif Nkind
(N
) = N_Attribute_Reference
then
19924 -- Catch beginner's error (use of attribute other than 'Range)
19926 if Attribute_Name
(N
) /= Name_Range
then
19927 Error_Msg_N
("expect attribute ''Range", N
);
19928 Set_Etype
(N
, Any_Type
);
19932 -- If the node denotes the range of a type mark, that is also the
19933 -- resulting type, and we do not need to create an Itype for it.
19935 if Is_Entity_Name
(Prefix
(N
))
19936 and then Comes_From_Source
(N
)
19937 and then Is_Discrete_Type
(Entity
(Prefix
(N
)))
19939 Def_Id
:= Entity
(Prefix
(N
));
19942 Analyze_And_Resolve
(N
);
19946 -- If none of the above, must be a subtype. We convert this to a
19947 -- range attribute reference because in the case of declared first
19948 -- named subtypes, the types in the range reference can be different
19949 -- from the type of the entity. A range attribute normalizes the
19950 -- reference and obtains the correct types for the bounds.
19952 -- This transformation is in the nature of an expansion, is only
19953 -- done if expansion is active. In particular, it is not done on
19954 -- formal generic types, because we need to retain the name of the
19955 -- original index for instantiation purposes.
19958 if not Is_Entity_Name
(N
) or else not Is_Type
(Entity
(N
)) then
19959 Error_Msg_N
("invalid subtype mark in discrete range", N
);
19960 Set_Etype
(N
, Any_Integer
);
19964 -- The type mark may be that of an incomplete type. It is only
19965 -- now that we can get the full view, previous analysis does
19966 -- not look specifically for a type mark.
19968 Set_Entity
(N
, Get_Full_View
(Entity
(N
)));
19969 Set_Etype
(N
, Entity
(N
));
19970 Def_Id
:= Entity
(N
);
19972 if not Is_Discrete_Type
(Def_Id
) then
19973 Error_Msg_N
("discrete type required for index", N
);
19974 Set_Etype
(N
, Any_Type
);
19979 if Expander_Active
then
19981 Make_Attribute_Reference
(Sloc
(N
),
19982 Attribute_Name
=> Name_Range
,
19983 Prefix
=> Relocate_Node
(N
)));
19985 -- The original was a subtype mark that does not freeze. This
19986 -- means that the rewritten version must not freeze either.
19988 Set_Must_Not_Freeze
(N
);
19989 Set_Must_Not_Freeze
(Prefix
(N
));
19990 Analyze_And_Resolve
(N
);
19994 -- If expander is inactive, type is legal, nothing else to construct
20001 if not Is_Discrete_Type
(T
) then
20002 Error_Msg_N
("discrete type required for range", N
);
20003 Set_Etype
(N
, Any_Type
);
20006 elsif T
= Any_Type
then
20007 Set_Etype
(N
, Any_Type
);
20011 -- We will now create the appropriate Itype to describe the range, but
20012 -- first a check. If we originally had a subtype, then we just label
20013 -- the range with this subtype. Not only is there no need to construct
20014 -- a new subtype, but it is wrong to do so for two reasons:
20016 -- 1. A legality concern, if we have a subtype, it must not freeze,
20017 -- and the Itype would cause freezing incorrectly
20019 -- 2. An efficiency concern, if we created an Itype, it would not be
20020 -- recognized as the same type for the purposes of eliminating
20021 -- checks in some circumstances.
20023 -- We signal this case by setting the subtype entity in Def_Id
20025 if No
(Def_Id
) then
20027 Create_Itype
(E_Void
, Related_Nod
, Related_Id
, 'D', Suffix_Index
);
20028 Set_Etype
(Def_Id
, Base_Type
(T
));
20030 if Is_Signed_Integer_Type
(T
) then
20031 Mutate_Ekind
(Def_Id
, E_Signed_Integer_Subtype
);
20033 elsif Is_Modular_Integer_Type
(T
) then
20034 Mutate_Ekind
(Def_Id
, E_Modular_Integer_Subtype
);
20037 Mutate_Ekind
(Def_Id
, E_Enumeration_Subtype
);
20038 Set_Is_Character_Type
(Def_Id
, Is_Character_Type
(T
));
20039 Set_First_Literal
(Def_Id
, First_Literal
(T
));
20042 Set_Size_Info
(Def_Id
, (T
));
20043 Set_RM_Size
(Def_Id
, RM_Size
(T
));
20044 Set_First_Rep_Item
(Def_Id
, First_Rep_Item
(T
));
20046 Set_Scalar_Range
(Def_Id
, R
);
20047 Conditional_Delay
(Def_Id
, T
);
20049 -- In the subtype indication case inherit properties of the parent
20051 if Nkind
(N
) = N_Subtype_Indication
then
20053 -- It is enough to inherit predicate flags and not the predicate
20054 -- functions, because predicates on an index type are illegal
20055 -- anyway and the flags are enough to detect them.
20057 Inherit_Predicate_Flags
(Def_Id
, Entity
(Subtype_Mark
(N
)));
20059 -- If the immediate parent of the new subtype is nonstatic, then
20060 -- the subtype we create is nonstatic as well, even if its bounds
20063 if not Is_OK_Static_Subtype
(Entity
(Subtype_Mark
(N
))) then
20064 Set_Is_Non_Static_Subtype
(Def_Id
);
20068 Set_Parent
(Def_Id
, N
);
20071 -- Final step is to label the index with this constructed type
20073 Set_Etype
(N
, Def_Id
);
20076 ------------------------------
20077 -- Modular_Type_Declaration --
20078 ------------------------------
20080 procedure Modular_Type_Declaration
(T
: Entity_Id
; Def
: Node_Id
) is
20081 Mod_Expr
: constant Node_Id
:= Expression
(Def
);
20084 procedure Set_Modular_Size
(Bits
: Int
);
20085 -- Sets RM_Size to Bits, and Esize to normal word size above this
20087 ----------------------
20088 -- Set_Modular_Size --
20089 ----------------------
20091 procedure Set_Modular_Size
(Bits
: Int
) is
20095 Set_RM_Size
(T
, UI_From_Int
(Bits
));
20097 if Bits
< System_Max_Binary_Modulus_Power
then
20100 while Siz
< 128 loop
20101 exit when Bits
<= Siz
;
20105 Set_Esize
(T
, UI_From_Int
(Siz
));
20108 Set_Esize
(T
, UI_From_Int
(System_Max_Binary_Modulus_Power
));
20111 if not Non_Binary_Modulus
(T
) and then Esize
(T
) = RM_Size
(T
) then
20112 Set_Is_Known_Valid
(T
);
20114 end Set_Modular_Size
;
20116 -- Start of processing for Modular_Type_Declaration
20119 -- If the mod expression is (exactly) 2 * literal, where literal is
20120 -- 128 or less, then almost certainly the * was meant to be **. Warn.
20122 if Warn_On_Suspicious_Modulus_Value
20123 and then Nkind
(Mod_Expr
) = N_Op_Multiply
20124 and then Nkind
(Left_Opnd
(Mod_Expr
)) = N_Integer_Literal
20125 and then Intval
(Left_Opnd
(Mod_Expr
)) = Uint_2
20126 and then Nkind
(Right_Opnd
(Mod_Expr
)) = N_Integer_Literal
20127 and then Intval
(Right_Opnd
(Mod_Expr
)) <= Uint_128
20130 ("suspicious MOD value, was '*'* intended'??.m?", Mod_Expr
);
20133 -- Proceed with analysis of mod expression
20135 Analyze_And_Resolve
(Mod_Expr
, Any_Integer
);
20138 Mutate_Ekind
(T
, E_Modular_Integer_Type
);
20139 Reinit_Alignment
(T
);
20140 Set_Is_Constrained
(T
);
20142 if not Is_OK_Static_Expression
(Mod_Expr
) then
20143 Flag_Non_Static_Expr
20144 ("non-static expression used for modular type bound!", Mod_Expr
);
20145 M_Val
:= 2 ** System_Max_Binary_Modulus_Power
;
20147 M_Val
:= Expr_Value
(Mod_Expr
);
20151 Error_Msg_N
("modulus value must be positive", Mod_Expr
);
20152 M_Val
:= 2 ** System_Max_Binary_Modulus_Power
;
20155 if M_Val
> 2 ** Standard_Long_Integer_Size
then
20156 Check_Restriction
(No_Long_Long_Integers
, Mod_Expr
);
20159 Set_Modulus
(T
, M_Val
);
20161 -- Create bounds for the modular type based on the modulus given in
20162 -- the type declaration and then analyze and resolve those bounds.
20164 Set_Scalar_Range
(T
,
20165 Make_Range
(Sloc
(Mod_Expr
),
20166 Low_Bound
=> Make_Integer_Literal
(Sloc
(Mod_Expr
), 0),
20167 High_Bound
=> Make_Integer_Literal
(Sloc
(Mod_Expr
), M_Val
- 1)));
20169 -- Properly analyze the literals for the range. We do this manually
20170 -- because we can't go calling Resolve, since we are resolving these
20171 -- bounds with the type, and this type is certainly not complete yet.
20173 Set_Etype
(Low_Bound
(Scalar_Range
(T
)), T
);
20174 Set_Etype
(High_Bound
(Scalar_Range
(T
)), T
);
20175 Set_Is_Static_Expression
(Low_Bound
(Scalar_Range
(T
)));
20176 Set_Is_Static_Expression
(High_Bound
(Scalar_Range
(T
)));
20178 -- Loop through powers of two to find number of bits required
20180 for Bits
in Int
range 0 .. System_Max_Binary_Modulus_Power
loop
20184 if M_Val
= 2 ** Bits
then
20185 Set_Modular_Size
(Bits
);
20190 elsif M_Val
< 2 ** Bits
then
20191 Set_Non_Binary_Modulus
(T
);
20193 if Bits
> System_Max_Nonbinary_Modulus_Power
then
20194 Error_Msg_Uint_1
:=
20195 UI_From_Int
(System_Max_Nonbinary_Modulus_Power
);
20197 ("nonbinary modulus exceeds limit (2 '*'*^ - 1)", Mod_Expr
);
20198 Set_Modular_Size
(System_Max_Binary_Modulus_Power
);
20202 -- In the nonbinary case, set size as per RM 13.3(55)
20204 Set_Modular_Size
(Bits
);
20211 -- If we fall through, then the size exceed System.Max_Binary_Modulus
20212 -- so we just signal an error and set the maximum size.
20214 Error_Msg_Uint_1
:= UI_From_Int
(System_Max_Binary_Modulus_Power
);
20215 Error_Msg_F
("modulus exceeds limit (2 '*'*^)", Mod_Expr
);
20217 Set_Modular_Size
(System_Max_Binary_Modulus_Power
);
20218 Reinit_Alignment
(T
);
20220 end Modular_Type_Declaration
;
20222 --------------------------
20223 -- New_Concatenation_Op --
20224 --------------------------
20226 procedure New_Concatenation_Op
(Typ
: Entity_Id
) is
20227 Loc
: constant Source_Ptr
:= Sloc
(Typ
);
20230 function Make_Op_Formal
(Typ
, Op
: Entity_Id
) return Entity_Id
;
20231 -- Create abbreviated declaration for the formal of a predefined
20232 -- Operator 'Op' of type 'Typ'
20234 --------------------
20235 -- Make_Op_Formal --
20236 --------------------
20238 function Make_Op_Formal
(Typ
, Op
: Entity_Id
) return Entity_Id
is
20239 Formal
: Entity_Id
;
20241 Formal
:= New_Internal_Entity
(E_In_Parameter
, Op
, Loc
, 'P');
20242 Set_Etype
(Formal
, Typ
);
20243 Set_Mechanism
(Formal
, Default_Mechanism
);
20245 end Make_Op_Formal
;
20247 -- Start of processing for New_Concatenation_Op
20250 Op
:= Make_Defining_Operator_Symbol
(Loc
, Name_Op_Concat
);
20252 Mutate_Ekind
(Op
, E_Operator
);
20253 Set_Is_Not_Self_Hidden
(Op
);
20254 Set_Scope
(Op
, Current_Scope
);
20255 Set_Etype
(Op
, Typ
);
20256 Set_Homonym
(Op
, Get_Name_Entity_Id
(Name_Op_Concat
));
20257 Set_Is_Immediately_Visible
(Op
);
20258 Set_Is_Intrinsic_Subprogram
(Op
);
20259 Set_Has_Completion
(Op
);
20260 Append_Entity
(Op
, Current_Scope
);
20262 Set_Name_Entity_Id
(Name_Op_Concat
, Op
);
20264 Append_Entity
(Make_Op_Formal
(Typ
, Op
), Op
);
20265 Append_Entity
(Make_Op_Formal
(Typ
, Op
), Op
);
20266 end New_Concatenation_Op
;
20268 -------------------------
20269 -- OK_For_Limited_Init --
20270 -------------------------
20272 -- ???Check all calls of this, and compare the conditions under which it's
20275 function OK_For_Limited_Init
20277 Exp
: Node_Id
) return Boolean
20280 return Is_CPP_Constructor_Call
(Exp
)
20281 or else (Ada_Version
>= Ada_2005
20282 and then not Debug_Flag_Dot_L
20283 and then OK_For_Limited_Init_In_05
(Typ
, Exp
));
20284 end OK_For_Limited_Init
;
20286 -------------------------------
20287 -- OK_For_Limited_Init_In_05 --
20288 -------------------------------
20290 function OK_For_Limited_Init_In_05
20292 Exp
: Node_Id
) return Boolean
20295 -- An object of a limited interface type can be initialized with any
20296 -- expression of a nonlimited descendant type. However this does not
20297 -- apply if this is a view conversion of some other expression. This
20298 -- is checked below.
20300 if Is_Class_Wide_Type
(Typ
)
20301 and then Is_Limited_Interface
(Typ
)
20302 and then not Is_Limited_Type
(Etype
(Exp
))
20303 and then Nkind
(Exp
) /= N_Type_Conversion
20308 -- Ada 2005 (AI-287, AI-318): Relax the strictness of the front end in
20309 -- case of limited aggregates (including extension aggregates), and
20310 -- function calls. The function call may have been given in prefixed
20311 -- notation, in which case the original node is an indexed component.
20312 -- If the function is parameterless, the original node was an explicit
20313 -- dereference. The function may also be parameterless, in which case
20314 -- the source node is just an identifier.
20316 -- A branch of a conditional expression may have been removed if the
20317 -- condition is statically known. This happens during expansion, and
20318 -- thus will not happen if previous errors were encountered. The check
20319 -- will have been performed on the chosen branch, which replaces the
20320 -- original conditional expression.
20326 case Nkind
(Original_Node
(Exp
)) is
20328 | N_Delta_Aggregate
20329 | N_Extension_Aggregate
20335 when N_Identifier
=>
20336 return Present
(Entity
(Original_Node
(Exp
)))
20337 and then Ekind
(Entity
(Original_Node
(Exp
))) = E_Function
;
20339 when N_Qualified_Expression
=>
20341 OK_For_Limited_Init_In_05
20342 (Typ
, Expression
(Original_Node
(Exp
)));
20344 -- Ada 2005 (AI-251): If a class-wide interface object is initialized
20345 -- with a function call, the expander has rewritten the call into an
20346 -- N_Type_Conversion node to force displacement of the pointer to
20347 -- reference the component containing the secondary dispatch table.
20348 -- Otherwise a type conversion is not a legal context.
20349 -- A return statement for a build-in-place function returning a
20350 -- synchronized type also introduces an unchecked conversion.
20352 when N_Type_Conversion
20353 | N_Unchecked_Type_Conversion
20355 return not Comes_From_Source
(Exp
)
20357 -- If the conversion has been rewritten, check Original_Node;
20358 -- otherwise, check the expression of the compiler-generated
20359 -- conversion (which is a conversion that we want to ignore
20360 -- for purposes of the limited-initialization restrictions).
20362 (if Is_Rewrite_Substitution
(Exp
)
20363 then OK_For_Limited_Init_In_05
(Typ
, Original_Node
(Exp
))
20364 else OK_For_Limited_Init_In_05
(Typ
, Expression
(Exp
)));
20366 when N_Explicit_Dereference
20367 | N_Indexed_Component
20368 | N_Selected_Component
20370 return Nkind
(Exp
) = N_Function_Call
;
20372 -- A use of 'Input is a function call, hence allowed. Normally the
20373 -- attribute will be changed to a call, but the attribute by itself
20374 -- can occur with -gnatc.
20376 when N_Attribute_Reference
=>
20377 return Attribute_Name
(Original_Node
(Exp
)) = Name_Input
;
20379 -- "return raise ..." is OK
20381 when N_Raise_Expression
=>
20384 -- For a case expression, all dependent expressions must be legal
20386 when N_Case_Expression
=>
20391 Alt
:= First
(Alternatives
(Original_Node
(Exp
)));
20392 while Present
(Alt
) loop
20393 if not OK_For_Limited_Init_In_05
(Typ
, Expression
(Alt
)) then
20403 -- For an if expression, all dependent expressions must be legal
20405 when N_If_Expression
=>
20407 Then_Expr
: constant Node_Id
:=
20408 Next
(First
(Expressions
(Original_Node
(Exp
))));
20409 Else_Expr
: constant Node_Id
:= Next
(Then_Expr
);
20411 return OK_For_Limited_Init_In_05
(Typ
, Then_Expr
)
20413 OK_For_Limited_Init_In_05
(Typ
, Else_Expr
);
20419 end OK_For_Limited_Init_In_05
;
20421 -------------------------------------------
20422 -- Ordinary_Fixed_Point_Type_Declaration --
20423 -------------------------------------------
20425 procedure Ordinary_Fixed_Point_Type_Declaration
20429 Loc
: constant Source_Ptr
:= Sloc
(Def
);
20430 Delta_Expr
: constant Node_Id
:= Delta_Expression
(Def
);
20431 RRS
: constant Node_Id
:= Real_Range_Specification
(Def
);
20432 Implicit_Base
: Entity_Id
;
20439 Check_Restriction
(No_Fixed_Point
, Def
);
20441 -- Create implicit base type
20444 Create_Itype
(E_Ordinary_Fixed_Point_Type
, Parent
(Def
), T
, 'B');
20445 Set_Etype
(Implicit_Base
, Implicit_Base
);
20447 -- Analyze and process delta expression
20449 Analyze_And_Resolve
(Delta_Expr
, Any_Real
);
20451 Check_Delta_Expression
(Delta_Expr
);
20452 Delta_Val
:= Expr_Value_R
(Delta_Expr
);
20454 Set_Delta_Value
(Implicit_Base
, Delta_Val
);
20456 -- Compute default small from given delta, which is the largest power
20457 -- of two that does not exceed the given delta value.
20467 if Delta_Val
< Ureal_1
then
20468 while Delta_Val
< Tmp
loop
20469 Tmp
:= Tmp
/ Ureal_2
;
20470 Scale
:= Scale
+ 1;
20475 Tmp
:= Tmp
* Ureal_2
;
20476 exit when Tmp
> Delta_Val
;
20477 Scale
:= Scale
- 1;
20481 Small_Val
:= UR_From_Components
(Uint_1
, UI_From_Int
(Scale
), 2);
20484 Set_Small_Value
(Implicit_Base
, Small_Val
);
20486 -- If no range was given, set a dummy range
20488 if RRS
<= Empty_Or_Error
then
20489 Low_Val
:= -Small_Val
;
20490 High_Val
:= Small_Val
;
20492 -- Otherwise analyze and process given range
20496 Low
: constant Node_Id
:= Low_Bound
(RRS
);
20497 High
: constant Node_Id
:= High_Bound
(RRS
);
20500 Analyze_And_Resolve
(Low
, Any_Real
);
20501 Analyze_And_Resolve
(High
, Any_Real
);
20502 Check_Real_Bound
(Low
);
20503 Check_Real_Bound
(High
);
20505 -- Obtain and set the range
20507 Low_Val
:= Expr_Value_R
(Low
);
20508 High_Val
:= Expr_Value_R
(High
);
20510 if Low_Val
> High_Val
then
20511 Error_Msg_NE
("??fixed point type& has null range", Def
, T
);
20516 -- The range for both the implicit base and the declared first subtype
20517 -- cannot be set yet, so we use the special routine Set_Fixed_Range to
20518 -- set a temporary range in place. Note that the bounds of the base
20519 -- type will be widened to be symmetrical and to fill the available
20520 -- bits when the type is frozen.
20522 -- We could do this with all discrete types, and probably should, but
20523 -- we absolutely have to do it for fixed-point, since the end-points
20524 -- of the range and the size are determined by the small value, which
20525 -- could be reset before the freeze point.
20527 Set_Fixed_Range
(Implicit_Base
, Loc
, Low_Val
, High_Val
);
20528 Set_Fixed_Range
(T
, Loc
, Low_Val
, High_Val
);
20530 -- Complete definition of first subtype. The inheritance of the rep item
20531 -- chain ensures that SPARK-related pragmas are not clobbered when the
20532 -- ordinary fixed point type acts as a full view of a private type.
20534 Mutate_Ekind
(T
, E_Ordinary_Fixed_Point_Subtype
);
20535 Set_Etype
(T
, Implicit_Base
);
20536 Reinit_Size_Align
(T
);
20537 Inherit_Rep_Item_Chain
(T
, Implicit_Base
);
20538 Set_Small_Value
(T
, Small_Val
);
20539 Set_Delta_Value
(T
, Delta_Val
);
20540 Set_Is_Constrained
(T
);
20541 end Ordinary_Fixed_Point_Type_Declaration
;
20543 ----------------------------------
20544 -- Preanalyze_Assert_Expression --
20545 ----------------------------------
20547 procedure Preanalyze_Assert_Expression
(N
: Node_Id
; T
: Entity_Id
) is
20549 In_Assertion_Expr
:= In_Assertion_Expr
+ 1;
20550 Preanalyze_Spec_Expression
(N
, T
);
20551 In_Assertion_Expr
:= In_Assertion_Expr
- 1;
20552 end Preanalyze_Assert_Expression
;
20554 -- ??? The variant below explicitly saves and restores all the flags,
20555 -- because it is impossible to compose the existing variety of
20556 -- Analyze/Resolve (and their wrappers, e.g. Preanalyze_Spec_Expression)
20557 -- to achieve the desired semantics.
20559 procedure Preanalyze_Assert_Expression
(N
: Node_Id
) is
20560 Save_In_Spec_Expression
: constant Boolean := In_Spec_Expression
;
20561 Save_Must_Not_Freeze
: constant Boolean := Must_Not_Freeze
(N
);
20562 Save_Full_Analysis
: constant Boolean := Full_Analysis
;
20565 In_Assertion_Expr
:= In_Assertion_Expr
+ 1;
20566 In_Spec_Expression
:= True;
20567 Set_Must_Not_Freeze
(N
);
20568 Inside_Preanalysis_Without_Freezing
:=
20569 Inside_Preanalysis_Without_Freezing
+ 1;
20570 Full_Analysis
:= False;
20571 Expander_Mode_Save_And_Set
(False);
20573 if GNATprove_Mode
then
20574 Analyze_And_Resolve
(N
);
20576 Analyze_And_Resolve
(N
, Suppress
=> All_Checks
);
20579 Expander_Mode_Restore
;
20580 Full_Analysis
:= Save_Full_Analysis
;
20581 Inside_Preanalysis_Without_Freezing
:=
20582 Inside_Preanalysis_Without_Freezing
- 1;
20583 Set_Must_Not_Freeze
(N
, Save_Must_Not_Freeze
);
20584 In_Spec_Expression
:= Save_In_Spec_Expression
;
20585 In_Assertion_Expr
:= In_Assertion_Expr
- 1;
20586 end Preanalyze_Assert_Expression
;
20588 -----------------------------------
20589 -- Preanalyze_Default_Expression --
20590 -----------------------------------
20592 procedure Preanalyze_Default_Expression
(N
: Node_Id
; T
: Entity_Id
) is
20593 Save_In_Default_Expr
: constant Boolean := In_Default_Expr
;
20594 Save_In_Spec_Expression
: constant Boolean := In_Spec_Expression
;
20597 In_Default_Expr
:= True;
20598 In_Spec_Expression
:= True;
20600 Preanalyze_With_Freezing_And_Resolve
(N
, T
);
20602 In_Default_Expr
:= Save_In_Default_Expr
;
20603 In_Spec_Expression
:= Save_In_Spec_Expression
;
20604 end Preanalyze_Default_Expression
;
20606 --------------------------------
20607 -- Preanalyze_Spec_Expression --
20608 --------------------------------
20610 procedure Preanalyze_Spec_Expression
(N
: Node_Id
; T
: Entity_Id
) is
20611 Save_In_Spec_Expression
: constant Boolean := In_Spec_Expression
;
20613 In_Spec_Expression
:= True;
20614 Preanalyze_And_Resolve
(N
, T
);
20615 In_Spec_Expression
:= Save_In_Spec_Expression
;
20616 end Preanalyze_Spec_Expression
;
20618 ----------------------------------------
20619 -- Prepare_Private_Subtype_Completion --
20620 ----------------------------------------
20622 procedure Prepare_Private_Subtype_Completion
20624 Related_Nod
: Node_Id
)
20626 Id_B
: constant Entity_Id
:= Base_Type
(Id
);
20627 Full_B
: constant Entity_Id
:= Full_View
(Id_B
);
20631 if Present
(Full_B
) then
20633 -- The Base_Type is already completed, we can complete the subtype
20634 -- now. We have to create a new entity with the same name, Thus we
20635 -- can't use Create_Itype.
20637 Full
:= Make_Defining_Identifier
(Sloc
(Id
), Chars
(Id
));
20638 Set_Is_Itype
(Full
);
20639 Set_Associated_Node_For_Itype
(Full
, Related_Nod
);
20640 Complete_Private_Subtype
(Id
, Full
, Full_B
, Related_Nod
);
20641 Set_Full_View
(Id
, Full
);
20644 -- The parent subtype may be private, but the base might not, in some
20645 -- nested instances. In that case, the subtype does not need to be
20646 -- exchanged. It would still be nice to make private subtypes and their
20647 -- bases consistent at all times ???
20649 if Is_Private_Type
(Id_B
) then
20650 Append_Elmt
(Id
, Private_Dependents
(Id_B
));
20652 end Prepare_Private_Subtype_Completion
;
20654 ---------------------------
20655 -- Process_Discriminants --
20656 ---------------------------
20658 procedure Process_Discriminants
20660 Prev
: Entity_Id
:= Empty
)
20662 Elist
: constant Elist_Id
:= New_Elmt_List
;
20665 Discr_Number
: Uint
;
20666 Discr_Type
: Entity_Id
;
20667 Default_Present
: Boolean := False;
20668 Default_Not_Present
: Boolean := False;
20671 -- A composite type other than an array type can have discriminants.
20672 -- On entry, the current scope is the composite type.
20674 -- The discriminants are initially entered into the scope of the type
20675 -- via Enter_Name with the default Ekind of E_Void to prevent premature
20676 -- use, as explained at the end of this procedure.
20678 Discr
:= First
(Discriminant_Specifications
(N
));
20679 while Present
(Discr
) loop
20680 Enter_Name
(Defining_Identifier
(Discr
));
20682 -- For navigation purposes we add a reference to the discriminant
20683 -- in the entity for the type. If the current declaration is a
20684 -- completion, place references on the partial view. Otherwise the
20685 -- type is the current scope.
20687 if Present
(Prev
) then
20689 -- The references go on the partial view, if present. If the
20690 -- partial view has discriminants, the references have been
20691 -- generated already.
20693 if not Has_Discriminants
(Prev
) then
20694 Generate_Reference
(Prev
, Defining_Identifier
(Discr
), 'd');
20698 (Current_Scope
, Defining_Identifier
(Discr
), 'd');
20701 if Nkind
(Discriminant_Type
(Discr
)) = N_Access_Definition
then
20702 Check_Anonymous_Access_Component
20704 Typ
=> Defining_Identifier
(N
),
20707 Access_Def
=> Discriminant_Type
(Discr
));
20709 -- if Check_Anonymous_Access_Component replaced Discr then
20710 -- its Original_Node points to the old Discr and the access type
20711 -- for Discr_Type has already been created.
20713 if Is_Rewrite_Substitution
(Discr
) then
20714 Discr_Type
:= Etype
(Discriminant_Type
(Discr
));
20717 Access_Definition
(Discr
, Discriminant_Type
(Discr
));
20719 -- Ada 2005 (AI-254)
20721 if Present
(Access_To_Subprogram_Definition
20722 (Discriminant_Type
(Discr
)))
20723 and then Protected_Present
(Access_To_Subprogram_Definition
20724 (Discriminant_Type
(Discr
)))
20727 Replace_Anonymous_Access_To_Protected_Subprogram
(Discr
);
20731 Find_Type
(Discriminant_Type
(Discr
));
20732 Discr_Type
:= Etype
(Discriminant_Type
(Discr
));
20734 if Error_Posted
(Discriminant_Type
(Discr
)) then
20735 Discr_Type
:= Any_Type
;
20739 -- Handling of discriminants that are access types
20741 if Is_Access_Type
(Discr_Type
) then
20743 -- Ada 2005 (AI-230): Access discriminant allowed in non-
20744 -- limited record types
20746 if Ada_Version
< Ada_2005
then
20747 Check_Access_Discriminant_Requires_Limited
20748 (Discr
, Discriminant_Type
(Discr
));
20751 if Ada_Version
= Ada_83
and then Comes_From_Source
(Discr
) then
20753 ("(Ada 83) access discriminant not allowed", Discr
);
20756 -- If not access type, must be a discrete type
20758 elsif not Is_Discrete_Type
(Discr_Type
) then
20760 ("discriminants must have a discrete or access type",
20761 Discriminant_Type
(Discr
));
20764 Set_Etype
(Defining_Identifier
(Discr
), Discr_Type
);
20766 -- If a discriminant specification includes the assignment compound
20767 -- delimiter followed by an expression, the expression is the default
20768 -- expression of the discriminant; the default expression must be of
20769 -- the type of the discriminant. (RM 3.7.1) Since this expression is
20770 -- a default expression, we do the special preanalysis, since this
20771 -- expression does not freeze (see section "Handling of Default and
20772 -- Per-Object Expressions" in spec of package Sem).
20774 if Present
(Expression
(Discr
)) then
20775 Preanalyze_Default_Expression
(Expression
(Discr
), Discr_Type
);
20779 if Nkind
(N
) = N_Formal_Type_Declaration
then
20781 ("discriminant defaults not allowed for formal type",
20782 Expression
(Discr
));
20784 -- Flag an error for a tagged type with defaulted discriminants,
20785 -- excluding limited tagged types when compiling for Ada 2012
20786 -- (see AI05-0214).
20788 elsif Is_Tagged_Type
(Current_Scope
)
20789 and then (not Is_Limited_Type
(Current_Scope
)
20790 or else Ada_Version
< Ada_2012
)
20791 and then Comes_From_Source
(N
)
20793 -- Note: see similar test in Check_Or_Process_Discriminants, to
20794 -- handle the (illegal) case of the completion of an untagged
20795 -- view with discriminants with defaults by a tagged full view.
20796 -- We skip the check if Discr does not come from source, to
20797 -- account for the case of an untagged derived type providing
20798 -- defaults for a renamed discriminant from a private untagged
20799 -- ancestor with a tagged full view (ACATS B460006).
20801 if Ada_Version
>= Ada_2012
then
20803 ("discriminants of nonlimited tagged type cannot have"
20805 Expression
(Discr
));
20808 ("discriminants of tagged type cannot have defaults",
20809 Expression
(Discr
));
20813 Default_Present
:= True;
20814 Append_Elmt
(Expression
(Discr
), Elist
);
20816 -- Tag the defining identifiers for the discriminants with
20817 -- their corresponding default expressions from the tree.
20819 Set_Discriminant_Default_Value
20820 (Defining_Identifier
(Discr
), Expression
(Discr
));
20823 -- In gnatc or GNATprove mode, make sure set Do_Range_Check flag
20824 -- gets set unless we can be sure that no range check is required.
20826 if not Expander_Active
20829 (Expression
(Discr
), Discr_Type
, Assume_Valid
=> True)
20831 Set_Do_Range_Check
(Expression
(Discr
));
20834 -- No default discriminant value given
20837 Default_Not_Present
:= True;
20840 -- Ada 2005 (AI-231): Create an Itype that is a duplicate of
20841 -- Discr_Type but with the null-exclusion attribute
20843 if Ada_Version
>= Ada_2005
then
20845 -- Ada 2005 (AI-231): Static checks
20847 if Can_Never_Be_Null
(Discr_Type
) then
20848 Null_Exclusion_Static_Checks
(Discr
);
20850 elsif Is_Access_Type
(Discr_Type
)
20851 and then Null_Exclusion_Present
(Discr
)
20853 -- No need to check itypes because in their case this check
20854 -- was done at their point of creation
20856 and then not Is_Itype
(Discr_Type
)
20858 if Can_Never_Be_Null
(Discr_Type
) then
20860 ("`NOT NULL` not allowed (& already excludes null)",
20865 Set_Etype
(Defining_Identifier
(Discr
),
20866 Create_Null_Excluding_Itype
20868 Related_Nod
=> Discr
));
20870 -- Check for improper null exclusion if the type is otherwise
20871 -- legal for a discriminant.
20873 elsif Null_Exclusion_Present
(Discr
)
20874 and then Is_Discrete_Type
(Discr_Type
)
20877 ("null exclusion can only apply to an access type", Discr
);
20880 -- Ada 2005 (AI-402): access discriminants of nonlimited types
20881 -- can't have defaults. Synchronized types, or types that are
20882 -- explicitly limited are fine, but special tests apply to derived
20883 -- types in generics: in a generic body we have to assume the
20884 -- worst, and therefore defaults are not allowed if the parent is
20885 -- a generic formal private type (see ACATS B370001).
20887 if Is_Access_Type
(Discr_Type
) and then Default_Present
then
20888 if Ekind
(Discr_Type
) /= E_Anonymous_Access_Type
20889 or else Is_Limited_Record
(Current_Scope
)
20890 or else Is_Concurrent_Type
(Current_Scope
)
20891 or else Is_Concurrent_Record_Type
(Current_Scope
)
20892 or else Ekind
(Current_Scope
) = E_Limited_Private_Type
20894 if not Is_Derived_Type
(Current_Scope
)
20895 or else not Is_Generic_Type
(Etype
(Current_Scope
))
20896 or else not In_Package_Body
(Scope
(Etype
(Current_Scope
)))
20897 or else Limited_Present
20898 (Type_Definition
(Parent
(Current_Scope
)))
20904 ("access discriminants of nonlimited types cannot "
20905 & "have defaults", Expression
(Discr
));
20908 elsif Present
(Expression
(Discr
)) then
20910 ("(Ada 2005) access discriminants of nonlimited types "
20911 & "cannot have defaults", Expression
(Discr
));
20916 -- A discriminant cannot be effectively volatile (SPARK RM 7.1.3(4)).
20917 -- This check is relevant only when SPARK_Mode is on as it is not a
20918 -- standard Ada legality rule. The only way for a discriminant to be
20919 -- effectively volatile is to have an effectively volatile type, so
20920 -- we check this directly, because the Ekind of Discr might not be
20921 -- set yet (to help preventing cascaded errors on derived types).
20924 and then Is_Effectively_Volatile
(Discr_Type
)
20926 Error_Msg_N
("discriminant cannot be volatile", Discr
);
20932 -- An element list consisting of the default expressions of the
20933 -- discriminants is constructed in the above loop and used to set
20934 -- the Discriminant_Constraint attribute for the type. If an object
20935 -- is declared of this (record or task) type without any explicit
20936 -- discriminant constraint given, this element list will form the
20937 -- actual parameters for the corresponding initialization procedure
20940 Set_Discriminant_Constraint
(Current_Scope
, Elist
);
20941 Set_Stored_Constraint
(Current_Scope
, No_Elist
);
20943 -- Default expressions must be provided either for all or for none
20944 -- of the discriminants of a discriminant part. (RM 3.7.1)
20946 if Default_Present
and then Default_Not_Present
then
20948 ("incomplete specification of defaults for discriminants", N
);
20951 -- The use of the name of a discriminant is not allowed in default
20952 -- expressions of a discriminant part if the specification of the
20953 -- discriminant is itself given in the discriminant part. (RM 3.7.1)
20955 -- To detect this, the discriminant names are entered initially with an
20956 -- Ekind of E_Void (which is the default Ekind given by Enter_Name). Any
20957 -- attempt to use a void entity (for example in an expression that is
20958 -- type-checked) produces the error message: premature usage. Now after
20959 -- completing the semantic analysis of the discriminant part, we can set
20960 -- the Ekind of all the discriminants appropriately.
20962 Discr
:= First
(Discriminant_Specifications
(N
));
20963 Discr_Number
:= Uint_1
;
20964 while Present
(Discr
) loop
20965 Id
:= Defining_Identifier
(Discr
);
20967 if Ekind
(Id
) = E_In_Parameter
then
20968 Reinit_Field_To_Zero
(Id
, F_Discriminal_Link
);
20971 Mutate_Ekind
(Id
, E_Discriminant
);
20972 Set_Is_Not_Self_Hidden
(Id
);
20973 Reinit_Component_Location
(Id
);
20975 Set_Discriminant_Number
(Id
, Discr_Number
);
20977 -- Make sure this is always set, even in illegal programs
20979 Set_Corresponding_Discriminant
(Id
, Empty
);
20981 -- Initialize the Original_Record_Component to the entity itself.
20982 -- Inherit_Components will propagate the right value to
20983 -- discriminants in derived record types.
20985 Set_Original_Record_Component
(Id
, Id
);
20987 -- Create the discriminal for the discriminant
20989 Build_Discriminal
(Id
);
20992 Discr_Number
:= Discr_Number
+ 1;
20995 Set_Has_Discriminants
(Current_Scope
);
20996 end Process_Discriminants
;
20998 -----------------------
20999 -- Process_Full_View --
21000 -----------------------
21002 -- WARNING: This routine manages Ghost regions. Return statements must be
21003 -- replaced by gotos which jump to the end of the routine and restore the
21006 procedure Process_Full_View
(N
: Node_Id
; Full_T
, Priv_T
: Entity_Id
) is
21007 procedure Collect_Implemented_Interfaces
21009 Ifaces
: Elist_Id
);
21010 -- Ada 2005: Gather all the interfaces that Typ directly or
21011 -- inherently implements. Duplicate entries are not added to
21012 -- the list Ifaces.
21014 ------------------------------------
21015 -- Collect_Implemented_Interfaces --
21016 ------------------------------------
21018 procedure Collect_Implemented_Interfaces
21023 Iface_Elmt
: Elmt_Id
;
21026 -- Abstract interfaces are only associated with tagged record types
21028 if not Is_Tagged_Type
(Typ
) or else not Is_Record_Type
(Typ
) then
21032 -- Recursively climb to the ancestors
21034 if Etype
(Typ
) /= Typ
21036 -- Protect the frontend against wrong cyclic declarations like:
21038 -- type B is new A with private;
21039 -- type C is new A with private;
21041 -- type B is new C with null record;
21042 -- type C is new B with null record;
21044 and then Etype
(Typ
) /= Priv_T
21045 and then Etype
(Typ
) /= Full_T
21047 -- Keep separate the management of private type declarations
21049 if Ekind
(Typ
) = E_Record_Type_With_Private
then
21051 -- Handle the following illegal usage:
21052 -- type Private_Type is tagged private;
21054 -- type Private_Type is new Type_Implementing_Iface;
21056 if Present
(Full_View
(Typ
))
21057 and then Etype
(Typ
) /= Full_View
(Typ
)
21059 if Is_Interface
(Etype
(Typ
)) then
21060 Append_Unique_Elmt
(Etype
(Typ
), Ifaces
);
21063 Collect_Implemented_Interfaces
(Etype
(Typ
), Ifaces
);
21066 -- Non-private types
21069 if Is_Interface
(Etype
(Typ
)) then
21070 Append_Unique_Elmt
(Etype
(Typ
), Ifaces
);
21073 Collect_Implemented_Interfaces
(Etype
(Typ
), Ifaces
);
21077 -- Handle entities in the list of abstract interfaces
21079 if Present
(Interfaces
(Typ
)) then
21080 Iface_Elmt
:= First_Elmt
(Interfaces
(Typ
));
21081 while Present
(Iface_Elmt
) loop
21082 Iface
:= Node
(Iface_Elmt
);
21084 pragma Assert
(Is_Interface
(Iface
));
21086 if not Contain_Interface
(Iface
, Ifaces
) then
21087 Append_Elmt
(Iface
, Ifaces
);
21088 Collect_Implemented_Interfaces
(Iface
, Ifaces
);
21091 Next_Elmt
(Iface_Elmt
);
21094 end Collect_Implemented_Interfaces
;
21098 Saved_GM
: constant Ghost_Mode_Type
:= Ghost_Mode
;
21099 Saved_IGR
: constant Node_Id
:= Ignored_Ghost_Region
;
21100 -- Save the Ghost-related attributes to restore on exit
21102 Full_Indic
: Node_Id
;
21103 Full_Parent
: Entity_Id
;
21104 Priv_Parent
: Entity_Id
;
21106 -- Start of processing for Process_Full_View
21109 Mark_And_Set_Ghost_Completion
(N
, Priv_T
);
21111 -- First some sanity checks that must be done after semantic
21112 -- decoration of the full view and thus cannot be placed with other
21113 -- similar checks in Find_Type_Name
21115 if not Is_Limited_Type
(Priv_T
)
21116 and then (Is_Limited_Type
(Full_T
)
21117 or else Is_Limited_Composite
(Full_T
))
21119 if In_Instance
then
21123 ("completion of nonlimited type cannot be limited", Full_T
);
21124 Explain_Limited_Type
(Full_T
, Full_T
);
21127 elsif Is_Abstract_Type
(Full_T
)
21128 and then not Is_Abstract_Type
(Priv_T
)
21131 ("completion of nonabstract type cannot be abstract", Full_T
);
21133 elsif Is_Tagged_Type
(Priv_T
)
21134 and then Is_Limited_Type
(Priv_T
)
21135 and then not Is_Limited_Type
(Full_T
)
21137 -- If pragma CPP_Class was applied to the private declaration
21138 -- propagate the limitedness to the full-view
21140 if Is_CPP_Class
(Priv_T
) then
21141 Set_Is_Limited_Record
(Full_T
);
21143 -- GNAT allow its own definition of Limited_Controlled to disobey
21144 -- this rule in order in ease the implementation. This test is safe
21145 -- because Root_Controlled is defined in a child of System that
21146 -- normal programs are not supposed to use.
21148 elsif Is_RTE
(Etype
(Full_T
), RE_Root_Controlled
) then
21149 Set_Is_Limited_Composite
(Full_T
);
21152 ("completion of limited tagged type must be limited", Full_T
);
21155 elsif Is_Generic_Type
(Priv_T
) then
21156 Error_Msg_N
("generic type cannot have a completion", Full_T
);
21159 -- Check that ancestor interfaces of private and full views are
21160 -- consistent. We omit this check for synchronized types because
21161 -- they are performed on the corresponding record type when frozen.
21163 if Ada_Version
>= Ada_2005
21164 and then Is_Tagged_Type
(Priv_T
)
21165 and then Is_Tagged_Type
(Full_T
)
21166 and then not Is_Concurrent_Type
(Full_T
)
21170 Priv_T_Ifaces
: constant Elist_Id
:= New_Elmt_List
;
21171 Full_T_Ifaces
: constant Elist_Id
:= New_Elmt_List
;
21174 Collect_Implemented_Interfaces
(Priv_T
, Priv_T_Ifaces
);
21175 Collect_Implemented_Interfaces
(Full_T
, Full_T_Ifaces
);
21177 -- Ada 2005 (AI-251): The partial view shall be a descendant of
21178 -- an interface type if and only if the full type is descendant
21179 -- of the interface type (AARM 7.3 (7.3/2)).
21181 Iface
:= Find_Hidden_Interface
(Priv_T_Ifaces
, Full_T_Ifaces
);
21183 if Present
(Iface
) then
21185 ("interface in partial view& not implemented by full type "
21186 & "(RM-2005 7.3 (7.3/2))", Full_T
, Iface
);
21189 Iface
:= Find_Hidden_Interface
(Full_T_Ifaces
, Priv_T_Ifaces
);
21191 if Present
(Iface
) then
21193 ("interface & not implemented by partial view "
21194 & "(RM-2005 7.3 (7.3/2))", Full_T
, Iface
);
21199 if Is_Tagged_Type
(Priv_T
)
21200 and then Nkind
(Parent
(Priv_T
)) = N_Private_Extension_Declaration
21201 and then Is_Derived_Type
(Full_T
)
21203 Priv_Parent
:= Etype
(Priv_T
);
21205 -- The full view of a private extension may have been transformed
21206 -- into an unconstrained derived type declaration and a subtype
21207 -- declaration (see build_derived_record_type for details).
21209 if Nkind
(N
) = N_Subtype_Declaration
then
21210 Full_Indic
:= Subtype_Indication
(N
);
21211 Full_Parent
:= Etype
(Base_Type
(Full_T
));
21213 Full_Indic
:= Subtype_Indication
(Type_Definition
(N
));
21214 Full_Parent
:= Etype
(Full_T
);
21217 -- Check that the parent type of the full type is a descendant of
21218 -- the ancestor subtype given in the private extension. If either
21219 -- entity has an Etype equal to Any_Type then we had some previous
21220 -- error situation [7.3(8)].
21222 if Priv_Parent
= Any_Type
or else Full_Parent
= Any_Type
then
21225 -- Ada 2005 (AI-251): Interfaces in the full type can be given in
21226 -- any order. Therefore we don't have to check that its parent must
21227 -- be a descendant of the parent of the private type declaration.
21229 elsif Is_Interface
(Priv_Parent
)
21230 and then Is_Interface
(Full_Parent
)
21234 -- Ada 2005 (AI-251): If the parent of the private type declaration
21235 -- is an interface there is no need to check that it is an ancestor
21236 -- of the associated full type declaration. The required tests for
21237 -- this case are performed by Build_Derived_Record_Type.
21239 elsif not Is_Interface
(Base_Type
(Priv_Parent
))
21240 and then not Is_Ancestor
(Base_Type
(Priv_Parent
), Full_Parent
)
21243 ("parent of full type must descend from parent of private "
21244 & "extension", Full_Indic
);
21246 -- First check a formal restriction, and then proceed with checking
21247 -- Ada rules. Since the formal restriction is not a serious error, we
21248 -- don't prevent further error detection for this check, hence the
21252 -- Check the rules of 7.3(10): if the private extension inherits
21253 -- known discriminants, then the full type must also inherit those
21254 -- discriminants from the same (ancestor) type, and the parent
21255 -- subtype of the full type must be constrained if and only if
21256 -- the ancestor subtype of the private extension is constrained.
21258 if No
(Discriminant_Specifications
(Parent
(Priv_T
)))
21259 and then not Has_Unknown_Discriminants
(Priv_T
)
21260 and then Has_Discriminants
(Base_Type
(Priv_Parent
))
21263 Priv_Indic
: constant Node_Id
:=
21264 Subtype_Indication
(Parent
(Priv_T
));
21266 Priv_Constr
: constant Boolean :=
21267 Is_Constrained
(Priv_Parent
)
21269 Nkind
(Priv_Indic
) = N_Subtype_Indication
21271 Is_Constrained
(Entity
(Priv_Indic
));
21273 Full_Constr
: constant Boolean :=
21274 Is_Constrained
(Full_Parent
)
21276 Nkind
(Full_Indic
) = N_Subtype_Indication
21278 Is_Constrained
(Entity
(Full_Indic
));
21280 Priv_Discr
: Entity_Id
;
21281 Full_Discr
: Entity_Id
;
21284 Priv_Discr
:= First_Discriminant
(Priv_Parent
);
21285 Full_Discr
:= First_Discriminant
(Full_Parent
);
21286 while Present
(Priv_Discr
) and then Present
(Full_Discr
) loop
21287 if Original_Record_Component
(Priv_Discr
) =
21288 Original_Record_Component
(Full_Discr
)
21290 Corresponding_Discriminant
(Priv_Discr
) =
21291 Corresponding_Discriminant
(Full_Discr
)
21298 Next_Discriminant
(Priv_Discr
);
21299 Next_Discriminant
(Full_Discr
);
21302 if Present
(Priv_Discr
) or else Present
(Full_Discr
) then
21304 ("full view must inherit discriminants of the parent "
21305 & "type used in the private extension", Full_Indic
);
21307 elsif Priv_Constr
and then not Full_Constr
then
21309 ("parent subtype of full type must be constrained",
21312 elsif Full_Constr
and then not Priv_Constr
then
21314 ("parent subtype of full type must be unconstrained",
21319 -- Check the rules of 7.3(12): if a partial view has neither
21320 -- known or unknown discriminants, then the full type
21321 -- declaration shall define a definite subtype.
21323 elsif not Has_Unknown_Discriminants
(Priv_T
)
21324 and then not Has_Discriminants
(Priv_T
)
21325 and then not Is_Constrained
(Full_T
)
21328 ("full view must define a constrained type if partial view "
21329 & "has no discriminants", Full_T
);
21332 -- Do we implement the following properly???
21333 -- If the ancestor subtype of a private extension has constrained
21334 -- discriminants, then the parent subtype of the full view shall
21335 -- impose a statically matching constraint on those discriminants
21340 -- For untagged types, verify that a type without discriminants is
21341 -- not completed with an unconstrained type. A separate error message
21342 -- is produced if the full type has defaulted discriminants.
21344 if Is_Definite_Subtype
(Priv_T
)
21345 and then not Is_Definite_Subtype
(Full_T
)
21347 Error_Msg_Sloc
:= Sloc
(Parent
(Priv_T
));
21349 ("full view of& not compatible with declaration#",
21352 if not Is_Tagged_Type
(Full_T
) then
21354 ("\one is constrained, the other unconstrained", Full_T
);
21359 -- AI-419: verify that the use of "limited" is consistent
21362 Orig_Decl
: constant Node_Id
:= Original_Node
(N
);
21365 if Nkind
(Parent
(Priv_T
)) = N_Private_Extension_Declaration
21366 and then Nkind
(Orig_Decl
) = N_Full_Type_Declaration
21368 (Type_Definition
(Orig_Decl
)) = N_Derived_Type_Definition
21370 if not Limited_Present
(Parent
(Priv_T
))
21371 and then not Synchronized_Present
(Parent
(Priv_T
))
21372 and then Limited_Present
(Type_Definition
(Orig_Decl
))
21375 ("full view of non-limited extension cannot be limited", N
);
21377 -- Conversely, if the partial view carries the limited keyword,
21378 -- the full view must as well, even if it may be redundant.
21380 elsif Limited_Present
(Parent
(Priv_T
))
21381 and then not Limited_Present
(Type_Definition
(Orig_Decl
))
21384 ("full view of limited extension must be explicitly limited",
21390 -- Ada 2005 (AI-443): A synchronized private extension must be
21391 -- completed by a task or protected type.
21393 if Ada_Version
>= Ada_2005
21394 and then Nkind
(Parent
(Priv_T
)) = N_Private_Extension_Declaration
21395 and then Synchronized_Present
(Parent
(Priv_T
))
21396 and then not Is_Concurrent_Type
(Full_T
)
21398 Error_Msg_N
("full view of synchronized extension must " &
21399 "be synchronized type", N
);
21402 -- Ada 2005 AI-363: if the full view has discriminants with
21403 -- defaults, it is illegal to declare constrained access subtypes
21404 -- whose designated type is the current type. This allows objects
21405 -- of the type that are declared in the heap to be unconstrained.
21407 if not Has_Unknown_Discriminants
(Priv_T
)
21408 and then not Has_Discriminants
(Priv_T
)
21409 and then Has_Defaulted_Discriminants
(Full_T
)
21411 Set_Has_Constrained_Partial_View
(Base_Type
(Full_T
));
21412 Set_Has_Constrained_Partial_View
(Priv_T
);
21415 -- Create a full declaration for all its subtypes recorded in
21416 -- Private_Dependents and swap them similarly to the base type. These
21417 -- are subtypes that have been define before the full declaration of
21418 -- the private type. We also swap the entry in Private_Dependents list
21419 -- so we can properly restore the private view on exit from the scope.
21422 Priv_Elmt
: Elmt_Id
;
21423 Priv_Scop
: Entity_Id
;
21428 Priv_Elmt
:= First_Elmt
(Private_Dependents
(Priv_T
));
21429 while Present
(Priv_Elmt
) loop
21430 Priv
:= Node
(Priv_Elmt
);
21431 Priv_Scop
:= Scope
(Priv
);
21433 if Ekind
(Priv
) in E_Private_Subtype
21434 | E_Limited_Private_Subtype
21435 | E_Record_Subtype_With_Private
21437 Full
:= Make_Defining_Identifier
(Sloc
(Priv
), Chars
(Priv
));
21438 Set_Is_Itype
(Full
);
21439 Set_Parent
(Full
, Parent
(Priv
));
21440 Set_Associated_Node_For_Itype
(Full
, N
);
21442 -- Now we need to complete the private subtype, but since the
21443 -- base type has already been swapped, we must also swap the
21444 -- subtypes (and thus, reverse the arguments in the call to
21445 -- Complete_Private_Subtype). Also note that we may need to
21446 -- re-establish the scope of the private subtype.
21448 Copy_And_Swap
(Priv
, Full
);
21450 if not In_Open_Scopes
(Priv_Scop
) then
21451 Push_Scope
(Priv_Scop
);
21454 -- Reset Priv_Scop to Empty to indicate no scope was pushed
21456 Priv_Scop
:= Empty
;
21459 Complete_Private_Subtype
(Full
, Priv
, Full_T
, N
);
21460 Set_Full_View
(Full
, Priv
);
21462 if Present
(Priv_Scop
) then
21466 Replace_Elmt
(Priv_Elmt
, Full
);
21469 Next_Elmt
(Priv_Elmt
);
21474 Disp_Typ
: Entity_Id
;
21475 Full_List
: Elist_Id
;
21477 Prim_Elmt
: Elmt_Id
;
21478 Priv_List
: Elist_Id
;
21482 L
: Elist_Id
) return Boolean;
21483 -- Determine whether list L contains element E
21491 L
: Elist_Id
) return Boolean
21493 List_Elmt
: Elmt_Id
;
21496 List_Elmt
:= First_Elmt
(L
);
21497 while Present
(List_Elmt
) loop
21498 if Node
(List_Elmt
) = E
then
21502 Next_Elmt
(List_Elmt
);
21508 -- Start of processing
21511 -- If the private view was tagged, copy the new primitive operations
21512 -- from the private view to the full view.
21514 if Is_Tagged_Type
(Full_T
) then
21515 if Is_Tagged_Type
(Priv_T
) then
21516 Priv_List
:= Primitive_Operations
(Priv_T
);
21517 Prim_Elmt
:= First_Elmt
(Priv_List
);
21519 -- In the case of a concurrent type completing a private tagged
21520 -- type, primitives may have been declared in between the two
21521 -- views. These subprograms need to be wrapped the same way
21522 -- entries and protected procedures are handled because they
21523 -- cannot be directly shared by the two views.
21525 if Is_Concurrent_Type
(Full_T
) then
21527 Conc_Typ
: constant Entity_Id
:=
21528 Corresponding_Record_Type
(Full_T
);
21529 Curr_Nod
: Node_Id
:= Parent
(Conc_Typ
);
21530 Wrap_Spec
: Node_Id
;
21533 while Present
(Prim_Elmt
) loop
21534 Prim
:= Node
(Prim_Elmt
);
21536 if Comes_From_Source
(Prim
)
21537 and then not Is_Abstract_Subprogram
(Prim
)
21540 Make_Subprogram_Declaration
(Sloc
(Prim
),
21544 Obj_Typ
=> Conc_Typ
,
21546 Parameter_Specifications
21549 Insert_After
(Curr_Nod
, Wrap_Spec
);
21550 Curr_Nod
:= Wrap_Spec
;
21552 Analyze
(Wrap_Spec
);
21554 -- Remove the wrapper from visibility to avoid
21555 -- spurious conflict with the wrapped entity.
21557 Set_Is_Immediately_Visible
21558 (Defining_Entity
(Specification
(Wrap_Spec
)),
21562 Next_Elmt
(Prim_Elmt
);
21568 -- For nonconcurrent types, transfer explicit primitives, but
21569 -- omit those inherited from the parent of the private view
21570 -- since they will be re-inherited later on.
21573 Full_List
:= Primitive_Operations
(Full_T
);
21574 while Present
(Prim_Elmt
) loop
21575 Prim
:= Node
(Prim_Elmt
);
21577 if Comes_From_Source
(Prim
)
21578 and then not Contains
(Prim
, Full_List
)
21580 Append_Elmt
(Prim
, Full_List
);
21583 Next_Elmt
(Prim_Elmt
);
21587 -- Untagged private view
21590 Full_List
:= Primitive_Operations
(Full_T
);
21592 -- In this case the partial view is untagged, so here we locate
21593 -- all of the earlier primitives that need to be treated as
21594 -- dispatching (those that appear between the two views). Note
21595 -- that these additional operations must all be new operations
21596 -- (any earlier operations that override inherited operations
21597 -- of the full view will already have been inserted in the
21598 -- primitives list, marked by Check_Operation_From_Private_View
21599 -- as dispatching. Note that implicit "/=" operators are
21600 -- excluded from being added to the primitives list since they
21601 -- shouldn't be treated as dispatching (tagged "/=" is handled
21604 Prim
:= Next_Entity
(Full_T
);
21605 while Present
(Prim
) and then Prim
/= Priv_T
loop
21606 if Ekind
(Prim
) in E_Procedure | E_Function
then
21607 Disp_Typ
:= Find_Dispatching_Type
(Prim
);
21609 if Disp_Typ
= Full_T
21610 and then (Chars
(Prim
) /= Name_Op_Ne
21611 or else Comes_From_Source
(Prim
))
21613 Check_Controlling_Formals
(Full_T
, Prim
);
21615 if Is_Suitable_Primitive
(Prim
)
21616 and then not Is_Dispatching_Operation
(Prim
)
21618 Append_Elmt
(Prim
, Full_List
);
21619 Set_Is_Dispatching_Operation
(Prim
);
21620 Set_DT_Position_Value
(Prim
, No_Uint
);
21623 elsif Is_Dispatching_Operation
(Prim
)
21624 and then Disp_Typ
/= Full_T
21626 -- Verify that it is not otherwise controlled by a
21627 -- formal or a return value of type T.
21629 Check_Controlling_Formals
(Disp_Typ
, Prim
);
21633 Next_Entity
(Prim
);
21637 -- For the tagged case, the two views can share the same primitive
21638 -- operations list and the same class-wide type. Update attributes
21639 -- of the class-wide type which depend on the full declaration.
21641 if Is_Tagged_Type
(Priv_T
) then
21642 Set_Direct_Primitive_Operations
(Priv_T
, Full_List
);
21643 Set_Class_Wide_Type
21644 (Base_Type
(Full_T
), Class_Wide_Type
(Priv_T
));
21646 Propagate_Concurrent_Flags
(Class_Wide_Type
(Priv_T
), Full_T
);
21649 -- For untagged types, copy the primitives across from the private
21650 -- view to the full view, for support of prefixed calls when
21651 -- extensions are enabled, and better error messages otherwise.
21654 Priv_List
:= Primitive_Operations
(Priv_T
);
21655 Prim_Elmt
:= First_Elmt
(Priv_List
);
21657 Full_List
:= Primitive_Operations
(Full_T
);
21658 while Present
(Prim_Elmt
) loop
21659 Prim
:= Node
(Prim_Elmt
);
21660 Append_Elmt
(Prim
, Full_List
);
21661 Next_Elmt
(Prim_Elmt
);
21666 -- Ada 2005 AI 161: Check preelaborable initialization consistency
21668 if Known_To_Have_Preelab_Init
(Priv_T
) then
21670 -- Case where there is a pragma Preelaborable_Initialization. We
21671 -- always allow this in predefined units, which is cheating a bit,
21672 -- but it means we don't have to struggle to meet the requirements in
21673 -- the RM for having Preelaborable Initialization. Otherwise we
21674 -- require that the type meets the RM rules. But we can't check that
21675 -- yet, because of the rule about overriding Initialize, so we simply
21676 -- set a flag that will be checked at freeze time.
21678 if not In_Predefined_Unit
(Full_T
) then
21679 Set_Must_Have_Preelab_Init
(Full_T
);
21683 -- If pragma CPP_Class was applied to the private type declaration,
21684 -- propagate it now to the full type declaration.
21686 if Is_CPP_Class
(Priv_T
) then
21687 Set_Is_CPP_Class
(Full_T
);
21688 Set_Convention
(Full_T
, Convention_CPP
);
21690 -- Check that components of imported CPP types do not have default
21693 Check_CPP_Type_Has_No_Defaults
(Full_T
);
21696 -- If the private view has user specified stream attributes, then so has
21699 -- Why the test, how could these flags be already set in Full_T ???
21701 if Has_Specified_Stream_Read
(Priv_T
) then
21702 Set_Has_Specified_Stream_Read
(Full_T
);
21705 if Has_Specified_Stream_Write
(Priv_T
) then
21706 Set_Has_Specified_Stream_Write
(Full_T
);
21709 if Has_Specified_Stream_Input
(Priv_T
) then
21710 Set_Has_Specified_Stream_Input
(Full_T
);
21713 if Has_Specified_Stream_Output
(Priv_T
) then
21714 Set_Has_Specified_Stream_Output
(Full_T
);
21717 -- Propagate Default_Initial_Condition-related attributes from the
21718 -- partial view to the full view.
21720 Propagate_DIC_Attributes
(Full_T
, From_Typ
=> Priv_T
);
21722 -- And to the underlying full view, if any
21724 if Is_Private_Type
(Full_T
)
21725 and then Present
(Underlying_Full_View
(Full_T
))
21727 Propagate_DIC_Attributes
21728 (Underlying_Full_View
(Full_T
), From_Typ
=> Priv_T
);
21731 -- Propagate invariant-related attributes from the partial view to the
21734 Propagate_Invariant_Attributes
(Full_T
, From_Typ
=> Priv_T
);
21736 -- And to the underlying full view, if any
21738 if Is_Private_Type
(Full_T
)
21739 and then Present
(Underlying_Full_View
(Full_T
))
21741 Propagate_Invariant_Attributes
21742 (Underlying_Full_View
(Full_T
), From_Typ
=> Priv_T
);
21745 -- AI12-0041: Detect an attempt to inherit a class-wide type invariant
21746 -- in the full view without advertising the inheritance in the partial
21747 -- view. This can only occur when the partial view has no parent type
21748 -- and the full view has an interface as a parent. Any other scenarios
21749 -- are illegal because implemented interfaces must match between the
21752 if Is_Tagged_Type
(Priv_T
) and then Is_Tagged_Type
(Full_T
) then
21754 Full_Par
: constant Entity_Id
:= Etype
(Full_T
);
21755 Priv_Par
: constant Entity_Id
:= Etype
(Priv_T
);
21758 if not Is_Interface
(Priv_Par
)
21759 and then Is_Interface
(Full_Par
)
21760 and then Has_Inheritable_Invariants
(Full_Par
)
21763 ("hidden inheritance of class-wide type invariants not "
21769 -- Propagate predicates to full type, and predicate function if already
21770 -- defined. It is not clear that this can actually happen? the partial
21771 -- view cannot be frozen yet, and the predicate function has not been
21772 -- built. Still it is a cheap check and seems safer to make it.
21774 Propagate_Predicate_Attributes
(Full_T
, Priv_T
);
21776 if Is_Private_Type
(Full_T
)
21777 and then Present
(Underlying_Full_View
(Full_T
))
21779 Propagate_Predicate_Attributes
21780 (Underlying_Full_View
(Full_T
), Priv_T
);
21784 Restore_Ghost_Region
(Saved_GM
, Saved_IGR
);
21785 end Process_Full_View
;
21787 -----------------------------------
21788 -- Process_Incomplete_Dependents --
21789 -----------------------------------
21791 procedure Process_Incomplete_Dependents
21793 Full_T
: Entity_Id
;
21796 Inc_Elmt
: Elmt_Id
;
21797 Priv_Dep
: Entity_Id
;
21798 New_Subt
: Entity_Id
;
21800 Disc_Constraint
: Elist_Id
;
21803 if No
(Private_Dependents
(Inc_T
)) then
21807 -- Itypes that may be generated by the completion of an incomplete
21808 -- subtype are not used by the back-end and not attached to the tree.
21809 -- They are created only for constraint-checking purposes.
21811 Inc_Elmt
:= First_Elmt
(Private_Dependents
(Inc_T
));
21812 while Present
(Inc_Elmt
) loop
21813 Priv_Dep
:= Node
(Inc_Elmt
);
21815 if Ekind
(Priv_Dep
) = E_Subprogram_Type
then
21817 -- An Access_To_Subprogram type may have a return type or a
21818 -- parameter type that is incomplete. Replace with the full view.
21820 if Etype
(Priv_Dep
) = Inc_T
then
21821 Set_Etype
(Priv_Dep
, Full_T
);
21825 Formal
: Entity_Id
;
21828 Formal
:= First_Formal
(Priv_Dep
);
21829 while Present
(Formal
) loop
21830 if Etype
(Formal
) = Inc_T
then
21831 Set_Etype
(Formal
, Full_T
);
21834 Next_Formal
(Formal
);
21838 elsif Is_Overloadable
(Priv_Dep
) then
21840 -- If a subprogram in the incomplete dependents list is primitive
21841 -- for a tagged full type then mark it as a dispatching operation,
21842 -- check whether it overrides an inherited subprogram, and check
21843 -- restrictions on its controlling formals. Note that a protected
21844 -- operation is never dispatching: only its wrapper operation
21845 -- (which has convention Ada) is.
21847 if Is_Tagged_Type
(Full_T
)
21848 and then Is_Primitive
(Priv_Dep
)
21849 and then Convention
(Priv_Dep
) /= Convention_Protected
21851 Check_Operation_From_Incomplete_Type
(Priv_Dep
, Inc_T
);
21852 Set_Is_Dispatching_Operation
(Priv_Dep
);
21853 Check_Controlling_Formals
(Full_T
, Priv_Dep
);
21856 elsif Ekind
(Priv_Dep
) = E_Subprogram_Body
then
21858 -- Can happen during processing of a body before the completion
21859 -- of a TA type. Ignore, because spec is also on dependent list.
21863 -- Ada 2005 (AI-412): Transform a regular incomplete subtype into a
21864 -- corresponding subtype of the full view.
21866 elsif Ekind
(Priv_Dep
) = E_Incomplete_Subtype
21867 and then Comes_From_Source
(Priv_Dep
)
21869 Set_Subtype_Indication
21870 (Parent
(Priv_Dep
), New_Occurrence_Of
(Full_T
, Sloc
(Priv_Dep
)));
21871 Reinit_Field_To_Zero
21872 (Priv_Dep
, F_Private_Dependents
,
21873 Old_Ekind
=> E_Incomplete_Subtype
);
21874 Mutate_Ekind
(Priv_Dep
, Subtype_Kind
(Ekind
(Full_T
)));
21875 Set_Etype
(Priv_Dep
, Full_T
);
21876 Set_Analyzed
(Parent
(Priv_Dep
), False);
21878 -- Reanalyze the declaration, suppressing the call to Enter_Name
21879 -- to avoid duplicate names.
21881 Analyze_Subtype_Declaration
21882 (N
=> Parent
(Priv_Dep
),
21885 -- Dependent is a subtype
21888 -- We build a new subtype indication using the full view of the
21889 -- incomplete parent. The discriminant constraints have been
21890 -- elaborated already at the point of the subtype declaration.
21892 New_Subt
:= Create_Itype
(E_Void
, N
);
21894 if Has_Discriminants
(Full_T
) then
21895 Disc_Constraint
:= Discriminant_Constraint
(Priv_Dep
);
21897 Disc_Constraint
:= No_Elist
;
21900 Build_Discriminated_Subtype
(Full_T
, New_Subt
, Disc_Constraint
, N
);
21901 Set_Full_View
(Priv_Dep
, New_Subt
);
21904 Next_Elmt
(Inc_Elmt
);
21906 end Process_Incomplete_Dependents
;
21908 --------------------------------
21909 -- Process_Range_Expr_In_Decl --
21910 --------------------------------
21912 procedure Process_Range_Expr_In_Decl
21915 Subtyp
: Entity_Id
:= Empty
;
21916 Check_List
: List_Id
:= No_List
)
21919 R_Checks
: Check_Result
;
21920 Insert_Node
: Node_Id
;
21921 Def_Id
: Entity_Id
;
21924 Analyze_And_Resolve
(R
, Base_Type
(T
));
21926 if Nkind
(R
) = N_Range
then
21927 Lo
:= Low_Bound
(R
);
21928 Hi
:= High_Bound
(R
);
21930 -- Validity checks on the range of a quantified expression are
21931 -- delayed until the construct is transformed into a loop.
21933 if Nkind
(Parent
(R
)) = N_Loop_Parameter_Specification
21934 and then Nkind
(Parent
(Parent
(R
))) = N_Quantified_Expression
21938 -- We need to ensure validity of the bounds here, because if we
21939 -- go ahead and do the expansion, then the expanded code will get
21940 -- analyzed with range checks suppressed and we miss the check.
21942 -- WARNING: The capture of the range bounds with xxx_FIRST/_LAST and
21943 -- the temporaries generated by routine Remove_Side_Effects by means
21944 -- of validity checks must use the same names. When a range appears
21945 -- in the parent of a generic, the range is processed with checks
21946 -- disabled as part of the generic context and with checks enabled
21947 -- for code generation purposes. This leads to link issues as the
21948 -- generic contains references to xxx_FIRST/_LAST, but the inlined
21949 -- template sees the temporaries generated by Remove_Side_Effects.
21952 Validity_Check_Range
(R
, Subtyp
);
21955 -- If there were errors in the declaration, try and patch up some
21956 -- common mistakes in the bounds. The cases handled are literals
21957 -- which are Integer where the expected type is Real and vice versa.
21958 -- These corrections allow the compilation process to proceed further
21959 -- along since some basic assumptions of the format of the bounds
21962 if Etype
(R
) = Any_Type
then
21963 if Nkind
(Lo
) = N_Integer_Literal
and then Is_Real_Type
(T
) then
21965 Make_Real_Literal
(Sloc
(Lo
), UR_From_Uint
(Intval
(Lo
))));
21967 elsif Nkind
(Hi
) = N_Integer_Literal
and then Is_Real_Type
(T
) then
21969 Make_Real_Literal
(Sloc
(Hi
), UR_From_Uint
(Intval
(Hi
))));
21971 elsif Nkind
(Lo
) = N_Real_Literal
and then Is_Integer_Type
(T
) then
21973 Make_Integer_Literal
(Sloc
(Lo
), UR_To_Uint
(Realval
(Lo
))));
21975 elsif Nkind
(Hi
) = N_Real_Literal
and then Is_Integer_Type
(T
) then
21977 Make_Integer_Literal
(Sloc
(Hi
), UR_To_Uint
(Realval
(Hi
))));
21984 -- If the bounds of the range have been mistakenly given as string
21985 -- literals (perhaps in place of character literals), then an error
21986 -- has already been reported, but we rewrite the string literal as a
21987 -- bound of the range's type to avoid blowups in later processing
21988 -- that looks at static values.
21990 if Nkind
(Lo
) = N_String_Literal
then
21992 Make_Attribute_Reference
(Sloc
(Lo
),
21993 Prefix
=> New_Occurrence_Of
(T
, Sloc
(Lo
)),
21994 Attribute_Name
=> Name_First
));
21995 Analyze_And_Resolve
(Lo
);
21998 if Nkind
(Hi
) = N_String_Literal
then
22000 Make_Attribute_Reference
(Sloc
(Hi
),
22001 Prefix
=> New_Occurrence_Of
(T
, Sloc
(Hi
)),
22002 Attribute_Name
=> Name_First
));
22003 Analyze_And_Resolve
(Hi
);
22006 -- If bounds aren't scalar at this point then exit, avoiding
22007 -- problems with further processing of the range in this procedure.
22009 if not Is_Scalar_Type
(Etype
(Lo
)) then
22013 -- Resolve (actually Sem_Eval) has checked that the bounds are in
22014 -- then range of the base type. Here we check whether the bounds
22015 -- are in the range of the subtype itself. Note that if the bounds
22016 -- represent the null range the Constraint_Error exception should
22019 -- Capture values of bounds and generate temporaries for them
22020 -- if needed, before applying checks, since checks may cause
22021 -- duplication of the expression without forcing evaluation.
22023 -- The forced evaluation removes side effects from expressions,
22024 -- which should occur also in GNATprove mode. Otherwise, we end up
22025 -- with unexpected insertions of actions at places where this is
22026 -- not supposed to occur, e.g. on default parameters of a call.
22028 if Expander_Active
or GNATprove_Mode
then
22030 -- Call Force_Evaluation to create declarations as needed
22031 -- to deal with side effects, and also create typ_FIRST/LAST
22032 -- entities for bounds if we have a subtype name.
22034 -- Note: we do this transformation even if expansion is not
22035 -- active if we are in GNATprove_Mode since the transformation
22036 -- is in general required to ensure that the resulting tree has
22037 -- proper Ada semantics.
22040 (Lo
, Related_Id
=> Subtyp
, Is_Low_Bound
=> True);
22042 (Hi
, Related_Id
=> Subtyp
, Is_High_Bound
=> True);
22045 -- We use a flag here instead of suppressing checks on the type
22046 -- because the type we check against isn't necessarily the place
22047 -- where we put the check.
22049 R_Checks
:= Get_Range_Checks
(R
, T
);
22051 -- Look up tree to find an appropriate insertion point. We can't
22052 -- just use insert_actions because later processing depends on
22053 -- the insertion node. Prior to Ada 2012 the insertion point could
22054 -- only be a declaration or a loop, but quantified expressions can
22055 -- appear within any context in an expression, and the insertion
22056 -- point can be any statement, pragma, or declaration.
22058 Insert_Node
:= Parent
(R
);
22059 while Present
(Insert_Node
) loop
22061 Nkind
(Insert_Node
) in N_Declaration
22063 Nkind
(Insert_Node
) not in N_Component_Declaration
22064 | N_Loop_Parameter_Specification
22065 | N_Function_Specification
22066 | N_Procedure_Specification
;
22068 exit when Nkind
(Insert_Node
) in
22069 N_Later_Decl_Item |
22070 N_Statement_Other_Than_Procedure_Call |
22071 N_Procedure_Call_Statement |
22074 Insert_Node
:= Parent
(Insert_Node
);
22077 if Present
(Insert_Node
) then
22079 -- Case of loop statement. Verify that the range is part of the
22080 -- subtype indication of the iteration scheme.
22082 if Nkind
(Insert_Node
) = N_Loop_Statement
then
22087 Indic
:= Parent
(R
);
22088 while Present
(Indic
)
22089 and then Nkind
(Indic
) /= N_Subtype_Indication
22091 Indic
:= Parent
(Indic
);
22094 if Present
(Indic
) then
22095 Def_Id
:= Etype
(Subtype_Mark
(Indic
));
22097 Insert_Range_Checks
22101 Sloc
(Insert_Node
),
22102 Do_Before
=> True);
22106 -- Case of declarations. If the declaration is for a type and
22107 -- involves discriminants, the checks are premature at the
22108 -- declaration point and need to wait for the expansion of the
22109 -- initialization procedure, which will pass in the list to put
22110 -- them on; otherwise, the checks are done at the declaration
22111 -- point and there is no need to do them again in the
22112 -- initialization procedure.
22114 elsif Nkind
(Insert_Node
) in N_Declaration
then
22115 Def_Id
:= Defining_Identifier
(Insert_Node
);
22117 if (Ekind
(Def_Id
) = E_Record_Type
22118 and then Depends_On_Discriminant
(R
))
22120 (Ekind
(Def_Id
) = E_Protected_Type
22121 and then Has_Discriminants
(Def_Id
))
22123 if Present
(Check_List
) then
22124 Append_Range_Checks
22126 Check_List
, Def_Id
, Sloc
(Insert_Node
));
22130 if No
(Check_List
) then
22131 Insert_Range_Checks
22133 Insert_Node
, Def_Id
, Sloc
(Insert_Node
));
22137 -- Case of statements. Drop the checks, as the range appears in
22138 -- the context of a quantified expression. Insertion will take
22139 -- place when expression is expanded.
22146 -- Case of other than an explicit N_Range node
22148 -- The forced evaluation removes side effects from expressions, which
22149 -- should occur also in GNATprove mode. Otherwise, we end up with
22150 -- unexpected insertions of actions at places where this is not
22151 -- supposed to occur, e.g. on default parameters of a call.
22153 elsif Expander_Active
or GNATprove_Mode
then
22154 Get_Index_Bounds
(R
, Lo
, Hi
);
22155 Force_Evaluation
(Lo
);
22156 Force_Evaluation
(Hi
);
22158 end Process_Range_Expr_In_Decl
;
22160 --------------------------------------
22161 -- Process_Real_Range_Specification --
22162 --------------------------------------
22164 procedure Process_Real_Range_Specification
(Def
: Node_Id
) is
22165 Spec
: constant Node_Id
:= Real_Range_Specification
(Def
);
22168 Err
: Boolean := False;
22170 procedure Analyze_Bound
(N
: Node_Id
);
22171 -- Analyze and check one bound
22173 -------------------
22174 -- Analyze_Bound --
22175 -------------------
22177 procedure Analyze_Bound
(N
: Node_Id
) is
22179 Analyze_And_Resolve
(N
, Any_Real
);
22181 if not Is_OK_Static_Expression
(N
) then
22182 Flag_Non_Static_Expr
22183 ("bound in real type definition is not static!", N
);
22188 -- Start of processing for Process_Real_Range_Specification
22191 if Present
(Spec
) then
22192 Lo
:= Low_Bound
(Spec
);
22193 Hi
:= High_Bound
(Spec
);
22194 Analyze_Bound
(Lo
);
22195 Analyze_Bound
(Hi
);
22197 -- If error, clear away junk range specification
22200 Set_Real_Range_Specification
(Def
, Empty
);
22203 end Process_Real_Range_Specification
;
22205 ---------------------
22206 -- Process_Subtype --
22207 ---------------------
22209 function Process_Subtype
22211 Related_Nod
: Node_Id
;
22212 Related_Id
: Entity_Id
:= Empty
;
22213 Suffix
: Character := ' ') return Entity_Id
22215 procedure Check_Incomplete
(T
: Node_Id
);
22216 -- Called to verify that an incomplete type is not used prematurely
22218 ----------------------
22219 -- Check_Incomplete --
22220 ----------------------
22222 procedure Check_Incomplete
(T
: Node_Id
) is
22224 -- Ada 2005 (AI-412): Incomplete subtypes are legal
22226 if Ekind
(Root_Type
(Entity
(T
))) = E_Incomplete_Type
22228 not (Ada_Version
>= Ada_2005
22230 (Nkind
(Parent
(T
)) = N_Subtype_Declaration
22231 or else (Nkind
(Parent
(T
)) = N_Subtype_Indication
22232 and then Nkind
(Parent
(Parent
(T
))) =
22233 N_Subtype_Declaration
)))
22235 Error_Msg_N
("invalid use of type before its full declaration", T
);
22237 end Check_Incomplete
;
22242 Def_Id
: Entity_Id
;
22243 Error_Node
: Node_Id
;
22244 Full_View_Id
: Entity_Id
;
22245 Subtype_Mark_Id
: Entity_Id
;
22247 May_Have_Null_Exclusion
: Boolean;
22249 -- Start of processing for Process_Subtype
22252 -- Case of no constraints present
22254 if Nkind
(S
) /= N_Subtype_Indication
then
22257 -- No way to proceed if the subtype indication is malformed. This
22258 -- will happen for example when the subtype indication in an object
22259 -- declaration is missing altogether and the expression is analyzed
22260 -- as if it were that indication.
22262 if not Is_Entity_Name
(S
) then
22266 Check_Incomplete
(S
);
22269 -- The following mirroring of assertion in Null_Exclusion_Present is
22270 -- ugly, can't we have a range, a static predicate or even a flag???
22272 May_Have_Null_Exclusion
:=
22275 Nkind
(P
) in N_Access_Definition
22276 | N_Access_Function_Definition
22277 | N_Access_Procedure_Definition
22278 | N_Access_To_Object_Definition
22280 | N_Component_Definition
22281 | N_Derived_Type_Definition
22282 | N_Discriminant_Specification
22283 | N_Formal_Object_Declaration
22284 | N_Function_Specification
22285 | N_Object_Declaration
22286 | N_Object_Renaming_Declaration
22287 | N_Parameter_Specification
22288 | N_Subtype_Declaration
;
22290 -- Ada 2005 (AI-231): Static check
22292 if Ada_Version
>= Ada_2005
22293 and then May_Have_Null_Exclusion
22294 and then Null_Exclusion_Present
(P
)
22295 and then Nkind
(P
) /= N_Access_To_Object_Definition
22296 and then not Is_Access_Type
(Entity
(S
))
22298 Error_Msg_N
("`NOT NULL` only allowed for an access type", S
);
22301 -- Create an Itype that is a duplicate of Entity (S) but with the
22302 -- null-exclusion attribute.
22304 if May_Have_Null_Exclusion
22305 and then Is_Access_Type
(Entity
(S
))
22306 and then Null_Exclusion_Present
(P
)
22308 -- No need to check the case of an access to object definition.
22309 -- It is correct to define double not-null pointers.
22312 -- type Not_Null_Int_Ptr is not null access Integer;
22313 -- type Acc is not null access Not_Null_Int_Ptr;
22315 and then Nkind
(P
) /= N_Access_To_Object_Definition
22317 if Can_Never_Be_Null
(Entity
(S
)) then
22318 case Nkind
(Related_Nod
) is
22319 when N_Full_Type_Declaration
=>
22320 if Nkind
(Type_Definition
(Related_Nod
))
22321 in N_Array_Type_Definition
22325 (Component_Definition
22326 (Type_Definition
(Related_Nod
)));
22329 Subtype_Indication
(Type_Definition
(Related_Nod
));
22332 when N_Subtype_Declaration
=>
22333 Error_Node
:= Subtype_Indication
(Related_Nod
);
22335 when N_Object_Declaration
=>
22336 Error_Node
:= Object_Definition
(Related_Nod
);
22338 when N_Component_Declaration
=>
22340 Subtype_Indication
(Component_Definition
(Related_Nod
));
22342 when N_Allocator
=>
22343 Error_Node
:= Expression
(Related_Nod
);
22346 pragma Assert
(False);
22347 Error_Node
:= Related_Nod
;
22351 ("`NOT NULL` not allowed (& already excludes null)",
22357 Create_Null_Excluding_Itype
22359 Related_Nod
=> P
));
22360 Set_Entity
(S
, Etype
(S
));
22365 -- Case of constraint present, so that we have an N_Subtype_Indication
22366 -- node (this node is created only if constraints are present).
22369 Find_Type
(Subtype_Mark
(S
));
22371 if Nkind
(Parent
(S
)) /= N_Access_To_Object_Definition
22373 (Nkind
(Parent
(S
)) = N_Subtype_Declaration
22374 and then Is_Itype
(Defining_Identifier
(Parent
(S
))))
22376 Check_Incomplete
(Subtype_Mark
(S
));
22380 Subtype_Mark_Id
:= Entity
(Subtype_Mark
(S
));
22382 -- Explicit subtype declaration case
22384 if Nkind
(P
) = N_Subtype_Declaration
then
22385 Def_Id
:= Defining_Identifier
(P
);
22387 -- Explicit derived type definition case
22389 elsif Nkind
(P
) = N_Derived_Type_Definition
then
22390 Def_Id
:= Defining_Identifier
(Parent
(P
));
22392 -- Implicit case, the Def_Id must be created as an implicit type.
22393 -- The one exception arises in the case of concurrent types, array
22394 -- and access types, where other subsidiary implicit types may be
22395 -- created and must appear before the main implicit type. In these
22396 -- cases we leave Def_Id set to Empty as a signal that Create_Itype
22397 -- has not yet been called to create Def_Id.
22400 if Is_Array_Type
(Subtype_Mark_Id
)
22401 or else Is_Concurrent_Type
(Subtype_Mark_Id
)
22402 or else Is_Access_Type
(Subtype_Mark_Id
)
22406 -- For the other cases, we create a new unattached Itype,
22407 -- and set the indication to ensure it gets attached later.
22411 Create_Itype
(E_Void
, Related_Nod
, Related_Id
, Suffix
);
22415 -- If the kind of constraint is invalid for this kind of type,
22416 -- then give an error, and then pretend no constraint was given.
22418 if not Is_Valid_Constraint_Kind
22419 (Ekind
(Subtype_Mark_Id
), Nkind
(Constraint
(S
)))
22422 ("incorrect constraint for this kind of type", Constraint
(S
));
22424 Rewrite
(S
, New_Copy_Tree
(Subtype_Mark
(S
)));
22426 -- Set Ekind of orphan itype, to prevent cascaded errors
22428 if Present
(Def_Id
) then
22429 Mutate_Ekind
(Def_Id
, Ekind
(Any_Type
));
22432 -- Make recursive call, having got rid of the bogus constraint
22434 return Process_Subtype
(S
, Related_Nod
, Related_Id
, Suffix
);
22437 -- Remaining processing depends on type. Select on Base_Type kind to
22438 -- ensure getting to the concrete type kind in the case of a private
22439 -- subtype (needed when only doing semantic analysis).
22441 case Ekind
(Base_Type
(Subtype_Mark_Id
)) is
22442 when Access_Kind
=>
22444 -- If this is a constraint on a class-wide type, discard it.
22445 -- There is currently no way to express a partial discriminant
22446 -- constraint on a type with unknown discriminants. This is
22447 -- a pathology that the ACATS wisely decides not to test.
22449 if Is_Class_Wide_Type
(Designated_Type
(Subtype_Mark_Id
)) then
22450 if Comes_From_Source
(S
) then
22452 ("constraint on class-wide type ignored??",
22456 if Nkind
(P
) = N_Subtype_Declaration
then
22457 Set_Subtype_Indication
(P
,
22458 New_Occurrence_Of
(Subtype_Mark_Id
, Sloc
(S
)));
22461 return Subtype_Mark_Id
;
22464 Constrain_Access
(Def_Id
, S
, Related_Nod
);
22467 and then Is_Itype
(Designated_Type
(Def_Id
))
22468 and then Nkind
(Related_Nod
) = N_Subtype_Declaration
22469 and then not Is_Incomplete_Type
(Designated_Type
(Def_Id
))
22471 Build_Itype_Reference
22472 (Designated_Type
(Def_Id
), Related_Nod
);
22476 Constrain_Array
(Def_Id
, S
, Related_Nod
, Related_Id
, Suffix
);
22478 when Decimal_Fixed_Point_Kind
=>
22479 Constrain_Decimal
(Def_Id
, S
);
22481 when Enumeration_Kind
=>
22482 Constrain_Enumeration
(Def_Id
, S
);
22484 when Ordinary_Fixed_Point_Kind
=>
22485 Constrain_Ordinary_Fixed
(Def_Id
, S
);
22488 Constrain_Float
(Def_Id
, S
);
22490 when Integer_Kind
=>
22491 Constrain_Integer
(Def_Id
, S
);
22493 when Class_Wide_Kind
22494 | E_Incomplete_Type
22498 Constrain_Discriminated_Type
(Def_Id
, S
, Related_Nod
);
22500 if Ekind
(Def_Id
) = E_Incomplete_Type
then
22501 Set_Private_Dependents
(Def_Id
, New_Elmt_List
);
22504 when Private_Kind
=>
22506 -- A private type with unknown discriminants may be completed
22507 -- by an unconstrained array type.
22509 if Has_Unknown_Discriminants
(Subtype_Mark_Id
)
22510 and then Present
(Full_View
(Subtype_Mark_Id
))
22511 and then Is_Array_Type
(Full_View
(Subtype_Mark_Id
))
22513 Constrain_Array
(Def_Id
, S
, Related_Nod
, Related_Id
, Suffix
);
22515 -- ... but more commonly is completed by a discriminated record
22519 Constrain_Discriminated_Type
(Def_Id
, S
, Related_Nod
);
22522 -- The base type may be private but Def_Id may be a full view
22525 if Is_Private_Type
(Def_Id
) then
22526 Set_Private_Dependents
(Def_Id
, New_Elmt_List
);
22529 -- In case of an invalid constraint prevent further processing
22530 -- since the type constructed is missing expected fields.
22532 if Etype
(Def_Id
) = Any_Type
then
22536 -- If the full view is that of a task with discriminants,
22537 -- we must constrain both the concurrent type and its
22538 -- corresponding record type. Otherwise we will just propagate
22539 -- the constraint to the full view, if available.
22541 if Present
(Full_View
(Subtype_Mark_Id
))
22542 and then Has_Discriminants
(Subtype_Mark_Id
)
22543 and then Is_Concurrent_Type
(Full_View
(Subtype_Mark_Id
))
22546 Create_Itype
(E_Void
, Related_Nod
, Related_Id
, Suffix
);
22548 Set_Entity
(Subtype_Mark
(S
), Full_View
(Subtype_Mark_Id
));
22549 Constrain_Concurrent
(Full_View_Id
, S
,
22550 Related_Nod
, Related_Id
, Suffix
);
22551 Set_Entity
(Subtype_Mark
(S
), Subtype_Mark_Id
);
22552 Set_Full_View
(Def_Id
, Full_View_Id
);
22554 -- Introduce an explicit reference to the private subtype,
22555 -- to prevent scope anomalies in gigi if first use appears
22556 -- in a nested context, e.g. a later function body.
22557 -- Should this be generated in other contexts than a full
22558 -- type declaration?
22560 if Is_Itype
(Def_Id
)
22562 Nkind
(Parent
(P
)) = N_Full_Type_Declaration
22564 Build_Itype_Reference
(Def_Id
, Parent
(P
));
22568 Prepare_Private_Subtype_Completion
(Def_Id
, Related_Nod
);
22571 when Concurrent_Kind
=>
22572 Constrain_Concurrent
(Def_Id
, S
,
22573 Related_Nod
, Related_Id
, Suffix
);
22576 Error_Msg_N
("invalid subtype mark in subtype indication", S
);
22579 -- Size, Alignment, Representation aspects and Convention are always
22580 -- inherited from the base type.
22582 Set_Size_Info
(Def_Id
, (Subtype_Mark_Id
));
22583 Set_Rep_Info
(Def_Id
, (Subtype_Mark_Id
));
22584 Set_Convention
(Def_Id
, Convention
(Subtype_Mark_Id
));
22586 -- The anonymous subtype created for the subtype indication
22587 -- inherits the predicates of the parent.
22589 if Has_Predicates
(Subtype_Mark_Id
) then
22590 Inherit_Predicate_Flags
(Def_Id
, Subtype_Mark_Id
);
22592 -- Indicate where the predicate function may be found
22594 if No
(Predicate_Function
(Def_Id
)) and then Is_Itype
(Def_Id
) then
22595 Set_Predicated_Parent
(Def_Id
, Subtype_Mark_Id
);
22601 end Process_Subtype
;
22603 -----------------------------
22604 -- Record_Type_Declaration --
22605 -----------------------------
22607 procedure Record_Type_Declaration
22612 Def
: constant Node_Id
:= Type_Definition
(N
);
22613 Is_Tagged
: Boolean;
22614 Tag_Comp
: Entity_Id
;
22617 -- These flags must be initialized before calling Process_Discriminants
22618 -- because this routine makes use of them.
22620 Mutate_Ekind
(T
, E_Record_Type
);
22622 Reinit_Size_Align
(T
);
22623 Set_Interfaces
(T
, No_Elist
);
22624 Set_Stored_Constraint
(T
, No_Elist
);
22625 Set_Default_SSO
(T
);
22626 Set_No_Reordering
(T
, No_Component_Reordering
);
22630 if Ada_Version
< Ada_2005
or else not Interface_Present
(Def
) then
22631 -- The flag Is_Tagged_Type might have already been set by
22632 -- Find_Type_Name if it detected an error for declaration T. This
22633 -- arises in the case of private tagged types where the full view
22634 -- omits the word tagged.
22637 Tagged_Present
(Def
)
22638 or else (Serious_Errors_Detected
> 0 and then Is_Tagged_Type
(T
));
22640 Set_Is_Limited_Record
(T
, Limited_Present
(Def
));
22643 Set_Is_Tagged_Type
(T
, True);
22644 Set_No_Tagged_Streams_Pragma
(T
, No_Tagged_Streams
);
22647 -- Type is abstract if full declaration carries keyword, or if
22648 -- previous partial view did.
22650 Set_Is_Abstract_Type
(T
, Is_Abstract_Type
(T
)
22651 or else Abstract_Present
(Def
));
22655 Analyze_Interface_Declaration
(T
, Def
);
22657 if Present
(Discriminant_Specifications
(N
)) then
22659 ("interface types cannot have discriminants",
22660 Defining_Identifier
22661 (First
(Discriminant_Specifications
(N
))));
22665 -- First pass: if there are self-referential access components,
22666 -- create the required anonymous access type declarations, and if
22667 -- need be an incomplete type declaration for T itself.
22669 Check_Anonymous_Access_Components
(N
, T
, Prev
, Component_List
(Def
));
22671 if Ada_Version
>= Ada_2005
22672 and then Present
(Interface_List
(Def
))
22674 Check_Interfaces
(N
, Def
);
22677 Ifaces_List
: Elist_Id
;
22680 -- Ada 2005 (AI-251): Collect the list of progenitors that are not
22681 -- already in the parents.
22685 Ifaces_List
=> Ifaces_List
,
22686 Exclude_Parents
=> True);
22688 Set_Interfaces
(T
, Ifaces_List
);
22692 -- Records constitute a scope for the component declarations within.
22693 -- The scope is created prior to the processing of these declarations.
22694 -- Discriminants are processed first, so that they are visible when
22695 -- processing the other components. The Ekind of the record type itself
22696 -- is set to E_Record_Type (subtypes appear as E_Record_Subtype).
22698 -- Enter record scope
22702 -- If an incomplete or private type declaration was already given for
22703 -- the type, then this scope already exists, and the discriminants have
22704 -- been declared within. We must verify that the full declaration
22705 -- matches the incomplete one.
22707 Check_Or_Process_Discriminants
(N
, T
, Prev
);
22709 Set_Is_Constrained
(T
, not Has_Discriminants
(T
));
22710 Set_Has_Delayed_Freeze
(T
, True);
22712 -- For tagged types add a manually analyzed component corresponding
22713 -- to the component _tag, the corresponding piece of tree will be
22714 -- expanded as part of the freezing actions if it is not a CPP_Class.
22718 -- Do not add the tag unless we are in expansion mode
22720 if Expander_Active
then
22721 Tag_Comp
:= Make_Defining_Identifier
(Sloc
(Def
), Name_uTag
);
22722 Enter_Name
(Tag_Comp
);
22724 Mutate_Ekind
(Tag_Comp
, E_Component
);
22725 Set_Is_Tag
(Tag_Comp
);
22726 Set_Is_Aliased
(Tag_Comp
);
22727 Set_Is_Independent
(Tag_Comp
);
22728 Set_Etype
(Tag_Comp
, RTE
(RE_Tag
));
22729 Set_DT_Entry_Count
(Tag_Comp
, No_Uint
);
22730 Set_Original_Record_Component
(Tag_Comp
, Tag_Comp
);
22731 Reinit_Component_Location
(Tag_Comp
);
22733 -- Ada 2005 (AI-251): Addition of the Tag corresponding to all the
22734 -- implemented interfaces.
22736 if Has_Interfaces
(T
) then
22737 Add_Interface_Tag_Components
(N
, T
);
22741 Make_Class_Wide_Type
(T
);
22742 Set_Direct_Primitive_Operations
(T
, New_Elmt_List
);
22745 -- We must suppress range checks when processing record components in
22746 -- the presence of discriminants, since we don't want spurious checks to
22747 -- be generated during their analysis, but Suppress_Range_Checks flags
22748 -- must be reset the after processing the record definition.
22750 -- Note: this is the only use of Kill_Range_Checks, and is a bit odd,
22751 -- couldn't we just use the normal range check suppression method here.
22752 -- That would seem cleaner ???
22754 if Has_Discriminants
(T
) and then not Range_Checks_Suppressed
(T
) then
22755 Set_Kill_Range_Checks
(T
, True);
22756 Record_Type_Definition
(Def
, Prev
);
22757 Set_Kill_Range_Checks
(T
, False);
22759 Record_Type_Definition
(Def
, Prev
);
22762 -- Exit from record scope
22766 -- Ada 2005 (AI-251 and AI-345): Derive the interface subprograms of all
22767 -- the implemented interfaces and associate them an aliased entity.
22770 and then not Is_Empty_List
(Interface_List
(Def
))
22772 Derive_Progenitor_Subprograms
(T
, T
);
22775 Check_Function_Writable_Actuals
(N
);
22776 end Record_Type_Declaration
;
22778 ----------------------------
22779 -- Record_Type_Definition --
22780 ----------------------------
22782 procedure Record_Type_Definition
(Def
: Node_Id
; Prev_T
: Entity_Id
) is
22783 Component
: Entity_Id
;
22784 Ctrl_Components
: Boolean := False;
22785 Final_Storage_Only
: Boolean;
22789 if Ekind
(Prev_T
) = E_Incomplete_Type
then
22790 T
:= Full_View
(Prev_T
);
22795 Set_Is_Not_Self_Hidden
(T
);
22797 Final_Storage_Only
:= not Is_Controlled
(T
);
22799 -- Ada 2005: Check whether an explicit "limited" is present in a derived
22800 -- type declaration.
22802 if Parent_Kind
(Def
) = N_Derived_Type_Definition
22803 and then Limited_Present
(Parent
(Def
))
22805 Set_Is_Limited_Record
(T
);
22808 -- If the component list of a record type is defined by the reserved
22809 -- word null and there is no discriminant part, then the record type has
22810 -- no components and all records of the type are null records (RM 3.7)
22811 -- This procedure is also called to process the extension part of a
22812 -- record extension, in which case the current scope may have inherited
22816 and then Present
(Component_List
(Def
))
22817 and then not Null_Present
(Component_List
(Def
))
22819 Analyze_Declarations
(Component_Items
(Component_List
(Def
)));
22821 if Present
(Variant_Part
(Component_List
(Def
))) then
22822 Analyze
(Variant_Part
(Component_List
(Def
)));
22826 -- After completing the semantic analysis of the record definition,
22827 -- record components, both new and inherited, are accessible. Set their
22828 -- kind accordingly. Exclude malformed itypes from illegal declarations,
22829 -- whose Ekind may be void.
22831 Component
:= First_Entity
(Current_Scope
);
22832 while Present
(Component
) loop
22833 if Ekind
(Component
) = E_Void
22834 and then not Is_Itype
(Component
)
22836 Mutate_Ekind
(Component
, E_Component
);
22837 Reinit_Component_Location
(Component
);
22838 Set_Is_Not_Self_Hidden
(Component
);
22841 Propagate_Concurrent_Flags
(T
, Etype
(Component
));
22843 if Ekind
(Component
) /= E_Component
then
22846 -- Do not set Has_Controlled_Component on a class-wide equivalent
22847 -- type. See Make_CW_Equivalent_Type.
22849 elsif not Is_Class_Wide_Equivalent_Type
(T
)
22850 and then (Has_Controlled_Component
(Etype
(Component
))
22851 or else (Chars
(Component
) /= Name_uParent
22852 and then Is_Controlled
(Etype
(Component
))))
22854 Set_Has_Controlled_Component
(T
, True);
22855 Final_Storage_Only
:=
22857 and then Finalize_Storage_Only
(Etype
(Component
));
22858 Ctrl_Components
:= True;
22861 Next_Entity
(Component
);
22864 -- A Type is Finalize_Storage_Only only if all its controlled components
22867 if Ctrl_Components
then
22868 Set_Finalize_Storage_Only
(T
, Final_Storage_Only
);
22871 -- Place reference to end record on the proper entity, which may
22872 -- be a partial view.
22874 if Present
(Def
) then
22875 Process_End_Label
(Def
, 'e', Prev_T
);
22877 end Record_Type_Definition
;
22879 ---------------------------
22880 -- Replace_Discriminants --
22881 ---------------------------
22883 procedure Replace_Discriminants
(Typ
: Entity_Id
; Decl
: Node_Id
) is
22884 function Process
(N
: Node_Id
) return Traverse_Result
;
22890 function Process
(N
: Node_Id
) return Traverse_Result
is
22894 if Nkind
(N
) = N_Discriminant_Specification
then
22895 Comp
:= First_Discriminant
(Typ
);
22896 while Present
(Comp
) loop
22897 if Original_Record_Component
(Comp
) = Defining_Identifier
(N
)
22898 or else Chars
(Comp
) = Chars
(Defining_Identifier
(N
))
22900 Set_Defining_Identifier
(N
, Comp
);
22904 Next_Discriminant
(Comp
);
22907 elsif Nkind
(N
) = N_Variant_Part
then
22908 Comp
:= First_Discriminant
(Typ
);
22909 while Present
(Comp
) loop
22910 if Original_Record_Component
(Comp
) = Entity
(Name
(N
))
22911 or else Chars
(Comp
) = Chars
(Name
(N
))
22913 -- Make sure to preserve the type coming from the parent on
22914 -- the Name, even if the subtype of the discriminant can be
22915 -- constrained, so that discrete choices inherited from the
22916 -- parent in the variant part are not flagged as violating
22917 -- the constraints of the subtype.
22920 Typ
: constant Entity_Id
:= Etype
(Name
(N
));
22922 Rewrite
(Name
(N
), New_Occurrence_Of
(Comp
, Sloc
(N
)));
22923 Set_Etype
(Name
(N
), Typ
);
22928 Next_Discriminant
(Comp
);
22935 procedure Replace
is new Traverse_Proc
(Process
);
22937 -- Start of processing for Replace_Discriminants
22941 end Replace_Discriminants
;
22943 -------------------------------
22944 -- Set_Completion_Referenced --
22945 -------------------------------
22947 procedure Set_Completion_Referenced
(E
: Entity_Id
) is
22949 -- If in main unit, mark entity that is a completion as referenced,
22950 -- warnings go on the partial view when needed.
22952 if In_Extended_Main_Source_Unit
(E
) then
22953 Set_Referenced
(E
);
22955 end Set_Completion_Referenced
;
22957 ---------------------
22958 -- Set_Default_SSO --
22959 ---------------------
22961 procedure Set_Default_SSO
(T
: Entity_Id
) is
22963 case Opt
.Default_SSO
is
22967 Set_SSO_Set_Low_By_Default
(T
, True);
22969 Set_SSO_Set_High_By_Default
(T
, True);
22971 raise Program_Error
;
22973 end Set_Default_SSO
;
22975 ---------------------
22976 -- Set_Fixed_Range --
22977 ---------------------
22979 -- The range for fixed-point types is complicated by the fact that we
22980 -- do not know the exact end points at the time of the declaration. This
22981 -- is true for three reasons:
22983 -- A size clause may affect the fudging of the end-points.
22984 -- A small clause may affect the values of the end-points.
22985 -- We try to include the end-points if it does not affect the size.
22987 -- This means that the actual end-points must be established at the
22988 -- point when the type is frozen. Meanwhile, we first narrow the range
22989 -- as permitted (so that it will fit if necessary in a small specified
22990 -- size), and then build a range subtree with these narrowed bounds.
22991 -- Set_Fixed_Range constructs the range from real literal values, and
22992 -- sets the range as the Scalar_Range of the given fixed-point type entity.
22994 -- The parent of this range is set to point to the entity so that it is
22995 -- properly hooked into the tree (unlike normal Scalar_Range entries for
22996 -- other scalar types, which are just pointers to the range in the
22997 -- original tree, this would otherwise be an orphan).
22999 -- The tree is left unanalyzed. When the type is frozen, the processing
23000 -- in Freeze.Freeze_Fixed_Point_Type notices that the range is not
23001 -- analyzed, and uses this as an indication that it should complete
23002 -- work on the range (it will know the final small and size values).
23004 procedure Set_Fixed_Range
23010 S
: constant Node_Id
:=
23012 Low_Bound
=> Make_Real_Literal
(Loc
, Lo
),
23013 High_Bound
=> Make_Real_Literal
(Loc
, Hi
));
23015 Set_Scalar_Range
(E
, S
);
23018 -- Before the freeze point, the bounds of a fixed point are universal
23019 -- and carry the corresponding type.
23021 Set_Etype
(Low_Bound
(S
), Universal_Real
);
23022 Set_Etype
(High_Bound
(S
), Universal_Real
);
23023 end Set_Fixed_Range
;
23025 ----------------------------------
23026 -- Set_Scalar_Range_For_Subtype --
23027 ----------------------------------
23029 procedure Set_Scalar_Range_For_Subtype
23030 (Def_Id
: Entity_Id
;
23034 Kind
: constant Entity_Kind
:= Ekind
(Def_Id
);
23037 -- Defend against previous error
23039 if Nkind
(R
) = N_Error
then
23043 Set_Scalar_Range
(Def_Id
, R
);
23045 -- We need to link the range into the tree before resolving it so
23046 -- that types that are referenced, including importantly the subtype
23047 -- itself, are properly frozen (Freeze_Expression requires that the
23048 -- expression be properly linked into the tree). Of course if it is
23049 -- already linked in, then we do not disturb the current link.
23051 if No
(Parent
(R
)) then
23052 Set_Parent
(R
, Def_Id
);
23055 -- Reset the kind of the subtype during analysis of the range, to
23056 -- catch possible premature use in the bounds themselves.
23058 Process_Range_Expr_In_Decl
(R
, Subt
, Subtyp
=> Def_Id
);
23059 pragma Assert
(Ekind
(Def_Id
) = Kind
);
23060 end Set_Scalar_Range_For_Subtype
;
23062 --------------------------------------------------------
23063 -- Set_Stored_Constraint_From_Discriminant_Constraint --
23064 --------------------------------------------------------
23066 procedure Set_Stored_Constraint_From_Discriminant_Constraint
23070 -- Make sure set if encountered during Expand_To_Stored_Constraint
23072 Set_Stored_Constraint
(E
, No_Elist
);
23074 -- Give it the right value
23076 if Is_Constrained
(E
) and then Has_Discriminants
(E
) then
23077 Set_Stored_Constraint
(E
,
23078 Expand_To_Stored_Constraint
(E
, Discriminant_Constraint
(E
)));
23080 end Set_Stored_Constraint_From_Discriminant_Constraint
;
23082 -------------------------------------
23083 -- Signed_Integer_Type_Declaration --
23084 -------------------------------------
23086 procedure Signed_Integer_Type_Declaration
(T
: Entity_Id
; Def
: Node_Id
) is
23087 Implicit_Base
: Entity_Id
;
23088 Base_Typ
: Entity_Id
;
23091 Errs
: Boolean := False;
23095 function Can_Derive_From
(E
: Entity_Id
) return Boolean;
23096 -- Determine whether given bounds allow derivation from specified type
23098 procedure Check_Bound
(Expr
: Node_Id
);
23099 -- Check bound to make sure it is integral and static. If not, post
23100 -- appropriate error message and set Errs flag
23102 ---------------------
23103 -- Can_Derive_From --
23104 ---------------------
23106 -- Note we check both bounds against both end values, to deal with
23107 -- strange types like ones with a range of 0 .. -12341234.
23109 function Can_Derive_From
(E
: Entity_Id
) return Boolean is
23110 Lo
: constant Uint
:= Expr_Value
(Type_Low_Bound
(E
));
23111 Hi
: constant Uint
:= Expr_Value
(Type_High_Bound
(E
));
23113 return Lo
<= Lo_Val
and then Lo_Val
<= Hi
23115 Lo
<= Hi_Val
and then Hi_Val
<= Hi
;
23116 end Can_Derive_From
;
23122 procedure Check_Bound
(Expr
: Node_Id
) is
23124 -- If a range constraint is used as an integer type definition, each
23125 -- bound of the range must be defined by a static expression of some
23126 -- integer type, but the two bounds need not have the same integer
23127 -- type (Negative bounds are allowed.) (RM 3.5.4)
23129 if not Is_Integer_Type
(Etype
(Expr
)) then
23131 ("integer type definition bounds must be of integer type", Expr
);
23134 elsif not Is_OK_Static_Expression
(Expr
) then
23135 Flag_Non_Static_Expr
23136 ("non-static expression used for integer type bound!", Expr
);
23139 -- Otherwise the bounds are folded into literals
23141 elsif Is_Entity_Name
(Expr
) then
23142 Fold_Uint
(Expr
, Expr_Value
(Expr
), True);
23146 -- Start of processing for Signed_Integer_Type_Declaration
23149 -- Create an anonymous base type
23152 Create_Itype
(E_Signed_Integer_Type
, Parent
(Def
), T
, 'B');
23154 -- Analyze and check the bounds, they can be of any integer type
23156 Lo
:= Low_Bound
(Def
);
23157 Hi
:= High_Bound
(Def
);
23159 -- Arbitrarily use Integer as the type if either bound had an error
23161 if Hi
= Error
or else Lo
= Error
then
23162 Base_Typ
:= Any_Integer
;
23163 Set_Error_Posted
(T
, True);
23166 -- Here both bounds are OK expressions
23169 Analyze_And_Resolve
(Lo
, Any_Integer
);
23170 Analyze_And_Resolve
(Hi
, Any_Integer
);
23176 Hi
:= Type_High_Bound
(Standard_Long_Long_Long_Integer
);
23177 Lo
:= Type_Low_Bound
(Standard_Long_Long_Long_Integer
);
23180 -- Find type to derive from
23182 Lo_Val
:= Expr_Value
(Lo
);
23183 Hi_Val
:= Expr_Value
(Hi
);
23185 if Can_Derive_From
(Standard_Short_Short_Integer
) then
23186 Base_Typ
:= Base_Type
(Standard_Short_Short_Integer
);
23188 elsif Can_Derive_From
(Standard_Short_Integer
) then
23189 Base_Typ
:= Base_Type
(Standard_Short_Integer
);
23191 elsif Can_Derive_From
(Standard_Integer
) then
23192 Base_Typ
:= Base_Type
(Standard_Integer
);
23194 elsif Can_Derive_From
(Standard_Long_Integer
) then
23195 Base_Typ
:= Base_Type
(Standard_Long_Integer
);
23197 elsif Can_Derive_From
(Standard_Long_Long_Integer
) then
23198 Check_Restriction
(No_Long_Long_Integers
, Def
);
23199 Base_Typ
:= Base_Type
(Standard_Long_Long_Integer
);
23201 elsif Can_Derive_From
(Standard_Long_Long_Long_Integer
) then
23202 Check_Restriction
(No_Long_Long_Integers
, Def
);
23203 Base_Typ
:= Base_Type
(Standard_Long_Long_Long_Integer
);
23206 Base_Typ
:= Base_Type
(Standard_Long_Long_Long_Integer
);
23207 Error_Msg_N
("integer type definition bounds out of range", Def
);
23208 Hi
:= Type_High_Bound
(Standard_Long_Long_Long_Integer
);
23209 Lo
:= Type_Low_Bound
(Standard_Long_Long_Long_Integer
);
23213 -- Set the type of the bounds to the implicit base: we cannot set it to
23214 -- the new type, because this would be a forward reference for the code
23215 -- generator and, if the original type is user-defined, this could even
23216 -- lead to spurious semantic errors. Furthermore we do not set it to be
23217 -- universal, because this could make it much larger than needed here.
23220 Set_Etype
(Lo
, Implicit_Base
);
23221 Set_Etype
(Hi
, Implicit_Base
);
23224 -- Complete both implicit base and declared first subtype entities. The
23225 -- inheritance of the rep item chain ensures that SPARK-related pragmas
23226 -- are not clobbered when the signed integer type acts as a full view of
23229 Set_Etype
(Implicit_Base
, Base_Typ
);
23230 Set_Size_Info
(Implicit_Base
, Base_Typ
);
23231 Set_RM_Size
(Implicit_Base
, RM_Size
(Base_Typ
));
23232 Set_First_Rep_Item
(Implicit_Base
, First_Rep_Item
(Base_Typ
));
23233 Set_Scalar_Range
(Implicit_Base
, Scalar_Range
(Base_Typ
));
23235 Mutate_Ekind
(T
, E_Signed_Integer_Subtype
);
23236 Set_Etype
(T
, Implicit_Base
);
23237 Set_Size_Info
(T
, Implicit_Base
);
23238 Inherit_Rep_Item_Chain
(T
, Implicit_Base
);
23239 Set_Scalar_Range
(T
, Def
);
23240 Set_RM_Size
(T
, UI_From_Int
(Minimum_Size
(T
)));
23241 Set_Is_Constrained
(T
);
23242 end Signed_Integer_Type_Declaration
;