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 Atree
; use Atree
;
27 with Debug
; use Debug
;
28 with Einfo
; use Einfo
;
29 with Einfo
.Utils
; use Einfo
.Utils
;
30 with Elists
; use Elists
;
31 with Errout
; use Errout
;
32 with Exp_Disp
; use Exp_Disp
;
33 with Exp_Tss
; use Exp_Tss
;
34 with Exp_Util
; use Exp_Util
;
35 with Freeze
; use Freeze
;
36 with Ghost
; use Ghost
;
37 with Impunit
; use Impunit
;
39 with Lib
.Load
; use Lib
.Load
;
40 with Lib
.Xref
; use Lib
.Xref
;
42 with Namet
; use Namet
;
43 with Namet
.Sp
; use Namet
.Sp
;
44 with Nlists
; use Nlists
;
45 with Nmake
; use Nmake
;
47 with Output
; use Output
;
48 with Restrict
; use Restrict
;
49 with Rident
; use Rident
;
50 with Rtsfind
; use Rtsfind
;
52 with Sem_Aux
; use Sem_Aux
;
53 with Sem_Cat
; use Sem_Cat
;
54 with Sem_Ch3
; use Sem_Ch3
;
55 with Sem_Ch4
; use Sem_Ch4
;
56 with Sem_Ch6
; use Sem_Ch6
;
57 with Sem_Ch10
; use Sem_Ch10
;
58 with Sem_Ch12
; use Sem_Ch12
;
59 with Sem_Ch13
; use Sem_Ch13
;
60 with Sem_Dim
; use Sem_Dim
;
61 with Sem_Disp
; use Sem_Disp
;
62 with Sem_Dist
; use Sem_Dist
;
63 with Sem_Elab
; use Sem_Elab
;
64 with Sem_Eval
; use Sem_Eval
;
65 with Sem_Prag
; use Sem_Prag
;
66 with Sem_Res
; use Sem_Res
;
67 with Sem_Util
; use Sem_Util
;
68 with Sem_Type
; use Sem_Type
;
69 with Stand
; use Stand
;
70 with Sinfo
; use Sinfo
;
71 with Sinfo
.Nodes
; use Sinfo
.Nodes
;
72 with Sinfo
.Utils
; use Sinfo
.Utils
;
73 with Sinfo
.CN
; use Sinfo
.CN
;
74 with Snames
; use Snames
;
77 with Tbuild
; use Tbuild
;
78 with Uintp
; use Uintp
;
79 with Warnsw
; use Warnsw
;
81 package body Sem_Ch8
is
83 ------------------------------------
84 -- Visibility and Name Resolution --
85 ------------------------------------
87 -- This package handles name resolution and the collection of possible
88 -- interpretations for overloaded names, prior to overload resolution.
90 -- Name resolution is the process that establishes a mapping between source
91 -- identifiers and the entities they denote at each point in the program.
92 -- Each entity is represented by a defining occurrence. Each identifier
93 -- that denotes an entity points to the corresponding defining occurrence.
94 -- This is the entity of the applied occurrence. Each occurrence holds
95 -- an index into the names table, where source identifiers are stored.
97 -- Each entry in the names table for an identifier or designator uses the
98 -- Info pointer to hold a link to the currently visible entity that has
99 -- this name (see subprograms Get_Name_Entity_Id and Set_Name_Entity_Id
100 -- in package Sem_Util). The visibility is initialized at the beginning of
101 -- semantic processing to make entities in package Standard immediately
102 -- visible. The visibility table is used in a more subtle way when
103 -- compiling subunits (see below).
105 -- Entities that have the same name (i.e. homonyms) are chained. In the
106 -- case of overloaded entities, this chain holds all the possible meanings
107 -- of a given identifier. The process of overload resolution uses type
108 -- information to select from this chain the unique meaning of a given
111 -- Entities are also chained in their scope, through the Next_Entity link.
112 -- As a consequence, the name space is organized as a sparse matrix, where
113 -- each row corresponds to a scope, and each column to a source identifier.
114 -- Open scopes, that is to say scopes currently being compiled, have their
115 -- corresponding rows of entities in order, innermost scope first.
117 -- The scopes of packages that are mentioned in context clauses appear in
118 -- no particular order, interspersed among open scopes. This is because
119 -- in the course of analyzing the context of a compilation, a package
120 -- declaration is first an open scope, and subsequently an element of the
121 -- context. If subunits or child units are present, a parent unit may
122 -- appear under various guises at various times in the compilation.
124 -- When the compilation of the innermost scope is complete, the entities
125 -- defined therein are no longer visible. If the scope is not a package
126 -- declaration, these entities are never visible subsequently, and can be
127 -- removed from visibility chains. If the scope is a package declaration,
128 -- its visible declarations may still be accessible. Therefore the entities
129 -- defined in such a scope are left on the visibility chains, and only
130 -- their visibility (immediately visibility or potential use-visibility)
133 -- The ordering of homonyms on their chain does not necessarily follow
134 -- the order of their corresponding scopes on the scope stack. For
135 -- example, if package P and the enclosing scope both contain entities
136 -- named E, then when compiling the package body the chain for E will
137 -- hold the global entity first, and the local one (corresponding to
138 -- the current inner scope) next. As a result, name resolution routines
139 -- do not assume any relative ordering of the homonym chains, either
140 -- for scope nesting or to order of appearance of context clauses.
142 -- When compiling a child unit, entities in the parent scope are always
143 -- immediately visible. When compiling the body of a child unit, private
144 -- entities in the parent must also be made immediately visible. There
145 -- are separate routines to make the visible and private declarations
146 -- visible at various times (see package Sem_Ch7).
148 -- +--------+ +-----+
149 -- | In use |-------->| EU1 |-------------------------->
150 -- +--------+ +-----+
152 -- +--------+ +-----+ +-----+
153 -- | Stand. |---------------->| ES1 |--------------->| ES2 |--->
154 -- +--------+ +-----+ +-----+
156 -- +---------+ | +-----+
157 -- | with'ed |------------------------------>| EW2 |--->
158 -- +---------+ | +-----+
160 -- +--------+ +-----+ +-----+
161 -- | Scope2 |---------------->| E12 |--------------->| E22 |--->
162 -- +--------+ +-----+ +-----+
164 -- +--------+ +-----+ +-----+
165 -- | Scope1 |---------------->| E11 |--------------->| E12 |--->
166 -- +--------+ +-----+ +-----+
170 -- | | with'ed |----------------------------------------->
174 -- (innermost first) | |
175 -- +----------------------------+
176 -- Names table => | Id1 | | | | Id2 |
177 -- +----------------------------+
179 -- Name resolution must deal with several syntactic forms: simple names,
180 -- qualified names, indexed names, and various forms of calls.
182 -- Each identifier points to an entry in the names table. The resolution
183 -- of a simple name consists in traversing the homonym chain, starting
184 -- from the names table. If an entry is immediately visible, it is the one
185 -- designated by the identifier. If only potentially use-visible entities
186 -- are on the chain, we must verify that they do not hide each other. If
187 -- the entity we find is overloadable, we collect all other overloadable
188 -- entities on the chain as long as they are not hidden.
190 -- To resolve expanded names, we must find the entity at the intersection
191 -- of the entity chain for the scope (the prefix) and the homonym chain
192 -- for the selector. In general, homonym chains will be much shorter than
193 -- entity chains, so it is preferable to start from the names table as
194 -- well. If the entity found is overloadable, we must collect all other
195 -- interpretations that are defined in the scope denoted by the prefix.
197 -- For records, protected types, and tasks, their local entities are
198 -- removed from visibility chains on exit from the corresponding scope.
199 -- From the outside, these entities are always accessed by selected
200 -- notation, and the entity chain for the record type, protected type,
201 -- etc. is traversed sequentially in order to find the designated entity.
203 -- The discriminants of a type and the operations of a protected type or
204 -- task are unchained on exit from the first view of the type, (such as
205 -- a private or incomplete type declaration, or a protected type speci-
206 -- fication) and re-chained when compiling the second view.
208 -- In the case of operators, we do not make operators on derived types
209 -- explicit. As a result, the notation P."+" may denote either a user-
210 -- defined function with name "+", or else an implicit declaration of the
211 -- operator "+" in package P. The resolution of expanded names always
212 -- tries to resolve an operator name as such an implicitly defined entity,
213 -- in addition to looking for explicit declarations.
215 -- All forms of names that denote entities (simple names, expanded names,
216 -- character literals in some cases) have a Entity attribute, which
217 -- identifies the entity denoted by the name.
219 ---------------------
220 -- The Scope Stack --
221 ---------------------
223 -- The Scope stack keeps track of the scopes currently been compiled.
224 -- Every entity that contains declarations (including records) is placed
225 -- on the scope stack while it is being processed, and removed at the end.
226 -- Whenever a non-package scope is exited, the entities defined therein
227 -- are removed from the visibility table, so that entities in outer scopes
228 -- become visible (see previous description). On entry to Sem, the scope
229 -- stack only contains the package Standard. As usual, subunits complicate
230 -- this picture ever so slightly.
232 -- The Rtsfind mechanism can force a call to Semantics while another
233 -- compilation is in progress. The unit retrieved by Rtsfind must be
234 -- compiled in its own context, and has no access to the visibility of
235 -- the unit currently being compiled. The procedures Save_Scope_Stack and
236 -- Restore_Scope_Stack make entities in current open scopes invisible
237 -- before compiling the retrieved unit, and restore the compilation
238 -- environment afterwards.
240 ------------------------
241 -- Compiling subunits --
242 ------------------------
244 -- Subunits must be compiled in the environment of the corresponding stub,
245 -- that is to say with the same visibility into the parent (and its
246 -- context) that is available at the point of the stub declaration, but
247 -- with the additional visibility provided by the context clause of the
248 -- subunit itself. As a result, compilation of a subunit forces compilation
249 -- of the parent (see description in lib-). At the point of the stub
250 -- declaration, Analyze is called recursively to compile the proper body of
251 -- the subunit, but without reinitializing the names table, nor the scope
252 -- stack (i.e. standard is not pushed on the stack). In this fashion the
253 -- context of the subunit is added to the context of the parent, and the
254 -- subunit is compiled in the correct environment. Note that in the course
255 -- of processing the context of a subunit, Standard will appear twice on
256 -- the scope stack: once for the parent of the subunit, and once for the
257 -- unit in the context clause being compiled. However, the two sets of
258 -- entities are not linked by homonym chains, so that the compilation of
259 -- any context unit happens in a fresh visibility environment.
261 -------------------------------
262 -- Processing of USE Clauses --
263 -------------------------------
265 -- Every defining occurrence has a flag indicating if it is potentially use
266 -- visible. Resolution of simple names examines this flag. The processing
267 -- of use clauses consists in setting this flag on all visible entities
268 -- defined in the corresponding package. On exit from the scope of the use
269 -- clause, the corresponding flag must be reset. However, a package may
270 -- appear in several nested use clauses (pathological but legal, alas)
271 -- which forces us to use a slightly more involved scheme:
273 -- a) The defining occurrence for a package holds a flag -In_Use- to
274 -- indicate that it is currently in the scope of a use clause. If a
275 -- redundant use clause is encountered, then the corresponding occurrence
276 -- of the package name is flagged -Redundant_Use-.
278 -- b) On exit from a scope, the use clauses in its declarative part are
279 -- scanned. The visibility flag is reset in all entities declared in
280 -- package named in a use clause, as long as the package is not flagged
281 -- as being in a redundant use clause (in which case the outer use
282 -- clause is still in effect, and the direct visibility of its entities
283 -- must be retained).
285 -- Note that entities are not removed from their homonym chains on exit
286 -- from the package specification. A subsequent use clause does not need
287 -- to rechain the visible entities, but only to establish their direct
290 -----------------------------------
291 -- Handling private declarations --
292 -----------------------------------
294 -- The principle that each entity has a single defining occurrence clashes
295 -- with the presence of two separate definitions for private types: the
296 -- first is the private type declaration, and second is the full type
297 -- declaration. It is important that all references to the type point to
298 -- the same defining occurrence, namely the first one. To enforce the two
299 -- separate views of the entity, the corresponding information is swapped
300 -- between the two declarations. Outside of the package, the defining
301 -- occurrence only contains the private declaration information, while in
302 -- the private part and the body of the package the defining occurrence
303 -- contains the full declaration. To simplify the swap, the defining
304 -- occurrence that currently holds the private declaration points to the
305 -- full declaration. During semantic processing the defining occurrence
306 -- also points to a list of private dependents, that is to say access types
307 -- or composite types whose designated types or component types are
308 -- subtypes or derived types of the private type in question. After the
309 -- full declaration has been seen, the private dependents are updated to
310 -- indicate that they have full definitions.
312 ------------------------------------
313 -- Handling of Undefined Messages --
314 ------------------------------------
316 -- In normal mode, only the first use of an undefined identifier generates
317 -- a message. The table Urefs is used to record error messages that have
318 -- been issued so that second and subsequent ones do not generate further
319 -- messages. However, the second reference causes text to be added to the
320 -- original undefined message noting "(more references follow)". The
321 -- full error list option (-gnatf) forces messages to be generated for
322 -- every reference and disconnects the use of this table.
324 type Uref_Entry
is record
326 -- Node for identifier for which original message was posted. The
327 -- Chars field of this identifier is used to detect later references
328 -- to the same identifier.
331 -- Records error message Id of original undefined message. Reset to
332 -- No_Error_Msg after the second occurrence, where it is used to add
333 -- text to the original message as described above.
336 -- Set if the message is not visible rather than undefined
339 -- Records location of error message. Used to make sure that we do
340 -- not consider a, b : undefined as two separate instances, which
341 -- would otherwise happen, since the parser converts this sequence
342 -- to a : undefined; b : undefined.
346 package Urefs
is new Table
.Table
(
347 Table_Component_Type
=> Uref_Entry
,
348 Table_Index_Type
=> Nat
,
349 Table_Low_Bound
=> 1,
351 Table_Increment
=> 100,
352 Table_Name
=> "Urefs");
354 Candidate_Renaming
: Entity_Id
;
355 -- Holds a candidate interpretation that appears in a subprogram renaming
356 -- declaration and does not match the given specification, but matches at
357 -- least on the first formal. Allows better error message when given
358 -- specification omits defaulted parameters, a common error.
360 -----------------------
361 -- Local Subprograms --
362 -----------------------
364 procedure Analyze_Generic_Renaming
367 -- Common processing for all three kinds of generic renaming declarations.
368 -- Enter new name and indicate that it renames the generic unit.
370 procedure Analyze_Renamed_Character
374 -- Renamed entity is given by a character literal, which must belong
375 -- to the return type of the new entity. Is_Body indicates whether the
376 -- declaration is a renaming_as_body. If the original declaration has
377 -- already been frozen (because of an intervening body, e.g.) the body of
378 -- the function must be built now. The same applies to the following
379 -- various renaming procedures.
381 procedure Analyze_Renamed_Dereference
385 -- Renamed entity is given by an explicit dereference. Prefix must be a
386 -- conformant access_to_subprogram type.
388 procedure Analyze_Renamed_Entry
392 -- If the renamed entity in a subprogram renaming is an entry or protected
393 -- subprogram, build a body for the new entity whose only statement is a
394 -- call to the renamed entity.
396 procedure Analyze_Renamed_Family_Member
400 -- Used when the renamed entity is an indexed component. The prefix must
401 -- denote an entry family.
403 procedure Analyze_Renamed_Primitive_Operation
407 -- If the renamed entity in a subprogram renaming is a primitive operation
408 -- or a class-wide operation in prefix form, save the target object,
409 -- which must be added to the list of actuals in any subsequent call.
410 -- The renaming operation is intrinsic because the compiler must in
411 -- fact generate a wrapper for it (6.3.1 (10 1/2)).
413 procedure Attribute_Renaming
(N
: Node_Id
);
414 -- Analyze renaming of attribute as subprogram. The renaming declaration N
415 -- is rewritten as a subprogram body that returns the attribute reference
416 -- applied to the formals of the function.
418 procedure Set_Entity_Or_Discriminal
(N
: Node_Id
; E
: Entity_Id
);
419 -- Set Entity, with style check if need be. For a discriminant reference,
420 -- replace by the corresponding discriminal, i.e. the parameter of the
421 -- initialization procedure that corresponds to the discriminant.
423 procedure Check_Frozen_Renaming
(N
: Node_Id
; Subp
: Entity_Id
);
424 -- A renaming_as_body may occur after the entity of the original decla-
425 -- ration has been frozen. In that case, the body of the new entity must
426 -- be built now, because the usual mechanism of building the renamed
427 -- body at the point of freezing will not work. Subp is the subprogram
428 -- for which N provides the Renaming_As_Body.
430 procedure Check_In_Previous_With_Clause
(N
, Nam
: Node_Id
);
431 -- N is a use_package clause and Nam the package name, or N is a use_type
432 -- clause and Nam is the prefix of the type name. In either case, verify
433 -- that the package is visible at that point in the context: either it
434 -- appears in a previous with_clause, or because it is a fully qualified
435 -- name and the root ancestor appears in a previous with_clause.
437 procedure Check_Library_Unit_Renaming
(N
: Node_Id
; Old_E
: Entity_Id
);
438 -- Verify that the entity in a renaming declaration that is a library unit
439 -- is itself a library unit and not a nested unit or subunit. Also check
440 -- that if the renaming is a child unit of a generic parent, then the
441 -- renamed unit must also be a child unit of that parent. Finally, verify
442 -- that a renamed generic unit is not an implicit child declared within
443 -- an instance of the parent.
445 procedure Chain_Use_Clause
(N
: Node_Id
);
446 -- Chain use clause onto list of uses clauses headed by First_Use_Clause in
447 -- the proper scope table entry. This is usually the current scope, but it
448 -- will be an inner scope when installing the use clauses of the private
449 -- declarations of a parent unit prior to compiling the private part of a
450 -- child unit. This chain is traversed when installing/removing use clauses
451 -- when compiling a subunit or instantiating a generic body on the fly,
452 -- when it is necessary to save and restore full environments.
454 function Enclosing_Instance
return Entity_Id
;
455 -- In an instance nested within another one, several semantic checks are
456 -- unnecessary because the legality of the nested instance has been checked
457 -- in the enclosing generic unit. This applies in particular to legality
458 -- checks on actuals for formal subprograms of the inner instance, which
459 -- are checked as subprogram renamings, and may be complicated by confusion
460 -- in private/full views. This function returns the instance enclosing the
461 -- current one if there is such, else it returns Empty.
463 -- If the renaming determines the entity for the default of a formal
464 -- subprogram nested within another instance, choose the innermost
465 -- candidate. This is because if the formal has a box, and we are within
466 -- an enclosing instance where some candidate interpretations are local
467 -- to this enclosing instance, we know that the default was properly
468 -- resolved when analyzing the generic, so we prefer the local
469 -- candidates to those that are external. This is not always the case
470 -- but is a reasonable heuristic on the use of nested generics. The
471 -- proper solution requires a full renaming model.
473 function Entity_Of_Unit
(U
: Node_Id
) return Entity_Id
;
474 -- Return the appropriate entity for determining which unit has a deeper
475 -- scope: the defining entity for U, unless U is a package instance, in
476 -- which case we retrieve the entity of the instance spec.
478 procedure Error_Missing_With_Of_Known_Unit
(Pkg
: Node_Id
);
479 -- Display an error message denoting a "with" is missing for a given known
480 -- package Pkg with its full path name.
482 procedure Find_Expanded_Name
(N
: Node_Id
);
483 -- The input is a selected component known to be an expanded name. Verify
484 -- legality of selector given the scope denoted by prefix, and change node
485 -- N into a expanded name with a properly set Entity field.
487 function Find_First_Use
(Use_Clause
: Node_Id
) return Node_Id
;
488 -- Find the most previous use clause (that is, the first one to appear in
489 -- the source) by traversing the previous clause chain that exists in both
490 -- N_Use_Package_Clause nodes and N_Use_Type_Clause nodes.
492 function Find_Renamed_Entity
496 Is_Actual
: Boolean := False) return Entity_Id
;
497 -- Find the renamed entity that corresponds to the given parameter profile
498 -- in a subprogram renaming declaration. The renamed entity may be an
499 -- operator, a subprogram, an entry, or a protected operation. Is_Actual
500 -- indicates that the renaming is the one generated for an actual subpro-
501 -- gram in an instance, for which special visibility checks apply.
503 function Has_Implicit_Character_Literal
(N
: Node_Id
) return Boolean;
504 -- Find a type derived from Character or Wide_Character in the prefix of N.
505 -- Used to resolved qualified names whose selector is a character literal.
507 function Has_Private_With
(E
: Entity_Id
) return Boolean;
508 -- Ada 2005 (AI-262): Determines if the current compilation unit has a
509 -- private with on E.
511 function Has_Components
(Typ
: Entity_Id
) return Boolean;
512 -- Determine if given type has components, i.e. is either a record type or
513 -- type or a type that has discriminants.
515 function Has_Implicit_Operator
(N
: Node_Id
) return Boolean;
516 -- N is an expanded name whose selector is an operator name (e.g. P."+").
517 -- Determine if N denotes an operator implicitly declared in prefix P: P's
518 -- declarative part contains an implicit declaration of an operator if it
519 -- has a declaration of a type to which one of the predefined operators
520 -- apply. The existence of this routine is an implementation artifact. A
521 -- more straightforward but more space-consuming choice would be to make
522 -- all inherited operators explicit in the symbol table.
524 procedure Inherit_Renamed_Profile
(New_S
: Entity_Id
; Old_S
: Entity_Id
);
525 -- A subprogram defined by a renaming declaration inherits the parameter
526 -- profile of the renamed entity. The subtypes given in the subprogram
527 -- specification are discarded and replaced with those of the renamed
528 -- subprogram, which are then used to recheck the default values.
530 function Most_Descendant_Use_Clause
531 (Clause1
: Entity_Id
;
532 Clause2
: Entity_Id
) return Entity_Id
;
533 -- Determine which use clause parameter is the most descendant in terms of
536 procedure Premature_Usage
(N
: Node_Id
);
537 -- Diagnose usage of an entity before it is visible
539 function Is_Self_Hidden
(E
: Entity_Id
) return Boolean;
540 -- True within a declaration if it is hidden from all visibility by itself
541 -- (see RM-8.3(16-18)). This is mostly just "not Is_Not_Self_Hidden", but
542 -- we need to check for E_Void in case of errors.
544 procedure Use_One_Package
546 Pack_Name
: Entity_Id
:= Empty
;
547 Force
: Boolean := False);
548 -- Make visible entities declared in package P potentially use-visible
549 -- in the current context. Also used in the analysis of subunits, when
550 -- re-installing use clauses of parent units. N is the use_clause that
551 -- names P (and possibly other packages).
553 procedure Use_One_Type
555 Installed
: Boolean := False;
556 Force
: Boolean := False);
557 -- Id is the subtype mark from a use_type_clause. This procedure makes
558 -- the primitive operators of the type potentially use-visible. The
559 -- boolean flag Installed indicates that the clause is being reinstalled
560 -- after previous analysis, and primitive operations are already chained
561 -- on the Used_Operations list of the clause.
563 procedure Write_Info
;
564 -- Write debugging information on entities declared in current scope
566 --------------------------------
567 -- Analyze_Exception_Renaming --
568 --------------------------------
570 -- The language only allows a single identifier, but the tree holds an
571 -- identifier list. The parser has already issued an error message if
572 -- there is more than one element in the list.
574 procedure Analyze_Exception_Renaming
(N
: Node_Id
) is
575 Id
: constant Entity_Id
:= Defining_Entity
(N
);
576 Nam
: constant Node_Id
:= Name
(N
);
582 Mutate_Ekind
(Id
, E_Exception
);
583 Set_Etype
(Id
, Standard_Exception_Type
);
584 Set_Is_Pure
(Id
, Is_Pure
(Current_Scope
));
586 if Is_Entity_Name
(Nam
)
587 and then Present
(Entity
(Nam
))
588 and then Ekind
(Entity
(Nam
)) = E_Exception
590 if Present
(Renamed_Entity
(Entity
(Nam
))) then
591 Set_Renamed_Entity
(Id
, Renamed_Entity
(Entity
(Nam
)));
593 Set_Renamed_Entity
(Id
, Entity
(Nam
));
596 -- The exception renaming declaration may become Ghost if it renames
599 Mark_Ghost_Renaming
(N
, Entity
(Nam
));
601 Error_Msg_N
("invalid exception name in renaming", Nam
);
604 -- Implementation-defined aspect specifications can appear in a renaming
605 -- declaration, but not language-defined ones. The call to procedure
606 -- Analyze_Aspect_Specifications will take care of this error check.
608 Analyze_Aspect_Specifications
(N
, Id
);
609 end Analyze_Exception_Renaming
;
611 ---------------------------
612 -- Analyze_Expanded_Name --
613 ---------------------------
615 procedure Analyze_Expanded_Name
(N
: Node_Id
) is
617 -- If the entity pointer is already set, this is an internal node, or a
618 -- node that is analyzed more than once, after a tree modification. In
619 -- such a case there is no resolution to perform, just set the type. In
620 -- either case, start by analyzing the prefix.
622 Analyze
(Prefix
(N
));
624 if Present
(Entity
(N
)) then
625 if Is_Type
(Entity
(N
)) then
626 Set_Etype
(N
, Entity
(N
));
628 Set_Etype
(N
, Etype
(Entity
(N
)));
632 Find_Expanded_Name
(N
);
635 -- In either case, propagate dimension of entity to expanded name
637 Analyze_Dimension
(N
);
638 end Analyze_Expanded_Name
;
640 ---------------------------------------
641 -- Analyze_Generic_Function_Renaming --
642 ---------------------------------------
644 procedure Analyze_Generic_Function_Renaming
(N
: Node_Id
) is
646 Analyze_Generic_Renaming
(N
, E_Generic_Function
);
647 end Analyze_Generic_Function_Renaming
;
649 --------------------------------------
650 -- Analyze_Generic_Package_Renaming --
651 --------------------------------------
653 procedure Analyze_Generic_Package_Renaming
(N
: Node_Id
) is
655 -- Test for the Text_IO special unit case here, since we may be renaming
656 -- one of the subpackages of Text_IO, then join common routine.
658 Check_Text_IO_Special_Unit
(Name
(N
));
660 Analyze_Generic_Renaming
(N
, E_Generic_Package
);
661 end Analyze_Generic_Package_Renaming
;
663 ----------------------------------------
664 -- Analyze_Generic_Procedure_Renaming --
665 ----------------------------------------
667 procedure Analyze_Generic_Procedure_Renaming
(N
: Node_Id
) is
669 Analyze_Generic_Renaming
(N
, E_Generic_Procedure
);
670 end Analyze_Generic_Procedure_Renaming
;
672 ------------------------------
673 -- Analyze_Generic_Renaming --
674 ------------------------------
676 procedure Analyze_Generic_Renaming
680 New_P
: constant Entity_Id
:= Defining_Entity
(N
);
681 Inst
: Boolean := False;
685 if Name
(N
) = Error
then
689 Generate_Definition
(New_P
);
691 if Current_Scope
/= Standard_Standard
then
692 Set_Is_Pure
(New_P
, Is_Pure
(Current_Scope
));
695 if Nkind
(Name
(N
)) = N_Selected_Component
then
696 Check_Generic_Child_Unit
(Name
(N
), Inst
);
701 if not Is_Entity_Name
(Name
(N
)) then
702 Error_Msg_N
("expect entity name in renaming declaration", Name
(N
));
705 Old_P
:= Entity
(Name
(N
));
709 Mutate_Ekind
(New_P
, K
);
711 if Etype
(Old_P
) = Any_Type
then
714 elsif Ekind
(Old_P
) /= K
then
715 Error_Msg_N
("invalid generic unit name", Name
(N
));
718 if Present
(Renamed_Entity
(Old_P
)) then
719 Set_Renamed_Entity
(New_P
, Renamed_Entity
(Old_P
));
721 Set_Renamed_Entity
(New_P
, Old_P
);
724 -- The generic renaming declaration may become Ghost if it renames a
727 Mark_Ghost_Renaming
(N
, Old_P
);
729 Set_Is_Pure
(New_P
, Is_Pure
(Old_P
));
730 Set_Is_Preelaborated
(New_P
, Is_Preelaborated
(Old_P
));
732 Set_Etype
(New_P
, Etype
(Old_P
));
733 Set_Has_Completion
(New_P
);
735 if In_Open_Scopes
(Old_P
) then
736 Error_Msg_N
("within its scope, generic denotes its instance", N
);
739 -- For subprograms, propagate the Intrinsic flag, to allow, e.g.
740 -- renamings and subsequent instantiations of Unchecked_Conversion.
742 if Is_Generic_Subprogram
(Old_P
) then
743 Set_Is_Intrinsic_Subprogram
744 (New_P
, Is_Intrinsic_Subprogram
(Old_P
));
747 Check_Library_Unit_Renaming
(N
, Old_P
);
750 -- Implementation-defined aspect specifications can appear in a renaming
751 -- declaration, but not language-defined ones. The call to procedure
752 -- Analyze_Aspect_Specifications will take care of this error check.
754 Analyze_Aspect_Specifications
(N
, New_P
);
755 end Analyze_Generic_Renaming
;
757 -----------------------------
758 -- Analyze_Object_Renaming --
759 -----------------------------
761 procedure Analyze_Object_Renaming
(N
: Node_Id
) is
762 Id
: constant Entity_Id
:= Defining_Identifier
(N
);
763 Loc
: constant Source_Ptr
:= Sloc
(N
);
764 Nam
: constant Node_Id
:= Name
(N
);
765 Is_Object_Ref
: Boolean;
771 procedure Check_Constrained_Object
;
772 -- If the nominal type is unconstrained but the renamed object is
773 -- constrained, as can happen with renaming an explicit dereference or
774 -- a function return, build a constrained subtype from the object. If
775 -- the renaming is for a formal in an accept statement, the analysis
776 -- has already established its actual subtype. This is only relevant
777 -- if the renamed object is an explicit dereference.
779 function Get_Object_Name
(Nod
: Node_Id
) return Node_Id
;
780 -- Obtain the name of the object from node Nod which is being renamed by
781 -- the object renaming declaration N.
783 function Find_Raise_Node
(N
: Node_Id
) return Traverse_Result
;
784 -- Process one node in search for N_Raise_xxx_Error nodes.
785 -- Return Abandon if found, OK otherwise.
787 ---------------------
788 -- Find_Raise_Node --
789 ---------------------
791 function Find_Raise_Node
(N
: Node_Id
) return Traverse_Result
is
793 if Nkind
(N
) in N_Raise_xxx_Error
then
800 ------------------------
801 -- No_Raise_xxx_Error --
802 ------------------------
804 function No_Raise_xxx_Error
is new Traverse_Func
(Find_Raise_Node
);
805 -- Traverse tree to look for a N_Raise_xxx_Error node and returns
806 -- Abandon if so and OK if none found.
808 ------------------------------
809 -- Check_Constrained_Object --
810 ------------------------------
812 procedure Check_Constrained_Object
is
813 Typ
: constant Entity_Id
:= Etype
(Nam
);
815 Loop_Scheme
: Node_Id
;
818 if Nkind
(Nam
) in N_Function_Call | N_Explicit_Dereference
819 and then Is_Composite_Type
(Typ
)
820 and then not Is_Constrained
(Typ
)
821 and then not Has_Unknown_Discriminants
(Typ
)
822 and then Expander_Active
824 -- If Actual_Subtype is already set, nothing to do
826 if Ekind
(Id
) in E_Variable | E_Constant
827 and then Present
(Actual_Subtype
(Id
))
831 -- A renaming of an unchecked union has no actual subtype
833 elsif Is_Unchecked_Union
(Typ
) then
836 -- If a record is limited its size is invariant. This is the case
837 -- in particular with record types with an access discriminant
838 -- that are used in iterators. This is an optimization, but it
839 -- also prevents typing anomalies when the prefix is further
842 -- Note that we cannot just use the Is_Limited_Record flag because
843 -- it does not apply to records with limited components, for which
844 -- this syntactic flag is not set, but whose size is also fixed.
846 -- Note also that we need to build the constrained subtype for an
847 -- array in order to make the bounds explicit in most cases, but
848 -- not if the object comes from an extended return statement, as
849 -- this would create dangling references to them later on.
851 elsif Is_Limited_Type
(Typ
)
852 and then (not Is_Array_Type
(Typ
) or else Is_Return_Object
(Id
))
857 Subt
:= Make_Temporary
(Loc
, 'T');
858 Remove_Side_Effects
(Nam
);
860 Make_Subtype_Declaration
(Loc
,
861 Defining_Identifier
=> Subt
,
862 Subtype_Indication
=>
863 Make_Subtype_From_Expr
(Nam
, Typ
)));
866 New_Subtype_Mark
: constant Node_Id
:=
867 New_Occurrence_Of
(Subt
, Loc
);
869 if Present
(Subtype_Mark
(N
)) then
870 Rewrite
(Subtype_Mark
(N
), New_Subtype_Mark
);
872 -- An Ada2022 renaming with no subtype mark
873 Set_Subtype_Mark
(N
, New_Subtype_Mark
);
877 Set_Etype
(Nam
, Subt
);
879 -- Suppress discriminant checks on this subtype if the original
880 -- type has defaulted discriminants and Id is a "for of" loop
883 if Has_Defaulted_Discriminants
(Typ
)
884 and then Nkind
(Original_Node
(Parent
(N
))) = N_Loop_Statement
886 Loop_Scheme
:= Iteration_Scheme
(Original_Node
(Parent
(N
)));
888 if Present
(Loop_Scheme
)
889 and then Present
(Iterator_Specification
(Loop_Scheme
))
892 (Iterator_Specification
(Loop_Scheme
)) = Id
894 Set_Checks_May_Be_Suppressed
(Subt
);
895 Push_Local_Suppress_Stack_Entry
897 Check
=> Discriminant_Check
,
902 -- Freeze subtype at once, to prevent order of elaboration
903 -- issues in the backend. The renamed object exists, so its
904 -- type is already frozen in any case.
906 Freeze_Before
(N
, Subt
);
909 end Check_Constrained_Object
;
911 ---------------------
912 -- Get_Object_Name --
913 ---------------------
915 function Get_Object_Name
(Nod
: Node_Id
) return Node_Id
is
920 while Present
(Obj_Nam
) loop
921 case Nkind
(Obj_Nam
) is
922 when N_Attribute_Reference
923 | N_Explicit_Dereference
924 | N_Indexed_Component
927 Obj_Nam
:= Prefix
(Obj_Nam
);
929 when N_Selected_Component
=>
930 Obj_Nam
:= Selector_Name
(Obj_Nam
);
932 when N_Qualified_Expression | N_Type_Conversion
=>
933 Obj_Nam
:= Expression
(Obj_Nam
);
943 -- Start of processing for Analyze_Object_Renaming
950 Set_Is_Pure
(Id
, Is_Pure
(Current_Scope
));
953 -- The renaming of a component that depends on a discriminant requires
954 -- an actual subtype, because in subsequent use of the object Gigi will
955 -- be unable to locate the actual bounds. This explicit step is required
956 -- when the renaming is generated in removing side effects of an
957 -- already-analyzed expression.
959 if Nkind
(Nam
) = N_Selected_Component
and then Analyzed
(Nam
) then
961 -- The object renaming declaration may become Ghost if it renames a
964 if Is_Entity_Name
(Nam
) then
965 Mark_Ghost_Renaming
(N
, Entity
(Nam
));
969 Dec
:= Build_Actual_Subtype_Of_Component
(Etype
(Nam
), Nam
);
971 if Present
(Dec
) then
972 Insert_Action
(N
, Dec
);
973 T
:= Defining_Identifier
(Dec
);
976 elsif Present
(Subtype_Mark
(N
))
977 or else No
(Access_Definition
(N
))
979 if Present
(Subtype_Mark
(N
)) then
980 Find_Type
(Subtype_Mark
(N
));
981 T
:= Entity
(Subtype_Mark
(N
));
984 -- AI12-0275: Case of object renaming without a subtype_mark
989 -- Normal case of no overloading in object name
991 if not Is_Overloaded
(Nam
) then
993 -- Catch error cases (such as attempting to rename a procedure
994 -- or package) using the shorthand form.
997 or else Etype
(Nam
) = Standard_Void_Type
1000 ("object name or value expected in renaming", Nam
);
1002 Mutate_Ekind
(Id
, E_Variable
);
1003 Set_Etype
(Id
, Any_Type
);
1011 -- Case of overloaded name, which will be illegal if there's more
1012 -- than one acceptable interpretation (such as overloaded function
1024 -- More than one candidate interpretation is available
1026 -- Remove procedure calls, which syntactically cannot appear
1027 -- in this context, but which cannot be removed by type
1028 -- checking, because the context does not impose a type.
1030 Get_First_Interp
(Nam
, I
, It
);
1031 while Present
(It
.Typ
) loop
1032 if It
.Typ
= Standard_Void_Type
then
1036 Get_Next_Interp
(I
, It
);
1039 Get_First_Interp
(Nam
, I
, It
);
1043 -- If there's no type present, we have an error case (such
1044 -- as overloaded procedures named in the object renaming).
1048 ("object name or value expected in renaming", Nam
);
1050 Mutate_Ekind
(Id
, E_Variable
);
1051 Set_Etype
(Id
, Any_Type
);
1056 Get_Next_Interp
(I
, It
);
1058 if Present
(It
.Typ
) then
1060 It1
:= Disambiguate
(Nam
, I1
, I
, Any_Type
);
1062 if It1
= No_Interp
then
1063 Error_Msg_N
("ambiguous name in object renaming", Nam
);
1065 Error_Msg_Sloc
:= Sloc
(It
.Nam
);
1066 Error_Msg_N
("\\possible interpretation#!", Nam
);
1068 Error_Msg_Sloc
:= Sloc
(Nam1
);
1069 Error_Msg_N
("\\possible interpretation#!", Nam
);
1075 Set_Etype
(Nam
, It1
.Typ
);
1080 if Etype
(Nam
) = Standard_Exception_Type
then
1082 ("exception requires a subtype mark in renaming", Nam
);
1087 -- The object renaming declaration may become Ghost if it renames a
1090 if Is_Entity_Name
(Nam
) then
1091 Mark_Ghost_Renaming
(N
, Entity
(Nam
));
1094 -- Check against AI12-0401 here before Resolve may rewrite Nam and
1095 -- potentially generate spurious warnings.
1097 -- In the case where the object_name is a qualified_expression with
1098 -- a nominal subtype T and whose expression is a name that denotes
1100 -- * if T is an elementary subtype, then:
1101 -- * Q shall be a constant other than a dereference of an access
1103 -- * the nominal subtype of Q shall be statically compatible with
1105 -- * T shall statically match the base subtype of its type if
1106 -- scalar, or the first subtype of its type if an access type.
1107 -- * if T is a composite subtype, then Q shall be known to be
1108 -- constrained or T shall statically match the first subtype of
1111 if Nkind
(Nam
) = N_Qualified_Expression
1112 and then Is_Object_Reference
(Expression
(Nam
))
1114 Q
:= Expression
(Nam
);
1116 if (Is_Elementary_Type
(T
)
1118 not ((not Is_Variable
(Q
)
1119 and then Nkind
(Q
) /= N_Explicit_Dereference
)
1120 or else Subtypes_Statically_Compatible
(Etype
(Q
), T
)
1121 or else (Is_Scalar_Type
(T
)
1122 and then Subtypes_Statically_Match
1124 or else (Is_Access_Type
(T
)
1125 and then Subtypes_Statically_Match
1126 (T
, First_Subtype
(T
)))))
1127 or else (Is_Composite_Type
(T
)
1130 -- If Q is an aggregate, Is_Constrained may not be set
1131 -- yet and its type may not be resolved yet.
1132 -- This doesn't quite correspond to the complex notion
1133 -- of "known to be constrained" but this is good enough
1134 -- for a rule which is in any case too complex.
1136 not (Is_Constrained
(Etype
(Q
))
1137 or else Nkind
(Q
) = N_Aggregate
1138 or else Subtypes_Statically_Match
1139 (T
, First_Subtype
(T
))))
1142 ("subtype of renamed qualified expression does not " &
1143 "statically match", N
);
1150 -- If the renamed object is a function call of a limited type,
1151 -- the expansion of the renaming is complicated by the presence
1152 -- of various temporaries and subtypes that capture constraints
1153 -- of the renamed object. Rewrite node as an object declaration,
1154 -- whose expansion is simpler. Given that the object is limited
1155 -- there is no copy involved and no performance hit.
1157 if Nkind
(Nam
) = N_Function_Call
1158 and then Is_Inherently_Limited_Type
(Etype
(Nam
))
1159 and then not Is_Constrained
(Etype
(Nam
))
1160 and then Comes_From_Source
(N
)
1163 Mutate_Ekind
(Id
, E_Constant
);
1165 Make_Object_Declaration
(Loc
,
1166 Defining_Identifier
=> Id
,
1167 Constant_Present
=> True,
1168 Object_Definition
=> New_Occurrence_Of
(Etype
(Nam
), Loc
),
1169 Expression
=> Relocate_Node
(Nam
)));
1173 -- Ada 2012 (AI05-149): Reject renaming of an anonymous access object
1174 -- when renaming declaration has a named access type. The Ada 2012
1175 -- coverage rules allow an anonymous access type in the context of
1176 -- an expected named general access type, but the renaming rules
1177 -- require the types to be the same. (An exception is when the type
1178 -- of the renaming is also an anonymous access type, which can only
1179 -- happen due to a renaming created by the expander.)
1181 if Nkind
(Nam
) = N_Type_Conversion
1182 and then not Comes_From_Source
(Nam
)
1183 and then Is_Anonymous_Access_Type
(Etype
(Expression
(Nam
)))
1184 and then not Is_Anonymous_Access_Type
(T
)
1187 ("cannot rename anonymous access object "
1188 & "as a named access type", Expression
(Nam
), T
);
1191 -- Check that a class-wide object is not being renamed as an object
1192 -- of a specific type. The test for access types is needed to exclude
1193 -- cases where the renamed object is a dynamically tagged access
1194 -- result, such as occurs in certain expansions.
1196 if Is_Tagged_Type
(T
) then
1197 Check_Dynamically_Tagged_Expression
1203 -- Ada 2005 (AI-230/AI-254): Access renaming
1205 else pragma Assert
(Present
(Access_Definition
(N
)));
1209 N
=> Access_Definition
(N
));
1213 -- The object renaming declaration may become Ghost if it renames a
1216 if Is_Entity_Name
(Nam
) then
1217 Mark_Ghost_Renaming
(N
, Entity
(Nam
));
1220 -- Ada 2005 AI05-105: if the declaration has an anonymous access
1221 -- type, the renamed object must also have an anonymous type, and
1222 -- this is a name resolution rule. This was implicit in the last part
1223 -- of the first sentence in 8.5.1(3/2), and is made explicit by this
1226 if not Is_Overloaded
(Nam
) then
1227 if Ekind
(Etype
(Nam
)) /= Ekind
(T
) then
1229 ("expect anonymous access type in object renaming", N
);
1236 Typ
: Entity_Id
:= Empty
;
1237 Seen
: Boolean := False;
1240 Get_First_Interp
(Nam
, I
, It
);
1241 while Present
(It
.Typ
) loop
1243 -- Renaming is ambiguous if more than one candidate
1244 -- interpretation is type-conformant with the context.
1246 if Ekind
(It
.Typ
) = Ekind
(T
) then
1247 if Ekind
(T
) = E_Anonymous_Access_Subprogram_Type
1250 (Designated_Type
(T
), Designated_Type
(It
.Typ
))
1256 ("ambiguous expression in renaming", Nam
);
1259 elsif Ekind
(T
) = E_Anonymous_Access_Type
1261 Covers
(Designated_Type
(T
), Designated_Type
(It
.Typ
))
1267 ("ambiguous expression in renaming", Nam
);
1271 if Covers
(T
, It
.Typ
) then
1273 Set_Etype
(Nam
, Typ
);
1274 Set_Is_Overloaded
(Nam
, False);
1278 Get_Next_Interp
(I
, It
);
1285 -- Do not perform the legality checks below when the resolution of
1286 -- the renaming name failed because the associated type is Any_Type.
1288 if Etype
(Nam
) = Any_Type
then
1291 -- Ada 2005 (AI-231): In the case where the type is defined by an
1292 -- access_definition, the renamed entity shall be of an access-to-
1293 -- constant type if and only if the access_definition defines an
1294 -- access-to-constant type. ARM 8.5.1(4)
1296 elsif Constant_Present
(Access_Definition
(N
))
1297 and then not Is_Access_Constant
(Etype
(Nam
))
1300 ("(Ada 2005): the renamed object is not access-to-constant "
1301 & "(RM 8.5.1(6))", N
);
1303 elsif not Constant_Present
(Access_Definition
(N
))
1304 and then Is_Access_Constant
(Etype
(Nam
))
1307 ("(Ada 2005): the renamed object is not access-to-variable "
1308 & "(RM 8.5.1(6))", N
);
1311 if Is_Access_Subprogram_Type
(Etype
(Nam
)) then
1312 Check_Subtype_Conformant
1313 (Designated_Type
(T
), Designated_Type
(Etype
(Nam
)));
1315 elsif not Subtypes_Statically_Match
1316 (Designated_Type
(T
),
1317 Available_View
(Designated_Type
(Etype
(Nam
))))
1320 ("subtype of renamed object does not statically match", N
);
1324 -- Special processing for renaming function return object. Some errors
1325 -- and warnings are produced only for calls that come from source.
1327 if Nkind
(Nam
) = N_Function_Call
then
1330 -- Usage is illegal in Ada 83, but renamings are also introduced
1331 -- during expansion, and error does not apply to those.
1334 if Comes_From_Source
(N
) then
1336 ("(Ada 83) cannot rename function return object", Nam
);
1339 -- In Ada 95, warn for odd case of renaming parameterless function
1340 -- call if this is not a limited type (where this is useful).
1343 if Warn_On_Object_Renames_Function
1344 and then No
(Parameter_Associations
(Nam
))
1345 and then not Is_Limited_Type
(Etype
(Nam
))
1346 and then Comes_From_Source
(Nam
)
1349 ("renaming function result object is suspicious?.r?", Nam
);
1351 ("\function & will be called only once?.r?", Nam
,
1352 Entity
(Name
(Nam
)));
1353 Error_Msg_N
-- CODEFIX
1354 ("\suggest using an initialized constant object "
1355 & "instead?.r?", Nam
);
1360 Check_Constrained_Object
;
1362 -- An object renaming requires an exact match of the type. Class-wide
1363 -- matching is not allowed.
1365 if Is_Class_Wide_Type
(T
)
1366 and then Base_Type
(Etype
(Nam
)) /= Base_Type
(T
)
1368 Wrong_Type
(Nam
, T
);
1371 -- We must search for an actual subtype here so that the bounds of
1372 -- objects of unconstrained types don't get dropped on the floor - such
1373 -- as with renamings of formal parameters.
1375 T2
:= Get_Actual_Subtype_If_Available
(Nam
);
1377 -- Ada 2005 (AI-326): Handle wrong use of incomplete type
1379 if Nkind
(Nam
) = N_Explicit_Dereference
1380 and then Ekind
(Etype
(T2
)) = E_Incomplete_Type
1382 Error_Msg_NE
("invalid use of incomplete type&", Id
, T2
);
1385 elsif Ekind
(Etype
(T
)) = E_Incomplete_Type
then
1386 Error_Msg_NE
("invalid use of incomplete type&", Id
, T
);
1390 if Ada_Version
>= Ada_2005
and then Nkind
(Nam
) in N_Has_Entity
then
1392 Nam_Ent
: constant Entity_Id
:= Entity
(Get_Object_Name
(Nam
));
1393 Nam_Decl
: constant Node_Id
:= Declaration_Node
(Nam_Ent
);
1396 if Has_Null_Exclusion
(N
)
1397 and then not Has_Null_Exclusion
(Nam_Decl
)
1399 -- Ada 2005 (AI-423): If the object name denotes a generic
1400 -- formal object of a generic unit G, and the object renaming
1401 -- declaration occurs within the body of G or within the body
1402 -- of a generic unit declared within the declarative region
1403 -- of G, then the declaration of the formal object of G must
1404 -- have a null exclusion or a null-excluding subtype.
1406 if Is_Formal_Object
(Nam_Ent
)
1407 and then In_Generic_Scope
(Id
)
1409 if not Can_Never_Be_Null
(Etype
(Nam_Ent
)) then
1411 ("object does not exclude `NULL` "
1412 & "(RM 8.5.1(4.6/2))", N
);
1414 elsif In_Package_Body
(Scope
(Id
)) then
1416 ("formal object does not have a null exclusion"
1417 & "(RM 8.5.1(4.6/2))", N
);
1420 -- Ada 2005 (AI-423): Otherwise, the subtype of the object name
1421 -- shall exclude null.
1423 elsif not Can_Never_Be_Null
(Etype
(Nam_Ent
)) then
1425 ("object does not exclude `NULL` "
1426 & "(RM 8.5.1(4.6/2))", N
);
1428 -- An instance is illegal if it contains a renaming that
1429 -- excludes null, and the actual does not. The renaming
1430 -- declaration has already indicated that the declaration
1431 -- of the renamed actual in the instance will raise
1432 -- constraint_error.
1434 elsif Nkind
(Nam_Decl
) = N_Object_Declaration
1435 and then In_Instance
1437 Present
(Corresponding_Generic_Association
(Nam_Decl
))
1438 and then Nkind
(Expression
(Nam_Decl
)) =
1439 N_Raise_Constraint_Error
1442 ("actual does not exclude `NULL` (RM 8.5.1(4.6/2))", N
);
1444 -- Finally, if there is a null exclusion, the subtype mark
1445 -- must not be null-excluding.
1447 elsif No
(Access_Definition
(N
))
1448 and then Can_Never_Be_Null
(T
)
1451 ("`NOT NULL` not allowed (& already excludes null)",
1456 elsif Can_Never_Be_Null
(T
)
1457 and then not Can_Never_Be_Null
(Etype
(Nam_Ent
))
1460 ("object does not exclude `NULL` (RM 8.5.1(4.6/2))", N
);
1462 elsif Has_Null_Exclusion
(N
)
1463 and then No
(Access_Definition
(N
))
1464 and then Can_Never_Be_Null
(T
)
1467 ("`NOT NULL` not allowed (& already excludes null)", N
, T
);
1472 -- Set the Ekind of the entity, unless it has been set already, as is
1473 -- the case for the iteration object over a container with no variable
1474 -- indexing. In that case it's been marked as a constant, and we do not
1475 -- want to change it to a variable.
1477 if Ekind
(Id
) /= E_Constant
then
1478 Mutate_Ekind
(Id
, E_Variable
);
1481 Reinit_Object_Size_Align
(Id
);
1483 -- If N comes from source then check that the original node is an
1484 -- object reference since there may have been several rewritting and
1485 -- folding. Do not do this for N_Function_Call or N_Explicit_Dereference
1486 -- which might correspond to rewrites of e.g. N_Selected_Component
1487 -- (for example Object.Method rewriting).
1488 -- If N does not come from source then assume the tree is properly
1489 -- formed and accept any object reference. In such cases we do support
1490 -- more cases of renamings anyway, so the actual check on which renaming
1491 -- is valid is better left to the code generator as a last sanity
1494 if Comes_From_Source
(N
) then
1495 if Nkind
(Nam
) in N_Function_Call | N_Explicit_Dereference
then
1496 Is_Object_Ref
:= Is_Object_Reference
(Nam
);
1498 Is_Object_Ref
:= Is_Object_Reference
(Original_Node
(Nam
));
1501 Is_Object_Ref
:= True;
1504 if T
= Any_Type
or else Etype
(Nam
) = Any_Type
then
1507 -- Verify that the renamed entity is an object or function call
1509 elsif Is_Object_Ref
then
1510 if Comes_From_Source
(N
) then
1511 if Is_Dependent_Component_Of_Mutable_Object
(Nam
) then
1513 ("illegal renaming of discriminant-dependent component", Nam
);
1516 -- If the renaming comes from source and the renamed object is a
1517 -- dereference, then mark the prefix as needing debug information,
1518 -- since it might have been rewritten hence internally generated
1519 -- and Debug_Renaming_Declaration will link the renaming to it.
1521 if Nkind
(Nam
) = N_Explicit_Dereference
1522 and then Is_Entity_Name
(Prefix
(Nam
))
1524 Set_Debug_Info_Needed
(Entity
(Prefix
(Nam
)));
1528 -- Weird but legal, equivalent to renaming a function call. Illegal
1529 -- if the literal is the result of constant-folding an attribute
1530 -- reference that is not a function.
1532 elsif Is_Entity_Name
(Nam
)
1533 and then Ekind
(Entity
(Nam
)) = E_Enumeration_Literal
1534 and then Nkind
(Original_Node
(Nam
)) /= N_Attribute_Reference
1538 -- A named number can only be renamed without a subtype mark
1540 elsif Nkind
(Nam
) in N_Real_Literal | N_Integer_Literal
1541 and then Present
(Subtype_Mark
(N
))
1542 and then Present
(Original_Entity
(Nam
))
1544 Error_Msg_N
("incompatible types in renaming", Nam
);
1546 -- AI12-0383: Names that denote values can be renamed.
1547 -- Ignore (accept) N_Raise_xxx_Error nodes in this context.
1549 elsif No_Raise_xxx_Error
(Nam
) = OK
then
1550 Error_Msg_Ada_2022_Feature
("value in renaming", Sloc
(Nam
));
1555 if not Is_Variable
(Nam
) then
1556 Mutate_Ekind
(Id
, E_Constant
);
1557 Set_Never_Set_In_Source
(Id
, True);
1558 Set_Is_True_Constant
(Id
, True);
1561 -- The entity of the renaming declaration needs to reflect whether the
1562 -- renamed object is atomic, independent, volatile or VFA. These flags
1563 -- are set on the renamed object in the RM legality sense.
1565 Set_Is_Atomic
(Id
, Is_Atomic_Object
(Nam
));
1566 Set_Is_Independent
(Id
, Is_Independent_Object
(Nam
));
1567 Set_Is_Volatile
(Id
, Is_Volatile_Object_Ref
(Nam
));
1568 Set_Is_Volatile_Full_Access
1569 (Id
, Is_Volatile_Full_Access_Object_Ref
(Nam
));
1571 -- Treat as volatile if we just set the Volatile flag
1575 -- Or if we are renaming an entity which was marked this way
1577 -- Are there more cases, e.g. X(J) where X is Treat_As_Volatile ???
1579 or else (Is_Entity_Name
(Nam
)
1580 and then Treat_As_Volatile
(Entity
(Nam
)))
1582 Set_Treat_As_Volatile
(Id
, True);
1585 -- Now make the link to the renamed object
1587 Set_Renamed_Object
(Id
, Nam
);
1589 -- Implementation-defined aspect specifications can appear in a renaming
1590 -- declaration, but not language-defined ones. The call to procedure
1591 -- Analyze_Aspect_Specifications will take care of this error check.
1593 Analyze_Aspect_Specifications
(N
, Id
);
1595 -- Deal with dimensions
1597 Analyze_Dimension
(N
);
1598 end Analyze_Object_Renaming
;
1600 ------------------------------
1601 -- Analyze_Package_Renaming --
1602 ------------------------------
1604 procedure Analyze_Package_Renaming
(N
: Node_Id
) is
1605 New_P
: constant Entity_Id
:= Defining_Entity
(N
);
1610 if Name
(N
) = Error
then
1614 -- Check for Text_IO special units (we may be renaming a Text_IO child),
1615 -- but make sure not to catch renamings generated for package instances
1616 -- that have nothing to do with them but are nevertheless homonyms.
1618 if Is_Entity_Name
(Name
(N
))
1619 and then Present
(Entity
(Name
(N
)))
1620 and then Is_Generic_Instance
(Entity
(Name
(N
)))
1624 Check_Text_IO_Special_Unit
(Name
(N
));
1627 if Current_Scope
/= Standard_Standard
then
1628 Set_Is_Pure
(New_P
, Is_Pure
(Current_Scope
));
1634 if Is_Entity_Name
(Name
(N
)) then
1635 Old_P
:= Entity
(Name
(N
));
1640 if Etype
(Old_P
) = Any_Type
then
1641 Error_Msg_N
("expect package name in renaming", Name
(N
));
1643 elsif Ekind
(Old_P
) /= E_Package
1644 and then not (Ekind
(Old_P
) = E_Generic_Package
1645 and then In_Open_Scopes
(Old_P
))
1647 if Ekind
(Old_P
) = E_Generic_Package
then
1649 ("generic package cannot be renamed as a package", Name
(N
));
1651 Error_Msg_Sloc
:= Sloc
(Old_P
);
1653 ("expect package name in renaming, found& declared#",
1657 -- Set basic attributes to minimize cascaded errors
1659 Mutate_Ekind
(New_P
, E_Package
);
1660 Set_Etype
(New_P
, Standard_Void_Type
);
1662 elsif Present
(Renamed_Entity
(Old_P
))
1663 and then (From_Limited_With
(Renamed_Entity
(Old_P
))
1664 or else Has_Limited_View
(Renamed_Entity
(Old_P
)))
1666 Unit_Is_Visible
(Cunit
(Get_Source_Unit
(Renamed_Entity
(Old_P
))))
1669 ("renaming of limited view of package & not usable in this context"
1670 & " (RM 8.5.3(3.1/2))", Name
(N
), Renamed_Entity
(Old_P
));
1672 -- Set basic attributes to minimize cascaded errors
1674 Mutate_Ekind
(New_P
, E_Package
);
1675 Set_Etype
(New_P
, Standard_Void_Type
);
1677 -- Here for OK package renaming
1680 -- Entities in the old package are accessible through the renaming
1681 -- entity. The simplest implementation is to have both packages share
1684 Mutate_Ekind
(New_P
, E_Package
);
1685 Set_Etype
(New_P
, Standard_Void_Type
);
1687 if Present
(Renamed_Entity
(Old_P
)) then
1688 Set_Renamed_Entity
(New_P
, Renamed_Entity
(Old_P
));
1690 Set_Renamed_Entity
(New_P
, Old_P
);
1693 -- The package renaming declaration may become Ghost if it renames a
1696 Mark_Ghost_Renaming
(N
, Old_P
);
1698 Set_Has_Completion
(New_P
);
1699 Set_First_Entity
(New_P
, First_Entity
(Old_P
));
1700 Set_Last_Entity
(New_P
, Last_Entity
(Old_P
));
1701 Set_First_Private_Entity
(New_P
, First_Private_Entity
(Old_P
));
1702 Check_Library_Unit_Renaming
(N
, Old_P
);
1703 Generate_Reference
(Old_P
, Name
(N
));
1705 -- If the renaming is in the visible part of a package, then we set
1706 -- Renamed_In_Spec for the renamed package, to prevent giving
1707 -- warnings about no entities referenced. Such a warning would be
1708 -- overenthusiastic, since clients can see entities in the renamed
1709 -- package via the visible package renaming.
1712 Ent
: constant Entity_Id
:= Cunit_Entity
(Current_Sem_Unit
);
1714 if Ekind
(Ent
) = E_Package
1715 and then not In_Private_Part
(Ent
)
1716 and then In_Extended_Main_Source_Unit
(N
)
1717 and then Ekind
(Old_P
) = E_Package
1719 Set_Renamed_In_Spec
(Old_P
);
1723 -- If this is the renaming declaration of a package instantiation
1724 -- within itself, it is the declaration that ends the list of actuals
1725 -- for the instantiation. At this point, the subtypes that rename
1726 -- the actuals are flagged as generic, to avoid spurious ambiguities
1727 -- if the actuals for two distinct formals happen to coincide. If
1728 -- the actual is a private type, the subtype has a private completion
1729 -- that is flagged in the same fashion.
1731 -- Resolution is identical to what is was in the original generic.
1732 -- On exit from the generic instance, these are turned into regular
1733 -- subtypes again, so they are compatible with types in their class.
1735 if not Is_Generic_Instance
(Old_P
) then
1738 Spec
:= Specification
(Unit_Declaration_Node
(Old_P
));
1741 if Nkind
(Spec
) = N_Package_Specification
1742 and then Present
(Generic_Parent
(Spec
))
1743 and then Old_P
= Current_Scope
1744 and then Chars
(New_P
) = Chars
(Generic_Parent
(Spec
))
1750 E
:= First_Entity
(Old_P
);
1751 while Present
(E
) and then E
/= New_P
loop
1753 and then Nkind
(Parent
(E
)) = N_Subtype_Declaration
1755 Set_Is_Generic_Actual_Type
(E
);
1757 if Is_Private_Type
(E
)
1758 and then Present
(Full_View
(E
))
1760 Set_Is_Generic_Actual_Type
(Full_View
(E
));
1770 -- Implementation-defined aspect specifications can appear in a renaming
1771 -- declaration, but not language-defined ones. The call to procedure
1772 -- Analyze_Aspect_Specifications will take care of this error check.
1774 Analyze_Aspect_Specifications
(N
, New_P
);
1775 end Analyze_Package_Renaming
;
1777 -------------------------------
1778 -- Analyze_Renamed_Character --
1779 -------------------------------
1781 procedure Analyze_Renamed_Character
1786 C
: constant Node_Id
:= Name
(N
);
1789 if Ekind
(New_S
) = E_Function
then
1790 Resolve
(C
, Etype
(New_S
));
1793 Check_Frozen_Renaming
(N
, New_S
);
1797 Error_Msg_N
("character literal can only be renamed as function", N
);
1799 end Analyze_Renamed_Character
;
1801 ---------------------------------
1802 -- Analyze_Renamed_Dereference --
1803 ---------------------------------
1805 procedure Analyze_Renamed_Dereference
1810 Nam
: constant Node_Id
:= Name
(N
);
1811 P
: constant Node_Id
:= Prefix
(Nam
);
1817 if not Is_Overloaded
(P
) then
1818 if Ekind
(Etype
(Nam
)) /= E_Subprogram_Type
1819 or else not Type_Conformant
(Etype
(Nam
), New_S
)
1821 Error_Msg_N
("designated type does not match specification", P
);
1830 Get_First_Interp
(Nam
, Ind
, It
);
1832 while Present
(It
.Nam
) loop
1834 if Ekind
(It
.Nam
) = E_Subprogram_Type
1835 and then Type_Conformant
(It
.Nam
, New_S
)
1837 if Typ
/= Any_Id
then
1838 Error_Msg_N
("ambiguous renaming", P
);
1845 Get_Next_Interp
(Ind
, It
);
1848 if Typ
= Any_Type
then
1849 Error_Msg_N
("designated type does not match specification", P
);
1854 Check_Frozen_Renaming
(N
, New_S
);
1858 end Analyze_Renamed_Dereference
;
1860 ---------------------------
1861 -- Analyze_Renamed_Entry --
1862 ---------------------------
1864 procedure Analyze_Renamed_Entry
1869 Nam
: constant Node_Id
:= Name
(N
);
1870 Sel
: constant Node_Id
:= Selector_Name
(Nam
);
1871 Is_Actual
: constant Boolean := Present
(Corresponding_Formal_Spec
(N
));
1875 if Entity
(Sel
) = Any_Id
then
1877 -- Selector is undefined on prefix. Error emitted already
1879 Set_Has_Completion
(New_S
);
1883 -- Otherwise find renamed entity and build body of New_S as a call to it
1885 Old_S
:= Find_Renamed_Entity
(N
, Selector_Name
(Nam
), New_S
);
1887 if Old_S
= Any_Id
then
1888 Error_Msg_N
("no subprogram or entry matches specification", N
);
1891 Check_Subtype_Conformant
(New_S
, Old_S
, N
);
1892 Generate_Reference
(New_S
, Defining_Entity
(N
), 'b');
1893 Style
.Check_Identifier
(Defining_Entity
(N
), New_S
);
1896 -- Only mode conformance required for a renaming_as_declaration
1898 Check_Mode_Conformant
(New_S
, Old_S
, N
);
1901 Inherit_Renamed_Profile
(New_S
, Old_S
);
1903 -- The prefix can be an arbitrary expression that yields a task or
1904 -- protected object, so it must be resolved.
1906 if Is_Access_Type
(Etype
(Prefix
(Nam
))) then
1907 Insert_Explicit_Dereference
(Prefix
(Nam
));
1909 Resolve
(Prefix
(Nam
), Scope
(Old_S
));
1912 Set_Convention
(New_S
, Convention
(Old_S
));
1913 Set_Has_Completion
(New_S
, Inside_A_Generic
);
1915 -- AI05-0225: If the renamed entity is a procedure or entry of a
1916 -- protected object, the target object must be a variable.
1918 if Is_Protected_Type
(Scope
(Old_S
))
1919 and then Ekind
(New_S
) = E_Procedure
1920 and then not Is_Variable
(Prefix
(Nam
))
1924 ("target object of protected operation used as actual for "
1925 & "formal procedure must be a variable", Nam
);
1928 ("target object of protected operation renamed as procedure, "
1929 & "must be a variable", Nam
);
1934 Check_Frozen_Renaming
(N
, New_S
);
1936 end Analyze_Renamed_Entry
;
1938 -----------------------------------
1939 -- Analyze_Renamed_Family_Member --
1940 -----------------------------------
1942 procedure Analyze_Renamed_Family_Member
1947 Nam
: constant Node_Id
:= Name
(N
);
1948 P
: constant Node_Id
:= Prefix
(Nam
);
1952 if (Is_Entity_Name
(P
) and then Ekind
(Entity
(P
)) = E_Entry_Family
)
1953 or else (Nkind
(P
) = N_Selected_Component
1954 and then Ekind
(Entity
(Selector_Name
(P
))) = E_Entry_Family
)
1956 if Is_Entity_Name
(P
) then
1957 Old_S
:= Entity
(P
);
1959 Old_S
:= Entity
(Selector_Name
(P
));
1962 if not Entity_Matches_Spec
(Old_S
, New_S
) then
1963 Error_Msg_N
("entry family does not match specification", N
);
1966 Check_Subtype_Conformant
(New_S
, Old_S
, N
);
1967 Generate_Reference
(New_S
, Defining_Entity
(N
), 'b');
1968 Style
.Check_Identifier
(Defining_Entity
(N
), New_S
);
1972 Error_Msg_N
("no entry family matches specification", N
);
1975 Set_Has_Completion
(New_S
, Inside_A_Generic
);
1978 Check_Frozen_Renaming
(N
, New_S
);
1980 end Analyze_Renamed_Family_Member
;
1982 -----------------------------------------
1983 -- Analyze_Renamed_Primitive_Operation --
1984 -----------------------------------------
1986 procedure Analyze_Renamed_Primitive_Operation
1996 Ctyp
: Conformance_Type
) return Boolean;
1997 -- Verify that the signatures of the renamed entity and the new entity
1998 -- match. The first formal of the renamed entity is skipped because it
1999 -- is the target object in any subsequent call.
2007 Ctyp
: Conformance_Type
) return Boolean
2013 if Ekind
(Subp
) /= Ekind
(New_S
) then
2017 Old_F
:= Next_Formal
(First_Formal
(Subp
));
2018 New_F
:= First_Formal
(New_S
);
2019 while Present
(Old_F
) and then Present
(New_F
) loop
2020 if not Conforming_Types
(Etype
(Old_F
), Etype
(New_F
), Ctyp
) then
2024 if Ctyp
>= Mode_Conformant
2025 and then Ekind
(Old_F
) /= Ekind
(New_F
)
2030 Next_Formal
(New_F
);
2031 Next_Formal
(Old_F
);
2037 -- Start of processing for Analyze_Renamed_Primitive_Operation
2040 if not Is_Overloaded
(Selector_Name
(Name
(N
))) then
2041 Old_S
:= Entity
(Selector_Name
(Name
(N
)));
2043 if not Conforms
(Old_S
, Type_Conformant
) then
2048 -- Find the operation that matches the given signature
2056 Get_First_Interp
(Selector_Name
(Name
(N
)), Ind
, It
);
2058 while Present
(It
.Nam
) loop
2059 if Conforms
(It
.Nam
, Type_Conformant
) then
2063 Get_Next_Interp
(Ind
, It
);
2068 if Old_S
= Any_Id
then
2069 Error_Msg_N
("no subprogram or entry matches specification", N
);
2073 if not Conforms
(Old_S
, Subtype_Conformant
) then
2074 Error_Msg_N
("subtype conformance error in renaming", N
);
2077 Generate_Reference
(New_S
, Defining_Entity
(N
), 'b');
2078 Style
.Check_Identifier
(Defining_Entity
(N
), New_S
);
2081 -- Only mode conformance required for a renaming_as_declaration
2083 if not Conforms
(Old_S
, Mode_Conformant
) then
2084 Error_Msg_N
("mode conformance error in renaming", N
);
2087 -- AI12-0204: The prefix of a prefixed view that is renamed or
2088 -- passed as a formal subprogram must be renamable as an object.
2090 Nam
:= Prefix
(Name
(N
));
2092 if Is_Object_Reference
(Nam
) then
2093 if Is_Dependent_Component_Of_Mutable_Object
(Nam
) then
2095 ("illegal renaming of discriminant-dependent component",
2099 Error_Msg_N
("expect object name in renaming", Nam
);
2102 -- Enforce the rule given in (RM 6.3.1 (10.1/2)): a prefixed
2103 -- view of a subprogram is intrinsic, because the compiler has
2104 -- to generate a wrapper for any call to it. If the name in a
2105 -- subprogram renaming is a prefixed view, the entity is thus
2106 -- intrinsic, and 'Access cannot be applied to it.
2108 Set_Convention
(New_S
, Convention_Intrinsic
);
2111 -- Inherit_Renamed_Profile (New_S, Old_S);
2113 -- The prefix can be an arbitrary expression that yields an
2114 -- object, so it must be resolved.
2116 Resolve
(Prefix
(Name
(N
)));
2118 end Analyze_Renamed_Primitive_Operation
;
2120 ---------------------------------
2121 -- Analyze_Subprogram_Renaming --
2122 ---------------------------------
2124 procedure Analyze_Subprogram_Renaming
(N
: Node_Id
) is
2125 Formal_Spec
: constant Entity_Id
:= Corresponding_Formal_Spec
(N
);
2126 Is_Actual
: constant Boolean := Present
(Formal_Spec
);
2127 Nam
: constant Node_Id
:= Name
(N
);
2128 Save_AV
: constant Ada_Version_Type
:= Ada_Version
;
2129 Save_AVP
: constant Node_Id
:= Ada_Version_Pragma
;
2130 Save_AV_Exp
: constant Ada_Version_Type
:= Ada_Version_Explicit
;
2131 Spec
: constant Node_Id
:= Specification
(N
);
2133 Old_S
: Entity_Id
:= Empty
;
2134 Rename_Spec
: Entity_Id
;
2136 procedure Check_Null_Exclusion
2139 -- Ada 2005 (AI-423): Given renaming Ren of subprogram Sub, check the
2140 -- following AI rules:
2142 -- If Ren denotes a generic formal object of a generic unit G, and the
2143 -- renaming (or instantiation containing the actual) occurs within the
2144 -- body of G or within the body of a generic unit declared within the
2145 -- declarative region of G, then the corresponding parameter of G
2146 -- shall have a null_exclusion; Otherwise the subtype of the Sub's
2147 -- formal parameter shall exclude null.
2149 -- Similarly for its return profile.
2151 procedure Check_SPARK_Primitive_Operation
(Subp_Id
: Entity_Id
);
2152 -- Ensure that a SPARK renaming denoted by its entity Subp_Id does not
2153 -- declare a primitive operation of a tagged type (SPARK RM 6.1.1(3)).
2155 procedure Freeze_Actual_Profile
;
2156 -- In Ada 2012, enforce the freezing rule concerning formal incomplete
2157 -- types: a callable entity freezes its profile, unless it has an
2158 -- incomplete untagged formal (RM 13.14(10.2/3)).
2160 function Has_Class_Wide_Actual
return Boolean;
2161 -- Ada 2012 (AI05-071, AI05-0131) and Ada 2022 (AI12-0165): True if N is
2162 -- the renaming for a defaulted formal subprogram where the actual for
2163 -- the controlling formal type is class-wide.
2165 procedure Handle_Instance_With_Class_Wide_Type
2166 (Inst_Node
: Node_Id
;
2168 Wrapped_Prim
: out Entity_Id
;
2169 Wrap_Id
: out Entity_Id
);
2170 -- Ada 2012 (AI05-0071), Ada 2022 (AI12-0165): when the actual type
2171 -- of an instantiation is a class-wide type T'Class we may need to
2172 -- wrap a primitive operation of T; this routine looks for a suitable
2173 -- primitive to be wrapped and (if the wrapper is required) returns the
2174 -- Id of the wrapped primitive and the Id of the built wrapper. Ren_Id
2175 -- is the defining entity for the renamed subprogram specification.
2177 function Original_Subprogram
(Subp
: Entity_Id
) return Entity_Id
;
2178 -- Find renamed entity when the declaration is a renaming_as_body and
2179 -- the renamed entity may itself be a renaming_as_body. Used to enforce
2180 -- rule that a renaming_as_body is illegal if the declaration occurs
2181 -- before the subprogram it completes is frozen, and renaming indirectly
2182 -- renames the subprogram itself.(Defect Report 8652/0027).
2184 --------------------------
2185 -- Check_Null_Exclusion --
2186 --------------------------
2188 procedure Check_Null_Exclusion
2192 Ren_Formal
: Entity_Id
;
2193 Sub_Formal
: Entity_Id
;
2195 function Null_Exclusion_Mismatch
2196 (Renaming
: Entity_Id
; Renamed
: Entity_Id
) return Boolean;
2197 -- Return True if there is a null exclusion mismatch between
2198 -- Renaming and Renamed, False otherwise.
2200 -----------------------------
2201 -- Null_Exclusion_Mismatch --
2202 -----------------------------
2204 function Null_Exclusion_Mismatch
2205 (Renaming
: Entity_Id
; Renamed
: Entity_Id
) return Boolean is
2207 return Has_Null_Exclusion
(Parent
(Renaming
))
2209 not (Has_Null_Exclusion
(Parent
(Renamed
))
2210 or else (Can_Never_Be_Null
(Etype
(Renamed
))
2212 (Is_Formal_Subprogram
(Sub
)
2213 and then In_Generic_Body
(Current_Scope
))));
2214 end Null_Exclusion_Mismatch
;
2219 Ren_Formal
:= First_Formal
(Ren
);
2220 Sub_Formal
:= First_Formal
(Sub
);
2221 while Present
(Ren_Formal
) and then Present
(Sub_Formal
) loop
2222 if Null_Exclusion_Mismatch
(Ren_Formal
, Sub_Formal
) then
2223 Error_Msg_Sloc
:= Sloc
(Sub_Formal
);
2225 ("`NOT NULL` required for parameter &#",
2226 Ren_Formal
, Sub_Formal
);
2229 Next_Formal
(Ren_Formal
);
2230 Next_Formal
(Sub_Formal
);
2233 -- Return profile check
2235 if Nkind
(Parent
(Ren
)) = N_Function_Specification
2236 and then Nkind
(Parent
(Sub
)) = N_Function_Specification
2237 and then Null_Exclusion_Mismatch
(Ren
, Sub
)
2239 Error_Msg_Sloc
:= Sloc
(Sub
);
2240 Error_Msg_N
("return must specify `NOT NULL`#", Ren
);
2242 end Check_Null_Exclusion
;
2244 -------------------------------------
2245 -- Check_SPARK_Primitive_Operation --
2246 -------------------------------------
2248 procedure Check_SPARK_Primitive_Operation
(Subp_Id
: Entity_Id
) is
2249 Prag
: constant Node_Id
:= SPARK_Pragma
(Subp_Id
);
2253 -- Nothing to do when the subprogram is not subject to SPARK_Mode On
2254 -- because this check applies to SPARK code only.
2256 if not (Present
(Prag
)
2257 and then Get_SPARK_Mode_From_Annotation
(Prag
) = On
)
2261 -- Nothing to do when the subprogram is not a primitive operation
2263 elsif not Is_Primitive
(Subp_Id
) then
2267 Typ
:= Find_Dispatching_Type
(Subp_Id
);
2269 -- Nothing to do when the subprogram is a primitive operation of an
2276 -- At this point a renaming declaration introduces a new primitive
2277 -- operation for a tagged type.
2279 Error_Msg_Node_2
:= Typ
;
2281 ("subprogram renaming & cannot declare primitive for type & "
2282 & "(SPARK RM 6.1.1(3))", N
, Subp_Id
);
2283 end Check_SPARK_Primitive_Operation
;
2285 ---------------------------
2286 -- Freeze_Actual_Profile --
2287 ---------------------------
2289 procedure Freeze_Actual_Profile
is
2291 Has_Untagged_Inc
: Boolean;
2292 Instantiation_Node
: constant Node_Id
:= Parent
(N
);
2295 if Ada_Version
>= Ada_2012
then
2296 F
:= First_Formal
(Formal_Spec
);
2297 Has_Untagged_Inc
:= False;
2298 while Present
(F
) loop
2299 if Ekind
(Etype
(F
)) = E_Incomplete_Type
2300 and then not Is_Tagged_Type
(Etype
(F
))
2302 Has_Untagged_Inc
:= True;
2309 if Ekind
(Formal_Spec
) = E_Function
2310 and then not Is_Tagged_Type
(Etype
(Formal_Spec
))
2312 Has_Untagged_Inc
:= True;
2315 if not Has_Untagged_Inc
then
2316 F
:= First_Formal
(Old_S
);
2317 while Present
(F
) loop
2318 Freeze_Before
(Instantiation_Node
, Etype
(F
));
2320 if Is_Incomplete_Or_Private_Type
(Etype
(F
))
2321 and then No
(Underlying_Type
(Etype
(F
)))
2323 -- Exclude generic types, or types derived from them.
2324 -- They will be frozen in the enclosing instance.
2326 if Is_Generic_Type
(Etype
(F
))
2327 or else Is_Generic_Type
(Root_Type
(Etype
(F
)))
2331 -- A limited view of a type declared elsewhere needs no
2332 -- freezing actions.
2334 elsif From_Limited_With
(Etype
(F
)) then
2339 ("type& must be frozen before this point",
2340 Instantiation_Node
, Etype
(F
));
2348 end Freeze_Actual_Profile
;
2350 ---------------------------
2351 -- Has_Class_Wide_Actual --
2352 ---------------------------
2354 function Has_Class_Wide_Actual
return Boolean is
2356 Formal_Typ
: Entity_Id
;
2360 Formal
:= First_Formal
(Formal_Spec
);
2361 while Present
(Formal
) loop
2362 Formal_Typ
:= Etype
(Formal
);
2364 if Has_Unknown_Discriminants
(Formal_Typ
)
2365 and then not Is_Class_Wide_Type
(Formal_Typ
)
2366 and then Is_Class_Wide_Type
(Get_Instance_Of
(Formal_Typ
))
2371 Next_Formal
(Formal
);
2376 end Has_Class_Wide_Actual
;
2378 ------------------------------------------
2379 -- Handle_Instance_With_Class_Wide_Type --
2380 ------------------------------------------
2382 procedure Handle_Instance_With_Class_Wide_Type
2383 (Inst_Node
: Node_Id
;
2385 Wrapped_Prim
: out Entity_Id
;
2386 Wrap_Id
: out Entity_Id
)
2388 procedure Build_Class_Wide_Wrapper
2389 (Ren_Id
: Entity_Id
;
2390 Prim_Op
: Entity_Id
;
2391 Wrap_Id
: out Entity_Id
);
2392 -- Build a wrapper for the renaming Ren_Id of subprogram Prim_Op.
2394 procedure Find_Suitable_Candidate
2395 (Prim_Op
: out Entity_Id
;
2396 Is_CW_Prim
: out Boolean);
2397 -- Look for a suitable primitive to be wrapped (Prim_Op); Is_CW_Prim
2398 -- indicates that the found candidate is a class-wide primitive (to
2399 -- help the caller decide if the wrapper is required).
2401 ------------------------------
2402 -- Build_Class_Wide_Wrapper --
2403 ------------------------------
2405 procedure Build_Class_Wide_Wrapper
2406 (Ren_Id
: Entity_Id
;
2407 Prim_Op
: Entity_Id
;
2408 Wrap_Id
: out Entity_Id
)
2410 Loc
: constant Source_Ptr
:= Sloc
(N
);
2413 (Subp_Id
: Entity_Id
;
2414 Params
: List_Id
) return Node_Id
;
2415 -- Create a dispatching call to invoke routine Subp_Id with
2416 -- actuals built from the parameter specifications of list Params.
2418 function Build_Expr_Fun_Call
2419 (Subp_Id
: Entity_Id
;
2420 Params
: List_Id
) return Node_Id
;
2421 -- Create a dispatching call to invoke function Subp_Id with
2422 -- actuals built from the parameter specifications of list Params.
2423 -- Directly return the call, so that it can be used inside an
2424 -- expression function. This is a requirement of GNATprove mode.
2426 function Build_Spec
(Subp_Id
: Entity_Id
) return Node_Id
;
2427 -- Create a subprogram specification based on the subprogram
2428 -- profile of Subp_Id.
2435 (Subp_Id
: Entity_Id
;
2436 Params
: List_Id
) return Node_Id
2438 Actuals
: constant List_Id
:= New_List
;
2439 Call_Ref
: constant Node_Id
:= New_Occurrence_Of
(Subp_Id
, Loc
);
2443 -- Build the actual parameters of the call
2445 Formal
:= First
(Params
);
2446 while Present
(Formal
) loop
2448 Make_Identifier
(Loc
,
2449 Chars
(Defining_Identifier
(Formal
))));
2454 -- return Subp_Id (Actuals);
2456 if Ekind
(Subp_Id
) in E_Function | E_Operator
then
2458 Make_Simple_Return_Statement
(Loc
,
2460 Make_Function_Call
(Loc
,
2462 Parameter_Associations
=> Actuals
));
2465 -- Subp_Id (Actuals);
2469 Make_Procedure_Call_Statement
(Loc
,
2471 Parameter_Associations
=> Actuals
);
2475 -------------------------
2476 -- Build_Expr_Fun_Call --
2477 -------------------------
2479 function Build_Expr_Fun_Call
2480 (Subp_Id
: Entity_Id
;
2481 Params
: List_Id
) return Node_Id
2483 Actuals
: constant List_Id
:= New_List
;
2484 Call_Ref
: constant Node_Id
:= New_Occurrence_Of
(Subp_Id
, Loc
);
2488 pragma Assert
(Ekind
(Subp_Id
) in E_Function | E_Operator
);
2490 -- Build the actual parameters of the call
2492 Formal
:= First
(Params
);
2493 while Present
(Formal
) loop
2495 Make_Identifier
(Loc
,
2496 Chars
(Defining_Identifier
(Formal
))));
2501 -- Subp_Id (Actuals);
2504 Make_Function_Call
(Loc
,
2506 Parameter_Associations
=> Actuals
);
2507 end Build_Expr_Fun_Call
;
2513 function Build_Spec
(Subp_Id
: Entity_Id
) return Node_Id
is
2514 Params
: constant List_Id
:= Copy_Parameter_List
(Subp_Id
);
2515 Spec_Id
: constant Entity_Id
:=
2516 Make_Defining_Identifier
(Loc
,
2517 New_External_Name
(Chars
(Subp_Id
), 'R'));
2520 if Ekind
(Formal_Spec
) = E_Procedure
then
2522 Make_Procedure_Specification
(Loc
,
2523 Defining_Unit_Name
=> Spec_Id
,
2524 Parameter_Specifications
=> Params
);
2527 Make_Function_Specification
(Loc
,
2528 Defining_Unit_Name
=> Spec_Id
,
2529 Parameter_Specifications
=> Params
,
2530 Result_Definition
=>
2531 New_Copy_Tree
(Result_Definition
(Spec
)));
2537 Body_Decl
: Node_Id
;
2538 Spec_Decl
: Node_Id
;
2541 -- Start of processing for Build_Class_Wide_Wrapper
2544 pragma Assert
(not Error_Posted
(Nam
));
2546 -- Step 1: Create the declaration and the body of the wrapper,
2547 -- insert all the pieces into the tree.
2549 -- In GNATprove mode, create a function wrapper in the form of an
2550 -- expression function, so that an implicit postcondition relating
2551 -- the result of calling the wrapper function and the result of
2552 -- the dispatching call to the wrapped function is known during
2556 and then Ekind
(Ren_Id
) in E_Function | E_Operator
2558 New_Spec
:= Build_Spec
(Ren_Id
);
2560 Make_Expression_Function
(Loc
,
2561 Specification
=> New_Spec
,
2564 (Subp_Id
=> Prim_Op
,
2565 Params
=> Parameter_Specifications
(New_Spec
)));
2567 Wrap_Id
:= Defining_Entity
(Body_Decl
);
2569 -- Otherwise, create separate spec and body for the subprogram
2573 Make_Subprogram_Declaration
(Loc
,
2574 Specification
=> Build_Spec
(Ren_Id
));
2575 Insert_Before_And_Analyze
(N
, Spec_Decl
);
2577 Wrap_Id
:= Defining_Entity
(Spec_Decl
);
2580 Make_Subprogram_Body
(Loc
,
2581 Specification
=> Build_Spec
(Ren_Id
),
2582 Declarations
=> New_List
,
2583 Handled_Statement_Sequence
=>
2584 Make_Handled_Sequence_Of_Statements
(Loc
,
2585 Statements
=> New_List
(
2587 (Subp_Id
=> Prim_Op
,
2589 Parameter_Specifications
2590 (Specification
(Spec_Decl
))))));
2592 Set_Corresponding_Body
(Spec_Decl
, Defining_Entity
(Body_Decl
));
2595 Set_Is_Class_Wide_Wrapper
(Wrap_Id
);
2597 -- If the operator carries an Eliminated pragma, indicate that
2598 -- the wrapper is also to be eliminated, to prevent spurious
2599 -- errors when using gnatelim on programs that include box-
2600 -- defaulted initialization of equality operators.
2602 Set_Is_Eliminated
(Wrap_Id
, Is_Eliminated
(Prim_Op
));
2604 -- In GNATprove mode, insert the body in the tree for analysis
2606 if GNATprove_Mode
then
2607 Insert_Before_And_Analyze
(N
, Body_Decl
);
2610 -- The generated body does not freeze and must be analyzed when
2611 -- the class-wide wrapper is frozen. The body is only needed if
2612 -- expansion is enabled.
2614 if Expander_Active
then
2615 Append_Freeze_Action
(Wrap_Id
, Body_Decl
);
2618 -- Step 2: The subprogram renaming aliases the wrapper
2620 Rewrite
(Name
(N
), New_Occurrence_Of
(Wrap_Id
, Loc
));
2621 end Build_Class_Wide_Wrapper
;
2623 -----------------------------
2624 -- Find_Suitable_Candidate --
2625 -----------------------------
2627 procedure Find_Suitable_Candidate
2628 (Prim_Op
: out Entity_Id
;
2629 Is_CW_Prim
: out Boolean)
2631 Loc
: constant Source_Ptr
:= Sloc
(N
);
2633 function Find_Primitive
(Typ
: Entity_Id
) return Entity_Id
;
2634 -- Find a primitive subprogram of type Typ which matches the
2635 -- profile of the renaming declaration.
2637 procedure Interpretation_Error
(Subp_Id
: Entity_Id
);
2638 -- Emit a continuation error message suggesting subprogram Subp_Id
2639 -- as a possible interpretation.
2641 function Is_Intrinsic_Equality
2642 (Subp_Id
: Entity_Id
) return Boolean;
2643 -- Determine whether subprogram Subp_Id denotes the intrinsic "="
2646 function Is_Suitable_Candidate
2647 (Subp_Id
: Entity_Id
) return Boolean;
2648 -- Determine whether subprogram Subp_Id is a suitable candidate
2649 -- for the role of a wrapped subprogram.
2651 --------------------
2652 -- Find_Primitive --
2653 --------------------
2655 function Find_Primitive
(Typ
: Entity_Id
) return Entity_Id
is
2656 procedure Replace_Parameter_Types
(Spec
: Node_Id
);
2657 -- Given a specification Spec, replace all class-wide parameter
2658 -- types with reference to type Typ.
2660 -----------------------------
2661 -- Replace_Parameter_Types --
2662 -----------------------------
2664 procedure Replace_Parameter_Types
(Spec
: Node_Id
) is
2666 Formal_Id
: Entity_Id
;
2667 Formal_Typ
: Node_Id
;
2670 Formal
:= First
(Parameter_Specifications
(Spec
));
2671 while Present
(Formal
) loop
2672 Formal_Id
:= Defining_Identifier
(Formal
);
2673 Formal_Typ
:= Parameter_Type
(Formal
);
2675 -- Create a new entity for each class-wide formal to
2676 -- prevent aliasing with the original renaming. Replace
2677 -- the type of such a parameter with the candidate type.
2679 if Nkind
(Formal_Typ
) = N_Identifier
2680 and then Is_Class_Wide_Type
(Etype
(Formal_Typ
))
2682 Set_Defining_Identifier
(Formal
,
2683 Make_Defining_Identifier
(Loc
, Chars
(Formal_Id
)));
2685 Set_Parameter_Type
(Formal
,
2686 New_Occurrence_Of
(Typ
, Loc
));
2691 end Replace_Parameter_Types
;
2695 Alt_Ren
: constant Node_Id
:= New_Copy_Tree
(N
);
2696 Alt_Nam
: constant Node_Id
:= Name
(Alt_Ren
);
2697 Alt_Spec
: constant Node_Id
:= Specification
(Alt_Ren
);
2698 Subp_Id
: Entity_Id
;
2700 -- Start of processing for Find_Primitive
2703 -- Each attempt to find a suitable primitive of a particular
2704 -- type operates on its own copy of the original renaming.
2705 -- As a result the original renaming is kept decoration and
2706 -- side-effect free.
2708 -- Inherit the overloaded status of the renamed subprogram name
2710 if Is_Overloaded
(Nam
) then
2711 Set_Is_Overloaded
(Alt_Nam
);
2712 Save_Interps
(Nam
, Alt_Nam
);
2715 -- The copied renaming is hidden from visibility to prevent the
2716 -- pollution of the enclosing context.
2718 Set_Defining_Unit_Name
(Alt_Spec
, Make_Temporary
(Loc
, 'R'));
2720 -- The types of all class-wide parameters must be changed to
2721 -- the candidate type.
2723 Replace_Parameter_Types
(Alt_Spec
);
2725 -- Try to find a suitable primitive that matches the altered
2726 -- profile of the renaming specification.
2731 Nam
=> Name
(Alt_Ren
),
2732 New_S
=> Analyze_Subprogram_Specification
(Alt_Spec
),
2733 Is_Actual
=> Is_Actual
);
2735 -- Do not return Any_Id if the resolution of the altered
2736 -- profile failed as this complicates further checks on
2737 -- the caller side; return Empty instead.
2739 if Subp_Id
= Any_Id
then
2746 --------------------------
2747 -- Interpretation_Error --
2748 --------------------------
2750 procedure Interpretation_Error
(Subp_Id
: Entity_Id
) is
2752 Error_Msg_Sloc
:= Sloc
(Subp_Id
);
2754 if Is_Internal
(Subp_Id
) then
2756 ("\\possible interpretation: predefined & #",
2760 ("\\possible interpretation: & defined #",
2763 end Interpretation_Error
;
2765 ---------------------------
2766 -- Is_Intrinsic_Equality --
2767 ---------------------------
2769 function Is_Intrinsic_Equality
(Subp_Id
: Entity_Id
) return Boolean
2773 Ekind
(Subp_Id
) = E_Operator
2774 and then Chars
(Subp_Id
) = Name_Op_Eq
2775 and then Is_Intrinsic_Subprogram
(Subp_Id
);
2776 end Is_Intrinsic_Equality
;
2778 ---------------------------
2779 -- Is_Suitable_Candidate --
2780 ---------------------------
2782 function Is_Suitable_Candidate
(Subp_Id
: Entity_Id
) return Boolean
2785 if No
(Subp_Id
) then
2788 -- An intrinsic subprogram is never a good candidate. This
2789 -- is an indication of a missing primitive, either defined
2790 -- directly or inherited from a parent tagged type.
2792 elsif Is_Intrinsic_Subprogram
(Subp_Id
) then
2798 end Is_Suitable_Candidate
;
2802 Actual_Typ
: Entity_Id
:= Empty
;
2803 -- The actual class-wide type for Formal_Typ
2805 CW_Prim_OK
: Boolean;
2806 CW_Prim_Op
: Entity_Id
;
2807 -- The class-wide subprogram (if available) that corresponds to
2808 -- the renamed generic formal subprogram.
2810 Formal_Typ
: Entity_Id
:= Empty
;
2811 -- The generic formal type with unknown discriminants
2813 Root_Prim_OK
: Boolean;
2814 Root_Prim_Op
: Entity_Id
;
2815 -- The root type primitive (if available) that corresponds to the
2816 -- renamed generic formal subprogram.
2818 Root_Typ
: Entity_Id
:= Empty
;
2819 -- The root type of Actual_Typ
2823 -- Start of processing for Find_Suitable_Candidate
2826 pragma Assert
(not Error_Posted
(Nam
));
2829 Is_CW_Prim
:= False;
2831 -- Analyze the renamed name, but do not resolve it. The resolution
2832 -- is completed once a suitable subprogram is found.
2836 -- When the renamed name denotes the intrinsic operator equals,
2837 -- the name must be treated as overloaded. This allows for a
2838 -- potential match against the root type's predefined equality
2841 if Is_Intrinsic_Equality
(Entity
(Nam
)) then
2842 Set_Is_Overloaded
(Nam
);
2843 Collect_Interps
(Nam
);
2846 -- Step 1: Find the generic formal type and its corresponding
2847 -- class-wide actual type from the renamed generic formal
2850 Formal
:= First_Formal
(Formal_Spec
);
2851 while Present
(Formal
) loop
2852 if Has_Unknown_Discriminants
(Etype
(Formal
))
2853 and then not Is_Class_Wide_Type
(Etype
(Formal
))
2854 and then Is_Class_Wide_Type
(Get_Instance_Of
(Etype
(Formal
)))
2856 Formal_Typ
:= Etype
(Formal
);
2857 Actual_Typ
:= Base_Type
(Get_Instance_Of
(Formal_Typ
));
2858 Root_Typ
:= Root_Type
(Actual_Typ
);
2862 Next_Formal
(Formal
);
2865 -- The specification of the generic formal subprogram should
2866 -- always contain a formal type with unknown discriminants whose
2867 -- actual is a class-wide type; otherwise this indicates a failure
2868 -- in function Has_Class_Wide_Actual.
2870 pragma Assert
(Present
(Formal_Typ
));
2872 -- Step 2: Find the proper class-wide subprogram or primitive
2873 -- that corresponds to the renamed generic formal subprogram.
2875 CW_Prim_Op
:= Find_Primitive
(Actual_Typ
);
2876 CW_Prim_OK
:= Is_Suitable_Candidate
(CW_Prim_Op
);
2877 Root_Prim_Op
:= Find_Primitive
(Root_Typ
);
2878 Root_Prim_OK
:= Is_Suitable_Candidate
(Root_Prim_Op
);
2880 -- The class-wide actual type has two subprograms that correspond
2881 -- to the renamed generic formal subprogram:
2883 -- with procedure Prim_Op (Param : Formal_Typ);
2885 -- procedure Prim_Op (Param : Actual_Typ); -- may be inherited
2886 -- procedure Prim_Op (Param : Actual_Typ'Class);
2888 -- Even though the declaration of the two subprograms is legal, a
2889 -- call to either one is ambiguous and therefore illegal.
2891 if CW_Prim_OK
and Root_Prim_OK
then
2893 -- A user-defined primitive has precedence over a predefined
2896 if Is_Internal
(CW_Prim_Op
)
2897 and then not Is_Internal
(Root_Prim_Op
)
2899 Prim_Op
:= Root_Prim_Op
;
2901 elsif Is_Internal
(Root_Prim_Op
)
2902 and then not Is_Internal
(CW_Prim_Op
)
2904 Prim_Op
:= CW_Prim_Op
;
2907 elsif CW_Prim_Op
= Root_Prim_Op
then
2908 Prim_Op
:= Root_Prim_Op
;
2910 -- The two subprograms are legal but the class-wide subprogram
2911 -- is a class-wide wrapper built for a previous instantiation;
2912 -- the wrapper has precedence.
2914 elsif Present
(Alias
(CW_Prim_Op
))
2915 and then Is_Class_Wide_Wrapper
(Ultimate_Alias
(CW_Prim_Op
))
2917 Prim_Op
:= CW_Prim_Op
;
2920 -- Otherwise both candidate subprograms are user-defined and
2925 ("ambiguous actual for generic subprogram &",
2927 Interpretation_Error
(Root_Prim_Op
);
2928 Interpretation_Error
(CW_Prim_Op
);
2932 elsif CW_Prim_OK
and not Root_Prim_OK
then
2933 Prim_Op
:= CW_Prim_Op
;
2936 elsif not CW_Prim_OK
and Root_Prim_OK
then
2937 Prim_Op
:= Root_Prim_Op
;
2939 -- An intrinsic equality may act as a suitable candidate in the
2940 -- case of a null type extension where the parent's equality
2941 -- is hidden. A call to an intrinsic equality is expanded as
2944 elsif Present
(Root_Prim_Op
)
2945 and then Is_Intrinsic_Equality
(Root_Prim_Op
)
2947 Prim_Op
:= Root_Prim_Op
;
2949 -- Otherwise there are no candidate subprograms. Let the caller
2950 -- diagnose the error.
2956 -- At this point resolution has taken place and the name is no
2957 -- longer overloaded. Mark the primitive as referenced.
2959 Set_Is_Overloaded
(Name
(N
), False);
2960 Set_Referenced
(Prim_Op
);
2961 end Find_Suitable_Candidate
;
2965 Is_CW_Prim
: Boolean;
2967 -- Start of processing for Handle_Instance_With_Class_Wide_Type
2970 Wrapped_Prim
:= Empty
;
2973 -- Ada 2012 (AI05-0071): A generic/instance scenario involving a
2974 -- formal type with unknown discriminants and a generic primitive
2975 -- operation of the said type with a box require special processing
2976 -- when the actual is a class-wide type:
2979 -- type Formal_Typ (<>) is private;
2980 -- with procedure Prim_Op (Param : Formal_Typ) is <>;
2981 -- package Gen is ...
2983 -- package Inst is new Gen (Actual_Typ'Class);
2985 -- In this case the general renaming mechanism used in the prologue
2986 -- of an instance no longer applies:
2988 -- procedure Prim_Op (Param : Formal_Typ) renames Prim_Op;
2990 -- The above is replaced the following wrapper/renaming combination:
2992 -- procedure Wrapper (Param : Formal_Typ) is -- wrapper
2994 -- Prim_Op (Param); -- primitive
2997 -- procedure Prim_Op (Param : Formal_Typ) renames Wrapper;
2999 -- This transformation applies only if there is no explicit visible
3000 -- class-wide operation at the point of the instantiation. Ren_Id is
3001 -- the entity of the renaming declaration. When the transformation
3002 -- applies, Wrapped_Prim is the entity of the wrapped primitive.
3004 if Box_Present
(Inst_Node
) then
3005 Find_Suitable_Candidate
3006 (Prim_Op
=> Wrapped_Prim
,
3007 Is_CW_Prim
=> Is_CW_Prim
);
3009 if Present
(Wrapped_Prim
) then
3010 if not Is_CW_Prim
then
3011 Build_Class_Wide_Wrapper
(Ren_Id
, Wrapped_Prim
, Wrap_Id
);
3013 -- Small optimization: When the candidate is a class-wide
3014 -- subprogram we don't build the wrapper; we modify the
3015 -- renaming declaration to directly map the actual to the
3016 -- generic formal and discard the candidate.
3019 Rewrite
(Nam
, New_Occurrence_Of
(Wrapped_Prim
, Sloc
(N
)));
3020 Wrapped_Prim
:= Empty
;
3024 -- Ada 2022 (AI12-0165, RM 12.6(8.5/3)): The actual subprogram for a
3025 -- formal_abstract_subprogram_declaration shall be:
3026 -- a) a dispatching operation of the controlling type; or
3027 -- b) if the controlling type is a formal type, and the actual
3028 -- type corresponding to that formal type is a specific type T,
3029 -- a dispatching operation of type T; or
3030 -- c) if the controlling type is a formal type, and the actual
3031 -- type is a class-wide type T'Class, an implicitly declared
3032 -- subprogram corresponding to a primitive operation of type T.
3034 elsif Nkind
(Inst_Node
) = N_Formal_Abstract_Subprogram_Declaration
3035 and then Is_Entity_Name
(Nam
)
3037 Find_Suitable_Candidate
3038 (Prim_Op
=> Wrapped_Prim
,
3039 Is_CW_Prim
=> Is_CW_Prim
);
3041 if Present
(Wrapped_Prim
) then
3043 -- Cases (a) and (b); see previous description.
3045 if not Is_CW_Prim
then
3046 Build_Class_Wide_Wrapper
(Ren_Id
, Wrapped_Prim
, Wrap_Id
);
3048 -- Case (c); see previous description.
3050 -- Implicit operations of T'Class for subtype declarations
3051 -- are built by Derive_Subprogram, and their Alias attribute
3052 -- references the primitive operation of T.
3054 elsif not Comes_From_Source
(Wrapped_Prim
)
3055 and then Nkind
(Parent
(Wrapped_Prim
)) = N_Subtype_Declaration
3056 and then Present
(Alias
(Wrapped_Prim
))
3058 -- We don't need to build the wrapper; we modify the
3059 -- renaming declaration to directly map the actual to
3060 -- the generic formal and discard the candidate.
3063 New_Occurrence_Of
(Alias
(Wrapped_Prim
), Sloc
(N
)));
3064 Wrapped_Prim
:= Empty
;
3066 -- Legality rules do not apply; discard the candidate.
3069 Wrapped_Prim
:= Empty
;
3073 end Handle_Instance_With_Class_Wide_Type
;
3075 -------------------------
3076 -- Original_Subprogram --
3077 -------------------------
3079 function Original_Subprogram
(Subp
: Entity_Id
) return Entity_Id
is
3080 Orig_Decl
: Node_Id
;
3081 Orig_Subp
: Entity_Id
;
3084 -- First case: renamed entity is itself a renaming
3086 if Present
(Alias
(Subp
)) then
3087 return Alias
(Subp
);
3089 elsif Nkind
(Unit_Declaration_Node
(Subp
)) = N_Subprogram_Declaration
3090 and then Present
(Corresponding_Body
(Unit_Declaration_Node
(Subp
)))
3092 -- Check if renamed entity is a renaming_as_body
3095 Unit_Declaration_Node
3096 (Corresponding_Body
(Unit_Declaration_Node
(Subp
)));
3098 if Nkind
(Orig_Decl
) = N_Subprogram_Renaming_Declaration
then
3099 Orig_Subp
:= Entity
(Name
(Orig_Decl
));
3101 if Orig_Subp
= Rename_Spec
then
3103 -- Circularity detected
3108 return (Original_Subprogram
(Orig_Subp
));
3116 end Original_Subprogram
;
3120 CW_Actual
: constant Boolean := Has_Class_Wide_Actual
;
3121 -- Ada 2012 (AI05-071, AI05-0131) and Ada 2022 (AI12-0165): True if the
3122 -- renaming is for a defaulted formal subprogram when the actual for a
3123 -- related formal type is class-wide.
3125 Inst_Node
: Node_Id
:= Empty
;
3126 New_S
: Entity_Id
:= Empty
;
3127 Wrapped_Prim
: Entity_Id
:= Empty
;
3129 -- Start of processing for Analyze_Subprogram_Renaming
3132 -- We must test for the attribute renaming case before the Analyze
3133 -- call because otherwise Sem_Attr will complain that the attribute
3134 -- is missing an argument when it is analyzed.
3136 if Nkind
(Nam
) = N_Attribute_Reference
then
3138 -- In the case of an abstract formal subprogram association, rewrite
3139 -- an actual given by a stream or Put_Image attribute as the name of
3140 -- the corresponding stream or Put_Image primitive of the type.
3142 -- In a generic context the stream and Put_Image operations are not
3143 -- generated, and this must be treated as a normal attribute
3144 -- reference, to be expanded in subsequent instantiations.
3147 and then Is_Abstract_Subprogram
(Formal_Spec
)
3148 and then Expander_Active
3151 Prefix_Type
: constant Entity_Id
:= Entity
(Prefix
(Nam
));
3155 -- The class-wide forms of the stream and Put_Image attributes
3156 -- are not primitive dispatching operations (even though they
3157 -- internally dispatch).
3159 if Is_Class_Wide_Type
(Prefix_Type
) then
3161 ("attribute must be a primitive dispatching operation",
3166 -- Retrieve the primitive subprogram associated with the
3167 -- attribute. This can only be a stream attribute, since those
3168 -- are the only ones that are dispatching (and the actual for
3169 -- an abstract formal subprogram must be dispatching
3172 case Attribute_Name
(Nam
) is
3175 Find_Optional_Prim_Op
(Prefix_Type
, TSS_Stream_Input
);
3179 Find_Optional_Prim_Op
(Prefix_Type
, TSS_Stream_Output
);
3183 Find_Optional_Prim_Op
(Prefix_Type
, TSS_Stream_Read
);
3187 Find_Optional_Prim_Op
(Prefix_Type
, TSS_Stream_Write
);
3189 when Name_Put_Image
=>
3191 Find_Optional_Prim_Op
(Prefix_Type
, TSS_Put_Image
);
3195 ("attribute must be a primitive dispatching operation",
3200 -- If no stream operation was found, and the type is limited,
3201 -- the user should have defined one. This rule does not apply
3205 and then Attribute_Name
(Nam
) /= Name_Put_Image
3207 if Is_Limited_Type
(Prefix_Type
) then
3209 ("stream operation not defined for type&",
3213 -- Otherwise, compiler should have generated default
3216 raise Program_Error
;
3220 -- Rewrite the attribute into the name of its corresponding
3221 -- primitive dispatching subprogram. We can then proceed with
3222 -- the usual processing for subprogram renamings.
3225 Prim_Name
: constant Node_Id
:=
3226 Make_Identifier
(Sloc
(Nam
),
3227 Chars
=> Chars
(Prim
));
3229 Set_Entity
(Prim_Name
, Prim
);
3230 Rewrite
(Nam
, Prim_Name
);
3235 -- Normal processing for a renaming of an attribute
3238 Attribute_Renaming
(N
);
3243 -- Check whether this declaration corresponds to the instantiation of a
3244 -- formal subprogram.
3246 -- If this is an instantiation, the corresponding actual is frozen and
3247 -- error messages can be made more precise. If this is a default
3248 -- subprogram, the entity is already established in the generic, and is
3249 -- not retrieved by visibility. If it is a default with a box, the
3250 -- candidate interpretations, if any, have been collected when building
3251 -- the renaming declaration. If overloaded, the proper interpretation is
3252 -- determined in Find_Renamed_Entity. If the entity is an operator,
3253 -- Find_Renamed_Entity applies additional visibility checks.
3256 Inst_Node
:= Unit_Declaration_Node
(Formal_Spec
);
3258 -- Ada 2012 (AI05-0071) and Ada 2022 (AI12-0165): when the actual
3259 -- type is a class-wide type T'Class we may need to wrap a primitive
3260 -- operation of T. Search for the wrapped primitive and (if required)
3261 -- build a wrapper whose body consists of a dispatching call to the
3262 -- wrapped primitive of T, with its formal parameters as the actual
3265 if CW_Actual
and then
3267 -- Ada 2012 (AI05-0071): Check whether the renaming is for a
3268 -- defaulted actual subprogram with a class-wide actual.
3270 (Box_Present
(Inst_Node
)
3274 -- Ada 2022 (AI12-0165): Check whether the renaming is for a formal
3275 -- abstract subprogram declaration with a class-wide actual.
3277 (Nkind
(Inst_Node
) = N_Formal_Abstract_Subprogram_Declaration
3278 and then Is_Entity_Name
(Nam
)))
3280 New_S
:= Analyze_Subprogram_Specification
(Spec
);
3282 -- Do not attempt to build the wrapper if the renaming is in error
3284 if not Error_Posted
(Nam
) then
3285 Handle_Instance_With_Class_Wide_Type
3286 (Inst_Node
=> Inst_Node
,
3288 Wrapped_Prim
=> Wrapped_Prim
,
3291 -- If several candidates were found, then we reported the
3292 -- ambiguity; stop processing the renaming declaration to
3293 -- avoid reporting further (spurious) errors.
3295 if Error_Posted
(Spec
) then
3302 if Present
(Wrapped_Prim
) then
3304 -- When the wrapper is built, the subprogram renaming aliases
3309 pragma Assert
(Old_S
= Entity
(Nam
)
3310 and then Is_Class_Wide_Wrapper
(Old_S
));
3312 -- The subprogram renaming declaration may become Ghost if it
3313 -- renames a wrapper of a Ghost entity.
3315 Mark_Ghost_Renaming
(N
, Wrapped_Prim
);
3317 elsif Is_Entity_Name
(Nam
)
3318 and then Present
(Entity
(Nam
))
3319 and then not Comes_From_Source
(Nam
)
3320 and then not Is_Overloaded
(Nam
)
3322 Old_S
:= Entity
(Nam
);
3324 -- The subprogram renaming declaration may become Ghost if it
3325 -- renames a Ghost entity.
3327 Mark_Ghost_Renaming
(N
, Old_S
);
3329 New_S
:= Analyze_Subprogram_Specification
(Spec
);
3333 if Ekind
(Old_S
) = E_Operator
then
3337 if Box_Present
(Inst_Node
) then
3338 Old_S
:= Find_Renamed_Entity
(N
, Name
(N
), New_S
, Is_Actual
);
3340 -- If there is an immediately visible homonym of the operator
3341 -- and the declaration has a default, this is worth a warning
3342 -- because the user probably did not intend to get the pre-
3343 -- defined operator, visible in the generic declaration. To
3344 -- find if there is an intended candidate, analyze the renaming
3345 -- again in the current context.
3347 elsif Scope
(Old_S
) = Standard_Standard
3348 and then Present
(Default_Name
(Inst_Node
))
3351 Decl
: constant Node_Id
:= New_Copy_Tree
(N
);
3355 Set_Entity
(Name
(Decl
), Empty
);
3356 Analyze
(Name
(Decl
));
3358 Find_Renamed_Entity
(Decl
, Name
(Decl
), New_S
, True);
3361 and then In_Open_Scopes
(Scope
(Hidden
))
3362 and then Is_Immediately_Visible
(Hidden
)
3363 and then Comes_From_Source
(Hidden
)
3364 and then Hidden
/= Old_S
3366 Error_Msg_Sloc
:= Sloc
(Hidden
);
3368 ("default subprogram is resolved in the generic "
3369 & "declaration (RM 12.6(17))??", N
);
3370 Error_Msg_NE
("\and will not use & #??", N
, Hidden
);
3379 -- The subprogram renaming declaration may become Ghost if it
3380 -- renames a Ghost entity.
3382 if Is_Entity_Name
(Nam
) then
3383 Mark_Ghost_Renaming
(N
, Entity
(Nam
));
3386 New_S
:= Analyze_Subprogram_Specification
(Spec
);
3390 -- Renamed entity must be analyzed first, to avoid being hidden by
3391 -- new name (which might be the same in a generic instance).
3395 -- The subprogram renaming declaration may become Ghost if it renames
3398 if Is_Entity_Name
(Nam
) then
3399 Mark_Ghost_Renaming
(N
, Entity
(Nam
));
3402 -- The renaming defines a new overloaded entity, which is analyzed
3403 -- like a subprogram declaration.
3405 New_S
:= Analyze_Subprogram_Specification
(Spec
);
3408 if Current_Scope
/= Standard_Standard
then
3409 Set_Is_Pure
(New_S
, Is_Pure
(Current_Scope
));
3412 -- Set SPARK mode from current context
3414 Set_SPARK_Pragma
(New_S
, SPARK_Mode_Pragma
);
3415 Set_SPARK_Pragma_Inherited
(New_S
);
3417 Rename_Spec
:= Find_Corresponding_Spec
(N
);
3419 -- Case of Renaming_As_Body
3421 if Present
(Rename_Spec
) then
3422 Check_Previous_Null_Procedure
(N
, Rename_Spec
);
3424 -- Renaming declaration is the completion of the declaration of
3425 -- Rename_Spec. We build an actual body for it at the freezing point.
3427 Set_Corresponding_Spec
(N
, Rename_Spec
);
3429 -- Deal with special case of stream functions of abstract types
3432 if Nkind
(Unit_Declaration_Node
(Rename_Spec
)) =
3433 N_Abstract_Subprogram_Declaration
3435 -- Input stream functions are abstract if the object type is
3436 -- abstract. Similarly, all default stream functions for an
3437 -- interface type are abstract. However, these subprograms may
3438 -- receive explicit declarations in representation clauses, making
3439 -- the attribute subprograms usable as defaults in subsequent
3441 -- In this case we rewrite the declaration to make the subprogram
3442 -- non-abstract. We remove the previous declaration, and insert
3443 -- the new one at the point of the renaming, to prevent premature
3444 -- access to unfrozen types. The new declaration reuses the
3445 -- specification of the previous one, and must not be analyzed.
3448 (Is_Primitive
(Entity
(Nam
))
3450 Is_Abstract_Type
(Find_Dispatching_Type
(Entity
(Nam
))));
3452 Old_Decl
: constant Node_Id
:=
3453 Unit_Declaration_Node
(Rename_Spec
);
3454 New_Decl
: constant Node_Id
:=
3455 Make_Subprogram_Declaration
(Sloc
(N
),
3457 Relocate_Node
(Specification
(Old_Decl
)));
3460 Insert_After
(N
, New_Decl
);
3461 Set_Is_Abstract_Subprogram
(Rename_Spec
, False);
3462 Set_Analyzed
(New_Decl
);
3466 Set_Corresponding_Body
(Unit_Declaration_Node
(Rename_Spec
), New_S
);
3468 if Ada_Version
= Ada_83
and then Comes_From_Source
(N
) then
3469 Error_Msg_N
("(Ada 83) renaming cannot serve as a body", N
);
3472 Set_Convention
(New_S
, Convention
(Rename_Spec
));
3473 Check_Fully_Conformant
(New_S
, Rename_Spec
);
3474 Set_Public_Status
(New_S
);
3476 if No_Return
(Rename_Spec
)
3477 and then not No_Return
(Entity
(Nam
))
3480 ("renamed subprogram & must be No_Return", N
, Entity
(Nam
));
3482 ("\since renaming subprogram is No_Return (RM 6.5.1(7/2))", N
);
3485 -- The specification does not introduce new formals, but only
3486 -- repeats the formals of the original subprogram declaration.
3487 -- For cross-reference purposes, and for refactoring tools, we
3488 -- treat the formals of the renaming declaration as body formals.
3490 Reference_Body_Formals
(Rename_Spec
, New_S
);
3492 -- Indicate that the entity in the declaration functions like the
3493 -- corresponding body, and is not a new entity. The body will be
3494 -- constructed later at the freeze point, so indicate that the
3495 -- completion has not been seen yet.
3497 Reinit_Field_To_Zero
(New_S
, F_Has_Out_Or_In_Out_Parameter
,
3498 Old_Ekind
=> (E_Function | E_Procedure
=> True, others => False));
3499 Reinit_Field_To_Zero
(New_S
, F_Needs_No_Actuals
);
3500 Reinit_Field_To_Zero
(New_S
, F_Is_Predicate_Function
);
3501 Reinit_Field_To_Zero
(New_S
, F_Protected_Subprogram
);
3502 Reinit_Field_To_Zero
(New_S
, F_Is_Inlined_Always
);
3503 Reinit_Field_To_Zero
(New_S
, F_Is_Generic_Actual_Subprogram
);
3504 Mutate_Ekind
(New_S
, E_Subprogram_Body
);
3505 New_S
:= Rename_Spec
;
3506 Set_Has_Completion
(Rename_Spec
, False);
3508 -- Ada 2005: check overriding indicator
3510 if Present
(Overridden_Operation
(Rename_Spec
)) then
3511 if Must_Not_Override
(Specification
(N
)) then
3513 ("subprogram& overrides inherited operation",
3517 and then not Must_Override
(Specification
(N
))
3519 Style
.Missing_Overriding
(N
, Rename_Spec
);
3522 elsif Must_Override
(Specification
(N
))
3523 and then not Can_Override_Operator
(Rename_Spec
)
3525 Error_Msg_NE
("subprogram& is not overriding", N
, Rename_Spec
);
3528 -- AI12-0132: a renames-as-body freezes the expression of any
3529 -- expression function that it renames.
3531 if Is_Entity_Name
(Nam
)
3532 and then Is_Expression_Function
(Entity
(Nam
))
3533 and then not Inside_A_Generic
3536 (Def_Id
=> Entity
(Nam
),
3537 Typ
=> Etype
(Entity
(Nam
)),
3540 (Original_Node
(Unit_Declaration_Node
(Entity
(Nam
)))),
3544 -- Normal subprogram renaming (not renaming as body)
3547 Generate_Definition
(New_S
);
3548 New_Overloaded_Entity
(New_S
);
3550 if not (Is_Entity_Name
(Nam
)
3551 and then Is_Intrinsic_Subprogram
(Entity
(Nam
)))
3553 Check_Delayed_Subprogram
(New_S
);
3556 -- Verify that a SPARK renaming does not declare a primitive
3557 -- operation of a tagged type.
3559 Check_SPARK_Primitive_Operation
(New_S
);
3562 -- There is no need for elaboration checks on the new entity, which may
3563 -- be called before the next freezing point where the body will appear.
3564 -- Elaboration checks refer to the real entity, not the one created by
3565 -- the renaming declaration.
3567 Set_Kill_Elaboration_Checks
(New_S
, True);
3569 -- If we had a previous error, indicate a completion is present to stop
3570 -- junk cascaded messages, but don't take any further action.
3572 if Etype
(Nam
) = Any_Type
then
3573 Set_Has_Completion
(New_S
);
3576 -- Case where name has the form of a selected component
3578 elsif Nkind
(Nam
) = N_Selected_Component
then
3580 -- A name which has the form A.B can designate an entry of task A, a
3581 -- protected operation of protected object A, or finally a primitive
3582 -- operation of object A. In the later case, A is an object of some
3583 -- tagged type, or an access type that denotes one such. To further
3584 -- distinguish these cases, note that the scope of a task entry or
3585 -- protected operation is type of the prefix.
3587 -- The prefix could be an overloaded function call that returns both
3588 -- kinds of operations. This overloading pathology is left to the
3589 -- dedicated reader ???
3592 T
: constant Entity_Id
:= Etype
(Prefix
(Nam
));
3600 and then Is_Tagged_Type
(Designated_Type
(T
))))
3601 and then Scope
(Entity
(Selector_Name
(Nam
))) /= T
3603 Analyze_Renamed_Primitive_Operation
3604 (N
, New_S
, Present
(Rename_Spec
));
3608 -- Renamed entity is an entry or protected operation. For those
3609 -- cases an explicit body is built (at the point of freezing of
3610 -- this entity) that contains a call to the renamed entity.
3612 -- This is not allowed for renaming as body if the renamed
3613 -- spec is already frozen (see RM 8.5.4(5) for details).
3615 if Present
(Rename_Spec
) and then Is_Frozen
(Rename_Spec
) then
3617 ("renaming-as-body cannot rename entry as subprogram", N
);
3619 ("\since & is already frozen (RM 8.5.4(5))",
3622 Analyze_Renamed_Entry
(N
, New_S
, Present
(Rename_Spec
));
3629 -- Case where name is an explicit dereference X.all
3631 elsif Nkind
(Nam
) = N_Explicit_Dereference
then
3633 -- Renamed entity is designated by access_to_subprogram expression.
3634 -- Must build body to encapsulate call, as in the entry case.
3636 Analyze_Renamed_Dereference
(N
, New_S
, Present
(Rename_Spec
));
3639 -- Indexed component
3641 elsif Nkind
(Nam
) = N_Indexed_Component
then
3642 Analyze_Renamed_Family_Member
(N
, New_S
, Present
(Rename_Spec
));
3645 -- Character literal
3647 elsif Nkind
(Nam
) = N_Character_Literal
then
3648 Analyze_Renamed_Character
(N
, New_S
, Present
(Rename_Spec
));
3651 -- Only remaining case is where we have a non-entity name, or a renaming
3652 -- of some other non-overloadable entity.
3654 elsif not Is_Entity_Name
(Nam
)
3655 or else not Is_Overloadable
(Entity
(Nam
))
3657 -- Do not mention the renaming if it comes from an instance
3659 if not Is_Actual
then
3660 Error_Msg_N
("expect valid subprogram name in renaming", N
);
3662 Error_Msg_NE
("no visible subprogram for formal&", N
, Nam
);
3668 -- Find the renamed entity that matches the given specification. Disable
3669 -- Ada_83 because there is no requirement of full conformance between
3670 -- renamed entity and new entity, even though the same circuit is used.
3672 -- This is a bit of an odd case, which introduces a really irregular use
3673 -- of Ada_Version[_Explicit]. Would be nice to find cleaner way to do
3676 Ada_Version
:= Ada_Version_Type
'Max (Ada_Version
, Ada_95
);
3677 Ada_Version_Pragma
:= Empty
;
3678 Ada_Version_Explicit
:= Ada_Version
;
3681 Old_S
:= Find_Renamed_Entity
(N
, Name
(N
), New_S
, Is_Actual
);
3683 -- The visible operation may be an inherited abstract operation that
3684 -- was overridden in the private part, in which case a call will
3685 -- dispatch to the overriding operation. Use the overriding one in
3686 -- the renaming declaration, to prevent spurious errors below.
3688 if Is_Overloadable
(Old_S
)
3689 and then Is_Abstract_Subprogram
(Old_S
)
3690 and then No
(DTC_Entity
(Old_S
))
3691 and then Present
(Alias
(Old_S
))
3692 and then not Is_Abstract_Subprogram
(Alias
(Old_S
))
3693 and then Present
(Overridden_Operation
(Alias
(Old_S
)))
3695 Old_S
:= Alias
(Old_S
);
3698 -- When the renamed subprogram is overloaded and used as an actual
3699 -- of a generic, its entity is set to the first available homonym.
3700 -- We must first disambiguate the name, then set the proper entity.
3702 if Is_Actual
and then Is_Overloaded
(Nam
) then
3703 Set_Entity
(Nam
, Old_S
);
3707 -- Most common case: subprogram renames subprogram. No body is generated
3708 -- in this case, so we must indicate the declaration is complete as is.
3709 -- and inherit various attributes of the renamed subprogram.
3711 if No
(Rename_Spec
) then
3712 Set_Has_Completion
(New_S
);
3713 Set_Is_Imported
(New_S
, Is_Imported
(Entity
(Nam
)));
3714 Set_Is_Pure
(New_S
, Is_Pure
(Entity
(Nam
)));
3715 Set_Is_Preelaborated
(New_S
, Is_Preelaborated
(Entity
(Nam
)));
3717 -- Ada 2005 (AI-423): Check the consistency of null exclusions
3718 -- between a subprogram and its correct renaming.
3720 -- Note: the Any_Id check is a guard that prevents compiler crashes
3721 -- when performing a null exclusion check between a renaming and a
3722 -- renamed subprogram that has been found to be illegal.
3724 if Ada_Version
>= Ada_2005
and then Entity
(Nam
) /= Any_Id
then
3725 Check_Null_Exclusion
3727 Sub
=> Entity
(Nam
));
3730 -- Enforce the Ada 2005 rule that the renamed entity cannot require
3731 -- overriding. The flag Requires_Overriding is set very selectively
3732 -- and misses some other illegal cases. The additional conditions
3733 -- checked below are sufficient but not necessary ???
3735 -- The rule does not apply to the renaming generated for an actual
3736 -- subprogram in an instance.
3741 -- Guard against previous errors, and omit renamings of predefined
3744 elsif Ekind
(Old_S
) not in E_Function | E_Procedure
then
3747 elsif Requires_Overriding
(Old_S
)
3749 (Is_Abstract_Subprogram
(Old_S
)
3750 and then Present
(Find_Dispatching_Type
(Old_S
))
3751 and then not Is_Abstract_Type
(Find_Dispatching_Type
(Old_S
)))
3754 ("renamed entity cannot be subprogram that requires overriding "
3755 & "(RM 8.5.4 (5.1))", N
);
3759 Prev
: constant Entity_Id
:= Overridden_Operation
(New_S
);
3763 (Has_Non_Trivial_Precondition
(Prev
)
3764 or else Has_Non_Trivial_Precondition
(Old_S
))
3767 ("conflicting inherited classwide preconditions in renaming "
3768 & "of& (RM 6.1.1 (17)", N
, Old_S
);
3773 if Old_S
/= Any_Id
then
3774 if Is_Actual
and then From_Default
(N
) then
3776 -- This is an implicit reference to the default actual
3778 Generate_Reference
(Old_S
, Nam
, Typ
=> 'i', Force
=> True);
3781 Generate_Reference
(Old_S
, Nam
);
3784 Check_Internal_Protected_Use
(N
, Old_S
);
3786 -- For a renaming-as-body, require subtype conformance, but if the
3787 -- declaration being completed has not been frozen, then inherit the
3788 -- convention of the renamed subprogram prior to checking conformance
3789 -- (unless the renaming has an explicit convention established; the
3790 -- rule stated in the RM doesn't seem to address this ???).
3792 if Present
(Rename_Spec
) then
3793 Generate_Reference
(Rename_Spec
, Defining_Entity
(Spec
), 'b');
3794 Style
.Check_Identifier
(Defining_Entity
(Spec
), Rename_Spec
);
3796 if not Is_Frozen
(Rename_Spec
) then
3797 if not Has_Convention_Pragma
(Rename_Spec
) then
3798 Set_Convention
(New_S
, Convention
(Old_S
));
3801 if Ekind
(Old_S
) /= E_Operator
then
3802 Check_Mode_Conformant
(New_S
, Old_S
, Spec
);
3805 if Original_Subprogram
(Old_S
) = Rename_Spec
then
3806 Error_Msg_N
("unfrozen subprogram cannot rename itself", N
);
3808 Check_Formal_Subprogram_Conformance
(New_S
, Old_S
, Spec
);
3811 Check_Subtype_Conformant
(New_S
, Old_S
, Spec
);
3814 Check_Frozen_Renaming
(N
, Rename_Spec
);
3816 -- Check explicitly that renamed entity is not intrinsic, because
3817 -- in a generic the renamed body is not built. In this case,
3818 -- the renaming_as_body is a completion.
3820 if Inside_A_Generic
then
3821 if Is_Frozen
(Rename_Spec
)
3822 and then Is_Intrinsic_Subprogram
(Old_S
)
3825 ("subprogram in renaming_as_body cannot be intrinsic",
3829 Set_Has_Completion
(Rename_Spec
);
3832 elsif Ekind
(Old_S
) /= E_Operator
then
3834 -- If this a defaulted subprogram for a class-wide actual there is
3835 -- no check for mode conformance, given that the signatures don't
3836 -- match (the source mentions T but the actual mentions T'Class).
3841 -- No need for a redundant error message if this is a nested
3842 -- instance, unless the current instantiation (of a child unit)
3843 -- is a compilation unit, which is not analyzed when the parent
3844 -- generic is analyzed.
3847 or else No
(Enclosing_Instance
)
3848 or else Is_Compilation_Unit
(Current_Scope
)
3850 Check_Mode_Conformant
(New_S
, Old_S
);
3854 if No
(Rename_Spec
) then
3856 -- The parameter profile of the new entity is that of the renamed
3857 -- entity: the subtypes given in the specification are irrelevant.
3859 Inherit_Renamed_Profile
(New_S
, Old_S
);
3861 -- A call to the subprogram is transformed into a call to the
3862 -- renamed entity. This is transitive if the renamed entity is
3863 -- itself a renaming.
3865 if Present
(Alias
(Old_S
)) then
3866 Set_Alias
(New_S
, Alias
(Old_S
));
3868 Set_Alias
(New_S
, Old_S
);
3871 -- Note that we do not set Is_Intrinsic_Subprogram if we have a
3872 -- renaming as body, since the entity in this case is not an
3873 -- intrinsic (it calls an intrinsic, but we have a real body for
3874 -- this call, and it is in this body that the required intrinsic
3875 -- processing will take place).
3877 -- Also, if this is a renaming of inequality, the renamed operator
3878 -- is intrinsic, but what matters is the corresponding equality
3879 -- operator, which may be user-defined.
3881 Set_Is_Intrinsic_Subprogram
3883 Is_Intrinsic_Subprogram
(Old_S
)
3885 (Chars
(Old_S
) /= Name_Op_Ne
3886 or else Ekind
(Old_S
) = E_Operator
3887 or else Is_Intrinsic_Subprogram
3888 (Corresponding_Equality
(Old_S
))));
3890 if Ekind
(Alias
(New_S
)) = E_Operator
then
3891 Set_Has_Delayed_Freeze
(New_S
, False);
3894 -- If the renaming corresponds to an association for an abstract
3895 -- formal subprogram, then various attributes must be set to
3896 -- indicate that the renaming is an abstract dispatching operation
3897 -- with a controlling type.
3899 -- Skip this decoration when the renaming corresponds to an
3900 -- association with class-wide wrapper (see above) because such
3901 -- wrapper is neither abstract nor a dispatching operation (its
3902 -- body has the dispatching call to the wrapped primitive).
3905 and then Is_Abstract_Subprogram
(Formal_Spec
)
3906 and then No
(Wrapped_Prim
)
3909 -- Mark the renaming as abstract here, so Find_Dispatching_Type
3910 -- see it as corresponding to a generic association for a
3911 -- formal abstract subprogram
3913 Set_Is_Abstract_Subprogram
(New_S
);
3916 New_S_Ctrl_Type
: constant Entity_Id
:=
3917 Find_Dispatching_Type
(New_S
);
3918 Old_S_Ctrl_Type
: constant Entity_Id
:=
3919 Find_Dispatching_Type
(Old_S
);
3923 -- The actual must match the (instance of the) formal,
3924 -- and must be a controlling type.
3926 if Old_S_Ctrl_Type
/= New_S_Ctrl_Type
3927 or else No
(New_S_Ctrl_Type
)
3929 if No
(New_S_Ctrl_Type
) then
3931 ("actual must be dispatching subprogram", Nam
);
3934 ("actual must be dispatching subprogram for type&",
3935 Nam
, New_S_Ctrl_Type
);
3939 Set_Is_Dispatching_Operation
(New_S
);
3940 Check_Controlling_Formals
(New_S_Ctrl_Type
, New_S
);
3942 -- If the actual in the formal subprogram is itself a
3943 -- formal abstract subprogram association, there's no
3944 -- dispatch table component or position to inherit.
3946 if Present
(DTC_Entity
(Old_S
)) then
3947 Set_DTC_Entity
(New_S
, DTC_Entity
(Old_S
));
3948 Set_DT_Position_Value
(New_S
, DT_Position
(Old_S
));
3958 -- The following is illegal, because F hides whatever other F may
3960 -- function F (...) renames F;
3963 or else (Nkind
(Nam
) /= N_Expanded_Name
3964 and then Chars
(Old_S
) = Chars
(New_S
))
3966 Error_Msg_N
("subprogram cannot rename itself", N
);
3968 -- This is illegal even if we use a selector:
3969 -- function F (...) renames Pkg.F;
3970 -- because F is still hidden.
3972 elsif Nkind
(Nam
) = N_Expanded_Name
3973 and then Entity
(Prefix
(Nam
)) = Current_Scope
3974 and then Chars
(Selector_Name
(Nam
)) = Chars
(New_S
)
3976 -- This is an error, but we overlook the error and accept the
3977 -- renaming if the special Overriding_Renamings mode is in effect.
3979 if not Overriding_Renamings
then
3981 ("implicit operation& is not visible (RM 8.3 (15))",
3985 -- Check whether an expanded name used for the renamed subprogram
3986 -- begins with the same name as the renaming itself, and if so,
3987 -- issue an error about the prefix being hidden by the renaming.
3988 -- We exclude generic instances from this checking, since such
3989 -- normally illegal renamings can be constructed when expanding
3992 elsif Nkind
(Nam
) = N_Expanded_Name
and then not In_Instance
then
3994 function Ult_Expanded_Prefix
(N
: Node_Id
) return Node_Id
is
3995 (if Nkind
(N
) /= N_Expanded_Name
3997 else Ult_Expanded_Prefix
(Prefix
(N
)));
3998 -- Returns the ultimate prefix of an expanded name
4001 if Chars
(Entity
(Ult_Expanded_Prefix
(Nam
))) = Chars
(New_S
)
4003 Error_Msg_Sloc
:= Sloc
(N
);
4005 ("& is hidden by declaration#", Nam
, New_S
);
4010 Set_Convention
(New_S
, Convention
(Old_S
));
4012 if Is_Abstract_Subprogram
(Old_S
) then
4013 if Present
(Rename_Spec
) then
4015 ("a renaming-as-body cannot rename an abstract subprogram",
4017 Set_Has_Completion
(Rename_Spec
);
4019 Set_Is_Abstract_Subprogram
(New_S
);
4023 Check_Library_Unit_Renaming
(N
, Old_S
);
4025 -- Pathological case: procedure renames entry in the scope of its
4026 -- task. Entry is given by simple name, but body must be built for
4027 -- procedure. Of course if called it will deadlock.
4029 if Ekind
(Old_S
) = E_Entry
then
4030 Set_Has_Completion
(New_S
, False);
4031 Set_Alias
(New_S
, Empty
);
4034 -- Do not freeze the renaming nor the renamed entity when the context
4035 -- is an enclosing generic. Freezing is an expansion activity, and in
4036 -- addition the renamed entity may depend on the generic formals of
4037 -- the enclosing generic.
4039 if Is_Actual
and not Inside_A_Generic
then
4040 Freeze_Before
(N
, Old_S
);
4041 Freeze_Actual_Profile
;
4042 Set_Has_Delayed_Freeze
(New_S
, False);
4043 Freeze_Before
(N
, New_S
);
4045 if (Ekind
(Old_S
) = E_Procedure
or else Ekind
(Old_S
) = E_Function
)
4046 and then not Is_Abstract_Subprogram
(Formal_Spec
)
4048 -- An abstract subprogram is only allowed as an actual in the
4049 -- case where the formal subprogram is also abstract.
4051 if Is_Abstract_Subprogram
(Old_S
) then
4053 ("abstract subprogram not allowed as generic actual", Nam
);
4056 -- AI12-0412: A primitive of an abstract type with Pre'Class
4057 -- or Post'Class aspects specified with nonstatic expressions
4058 -- is not allowed as actual for a nonabstract formal subprogram
4059 -- (see RM 6.1.1(18.2/5).
4061 if Is_Dispatching_Operation
(Old_S
)
4063 Is_Prim_Of_Abst_Type_With_Nonstatic_CW_Pre_Post
(Old_S
)
4066 ("primitive of abstract type with nonstatic class-wide "
4067 & "pre/postconditions not allowed as actual",
4074 -- A common error is to assume that implicit operators for types are
4075 -- defined in Standard, or in the scope of a subtype. In those cases
4076 -- where the renamed entity is given with an expanded name, it is
4077 -- worth mentioning that operators for the type are not declared in
4078 -- the scope given by the prefix.
4080 if Nkind
(Nam
) = N_Expanded_Name
4081 and then Nkind
(Selector_Name
(Nam
)) = N_Operator_Symbol
4082 and then Scope
(Entity
(Nam
)) = Standard_Standard
4085 T
: constant Entity_Id
:=
4086 Base_Type
(Etype
(First_Formal
(New_S
)));
4088 Error_Msg_Node_2
:= Prefix
(Nam
);
4090 ("operator for type& is not declared in&", Prefix
(Nam
), T
);
4095 ("no visible subprogram matches the specification for&",
4099 if Present
(Candidate_Renaming
) then
4106 F1
:= First_Formal
(Candidate_Renaming
);
4107 F2
:= First_Formal
(New_S
);
4108 T1
:= First_Subtype
(Etype
(F1
));
4109 while Present
(F1
) and then Present
(F2
) loop
4114 if Present
(F1
) and then Present
(Default_Value
(F1
)) then
4115 if Present
(Next_Formal
(F1
)) then
4117 ("\missing specification for & and other formals with "
4118 & "defaults", Spec
, F1
);
4120 Error_Msg_NE
("\missing specification for &", Spec
, F1
);
4124 if Nkind
(Nam
) = N_Operator_Symbol
4125 and then From_Default
(N
)
4127 Error_Msg_Node_2
:= T1
;
4129 ("default & on & is not directly visible", Nam
, Nam
);
4135 -- Ada 2005 AI 404: if the new subprogram is dispatching, verify that
4136 -- controlling access parameters are known non-null for the renamed
4137 -- subprogram. Test also applies to a subprogram instantiation that
4138 -- is dispatching. Test is skipped if some previous error was detected
4139 -- that set Old_S to Any_Id.
4141 if Ada_Version
>= Ada_2005
4142 and then Old_S
/= Any_Id
4143 and then not Is_Dispatching_Operation
(Old_S
)
4144 and then Is_Dispatching_Operation
(New_S
)
4151 Old_F
:= First_Formal
(Old_S
);
4152 New_F
:= First_Formal
(New_S
);
4153 while Present
(Old_F
) loop
4154 if Ekind
(Etype
(Old_F
)) = E_Anonymous_Access_Type
4155 and then Is_Controlling_Formal
(New_F
)
4156 and then not Can_Never_Be_Null
(Old_F
)
4158 Error_Msg_N
("access parameter is controlling,", New_F
);
4160 ("\corresponding parameter of& must be explicitly null "
4161 & "excluding", New_F
, Old_S
);
4164 Next_Formal
(Old_F
);
4165 Next_Formal
(New_F
);
4170 -- A useful warning, suggested by Ada Bug Finder (Ada-Europe 2005)
4171 -- is to warn if an operator is being renamed as a different operator.
4172 -- If the operator is predefined, examine the kind of the entity, not
4173 -- the abbreviated declaration in Standard.
4175 if Comes_From_Source
(N
)
4176 and then Present
(Old_S
)
4177 and then (Nkind
(Old_S
) = N_Defining_Operator_Symbol
4178 or else Ekind
(Old_S
) = E_Operator
)
4179 and then Nkind
(New_S
) = N_Defining_Operator_Symbol
4180 and then Chars
(Old_S
) /= Chars
(New_S
)
4183 ("& is being renamed as a different operator??", N
, Old_S
);
4186 -- Check for renaming of obsolescent subprogram
4188 Check_Obsolescent_2005_Entity
(Entity
(Nam
), Nam
);
4190 -- Another warning or some utility: if the new subprogram as the same
4191 -- name as the old one, the old one is not hidden by an outer homograph,
4192 -- the new one is not a public symbol, and the old one is otherwise
4193 -- directly visible, the renaming is superfluous.
4195 if Chars
(Old_S
) = Chars
(New_S
)
4196 and then Comes_From_Source
(N
)
4197 and then Scope
(Old_S
) /= Standard_Standard
4198 and then Warn_On_Redundant_Constructs
4199 and then (Is_Immediately_Visible
(Old_S
)
4200 or else Is_Potentially_Use_Visible
(Old_S
))
4201 and then Is_Overloadable
(Current_Scope
)
4202 and then Chars
(Current_Scope
) /= Chars
(Old_S
)
4205 ("redundant renaming, entity is directly visible?r?", Name
(N
));
4208 -- Implementation-defined aspect specifications can appear in a renaming
4209 -- declaration, but not language-defined ones. The call to procedure
4210 -- Analyze_Aspect_Specifications will take care of this error check.
4212 Analyze_Aspect_Specifications
(N
, New_S
);
4217 and then Has_Yield_Aspect
(Formal_Spec
)
4218 and then not Has_Yield_Aspect
(Old_S
)
4220 Error_Msg_Name_1
:= Name_Yield
;
4222 ("actual subprogram& must have aspect% to match formal", Name
(N
));
4225 Ada_Version
:= Save_AV
;
4226 Ada_Version_Pragma
:= Save_AVP
;
4227 Ada_Version_Explicit
:= Save_AV_Exp
;
4229 -- Check if we are looking at an Ada 2012 defaulted formal subprogram
4230 -- and mark any use_package_clauses that affect the visibility of the
4231 -- implicit generic actual.
4233 -- Also, we may be looking at an internal renaming of a user-defined
4234 -- subprogram created for a generic formal subprogram association,
4235 -- which will also have to be marked here. This can occur when the
4236 -- corresponding formal subprogram contains references to other generic
4239 if Is_Generic_Actual_Subprogram
(New_S
)
4240 and then (Is_Intrinsic_Subprogram
(New_S
)
4241 or else From_Default
(N
)
4242 or else Nkind
(N
) = N_Subprogram_Renaming_Declaration
)
4244 Mark_Use_Clauses
(New_S
);
4246 -- Handle overloaded subprograms
4248 if Present
(Alias
(New_S
)) then
4249 Mark_Use_Clauses
(Alias
(New_S
));
4254 Local_Restrict
.Check_Actual_Subprogram_For_Instance
4255 (Actual_Subp_Name
=> Nam
, Formal_Subp
=> Formal_Spec
);
4257 end Analyze_Subprogram_Renaming
;
4259 -------------------------
4260 -- Analyze_Use_Package --
4261 -------------------------
4263 -- Resolve the package names in the use clause, and make all the visible
4264 -- entities defined in the package potentially use-visible. If the package
4265 -- is already in use from a previous use clause, its visible entities are
4266 -- already use-visible. In that case, mark the occurrence as a redundant
4267 -- use. If the package is an open scope, i.e. if the use clause occurs
4268 -- within the package itself, ignore it.
4270 procedure Analyze_Use_Package
(N
: Node_Id
; Chain
: Boolean := True) is
4271 procedure Analyze_Package_Name
(Clause
: Node_Id
);
4272 -- Perform analysis on a package name from a use_package_clause
4274 procedure Analyze_Package_Name_List
(Head_Clause
: Node_Id
);
4275 -- Similar to Analyze_Package_Name but iterates over all the names
4278 --------------------------
4279 -- Analyze_Package_Name --
4280 --------------------------
4282 procedure Analyze_Package_Name
(Clause
: Node_Id
) is
4283 Pack
: constant Node_Id
:= Name
(Clause
);
4287 pragma Assert
(Nkind
(Clause
) = N_Use_Package_Clause
);
4290 -- Verify that the package standard is not directly named in a
4291 -- use_package_clause.
4293 if Nkind
(Parent
(Clause
)) = N_Compilation_Unit
4294 and then Nkind
(Pack
) = N_Expanded_Name
4296 Pref
:= Prefix
(Pack
);
4298 while Nkind
(Pref
) = N_Expanded_Name
loop
4299 Pref
:= Prefix
(Pref
);
4302 if Entity
(Pref
) = Standard_Standard
then
4304 ("predefined package Standard cannot appear in a context "
4308 end Analyze_Package_Name
;
4310 -------------------------------
4311 -- Analyze_Package_Name_List --
4312 -------------------------------
4314 procedure Analyze_Package_Name_List
(Head_Clause
: Node_Id
) is
4318 -- Due to the way source use clauses are split during parsing we are
4319 -- forced to simply iterate through all entities in scope until the
4320 -- clause representing the last name in the list is found.
4322 Curr
:= Head_Clause
;
4323 while Present
(Curr
) loop
4324 Analyze_Package_Name
(Curr
);
4326 -- Stop iterating over the names in the use clause when we are at
4329 exit when not More_Ids
(Curr
) and then Prev_Ids
(Curr
);
4332 end Analyze_Package_Name_List
;
4338 -- Start of processing for Analyze_Use_Package
4341 Set_Hidden_By_Use_Clause
(N
, No_Elist
);
4343 -- Use clause not allowed in a spec of a predefined package declaration
4344 -- except that packages whose file name starts a-n are OK (these are
4345 -- children of Ada.Numerics, which are never loaded by Rtsfind).
4347 if Is_Predefined_Unit
(Current_Sem_Unit
)
4348 and then Get_Name_String
4349 (Unit_File_Name
(Current_Sem_Unit
)) (1 .. 3) /= "a-n"
4350 and then Nkind
(Unit
(Cunit
(Current_Sem_Unit
))) =
4351 N_Package_Declaration
4353 Error_Msg_N
("use clause not allowed in predefined spec", N
);
4356 -- Loop through all package names from the original use clause in
4357 -- order to analyze referenced packages. A use_package_clause with only
4358 -- one name does not have More_Ids or Prev_Ids set, while a clause with
4359 -- More_Ids only starts the chain produced by the parser.
4361 if not More_Ids
(N
) and then not Prev_Ids
(N
) then
4362 Analyze_Package_Name
(N
);
4364 elsif More_Ids
(N
) and then not Prev_Ids
(N
) then
4365 Analyze_Package_Name_List
(N
);
4368 if not Is_Entity_Name
(Name
(N
)) then
4369 Error_Msg_N
("& is not a package", Name
(N
));
4375 Chain_Use_Clause
(N
);
4378 Pack
:= Entity
(Name
(N
));
4380 -- There are many cases where scopes are manipulated during analysis, so
4381 -- check that Pack's current use clause has not already been chained
4382 -- before setting its previous use clause.
4384 if Ekind
(Pack
) = E_Package
4385 and then Present
(Current_Use_Clause
(Pack
))
4386 and then Current_Use_Clause
(Pack
) /= N
4387 and then No
(Prev_Use_Clause
(N
))
4388 and then Prev_Use_Clause
(Current_Use_Clause
(Pack
)) /= N
4390 Set_Prev_Use_Clause
(N
, Current_Use_Clause
(Pack
));
4393 -- Mark all entities as potentially use visible
4395 if Ekind
(Pack
) /= E_Package
and then Etype
(Pack
) /= Any_Type
then
4396 if Ekind
(Pack
) = E_Generic_Package
then
4397 Error_Msg_N
-- CODEFIX
4398 ("a generic package is not allowed in a use clause", Name
(N
));
4400 elsif Is_Generic_Subprogram
(Pack
) then
4401 Error_Msg_N
-- CODEFIX
4402 ("a generic subprogram is not allowed in a use clause",
4405 elsif Is_Subprogram
(Pack
) then
4406 Error_Msg_N
-- CODEFIX
4407 ("a subprogram is not allowed in a use clause", Name
(N
));
4410 Error_Msg_N
("& is not allowed in a use clause", Name
(N
));
4414 if Nkind
(Parent
(N
)) = N_Compilation_Unit
then
4415 Check_In_Previous_With_Clause
(N
, Name
(N
));
4418 Use_One_Package
(N
, Name
(N
));
4421 Mark_Ghost_Clause
(N
);
4422 end Analyze_Use_Package
;
4424 ----------------------
4425 -- Analyze_Use_Type --
4426 ----------------------
4428 procedure Analyze_Use_Type
(N
: Node_Id
; Chain
: Boolean := True) is
4433 Set_Hidden_By_Use_Clause
(N
, No_Elist
);
4435 -- Chain clause to list of use clauses in current scope when flagged
4438 Chain_Use_Clause
(N
);
4441 -- Obtain the base type of the type denoted within the use_type_clause's
4444 Id
:= Subtype_Mark
(N
);
4446 E
:= Base_Type
(Entity
(Id
));
4448 -- There are many cases where a use_type_clause may be reanalyzed due to
4449 -- manipulation of the scope stack so we much guard against those cases
4450 -- here, otherwise, we must add the new use_type_clause to the previous
4451 -- use_type_clause chain in order to mark redundant use_type_clauses as
4452 -- used. When the redundant use-type clauses appear in a parent unit and
4453 -- a child unit we must prevent a circularity in the chain that would
4454 -- otherwise result from the separate steps of analysis and installation
4455 -- of the parent context.
4457 if Present
(Current_Use_Clause
(E
))
4458 and then Current_Use_Clause
(E
) /= N
4459 and then Prev_Use_Clause
(Current_Use_Clause
(E
)) /= N
4460 and then No
(Prev_Use_Clause
(N
))
4462 Set_Prev_Use_Clause
(N
, Current_Use_Clause
(E
));
4465 -- If the Used_Operations list is already initialized, the clause has
4466 -- been analyzed previously, and it is being reinstalled, for example
4467 -- when the clause appears in a package spec and we are compiling the
4468 -- corresponding package body. In that case, make the entities on the
4469 -- existing list use_visible, and mark the corresponding types In_Use.
4471 if Present
(Used_Operations
(N
)) then
4476 Use_One_Type
(Subtype_Mark
(N
), Installed
=> True);
4478 Elmt
:= First_Elmt
(Used_Operations
(N
));
4479 while Present
(Elmt
) loop
4480 Set_Is_Potentially_Use_Visible
(Node
(Elmt
));
4488 -- Otherwise, create new list and attach to it the operations that are
4489 -- made use-visible by the clause.
4491 Set_Used_Operations
(N
, New_Elmt_List
);
4494 if E
/= Any_Type
then
4497 if Nkind
(Parent
(N
)) = N_Compilation_Unit
then
4498 if Nkind
(Id
) = N_Identifier
then
4499 Error_Msg_N
("type is not directly visible", Id
);
4501 elsif Is_Child_Unit
(Scope
(E
))
4502 and then Scope
(E
) /= System_Aux_Id
4504 Check_In_Previous_With_Clause
(N
, Prefix
(Id
));
4509 -- If the use_type_clause appears in a compilation unit context,
4510 -- check whether it comes from a unit that may appear in a
4511 -- limited_with_clause, for a better error message.
4513 if Nkind
(Parent
(N
)) = N_Compilation_Unit
4514 and then Nkind
(Id
) /= N_Identifier
4520 function Mentioned
(Nam
: Node_Id
) return Boolean;
4521 -- Check whether the prefix of expanded name for the type
4522 -- appears in the prefix of some limited_with_clause.
4528 function Mentioned
(Nam
: Node_Id
) return Boolean is
4530 return Nkind
(Name
(Item
)) = N_Selected_Component
4531 and then Chars
(Prefix
(Name
(Item
))) = Chars
(Nam
);
4535 Pref
:= Prefix
(Id
);
4536 Item
:= First
(Context_Items
(Parent
(N
)));
4537 while Present
(Item
) and then Item
/= N
loop
4538 if Nkind
(Item
) = N_With_Clause
4539 and then Limited_Present
(Item
)
4540 and then Mentioned
(Pref
)
4543 (Get_Msg_Id
, "premature usage of incomplete type");
4552 Mark_Ghost_Clause
(N
);
4553 end Analyze_Use_Type
;
4555 ------------------------
4556 -- Attribute_Renaming --
4557 ------------------------
4559 procedure Attribute_Renaming
(N
: Node_Id
) is
4560 Loc
: constant Source_Ptr
:= Sloc
(N
);
4561 Nam
: constant Node_Id
:= Name
(N
);
4562 Spec
: constant Node_Id
:= Specification
(N
);
4563 New_S
: constant Entity_Id
:= Defining_Unit_Name
(Spec
);
4564 Aname
: constant Name_Id
:= Attribute_Name
(Nam
);
4566 Form_Num
: Nat
:= 0;
4567 Expr_List
: List_Id
:= No_List
;
4569 Attr_Node
: Node_Id
;
4570 Body_Node
: Node_Id
;
4571 Param_Spec
: Node_Id
;
4574 Generate_Definition
(New_S
);
4576 -- This procedure is called in the context of subprogram renaming, and
4577 -- thus the attribute must be one that is a subprogram. All of those
4578 -- have at least one formal parameter, with the exceptions of the GNAT
4579 -- attribute 'Img, which GNAT treats as renameable.
4581 if Is_Empty_List
(Parameter_Specifications
(Spec
)) then
4582 if Aname
/= Name_Img
then
4584 ("subprogram renaming an attribute must have formals", N
);
4589 Param_Spec
:= First
(Parameter_Specifications
(Spec
));
4590 while Present
(Param_Spec
) loop
4591 Form_Num
:= Form_Num
+ 1;
4593 if Nkind
(Parameter_Type
(Param_Spec
)) /= N_Access_Definition
then
4594 Find_Type
(Parameter_Type
(Param_Spec
));
4596 -- The profile of the new entity denotes the base type (s) of
4597 -- the types given in the specification. For access parameters
4598 -- there are no subtypes involved.
4600 Rewrite
(Parameter_Type
(Param_Spec
),
4602 (Base_Type
(Entity
(Parameter_Type
(Param_Spec
))), Loc
));
4605 if No
(Expr_List
) then
4606 Expr_List
:= New_List
;
4609 Append_To
(Expr_List
,
4610 Make_Identifier
(Loc
,
4611 Chars
=> Chars
(Defining_Identifier
(Param_Spec
))));
4613 -- The expressions in the attribute reference are not freeze
4614 -- points. Neither is the attribute as a whole, see below.
4616 Set_Must_Not_Freeze
(Last
(Expr_List
));
4621 -- Immediate error if too many formals. Other mismatches in number or
4622 -- types of parameters are detected when we analyze the body of the
4623 -- subprogram that we construct.
4625 if Form_Num
> 2 then
4626 Error_Msg_N
("too many formals for attribute", N
);
4628 -- Error if the attribute reference has expressions that look like
4629 -- formal parameters.
4631 elsif Present
(Expressions
(Nam
)) then
4632 Error_Msg_N
("illegal expressions in attribute reference", Nam
);
4634 elsif Aname
in Name_Compose | Name_Exponent | Name_Leading_Part |
4635 Name_Pos | Name_Round | Name_Scaling |
4638 if Nkind
(N
) = N_Subprogram_Renaming_Declaration
4639 and then Present
(Corresponding_Formal_Spec
(N
))
4642 ("generic actual cannot be attribute involving universal type",
4646 ("attribute involving a universal type cannot be renamed",
4651 -- Rewrite attribute node to have a list of expressions corresponding to
4652 -- the subprogram formals. A renaming declaration is not a freeze point,
4653 -- and the analysis of the attribute reference should not freeze the
4654 -- type of the prefix. We use the original node in the renaming so that
4655 -- its source location is preserved, and checks on stream attributes are
4656 -- properly applied.
4658 Attr_Node
:= Relocate_Node
(Nam
);
4659 Set_Expressions
(Attr_Node
, Expr_List
);
4661 Set_Must_Not_Freeze
(Attr_Node
);
4662 Set_Must_Not_Freeze
(Prefix
(Nam
));
4664 -- Case of renaming a function
4666 if Nkind
(Spec
) = N_Function_Specification
then
4667 if Is_Procedure_Attribute_Name
(Aname
) then
4668 Error_Msg_N
("attribute can only be renamed as procedure", Nam
);
4672 Find_Type
(Result_Definition
(Spec
));
4673 Rewrite
(Result_Definition
(Spec
),
4675 (Base_Type
(Entity
(Result_Definition
(Spec
))), Loc
));
4678 Make_Subprogram_Body
(Loc
,
4679 Specification
=> Spec
,
4680 Declarations
=> New_List
,
4681 Handled_Statement_Sequence
=>
4682 Make_Handled_Sequence_Of_Statements
(Loc
,
4683 Statements
=> New_List
(
4684 Make_Simple_Return_Statement
(Loc
,
4685 Expression
=> Attr_Node
))));
4687 -- Case of renaming a procedure
4690 if not Is_Procedure_Attribute_Name
(Aname
) then
4691 Error_Msg_N
("attribute can only be renamed as function", Nam
);
4696 Make_Subprogram_Body
(Loc
,
4697 Specification
=> Spec
,
4698 Declarations
=> New_List
,
4699 Handled_Statement_Sequence
=>
4700 Make_Handled_Sequence_Of_Statements
(Loc
,
4701 Statements
=> New_List
(Attr_Node
)));
4704 -- Signal the ABE mechanism that the generated subprogram body has not
4705 -- ABE ramifications.
4707 Set_Was_Attribute_Reference
(Body_Node
);
4709 -- In case of tagged types we add the body of the generated function to
4710 -- the freezing actions of the type (because in the general case such
4711 -- type is still not frozen). We exclude from this processing generic
4712 -- formal subprograms found in instantiations.
4714 -- We must exclude restricted run-time libraries because
4715 -- entity AST_Handler is defined in package System.Aux_Dec which is not
4716 -- available in those platforms. Note that we cannot use the function
4717 -- Restricted_Profile (instead of Configurable_Run_Time_Mode) because
4718 -- the ZFP run-time library is not defined as a profile, and we do not
4719 -- want to deal with AST_Handler in ZFP mode.
4721 if not Configurable_Run_Time_Mode
4722 and then No
(Corresponding_Formal_Spec
(N
))
4723 and then not Is_RTE
(Etype
(Nam
), RE_AST_Handler
)
4726 P
: constant Node_Id
:= Prefix
(Nam
);
4729 -- The prefix of 'Img is an object that is evaluated for each call
4730 -- of the function that renames it.
4732 if Aname
= Name_Img
then
4733 Preanalyze_And_Resolve
(P
);
4735 -- For all other attribute renamings, the prefix is a subtype
4741 -- If the target type is not yet frozen, add the body to the
4742 -- actions to be elaborated at freeze time.
4744 if Is_Tagged_Type
(Etype
(P
))
4745 and then In_Open_Scopes
(Scope
(Etype
(P
)))
4747 Append_Freeze_Action
(Etype
(P
), Body_Node
);
4749 Rewrite
(N
, Body_Node
);
4751 Set_Etype
(New_S
, Base_Type
(Etype
(New_S
)));
4755 -- Generic formal subprograms or AST_Handler renaming
4758 Rewrite
(N
, Body_Node
);
4760 Set_Etype
(New_S
, Base_Type
(Etype
(New_S
)));
4763 if Is_Compilation_Unit
(New_S
) then
4765 ("a library unit can only rename another library unit", N
);
4768 -- We suppress elaboration warnings for the resulting entity, since
4769 -- clearly they are not needed, and more particularly, in the case
4770 -- of a generic formal subprogram, the resulting entity can appear
4771 -- after the instantiation itself, and thus look like a bogus case
4772 -- of access before elaboration.
4774 if Legacy_Elaboration_Checks
then
4775 Set_Suppress_Elaboration_Warnings
(New_S
);
4777 end Attribute_Renaming
;
4779 ----------------------
4780 -- Chain_Use_Clause --
4781 ----------------------
4783 procedure Chain_Use_Clause
(N
: Node_Id
) is
4784 Level
: Int
:= Scope_Stack
.Last
;
4790 if not Is_Compilation_Unit
(Current_Scope
)
4791 or else not Is_Child_Unit
(Current_Scope
)
4795 -- Common case for compilation unit
4797 elsif Defining_Entity
(Parent
(N
)) = Current_Scope
then
4801 -- If declaration appears in some other scope, it must be in some
4802 -- parent unit when compiling a child.
4804 Pack
:= Defining_Entity
(Parent
(N
));
4806 if not In_Open_Scopes
(Pack
) then
4809 -- If the use clause appears in an ancestor and we are in the
4810 -- private part of the immediate parent, the use clauses are
4811 -- already installed.
4813 elsif Pack
/= Scope
(Current_Scope
)
4814 and then In_Private_Part
(Scope
(Current_Scope
))
4819 -- Find entry for parent unit in scope stack
4821 while Scope_Stack
.Table
(Level
).Entity
/= Pack
loop
4827 Set_Next_Use_Clause
(N
,
4828 Scope_Stack
.Table
(Level
).First_Use_Clause
);
4829 Scope_Stack
.Table
(Level
).First_Use_Clause
:= N
;
4830 end Chain_Use_Clause
;
4832 ---------------------------
4833 -- Check_Frozen_Renaming --
4834 ---------------------------
4836 procedure Check_Frozen_Renaming
(N
: Node_Id
; Subp
: Entity_Id
) is
4841 if Is_Frozen
(Subp
) and then not Has_Completion
(Subp
) then
4844 (Parent
(Declaration_Node
(Subp
)), Defining_Entity
(N
));
4846 if Is_Entity_Name
(Name
(N
)) then
4847 Old_S
:= Entity
(Name
(N
));
4849 if not Is_Frozen
(Old_S
)
4850 and then Operating_Mode
/= Check_Semantics
4852 Append_Freeze_Action
(Old_S
, B_Node
);
4854 Insert_After
(N
, B_Node
);
4858 if Is_Intrinsic_Subprogram
(Old_S
)
4859 and then not In_Instance
4860 and then not Relaxed_RM_Semantics
4863 ("subprogram used in renaming_as_body cannot be intrinsic",
4868 Insert_After
(N
, B_Node
);
4872 end Check_Frozen_Renaming
;
4874 -------------------------------
4875 -- Set_Entity_Or_Discriminal --
4876 -------------------------------
4878 procedure Set_Entity_Or_Discriminal
(N
: Node_Id
; E
: Entity_Id
) is
4882 -- If the entity is not a discriminant, or else expansion is disabled,
4883 -- simply set the entity.
4885 if not In_Spec_Expression
4886 or else Ekind
(E
) /= E_Discriminant
4887 or else Inside_A_Generic
4889 Set_Entity_With_Checks
(N
, E
);
4891 -- The replacement of a discriminant by the corresponding discriminal
4892 -- is not done for a task discriminant that appears in a default
4893 -- expression of an entry parameter. See Exp_Ch2.Expand_Discriminant
4894 -- for details on their handling.
4896 elsif Is_Concurrent_Type
(Scope
(E
)) then
4899 and then Nkind
(P
) not in
4900 N_Parameter_Specification | N_Component_Declaration
4906 and then Nkind
(P
) = N_Parameter_Specification
4910 -- Don't replace a non-qualified discriminant in strict preanalysis
4911 -- mode since it can lead to errors during full analysis when the
4912 -- discriminant gets referenced later.
4914 -- This can occur in situations where a protected type contains
4915 -- an expression function which references a non-prefixed
4919 and then Preanalysis_Active
4920 and then Inside_Preanalysis_Without_Freezing
= 0
4925 Set_Entity
(N
, Discriminal
(E
));
4928 -- Otherwise, this is a discriminant in a context in which
4929 -- it is a reference to the corresponding parameter of the
4930 -- init proc for the enclosing type.
4933 Set_Entity
(N
, Discriminal
(E
));
4935 end Set_Entity_Or_Discriminal
;
4937 -----------------------------------
4938 -- Check_In_Previous_With_Clause --
4939 -----------------------------------
4941 procedure Check_In_Previous_With_Clause
(N
, Nam
: Node_Id
) is
4942 Pack
: constant Entity_Id
:= Entity
(Original_Node
(Nam
));
4947 Item
:= First
(Context_Items
(Parent
(N
)));
4948 while Present
(Item
) and then Item
/= N
loop
4949 if Nkind
(Item
) = N_With_Clause
4951 -- Protect the frontend against previous critical errors
4953 and then Nkind
(Name
(Item
)) /= N_Selected_Component
4954 and then Entity
(Name
(Item
)) = Pack
4958 -- Find root library unit in with_clause
4960 while Nkind
(Par
) = N_Expanded_Name
loop
4961 Par
:= Prefix
(Par
);
4964 if Is_Child_Unit
(Entity
(Original_Node
(Par
))) then
4965 Error_Msg_NE
("& is not directly visible", Par
, Entity
(Par
));
4974 -- On exit, package is not mentioned in a previous with_clause.
4975 -- Check if its prefix is.
4977 if Nkind
(Nam
) = N_Expanded_Name
then
4978 Check_In_Previous_With_Clause
(N
, Prefix
(Nam
));
4980 elsif Pack
/= Any_Id
then
4981 Error_Msg_NE
("& is not visible", Nam
, Pack
);
4983 end Check_In_Previous_With_Clause
;
4985 ---------------------------------
4986 -- Check_Library_Unit_Renaming --
4987 ---------------------------------
4989 procedure Check_Library_Unit_Renaming
(N
: Node_Id
; Old_E
: Entity_Id
) is
4993 if Nkind
(Parent
(N
)) /= N_Compilation_Unit
then
4996 -- Check for library unit. Note that we used to check for the scope
4997 -- being Standard here, but that was wrong for Standard itself.
4999 elsif not Is_Compilation_Unit
(Old_E
)
5000 and then not Is_Child_Unit
(Old_E
)
5002 Error_Msg_N
("renamed unit must be a library unit", Name
(N
));
5004 -- Entities defined in Standard (operators and boolean literals) cannot
5005 -- be renamed as library units.
5007 elsif Scope
(Old_E
) = Standard_Standard
5008 and then Sloc
(Old_E
) = Standard_Location
5010 Error_Msg_N
("renamed unit must be a library unit", Name
(N
));
5012 elsif Present
(Parent_Spec
(N
))
5013 and then Nkind
(Unit
(Parent_Spec
(N
))) = N_Generic_Package_Declaration
5014 and then not Is_Child_Unit
(Old_E
)
5017 ("renamed unit must be a child unit of generic parent", Name
(N
));
5019 elsif Nkind
(N
) in N_Generic_Renaming_Declaration
5020 and then Nkind
(Name
(N
)) = N_Expanded_Name
5021 and then Is_Generic_Instance
(Entity
(Prefix
(Name
(N
))))
5022 and then Is_Generic_Unit
(Old_E
)
5025 ("renamed generic unit must be a library unit", Name
(N
));
5027 elsif Is_Package_Or_Generic_Package
(Old_E
) then
5029 -- Inherit categorization flags
5031 New_E
:= Defining_Entity
(N
);
5032 Set_Is_Pure
(New_E
, Is_Pure
(Old_E
));
5033 Set_Is_Preelaborated
(New_E
, Is_Preelaborated
(Old_E
));
5034 Set_Is_Remote_Call_Interface
(New_E
,
5035 Is_Remote_Call_Interface
(Old_E
));
5036 Set_Is_Remote_Types
(New_E
, Is_Remote_Types
(Old_E
));
5037 Set_Is_Shared_Passive
(New_E
, Is_Shared_Passive
(Old_E
));
5039 end Check_Library_Unit_Renaming
;
5041 ------------------------
5042 -- Enclosing_Instance --
5043 ------------------------
5045 function Enclosing_Instance
return Entity_Id
is
5049 if not Is_Generic_Instance
(Current_Scope
) then
5053 S
:= Scope
(Current_Scope
);
5054 while S
/= Standard_Standard
loop
5055 if Is_Generic_Instance
(S
) then
5063 end Enclosing_Instance
;
5069 procedure End_Scope
is
5075 Id
:= First_Entity
(Current_Scope
);
5076 while Present
(Id
) loop
5077 -- An entity in the current scope is not necessarily the first one
5078 -- on its homonym chain. Find its predecessor if any,
5079 -- If it is an internal entity, it will not be in the visibility
5080 -- chain altogether, and there is nothing to unchain.
5082 if Id
/= Current_Entity
(Id
) then
5083 Prev
:= Current_Entity
(Id
);
5084 while Present
(Prev
)
5085 and then Homonym
(Prev
) /= Id
5087 Prev
:= Homonym
(Prev
);
5090 -- Skip to end of loop if Id is not in the visibility chain
5100 Set_Is_Immediately_Visible
(Id
, False);
5102 Outer
:= Homonym
(Id
);
5103 while Present
(Outer
) and then Scope
(Outer
) = Current_Scope
loop
5104 Outer
:= Homonym
(Outer
);
5107 -- Reset homonym link of other entities, but do not modify link
5108 -- between entities in current scope, so that the back-end can have
5109 -- a proper count of local overloadings.
5112 Set_Name_Entity_Id
(Chars
(Id
), Outer
);
5114 elsif Scope
(Prev
) /= Scope
(Id
) then
5115 Set_Homonym
(Prev
, Outer
);
5122 -- If the scope generated freeze actions, place them before the
5123 -- current declaration and analyze them. Type declarations and
5124 -- the bodies of initialization procedures can generate such nodes.
5125 -- We follow the parent chain until we reach a list node, which is
5126 -- the enclosing list of declarations. If the list appears within
5127 -- a protected definition, move freeze nodes outside the protected
5131 (Scope_Stack
.Table
(Scope_Stack
.Last
).Pending_Freeze_Actions
)
5135 L
: constant List_Id
:= Scope_Stack
.Table
5136 (Scope_Stack
.Last
).Pending_Freeze_Actions
;
5139 if Is_Itype
(Current_Scope
) then
5140 Decl
:= Associated_Node_For_Itype
(Current_Scope
);
5142 Decl
:= Parent
(Current_Scope
);
5147 while not Is_List_Member
(Decl
)
5148 or else Nkind
(Parent
(Decl
)) in N_Protected_Definition
5151 Decl
:= Parent
(Decl
);
5154 Insert_List_Before_And_Analyze
(Decl
, L
);
5162 ---------------------
5163 -- End_Use_Clauses --
5164 ---------------------
5166 procedure End_Use_Clauses
(Clause
: Node_Id
) is
5170 -- Remove use_type_clauses first, because they affect the visibility of
5171 -- operators in subsequent used packages.
5174 while Present
(U
) loop
5175 if Nkind
(U
) = N_Use_Type_Clause
then
5179 Next_Use_Clause
(U
);
5183 while Present
(U
) loop
5184 if Nkind
(U
) = N_Use_Package_Clause
then
5185 End_Use_Package
(U
);
5188 Next_Use_Clause
(U
);
5190 end End_Use_Clauses
;
5192 ---------------------
5193 -- End_Use_Package --
5194 ---------------------
5196 procedure End_Use_Package
(N
: Node_Id
) is
5198 Pack_Name
: Node_Id
;
5202 function Is_Primitive_Operator_In_Use
5204 F
: Entity_Id
) return Boolean;
5205 -- Check whether Op is a primitive operator of a use-visible type
5207 ----------------------------------
5208 -- Is_Primitive_Operator_In_Use --
5209 ----------------------------------
5211 function Is_Primitive_Operator_In_Use
5213 F
: Entity_Id
) return Boolean
5215 T
: constant Entity_Id
:= Base_Type
(Etype
(F
));
5217 return In_Use
(T
) and then Scope
(T
) = Scope
(Op
);
5218 end Is_Primitive_Operator_In_Use
;
5220 -- Start of processing for End_Use_Package
5223 Pack_Name
:= Name
(N
);
5225 -- Test that Pack_Name actually denotes a package before processing
5227 if Is_Entity_Name
(Pack_Name
)
5228 and then Ekind
(Entity
(Pack_Name
)) = E_Package
5230 Pack
:= Entity
(Pack_Name
);
5232 if In_Open_Scopes
(Pack
) then
5235 elsif not Redundant_Use
(Pack_Name
) then
5236 Set_In_Use
(Pack
, False);
5237 Set_Current_Use_Clause
(Pack
, Empty
);
5239 Id
:= First_Entity
(Pack
);
5240 while Present
(Id
) loop
5242 -- Preserve use-visibility of operators that are primitive
5243 -- operators of a type that is use-visible through an active
5246 if Nkind
(Id
) = N_Defining_Operator_Symbol
5248 (Is_Primitive_Operator_In_Use
(Id
, First_Formal
(Id
))
5250 (Present
(Next_Formal
(First_Formal
(Id
)))
5252 Is_Primitive_Operator_In_Use
5253 (Id
, Next_Formal
(First_Formal
(Id
)))))
5257 Set_Is_Potentially_Use_Visible
(Id
, False);
5260 if Is_Private_Type
(Id
)
5261 and then Present
(Full_View
(Id
))
5263 Set_Is_Potentially_Use_Visible
(Full_View
(Id
), False);
5269 if Present
(Renamed_Entity
(Pack
)) then
5270 Set_In_Use
(Renamed_Entity
(Pack
), False);
5271 Set_Current_Use_Clause
(Renamed_Entity
(Pack
), Empty
);
5274 if Chars
(Pack
) = Name_System
5275 and then Scope
(Pack
) = Standard_Standard
5276 and then Present_System_Aux
5278 Id
:= First_Entity
(System_Aux_Id
);
5279 while Present
(Id
) loop
5280 Set_Is_Potentially_Use_Visible
(Id
, False);
5282 if Is_Private_Type
(Id
)
5283 and then Present
(Full_View
(Id
))
5285 Set_Is_Potentially_Use_Visible
(Full_View
(Id
), False);
5291 Set_In_Use
(System_Aux_Id
, False);
5294 Set_Redundant_Use
(Pack_Name
, False);
5298 if Present
(Hidden_By_Use_Clause
(N
)) then
5299 Elmt
:= First_Elmt
(Hidden_By_Use_Clause
(N
));
5300 while Present
(Elmt
) loop
5302 E
: constant Entity_Id
:= Node
(Elmt
);
5305 -- Reset either Use_Visibility or Direct_Visibility, depending
5306 -- on how the entity was hidden by the use clause.
5308 if In_Use
(Scope
(E
))
5309 and then Used_As_Generic_Actual
(Scope
(E
))
5311 Set_Is_Potentially_Use_Visible
(Node
(Elmt
));
5313 Set_Is_Immediately_Visible
(Node
(Elmt
));
5320 Set_Hidden_By_Use_Clause
(N
, No_Elist
);
5322 end End_Use_Package
;
5328 procedure End_Use_Type
(N
: Node_Id
) is
5333 -- Start of processing for End_Use_Type
5336 Id
:= Subtype_Mark
(N
);
5338 -- A call to Rtsfind may occur while analyzing a use_type_clause, in
5339 -- which case the type marks are not resolved yet, so guard against that
5342 if Is_Entity_Name
(Id
) and then Present
(Entity
(Id
)) then
5345 if T
= Any_Type
or else From_Limited_With
(T
) then
5348 -- Note that the use_type_clause may mention a subtype of the type
5349 -- whose primitive operations have been made visible. Here as
5350 -- elsewhere, it is the base type that matters for visibility.
5352 elsif In_Open_Scopes
(Scope
(Base_Type
(T
))) then
5355 elsif not Redundant_Use
(Id
) then
5356 Set_In_Use
(T
, False);
5357 Set_In_Use
(Base_Type
(T
), False);
5358 Set_Current_Use_Clause
(T
, Empty
);
5359 Set_Current_Use_Clause
(Base_Type
(T
), Empty
);
5361 -- See Use_One_Type for the rationale. This is a bit on the naive
5362 -- side, but should be good enough in practice.
5364 if Is_Tagged_Type
(T
) then
5365 Set_In_Use
(Class_Wide_Type
(T
), False);
5370 if Is_Empty_Elmt_List
(Used_Operations
(N
)) then
5374 Elmt
:= First_Elmt
(Used_Operations
(N
));
5375 while Present
(Elmt
) loop
5376 Set_Is_Potentially_Use_Visible
(Node
(Elmt
), False);
5382 --------------------
5383 -- Entity_Of_Unit --
5384 --------------------
5386 function Entity_Of_Unit
(U
: Node_Id
) return Entity_Id
is
5388 if Nkind
(U
) = N_Package_Instantiation
and then Analyzed
(U
) then
5389 return Defining_Entity
(Instance_Spec
(U
));
5391 return Defining_Entity
(U
);
5395 --------------------------------------
5396 -- Error_Missing_With_Of_Known_Unit --
5397 --------------------------------------
5399 procedure Error_Missing_With_Of_Known_Unit
(Pkg
: Node_Id
) is
5400 Selectors
: array (1 .. 6) of Node_Id
;
5401 -- Contains the chars of the full package name up to maximum number
5402 -- allowed as per Errout.Error_Msg_Name_# variables.
5404 Count
: Integer := Selectors
'First;
5405 -- Count of selector names forming the full package name
5407 Current_Pkg
: Node_Id
:= Parent
(Pkg
);
5410 Selectors
(Count
) := Pkg
;
5412 -- Gather all the selectors we can display
5414 while Nkind
(Current_Pkg
) = N_Selected_Component
5415 and then Is_Known_Unit
(Current_Pkg
)
5416 and then Count
< Selectors
'Length
5419 Selectors
(Count
) := Selector_Name
(Current_Pkg
);
5420 Current_Pkg
:= Parent
(Current_Pkg
);
5423 -- Display the error message based on the number of selectors found
5427 Error_Msg_Node_1
:= Selectors
(1);
5428 Error_Msg_N
-- CODEFIX
5429 ("\\missing `WITH &;`", Pkg
);
5431 Error_Msg_Node_1
:= Selectors
(1);
5432 Error_Msg_Node_2
:= Selectors
(2);
5433 Error_Msg_N
-- CODEFIX
5434 ("\\missing `WITH &.&;`", Pkg
);
5436 Error_Msg_Node_1
:= Selectors
(1);
5437 Error_Msg_Node_2
:= Selectors
(2);
5438 Error_Msg_Node_3
:= Selectors
(3);
5439 Error_Msg_N
-- CODEFIX
5440 ("\\missing `WITH &.&.&;`", Pkg
);
5442 Error_Msg_Node_1
:= Selectors
(1);
5443 Error_Msg_Node_2
:= Selectors
(2);
5444 Error_Msg_Node_3
:= Selectors
(3);
5445 Error_Msg_Node_3
:= Selectors
(4);
5446 Error_Msg_N
-- CODEFIX
5447 ("\\missing `WITH &.&.&.&;`", Pkg
);
5449 Error_Msg_Node_1
:= Selectors
(1);
5450 Error_Msg_Node_2
:= Selectors
(2);
5451 Error_Msg_Node_3
:= Selectors
(3);
5452 Error_Msg_Node_3
:= Selectors
(4);
5453 Error_Msg_Node_3
:= Selectors
(5);
5454 Error_Msg_N
-- CODEFIX
5455 ("\\missing `WITH &.&.&.&.&;`", Pkg
);
5457 Error_Msg_Node_1
:= Selectors
(1);
5458 Error_Msg_Node_2
:= Selectors
(2);
5459 Error_Msg_Node_3
:= Selectors
(3);
5460 Error_Msg_Node_4
:= Selectors
(4);
5461 Error_Msg_Node_5
:= Selectors
(5);
5462 Error_Msg_Node_6
:= Selectors
(6);
5463 Error_Msg_N
-- CODEFIX
5464 ("\\missing `WITH &.&.&.&.&.&;`", Pkg
);
5466 raise Program_Error
;
5468 end Error_Missing_With_Of_Known_Unit
;
5470 --------------------
5471 -- Is_Self_Hidden --
5472 --------------------
5474 function Is_Self_Hidden
(E
: Entity_Id
) return Boolean is
5476 if Is_Not_Self_Hidden
(E
) then
5477 return Ekind
(E
) = E_Void
;
5483 ----------------------
5484 -- Find_Direct_Name --
5485 ----------------------
5487 procedure Find_Direct_Name
(N
: Node_Id
) is
5492 Homonyms
: Entity_Id
;
5493 -- Saves start of homonym chain
5495 Inst
: Entity_Id
:= Empty
;
5496 -- Enclosing instance, if any
5498 Nvis_Entity
: Boolean;
5499 -- Set True to indicate that there is at least one entity on the homonym
5500 -- chain which, while not visible, is visible enough from the user point
5501 -- of view to warrant an error message of "not visible" rather than
5504 Nvis_Is_Private_Subprg
: Boolean := False;
5505 -- Ada 2005 (AI-262): Set True to indicate that a form of Beaujolais
5506 -- effect concerning library subprograms has been detected. Used to
5507 -- generate the precise error message.
5509 function From_Actual_Package
(E
: Entity_Id
) return Boolean;
5510 -- Returns true if the entity is an actual for a package that is itself
5511 -- an actual for a formal package of the current instance. Such an
5512 -- entity requires special handling because it may be use-visible but
5513 -- hides directly visible entities defined outside the instance, because
5514 -- the corresponding formal did so in the generic.
5516 function Is_Actual_Parameter
return Boolean;
5517 -- This function checks if the node N is an identifier that is an actual
5518 -- parameter of a procedure call. If so it returns True, otherwise it
5519 -- return False. The reason for this check is that at this stage we do
5520 -- not know what procedure is being called if the procedure might be
5521 -- overloaded, so it is premature to go setting referenced flags or
5522 -- making calls to Generate_Reference. We will wait till Resolve_Actuals
5523 -- for that processing.
5524 -- Note: there is a similar routine Sem_Util.Is_Actual_Parameter, but
5525 -- it works for both function and procedure calls, while here we are
5526 -- only concerned with procedure calls (and with entry calls as well,
5527 -- but they are parsed as procedure calls and only later rewritten to
5530 function Known_But_Invisible
(E
: Entity_Id
) return Boolean;
5531 -- This function determines whether a reference to the entity E, which
5532 -- is not visible, can reasonably be considered to be known to the
5533 -- writer of the reference. This is a heuristic test, used only for
5534 -- the purposes of figuring out whether we prefer to complain that an
5535 -- entity is undefined or invisible (and identify the declaration of
5536 -- the invisible entity in the latter case). The point here is that we
5537 -- don't want to complain that something is invisible and then point to
5538 -- something entirely mysterious to the writer.
5540 procedure Nvis_Messages
;
5541 -- Called if there are no visible entries for N, but there is at least
5542 -- one non-directly visible, or hidden declaration. This procedure
5543 -- outputs an appropriate set of error messages.
5545 procedure Undefined
(Nvis
: Boolean);
5546 -- This function is called if the current node has no corresponding
5547 -- visible entity or entities. The value set in Msg indicates whether
5548 -- an error message was generated (multiple error messages for the
5549 -- same variable are generally suppressed, see body for details).
5550 -- Msg is True if an error message was generated, False if not. This
5551 -- value is used by the caller to determine whether or not to output
5552 -- additional messages where appropriate. The parameter is set False
5553 -- to get the message "X is undefined", and True to get the message
5554 -- "X is not visible".
5556 -------------------------
5557 -- From_Actual_Package --
5558 -------------------------
5560 function From_Actual_Package
(E
: Entity_Id
) return Boolean is
5561 Scop
: constant Entity_Id
:= Scope
(E
);
5562 -- Declared scope of candidate entity
5564 function Declared_In_Actual
(Pack
: Entity_Id
) return Boolean;
5565 -- Recursive function that does the work and examines actuals of
5566 -- actual packages of current instance.
5568 ------------------------
5569 -- Declared_In_Actual --
5570 ------------------------
5572 function Declared_In_Actual
(Pack
: Entity_Id
) return Boolean is
5573 pragma Assert
(Ekind
(Pack
) = E_Package
);
5576 if No
(Associated_Formal_Package
(Pack
)) then
5580 Act
:= First_Entity
(Pack
);
5581 while Present
(Act
) loop
5582 if Renamed_Entity
(Pack
) = Scop
then
5585 -- Check for end of list of actuals
5587 elsif Ekind
(Act
) = E_Package
5588 and then Renamed_Entity
(Act
) = Pack
5592 elsif Ekind
(Act
) = E_Package
5593 and then Declared_In_Actual
(Act
)
5603 end Declared_In_Actual
;
5609 -- Start of processing for From_Actual_Package
5612 if not In_Instance
then
5616 Inst
:= Current_Scope
;
5617 while Present
(Inst
)
5618 and then Ekind
(Inst
) /= E_Package
5619 and then not Is_Generic_Instance
(Inst
)
5621 Inst
:= Scope
(Inst
);
5628 Act
:= First_Entity
(Inst
);
5629 while Present
(Act
) loop
5630 if Ekind
(Act
) = E_Package
5631 and then Declared_In_Actual
(Act
)
5641 end From_Actual_Package
;
5643 -------------------------
5644 -- Is_Actual_Parameter --
5645 -------------------------
5647 function Is_Actual_Parameter
return Boolean is
5649 if Nkind
(N
) = N_Identifier
then
5650 case Nkind
(Parent
(N
)) is
5651 when N_Procedure_Call_Statement
=>
5652 return Is_List_Member
(N
)
5653 and then List_Containing
(N
) =
5654 Parameter_Associations
(Parent
(N
));
5656 when N_Parameter_Association
=>
5657 return N
= Explicit_Actual_Parameter
(Parent
(N
))
5658 and then Nkind
(Parent
(Parent
(N
))) =
5659 N_Procedure_Call_Statement
;
5667 end Is_Actual_Parameter
;
5669 -------------------------
5670 -- Known_But_Invisible --
5671 -------------------------
5673 function Known_But_Invisible
(E
: Entity_Id
) return Boolean is
5674 Fname
: File_Name_Type
;
5677 -- Entities in Standard are always considered to be known
5679 if Sloc
(E
) <= Standard_Location
then
5682 -- An entity that does not come from source is always considered
5683 -- to be unknown, since it is an artifact of code expansion.
5685 elsif not Comes_From_Source
(E
) then
5689 -- Here we have an entity that is not from package Standard, and
5690 -- which comes from Source. See if it comes from an internal file.
5692 Fname
:= Unit_File_Name
(Get_Source_Unit
(E
));
5694 -- Case of from internal file
5696 if In_Internal_Unit
(E
) then
5698 -- Private part entities in internal files are never considered
5699 -- to be known to the writer of normal application code.
5701 if Is_Hidden
(E
) then
5705 -- Entities from System packages other than System and
5706 -- System.Storage_Elements are not considered to be known.
5707 -- System.Auxxxx files are also considered known to the user.
5709 -- Should refine this at some point to generally distinguish
5710 -- between known and unknown internal files ???
5712 Get_Name_String
(Fname
);
5717 Name_Buffer
(1 .. 2) /= "s-"
5719 Name_Buffer
(3 .. 8) = "stoele"
5721 Name_Buffer
(3 .. 5) = "aux";
5723 -- If not an internal file, then entity is definitely known, even if
5724 -- it is in a private part (the message generated will note that it
5725 -- is in a private part).
5730 end Known_But_Invisible
;
5736 procedure Nvis_Messages
is
5737 Comp_Unit
: Node_Id
;
5739 Found
: Boolean := False;
5740 Hidden
: Boolean := False;
5744 -- Ada 2005 (AI-262): Generate a precise error concerning the
5745 -- Beaujolais effect that was previously detected
5747 if Nvis_Is_Private_Subprg
then
5749 pragma Assert
(Nkind
(E2
) = N_Defining_Identifier
5750 and then Ekind
(E2
) = E_Function
5751 and then Scope
(E2
) = Standard_Standard
5752 and then Has_Private_With
(E2
));
5754 -- Find the sloc corresponding to the private with'ed unit
5756 Comp_Unit
:= Cunit
(Current_Sem_Unit
);
5757 Error_Msg_Sloc
:= No_Location
;
5759 Item
:= First
(Context_Items
(Comp_Unit
));
5760 while Present
(Item
) loop
5761 if Nkind
(Item
) = N_With_Clause
5762 and then Private_Present
(Item
)
5763 and then Entity
(Name
(Item
)) = E2
5765 Error_Msg_Sloc
:= Sloc
(Item
);
5772 pragma Assert
(Error_Msg_Sloc
/= No_Location
);
5774 Error_Msg_N
("(Ada 2005): hidden by private with clause #", N
);
5778 Undefined
(Nvis
=> True);
5782 -- First loop does hidden declarations
5785 while Present
(Ent
) loop
5786 if Is_Potentially_Use_Visible
(Ent
) then
5788 Error_Msg_N
-- CODEFIX
5789 ("multiple use clauses cause hiding!", N
);
5793 Error_Msg_Sloc
:= Sloc
(Ent
);
5794 Error_Msg_N
-- CODEFIX
5795 ("hidden declaration#!", N
);
5798 Ent
:= Homonym
(Ent
);
5801 -- If we found hidden declarations, then that's enough, don't
5802 -- bother looking for non-visible declarations as well.
5808 -- Second loop does non-directly visible declarations
5811 while Present
(Ent
) loop
5812 if not Is_Potentially_Use_Visible
(Ent
) then
5814 -- Do not bother the user with unknown entities
5816 if not Known_But_Invisible
(Ent
) then
5820 Error_Msg_Sloc
:= Sloc
(Ent
);
5822 -- Output message noting that there is a non-visible
5823 -- declaration, distinguishing the private part case.
5825 if Is_Hidden
(Ent
) then
5826 Error_Msg_N
("non-visible (private) declaration#!", N
);
5828 -- If the entity is declared in a generic package, it
5829 -- cannot be visible, so there is no point in adding it
5830 -- to the list of candidates if another homograph from a
5831 -- non-generic package has been seen.
5833 elsif Ekind
(Scope
(Ent
)) = E_Generic_Package
5839 -- When the entity comes from a generic instance the
5840 -- normal error message machinery will give the line
5841 -- number of the generic package and the location of
5842 -- the generic instance, but not the name of the
5845 -- So, in order to give more descriptive error messages
5846 -- in this case, we include the name of the generic
5849 if Is_Generic_Instance
(Scope
(Ent
)) then
5850 Error_Msg_Name_1
:= Chars
(Scope
(Ent
));
5851 Error_Msg_N
-- CODEFIX
5852 ("non-visible declaration from %#!", N
);
5854 -- Otherwise print the message normally
5857 Error_Msg_N
-- CODEFIX
5858 ("non-visible declaration#!", N
);
5861 if Ekind
(Scope
(Ent
)) /= E_Generic_Package
then
5865 if Is_Compilation_Unit
(Ent
)
5867 Nkind
(Parent
(Parent
(N
))) = N_Use_Package_Clause
5869 Error_Msg_Qual_Level
:= 99;
5870 Error_Msg_NE
-- CODEFIX
5871 ("\\missing `WITH &;`", N
, Ent
);
5872 Error_Msg_Qual_Level
:= 0;
5875 if Ekind
(Ent
) = E_Discriminant
5876 and then Present
(Corresponding_Discriminant
(Ent
))
5877 and then Scope
(Corresponding_Discriminant
(Ent
)) =
5881 ("inherited discriminant not allowed here" &
5882 " (RM 3.8 (12), 3.8.1 (6))!", N
);
5886 -- Set entity and its containing package as referenced. We
5887 -- can't be sure of this, but this seems a better choice
5888 -- to avoid unused entity messages.
5890 if Comes_From_Source
(Ent
) then
5891 Set_Referenced
(Ent
);
5892 Set_Referenced
(Cunit_Entity
(Get_Source_Unit
(Ent
)));
5897 Ent
:= Homonym
(Ent
);
5906 procedure Undefined
(Nvis
: Boolean) is
5907 Emsg
: Error_Msg_Id
;
5910 -- We should never find an undefined internal name. If we do, then
5911 -- see if we have previous errors. If so, ignore on the grounds that
5912 -- it is probably a cascaded message (e.g. a block label from a badly
5913 -- formed block). If no previous errors, then we have a real internal
5914 -- error of some kind so raise an exception.
5916 if Is_Internal_Name
(Chars
(N
)) then
5917 if Total_Errors_Detected
/= 0 then
5920 raise Program_Error
;
5924 -- A very specialized error check, if the undefined variable is
5925 -- a case tag, and the case type is an enumeration type, check
5926 -- for a possible misspelling, and if so, modify the identifier
5928 -- Named aggregate should also be handled similarly ???
5930 if Nkind
(N
) = N_Identifier
5931 and then Nkind
(Parent
(N
)) = N_Case_Statement_Alternative
5934 Case_Stm
: constant Node_Id
:= Parent
(Parent
(N
));
5935 Case_Typ
: constant Entity_Id
:= Etype
(Expression
(Case_Stm
));
5940 if Is_Enumeration_Type
(Case_Typ
)
5941 and then not Is_Standard_Character_Type
(Case_Typ
)
5943 Lit
:= First_Literal
(Case_Typ
);
5944 Get_Name_String
(Chars
(Lit
));
5946 if Chars
(Lit
) /= Chars
(N
)
5947 and then Is_Bad_Spelling_Of
(Chars
(N
), Chars
(Lit
))
5949 Error_Msg_Node_2
:= Lit
;
5950 Error_Msg_N
-- CODEFIX
5951 ("& is undefined, assume misspelling of &", N
);
5952 Rewrite
(N
, New_Occurrence_Of
(Lit
, Sloc
(N
)));
5961 -- Normal processing
5963 Set_Entity
(N
, Any_Id
);
5964 Set_Etype
(N
, Any_Type
);
5966 -- We use the table Urefs to keep track of entities for which we
5967 -- have issued errors for undefined references. Multiple errors
5968 -- for a single name are normally suppressed, however we modify
5969 -- the error message to alert the programmer to this effect.
5971 for J
in Urefs
.First
.. Urefs
.Last
loop
5972 if Chars
(N
) = Chars
(Urefs
.Table
(J
).Node
) then
5973 if Urefs
.Table
(J
).Err
/= No_Error_Msg
5974 and then Sloc
(N
) /= Urefs
.Table
(J
).Loc
5976 Error_Msg_Node_1
:= Urefs
.Table
(J
).Node
;
5978 if Urefs
.Table
(J
).Nvis
then
5979 Change_Error_Text
(Urefs
.Table
(J
).Err
,
5980 "& is not visible (more references follow)");
5982 Change_Error_Text
(Urefs
.Table
(J
).Err
,
5983 "& is undefined (more references follow)");
5986 Urefs
.Table
(J
).Err
:= No_Error_Msg
;
5989 -- Although we will set Msg False, and thus suppress the
5990 -- message, we also set Error_Posted True, to avoid any
5991 -- cascaded messages resulting from the undefined reference.
5994 Set_Error_Posted
(N
);
5999 -- If entry not found, this is first undefined occurrence
6002 Error_Msg_N
("& is not visible!", N
);
6006 Error_Msg_N
("& is undefined!", N
);
6009 -- A very bizarre special check, if the undefined identifier
6010 -- is Put or Put_Line, then add a special error message (since
6011 -- this is a very common error for beginners to make).
6013 if Chars
(N
) in Name_Put | Name_Put_Line
then
6014 Error_Msg_N
-- CODEFIX
6015 ("\\possible missing `WITH Ada.Text_'I'O; " &
6016 "USE Ada.Text_'I'O`!", N
);
6018 -- Another special check if N is the prefix of a selected
6019 -- component which is a known unit: add message complaining
6020 -- about missing with for this unit.
6022 elsif Nkind
(Parent
(N
)) = N_Selected_Component
6023 and then N
= Prefix
(Parent
(N
))
6024 and then Is_Known_Unit
(Parent
(N
))
6026 Error_Missing_With_Of_Known_Unit
(N
);
6029 -- Now check for possible misspellings
6033 Ematch
: Entity_Id
:= Empty
;
6035 for Nam
in First_Name_Id
.. Last_Name_Id
loop
6036 E
:= Get_Name_Entity_Id
(Nam
);
6039 and then (Is_Immediately_Visible
(E
)
6041 Is_Potentially_Use_Visible
(E
))
6043 if Is_Bad_Spelling_Of
(Chars
(N
), Nam
) then
6050 if Present
(Ematch
) then
6051 Error_Msg_NE
-- CODEFIX
6052 ("\possible misspelling of&", N
, Ematch
);
6057 -- Make entry in undefined references table unless the full errors
6058 -- switch is set, in which case by refraining from generating the
6059 -- table entry we guarantee that we get an error message for every
6060 -- undefined reference. The entry is not added if we are ignoring
6063 if not All_Errors_Mode
6064 and then Ignore_Errors_Enable
= 0
6065 and then not Get_Ignore_Errors
6079 Nested_Inst
: Entity_Id
:= Empty
;
6080 -- The entity of a nested instance which appears within Inst (if any)
6082 -- Start of processing for Find_Direct_Name
6085 -- If the entity pointer is already set, this is an internal node, or
6086 -- a node that is analyzed more than once, after a tree modification.
6087 -- In such a case there is no resolution to perform, just set the type.
6089 if Present
(Entity
(N
)) then
6090 if Is_Type
(Entity
(N
)) then
6091 Set_Etype
(N
, Entity
(N
));
6095 Entyp
: constant Entity_Id
:= Etype
(Entity
(N
));
6098 -- One special case here. If the Etype field is already set,
6099 -- and references the packed array type corresponding to the
6100 -- etype of the referenced entity, then leave it alone. This
6101 -- happens for trees generated from Exp_Pakd, where expressions
6102 -- can be deliberately "mis-typed" to the packed array type.
6104 if Is_Packed_Array
(Entyp
)
6105 and then Present
(Etype
(N
))
6106 and then Etype
(N
) = Packed_Array_Impl_Type
(Entyp
)
6110 -- If not that special case, then just reset the Etype
6113 Set_Etype
(N
, Entyp
);
6118 -- Although the marking of use clauses happens at the end of
6119 -- Find_Direct_Name, a certain case where a generic actual satisfies
6120 -- a use clause must be checked here due to how the generic machinery
6121 -- handles the analysis of said actuals.
6124 and then Nkind
(Parent
(N
)) = N_Generic_Association
6126 Mark_Use_Clauses
(Entity
(N
));
6132 -- Preserve relevant elaboration-related attributes of the context which
6133 -- are no longer available or very expensive to recompute once analysis,
6134 -- resolution, and expansion are over.
6136 if Nkind
(N
) = N_Identifier
then
6137 Mark_Elaboration_Attributes
6144 -- Here if Entity pointer was not set, we need full visibility analysis
6145 -- First we generate debugging output if the debug E flag is set.
6147 if Debug_Flag_E
then
6148 Write_Str
("Looking for ");
6149 Write_Name
(Chars
(N
));
6153 Homonyms
:= Current_Entity
(N
);
6154 Nvis_Entity
:= False;
6157 while Present
(E
) loop
6159 -- If entity is immediately visible or potentially use visible, then
6160 -- process the entity and we are done.
6162 if Is_Immediately_Visible
(E
) then
6163 goto Immediately_Visible_Entity
;
6165 elsif Is_Potentially_Use_Visible
(E
) then
6166 goto Potentially_Use_Visible_Entity
;
6168 -- Note if a known but invisible entity encountered
6170 elsif Known_But_Invisible
(E
) then
6171 Nvis_Entity
:= True;
6174 -- Move to next entity in chain and continue search
6179 -- If no entries on homonym chain that were potentially visible,
6180 -- and no entities reasonably considered as non-visible, then
6181 -- we have a plain undefined reference, with no additional
6182 -- explanation required.
6184 if not Nvis_Entity
then
6185 Undefined
(Nvis
=> False);
6187 -- Otherwise there is at least one entry on the homonym chain that
6188 -- is reasonably considered as being known and non-visible.
6196 -- Processing for a potentially use visible entry found. We must search
6197 -- the rest of the homonym chain for two reasons. First, if there is a
6198 -- directly visible entry, then none of the potentially use-visible
6199 -- entities are directly visible (RM 8.4(10)). Second, we need to check
6200 -- for the case of multiple potentially use-visible entries hiding one
6201 -- another and as a result being non-directly visible (RM 8.4(11)).
6203 <<Potentially_Use_Visible_Entity
>> declare
6204 Only_One_Visible
: Boolean := True;
6205 All_Overloadable
: Boolean := Is_Overloadable
(E
);
6209 while Present
(E2
) loop
6210 if Is_Immediately_Visible
(E2
) then
6212 -- If the use-visible entity comes from the actual for a
6213 -- formal package, it hides a directly visible entity from
6214 -- outside the instance.
6216 if From_Actual_Package
(E
)
6217 and then Scope_Depth
(Scope
(E2
)) < Scope_Depth
(Inst
)
6222 goto Immediately_Visible_Entity
;
6225 elsif Is_Potentially_Use_Visible
(E2
) then
6226 Only_One_Visible
:= False;
6227 All_Overloadable
:= All_Overloadable
and Is_Overloadable
(E2
);
6229 -- Ada 2005 (AI-262): Protect against a form of Beaujolais effect
6230 -- that can occur in private_with clauses. Example:
6233 -- private with B; package A is
6234 -- package C is function B return Integer;
6236 -- V1 : Integer := B;
6237 -- private function B return Integer;
6238 -- V2 : Integer := B;
6241 -- V1 resolves to A.B, but V2 resolves to library unit B
6243 elsif Ekind
(E2
) = E_Function
6244 and then Scope
(E2
) = Standard_Standard
6245 and then Has_Private_With
(E2
)
6247 Only_One_Visible
:= False;
6248 All_Overloadable
:= False;
6249 Nvis_Is_Private_Subprg
:= True;
6256 -- On falling through this loop, we have checked that there are no
6257 -- immediately visible entities. Only_One_Visible is set if exactly
6258 -- one potentially use visible entity exists. All_Overloadable is
6259 -- set if all the potentially use visible entities are overloadable.
6260 -- The condition for legality is that either there is one potentially
6261 -- use visible entity, or if there is more than one, then all of them
6262 -- are overloadable.
6264 if Only_One_Visible
or All_Overloadable
then
6267 -- If there is more than one potentially use-visible entity and at
6268 -- least one of them non-overloadable, we have an error (RM 8.4(11)).
6269 -- Note that E points to the first such entity on the homonym list.
6272 -- If one of the entities is declared in an actual package, it
6273 -- was visible in the generic, and takes precedence over other
6274 -- entities that are potentially use-visible. The same applies
6275 -- if the entity is declared in a local instantiation of the
6276 -- current instance.
6280 -- Find the current instance
6282 Inst
:= Current_Scope
;
6283 while Present
(Inst
) and then Inst
/= Standard_Standard
loop
6284 if Is_Generic_Instance
(Inst
) then
6288 Inst
:= Scope
(Inst
);
6291 -- Reexamine the candidate entities, giving priority to those
6292 -- that were visible within the generic.
6295 while Present
(E2
) loop
6296 Nested_Inst
:= Nearest_Enclosing_Instance
(E2
);
6298 -- The entity is declared within an actual package, or in a
6299 -- nested instance. The ">=" accounts for the case where the
6300 -- current instance and the nested instance are the same.
6302 if From_Actual_Package
(E2
)
6303 or else (Present
(Nested_Inst
)
6304 and then Scope_Depth
(Nested_Inst
) >=
6317 elsif Is_Predefined_Unit
(Current_Sem_Unit
) then
6318 -- A use clause in the body of a system file creates conflict
6319 -- with some entity in a user scope, while rtsfind is active.
6320 -- Keep only the entity coming from another predefined unit.
6323 while Present
(E2
) loop
6324 if In_Predefined_Unit
(E2
) then
6332 -- Entity must exist because predefined unit is correct
6334 raise Program_Error
;
6343 -- Come here with E set to the first immediately visible entity on
6344 -- the homonym chain. This is the one we want unless there is another
6345 -- immediately visible entity further on in the chain for an inner
6346 -- scope (RM 8.3(8)).
6348 <<Immediately_Visible_Entity
>> declare
6353 -- Find scope level of initial entity. When compiling through
6354 -- Rtsfind, the previous context is not completely invisible, and
6355 -- an outer entity may appear on the chain, whose scope is below
6356 -- the entry for Standard that delimits the current scope stack.
6357 -- Indicate that the level for this spurious entry is outside of
6358 -- the current scope stack.
6360 Level
:= Scope_Stack
.Last
;
6362 Scop
:= Scope_Stack
.Table
(Level
).Entity
;
6363 exit when Scop
= Scope
(E
);
6365 exit when Scop
= Standard_Standard
;
6368 -- Now search remainder of homonym chain for more inner entry
6369 -- If the entity is Standard itself, it has no scope, and we
6370 -- compare it with the stack entry directly.
6373 while Present
(E2
) loop
6374 if Is_Immediately_Visible
(E2
) then
6376 -- If a generic package contains a local declaration that
6377 -- has the same name as the generic, there may be a visibility
6378 -- conflict in an instance, where the local declaration must
6379 -- also hide the name of the corresponding package renaming.
6380 -- We check explicitly for a package declared by a renaming,
6381 -- whose renamed entity is an instance that is on the scope
6382 -- stack, and that contains a homonym in the same scope. Once
6383 -- we have found it, we know that the package renaming is not
6384 -- immediately visible, and that the identifier denotes the
6385 -- other entity (and its homonyms if overloaded).
6387 if Scope
(E
) = Scope
(E2
)
6388 and then Ekind
(E
) = E_Package
6389 and then Present
(Renamed_Entity
(E
))
6390 and then Is_Generic_Instance
(Renamed_Entity
(E
))
6391 and then In_Open_Scopes
(Renamed_Entity
(E
))
6392 and then Comes_From_Source
(N
)
6394 Set_Is_Immediately_Visible
(E
, False);
6398 for J
in Level
+ 1 .. Scope_Stack
.Last
loop
6399 if Scope_Stack
.Table
(J
).Entity
= Scope
(E2
)
6400 or else Scope_Stack
.Table
(J
).Entity
= E2
6413 -- At the end of that loop, E is the innermost immediately
6414 -- visible entity, so we are all set.
6417 -- Come here with entity found, and stored in E
6421 -- Check violation of No_Wide_Characters restriction
6423 Check_Wide_Character_Restriction
(E
, N
);
6425 -- When distribution features are available (Get_PCS_Name /=
6426 -- Name_No_DSA), a remote access-to-subprogram type is converted
6427 -- into a record type holding whatever information is needed to
6428 -- perform a remote call on an RCI subprogram. In that case we
6429 -- rewrite any occurrence of the RAS type into the equivalent record
6430 -- type here. 'Access attribute references and RAS dereferences are
6431 -- then implemented using specific TSSs. However when distribution is
6432 -- not available (case of Get_PCS_Name = Name_No_DSA), we bypass the
6433 -- generation of these TSSs, and we must keep the RAS type in its
6434 -- original access-to-subprogram form (since all calls through a
6435 -- value of such type will be local anyway in the absence of a PCS).
6437 if Comes_From_Source
(N
)
6438 and then Is_Remote_Access_To_Subprogram_Type
(E
)
6439 and then Ekind
(E
) = E_Access_Subprogram_Type
6440 and then Expander_Active
6441 and then Get_PCS_Name
/= Name_No_DSA
6443 Rewrite
(N
, New_Occurrence_Of
(Equivalent_Type
(E
), Sloc
(N
)));
6447 -- Set the entity. Note that the reason we call Set_Entity for the
6448 -- overloadable case, as opposed to Set_Entity_With_Checks is
6449 -- that in the overloaded case, the initial call can set the wrong
6450 -- homonym. The call that sets the right homonym is in Sem_Res and
6451 -- that call does use Set_Entity_With_Checks, so we don't miss
6454 if Is_Overloadable
(E
) then
6457 Set_Entity_With_Checks
(N
, E
);
6463 Set_Etype
(N
, Get_Full_View
(Etype
(E
)));
6466 if Debug_Flag_E
then
6467 Write_Str
(" found ");
6468 Write_Entity_Info
(E
, " ");
6471 if Is_Self_Hidden
(E
)
6473 (not Is_Record_Type
(Current_Scope
)
6474 or else Nkind
(Parent
(N
)) /= N_Pragma_Argument_Association
)
6476 Premature_Usage
(N
);
6478 -- If the entity is overloadable, collect all interpretations of the
6479 -- name for subsequent overload resolution. We optimize a bit here to
6480 -- do this only if we have an overloadable entity that is not on its
6481 -- own on the homonym chain.
6483 elsif Is_Overloadable
(E
)
6484 and then (Present
(Homonym
(E
)) or else Current_Entity
(N
) /= E
)
6486 Collect_Interps
(N
);
6488 -- Background: for an instance of a generic, expansion sets
6489 -- entity fields on names that refer to things declared
6490 -- outside of the instance, but leaves the entity field
6491 -- unset on names that should end up referring to things
6492 -- declared within the instance. These will instead be set by
6493 -- analysis - the idea is that if a name resolves a certain
6494 -- way in the generic, then we should get corresponding results
6495 -- if we resolve the corresponding name in an instance. For this
6496 -- to work, we have to prevent unrelated declarations that
6497 -- happen to be visible at the point of the instantiation from
6498 -- participating in resolution and causing problems (typically
6499 -- ambiguities, but incorrect resolutions are also probably
6500 -- possible). So here we filter out such unwanted interpretations.
6502 -- Note that there are other problems with this approach to
6503 -- implementing generic instances that are not addressed here.
6504 -- Inside a generic, we might have no trouble resolving a call
6505 -- where the two candidates are a function that returns a
6506 -- formal type and a function that returns Standard.Integer.
6507 -- If we instantiate that generic and the corresponding actual
6508 -- type is Standard.Integer, then we may incorrectly reject the
6509 -- corresponding call in the instance as ambiguous (or worse,
6510 -- we may quietly choose the wrong resolution).
6512 -- Another such problem can occur with a type derived from a
6513 -- formal derived type. In an instance, such a type may have
6514 -- inherited subprograms that are not present in the generic.
6515 -- These can then interfere with name resolution (e.g., if
6516 -- some declaration is visible via a use-clause in the generic
6517 -- and some name in the generic refers to it, then the
6518 -- corresponding declaration in an instance may be hidden by
6519 -- a directly visible inherited subprogram and the corresponding
6520 -- name in the instance may then incorrectly refer to the
6521 -- inherited subprogram).
6525 function Is_Actual_Subp_Of_Inst
6526 (E
: Entity_Id
; Inst
: Entity_Id
) return Boolean;
6527 -- Return True if E is an actual parameter
6528 -- corresponding to a formal subprogram of the
6529 -- instantiation Inst.
6531 function Is_Extraneously_Visible
6532 (E
: Entity_Id
; Inst
: Entity_Id
) return Boolean;
6533 -- Return True if E is an interpretation that should
6534 -- be filtered out. That is, if E is an "unwanted"
6535 -- resolution candidate as described in the
6536 -- preceding "Background:" commment.
6538 function Is_Generic_Actual_Subp_Name
6539 (N
: Node_Id
) return Boolean;
6540 -- Return True if N is the name of a subprogram
6541 -- renaming generated for a generic actual.
6543 ----------------------------
6544 -- Is_Actual_Subp_Of_Inst --
6545 ----------------------------
6547 function Is_Actual_Subp_Of_Inst
6548 (E
: Entity_Id
; Inst
: Entity_Id
) return Boolean
6551 Generic_From_E
, Generic_From_Inst
: Entity_Id
;
6554 -- Why is Is_Generic_Actual_Subprogram undefined
6555 -- in the E_Operator case?
6557 if Ekind
(E
) not in E_Function | E_Procedure
6558 or else not Is_Generic_Actual_Subprogram
(E
)
6563 Decl
:= Enclosing_Declaration
(E
);
6565 -- Look for the suprogram renaming declaration built
6566 -- for a generic actual subprogram. Unclear why
6567 -- Original_Node call is needed, but sometimes it is.
6569 if Decl
not in N_Subprogram_Renaming_Declaration_Id
then
6570 Decl
:= Original_Node
(Decl
);
6573 if Decl
in N_Subprogram_Renaming_Declaration_Id
then
6575 Scope
(Corresponding_Formal_Spec
(Decl
));
6577 -- ??? In the case of a generic formal subprogram
6578 -- which has a pre/post condition, it is unclear how
6579 -- to find the Corresponding_Formal_Spec-bearing node.
6581 Generic_From_E
:= Empty
;
6585 Inst_Parent
: Node_Id
:= Parent
(Inst
);
6587 if Nkind
(Inst_Parent
) = N_Defining_Program_Unit_Name
6589 Inst_Parent
:= Parent
(Inst_Parent
);
6592 Generic_From_Inst
:= Generic_Parent
(Inst_Parent
);
6595 return Generic_From_E
= Generic_From_Inst
6596 and then Present
(Generic_From_E
);
6597 end Is_Actual_Subp_Of_Inst
;
6599 -----------------------------
6600 -- Is_Extraneously_Visible --
6601 -----------------------------
6603 function Is_Extraneously_Visible
6604 (E
: Entity_Id
; Inst
: Entity_Id
) return Boolean is
6606 -- Return False in various non-extraneous cases.
6607 -- If none of those apply, then return True.
6609 if Within_Scope
(E
, Inst
) then
6610 -- return False if E declared within Inst
6613 elsif Is_Actual_Subp_Of_Inst
(E
, Inst
) then
6614 -- Return False if E is an actual subprogram,
6615 -- and therefore may be referenced within Inst.
6618 elsif Nkind
(Parent
(E
)) = N_Subtype_Declaration
6619 and then Defining_Identifier
(Parent
(E
)) /= E
6621 -- Return False for a primitive subp of an
6622 -- actual corresponding to a formal type.
6626 elsif not In_Open_Scopes
(Scope
(E
)) then
6627 -- Return False if this candidate is not
6628 -- declared in a currently open scope.
6634 -- We want to know whether the declaration of
6635 -- E comes textually after the declaration of
6636 -- the generic that Inst is an instance of
6637 -- (and after the generic body if there is one).
6638 -- To compare, we climb up the deeper of the two
6639 -- scope chains until we the levels match.
6640 -- There is a separate loop for each starting
6641 -- point, but we will execute zero iterations
6642 -- for at least one of the two loops.
6643 -- For each Xxx_Scope, we have a corresponding
6644 -- Xxx_Trailer; the latter is the predecessor of
6645 -- the former in the scope traversal.
6647 E_Trailer
: Entity_Id
:= E
;
6648 E_Scope
: Entity_Id
:= Scope
(E
);
6649 pragma Assert
(Present
(E_Scope
));
6651 -- the generic that Inst is an instance of
6652 Gen_Trailer
: Entity_Id
:=
6653 Generic_Parent
(Specification
6654 (Unit_Declaration_Node
(Inst
)));
6655 Gen_Scope
: Entity_Id
;
6657 function Has_Formal_Package_Parameter
6658 (Generic_Id
: Entity_Id
) return Boolean;
6659 -- Return True iff given generic has at least one
6660 -- formal package parameter.
6662 ----------------------------------
6663 -- Has_Formal_Package_Parameter --
6664 ----------------------------------
6666 function Has_Formal_Package_Parameter
6667 (Generic_Id
: Entity_Id
) return Boolean is
6668 Formal_Decl
: Node_Id
:=
6669 First
(Generic_Formal_Declarations
6670 (Enclosing_Generic_Unit
(Generic_Id
)));
6672 while Present
(Formal_Decl
) loop
6673 if Nkind
(Original_Node
(Formal_Decl
)) =
6674 N_Formal_Package_Declaration
6682 end Has_Formal_Package_Parameter
;
6685 if No
(Gen_Trailer
) then
6686 -- Dunno how this can happen, but it can.
6689 if Has_Formal_Package_Parameter
(Gen_Trailer
)
6691 -- Punt on sorting out what is visible via a
6697 if Is_Child_Unit
(Gen_Trailer
)
6698 and then Is_Generic_Unit
6700 (Parent
(Gen_Trailer
))))
6702 -- Punt on dealing with how the FE fails
6703 -- to build a tree for a "sprouted" generic
6704 -- so that what should be a reference to
6705 -- I1.G2 instead points into G1.G2 .
6710 Gen_Scope
:= Scope
(Gen_Trailer
);
6712 while Scope_Depth
(E_Scope
)
6713 > Scope_Depth
(Gen_Scope
)
6715 E_Trailer
:= E_Scope
;
6716 E_Scope
:= Scope
(E_Scope
);
6718 while Scope_Depth
(E_Scope
)
6719 < Scope_Depth
(Gen_Scope
)
6721 Gen_Trailer
:= Gen_Scope
;
6722 Gen_Scope
:= Scope
(Gen_Scope
);
6726 if Gen_Scope
= E_Scope
then
6727 -- if Gen_Trailer and E_Trailer are declared
6728 -- in the same declarative part and E_Trailer
6729 -- occurs after the declaration (and body, if
6730 -- there is one) of Gen_Trailer, then
6731 -- return True because E was declared after
6732 -- the generic that Inst is an instance of
6733 -- (and also after that generic's body, if it
6736 if Is_Package_Or_Generic_Package
(Gen_Trailer
)
6737 and then Present
(Package_Body
(Gen_Trailer
))
6741 (Package_Spec
(Gen_Trailer
));
6745 Id
: Entity_Id
:= Gen_Trailer
;
6749 -- E_Trailer presumably occurred
6750 -- earlier on the entity list than
6751 -- Gen_Trailer. So E preceded the
6752 -- generic that Inst is an instance
6753 -- of (or the body of that generic if
6754 -- it has one) and so could have
6755 -- been referenced within the generic.
6758 exit when Id
= E_Trailer
;
6766 if Present
(Nearest_Enclosing_Instance
(Inst
)) then
6767 return Is_Extraneously_Visible
6768 (E
=> E
, Inst
=> Nearest_Enclosing_Instance
(Inst
));
6770 -- The preceding Nearest_Enclosing_Instance test
6771 -- doesn't handle the case of an instance of a
6772 -- "sprouted" generic. For example, if Inst=I2 in
6773 -- generic package G1
6774 -- generic package G1.G2;
6775 -- package I1 is new G1;
6776 -- package I2 is new I1.G2;
6777 -- then N_E_I (Inst) = Empty. So deal with that case.
6779 elsif Present
(Nearest_Enclosing_Instance
(E
)) then
6780 return Is_Extraneously_Visible
6781 (E
=> Nearest_Enclosing_Instance
(E
),
6786 end Is_Extraneously_Visible
;
6788 ---------------------------------
6789 -- Is_Generic_Actual_Subp_Name --
6790 ---------------------------------
6792 function Is_Generic_Actual_Subp_Name
6793 (N
: Node_Id
) return Boolean
6795 Decl
: constant Node_Id
:= Enclosing_Declaration
(N
);
6797 return Nkind
(Decl
) = N_Subprogram_Renaming_Declaration
6798 and then Present
(Corresponding_Formal_Spec
(Decl
));
6799 end Is_Generic_Actual_Subp_Name
;
6803 Inst
: Entity_Id
:= Current_Scope
;
6806 while Present
(Inst
)
6807 and then not Is_Generic_Instance
(Inst
)
6809 Inst
:= Scope
(Inst
);
6812 if Present
(Inst
) then
6813 Get_First_Interp
(N
, I
, It
);
6814 while Present
(It
.Nam
) loop
6815 if Is_Extraneously_Visible
(E
=> It
.Nam
, Inst
=> Inst
)
6816 and then not Is_Generic_Actual_Subp_Name
(N
)
6820 Get_Next_Interp
(I
, It
);
6826 -- If no homonyms were visible, the entity is unambiguous
6828 if not Is_Overloaded
(N
) then
6829 if not Is_Actual_Parameter
then
6830 Generate_Reference
(E
, N
);
6834 -- Case of non-overloadable entity, set the entity providing that
6835 -- we do not have the case of a discriminant reference within a
6836 -- default expression. Such references are replaced with the
6837 -- corresponding discriminal, which is the formal corresponding to
6838 -- to the discriminant in the initialization procedure.
6841 -- Entity is unambiguous, indicate that it is referenced here
6843 -- For a renaming of an object, always generate simple reference,
6844 -- we don't try to keep track of assignments in this case, except
6845 -- in SPARK mode where renamings are traversed for generating
6846 -- local effects of subprograms.
6849 and then Present
(Renamed_Object
(E
))
6850 and then not GNATprove_Mode
6852 Generate_Reference
(E
, N
);
6854 -- If the renamed entity is a private protected component,
6855 -- reference the original component as well. This needs to be
6856 -- done because the private renamings are installed before any
6857 -- analysis has occurred. Reference to a private component will
6858 -- resolve to the renaming and the original component will be
6859 -- left unreferenced, hence the following.
6861 if Is_Prival
(E
) then
6862 Generate_Reference
(Prival_Link
(E
), N
);
6865 -- One odd case is that we do not want to set the Referenced flag
6866 -- if the entity is a label, and the identifier is the label in
6867 -- the source, since this is not a reference from the point of
6868 -- view of the user.
6870 elsif Nkind
(Parent
(N
)) = N_Label
then
6872 R
: constant Boolean := Referenced
(E
);
6875 -- Generate reference unless this is an actual parameter
6876 -- (see comment below).
6878 if not Is_Actual_Parameter
then
6879 Generate_Reference
(E
, N
);
6880 Set_Referenced
(E
, R
);
6884 -- Normal case, not a label: generate reference
6887 if not Is_Actual_Parameter
then
6889 -- Package or generic package is always a simple reference
6891 if Is_Package_Or_Generic_Package
(E
) then
6892 Generate_Reference
(E
, N
, 'r');
6894 -- Else see if we have a left hand side
6897 case Known_To_Be_Assigned
(N
, Only_LHS
=> True) is
6899 Generate_Reference
(E
, N
, 'm');
6902 Generate_Reference
(E
, N
, 'r');
6909 Set_Entity_Or_Discriminal
(N
, E
);
6911 -- The name may designate a generalized reference, in which case
6912 -- the dereference interpretation will be included. Context is
6913 -- one in which a name is legal.
6915 if Ada_Version
>= Ada_2012
6917 (Nkind
(Parent
(N
)) in N_Subexpr
6918 or else Nkind
(Parent
(N
)) in N_Assignment_Statement
6919 | N_Object_Declaration
6920 | N_Parameter_Association
)
6922 Check_Implicit_Dereference
(N
, Etype
(E
));
6927 -- Mark relevant use-type and use-package clauses as effective if the
6928 -- node in question is not overloaded and therefore does not require
6931 -- Note: Generic actual subprograms do not follow the normal resolution
6932 -- path, so ignore the fact that they are overloaded and mark them
6935 if Nkind
(N
) not in N_Subexpr
or else not Is_Overloaded
(N
) then
6936 Mark_Use_Clauses
(N
);
6939 -- Come here with entity set
6942 Check_Restriction_No_Use_Of_Entity
(N
);
6944 -- Annotate the tree by creating a variable reference marker in case the
6945 -- original variable reference is folded or optimized away. The variable
6946 -- reference marker is automatically saved for later examination by the
6947 -- ABE Processing phase. Variable references which act as actuals in a
6948 -- call require special processing and are left to Resolve_Actuals. The
6949 -- reference is a write when it appears on the left hand side of an
6952 if Needs_Variable_Reference_Marker
(N
=> N
, Calls_OK
=> False) then
6954 Is_Assignment_LHS
: constant Boolean := Known_To_Be_Assigned
(N
);
6957 Build_Variable_Reference_Marker
6959 Read
=> not Is_Assignment_LHS
,
6960 Write
=> Is_Assignment_LHS
);
6963 end Find_Direct_Name
;
6965 ------------------------
6966 -- Find_Expanded_Name --
6967 ------------------------
6969 -- This routine searches the homonym chain of the entity until it finds
6970 -- an entity declared in the scope denoted by the prefix. If the entity
6971 -- is private, it may nevertheless be immediately visible, if we are in
6972 -- the scope of its declaration.
6974 procedure Find_Expanded_Name
(N
: Node_Id
) is
6975 function In_Abstract_View_Pragma
(Nod
: Node_Id
) return Boolean;
6976 -- Determine whether expanded name Nod appears within a pragma which is
6977 -- a suitable context for an abstract view of a state or variable. The
6978 -- following pragmas fall in this category:
6985 -- In addition, pragma Abstract_State is also considered suitable even
6986 -- though it is an illegal context for an abstract view as this allows
6987 -- for proper resolution of abstract views of variables. This illegal
6988 -- context is later flagged in the analysis of indicator Part_Of.
6990 -----------------------------
6991 -- In_Abstract_View_Pragma --
6992 -----------------------------
6994 function In_Abstract_View_Pragma
(Nod
: Node_Id
) return Boolean is
6998 -- Climb the parent chain looking for a pragma
7001 while Present
(Par
) loop
7002 if Nkind
(Par
) = N_Pragma
then
7003 if Pragma_Name_Unmapped
(Par
)
7004 in Name_Abstract_State
7008 | Name_Refined_Depends
7009 | Name_Refined_Global
7013 -- Otherwise the pragma is not a legal context for an abstract
7020 -- Prevent the search from going too far
7022 elsif Is_Body_Or_Package_Declaration
(Par
) then
7026 Par
:= Parent
(Par
);
7030 end In_Abstract_View_Pragma
;
7034 Selector
: constant Node_Id
:= Selector_Name
(N
);
7036 Candidate
: Entity_Id
:= Empty
;
7040 -- Start of processing for Find_Expanded_Name
7043 P_Name
:= Entity
(Prefix
(N
));
7045 -- If the prefix is a renamed package, look for the entity in the
7046 -- original package.
7048 if Ekind
(P_Name
) = E_Package
7049 and then Present
(Renamed_Entity
(P_Name
))
7051 P_Name
:= Renamed_Entity
(P_Name
);
7053 if From_Limited_With
(P_Name
)
7054 and then not Unit_Is_Visible
(Cunit
(Get_Source_Unit
(P_Name
)))
7057 ("renaming of limited view of package & not usable in this"
7058 & " context (RM 8.5.3(3.1/2))", Prefix
(N
), P_Name
);
7060 elsif Has_Limited_View
(P_Name
)
7061 and then not Unit_Is_Visible
(Cunit
(Get_Source_Unit
(P_Name
)))
7062 and then not Is_Visible_Through_Renamings
(P_Name
)
7065 ("renaming of limited view of package & not usable in this"
7066 & " context (RM 8.5.3(3.1/2))", Prefix
(N
), P_Name
);
7069 -- Rewrite node with entity field pointing to renamed object
7071 Rewrite
(Prefix
(N
), New_Copy
(Prefix
(N
)));
7072 Set_Entity
(Prefix
(N
), P_Name
);
7074 -- If the prefix is an object of a concurrent type, look for
7075 -- the entity in the associated task or protected type.
7077 elsif Is_Concurrent_Type
(Etype
(P_Name
)) then
7078 P_Name
:= Etype
(P_Name
);
7081 Id
:= Current_Entity
(Selector
);
7084 Is_New_Candidate
: Boolean;
7087 while Present
(Id
) loop
7088 if Scope
(Id
) = P_Name
then
7090 Is_New_Candidate
:= True;
7092 -- Handle abstract views of states and variables. These are
7093 -- acceptable candidates only when the reference to the view
7094 -- appears in certain pragmas.
7096 if Ekind
(Id
) = E_Abstract_State
7097 and then From_Limited_With
(Id
)
7098 and then Present
(Non_Limited_View
(Id
))
7100 if In_Abstract_View_Pragma
(N
) then
7101 Candidate
:= Non_Limited_View
(Id
);
7102 Is_New_Candidate
:= True;
7104 -- Hide the candidate because it is not used in a proper
7109 Is_New_Candidate
:= False;
7113 -- Ada 2005 (AI-217): Handle shadow entities associated with
7114 -- types declared in limited-withed nested packages. We don't need
7115 -- to handle E_Incomplete_Subtype entities because the entities
7116 -- in the limited view are always E_Incomplete_Type and
7117 -- E_Class_Wide_Type entities (see Build_Limited_Views).
7119 -- Regarding the expression used to evaluate the scope, it
7120 -- is important to note that the limited view also has shadow
7121 -- entities associated nested packages. For this reason the
7122 -- correct scope of the entity is the scope of the real entity.
7123 -- The non-limited view may itself be incomplete, in which case
7124 -- get the full view if available.
7126 elsif Ekind
(Id
) in E_Incomplete_Type | E_Class_Wide_Type
7127 and then From_Limited_With
(Id
)
7128 and then Present
(Non_Limited_View
(Id
))
7129 and then Scope
(Non_Limited_View
(Id
)) = P_Name
7131 Candidate
:= Get_Full_View
(Non_Limited_View
(Id
));
7132 Is_New_Candidate
:= True;
7134 -- Handle special case where the prefix is a renaming of a shadow
7135 -- package which is visible. Required to avoid reporting spurious
7138 elsif Ekind
(P_Name
) = E_Package
7139 and then From_Limited_With
(P_Name
)
7140 and then not From_Limited_With
(Id
)
7141 and then Sloc
(Scope
(Id
)) = Sloc
(P_Name
)
7142 and then Unit_Is_Visible
(Cunit
(Get_Source_Unit
(P_Name
)))
7144 Candidate
:= Get_Full_View
(Id
);
7145 Is_New_Candidate
:= True;
7147 -- An unusual case arises with a fully qualified name for an
7148 -- entity local to a generic child unit package, within an
7149 -- instantiation of that package. The name of the unit now
7150 -- denotes the renaming created within the instance. This is
7151 -- only relevant in an instance body, see below.
7153 elsif Is_Generic_Instance
(Scope
(Id
))
7154 and then In_Open_Scopes
(Scope
(Id
))
7155 and then In_Instance_Body
7156 and then Ekind
(Scope
(Id
)) = E_Package
7157 and then Ekind
(Id
) = E_Package
7158 and then Renamed_Entity
(Id
) = Scope
(Id
)
7159 and then Is_Immediately_Visible
(P_Name
)
7161 Is_New_Candidate
:= True;
7164 Is_New_Candidate
:= False;
7167 if Is_New_Candidate
then
7169 -- If entity is a child unit, either it is a visible child of
7170 -- the prefix, or we are in the body of a generic prefix, as
7171 -- will happen when a child unit is instantiated in the body
7172 -- of a generic parent. This is because the instance body does
7173 -- not restore the full compilation context, given that all
7174 -- non-local references have been captured.
7176 if Is_Child_Unit
(Id
) or else P_Name
= Standard_Standard
then
7177 exit when Is_Visible_Lib_Unit
(Id
)
7178 or else (Is_Child_Unit
(Id
)
7179 and then In_Open_Scopes
(Scope
(Id
))
7180 and then In_Instance_Body
);
7182 exit when not Is_Hidden
(Id
);
7185 exit when Is_Immediately_Visible
(Id
);
7193 and then Ekind
(P_Name
) in E_Procedure | E_Function
7194 and then Is_Generic_Instance
(P_Name
)
7196 -- Expanded name denotes entity in (instance of) generic subprogram.
7197 -- The entity may be in the subprogram instance, or may denote one of
7198 -- the formals, which is declared in the enclosing wrapper package.
7200 P_Name
:= Scope
(P_Name
);
7202 Id
:= Current_Entity
(Selector
);
7203 while Present
(Id
) loop
7204 exit when Scope
(Id
) = P_Name
;
7209 if No
(Id
) or else Chars
(Id
) /= Chars
(Selector
) then
7210 Set_Etype
(N
, Any_Type
);
7212 -- If we are looking for an entity defined in System, try to find it
7213 -- in the child package that may have been provided as an extension
7214 -- to System. The Extend_System pragma will have supplied the name of
7215 -- the extension, which may have to be loaded.
7217 if Chars
(P_Name
) = Name_System
7218 and then Scope
(P_Name
) = Standard_Standard
7219 and then Present
(System_Extend_Unit
)
7220 and then Present_System_Aux
(N
)
7222 Set_Entity
(Prefix
(N
), System_Aux_Id
);
7223 Find_Expanded_Name
(N
);
7226 -- There is an implicit instance of the predefined operator in
7227 -- the given scope. The operator entity is defined in Standard.
7228 -- Has_Implicit_Operator makes the node into an Expanded_Name.
7230 elsif Nkind
(Selector
) = N_Operator_Symbol
7231 and then Has_Implicit_Operator
(N
)
7235 -- If there is no literal defined in the scope denoted by the
7236 -- prefix, the literal may belong to (a type derived from)
7237 -- Standard_Character, for which we have no explicit literals.
7239 elsif Nkind
(Selector
) = N_Character_Literal
7240 and then Has_Implicit_Character_Literal
(N
)
7245 -- If the prefix is a single concurrent object, use its name in
7246 -- the error message, rather than that of the anonymous type.
7248 if Is_Concurrent_Type
(P_Name
)
7249 and then Is_Internal_Name
(Chars
(P_Name
))
7251 Error_Msg_Node_2
:= Entity
(Prefix
(N
));
7253 Error_Msg_Node_2
:= P_Name
;
7256 if P_Name
= System_Aux_Id
then
7257 P_Name
:= Scope
(P_Name
);
7258 Set_Entity
(Prefix
(N
), P_Name
);
7261 if Present
(Candidate
) then
7263 -- If we know that the unit is a child unit we can give a more
7264 -- accurate error message.
7266 if Is_Child_Unit
(Candidate
) then
7268 -- If the candidate is a private child unit and we are in
7269 -- the visible part of a public unit, specialize the error
7270 -- message. There might be a private with_clause for it,
7271 -- but it is not currently active.
7273 if Is_Private_Descendant
(Candidate
)
7274 and then Ekind
(Current_Scope
) = E_Package
7275 and then not In_Private_Part
(Current_Scope
)
7276 and then not Is_Private_Descendant
(Current_Scope
)
7279 ("private child unit& is not visible here", Selector
);
7281 -- Normal case where we have a missing with for a child unit
7284 Error_Msg_Qual_Level
:= 99;
7285 Error_Msg_NE
-- CODEFIX
7286 ("missing `WITH &;`", Selector
, Candidate
);
7287 Error_Msg_Qual_Level
:= 0;
7290 -- Here we don't know that this is a child unit
7293 Error_Msg_NE
("& is not a visible entity of&", N
, Selector
);
7297 -- Within the instantiation of a child unit, the prefix may
7298 -- denote the parent instance, but the selector has the name
7299 -- of the original child. That is to say, when A.B appears
7300 -- within an instantiation of generic child unit B, the scope
7301 -- stack includes an instance of A (P_Name) and an instance
7302 -- of B under some other name. We scan the scope to find this
7303 -- child instance, which is the desired entity.
7304 -- Note that the parent may itself be a child instance, if
7305 -- the reference is of the form A.B.C, in which case A.B has
7306 -- already been rewritten with the proper entity.
7308 if In_Open_Scopes
(P_Name
)
7309 and then Is_Generic_Instance
(P_Name
)
7312 Gen_Par
: constant Entity_Id
:=
7313 Generic_Parent
(Specification
7314 (Unit_Declaration_Node
(P_Name
)));
7315 S
: Entity_Id
:= Current_Scope
;
7319 for J
in reverse 0 .. Scope_Stack
.Last
loop
7320 S
:= Scope_Stack
.Table
(J
).Entity
;
7322 exit when S
= Standard_Standard
;
7324 if Ekind
(S
) in E_Function | E_Package | E_Procedure
7327 Generic_Parent
(Specification
7328 (Unit_Declaration_Node
(S
)));
7330 -- Check that P is a generic child of the generic
7331 -- parent of the prefix.
7334 and then Chars
(P
) = Chars
(Selector
)
7335 and then Scope
(P
) = Gen_Par
7346 -- If this is a selection from Ada, System or Interfaces, then
7347 -- we assume a missing with for the corresponding package.
7349 if Is_Known_Unit
(N
)
7350 and then not (Present
(Entity
(Prefix
(N
)))
7351 and then Scope
(Entity
(Prefix
(N
))) /=
7354 if not Error_Posted
(N
) then
7356 ("& is not a visible entity of&", Prefix
(N
), Selector
);
7357 Error_Missing_With_Of_Known_Unit
(Prefix
(N
));
7360 -- If this is a selection from a dummy package, then suppress
7361 -- the error message, of course the entity is missing if the
7362 -- package is missing.
7364 elsif Sloc
(Error_Msg_Node_2
) = No_Location
then
7367 -- Here we have the case of an undefined component
7370 -- The prefix may hide a homonym in the context that
7371 -- declares the desired entity. This error can use a
7372 -- specialized message.
7374 if In_Open_Scopes
(P_Name
) then
7376 H
: constant Entity_Id
:= Homonym
(P_Name
);
7380 and then Is_Compilation_Unit
(H
)
7382 (Is_Immediately_Visible
(H
)
7383 or else Is_Visible_Lib_Unit
(H
))
7385 Id
:= First_Entity
(H
);
7386 while Present
(Id
) loop
7387 if Chars
(Id
) = Chars
(Selector
) then
7388 Error_Msg_Qual_Level
:= 99;
7389 Error_Msg_Name_1
:= Chars
(Selector
);
7391 ("% not declared in&", N
, P_Name
);
7393 ("\use fully qualified name starting with "
7394 & "Standard to make& visible", N
, H
);
7395 Error_Msg_Qual_Level
:= 0;
7403 -- If not found, standard error message
7405 Error_Msg_NE
("& not declared in&", N
, Selector
);
7411 -- Might be worth specializing the case when the prefix
7412 -- is a limited view.
7413 -- ... not declared in limited view of...
7415 Error_Msg_NE
("& not declared in&", N
, Selector
);
7418 -- Check for misspelling of some entity in prefix
7420 Id
:= First_Entity
(P_Name
);
7421 while Present
(Id
) loop
7422 if Is_Bad_Spelling_Of
(Chars
(Id
), Chars
(Selector
))
7423 and then not Is_Internal_Name
(Chars
(Id
))
7425 Error_Msg_NE
-- CODEFIX
7426 ("possible misspelling of&", Selector
, Id
);
7433 -- Specialize the message if this may be an instantiation
7434 -- of a child unit that was not mentioned in the context.
7436 if Nkind
(Parent
(N
)) = N_Package_Instantiation
7437 and then Is_Generic_Instance
(Entity
(Prefix
(N
)))
7438 and then Is_Compilation_Unit
7439 (Generic_Parent
(Parent
(Entity
(Prefix
(N
)))))
7441 Error_Msg_Node_2
:= Selector
;
7442 Error_Msg_N
-- CODEFIX
7443 ("\missing `WITH &.&;`", Prefix
(N
));
7453 if Comes_From_Source
(N
)
7454 and then Is_Remote_Access_To_Subprogram_Type
(Id
)
7455 and then Ekind
(Id
) = E_Access_Subprogram_Type
7456 and then Present
(Equivalent_Type
(Id
))
7458 -- If we are not actually generating distribution code (i.e. the
7459 -- current PCS is the dummy non-distributed version), then the
7460 -- Equivalent_Type will be missing, and Id should be treated as
7461 -- a regular access-to-subprogram type.
7463 Id
:= Equivalent_Type
(Id
);
7464 Set_Chars
(Selector
, Chars
(Id
));
7467 -- Ada 2005 (AI-50217): Check usage of entities in limited withed units
7469 if Ekind
(P_Name
) = E_Package
and then From_Limited_With
(P_Name
) then
7470 if From_Limited_With
(Id
)
7471 or else Is_Type
(Id
)
7472 or else Ekind
(Id
) = E_Package
7477 ("limited withed package can only be used to access incomplete "
7482 if Is_Task_Type
(P_Name
)
7483 and then ((Ekind
(Id
) = E_Entry
7484 and then Nkind
(Parent
(N
)) /= N_Attribute_Reference
)
7486 (Ekind
(Id
) = E_Entry_Family
7488 Nkind
(Parent
(Parent
(N
))) /= N_Attribute_Reference
))
7490 -- If both the task type and the entry are in scope, this may still
7491 -- be the expanded name of an entry formal.
7493 if In_Open_Scopes
(Id
)
7494 and then Nkind
(Parent
(N
)) = N_Selected_Component
7499 -- It is an entry call after all, either to the current task
7500 -- (which will deadlock) or to an enclosing task.
7502 Analyze_Selected_Component
(N
);
7508 when N_Selected_Component
=>
7509 Reinit_Field_To_Zero
(N
, F_Is_Prefixed_Call
);
7510 Change_Selected_Component_To_Expanded_Name
(N
);
7512 when N_Expanded_Name
=>
7516 pragma Assert
(False);
7519 -- Preserve relevant elaboration-related attributes of the context which
7520 -- are no longer available or very expensive to recompute once analysis,
7521 -- resolution, and expansion are over.
7523 Mark_Elaboration_Attributes
7529 -- Set appropriate type
7531 if Is_Type
(Id
) then
7534 Set_Etype
(N
, Get_Full_View
(Etype
(Id
)));
7537 -- Do style check and generate reference, but skip both steps if this
7538 -- entity has homonyms, since we may not have the right homonym set yet.
7539 -- The proper homonym will be set during the resolve phase.
7541 if Has_Homonym
(Id
) then
7545 Set_Entity_Or_Discriminal
(N
, Id
);
7547 case Known_To_Be_Assigned
(N
, Only_LHS
=> True) is
7549 Generate_Reference
(Id
, N
, 'm');
7552 Generate_Reference
(Id
, N
, 'r');
7557 -- Check for violation of No_Wide_Characters
7559 Check_Wide_Character_Restriction
(Id
, N
);
7561 if Is_Self_Hidden
(Id
) then
7562 Premature_Usage
(N
);
7564 elsif Is_Overloadable
(Id
) and then Present
(Homonym
(Id
)) then
7566 H
: Entity_Id
:= Homonym
(Id
);
7569 while Present
(H
) loop
7570 if Scope
(H
) = Scope
(Id
)
7571 and then (not Is_Hidden
(H
)
7572 or else Is_Immediately_Visible
(H
))
7574 Collect_Interps
(N
);
7581 -- If an extension of System is present, collect possible explicit
7582 -- overloadings declared in the extension.
7584 if Chars
(P_Name
) = Name_System
7585 and then Scope
(P_Name
) = Standard_Standard
7586 and then Present
(System_Extend_Unit
)
7587 and then Present_System_Aux
(N
)
7589 H
:= Current_Entity
(Id
);
7591 while Present
(H
) loop
7592 if Scope
(H
) = System_Aux_Id
then
7593 Add_One_Interp
(N
, H
, Etype
(H
));
7602 if Nkind
(Selector_Name
(N
)) = N_Operator_Symbol
7603 and then Scope
(Id
) /= Standard_Standard
7605 -- In addition to user-defined operators in the given scope, there
7606 -- may be an implicit instance of the predefined operator. The
7607 -- operator (defined in Standard) is found in Has_Implicit_Operator,
7608 -- and added to the interpretations. Procedure Add_One_Interp will
7609 -- determine which hides which.
7611 if Has_Implicit_Operator
(N
) then
7616 -- If there is a single interpretation for N we can generate a
7617 -- reference to the unique entity found.
7619 if Is_Overloadable
(Id
) and then not Is_Overloaded
(N
) then
7620 Generate_Reference
(Id
, N
);
7623 -- Mark relevant use-type and use-package clauses as effective if the
7624 -- node in question is not overloaded and therefore does not require
7627 if Nkind
(N
) not in N_Subexpr
or else not Is_Overloaded
(N
) then
7628 Mark_Use_Clauses
(N
);
7631 Check_Restriction_No_Use_Of_Entity
(N
);
7633 -- Annotate the tree by creating a variable reference marker in case the
7634 -- original variable reference is folded or optimized away. The variable
7635 -- reference marker is automatically saved for later examination by the
7636 -- ABE Processing phase. Variable references which act as actuals in a
7637 -- call require special processing and are left to Resolve_Actuals. The
7638 -- reference is a write when it appears on the left hand side of an
7641 if Needs_Variable_Reference_Marker
7646 Is_Assignment_LHS
: constant Boolean := Known_To_Be_Assigned
(N
);
7649 Build_Variable_Reference_Marker
7651 Read
=> not Is_Assignment_LHS
,
7652 Write
=> Is_Assignment_LHS
);
7655 end Find_Expanded_Name
;
7657 --------------------
7658 -- Find_First_Use --
7659 --------------------
7661 function Find_First_Use
(Use_Clause
: Node_Id
) return Node_Id
is
7665 -- Loop through the Prev_Use_Clause chain
7668 while Present
(Prev_Use_Clause
(Curr
)) loop
7669 Curr
:= Prev_Use_Clause
(Curr
);
7675 -------------------------
7676 -- Find_Renamed_Entity --
7677 -------------------------
7679 function Find_Renamed_Entity
7683 Is_Actual
: Boolean := False) return Entity_Id
7686 I1
: Interp_Index
:= 0; -- Suppress junk warnings
7692 function Find_Nearer_Entity
7695 Old2_S
: Entity_Id
) return Entity_Id
;
7696 -- Determine whether one of Old_S1 and Old_S2 is nearer to New_S than
7697 -- the other, and return it if so. Return Empty otherwise. We use this
7698 -- in conjunction with Inherit_Renamed_Profile to simplify later type
7699 -- disambiguation for actual subprograms in instances.
7701 function Is_Visible_Operation
(Op
: Entity_Id
) return Boolean;
7702 -- If the renamed entity is an implicit operator, check whether it is
7703 -- visible because its operand type is properly visible. This check
7704 -- applies to explicit renamed entities that appear in the source in a
7705 -- renaming declaration or a formal subprogram instance, but not to
7706 -- default generic actuals with a name.
7708 function Report_Overload
return Entity_Id
;
7709 -- List possible interpretations, and specialize message in the
7710 -- case of a generic actual.
7712 function Within
(Inner
, Outer
: Entity_Id
) return Boolean;
7713 -- Determine whether a candidate subprogram is defined within the
7714 -- enclosing instance. If yes, it has precedence over outer candidates.
7716 --------------------------
7717 -- Find_Nearer_Entity --
7718 --------------------------
7720 function Find_Nearer_Entity
7723 Old2_S
: Entity_Id
) return Entity_Id
7731 New_F
:= First_Formal
(New_S
);
7732 Old1_F
:= First_Formal
(Old1_S
);
7733 Old2_F
:= First_Formal
(Old2_S
);
7735 -- The criterion is whether the type of the formals of one of Old1_S
7736 -- and Old2_S is an ancestor subtype of the type of the corresponding
7737 -- formals of New_S while the other is not (we already know that they
7738 -- are all subtypes of the same base type).
7740 -- This makes it possible to find the more correct renamed entity in
7741 -- the case of a generic instantiation nested in an enclosing one for
7742 -- which different formal types get the same actual type, which will
7743 -- in turn make it possible for Inherit_Renamed_Profile to preserve
7744 -- types on formal parameters and ultimately simplify disambiguation.
7746 -- Consider the follow package G:
7749 -- type Item_T is private;
7750 -- with function Compare (L, R: Item_T) return Boolean is <>;
7752 -- type Bound_T is private;
7753 -- with function Compare (L, R : Bound_T) return Boolean is <>;
7758 -- package body G is
7759 -- package My_Inner is Inner_G (Bound_T);
7763 -- with the following package Inner_G:
7766 -- type T is private;
7767 -- with function Compare (L, R: T) return Boolean is <>;
7768 -- package Inner_G is
7769 -- function "<" (L, R: T) return Boolean is (Compare (L, R));
7772 -- If G is instantiated on the same actual type with a single Compare
7776 -- function Compare (L, R : T) return Boolean;
7777 -- package My_G is new (T, T);
7779 -- then the renaming generated for Compare in the inner instantiation
7780 -- is ambiguous: it can rename either of the renamings generated for
7781 -- the outer instantiation. Now if the first one is picked up, then
7782 -- the subtypes of the formal parameters of the renaming will not be
7783 -- preserved in Inherit_Renamed_Profile because they are subtypes of
7784 -- the Bound_T formal type and not of the Item_T formal type, so we
7785 -- need to arrange for the second one to be picked up instead.
7787 while Present
(New_F
) loop
7788 if Etype
(Old1_F
) /= Etype
(Old2_F
) then
7789 Anc_T
:= Ancestor_Subtype
(Etype
(New_F
));
7791 if Etype
(Old1_F
) = Anc_T
then
7793 elsif Etype
(Old2_F
) = Anc_T
then
7798 Next_Formal
(New_F
);
7799 Next_Formal
(Old1_F
);
7800 Next_Formal
(Old2_F
);
7803 pragma Assert
(No
(Old1_F
));
7804 pragma Assert
(No
(Old2_F
));
7807 end Find_Nearer_Entity
;
7809 --------------------------
7810 -- Is_Visible_Operation --
7811 --------------------------
7813 function Is_Visible_Operation
(Op
: Entity_Id
) return Boolean is
7819 if Ekind
(Op
) /= E_Operator
7820 or else Scope
(Op
) /= Standard_Standard
7821 or else (In_Instance
7822 and then (not Is_Actual
7823 or else Present
(Enclosing_Instance
)))
7828 -- For a fixed point type operator, check the resulting type,
7829 -- because it may be a mixed mode integer * fixed operation.
7831 if Present
(Next_Formal
(First_Formal
(New_S
)))
7832 and then Is_Fixed_Point_Type
(Etype
(New_S
))
7834 Typ
:= Etype
(New_S
);
7836 Typ
:= Etype
(First_Formal
(New_S
));
7839 Btyp
:= Base_Type
(Typ
);
7841 if Nkind
(Nam
) /= N_Expanded_Name
then
7842 return (In_Open_Scopes
(Scope
(Btyp
))
7843 or else Is_Potentially_Use_Visible
(Btyp
)
7844 or else In_Use
(Btyp
)
7845 or else In_Use
(Scope
(Btyp
)));
7848 Scop
:= Entity
(Prefix
(Nam
));
7850 if Ekind
(Scop
) = E_Package
7851 and then Present
(Renamed_Entity
(Scop
))
7853 Scop
:= Renamed_Entity
(Scop
);
7856 -- Operator is visible if prefix of expanded name denotes
7857 -- scope of type, or else type is defined in System_Aux
7858 -- and the prefix denotes System.
7860 return Scope
(Btyp
) = Scop
7861 or else (Scope
(Btyp
) = System_Aux_Id
7862 and then Scope
(Scope
(Btyp
)) = Scop
);
7865 end Is_Visible_Operation
;
7871 function Within
(Inner
, Outer
: Entity_Id
) return Boolean is
7875 Sc
:= Scope
(Inner
);
7876 while Sc
/= Standard_Standard
loop
7887 ---------------------
7888 -- Report_Overload --
7889 ---------------------
7891 function Report_Overload
return Entity_Id
is
7894 Error_Msg_NE
-- CODEFIX
7895 ("ambiguous actual subprogram&, " &
7896 "possible interpretations:", N
, Nam
);
7898 Error_Msg_N
-- CODEFIX
7899 ("ambiguous subprogram, " &
7900 "possible interpretations:", N
);
7903 List_Interps
(Nam
, N
);
7905 end Report_Overload
;
7907 -- Start of processing for Find_Renamed_Entity
7911 Candidate_Renaming
:= Empty
;
7913 if Is_Overloaded
(Nam
) then
7914 Get_First_Interp
(Nam
, Ind
, It
);
7915 while Present
(It
.Nam
) loop
7916 if Entity_Matches_Spec
(It
.Nam
, New_S
)
7917 and then Is_Visible_Operation
(It
.Nam
)
7919 if Old_S
/= Any_Id
then
7921 -- Note: The call to Disambiguate only happens if a
7922 -- previous interpretation was found, in which case I1
7923 -- has received a value.
7925 It1
:= Disambiguate
(Nam
, I1
, Ind
, Etype
(Old_S
));
7927 if It1
= No_Interp
then
7928 Inst
:= Enclosing_Instance
;
7930 if Present
(Inst
) then
7931 if Within
(It
.Nam
, Inst
) then
7932 if Within
(Old_S
, Inst
) then
7934 It_D
: constant Uint
:=
7935 Scope_Depth_Default_0
(It
.Nam
);
7936 Old_D
: constant Uint
:=
7937 Scope_Depth_Default_0
(Old_S
);
7940 -- Choose the innermost subprogram, which
7941 -- would hide the outer one in the generic.
7943 if Old_D
> It_D
then
7945 elsif It_D
> Old_D
then
7949 -- Otherwise, if we can determine that one
7950 -- of the entities is nearer to the renaming
7951 -- than the other, choose it. If not, then
7952 -- return the newer one as done historically.
7955 Find_Nearer_Entity
(New_S
, Old_S
, It
.Nam
);
7956 if Present
(N_Ent
) then
7964 elsif Within
(Old_S
, Inst
) then
7968 return Report_Overload
;
7971 -- If not within an instance, ambiguity is real
7974 return Report_Overload
;
7988 Present
(First_Formal
(It
.Nam
))
7989 and then Present
(First_Formal
(New_S
))
7990 and then Base_Type
(Etype
(First_Formal
(It
.Nam
))) =
7991 Base_Type
(Etype
(First_Formal
(New_S
)))
7993 Candidate_Renaming
:= It
.Nam
;
7996 Get_Next_Interp
(Ind
, It
);
7999 Set_Entity
(Nam
, Old_S
);
8001 if Old_S
/= Any_Id
then
8002 Set_Is_Overloaded
(Nam
, False);
8005 -- Non-overloaded case
8009 and then Present
(Enclosing_Instance
)
8010 and then Entity_Matches_Spec
(Entity
(Nam
), New_S
)
8012 Old_S
:= Entity
(Nam
);
8014 elsif Entity_Matches_Spec
(Entity
(Nam
), New_S
) then
8015 Candidate_Renaming
:= New_S
;
8017 if Is_Visible_Operation
(Entity
(Nam
)) then
8018 Old_S
:= Entity
(Nam
);
8021 elsif Present
(First_Formal
(Entity
(Nam
)))
8022 and then Present
(First_Formal
(New_S
))
8023 and then Base_Type
(Etype
(First_Formal
(Entity
(Nam
)))) =
8024 Base_Type
(Etype
(First_Formal
(New_S
)))
8026 Candidate_Renaming
:= Entity
(Nam
);
8031 end Find_Renamed_Entity
;
8033 -----------------------------
8034 -- Find_Selected_Component --
8035 -----------------------------
8037 procedure Find_Selected_Component
(N
: Node_Id
) is
8038 P
: constant Node_Id
:= Prefix
(N
);
8041 -- Entity denoted by prefix
8048 function Available_Subtype
return Boolean;
8049 -- A small optimization: if the prefix is constrained and the component
8050 -- is an array type we may already have a usable subtype for it, so we
8051 -- can use it rather than generating a new one, because the bounds
8052 -- will be the values of the discriminants and not discriminant refs.
8053 -- This simplifies value tracing in GNATprove. For consistency, both
8054 -- the entity name and the subtype come from the constrained component.
8056 -- This is only used in GNATprove mode: when generating code it may be
8057 -- necessary to create an itype in the scope of use of the selected
8058 -- component, e.g. in the context of a expanded record equality.
8060 function Is_Reference_In_Subunit
return Boolean;
8061 -- In a subunit, the scope depth is not a proper measure of hiding,
8062 -- because the context of the proper body may itself hide entities in
8063 -- parent units. This rare case requires inspecting the tree directly
8064 -- because the proper body is inserted in the main unit and its context
8065 -- is simply added to that of the parent.
8067 -----------------------
8068 -- Available_Subtype --
8069 -----------------------
8071 function Available_Subtype
return Boolean is
8075 if GNATprove_Mode
then
8076 Comp
:= First_Entity
(Etype
(P
));
8077 while Present
(Comp
) loop
8078 if Chars
(Comp
) = Chars
(Selector_Name
(N
)) then
8079 Set_Etype
(N
, Etype
(Comp
));
8080 Set_Entity
(Selector_Name
(N
), Comp
);
8081 Set_Etype
(Selector_Name
(N
), Etype
(Comp
));
8085 Next_Component
(Comp
);
8090 end Available_Subtype
;
8092 -----------------------------
8093 -- Is_Reference_In_Subunit --
8094 -----------------------------
8096 function Is_Reference_In_Subunit
return Boolean is
8098 Comp_Unit
: Node_Id
;
8102 while Present
(Comp_Unit
)
8103 and then Nkind
(Comp_Unit
) /= N_Compilation_Unit
8105 Comp_Unit
:= Parent
(Comp_Unit
);
8108 if No
(Comp_Unit
) or else Nkind
(Unit
(Comp_Unit
)) /= N_Subunit
then
8112 -- Now check whether the package is in the context of the subunit
8114 Clause
:= First
(Context_Items
(Comp_Unit
));
8115 while Present
(Clause
) loop
8116 if Nkind
(Clause
) = N_With_Clause
8117 and then Entity
(Name
(Clause
)) = P_Name
8126 end Is_Reference_In_Subunit
;
8128 -- Start of processing for Find_Selected_Component
8133 if Nkind
(P
) = N_Error
then
8137 -- If the selector already has an entity, the node has been constructed
8138 -- in the course of expansion, and is known to be valid. Do not verify
8139 -- that it is defined for the type (it may be a private component used
8140 -- in the expansion of record equality).
8142 if Present
(Entity
(Selector_Name
(N
))) then
8143 if No
(Etype
(N
)) or else Etype
(N
) = Any_Type
then
8145 Sel_Name
: constant Node_Id
:= Selector_Name
(N
);
8146 Selector
: constant Entity_Id
:= Entity
(Sel_Name
);
8150 Set_Etype
(Sel_Name
, Etype
(Selector
));
8152 if not Is_Entity_Name
(P
) then
8156 -- Build an actual subtype except for the first parameter
8157 -- of an init proc, where this actual subtype is by
8158 -- definition incorrect, since the object is uninitialized
8159 -- (and does not even have defined discriminants etc.)
8161 if Is_Entity_Name
(P
)
8162 and then Ekind
(Entity
(P
)) = E_Function
8164 Nam
:= New_Copy
(P
);
8166 if Is_Overloaded
(P
) then
8167 Save_Interps
(P
, Nam
);
8170 Rewrite
(P
, Make_Function_Call
(Sloc
(P
), Name
=> Nam
));
8172 Analyze_Selected_Component
(N
);
8175 elsif Ekind
(Selector
) = E_Component
8176 and then (not Is_Entity_Name
(P
)
8177 or else Chars
(Entity
(P
)) /= Name_uInit
)
8179 -- Check if we already have an available subtype we can use
8181 if Ekind
(Etype
(P
)) = E_Record_Subtype
8182 and then Nkind
(Parent
(Etype
(P
))) = N_Subtype_Declaration
8183 and then Is_Array_Type
(Etype
(Selector
))
8184 and then not Is_Packed
(Etype
(Selector
))
8185 and then Available_Subtype
8189 -- Do not build the subtype when referencing components of
8190 -- dispatch table wrappers. Required to avoid generating
8191 -- elaboration code with HI runtimes.
8193 elsif Is_RTE
(Scope
(Selector
), RE_Dispatch_Table_Wrapper
)
8195 Is_RTE
(Scope
(Selector
), RE_No_Dispatch_Table_Wrapper
)
8200 Build_Actual_Subtype_Of_Component
8201 (Etype
(Selector
), N
);
8208 if No
(C_Etype
) then
8209 C_Etype
:= Etype
(Selector
);
8211 Insert_Action
(N
, C_Etype
);
8212 C_Etype
:= Defining_Identifier
(C_Etype
);
8215 Set_Etype
(N
, C_Etype
);
8218 -- If the selected component appears within a default expression
8219 -- and it has an actual subtype, the preanalysis has not yet
8220 -- completed its analysis, because Insert_Actions is disabled in
8221 -- that context. Within the init proc of the enclosing type we
8222 -- must complete this analysis, if an actual subtype was created.
8224 elsif Inside_Init_Proc
then
8226 Typ
: constant Entity_Id
:= Etype
(N
);
8227 Decl
: constant Node_Id
:= Declaration_Node
(Typ
);
8229 if Nkind
(Decl
) = N_Subtype_Declaration
8230 and then not Analyzed
(Decl
)
8231 and then Is_List_Member
(Decl
)
8232 and then No
(Parent
(Decl
))
8235 Insert_Action
(N
, Decl
);
8242 elsif Is_Entity_Name
(P
) then
8243 P_Name
:= Entity
(P
);
8245 -- The prefix may denote an enclosing type which is the completion
8246 -- of an incomplete type declaration.
8248 if Is_Type
(P_Name
) then
8249 Set_Entity
(P
, Get_Full_View
(P_Name
));
8250 Set_Etype
(P
, Entity
(P
));
8251 P_Name
:= Entity
(P
);
8254 P_Type
:= Base_Type
(Etype
(P
));
8256 if Debug_Flag_E
then
8257 Write_Str
("Found prefix type to be ");
8258 Write_Entity_Info
(P_Type
, " "); Write_Eol
;
8261 -- If the prefix's type is an access type, get to the record type
8263 if Is_Access_Type
(P_Type
) then
8264 P_Type
:= Implicitly_Designated_Type
(P_Type
);
8267 -- First check for components of a record object (not the result of
8268 -- a call, which is handled below). This also covers the case where
8269 -- the extension feature that supports the prefixed form of calls
8270 -- for primitives of untagged types is enabled (excluding concurrent
8271 -- cases, which are handled further below).
8274 and then (Has_Components
(P_Type
)
8275 or else (Core_Extensions_Allowed
8276 and then not Is_Concurrent_Type
(P_Type
)))
8277 and then not Is_Overloadable
(P_Name
)
8278 and then not Is_Type
(P_Name
)
8280 -- Selected component of record. Type checking will validate
8281 -- name of selector.
8283 -- ??? Could we rewrite an implicit dereference into an explicit
8286 Analyze_Selected_Component
(N
);
8288 -- Reference to type name in predicate/invariant expression
8290 elsif Is_Concurrent_Type
(P_Type
)
8291 and then not In_Open_Scopes
(P_Name
)
8292 and then (not Is_Concurrent_Type
(Etype
(P_Name
))
8293 or else not In_Open_Scopes
(Etype
(P_Name
)))
8295 -- Call to protected operation or entry. Type checking is
8296 -- needed on the prefix.
8298 Analyze_Selected_Component
(N
);
8300 elsif (In_Open_Scopes
(P_Name
)
8301 and then Ekind
(P_Name
) /= E_Void
8302 and then not Is_Overloadable
(P_Name
))
8303 or else (Is_Concurrent_Type
(Etype
(P_Name
))
8304 and then In_Open_Scopes
(Etype
(P_Name
)))
8306 -- Prefix denotes an enclosing loop, block, or task, i.e. an
8307 -- enclosing construct that is not a subprogram or accept.
8309 -- A special case: a protected body may call an operation
8310 -- on an external object of the same type, in which case it
8311 -- is not an expanded name. If the prefix is the type itself,
8312 -- or the context is a single synchronized object it can only
8313 -- be interpreted as an expanded name.
8315 if Is_Concurrent_Type
(Etype
(P_Name
)) then
8317 or else Present
(Anonymous_Object
(Etype
(P_Name
)))
8319 Find_Expanded_Name
(N
);
8322 Analyze_Selected_Component
(N
);
8327 Find_Expanded_Name
(N
);
8330 elsif Ekind
(P_Name
) = E_Package
then
8331 Find_Expanded_Name
(N
);
8333 elsif Is_Overloadable
(P_Name
) then
8335 -- The subprogram may be a renaming (of an enclosing scope) as
8336 -- in the case of the name of the generic within an instantiation.
8338 if Ekind
(P_Name
) in E_Procedure | E_Function
8339 and then Present
(Alias
(P_Name
))
8340 and then Is_Generic_Instance
(Alias
(P_Name
))
8342 P_Name
:= Alias
(P_Name
);
8345 if Is_Overloaded
(P
) then
8347 -- The prefix must resolve to a unique enclosing construct
8350 Found
: Boolean := False;
8355 Get_First_Interp
(P
, Ind
, It
);
8356 while Present
(It
.Nam
) loop
8357 if In_Open_Scopes
(It
.Nam
) then
8360 "prefix must be unique enclosing scope", N
);
8361 Set_Entity
(N
, Any_Id
);
8362 Set_Etype
(N
, Any_Type
);
8371 Get_Next_Interp
(Ind
, It
);
8376 if In_Open_Scopes
(P_Name
) then
8377 Set_Entity
(P
, P_Name
);
8378 Set_Is_Overloaded
(P
, False);
8379 Find_Expanded_Name
(N
);
8382 -- If no interpretation as an expanded name is possible, it
8383 -- must be a selected component of a record returned by a
8384 -- function call. Reformat prefix as a function call, the rest
8385 -- is done by type resolution.
8387 -- Error if the prefix is procedure or entry, as is P.X
8389 if Ekind
(P_Name
) /= E_Function
8391 (not Is_Overloaded
(P
)
8392 or else Nkind
(Parent
(N
)) = N_Procedure_Call_Statement
)
8394 -- Prefix may mention a package that is hidden by a local
8395 -- declaration: let the user know. Scan the full homonym
8396 -- chain, the candidate package may be anywhere on it.
8398 if Present
(Homonym
(Current_Entity
(P_Name
))) then
8399 P_Name
:= Current_Entity
(P_Name
);
8401 while Present
(P_Name
) loop
8402 exit when Ekind
(P_Name
) = E_Package
;
8403 P_Name
:= Homonym
(P_Name
);
8406 if Present
(P_Name
) then
8407 if not Is_Reference_In_Subunit
then
8408 Error_Msg_Sloc
:= Sloc
(Entity
(Prefix
(N
)));
8410 ("package& is hidden by declaration#", N
, P_Name
);
8413 Set_Entity
(Prefix
(N
), P_Name
);
8414 Find_Expanded_Name
(N
);
8418 P_Name
:= Entity
(Prefix
(N
));
8423 ("invalid prefix in selected component&", N
, P_Name
);
8424 Change_Selected_Component_To_Expanded_Name
(N
);
8425 Set_Entity
(N
, Any_Id
);
8426 Set_Etype
(N
, Any_Type
);
8428 -- Here we have a function call, so do the reformatting
8431 Nam
:= New_Copy
(P
);
8432 Save_Interps
(P
, Nam
);
8434 -- We use Replace here because this is one of those cases
8435 -- where the parser has missclassified the node, and we fix
8436 -- things up and then do the semantic analysis on the fixed
8437 -- up node. Normally we do this using one of the Sinfo.CN
8438 -- routines, but this is too tricky for that.
8440 -- Note that using Rewrite would be wrong, because we would
8441 -- have a tree where the original node is unanalyzed.
8444 Make_Function_Call
(Sloc
(P
), Name
=> Nam
));
8446 -- Now analyze the reformatted node
8450 -- If the prefix is illegal after this transformation, there
8451 -- may be visibility errors on the prefix. The safest is to
8452 -- treat the selected component as an error.
8454 if Error_Posted
(P
) then
8455 Set_Etype
(N
, Any_Type
);
8459 Analyze_Selected_Component
(N
);
8464 -- Remaining cases generate various error messages
8467 -- Format node as expanded name, to avoid cascaded errors
8469 Change_Selected_Component_To_Expanded_Name
(N
);
8470 Set_Entity
(N
, Any_Id
);
8471 Set_Etype
(N
, Any_Type
);
8473 -- Issue error message, but avoid this if error issued already.
8474 -- Use identifier of prefix if one is available.
8476 if P_Name
= Any_Id
then
8479 -- It is not an error if the prefix is the current instance of
8480 -- type name, e.g. the expression of a type aspect, when it is
8481 -- analyzed within a generic unit. We still have to verify that a
8482 -- component of that name exists, and decorate the node
8485 elsif Is_Entity_Name
(P
) and then Is_Current_Instance
(P
) then
8490 Comp
:= First_Entity
(Entity
(P
));
8491 while Present
(Comp
) loop
8492 if Chars
(Comp
) = Chars
(Selector_Name
(N
)) then
8493 Set_Entity
(N
, Comp
);
8494 Set_Etype
(N
, Etype
(Comp
));
8495 Set_Entity
(Selector_Name
(N
), Comp
);
8496 Set_Etype
(Selector_Name
(N
), Etype
(Comp
));
8504 elsif Is_Self_Hidden
(P_Name
) then
8505 Premature_Usage
(P
);
8507 elsif Ekind
(P_Name
) = E_Generic_Package
then
8508 Error_Msg_N
("prefix must not be a generic package", N
);
8509 Error_Msg_N
("\use package instantiation as prefix instead", N
);
8511 elsif Nkind
(P
) /= N_Attribute_Reference
then
8513 -- This may have been meant as a prefixed call to a primitive
8514 -- of an untagged type. If it is a function call check type of
8515 -- its first formal and add explanation.
8518 F
: constant Entity_Id
:=
8519 Current_Entity
(Selector_Name
(N
));
8522 and then Is_Overloadable
(F
)
8523 and then Present
(First_Entity
(F
))
8524 and then not Is_Tagged_Type
(Etype
(First_Entity
(F
)))
8527 ("prefixed call is only allowed for objects of a "
8528 & "tagged type unless -gnatX is used", N
);
8530 if not Core_Extensions_Allowed
8532 Try_Object_Operation
(N
, Allow_Extensions
=> True)
8535 ("\using -gnatX would make the prefixed call legal",
8541 Error_Msg_N
("invalid prefix in selected component&", P
);
8543 if Is_Incomplete_Type
(P_Type
)
8544 and then Is_Access_Type
(Etype
(P
))
8547 ("\dereference must not be of an incomplete type "
8548 & "(RM 3.10.1)", P
);
8552 Error_Msg_N
("invalid prefix in selected component", P
);
8556 -- If prefix is not the name of an entity, it must be an expression,
8557 -- whose type is appropriate for a record. This is determined by
8560 Analyze_Selected_Component
(N
);
8563 Analyze_Dimension
(N
);
8564 end Find_Selected_Component
;
8570 procedure Find_Type
(N
: Node_Id
) is
8580 elsif Nkind
(N
) = N_Attribute_Reference
then
8582 -- Class attribute. This is not valid in Ada 83 mode, but we do not
8583 -- need to enforce that at this point, since the declaration of the
8584 -- tagged type in the prefix would have been flagged already.
8586 if Attribute_Name
(N
) = Name_Class
then
8587 Check_Restriction
(No_Dispatch
, N
);
8588 Find_Type
(Prefix
(N
));
8590 -- Propagate error from bad prefix
8592 if Etype
(Prefix
(N
)) = Any_Type
then
8593 Set_Entity
(N
, Any_Type
);
8594 Set_Etype
(N
, Any_Type
);
8598 T
:= Base_Type
(Entity
(Prefix
(N
)));
8600 -- Case where type is not known to be tagged. Its appearance in
8601 -- the prefix of the 'Class attribute indicates that the full view
8604 if not Is_Tagged_Type
(T
) then
8605 if Ekind
(T
) = E_Incomplete_Type
then
8607 -- It is legal to denote the class type of an incomplete
8608 -- type. The full type will have to be tagged, of course.
8609 -- In Ada 2005 this usage is declared obsolescent, so we
8610 -- warn accordingly. This usage is only legal if the type
8611 -- is completed in the current scope, and not for a limited
8614 if Ada_Version
>= Ada_2005
then
8616 -- Test whether the Available_View of a limited type view
8617 -- is tagged, since the limited view may not be marked as
8618 -- tagged if the type itself has an untagged incomplete
8619 -- type view in its package.
8621 if From_Limited_With
(T
)
8622 and then not Is_Tagged_Type
(Available_View
(T
))
8625 ("prefix of Class attribute must be tagged", N
);
8626 Set_Etype
(N
, Any_Type
);
8627 Set_Entity
(N
, Any_Type
);
8631 if Restriction_Check_Required
(No_Obsolescent_Features
)
8634 (No_Obsolescent_Features
, Prefix
(N
));
8637 if Warn_On_Obsolescent_Feature
then
8639 ("applying ''Class to an untagged incomplete type"
8640 & " is an obsolescent feature (RM J.11)?r?", N
);
8645 Set_Is_Tagged_Type
(T
);
8646 Set_Direct_Primitive_Operations
(T
, New_Elmt_List
);
8647 Make_Class_Wide_Type
(T
);
8648 Set_Entity
(N
, Class_Wide_Type
(T
));
8649 Set_Etype
(N
, Class_Wide_Type
(T
));
8651 elsif Ekind
(T
) = E_Private_Type
8652 and then not Is_Generic_Type
(T
)
8653 and then In_Private_Part
(Scope
(T
))
8655 -- The Class attribute can be applied to an untagged private
8656 -- type fulfilled by a tagged type prior to the full type
8657 -- declaration (but only within the parent package's private
8658 -- part). Create the class-wide type now and check that the
8659 -- full type is tagged later during its analysis. Note that
8660 -- we do not mark the private type as tagged, unlike the
8661 -- case of incomplete types, because the type must still
8662 -- appear untagged to outside units.
8664 if No
(Class_Wide_Type
(T
)) then
8665 Make_Class_Wide_Type
(T
);
8668 Set_Entity
(N
, Class_Wide_Type
(T
));
8669 Set_Etype
(N
, Class_Wide_Type
(T
));
8672 -- Should we introduce a type Any_Tagged and use Wrong_Type
8673 -- here, it would be a bit more consistent???
8676 ("tagged type required, found}",
8677 Prefix
(N
), First_Subtype
(T
));
8678 Set_Entity
(N
, Any_Type
);
8682 -- Case of tagged type
8685 if Is_Concurrent_Type
(T
) then
8686 if No
(Corresponding_Record_Type
(Entity
(Prefix
(N
)))) then
8688 -- Previous error. Create a class-wide type for the
8689 -- synchronized type itself, with minimal semantic
8690 -- attributes, to catch other errors in some ACATS tests.
8692 pragma Assert
(Serious_Errors_Detected
/= 0);
8693 Make_Class_Wide_Type
(T
);
8694 C
:= Class_Wide_Type
(T
);
8695 Set_First_Entity
(C
, First_Entity
(T
));
8698 C
:= Class_Wide_Type
8699 (Corresponding_Record_Type
(Entity
(Prefix
(N
))));
8703 C
:= Class_Wide_Type
(Entity
(Prefix
(N
)));
8706 Set_Entity_With_Checks
(N
, C
);
8707 Generate_Reference
(C
, N
);
8711 -- Base attribute, not allowed in Ada 83
8713 elsif Attribute_Name
(N
) = Name_Base
then
8714 if Ada_Version
= Ada_83
and then Comes_From_Source
(N
) then
8716 ("(Ada 83) Base attribute not allowed in subtype mark", N
);
8719 Find_Type
(Prefix
(N
));
8720 Typ
:= Entity
(Prefix
(N
));
8722 if Ada_Version
>= Ada_95
8723 and then not Is_Scalar_Type
(Typ
)
8724 and then not Is_Generic_Type
(Typ
)
8727 ("prefix of Base attribute must be scalar type",
8730 elsif Warn_On_Redundant_Constructs
8731 and then Base_Type
(Typ
) = Typ
8733 Error_Msg_NE
-- CODEFIX
8734 ("redundant attribute, & is its own base type?r?", N
, Typ
);
8737 T
:= Base_Type
(Typ
);
8739 -- Rewrite attribute reference with type itself (see similar
8740 -- processing in Analyze_Attribute, case Base). Preserve prefix
8741 -- if present, for other legality checks.
8743 if Nkind
(Prefix
(N
)) = N_Expanded_Name
then
8745 Make_Expanded_Name
(Sloc
(N
),
8747 Prefix
=> New_Copy
(Prefix
(Prefix
(N
))),
8748 Selector_Name
=> New_Occurrence_Of
(T
, Sloc
(N
))));
8751 Rewrite
(N
, New_Occurrence_Of
(T
, Sloc
(N
)));
8758 elsif Attribute_Name
(N
) = Name_Stub_Type
then
8760 -- This is handled in Analyze_Attribute
8764 -- All other attributes are invalid in a subtype mark
8767 Error_Msg_N
("invalid attribute in subtype mark", N
);
8773 if Is_Entity_Name
(N
) then
8774 T_Name
:= Entity
(N
);
8776 Error_Msg_N
("subtype mark required in this context", N
);
8777 Set_Etype
(N
, Any_Type
);
8781 if T_Name
= Any_Id
or else Etype
(N
) = Any_Type
then
8783 -- Undefined id. Make it into a valid type
8785 Set_Entity
(N
, Any_Type
);
8787 elsif not Is_Type
(T_Name
)
8788 and then T_Name
/= Standard_Void_Type
8790 Error_Msg_Sloc
:= Sloc
(T_Name
);
8791 Error_Msg_N
("subtype mark required in this context", N
);
8792 Error_Msg_NE
("\\found & declared#", N
, T_Name
);
8793 Set_Entity
(N
, Any_Type
);
8796 -- If the type is an incomplete type created to handle
8797 -- anonymous access components of a record type, then the
8798 -- incomplete type is the visible entity and subsequent
8799 -- references will point to it. Mark the original full
8800 -- type as referenced, to prevent spurious warnings.
8802 if Is_Incomplete_Type
(T_Name
)
8803 and then Present
(Full_View
(T_Name
))
8804 and then not Comes_From_Source
(T_Name
)
8806 Set_Referenced
(Full_View
(T_Name
));
8809 T_Name
:= Get_Full_View
(T_Name
);
8811 -- Ada 2005 (AI-251, AI-50217): Handle interfaces visible through
8812 -- limited-with clauses
8814 if From_Limited_With
(T_Name
)
8815 and then Is_Incomplete_Type
(T_Name
)
8816 and then Present
(Non_Limited_View
(T_Name
))
8817 and then Is_Interface
(Non_Limited_View
(T_Name
))
8819 T_Name
:= Non_Limited_View
(T_Name
);
8822 if In_Open_Scopes
(T_Name
) then
8823 if Ekind
(Base_Type
(T_Name
)) = E_Task_Type
then
8825 -- In Ada 2005, a task name can be used in an access
8826 -- definition within its own body.
8828 if Ada_Version
>= Ada_2005
8829 and then Nkind
(Parent
(N
)) = N_Access_Definition
8831 Set_Entity
(N
, T_Name
);
8832 Set_Etype
(N
, T_Name
);
8837 ("task type cannot be used as type mark " &
8838 "within its own spec or body", N
);
8841 elsif Ekind
(Base_Type
(T_Name
)) = E_Protected_Type
then
8843 -- In Ada 2005, a protected name can be used in an access
8844 -- definition within its own body.
8846 if Ada_Version
>= Ada_2005
8847 and then Nkind
(Parent
(N
)) = N_Access_Definition
8849 Set_Entity
(N
, T_Name
);
8850 Set_Etype
(N
, T_Name
);
8855 ("protected type cannot be used as type mark " &
8856 "within its own spec or body", N
);
8860 Error_Msg_N
("type declaration cannot refer to itself", N
);
8863 Set_Etype
(N
, Any_Type
);
8864 Set_Entity
(N
, Any_Type
);
8865 Set_Error_Posted
(T_Name
);
8869 Set_Entity
(N
, T_Name
);
8870 Set_Etype
(N
, T_Name
);
8874 if Present
(Etype
(N
)) and then Comes_From_Source
(N
) then
8875 if Is_Fixed_Point_Type
(Etype
(N
)) then
8876 Check_Restriction
(No_Fixed_Point
, N
);
8877 elsif Is_Floating_Point_Type
(Etype
(N
)) then
8878 Check_Restriction
(No_Floating_Point
, N
);
8881 -- A Ghost type must appear in a specific context
8883 if Is_Ghost_Entity
(Etype
(N
)) then
8884 Check_Ghost_Context
(Etype
(N
), N
);
8889 --------------------
8890 -- Has_Components --
8891 --------------------
8893 function Has_Components
(Typ
: Entity_Id
) return Boolean is
8895 return Is_Record_Type
(Typ
)
8896 or else (Is_Private_Type
(Typ
) and then Has_Discriminants
(Typ
))
8897 or else (Is_Task_Type
(Typ
) and then Has_Discriminants
(Typ
))
8898 or else (Is_Incomplete_Type
(Typ
)
8899 and then From_Limited_With
(Typ
)
8900 and then Is_Record_Type
(Available_View
(Typ
)));
8903 ------------------------------------
8904 -- Has_Implicit_Character_Literal --
8905 ------------------------------------
8907 function Has_Implicit_Character_Literal
(N
: Node_Id
) return Boolean is
8909 Found
: Boolean := False;
8910 P
: constant Entity_Id
:= Entity
(Prefix
(N
));
8911 Priv_Id
: Entity_Id
:= Empty
;
8914 if Ekind
(P
) = E_Package
and then not In_Open_Scopes
(P
) then
8915 Priv_Id
:= First_Private_Entity
(P
);
8918 if P
= Standard_Standard
then
8919 Change_Selected_Component_To_Expanded_Name
(N
);
8920 Rewrite
(N
, Selector_Name
(N
));
8922 Set_Etype
(Original_Node
(N
), Standard_Character
);
8926 Id
:= First_Entity
(P
);
8927 while Present
(Id
) and then Id
/= Priv_Id
loop
8928 if Is_Standard_Character_Type
(Id
) and then Is_Base_Type
(Id
) then
8930 -- We replace the node with the literal itself, resolve as a
8931 -- character, and set the type correctly.
8934 Change_Selected_Component_To_Expanded_Name
(N
);
8935 Rewrite
(N
, Selector_Name
(N
));
8938 Set_Etype
(Original_Node
(N
), Id
);
8942 -- More than one type derived from Character in given scope.
8943 -- Collect all possible interpretations.
8945 Add_One_Interp
(N
, Id
, Id
);
8953 end Has_Implicit_Character_Literal
;
8955 ----------------------
8956 -- Has_Private_With --
8957 ----------------------
8959 function Has_Private_With
(E
: Entity_Id
) return Boolean is
8960 Comp_Unit
: constant Node_Id
:= Cunit
(Current_Sem_Unit
);
8964 Item
:= First
(Context_Items
(Comp_Unit
));
8965 while Present
(Item
) loop
8966 if Nkind
(Item
) = N_With_Clause
8967 and then Private_Present
(Item
)
8968 and then Entity
(Name
(Item
)) = E
8977 end Has_Private_With
;
8979 ---------------------------
8980 -- Has_Implicit_Operator --
8981 ---------------------------
8983 function Has_Implicit_Operator
(N
: Node_Id
) return Boolean is
8984 Op_Id
: constant Name_Id
:= Chars
(Selector_Name
(N
));
8985 P
: constant Entity_Id
:= Entity
(Prefix
(N
));
8987 Priv_Id
: Entity_Id
:= Empty
;
8989 procedure Add_Implicit_Operator
8991 Op_Type
: Entity_Id
:= Empty
);
8992 -- Add implicit interpretation to node N, using the type for which a
8993 -- predefined operator exists. If the operator yields a boolean type,
8994 -- the Operand_Type is implicitly referenced by the operator, and a
8995 -- reference to it must be generated.
8997 ---------------------------
8998 -- Add_Implicit_Operator --
8999 ---------------------------
9001 procedure Add_Implicit_Operator
9003 Op_Type
: Entity_Id
:= Empty
)
9005 Predef_Op
: Entity_Id
;
9008 Predef_Op
:= Current_Entity
(Selector_Name
(N
));
9009 while Present
(Predef_Op
)
9010 and then Scope
(Predef_Op
) /= Standard_Standard
9012 Predef_Op
:= Homonym
(Predef_Op
);
9015 if Nkind
(N
) = N_Selected_Component
then
9016 Change_Selected_Component_To_Expanded_Name
(N
);
9019 -- If the context is an unanalyzed function call, determine whether
9020 -- a binary or unary interpretation is required.
9022 if Nkind
(Parent
(N
)) = N_Indexed_Component
then
9024 Is_Binary_Call
: constant Boolean :=
9026 (Next
(First
(Expressions
(Parent
(N
)))));
9027 Is_Binary_Op
: constant Boolean :=
9029 (Predef_Op
) /= Last_Entity
(Predef_Op
);
9030 Predef_Op2
: constant Entity_Id
:= Homonym
(Predef_Op
);
9033 if Is_Binary_Call
then
9034 if Is_Binary_Op
then
9035 Add_One_Interp
(N
, Predef_Op
, T
);
9037 Add_One_Interp
(N
, Predef_Op2
, T
);
9040 if not Is_Binary_Op
then
9041 Add_One_Interp
(N
, Predef_Op
, T
);
9043 -- Predef_Op2 may be empty in case of previous errors
9045 elsif Present
(Predef_Op2
) then
9046 Add_One_Interp
(N
, Predef_Op2
, T
);
9052 Add_One_Interp
(N
, Predef_Op
, T
);
9054 -- For operators with unary and binary interpretations, if
9055 -- context is not a call, add both
9057 if Present
(Homonym
(Predef_Op
)) then
9058 Add_One_Interp
(N
, Homonym
(Predef_Op
), T
);
9062 -- The node is a reference to a predefined operator, and
9063 -- an implicit reference to the type of its operands.
9065 if Present
(Op_Type
) then
9066 Generate_Operator_Reference
(N
, Op_Type
);
9068 Generate_Operator_Reference
(N
, T
);
9070 end Add_Implicit_Operator
;
9072 -- Start of processing for Has_Implicit_Operator
9075 if Ekind
(P
) = E_Package
and then not In_Open_Scopes
(P
) then
9076 Priv_Id
:= First_Private_Entity
(P
);
9079 Id
:= First_Entity
(P
);
9083 -- Boolean operators: an implicit declaration exists if the scope
9084 -- contains a declaration for a derived Boolean type, or for an
9085 -- array of Boolean type.
9092 while Id
/= Priv_Id
loop
9094 and then Valid_Boolean_Arg
(Id
)
9095 and then Is_Base_Type
(Id
)
9097 Add_Implicit_Operator
(Id
);
9104 -- Equality: look for any non-limited type (result is Boolean)
9109 while Id
/= Priv_Id
loop
9111 and then Valid_Equality_Arg
(Id
)
9112 and then Is_Base_Type
(Id
)
9114 Add_Implicit_Operator
(Standard_Boolean
, Id
);
9121 -- Comparison operators: scalar type, or array of scalar
9128 while Id
/= Priv_Id
loop
9130 and then Valid_Comparison_Arg
(Id
)
9131 and then Is_Base_Type
(Id
)
9133 Add_Implicit_Operator
(Standard_Boolean
, Id
);
9140 -- Arithmetic operators: any numeric type
9151 while Id
/= Priv_Id
loop
9152 if Is_Numeric_Type
(Id
) and then Is_Base_Type
(Id
) then
9153 Add_Implicit_Operator
(Id
);
9160 -- Concatenation: any one-dimensional array type
9162 when Name_Op_Concat
=>
9163 while Id
/= Priv_Id
loop
9164 if Is_Array_Type
(Id
)
9165 and then Number_Dimensions
(Id
) = 1
9166 and then Is_Base_Type
(Id
)
9168 Add_Implicit_Operator
(Id
);
9175 -- What is the others condition here? Should we be using a
9176 -- subtype of Name_Id that would restrict to operators ???
9182 -- If we fall through, then we do not have an implicit operator
9185 end Has_Implicit_Operator
;
9187 -----------------------------------
9188 -- Has_Loop_In_Inner_Open_Scopes --
9189 -----------------------------------
9191 function Has_Loop_In_Inner_Open_Scopes
(S
: Entity_Id
) return Boolean is
9193 -- Several scope stacks are maintained by Scope_Stack. The base of the
9194 -- currently active scope stack is denoted by the Is_Active_Stack_Base
9195 -- flag in the scope stack entry. Note that the scope stacks used to
9196 -- simply be delimited implicitly by the presence of Standard_Standard
9197 -- at their base, but there now are cases where this is not sufficient
9198 -- because Standard_Standard actually may appear in the middle of the
9199 -- active set of scopes.
9201 for J
in reverse 0 .. Scope_Stack
.Last
loop
9203 -- S was reached without seing a loop scope first
9205 if Scope_Stack
.Table
(J
).Entity
= S
then
9208 -- S was not yet reached, so it contains at least one inner loop
9210 elsif Ekind
(Scope_Stack
.Table
(J
).Entity
) = E_Loop
then
9214 -- Check Is_Active_Stack_Base to tell us when to stop, as there are
9215 -- cases where Standard_Standard appears in the middle of the active
9216 -- set of scopes. This affects the declaration and overriding of
9217 -- private inherited operations in instantiations of generic child
9220 pragma Assert
(not Scope_Stack
.Table
(J
).Is_Active_Stack_Base
);
9223 raise Program_Error
; -- unreachable
9224 end Has_Loop_In_Inner_Open_Scopes
;
9226 --------------------
9227 -- In_Open_Scopes --
9228 --------------------
9230 function In_Open_Scopes
(S
: Entity_Id
) return Boolean is
9232 -- Several scope stacks are maintained by Scope_Stack. The base of the
9233 -- currently active scope stack is denoted by the Is_Active_Stack_Base
9234 -- flag in the scope stack entry. Note that the scope stacks used to
9235 -- simply be delimited implicitly by the presence of Standard_Standard
9236 -- at their base, but there now are cases where this is not sufficient
9237 -- because Standard_Standard actually may appear in the middle of the
9238 -- active set of scopes.
9240 for J
in reverse 0 .. Scope_Stack
.Last
loop
9241 if Scope_Stack
.Table
(J
).Entity
= S
then
9245 -- Check Is_Active_Stack_Base to tell us when to stop, as there are
9246 -- cases where Standard_Standard appears in the middle of the active
9247 -- set of scopes. This affects the declaration and overriding of
9248 -- private inherited operations in instantiations of generic child
9251 exit when Scope_Stack
.Table
(J
).Is_Active_Stack_Base
;
9257 -----------------------------
9258 -- Inherit_Renamed_Profile --
9259 -----------------------------
9261 procedure Inherit_Renamed_Profile
(New_S
: Entity_Id
; Old_S
: Entity_Id
) is
9268 if Ekind
(Old_S
) = E_Operator
then
9269 New_F
:= First_Formal
(New_S
);
9271 while Present
(New_F
) loop
9272 Set_Etype
(New_F
, Base_Type
(Etype
(New_F
)));
9273 Next_Formal
(New_F
);
9276 Set_Etype
(New_S
, Base_Type
(Etype
(New_S
)));
9279 New_F
:= First_Formal
(New_S
);
9280 Old_F
:= First_Formal
(Old_S
);
9282 while Present
(New_F
) loop
9283 New_T
:= Etype
(New_F
);
9284 Old_T
:= Etype
(Old_F
);
9286 -- If the new type is a renaming of the old one, as is the case
9287 -- for actuals in instances, retain its name, to simplify later
9290 if Nkind
(Parent
(New_T
)) = N_Subtype_Declaration
9291 and then Is_Entity_Name
(Subtype_Indication
(Parent
(New_T
)))
9292 and then Entity
(Subtype_Indication
(Parent
(New_T
))) = Old_T
9296 Set_Etype
(New_F
, Old_T
);
9299 Next_Formal
(New_F
);
9300 Next_Formal
(Old_F
);
9303 pragma Assert
(No
(Old_F
));
9305 if Ekind
(Old_S
) in E_Function | E_Enumeration_Literal
then
9306 Set_Etype
(New_S
, Etype
(Old_S
));
9309 end Inherit_Renamed_Profile
;
9315 procedure Initialize
is
9320 -------------------------
9321 -- Install_Use_Clauses --
9322 -------------------------
9324 procedure Install_Use_Clauses
9326 Force_Installation
: Boolean := False)
9332 while Present
(U
) loop
9334 -- Case of USE package
9336 if Nkind
(U
) = N_Use_Package_Clause
then
9337 Use_One_Package
(U
, Name
(U
), True);
9342 Use_One_Type
(Subtype_Mark
(U
), Force
=> Force_Installation
);
9346 Next_Use_Clause
(U
);
9348 end Install_Use_Clauses
;
9350 ----------------------
9351 -- Mark_Use_Clauses --
9352 ----------------------
9354 procedure Mark_Use_Clauses
(Id
: Node_Or_Entity_Id
) is
9355 procedure Mark_Parameters
(Call
: Entity_Id
);
9356 -- Perform use_type_clause marking for all parameters in a subprogram
9357 -- or operator call.
9359 procedure Mark_Use_Package
(Pak
: Entity_Id
);
9360 -- Move up the Prev_Use_Clause chain for packages denoted by Pak -
9361 -- marking each clause in the chain as effective in the process.
9363 procedure Mark_Use_Type
(E
: Entity_Id
);
9364 -- Similar to Do_Use_Package_Marking except we move up the
9365 -- Prev_Use_Clause chain for the type denoted by E.
9367 ---------------------
9368 -- Mark_Parameters --
9369 ---------------------
9371 procedure Mark_Parameters
(Call
: Entity_Id
) is
9375 -- Move through all of the formals
9377 Curr
:= First_Formal
(Call
);
9378 while Present
(Curr
) loop
9379 Mark_Use_Type
(Curr
);
9384 -- Handle the return type
9386 Mark_Use_Type
(Call
);
9387 end Mark_Parameters
;
9389 ----------------------
9390 -- Mark_Use_Package --
9391 ----------------------
9393 procedure Mark_Use_Package
(Pak
: Entity_Id
) is
9397 -- Ignore cases where the scope of the type is not a package (e.g.
9398 -- Standard_Standard).
9400 if Ekind
(Pak
) /= E_Package
then
9404 Curr
:= Current_Use_Clause
(Pak
);
9405 while Present
(Curr
)
9406 and then not Is_Effective_Use_Clause
(Curr
)
9408 -- We need to mark the previous use clauses as effective, but
9409 -- each use clause may in turn render other use_package_clauses
9410 -- effective. Additionally, it is possible to have a parent
9411 -- package renamed as a child of itself so we must check the
9412 -- prefix entity is not the same as the package we are marking.
9414 if Nkind
(Name
(Curr
)) /= N_Identifier
9415 and then Present
(Prefix
(Name
(Curr
)))
9416 and then Entity
(Prefix
(Name
(Curr
))) /= Pak
9418 Mark_Use_Package
(Entity
(Prefix
(Name
(Curr
))));
9420 -- It is also possible to have a child package without a prefix
9421 -- that relies on a previous use_package_clause.
9423 elsif Nkind
(Name
(Curr
)) = N_Identifier
9424 and then Is_Child_Unit
(Entity
(Name
(Curr
)))
9426 Mark_Use_Package
(Scope
(Entity
(Name
(Curr
))));
9429 -- Mark the use_package_clause as effective and move up the chain
9431 Set_Is_Effective_Use_Clause
(Curr
);
9433 Curr
:= Prev_Use_Clause
(Curr
);
9435 end Mark_Use_Package
;
9441 procedure Mark_Use_Type
(E
: Entity_Id
) is
9446 -- Ignore void types and unresolved string literals and primitives
9448 if Nkind
(E
) = N_String_Literal
9449 or else Nkind
(Etype
(E
)) not in N_Entity
9450 or else not Is_Type
(Etype
(E
))
9455 -- Primitives with class-wide operands might additionally render
9456 -- their base type's use_clauses effective - so do a recursive check
9459 Base
:= Base_Type
(Etype
(E
));
9461 if Ekind
(Base
) = E_Class_Wide_Type
then
9462 Mark_Use_Type
(Base
);
9465 -- The package containing the type or operator function being used
9466 -- may be in use as well, so mark any use_package_clauses for it as
9467 -- effective. There are also additional sanity checks performed here
9468 -- for ignoring previous errors.
9470 Mark_Use_Package
(Scope
(Base
));
9472 if Nkind
(E
) in N_Op
9473 and then Present
(Entity
(E
))
9474 and then Present
(Scope
(Entity
(E
)))
9476 Mark_Use_Package
(Scope
(Entity
(E
)));
9479 Curr
:= Current_Use_Clause
(Base
);
9480 while Present
(Curr
)
9481 and then not Is_Effective_Use_Clause
(Curr
)
9483 -- Current use_type_clause may render other use_package_clauses
9486 if Nkind
(Subtype_Mark
(Curr
)) /= N_Identifier
9487 and then Present
(Prefix
(Subtype_Mark
(Curr
)))
9489 Mark_Use_Package
(Entity
(Prefix
(Subtype_Mark
(Curr
))));
9492 -- Mark the use_type_clause as effective and move up the chain
9494 Set_Is_Effective_Use_Clause
(Curr
);
9496 Curr
:= Prev_Use_Clause
(Curr
);
9500 -- Start of processing for Mark_Use_Clauses
9503 -- Use clauses in and of themselves do not count as a "use" of a
9506 if Nkind
(Parent
(Id
)) in N_Use_Package_Clause | N_Use_Type_Clause
then
9512 if Nkind
(Id
) in N_Entity
then
9514 -- Mark the entity's package
9516 if Is_Potentially_Use_Visible
(Id
) then
9517 Mark_Use_Package
(Scope
(Id
));
9520 -- Mark enumeration literals
9522 if Ekind
(Id
) = E_Enumeration_Literal
then
9527 elsif (Is_Overloadable
(Id
)
9528 or else Is_Generic_Subprogram
(Id
))
9529 and then (Is_Potentially_Use_Visible
(Id
)
9530 or else Is_Intrinsic_Subprogram
(Id
)
9531 or else (Ekind
(Id
) in E_Function | E_Procedure
9532 and then Is_Generic_Actual_Subprogram
(Id
)))
9534 Mark_Parameters
(Id
);
9542 if Nkind
(Id
) in N_Op
then
9544 -- At this point the left operand may not be resolved if we are
9545 -- encountering multiple operators next to eachother in an
9548 if Nkind
(Id
) in N_Binary_Op
9549 and then not (Nkind
(Left_Opnd
(Id
)) in N_Op
)
9551 Mark_Use_Type
(Left_Opnd
(Id
));
9554 Mark_Use_Type
(Right_Opnd
(Id
));
9557 -- Mark entity identifiers
9559 elsif Nkind
(Id
) in N_Has_Entity
9560 and then (Is_Potentially_Use_Visible
(Entity
(Id
))
9561 or else (Is_Generic_Instance
(Entity
(Id
))
9562 and then Is_Immediately_Visible
(Entity
(Id
))))
9564 -- Ignore fully qualified names as they do not count as a "use" of
9567 if Nkind
(Id
) in N_Identifier | N_Operator_Symbol
9568 or else (Present
(Prefix
(Id
))
9569 and then Scope
(Entity
(Id
)) /= Entity
(Prefix
(Id
)))
9571 Mark_Use_Clauses
(Entity
(Id
));
9575 end Mark_Use_Clauses
;
9577 --------------------------------
9578 -- Most_Descendant_Use_Clause --
9579 --------------------------------
9581 function Most_Descendant_Use_Clause
9582 (Clause1
: Entity_Id
;
9583 Clause2
: Entity_Id
) return Entity_Id
9585 function Determine_Package_Scope
(Clause
: Node_Id
) return Entity_Id
;
9586 -- Given a use clause, determine which package it belongs to
9588 -----------------------------
9589 -- Determine_Package_Scope --
9590 -----------------------------
9592 function Determine_Package_Scope
(Clause
: Node_Id
) return Entity_Id
is
9594 -- Check if the clause appears in the context area
9596 -- Note we cannot employ Enclosing_Packge for use clauses within
9597 -- context clauses since they are not actually "enclosed."
9599 if Nkind
(Parent
(Clause
)) = N_Compilation_Unit
then
9600 return Entity_Of_Unit
(Unit
(Parent
(Clause
)));
9603 -- Otherwise, obtain the enclosing package normally
9605 return Enclosing_Package
(Clause
);
9606 end Determine_Package_Scope
;
9611 -- Start of processing for Most_Descendant_Use_Clause
9614 if Clause1
= Clause2
then
9618 -- We determine which one is the most descendant by the scope distance
9619 -- to the ultimate parent unit.
9621 Scope1
:= Determine_Package_Scope
(Clause1
);
9622 Scope2
:= Determine_Package_Scope
(Clause2
);
9623 while Scope1
/= Standard_Standard
9624 and then Scope2
/= Standard_Standard
9626 Scope1
:= Scope
(Scope1
);
9627 Scope2
:= Scope
(Scope2
);
9631 elsif No
(Scope2
) then
9636 if Scope1
= Standard_Standard
then
9641 end Most_Descendant_Use_Clause
;
9647 procedure Pop_Scope
is
9648 SST
: Scope_Stack_Entry
renames Scope_Stack
.Table
(Scope_Stack
.Last
);
9649 S
: constant Scope_Kind_Id
:= SST
.Entity
;
9652 if Debug_Flag_E
then
9656 -- Set Default_Storage_Pool field of the library unit if necessary
9658 if Is_Package_Or_Generic_Package
(S
)
9660 Nkind
(Parent
(Unit_Declaration_Node
(S
))) = N_Compilation_Unit
9663 Aux
: constant Node_Id
:=
9664 Aux_Decls_Node
(Parent
(Unit_Declaration_Node
(S
)));
9666 if No
(Default_Storage_Pool
(Aux
)) then
9667 Set_Default_Storage_Pool
(Aux
, Default_Pool
);
9672 Scope_Suppress
:= SST
.Save_Scope_Suppress
;
9673 Local_Suppress_Stack_Top
:= SST
.Save_Local_Suppress_Stack_Top
;
9674 Check_Policy_List
:= SST
.Save_Check_Policy_List
;
9675 Default_Pool
:= SST
.Save_Default_Storage_Pool
;
9676 No_Tagged_Streams
:= SST
.Save_No_Tagged_Streams
;
9677 SPARK_Mode
:= SST
.Save_SPARK_Mode
;
9678 SPARK_Mode_Pragma
:= SST
.Save_SPARK_Mode_Pragma
;
9679 Default_SSO
:= SST
.Save_Default_SSO
;
9680 Uneval_Old
:= SST
.Save_Uneval_Old
;
9682 if Debug_Flag_W
then
9683 Write_Str
("<-- exiting scope: ");
9684 Write_Name
(Chars
(Current_Scope
));
9685 Write_Str
(", Depth=");
9686 Write_Int
(Int
(Scope_Stack
.Last
));
9690 End_Use_Clauses
(SST
.First_Use_Clause
);
9692 -- If the actions to be wrapped are still there they will get lost
9693 -- causing incomplete code to be generated. It is better to abort in
9694 -- this case (and we do the abort even with assertions off since the
9695 -- penalty is incorrect code generation).
9697 if SST
.Actions_To_Be_Wrapped
/= Scope_Actions
'(others => No_List) then
9698 raise Program_Error;
9701 -- Free last subprogram name if allocated, and pop scope
9703 Free (SST.Last_Subprogram_Name);
9704 Scope_Stack.Decrement_Last;
9711 procedure Push_Scope (S : Scope_Kind_Id) is
9712 E : constant Entity_Id := Scope (S);
9714 function Component_Alignment_Default return Component_Alignment_Kind;
9715 -- Return Component_Alignment_Kind for the newly-pushed scope.
9717 function Component_Alignment_Default return Component_Alignment_Kind is
9719 -- Each new scope pushed onto the scope stack inherits the component
9720 -- alignment of the previous scope. This emulates the "visibility"
9721 -- semantics of pragma Component_Alignment.
9723 if Scope_Stack.Last > Scope_Stack.First then
9724 return Scope_Stack.Table
9725 (Scope_Stack.Last - 1).Component_Alignment_Default;
9727 -- Otherwise, this is the first scope being pushed on the scope
9728 -- stack. Inherit the component alignment from the configuration
9729 -- form of pragma Component_Alignment (if any).
9732 return Configuration_Component_Alignment;
9734 end Component_Alignment_Default;
9737 if Ekind (S) = E_Void then
9740 -- Set scope depth if not a nonconcurrent type, and we have not yet set
9741 -- the scope depth. This means that we have the first occurrence of the
9742 -- scope, and this is where the depth is set.
9744 elsif (not Is_Type (S) or else Is_Concurrent_Type (S))
9745 and then not Scope_Depth_Set (S)
9747 if S = Standard_Standard then
9748 Set_Scope_Depth_Value (S, Uint_0);
9750 elsif Is_Child_Unit (S) then
9751 Set_Scope_Depth_Value (S, Uint_1);
9753 elsif not Is_Record_Type (Current_Scope) then
9754 if Scope_Depth_Set (Current_Scope) then
9755 if Ekind (S) = E_Loop then
9756 Set_Scope_Depth_Value (S, Scope_Depth (Current_Scope));
9758 Set_Scope_Depth_Value (S, Scope_Depth (Current_Scope) + 1);
9764 Scope_Stack.Increment_Last;
9766 Scope_Stack.Table (Scope_Stack.Last) :=
9768 Save_Scope_Suppress => Scope_Suppress,
9769 Save_Local_Suppress_Stack_Top => Local_Suppress_Stack_Top,
9770 Save_Check_Policy_List => Check_Policy_List,
9771 Save_Default_Storage_Pool => Default_Pool,
9772 Save_No_Tagged_Streams => No_Tagged_Streams,
9773 Save_SPARK_Mode => SPARK_Mode,
9774 Save_SPARK_Mode_Pragma => SPARK_Mode_Pragma,
9775 Save_Default_SSO => Default_SSO,
9776 Save_Uneval_Old => Uneval_Old,
9777 Component_Alignment_Default => Component_Alignment_Default,
9778 Last_Subprogram_Name => null,
9779 Is_Transient => False,
9780 Node_To_Be_Wrapped => Empty,
9781 Pending_Freeze_Actions => No_List,
9782 Actions_To_Be_Wrapped => (others => No_List),
9783 First_Use_Clause => Empty,
9784 Is_Active_Stack_Base => False,
9785 Previous_Visibility => False,
9786 Locked_Shared_Objects => No_Elist);
9788 if Debug_Flag_W then
9789 Write_Str ("--> new scope: ");
9790 Write_Name (Chars (Current_Scope));
9791 Write_Str (", Id=");
9792 Write_Int (Int (Current_Scope));
9793 Write_Str (", Depth=");
9794 Write_Int (Int (Scope_Stack.Last));
9798 -- Deal with copying flags from the previous scope to this one. This is
9799 -- not necessary if either scope is standard, or if the new scope is a
9802 if S /= Standard_Standard
9803 and then Scope (S) /= Standard_Standard
9804 and then not Is_Child_Unit (S)
9806 if Nkind (E) not in N_Entity then
9810 -- Copy categorization flags from Scope (S) to S, this is not done
9811 -- when Scope (S) is Standard_Standard since propagation is from
9812 -- library unit entity inwards. Copy other relevant attributes as
9813 -- well (Discard_Names in particular).
9815 -- We only propagate inwards for library level entities,
9816 -- inner level subprograms do not inherit the categorization.
9818 if Is_Library_Level_Entity (S) then
9819 Set_Is_Preelaborated (S, Is_Preelaborated (E));
9820 Set_Is_Shared_Passive (S, Is_Shared_Passive (E));
9821 Set_Discard_Names (S, Discard_Names (E));
9822 Set_Suppress_Value_Tracking_On_Call
9823 (S, Suppress_Value_Tracking_On_Call (E));
9824 Set_Categorization_From_Scope (E => S, Scop => E);
9828 if Is_Child_Unit (S)
9829 and then Present (E)
9830 and then Is_Package_Or_Generic_Package (E)
9832 Nkind (Parent (Unit_Declaration_Node (E))) = N_Compilation_Unit
9835 Aux : constant Node_Id :=
9836 Aux_Decls_Node (Parent (Unit_Declaration_Node (E)));
9838 if Present (Default_Storage_Pool (Aux)) then
9839 Default_Pool := Default_Storage_Pool (Aux);
9845 ---------------------
9846 -- Premature_Usage --
9847 ---------------------
9849 procedure Premature_Usage (N : Node_Id) is
9850 Kind : constant Node_Kind := Nkind (Parent (Entity (N)));
9851 E : Entity_Id := Entity (N);
9854 -- Within an instance, the analysis of the actual for a formal object
9855 -- does not see the name of the object itself. This is significant only
9856 -- if the object is an aggregate, where its analysis does not do any
9857 -- name resolution on component associations. (see 4717-008). In such a
9858 -- case, look for the visible homonym on the chain.
9860 if In_Instance and then Present (Homonym (E)) then
9862 while Present (E) and then not In_Open_Scopes (Scope (E)) loop
9868 Set_Etype (N, Etype (E));
9874 when N_Component_Declaration =>
9876 ("component&! cannot be used before end of record declaration",
9879 when N_Parameter_Specification =>
9881 ("formal parameter&! cannot be used before end of specification",
9884 when N_Discriminant_Specification =>
9886 ("discriminant&! cannot be used before end of discriminant part",
9889 when N_Procedure_Specification | N_Function_Specification =>
9891 ("subprogram&! cannot be used before end of its declaration",
9894 when N_Full_Type_Declaration | N_Subtype_Declaration =>
9896 ("type& cannot be used before end of its declaration!", N);
9900 ("object& cannot be used before end of its declaration!", N);
9902 -- If the premature reference appears as the expression in its own
9903 -- declaration, rewrite it to prevent compiler loops in subsequent
9904 -- uses of this mangled declaration in address clauses.
9906 if Nkind (Parent (N)) = N_Object_Declaration then
9907 Set_Entity (N, Any_Id);
9910 end Premature_Usage;
9912 ------------------------
9913 -- Present_System_Aux --
9914 ------------------------
9916 function Present_System_Aux (N : Node_Id := Empty) return Boolean is
9918 Aux_Name : Unit_Name_Type;
9919 Unum : Unit_Number_Type;
9924 function Find_System (C_Unit : Node_Id) return Entity_Id;
9925 -- Scan context clause of compilation unit to find with_clause
9932 function Find_System (C_Unit : Node_Id) return Entity_Id is
9933 With_Clause : Node_Id;
9936 With_Clause := First (Context_Items (C_Unit));
9937 while Present (With_Clause) loop
9938 if (Nkind (With_Clause) = N_With_Clause
9939 and then Chars (Name (With_Clause)) = Name_System)
9940 and then Comes_From_Source (With_Clause)
9951 -- Start of processing for Present_System_Aux
9954 -- The child unit may have been loaded and analyzed already
9956 if Present (System_Aux_Id) then
9959 -- If no previous pragma for System.Aux, nothing to load
9961 elsif No (System_Extend_Unit) then
9964 -- Use the unit name given in the pragma to retrieve the unit.
9965 -- Verify that System itself appears in the context clause of the
9966 -- current compilation. If System is not present, an error will
9967 -- have been reported already.
9970 With_Sys := Find_System (Cunit (Current_Sem_Unit));
9972 The_Unit := Unit (Cunit (Current_Sem_Unit));
9976 (Nkind (The_Unit) = N_Package_Body
9977 or else (Nkind (The_Unit) = N_Subprogram_Body
9978 and then not Acts_As_Spec (Cunit (Current_Sem_Unit))))
9980 With_Sys := Find_System (Library_Unit (Cunit (Current_Sem_Unit)));
9983 if No (With_Sys) and then Present (N) then
9985 -- If we are compiling a subunit, we need to examine its
9986 -- context as well (Current_Sem_Unit is the parent unit);
9988 The_Unit := Parent (N);
9989 while Nkind (The_Unit) /= N_Compilation_Unit loop
9990 The_Unit := Parent (The_Unit);
9993 if Nkind (Unit (The_Unit)) = N_Subunit then
9994 With_Sys := Find_System (The_Unit);
9998 if No (With_Sys) then
10002 Loc := Sloc (With_Sys);
10003 Get_Name_String (Chars (Expression (System_Extend_Unit)));
10004 Name_Buffer (8 .. Name_Len + 7) := Name_Buffer (1 .. Name_Len);
10005 Name_Buffer (1 .. 7) := "system.";
10006 Name_Buffer (Name_Len + 8) := '%';
10007 Name_Buffer (Name_Len + 9) := 's
';
10008 Name_Len := Name_Len + 9;
10009 Aux_Name := Name_Find;
10013 (Load_Name => Aux_Name,
10016 Error_Node => With_Sys);
10018 if Unum /= No_Unit then
10019 Semantics (Cunit (Unum));
10021 Defining_Entity (Specification (Unit (Cunit (Unum))));
10024 Make_With_Clause (Loc,
10026 Make_Expanded_Name (Loc,
10027 Chars => Chars (System_Aux_Id),
10029 New_Occurrence_Of (Scope (System_Aux_Id), Loc),
10030 Selector_Name => New_Occurrence_Of (System_Aux_Id, Loc)));
10032 Set_Entity (Name (Withn), System_Aux_Id);
10034 Set_Corresponding_Spec (Withn, System_Aux_Id);
10035 Set_First_Name (Withn);
10036 Set_Implicit_With (Withn);
10037 Set_Library_Unit (Withn, Cunit (Unum));
10039 Insert_After (With_Sys, Withn);
10040 Mark_Rewrite_Insertion (Withn);
10041 Set_Context_Installed (Withn);
10045 -- Here if unit load failed
10048 Error_Msg_Name_1 := Name_System;
10049 Error_Msg_Name_2 := Chars (Expression (System_Extend_Unit));
10051 ("extension package `%.%` does not exist",
10052 Opt.System_Extend_Unit);
10056 end Present_System_Aux;
10058 -------------------------
10059 -- Restore_Scope_Stack --
10060 -------------------------
10062 procedure Restore_Scope_Stack
10064 Handle_Use : Boolean := True)
10066 SS_Last : constant Int := Scope_Stack.Last;
10070 -- Restore visibility of previous scope stack, if any, using the list
10071 -- we saved (we use Remove, since this list will not be used again).
10074 Elmt := First_Elmt (List);
10075 exit when Elmt = No_Elmt;
10076 Set_Is_Immediately_Visible (Node (Elmt));
10077 Remove_Elmt (List, Elmt);
10080 -- Restore use clauses
10082 if SS_Last >= Scope_Stack.First
10083 and then Scope_Stack.Table (SS_Last).Entity /= Standard_Standard
10084 and then Handle_Use
10086 Install_Use_Clauses
10087 (Scope_Stack.Table (SS_Last).First_Use_Clause,
10088 Force_Installation => True);
10090 end Restore_Scope_Stack;
10092 ----------------------
10093 -- Save_Scope_Stack --
10094 ----------------------
10096 -- Save_Scope_Stack/Restore_Scope_Stack were originally designed to avoid
10097 -- consuming any memory. That is, Save_Scope_Stack took care of removing
10098 -- from immediate visibility entities and Restore_Scope_Stack took care
10099 -- of restoring their visibility analyzing the context of each entity. The
10100 -- problem of such approach is that it was fragile and caused unexpected
10101 -- visibility problems, and indeed one test was found where there was a
10104 -- Furthermore, the following experiment was carried out:
10106 -- - Save_Scope_Stack was modified to store in an Elist1 all those
10107 -- entities whose attribute Is_Immediately_Visible is modified
10108 -- from True to False.
10110 -- - Restore_Scope_Stack was modified to store in another Elist2
10111 -- all the entities whose attribute Is_Immediately_Visible is
10112 -- modified from False to True.
10114 -- - Extra code was added to verify that all the elements of Elist1
10115 -- are found in Elist2
10117 -- This test shows that there may be more occurrences of this problem which
10118 -- have not yet been detected. As a result, we replaced that approach by
10119 -- the current one in which Save_Scope_Stack returns the list of entities
10120 -- whose visibility is changed, and that list is passed to Restore_Scope_
10121 -- Stack to undo that change. This approach is simpler and safer, although
10122 -- it consumes more memory.
10124 function Save_Scope_Stack (Handle_Use : Boolean := True) return Elist_Id is
10125 Result : constant Elist_Id := New_Elmt_List;
10128 SS_Last : constant Int := Scope_Stack.Last;
10130 procedure Remove_From_Visibility (E : Entity_Id);
10131 -- If E is immediately visible then append it to the result and remove
10132 -- it temporarily from visibility.
10134 ----------------------------
10135 -- Remove_From_Visibility --
10136 ----------------------------
10138 procedure Remove_From_Visibility (E : Entity_Id) is
10140 if Is_Immediately_Visible (E) then
10141 Append_Elmt (E, Result);
10142 Set_Is_Immediately_Visible (E, False);
10144 end Remove_From_Visibility;
10146 -- Start of processing for Save_Scope_Stack
10149 if SS_Last >= Scope_Stack.First
10150 and then Scope_Stack.Table (SS_Last).Entity /= Standard_Standard
10153 End_Use_Clauses (Scope_Stack.Table (SS_Last).First_Use_Clause);
10156 -- If the call is from within a compilation unit, as when called from
10157 -- Rtsfind, make current entries in scope stack invisible while we
10158 -- analyze the new unit.
10160 for J in reverse 0 .. SS_Last loop
10161 exit when Scope_Stack.Table (J).Entity = Standard_Standard
10162 or else No (Scope_Stack.Table (J).Entity);
10164 S := Scope_Stack.Table (J).Entity;
10166 Remove_From_Visibility (S);
10168 E := First_Entity (S);
10169 while Present (E) loop
10170 Remove_From_Visibility (E);
10178 end Save_Scope_Stack;
10184 procedure Set_Use (L : List_Id) is
10189 while Present (Decl) loop
10190 if Nkind (Decl) = N_Use_Package_Clause then
10191 Chain_Use_Clause (Decl);
10192 Use_One_Package (Decl, Name (Decl));
10194 elsif Nkind (Decl) = N_Use_Type_Clause then
10195 Chain_Use_Clause (Decl);
10196 Use_One_Type (Subtype_Mark (Decl));
10204 -----------------------------
10205 -- Update_Use_Clause_Chain --
10206 -----------------------------
10208 procedure Update_Use_Clause_Chain is
10210 procedure Update_Chain_In_Scope (Level : Int);
10211 -- Iterate through one level in the scope stack verifying each use-type
10212 -- clause within said level is used then reset the Current_Use_Clause
10213 -- to a redundant use clause outside of the current ending scope if such
10214 -- a clause exists.
10216 ---------------------------
10217 -- Update_Chain_In_Scope --
10218 ---------------------------
10220 procedure Update_Chain_In_Scope (Level : Int) is
10225 -- Loop through all use clauses within the scope dictated by Level
10227 Curr := Scope_Stack.Table (Level).First_Use_Clause;
10228 while Present (Curr) loop
10230 -- Retrieve the subtype mark or name within the current current
10233 if Nkind (Curr) = N_Use_Type_Clause then
10234 N := Subtype_Mark (Curr);
10239 -- If warnings for unreferenced entities are enabled and the
10240 -- current use clause has not been marked effective.
10242 if Check_Unreferenced
10243 and then Comes_From_Source (Curr)
10244 and then not Is_Effective_Use_Clause (Curr)
10245 and then not In_Instance
10246 and then not In_Inlined_Body
10248 -- We are dealing with a potentially unused use_package_clause
10250 if Nkind (Curr) = N_Use_Package_Clause then
10252 -- Renamings and formal subprograms may cause the associated
10253 -- node to be marked as effective instead of the original.
10255 if not (Present (Associated_Node (N))
10257 (Current_Use_Clause
10258 (Associated_Node (N)))
10259 and then Is_Effective_Use_Clause
10260 (Current_Use_Clause
10261 (Associated_Node (N))))
10263 Error_Msg_Node_1 := Entity (N);
10265 ("use clause for package & has no effect?u?",
10269 -- We are dealing with an unused use_type_clause
10272 Error_Msg_Node_1 := Etype (N);
10274 ("use clause for } has no effect?u?", Curr, Etype (N));
10278 -- Verify that we haven't already processed a redundant
10279 -- use_type_clause within the same scope before we move the
10280 -- current use clause up to a previous one for type T.
10282 if Present (Prev_Use_Clause (Curr)) then
10283 Set_Current_Use_Clause (Entity (N), Prev_Use_Clause (Curr));
10286 Next_Use_Clause (Curr);
10288 end Update_Chain_In_Scope;
10290 -- Start of processing for Update_Use_Clause_Chain
10293 Update_Chain_In_Scope (Scope_Stack.Last);
10295 -- Deal with use clauses within the context area if the current
10296 -- scope is a compilation unit.
10298 if Is_Compilation_Unit (Current_Scope)
10299 and then Sloc (Scope_Stack.Table
10300 (Scope_Stack.Last - 1).Entity) = Standard_Location
10302 Update_Chain_In_Scope (Scope_Stack.Last - 1);
10304 end Update_Use_Clause_Chain;
10306 ---------------------
10307 -- Use_One_Package --
10308 ---------------------
10310 procedure Use_One_Package
10312 Pack_Name : Entity_Id := Empty;
10313 Force : Boolean := False)
10315 procedure Note_Redundant_Use (Clause : Node_Id);
10316 -- Mark the name in a use clause as redundant if the corresponding
10317 -- entity is already use-visible. Emit a warning if the use clause comes
10318 -- from source and the proper warnings are enabled.
10320 ------------------------
10321 -- Note_Redundant_Use --
10322 ------------------------
10324 procedure Note_Redundant_Use (Clause : Node_Id) is
10325 Decl : constant Node_Id := Parent (Clause);
10326 Pack_Name : constant Entity_Id := Entity (Clause);
10328 Cur_Use : Node_Id := Current_Use_Clause (Pack_Name);
10329 Prev_Use : Node_Id := Empty;
10330 Redundant : Node_Id := Empty;
10331 -- The Use_Clause which is actually redundant. In the simplest case
10332 -- it is Pack itself, but when we compile a body we install its
10333 -- context before that of its spec, in which case it is the
10334 -- use_clause in the spec that will appear to be redundant, and we
10335 -- want the warning to be placed on the body. Similar complications
10336 -- appear when the redundancy is between a child unit and one of its
10340 -- Could be renamed...
10342 if No (Cur_Use) then
10343 Cur_Use := Current_Use_Clause (Renamed_Entity (Pack_Name));
10346 Set_Redundant_Use (Clause, True);
10348 -- Do not check for redundant use if clause is generated, or in an
10349 -- instance, or in a predefined unit to avoid misleading warnings
10350 -- that may occur as part of a rtsfind load.
10352 if not Comes_From_Source (Clause)
10353 or else In_Instance
10354 or else not Warn_On_Redundant_Constructs
10355 or else Is_Predefined_Unit (Current_Sem_Unit)
10360 if not Is_Compilation_Unit (Current_Scope) then
10362 -- If the use_clause is in an inner scope, it is made redundant by
10363 -- some clause in the current context, with one exception: If we
10364 -- are compiling a nested package body, and the use_clause comes
10365 -- from then corresponding spec, the clause is not necessarily
10366 -- fully redundant, so we should not warn. If a warning was
10367 -- warranted, it would have been given when the spec was
10370 if Nkind (Parent (Decl)) = N_Package_Specification then
10372 Package_Spec_Entity : constant Entity_Id :=
10373 Defining_Unit_Name (Parent (Decl));
10375 if In_Package_Body (Package_Spec_Entity) then
10381 Redundant := Clause;
10382 Prev_Use := Cur_Use;
10384 elsif Nkind (Unit (Cunit (Current_Sem_Unit))) = N_Package_Body then
10386 Cur_Unit : constant Unit_Number_Type :=
10387 Get_Source_Unit (Cur_Use);
10388 New_Unit : constant Unit_Number_Type :=
10389 Get_Source_Unit (Clause);
10394 if Cur_Unit = New_Unit then
10396 -- Redundant clause in same body
10398 Redundant := Clause;
10399 Prev_Use := Cur_Use;
10401 elsif Cur_Unit = Current_Sem_Unit then
10403 -- If the new clause is not in the current unit it has been
10404 -- analyzed first, and it makes the other one redundant.
10405 -- However, if the new clause appears in a subunit, Cur_Unit
10406 -- is still the parent, and in that case the redundant one
10407 -- is the one appearing in the subunit.
10409 if Nkind (Unit (Cunit (New_Unit))) = N_Subunit then
10410 Redundant := Clause;
10411 Prev_Use := Cur_Use;
10413 -- Most common case: redundant clause in body, original
10414 -- clause in spec. Current scope is spec entity.
10416 elsif Current_Scope = Cunit_Entity (Current_Sem_Unit) then
10417 Redundant := Cur_Use;
10418 Prev_Use := Clause;
10421 -- The new clause may appear in an unrelated unit, when
10422 -- the parents of a generic are being installed prior to
10423 -- instantiation. In this case there must be no warning.
10424 -- We detect this case by checking whether the current
10425 -- top of the stack is related to the current
10428 Scop := Current_Scope;
10429 while Present (Scop)
10430 and then Scop /= Standard_Standard
10432 if Is_Compilation_Unit (Scop)
10433 and then not Is_Child_Unit (Scop)
10437 elsif Scop = Cunit_Entity (Current_Sem_Unit) then
10441 Scop := Scope (Scop);
10444 Redundant := Cur_Use;
10445 Prev_Use := Clause;
10448 elsif New_Unit = Current_Sem_Unit then
10449 Redundant := Clause;
10450 Prev_Use := Cur_Use;
10453 -- Neither is the current unit, so they appear in parent or
10454 -- sibling units. Warning will be emitted elsewhere.
10460 elsif Nkind (Unit (Cunit (Current_Sem_Unit))) = N_Package_Declaration
10461 and then Present (Parent_Spec (Unit (Cunit (Current_Sem_Unit))))
10463 -- Use_clause is in child unit of current unit, and the child unit
10464 -- appears in the context of the body of the parent, so it has
10465 -- been installed first, even though it is the redundant one.
10466 -- Depending on their placement in the context, the visible or the
10467 -- private parts of the two units, either might appear as
10468 -- redundant, but the message has to be on the current unit.
10470 if Get_Source_Unit (Cur_Use) = Current_Sem_Unit then
10471 Redundant := Cur_Use;
10472 Prev_Use := Clause;
10474 Redundant := Clause;
10475 Prev_Use := Cur_Use;
10478 -- If the new use clause appears in the private part of a parent
10479 -- unit it may appear to be redundant w.r.t. a use clause in a
10480 -- child unit, but the previous use clause was needed in the
10481 -- visible part of the child, and no warning should be emitted.
10483 if Nkind (Parent (Decl)) = N_Package_Specification
10484 and then List_Containing (Decl) =
10485 Private_Declarations (Parent (Decl))
10488 Par : constant Entity_Id :=
10489 Defining_Entity (Parent (Decl));
10490 Spec : constant Node_Id :=
10491 Specification (Unit (Cunit (Current_Sem_Unit)));
10492 Cur_List : constant List_Id := List_Containing (Cur_Use);
10495 if Is_Compilation_Unit (Par)
10496 and then Par /= Cunit_Entity (Current_Sem_Unit)
10498 if Cur_List = Context_Items (Cunit (Current_Sem_Unit))
10499 or else Cur_List = Visible_Declarations (Spec)
10507 -- Finally, if the current use clause is in the context then the
10508 -- clause is redundant when it is nested within the unit.
10510 elsif Nkind (Parent (Cur_Use)) = N_Compilation_Unit
10511 and then Nkind (Parent (Parent (Clause))) /= N_Compilation_Unit
10512 and then Get_Source_Unit (Cur_Use) = Get_Source_Unit (Clause)
10514 Redundant := Clause;
10515 Prev_Use := Cur_Use;
10518 if Present (Redundant) and then Parent (Redundant) /= Prev_Use then
10520 -- Make sure we are looking at most-descendant use_package_clause
10521 -- by traversing the chain with Find_First_Use and then verifying
10522 -- there is no scope manipulation via Most_Descendant_Use_Clause.
10524 if Nkind (Prev_Use) = N_Use_Package_Clause
10526 (Nkind (Parent (Prev_Use)) /= N_Compilation_Unit
10527 or else Most_Descendant_Use_Clause
10528 (Prev_Use, Find_First_Use (Prev_Use)) /= Prev_Use)
10530 Prev_Use := Find_First_Use (Prev_Use);
10533 Error_Msg_Sloc := Sloc (Prev_Use);
10534 Error_Msg_NE -- CODEFIX
10535 ("& is already use-visible through previous use_clause #?r?",
10536 Redundant, Pack_Name);
10538 end Note_Redundant_Use;
10542 Current_Instance : Entity_Id := Empty;
10546 Private_With_OK : Boolean := False;
10547 Real_P : Entity_Id;
10549 -- Start of processing for Use_One_Package
10552 -- Use_One_Package may have been called recursively to handle an
10553 -- implicit use for a auxiliary system package, so set P accordingly
10554 -- and skip redundancy checks.
10556 if No (Pack_Name) and then Present_System_Aux (N) then
10557 P := System_Aux_Id;
10559 -- Check for redundant use_package_clauses
10562 -- Ignore cases where we are dealing with a non user defined package
10563 -- like Standard_Standard or something other than a valid package.
10565 if not Is_Entity_Name (Pack_Name)
10566 or else No (Entity (Pack_Name))
10567 or else Ekind (Entity (Pack_Name)) /= E_Package
10572 -- When a renaming exists we must check it for redundancy. The
10573 -- original package would have already been seen at this point.
10575 if Present (Renamed_Entity (Entity (Pack_Name))) then
10576 P := Renamed_Entity (Entity (Pack_Name));
10578 P := Entity (Pack_Name);
10581 -- Check for redundant clauses then set the current use clause for
10582 -- P if were are not "forcing" an installation from a scope
10583 -- reinstallation that is done throughout analysis for various
10587 Note_Redundant_Use (Pack_Name);
10590 Set_Current_Use_Clause (P, N);
10595 -- Warn about detected redundant clauses
10598 and then In_Open_Scopes (P)
10599 and then not Is_Hidden_Open_Scope (P)
10601 if Warn_On_Redundant_Constructs and then P = Current_Scope then
10602 Error_Msg_NE -- CODEFIX
10603 ("& is already use-visible within itself?r?",
10610 -- Set P back to the non-renamed package so that visibility of the
10611 -- entities within the package can be properly set below.
10613 P := Entity (Pack_Name);
10617 Set_Current_Use_Clause (P, N);
10619 -- Ada 2005 (AI-50217): Check restriction
10621 if From_Limited_With (P) then
10622 Error_Msg_N ("limited withed package cannot appear in use clause", N);
10625 -- Find enclosing instance, if any
10627 if In_Instance then
10628 Current_Instance := Current_Scope;
10629 while not Is_Generic_Instance (Current_Instance) loop
10630 Current_Instance := Scope (Current_Instance);
10633 if No (Hidden_By_Use_Clause (N)) then
10634 Set_Hidden_By_Use_Clause (N, New_Elmt_List);
10638 -- If unit is a package renaming, indicate that the renamed package is
10639 -- also in use (the flags on both entities must remain consistent, and a
10640 -- subsequent use of either of them should be recognized as redundant).
10642 if Present (Renamed_Entity (P)) then
10643 Set_In_Use (Renamed_Entity (P));
10644 Set_Current_Use_Clause (Renamed_Entity (P), N);
10645 Real_P := Renamed_Entity (P);
10650 -- Ada 2005 (AI-262): Check the use_clause of a private withed package
10651 -- found in the private part of a package specification
10653 if In_Private_Part (Current_Scope)
10654 and then Has_Private_With (P)
10655 and then Is_Child_Unit (Current_Scope)
10656 and then Is_Child_Unit (P)
10657 and then Is_Ancestor_Package (Scope (Current_Scope), P)
10659 Private_With_OK := True;
10662 -- Loop through entities in one package making them potentially
10665 Id := First_Entity (P);
10667 and then (Id /= First_Private_Entity (P)
10668 or else Private_With_OK) -- Ada 2005 (AI-262)
10670 Prev := Current_Entity (Id);
10671 while Present (Prev) loop
10672 if Is_Immediately_Visible (Prev)
10673 and then (not Is_Overloadable (Prev)
10674 or else not Is_Overloadable (Id)
10675 or else Type_Conformant (Id, Prev))
10677 if No (Current_Instance) then
10679 -- Potentially use-visible entity remains hidden
10681 if Warn_On_Hiding then
10682 Warn_On_Hiding_Entity (N, Hidden => Id, Visible => Prev,
10683 On_Use_Clause => True);
10686 goto Next_Usable_Entity;
10688 -- A use clause within an instance hides outer global entities,
10689 -- which are not used to resolve local entities in the
10690 -- instance. Note that the predefined entities in Standard
10691 -- could not have been hidden in the generic by a use clause,
10692 -- and therefore remain visible. Other compilation units whose
10693 -- entities appear in Standard must be hidden in an instance.
10695 -- To determine whether an entity is external to the instance
10696 -- we compare the scope depth of its scope with that of the
10697 -- current instance. However, a generic actual of a subprogram
10698 -- instance is declared in the wrapper package but will not be
10699 -- hidden by a use-visible entity. similarly, an entity that is
10700 -- declared in an enclosing instance will not be hidden by an
10701 -- an entity declared in a generic actual, which can only have
10702 -- been use-visible in the generic and will not have hidden the
10703 -- entity in the generic parent.
10705 -- If Id is called Standard, the predefined package with the
10706 -- same name is in the homonym chain. It has to be ignored
10707 -- because it has no defined scope (being the only entity in
10708 -- the system with this mandated behavior).
10710 elsif not Is_Hidden (Id)
10711 and then Present (Scope (Prev))
10712 and then not Is_Wrapper_Package (Scope (Prev))
10713 and then Scope_Depth (Scope (Prev)) <
10714 Scope_Depth (Current_Instance)
10715 and then (Scope (Prev) /= Standard_Standard
10716 or else Sloc (Prev) > Standard_Location)
10718 if In_Open_Scopes (Scope (Prev))
10719 and then Is_Generic_Instance (Scope (Prev))
10720 and then Present (Associated_Formal_Package (P))
10725 Set_Is_Potentially_Use_Visible (Id);
10726 Set_Is_Immediately_Visible (Prev, False);
10727 Append_Elmt (Prev, Hidden_By_Use_Clause (N));
10731 -- A user-defined operator is not use-visible if the predefined
10732 -- operator for the type is immediately visible, which is the case
10733 -- if the type of the operand is in an open scope. This does not
10734 -- apply to user-defined operators that have operands of different
10735 -- types, because the predefined mixed mode operations (multiply
10736 -- and divide) apply to universal types and do not hide anything.
10738 elsif Ekind (Prev) = E_Operator
10739 and then Operator_Matches_Spec (Prev, Id)
10740 and then In_Open_Scopes
10741 (Scope (Base_Type (Etype (First_Formal (Id)))))
10742 and then (No (Next_Formal (First_Formal (Id)))
10743 or else Etype (First_Formal (Id)) =
10744 Etype (Next_Formal (First_Formal (Id)))
10745 or else Chars (Prev) = Name_Op_Expon)
10747 goto Next_Usable_Entity;
10749 -- In an instance, two homonyms may become use_visible through the
10750 -- actuals of distinct formal packages. In the generic, only the
10751 -- current one would have been visible, so make the other one
10752 -- not use_visible.
10754 -- In certain pathological cases it is possible that unrelated
10755 -- homonyms from distinct formal packages may exist in an
10756 -- uninstalled scope. We must test for that here.
10758 elsif Present (Current_Instance)
10759 and then Is_Potentially_Use_Visible (Prev)
10760 and then not Is_Overloadable (Prev)
10761 and then Scope (Id) /= Scope (Prev)
10762 and then Used_As_Generic_Actual (Scope (Prev))
10763 and then Used_As_Generic_Actual (Scope (Id))
10764 and then Is_List_Member (Scope (Prev))
10765 and then not In_Same_List (Current_Use_Clause (Scope (Prev)),
10766 Current_Use_Clause (Scope (Id)))
10768 Set_Is_Potentially_Use_Visible (Prev, False);
10769 Append_Elmt (Prev, Hidden_By_Use_Clause (N));
10772 Prev := Homonym (Prev);
10775 -- On exit, we know entity is not hidden, unless it is private
10777 if not Is_Hidden (Id)
10778 and then (not Is_Child_Unit (Id) or else Is_Visible_Lib_Unit (Id))
10780 Set_Is_Potentially_Use_Visible (Id);
10782 if Is_Private_Type (Id) and then Present (Full_View (Id)) then
10783 Set_Is_Potentially_Use_Visible (Full_View (Id));
10787 <<Next_Usable_Entity>>
10791 -- Child units are also made use-visible by a use clause, but they may
10792 -- appear after all visible declarations in the parent entity list.
10794 while Present (Id) loop
10795 if Is_Child_Unit (Id) and then Is_Visible_Lib_Unit (Id) then
10796 Set_Is_Potentially_Use_Visible (Id);
10802 if Chars (Real_P) = Name_System
10803 and then Scope (Real_P) = Standard_Standard
10804 and then Present_System_Aux (N)
10806 Use_One_Package (N);
10808 end Use_One_Package;
10814 procedure Use_One_Type
10816 Installed : Boolean := False;
10817 Force : Boolean := False)
10819 function Spec_Reloaded_For_Body return Boolean;
10820 -- Determine whether the compilation unit is a package body and the use
10821 -- type clause is in the spec of the same package. Even though the spec
10822 -- was analyzed first, its context is reloaded when analysing the body.
10824 procedure Use_Class_Wide_Operations (Typ : Entity_Id);
10825 -- AI05-150: if the use_type_clause carries the "all" qualifier,
10826 -- class-wide operations of ancestor types are use-visible if the
10827 -- ancestor type is visible.
10829 ----------------------------
10830 -- Spec_Reloaded_For_Body --
10831 ----------------------------
10833 function Spec_Reloaded_For_Body return Boolean is
10835 if Nkind (Unit (Cunit (Current_Sem_Unit))) = N_Package_Body then
10837 Spec : constant Node_Id :=
10838 Parent (List_Containing (Parent (Id)));
10841 -- Check whether type is declared in a package specification,
10842 -- and current unit is the corresponding package body. The
10843 -- use clauses themselves may be within a nested package.
10846 Nkind (Spec) = N_Package_Specification
10847 and then In_Same_Source_Unit
10848 (Corresponding_Body (Parent (Spec)),
10849 Cunit_Entity (Current_Sem_Unit));
10854 end Spec_Reloaded_For_Body;
10856 -------------------------------
10857 -- Use_Class_Wide_Operations --
10858 -------------------------------
10860 procedure Use_Class_Wide_Operations (Typ : Entity_Id) is
10861 function Is_Class_Wide_Operation_Of
10863 T : Entity_Id) return Boolean;
10864 -- Determine whether a subprogram has a class-wide parameter or
10865 -- result that is T'Class.
10867 ---------------------------------
10868 -- Is_Class_Wide_Operation_Of --
10869 ---------------------------------
10871 function Is_Class_Wide_Operation_Of
10873 T : Entity_Id) return Boolean
10875 Formal : Entity_Id;
10878 Formal := First_Formal (Op);
10879 while Present (Formal) loop
10880 if Etype (Formal) = Class_Wide_Type (T) then
10884 Next_Formal (Formal);
10887 if Etype (Op) = Class_Wide_Type (T) then
10892 end Is_Class_Wide_Operation_Of;
10899 -- Start of processing for Use_Class_Wide_Operations
10902 Scop := Scope (Typ);
10903 if not Is_Hidden (Scop) then
10904 Ent := First_Entity (Scop);
10905 while Present (Ent) loop
10906 if Is_Overloadable (Ent)
10907 and then Is_Class_Wide_Operation_Of (Ent, Typ)
10908 and then not Is_Potentially_Use_Visible (Ent)
10910 Set_Is_Potentially_Use_Visible (Ent);
10911 Append_Elmt (Ent, Used_Operations (Parent (Id)));
10918 if Is_Derived_Type (Typ) then
10919 Use_Class_Wide_Operations (Etype (Base_Type (Typ)));
10921 end Use_Class_Wide_Operations;
10926 Is_Known_Used : Boolean;
10927 Op_List : Elist_Id;
10930 -- Start of processing for Use_One_Type
10933 if Entity (Id) = Any_Type then
10937 -- It is the type determined by the subtype mark (8.4(8)) whose
10938 -- operations become potentially use-visible.
10940 T := Base_Type (Entity (Id));
10942 -- Either the type itself is used, the package where it is declared is
10943 -- in use or the entity is declared in the current package, thus
10948 and then ((Present (Current_Use_Clause (T))
10949 and then All_Present (Current_Use_Clause (T)))
10950 or else not All_Present (Parent (Id))))
10951 or else In_Use (Scope (T))
10952 or else Scope (T) = Current_Scope;
10954 Set_Redundant_Use (Id,
10955 Is_Known_Used or else Is_Potentially_Use_Visible (T));
10957 if Ekind (T) = E_Incomplete_Type then
10958 Error_Msg_N ("premature usage of incomplete type", Id);
10960 elsif In_Open_Scopes (Scope (T)) then
10963 -- A limited view cannot appear in a use_type_clause. However, an access
10964 -- type whose designated type is limited has the flag but is not itself
10965 -- a limited view unless we only have a limited view of its enclosing
10968 elsif From_Limited_With (T) and then From_Limited_With (Scope (T)) then
10970 ("incomplete type from limited view cannot appear in use clause",
10973 -- If the use clause is redundant, Used_Operations will usually be
10974 -- empty, but we need to set it to empty here in one case: If we are
10975 -- instantiating a generic library unit, then we install the ancestors
10976 -- of that unit in the scope stack, which involves reprocessing use
10977 -- clauses in those ancestors. Such a use clause will typically have a
10978 -- nonempty Used_Operations unless it was redundant in the generic unit,
10979 -- even if it is redundant at the place of the instantiation.
10981 elsif Redundant_Use (Id) then
10982 Set_Used_Operations (Parent (Id), New_Elmt_List);
10984 -- If the subtype mark designates a subtype in a different package,
10985 -- we have to check that the parent type is visible, otherwise the
10986 -- use_type_clause is a no-op. Not clear how to do that???
10989 Set_Current_Use_Clause (T, Parent (Id));
10992 -- If T is tagged, primitive operators on class-wide operands are
10993 -- also deemed available. Note that this is really necessary only
10994 -- in semantics-only mode, because the primitive operators are not
10995 -- fully constructed in this mode, but we do it in all modes for the
10996 -- sake of uniformity, as this should not matter in practice.
10998 if Is_Tagged_Type (T) then
10999 Set_In_Use (Class_Wide_Type (T));
11002 -- Iterate over primitive operations of the type. If an operation is
11003 -- already use_visible, it is the result of a previous use_clause,
11004 -- and already appears on the corresponding entity chain. If the
11005 -- clause is being reinstalled, operations are already use-visible.
11011 Op_List := Collect_Primitive_Operations (T);
11012 Elmt := First_Elmt (Op_List);
11013 while Present (Elmt) loop
11014 if (Nkind (Node (Elmt)) = N_Defining_Operator_Symbol
11015 or else Chars (Node (Elmt)) in Any_Operator_Name)
11016 and then not Is_Hidden (Node (Elmt))
11017 and then not Is_Potentially_Use_Visible (Node (Elmt))
11019 Set_Is_Potentially_Use_Visible (Node (Elmt));
11020 Append_Elmt (Node (Elmt), Used_Operations (Parent (Id)));
11022 elsif Ada_Version >= Ada_2012
11023 and then All_Present (Parent (Id))
11024 and then not Is_Hidden (Node (Elmt))
11025 and then not Is_Potentially_Use_Visible (Node (Elmt))
11027 Set_Is_Potentially_Use_Visible (Node (Elmt));
11028 Append_Elmt (Node (Elmt), Used_Operations (Parent (Id)));
11035 if Ada_Version >= Ada_2012
11036 and then All_Present (Parent (Id))
11037 and then Is_Tagged_Type (T)
11039 Use_Class_Wide_Operations (T);
11043 -- If warning on redundant constructs, check for unnecessary WITH
11046 and then Warn_On_Redundant_Constructs
11047 and then Is_Known_Used
11049 -- with P; with P; use P;
11050 -- package P is package X is package body X is
11051 -- type T ... use P.T;
11053 -- The compilation unit is the body of X. GNAT first compiles the
11054 -- spec of X, then proceeds to the body. At that point P is marked
11055 -- as use visible. The analysis then reinstalls the spec along with
11056 -- its context. The use clause P.T is now recognized as redundant,
11057 -- but in the wrong context. Do not emit a warning in such cases.
11058 -- Do not emit a warning either if we are in an instance, there is
11059 -- no redundancy between an outer use_clause and one that appears
11060 -- within the generic.
11062 and then not Spec_Reloaded_For_Body
11063 and then not In_Instance
11064 and then not In_Inlined_Body
11066 -- The type already has a use clause
11070 -- Case where we know the current use clause for the type
11072 if Present (Current_Use_Clause (T)) then
11073 Use_Clause_Known : declare
11074 Clause1 : constant Node_Id :=
11075 Find_First_Use (Current_Use_Clause (T));
11076 Clause2 : constant Node_Id := Parent (Id);
11083 -- Start of processing for Use_Clause_Known
11086 -- If the unit is a subprogram body that acts as spec, the
11087 -- context clause is shared with the constructed subprogram
11088 -- spec. Clearly there is no redundancy.
11090 if Clause1 = Clause2 then
11094 Unit1 := Unit (Enclosing_Comp_Unit_Node (Clause1));
11095 Unit2 := Unit (Enclosing_Comp_Unit_Node (Clause2));
11097 -- If both clauses are on same unit, or one is the body of
11098 -- the other, or one of them is in a subunit, report
11099 -- redundancy on the later one.
11102 or else Nkind (Unit1) = N_Subunit
11104 (Nkind (Unit2) in N_Package_Body | N_Subprogram_Body
11105 and then Nkind (Unit1) /= Nkind (Unit2)
11106 and then Nkind (Unit1) /= N_Subunit)
11108 Error_Msg_Sloc := Sloc (Clause1);
11109 Error_Msg_NE -- CODEFIX
11110 ("& is already use-visible through previous "
11111 & "use_type_clause #?r?", Clause2, T);
11115 -- If there is a redundant use_type_clause in a child unit
11116 -- determine which of the units is more deeply nested. If a
11117 -- unit is a package instance, retrieve the entity and its
11118 -- scope from the instance spec.
11120 Ent1 := Entity_Of_Unit (Unit1);
11121 Ent2 := Entity_Of_Unit (Unit2);
11123 -- When the scope of both units' entities are
11124 -- Standard_Standard then neither Unit1 or Unit2 are child
11125 -- units - so return in that case.
11127 if Scope
(Ent1
) = Standard_Standard
11128 and then Scope
(Ent2
) = Standard_Standard
11132 -- Otherwise, determine if one of the units is not a child
11134 elsif Scope
(Ent2
) = Standard_Standard
then
11135 Error_Msg_Sloc
:= Sloc
(Clause2
);
11138 elsif Scope
(Ent1
) = Standard_Standard
then
11139 Error_Msg_Sloc
:= Sloc
(Id
);
11142 -- If both units are child units, we determine which one is
11143 -- the descendant by the scope distance to the ultimate
11152 S1
:= Scope
(Ent1
);
11153 S2
:= Scope
(Ent2
);
11155 and then Present
(S2
)
11156 and then S1
/= Standard_Standard
11157 and then S2
/= Standard_Standard
11163 if S1
= Standard_Standard
then
11164 Error_Msg_Sloc
:= Sloc
(Id
);
11167 Error_Msg_Sloc
:= Sloc
(Clause2
);
11173 if Parent
(Id
) /= Err_No
then
11174 if Most_Descendant_Use_Clause
11175 (Err_No
, Parent
(Id
)) = Parent
(Id
)
11177 Error_Msg_Sloc
:= Sloc
(Err_No
);
11178 Err_No
:= Parent
(Id
);
11181 Error_Msg_NE
-- CODEFIX
11182 ("& is already use-visible through previous "
11183 & "use_type_clause #?r?", Err_No
, Id
);
11185 end Use_Clause_Known
;
11187 -- Here Current_Use_Clause is not set for T, so we do not have the
11188 -- location information available.
11191 Error_Msg_NE
-- CODEFIX
11192 ("& is already use-visible through previous "
11193 & "use_type_clause?r?", Id
, T
);
11196 -- The package where T is declared is already used
11198 elsif In_Use
(Scope
(T
)) then
11199 -- Due to expansion of contracts we could be attempting to issue
11200 -- a spurious warning - so verify there is a previous use clause.
11202 if Current_Use_Clause
(Scope
(T
)) /=
11203 Find_First_Use
(Current_Use_Clause
(Scope
(T
)))
11206 Sloc
(Find_First_Use
(Current_Use_Clause
(Scope
(T
))));
11207 Error_Msg_NE
-- CODEFIX
11208 ("& is already use-visible through package use clause #?r?",
11212 -- The current scope is the package where T is declared
11215 Error_Msg_Node_2
:= Scope
(T
);
11216 Error_Msg_NE
-- CODEFIX
11217 ("& is already use-visible inside package &?r?", Id
, T
);
11226 procedure Write_Info
is
11227 Id
: Entity_Id
:= First_Entity
(Current_Scope
);
11230 -- No point in dumping standard entities
11232 if Current_Scope
= Standard_Standard
then
11236 Write_Str
("========================================================");
11238 Write_Str
(" Defined Entities in ");
11239 Write_Name
(Chars
(Current_Scope
));
11241 Write_Str
("========================================================");
11245 Write_Str
("-- none --");
11249 while Present
(Id
) loop
11250 Write_Entity_Info
(Id
, " ");
11255 if Scope
(Current_Scope
) = Standard_Standard
then
11257 -- Print information on the current unit itself
11259 Write_Entity_Info
(Current_Scope
, " ");
11272 for J
in reverse 1 .. Scope_Stack
.Last
loop
11273 S
:= Scope_Stack
.Table
(J
).Entity
;
11274 Write_Int
(Int
(S
));
11275 Write_Str
(" === ");
11276 Write_Name
(Chars
(S
));
11285 procedure we
(S
: Entity_Id
) is
11288 E
:= First_Entity
(S
);
11289 while Present
(E
) loop
11290 Write_Int
(Int
(E
));
11291 Write_Str
(" === ");
11292 Write_Name
(Chars
(E
));