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
)));
864 Rewrite
(Subtype_Mark
(N
), New_Occurrence_Of
(Subt
, Loc
));
865 Set_Etype
(Nam
, Subt
);
867 -- Suppress discriminant checks on this subtype if the original
868 -- type has defaulted discriminants and Id is a "for of" loop
871 if Has_Defaulted_Discriminants
(Typ
)
872 and then Nkind
(Original_Node
(Parent
(N
))) = N_Loop_Statement
874 Loop_Scheme
:= Iteration_Scheme
(Original_Node
(Parent
(N
)));
876 if Present
(Loop_Scheme
)
877 and then Present
(Iterator_Specification
(Loop_Scheme
))
880 (Iterator_Specification
(Loop_Scheme
)) = Id
882 Set_Checks_May_Be_Suppressed
(Subt
);
883 Push_Local_Suppress_Stack_Entry
885 Check
=> Discriminant_Check
,
890 -- Freeze subtype at once, to prevent order of elaboration
891 -- issues in the backend. The renamed object exists, so its
892 -- type is already frozen in any case.
894 Freeze_Before
(N
, Subt
);
897 end Check_Constrained_Object
;
899 ---------------------
900 -- Get_Object_Name --
901 ---------------------
903 function Get_Object_Name
(Nod
: Node_Id
) return Node_Id
is
908 while Present
(Obj_Nam
) loop
909 case Nkind
(Obj_Nam
) is
910 when N_Attribute_Reference
911 | N_Explicit_Dereference
912 | N_Indexed_Component
915 Obj_Nam
:= Prefix
(Obj_Nam
);
917 when N_Selected_Component
=>
918 Obj_Nam
:= Selector_Name
(Obj_Nam
);
920 when N_Qualified_Expression | N_Type_Conversion
=>
921 Obj_Nam
:= Expression
(Obj_Nam
);
931 -- Start of processing for Analyze_Object_Renaming
938 Set_Is_Pure
(Id
, Is_Pure
(Current_Scope
));
941 -- The renaming of a component that depends on a discriminant requires
942 -- an actual subtype, because in subsequent use of the object Gigi will
943 -- be unable to locate the actual bounds. This explicit step is required
944 -- when the renaming is generated in removing side effects of an
945 -- already-analyzed expression.
947 if Nkind
(Nam
) = N_Selected_Component
and then Analyzed
(Nam
) then
949 -- The object renaming declaration may become Ghost if it renames a
952 if Is_Entity_Name
(Nam
) then
953 Mark_Ghost_Renaming
(N
, Entity
(Nam
));
957 Dec
:= Build_Actual_Subtype_Of_Component
(Etype
(Nam
), Nam
);
959 if Present
(Dec
) then
960 Insert_Action
(N
, Dec
);
961 T
:= Defining_Identifier
(Dec
);
964 elsif Present
(Subtype_Mark
(N
))
965 or else No
(Access_Definition
(N
))
967 if Present
(Subtype_Mark
(N
)) then
968 Find_Type
(Subtype_Mark
(N
));
969 T
:= Entity
(Subtype_Mark
(N
));
972 -- AI12-0275: Case of object renaming without a subtype_mark
977 -- Normal case of no overloading in object name
979 if not Is_Overloaded
(Nam
) then
981 -- Catch error cases (such as attempting to rename a procedure
982 -- or package) using the shorthand form.
985 or else Etype
(Nam
) = Standard_Void_Type
988 ("object name or value expected in renaming", Nam
);
990 Mutate_Ekind
(Id
, E_Variable
);
991 Set_Etype
(Id
, Any_Type
);
999 -- Case of overloaded name, which will be illegal if there's more
1000 -- than one acceptable interpretation (such as overloaded function
1012 -- More than one candidate interpretation is available
1014 -- Remove procedure calls, which syntactically cannot appear
1015 -- in this context, but which cannot be removed by type
1016 -- checking, because the context does not impose a type.
1018 Get_First_Interp
(Nam
, I
, It
);
1019 while Present
(It
.Typ
) loop
1020 if It
.Typ
= Standard_Void_Type
then
1024 Get_Next_Interp
(I
, It
);
1027 Get_First_Interp
(Nam
, I
, It
);
1031 -- If there's no type present, we have an error case (such
1032 -- as overloaded procedures named in the object renaming).
1036 ("object name or value expected in renaming", Nam
);
1038 Mutate_Ekind
(Id
, E_Variable
);
1039 Set_Etype
(Id
, Any_Type
);
1044 Get_Next_Interp
(I
, It
);
1046 if Present
(It
.Typ
) then
1048 It1
:= Disambiguate
(Nam
, I1
, I
, Any_Type
);
1050 if It1
= No_Interp
then
1051 Error_Msg_N
("ambiguous name in object renaming", Nam
);
1053 Error_Msg_Sloc
:= Sloc
(It
.Nam
);
1054 Error_Msg_N
("\\possible interpretation#!", Nam
);
1056 Error_Msg_Sloc
:= Sloc
(Nam1
);
1057 Error_Msg_N
("\\possible interpretation#!", Nam
);
1063 Set_Etype
(Nam
, It1
.Typ
);
1068 if Etype
(Nam
) = Standard_Exception_Type
then
1070 ("exception requires a subtype mark in renaming", Nam
);
1075 -- The object renaming declaration may become Ghost if it renames a
1078 if Is_Entity_Name
(Nam
) then
1079 Mark_Ghost_Renaming
(N
, Entity
(Nam
));
1082 -- Check against AI12-0401 here before Resolve may rewrite Nam and
1083 -- potentially generate spurious warnings.
1085 -- In the case where the object_name is a qualified_expression with
1086 -- a nominal subtype T and whose expression is a name that denotes
1088 -- * if T is an elementary subtype, then:
1089 -- * Q shall be a constant other than a dereference of an access
1091 -- * the nominal subtype of Q shall be statically compatible with
1093 -- * T shall statically match the base subtype of its type if
1094 -- scalar, or the first subtype of its type if an access type.
1095 -- * if T is a composite subtype, then Q shall be known to be
1096 -- constrained or T shall statically match the first subtype of
1099 if Nkind
(Nam
) = N_Qualified_Expression
1100 and then Is_Object_Reference
(Expression
(Nam
))
1102 Q
:= Expression
(Nam
);
1104 if (Is_Elementary_Type
(T
)
1106 not ((not Is_Variable
(Q
)
1107 and then Nkind
(Q
) /= N_Explicit_Dereference
)
1108 or else Subtypes_Statically_Compatible
(Etype
(Q
), T
)
1109 or else (Is_Scalar_Type
(T
)
1110 and then Subtypes_Statically_Match
1112 or else (Is_Access_Type
(T
)
1113 and then Subtypes_Statically_Match
1114 (T
, First_Subtype
(T
)))))
1115 or else (Is_Composite_Type
(T
)
1118 -- If Q is an aggregate, Is_Constrained may not be set
1119 -- yet and its type may not be resolved yet.
1120 -- This doesn't quite correspond to the complex notion
1121 -- of "known to be constrained" but this is good enough
1122 -- for a rule which is in any case too complex.
1124 not (Is_Constrained
(Etype
(Q
))
1125 or else Nkind
(Q
) = N_Aggregate
1126 or else Subtypes_Statically_Match
1127 (T
, First_Subtype
(T
))))
1130 ("subtype of renamed qualified expression does not " &
1131 "statically match", N
);
1138 -- If the renamed object is a function call of a limited type,
1139 -- the expansion of the renaming is complicated by the presence
1140 -- of various temporaries and subtypes that capture constraints
1141 -- of the renamed object. Rewrite node as an object declaration,
1142 -- whose expansion is simpler. Given that the object is limited
1143 -- there is no copy involved and no performance hit.
1145 if Nkind
(Nam
) = N_Function_Call
1146 and then Is_Inherently_Limited_Type
(Etype
(Nam
))
1147 and then not Is_Constrained
(Etype
(Nam
))
1148 and then Comes_From_Source
(N
)
1151 Mutate_Ekind
(Id
, E_Constant
);
1153 Make_Object_Declaration
(Loc
,
1154 Defining_Identifier
=> Id
,
1155 Constant_Present
=> True,
1156 Object_Definition
=> New_Occurrence_Of
(Etype
(Nam
), Loc
),
1157 Expression
=> Relocate_Node
(Nam
)));
1161 -- Ada 2012 (AI05-149): Reject renaming of an anonymous access object
1162 -- when renaming declaration has a named access type. The Ada 2012
1163 -- coverage rules allow an anonymous access type in the context of
1164 -- an expected named general access type, but the renaming rules
1165 -- require the types to be the same. (An exception is when the type
1166 -- of the renaming is also an anonymous access type, which can only
1167 -- happen due to a renaming created by the expander.)
1169 if Nkind
(Nam
) = N_Type_Conversion
1170 and then not Comes_From_Source
(Nam
)
1171 and then Is_Anonymous_Access_Type
(Etype
(Expression
(Nam
)))
1172 and then not Is_Anonymous_Access_Type
(T
)
1175 ("cannot rename anonymous access object "
1176 & "as a named access type", Expression
(Nam
), T
);
1179 -- Check that a class-wide object is not being renamed as an object
1180 -- of a specific type. The test for access types is needed to exclude
1181 -- cases where the renamed object is a dynamically tagged access
1182 -- result, such as occurs in certain expansions.
1184 if Is_Tagged_Type
(T
) then
1185 Check_Dynamically_Tagged_Expression
1191 -- Ada 2005 (AI-230/AI-254): Access renaming
1193 else pragma Assert
(Present
(Access_Definition
(N
)));
1197 N
=> Access_Definition
(N
));
1201 -- The object renaming declaration may become Ghost if it renames a
1204 if Is_Entity_Name
(Nam
) then
1205 Mark_Ghost_Renaming
(N
, Entity
(Nam
));
1208 -- Ada 2005 AI05-105: if the declaration has an anonymous access
1209 -- type, the renamed object must also have an anonymous type, and
1210 -- this is a name resolution rule. This was implicit in the last part
1211 -- of the first sentence in 8.5.1(3/2), and is made explicit by this
1214 if not Is_Overloaded
(Nam
) then
1215 if Ekind
(Etype
(Nam
)) /= Ekind
(T
) then
1217 ("expect anonymous access type in object renaming", N
);
1224 Typ
: Entity_Id
:= Empty
;
1225 Seen
: Boolean := False;
1228 Get_First_Interp
(Nam
, I
, It
);
1229 while Present
(It
.Typ
) loop
1231 -- Renaming is ambiguous if more than one candidate
1232 -- interpretation is type-conformant with the context.
1234 if Ekind
(It
.Typ
) = Ekind
(T
) then
1235 if Ekind
(T
) = E_Anonymous_Access_Subprogram_Type
1238 (Designated_Type
(T
), Designated_Type
(It
.Typ
))
1244 ("ambiguous expression in renaming", Nam
);
1247 elsif Ekind
(T
) = E_Anonymous_Access_Type
1249 Covers
(Designated_Type
(T
), Designated_Type
(It
.Typ
))
1255 ("ambiguous expression in renaming", Nam
);
1259 if Covers
(T
, It
.Typ
) then
1261 Set_Etype
(Nam
, Typ
);
1262 Set_Is_Overloaded
(Nam
, False);
1266 Get_Next_Interp
(I
, It
);
1273 -- Do not perform the legality checks below when the resolution of
1274 -- the renaming name failed because the associated type is Any_Type.
1276 if Etype
(Nam
) = Any_Type
then
1279 -- Ada 2005 (AI-231): In the case where the type is defined by an
1280 -- access_definition, the renamed entity shall be of an access-to-
1281 -- constant type if and only if the access_definition defines an
1282 -- access-to-constant type. ARM 8.5.1(4)
1284 elsif Constant_Present
(Access_Definition
(N
))
1285 and then not Is_Access_Constant
(Etype
(Nam
))
1288 ("(Ada 2005): the renamed object is not access-to-constant "
1289 & "(RM 8.5.1(6))", N
);
1291 elsif not Constant_Present
(Access_Definition
(N
))
1292 and then Is_Access_Constant
(Etype
(Nam
))
1295 ("(Ada 2005): the renamed object is not access-to-variable "
1296 & "(RM 8.5.1(6))", N
);
1299 if Is_Access_Subprogram_Type
(Etype
(Nam
)) then
1300 Check_Subtype_Conformant
1301 (Designated_Type
(T
), Designated_Type
(Etype
(Nam
)));
1303 elsif not Subtypes_Statically_Match
1304 (Designated_Type
(T
),
1305 Available_View
(Designated_Type
(Etype
(Nam
))))
1308 ("subtype of renamed object does not statically match", N
);
1312 -- Special processing for renaming function return object. Some errors
1313 -- and warnings are produced only for calls that come from source.
1315 if Nkind
(Nam
) = N_Function_Call
then
1318 -- Usage is illegal in Ada 83, but renamings are also introduced
1319 -- during expansion, and error does not apply to those.
1322 if Comes_From_Source
(N
) then
1324 ("(Ada 83) cannot rename function return object", Nam
);
1327 -- In Ada 95, warn for odd case of renaming parameterless function
1328 -- call if this is not a limited type (where this is useful).
1331 if Warn_On_Object_Renames_Function
1332 and then No
(Parameter_Associations
(Nam
))
1333 and then not Is_Limited_Type
(Etype
(Nam
))
1334 and then Comes_From_Source
(Nam
)
1337 ("renaming function result object is suspicious?.r?", Nam
);
1339 ("\function & will be called only once?.r?", Nam
,
1340 Entity
(Name
(Nam
)));
1341 Error_Msg_N
-- CODEFIX
1342 ("\suggest using an initialized constant object "
1343 & "instead?.r?", Nam
);
1348 Check_Constrained_Object
;
1350 -- An object renaming requires an exact match of the type. Class-wide
1351 -- matching is not allowed.
1353 if Is_Class_Wide_Type
(T
)
1354 and then Base_Type
(Etype
(Nam
)) /= Base_Type
(T
)
1356 Wrong_Type
(Nam
, T
);
1359 -- We must search for an actual subtype here so that the bounds of
1360 -- objects of unconstrained types don't get dropped on the floor - such
1361 -- as with renamings of formal parameters.
1363 T2
:= Get_Actual_Subtype_If_Available
(Nam
);
1365 -- Ada 2005 (AI-326): Handle wrong use of incomplete type
1367 if Nkind
(Nam
) = N_Explicit_Dereference
1368 and then Ekind
(Etype
(T2
)) = E_Incomplete_Type
1370 Error_Msg_NE
("invalid use of incomplete type&", Id
, T2
);
1373 elsif Ekind
(Etype
(T
)) = E_Incomplete_Type
then
1374 Error_Msg_NE
("invalid use of incomplete type&", Id
, T
);
1378 if Ada_Version
>= Ada_2005
and then Nkind
(Nam
) in N_Has_Entity
then
1380 Nam_Ent
: constant Entity_Id
:= Entity
(Get_Object_Name
(Nam
));
1381 Nam_Decl
: constant Node_Id
:= Declaration_Node
(Nam_Ent
);
1384 if Has_Null_Exclusion
(N
)
1385 and then not Has_Null_Exclusion
(Nam_Decl
)
1387 -- Ada 2005 (AI-423): If the object name denotes a generic
1388 -- formal object of a generic unit G, and the object renaming
1389 -- declaration occurs within the body of G or within the body
1390 -- of a generic unit declared within the declarative region
1391 -- of G, then the declaration of the formal object of G must
1392 -- have a null exclusion or a null-excluding subtype.
1394 if Is_Formal_Object
(Nam_Ent
)
1395 and then In_Generic_Scope
(Id
)
1397 if not Can_Never_Be_Null
(Etype
(Nam_Ent
)) then
1399 ("object does not exclude `NULL` "
1400 & "(RM 8.5.1(4.6/2))", N
);
1402 elsif In_Package_Body
(Scope
(Id
)) then
1404 ("formal object does not have a null exclusion"
1405 & "(RM 8.5.1(4.6/2))", N
);
1408 -- Ada 2005 (AI-423): Otherwise, the subtype of the object name
1409 -- shall exclude null.
1411 elsif not Can_Never_Be_Null
(Etype
(Nam_Ent
)) then
1413 ("object does not exclude `NULL` "
1414 & "(RM 8.5.1(4.6/2))", N
);
1416 -- An instance is illegal if it contains a renaming that
1417 -- excludes null, and the actual does not. The renaming
1418 -- declaration has already indicated that the declaration
1419 -- of the renamed actual in the instance will raise
1420 -- constraint_error.
1422 elsif Nkind
(Nam_Decl
) = N_Object_Declaration
1423 and then In_Instance
1425 Present
(Corresponding_Generic_Association
(Nam_Decl
))
1426 and then Nkind
(Expression
(Nam_Decl
)) =
1427 N_Raise_Constraint_Error
1430 ("actual does not exclude `NULL` (RM 8.5.1(4.6/2))", N
);
1432 -- Finally, if there is a null exclusion, the subtype mark
1433 -- must not be null-excluding.
1435 elsif No
(Access_Definition
(N
))
1436 and then Can_Never_Be_Null
(T
)
1439 ("`NOT NULL` not allowed (& already excludes null)",
1444 elsif Can_Never_Be_Null
(T
)
1445 and then not Can_Never_Be_Null
(Etype
(Nam_Ent
))
1448 ("object does not exclude `NULL` (RM 8.5.1(4.6/2))", N
);
1450 elsif Has_Null_Exclusion
(N
)
1451 and then No
(Access_Definition
(N
))
1452 and then Can_Never_Be_Null
(T
)
1455 ("`NOT NULL` not allowed (& already excludes null)", N
, T
);
1460 -- Set the Ekind of the entity, unless it has been set already, as is
1461 -- the case for the iteration object over a container with no variable
1462 -- indexing. In that case it's been marked as a constant, and we do not
1463 -- want to change it to a variable.
1465 if Ekind
(Id
) /= E_Constant
then
1466 Mutate_Ekind
(Id
, E_Variable
);
1469 Reinit_Object_Size_Align
(Id
);
1471 -- If N comes from source then check that the original node is an
1472 -- object reference since there may have been several rewritting and
1473 -- folding. Do not do this for N_Function_Call or N_Explicit_Dereference
1474 -- which might correspond to rewrites of e.g. N_Selected_Component
1475 -- (for example Object.Method rewriting).
1476 -- If N does not come from source then assume the tree is properly
1477 -- formed and accept any object reference. In such cases we do support
1478 -- more cases of renamings anyway, so the actual check on which renaming
1479 -- is valid is better left to the code generator as a last sanity
1482 if Comes_From_Source
(N
) then
1483 if Nkind
(Nam
) in N_Function_Call | N_Explicit_Dereference
then
1484 Is_Object_Ref
:= Is_Object_Reference
(Nam
);
1486 Is_Object_Ref
:= Is_Object_Reference
(Original_Node
(Nam
));
1489 Is_Object_Ref
:= True;
1492 if T
= Any_Type
or else Etype
(Nam
) = Any_Type
then
1495 -- Verify that the renamed entity is an object or function call
1497 elsif Is_Object_Ref
then
1498 if Comes_From_Source
(N
) then
1499 if Is_Dependent_Component_Of_Mutable_Object
(Nam
) then
1501 ("illegal renaming of discriminant-dependent component", Nam
);
1504 -- If the renaming comes from source and the renamed object is a
1505 -- dereference, then mark the prefix as needing debug information,
1506 -- since it might have been rewritten hence internally generated
1507 -- and Debug_Renaming_Declaration will link the renaming to it.
1509 if Nkind
(Nam
) = N_Explicit_Dereference
1510 and then Is_Entity_Name
(Prefix
(Nam
))
1512 Set_Debug_Info_Needed
(Entity
(Prefix
(Nam
)));
1516 -- Weird but legal, equivalent to renaming a function call. Illegal
1517 -- if the literal is the result of constant-folding an attribute
1518 -- reference that is not a function.
1520 elsif Is_Entity_Name
(Nam
)
1521 and then Ekind
(Entity
(Nam
)) = E_Enumeration_Literal
1522 and then Nkind
(Original_Node
(Nam
)) /= N_Attribute_Reference
1526 -- A named number can only be renamed without a subtype mark
1528 elsif Nkind
(Nam
) in N_Real_Literal | N_Integer_Literal
1529 and then Present
(Subtype_Mark
(N
))
1530 and then Present
(Original_Entity
(Nam
))
1532 Error_Msg_N
("incompatible types in renaming", Nam
);
1534 -- AI12-0383: Names that denote values can be renamed.
1535 -- Ignore (accept) N_Raise_xxx_Error nodes in this context.
1537 elsif No_Raise_xxx_Error
(Nam
) = OK
then
1538 Error_Msg_Ada_2022_Feature
("value in renaming", Sloc
(Nam
));
1543 if not Is_Variable
(Nam
) then
1544 Mutate_Ekind
(Id
, E_Constant
);
1545 Set_Never_Set_In_Source
(Id
, True);
1546 Set_Is_True_Constant
(Id
, True);
1549 -- The entity of the renaming declaration needs to reflect whether the
1550 -- renamed object is atomic, independent, volatile or VFA. These flags
1551 -- are set on the renamed object in the RM legality sense.
1553 Set_Is_Atomic
(Id
, Is_Atomic_Object
(Nam
));
1554 Set_Is_Independent
(Id
, Is_Independent_Object
(Nam
));
1555 Set_Is_Volatile
(Id
, Is_Volatile_Object_Ref
(Nam
));
1556 Set_Is_Volatile_Full_Access
1557 (Id
, Is_Volatile_Full_Access_Object_Ref
(Nam
));
1559 -- Treat as volatile if we just set the Volatile flag
1563 -- Or if we are renaming an entity which was marked this way
1565 -- Are there more cases, e.g. X(J) where X is Treat_As_Volatile ???
1567 or else (Is_Entity_Name
(Nam
)
1568 and then Treat_As_Volatile
(Entity
(Nam
)))
1570 Set_Treat_As_Volatile
(Id
, True);
1573 -- Now make the link to the renamed object
1575 Set_Renamed_Object
(Id
, Nam
);
1577 -- Implementation-defined aspect specifications can appear in a renaming
1578 -- declaration, but not language-defined ones. The call to procedure
1579 -- Analyze_Aspect_Specifications will take care of this error check.
1581 Analyze_Aspect_Specifications
(N
, Id
);
1583 -- Deal with dimensions
1585 Analyze_Dimension
(N
);
1586 end Analyze_Object_Renaming
;
1588 ------------------------------
1589 -- Analyze_Package_Renaming --
1590 ------------------------------
1592 procedure Analyze_Package_Renaming
(N
: Node_Id
) is
1593 New_P
: constant Entity_Id
:= Defining_Entity
(N
);
1598 if Name
(N
) = Error
then
1602 -- Check for Text_IO special units (we may be renaming a Text_IO child),
1603 -- but make sure not to catch renamings generated for package instances
1604 -- that have nothing to do with them but are nevertheless homonyms.
1606 if Is_Entity_Name
(Name
(N
))
1607 and then Present
(Entity
(Name
(N
)))
1608 and then Is_Generic_Instance
(Entity
(Name
(N
)))
1612 Check_Text_IO_Special_Unit
(Name
(N
));
1615 if Current_Scope
/= Standard_Standard
then
1616 Set_Is_Pure
(New_P
, Is_Pure
(Current_Scope
));
1622 if Is_Entity_Name
(Name
(N
)) then
1623 Old_P
:= Entity
(Name
(N
));
1628 if Etype
(Old_P
) = Any_Type
then
1629 Error_Msg_N
("expect package name in renaming", Name
(N
));
1631 elsif Ekind
(Old_P
) /= E_Package
1632 and then not (Ekind
(Old_P
) = E_Generic_Package
1633 and then In_Open_Scopes
(Old_P
))
1635 if Ekind
(Old_P
) = E_Generic_Package
then
1637 ("generic package cannot be renamed as a package", Name
(N
));
1639 Error_Msg_Sloc
:= Sloc
(Old_P
);
1641 ("expect package name in renaming, found& declared#",
1645 -- Set basic attributes to minimize cascaded errors
1647 Mutate_Ekind
(New_P
, E_Package
);
1648 Set_Etype
(New_P
, Standard_Void_Type
);
1650 elsif Present
(Renamed_Entity
(Old_P
))
1651 and then (From_Limited_With
(Renamed_Entity
(Old_P
))
1652 or else Has_Limited_View
(Renamed_Entity
(Old_P
)))
1654 Unit_Is_Visible
(Cunit
(Get_Source_Unit
(Renamed_Entity
(Old_P
))))
1657 ("renaming of limited view of package & not usable in this context"
1658 & " (RM 8.5.3(3.1/2))", Name
(N
), Renamed_Entity
(Old_P
));
1660 -- Set basic attributes to minimize cascaded errors
1662 Mutate_Ekind
(New_P
, E_Package
);
1663 Set_Etype
(New_P
, Standard_Void_Type
);
1665 -- Here for OK package renaming
1668 -- Entities in the old package are accessible through the renaming
1669 -- entity. The simplest implementation is to have both packages share
1672 Mutate_Ekind
(New_P
, E_Package
);
1673 Set_Etype
(New_P
, Standard_Void_Type
);
1675 if Present
(Renamed_Entity
(Old_P
)) then
1676 Set_Renamed_Entity
(New_P
, Renamed_Entity
(Old_P
));
1678 Set_Renamed_Entity
(New_P
, Old_P
);
1681 -- The package renaming declaration may become Ghost if it renames a
1684 Mark_Ghost_Renaming
(N
, Old_P
);
1686 Set_Has_Completion
(New_P
);
1687 Set_First_Entity
(New_P
, First_Entity
(Old_P
));
1688 Set_Last_Entity
(New_P
, Last_Entity
(Old_P
));
1689 Set_First_Private_Entity
(New_P
, First_Private_Entity
(Old_P
));
1690 Check_Library_Unit_Renaming
(N
, Old_P
);
1691 Generate_Reference
(Old_P
, Name
(N
));
1693 -- If the renaming is in the visible part of a package, then we set
1694 -- Renamed_In_Spec for the renamed package, to prevent giving
1695 -- warnings about no entities referenced. Such a warning would be
1696 -- overenthusiastic, since clients can see entities in the renamed
1697 -- package via the visible package renaming.
1700 Ent
: constant Entity_Id
:= Cunit_Entity
(Current_Sem_Unit
);
1702 if Ekind
(Ent
) = E_Package
1703 and then not In_Private_Part
(Ent
)
1704 and then In_Extended_Main_Source_Unit
(N
)
1705 and then Ekind
(Old_P
) = E_Package
1707 Set_Renamed_In_Spec
(Old_P
);
1711 -- If this is the renaming declaration of a package instantiation
1712 -- within itself, it is the declaration that ends the list of actuals
1713 -- for the instantiation. At this point, the subtypes that rename
1714 -- the actuals are flagged as generic, to avoid spurious ambiguities
1715 -- if the actuals for two distinct formals happen to coincide. If
1716 -- the actual is a private type, the subtype has a private completion
1717 -- that is flagged in the same fashion.
1719 -- Resolution is identical to what is was in the original generic.
1720 -- On exit from the generic instance, these are turned into regular
1721 -- subtypes again, so they are compatible with types in their class.
1723 if not Is_Generic_Instance
(Old_P
) then
1726 Spec
:= Specification
(Unit_Declaration_Node
(Old_P
));
1729 if Nkind
(Spec
) = N_Package_Specification
1730 and then Present
(Generic_Parent
(Spec
))
1731 and then Old_P
= Current_Scope
1732 and then Chars
(New_P
) = Chars
(Generic_Parent
(Spec
))
1738 E
:= First_Entity
(Old_P
);
1739 while Present
(E
) and then E
/= New_P
loop
1741 and then Nkind
(Parent
(E
)) = N_Subtype_Declaration
1743 Set_Is_Generic_Actual_Type
(E
);
1745 if Is_Private_Type
(E
)
1746 and then Present
(Full_View
(E
))
1748 Set_Is_Generic_Actual_Type
(Full_View
(E
));
1758 -- Implementation-defined aspect specifications can appear in a renaming
1759 -- declaration, but not language-defined ones. The call to procedure
1760 -- Analyze_Aspect_Specifications will take care of this error check.
1762 Analyze_Aspect_Specifications
(N
, New_P
);
1763 end Analyze_Package_Renaming
;
1765 -------------------------------
1766 -- Analyze_Renamed_Character --
1767 -------------------------------
1769 procedure Analyze_Renamed_Character
1774 C
: constant Node_Id
:= Name
(N
);
1777 if Ekind
(New_S
) = E_Function
then
1778 Resolve
(C
, Etype
(New_S
));
1781 Check_Frozen_Renaming
(N
, New_S
);
1785 Error_Msg_N
("character literal can only be renamed as function", N
);
1787 end Analyze_Renamed_Character
;
1789 ---------------------------------
1790 -- Analyze_Renamed_Dereference --
1791 ---------------------------------
1793 procedure Analyze_Renamed_Dereference
1798 Nam
: constant Node_Id
:= Name
(N
);
1799 P
: constant Node_Id
:= Prefix
(Nam
);
1805 if not Is_Overloaded
(P
) then
1806 if Ekind
(Etype
(Nam
)) /= E_Subprogram_Type
1807 or else not Type_Conformant
(Etype
(Nam
), New_S
)
1809 Error_Msg_N
("designated type does not match specification", P
);
1818 Get_First_Interp
(Nam
, Ind
, It
);
1820 while Present
(It
.Nam
) loop
1822 if Ekind
(It
.Nam
) = E_Subprogram_Type
1823 and then Type_Conformant
(It
.Nam
, New_S
)
1825 if Typ
/= Any_Id
then
1826 Error_Msg_N
("ambiguous renaming", P
);
1833 Get_Next_Interp
(Ind
, It
);
1836 if Typ
= Any_Type
then
1837 Error_Msg_N
("designated type does not match specification", P
);
1842 Check_Frozen_Renaming
(N
, New_S
);
1846 end Analyze_Renamed_Dereference
;
1848 ---------------------------
1849 -- Analyze_Renamed_Entry --
1850 ---------------------------
1852 procedure Analyze_Renamed_Entry
1857 Nam
: constant Node_Id
:= Name
(N
);
1858 Sel
: constant Node_Id
:= Selector_Name
(Nam
);
1859 Is_Actual
: constant Boolean := Present
(Corresponding_Formal_Spec
(N
));
1863 if Entity
(Sel
) = Any_Id
then
1865 -- Selector is undefined on prefix. Error emitted already
1867 Set_Has_Completion
(New_S
);
1871 -- Otherwise find renamed entity and build body of New_S as a call to it
1873 Old_S
:= Find_Renamed_Entity
(N
, Selector_Name
(Nam
), New_S
);
1875 if Old_S
= Any_Id
then
1876 Error_Msg_N
("no subprogram or entry matches specification", N
);
1879 Check_Subtype_Conformant
(New_S
, Old_S
, N
);
1880 Generate_Reference
(New_S
, Defining_Entity
(N
), 'b');
1881 Style
.Check_Identifier
(Defining_Entity
(N
), New_S
);
1884 -- Only mode conformance required for a renaming_as_declaration
1886 Check_Mode_Conformant
(New_S
, Old_S
, N
);
1889 Inherit_Renamed_Profile
(New_S
, Old_S
);
1891 -- The prefix can be an arbitrary expression that yields a task or
1892 -- protected object, so it must be resolved.
1894 if Is_Access_Type
(Etype
(Prefix
(Nam
))) then
1895 Insert_Explicit_Dereference
(Prefix
(Nam
));
1897 Resolve
(Prefix
(Nam
), Scope
(Old_S
));
1900 Set_Convention
(New_S
, Convention
(Old_S
));
1901 Set_Has_Completion
(New_S
, Inside_A_Generic
);
1903 -- AI05-0225: If the renamed entity is a procedure or entry of a
1904 -- protected object, the target object must be a variable.
1906 if Is_Protected_Type
(Scope
(Old_S
))
1907 and then Ekind
(New_S
) = E_Procedure
1908 and then not Is_Variable
(Prefix
(Nam
))
1912 ("target object of protected operation used as actual for "
1913 & "formal procedure must be a variable", Nam
);
1916 ("target object of protected operation renamed as procedure, "
1917 & "must be a variable", Nam
);
1922 Check_Frozen_Renaming
(N
, New_S
);
1924 end Analyze_Renamed_Entry
;
1926 -----------------------------------
1927 -- Analyze_Renamed_Family_Member --
1928 -----------------------------------
1930 procedure Analyze_Renamed_Family_Member
1935 Nam
: constant Node_Id
:= Name
(N
);
1936 P
: constant Node_Id
:= Prefix
(Nam
);
1940 if (Is_Entity_Name
(P
) and then Ekind
(Entity
(P
)) = E_Entry_Family
)
1941 or else (Nkind
(P
) = N_Selected_Component
1942 and then Ekind
(Entity
(Selector_Name
(P
))) = E_Entry_Family
)
1944 if Is_Entity_Name
(P
) then
1945 Old_S
:= Entity
(P
);
1947 Old_S
:= Entity
(Selector_Name
(P
));
1950 if not Entity_Matches_Spec
(Old_S
, New_S
) then
1951 Error_Msg_N
("entry family does not match specification", N
);
1954 Check_Subtype_Conformant
(New_S
, Old_S
, N
);
1955 Generate_Reference
(New_S
, Defining_Entity
(N
), 'b');
1956 Style
.Check_Identifier
(Defining_Entity
(N
), New_S
);
1960 Error_Msg_N
("no entry family matches specification", N
);
1963 Set_Has_Completion
(New_S
, Inside_A_Generic
);
1966 Check_Frozen_Renaming
(N
, New_S
);
1968 end Analyze_Renamed_Family_Member
;
1970 -----------------------------------------
1971 -- Analyze_Renamed_Primitive_Operation --
1972 -----------------------------------------
1974 procedure Analyze_Renamed_Primitive_Operation
1984 Ctyp
: Conformance_Type
) return Boolean;
1985 -- Verify that the signatures of the renamed entity and the new entity
1986 -- match. The first formal of the renamed entity is skipped because it
1987 -- is the target object in any subsequent call.
1995 Ctyp
: Conformance_Type
) return Boolean
2001 if Ekind
(Subp
) /= Ekind
(New_S
) then
2005 Old_F
:= Next_Formal
(First_Formal
(Subp
));
2006 New_F
:= First_Formal
(New_S
);
2007 while Present
(Old_F
) and then Present
(New_F
) loop
2008 if not Conforming_Types
(Etype
(Old_F
), Etype
(New_F
), Ctyp
) then
2012 if Ctyp
>= Mode_Conformant
2013 and then Ekind
(Old_F
) /= Ekind
(New_F
)
2018 Next_Formal
(New_F
);
2019 Next_Formal
(Old_F
);
2025 -- Start of processing for Analyze_Renamed_Primitive_Operation
2028 if not Is_Overloaded
(Selector_Name
(Name
(N
))) then
2029 Old_S
:= Entity
(Selector_Name
(Name
(N
)));
2031 if not Conforms
(Old_S
, Type_Conformant
) then
2036 -- Find the operation that matches the given signature
2044 Get_First_Interp
(Selector_Name
(Name
(N
)), Ind
, It
);
2046 while Present
(It
.Nam
) loop
2047 if Conforms
(It
.Nam
, Type_Conformant
) then
2051 Get_Next_Interp
(Ind
, It
);
2056 if Old_S
= Any_Id
then
2057 Error_Msg_N
("no subprogram or entry matches specification", N
);
2061 if not Conforms
(Old_S
, Subtype_Conformant
) then
2062 Error_Msg_N
("subtype conformance error in renaming", N
);
2065 Generate_Reference
(New_S
, Defining_Entity
(N
), 'b');
2066 Style
.Check_Identifier
(Defining_Entity
(N
), New_S
);
2069 -- Only mode conformance required for a renaming_as_declaration
2071 if not Conforms
(Old_S
, Mode_Conformant
) then
2072 Error_Msg_N
("mode conformance error in renaming", N
);
2075 -- AI12-0204: The prefix of a prefixed view that is renamed or
2076 -- passed as a formal subprogram must be renamable as an object.
2078 Nam
:= Prefix
(Name
(N
));
2080 if Is_Object_Reference
(Nam
) then
2081 if Is_Dependent_Component_Of_Mutable_Object
(Nam
) then
2083 ("illegal renaming of discriminant-dependent component",
2087 Error_Msg_N
("expect object name in renaming", Nam
);
2090 -- Enforce the rule given in (RM 6.3.1 (10.1/2)): a prefixed
2091 -- view of a subprogram is intrinsic, because the compiler has
2092 -- to generate a wrapper for any call to it. If the name in a
2093 -- subprogram renaming is a prefixed view, the entity is thus
2094 -- intrinsic, and 'Access cannot be applied to it.
2096 Set_Convention
(New_S
, Convention_Intrinsic
);
2099 -- Inherit_Renamed_Profile (New_S, Old_S);
2101 -- The prefix can be an arbitrary expression that yields an
2102 -- object, so it must be resolved.
2104 Resolve
(Prefix
(Name
(N
)));
2106 end Analyze_Renamed_Primitive_Operation
;
2108 ---------------------------------
2109 -- Analyze_Subprogram_Renaming --
2110 ---------------------------------
2112 procedure Analyze_Subprogram_Renaming
(N
: Node_Id
) is
2113 Formal_Spec
: constant Entity_Id
:= Corresponding_Formal_Spec
(N
);
2114 Is_Actual
: constant Boolean := Present
(Formal_Spec
);
2115 Nam
: constant Node_Id
:= Name
(N
);
2116 Save_AV
: constant Ada_Version_Type
:= Ada_Version
;
2117 Save_AVP
: constant Node_Id
:= Ada_Version_Pragma
;
2118 Save_AV_Exp
: constant Ada_Version_Type
:= Ada_Version_Explicit
;
2119 Spec
: constant Node_Id
:= Specification
(N
);
2121 Old_S
: Entity_Id
:= Empty
;
2122 Rename_Spec
: Entity_Id
;
2124 procedure Check_Null_Exclusion
2127 -- Ada 2005 (AI-423): Given renaming Ren of subprogram Sub, check the
2128 -- following AI rules:
2130 -- If Ren denotes a generic formal object of a generic unit G, and the
2131 -- renaming (or instantiation containing the actual) occurs within the
2132 -- body of G or within the body of a generic unit declared within the
2133 -- declarative region of G, then the corresponding parameter of G
2134 -- shall have a null_exclusion; Otherwise the subtype of the Sub's
2135 -- formal parameter shall exclude null.
2137 -- Similarly for its return profile.
2139 procedure Check_SPARK_Primitive_Operation
(Subp_Id
: Entity_Id
);
2140 -- Ensure that a SPARK renaming denoted by its entity Subp_Id does not
2141 -- declare a primitive operation of a tagged type (SPARK RM 6.1.1(3)).
2143 procedure Freeze_Actual_Profile
;
2144 -- In Ada 2012, enforce the freezing rule concerning formal incomplete
2145 -- types: a callable entity freezes its profile, unless it has an
2146 -- incomplete untagged formal (RM 13.14(10.2/3)).
2148 function Has_Class_Wide_Actual
return Boolean;
2149 -- Ada 2012 (AI05-071, AI05-0131) and Ada 2022 (AI12-0165): True if N is
2150 -- the renaming for a defaulted formal subprogram where the actual for
2151 -- the controlling formal type is class-wide.
2153 procedure Handle_Instance_With_Class_Wide_Type
2154 (Inst_Node
: Node_Id
;
2156 Wrapped_Prim
: out Entity_Id
;
2157 Wrap_Id
: out Entity_Id
);
2158 -- Ada 2012 (AI05-0071), Ada 2022 (AI12-0165): when the actual type
2159 -- of an instantiation is a class-wide type T'Class we may need to
2160 -- wrap a primitive operation of T; this routine looks for a suitable
2161 -- primitive to be wrapped and (if the wrapper is required) returns the
2162 -- Id of the wrapped primitive and the Id of the built wrapper. Ren_Id
2163 -- is the defining entity for the renamed subprogram specification.
2165 function Original_Subprogram
(Subp
: Entity_Id
) return Entity_Id
;
2166 -- Find renamed entity when the declaration is a renaming_as_body and
2167 -- the renamed entity may itself be a renaming_as_body. Used to enforce
2168 -- rule that a renaming_as_body is illegal if the declaration occurs
2169 -- before the subprogram it completes is frozen, and renaming indirectly
2170 -- renames the subprogram itself.(Defect Report 8652/0027).
2172 --------------------------
2173 -- Check_Null_Exclusion --
2174 --------------------------
2176 procedure Check_Null_Exclusion
2180 Ren_Formal
: Entity_Id
;
2181 Sub_Formal
: Entity_Id
;
2183 function Null_Exclusion_Mismatch
2184 (Renaming
: Entity_Id
; Renamed
: Entity_Id
) return Boolean;
2185 -- Return True if there is a null exclusion mismatch between
2186 -- Renaming and Renamed, False otherwise.
2188 -----------------------------
2189 -- Null_Exclusion_Mismatch --
2190 -----------------------------
2192 function Null_Exclusion_Mismatch
2193 (Renaming
: Entity_Id
; Renamed
: Entity_Id
) return Boolean is
2195 return Has_Null_Exclusion
(Parent
(Renaming
))
2197 not (Has_Null_Exclusion
(Parent
(Renamed
))
2198 or else (Can_Never_Be_Null
(Etype
(Renamed
))
2200 (Is_Formal_Subprogram
(Sub
)
2201 and then In_Generic_Body
(Current_Scope
))));
2202 end Null_Exclusion_Mismatch
;
2207 Ren_Formal
:= First_Formal
(Ren
);
2208 Sub_Formal
:= First_Formal
(Sub
);
2209 while Present
(Ren_Formal
) and then Present
(Sub_Formal
) loop
2210 if Null_Exclusion_Mismatch
(Ren_Formal
, Sub_Formal
) then
2211 Error_Msg_Sloc
:= Sloc
(Sub_Formal
);
2213 ("`NOT NULL` required for parameter &#",
2214 Ren_Formal
, Sub_Formal
);
2217 Next_Formal
(Ren_Formal
);
2218 Next_Formal
(Sub_Formal
);
2221 -- Return profile check
2223 if Nkind
(Parent
(Ren
)) = N_Function_Specification
2224 and then Nkind
(Parent
(Sub
)) = N_Function_Specification
2225 and then Null_Exclusion_Mismatch
(Ren
, Sub
)
2227 Error_Msg_Sloc
:= Sloc
(Sub
);
2228 Error_Msg_N
("return must specify `NOT NULL`#", Ren
);
2230 end Check_Null_Exclusion
;
2232 -------------------------------------
2233 -- Check_SPARK_Primitive_Operation --
2234 -------------------------------------
2236 procedure Check_SPARK_Primitive_Operation
(Subp_Id
: Entity_Id
) is
2237 Prag
: constant Node_Id
:= SPARK_Pragma
(Subp_Id
);
2241 -- Nothing to do when the subprogram is not subject to SPARK_Mode On
2242 -- because this check applies to SPARK code only.
2244 if not (Present
(Prag
)
2245 and then Get_SPARK_Mode_From_Annotation
(Prag
) = On
)
2249 -- Nothing to do when the subprogram is not a primitive operation
2251 elsif not Is_Primitive
(Subp_Id
) then
2255 Typ
:= Find_Dispatching_Type
(Subp_Id
);
2257 -- Nothing to do when the subprogram is a primitive operation of an
2264 -- At this point a renaming declaration introduces a new primitive
2265 -- operation for a tagged type.
2267 Error_Msg_Node_2
:= Typ
;
2269 ("subprogram renaming & cannot declare primitive for type & "
2270 & "(SPARK RM 6.1.1(3))", N
, Subp_Id
);
2271 end Check_SPARK_Primitive_Operation
;
2273 ---------------------------
2274 -- Freeze_Actual_Profile --
2275 ---------------------------
2277 procedure Freeze_Actual_Profile
is
2279 Has_Untagged_Inc
: Boolean;
2280 Instantiation_Node
: constant Node_Id
:= Parent
(N
);
2283 if Ada_Version
>= Ada_2012
then
2284 F
:= First_Formal
(Formal_Spec
);
2285 Has_Untagged_Inc
:= False;
2286 while Present
(F
) loop
2287 if Ekind
(Etype
(F
)) = E_Incomplete_Type
2288 and then not Is_Tagged_Type
(Etype
(F
))
2290 Has_Untagged_Inc
:= True;
2297 if Ekind
(Formal_Spec
) = E_Function
2298 and then not Is_Tagged_Type
(Etype
(Formal_Spec
))
2300 Has_Untagged_Inc
:= True;
2303 if not Has_Untagged_Inc
then
2304 F
:= First_Formal
(Old_S
);
2305 while Present
(F
) loop
2306 Freeze_Before
(Instantiation_Node
, Etype
(F
));
2308 if Is_Incomplete_Or_Private_Type
(Etype
(F
))
2309 and then No
(Underlying_Type
(Etype
(F
)))
2311 -- Exclude generic types, or types derived from them.
2312 -- They will be frozen in the enclosing instance.
2314 if Is_Generic_Type
(Etype
(F
))
2315 or else Is_Generic_Type
(Root_Type
(Etype
(F
)))
2319 -- A limited view of a type declared elsewhere needs no
2320 -- freezing actions.
2322 elsif From_Limited_With
(Etype
(F
)) then
2327 ("type& must be frozen before this point",
2328 Instantiation_Node
, Etype
(F
));
2336 end Freeze_Actual_Profile
;
2338 ---------------------------
2339 -- Has_Class_Wide_Actual --
2340 ---------------------------
2342 function Has_Class_Wide_Actual
return Boolean is
2344 Formal_Typ
: Entity_Id
;
2348 Formal
:= First_Formal
(Formal_Spec
);
2349 while Present
(Formal
) loop
2350 Formal_Typ
:= Etype
(Formal
);
2352 if Has_Unknown_Discriminants
(Formal_Typ
)
2353 and then not Is_Class_Wide_Type
(Formal_Typ
)
2354 and then Is_Class_Wide_Type
(Get_Instance_Of
(Formal_Typ
))
2359 Next_Formal
(Formal
);
2364 end Has_Class_Wide_Actual
;
2366 ------------------------------------------
2367 -- Handle_Instance_With_Class_Wide_Type --
2368 ------------------------------------------
2370 procedure Handle_Instance_With_Class_Wide_Type
2371 (Inst_Node
: Node_Id
;
2373 Wrapped_Prim
: out Entity_Id
;
2374 Wrap_Id
: out Entity_Id
)
2376 procedure Build_Class_Wide_Wrapper
2377 (Ren_Id
: Entity_Id
;
2378 Prim_Op
: Entity_Id
;
2379 Wrap_Id
: out Entity_Id
);
2380 -- Build a wrapper for the renaming Ren_Id of subprogram Prim_Op.
2382 procedure Find_Suitable_Candidate
2383 (Prim_Op
: out Entity_Id
;
2384 Is_CW_Prim
: out Boolean);
2385 -- Look for a suitable primitive to be wrapped (Prim_Op); Is_CW_Prim
2386 -- indicates that the found candidate is a class-wide primitive (to
2387 -- help the caller decide if the wrapper is required).
2389 ------------------------------
2390 -- Build_Class_Wide_Wrapper --
2391 ------------------------------
2393 procedure Build_Class_Wide_Wrapper
2394 (Ren_Id
: Entity_Id
;
2395 Prim_Op
: Entity_Id
;
2396 Wrap_Id
: out Entity_Id
)
2398 Loc
: constant Source_Ptr
:= Sloc
(N
);
2401 (Subp_Id
: Entity_Id
;
2402 Params
: List_Id
) return Node_Id
;
2403 -- Create a dispatching call to invoke routine Subp_Id with
2404 -- actuals built from the parameter specifications of list Params.
2406 function Build_Expr_Fun_Call
2407 (Subp_Id
: Entity_Id
;
2408 Params
: List_Id
) return Node_Id
;
2409 -- Create a dispatching call to invoke function Subp_Id with
2410 -- actuals built from the parameter specifications of list Params.
2411 -- Directly return the call, so that it can be used inside an
2412 -- expression function. This is a requirement of GNATprove mode.
2414 function Build_Spec
(Subp_Id
: Entity_Id
) return Node_Id
;
2415 -- Create a subprogram specification based on the subprogram
2416 -- profile of Subp_Id.
2423 (Subp_Id
: Entity_Id
;
2424 Params
: List_Id
) return Node_Id
2426 Actuals
: constant List_Id
:= New_List
;
2427 Call_Ref
: constant Node_Id
:= New_Occurrence_Of
(Subp_Id
, Loc
);
2431 -- Build the actual parameters of the call
2433 Formal
:= First
(Params
);
2434 while Present
(Formal
) loop
2436 Make_Identifier
(Loc
,
2437 Chars
(Defining_Identifier
(Formal
))));
2442 -- return Subp_Id (Actuals);
2444 if Ekind
(Subp_Id
) in E_Function | E_Operator
then
2446 Make_Simple_Return_Statement
(Loc
,
2448 Make_Function_Call
(Loc
,
2450 Parameter_Associations
=> Actuals
));
2453 -- Subp_Id (Actuals);
2457 Make_Procedure_Call_Statement
(Loc
,
2459 Parameter_Associations
=> Actuals
);
2463 -------------------------
2464 -- Build_Expr_Fun_Call --
2465 -------------------------
2467 function Build_Expr_Fun_Call
2468 (Subp_Id
: Entity_Id
;
2469 Params
: List_Id
) return Node_Id
2471 Actuals
: constant List_Id
:= New_List
;
2472 Call_Ref
: constant Node_Id
:= New_Occurrence_Of
(Subp_Id
, Loc
);
2476 pragma Assert
(Ekind
(Subp_Id
) in E_Function | E_Operator
);
2478 -- Build the actual parameters of the call
2480 Formal
:= First
(Params
);
2481 while Present
(Formal
) loop
2483 Make_Identifier
(Loc
,
2484 Chars
(Defining_Identifier
(Formal
))));
2489 -- Subp_Id (Actuals);
2492 Make_Function_Call
(Loc
,
2494 Parameter_Associations
=> Actuals
);
2495 end Build_Expr_Fun_Call
;
2501 function Build_Spec
(Subp_Id
: Entity_Id
) return Node_Id
is
2502 Params
: constant List_Id
:= Copy_Parameter_List
(Subp_Id
);
2503 Spec_Id
: constant Entity_Id
:=
2504 Make_Defining_Identifier
(Loc
,
2505 New_External_Name
(Chars
(Subp_Id
), 'R'));
2508 if Ekind
(Formal_Spec
) = E_Procedure
then
2510 Make_Procedure_Specification
(Loc
,
2511 Defining_Unit_Name
=> Spec_Id
,
2512 Parameter_Specifications
=> Params
);
2515 Make_Function_Specification
(Loc
,
2516 Defining_Unit_Name
=> Spec_Id
,
2517 Parameter_Specifications
=> Params
,
2518 Result_Definition
=>
2519 New_Copy_Tree
(Result_Definition
(Spec
)));
2525 Body_Decl
: Node_Id
;
2526 Spec_Decl
: Node_Id
;
2529 -- Start of processing for Build_Class_Wide_Wrapper
2532 pragma Assert
(not Error_Posted
(Nam
));
2534 -- Step 1: Create the declaration and the body of the wrapper,
2535 -- insert all the pieces into the tree.
2537 -- In GNATprove mode, create a function wrapper in the form of an
2538 -- expression function, so that an implicit postcondition relating
2539 -- the result of calling the wrapper function and the result of
2540 -- the dispatching call to the wrapped function is known during
2544 and then Ekind
(Ren_Id
) in E_Function | E_Operator
2546 New_Spec
:= Build_Spec
(Ren_Id
);
2548 Make_Expression_Function
(Loc
,
2549 Specification
=> New_Spec
,
2552 (Subp_Id
=> Prim_Op
,
2553 Params
=> Parameter_Specifications
(New_Spec
)));
2555 Wrap_Id
:= Defining_Entity
(Body_Decl
);
2557 -- Otherwise, create separate spec and body for the subprogram
2561 Make_Subprogram_Declaration
(Loc
,
2562 Specification
=> Build_Spec
(Ren_Id
));
2563 Insert_Before_And_Analyze
(N
, Spec_Decl
);
2565 Wrap_Id
:= Defining_Entity
(Spec_Decl
);
2568 Make_Subprogram_Body
(Loc
,
2569 Specification
=> Build_Spec
(Ren_Id
),
2570 Declarations
=> New_List
,
2571 Handled_Statement_Sequence
=>
2572 Make_Handled_Sequence_Of_Statements
(Loc
,
2573 Statements
=> New_List
(
2575 (Subp_Id
=> Prim_Op
,
2577 Parameter_Specifications
2578 (Specification
(Spec_Decl
))))));
2580 Set_Corresponding_Body
(Spec_Decl
, Defining_Entity
(Body_Decl
));
2583 Set_Is_Class_Wide_Wrapper
(Wrap_Id
);
2585 -- If the operator carries an Eliminated pragma, indicate that
2586 -- the wrapper is also to be eliminated, to prevent spurious
2587 -- errors when using gnatelim on programs that include box-
2588 -- defaulted initialization of equality operators.
2590 Set_Is_Eliminated
(Wrap_Id
, Is_Eliminated
(Prim_Op
));
2592 -- In GNATprove mode, insert the body in the tree for analysis
2594 if GNATprove_Mode
then
2595 Insert_Before_And_Analyze
(N
, Body_Decl
);
2598 -- The generated body does not freeze and must be analyzed when
2599 -- the class-wide wrapper is frozen. The body is only needed if
2600 -- expansion is enabled.
2602 if Expander_Active
then
2603 Append_Freeze_Action
(Wrap_Id
, Body_Decl
);
2606 -- Step 2: The subprogram renaming aliases the wrapper
2608 Rewrite
(Name
(N
), New_Occurrence_Of
(Wrap_Id
, Loc
));
2609 end Build_Class_Wide_Wrapper
;
2611 -----------------------------
2612 -- Find_Suitable_Candidate --
2613 -----------------------------
2615 procedure Find_Suitable_Candidate
2616 (Prim_Op
: out Entity_Id
;
2617 Is_CW_Prim
: out Boolean)
2619 Loc
: constant Source_Ptr
:= Sloc
(N
);
2621 function Find_Primitive
(Typ
: Entity_Id
) return Entity_Id
;
2622 -- Find a primitive subprogram of type Typ which matches the
2623 -- profile of the renaming declaration.
2625 procedure Interpretation_Error
(Subp_Id
: Entity_Id
);
2626 -- Emit a continuation error message suggesting subprogram Subp_Id
2627 -- as a possible interpretation.
2629 function Is_Intrinsic_Equality
2630 (Subp_Id
: Entity_Id
) return Boolean;
2631 -- Determine whether subprogram Subp_Id denotes the intrinsic "="
2634 function Is_Suitable_Candidate
2635 (Subp_Id
: Entity_Id
) return Boolean;
2636 -- Determine whether subprogram Subp_Id is a suitable candidate
2637 -- for the role of a wrapped subprogram.
2639 --------------------
2640 -- Find_Primitive --
2641 --------------------
2643 function Find_Primitive
(Typ
: Entity_Id
) return Entity_Id
is
2644 procedure Replace_Parameter_Types
(Spec
: Node_Id
);
2645 -- Given a specification Spec, replace all class-wide parameter
2646 -- types with reference to type Typ.
2648 -----------------------------
2649 -- Replace_Parameter_Types --
2650 -----------------------------
2652 procedure Replace_Parameter_Types
(Spec
: Node_Id
) is
2654 Formal_Id
: Entity_Id
;
2655 Formal_Typ
: Node_Id
;
2658 Formal
:= First
(Parameter_Specifications
(Spec
));
2659 while Present
(Formal
) loop
2660 Formal_Id
:= Defining_Identifier
(Formal
);
2661 Formal_Typ
:= Parameter_Type
(Formal
);
2663 -- Create a new entity for each class-wide formal to
2664 -- prevent aliasing with the original renaming. Replace
2665 -- the type of such a parameter with the candidate type.
2667 if Nkind
(Formal_Typ
) = N_Identifier
2668 and then Is_Class_Wide_Type
(Etype
(Formal_Typ
))
2670 Set_Defining_Identifier
(Formal
,
2671 Make_Defining_Identifier
(Loc
, Chars
(Formal_Id
)));
2673 Set_Parameter_Type
(Formal
,
2674 New_Occurrence_Of
(Typ
, Loc
));
2679 end Replace_Parameter_Types
;
2683 Alt_Ren
: constant Node_Id
:= New_Copy_Tree
(N
);
2684 Alt_Nam
: constant Node_Id
:= Name
(Alt_Ren
);
2685 Alt_Spec
: constant Node_Id
:= Specification
(Alt_Ren
);
2686 Subp_Id
: Entity_Id
;
2688 -- Start of processing for Find_Primitive
2691 -- Each attempt to find a suitable primitive of a particular
2692 -- type operates on its own copy of the original renaming.
2693 -- As a result the original renaming is kept decoration and
2694 -- side-effect free.
2696 -- Inherit the overloaded status of the renamed subprogram name
2698 if Is_Overloaded
(Nam
) then
2699 Set_Is_Overloaded
(Alt_Nam
);
2700 Save_Interps
(Nam
, Alt_Nam
);
2703 -- The copied renaming is hidden from visibility to prevent the
2704 -- pollution of the enclosing context.
2706 Set_Defining_Unit_Name
(Alt_Spec
, Make_Temporary
(Loc
, 'R'));
2708 -- The types of all class-wide parameters must be changed to
2709 -- the candidate type.
2711 Replace_Parameter_Types
(Alt_Spec
);
2713 -- Try to find a suitable primitive that matches the altered
2714 -- profile of the renaming specification.
2719 Nam
=> Name
(Alt_Ren
),
2720 New_S
=> Analyze_Subprogram_Specification
(Alt_Spec
),
2721 Is_Actual
=> Is_Actual
);
2723 -- Do not return Any_Id if the resolution of the altered
2724 -- profile failed as this complicates further checks on
2725 -- the caller side; return Empty instead.
2727 if Subp_Id
= Any_Id
then
2734 --------------------------
2735 -- Interpretation_Error --
2736 --------------------------
2738 procedure Interpretation_Error
(Subp_Id
: Entity_Id
) is
2740 Error_Msg_Sloc
:= Sloc
(Subp_Id
);
2742 if Is_Internal
(Subp_Id
) then
2744 ("\\possible interpretation: predefined & #",
2748 ("\\possible interpretation: & defined #",
2751 end Interpretation_Error
;
2753 ---------------------------
2754 -- Is_Intrinsic_Equality --
2755 ---------------------------
2757 function Is_Intrinsic_Equality
(Subp_Id
: Entity_Id
) return Boolean
2761 Ekind
(Subp_Id
) = E_Operator
2762 and then Chars
(Subp_Id
) = Name_Op_Eq
2763 and then Is_Intrinsic_Subprogram
(Subp_Id
);
2764 end Is_Intrinsic_Equality
;
2766 ---------------------------
2767 -- Is_Suitable_Candidate --
2768 ---------------------------
2770 function Is_Suitable_Candidate
(Subp_Id
: Entity_Id
) return Boolean
2773 if No
(Subp_Id
) then
2776 -- An intrinsic subprogram is never a good candidate. This
2777 -- is an indication of a missing primitive, either defined
2778 -- directly or inherited from a parent tagged type.
2780 elsif Is_Intrinsic_Subprogram
(Subp_Id
) then
2786 end Is_Suitable_Candidate
;
2790 Actual_Typ
: Entity_Id
:= Empty
;
2791 -- The actual class-wide type for Formal_Typ
2793 CW_Prim_OK
: Boolean;
2794 CW_Prim_Op
: Entity_Id
;
2795 -- The class-wide subprogram (if available) that corresponds to
2796 -- the renamed generic formal subprogram.
2798 Formal_Typ
: Entity_Id
:= Empty
;
2799 -- The generic formal type with unknown discriminants
2801 Root_Prim_OK
: Boolean;
2802 Root_Prim_Op
: Entity_Id
;
2803 -- The root type primitive (if available) that corresponds to the
2804 -- renamed generic formal subprogram.
2806 Root_Typ
: Entity_Id
:= Empty
;
2807 -- The root type of Actual_Typ
2811 -- Start of processing for Find_Suitable_Candidate
2814 pragma Assert
(not Error_Posted
(Nam
));
2817 Is_CW_Prim
:= False;
2819 -- Analyze the renamed name, but do not resolve it. The resolution
2820 -- is completed once a suitable subprogram is found.
2824 -- When the renamed name denotes the intrinsic operator equals,
2825 -- the name must be treated as overloaded. This allows for a
2826 -- potential match against the root type's predefined equality
2829 if Is_Intrinsic_Equality
(Entity
(Nam
)) then
2830 Set_Is_Overloaded
(Nam
);
2831 Collect_Interps
(Nam
);
2834 -- Step 1: Find the generic formal type and its corresponding
2835 -- class-wide actual type from the renamed generic formal
2838 Formal
:= First_Formal
(Formal_Spec
);
2839 while Present
(Formal
) loop
2840 if Has_Unknown_Discriminants
(Etype
(Formal
))
2841 and then not Is_Class_Wide_Type
(Etype
(Formal
))
2842 and then Is_Class_Wide_Type
(Get_Instance_Of
(Etype
(Formal
)))
2844 Formal_Typ
:= Etype
(Formal
);
2845 Actual_Typ
:= Base_Type
(Get_Instance_Of
(Formal_Typ
));
2846 Root_Typ
:= Root_Type
(Actual_Typ
);
2850 Next_Formal
(Formal
);
2853 -- The specification of the generic formal subprogram should
2854 -- always contain a formal type with unknown discriminants whose
2855 -- actual is a class-wide type; otherwise this indicates a failure
2856 -- in function Has_Class_Wide_Actual.
2858 pragma Assert
(Present
(Formal_Typ
));
2860 -- Step 2: Find the proper class-wide subprogram or primitive
2861 -- that corresponds to the renamed generic formal subprogram.
2863 CW_Prim_Op
:= Find_Primitive
(Actual_Typ
);
2864 CW_Prim_OK
:= Is_Suitable_Candidate
(CW_Prim_Op
);
2865 Root_Prim_Op
:= Find_Primitive
(Root_Typ
);
2866 Root_Prim_OK
:= Is_Suitable_Candidate
(Root_Prim_Op
);
2868 -- The class-wide actual type has two subprograms that correspond
2869 -- to the renamed generic formal subprogram:
2871 -- with procedure Prim_Op (Param : Formal_Typ);
2873 -- procedure Prim_Op (Param : Actual_Typ); -- may be inherited
2874 -- procedure Prim_Op (Param : Actual_Typ'Class);
2876 -- Even though the declaration of the two subprograms is legal, a
2877 -- call to either one is ambiguous and therefore illegal.
2879 if CW_Prim_OK
and Root_Prim_OK
then
2881 -- A user-defined primitive has precedence over a predefined
2884 if Is_Internal
(CW_Prim_Op
)
2885 and then not Is_Internal
(Root_Prim_Op
)
2887 Prim_Op
:= Root_Prim_Op
;
2889 elsif Is_Internal
(Root_Prim_Op
)
2890 and then not Is_Internal
(CW_Prim_Op
)
2892 Prim_Op
:= CW_Prim_Op
;
2895 elsif CW_Prim_Op
= Root_Prim_Op
then
2896 Prim_Op
:= Root_Prim_Op
;
2898 -- The two subprograms are legal but the class-wide subprogram
2899 -- is a class-wide wrapper built for a previous instantiation;
2900 -- the wrapper has precedence.
2902 elsif Present
(Alias
(CW_Prim_Op
))
2903 and then Is_Class_Wide_Wrapper
(Ultimate_Alias
(CW_Prim_Op
))
2905 Prim_Op
:= CW_Prim_Op
;
2908 -- Otherwise both candidate subprograms are user-defined and
2913 ("ambiguous actual for generic subprogram &",
2915 Interpretation_Error
(Root_Prim_Op
);
2916 Interpretation_Error
(CW_Prim_Op
);
2920 elsif CW_Prim_OK
and not Root_Prim_OK
then
2921 Prim_Op
:= CW_Prim_Op
;
2924 elsif not CW_Prim_OK
and Root_Prim_OK
then
2925 Prim_Op
:= Root_Prim_Op
;
2927 -- An intrinsic equality may act as a suitable candidate in the
2928 -- case of a null type extension where the parent's equality
2929 -- is hidden. A call to an intrinsic equality is expanded as
2932 elsif Present
(Root_Prim_Op
)
2933 and then Is_Intrinsic_Equality
(Root_Prim_Op
)
2935 Prim_Op
:= Root_Prim_Op
;
2937 -- Otherwise there are no candidate subprograms. Let the caller
2938 -- diagnose the error.
2944 -- At this point resolution has taken place and the name is no
2945 -- longer overloaded. Mark the primitive as referenced.
2947 Set_Is_Overloaded
(Name
(N
), False);
2948 Set_Referenced
(Prim_Op
);
2949 end Find_Suitable_Candidate
;
2953 Is_CW_Prim
: Boolean;
2955 -- Start of processing for Handle_Instance_With_Class_Wide_Type
2958 Wrapped_Prim
:= Empty
;
2961 -- Ada 2012 (AI05-0071): A generic/instance scenario involving a
2962 -- formal type with unknown discriminants and a generic primitive
2963 -- operation of the said type with a box require special processing
2964 -- when the actual is a class-wide type:
2967 -- type Formal_Typ (<>) is private;
2968 -- with procedure Prim_Op (Param : Formal_Typ) is <>;
2969 -- package Gen is ...
2971 -- package Inst is new Gen (Actual_Typ'Class);
2973 -- In this case the general renaming mechanism used in the prologue
2974 -- of an instance no longer applies:
2976 -- procedure Prim_Op (Param : Formal_Typ) renames Prim_Op;
2978 -- The above is replaced the following wrapper/renaming combination:
2980 -- procedure Wrapper (Param : Formal_Typ) is -- wrapper
2982 -- Prim_Op (Param); -- primitive
2985 -- procedure Prim_Op (Param : Formal_Typ) renames Wrapper;
2987 -- This transformation applies only if there is no explicit visible
2988 -- class-wide operation at the point of the instantiation. Ren_Id is
2989 -- the entity of the renaming declaration. When the transformation
2990 -- applies, Wrapped_Prim is the entity of the wrapped primitive.
2992 if Box_Present
(Inst_Node
) then
2993 Find_Suitable_Candidate
2994 (Prim_Op
=> Wrapped_Prim
,
2995 Is_CW_Prim
=> Is_CW_Prim
);
2997 if Present
(Wrapped_Prim
) then
2998 if not Is_CW_Prim
then
2999 Build_Class_Wide_Wrapper
(Ren_Id
, Wrapped_Prim
, Wrap_Id
);
3001 -- Small optimization: When the candidate is a class-wide
3002 -- subprogram we don't build the wrapper; we modify the
3003 -- renaming declaration to directly map the actual to the
3004 -- generic formal and discard the candidate.
3007 Rewrite
(Nam
, New_Occurrence_Of
(Wrapped_Prim
, Sloc
(N
)));
3008 Wrapped_Prim
:= Empty
;
3012 -- Ada 2022 (AI12-0165, RM 12.6(8.5/3)): The actual subprogram for a
3013 -- formal_abstract_subprogram_declaration shall be:
3014 -- a) a dispatching operation of the controlling type; or
3015 -- b) if the controlling type is a formal type, and the actual
3016 -- type corresponding to that formal type is a specific type T,
3017 -- a dispatching operation of type T; or
3018 -- c) if the controlling type is a formal type, and the actual
3019 -- type is a class-wide type T'Class, an implicitly declared
3020 -- subprogram corresponding to a primitive operation of type T.
3022 elsif Nkind
(Inst_Node
) = N_Formal_Abstract_Subprogram_Declaration
3023 and then Is_Entity_Name
(Nam
)
3025 Find_Suitable_Candidate
3026 (Prim_Op
=> Wrapped_Prim
,
3027 Is_CW_Prim
=> Is_CW_Prim
);
3029 if Present
(Wrapped_Prim
) then
3031 -- Cases (a) and (b); see previous description.
3033 if not Is_CW_Prim
then
3034 Build_Class_Wide_Wrapper
(Ren_Id
, Wrapped_Prim
, Wrap_Id
);
3036 -- Case (c); see previous description.
3038 -- Implicit operations of T'Class for subtype declarations
3039 -- are built by Derive_Subprogram, and their Alias attribute
3040 -- references the primitive operation of T.
3042 elsif not Comes_From_Source
(Wrapped_Prim
)
3043 and then Nkind
(Parent
(Wrapped_Prim
)) = N_Subtype_Declaration
3044 and then Present
(Alias
(Wrapped_Prim
))
3046 -- We don't need to build the wrapper; we modify the
3047 -- renaming declaration to directly map the actual to
3048 -- the generic formal and discard the candidate.
3051 New_Occurrence_Of
(Alias
(Wrapped_Prim
), Sloc
(N
)));
3052 Wrapped_Prim
:= Empty
;
3054 -- Legality rules do not apply; discard the candidate.
3057 Wrapped_Prim
:= Empty
;
3061 end Handle_Instance_With_Class_Wide_Type
;
3063 -------------------------
3064 -- Original_Subprogram --
3065 -------------------------
3067 function Original_Subprogram
(Subp
: Entity_Id
) return Entity_Id
is
3068 Orig_Decl
: Node_Id
;
3069 Orig_Subp
: Entity_Id
;
3072 -- First case: renamed entity is itself a renaming
3074 if Present
(Alias
(Subp
)) then
3075 return Alias
(Subp
);
3077 elsif Nkind
(Unit_Declaration_Node
(Subp
)) = N_Subprogram_Declaration
3078 and then Present
(Corresponding_Body
(Unit_Declaration_Node
(Subp
)))
3080 -- Check if renamed entity is a renaming_as_body
3083 Unit_Declaration_Node
3084 (Corresponding_Body
(Unit_Declaration_Node
(Subp
)));
3086 if Nkind
(Orig_Decl
) = N_Subprogram_Renaming_Declaration
then
3087 Orig_Subp
:= Entity
(Name
(Orig_Decl
));
3089 if Orig_Subp
= Rename_Spec
then
3091 -- Circularity detected
3096 return (Original_Subprogram
(Orig_Subp
));
3104 end Original_Subprogram
;
3108 CW_Actual
: constant Boolean := Has_Class_Wide_Actual
;
3109 -- Ada 2012 (AI05-071, AI05-0131) and Ada 2022 (AI12-0165): True if the
3110 -- renaming is for a defaulted formal subprogram when the actual for a
3111 -- related formal type is class-wide.
3113 Inst_Node
: Node_Id
:= Empty
;
3114 New_S
: Entity_Id
:= Empty
;
3115 Wrapped_Prim
: Entity_Id
:= Empty
;
3117 -- Start of processing for Analyze_Subprogram_Renaming
3120 -- We must test for the attribute renaming case before the Analyze
3121 -- call because otherwise Sem_Attr will complain that the attribute
3122 -- is missing an argument when it is analyzed.
3124 if Nkind
(Nam
) = N_Attribute_Reference
then
3126 -- In the case of an abstract formal subprogram association, rewrite
3127 -- an actual given by a stream or Put_Image attribute as the name of
3128 -- the corresponding stream or Put_Image primitive of the type.
3130 -- In a generic context the stream and Put_Image operations are not
3131 -- generated, and this must be treated as a normal attribute
3132 -- reference, to be expanded in subsequent instantiations.
3135 and then Is_Abstract_Subprogram
(Formal_Spec
)
3136 and then Expander_Active
3139 Prefix_Type
: constant Entity_Id
:= Entity
(Prefix
(Nam
));
3143 -- The class-wide forms of the stream and Put_Image attributes
3144 -- are not primitive dispatching operations (even though they
3145 -- internally dispatch).
3147 if Is_Class_Wide_Type
(Prefix_Type
) then
3149 ("attribute must be a primitive dispatching operation",
3154 -- Retrieve the primitive subprogram associated with the
3155 -- attribute. This can only be a stream attribute, since those
3156 -- are the only ones that are dispatching (and the actual for
3157 -- an abstract formal subprogram must be dispatching
3160 case Attribute_Name
(Nam
) is
3163 Find_Optional_Prim_Op
(Prefix_Type
, TSS_Stream_Input
);
3167 Find_Optional_Prim_Op
(Prefix_Type
, TSS_Stream_Output
);
3171 Find_Optional_Prim_Op
(Prefix_Type
, TSS_Stream_Read
);
3175 Find_Optional_Prim_Op
(Prefix_Type
, TSS_Stream_Write
);
3177 when Name_Put_Image
=>
3179 Find_Optional_Prim_Op
(Prefix_Type
, TSS_Put_Image
);
3183 ("attribute must be a primitive dispatching operation",
3188 -- If no stream operation was found, and the type is limited,
3189 -- the user should have defined one. This rule does not apply
3193 and then Attribute_Name
(Nam
) /= Name_Put_Image
3195 if Is_Limited_Type
(Prefix_Type
) then
3197 ("stream operation not defined for type&",
3201 -- Otherwise, compiler should have generated default
3204 raise Program_Error
;
3208 -- Rewrite the attribute into the name of its corresponding
3209 -- primitive dispatching subprogram. We can then proceed with
3210 -- the usual processing for subprogram renamings.
3213 Prim_Name
: constant Node_Id
:=
3214 Make_Identifier
(Sloc
(Nam
),
3215 Chars
=> Chars
(Prim
));
3217 Set_Entity
(Prim_Name
, Prim
);
3218 Rewrite
(Nam
, Prim_Name
);
3223 -- Normal processing for a renaming of an attribute
3226 Attribute_Renaming
(N
);
3231 -- Check whether this declaration corresponds to the instantiation of a
3232 -- formal subprogram.
3234 -- If this is an instantiation, the corresponding actual is frozen and
3235 -- error messages can be made more precise. If this is a default
3236 -- subprogram, the entity is already established in the generic, and is
3237 -- not retrieved by visibility. If it is a default with a box, the
3238 -- candidate interpretations, if any, have been collected when building
3239 -- the renaming declaration. If overloaded, the proper interpretation is
3240 -- determined in Find_Renamed_Entity. If the entity is an operator,
3241 -- Find_Renamed_Entity applies additional visibility checks.
3244 Inst_Node
:= Unit_Declaration_Node
(Formal_Spec
);
3246 -- Ada 2012 (AI05-0071) and Ada 2022 (AI12-0165): when the actual
3247 -- type is a class-wide type T'Class we may need to wrap a primitive
3248 -- operation of T. Search for the wrapped primitive and (if required)
3249 -- build a wrapper whose body consists of a dispatching call to the
3250 -- wrapped primitive of T, with its formal parameters as the actual
3253 if CW_Actual
and then
3255 -- Ada 2012 (AI05-0071): Check whether the renaming is for a
3256 -- defaulted actual subprogram with a class-wide actual.
3258 (Box_Present
(Inst_Node
)
3262 -- Ada 2022 (AI12-0165): Check whether the renaming is for a formal
3263 -- abstract subprogram declaration with a class-wide actual.
3265 (Nkind
(Inst_Node
) = N_Formal_Abstract_Subprogram_Declaration
3266 and then Is_Entity_Name
(Nam
)))
3268 New_S
:= Analyze_Subprogram_Specification
(Spec
);
3270 -- Do not attempt to build the wrapper if the renaming is in error
3272 if not Error_Posted
(Nam
) then
3273 Handle_Instance_With_Class_Wide_Type
3274 (Inst_Node
=> Inst_Node
,
3276 Wrapped_Prim
=> Wrapped_Prim
,
3279 -- If several candidates were found, then we reported the
3280 -- ambiguity; stop processing the renaming declaration to
3281 -- avoid reporting further (spurious) errors.
3283 if Error_Posted
(Spec
) then
3290 if Present
(Wrapped_Prim
) then
3292 -- When the wrapper is built, the subprogram renaming aliases
3297 pragma Assert
(Old_S
= Entity
(Nam
)
3298 and then Is_Class_Wide_Wrapper
(Old_S
));
3300 -- The subprogram renaming declaration may become Ghost if it
3301 -- renames a wrapper of a Ghost entity.
3303 Mark_Ghost_Renaming
(N
, Wrapped_Prim
);
3305 elsif Is_Entity_Name
(Nam
)
3306 and then Present
(Entity
(Nam
))
3307 and then not Comes_From_Source
(Nam
)
3308 and then not Is_Overloaded
(Nam
)
3310 Old_S
:= Entity
(Nam
);
3312 -- The subprogram renaming declaration may become Ghost if it
3313 -- renames a Ghost entity.
3315 Mark_Ghost_Renaming
(N
, Old_S
);
3317 New_S
:= Analyze_Subprogram_Specification
(Spec
);
3321 if Ekind
(Old_S
) = E_Operator
then
3325 if Box_Present
(Inst_Node
) then
3326 Old_S
:= Find_Renamed_Entity
(N
, Name
(N
), New_S
, Is_Actual
);
3328 -- If there is an immediately visible homonym of the operator
3329 -- and the declaration has a default, this is worth a warning
3330 -- because the user probably did not intend to get the pre-
3331 -- defined operator, visible in the generic declaration. To
3332 -- find if there is an intended candidate, analyze the renaming
3333 -- again in the current context.
3335 elsif Scope
(Old_S
) = Standard_Standard
3336 and then Present
(Default_Name
(Inst_Node
))
3339 Decl
: constant Node_Id
:= New_Copy_Tree
(N
);
3343 Set_Entity
(Name
(Decl
), Empty
);
3344 Analyze
(Name
(Decl
));
3346 Find_Renamed_Entity
(Decl
, Name
(Decl
), New_S
, True);
3349 and then In_Open_Scopes
(Scope
(Hidden
))
3350 and then Is_Immediately_Visible
(Hidden
)
3351 and then Comes_From_Source
(Hidden
)
3352 and then Hidden
/= Old_S
3354 Error_Msg_Sloc
:= Sloc
(Hidden
);
3356 ("default subprogram is resolved in the generic "
3357 & "declaration (RM 12.6(17))??", N
);
3358 Error_Msg_NE
("\and will not use & #??", N
, Hidden
);
3367 -- The subprogram renaming declaration may become Ghost if it
3368 -- renames a Ghost entity.
3370 if Is_Entity_Name
(Nam
) then
3371 Mark_Ghost_Renaming
(N
, Entity
(Nam
));
3374 New_S
:= Analyze_Subprogram_Specification
(Spec
);
3378 -- Renamed entity must be analyzed first, to avoid being hidden by
3379 -- new name (which might be the same in a generic instance).
3383 -- The subprogram renaming declaration may become Ghost if it renames
3386 if Is_Entity_Name
(Nam
) then
3387 Mark_Ghost_Renaming
(N
, Entity
(Nam
));
3390 -- The renaming defines a new overloaded entity, which is analyzed
3391 -- like a subprogram declaration.
3393 New_S
:= Analyze_Subprogram_Specification
(Spec
);
3396 if Current_Scope
/= Standard_Standard
then
3397 Set_Is_Pure
(New_S
, Is_Pure
(Current_Scope
));
3400 -- Set SPARK mode from current context
3402 Set_SPARK_Pragma
(New_S
, SPARK_Mode_Pragma
);
3403 Set_SPARK_Pragma_Inherited
(New_S
);
3405 Rename_Spec
:= Find_Corresponding_Spec
(N
);
3407 -- Case of Renaming_As_Body
3409 if Present
(Rename_Spec
) then
3410 Check_Previous_Null_Procedure
(N
, Rename_Spec
);
3412 -- Renaming declaration is the completion of the declaration of
3413 -- Rename_Spec. We build an actual body for it at the freezing point.
3415 Set_Corresponding_Spec
(N
, Rename_Spec
);
3417 -- Deal with special case of stream functions of abstract types
3420 if Nkind
(Unit_Declaration_Node
(Rename_Spec
)) =
3421 N_Abstract_Subprogram_Declaration
3423 -- Input stream functions are abstract if the object type is
3424 -- abstract. Similarly, all default stream functions for an
3425 -- interface type are abstract. However, these subprograms may
3426 -- receive explicit declarations in representation clauses, making
3427 -- the attribute subprograms usable as defaults in subsequent
3429 -- In this case we rewrite the declaration to make the subprogram
3430 -- non-abstract. We remove the previous declaration, and insert
3431 -- the new one at the point of the renaming, to prevent premature
3432 -- access to unfrozen types. The new declaration reuses the
3433 -- specification of the previous one, and must not be analyzed.
3436 (Is_Primitive
(Entity
(Nam
))
3438 Is_Abstract_Type
(Find_Dispatching_Type
(Entity
(Nam
))));
3440 Old_Decl
: constant Node_Id
:=
3441 Unit_Declaration_Node
(Rename_Spec
);
3442 New_Decl
: constant Node_Id
:=
3443 Make_Subprogram_Declaration
(Sloc
(N
),
3445 Relocate_Node
(Specification
(Old_Decl
)));
3448 Insert_After
(N
, New_Decl
);
3449 Set_Is_Abstract_Subprogram
(Rename_Spec
, False);
3450 Set_Analyzed
(New_Decl
);
3454 Set_Corresponding_Body
(Unit_Declaration_Node
(Rename_Spec
), New_S
);
3456 if Ada_Version
= Ada_83
and then Comes_From_Source
(N
) then
3457 Error_Msg_N
("(Ada 83) renaming cannot serve as a body", N
);
3460 Set_Convention
(New_S
, Convention
(Rename_Spec
));
3461 Check_Fully_Conformant
(New_S
, Rename_Spec
);
3462 Set_Public_Status
(New_S
);
3464 if No_Return
(Rename_Spec
)
3465 and then not No_Return
(Entity
(Nam
))
3468 ("renamed subprogram & must be No_Return", N
, Entity
(Nam
));
3470 ("\since renaming subprogram is No_Return (RM 6.5.1(7/2))", N
);
3473 -- The specification does not introduce new formals, but only
3474 -- repeats the formals of the original subprogram declaration.
3475 -- For cross-reference purposes, and for refactoring tools, we
3476 -- treat the formals of the renaming declaration as body formals.
3478 Reference_Body_Formals
(Rename_Spec
, New_S
);
3480 -- Indicate that the entity in the declaration functions like the
3481 -- corresponding body, and is not a new entity. The body will be
3482 -- constructed later at the freeze point, so indicate that the
3483 -- completion has not been seen yet.
3485 Reinit_Field_To_Zero
(New_S
, F_Has_Out_Or_In_Out_Parameter
,
3486 Old_Ekind
=> (E_Function | E_Procedure
=> True, others => False));
3487 Reinit_Field_To_Zero
(New_S
, F_Needs_No_Actuals
);
3488 Reinit_Field_To_Zero
(New_S
, F_Is_Predicate_Function
);
3489 Reinit_Field_To_Zero
(New_S
, F_Protected_Subprogram
);
3490 Reinit_Field_To_Zero
(New_S
, F_Is_Inlined_Always
);
3491 Reinit_Field_To_Zero
(New_S
, F_Is_Generic_Actual_Subprogram
);
3492 Mutate_Ekind
(New_S
, E_Subprogram_Body
);
3493 New_S
:= Rename_Spec
;
3494 Set_Has_Completion
(Rename_Spec
, False);
3496 -- Ada 2005: check overriding indicator
3498 if Present
(Overridden_Operation
(Rename_Spec
)) then
3499 if Must_Not_Override
(Specification
(N
)) then
3501 ("subprogram& overrides inherited operation",
3505 and then not Must_Override
(Specification
(N
))
3507 Style
.Missing_Overriding
(N
, Rename_Spec
);
3510 elsif Must_Override
(Specification
(N
))
3511 and then not Can_Override_Operator
(Rename_Spec
)
3513 Error_Msg_NE
("subprogram& is not overriding", N
, Rename_Spec
);
3516 -- AI12-0132: a renames-as-body freezes the expression of any
3517 -- expression function that it renames.
3519 if Is_Entity_Name
(Nam
)
3520 and then Is_Expression_Function
(Entity
(Nam
))
3521 and then not Inside_A_Generic
3524 (Def_Id
=> Entity
(Nam
),
3525 Typ
=> Etype
(Entity
(Nam
)),
3528 (Original_Node
(Unit_Declaration_Node
(Entity
(Nam
)))),
3532 -- Normal subprogram renaming (not renaming as body)
3535 Generate_Definition
(New_S
);
3536 New_Overloaded_Entity
(New_S
);
3538 if not (Is_Entity_Name
(Nam
)
3539 and then Is_Intrinsic_Subprogram
(Entity
(Nam
)))
3541 Check_Delayed_Subprogram
(New_S
);
3544 -- Verify that a SPARK renaming does not declare a primitive
3545 -- operation of a tagged type.
3547 Check_SPARK_Primitive_Operation
(New_S
);
3550 -- There is no need for elaboration checks on the new entity, which may
3551 -- be called before the next freezing point where the body will appear.
3552 -- Elaboration checks refer to the real entity, not the one created by
3553 -- the renaming declaration.
3555 Set_Kill_Elaboration_Checks
(New_S
, True);
3557 -- If we had a previous error, indicate a completion is present to stop
3558 -- junk cascaded messages, but don't take any further action.
3560 if Etype
(Nam
) = Any_Type
then
3561 Set_Has_Completion
(New_S
);
3564 -- Case where name has the form of a selected component
3566 elsif Nkind
(Nam
) = N_Selected_Component
then
3568 -- A name which has the form A.B can designate an entry of task A, a
3569 -- protected operation of protected object A, or finally a primitive
3570 -- operation of object A. In the later case, A is an object of some
3571 -- tagged type, or an access type that denotes one such. To further
3572 -- distinguish these cases, note that the scope of a task entry or
3573 -- protected operation is type of the prefix.
3575 -- The prefix could be an overloaded function call that returns both
3576 -- kinds of operations. This overloading pathology is left to the
3577 -- dedicated reader ???
3580 T
: constant Entity_Id
:= Etype
(Prefix
(Nam
));
3588 and then Is_Tagged_Type
(Designated_Type
(T
))))
3589 and then Scope
(Entity
(Selector_Name
(Nam
))) /= T
3591 Analyze_Renamed_Primitive_Operation
3592 (N
, New_S
, Present
(Rename_Spec
));
3596 -- Renamed entity is an entry or protected operation. For those
3597 -- cases an explicit body is built (at the point of freezing of
3598 -- this entity) that contains a call to the renamed entity.
3600 -- This is not allowed for renaming as body if the renamed
3601 -- spec is already frozen (see RM 8.5.4(5) for details).
3603 if Present
(Rename_Spec
) and then Is_Frozen
(Rename_Spec
) then
3605 ("renaming-as-body cannot rename entry as subprogram", N
);
3607 ("\since & is already frozen (RM 8.5.4(5))",
3610 Analyze_Renamed_Entry
(N
, New_S
, Present
(Rename_Spec
));
3617 -- Case where name is an explicit dereference X.all
3619 elsif Nkind
(Nam
) = N_Explicit_Dereference
then
3621 -- Renamed entity is designated by access_to_subprogram expression.
3622 -- Must build body to encapsulate call, as in the entry case.
3624 Analyze_Renamed_Dereference
(N
, New_S
, Present
(Rename_Spec
));
3627 -- Indexed component
3629 elsif Nkind
(Nam
) = N_Indexed_Component
then
3630 Analyze_Renamed_Family_Member
(N
, New_S
, Present
(Rename_Spec
));
3633 -- Character literal
3635 elsif Nkind
(Nam
) = N_Character_Literal
then
3636 Analyze_Renamed_Character
(N
, New_S
, Present
(Rename_Spec
));
3639 -- Only remaining case is where we have a non-entity name, or a renaming
3640 -- of some other non-overloadable entity.
3642 elsif not Is_Entity_Name
(Nam
)
3643 or else not Is_Overloadable
(Entity
(Nam
))
3645 -- Do not mention the renaming if it comes from an instance
3647 if not Is_Actual
then
3648 Error_Msg_N
("expect valid subprogram name in renaming", N
);
3650 Error_Msg_NE
("no visible subprogram for formal&", N
, Nam
);
3656 -- Find the renamed entity that matches the given specification. Disable
3657 -- Ada_83 because there is no requirement of full conformance between
3658 -- renamed entity and new entity, even though the same circuit is used.
3660 -- This is a bit of an odd case, which introduces a really irregular use
3661 -- of Ada_Version[_Explicit]. Would be nice to find cleaner way to do
3664 Ada_Version
:= Ada_Version_Type
'Max (Ada_Version
, Ada_95
);
3665 Ada_Version_Pragma
:= Empty
;
3666 Ada_Version_Explicit
:= Ada_Version
;
3669 Old_S
:= Find_Renamed_Entity
(N
, Name
(N
), New_S
, Is_Actual
);
3671 -- The visible operation may be an inherited abstract operation that
3672 -- was overridden in the private part, in which case a call will
3673 -- dispatch to the overriding operation. Use the overriding one in
3674 -- the renaming declaration, to prevent spurious errors below.
3676 if Is_Overloadable
(Old_S
)
3677 and then Is_Abstract_Subprogram
(Old_S
)
3678 and then No
(DTC_Entity
(Old_S
))
3679 and then Present
(Alias
(Old_S
))
3680 and then not Is_Abstract_Subprogram
(Alias
(Old_S
))
3681 and then Present
(Overridden_Operation
(Alias
(Old_S
)))
3683 Old_S
:= Alias
(Old_S
);
3686 -- When the renamed subprogram is overloaded and used as an actual
3687 -- of a generic, its entity is set to the first available homonym.
3688 -- We must first disambiguate the name, then set the proper entity.
3690 if Is_Actual
and then Is_Overloaded
(Nam
) then
3691 Set_Entity
(Nam
, Old_S
);
3695 -- Most common case: subprogram renames subprogram. No body is generated
3696 -- in this case, so we must indicate the declaration is complete as is.
3697 -- and inherit various attributes of the renamed subprogram.
3699 if No
(Rename_Spec
) then
3700 Set_Has_Completion
(New_S
);
3701 Set_Is_Imported
(New_S
, Is_Imported
(Entity
(Nam
)));
3702 Set_Is_Pure
(New_S
, Is_Pure
(Entity
(Nam
)));
3703 Set_Is_Preelaborated
(New_S
, Is_Preelaborated
(Entity
(Nam
)));
3705 -- Ada 2005 (AI-423): Check the consistency of null exclusions
3706 -- between a subprogram and its correct renaming.
3708 -- Note: the Any_Id check is a guard that prevents compiler crashes
3709 -- when performing a null exclusion check between a renaming and a
3710 -- renamed subprogram that has been found to be illegal.
3712 if Ada_Version
>= Ada_2005
and then Entity
(Nam
) /= Any_Id
then
3713 Check_Null_Exclusion
3715 Sub
=> Entity
(Nam
));
3718 -- Enforce the Ada 2005 rule that the renamed entity cannot require
3719 -- overriding. The flag Requires_Overriding is set very selectively
3720 -- and misses some other illegal cases. The additional conditions
3721 -- checked below are sufficient but not necessary ???
3723 -- The rule does not apply to the renaming generated for an actual
3724 -- subprogram in an instance.
3729 -- Guard against previous errors, and omit renamings of predefined
3732 elsif Ekind
(Old_S
) not in E_Function | E_Procedure
then
3735 elsif Requires_Overriding
(Old_S
)
3737 (Is_Abstract_Subprogram
(Old_S
)
3738 and then Present
(Find_Dispatching_Type
(Old_S
))
3739 and then not Is_Abstract_Type
(Find_Dispatching_Type
(Old_S
)))
3742 ("renamed entity cannot be subprogram that requires overriding "
3743 & "(RM 8.5.4 (5.1))", N
);
3747 Prev
: constant Entity_Id
:= Overridden_Operation
(New_S
);
3751 (Has_Non_Trivial_Precondition
(Prev
)
3752 or else Has_Non_Trivial_Precondition
(Old_S
))
3755 ("conflicting inherited classwide preconditions in renaming "
3756 & "of& (RM 6.1.1 (17)", N
, Old_S
);
3761 if Old_S
/= Any_Id
then
3762 if Is_Actual
and then From_Default
(N
) then
3764 -- This is an implicit reference to the default actual
3766 Generate_Reference
(Old_S
, Nam
, Typ
=> 'i', Force
=> True);
3769 Generate_Reference
(Old_S
, Nam
);
3772 Check_Internal_Protected_Use
(N
, Old_S
);
3774 -- For a renaming-as-body, require subtype conformance, but if the
3775 -- declaration being completed has not been frozen, then inherit the
3776 -- convention of the renamed subprogram prior to checking conformance
3777 -- (unless the renaming has an explicit convention established; the
3778 -- rule stated in the RM doesn't seem to address this ???).
3780 if Present
(Rename_Spec
) then
3781 Generate_Reference
(Rename_Spec
, Defining_Entity
(Spec
), 'b');
3782 Style
.Check_Identifier
(Defining_Entity
(Spec
), Rename_Spec
);
3784 if not Is_Frozen
(Rename_Spec
) then
3785 if not Has_Convention_Pragma
(Rename_Spec
) then
3786 Set_Convention
(New_S
, Convention
(Old_S
));
3789 if Ekind
(Old_S
) /= E_Operator
then
3790 Check_Mode_Conformant
(New_S
, Old_S
, Spec
);
3793 if Original_Subprogram
(Old_S
) = Rename_Spec
then
3794 Error_Msg_N
("unfrozen subprogram cannot rename itself", N
);
3796 Check_Formal_Subprogram_Conformance
(New_S
, Old_S
, Spec
);
3799 Check_Subtype_Conformant
(New_S
, Old_S
, Spec
);
3802 Check_Frozen_Renaming
(N
, Rename_Spec
);
3804 -- Check explicitly that renamed entity is not intrinsic, because
3805 -- in a generic the renamed body is not built. In this case,
3806 -- the renaming_as_body is a completion.
3808 if Inside_A_Generic
then
3809 if Is_Frozen
(Rename_Spec
)
3810 and then Is_Intrinsic_Subprogram
(Old_S
)
3813 ("subprogram in renaming_as_body cannot be intrinsic",
3817 Set_Has_Completion
(Rename_Spec
);
3820 elsif Ekind
(Old_S
) /= E_Operator
then
3822 -- If this a defaulted subprogram for a class-wide actual there is
3823 -- no check for mode conformance, given that the signatures don't
3824 -- match (the source mentions T but the actual mentions T'Class).
3829 -- No need for a redundant error message if this is a nested
3830 -- instance, unless the current instantiation (of a child unit)
3831 -- is a compilation unit, which is not analyzed when the parent
3832 -- generic is analyzed.
3835 or else No
(Enclosing_Instance
)
3836 or else Is_Compilation_Unit
(Current_Scope
)
3838 Check_Mode_Conformant
(New_S
, Old_S
);
3842 if No
(Rename_Spec
) then
3844 -- The parameter profile of the new entity is that of the renamed
3845 -- entity: the subtypes given in the specification are irrelevant.
3847 Inherit_Renamed_Profile
(New_S
, Old_S
);
3849 -- A call to the subprogram is transformed into a call to the
3850 -- renamed entity. This is transitive if the renamed entity is
3851 -- itself a renaming.
3853 if Present
(Alias
(Old_S
)) then
3854 Set_Alias
(New_S
, Alias
(Old_S
));
3856 Set_Alias
(New_S
, Old_S
);
3859 -- Note that we do not set Is_Intrinsic_Subprogram if we have a
3860 -- renaming as body, since the entity in this case is not an
3861 -- intrinsic (it calls an intrinsic, but we have a real body for
3862 -- this call, and it is in this body that the required intrinsic
3863 -- processing will take place).
3865 -- Also, if this is a renaming of inequality, the renamed operator
3866 -- is intrinsic, but what matters is the corresponding equality
3867 -- operator, which may be user-defined.
3869 Set_Is_Intrinsic_Subprogram
3871 Is_Intrinsic_Subprogram
(Old_S
)
3873 (Chars
(Old_S
) /= Name_Op_Ne
3874 or else Ekind
(Old_S
) = E_Operator
3875 or else Is_Intrinsic_Subprogram
3876 (Corresponding_Equality
(Old_S
))));
3878 if Ekind
(Alias
(New_S
)) = E_Operator
then
3879 Set_Has_Delayed_Freeze
(New_S
, False);
3882 -- If the renaming corresponds to an association for an abstract
3883 -- formal subprogram, then various attributes must be set to
3884 -- indicate that the renaming is an abstract dispatching operation
3885 -- with a controlling type.
3887 -- Skip this decoration when the renaming corresponds to an
3888 -- association with class-wide wrapper (see above) because such
3889 -- wrapper is neither abstract nor a dispatching operation (its
3890 -- body has the dispatching call to the wrapped primitive).
3893 and then Is_Abstract_Subprogram
(Formal_Spec
)
3894 and then No
(Wrapped_Prim
)
3897 -- Mark the renaming as abstract here, so Find_Dispatching_Type
3898 -- see it as corresponding to a generic association for a
3899 -- formal abstract subprogram
3901 Set_Is_Abstract_Subprogram
(New_S
);
3904 New_S_Ctrl_Type
: constant Entity_Id
:=
3905 Find_Dispatching_Type
(New_S
);
3906 Old_S_Ctrl_Type
: constant Entity_Id
:=
3907 Find_Dispatching_Type
(Old_S
);
3911 -- The actual must match the (instance of the) formal,
3912 -- and must be a controlling type.
3914 if Old_S_Ctrl_Type
/= New_S_Ctrl_Type
3915 or else No
(New_S_Ctrl_Type
)
3917 if No
(New_S_Ctrl_Type
) then
3919 ("actual must be dispatching subprogram", Nam
);
3922 ("actual must be dispatching subprogram for type&",
3923 Nam
, New_S_Ctrl_Type
);
3927 Set_Is_Dispatching_Operation
(New_S
);
3928 Check_Controlling_Formals
(New_S_Ctrl_Type
, New_S
);
3930 -- If the actual in the formal subprogram is itself a
3931 -- formal abstract subprogram association, there's no
3932 -- dispatch table component or position to inherit.
3934 if Present
(DTC_Entity
(Old_S
)) then
3935 Set_DTC_Entity
(New_S
, DTC_Entity
(Old_S
));
3936 Set_DT_Position_Value
(New_S
, DT_Position
(Old_S
));
3946 -- The following is illegal, because F hides whatever other F may
3948 -- function F (...) renames F;
3951 or else (Nkind
(Nam
) /= N_Expanded_Name
3952 and then Chars
(Old_S
) = Chars
(New_S
))
3954 Error_Msg_N
("subprogram cannot rename itself", N
);
3956 -- This is illegal even if we use a selector:
3957 -- function F (...) renames Pkg.F;
3958 -- because F is still hidden.
3960 elsif Nkind
(Nam
) = N_Expanded_Name
3961 and then Entity
(Prefix
(Nam
)) = Current_Scope
3962 and then Chars
(Selector_Name
(Nam
)) = Chars
(New_S
)
3964 -- This is an error, but we overlook the error and accept the
3965 -- renaming if the special Overriding_Renamings mode is in effect.
3967 if not Overriding_Renamings
then
3969 ("implicit operation& is not visible (RM 8.3 (15))",
3973 -- Check whether an expanded name used for the renamed subprogram
3974 -- begins with the same name as the renaming itself, and if so,
3975 -- issue an error about the prefix being hidden by the renaming.
3976 -- We exclude generic instances from this checking, since such
3977 -- normally illegal renamings can be constructed when expanding
3980 elsif Nkind
(Nam
) = N_Expanded_Name
and then not In_Instance
then
3982 function Ult_Expanded_Prefix
(N
: Node_Id
) return Node_Id
is
3983 (if Nkind
(N
) /= N_Expanded_Name
3985 else Ult_Expanded_Prefix
(Prefix
(N
)));
3986 -- Returns the ultimate prefix of an expanded name
3989 if Chars
(Entity
(Ult_Expanded_Prefix
(Nam
))) = Chars
(New_S
)
3991 Error_Msg_Sloc
:= Sloc
(N
);
3993 ("& is hidden by declaration#", Nam
, New_S
);
3998 Set_Convention
(New_S
, Convention
(Old_S
));
4000 if Is_Abstract_Subprogram
(Old_S
) then
4001 if Present
(Rename_Spec
) then
4003 ("a renaming-as-body cannot rename an abstract subprogram",
4005 Set_Has_Completion
(Rename_Spec
);
4007 Set_Is_Abstract_Subprogram
(New_S
);
4011 Check_Library_Unit_Renaming
(N
, Old_S
);
4013 -- Pathological case: procedure renames entry in the scope of its
4014 -- task. Entry is given by simple name, but body must be built for
4015 -- procedure. Of course if called it will deadlock.
4017 if Ekind
(Old_S
) = E_Entry
then
4018 Set_Has_Completion
(New_S
, False);
4019 Set_Alias
(New_S
, Empty
);
4022 -- Do not freeze the renaming nor the renamed entity when the context
4023 -- is an enclosing generic. Freezing is an expansion activity, and in
4024 -- addition the renamed entity may depend on the generic formals of
4025 -- the enclosing generic.
4027 if Is_Actual
and not Inside_A_Generic
then
4028 Freeze_Before
(N
, Old_S
);
4029 Freeze_Actual_Profile
;
4030 Set_Has_Delayed_Freeze
(New_S
, False);
4031 Freeze_Before
(N
, New_S
);
4033 if (Ekind
(Old_S
) = E_Procedure
or else Ekind
(Old_S
) = E_Function
)
4034 and then not Is_Abstract_Subprogram
(Formal_Spec
)
4036 -- An abstract subprogram is only allowed as an actual in the
4037 -- case where the formal subprogram is also abstract.
4039 if Is_Abstract_Subprogram
(Old_S
) then
4041 ("abstract subprogram not allowed as generic actual", Nam
);
4044 -- AI12-0412: A primitive of an abstract type with Pre'Class
4045 -- or Post'Class aspects specified with nonstatic expressions
4046 -- is not allowed as actual for a nonabstract formal subprogram
4047 -- (see RM 6.1.1(18.2/5).
4049 if Is_Dispatching_Operation
(Old_S
)
4051 Is_Prim_Of_Abst_Type_With_Nonstatic_CW_Pre_Post
(Old_S
)
4054 ("primitive of abstract type with nonstatic class-wide "
4055 & "pre/postconditions not allowed as actual",
4062 -- A common error is to assume that implicit operators for types are
4063 -- defined in Standard, or in the scope of a subtype. In those cases
4064 -- where the renamed entity is given with an expanded name, it is
4065 -- worth mentioning that operators for the type are not declared in
4066 -- the scope given by the prefix.
4068 if Nkind
(Nam
) = N_Expanded_Name
4069 and then Nkind
(Selector_Name
(Nam
)) = N_Operator_Symbol
4070 and then Scope
(Entity
(Nam
)) = Standard_Standard
4073 T
: constant Entity_Id
:=
4074 Base_Type
(Etype
(First_Formal
(New_S
)));
4076 Error_Msg_Node_2
:= Prefix
(Nam
);
4078 ("operator for type& is not declared in&", Prefix
(Nam
), T
);
4083 ("no visible subprogram matches the specification for&",
4087 if Present
(Candidate_Renaming
) then
4094 F1
:= First_Formal
(Candidate_Renaming
);
4095 F2
:= First_Formal
(New_S
);
4096 T1
:= First_Subtype
(Etype
(F1
));
4097 while Present
(F1
) and then Present
(F2
) loop
4102 if Present
(F1
) and then Present
(Default_Value
(F1
)) then
4103 if Present
(Next_Formal
(F1
)) then
4105 ("\missing specification for & and other formals with "
4106 & "defaults", Spec
, F1
);
4108 Error_Msg_NE
("\missing specification for &", Spec
, F1
);
4112 if Nkind
(Nam
) = N_Operator_Symbol
4113 and then From_Default
(N
)
4115 Error_Msg_Node_2
:= T1
;
4117 ("default & on & is not directly visible", Nam
, Nam
);
4123 -- Ada 2005 AI 404: if the new subprogram is dispatching, verify that
4124 -- controlling access parameters are known non-null for the renamed
4125 -- subprogram. Test also applies to a subprogram instantiation that
4126 -- is dispatching. Test is skipped if some previous error was detected
4127 -- that set Old_S to Any_Id.
4129 if Ada_Version
>= Ada_2005
4130 and then Old_S
/= Any_Id
4131 and then not Is_Dispatching_Operation
(Old_S
)
4132 and then Is_Dispatching_Operation
(New_S
)
4139 Old_F
:= First_Formal
(Old_S
);
4140 New_F
:= First_Formal
(New_S
);
4141 while Present
(Old_F
) loop
4142 if Ekind
(Etype
(Old_F
)) = E_Anonymous_Access_Type
4143 and then Is_Controlling_Formal
(New_F
)
4144 and then not Can_Never_Be_Null
(Old_F
)
4146 Error_Msg_N
("access parameter is controlling,", New_F
);
4148 ("\corresponding parameter of& must be explicitly null "
4149 & "excluding", New_F
, Old_S
);
4152 Next_Formal
(Old_F
);
4153 Next_Formal
(New_F
);
4158 -- A useful warning, suggested by Ada Bug Finder (Ada-Europe 2005)
4159 -- is to warn if an operator is being renamed as a different operator.
4160 -- If the operator is predefined, examine the kind of the entity, not
4161 -- the abbreviated declaration in Standard.
4163 if Comes_From_Source
(N
)
4164 and then Present
(Old_S
)
4165 and then (Nkind
(Old_S
) = N_Defining_Operator_Symbol
4166 or else Ekind
(Old_S
) = E_Operator
)
4167 and then Nkind
(New_S
) = N_Defining_Operator_Symbol
4168 and then Chars
(Old_S
) /= Chars
(New_S
)
4171 ("& is being renamed as a different operator??", N
, Old_S
);
4174 -- Check for renaming of obsolescent subprogram
4176 Check_Obsolescent_2005_Entity
(Entity
(Nam
), Nam
);
4178 -- Another warning or some utility: if the new subprogram as the same
4179 -- name as the old one, the old one is not hidden by an outer homograph,
4180 -- the new one is not a public symbol, and the old one is otherwise
4181 -- directly visible, the renaming is superfluous.
4183 if Chars
(Old_S
) = Chars
(New_S
)
4184 and then Comes_From_Source
(N
)
4185 and then Scope
(Old_S
) /= Standard_Standard
4186 and then Warn_On_Redundant_Constructs
4187 and then (Is_Immediately_Visible
(Old_S
)
4188 or else Is_Potentially_Use_Visible
(Old_S
))
4189 and then Is_Overloadable
(Current_Scope
)
4190 and then Chars
(Current_Scope
) /= Chars
(Old_S
)
4193 ("redundant renaming, entity is directly visible?r?", Name
(N
));
4196 -- Implementation-defined aspect specifications can appear in a renaming
4197 -- declaration, but not language-defined ones. The call to procedure
4198 -- Analyze_Aspect_Specifications will take care of this error check.
4200 Analyze_Aspect_Specifications
(N
, New_S
);
4205 and then Has_Yield_Aspect
(Formal_Spec
)
4206 and then not Has_Yield_Aspect
(Old_S
)
4208 Error_Msg_Name_1
:= Name_Yield
;
4210 ("actual subprogram& must have aspect% to match formal", Name
(N
));
4213 Ada_Version
:= Save_AV
;
4214 Ada_Version_Pragma
:= Save_AVP
;
4215 Ada_Version_Explicit
:= Save_AV_Exp
;
4217 -- Check if we are looking at an Ada 2012 defaulted formal subprogram
4218 -- and mark any use_package_clauses that affect the visibility of the
4219 -- implicit generic actual.
4221 -- Also, we may be looking at an internal renaming of a user-defined
4222 -- subprogram created for a generic formal subprogram association,
4223 -- which will also have to be marked here. This can occur when the
4224 -- corresponding formal subprogram contains references to other generic
4227 if Is_Generic_Actual_Subprogram
(New_S
)
4228 and then (Is_Intrinsic_Subprogram
(New_S
)
4229 or else From_Default
(N
)
4230 or else Nkind
(N
) = N_Subprogram_Renaming_Declaration
)
4232 Mark_Use_Clauses
(New_S
);
4234 -- Handle overloaded subprograms
4236 if Present
(Alias
(New_S
)) then
4237 Mark_Use_Clauses
(Alias
(New_S
));
4242 Local_Restrict
.Check_Actual_Subprogram_For_Instance
4243 (Actual_Subp_Name
=> Nam
, Formal_Subp
=> Formal_Spec
);
4245 end Analyze_Subprogram_Renaming
;
4247 -------------------------
4248 -- Analyze_Use_Package --
4249 -------------------------
4251 -- Resolve the package names in the use clause, and make all the visible
4252 -- entities defined in the package potentially use-visible. If the package
4253 -- is already in use from a previous use clause, its visible entities are
4254 -- already use-visible. In that case, mark the occurrence as a redundant
4255 -- use. If the package is an open scope, i.e. if the use clause occurs
4256 -- within the package itself, ignore it.
4258 procedure Analyze_Use_Package
(N
: Node_Id
; Chain
: Boolean := True) is
4259 procedure Analyze_Package_Name
(Clause
: Node_Id
);
4260 -- Perform analysis on a package name from a use_package_clause
4262 procedure Analyze_Package_Name_List
(Head_Clause
: Node_Id
);
4263 -- Similar to Analyze_Package_Name but iterates over all the names
4266 --------------------------
4267 -- Analyze_Package_Name --
4268 --------------------------
4270 procedure Analyze_Package_Name
(Clause
: Node_Id
) is
4271 Pack
: constant Node_Id
:= Name
(Clause
);
4275 pragma Assert
(Nkind
(Clause
) = N_Use_Package_Clause
);
4278 -- Verify that the package standard is not directly named in a
4279 -- use_package_clause.
4281 if Nkind
(Parent
(Clause
)) = N_Compilation_Unit
4282 and then Nkind
(Pack
) = N_Expanded_Name
4284 Pref
:= Prefix
(Pack
);
4286 while Nkind
(Pref
) = N_Expanded_Name
loop
4287 Pref
:= Prefix
(Pref
);
4290 if Entity
(Pref
) = Standard_Standard
then
4292 ("predefined package Standard cannot appear in a context "
4296 end Analyze_Package_Name
;
4298 -------------------------------
4299 -- Analyze_Package_Name_List --
4300 -------------------------------
4302 procedure Analyze_Package_Name_List
(Head_Clause
: Node_Id
) is
4306 -- Due to the way source use clauses are split during parsing we are
4307 -- forced to simply iterate through all entities in scope until the
4308 -- clause representing the last name in the list is found.
4310 Curr
:= Head_Clause
;
4311 while Present
(Curr
) loop
4312 Analyze_Package_Name
(Curr
);
4314 -- Stop iterating over the names in the use clause when we are at
4317 exit when not More_Ids
(Curr
) and then Prev_Ids
(Curr
);
4320 end Analyze_Package_Name_List
;
4326 -- Start of processing for Analyze_Use_Package
4329 Set_Hidden_By_Use_Clause
(N
, No_Elist
);
4331 -- Use clause not allowed in a spec of a predefined package declaration
4332 -- except that packages whose file name starts a-n are OK (these are
4333 -- children of Ada.Numerics, which are never loaded by Rtsfind).
4335 if Is_Predefined_Unit
(Current_Sem_Unit
)
4336 and then Get_Name_String
4337 (Unit_File_Name
(Current_Sem_Unit
)) (1 .. 3) /= "a-n"
4338 and then Nkind
(Unit
(Cunit
(Current_Sem_Unit
))) =
4339 N_Package_Declaration
4341 Error_Msg_N
("use clause not allowed in predefined spec", N
);
4344 -- Loop through all package names from the original use clause in
4345 -- order to analyze referenced packages. A use_package_clause with only
4346 -- one name does not have More_Ids or Prev_Ids set, while a clause with
4347 -- More_Ids only starts the chain produced by the parser.
4349 if not More_Ids
(N
) and then not Prev_Ids
(N
) then
4350 Analyze_Package_Name
(N
);
4352 elsif More_Ids
(N
) and then not Prev_Ids
(N
) then
4353 Analyze_Package_Name_List
(N
);
4356 if not Is_Entity_Name
(Name
(N
)) then
4357 Error_Msg_N
("& is not a package", Name
(N
));
4363 Chain_Use_Clause
(N
);
4366 Pack
:= Entity
(Name
(N
));
4368 -- There are many cases where scopes are manipulated during analysis, so
4369 -- check that Pack's current use clause has not already been chained
4370 -- before setting its previous use clause.
4372 if Ekind
(Pack
) = E_Package
4373 and then Present
(Current_Use_Clause
(Pack
))
4374 and then Current_Use_Clause
(Pack
) /= N
4375 and then No
(Prev_Use_Clause
(N
))
4376 and then Prev_Use_Clause
(Current_Use_Clause
(Pack
)) /= N
4378 Set_Prev_Use_Clause
(N
, Current_Use_Clause
(Pack
));
4381 -- Mark all entities as potentially use visible
4383 if Ekind
(Pack
) /= E_Package
and then Etype
(Pack
) /= Any_Type
then
4384 if Ekind
(Pack
) = E_Generic_Package
then
4385 Error_Msg_N
-- CODEFIX
4386 ("a generic package is not allowed in a use clause", Name
(N
));
4388 elsif Is_Generic_Subprogram
(Pack
) then
4389 Error_Msg_N
-- CODEFIX
4390 ("a generic subprogram is not allowed in a use clause",
4393 elsif Is_Subprogram
(Pack
) then
4394 Error_Msg_N
-- CODEFIX
4395 ("a subprogram is not allowed in a use clause", Name
(N
));
4398 Error_Msg_N
("& is not allowed in a use clause", Name
(N
));
4402 if Nkind
(Parent
(N
)) = N_Compilation_Unit
then
4403 Check_In_Previous_With_Clause
(N
, Name
(N
));
4406 Use_One_Package
(N
, Name
(N
));
4409 Mark_Ghost_Clause
(N
);
4410 end Analyze_Use_Package
;
4412 ----------------------
4413 -- Analyze_Use_Type --
4414 ----------------------
4416 procedure Analyze_Use_Type
(N
: Node_Id
; Chain
: Boolean := True) is
4421 Set_Hidden_By_Use_Clause
(N
, No_Elist
);
4423 -- Chain clause to list of use clauses in current scope when flagged
4426 Chain_Use_Clause
(N
);
4429 -- Obtain the base type of the type denoted within the use_type_clause's
4432 Id
:= Subtype_Mark
(N
);
4434 E
:= Base_Type
(Entity
(Id
));
4436 -- There are many cases where a use_type_clause may be reanalyzed due to
4437 -- manipulation of the scope stack so we much guard against those cases
4438 -- here, otherwise, we must add the new use_type_clause to the previous
4439 -- use_type_clause chain in order to mark redundant use_type_clauses as
4440 -- used. When the redundant use-type clauses appear in a parent unit and
4441 -- a child unit we must prevent a circularity in the chain that would
4442 -- otherwise result from the separate steps of analysis and installation
4443 -- of the parent context.
4445 if Present
(Current_Use_Clause
(E
))
4446 and then Current_Use_Clause
(E
) /= N
4447 and then Prev_Use_Clause
(Current_Use_Clause
(E
)) /= N
4448 and then No
(Prev_Use_Clause
(N
))
4450 Set_Prev_Use_Clause
(N
, Current_Use_Clause
(E
));
4453 -- If the Used_Operations list is already initialized, the clause has
4454 -- been analyzed previously, and it is being reinstalled, for example
4455 -- when the clause appears in a package spec and we are compiling the
4456 -- corresponding package body. In that case, make the entities on the
4457 -- existing list use_visible, and mark the corresponding types In_Use.
4459 if Present
(Used_Operations
(N
)) then
4464 Use_One_Type
(Subtype_Mark
(N
), Installed
=> True);
4466 Elmt
:= First_Elmt
(Used_Operations
(N
));
4467 while Present
(Elmt
) loop
4468 Set_Is_Potentially_Use_Visible
(Node
(Elmt
));
4476 -- Otherwise, create new list and attach to it the operations that are
4477 -- made use-visible by the clause.
4479 Set_Used_Operations
(N
, New_Elmt_List
);
4482 if E
/= Any_Type
then
4485 if Nkind
(Parent
(N
)) = N_Compilation_Unit
then
4486 if Nkind
(Id
) = N_Identifier
then
4487 Error_Msg_N
("type is not directly visible", Id
);
4489 elsif Is_Child_Unit
(Scope
(E
))
4490 and then Scope
(E
) /= System_Aux_Id
4492 Check_In_Previous_With_Clause
(N
, Prefix
(Id
));
4497 -- If the use_type_clause appears in a compilation unit context,
4498 -- check whether it comes from a unit that may appear in a
4499 -- limited_with_clause, for a better error message.
4501 if Nkind
(Parent
(N
)) = N_Compilation_Unit
4502 and then Nkind
(Id
) /= N_Identifier
4508 function Mentioned
(Nam
: Node_Id
) return Boolean;
4509 -- Check whether the prefix of expanded name for the type
4510 -- appears in the prefix of some limited_with_clause.
4516 function Mentioned
(Nam
: Node_Id
) return Boolean is
4518 return Nkind
(Name
(Item
)) = N_Selected_Component
4519 and then Chars
(Prefix
(Name
(Item
))) = Chars
(Nam
);
4523 Pref
:= Prefix
(Id
);
4524 Item
:= First
(Context_Items
(Parent
(N
)));
4525 while Present
(Item
) and then Item
/= N
loop
4526 if Nkind
(Item
) = N_With_Clause
4527 and then Limited_Present
(Item
)
4528 and then Mentioned
(Pref
)
4531 (Get_Msg_Id
, "premature usage of incomplete type");
4540 Mark_Ghost_Clause
(N
);
4541 end Analyze_Use_Type
;
4543 ------------------------
4544 -- Attribute_Renaming --
4545 ------------------------
4547 procedure Attribute_Renaming
(N
: Node_Id
) is
4548 Loc
: constant Source_Ptr
:= Sloc
(N
);
4549 Nam
: constant Node_Id
:= Name
(N
);
4550 Spec
: constant Node_Id
:= Specification
(N
);
4551 New_S
: constant Entity_Id
:= Defining_Unit_Name
(Spec
);
4552 Aname
: constant Name_Id
:= Attribute_Name
(Nam
);
4554 Form_Num
: Nat
:= 0;
4555 Expr_List
: List_Id
:= No_List
;
4557 Attr_Node
: Node_Id
;
4558 Body_Node
: Node_Id
;
4559 Param_Spec
: Node_Id
;
4562 Generate_Definition
(New_S
);
4564 -- This procedure is called in the context of subprogram renaming, and
4565 -- thus the attribute must be one that is a subprogram. All of those
4566 -- have at least one formal parameter, with the exceptions of the GNAT
4567 -- attribute 'Img, which GNAT treats as renameable.
4569 if Is_Empty_List
(Parameter_Specifications
(Spec
)) then
4570 if Aname
/= Name_Img
then
4572 ("subprogram renaming an attribute must have formals", N
);
4577 Param_Spec
:= First
(Parameter_Specifications
(Spec
));
4578 while Present
(Param_Spec
) loop
4579 Form_Num
:= Form_Num
+ 1;
4581 if Nkind
(Parameter_Type
(Param_Spec
)) /= N_Access_Definition
then
4582 Find_Type
(Parameter_Type
(Param_Spec
));
4584 -- The profile of the new entity denotes the base type (s) of
4585 -- the types given in the specification. For access parameters
4586 -- there are no subtypes involved.
4588 Rewrite
(Parameter_Type
(Param_Spec
),
4590 (Base_Type
(Entity
(Parameter_Type
(Param_Spec
))), Loc
));
4593 if No
(Expr_List
) then
4594 Expr_List
:= New_List
;
4597 Append_To
(Expr_List
,
4598 Make_Identifier
(Loc
,
4599 Chars
=> Chars
(Defining_Identifier
(Param_Spec
))));
4601 -- The expressions in the attribute reference are not freeze
4602 -- points. Neither is the attribute as a whole, see below.
4604 Set_Must_Not_Freeze
(Last
(Expr_List
));
4609 -- Immediate error if too many formals. Other mismatches in number or
4610 -- types of parameters are detected when we analyze the body of the
4611 -- subprogram that we construct.
4613 if Form_Num
> 2 then
4614 Error_Msg_N
("too many formals for attribute", N
);
4616 -- Error if the attribute reference has expressions that look like
4617 -- formal parameters.
4619 elsif Present
(Expressions
(Nam
)) then
4620 Error_Msg_N
("illegal expressions in attribute reference", Nam
);
4622 elsif Aname
in Name_Compose | Name_Exponent | Name_Leading_Part |
4623 Name_Pos | Name_Round | Name_Scaling |
4626 if Nkind
(N
) = N_Subprogram_Renaming_Declaration
4627 and then Present
(Corresponding_Formal_Spec
(N
))
4630 ("generic actual cannot be attribute involving universal type",
4634 ("attribute involving a universal type cannot be renamed",
4639 -- Rewrite attribute node to have a list of expressions corresponding to
4640 -- the subprogram formals. A renaming declaration is not a freeze point,
4641 -- and the analysis of the attribute reference should not freeze the
4642 -- type of the prefix. We use the original node in the renaming so that
4643 -- its source location is preserved, and checks on stream attributes are
4644 -- properly applied.
4646 Attr_Node
:= Relocate_Node
(Nam
);
4647 Set_Expressions
(Attr_Node
, Expr_List
);
4649 Set_Must_Not_Freeze
(Attr_Node
);
4650 Set_Must_Not_Freeze
(Prefix
(Nam
));
4652 -- Case of renaming a function
4654 if Nkind
(Spec
) = N_Function_Specification
then
4655 if Is_Procedure_Attribute_Name
(Aname
) then
4656 Error_Msg_N
("attribute can only be renamed as procedure", Nam
);
4660 Find_Type
(Result_Definition
(Spec
));
4661 Rewrite
(Result_Definition
(Spec
),
4663 (Base_Type
(Entity
(Result_Definition
(Spec
))), Loc
));
4666 Make_Subprogram_Body
(Loc
,
4667 Specification
=> Spec
,
4668 Declarations
=> New_List
,
4669 Handled_Statement_Sequence
=>
4670 Make_Handled_Sequence_Of_Statements
(Loc
,
4671 Statements
=> New_List
(
4672 Make_Simple_Return_Statement
(Loc
,
4673 Expression
=> Attr_Node
))));
4675 -- Case of renaming a procedure
4678 if not Is_Procedure_Attribute_Name
(Aname
) then
4679 Error_Msg_N
("attribute can only be renamed as function", Nam
);
4684 Make_Subprogram_Body
(Loc
,
4685 Specification
=> Spec
,
4686 Declarations
=> New_List
,
4687 Handled_Statement_Sequence
=>
4688 Make_Handled_Sequence_Of_Statements
(Loc
,
4689 Statements
=> New_List
(Attr_Node
)));
4692 -- Signal the ABE mechanism that the generated subprogram body has not
4693 -- ABE ramifications.
4695 Set_Was_Attribute_Reference
(Body_Node
);
4697 -- In case of tagged types we add the body of the generated function to
4698 -- the freezing actions of the type (because in the general case such
4699 -- type is still not frozen). We exclude from this processing generic
4700 -- formal subprograms found in instantiations.
4702 -- We must exclude restricted run-time libraries because
4703 -- entity AST_Handler is defined in package System.Aux_Dec which is not
4704 -- available in those platforms. Note that we cannot use the function
4705 -- Restricted_Profile (instead of Configurable_Run_Time_Mode) because
4706 -- the ZFP run-time library is not defined as a profile, and we do not
4707 -- want to deal with AST_Handler in ZFP mode.
4709 if not Configurable_Run_Time_Mode
4710 and then No
(Corresponding_Formal_Spec
(N
))
4711 and then not Is_RTE
(Etype
(Nam
), RE_AST_Handler
)
4714 P
: constant Node_Id
:= Prefix
(Nam
);
4717 -- The prefix of 'Img is an object that is evaluated for each call
4718 -- of the function that renames it.
4720 if Aname
= Name_Img
then
4721 Preanalyze_And_Resolve
(P
);
4723 -- For all other attribute renamings, the prefix is a subtype
4729 -- If the target type is not yet frozen, add the body to the
4730 -- actions to be elaborated at freeze time.
4732 if Is_Tagged_Type
(Etype
(P
))
4733 and then In_Open_Scopes
(Scope
(Etype
(P
)))
4735 Append_Freeze_Action
(Etype
(P
), Body_Node
);
4737 Rewrite
(N
, Body_Node
);
4739 Set_Etype
(New_S
, Base_Type
(Etype
(New_S
)));
4743 -- Generic formal subprograms or AST_Handler renaming
4746 Rewrite
(N
, Body_Node
);
4748 Set_Etype
(New_S
, Base_Type
(Etype
(New_S
)));
4751 if Is_Compilation_Unit
(New_S
) then
4753 ("a library unit can only rename another library unit", N
);
4756 -- We suppress elaboration warnings for the resulting entity, since
4757 -- clearly they are not needed, and more particularly, in the case
4758 -- of a generic formal subprogram, the resulting entity can appear
4759 -- after the instantiation itself, and thus look like a bogus case
4760 -- of access before elaboration.
4762 if Legacy_Elaboration_Checks
then
4763 Set_Suppress_Elaboration_Warnings
(New_S
);
4765 end Attribute_Renaming
;
4767 ----------------------
4768 -- Chain_Use_Clause --
4769 ----------------------
4771 procedure Chain_Use_Clause
(N
: Node_Id
) is
4772 Level
: Int
:= Scope_Stack
.Last
;
4778 if not Is_Compilation_Unit
(Current_Scope
)
4779 or else not Is_Child_Unit
(Current_Scope
)
4783 -- Common case for compilation unit
4785 elsif Defining_Entity
(Parent
(N
)) = Current_Scope
then
4789 -- If declaration appears in some other scope, it must be in some
4790 -- parent unit when compiling a child.
4792 Pack
:= Defining_Entity
(Parent
(N
));
4794 if not In_Open_Scopes
(Pack
) then
4797 -- If the use clause appears in an ancestor and we are in the
4798 -- private part of the immediate parent, the use clauses are
4799 -- already installed.
4801 elsif Pack
/= Scope
(Current_Scope
)
4802 and then In_Private_Part
(Scope
(Current_Scope
))
4807 -- Find entry for parent unit in scope stack
4809 while Scope_Stack
.Table
(Level
).Entity
/= Pack
loop
4815 Set_Next_Use_Clause
(N
,
4816 Scope_Stack
.Table
(Level
).First_Use_Clause
);
4817 Scope_Stack
.Table
(Level
).First_Use_Clause
:= N
;
4818 end Chain_Use_Clause
;
4820 ---------------------------
4821 -- Check_Frozen_Renaming --
4822 ---------------------------
4824 procedure Check_Frozen_Renaming
(N
: Node_Id
; Subp
: Entity_Id
) is
4829 if Is_Frozen
(Subp
) and then not Has_Completion
(Subp
) then
4832 (Parent
(Declaration_Node
(Subp
)), Defining_Entity
(N
));
4834 if Is_Entity_Name
(Name
(N
)) then
4835 Old_S
:= Entity
(Name
(N
));
4837 if not Is_Frozen
(Old_S
)
4838 and then Operating_Mode
/= Check_Semantics
4840 Append_Freeze_Action
(Old_S
, B_Node
);
4842 Insert_After
(N
, B_Node
);
4846 if Is_Intrinsic_Subprogram
(Old_S
)
4847 and then not In_Instance
4848 and then not Relaxed_RM_Semantics
4851 ("subprogram used in renaming_as_body cannot be intrinsic",
4856 Insert_After
(N
, B_Node
);
4860 end Check_Frozen_Renaming
;
4862 -------------------------------
4863 -- Set_Entity_Or_Discriminal --
4864 -------------------------------
4866 procedure Set_Entity_Or_Discriminal
(N
: Node_Id
; E
: Entity_Id
) is
4870 -- If the entity is not a discriminant, or else expansion is disabled,
4871 -- simply set the entity.
4873 if not In_Spec_Expression
4874 or else Ekind
(E
) /= E_Discriminant
4875 or else Inside_A_Generic
4877 Set_Entity_With_Checks
(N
, E
);
4879 -- The replacement of a discriminant by the corresponding discriminal
4880 -- is not done for a task discriminant that appears in a default
4881 -- expression of an entry parameter. See Exp_Ch2.Expand_Discriminant
4882 -- for details on their handling.
4884 elsif Is_Concurrent_Type
(Scope
(E
)) then
4887 and then Nkind
(P
) not in
4888 N_Parameter_Specification | N_Component_Declaration
4894 and then Nkind
(P
) = N_Parameter_Specification
4898 -- Don't replace a non-qualified discriminant in strict preanalysis
4899 -- mode since it can lead to errors during full analysis when the
4900 -- discriminant gets referenced later.
4902 -- This can occur in situations where a protected type contains
4903 -- an expression function which references a non-prefixed
4907 and then Preanalysis_Active
4908 and then Inside_Preanalysis_Without_Freezing
= 0
4913 Set_Entity
(N
, Discriminal
(E
));
4916 -- Otherwise, this is a discriminant in a context in which
4917 -- it is a reference to the corresponding parameter of the
4918 -- init proc for the enclosing type.
4921 Set_Entity
(N
, Discriminal
(E
));
4923 end Set_Entity_Or_Discriminal
;
4925 -----------------------------------
4926 -- Check_In_Previous_With_Clause --
4927 -----------------------------------
4929 procedure Check_In_Previous_With_Clause
(N
, Nam
: Node_Id
) is
4930 Pack
: constant Entity_Id
:= Entity
(Original_Node
(Nam
));
4935 Item
:= First
(Context_Items
(Parent
(N
)));
4936 while Present
(Item
) and then Item
/= N
loop
4937 if Nkind
(Item
) = N_With_Clause
4939 -- Protect the frontend against previous critical errors
4941 and then Nkind
(Name
(Item
)) /= N_Selected_Component
4942 and then Entity
(Name
(Item
)) = Pack
4946 -- Find root library unit in with_clause
4948 while Nkind
(Par
) = N_Expanded_Name
loop
4949 Par
:= Prefix
(Par
);
4952 if Is_Child_Unit
(Entity
(Original_Node
(Par
))) then
4953 Error_Msg_NE
("& is not directly visible", Par
, Entity
(Par
));
4962 -- On exit, package is not mentioned in a previous with_clause.
4963 -- Check if its prefix is.
4965 if Nkind
(Nam
) = N_Expanded_Name
then
4966 Check_In_Previous_With_Clause
(N
, Prefix
(Nam
));
4968 elsif Pack
/= Any_Id
then
4969 Error_Msg_NE
("& is not visible", Nam
, Pack
);
4971 end Check_In_Previous_With_Clause
;
4973 ---------------------------------
4974 -- Check_Library_Unit_Renaming --
4975 ---------------------------------
4977 procedure Check_Library_Unit_Renaming
(N
: Node_Id
; Old_E
: Entity_Id
) is
4981 if Nkind
(Parent
(N
)) /= N_Compilation_Unit
then
4984 -- Check for library unit. Note that we used to check for the scope
4985 -- being Standard here, but that was wrong for Standard itself.
4987 elsif not Is_Compilation_Unit
(Old_E
)
4988 and then not Is_Child_Unit
(Old_E
)
4990 Error_Msg_N
("renamed unit must be a library unit", Name
(N
));
4992 -- Entities defined in Standard (operators and boolean literals) cannot
4993 -- be renamed as library units.
4995 elsif Scope
(Old_E
) = Standard_Standard
4996 and then Sloc
(Old_E
) = Standard_Location
4998 Error_Msg_N
("renamed unit must be a library unit", Name
(N
));
5000 elsif Present
(Parent_Spec
(N
))
5001 and then Nkind
(Unit
(Parent_Spec
(N
))) = N_Generic_Package_Declaration
5002 and then not Is_Child_Unit
(Old_E
)
5005 ("renamed unit must be a child unit of generic parent", Name
(N
));
5007 elsif Nkind
(N
) in N_Generic_Renaming_Declaration
5008 and then Nkind
(Name
(N
)) = N_Expanded_Name
5009 and then Is_Generic_Instance
(Entity
(Prefix
(Name
(N
))))
5010 and then Is_Generic_Unit
(Old_E
)
5013 ("renamed generic unit must be a library unit", Name
(N
));
5015 elsif Is_Package_Or_Generic_Package
(Old_E
) then
5017 -- Inherit categorization flags
5019 New_E
:= Defining_Entity
(N
);
5020 Set_Is_Pure
(New_E
, Is_Pure
(Old_E
));
5021 Set_Is_Preelaborated
(New_E
, Is_Preelaborated
(Old_E
));
5022 Set_Is_Remote_Call_Interface
(New_E
,
5023 Is_Remote_Call_Interface
(Old_E
));
5024 Set_Is_Remote_Types
(New_E
, Is_Remote_Types
(Old_E
));
5025 Set_Is_Shared_Passive
(New_E
, Is_Shared_Passive
(Old_E
));
5027 end Check_Library_Unit_Renaming
;
5029 ------------------------
5030 -- Enclosing_Instance --
5031 ------------------------
5033 function Enclosing_Instance
return Entity_Id
is
5037 if not Is_Generic_Instance
(Current_Scope
) then
5041 S
:= Scope
(Current_Scope
);
5042 while S
/= Standard_Standard
loop
5043 if Is_Generic_Instance
(S
) then
5051 end Enclosing_Instance
;
5057 procedure End_Scope
is
5063 Id
:= First_Entity
(Current_Scope
);
5064 while Present
(Id
) loop
5065 -- An entity in the current scope is not necessarily the first one
5066 -- on its homonym chain. Find its predecessor if any,
5067 -- If it is an internal entity, it will not be in the visibility
5068 -- chain altogether, and there is nothing to unchain.
5070 if Id
/= Current_Entity
(Id
) then
5071 Prev
:= Current_Entity
(Id
);
5072 while Present
(Prev
)
5073 and then Homonym
(Prev
) /= Id
5075 Prev
:= Homonym
(Prev
);
5078 -- Skip to end of loop if Id is not in the visibility chain
5088 Set_Is_Immediately_Visible
(Id
, False);
5090 Outer
:= Homonym
(Id
);
5091 while Present
(Outer
) and then Scope
(Outer
) = Current_Scope
loop
5092 Outer
:= Homonym
(Outer
);
5095 -- Reset homonym link of other entities, but do not modify link
5096 -- between entities in current scope, so that the back-end can have
5097 -- a proper count of local overloadings.
5100 Set_Name_Entity_Id
(Chars
(Id
), Outer
);
5102 elsif Scope
(Prev
) /= Scope
(Id
) then
5103 Set_Homonym
(Prev
, Outer
);
5110 -- If the scope generated freeze actions, place them before the
5111 -- current declaration and analyze them. Type declarations and
5112 -- the bodies of initialization procedures can generate such nodes.
5113 -- We follow the parent chain until we reach a list node, which is
5114 -- the enclosing list of declarations. If the list appears within
5115 -- a protected definition, move freeze nodes outside the protected
5119 (Scope_Stack
.Table
(Scope_Stack
.Last
).Pending_Freeze_Actions
)
5123 L
: constant List_Id
:= Scope_Stack
.Table
5124 (Scope_Stack
.Last
).Pending_Freeze_Actions
;
5127 if Is_Itype
(Current_Scope
) then
5128 Decl
:= Associated_Node_For_Itype
(Current_Scope
);
5130 Decl
:= Parent
(Current_Scope
);
5135 while not Is_List_Member
(Decl
)
5136 or else Nkind
(Parent
(Decl
)) in N_Protected_Definition
5139 Decl
:= Parent
(Decl
);
5142 Insert_List_Before_And_Analyze
(Decl
, L
);
5150 ---------------------
5151 -- End_Use_Clauses --
5152 ---------------------
5154 procedure End_Use_Clauses
(Clause
: Node_Id
) is
5158 -- Remove use_type_clauses first, because they affect the visibility of
5159 -- operators in subsequent used packages.
5162 while Present
(U
) loop
5163 if Nkind
(U
) = N_Use_Type_Clause
then
5167 Next_Use_Clause
(U
);
5171 while Present
(U
) loop
5172 if Nkind
(U
) = N_Use_Package_Clause
then
5173 End_Use_Package
(U
);
5176 Next_Use_Clause
(U
);
5178 end End_Use_Clauses
;
5180 ---------------------
5181 -- End_Use_Package --
5182 ---------------------
5184 procedure End_Use_Package
(N
: Node_Id
) is
5186 Pack_Name
: Node_Id
;
5190 function Is_Primitive_Operator_In_Use
5192 F
: Entity_Id
) return Boolean;
5193 -- Check whether Op is a primitive operator of a use-visible type
5195 ----------------------------------
5196 -- Is_Primitive_Operator_In_Use --
5197 ----------------------------------
5199 function Is_Primitive_Operator_In_Use
5201 F
: Entity_Id
) return Boolean
5203 T
: constant Entity_Id
:= Base_Type
(Etype
(F
));
5205 return In_Use
(T
) and then Scope
(T
) = Scope
(Op
);
5206 end Is_Primitive_Operator_In_Use
;
5208 -- Start of processing for End_Use_Package
5211 Pack_Name
:= Name
(N
);
5213 -- Test that Pack_Name actually denotes a package before processing
5215 if Is_Entity_Name
(Pack_Name
)
5216 and then Ekind
(Entity
(Pack_Name
)) = E_Package
5218 Pack
:= Entity
(Pack_Name
);
5220 if In_Open_Scopes
(Pack
) then
5223 elsif not Redundant_Use
(Pack_Name
) then
5224 Set_In_Use
(Pack
, False);
5225 Set_Current_Use_Clause
(Pack
, Empty
);
5227 Id
:= First_Entity
(Pack
);
5228 while Present
(Id
) loop
5230 -- Preserve use-visibility of operators that are primitive
5231 -- operators of a type that is use-visible through an active
5234 if Nkind
(Id
) = N_Defining_Operator_Symbol
5236 (Is_Primitive_Operator_In_Use
(Id
, First_Formal
(Id
))
5238 (Present
(Next_Formal
(First_Formal
(Id
)))
5240 Is_Primitive_Operator_In_Use
5241 (Id
, Next_Formal
(First_Formal
(Id
)))))
5245 Set_Is_Potentially_Use_Visible
(Id
, False);
5248 if Is_Private_Type
(Id
)
5249 and then Present
(Full_View
(Id
))
5251 Set_Is_Potentially_Use_Visible
(Full_View
(Id
), False);
5257 if Present
(Renamed_Entity
(Pack
)) then
5258 Set_In_Use
(Renamed_Entity
(Pack
), False);
5259 Set_Current_Use_Clause
(Renamed_Entity
(Pack
), Empty
);
5262 if Chars
(Pack
) = Name_System
5263 and then Scope
(Pack
) = Standard_Standard
5264 and then Present_System_Aux
5266 Id
:= First_Entity
(System_Aux_Id
);
5267 while Present
(Id
) loop
5268 Set_Is_Potentially_Use_Visible
(Id
, False);
5270 if Is_Private_Type
(Id
)
5271 and then Present
(Full_View
(Id
))
5273 Set_Is_Potentially_Use_Visible
(Full_View
(Id
), False);
5279 Set_In_Use
(System_Aux_Id
, False);
5282 Set_Redundant_Use
(Pack_Name
, False);
5286 if Present
(Hidden_By_Use_Clause
(N
)) then
5287 Elmt
:= First_Elmt
(Hidden_By_Use_Clause
(N
));
5288 while Present
(Elmt
) loop
5290 E
: constant Entity_Id
:= Node
(Elmt
);
5293 -- Reset either Use_Visibility or Direct_Visibility, depending
5294 -- on how the entity was hidden by the use clause.
5296 if In_Use
(Scope
(E
))
5297 and then Used_As_Generic_Actual
(Scope
(E
))
5299 Set_Is_Potentially_Use_Visible
(Node
(Elmt
));
5301 Set_Is_Immediately_Visible
(Node
(Elmt
));
5308 Set_Hidden_By_Use_Clause
(N
, No_Elist
);
5310 end End_Use_Package
;
5316 procedure End_Use_Type
(N
: Node_Id
) is
5321 -- Start of processing for End_Use_Type
5324 Id
:= Subtype_Mark
(N
);
5326 -- A call to Rtsfind may occur while analyzing a use_type_clause, in
5327 -- which case the type marks are not resolved yet, so guard against that
5330 if Is_Entity_Name
(Id
) and then Present
(Entity
(Id
)) then
5333 if T
= Any_Type
or else From_Limited_With
(T
) then
5336 -- Note that the use_type_clause may mention a subtype of the type
5337 -- whose primitive operations have been made visible. Here as
5338 -- elsewhere, it is the base type that matters for visibility.
5340 elsif In_Open_Scopes
(Scope
(Base_Type
(T
))) then
5343 elsif not Redundant_Use
(Id
) then
5344 Set_In_Use
(T
, False);
5345 Set_In_Use
(Base_Type
(T
), False);
5346 Set_Current_Use_Clause
(T
, Empty
);
5347 Set_Current_Use_Clause
(Base_Type
(T
), Empty
);
5349 -- See Use_One_Type for the rationale. This is a bit on the naive
5350 -- side, but should be good enough in practice.
5352 if Is_Tagged_Type
(T
) then
5353 Set_In_Use
(Class_Wide_Type
(T
), False);
5358 if Is_Empty_Elmt_List
(Used_Operations
(N
)) then
5362 Elmt
:= First_Elmt
(Used_Operations
(N
));
5363 while Present
(Elmt
) loop
5364 Set_Is_Potentially_Use_Visible
(Node
(Elmt
), False);
5370 --------------------
5371 -- Entity_Of_Unit --
5372 --------------------
5374 function Entity_Of_Unit
(U
: Node_Id
) return Entity_Id
is
5376 if Nkind
(U
) = N_Package_Instantiation
and then Analyzed
(U
) then
5377 return Defining_Entity
(Instance_Spec
(U
));
5379 return Defining_Entity
(U
);
5383 --------------------------------------
5384 -- Error_Missing_With_Of_Known_Unit --
5385 --------------------------------------
5387 procedure Error_Missing_With_Of_Known_Unit
(Pkg
: Node_Id
) is
5388 Selectors
: array (1 .. 6) of Node_Id
;
5389 -- Contains the chars of the full package name up to maximum number
5390 -- allowed as per Errout.Error_Msg_Name_# variables.
5392 Count
: Integer := Selectors
'First;
5393 -- Count of selector names forming the full package name
5395 Current_Pkg
: Node_Id
:= Parent
(Pkg
);
5398 Selectors
(Count
) := Pkg
;
5400 -- Gather all the selectors we can display
5402 while Nkind
(Current_Pkg
) = N_Selected_Component
5403 and then Is_Known_Unit
(Current_Pkg
)
5404 and then Count
< Selectors
'Length
5407 Selectors
(Count
) := Selector_Name
(Current_Pkg
);
5408 Current_Pkg
:= Parent
(Current_Pkg
);
5411 -- Display the error message based on the number of selectors found
5415 Error_Msg_Node_1
:= Selectors
(1);
5416 Error_Msg_N
-- CODEFIX
5417 ("\\missing `WITH &;`", Pkg
);
5419 Error_Msg_Node_1
:= Selectors
(1);
5420 Error_Msg_Node_2
:= Selectors
(2);
5421 Error_Msg_N
-- CODEFIX
5422 ("\\missing `WITH &.&;`", Pkg
);
5424 Error_Msg_Node_1
:= Selectors
(1);
5425 Error_Msg_Node_2
:= Selectors
(2);
5426 Error_Msg_Node_3
:= Selectors
(3);
5427 Error_Msg_N
-- CODEFIX
5428 ("\\missing `WITH &.&.&;`", Pkg
);
5430 Error_Msg_Node_1
:= Selectors
(1);
5431 Error_Msg_Node_2
:= Selectors
(2);
5432 Error_Msg_Node_3
:= Selectors
(3);
5433 Error_Msg_Node_3
:= Selectors
(4);
5434 Error_Msg_N
-- CODEFIX
5435 ("\\missing `WITH &.&.&.&;`", Pkg
);
5437 Error_Msg_Node_1
:= Selectors
(1);
5438 Error_Msg_Node_2
:= Selectors
(2);
5439 Error_Msg_Node_3
:= Selectors
(3);
5440 Error_Msg_Node_3
:= Selectors
(4);
5441 Error_Msg_Node_3
:= Selectors
(5);
5442 Error_Msg_N
-- CODEFIX
5443 ("\\missing `WITH &.&.&.&.&;`", Pkg
);
5445 Error_Msg_Node_1
:= Selectors
(1);
5446 Error_Msg_Node_2
:= Selectors
(2);
5447 Error_Msg_Node_3
:= Selectors
(3);
5448 Error_Msg_Node_4
:= Selectors
(4);
5449 Error_Msg_Node_5
:= Selectors
(5);
5450 Error_Msg_Node_6
:= Selectors
(6);
5451 Error_Msg_N
-- CODEFIX
5452 ("\\missing `WITH &.&.&.&.&.&;`", Pkg
);
5454 raise Program_Error
;
5456 end Error_Missing_With_Of_Known_Unit
;
5458 --------------------
5459 -- Is_Self_Hidden --
5460 --------------------
5462 function Is_Self_Hidden
(E
: Entity_Id
) return Boolean is
5464 if Is_Not_Self_Hidden
(E
) then
5465 return Ekind
(E
) = E_Void
;
5471 ----------------------
5472 -- Find_Direct_Name --
5473 ----------------------
5475 procedure Find_Direct_Name
(N
: Node_Id
) is
5480 Homonyms
: Entity_Id
;
5481 -- Saves start of homonym chain
5483 Inst
: Entity_Id
:= Empty
;
5484 -- Enclosing instance, if any
5486 Nvis_Entity
: Boolean;
5487 -- Set True to indicate that there is at least one entity on the homonym
5488 -- chain which, while not visible, is visible enough from the user point
5489 -- of view to warrant an error message of "not visible" rather than
5492 Nvis_Is_Private_Subprg
: Boolean := False;
5493 -- Ada 2005 (AI-262): Set True to indicate that a form of Beaujolais
5494 -- effect concerning library subprograms has been detected. Used to
5495 -- generate the precise error message.
5497 function From_Actual_Package
(E
: Entity_Id
) return Boolean;
5498 -- Returns true if the entity is an actual for a package that is itself
5499 -- an actual for a formal package of the current instance. Such an
5500 -- entity requires special handling because it may be use-visible but
5501 -- hides directly visible entities defined outside the instance, because
5502 -- the corresponding formal did so in the generic.
5504 function Is_Actual_Parameter
return Boolean;
5505 -- This function checks if the node N is an identifier that is an actual
5506 -- parameter of a procedure call. If so it returns True, otherwise it
5507 -- return False. The reason for this check is that at this stage we do
5508 -- not know what procedure is being called if the procedure might be
5509 -- overloaded, so it is premature to go setting referenced flags or
5510 -- making calls to Generate_Reference. We will wait till Resolve_Actuals
5511 -- for that processing.
5512 -- Note: there is a similar routine Sem_Util.Is_Actual_Parameter, but
5513 -- it works for both function and procedure calls, while here we are
5514 -- only concerned with procedure calls (and with entry calls as well,
5515 -- but they are parsed as procedure calls and only later rewritten to
5518 function Known_But_Invisible
(E
: Entity_Id
) return Boolean;
5519 -- This function determines whether a reference to the entity E, which
5520 -- is not visible, can reasonably be considered to be known to the
5521 -- writer of the reference. This is a heuristic test, used only for
5522 -- the purposes of figuring out whether we prefer to complain that an
5523 -- entity is undefined or invisible (and identify the declaration of
5524 -- the invisible entity in the latter case). The point here is that we
5525 -- don't want to complain that something is invisible and then point to
5526 -- something entirely mysterious to the writer.
5528 procedure Nvis_Messages
;
5529 -- Called if there are no visible entries for N, but there is at least
5530 -- one non-directly visible, or hidden declaration. This procedure
5531 -- outputs an appropriate set of error messages.
5533 procedure Undefined
(Nvis
: Boolean);
5534 -- This function is called if the current node has no corresponding
5535 -- visible entity or entities. The value set in Msg indicates whether
5536 -- an error message was generated (multiple error messages for the
5537 -- same variable are generally suppressed, see body for details).
5538 -- Msg is True if an error message was generated, False if not. This
5539 -- value is used by the caller to determine whether or not to output
5540 -- additional messages where appropriate. The parameter is set False
5541 -- to get the message "X is undefined", and True to get the message
5542 -- "X is not visible".
5544 -------------------------
5545 -- From_Actual_Package --
5546 -------------------------
5548 function From_Actual_Package
(E
: Entity_Id
) return Boolean is
5549 Scop
: constant Entity_Id
:= Scope
(E
);
5550 -- Declared scope of candidate entity
5552 function Declared_In_Actual
(Pack
: Entity_Id
) return Boolean;
5553 -- Recursive function that does the work and examines actuals of
5554 -- actual packages of current instance.
5556 ------------------------
5557 -- Declared_In_Actual --
5558 ------------------------
5560 function Declared_In_Actual
(Pack
: Entity_Id
) return Boolean is
5561 pragma Assert
(Ekind
(Pack
) = E_Package
);
5564 if No
(Associated_Formal_Package
(Pack
)) then
5568 Act
:= First_Entity
(Pack
);
5569 while Present
(Act
) loop
5570 if Renamed_Entity
(Pack
) = Scop
then
5573 -- Check for end of list of actuals
5575 elsif Ekind
(Act
) = E_Package
5576 and then Renamed_Entity
(Act
) = Pack
5580 elsif Ekind
(Act
) = E_Package
5581 and then Declared_In_Actual
(Act
)
5591 end Declared_In_Actual
;
5597 -- Start of processing for From_Actual_Package
5600 if not In_Instance
then
5604 Inst
:= Current_Scope
;
5605 while Present
(Inst
)
5606 and then Ekind
(Inst
) /= E_Package
5607 and then not Is_Generic_Instance
(Inst
)
5609 Inst
:= Scope
(Inst
);
5616 Act
:= First_Entity
(Inst
);
5617 while Present
(Act
) loop
5618 if Ekind
(Act
) = E_Package
5619 and then Declared_In_Actual
(Act
)
5629 end From_Actual_Package
;
5631 -------------------------
5632 -- Is_Actual_Parameter --
5633 -------------------------
5635 function Is_Actual_Parameter
return Boolean is
5637 if Nkind
(N
) = N_Identifier
then
5638 case Nkind
(Parent
(N
)) is
5639 when N_Procedure_Call_Statement
=>
5640 return Is_List_Member
(N
)
5641 and then List_Containing
(N
) =
5642 Parameter_Associations
(Parent
(N
));
5644 when N_Parameter_Association
=>
5645 return N
= Explicit_Actual_Parameter
(Parent
(N
))
5646 and then Nkind
(Parent
(Parent
(N
))) =
5647 N_Procedure_Call_Statement
;
5655 end Is_Actual_Parameter
;
5657 -------------------------
5658 -- Known_But_Invisible --
5659 -------------------------
5661 function Known_But_Invisible
(E
: Entity_Id
) return Boolean is
5662 Fname
: File_Name_Type
;
5665 -- Entities in Standard are always considered to be known
5667 if Sloc
(E
) <= Standard_Location
then
5670 -- An entity that does not come from source is always considered
5671 -- to be unknown, since it is an artifact of code expansion.
5673 elsif not Comes_From_Source
(E
) then
5677 -- Here we have an entity that is not from package Standard, and
5678 -- which comes from Source. See if it comes from an internal file.
5680 Fname
:= Unit_File_Name
(Get_Source_Unit
(E
));
5682 -- Case of from internal file
5684 if In_Internal_Unit
(E
) then
5686 -- Private part entities in internal files are never considered
5687 -- to be known to the writer of normal application code.
5689 if Is_Hidden
(E
) then
5693 -- Entities from System packages other than System and
5694 -- System.Storage_Elements are not considered to be known.
5695 -- System.Auxxxx files are also considered known to the user.
5697 -- Should refine this at some point to generally distinguish
5698 -- between known and unknown internal files ???
5700 Get_Name_String
(Fname
);
5705 Name_Buffer
(1 .. 2) /= "s-"
5707 Name_Buffer
(3 .. 8) = "stoele"
5709 Name_Buffer
(3 .. 5) = "aux";
5711 -- If not an internal file, then entity is definitely known, even if
5712 -- it is in a private part (the message generated will note that it
5713 -- is in a private part).
5718 end Known_But_Invisible
;
5724 procedure Nvis_Messages
is
5725 Comp_Unit
: Node_Id
;
5727 Found
: Boolean := False;
5728 Hidden
: Boolean := False;
5732 -- Ada 2005 (AI-262): Generate a precise error concerning the
5733 -- Beaujolais effect that was previously detected
5735 if Nvis_Is_Private_Subprg
then
5737 pragma Assert
(Nkind
(E2
) = N_Defining_Identifier
5738 and then Ekind
(E2
) = E_Function
5739 and then Scope
(E2
) = Standard_Standard
5740 and then Has_Private_With
(E2
));
5742 -- Find the sloc corresponding to the private with'ed unit
5744 Comp_Unit
:= Cunit
(Current_Sem_Unit
);
5745 Error_Msg_Sloc
:= No_Location
;
5747 Item
:= First
(Context_Items
(Comp_Unit
));
5748 while Present
(Item
) loop
5749 if Nkind
(Item
) = N_With_Clause
5750 and then Private_Present
(Item
)
5751 and then Entity
(Name
(Item
)) = E2
5753 Error_Msg_Sloc
:= Sloc
(Item
);
5760 pragma Assert
(Error_Msg_Sloc
/= No_Location
);
5762 Error_Msg_N
("(Ada 2005): hidden by private with clause #", N
);
5766 Undefined
(Nvis
=> True);
5770 -- First loop does hidden declarations
5773 while Present
(Ent
) loop
5774 if Is_Potentially_Use_Visible
(Ent
) then
5776 Error_Msg_N
-- CODEFIX
5777 ("multiple use clauses cause hiding!", N
);
5781 Error_Msg_Sloc
:= Sloc
(Ent
);
5782 Error_Msg_N
-- CODEFIX
5783 ("hidden declaration#!", N
);
5786 Ent
:= Homonym
(Ent
);
5789 -- If we found hidden declarations, then that's enough, don't
5790 -- bother looking for non-visible declarations as well.
5796 -- Second loop does non-directly visible declarations
5799 while Present
(Ent
) loop
5800 if not Is_Potentially_Use_Visible
(Ent
) then
5802 -- Do not bother the user with unknown entities
5804 if not Known_But_Invisible
(Ent
) then
5808 Error_Msg_Sloc
:= Sloc
(Ent
);
5810 -- Output message noting that there is a non-visible
5811 -- declaration, distinguishing the private part case.
5813 if Is_Hidden
(Ent
) then
5814 Error_Msg_N
("non-visible (private) declaration#!", N
);
5816 -- If the entity is declared in a generic package, it
5817 -- cannot be visible, so there is no point in adding it
5818 -- to the list of candidates if another homograph from a
5819 -- non-generic package has been seen.
5821 elsif Ekind
(Scope
(Ent
)) = E_Generic_Package
5827 -- When the entity comes from a generic instance the
5828 -- normal error message machinery will give the line
5829 -- number of the generic package and the location of
5830 -- the generic instance, but not the name of the
5833 -- So, in order to give more descriptive error messages
5834 -- in this case, we include the name of the generic
5837 if Is_Generic_Instance
(Scope
(Ent
)) then
5838 Error_Msg_Name_1
:= Chars
(Scope
(Ent
));
5839 Error_Msg_N
-- CODEFIX
5840 ("non-visible declaration from %#!", N
);
5842 -- Otherwise print the message normally
5845 Error_Msg_N
-- CODEFIX
5846 ("non-visible declaration#!", N
);
5849 if Ekind
(Scope
(Ent
)) /= E_Generic_Package
then
5853 if Is_Compilation_Unit
(Ent
)
5855 Nkind
(Parent
(Parent
(N
))) = N_Use_Package_Clause
5857 Error_Msg_Qual_Level
:= 99;
5858 Error_Msg_NE
-- CODEFIX
5859 ("\\missing `WITH &;`", N
, Ent
);
5860 Error_Msg_Qual_Level
:= 0;
5863 if Ekind
(Ent
) = E_Discriminant
5864 and then Present
(Corresponding_Discriminant
(Ent
))
5865 and then Scope
(Corresponding_Discriminant
(Ent
)) =
5869 ("inherited discriminant not allowed here" &
5870 " (RM 3.8 (12), 3.8.1 (6))!", N
);
5874 -- Set entity and its containing package as referenced. We
5875 -- can't be sure of this, but this seems a better choice
5876 -- to avoid unused entity messages.
5878 if Comes_From_Source
(Ent
) then
5879 Set_Referenced
(Ent
);
5880 Set_Referenced
(Cunit_Entity
(Get_Source_Unit
(Ent
)));
5885 Ent
:= Homonym
(Ent
);
5894 procedure Undefined
(Nvis
: Boolean) is
5895 Emsg
: Error_Msg_Id
;
5898 -- We should never find an undefined internal name. If we do, then
5899 -- see if we have previous errors. If so, ignore on the grounds that
5900 -- it is probably a cascaded message (e.g. a block label from a badly
5901 -- formed block). If no previous errors, then we have a real internal
5902 -- error of some kind so raise an exception.
5904 if Is_Internal_Name
(Chars
(N
)) then
5905 if Total_Errors_Detected
/= 0 then
5908 raise Program_Error
;
5912 -- A very specialized error check, if the undefined variable is
5913 -- a case tag, and the case type is an enumeration type, check
5914 -- for a possible misspelling, and if so, modify the identifier
5916 -- Named aggregate should also be handled similarly ???
5918 if Nkind
(N
) = N_Identifier
5919 and then Nkind
(Parent
(N
)) = N_Case_Statement_Alternative
5922 Case_Stm
: constant Node_Id
:= Parent
(Parent
(N
));
5923 Case_Typ
: constant Entity_Id
:= Etype
(Expression
(Case_Stm
));
5928 if Is_Enumeration_Type
(Case_Typ
)
5929 and then not Is_Standard_Character_Type
(Case_Typ
)
5931 Lit
:= First_Literal
(Case_Typ
);
5932 Get_Name_String
(Chars
(Lit
));
5934 if Chars
(Lit
) /= Chars
(N
)
5935 and then Is_Bad_Spelling_Of
(Chars
(N
), Chars
(Lit
))
5937 Error_Msg_Node_2
:= Lit
;
5938 Error_Msg_N
-- CODEFIX
5939 ("& is undefined, assume misspelling of &", N
);
5940 Rewrite
(N
, New_Occurrence_Of
(Lit
, Sloc
(N
)));
5949 -- Normal processing
5951 Set_Entity
(N
, Any_Id
);
5952 Set_Etype
(N
, Any_Type
);
5954 -- We use the table Urefs to keep track of entities for which we
5955 -- have issued errors for undefined references. Multiple errors
5956 -- for a single name are normally suppressed, however we modify
5957 -- the error message to alert the programmer to this effect.
5959 for J
in Urefs
.First
.. Urefs
.Last
loop
5960 if Chars
(N
) = Chars
(Urefs
.Table
(J
).Node
) then
5961 if Urefs
.Table
(J
).Err
/= No_Error_Msg
5962 and then Sloc
(N
) /= Urefs
.Table
(J
).Loc
5964 Error_Msg_Node_1
:= Urefs
.Table
(J
).Node
;
5966 if Urefs
.Table
(J
).Nvis
then
5967 Change_Error_Text
(Urefs
.Table
(J
).Err
,
5968 "& is not visible (more references follow)");
5970 Change_Error_Text
(Urefs
.Table
(J
).Err
,
5971 "& is undefined (more references follow)");
5974 Urefs
.Table
(J
).Err
:= No_Error_Msg
;
5977 -- Although we will set Msg False, and thus suppress the
5978 -- message, we also set Error_Posted True, to avoid any
5979 -- cascaded messages resulting from the undefined reference.
5982 Set_Error_Posted
(N
);
5987 -- If entry not found, this is first undefined occurrence
5990 Error_Msg_N
("& is not visible!", N
);
5994 Error_Msg_N
("& is undefined!", N
);
5997 -- A very bizarre special check, if the undefined identifier
5998 -- is Put or Put_Line, then add a special error message (since
5999 -- this is a very common error for beginners to make).
6001 if Chars
(N
) in Name_Put | Name_Put_Line
then
6002 Error_Msg_N
-- CODEFIX
6003 ("\\possible missing `WITH Ada.Text_'I'O; " &
6004 "USE Ada.Text_'I'O`!", N
);
6006 -- Another special check if N is the prefix of a selected
6007 -- component which is a known unit: add message complaining
6008 -- about missing with for this unit.
6010 elsif Nkind
(Parent
(N
)) = N_Selected_Component
6011 and then N
= Prefix
(Parent
(N
))
6012 and then Is_Known_Unit
(Parent
(N
))
6014 Error_Missing_With_Of_Known_Unit
(N
);
6017 -- Now check for possible misspellings
6021 Ematch
: Entity_Id
:= Empty
;
6023 for Nam
in First_Name_Id
.. Last_Name_Id
loop
6024 E
:= Get_Name_Entity_Id
(Nam
);
6027 and then (Is_Immediately_Visible
(E
)
6029 Is_Potentially_Use_Visible
(E
))
6031 if Is_Bad_Spelling_Of
(Chars
(N
), Nam
) then
6038 if Present
(Ematch
) then
6039 Error_Msg_NE
-- CODEFIX
6040 ("\possible misspelling of&", N
, Ematch
);
6045 -- Make entry in undefined references table unless the full errors
6046 -- switch is set, in which case by refraining from generating the
6047 -- table entry we guarantee that we get an error message for every
6048 -- undefined reference. The entry is not added if we are ignoring
6051 if not All_Errors_Mode
6052 and then Ignore_Errors_Enable
= 0
6053 and then not Get_Ignore_Errors
6067 Nested_Inst
: Entity_Id
:= Empty
;
6068 -- The entity of a nested instance which appears within Inst (if any)
6070 -- Start of processing for Find_Direct_Name
6073 -- If the entity pointer is already set, this is an internal node, or
6074 -- a node that is analyzed more than once, after a tree modification.
6075 -- In such a case there is no resolution to perform, just set the type.
6077 if Present
(Entity
(N
)) then
6078 if Is_Type
(Entity
(N
)) then
6079 Set_Etype
(N
, Entity
(N
));
6083 Entyp
: constant Entity_Id
:= Etype
(Entity
(N
));
6086 -- One special case here. If the Etype field is already set,
6087 -- and references the packed array type corresponding to the
6088 -- etype of the referenced entity, then leave it alone. This
6089 -- happens for trees generated from Exp_Pakd, where expressions
6090 -- can be deliberately "mis-typed" to the packed array type.
6092 if Is_Packed_Array
(Entyp
)
6093 and then Present
(Etype
(N
))
6094 and then Etype
(N
) = Packed_Array_Impl_Type
(Entyp
)
6098 -- If not that special case, then just reset the Etype
6101 Set_Etype
(N
, Entyp
);
6106 -- Although the marking of use clauses happens at the end of
6107 -- Find_Direct_Name, a certain case where a generic actual satisfies
6108 -- a use clause must be checked here due to how the generic machinery
6109 -- handles the analysis of said actuals.
6112 and then Nkind
(Parent
(N
)) = N_Generic_Association
6114 Mark_Use_Clauses
(Entity
(N
));
6120 -- Preserve relevant elaboration-related attributes of the context which
6121 -- are no longer available or very expensive to recompute once analysis,
6122 -- resolution, and expansion are over.
6124 if Nkind
(N
) = N_Identifier
then
6125 Mark_Elaboration_Attributes
6132 -- Here if Entity pointer was not set, we need full visibility analysis
6133 -- First we generate debugging output if the debug E flag is set.
6135 if Debug_Flag_E
then
6136 Write_Str
("Looking for ");
6137 Write_Name
(Chars
(N
));
6141 Homonyms
:= Current_Entity
(N
);
6142 Nvis_Entity
:= False;
6145 while Present
(E
) loop
6147 -- If entity is immediately visible or potentially use visible, then
6148 -- process the entity and we are done.
6150 if Is_Immediately_Visible
(E
) then
6151 goto Immediately_Visible_Entity
;
6153 elsif Is_Potentially_Use_Visible
(E
) then
6154 goto Potentially_Use_Visible_Entity
;
6156 -- Note if a known but invisible entity encountered
6158 elsif Known_But_Invisible
(E
) then
6159 Nvis_Entity
:= True;
6162 -- Move to next entity in chain and continue search
6167 -- If no entries on homonym chain that were potentially visible,
6168 -- and no entities reasonably considered as non-visible, then
6169 -- we have a plain undefined reference, with no additional
6170 -- explanation required.
6172 if not Nvis_Entity
then
6173 Undefined
(Nvis
=> False);
6175 -- Otherwise there is at least one entry on the homonym chain that
6176 -- is reasonably considered as being known and non-visible.
6184 -- Processing for a potentially use visible entry found. We must search
6185 -- the rest of the homonym chain for two reasons. First, if there is a
6186 -- directly visible entry, then none of the potentially use-visible
6187 -- entities are directly visible (RM 8.4(10)). Second, we need to check
6188 -- for the case of multiple potentially use-visible entries hiding one
6189 -- another and as a result being non-directly visible (RM 8.4(11)).
6191 <<Potentially_Use_Visible_Entity
>> declare
6192 Only_One_Visible
: Boolean := True;
6193 All_Overloadable
: Boolean := Is_Overloadable
(E
);
6197 while Present
(E2
) loop
6198 if Is_Immediately_Visible
(E2
) then
6200 -- If the use-visible entity comes from the actual for a
6201 -- formal package, it hides a directly visible entity from
6202 -- outside the instance.
6204 if From_Actual_Package
(E
)
6205 and then Scope_Depth
(Scope
(E2
)) < Scope_Depth
(Inst
)
6210 goto Immediately_Visible_Entity
;
6213 elsif Is_Potentially_Use_Visible
(E2
) then
6214 Only_One_Visible
:= False;
6215 All_Overloadable
:= All_Overloadable
and Is_Overloadable
(E2
);
6217 -- Ada 2005 (AI-262): Protect against a form of Beaujolais effect
6218 -- that can occur in private_with clauses. Example:
6221 -- private with B; package A is
6222 -- package C is function B return Integer;
6224 -- V1 : Integer := B;
6225 -- private function B return Integer;
6226 -- V2 : Integer := B;
6229 -- V1 resolves to A.B, but V2 resolves to library unit B
6231 elsif Ekind
(E2
) = E_Function
6232 and then Scope
(E2
) = Standard_Standard
6233 and then Has_Private_With
(E2
)
6235 Only_One_Visible
:= False;
6236 All_Overloadable
:= False;
6237 Nvis_Is_Private_Subprg
:= True;
6244 -- On falling through this loop, we have checked that there are no
6245 -- immediately visible entities. Only_One_Visible is set if exactly
6246 -- one potentially use visible entity exists. All_Overloadable is
6247 -- set if all the potentially use visible entities are overloadable.
6248 -- The condition for legality is that either there is one potentially
6249 -- use visible entity, or if there is more than one, then all of them
6250 -- are overloadable.
6252 if Only_One_Visible
or All_Overloadable
then
6255 -- If there is more than one potentially use-visible entity and at
6256 -- least one of them non-overloadable, we have an error (RM 8.4(11)).
6257 -- Note that E points to the first such entity on the homonym list.
6260 -- If one of the entities is declared in an actual package, it
6261 -- was visible in the generic, and takes precedence over other
6262 -- entities that are potentially use-visible. The same applies
6263 -- if the entity is declared in a local instantiation of the
6264 -- current instance.
6268 -- Find the current instance
6270 Inst
:= Current_Scope
;
6271 while Present
(Inst
) and then Inst
/= Standard_Standard
loop
6272 if Is_Generic_Instance
(Inst
) then
6276 Inst
:= Scope
(Inst
);
6279 -- Reexamine the candidate entities, giving priority to those
6280 -- that were visible within the generic.
6283 while Present
(E2
) loop
6284 Nested_Inst
:= Nearest_Enclosing_Instance
(E2
);
6286 -- The entity is declared within an actual package, or in a
6287 -- nested instance. The ">=" accounts for the case where the
6288 -- current instance and the nested instance are the same.
6290 if From_Actual_Package
(E2
)
6291 or else (Present
(Nested_Inst
)
6292 and then Scope_Depth
(Nested_Inst
) >=
6305 elsif Is_Predefined_Unit
(Current_Sem_Unit
) then
6306 -- A use clause in the body of a system file creates conflict
6307 -- with some entity in a user scope, while rtsfind is active.
6308 -- Keep only the entity coming from another predefined unit.
6311 while Present
(E2
) loop
6312 if In_Predefined_Unit
(E2
) then
6320 -- Entity must exist because predefined unit is correct
6322 raise Program_Error
;
6331 -- Come here with E set to the first immediately visible entity on
6332 -- the homonym chain. This is the one we want unless there is another
6333 -- immediately visible entity further on in the chain for an inner
6334 -- scope (RM 8.3(8)).
6336 <<Immediately_Visible_Entity
>> declare
6341 -- Find scope level of initial entity. When compiling through
6342 -- Rtsfind, the previous context is not completely invisible, and
6343 -- an outer entity may appear on the chain, whose scope is below
6344 -- the entry for Standard that delimits the current scope stack.
6345 -- Indicate that the level for this spurious entry is outside of
6346 -- the current scope stack.
6348 Level
:= Scope_Stack
.Last
;
6350 Scop
:= Scope_Stack
.Table
(Level
).Entity
;
6351 exit when Scop
= Scope
(E
);
6353 exit when Scop
= Standard_Standard
;
6356 -- Now search remainder of homonym chain for more inner entry
6357 -- If the entity is Standard itself, it has no scope, and we
6358 -- compare it with the stack entry directly.
6361 while Present
(E2
) loop
6362 if Is_Immediately_Visible
(E2
) then
6364 -- If a generic package contains a local declaration that
6365 -- has the same name as the generic, there may be a visibility
6366 -- conflict in an instance, where the local declaration must
6367 -- also hide the name of the corresponding package renaming.
6368 -- We check explicitly for a package declared by a renaming,
6369 -- whose renamed entity is an instance that is on the scope
6370 -- stack, and that contains a homonym in the same scope. Once
6371 -- we have found it, we know that the package renaming is not
6372 -- immediately visible, and that the identifier denotes the
6373 -- other entity (and its homonyms if overloaded).
6375 if Scope
(E
) = Scope
(E2
)
6376 and then Ekind
(E
) = E_Package
6377 and then Present
(Renamed_Entity
(E
))
6378 and then Is_Generic_Instance
(Renamed_Entity
(E
))
6379 and then In_Open_Scopes
(Renamed_Entity
(E
))
6380 and then Comes_From_Source
(N
)
6382 Set_Is_Immediately_Visible
(E
, False);
6386 for J
in Level
+ 1 .. Scope_Stack
.Last
loop
6387 if Scope_Stack
.Table
(J
).Entity
= Scope
(E2
)
6388 or else Scope_Stack
.Table
(J
).Entity
= E2
6401 -- At the end of that loop, E is the innermost immediately
6402 -- visible entity, so we are all set.
6405 -- Come here with entity found, and stored in E
6409 -- Check violation of No_Wide_Characters restriction
6411 Check_Wide_Character_Restriction
(E
, N
);
6413 -- When distribution features are available (Get_PCS_Name /=
6414 -- Name_No_DSA), a remote access-to-subprogram type is converted
6415 -- into a record type holding whatever information is needed to
6416 -- perform a remote call on an RCI subprogram. In that case we
6417 -- rewrite any occurrence of the RAS type into the equivalent record
6418 -- type here. 'Access attribute references and RAS dereferences are
6419 -- then implemented using specific TSSs. However when distribution is
6420 -- not available (case of Get_PCS_Name = Name_No_DSA), we bypass the
6421 -- generation of these TSSs, and we must keep the RAS type in its
6422 -- original access-to-subprogram form (since all calls through a
6423 -- value of such type will be local anyway in the absence of a PCS).
6425 if Comes_From_Source
(N
)
6426 and then Is_Remote_Access_To_Subprogram_Type
(E
)
6427 and then Ekind
(E
) = E_Access_Subprogram_Type
6428 and then Expander_Active
6429 and then Get_PCS_Name
/= Name_No_DSA
6431 Rewrite
(N
, New_Occurrence_Of
(Equivalent_Type
(E
), Sloc
(N
)));
6435 -- Set the entity. Note that the reason we call Set_Entity for the
6436 -- overloadable case, as opposed to Set_Entity_With_Checks is
6437 -- that in the overloaded case, the initial call can set the wrong
6438 -- homonym. The call that sets the right homonym is in Sem_Res and
6439 -- that call does use Set_Entity_With_Checks, so we don't miss
6442 if Is_Overloadable
(E
) then
6445 Set_Entity_With_Checks
(N
, E
);
6451 Set_Etype
(N
, Get_Full_View
(Etype
(E
)));
6454 if Debug_Flag_E
then
6455 Write_Str
(" found ");
6456 Write_Entity_Info
(E
, " ");
6459 if Is_Self_Hidden
(E
)
6461 (not Is_Record_Type
(Current_Scope
)
6462 or else Nkind
(Parent
(N
)) /= N_Pragma_Argument_Association
)
6464 Premature_Usage
(N
);
6466 -- If the entity is overloadable, collect all interpretations of the
6467 -- name for subsequent overload resolution. We optimize a bit here to
6468 -- do this only if we have an overloadable entity that is not on its
6469 -- own on the homonym chain.
6471 elsif Is_Overloadable
(E
)
6472 and then (Present
(Homonym
(E
)) or else Current_Entity
(N
) /= E
)
6474 Collect_Interps
(N
);
6476 -- Background: for an instance of a generic, expansion sets
6477 -- entity fields on names that refer to things declared
6478 -- outside of the instance, but leaves the entity field
6479 -- unset on names that should end up referring to things
6480 -- declared within the instance. These will instead be set by
6481 -- analysis - the idea is that if a name resolves a certain
6482 -- way in the generic, then we should get corresponding results
6483 -- if we resolve the corresponding name in an instance. For this
6484 -- to work, we have to prevent unrelated declarations that
6485 -- happen to be visible at the point of the instantiation from
6486 -- participating in resolution and causing problems (typically
6487 -- ambiguities, but incorrect resolutions are also probably
6488 -- possible). So here we filter out such unwanted interpretations.
6490 -- Note that there are other problems with this approach to
6491 -- implementing generic instances that are not addressed here.
6492 -- Inside a generic, we might have no trouble resolving a call
6493 -- where the two candidates are a function that returns a
6494 -- formal type and a function that returns Standard.Integer.
6495 -- If we instantiate that generic and the corresponding actual
6496 -- type is Standard.Integer, then we may incorrectly reject the
6497 -- corresponding call in the instance as ambiguous (or worse,
6498 -- we may quietly choose the wrong resolution).
6500 -- Another such problem can occur with a type derived from a
6501 -- formal derived type. In an instance, such a type may have
6502 -- inherited subprograms that are not present in the generic.
6503 -- These can then interfere with name resolution (e.g., if
6504 -- some declaration is visible via a use-clause in the generic
6505 -- and some name in the generic refers to it, then the
6506 -- corresponding declaration in an instance may be hidden by
6507 -- a directly visible inherited subprogram and the corresponding
6508 -- name in the instance may then incorrectly refer to the
6509 -- inherited subprogram).
6513 function Is_Actual_Subp_Of_Inst
6514 (E
: Entity_Id
; Inst
: Entity_Id
) return Boolean;
6515 -- Return True if E is an actual parameter
6516 -- corresponding to a formal subprogram of the
6517 -- instantiation Inst.
6519 function Is_Extraneously_Visible
6520 (E
: Entity_Id
; Inst
: Entity_Id
) return Boolean;
6521 -- Return True if E is an interpretation that should
6522 -- be filtered out. That is, if E is an "unwanted"
6523 -- resolution candidate as described in the
6524 -- preceding "Background:" commment.
6526 function Is_Generic_Actual_Subp_Name
6527 (N
: Node_Id
) return Boolean;
6528 -- Return True if N is the name of a subprogram
6529 -- renaming generated for a generic actual.
6531 ----------------------------
6532 -- Is_Actual_Subp_Of_Inst --
6533 ----------------------------
6535 function Is_Actual_Subp_Of_Inst
6536 (E
: Entity_Id
; Inst
: Entity_Id
) return Boolean
6539 Generic_From_E
, Generic_From_Inst
: Entity_Id
;
6542 -- Why is Is_Generic_Actual_Subprogram undefined
6543 -- in the E_Operator case?
6545 if Ekind
(E
) not in E_Function | E_Procedure
6546 or else not Is_Generic_Actual_Subprogram
(E
)
6551 Decl
:= Enclosing_Declaration
(E
);
6553 -- Enclosing_Declaration does not always return a
6554 -- declaration; cope with this irregularity.
6555 if Decl
in N_Subprogram_Specification_Id
6556 and then Nkind
(Parent
(Decl
)) in
6557 N_Subprogram_Body | N_Subprogram_Declaration
6558 | N_Subprogram_Renaming_Declaration
6560 Decl
:= Parent
(Decl
);
6563 -- Look for the suprogram renaming declaration built
6564 -- for a generic actual subprogram. Unclear why
6565 -- Original_Node call is needed, but sometimes it is.
6567 if Decl
not in N_Subprogram_Renaming_Declaration_Id
then
6568 Decl
:= Original_Node
(Decl
);
6571 if Decl
in N_Subprogram_Renaming_Declaration_Id
then
6573 Scope
(Corresponding_Formal_Spec
(Decl
));
6575 -- ??? In the case of a generic formal subprogram
6576 -- which has a pre/post condition, it is unclear how
6577 -- to find the Corresponding_Formal_Spec-bearing node.
6579 Generic_From_E
:= Empty
;
6583 Inst_Parent
: Node_Id
:= Parent
(Inst
);
6585 if Nkind
(Inst_Parent
) = N_Defining_Program_Unit_Name
6587 Inst_Parent
:= Parent
(Inst_Parent
);
6590 Generic_From_Inst
:= Generic_Parent
(Inst_Parent
);
6593 return Generic_From_E
= Generic_From_Inst
6594 and then Present
(Generic_From_E
);
6595 end Is_Actual_Subp_Of_Inst
;
6597 -----------------------------
6598 -- Is_Extraneously_Visible --
6599 -----------------------------
6601 function Is_Extraneously_Visible
6602 (E
: Entity_Id
; Inst
: Entity_Id
) return Boolean is
6604 -- Return False in various non-extraneous cases.
6605 -- If none of those apply, then return True.
6607 if Within_Scope
(E
, Inst
) then
6608 -- return False if E declared within Inst
6611 elsif Is_Actual_Subp_Of_Inst
(E
, Inst
) then
6612 -- Return False if E is an actual subprogram,
6613 -- and therefore may be referenced within Inst.
6616 elsif Nkind
(Parent
(E
)) = N_Subtype_Declaration
6617 and then Defining_Identifier
(Parent
(E
)) /= E
6619 -- Return False for a primitive subp of an
6620 -- actual corresponding to a formal type.
6624 elsif not In_Open_Scopes
(Scope
(E
)) then
6625 -- Return False if this candidate is not
6626 -- declared in a currently open scope.
6632 -- We want to know whether the declaration of
6633 -- E comes textually after the declaration of
6634 -- the generic that Inst is an instance of
6635 -- (and after the generic body if there is one).
6636 -- To compare, we climb up the deeper of the two
6637 -- scope chains until we the levels match.
6638 -- There is a separate loop for each starting
6639 -- point, but we will execute zero iterations
6640 -- for at least one of the two loops.
6641 -- For each Xxx_Scope, we have a corresponding
6642 -- Xxx_Trailer; the latter is the predecessor of
6643 -- the former in the scope traversal.
6645 E_Trailer
: Entity_Id
:= E
;
6646 E_Scope
: Entity_Id
:= Scope
(E
);
6647 pragma Assert
(Present
(E_Scope
));
6649 -- the generic that Inst is an instance of
6650 Gen_Trailer
: Entity_Id
:=
6651 Generic_Parent
(Specification
6652 (Unit_Declaration_Node
(Inst
)));
6653 Gen_Scope
: Entity_Id
;
6655 function Has_Formal_Package_Parameter
6656 (Generic_Id
: Entity_Id
) return Boolean;
6657 -- Return True iff given generic has at least one
6658 -- formal package parameter.
6660 ----------------------------------
6661 -- Has_Formal_Package_Parameter --
6662 ----------------------------------
6664 function Has_Formal_Package_Parameter
6665 (Generic_Id
: Entity_Id
) return Boolean is
6666 Formal_Decl
: Node_Id
:=
6667 First
(Generic_Formal_Declarations
6668 (Enclosing_Generic_Unit
(Generic_Id
)));
6670 while Present
(Formal_Decl
) loop
6671 if Nkind
(Original_Node
(Formal_Decl
)) =
6672 N_Formal_Package_Declaration
6680 end Has_Formal_Package_Parameter
;
6683 if No
(Gen_Trailer
) then
6684 -- Dunno how this can happen, but it can.
6687 if Has_Formal_Package_Parameter
(Gen_Trailer
)
6689 -- Punt on sorting out what is visible via a
6695 if Is_Child_Unit
(Gen_Trailer
)
6696 and then Is_Generic_Unit
6698 (Parent
(Gen_Trailer
))))
6700 -- Punt on dealing with how the FE fails
6701 -- to build a tree for a "sprouted" generic
6702 -- so that what should be a reference to
6703 -- I1.G2 instead points into G1.G2 .
6708 Gen_Scope
:= Scope
(Gen_Trailer
);
6710 while Scope_Depth
(E_Scope
)
6711 > Scope_Depth
(Gen_Scope
)
6713 E_Trailer
:= E_Scope
;
6714 E_Scope
:= Scope
(E_Scope
);
6716 while Scope_Depth
(E_Scope
)
6717 < Scope_Depth
(Gen_Scope
)
6719 Gen_Trailer
:= Gen_Scope
;
6720 Gen_Scope
:= Scope
(Gen_Scope
);
6724 if Gen_Scope
= E_Scope
then
6725 -- if Gen_Trailer and E_Trailer are declared
6726 -- in the same declarative part and E_Trailer
6727 -- occurs after the declaration (and body, if
6728 -- there is one) of Gen_Trailer, then
6729 -- return True because E was declared after
6730 -- the generic that Inst is an instance of
6731 -- (and also after that generic's body, if it
6734 if Is_Package_Or_Generic_Package
(Gen_Trailer
)
6735 and then Present
(Package_Body
(Gen_Trailer
))
6739 (Package_Spec
(Gen_Trailer
));
6743 Id
: Entity_Id
:= Gen_Trailer
;
6746 if not Present
(Id
) then
6747 -- E_Trailer presumably occurred
6748 -- earlier on the entity list than
6749 -- Gen_Trailer. So E preceded the
6750 -- generic that Inst is an instance
6751 -- of (or the body of that generic if
6752 -- it has one) and so could have
6753 -- been referenced within the generic.
6756 exit when Id
= E_Trailer
;
6764 if Present
(Nearest_Enclosing_Instance
(Inst
)) then
6765 return Is_Extraneously_Visible
6766 (E
=> E
, Inst
=> Nearest_Enclosing_Instance
(Inst
));
6768 -- The preceding Nearest_Enclosing_Instance test
6769 -- doesn't handle the case of an instance of a
6770 -- "sprouted" generic. For example, if Inst=I2 in
6771 -- generic package G1
6772 -- generic package G1.G2;
6773 -- package I1 is new G1;
6774 -- package I2 is new I1.G2;
6775 -- then N_E_I (Inst) = Empty. So deal with that case.
6777 elsif Present
(Nearest_Enclosing_Instance
(E
)) then
6778 return Is_Extraneously_Visible
6779 (E
=> Nearest_Enclosing_Instance
(E
),
6784 end Is_Extraneously_Visible
;
6786 ---------------------------------
6787 -- Is_Generic_Actual_Subp_Name --
6788 ---------------------------------
6790 function Is_Generic_Actual_Subp_Name
6791 (N
: Node_Id
) return Boolean
6793 Decl
: constant Node_Id
:= Enclosing_Declaration
(N
);
6795 return Nkind
(Decl
) = N_Subprogram_Renaming_Declaration
6796 and then Present
(Corresponding_Formal_Spec
(Decl
));
6797 end Is_Generic_Actual_Subp_Name
;
6801 Inst
: Entity_Id
:= Current_Scope
;
6804 while Present
(Inst
)
6805 and then not Is_Generic_Instance
(Inst
)
6807 Inst
:= Scope
(Inst
);
6810 if Present
(Inst
) then
6811 Get_First_Interp
(N
, I
, It
);
6812 while Present
(It
.Nam
) loop
6813 if Is_Extraneously_Visible
(E
=> It
.Nam
, Inst
=> Inst
)
6814 and then not Is_Generic_Actual_Subp_Name
(N
)
6818 Get_Next_Interp
(I
, It
);
6824 -- If no homonyms were visible, the entity is unambiguous
6826 if not Is_Overloaded
(N
) then
6827 if not Is_Actual_Parameter
then
6828 Generate_Reference
(E
, N
);
6832 -- Case of non-overloadable entity, set the entity providing that
6833 -- we do not have the case of a discriminant reference within a
6834 -- default expression. Such references are replaced with the
6835 -- corresponding discriminal, which is the formal corresponding to
6836 -- to the discriminant in the initialization procedure.
6839 -- Entity is unambiguous, indicate that it is referenced here
6841 -- For a renaming of an object, always generate simple reference,
6842 -- we don't try to keep track of assignments in this case, except
6843 -- in SPARK mode where renamings are traversed for generating
6844 -- local effects of subprograms.
6847 and then Present
(Renamed_Object
(E
))
6848 and then not GNATprove_Mode
6850 Generate_Reference
(E
, N
);
6852 -- If the renamed entity is a private protected component,
6853 -- reference the original component as well. This needs to be
6854 -- done because the private renamings are installed before any
6855 -- analysis has occurred. Reference to a private component will
6856 -- resolve to the renaming and the original component will be
6857 -- left unreferenced, hence the following.
6859 if Is_Prival
(E
) then
6860 Generate_Reference
(Prival_Link
(E
), N
);
6863 -- One odd case is that we do not want to set the Referenced flag
6864 -- if the entity is a label, and the identifier is the label in
6865 -- the source, since this is not a reference from the point of
6866 -- view of the user.
6868 elsif Nkind
(Parent
(N
)) = N_Label
then
6870 R
: constant Boolean := Referenced
(E
);
6873 -- Generate reference unless this is an actual parameter
6874 -- (see comment below).
6876 if not Is_Actual_Parameter
then
6877 Generate_Reference
(E
, N
);
6878 Set_Referenced
(E
, R
);
6882 -- Normal case, not a label: generate reference
6885 if not Is_Actual_Parameter
then
6887 -- Package or generic package is always a simple reference
6889 if Is_Package_Or_Generic_Package
(E
) then
6890 Generate_Reference
(E
, N
, 'r');
6892 -- Else see if we have a left hand side
6895 case Known_To_Be_Assigned
(N
, Only_LHS
=> True) is
6897 Generate_Reference
(E
, N
, 'm');
6900 Generate_Reference
(E
, N
, 'r');
6907 Set_Entity_Or_Discriminal
(N
, E
);
6909 -- The name may designate a generalized reference, in which case
6910 -- the dereference interpretation will be included. Context is
6911 -- one in which a name is legal.
6913 if Ada_Version
>= Ada_2012
6915 (Nkind
(Parent
(N
)) in N_Subexpr
6916 or else Nkind
(Parent
(N
)) in N_Assignment_Statement
6917 | N_Object_Declaration
6918 | N_Parameter_Association
)
6920 Check_Implicit_Dereference
(N
, Etype
(E
));
6925 -- Mark relevant use-type and use-package clauses as effective if the
6926 -- node in question is not overloaded and therefore does not require
6929 -- Note: Generic actual subprograms do not follow the normal resolution
6930 -- path, so ignore the fact that they are overloaded and mark them
6933 if Nkind
(N
) not in N_Subexpr
or else not Is_Overloaded
(N
) then
6934 Mark_Use_Clauses
(N
);
6937 -- Come here with entity set
6940 Check_Restriction_No_Use_Of_Entity
(N
);
6942 -- Annotate the tree by creating a variable reference marker in case the
6943 -- original variable reference is folded or optimized away. The variable
6944 -- reference marker is automatically saved for later examination by the
6945 -- ABE Processing phase. Variable references which act as actuals in a
6946 -- call require special processing and are left to Resolve_Actuals. The
6947 -- reference is a write when it appears on the left hand side of an
6950 if Needs_Variable_Reference_Marker
(N
=> N
, Calls_OK
=> False) then
6952 Is_Assignment_LHS
: constant Boolean := Known_To_Be_Assigned
(N
);
6955 Build_Variable_Reference_Marker
6957 Read
=> not Is_Assignment_LHS
,
6958 Write
=> Is_Assignment_LHS
);
6961 end Find_Direct_Name
;
6963 ------------------------
6964 -- Find_Expanded_Name --
6965 ------------------------
6967 -- This routine searches the homonym chain of the entity until it finds
6968 -- an entity declared in the scope denoted by the prefix. If the entity
6969 -- is private, it may nevertheless be immediately visible, if we are in
6970 -- the scope of its declaration.
6972 procedure Find_Expanded_Name
(N
: Node_Id
) is
6973 function In_Abstract_View_Pragma
(Nod
: Node_Id
) return Boolean;
6974 -- Determine whether expanded name Nod appears within a pragma which is
6975 -- a suitable context for an abstract view of a state or variable. The
6976 -- following pragmas fall in this category:
6983 -- In addition, pragma Abstract_State is also considered suitable even
6984 -- though it is an illegal context for an abstract view as this allows
6985 -- for proper resolution of abstract views of variables. This illegal
6986 -- context is later flagged in the analysis of indicator Part_Of.
6988 -----------------------------
6989 -- In_Abstract_View_Pragma --
6990 -----------------------------
6992 function In_Abstract_View_Pragma
(Nod
: Node_Id
) return Boolean is
6996 -- Climb the parent chain looking for a pragma
6999 while Present
(Par
) loop
7000 if Nkind
(Par
) = N_Pragma
then
7001 if Pragma_Name_Unmapped
(Par
)
7002 in Name_Abstract_State
7006 | Name_Refined_Depends
7007 | Name_Refined_Global
7011 -- Otherwise the pragma is not a legal context for an abstract
7018 -- Prevent the search from going too far
7020 elsif Is_Body_Or_Package_Declaration
(Par
) then
7024 Par
:= Parent
(Par
);
7028 end In_Abstract_View_Pragma
;
7032 Selector
: constant Node_Id
:= Selector_Name
(N
);
7034 Candidate
: Entity_Id
:= Empty
;
7038 -- Start of processing for Find_Expanded_Name
7041 P_Name
:= Entity
(Prefix
(N
));
7043 -- If the prefix is a renamed package, look for the entity in the
7044 -- original package.
7046 if Ekind
(P_Name
) = E_Package
7047 and then Present
(Renamed_Entity
(P_Name
))
7049 P_Name
:= Renamed_Entity
(P_Name
);
7051 if From_Limited_With
(P_Name
)
7052 and then not Unit_Is_Visible
(Cunit
(Get_Source_Unit
(P_Name
)))
7055 ("renaming of limited view of package & not usable in this"
7056 & " context (RM 8.5.3(3.1/2))", Prefix
(N
), P_Name
);
7058 elsif Has_Limited_View
(P_Name
)
7059 and then not Unit_Is_Visible
(Cunit
(Get_Source_Unit
(P_Name
)))
7060 and then not Is_Visible_Through_Renamings
(P_Name
)
7063 ("renaming of limited view of package & not usable in this"
7064 & " context (RM 8.5.3(3.1/2))", Prefix
(N
), P_Name
);
7067 -- Rewrite node with entity field pointing to renamed object
7069 Rewrite
(Prefix
(N
), New_Copy
(Prefix
(N
)));
7070 Set_Entity
(Prefix
(N
), P_Name
);
7072 -- If the prefix is an object of a concurrent type, look for
7073 -- the entity in the associated task or protected type.
7075 elsif Is_Concurrent_Type
(Etype
(P_Name
)) then
7076 P_Name
:= Etype
(P_Name
);
7079 Id
:= Current_Entity
(Selector
);
7082 Is_New_Candidate
: Boolean;
7085 while Present
(Id
) loop
7086 if Scope
(Id
) = P_Name
then
7088 Is_New_Candidate
:= True;
7090 -- Handle abstract views of states and variables. These are
7091 -- acceptable candidates only when the reference to the view
7092 -- appears in certain pragmas.
7094 if Ekind
(Id
) = E_Abstract_State
7095 and then From_Limited_With
(Id
)
7096 and then Present
(Non_Limited_View
(Id
))
7098 if In_Abstract_View_Pragma
(N
) then
7099 Candidate
:= Non_Limited_View
(Id
);
7100 Is_New_Candidate
:= True;
7102 -- Hide the candidate because it is not used in a proper
7107 Is_New_Candidate
:= False;
7111 -- Ada 2005 (AI-217): Handle shadow entities associated with
7112 -- types declared in limited-withed nested packages. We don't need
7113 -- to handle E_Incomplete_Subtype entities because the entities
7114 -- in the limited view are always E_Incomplete_Type and
7115 -- E_Class_Wide_Type entities (see Build_Limited_Views).
7117 -- Regarding the expression used to evaluate the scope, it
7118 -- is important to note that the limited view also has shadow
7119 -- entities associated nested packages. For this reason the
7120 -- correct scope of the entity is the scope of the real entity.
7121 -- The non-limited view may itself be incomplete, in which case
7122 -- get the full view if available.
7124 elsif Ekind
(Id
) in E_Incomplete_Type | E_Class_Wide_Type
7125 and then From_Limited_With
(Id
)
7126 and then Present
(Non_Limited_View
(Id
))
7127 and then Scope
(Non_Limited_View
(Id
)) = P_Name
7129 Candidate
:= Get_Full_View
(Non_Limited_View
(Id
));
7130 Is_New_Candidate
:= True;
7132 -- Handle special case where the prefix is a renaming of a shadow
7133 -- package which is visible. Required to avoid reporting spurious
7136 elsif Ekind
(P_Name
) = E_Package
7137 and then From_Limited_With
(P_Name
)
7138 and then not From_Limited_With
(Id
)
7139 and then Sloc
(Scope
(Id
)) = Sloc
(P_Name
)
7140 and then Unit_Is_Visible
(Cunit
(Get_Source_Unit
(P_Name
)))
7142 Candidate
:= Get_Full_View
(Id
);
7143 Is_New_Candidate
:= True;
7145 -- An unusual case arises with a fully qualified name for an
7146 -- entity local to a generic child unit package, within an
7147 -- instantiation of that package. The name of the unit now
7148 -- denotes the renaming created within the instance. This is
7149 -- only relevant in an instance body, see below.
7151 elsif Is_Generic_Instance
(Scope
(Id
))
7152 and then In_Open_Scopes
(Scope
(Id
))
7153 and then In_Instance_Body
7154 and then Ekind
(Scope
(Id
)) = E_Package
7155 and then Ekind
(Id
) = E_Package
7156 and then Renamed_Entity
(Id
) = Scope
(Id
)
7157 and then Is_Immediately_Visible
(P_Name
)
7159 Is_New_Candidate
:= True;
7162 Is_New_Candidate
:= False;
7165 if Is_New_Candidate
then
7167 -- If entity is a child unit, either it is a visible child of
7168 -- the prefix, or we are in the body of a generic prefix, as
7169 -- will happen when a child unit is instantiated in the body
7170 -- of a generic parent. This is because the instance body does
7171 -- not restore the full compilation context, given that all
7172 -- non-local references have been captured.
7174 if Is_Child_Unit
(Id
) or else P_Name
= Standard_Standard
then
7175 exit when Is_Visible_Lib_Unit
(Id
)
7176 or else (Is_Child_Unit
(Id
)
7177 and then In_Open_Scopes
(Scope
(Id
))
7178 and then In_Instance_Body
);
7180 exit when not Is_Hidden
(Id
);
7183 exit when Is_Immediately_Visible
(Id
);
7191 and then Ekind
(P_Name
) in E_Procedure | E_Function
7192 and then Is_Generic_Instance
(P_Name
)
7194 -- Expanded name denotes entity in (instance of) generic subprogram.
7195 -- The entity may be in the subprogram instance, or may denote one of
7196 -- the formals, which is declared in the enclosing wrapper package.
7198 P_Name
:= Scope
(P_Name
);
7200 Id
:= Current_Entity
(Selector
);
7201 while Present
(Id
) loop
7202 exit when Scope
(Id
) = P_Name
;
7207 if No
(Id
) or else Chars
(Id
) /= Chars
(Selector
) then
7208 Set_Etype
(N
, Any_Type
);
7210 -- If we are looking for an entity defined in System, try to find it
7211 -- in the child package that may have been provided as an extension
7212 -- to System. The Extend_System pragma will have supplied the name of
7213 -- the extension, which may have to be loaded.
7215 if Chars
(P_Name
) = Name_System
7216 and then Scope
(P_Name
) = Standard_Standard
7217 and then Present
(System_Extend_Unit
)
7218 and then Present_System_Aux
(N
)
7220 Set_Entity
(Prefix
(N
), System_Aux_Id
);
7221 Find_Expanded_Name
(N
);
7224 -- There is an implicit instance of the predefined operator in
7225 -- the given scope. The operator entity is defined in Standard.
7226 -- Has_Implicit_Operator makes the node into an Expanded_Name.
7228 elsif Nkind
(Selector
) = N_Operator_Symbol
7229 and then Has_Implicit_Operator
(N
)
7233 -- If there is no literal defined in the scope denoted by the
7234 -- prefix, the literal may belong to (a type derived from)
7235 -- Standard_Character, for which we have no explicit literals.
7237 elsif Nkind
(Selector
) = N_Character_Literal
7238 and then Has_Implicit_Character_Literal
(N
)
7243 -- If the prefix is a single concurrent object, use its name in
7244 -- the error message, rather than that of the anonymous type.
7246 if Is_Concurrent_Type
(P_Name
)
7247 and then Is_Internal_Name
(Chars
(P_Name
))
7249 Error_Msg_Node_2
:= Entity
(Prefix
(N
));
7251 Error_Msg_Node_2
:= P_Name
;
7254 if P_Name
= System_Aux_Id
then
7255 P_Name
:= Scope
(P_Name
);
7256 Set_Entity
(Prefix
(N
), P_Name
);
7259 if Present
(Candidate
) then
7261 -- If we know that the unit is a child unit we can give a more
7262 -- accurate error message.
7264 if Is_Child_Unit
(Candidate
) then
7266 -- If the candidate is a private child unit and we are in
7267 -- the visible part of a public unit, specialize the error
7268 -- message. There might be a private with_clause for it,
7269 -- but it is not currently active.
7271 if Is_Private_Descendant
(Candidate
)
7272 and then Ekind
(Current_Scope
) = E_Package
7273 and then not In_Private_Part
(Current_Scope
)
7274 and then not Is_Private_Descendant
(Current_Scope
)
7277 ("private child unit& is not visible here", Selector
);
7279 -- Normal case where we have a missing with for a child unit
7282 Error_Msg_Qual_Level
:= 99;
7283 Error_Msg_NE
-- CODEFIX
7284 ("missing `WITH &;`", Selector
, Candidate
);
7285 Error_Msg_Qual_Level
:= 0;
7288 -- Here we don't know that this is a child unit
7291 Error_Msg_NE
("& is not a visible entity of&", N
, Selector
);
7295 -- Within the instantiation of a child unit, the prefix may
7296 -- denote the parent instance, but the selector has the name
7297 -- of the original child. That is to say, when A.B appears
7298 -- within an instantiation of generic child unit B, the scope
7299 -- stack includes an instance of A (P_Name) and an instance
7300 -- of B under some other name. We scan the scope to find this
7301 -- child instance, which is the desired entity.
7302 -- Note that the parent may itself be a child instance, if
7303 -- the reference is of the form A.B.C, in which case A.B has
7304 -- already been rewritten with the proper entity.
7306 if In_Open_Scopes
(P_Name
)
7307 and then Is_Generic_Instance
(P_Name
)
7310 Gen_Par
: constant Entity_Id
:=
7311 Generic_Parent
(Specification
7312 (Unit_Declaration_Node
(P_Name
)));
7313 S
: Entity_Id
:= Current_Scope
;
7317 for J
in reverse 0 .. Scope_Stack
.Last
loop
7318 S
:= Scope_Stack
.Table
(J
).Entity
;
7320 exit when S
= Standard_Standard
;
7322 if Ekind
(S
) in E_Function | E_Package | E_Procedure
7325 Generic_Parent
(Specification
7326 (Unit_Declaration_Node
(S
)));
7328 -- Check that P is a generic child of the generic
7329 -- parent of the prefix.
7332 and then Chars
(P
) = Chars
(Selector
)
7333 and then Scope
(P
) = Gen_Par
7344 -- If this is a selection from Ada, System or Interfaces, then
7345 -- we assume a missing with for the corresponding package.
7347 if Is_Known_Unit
(N
)
7348 and then not (Present
(Entity
(Prefix
(N
)))
7349 and then Scope
(Entity
(Prefix
(N
))) /=
7352 if not Error_Posted
(N
) then
7354 ("& is not a visible entity of&", Prefix
(N
), Selector
);
7355 Error_Missing_With_Of_Known_Unit
(Prefix
(N
));
7358 -- If this is a selection from a dummy package, then suppress
7359 -- the error message, of course the entity is missing if the
7360 -- package is missing.
7362 elsif Sloc
(Error_Msg_Node_2
) = No_Location
then
7365 -- Here we have the case of an undefined component
7368 -- The prefix may hide a homonym in the context that
7369 -- declares the desired entity. This error can use a
7370 -- specialized message.
7372 if In_Open_Scopes
(P_Name
) then
7374 H
: constant Entity_Id
:= Homonym
(P_Name
);
7378 and then Is_Compilation_Unit
(H
)
7380 (Is_Immediately_Visible
(H
)
7381 or else Is_Visible_Lib_Unit
(H
))
7383 Id
:= First_Entity
(H
);
7384 while Present
(Id
) loop
7385 if Chars
(Id
) = Chars
(Selector
) then
7386 Error_Msg_Qual_Level
:= 99;
7387 Error_Msg_Name_1
:= Chars
(Selector
);
7389 ("% not declared in&", N
, P_Name
);
7391 ("\use fully qualified name starting with "
7392 & "Standard to make& visible", N
, H
);
7393 Error_Msg_Qual_Level
:= 0;
7401 -- If not found, standard error message
7403 Error_Msg_NE
("& not declared in&", N
, Selector
);
7409 -- Might be worth specializing the case when the prefix
7410 -- is a limited view.
7411 -- ... not declared in limited view of...
7413 Error_Msg_NE
("& not declared in&", N
, Selector
);
7416 -- Check for misspelling of some entity in prefix
7418 Id
:= First_Entity
(P_Name
);
7419 while Present
(Id
) loop
7420 if Is_Bad_Spelling_Of
(Chars
(Id
), Chars
(Selector
))
7421 and then not Is_Internal_Name
(Chars
(Id
))
7423 Error_Msg_NE
-- CODEFIX
7424 ("possible misspelling of&", Selector
, Id
);
7431 -- Specialize the message if this may be an instantiation
7432 -- of a child unit that was not mentioned in the context.
7434 if Nkind
(Parent
(N
)) = N_Package_Instantiation
7435 and then Is_Generic_Instance
(Entity
(Prefix
(N
)))
7436 and then Is_Compilation_Unit
7437 (Generic_Parent
(Parent
(Entity
(Prefix
(N
)))))
7439 Error_Msg_Node_2
:= Selector
;
7440 Error_Msg_N
-- CODEFIX
7441 ("\missing `WITH &.&;`", Prefix
(N
));
7451 if Comes_From_Source
(N
)
7452 and then Is_Remote_Access_To_Subprogram_Type
(Id
)
7453 and then Ekind
(Id
) = E_Access_Subprogram_Type
7454 and then Present
(Equivalent_Type
(Id
))
7456 -- If we are not actually generating distribution code (i.e. the
7457 -- current PCS is the dummy non-distributed version), then the
7458 -- Equivalent_Type will be missing, and Id should be treated as
7459 -- a regular access-to-subprogram type.
7461 Id
:= Equivalent_Type
(Id
);
7462 Set_Chars
(Selector
, Chars
(Id
));
7465 -- Ada 2005 (AI-50217): Check usage of entities in limited withed units
7467 if Ekind
(P_Name
) = E_Package
and then From_Limited_With
(P_Name
) then
7468 if From_Limited_With
(Id
)
7469 or else Is_Type
(Id
)
7470 or else Ekind
(Id
) = E_Package
7475 ("limited withed package can only be used to access incomplete "
7480 if Is_Task_Type
(P_Name
)
7481 and then ((Ekind
(Id
) = E_Entry
7482 and then Nkind
(Parent
(N
)) /= N_Attribute_Reference
)
7484 (Ekind
(Id
) = E_Entry_Family
7486 Nkind
(Parent
(Parent
(N
))) /= N_Attribute_Reference
))
7488 -- If both the task type and the entry are in scope, this may still
7489 -- be the expanded name of an entry formal.
7491 if In_Open_Scopes
(Id
)
7492 and then Nkind
(Parent
(N
)) = N_Selected_Component
7497 -- It is an entry call after all, either to the current task
7498 -- (which will deadlock) or to an enclosing task.
7500 Analyze_Selected_Component
(N
);
7506 when N_Selected_Component
=>
7507 Reinit_Field_To_Zero
(N
, F_Is_Prefixed_Call
);
7508 Change_Selected_Component_To_Expanded_Name
(N
);
7510 when N_Expanded_Name
=>
7514 pragma Assert
(False);
7517 -- Preserve relevant elaboration-related attributes of the context which
7518 -- are no longer available or very expensive to recompute once analysis,
7519 -- resolution, and expansion are over.
7521 Mark_Elaboration_Attributes
7527 -- Set appropriate type
7529 if Is_Type
(Id
) then
7532 Set_Etype
(N
, Get_Full_View
(Etype
(Id
)));
7535 -- Do style check and generate reference, but skip both steps if this
7536 -- entity has homonyms, since we may not have the right homonym set yet.
7537 -- The proper homonym will be set during the resolve phase.
7539 if Has_Homonym
(Id
) then
7543 Set_Entity_Or_Discriminal
(N
, Id
);
7545 case Known_To_Be_Assigned
(N
, Only_LHS
=> True) is
7547 Generate_Reference
(Id
, N
, 'm');
7550 Generate_Reference
(Id
, N
, 'r');
7555 -- Check for violation of No_Wide_Characters
7557 Check_Wide_Character_Restriction
(Id
, N
);
7559 if Is_Self_Hidden
(Id
) then
7560 Premature_Usage
(N
);
7562 elsif Is_Overloadable
(Id
) and then Present
(Homonym
(Id
)) then
7564 H
: Entity_Id
:= Homonym
(Id
);
7567 while Present
(H
) loop
7568 if Scope
(H
) = Scope
(Id
)
7569 and then (not Is_Hidden
(H
)
7570 or else Is_Immediately_Visible
(H
))
7572 Collect_Interps
(N
);
7579 -- If an extension of System is present, collect possible explicit
7580 -- overloadings declared in the extension.
7582 if Chars
(P_Name
) = Name_System
7583 and then Scope
(P_Name
) = Standard_Standard
7584 and then Present
(System_Extend_Unit
)
7585 and then Present_System_Aux
(N
)
7587 H
:= Current_Entity
(Id
);
7589 while Present
(H
) loop
7590 if Scope
(H
) = System_Aux_Id
then
7591 Add_One_Interp
(N
, H
, Etype
(H
));
7600 if Nkind
(Selector_Name
(N
)) = N_Operator_Symbol
7601 and then Scope
(Id
) /= Standard_Standard
7603 -- In addition to user-defined operators in the given scope, there
7604 -- may be an implicit instance of the predefined operator. The
7605 -- operator (defined in Standard) is found in Has_Implicit_Operator,
7606 -- and added to the interpretations. Procedure Add_One_Interp will
7607 -- determine which hides which.
7609 if Has_Implicit_Operator
(N
) then
7614 -- If there is a single interpretation for N we can generate a
7615 -- reference to the unique entity found.
7617 if Is_Overloadable
(Id
) and then not Is_Overloaded
(N
) then
7618 Generate_Reference
(Id
, N
);
7621 -- Mark relevant use-type and use-package clauses as effective if the
7622 -- node in question is not overloaded and therefore does not require
7625 if Nkind
(N
) not in N_Subexpr
or else not Is_Overloaded
(N
) then
7626 Mark_Use_Clauses
(N
);
7629 Check_Restriction_No_Use_Of_Entity
(N
);
7631 -- Annotate the tree by creating a variable reference marker in case the
7632 -- original variable reference is folded or optimized away. The variable
7633 -- reference marker is automatically saved for later examination by the
7634 -- ABE Processing phase. Variable references which act as actuals in a
7635 -- call require special processing and are left to Resolve_Actuals. The
7636 -- reference is a write when it appears on the left hand side of an
7639 if Needs_Variable_Reference_Marker
7644 Is_Assignment_LHS
: constant Boolean := Known_To_Be_Assigned
(N
);
7647 Build_Variable_Reference_Marker
7649 Read
=> not Is_Assignment_LHS
,
7650 Write
=> Is_Assignment_LHS
);
7653 end Find_Expanded_Name
;
7655 --------------------
7656 -- Find_First_Use --
7657 --------------------
7659 function Find_First_Use
(Use_Clause
: Node_Id
) return Node_Id
is
7663 -- Loop through the Prev_Use_Clause chain
7666 while Present
(Prev_Use_Clause
(Curr
)) loop
7667 Curr
:= Prev_Use_Clause
(Curr
);
7673 -------------------------
7674 -- Find_Renamed_Entity --
7675 -------------------------
7677 function Find_Renamed_Entity
7681 Is_Actual
: Boolean := False) return Entity_Id
7684 I1
: Interp_Index
:= 0; -- Suppress junk warnings
7690 function Find_Nearer_Entity
7693 Old2_S
: Entity_Id
) return Entity_Id
;
7694 -- Determine whether one of Old_S1 and Old_S2 is nearer to New_S than
7695 -- the other, and return it if so. Return Empty otherwise. We use this
7696 -- in conjunction with Inherit_Renamed_Profile to simplify later type
7697 -- disambiguation for actual subprograms in instances.
7699 function Is_Visible_Operation
(Op
: Entity_Id
) return Boolean;
7700 -- If the renamed entity is an implicit operator, check whether it is
7701 -- visible because its operand type is properly visible. This check
7702 -- applies to explicit renamed entities that appear in the source in a
7703 -- renaming declaration or a formal subprogram instance, but not to
7704 -- default generic actuals with a name.
7706 function Report_Overload
return Entity_Id
;
7707 -- List possible interpretations, and specialize message in the
7708 -- case of a generic actual.
7710 function Within
(Inner
, Outer
: Entity_Id
) return Boolean;
7711 -- Determine whether a candidate subprogram is defined within the
7712 -- enclosing instance. If yes, it has precedence over outer candidates.
7714 --------------------------
7715 -- Find_Nearer_Entity --
7716 --------------------------
7718 function Find_Nearer_Entity
7721 Old2_S
: Entity_Id
) return Entity_Id
7729 New_F
:= First_Formal
(New_S
);
7730 Old1_F
:= First_Formal
(Old1_S
);
7731 Old2_F
:= First_Formal
(Old2_S
);
7733 -- The criterion is whether the type of the formals of one of Old1_S
7734 -- and Old2_S is an ancestor subtype of the type of the corresponding
7735 -- formals of New_S while the other is not (we already know that they
7736 -- are all subtypes of the same base type).
7738 -- This makes it possible to find the more correct renamed entity in
7739 -- the case of a generic instantiation nested in an enclosing one for
7740 -- which different formal types get the same actual type, which will
7741 -- in turn make it possible for Inherit_Renamed_Profile to preserve
7742 -- types on formal parameters and ultimately simplify disambiguation.
7744 -- Consider the follow package G:
7747 -- type Item_T is private;
7748 -- with function Compare (L, R: Item_T) return Boolean is <>;
7750 -- type Bound_T is private;
7751 -- with function Compare (L, R : Bound_T) return Boolean is <>;
7756 -- package body G is
7757 -- package My_Inner is Inner_G (Bound_T);
7761 -- with the following package Inner_G:
7764 -- type T is private;
7765 -- with function Compare (L, R: T) return Boolean is <>;
7766 -- package Inner_G is
7767 -- function "<" (L, R: T) return Boolean is (Compare (L, R));
7770 -- If G is instantiated on the same actual type with a single Compare
7774 -- function Compare (L, R : T) return Boolean;
7775 -- package My_G is new (T, T);
7777 -- then the renaming generated for Compare in the inner instantiation
7778 -- is ambiguous: it can rename either of the renamings generated for
7779 -- the outer instantiation. Now if the first one is picked up, then
7780 -- the subtypes of the formal parameters of the renaming will not be
7781 -- preserved in Inherit_Renamed_Profile because they are subtypes of
7782 -- the Bound_T formal type and not of the Item_T formal type, so we
7783 -- need to arrange for the second one to be picked up instead.
7785 while Present
(New_F
) loop
7786 if Etype
(Old1_F
) /= Etype
(Old2_F
) then
7787 Anc_T
:= Ancestor_Subtype
(Etype
(New_F
));
7789 if Etype
(Old1_F
) = Anc_T
then
7791 elsif Etype
(Old2_F
) = Anc_T
then
7796 Next_Formal
(New_F
);
7797 Next_Formal
(Old1_F
);
7798 Next_Formal
(Old2_F
);
7801 pragma Assert
(No
(Old1_F
));
7802 pragma Assert
(No
(Old2_F
));
7805 end Find_Nearer_Entity
;
7807 --------------------------
7808 -- Is_Visible_Operation --
7809 --------------------------
7811 function Is_Visible_Operation
(Op
: Entity_Id
) return Boolean is
7817 if Ekind
(Op
) /= E_Operator
7818 or else Scope
(Op
) /= Standard_Standard
7819 or else (In_Instance
7820 and then (not Is_Actual
7821 or else Present
(Enclosing_Instance
)))
7826 -- For a fixed point type operator, check the resulting type,
7827 -- because it may be a mixed mode integer * fixed operation.
7829 if Present
(Next_Formal
(First_Formal
(New_S
)))
7830 and then Is_Fixed_Point_Type
(Etype
(New_S
))
7832 Typ
:= Etype
(New_S
);
7834 Typ
:= Etype
(First_Formal
(New_S
));
7837 Btyp
:= Base_Type
(Typ
);
7839 if Nkind
(Nam
) /= N_Expanded_Name
then
7840 return (In_Open_Scopes
(Scope
(Btyp
))
7841 or else Is_Potentially_Use_Visible
(Btyp
)
7842 or else In_Use
(Btyp
)
7843 or else In_Use
(Scope
(Btyp
)));
7846 Scop
:= Entity
(Prefix
(Nam
));
7848 if Ekind
(Scop
) = E_Package
7849 and then Present
(Renamed_Entity
(Scop
))
7851 Scop
:= Renamed_Entity
(Scop
);
7854 -- Operator is visible if prefix of expanded name denotes
7855 -- scope of type, or else type is defined in System_Aux
7856 -- and the prefix denotes System.
7858 return Scope
(Btyp
) = Scop
7859 or else (Scope
(Btyp
) = System_Aux_Id
7860 and then Scope
(Scope
(Btyp
)) = Scop
);
7863 end Is_Visible_Operation
;
7869 function Within
(Inner
, Outer
: Entity_Id
) return Boolean is
7873 Sc
:= Scope
(Inner
);
7874 while Sc
/= Standard_Standard
loop
7885 ---------------------
7886 -- Report_Overload --
7887 ---------------------
7889 function Report_Overload
return Entity_Id
is
7892 Error_Msg_NE
-- CODEFIX
7893 ("ambiguous actual subprogram&, " &
7894 "possible interpretations:", N
, Nam
);
7896 Error_Msg_N
-- CODEFIX
7897 ("ambiguous subprogram, " &
7898 "possible interpretations:", N
);
7901 List_Interps
(Nam
, N
);
7903 end Report_Overload
;
7905 -- Start of processing for Find_Renamed_Entity
7909 Candidate_Renaming
:= Empty
;
7911 if Is_Overloaded
(Nam
) then
7912 Get_First_Interp
(Nam
, Ind
, It
);
7913 while Present
(It
.Nam
) loop
7914 if Entity_Matches_Spec
(It
.Nam
, New_S
)
7915 and then Is_Visible_Operation
(It
.Nam
)
7917 if Old_S
/= Any_Id
then
7919 -- Note: The call to Disambiguate only happens if a
7920 -- previous interpretation was found, in which case I1
7921 -- has received a value.
7923 It1
:= Disambiguate
(Nam
, I1
, Ind
, Etype
(Old_S
));
7925 if It1
= No_Interp
then
7926 Inst
:= Enclosing_Instance
;
7928 if Present
(Inst
) then
7929 if Within
(It
.Nam
, Inst
) then
7930 if Within
(Old_S
, Inst
) then
7932 It_D
: constant Uint
:=
7933 Scope_Depth_Default_0
(It
.Nam
);
7934 Old_D
: constant Uint
:=
7935 Scope_Depth_Default_0
(Old_S
);
7938 -- Choose the innermost subprogram, which
7939 -- would hide the outer one in the generic.
7941 if Old_D
> It_D
then
7943 elsif It_D
> Old_D
then
7947 -- Otherwise, if we can determine that one
7948 -- of the entities is nearer to the renaming
7949 -- than the other, choose it. If not, then
7950 -- return the newer one as done historically.
7953 Find_Nearer_Entity
(New_S
, Old_S
, It
.Nam
);
7954 if Present
(N_Ent
) then
7962 elsif Within
(Old_S
, Inst
) then
7966 return Report_Overload
;
7969 -- If not within an instance, ambiguity is real
7972 return Report_Overload
;
7986 Present
(First_Formal
(It
.Nam
))
7987 and then Present
(First_Formal
(New_S
))
7988 and then Base_Type
(Etype
(First_Formal
(It
.Nam
))) =
7989 Base_Type
(Etype
(First_Formal
(New_S
)))
7991 Candidate_Renaming
:= It
.Nam
;
7994 Get_Next_Interp
(Ind
, It
);
7997 Set_Entity
(Nam
, Old_S
);
7999 if Old_S
/= Any_Id
then
8000 Set_Is_Overloaded
(Nam
, False);
8003 -- Non-overloaded case
8007 and then Present
(Enclosing_Instance
)
8008 and then Entity_Matches_Spec
(Entity
(Nam
), New_S
)
8010 Old_S
:= Entity
(Nam
);
8012 elsif Entity_Matches_Spec
(Entity
(Nam
), New_S
) then
8013 Candidate_Renaming
:= New_S
;
8015 if Is_Visible_Operation
(Entity
(Nam
)) then
8016 Old_S
:= Entity
(Nam
);
8019 elsif Present
(First_Formal
(Entity
(Nam
)))
8020 and then Present
(First_Formal
(New_S
))
8021 and then Base_Type
(Etype
(First_Formal
(Entity
(Nam
)))) =
8022 Base_Type
(Etype
(First_Formal
(New_S
)))
8024 Candidate_Renaming
:= Entity
(Nam
);
8029 end Find_Renamed_Entity
;
8031 -----------------------------
8032 -- Find_Selected_Component --
8033 -----------------------------
8035 procedure Find_Selected_Component
(N
: Node_Id
) is
8036 P
: constant Node_Id
:= Prefix
(N
);
8039 -- Entity denoted by prefix
8046 function Available_Subtype
return Boolean;
8047 -- A small optimization: if the prefix is constrained and the component
8048 -- is an array type we may already have a usable subtype for it, so we
8049 -- can use it rather than generating a new one, because the bounds
8050 -- will be the values of the discriminants and not discriminant refs.
8051 -- This simplifies value tracing in GNATprove. For consistency, both
8052 -- the entity name and the subtype come from the constrained component.
8054 -- This is only used in GNATprove mode: when generating code it may be
8055 -- necessary to create an itype in the scope of use of the selected
8056 -- component, e.g. in the context of a expanded record equality.
8058 function Is_Reference_In_Subunit
return Boolean;
8059 -- In a subunit, the scope depth is not a proper measure of hiding,
8060 -- because the context of the proper body may itself hide entities in
8061 -- parent units. This rare case requires inspecting the tree directly
8062 -- because the proper body is inserted in the main unit and its context
8063 -- is simply added to that of the parent.
8065 -----------------------
8066 -- Available_Subtype --
8067 -----------------------
8069 function Available_Subtype
return Boolean is
8073 if GNATprove_Mode
then
8074 Comp
:= First_Entity
(Etype
(P
));
8075 while Present
(Comp
) loop
8076 if Chars
(Comp
) = Chars
(Selector_Name
(N
)) then
8077 Set_Etype
(N
, Etype
(Comp
));
8078 Set_Entity
(Selector_Name
(N
), Comp
);
8079 Set_Etype
(Selector_Name
(N
), Etype
(Comp
));
8083 Next_Component
(Comp
);
8088 end Available_Subtype
;
8090 -----------------------------
8091 -- Is_Reference_In_Subunit --
8092 -----------------------------
8094 function Is_Reference_In_Subunit
return Boolean is
8096 Comp_Unit
: Node_Id
;
8100 while Present
(Comp_Unit
)
8101 and then Nkind
(Comp_Unit
) /= N_Compilation_Unit
8103 Comp_Unit
:= Parent
(Comp_Unit
);
8106 if No
(Comp_Unit
) or else Nkind
(Unit
(Comp_Unit
)) /= N_Subunit
then
8110 -- Now check whether the package is in the context of the subunit
8112 Clause
:= First
(Context_Items
(Comp_Unit
));
8113 while Present
(Clause
) loop
8114 if Nkind
(Clause
) = N_With_Clause
8115 and then Entity
(Name
(Clause
)) = P_Name
8124 end Is_Reference_In_Subunit
;
8126 -- Start of processing for Find_Selected_Component
8131 if Nkind
(P
) = N_Error
then
8135 -- If the selector already has an entity, the node has been constructed
8136 -- in the course of expansion, and is known to be valid. Do not verify
8137 -- that it is defined for the type (it may be a private component used
8138 -- in the expansion of record equality).
8140 if Present
(Entity
(Selector_Name
(N
))) then
8141 if No
(Etype
(N
)) or else Etype
(N
) = Any_Type
then
8143 Sel_Name
: constant Node_Id
:= Selector_Name
(N
);
8144 Selector
: constant Entity_Id
:= Entity
(Sel_Name
);
8148 Set_Etype
(Sel_Name
, Etype
(Selector
));
8150 if not Is_Entity_Name
(P
) then
8154 -- Build an actual subtype except for the first parameter
8155 -- of an init proc, where this actual subtype is by
8156 -- definition incorrect, since the object is uninitialized
8157 -- (and does not even have defined discriminants etc.)
8159 if Is_Entity_Name
(P
)
8160 and then Ekind
(Entity
(P
)) = E_Function
8162 Nam
:= New_Copy
(P
);
8164 if Is_Overloaded
(P
) then
8165 Save_Interps
(P
, Nam
);
8168 Rewrite
(P
, Make_Function_Call
(Sloc
(P
), Name
=> Nam
));
8170 Analyze_Selected_Component
(N
);
8173 elsif Ekind
(Selector
) = E_Component
8174 and then (not Is_Entity_Name
(P
)
8175 or else Chars
(Entity
(P
)) /= Name_uInit
)
8177 -- Check if we already have an available subtype we can use
8179 if Ekind
(Etype
(P
)) = E_Record_Subtype
8180 and then Nkind
(Parent
(Etype
(P
))) = N_Subtype_Declaration
8181 and then Is_Array_Type
(Etype
(Selector
))
8182 and then not Is_Packed
(Etype
(Selector
))
8183 and then Available_Subtype
8187 -- Do not build the subtype when referencing components of
8188 -- dispatch table wrappers. Required to avoid generating
8189 -- elaboration code with HI runtimes.
8191 elsif Is_RTE
(Scope
(Selector
), RE_Dispatch_Table_Wrapper
)
8193 Is_RTE
(Scope
(Selector
), RE_No_Dispatch_Table_Wrapper
)
8198 Build_Actual_Subtype_Of_Component
8199 (Etype
(Selector
), N
);
8206 if No
(C_Etype
) then
8207 C_Etype
:= Etype
(Selector
);
8209 Insert_Action
(N
, C_Etype
);
8210 C_Etype
:= Defining_Identifier
(C_Etype
);
8213 Set_Etype
(N
, C_Etype
);
8216 -- If the selected component appears within a default expression
8217 -- and it has an actual subtype, the preanalysis has not yet
8218 -- completed its analysis, because Insert_Actions is disabled in
8219 -- that context. Within the init proc of the enclosing type we
8220 -- must complete this analysis, if an actual subtype was created.
8222 elsif Inside_Init_Proc
then
8224 Typ
: constant Entity_Id
:= Etype
(N
);
8225 Decl
: constant Node_Id
:= Declaration_Node
(Typ
);
8227 if Nkind
(Decl
) = N_Subtype_Declaration
8228 and then not Analyzed
(Decl
)
8229 and then Is_List_Member
(Decl
)
8230 and then No
(Parent
(Decl
))
8233 Insert_Action
(N
, Decl
);
8240 elsif Is_Entity_Name
(P
) then
8241 P_Name
:= Entity
(P
);
8243 -- The prefix may denote an enclosing type which is the completion
8244 -- of an incomplete type declaration.
8246 if Is_Type
(P_Name
) then
8247 Set_Entity
(P
, Get_Full_View
(P_Name
));
8248 Set_Etype
(P
, Entity
(P
));
8249 P_Name
:= Entity
(P
);
8252 P_Type
:= Base_Type
(Etype
(P
));
8254 if Debug_Flag_E
then
8255 Write_Str
("Found prefix type to be ");
8256 Write_Entity_Info
(P_Type
, " "); Write_Eol
;
8259 -- If the prefix's type is an access type, get to the record type
8261 if Is_Access_Type
(P_Type
) then
8262 P_Type
:= Implicitly_Designated_Type
(P_Type
);
8265 -- First check for components of a record object (not the result of
8266 -- a call, which is handled below). This also covers the case where
8267 -- the extension feature that supports the prefixed form of calls
8268 -- for primitives of untagged types is enabled (excluding concurrent
8269 -- cases, which are handled further below).
8272 and then (Has_Components
(P_Type
)
8273 or else (Core_Extensions_Allowed
8274 and then not Is_Concurrent_Type
(P_Type
)))
8275 and then not Is_Overloadable
(P_Name
)
8276 and then not Is_Type
(P_Name
)
8278 -- Selected component of record. Type checking will validate
8279 -- name of selector.
8281 -- ??? Could we rewrite an implicit dereference into an explicit
8284 Analyze_Selected_Component
(N
);
8286 -- Reference to type name in predicate/invariant expression
8288 elsif Is_Concurrent_Type
(P_Type
)
8289 and then not In_Open_Scopes
(P_Name
)
8290 and then (not Is_Concurrent_Type
(Etype
(P_Name
))
8291 or else not In_Open_Scopes
(Etype
(P_Name
)))
8293 -- Call to protected operation or entry. Type checking is
8294 -- needed on the prefix.
8296 Analyze_Selected_Component
(N
);
8298 elsif (In_Open_Scopes
(P_Name
)
8299 and then Ekind
(P_Name
) /= E_Void
8300 and then not Is_Overloadable
(P_Name
))
8301 or else (Is_Concurrent_Type
(Etype
(P_Name
))
8302 and then In_Open_Scopes
(Etype
(P_Name
)))
8304 -- Prefix denotes an enclosing loop, block, or task, i.e. an
8305 -- enclosing construct that is not a subprogram or accept.
8307 -- A special case: a protected body may call an operation
8308 -- on an external object of the same type, in which case it
8309 -- is not an expanded name. If the prefix is the type itself,
8310 -- or the context is a single synchronized object it can only
8311 -- be interpreted as an expanded name.
8313 if Is_Concurrent_Type
(Etype
(P_Name
)) then
8315 or else Present
(Anonymous_Object
(Etype
(P_Name
)))
8317 Find_Expanded_Name
(N
);
8320 Analyze_Selected_Component
(N
);
8325 Find_Expanded_Name
(N
);
8328 elsif Ekind
(P_Name
) = E_Package
then
8329 Find_Expanded_Name
(N
);
8331 elsif Is_Overloadable
(P_Name
) then
8333 -- The subprogram may be a renaming (of an enclosing scope) as
8334 -- in the case of the name of the generic within an instantiation.
8336 if Ekind
(P_Name
) in E_Procedure | E_Function
8337 and then Present
(Alias
(P_Name
))
8338 and then Is_Generic_Instance
(Alias
(P_Name
))
8340 P_Name
:= Alias
(P_Name
);
8343 if Is_Overloaded
(P
) then
8345 -- The prefix must resolve to a unique enclosing construct
8348 Found
: Boolean := False;
8353 Get_First_Interp
(P
, Ind
, It
);
8354 while Present
(It
.Nam
) loop
8355 if In_Open_Scopes
(It
.Nam
) then
8358 "prefix must be unique enclosing scope", N
);
8359 Set_Entity
(N
, Any_Id
);
8360 Set_Etype
(N
, Any_Type
);
8369 Get_Next_Interp
(Ind
, It
);
8374 if In_Open_Scopes
(P_Name
) then
8375 Set_Entity
(P
, P_Name
);
8376 Set_Is_Overloaded
(P
, False);
8377 Find_Expanded_Name
(N
);
8380 -- If no interpretation as an expanded name is possible, it
8381 -- must be a selected component of a record returned by a
8382 -- function call. Reformat prefix as a function call, the rest
8383 -- is done by type resolution.
8385 -- Error if the prefix is procedure or entry, as is P.X
8387 if Ekind
(P_Name
) /= E_Function
8389 (not Is_Overloaded
(P
)
8390 or else Nkind
(Parent
(N
)) = N_Procedure_Call_Statement
)
8392 -- Prefix may mention a package that is hidden by a local
8393 -- declaration: let the user know. Scan the full homonym
8394 -- chain, the candidate package may be anywhere on it.
8396 if Present
(Homonym
(Current_Entity
(P_Name
))) then
8397 P_Name
:= Current_Entity
(P_Name
);
8399 while Present
(P_Name
) loop
8400 exit when Ekind
(P_Name
) = E_Package
;
8401 P_Name
:= Homonym
(P_Name
);
8404 if Present
(P_Name
) then
8405 if not Is_Reference_In_Subunit
then
8406 Error_Msg_Sloc
:= Sloc
(Entity
(Prefix
(N
)));
8408 ("package& is hidden by declaration#", N
, P_Name
);
8411 Set_Entity
(Prefix
(N
), P_Name
);
8412 Find_Expanded_Name
(N
);
8416 P_Name
:= Entity
(Prefix
(N
));
8421 ("invalid prefix in selected component&", N
, P_Name
);
8422 Change_Selected_Component_To_Expanded_Name
(N
);
8423 Set_Entity
(N
, Any_Id
);
8424 Set_Etype
(N
, Any_Type
);
8426 -- Here we have a function call, so do the reformatting
8429 Nam
:= New_Copy
(P
);
8430 Save_Interps
(P
, Nam
);
8432 -- We use Replace here because this is one of those cases
8433 -- where the parser has missclassified the node, and we fix
8434 -- things up and then do the semantic analysis on the fixed
8435 -- up node. Normally we do this using one of the Sinfo.CN
8436 -- routines, but this is too tricky for that.
8438 -- Note that using Rewrite would be wrong, because we would
8439 -- have a tree where the original node is unanalyzed.
8442 Make_Function_Call
(Sloc
(P
), Name
=> Nam
));
8444 -- Now analyze the reformatted node
8448 -- If the prefix is illegal after this transformation, there
8449 -- may be visibility errors on the prefix. The safest is to
8450 -- treat the selected component as an error.
8452 if Error_Posted
(P
) then
8453 Set_Etype
(N
, Any_Type
);
8457 Analyze_Selected_Component
(N
);
8462 -- Remaining cases generate various error messages
8465 -- Format node as expanded name, to avoid cascaded errors
8467 Change_Selected_Component_To_Expanded_Name
(N
);
8468 Set_Entity
(N
, Any_Id
);
8469 Set_Etype
(N
, Any_Type
);
8471 -- Issue error message, but avoid this if error issued already.
8472 -- Use identifier of prefix if one is available.
8474 if P_Name
= Any_Id
then
8477 -- It is not an error if the prefix is the current instance of
8478 -- type name, e.g. the expression of a type aspect, when it is
8479 -- analyzed within a generic unit. We still have to verify that a
8480 -- component of that name exists, and decorate the node
8483 elsif Is_Entity_Name
(P
) and then Is_Current_Instance
(P
) then
8488 Comp
:= First_Entity
(Entity
(P
));
8489 while Present
(Comp
) loop
8490 if Chars
(Comp
) = Chars
(Selector_Name
(N
)) then
8491 Set_Entity
(N
, Comp
);
8492 Set_Etype
(N
, Etype
(Comp
));
8493 Set_Entity
(Selector_Name
(N
), Comp
);
8494 Set_Etype
(Selector_Name
(N
), Etype
(Comp
));
8502 elsif Is_Self_Hidden
(P_Name
) then
8503 Premature_Usage
(P
);
8505 elsif Ekind
(P_Name
) = E_Generic_Package
then
8506 Error_Msg_N
("prefix must not be a generic package", N
);
8507 Error_Msg_N
("\use package instantiation as prefix instead", N
);
8509 elsif Nkind
(P
) /= N_Attribute_Reference
then
8511 -- This may have been meant as a prefixed call to a primitive
8512 -- of an untagged type. If it is a function call check type of
8513 -- its first formal and add explanation.
8516 F
: constant Entity_Id
:=
8517 Current_Entity
(Selector_Name
(N
));
8520 and then Is_Overloadable
(F
)
8521 and then Present
(First_Entity
(F
))
8522 and then not Is_Tagged_Type
(Etype
(First_Entity
(F
)))
8525 ("prefixed call is only allowed for objects of a "
8526 & "tagged type unless -gnatX is used", N
);
8528 if not Core_Extensions_Allowed
8530 Try_Object_Operation
(N
, Allow_Extensions
=> True)
8533 ("\using -gnatX would make the prefixed call legal",
8539 Error_Msg_N
("invalid prefix in selected component&", P
);
8541 if Is_Incomplete_Type
(P_Type
)
8542 and then Is_Access_Type
(Etype
(P
))
8545 ("\dereference must not be of an incomplete type "
8546 & "(RM 3.10.1)", P
);
8550 Error_Msg_N
("invalid prefix in selected component", P
);
8554 -- If prefix is not the name of an entity, it must be an expression,
8555 -- whose type is appropriate for a record. This is determined by
8558 Analyze_Selected_Component
(N
);
8561 Analyze_Dimension
(N
);
8562 end Find_Selected_Component
;
8568 procedure Find_Type
(N
: Node_Id
) is
8578 elsif Nkind
(N
) = N_Attribute_Reference
then
8580 -- Class attribute. This is not valid in Ada 83 mode, but we do not
8581 -- need to enforce that at this point, since the declaration of the
8582 -- tagged type in the prefix would have been flagged already.
8584 if Attribute_Name
(N
) = Name_Class
then
8585 Check_Restriction
(No_Dispatch
, N
);
8586 Find_Type
(Prefix
(N
));
8588 -- Propagate error from bad prefix
8590 if Etype
(Prefix
(N
)) = Any_Type
then
8591 Set_Entity
(N
, Any_Type
);
8592 Set_Etype
(N
, Any_Type
);
8596 T
:= Base_Type
(Entity
(Prefix
(N
)));
8598 -- Case where type is not known to be tagged. Its appearance in
8599 -- the prefix of the 'Class attribute indicates that the full view
8602 if not Is_Tagged_Type
(T
) then
8603 if Ekind
(T
) = E_Incomplete_Type
then
8605 -- It is legal to denote the class type of an incomplete
8606 -- type. The full type will have to be tagged, of course.
8607 -- In Ada 2005 this usage is declared obsolescent, so we
8608 -- warn accordingly. This usage is only legal if the type
8609 -- is completed in the current scope, and not for a limited
8612 if Ada_Version
>= Ada_2005
then
8614 -- Test whether the Available_View of a limited type view
8615 -- is tagged, since the limited view may not be marked as
8616 -- tagged if the type itself has an untagged incomplete
8617 -- type view in its package.
8619 if From_Limited_With
(T
)
8620 and then not Is_Tagged_Type
(Available_View
(T
))
8623 ("prefix of Class attribute must be tagged", N
);
8624 Set_Etype
(N
, Any_Type
);
8625 Set_Entity
(N
, Any_Type
);
8629 if Restriction_Check_Required
(No_Obsolescent_Features
)
8632 (No_Obsolescent_Features
, Prefix
(N
));
8635 if Warn_On_Obsolescent_Feature
then
8637 ("applying ''Class to an untagged incomplete type"
8638 & " is an obsolescent feature (RM J.11)?r?", N
);
8643 Set_Is_Tagged_Type
(T
);
8644 Set_Direct_Primitive_Operations
(T
, New_Elmt_List
);
8645 Make_Class_Wide_Type
(T
);
8646 Set_Entity
(N
, Class_Wide_Type
(T
));
8647 Set_Etype
(N
, Class_Wide_Type
(T
));
8649 elsif Ekind
(T
) = E_Private_Type
8650 and then not Is_Generic_Type
(T
)
8651 and then In_Private_Part
(Scope
(T
))
8653 -- The Class attribute can be applied to an untagged private
8654 -- type fulfilled by a tagged type prior to the full type
8655 -- declaration (but only within the parent package's private
8656 -- part). Create the class-wide type now and check that the
8657 -- full type is tagged later during its analysis. Note that
8658 -- we do not mark the private type as tagged, unlike the
8659 -- case of incomplete types, because the type must still
8660 -- appear untagged to outside units.
8662 if No
(Class_Wide_Type
(T
)) then
8663 Make_Class_Wide_Type
(T
);
8666 Set_Entity
(N
, Class_Wide_Type
(T
));
8667 Set_Etype
(N
, Class_Wide_Type
(T
));
8670 -- Should we introduce a type Any_Tagged and use Wrong_Type
8671 -- here, it would be a bit more consistent???
8674 ("tagged type required, found}",
8675 Prefix
(N
), First_Subtype
(T
));
8676 Set_Entity
(N
, Any_Type
);
8680 -- Case of tagged type
8683 if Is_Concurrent_Type
(T
) then
8684 if No
(Corresponding_Record_Type
(Entity
(Prefix
(N
)))) then
8686 -- Previous error. Create a class-wide type for the
8687 -- synchronized type itself, with minimal semantic
8688 -- attributes, to catch other errors in some ACATS tests.
8690 pragma Assert
(Serious_Errors_Detected
/= 0);
8691 Make_Class_Wide_Type
(T
);
8692 C
:= Class_Wide_Type
(T
);
8693 Set_First_Entity
(C
, First_Entity
(T
));
8696 C
:= Class_Wide_Type
8697 (Corresponding_Record_Type
(Entity
(Prefix
(N
))));
8701 C
:= Class_Wide_Type
(Entity
(Prefix
(N
)));
8704 Set_Entity_With_Checks
(N
, C
);
8705 Generate_Reference
(C
, N
);
8709 -- Base attribute, not allowed in Ada 83
8711 elsif Attribute_Name
(N
) = Name_Base
then
8712 if Ada_Version
= Ada_83
and then Comes_From_Source
(N
) then
8714 ("(Ada 83) Base attribute not allowed in subtype mark", N
);
8717 Find_Type
(Prefix
(N
));
8718 Typ
:= Entity
(Prefix
(N
));
8720 if Ada_Version
>= Ada_95
8721 and then not Is_Scalar_Type
(Typ
)
8722 and then not Is_Generic_Type
(Typ
)
8725 ("prefix of Base attribute must be scalar type",
8728 elsif Warn_On_Redundant_Constructs
8729 and then Base_Type
(Typ
) = Typ
8731 Error_Msg_NE
-- CODEFIX
8732 ("redundant attribute, & is its own base type?r?", N
, Typ
);
8735 T
:= Base_Type
(Typ
);
8737 -- Rewrite attribute reference with type itself (see similar
8738 -- processing in Analyze_Attribute, case Base). Preserve prefix
8739 -- if present, for other legality checks.
8741 if Nkind
(Prefix
(N
)) = N_Expanded_Name
then
8743 Make_Expanded_Name
(Sloc
(N
),
8745 Prefix
=> New_Copy
(Prefix
(Prefix
(N
))),
8746 Selector_Name
=> New_Occurrence_Of
(T
, Sloc
(N
))));
8749 Rewrite
(N
, New_Occurrence_Of
(T
, Sloc
(N
)));
8756 elsif Attribute_Name
(N
) = Name_Stub_Type
then
8758 -- This is handled in Analyze_Attribute
8762 -- All other attributes are invalid in a subtype mark
8765 Error_Msg_N
("invalid attribute in subtype mark", N
);
8771 if Is_Entity_Name
(N
) then
8772 T_Name
:= Entity
(N
);
8774 Error_Msg_N
("subtype mark required in this context", N
);
8775 Set_Etype
(N
, Any_Type
);
8779 if T_Name
= Any_Id
or else Etype
(N
) = Any_Type
then
8781 -- Undefined id. Make it into a valid type
8783 Set_Entity
(N
, Any_Type
);
8785 elsif not Is_Type
(T_Name
)
8786 and then T_Name
/= Standard_Void_Type
8788 Error_Msg_Sloc
:= Sloc
(T_Name
);
8789 Error_Msg_N
("subtype mark required in this context", N
);
8790 Error_Msg_NE
("\\found & declared#", N
, T_Name
);
8791 Set_Entity
(N
, Any_Type
);
8794 -- If the type is an incomplete type created to handle
8795 -- anonymous access components of a record type, then the
8796 -- incomplete type is the visible entity and subsequent
8797 -- references will point to it. Mark the original full
8798 -- type as referenced, to prevent spurious warnings.
8800 if Is_Incomplete_Type
(T_Name
)
8801 and then Present
(Full_View
(T_Name
))
8802 and then not Comes_From_Source
(T_Name
)
8804 Set_Referenced
(Full_View
(T_Name
));
8807 T_Name
:= Get_Full_View
(T_Name
);
8809 -- Ada 2005 (AI-251, AI-50217): Handle interfaces visible through
8810 -- limited-with clauses
8812 if From_Limited_With
(T_Name
)
8813 and then Is_Incomplete_Type
(T_Name
)
8814 and then Present
(Non_Limited_View
(T_Name
))
8815 and then Is_Interface
(Non_Limited_View
(T_Name
))
8817 T_Name
:= Non_Limited_View
(T_Name
);
8820 if In_Open_Scopes
(T_Name
) then
8821 if Ekind
(Base_Type
(T_Name
)) = E_Task_Type
then
8823 -- In Ada 2005, a task name can be used in an access
8824 -- definition within its own body.
8826 if Ada_Version
>= Ada_2005
8827 and then Nkind
(Parent
(N
)) = N_Access_Definition
8829 Set_Entity
(N
, T_Name
);
8830 Set_Etype
(N
, T_Name
);
8835 ("task type cannot be used as type mark " &
8836 "within its own spec or body", N
);
8839 elsif Ekind
(Base_Type
(T_Name
)) = E_Protected_Type
then
8841 -- In Ada 2005, a protected name can be used in an access
8842 -- definition within its own body.
8844 if Ada_Version
>= Ada_2005
8845 and then Nkind
(Parent
(N
)) = N_Access_Definition
8847 Set_Entity
(N
, T_Name
);
8848 Set_Etype
(N
, T_Name
);
8853 ("protected type cannot be used as type mark " &
8854 "within its own spec or body", N
);
8858 Error_Msg_N
("type declaration cannot refer to itself", N
);
8861 Set_Etype
(N
, Any_Type
);
8862 Set_Entity
(N
, Any_Type
);
8863 Set_Error_Posted
(T_Name
);
8867 Set_Entity
(N
, T_Name
);
8868 Set_Etype
(N
, T_Name
);
8872 if Present
(Etype
(N
)) and then Comes_From_Source
(N
) then
8873 if Is_Fixed_Point_Type
(Etype
(N
)) then
8874 Check_Restriction
(No_Fixed_Point
, N
);
8875 elsif Is_Floating_Point_Type
(Etype
(N
)) then
8876 Check_Restriction
(No_Floating_Point
, N
);
8879 -- A Ghost type must appear in a specific context
8881 if Is_Ghost_Entity
(Etype
(N
)) then
8882 Check_Ghost_Context
(Etype
(N
), N
);
8887 --------------------
8888 -- Has_Components --
8889 --------------------
8891 function Has_Components
(Typ
: Entity_Id
) return Boolean is
8893 return Is_Record_Type
(Typ
)
8894 or else (Is_Private_Type
(Typ
) and then Has_Discriminants
(Typ
))
8895 or else (Is_Task_Type
(Typ
) and then Has_Discriminants
(Typ
))
8896 or else (Is_Incomplete_Type
(Typ
)
8897 and then From_Limited_With
(Typ
)
8898 and then Is_Record_Type
(Available_View
(Typ
)));
8901 ------------------------------------
8902 -- Has_Implicit_Character_Literal --
8903 ------------------------------------
8905 function Has_Implicit_Character_Literal
(N
: Node_Id
) return Boolean is
8907 Found
: Boolean := False;
8908 P
: constant Entity_Id
:= Entity
(Prefix
(N
));
8909 Priv_Id
: Entity_Id
:= Empty
;
8912 if Ekind
(P
) = E_Package
and then not In_Open_Scopes
(P
) then
8913 Priv_Id
:= First_Private_Entity
(P
);
8916 if P
= Standard_Standard
then
8917 Change_Selected_Component_To_Expanded_Name
(N
);
8918 Rewrite
(N
, Selector_Name
(N
));
8920 Set_Etype
(Original_Node
(N
), Standard_Character
);
8924 Id
:= First_Entity
(P
);
8925 while Present
(Id
) and then Id
/= Priv_Id
loop
8926 if Is_Standard_Character_Type
(Id
) and then Is_Base_Type
(Id
) then
8928 -- We replace the node with the literal itself, resolve as a
8929 -- character, and set the type correctly.
8932 Change_Selected_Component_To_Expanded_Name
(N
);
8933 Rewrite
(N
, Selector_Name
(N
));
8936 Set_Etype
(Original_Node
(N
), Id
);
8940 -- More than one type derived from Character in given scope.
8941 -- Collect all possible interpretations.
8943 Add_One_Interp
(N
, Id
, Id
);
8951 end Has_Implicit_Character_Literal
;
8953 ----------------------
8954 -- Has_Private_With --
8955 ----------------------
8957 function Has_Private_With
(E
: Entity_Id
) return Boolean is
8958 Comp_Unit
: constant Node_Id
:= Cunit
(Current_Sem_Unit
);
8962 Item
:= First
(Context_Items
(Comp_Unit
));
8963 while Present
(Item
) loop
8964 if Nkind
(Item
) = N_With_Clause
8965 and then Private_Present
(Item
)
8966 and then Entity
(Name
(Item
)) = E
8975 end Has_Private_With
;
8977 ---------------------------
8978 -- Has_Implicit_Operator --
8979 ---------------------------
8981 function Has_Implicit_Operator
(N
: Node_Id
) return Boolean is
8982 Op_Id
: constant Name_Id
:= Chars
(Selector_Name
(N
));
8983 P
: constant Entity_Id
:= Entity
(Prefix
(N
));
8985 Priv_Id
: Entity_Id
:= Empty
;
8987 procedure Add_Implicit_Operator
8989 Op_Type
: Entity_Id
:= Empty
);
8990 -- Add implicit interpretation to node N, using the type for which a
8991 -- predefined operator exists. If the operator yields a boolean type,
8992 -- the Operand_Type is implicitly referenced by the operator, and a
8993 -- reference to it must be generated.
8995 ---------------------------
8996 -- Add_Implicit_Operator --
8997 ---------------------------
8999 procedure Add_Implicit_Operator
9001 Op_Type
: Entity_Id
:= Empty
)
9003 Predef_Op
: Entity_Id
;
9006 Predef_Op
:= Current_Entity
(Selector_Name
(N
));
9007 while Present
(Predef_Op
)
9008 and then Scope
(Predef_Op
) /= Standard_Standard
9010 Predef_Op
:= Homonym
(Predef_Op
);
9013 if Nkind
(N
) = N_Selected_Component
then
9014 Change_Selected_Component_To_Expanded_Name
(N
);
9017 -- If the context is an unanalyzed function call, determine whether
9018 -- a binary or unary interpretation is required.
9020 if Nkind
(Parent
(N
)) = N_Indexed_Component
then
9022 Is_Binary_Call
: constant Boolean :=
9024 (Next
(First
(Expressions
(Parent
(N
)))));
9025 Is_Binary_Op
: constant Boolean :=
9027 (Predef_Op
) /= Last_Entity
(Predef_Op
);
9028 Predef_Op2
: constant Entity_Id
:= Homonym
(Predef_Op
);
9031 if Is_Binary_Call
then
9032 if Is_Binary_Op
then
9033 Add_One_Interp
(N
, Predef_Op
, T
);
9035 Add_One_Interp
(N
, Predef_Op2
, T
);
9038 if not Is_Binary_Op
then
9039 Add_One_Interp
(N
, Predef_Op
, T
);
9041 -- Predef_Op2 may be empty in case of previous errors
9043 elsif Present
(Predef_Op2
) then
9044 Add_One_Interp
(N
, Predef_Op2
, T
);
9050 Add_One_Interp
(N
, Predef_Op
, T
);
9052 -- For operators with unary and binary interpretations, if
9053 -- context is not a call, add both
9055 if Present
(Homonym
(Predef_Op
)) then
9056 Add_One_Interp
(N
, Homonym
(Predef_Op
), T
);
9060 -- The node is a reference to a predefined operator, and
9061 -- an implicit reference to the type of its operands.
9063 if Present
(Op_Type
) then
9064 Generate_Operator_Reference
(N
, Op_Type
);
9066 Generate_Operator_Reference
(N
, T
);
9068 end Add_Implicit_Operator
;
9070 -- Start of processing for Has_Implicit_Operator
9073 if Ekind
(P
) = E_Package
and then not In_Open_Scopes
(P
) then
9074 Priv_Id
:= First_Private_Entity
(P
);
9077 Id
:= First_Entity
(P
);
9081 -- Boolean operators: an implicit declaration exists if the scope
9082 -- contains a declaration for a derived Boolean type, or for an
9083 -- array of Boolean type.
9090 while Id
/= Priv_Id
loop
9092 and then Valid_Boolean_Arg
(Id
)
9093 and then Is_Base_Type
(Id
)
9095 Add_Implicit_Operator
(Id
);
9102 -- Equality: look for any non-limited type (result is Boolean)
9107 while Id
/= Priv_Id
loop
9109 and then Valid_Equality_Arg
(Id
)
9110 and then Is_Base_Type
(Id
)
9112 Add_Implicit_Operator
(Standard_Boolean
, Id
);
9119 -- Comparison operators: scalar type, or array of scalar
9126 while Id
/= Priv_Id
loop
9128 and then Valid_Comparison_Arg
(Id
)
9129 and then Is_Base_Type
(Id
)
9131 Add_Implicit_Operator
(Standard_Boolean
, Id
);
9138 -- Arithmetic operators: any numeric type
9149 while Id
/= Priv_Id
loop
9150 if Is_Numeric_Type
(Id
) and then Is_Base_Type
(Id
) then
9151 Add_Implicit_Operator
(Id
);
9158 -- Concatenation: any one-dimensional array type
9160 when Name_Op_Concat
=>
9161 while Id
/= Priv_Id
loop
9162 if Is_Array_Type
(Id
)
9163 and then Number_Dimensions
(Id
) = 1
9164 and then Is_Base_Type
(Id
)
9166 Add_Implicit_Operator
(Id
);
9173 -- What is the others condition here? Should we be using a
9174 -- subtype of Name_Id that would restrict to operators ???
9180 -- If we fall through, then we do not have an implicit operator
9183 end Has_Implicit_Operator
;
9185 -----------------------------------
9186 -- Has_Loop_In_Inner_Open_Scopes --
9187 -----------------------------------
9189 function Has_Loop_In_Inner_Open_Scopes
(S
: Entity_Id
) return Boolean is
9191 -- Several scope stacks are maintained by Scope_Stack. The base of the
9192 -- currently active scope stack is denoted by the Is_Active_Stack_Base
9193 -- flag in the scope stack entry. Note that the scope stacks used to
9194 -- simply be delimited implicitly by the presence of Standard_Standard
9195 -- at their base, but there now are cases where this is not sufficient
9196 -- because Standard_Standard actually may appear in the middle of the
9197 -- active set of scopes.
9199 for J
in reverse 0 .. Scope_Stack
.Last
loop
9201 -- S was reached without seing a loop scope first
9203 if Scope_Stack
.Table
(J
).Entity
= S
then
9206 -- S was not yet reached, so it contains at least one inner loop
9208 elsif Ekind
(Scope_Stack
.Table
(J
).Entity
) = E_Loop
then
9212 -- Check Is_Active_Stack_Base to tell us when to stop, as there are
9213 -- cases where Standard_Standard appears in the middle of the active
9214 -- set of scopes. This affects the declaration and overriding of
9215 -- private inherited operations in instantiations of generic child
9218 pragma Assert
(not Scope_Stack
.Table
(J
).Is_Active_Stack_Base
);
9221 raise Program_Error
; -- unreachable
9222 end Has_Loop_In_Inner_Open_Scopes
;
9224 --------------------
9225 -- In_Open_Scopes --
9226 --------------------
9228 function In_Open_Scopes
(S
: Entity_Id
) return Boolean is
9230 -- Several scope stacks are maintained by Scope_Stack. The base of the
9231 -- currently active scope stack is denoted by the Is_Active_Stack_Base
9232 -- flag in the scope stack entry. Note that the scope stacks used to
9233 -- simply be delimited implicitly by the presence of Standard_Standard
9234 -- at their base, but there now are cases where this is not sufficient
9235 -- because Standard_Standard actually may appear in the middle of the
9236 -- active set of scopes.
9238 for J
in reverse 0 .. Scope_Stack
.Last
loop
9239 if Scope_Stack
.Table
(J
).Entity
= S
then
9243 -- Check Is_Active_Stack_Base to tell us when to stop, as there are
9244 -- cases where Standard_Standard appears in the middle of the active
9245 -- set of scopes. This affects the declaration and overriding of
9246 -- private inherited operations in instantiations of generic child
9249 exit when Scope_Stack
.Table
(J
).Is_Active_Stack_Base
;
9255 -----------------------------
9256 -- Inherit_Renamed_Profile --
9257 -----------------------------
9259 procedure Inherit_Renamed_Profile
(New_S
: Entity_Id
; Old_S
: Entity_Id
) is
9266 if Ekind
(Old_S
) = E_Operator
then
9267 New_F
:= First_Formal
(New_S
);
9269 while Present
(New_F
) loop
9270 Set_Etype
(New_F
, Base_Type
(Etype
(New_F
)));
9271 Next_Formal
(New_F
);
9274 Set_Etype
(New_S
, Base_Type
(Etype
(New_S
)));
9277 New_F
:= First_Formal
(New_S
);
9278 Old_F
:= First_Formal
(Old_S
);
9280 while Present
(New_F
) loop
9281 New_T
:= Etype
(New_F
);
9282 Old_T
:= Etype
(Old_F
);
9284 -- If the new type is a renaming of the old one, as is the case
9285 -- for actuals in instances, retain its name, to simplify later
9288 if Nkind
(Parent
(New_T
)) = N_Subtype_Declaration
9289 and then Is_Entity_Name
(Subtype_Indication
(Parent
(New_T
)))
9290 and then Entity
(Subtype_Indication
(Parent
(New_T
))) = Old_T
9294 Set_Etype
(New_F
, Old_T
);
9297 Next_Formal
(New_F
);
9298 Next_Formal
(Old_F
);
9301 pragma Assert
(No
(Old_F
));
9303 if Ekind
(Old_S
) in E_Function | E_Enumeration_Literal
then
9304 Set_Etype
(New_S
, Etype
(Old_S
));
9307 end Inherit_Renamed_Profile
;
9313 procedure Initialize
is
9318 -------------------------
9319 -- Install_Use_Clauses --
9320 -------------------------
9322 procedure Install_Use_Clauses
9324 Force_Installation
: Boolean := False)
9330 while Present
(U
) loop
9332 -- Case of USE package
9334 if Nkind
(U
) = N_Use_Package_Clause
then
9335 Use_One_Package
(U
, Name
(U
), True);
9340 Use_One_Type
(Subtype_Mark
(U
), Force
=> Force_Installation
);
9344 Next_Use_Clause
(U
);
9346 end Install_Use_Clauses
;
9348 ----------------------
9349 -- Mark_Use_Clauses --
9350 ----------------------
9352 procedure Mark_Use_Clauses
(Id
: Node_Or_Entity_Id
) is
9353 procedure Mark_Parameters
(Call
: Entity_Id
);
9354 -- Perform use_type_clause marking for all parameters in a subprogram
9355 -- or operator call.
9357 procedure Mark_Use_Package
(Pak
: Entity_Id
);
9358 -- Move up the Prev_Use_Clause chain for packages denoted by Pak -
9359 -- marking each clause in the chain as effective in the process.
9361 procedure Mark_Use_Type
(E
: Entity_Id
);
9362 -- Similar to Do_Use_Package_Marking except we move up the
9363 -- Prev_Use_Clause chain for the type denoted by E.
9365 ---------------------
9366 -- Mark_Parameters --
9367 ---------------------
9369 procedure Mark_Parameters
(Call
: Entity_Id
) is
9373 -- Move through all of the formals
9375 Curr
:= First_Formal
(Call
);
9376 while Present
(Curr
) loop
9377 Mark_Use_Type
(Curr
);
9382 -- Handle the return type
9384 Mark_Use_Type
(Call
);
9385 end Mark_Parameters
;
9387 ----------------------
9388 -- Mark_Use_Package --
9389 ----------------------
9391 procedure Mark_Use_Package
(Pak
: Entity_Id
) is
9395 -- Ignore cases where the scope of the type is not a package (e.g.
9396 -- Standard_Standard).
9398 if Ekind
(Pak
) /= E_Package
then
9402 Curr
:= Current_Use_Clause
(Pak
);
9403 while Present
(Curr
)
9404 and then not Is_Effective_Use_Clause
(Curr
)
9406 -- We need to mark the previous use clauses as effective, but
9407 -- each use clause may in turn render other use_package_clauses
9408 -- effective. Additionally, it is possible to have a parent
9409 -- package renamed as a child of itself so we must check the
9410 -- prefix entity is not the same as the package we are marking.
9412 if Nkind
(Name
(Curr
)) /= N_Identifier
9413 and then Present
(Prefix
(Name
(Curr
)))
9414 and then Entity
(Prefix
(Name
(Curr
))) /= Pak
9416 Mark_Use_Package
(Entity
(Prefix
(Name
(Curr
))));
9418 -- It is also possible to have a child package without a prefix
9419 -- that relies on a previous use_package_clause.
9421 elsif Nkind
(Name
(Curr
)) = N_Identifier
9422 and then Is_Child_Unit
(Entity
(Name
(Curr
)))
9424 Mark_Use_Package
(Scope
(Entity
(Name
(Curr
))));
9427 -- Mark the use_package_clause as effective and move up the chain
9429 Set_Is_Effective_Use_Clause
(Curr
);
9431 Curr
:= Prev_Use_Clause
(Curr
);
9433 end Mark_Use_Package
;
9439 procedure Mark_Use_Type
(E
: Entity_Id
) is
9444 -- Ignore void types and unresolved string literals and primitives
9446 if Nkind
(E
) = N_String_Literal
9447 or else Nkind
(Etype
(E
)) not in N_Entity
9448 or else not Is_Type
(Etype
(E
))
9453 -- Primitives with class-wide operands might additionally render
9454 -- their base type's use_clauses effective - so do a recursive check
9457 Base
:= Base_Type
(Etype
(E
));
9459 if Ekind
(Base
) = E_Class_Wide_Type
then
9460 Mark_Use_Type
(Base
);
9463 -- The package containing the type or operator function being used
9464 -- may be in use as well, so mark any use_package_clauses for it as
9465 -- effective. There are also additional sanity checks performed here
9466 -- for ignoring previous errors.
9468 Mark_Use_Package
(Scope
(Base
));
9470 if Nkind
(E
) in N_Op
9471 and then Present
(Entity
(E
))
9472 and then Present
(Scope
(Entity
(E
)))
9474 Mark_Use_Package
(Scope
(Entity
(E
)));
9477 Curr
:= Current_Use_Clause
(Base
);
9478 while Present
(Curr
)
9479 and then not Is_Effective_Use_Clause
(Curr
)
9481 -- Current use_type_clause may render other use_package_clauses
9484 if Nkind
(Subtype_Mark
(Curr
)) /= N_Identifier
9485 and then Present
(Prefix
(Subtype_Mark
(Curr
)))
9487 Mark_Use_Package
(Entity
(Prefix
(Subtype_Mark
(Curr
))));
9490 -- Mark the use_type_clause as effective and move up the chain
9492 Set_Is_Effective_Use_Clause
(Curr
);
9494 Curr
:= Prev_Use_Clause
(Curr
);
9498 -- Start of processing for Mark_Use_Clauses
9501 -- Use clauses in and of themselves do not count as a "use" of a
9504 if Nkind
(Parent
(Id
)) in N_Use_Package_Clause | N_Use_Type_Clause
then
9510 if Nkind
(Id
) in N_Entity
then
9512 -- Mark the entity's package
9514 if Is_Potentially_Use_Visible
(Id
) then
9515 Mark_Use_Package
(Scope
(Id
));
9518 -- Mark enumeration literals
9520 if Ekind
(Id
) = E_Enumeration_Literal
then
9525 elsif (Is_Overloadable
(Id
)
9526 or else Is_Generic_Subprogram
(Id
))
9527 and then (Is_Potentially_Use_Visible
(Id
)
9528 or else Is_Intrinsic_Subprogram
(Id
)
9529 or else (Ekind
(Id
) in E_Function | E_Procedure
9530 and then Is_Generic_Actual_Subprogram
(Id
)))
9532 Mark_Parameters
(Id
);
9540 if Nkind
(Id
) in N_Op
then
9542 -- At this point the left operand may not be resolved if we are
9543 -- encountering multiple operators next to eachother in an
9546 if Nkind
(Id
) in N_Binary_Op
9547 and then not (Nkind
(Left_Opnd
(Id
)) in N_Op
)
9549 Mark_Use_Type
(Left_Opnd
(Id
));
9552 Mark_Use_Type
(Right_Opnd
(Id
));
9555 -- Mark entity identifiers
9557 elsif Nkind
(Id
) in N_Has_Entity
9558 and then (Is_Potentially_Use_Visible
(Entity
(Id
))
9559 or else (Is_Generic_Instance
(Entity
(Id
))
9560 and then Is_Immediately_Visible
(Entity
(Id
))))
9562 -- Ignore fully qualified names as they do not count as a "use" of
9565 if Nkind
(Id
) in N_Identifier | N_Operator_Symbol
9566 or else (Present
(Prefix
(Id
))
9567 and then Scope
(Entity
(Id
)) /= Entity
(Prefix
(Id
)))
9569 Mark_Use_Clauses
(Entity
(Id
));
9573 end Mark_Use_Clauses
;
9575 --------------------------------
9576 -- Most_Descendant_Use_Clause --
9577 --------------------------------
9579 function Most_Descendant_Use_Clause
9580 (Clause1
: Entity_Id
;
9581 Clause2
: Entity_Id
) return Entity_Id
9583 function Determine_Package_Scope
(Clause
: Node_Id
) return Entity_Id
;
9584 -- Given a use clause, determine which package it belongs to
9586 -----------------------------
9587 -- Determine_Package_Scope --
9588 -----------------------------
9590 function Determine_Package_Scope
(Clause
: Node_Id
) return Entity_Id
is
9592 -- Check if the clause appears in the context area
9594 -- Note we cannot employ Enclosing_Packge for use clauses within
9595 -- context clauses since they are not actually "enclosed."
9597 if Nkind
(Parent
(Clause
)) = N_Compilation_Unit
then
9598 return Entity_Of_Unit
(Unit
(Parent
(Clause
)));
9601 -- Otherwise, obtain the enclosing package normally
9603 return Enclosing_Package
(Clause
);
9604 end Determine_Package_Scope
;
9609 -- Start of processing for Most_Descendant_Use_Clause
9612 if Clause1
= Clause2
then
9616 -- We determine which one is the most descendant by the scope distance
9617 -- to the ultimate parent unit.
9619 Scope1
:= Determine_Package_Scope
(Clause1
);
9620 Scope2
:= Determine_Package_Scope
(Clause2
);
9621 while Scope1
/= Standard_Standard
9622 and then Scope2
/= Standard_Standard
9624 Scope1
:= Scope
(Scope1
);
9625 Scope2
:= Scope
(Scope2
);
9629 elsif No
(Scope2
) then
9634 if Scope1
= Standard_Standard
then
9639 end Most_Descendant_Use_Clause
;
9645 procedure Pop_Scope
is
9646 SST
: Scope_Stack_Entry
renames Scope_Stack
.Table
(Scope_Stack
.Last
);
9647 S
: constant Scope_Kind_Id
:= SST
.Entity
;
9650 if Debug_Flag_E
then
9654 -- Set Default_Storage_Pool field of the library unit if necessary
9656 if Is_Package_Or_Generic_Package
(S
)
9658 Nkind
(Parent
(Unit_Declaration_Node
(S
))) = N_Compilation_Unit
9661 Aux
: constant Node_Id
:=
9662 Aux_Decls_Node
(Parent
(Unit_Declaration_Node
(S
)));
9664 if No
(Default_Storage_Pool
(Aux
)) then
9665 Set_Default_Storage_Pool
(Aux
, Default_Pool
);
9670 Scope_Suppress
:= SST
.Save_Scope_Suppress
;
9671 Local_Suppress_Stack_Top
:= SST
.Save_Local_Suppress_Stack_Top
;
9672 Check_Policy_List
:= SST
.Save_Check_Policy_List
;
9673 Default_Pool
:= SST
.Save_Default_Storage_Pool
;
9674 No_Tagged_Streams
:= SST
.Save_No_Tagged_Streams
;
9675 SPARK_Mode
:= SST
.Save_SPARK_Mode
;
9676 SPARK_Mode_Pragma
:= SST
.Save_SPARK_Mode_Pragma
;
9677 Default_SSO
:= SST
.Save_Default_SSO
;
9678 Uneval_Old
:= SST
.Save_Uneval_Old
;
9680 if Debug_Flag_W
then
9681 Write_Str
("<-- exiting scope: ");
9682 Write_Name
(Chars
(Current_Scope
));
9683 Write_Str
(", Depth=");
9684 Write_Int
(Int
(Scope_Stack
.Last
));
9688 End_Use_Clauses
(SST
.First_Use_Clause
);
9690 -- If the actions to be wrapped are still there they will get lost
9691 -- causing incomplete code to be generated. It is better to abort in
9692 -- this case (and we do the abort even with assertions off since the
9693 -- penalty is incorrect code generation).
9695 if SST
.Actions_To_Be_Wrapped
/= Scope_Actions
'(others => No_List) then
9696 raise Program_Error;
9699 -- Free last subprogram name if allocated, and pop scope
9701 Free (SST.Last_Subprogram_Name);
9702 Scope_Stack.Decrement_Last;
9709 procedure Push_Scope (S : Scope_Kind_Id) is
9710 E : constant Entity_Id := Scope (S);
9712 function Component_Alignment_Default return Component_Alignment_Kind;
9713 -- Return Component_Alignment_Kind for the newly-pushed scope.
9715 function Component_Alignment_Default return Component_Alignment_Kind is
9717 -- Each new scope pushed onto the scope stack inherits the component
9718 -- alignment of the previous scope. This emulates the "visibility"
9719 -- semantics of pragma Component_Alignment.
9721 if Scope_Stack.Last > Scope_Stack.First then
9722 return Scope_Stack.Table
9723 (Scope_Stack.Last - 1).Component_Alignment_Default;
9725 -- Otherwise, this is the first scope being pushed on the scope
9726 -- stack. Inherit the component alignment from the configuration
9727 -- form of pragma Component_Alignment (if any).
9730 return Configuration_Component_Alignment;
9732 end Component_Alignment_Default;
9735 if Ekind (S) = E_Void then
9738 -- Set scope depth if not a nonconcurrent type, and we have not yet set
9739 -- the scope depth. This means that we have the first occurrence of the
9740 -- scope, and this is where the depth is set.
9742 elsif (not Is_Type (S) or else Is_Concurrent_Type (S))
9743 and then not Scope_Depth_Set (S)
9745 if S = Standard_Standard then
9746 Set_Scope_Depth_Value (S, Uint_0);
9748 elsif Is_Child_Unit (S) then
9749 Set_Scope_Depth_Value (S, Uint_1);
9751 elsif not Is_Record_Type (Current_Scope) then
9752 if Scope_Depth_Set (Current_Scope) then
9753 if Ekind (S) = E_Loop then
9754 Set_Scope_Depth_Value (S, Scope_Depth (Current_Scope));
9756 Set_Scope_Depth_Value (S, Scope_Depth (Current_Scope) + 1);
9762 Scope_Stack.Increment_Last;
9764 Scope_Stack.Table (Scope_Stack.Last) :=
9766 Save_Scope_Suppress => Scope_Suppress,
9767 Save_Local_Suppress_Stack_Top => Local_Suppress_Stack_Top,
9768 Save_Check_Policy_List => Check_Policy_List,
9769 Save_Default_Storage_Pool => Default_Pool,
9770 Save_No_Tagged_Streams => No_Tagged_Streams,
9771 Save_SPARK_Mode => SPARK_Mode,
9772 Save_SPARK_Mode_Pragma => SPARK_Mode_Pragma,
9773 Save_Default_SSO => Default_SSO,
9774 Save_Uneval_Old => Uneval_Old,
9775 Component_Alignment_Default => Component_Alignment_Default,
9776 Last_Subprogram_Name => null,
9777 Is_Transient => False,
9778 Node_To_Be_Wrapped => Empty,
9779 Pending_Freeze_Actions => No_List,
9780 Actions_To_Be_Wrapped => (others => No_List),
9781 First_Use_Clause => Empty,
9782 Is_Active_Stack_Base => False,
9783 Previous_Visibility => False,
9784 Locked_Shared_Objects => No_Elist);
9786 if Debug_Flag_W then
9787 Write_Str ("--> new scope: ");
9788 Write_Name (Chars (Current_Scope));
9789 Write_Str (", Id=");
9790 Write_Int (Int (Current_Scope));
9791 Write_Str (", Depth=");
9792 Write_Int (Int (Scope_Stack.Last));
9796 -- Deal with copying flags from the previous scope to this one. This is
9797 -- not necessary if either scope is standard, or if the new scope is a
9800 if S /= Standard_Standard
9801 and then Scope (S) /= Standard_Standard
9802 and then not Is_Child_Unit (S)
9804 if Nkind (E) not in N_Entity then
9808 -- Copy categorization flags from Scope (S) to S, this is not done
9809 -- when Scope (S) is Standard_Standard since propagation is from
9810 -- library unit entity inwards. Copy other relevant attributes as
9811 -- well (Discard_Names in particular).
9813 -- We only propagate inwards for library level entities,
9814 -- inner level subprograms do not inherit the categorization.
9816 if Is_Library_Level_Entity (S) then
9817 Set_Is_Preelaborated (S, Is_Preelaborated (E));
9818 Set_Is_Shared_Passive (S, Is_Shared_Passive (E));
9819 Set_Discard_Names (S, Discard_Names (E));
9820 Set_Suppress_Value_Tracking_On_Call
9821 (S, Suppress_Value_Tracking_On_Call (E));
9822 Set_Categorization_From_Scope (E => S, Scop => E);
9826 if Is_Child_Unit (S)
9827 and then Present (E)
9828 and then Is_Package_Or_Generic_Package (E)
9830 Nkind (Parent (Unit_Declaration_Node (E))) = N_Compilation_Unit
9833 Aux : constant Node_Id :=
9834 Aux_Decls_Node (Parent (Unit_Declaration_Node (E)));
9836 if Present (Default_Storage_Pool (Aux)) then
9837 Default_Pool := Default_Storage_Pool (Aux);
9843 ---------------------
9844 -- Premature_Usage --
9845 ---------------------
9847 procedure Premature_Usage (N : Node_Id) is
9848 Kind : constant Node_Kind := Nkind (Parent (Entity (N)));
9849 E : Entity_Id := Entity (N);
9852 -- Within an instance, the analysis of the actual for a formal object
9853 -- does not see the name of the object itself. This is significant only
9854 -- if the object is an aggregate, where its analysis does not do any
9855 -- name resolution on component associations. (see 4717-008). In such a
9856 -- case, look for the visible homonym on the chain.
9858 if In_Instance and then Present (Homonym (E)) then
9860 while Present (E) and then not In_Open_Scopes (Scope (E)) loop
9866 Set_Etype (N, Etype (E));
9872 when N_Component_Declaration =>
9874 ("component&! cannot be used before end of record declaration",
9877 when N_Parameter_Specification =>
9879 ("formal parameter&! cannot be used before end of specification",
9882 when N_Discriminant_Specification =>
9884 ("discriminant&! cannot be used before end of discriminant part",
9887 when N_Procedure_Specification | N_Function_Specification =>
9889 ("subprogram&! cannot be used before end of its declaration",
9892 when N_Full_Type_Declaration | N_Subtype_Declaration =>
9894 ("type& cannot be used before end of its declaration!", N);
9898 ("object& cannot be used before end of its declaration!", N);
9900 -- If the premature reference appears as the expression in its own
9901 -- declaration, rewrite it to prevent compiler loops in subsequent
9902 -- uses of this mangled declaration in address clauses.
9904 if Nkind (Parent (N)) = N_Object_Declaration then
9905 Set_Entity (N, Any_Id);
9908 end Premature_Usage;
9910 ------------------------
9911 -- Present_System_Aux --
9912 ------------------------
9914 function Present_System_Aux (N : Node_Id := Empty) return Boolean is
9916 Aux_Name : Unit_Name_Type;
9917 Unum : Unit_Number_Type;
9922 function Find_System (C_Unit : Node_Id) return Entity_Id;
9923 -- Scan context clause of compilation unit to find with_clause
9930 function Find_System (C_Unit : Node_Id) return Entity_Id is
9931 With_Clause : Node_Id;
9934 With_Clause := First (Context_Items (C_Unit));
9935 while Present (With_Clause) loop
9936 if (Nkind (With_Clause) = N_With_Clause
9937 and then Chars (Name (With_Clause)) = Name_System)
9938 and then Comes_From_Source (With_Clause)
9949 -- Start of processing for Present_System_Aux
9952 -- The child unit may have been loaded and analyzed already
9954 if Present (System_Aux_Id) then
9957 -- If no previous pragma for System.Aux, nothing to load
9959 elsif No (System_Extend_Unit) then
9962 -- Use the unit name given in the pragma to retrieve the unit.
9963 -- Verify that System itself appears in the context clause of the
9964 -- current compilation. If System is not present, an error will
9965 -- have been reported already.
9968 With_Sys := Find_System (Cunit (Current_Sem_Unit));
9970 The_Unit := Unit (Cunit (Current_Sem_Unit));
9974 (Nkind (The_Unit) = N_Package_Body
9975 or else (Nkind (The_Unit) = N_Subprogram_Body
9976 and then not Acts_As_Spec (Cunit (Current_Sem_Unit))))
9978 With_Sys := Find_System (Library_Unit (Cunit (Current_Sem_Unit)));
9981 if No (With_Sys) and then Present (N) then
9983 -- If we are compiling a subunit, we need to examine its
9984 -- context as well (Current_Sem_Unit is the parent unit);
9986 The_Unit := Parent (N);
9987 while Nkind (The_Unit) /= N_Compilation_Unit loop
9988 The_Unit := Parent (The_Unit);
9991 if Nkind (Unit (The_Unit)) = N_Subunit then
9992 With_Sys := Find_System (The_Unit);
9996 if No (With_Sys) then
10000 Loc := Sloc (With_Sys);
10001 Get_Name_String (Chars (Expression (System_Extend_Unit)));
10002 Name_Buffer (8 .. Name_Len + 7) := Name_Buffer (1 .. Name_Len);
10003 Name_Buffer (1 .. 7) := "system.";
10004 Name_Buffer (Name_Len + 8) := '%';
10005 Name_Buffer (Name_Len + 9) := 's
';
10006 Name_Len := Name_Len + 9;
10007 Aux_Name := Name_Find;
10011 (Load_Name => Aux_Name,
10014 Error_Node => With_Sys);
10016 if Unum /= No_Unit then
10017 Semantics (Cunit (Unum));
10019 Defining_Entity (Specification (Unit (Cunit (Unum))));
10022 Make_With_Clause (Loc,
10024 Make_Expanded_Name (Loc,
10025 Chars => Chars (System_Aux_Id),
10027 New_Occurrence_Of (Scope (System_Aux_Id), Loc),
10028 Selector_Name => New_Occurrence_Of (System_Aux_Id, Loc)));
10030 Set_Entity (Name (Withn), System_Aux_Id);
10032 Set_Corresponding_Spec (Withn, System_Aux_Id);
10033 Set_First_Name (Withn);
10034 Set_Implicit_With (Withn);
10035 Set_Library_Unit (Withn, Cunit (Unum));
10037 Insert_After (With_Sys, Withn);
10038 Mark_Rewrite_Insertion (Withn);
10039 Set_Context_Installed (Withn);
10043 -- Here if unit load failed
10046 Error_Msg_Name_1 := Name_System;
10047 Error_Msg_Name_2 := Chars (Expression (System_Extend_Unit));
10049 ("extension package `%.%` does not exist",
10050 Opt.System_Extend_Unit);
10054 end Present_System_Aux;
10056 -------------------------
10057 -- Restore_Scope_Stack --
10058 -------------------------
10060 procedure Restore_Scope_Stack
10062 Handle_Use : Boolean := True)
10064 SS_Last : constant Int := Scope_Stack.Last;
10068 -- Restore visibility of previous scope stack, if any, using the list
10069 -- we saved (we use Remove, since this list will not be used again).
10072 Elmt := First_Elmt (List);
10073 exit when Elmt = No_Elmt;
10074 Set_Is_Immediately_Visible (Node (Elmt));
10075 Remove_Elmt (List, Elmt);
10078 -- Restore use clauses
10080 if SS_Last >= Scope_Stack.First
10081 and then Scope_Stack.Table (SS_Last).Entity /= Standard_Standard
10082 and then Handle_Use
10084 Install_Use_Clauses
10085 (Scope_Stack.Table (SS_Last).First_Use_Clause,
10086 Force_Installation => True);
10088 end Restore_Scope_Stack;
10090 ----------------------
10091 -- Save_Scope_Stack --
10092 ----------------------
10094 -- Save_Scope_Stack/Restore_Scope_Stack were originally designed to avoid
10095 -- consuming any memory. That is, Save_Scope_Stack took care of removing
10096 -- from immediate visibility entities and Restore_Scope_Stack took care
10097 -- of restoring their visibility analyzing the context of each entity. The
10098 -- problem of such approach is that it was fragile and caused unexpected
10099 -- visibility problems, and indeed one test was found where there was a
10102 -- Furthermore, the following experiment was carried out:
10104 -- - Save_Scope_Stack was modified to store in an Elist1 all those
10105 -- entities whose attribute Is_Immediately_Visible is modified
10106 -- from True to False.
10108 -- - Restore_Scope_Stack was modified to store in another Elist2
10109 -- all the entities whose attribute Is_Immediately_Visible is
10110 -- modified from False to True.
10112 -- - Extra code was added to verify that all the elements of Elist1
10113 -- are found in Elist2
10115 -- This test shows that there may be more occurrences of this problem which
10116 -- have not yet been detected. As a result, we replaced that approach by
10117 -- the current one in which Save_Scope_Stack returns the list of entities
10118 -- whose visibility is changed, and that list is passed to Restore_Scope_
10119 -- Stack to undo that change. This approach is simpler and safer, although
10120 -- it consumes more memory.
10122 function Save_Scope_Stack (Handle_Use : Boolean := True) return Elist_Id is
10123 Result : constant Elist_Id := New_Elmt_List;
10126 SS_Last : constant Int := Scope_Stack.Last;
10128 procedure Remove_From_Visibility (E : Entity_Id);
10129 -- If E is immediately visible then append it to the result and remove
10130 -- it temporarily from visibility.
10132 ----------------------------
10133 -- Remove_From_Visibility --
10134 ----------------------------
10136 procedure Remove_From_Visibility (E : Entity_Id) is
10138 if Is_Immediately_Visible (E) then
10139 Append_Elmt (E, Result);
10140 Set_Is_Immediately_Visible (E, False);
10142 end Remove_From_Visibility;
10144 -- Start of processing for Save_Scope_Stack
10147 if SS_Last >= Scope_Stack.First
10148 and then Scope_Stack.Table (SS_Last).Entity /= Standard_Standard
10151 End_Use_Clauses (Scope_Stack.Table (SS_Last).First_Use_Clause);
10154 -- If the call is from within a compilation unit, as when called from
10155 -- Rtsfind, make current entries in scope stack invisible while we
10156 -- analyze the new unit.
10158 for J in reverse 0 .. SS_Last loop
10159 exit when Scope_Stack.Table (J).Entity = Standard_Standard
10160 or else No (Scope_Stack.Table (J).Entity);
10162 S := Scope_Stack.Table (J).Entity;
10164 Remove_From_Visibility (S);
10166 E := First_Entity (S);
10167 while Present (E) loop
10168 Remove_From_Visibility (E);
10176 end Save_Scope_Stack;
10182 procedure Set_Use (L : List_Id) is
10187 while Present (Decl) loop
10188 if Nkind (Decl) = N_Use_Package_Clause then
10189 Chain_Use_Clause (Decl);
10190 Use_One_Package (Decl, Name (Decl));
10192 elsif Nkind (Decl) = N_Use_Type_Clause then
10193 Chain_Use_Clause (Decl);
10194 Use_One_Type (Subtype_Mark (Decl));
10202 -----------------------------
10203 -- Update_Use_Clause_Chain --
10204 -----------------------------
10206 procedure Update_Use_Clause_Chain is
10208 procedure Update_Chain_In_Scope (Level : Int);
10209 -- Iterate through one level in the scope stack verifying each use-type
10210 -- clause within said level is used then reset the Current_Use_Clause
10211 -- to a redundant use clause outside of the current ending scope if such
10212 -- a clause exists.
10214 ---------------------------
10215 -- Update_Chain_In_Scope --
10216 ---------------------------
10218 procedure Update_Chain_In_Scope (Level : Int) is
10223 -- Loop through all use clauses within the scope dictated by Level
10225 Curr := Scope_Stack.Table (Level).First_Use_Clause;
10226 while Present (Curr) loop
10228 -- Retrieve the subtype mark or name within the current current
10231 if Nkind (Curr) = N_Use_Type_Clause then
10232 N := Subtype_Mark (Curr);
10237 -- If warnings for unreferenced entities are enabled and the
10238 -- current use clause has not been marked effective.
10240 if Check_Unreferenced
10241 and then Comes_From_Source (Curr)
10242 and then not Is_Effective_Use_Clause (Curr)
10243 and then not In_Instance
10244 and then not In_Inlined_Body
10246 -- We are dealing with a potentially unused use_package_clause
10248 if Nkind (Curr) = N_Use_Package_Clause then
10250 -- Renamings and formal subprograms may cause the associated
10251 -- node to be marked as effective instead of the original.
10253 if not (Present (Associated_Node (N))
10255 (Current_Use_Clause
10256 (Associated_Node (N)))
10257 and then Is_Effective_Use_Clause
10258 (Current_Use_Clause
10259 (Associated_Node (N))))
10261 Error_Msg_Node_1 := Entity (N);
10263 ("use clause for package & has no effect?u?",
10267 -- We are dealing with an unused use_type_clause
10270 Error_Msg_Node_1 := Etype (N);
10272 ("use clause for } has no effect?u?", Curr, Etype (N));
10276 -- Verify that we haven't already processed a redundant
10277 -- use_type_clause within the same scope before we move the
10278 -- current use clause up to a previous one for type T.
10280 if Present (Prev_Use_Clause (Curr)) then
10281 Set_Current_Use_Clause (Entity (N), Prev_Use_Clause (Curr));
10284 Next_Use_Clause (Curr);
10286 end Update_Chain_In_Scope;
10288 -- Start of processing for Update_Use_Clause_Chain
10291 Update_Chain_In_Scope (Scope_Stack.Last);
10293 -- Deal with use clauses within the context area if the current
10294 -- scope is a compilation unit.
10296 if Is_Compilation_Unit (Current_Scope)
10297 and then Sloc (Scope_Stack.Table
10298 (Scope_Stack.Last - 1).Entity) = Standard_Location
10300 Update_Chain_In_Scope (Scope_Stack.Last - 1);
10302 end Update_Use_Clause_Chain;
10304 ---------------------
10305 -- Use_One_Package --
10306 ---------------------
10308 procedure Use_One_Package
10310 Pack_Name : Entity_Id := Empty;
10311 Force : Boolean := False)
10313 procedure Note_Redundant_Use (Clause : Node_Id);
10314 -- Mark the name in a use clause as redundant if the corresponding
10315 -- entity is already use-visible. Emit a warning if the use clause comes
10316 -- from source and the proper warnings are enabled.
10318 ------------------------
10319 -- Note_Redundant_Use --
10320 ------------------------
10322 procedure Note_Redundant_Use (Clause : Node_Id) is
10323 Decl : constant Node_Id := Parent (Clause);
10324 Pack_Name : constant Entity_Id := Entity (Clause);
10326 Cur_Use : Node_Id := Current_Use_Clause (Pack_Name);
10327 Prev_Use : Node_Id := Empty;
10328 Redundant : Node_Id := Empty;
10329 -- The Use_Clause which is actually redundant. In the simplest case
10330 -- it is Pack itself, but when we compile a body we install its
10331 -- context before that of its spec, in which case it is the
10332 -- use_clause in the spec that will appear to be redundant, and we
10333 -- want the warning to be placed on the body. Similar complications
10334 -- appear when the redundancy is between a child unit and one of its
10338 -- Could be renamed...
10340 if No (Cur_Use) then
10341 Cur_Use := Current_Use_Clause (Renamed_Entity (Pack_Name));
10344 Set_Redundant_Use (Clause, True);
10346 -- Do not check for redundant use if clause is generated, or in an
10347 -- instance, or in a predefined unit to avoid misleading warnings
10348 -- that may occur as part of a rtsfind load.
10350 if not Comes_From_Source (Clause)
10351 or else In_Instance
10352 or else not Warn_On_Redundant_Constructs
10353 or else Is_Predefined_Unit (Current_Sem_Unit)
10358 if not Is_Compilation_Unit (Current_Scope) then
10360 -- If the use_clause is in an inner scope, it is made redundant by
10361 -- some clause in the current context, with one exception: If we
10362 -- are compiling a nested package body, and the use_clause comes
10363 -- from then corresponding spec, the clause is not necessarily
10364 -- fully redundant, so we should not warn. If a warning was
10365 -- warranted, it would have been given when the spec was
10368 if Nkind (Parent (Decl)) = N_Package_Specification then
10370 Package_Spec_Entity : constant Entity_Id :=
10371 Defining_Unit_Name (Parent (Decl));
10373 if In_Package_Body (Package_Spec_Entity) then
10379 Redundant := Clause;
10380 Prev_Use := Cur_Use;
10382 elsif Nkind (Unit (Cunit (Current_Sem_Unit))) = N_Package_Body then
10384 Cur_Unit : constant Unit_Number_Type :=
10385 Get_Source_Unit (Cur_Use);
10386 New_Unit : constant Unit_Number_Type :=
10387 Get_Source_Unit (Clause);
10392 if Cur_Unit = New_Unit then
10394 -- Redundant clause in same body
10396 Redundant := Clause;
10397 Prev_Use := Cur_Use;
10399 elsif Cur_Unit = Current_Sem_Unit then
10401 -- If the new clause is not in the current unit it has been
10402 -- analyzed first, and it makes the other one redundant.
10403 -- However, if the new clause appears in a subunit, Cur_Unit
10404 -- is still the parent, and in that case the redundant one
10405 -- is the one appearing in the subunit.
10407 if Nkind (Unit (Cunit (New_Unit))) = N_Subunit then
10408 Redundant := Clause;
10409 Prev_Use := Cur_Use;
10411 -- Most common case: redundant clause in body, original
10412 -- clause in spec. Current scope is spec entity.
10414 elsif Current_Scope = Cunit_Entity (Current_Sem_Unit) then
10415 Redundant := Cur_Use;
10416 Prev_Use := Clause;
10419 -- The new clause may appear in an unrelated unit, when
10420 -- the parents of a generic are being installed prior to
10421 -- instantiation. In this case there must be no warning.
10422 -- We detect this case by checking whether the current
10423 -- top of the stack is related to the current
10426 Scop := Current_Scope;
10427 while Present (Scop)
10428 and then Scop /= Standard_Standard
10430 if Is_Compilation_Unit (Scop)
10431 and then not Is_Child_Unit (Scop)
10435 elsif Scop = Cunit_Entity (Current_Sem_Unit) then
10439 Scop := Scope (Scop);
10442 Redundant := Cur_Use;
10443 Prev_Use := Clause;
10446 elsif New_Unit = Current_Sem_Unit then
10447 Redundant := Clause;
10448 Prev_Use := Cur_Use;
10451 -- Neither is the current unit, so they appear in parent or
10452 -- sibling units. Warning will be emitted elsewhere.
10458 elsif Nkind (Unit (Cunit (Current_Sem_Unit))) = N_Package_Declaration
10459 and then Present (Parent_Spec (Unit (Cunit (Current_Sem_Unit))))
10461 -- Use_clause is in child unit of current unit, and the child unit
10462 -- appears in the context of the body of the parent, so it has
10463 -- been installed first, even though it is the redundant one.
10464 -- Depending on their placement in the context, the visible or the
10465 -- private parts of the two units, either might appear as
10466 -- redundant, but the message has to be on the current unit.
10468 if Get_Source_Unit (Cur_Use) = Current_Sem_Unit then
10469 Redundant := Cur_Use;
10470 Prev_Use := Clause;
10472 Redundant := Clause;
10473 Prev_Use := Cur_Use;
10476 -- If the new use clause appears in the private part of a parent
10477 -- unit it may appear to be redundant w.r.t. a use clause in a
10478 -- child unit, but the previous use clause was needed in the
10479 -- visible part of the child, and no warning should be emitted.
10481 if Nkind (Parent (Decl)) = N_Package_Specification
10482 and then List_Containing (Decl) =
10483 Private_Declarations (Parent (Decl))
10486 Par : constant Entity_Id :=
10487 Defining_Entity (Parent (Decl));
10488 Spec : constant Node_Id :=
10489 Specification (Unit (Cunit (Current_Sem_Unit)));
10490 Cur_List : constant List_Id := List_Containing (Cur_Use);
10493 if Is_Compilation_Unit (Par)
10494 and then Par /= Cunit_Entity (Current_Sem_Unit)
10496 if Cur_List = Context_Items (Cunit (Current_Sem_Unit))
10497 or else Cur_List = Visible_Declarations (Spec)
10505 -- Finally, if the current use clause is in the context then the
10506 -- clause is redundant when it is nested within the unit.
10508 elsif Nkind (Parent (Cur_Use)) = N_Compilation_Unit
10509 and then Nkind (Parent (Parent (Clause))) /= N_Compilation_Unit
10510 and then Get_Source_Unit (Cur_Use) = Get_Source_Unit (Clause)
10512 Redundant := Clause;
10513 Prev_Use := Cur_Use;
10516 if Present (Redundant) and then Parent (Redundant) /= Prev_Use then
10518 -- Make sure we are looking at most-descendant use_package_clause
10519 -- by traversing the chain with Find_First_Use and then verifying
10520 -- there is no scope manipulation via Most_Descendant_Use_Clause.
10522 if Nkind (Prev_Use) = N_Use_Package_Clause
10524 (Nkind (Parent (Prev_Use)) /= N_Compilation_Unit
10525 or else Most_Descendant_Use_Clause
10526 (Prev_Use, Find_First_Use (Prev_Use)) /= Prev_Use)
10528 Prev_Use := Find_First_Use (Prev_Use);
10531 Error_Msg_Sloc := Sloc (Prev_Use);
10532 Error_Msg_NE -- CODEFIX
10533 ("& is already use-visible through previous use_clause #?r?",
10534 Redundant, Pack_Name);
10536 end Note_Redundant_Use;
10540 Current_Instance : Entity_Id := Empty;
10544 Private_With_OK : Boolean := False;
10545 Real_P : Entity_Id;
10547 -- Start of processing for Use_One_Package
10550 -- Use_One_Package may have been called recursively to handle an
10551 -- implicit use for a auxiliary system package, so set P accordingly
10552 -- and skip redundancy checks.
10554 if No (Pack_Name) and then Present_System_Aux (N) then
10555 P := System_Aux_Id;
10557 -- Check for redundant use_package_clauses
10560 -- Ignore cases where we are dealing with a non user defined package
10561 -- like Standard_Standard or something other than a valid package.
10563 if not Is_Entity_Name (Pack_Name)
10564 or else No (Entity (Pack_Name))
10565 or else Ekind (Entity (Pack_Name)) /= E_Package
10570 -- When a renaming exists we must check it for redundancy. The
10571 -- original package would have already been seen at this point.
10573 if Present (Renamed_Entity (Entity (Pack_Name))) then
10574 P := Renamed_Entity (Entity (Pack_Name));
10576 P := Entity (Pack_Name);
10579 -- Check for redundant clauses then set the current use clause for
10580 -- P if were are not "forcing" an installation from a scope
10581 -- reinstallation that is done throughout analysis for various
10585 Note_Redundant_Use (Pack_Name);
10588 Set_Current_Use_Clause (P, N);
10593 -- Warn about detected redundant clauses
10596 and then In_Open_Scopes (P)
10597 and then not Is_Hidden_Open_Scope (P)
10599 if Warn_On_Redundant_Constructs and then P = Current_Scope then
10600 Error_Msg_NE -- CODEFIX
10601 ("& is already use-visible within itself?r?",
10608 -- Set P back to the non-renamed package so that visibility of the
10609 -- entities within the package can be properly set below.
10611 P := Entity (Pack_Name);
10615 Set_Current_Use_Clause (P, N);
10617 -- Ada 2005 (AI-50217): Check restriction
10619 if From_Limited_With (P) then
10620 Error_Msg_N ("limited withed package cannot appear in use clause", N);
10623 -- Find enclosing instance, if any
10625 if In_Instance then
10626 Current_Instance := Current_Scope;
10627 while not Is_Generic_Instance (Current_Instance) loop
10628 Current_Instance := Scope (Current_Instance);
10631 if No (Hidden_By_Use_Clause (N)) then
10632 Set_Hidden_By_Use_Clause (N, New_Elmt_List);
10636 -- If unit is a package renaming, indicate that the renamed package is
10637 -- also in use (the flags on both entities must remain consistent, and a
10638 -- subsequent use of either of them should be recognized as redundant).
10640 if Present (Renamed_Entity (P)) then
10641 Set_In_Use (Renamed_Entity (P));
10642 Set_Current_Use_Clause (Renamed_Entity (P), N);
10643 Real_P := Renamed_Entity (P);
10648 -- Ada 2005 (AI-262): Check the use_clause of a private withed package
10649 -- found in the private part of a package specification
10651 if In_Private_Part (Current_Scope)
10652 and then Has_Private_With (P)
10653 and then Is_Child_Unit (Current_Scope)
10654 and then Is_Child_Unit (P)
10655 and then Is_Ancestor_Package (Scope (Current_Scope), P)
10657 Private_With_OK := True;
10660 -- Loop through entities in one package making them potentially
10663 Id := First_Entity (P);
10665 and then (Id /= First_Private_Entity (P)
10666 or else Private_With_OK) -- Ada 2005 (AI-262)
10668 Prev := Current_Entity (Id);
10669 while Present (Prev) loop
10670 if Is_Immediately_Visible (Prev)
10671 and then (not Is_Overloadable (Prev)
10672 or else not Is_Overloadable (Id)
10673 or else Type_Conformant (Id, Prev))
10675 if No (Current_Instance) then
10677 -- Potentially use-visible entity remains hidden
10679 if Warn_On_Hiding then
10680 Warn_On_Hiding_Entity (N, Hidden => Id, Visible => Prev,
10681 On_Use_Clause => True);
10684 goto Next_Usable_Entity;
10686 -- A use clause within an instance hides outer global entities,
10687 -- which are not used to resolve local entities in the
10688 -- instance. Note that the predefined entities in Standard
10689 -- could not have been hidden in the generic by a use clause,
10690 -- and therefore remain visible. Other compilation units whose
10691 -- entities appear in Standard must be hidden in an instance.
10693 -- To determine whether an entity is external to the instance
10694 -- we compare the scope depth of its scope with that of the
10695 -- current instance. However, a generic actual of a subprogram
10696 -- instance is declared in the wrapper package but will not be
10697 -- hidden by a use-visible entity. similarly, an entity that is
10698 -- declared in an enclosing instance will not be hidden by an
10699 -- an entity declared in a generic actual, which can only have
10700 -- been use-visible in the generic and will not have hidden the
10701 -- entity in the generic parent.
10703 -- If Id is called Standard, the predefined package with the
10704 -- same name is in the homonym chain. It has to be ignored
10705 -- because it has no defined scope (being the only entity in
10706 -- the system with this mandated behavior).
10708 elsif not Is_Hidden (Id)
10709 and then Present (Scope (Prev))
10710 and then not Is_Wrapper_Package (Scope (Prev))
10711 and then Scope_Depth (Scope (Prev)) <
10712 Scope_Depth (Current_Instance)
10713 and then (Scope (Prev) /= Standard_Standard
10714 or else Sloc (Prev) > Standard_Location)
10716 if In_Open_Scopes (Scope (Prev))
10717 and then Is_Generic_Instance (Scope (Prev))
10718 and then Present (Associated_Formal_Package (P))
10723 Set_Is_Potentially_Use_Visible (Id);
10724 Set_Is_Immediately_Visible (Prev, False);
10725 Append_Elmt (Prev, Hidden_By_Use_Clause (N));
10729 -- A user-defined operator is not use-visible if the predefined
10730 -- operator for the type is immediately visible, which is the case
10731 -- if the type of the operand is in an open scope. This does not
10732 -- apply to user-defined operators that have operands of different
10733 -- types, because the predefined mixed mode operations (multiply
10734 -- and divide) apply to universal types and do not hide anything.
10736 elsif Ekind (Prev) = E_Operator
10737 and then Operator_Matches_Spec (Prev, Id)
10738 and then In_Open_Scopes
10739 (Scope (Base_Type (Etype (First_Formal (Id)))))
10740 and then (No (Next_Formal (First_Formal (Id)))
10741 or else Etype (First_Formal (Id)) =
10742 Etype (Next_Formal (First_Formal (Id)))
10743 or else Chars (Prev) = Name_Op_Expon)
10745 goto Next_Usable_Entity;
10747 -- In an instance, two homonyms may become use_visible through the
10748 -- actuals of distinct formal packages. In the generic, only the
10749 -- current one would have been visible, so make the other one
10750 -- not use_visible.
10752 -- In certain pathological cases it is possible that unrelated
10753 -- homonyms from distinct formal packages may exist in an
10754 -- uninstalled scope. We must test for that here.
10756 elsif Present (Current_Instance)
10757 and then Is_Potentially_Use_Visible (Prev)
10758 and then not Is_Overloadable (Prev)
10759 and then Scope (Id) /= Scope (Prev)
10760 and then Used_As_Generic_Actual (Scope (Prev))
10761 and then Used_As_Generic_Actual (Scope (Id))
10762 and then Is_List_Member (Scope (Prev))
10763 and then not In_Same_List (Current_Use_Clause (Scope (Prev)),
10764 Current_Use_Clause (Scope (Id)))
10766 Set_Is_Potentially_Use_Visible (Prev, False);
10767 Append_Elmt (Prev, Hidden_By_Use_Clause (N));
10770 Prev := Homonym (Prev);
10773 -- On exit, we know entity is not hidden, unless it is private
10775 if not Is_Hidden (Id)
10776 and then (not Is_Child_Unit (Id) or else Is_Visible_Lib_Unit (Id))
10778 Set_Is_Potentially_Use_Visible (Id);
10780 if Is_Private_Type (Id) and then Present (Full_View (Id)) then
10781 Set_Is_Potentially_Use_Visible (Full_View (Id));
10785 <<Next_Usable_Entity>>
10789 -- Child units are also made use-visible by a use clause, but they may
10790 -- appear after all visible declarations in the parent entity list.
10792 while Present (Id) loop
10793 if Is_Child_Unit (Id) and then Is_Visible_Lib_Unit (Id) then
10794 Set_Is_Potentially_Use_Visible (Id);
10800 if Chars (Real_P) = Name_System
10801 and then Scope (Real_P) = Standard_Standard
10802 and then Present_System_Aux (N)
10804 Use_One_Package (N);
10806 end Use_One_Package;
10812 procedure Use_One_Type
10814 Installed : Boolean := False;
10815 Force : Boolean := False)
10817 function Spec_Reloaded_For_Body return Boolean;
10818 -- Determine whether the compilation unit is a package body and the use
10819 -- type clause is in the spec of the same package. Even though the spec
10820 -- was analyzed first, its context is reloaded when analysing the body.
10822 procedure Use_Class_Wide_Operations (Typ : Entity_Id);
10823 -- AI05-150: if the use_type_clause carries the "all" qualifier,
10824 -- class-wide operations of ancestor types are use-visible if the
10825 -- ancestor type is visible.
10827 ----------------------------
10828 -- Spec_Reloaded_For_Body --
10829 ----------------------------
10831 function Spec_Reloaded_For_Body return Boolean is
10833 if Nkind (Unit (Cunit (Current_Sem_Unit))) = N_Package_Body then
10835 Spec : constant Node_Id :=
10836 Parent (List_Containing (Parent (Id)));
10839 -- Check whether type is declared in a package specification,
10840 -- and current unit is the corresponding package body. The
10841 -- use clauses themselves may be within a nested package.
10844 Nkind (Spec) = N_Package_Specification
10845 and then In_Same_Source_Unit
10846 (Corresponding_Body (Parent (Spec)),
10847 Cunit_Entity (Current_Sem_Unit));
10852 end Spec_Reloaded_For_Body;
10854 -------------------------------
10855 -- Use_Class_Wide_Operations --
10856 -------------------------------
10858 procedure Use_Class_Wide_Operations (Typ : Entity_Id) is
10859 function Is_Class_Wide_Operation_Of
10861 T : Entity_Id) return Boolean;
10862 -- Determine whether a subprogram has a class-wide parameter or
10863 -- result that is T'Class.
10865 ---------------------------------
10866 -- Is_Class_Wide_Operation_Of --
10867 ---------------------------------
10869 function Is_Class_Wide_Operation_Of
10871 T : Entity_Id) return Boolean
10873 Formal : Entity_Id;
10876 Formal := First_Formal (Op);
10877 while Present (Formal) loop
10878 if Etype (Formal) = Class_Wide_Type (T) then
10882 Next_Formal (Formal);
10885 if Etype (Op) = Class_Wide_Type (T) then
10890 end Is_Class_Wide_Operation_Of;
10897 -- Start of processing for Use_Class_Wide_Operations
10900 Scop := Scope (Typ);
10901 if not Is_Hidden (Scop) then
10902 Ent := First_Entity (Scop);
10903 while Present (Ent) loop
10904 if Is_Overloadable (Ent)
10905 and then Is_Class_Wide_Operation_Of (Ent, Typ)
10906 and then not Is_Potentially_Use_Visible (Ent)
10908 Set_Is_Potentially_Use_Visible (Ent);
10909 Append_Elmt (Ent, Used_Operations (Parent (Id)));
10916 if Is_Derived_Type (Typ) then
10917 Use_Class_Wide_Operations (Etype (Base_Type (Typ)));
10919 end Use_Class_Wide_Operations;
10924 Is_Known_Used : Boolean;
10925 Op_List : Elist_Id;
10928 -- Start of processing for Use_One_Type
10931 if Entity (Id) = Any_Type then
10935 -- It is the type determined by the subtype mark (8.4(8)) whose
10936 -- operations become potentially use-visible.
10938 T := Base_Type (Entity (Id));
10940 -- Either the type itself is used, the package where it is declared is
10941 -- in use or the entity is declared in the current package, thus
10946 and then ((Present (Current_Use_Clause (T))
10947 and then All_Present (Current_Use_Clause (T)))
10948 or else not All_Present (Parent (Id))))
10949 or else In_Use (Scope (T))
10950 or else Scope (T) = Current_Scope;
10952 Set_Redundant_Use (Id,
10953 Is_Known_Used or else Is_Potentially_Use_Visible (T));
10955 if Ekind (T) = E_Incomplete_Type then
10956 Error_Msg_N ("premature usage of incomplete type", Id);
10958 elsif In_Open_Scopes (Scope (T)) then
10961 -- A limited view cannot appear in a use_type_clause. However, an access
10962 -- type whose designated type is limited has the flag but is not itself
10963 -- a limited view unless we only have a limited view of its enclosing
10966 elsif From_Limited_With (T) and then From_Limited_With (Scope (T)) then
10968 ("incomplete type from limited view cannot appear in use clause",
10971 -- If the use clause is redundant, Used_Operations will usually be
10972 -- empty, but we need to set it to empty here in one case: If we are
10973 -- instantiating a generic library unit, then we install the ancestors
10974 -- of that unit in the scope stack, which involves reprocessing use
10975 -- clauses in those ancestors. Such a use clause will typically have a
10976 -- nonempty Used_Operations unless it was redundant in the generic unit,
10977 -- even if it is redundant at the place of the instantiation.
10979 elsif Redundant_Use (Id) then
10980 Set_Used_Operations (Parent (Id), New_Elmt_List);
10982 -- If the subtype mark designates a subtype in a different package,
10983 -- we have to check that the parent type is visible, otherwise the
10984 -- use_type_clause is a no-op. Not clear how to do that???
10987 Set_Current_Use_Clause (T, Parent (Id));
10990 -- If T is tagged, primitive operators on class-wide operands are
10991 -- also deemed available. Note that this is really necessary only
10992 -- in semantics-only mode, because the primitive operators are not
10993 -- fully constructed in this mode, but we do it in all modes for the
10994 -- sake of uniformity, as this should not matter in practice.
10996 if Is_Tagged_Type (T) then
10997 Set_In_Use (Class_Wide_Type (T));
11000 -- Iterate over primitive operations of the type. If an operation is
11001 -- already use_visible, it is the result of a previous use_clause,
11002 -- and already appears on the corresponding entity chain. If the
11003 -- clause is being reinstalled, operations are already use-visible.
11009 Op_List := Collect_Primitive_Operations (T);
11010 Elmt := First_Elmt (Op_List);
11011 while Present (Elmt) loop
11012 if (Nkind (Node (Elmt)) = N_Defining_Operator_Symbol
11013 or else Chars (Node (Elmt)) in Any_Operator_Name)
11014 and then not Is_Hidden (Node (Elmt))
11015 and then not Is_Potentially_Use_Visible (Node (Elmt))
11017 Set_Is_Potentially_Use_Visible (Node (Elmt));
11018 Append_Elmt (Node (Elmt), Used_Operations (Parent (Id)));
11020 elsif Ada_Version >= Ada_2012
11021 and then All_Present (Parent (Id))
11022 and then not Is_Hidden (Node (Elmt))
11023 and then not Is_Potentially_Use_Visible (Node (Elmt))
11025 Set_Is_Potentially_Use_Visible (Node (Elmt));
11026 Append_Elmt (Node (Elmt), Used_Operations (Parent (Id)));
11033 if Ada_Version >= Ada_2012
11034 and then All_Present (Parent (Id))
11035 and then Is_Tagged_Type (T)
11037 Use_Class_Wide_Operations (T);
11041 -- If warning on redundant constructs, check for unnecessary WITH
11044 and then Warn_On_Redundant_Constructs
11045 and then Is_Known_Used
11047 -- with P; with P; use P;
11048 -- package P is package X is package body X is
11049 -- type T ... use P.T;
11051 -- The compilation unit is the body of X. GNAT first compiles the
11052 -- spec of X, then proceeds to the body. At that point P is marked
11053 -- as use visible. The analysis then reinstalls the spec along with
11054 -- its context. The use clause P.T is now recognized as redundant,
11055 -- but in the wrong context. Do not emit a warning in such cases.
11056 -- Do not emit a warning either if we are in an instance, there is
11057 -- no redundancy between an outer use_clause and one that appears
11058 -- within the generic.
11060 and then not Spec_Reloaded_For_Body
11061 and then not In_Instance
11062 and then not In_Inlined_Body
11064 -- The type already has a use clause
11068 -- Case where we know the current use clause for the type
11070 if Present (Current_Use_Clause (T)) then
11071 Use_Clause_Known : declare
11072 Clause1 : constant Node_Id :=
11073 Find_First_Use (Current_Use_Clause (T));
11074 Clause2 : constant Node_Id := Parent (Id);
11081 -- Start of processing for Use_Clause_Known
11084 -- If the unit is a subprogram body that acts as spec, the
11085 -- context clause is shared with the constructed subprogram
11086 -- spec. Clearly there is no redundancy.
11088 if Clause1 = Clause2 then
11092 Unit1 := Unit (Enclosing_Comp_Unit_Node (Clause1));
11093 Unit2 := Unit (Enclosing_Comp_Unit_Node (Clause2));
11095 -- If both clauses are on same unit, or one is the body of
11096 -- the other, or one of them is in a subunit, report
11097 -- redundancy on the later one.
11100 or else Nkind (Unit1) = N_Subunit
11102 (Nkind (Unit2) in N_Package_Body | N_Subprogram_Body
11103 and then Nkind (Unit1) /= Nkind (Unit2)
11104 and then Nkind (Unit1) /= N_Subunit)
11106 Error_Msg_Sloc := Sloc (Clause1);
11107 Error_Msg_NE -- CODEFIX
11108 ("& is already use-visible through previous "
11109 & "use_type_clause #?r?", Clause2, T);
11113 -- If there is a redundant use_type_clause in a child unit
11114 -- determine which of the units is more deeply nested. If a
11115 -- unit is a package instance, retrieve the entity and its
11116 -- scope from the instance spec.
11118 Ent1 := Entity_Of_Unit (Unit1);
11119 Ent2 := Entity_Of_Unit (Unit2);
11121 -- When the scope of both units' entities are
11122 -- Standard_Standard then neither Unit1 or Unit2 are child
11123 -- units - so return in that case.
11125 if Scope
(Ent1
) = Standard_Standard
11126 and then Scope
(Ent2
) = Standard_Standard
11130 -- Otherwise, determine if one of the units is not a child
11132 elsif Scope
(Ent2
) = Standard_Standard
then
11133 Error_Msg_Sloc
:= Sloc
(Clause2
);
11136 elsif Scope
(Ent1
) = Standard_Standard
then
11137 Error_Msg_Sloc
:= Sloc
(Id
);
11140 -- If both units are child units, we determine which one is
11141 -- the descendant by the scope distance to the ultimate
11150 S1
:= Scope
(Ent1
);
11151 S2
:= Scope
(Ent2
);
11153 and then Present
(S2
)
11154 and then S1
/= Standard_Standard
11155 and then S2
/= Standard_Standard
11161 if S1
= Standard_Standard
then
11162 Error_Msg_Sloc
:= Sloc
(Id
);
11165 Error_Msg_Sloc
:= Sloc
(Clause2
);
11171 if Parent
(Id
) /= Err_No
then
11172 if Most_Descendant_Use_Clause
11173 (Err_No
, Parent
(Id
)) = Parent
(Id
)
11175 Error_Msg_Sloc
:= Sloc
(Err_No
);
11176 Err_No
:= Parent
(Id
);
11179 Error_Msg_NE
-- CODEFIX
11180 ("& is already use-visible through previous "
11181 & "use_type_clause #?r?", Err_No
, Id
);
11183 end Use_Clause_Known
;
11185 -- Here Current_Use_Clause is not set for T, so we do not have the
11186 -- location information available.
11189 Error_Msg_NE
-- CODEFIX
11190 ("& is already use-visible through previous "
11191 & "use_type_clause?r?", Id
, T
);
11194 -- The package where T is declared is already used
11196 elsif In_Use
(Scope
(T
)) then
11197 -- Due to expansion of contracts we could be attempting to issue
11198 -- a spurious warning - so verify there is a previous use clause.
11200 if Current_Use_Clause
(Scope
(T
)) /=
11201 Find_First_Use
(Current_Use_Clause
(Scope
(T
)))
11204 Sloc
(Find_First_Use
(Current_Use_Clause
(Scope
(T
))));
11205 Error_Msg_NE
-- CODEFIX
11206 ("& is already use-visible through package use clause #?r?",
11210 -- The current scope is the package where T is declared
11213 Error_Msg_Node_2
:= Scope
(T
);
11214 Error_Msg_NE
-- CODEFIX
11215 ("& is already use-visible inside package &?r?", Id
, T
);
11224 procedure Write_Info
is
11225 Id
: Entity_Id
:= First_Entity
(Current_Scope
);
11228 -- No point in dumping standard entities
11230 if Current_Scope
= Standard_Standard
then
11234 Write_Str
("========================================================");
11236 Write_Str
(" Defined Entities in ");
11237 Write_Name
(Chars
(Current_Scope
));
11239 Write_Str
("========================================================");
11243 Write_Str
("-- none --");
11247 while Present
(Id
) loop
11248 Write_Entity_Info
(Id
, " ");
11253 if Scope
(Current_Scope
) = Standard_Standard
then
11255 -- Print information on the current unit itself
11257 Write_Entity_Info
(Current_Scope
, " ");
11270 for J
in reverse 1 .. Scope_Stack
.Last
loop
11271 S
:= Scope_Stack
.Table
(J
).Entity
;
11272 Write_Int
(Int
(S
));
11273 Write_Str
(" === ");
11274 Write_Name
(Chars
(S
));
11283 procedure we
(S
: Entity_Id
) is
11286 E
:= First_Entity
(S
);
11287 while Present
(E
) loop
11288 Write_Int
(Int
(E
));
11289 Write_Str
(" === ");
11290 Write_Name
(Chars
(E
));