c++: remove some xfails
[official-gcc.git] / gcc / ada / sem_ch8.adb
blobeb9e359e4976adde68ac64e5aa2e74e108ceaed2
1 ------------------------------------------------------------------------------
2 -- --
3 -- GNAT COMPILER COMPONENTS --
4 -- --
5 -- S E M _ C H 8 --
6 -- --
7 -- B o d y --
8 -- --
9 -- Copyright (C) 1992-2022, Free Software Foundation, Inc. --
10 -- --
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. --
20 -- --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
23 -- --
24 ------------------------------------------------------------------------------
26 with Atree; use Atree;
27 with Debug; use Debug;
28 with Einfo; use Einfo;
29 with Einfo.Entities; use Einfo.Entities;
30 with Einfo.Utils; use Einfo.Utils;
31 with Elists; use Elists;
32 with Errout; use Errout;
33 with Exp_Disp; use Exp_Disp;
34 with Exp_Tss; use Exp_Tss;
35 with Exp_Util; use Exp_Util;
36 with Freeze; use Freeze;
37 with Ghost; use Ghost;
38 with Impunit; use Impunit;
39 with Lib; use Lib;
40 with Lib.Load; use Lib.Load;
41 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;
46 with Opt; use Opt;
47 with Output; use Output;
48 with Restrict; use Restrict;
49 with Rident; use Rident;
50 with Rtsfind; use Rtsfind;
51 with Sem; use Sem;
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;
75 with Style;
76 with Table;
77 with Tbuild; use Tbuild;
78 with Uintp; use Uintp;
80 package body Sem_Ch8 is
82 ------------------------------------
83 -- Visibility and Name Resolution --
84 ------------------------------------
86 -- This package handles name resolution and the collection of possible
87 -- interpretations for overloaded names, prior to overload resolution.
89 -- Name resolution is the process that establishes a mapping between source
90 -- identifiers and the entities they denote at each point in the program.
91 -- Each entity is represented by a defining occurrence. Each identifier
92 -- that denotes an entity points to the corresponding defining occurrence.
93 -- This is the entity of the applied occurrence. Each occurrence holds
94 -- an index into the names table, where source identifiers are stored.
96 -- Each entry in the names table for an identifier or designator uses the
97 -- Info pointer to hold a link to the currently visible entity that has
98 -- this name (see subprograms Get_Name_Entity_Id and Set_Name_Entity_Id
99 -- in package Sem_Util). The visibility is initialized at the beginning of
100 -- semantic processing to make entities in package Standard immediately
101 -- visible. The visibility table is used in a more subtle way when
102 -- compiling subunits (see below).
104 -- Entities that have the same name (i.e. homonyms) are chained. In the
105 -- case of overloaded entities, this chain holds all the possible meanings
106 -- of a given identifier. The process of overload resolution uses type
107 -- information to select from this chain the unique meaning of a given
108 -- identifier.
110 -- Entities are also chained in their scope, through the Next_Entity link.
111 -- As a consequence, the name space is organized as a sparse matrix, where
112 -- each row corresponds to a scope, and each column to a source identifier.
113 -- Open scopes, that is to say scopes currently being compiled, have their
114 -- corresponding rows of entities in order, innermost scope first.
116 -- The scopes of packages that are mentioned in context clauses appear in
117 -- no particular order, interspersed among open scopes. This is because
118 -- in the course of analyzing the context of a compilation, a package
119 -- declaration is first an open scope, and subsequently an element of the
120 -- context. If subunits or child units are present, a parent unit may
121 -- appear under various guises at various times in the compilation.
123 -- When the compilation of the innermost scope is complete, the entities
124 -- defined therein are no longer visible. If the scope is not a package
125 -- declaration, these entities are never visible subsequently, and can be
126 -- removed from visibility chains. If the scope is a package declaration,
127 -- its visible declarations may still be accessible. Therefore the entities
128 -- defined in such a scope are left on the visibility chains, and only
129 -- their visibility (immediately visibility or potential use-visibility)
130 -- is affected.
132 -- The ordering of homonyms on their chain does not necessarily follow
133 -- the order of their corresponding scopes on the scope stack. For
134 -- example, if package P and the enclosing scope both contain entities
135 -- named E, then when compiling the package body the chain for E will
136 -- hold the global entity first, and the local one (corresponding to
137 -- the current inner scope) next. As a result, name resolution routines
138 -- do not assume any relative ordering of the homonym chains, either
139 -- for scope nesting or to order of appearance of context clauses.
141 -- When compiling a child unit, entities in the parent scope are always
142 -- immediately visible. When compiling the body of a child unit, private
143 -- entities in the parent must also be made immediately visible. There
144 -- are separate routines to make the visible and private declarations
145 -- visible at various times (see package Sem_Ch7).
147 -- +--------+ +-----+
148 -- | In use |-------->| EU1 |-------------------------->
149 -- +--------+ +-----+
150 -- | |
151 -- +--------+ +-----+ +-----+
152 -- | Stand. |---------------->| ES1 |--------------->| ES2 |--->
153 -- +--------+ +-----+ +-----+
154 -- | |
155 -- +---------+ | +-----+
156 -- | with'ed |------------------------------>| EW2 |--->
157 -- +---------+ | +-----+
158 -- | |
159 -- +--------+ +-----+ +-----+
160 -- | Scope2 |---------------->| E12 |--------------->| E22 |--->
161 -- +--------+ +-----+ +-----+
162 -- | |
163 -- +--------+ +-----+ +-----+
164 -- | Scope1 |---------------->| E11 |--------------->| E12 |--->
165 -- +--------+ +-----+ +-----+
166 -- ^ | |
167 -- | | |
168 -- | +---------+ | |
169 -- | | with'ed |----------------------------------------->
170 -- | +---------+ | |
171 -- | | |
172 -- Scope stack | |
173 -- (innermost first) | |
174 -- +----------------------------+
175 -- Names table => | Id1 | | | | Id2 |
176 -- +----------------------------+
178 -- Name resolution must deal with several syntactic forms: simple names,
179 -- qualified names, indexed names, and various forms of calls.
181 -- Each identifier points to an entry in the names table. The resolution
182 -- of a simple name consists in traversing the homonym chain, starting
183 -- from the names table. If an entry is immediately visible, it is the one
184 -- designated by the identifier. If only potentially use-visible entities
185 -- are on the chain, we must verify that they do not hide each other. If
186 -- the entity we find is overloadable, we collect all other overloadable
187 -- entities on the chain as long as they are not hidden.
189 -- To resolve expanded names, we must find the entity at the intersection
190 -- of the entity chain for the scope (the prefix) and the homonym chain
191 -- for the selector. In general, homonym chains will be much shorter than
192 -- entity chains, so it is preferable to start from the names table as
193 -- well. If the entity found is overloadable, we must collect all other
194 -- interpretations that are defined in the scope denoted by the prefix.
196 -- For records, protected types, and tasks, their local entities are
197 -- removed from visibility chains on exit from the corresponding scope.
198 -- From the outside, these entities are always accessed by selected
199 -- notation, and the entity chain for the record type, protected type,
200 -- etc. is traversed sequentially in order to find the designated entity.
202 -- The discriminants of a type and the operations of a protected type or
203 -- task are unchained on exit from the first view of the type, (such as
204 -- a private or incomplete type declaration, or a protected type speci-
205 -- fication) and re-chained when compiling the second view.
207 -- In the case of operators, we do not make operators on derived types
208 -- explicit. As a result, the notation P."+" may denote either a user-
209 -- defined function with name "+", or else an implicit declaration of the
210 -- operator "+" in package P. The resolution of expanded names always
211 -- tries to resolve an operator name as such an implicitly defined entity,
212 -- in addition to looking for explicit declarations.
214 -- All forms of names that denote entities (simple names, expanded names,
215 -- character literals in some cases) have a Entity attribute, which
216 -- identifies the entity denoted by the name.
218 ---------------------
219 -- The Scope Stack --
220 ---------------------
222 -- The Scope stack keeps track of the scopes currently been compiled.
223 -- Every entity that contains declarations (including records) is placed
224 -- on the scope stack while it is being processed, and removed at the end.
225 -- Whenever a non-package scope is exited, the entities defined therein
226 -- are removed from the visibility table, so that entities in outer scopes
227 -- become visible (see previous description). On entry to Sem, the scope
228 -- stack only contains the package Standard. As usual, subunits complicate
229 -- this picture ever so slightly.
231 -- The Rtsfind mechanism can force a call to Semantics while another
232 -- compilation is in progress. The unit retrieved by Rtsfind must be
233 -- compiled in its own context, and has no access to the visibility of
234 -- the unit currently being compiled. The procedures Save_Scope_Stack and
235 -- Restore_Scope_Stack make entities in current open scopes invisible
236 -- before compiling the retrieved unit, and restore the compilation
237 -- environment afterwards.
239 ------------------------
240 -- Compiling subunits --
241 ------------------------
243 -- Subunits must be compiled in the environment of the corresponding stub,
244 -- that is to say with the same visibility into the parent (and its
245 -- context) that is available at the point of the stub declaration, but
246 -- with the additional visibility provided by the context clause of the
247 -- subunit itself. As a result, compilation of a subunit forces compilation
248 -- of the parent (see description in lib-). At the point of the stub
249 -- declaration, Analyze is called recursively to compile the proper body of
250 -- the subunit, but without reinitializing the names table, nor the scope
251 -- stack (i.e. standard is not pushed on the stack). In this fashion the
252 -- context of the subunit is added to the context of the parent, and the
253 -- subunit is compiled in the correct environment. Note that in the course
254 -- of processing the context of a subunit, Standard will appear twice on
255 -- the scope stack: once for the parent of the subunit, and once for the
256 -- unit in the context clause being compiled. However, the two sets of
257 -- entities are not linked by homonym chains, so that the compilation of
258 -- any context unit happens in a fresh visibility environment.
260 -------------------------------
261 -- Processing of USE Clauses --
262 -------------------------------
264 -- Every defining occurrence has a flag indicating if it is potentially use
265 -- visible. Resolution of simple names examines this flag. The processing
266 -- of use clauses consists in setting this flag on all visible entities
267 -- defined in the corresponding package. On exit from the scope of the use
268 -- clause, the corresponding flag must be reset. However, a package may
269 -- appear in several nested use clauses (pathological but legal, alas)
270 -- which forces us to use a slightly more involved scheme:
272 -- a) The defining occurrence for a package holds a flag -In_Use- to
273 -- indicate that it is currently in the scope of a use clause. If a
274 -- redundant use clause is encountered, then the corresponding occurrence
275 -- of the package name is flagged -Redundant_Use-.
277 -- b) On exit from a scope, the use clauses in its declarative part are
278 -- scanned. The visibility flag is reset in all entities declared in
279 -- package named in a use clause, as long as the package is not flagged
280 -- as being in a redundant use clause (in which case the outer use
281 -- clause is still in effect, and the direct visibility of its entities
282 -- must be retained).
284 -- Note that entities are not removed from their homonym chains on exit
285 -- from the package specification. A subsequent use clause does not need
286 -- to rechain the visible entities, but only to establish their direct
287 -- visibility.
289 -----------------------------------
290 -- Handling private declarations --
291 -----------------------------------
293 -- The principle that each entity has a single defining occurrence clashes
294 -- with the presence of two separate definitions for private types: the
295 -- first is the private type declaration, and second is the full type
296 -- declaration. It is important that all references to the type point to
297 -- the same defining occurrence, namely the first one. To enforce the two
298 -- separate views of the entity, the corresponding information is swapped
299 -- between the two declarations. Outside of the package, the defining
300 -- occurrence only contains the private declaration information, while in
301 -- the private part and the body of the package the defining occurrence
302 -- contains the full declaration. To simplify the swap, the defining
303 -- occurrence that currently holds the private declaration points to the
304 -- full declaration. During semantic processing the defining occurrence
305 -- also points to a list of private dependents, that is to say access types
306 -- or composite types whose designated types or component types are
307 -- subtypes or derived types of the private type in question. After the
308 -- full declaration has been seen, the private dependents are updated to
309 -- indicate that they have full definitions.
311 ------------------------------------
312 -- Handling of Undefined Messages --
313 ------------------------------------
315 -- In normal mode, only the first use of an undefined identifier generates
316 -- a message. The table Urefs is used to record error messages that have
317 -- been issued so that second and subsequent ones do not generate further
318 -- messages. However, the second reference causes text to be added to the
319 -- original undefined message noting "(more references follow)". The
320 -- full error list option (-gnatf) forces messages to be generated for
321 -- every reference and disconnects the use of this table.
323 type Uref_Entry is record
324 Node : Node_Id;
325 -- Node for identifier for which original message was posted. The
326 -- Chars field of this identifier is used to detect later references
327 -- to the same identifier.
329 Err : Error_Msg_Id;
330 -- Records error message Id of original undefined message. Reset to
331 -- No_Error_Msg after the second occurrence, where it is used to add
332 -- text to the original message as described above.
334 Nvis : Boolean;
335 -- Set if the message is not visible rather than undefined
337 Loc : Source_Ptr;
338 -- Records location of error message. Used to make sure that we do
339 -- not consider a, b : undefined as two separate instances, which
340 -- would otherwise happen, since the parser converts this sequence
341 -- to a : undefined; b : undefined.
343 end record;
345 package Urefs is new Table.Table (
346 Table_Component_Type => Uref_Entry,
347 Table_Index_Type => Nat,
348 Table_Low_Bound => 1,
349 Table_Initial => 10,
350 Table_Increment => 100,
351 Table_Name => "Urefs");
353 Candidate_Renaming : Entity_Id;
354 -- Holds a candidate interpretation that appears in a subprogram renaming
355 -- declaration and does not match the given specification, but matches at
356 -- least on the first formal. Allows better error message when given
357 -- specification omits defaulted parameters, a common error.
359 -----------------------
360 -- Local Subprograms --
361 -----------------------
363 procedure Analyze_Generic_Renaming
364 (N : Node_Id;
365 K : Entity_Kind);
366 -- Common processing for all three kinds of generic renaming declarations.
367 -- Enter new name and indicate that it renames the generic unit.
369 procedure Analyze_Renamed_Character
370 (N : Node_Id;
371 New_S : Entity_Id;
372 Is_Body : Boolean);
373 -- Renamed entity is given by a character literal, which must belong
374 -- to the return type of the new entity. Is_Body indicates whether the
375 -- declaration is a renaming_as_body. If the original declaration has
376 -- already been frozen (because of an intervening body, e.g.) the body of
377 -- the function must be built now. The same applies to the following
378 -- various renaming procedures.
380 procedure Analyze_Renamed_Dereference
381 (N : Node_Id;
382 New_S : Entity_Id;
383 Is_Body : Boolean);
384 -- Renamed entity is given by an explicit dereference. Prefix must be a
385 -- conformant access_to_subprogram type.
387 procedure Analyze_Renamed_Entry
388 (N : Node_Id;
389 New_S : Entity_Id;
390 Is_Body : Boolean);
391 -- If the renamed entity in a subprogram renaming is an entry or protected
392 -- subprogram, build a body for the new entity whose only statement is a
393 -- call to the renamed entity.
395 procedure Analyze_Renamed_Family_Member
396 (N : Node_Id;
397 New_S : Entity_Id;
398 Is_Body : Boolean);
399 -- Used when the renamed entity is an indexed component. The prefix must
400 -- denote an entry family.
402 procedure Analyze_Renamed_Primitive_Operation
403 (N : Node_Id;
404 New_S : Entity_Id;
405 Is_Body : Boolean);
406 -- If the renamed entity in a subprogram renaming is a primitive operation
407 -- or a class-wide operation in prefix form, save the target object,
408 -- which must be added to the list of actuals in any subsequent call.
409 -- The renaming operation is intrinsic because the compiler must in
410 -- fact generate a wrapper for it (6.3.1 (10 1/2)).
412 procedure Attribute_Renaming (N : Node_Id);
413 -- Analyze renaming of attribute as subprogram. The renaming declaration N
414 -- is rewritten as a subprogram body that returns the attribute reference
415 -- applied to the formals of the function.
417 procedure Set_Entity_Or_Discriminal (N : Node_Id; E : Entity_Id);
418 -- Set Entity, with style check if need be. For a discriminant reference,
419 -- replace by the corresponding discriminal, i.e. the parameter of the
420 -- initialization procedure that corresponds to the discriminant.
422 procedure Check_Frozen_Renaming (N : Node_Id; Subp : Entity_Id);
423 -- A renaming_as_body may occur after the entity of the original decla-
424 -- ration has been frozen. In that case, the body of the new entity must
425 -- be built now, because the usual mechanism of building the renamed
426 -- body at the point of freezing will not work. Subp is the subprogram
427 -- for which N provides the Renaming_As_Body.
429 procedure Check_In_Previous_With_Clause (N, Nam : Node_Id);
430 -- N is a use_package clause and Nam the package name, or N is a use_type
431 -- clause and Nam is the prefix of the type name. In either case, verify
432 -- that the package is visible at that point in the context: either it
433 -- appears in a previous with_clause, or because it is a fully qualified
434 -- name and the root ancestor appears in a previous with_clause.
436 procedure Check_Library_Unit_Renaming (N : Node_Id; Old_E : Entity_Id);
437 -- Verify that the entity in a renaming declaration that is a library unit
438 -- is itself a library unit and not a nested unit or subunit. Also check
439 -- that if the renaming is a child unit of a generic parent, then the
440 -- renamed unit must also be a child unit of that parent. Finally, verify
441 -- that a renamed generic unit is not an implicit child declared within
442 -- an instance of the parent.
444 procedure Chain_Use_Clause (N : Node_Id);
445 -- Chain use clause onto list of uses clauses headed by First_Use_Clause in
446 -- the proper scope table entry. This is usually the current scope, but it
447 -- will be an inner scope when installing the use clauses of the private
448 -- declarations of a parent unit prior to compiling the private part of a
449 -- child unit. This chain is traversed when installing/removing use clauses
450 -- when compiling a subunit or instantiating a generic body on the fly,
451 -- when it is necessary to save and restore full environments.
453 function Enclosing_Instance return Entity_Id;
454 -- In an instance nested within another one, several semantic checks are
455 -- unnecessary because the legality of the nested instance has been checked
456 -- in the enclosing generic unit. This applies in particular to legality
457 -- checks on actuals for formal subprograms of the inner instance, which
458 -- are checked as subprogram renamings, and may be complicated by confusion
459 -- in private/full views. This function returns the instance enclosing the
460 -- current one if there is such, else it returns Empty.
462 -- If the renaming determines the entity for the default of a formal
463 -- subprogram nested within another instance, choose the innermost
464 -- candidate. This is because if the formal has a box, and we are within
465 -- an enclosing instance where some candidate interpretations are local
466 -- to this enclosing instance, we know that the default was properly
467 -- resolved when analyzing the generic, so we prefer the local
468 -- candidates to those that are external. This is not always the case
469 -- but is a reasonable heuristic on the use of nested generics. The
470 -- proper solution requires a full renaming model.
472 function Entity_Of_Unit (U : Node_Id) return Entity_Id;
473 -- Return the appropriate entity for determining which unit has a deeper
474 -- scope: the defining entity for U, unless U is a package instance, in
475 -- which case we retrieve the entity of the instance spec.
477 procedure Error_Missing_With_Of_Known_Unit (Pkg : Node_Id);
478 -- Display an error message denoting a "with" is missing for a given known
479 -- package Pkg with its full path name.
481 procedure Find_Expanded_Name (N : Node_Id);
482 -- The input is a selected component known to be an expanded name. Verify
483 -- legality of selector given the scope denoted by prefix, and change node
484 -- N into a expanded name with a properly set Entity field.
486 function Find_First_Use (Use_Clause : Node_Id) return Node_Id;
487 -- Find the most previous use clause (that is, the first one to appear in
488 -- the source) by traversing the previous clause chain that exists in both
489 -- N_Use_Package_Clause nodes and N_Use_Type_Clause nodes.
491 function Find_Renamed_Entity
492 (N : Node_Id;
493 Nam : Node_Id;
494 New_S : Entity_Id;
495 Is_Actual : Boolean := False) return Entity_Id;
496 -- Find the renamed entity that corresponds to the given parameter profile
497 -- in a subprogram renaming declaration. The renamed entity may be an
498 -- operator, a subprogram, an entry, or a protected operation. Is_Actual
499 -- indicates that the renaming is the one generated for an actual subpro-
500 -- gram in an instance, for which special visibility checks apply.
502 function Has_Implicit_Character_Literal (N : Node_Id) return Boolean;
503 -- Find a type derived from Character or Wide_Character in the prefix of N.
504 -- Used to resolved qualified names whose selector is a character literal.
506 function Has_Private_With (E : Entity_Id) return Boolean;
507 -- Ada 2005 (AI-262): Determines if the current compilation unit has a
508 -- private with on E.
510 function Has_Components (Typ : Entity_Id) return Boolean;
511 -- Determine if given type has components, i.e. is either a record type or
512 -- type or a type that has discriminants.
514 function Has_Implicit_Operator (N : Node_Id) return Boolean;
515 -- N is an expanded name whose selector is an operator name (e.g. P."+").
516 -- Determine if N denotes an operator implicitly declared in prefix P: P's
517 -- declarative part contains an implicit declaration of an operator if it
518 -- has a declaration of a type to which one of the predefined operators
519 -- apply. The existence of this routine is an implementation artifact. A
520 -- more straightforward but more space-consuming choice would be to make
521 -- all inherited operators explicit in the symbol table.
523 procedure Inherit_Renamed_Profile (New_S : Entity_Id; Old_S : Entity_Id);
524 -- A subprogram defined by a renaming declaration inherits the parameter
525 -- profile of the renamed entity. The subtypes given in the subprogram
526 -- specification are discarded and replaced with those of the renamed
527 -- subprogram, which are then used to recheck the default values.
529 function Most_Descendant_Use_Clause
530 (Clause1 : Entity_Id;
531 Clause2 : Entity_Id) return Entity_Id;
532 -- Determine which use clause parameter is the most descendant in terms of
533 -- scope.
535 procedure Premature_Usage (N : Node_Id);
536 -- Diagnose usage of an entity before it is visible
538 procedure Use_One_Package
539 (N : Node_Id;
540 Pack_Name : Entity_Id := Empty;
541 Force : Boolean := False);
542 -- Make visible entities declared in package P potentially use-visible
543 -- in the current context. Also used in the analysis of subunits, when
544 -- re-installing use clauses of parent units. N is the use_clause that
545 -- names P (and possibly other packages).
547 procedure Use_One_Type
548 (Id : Node_Id;
549 Installed : Boolean := False;
550 Force : Boolean := False);
551 -- Id is the subtype mark from a use_type_clause. This procedure makes
552 -- the primitive operators of the type potentially use-visible. The
553 -- boolean flag Installed indicates that the clause is being reinstalled
554 -- after previous analysis, and primitive operations are already chained
555 -- on the Used_Operations list of the clause.
557 procedure Write_Info;
558 -- Write debugging information on entities declared in current scope
560 --------------------------------
561 -- Analyze_Exception_Renaming --
562 --------------------------------
564 -- The language only allows a single identifier, but the tree holds an
565 -- identifier list. The parser has already issued an error message if
566 -- there is more than one element in the list.
568 procedure Analyze_Exception_Renaming (N : Node_Id) is
569 Id : constant Entity_Id := Defining_Entity (N);
570 Nam : constant Node_Id := Name (N);
572 begin
573 Enter_Name (Id);
574 Analyze (Nam);
576 Mutate_Ekind (Id, E_Exception);
577 Set_Etype (Id, Standard_Exception_Type);
578 Set_Is_Pure (Id, Is_Pure (Current_Scope));
580 if Is_Entity_Name (Nam)
581 and then Present (Entity (Nam))
582 and then Ekind (Entity (Nam)) = E_Exception
583 then
584 if Present (Renamed_Entity (Entity (Nam))) then
585 Set_Renamed_Entity (Id, Renamed_Entity (Entity (Nam)));
586 else
587 Set_Renamed_Entity (Id, Entity (Nam));
588 end if;
590 -- The exception renaming declaration may become Ghost if it renames
591 -- a Ghost entity.
593 Mark_Ghost_Renaming (N, Entity (Nam));
594 else
595 Error_Msg_N ("invalid exception name in renaming", Nam);
596 end if;
598 -- Implementation-defined aspect specifications can appear in a renaming
599 -- declaration, but not language-defined ones. The call to procedure
600 -- Analyze_Aspect_Specifications will take care of this error check.
602 if Has_Aspects (N) then
603 Analyze_Aspect_Specifications (N, Id);
604 end if;
605 end Analyze_Exception_Renaming;
607 ---------------------------
608 -- Analyze_Expanded_Name --
609 ---------------------------
611 procedure Analyze_Expanded_Name (N : Node_Id) is
612 begin
613 -- If the entity pointer is already set, this is an internal node, or a
614 -- node that is analyzed more than once, after a tree modification. In
615 -- such a case there is no resolution to perform, just set the type. In
616 -- either case, start by analyzing the prefix.
618 Analyze (Prefix (N));
620 if Present (Entity (N)) then
621 if Is_Type (Entity (N)) then
622 Set_Etype (N, Entity (N));
623 else
624 Set_Etype (N, Etype (Entity (N)));
625 end if;
627 else
628 Find_Expanded_Name (N);
629 end if;
631 -- In either case, propagate dimension of entity to expanded name
633 Analyze_Dimension (N);
634 end Analyze_Expanded_Name;
636 ---------------------------------------
637 -- Analyze_Generic_Function_Renaming --
638 ---------------------------------------
640 procedure Analyze_Generic_Function_Renaming (N : Node_Id) is
641 begin
642 Analyze_Generic_Renaming (N, E_Generic_Function);
643 end Analyze_Generic_Function_Renaming;
645 --------------------------------------
646 -- Analyze_Generic_Package_Renaming --
647 --------------------------------------
649 procedure Analyze_Generic_Package_Renaming (N : Node_Id) is
650 begin
651 -- Test for the Text_IO special unit case here, since we may be renaming
652 -- one of the subpackages of Text_IO, then join common routine.
654 Check_Text_IO_Special_Unit (Name (N));
656 Analyze_Generic_Renaming (N, E_Generic_Package);
657 end Analyze_Generic_Package_Renaming;
659 ----------------------------------------
660 -- Analyze_Generic_Procedure_Renaming --
661 ----------------------------------------
663 procedure Analyze_Generic_Procedure_Renaming (N : Node_Id) is
664 begin
665 Analyze_Generic_Renaming (N, E_Generic_Procedure);
666 end Analyze_Generic_Procedure_Renaming;
668 ------------------------------
669 -- Analyze_Generic_Renaming --
670 ------------------------------
672 procedure Analyze_Generic_Renaming
673 (N : Node_Id;
674 K : Entity_Kind)
676 New_P : constant Entity_Id := Defining_Entity (N);
677 Inst : Boolean := False;
678 Old_P : Entity_Id;
680 begin
681 if Name (N) = Error then
682 return;
683 end if;
685 Generate_Definition (New_P);
687 if Current_Scope /= Standard_Standard then
688 Set_Is_Pure (New_P, Is_Pure (Current_Scope));
689 end if;
691 if Nkind (Name (N)) = N_Selected_Component then
692 Check_Generic_Child_Unit (Name (N), Inst);
693 else
694 Analyze (Name (N));
695 end if;
697 if not Is_Entity_Name (Name (N)) then
698 Error_Msg_N ("expect entity name in renaming declaration", Name (N));
699 Old_P := Any_Id;
700 else
701 Old_P := Entity (Name (N));
702 end if;
704 Enter_Name (New_P);
705 Mutate_Ekind (New_P, K);
707 if Etype (Old_P) = Any_Type then
708 null;
710 elsif Ekind (Old_P) /= K then
711 Error_Msg_N ("invalid generic unit name", Name (N));
713 else
714 if Present (Renamed_Entity (Old_P)) then
715 Set_Renamed_Entity (New_P, Renamed_Entity (Old_P));
716 else
717 Set_Renamed_Entity (New_P, Old_P);
718 end if;
720 -- The generic renaming declaration may become Ghost if it renames a
721 -- Ghost entity.
723 Mark_Ghost_Renaming (N, Old_P);
725 Set_Is_Pure (New_P, Is_Pure (Old_P));
726 Set_Is_Preelaborated (New_P, Is_Preelaborated (Old_P));
728 Set_Etype (New_P, Etype (Old_P));
729 Set_Has_Completion (New_P);
731 if In_Open_Scopes (Old_P) then
732 Error_Msg_N ("within its scope, generic denotes its instance", N);
733 end if;
735 -- For subprograms, propagate the Intrinsic flag, to allow, e.g.
736 -- renamings and subsequent instantiations of Unchecked_Conversion.
738 if Is_Generic_Subprogram (Old_P) then
739 Set_Is_Intrinsic_Subprogram
740 (New_P, Is_Intrinsic_Subprogram (Old_P));
741 end if;
743 Check_Library_Unit_Renaming (N, Old_P);
744 end if;
746 -- Implementation-defined aspect specifications can appear in a renaming
747 -- declaration, but not language-defined ones. The call to procedure
748 -- Analyze_Aspect_Specifications will take care of this error check.
750 if Has_Aspects (N) then
751 Analyze_Aspect_Specifications (N, New_P);
752 end if;
753 end Analyze_Generic_Renaming;
755 -----------------------------
756 -- Analyze_Object_Renaming --
757 -----------------------------
759 procedure Analyze_Object_Renaming (N : Node_Id) is
760 Id : constant Entity_Id := Defining_Identifier (N);
761 Loc : constant Source_Ptr := Sloc (N);
762 Nam : constant Node_Id := Name (N);
763 Is_Object_Ref : Boolean;
764 Dec : Node_Id;
765 T : Entity_Id;
766 T2 : Entity_Id;
767 Q : Node_Id;
769 procedure Check_Constrained_Object;
770 -- If the nominal type is unconstrained but the renamed object is
771 -- constrained, as can happen with renaming an explicit dereference or
772 -- a function return, build a constrained subtype from the object. If
773 -- the renaming is for a formal in an accept statement, the analysis
774 -- has already established its actual subtype. This is only relevant
775 -- if the renamed object is an explicit dereference.
777 function Get_Object_Name (Nod : Node_Id) return Node_Id;
778 -- Obtain the name of the object from node Nod which is being renamed by
779 -- the object renaming declaration N.
781 function Find_Raise_Node (N : Node_Id) return Traverse_Result;
782 -- Process one node in search for N_Raise_xxx_Error nodes.
783 -- Return Abandon if found, OK otherwise.
785 ---------------------
786 -- Find_Raise_Node --
787 ---------------------
789 function Find_Raise_Node (N : Node_Id) return Traverse_Result is
790 begin
791 if Nkind (N) in N_Raise_xxx_Error then
792 return Abandon;
793 else
794 return OK;
795 end if;
796 end Find_Raise_Node;
798 ------------------------
799 -- No_Raise_xxx_Error --
800 ------------------------
802 function No_Raise_xxx_Error is new Traverse_Func (Find_Raise_Node);
803 -- Traverse tree to look for a N_Raise_xxx_Error node and returns
804 -- Abandon if so and OK if none found.
806 ------------------------------
807 -- Check_Constrained_Object --
808 ------------------------------
810 procedure Check_Constrained_Object is
811 Typ : constant Entity_Id := Etype (Nam);
812 Subt : Entity_Id;
813 Loop_Scheme : Node_Id;
815 begin
816 if Nkind (Nam) in N_Function_Call | N_Explicit_Dereference
817 and then Is_Composite_Type (Typ)
818 and then not Is_Constrained (Typ)
819 and then not Has_Unknown_Discriminants (Typ)
820 and then Expander_Active
821 then
822 -- If Actual_Subtype is already set, nothing to do
824 if Ekind (Id) in E_Variable | E_Constant
825 and then Present (Actual_Subtype (Id))
826 then
827 null;
829 -- A renaming of an unchecked union has no actual subtype
831 elsif Is_Unchecked_Union (Typ) then
832 null;
834 -- If a record is limited its size is invariant. This is the case
835 -- in particular with record types with an access discriminant
836 -- that are used in iterators. This is an optimization, but it
837 -- also prevents typing anomalies when the prefix is further
838 -- expanded.
840 -- Note that we cannot just use the Is_Limited_Record flag because
841 -- it does not apply to records with limited components, for which
842 -- this syntactic flag is not set, but whose size is also fixed.
844 -- Note also that we need to build the constrained subtype for an
845 -- array in order to make the bounds explicit in most cases, but
846 -- not if the object comes from an extended return statement, as
847 -- this would create dangling references to them later on.
849 elsif Is_Limited_Type (Typ)
850 and then (not Is_Array_Type (Typ) or else Is_Return_Object (Id))
851 then
852 null;
854 else
855 Subt := Make_Temporary (Loc, 'T');
856 Remove_Side_Effects (Nam);
857 Insert_Action (N,
858 Make_Subtype_Declaration (Loc,
859 Defining_Identifier => Subt,
860 Subtype_Indication =>
861 Make_Subtype_From_Expr (Nam, Typ)));
862 Rewrite (Subtype_Mark (N), New_Occurrence_Of (Subt, Loc));
863 Set_Etype (Nam, Subt);
865 -- Suppress discriminant checks on this subtype if the original
866 -- type has defaulted discriminants and Id is a "for of" loop
867 -- iterator.
869 if Has_Defaulted_Discriminants (Typ)
870 and then Nkind (Original_Node (Parent (N))) = N_Loop_Statement
871 then
872 Loop_Scheme := Iteration_Scheme (Original_Node (Parent (N)));
874 if Present (Loop_Scheme)
875 and then Present (Iterator_Specification (Loop_Scheme))
876 and then
877 Defining_Identifier
878 (Iterator_Specification (Loop_Scheme)) = Id
879 then
880 Set_Checks_May_Be_Suppressed (Subt);
881 Push_Local_Suppress_Stack_Entry
882 (Entity => Subt,
883 Check => Discriminant_Check,
884 Suppress => True);
885 end if;
886 end if;
888 -- Freeze subtype at once, to prevent order of elaboration
889 -- issues in the backend. The renamed object exists, so its
890 -- type is already frozen in any case.
892 Freeze_Before (N, Subt);
893 end if;
894 end if;
895 end Check_Constrained_Object;
897 ---------------------
898 -- Get_Object_Name --
899 ---------------------
901 function Get_Object_Name (Nod : Node_Id) return Node_Id is
902 Obj_Nam : Node_Id;
904 begin
905 Obj_Nam := Nod;
906 while Present (Obj_Nam) loop
907 case Nkind (Obj_Nam) is
908 when N_Attribute_Reference
909 | N_Explicit_Dereference
910 | N_Indexed_Component
911 | N_Slice
913 Obj_Nam := Prefix (Obj_Nam);
915 when N_Selected_Component =>
916 Obj_Nam := Selector_Name (Obj_Nam);
918 when N_Qualified_Expression | N_Type_Conversion =>
919 Obj_Nam := Expression (Obj_Nam);
921 when others =>
922 exit;
923 end case;
924 end loop;
926 return Obj_Nam;
927 end Get_Object_Name;
929 -- Start of processing for Analyze_Object_Renaming
931 begin
932 if Nam = Error then
933 return;
934 end if;
936 Set_Is_Pure (Id, Is_Pure (Current_Scope));
937 Enter_Name (Id);
939 -- The renaming of a component that depends on a discriminant requires
940 -- an actual subtype, because in subsequent use of the object Gigi will
941 -- be unable to locate the actual bounds. This explicit step is required
942 -- when the renaming is generated in removing side effects of an
943 -- already-analyzed expression.
945 if Nkind (Nam) = N_Selected_Component and then Analyzed (Nam) then
947 -- The object renaming declaration may become Ghost if it renames a
948 -- Ghost entity.
950 if Is_Entity_Name (Nam) then
951 Mark_Ghost_Renaming (N, Entity (Nam));
952 end if;
954 T := Etype (Nam);
955 Dec := Build_Actual_Subtype_Of_Component (Etype (Nam), Nam);
957 if Present (Dec) then
958 Insert_Action (N, Dec);
959 T := Defining_Identifier (Dec);
960 Set_Etype (Nam, T);
961 end if;
962 elsif Present (Subtype_Mark (N))
963 or else not Present (Access_Definition (N))
964 then
965 if Present (Subtype_Mark (N)) then
966 Find_Type (Subtype_Mark (N));
967 T := Entity (Subtype_Mark (N));
968 Analyze (Nam);
970 -- AI12-0275: Case of object renaming without a subtype_mark
972 else
973 Analyze (Nam);
975 -- Normal case of no overloading in object name
977 if not Is_Overloaded (Nam) then
979 -- Catch error cases (such as attempting to rename a procedure
980 -- or package) using the shorthand form.
982 if No (Etype (Nam))
983 or else Etype (Nam) = Standard_Void_Type
984 then
985 Error_Msg_N
986 ("object name or value expected in renaming", Nam);
988 Mutate_Ekind (Id, E_Variable);
989 Set_Etype (Id, Any_Type);
991 return;
993 else
994 T := Etype (Nam);
995 end if;
997 -- Case of overloaded name, which will be illegal if there's more
998 -- than one acceptable interpretation (such as overloaded function
999 -- calls).
1001 else
1002 declare
1003 I : Interp_Index;
1004 I1 : Interp_Index;
1005 It : Interp;
1006 It1 : Interp;
1007 Nam1 : Entity_Id;
1009 begin
1010 -- More than one candidate interpretation is available
1012 -- Remove procedure calls, which syntactically cannot appear
1013 -- in this context, but which cannot be removed by type
1014 -- checking, because the context does not impose a type.
1016 Get_First_Interp (Nam, I, It);
1017 while Present (It.Typ) loop
1018 if It.Typ = Standard_Void_Type then
1019 Remove_Interp (I);
1020 end if;
1022 Get_Next_Interp (I, It);
1023 end loop;
1025 Get_First_Interp (Nam, I, It);
1026 I1 := I;
1027 It1 := It;
1029 -- If there's no type present, we have an error case (such
1030 -- as overloaded procedures named in the object renaming).
1032 if No (It.Typ) then
1033 Error_Msg_N
1034 ("object name or value expected in renaming", Nam);
1036 Mutate_Ekind (Id, E_Variable);
1037 Set_Etype (Id, Any_Type);
1039 return;
1040 end if;
1042 Get_Next_Interp (I, It);
1044 if Present (It.Typ) then
1045 Nam1 := It1.Nam;
1046 It1 := Disambiguate (Nam, I1, I, Any_Type);
1048 if It1 = No_Interp then
1049 Error_Msg_N ("ambiguous name in object renaming", Nam);
1051 Error_Msg_Sloc := Sloc (It.Nam);
1052 Error_Msg_N ("\\possible interpretation#!", Nam);
1054 Error_Msg_Sloc := Sloc (Nam1);
1055 Error_Msg_N ("\\possible interpretation#!", Nam);
1057 return;
1058 end if;
1059 end if;
1061 Set_Etype (Nam, It1.Typ);
1062 T := It1.Typ;
1063 end;
1064 end if;
1066 if Etype (Nam) = Standard_Exception_Type then
1067 Error_Msg_N
1068 ("exception requires a subtype mark in renaming", Nam);
1069 return;
1070 end if;
1071 end if;
1073 -- The object renaming declaration may become Ghost if it renames a
1074 -- Ghost entity.
1076 if Is_Entity_Name (Nam) then
1077 Mark_Ghost_Renaming (N, Entity (Nam));
1078 end if;
1080 -- Check against AI12-0401 here before Resolve may rewrite Nam and
1081 -- potentially generate spurious warnings.
1083 -- In the case where the object_name is a qualified_expression with
1084 -- a nominal subtype T and whose expression is a name that denotes
1085 -- an object Q:
1086 -- * if T is an elementary subtype, then:
1087 -- * Q shall be a constant other than a dereference of an access
1088 -- type; or
1089 -- * the nominal subtype of Q shall be statically compatible with
1090 -- T; or
1091 -- * T shall statically match the base subtype of its type if
1092 -- scalar, or the first subtype of its type if an access type.
1093 -- * if T is a composite subtype, then Q shall be known to be
1094 -- constrained or T shall statically match the first subtype of
1095 -- its type.
1097 if Nkind (Nam) = N_Qualified_Expression
1098 and then Is_Object_Reference (Expression (Nam))
1099 then
1100 Q := Expression (Nam);
1102 if (Is_Elementary_Type (T)
1103 and then
1104 not ((not Is_Variable (Q)
1105 and then Nkind (Q) /= N_Explicit_Dereference)
1106 or else Subtypes_Statically_Compatible (Etype (Q), T)
1107 or else (Is_Scalar_Type (T)
1108 and then Subtypes_Statically_Match
1109 (T, Base_Type (T)))
1110 or else (Is_Access_Type (T)
1111 and then Subtypes_Statically_Match
1112 (T, First_Subtype (T)))))
1113 or else (Is_Composite_Type (T)
1114 and then
1116 -- If Q is an aggregate, Is_Constrained may not be set
1117 -- yet and its type may not be resolved yet.
1118 -- This doesn't quite correspond to the complex notion
1119 -- of "known to be constrained" but this is good enough
1120 -- for a rule which is in any case too complex.
1122 not (Is_Constrained (Etype (Q))
1123 or else Nkind (Q) = N_Aggregate
1124 or else Subtypes_Statically_Match
1125 (T, First_Subtype (T))))
1126 then
1127 Error_Msg_N
1128 ("subtype of renamed qualified expression does not " &
1129 "statically match", N);
1130 return;
1131 end if;
1132 end if;
1134 Resolve (Nam, T);
1136 -- If the renamed object is a function call of a limited type,
1137 -- the expansion of the renaming is complicated by the presence
1138 -- of various temporaries and subtypes that capture constraints
1139 -- of the renamed object. Rewrite node as an object declaration,
1140 -- whose expansion is simpler. Given that the object is limited
1141 -- there is no copy involved and no performance hit.
1143 if Nkind (Nam) = N_Function_Call
1144 and then Is_Limited_View (Etype (Nam))
1145 and then not Is_Constrained (Etype (Nam))
1146 and then Comes_From_Source (N)
1147 then
1148 Set_Etype (Id, T);
1149 Mutate_Ekind (Id, E_Constant);
1150 Rewrite (N,
1151 Make_Object_Declaration (Loc,
1152 Defining_Identifier => Id,
1153 Constant_Present => True,
1154 Object_Definition => New_Occurrence_Of (Etype (Nam), Loc),
1155 Expression => Relocate_Node (Nam)));
1156 return;
1157 end if;
1159 -- Ada 2012 (AI05-149): Reject renaming of an anonymous access object
1160 -- when renaming declaration has a named access type. The Ada 2012
1161 -- coverage rules allow an anonymous access type in the context of
1162 -- an expected named general access type, but the renaming rules
1163 -- require the types to be the same. (An exception is when the type
1164 -- of the renaming is also an anonymous access type, which can only
1165 -- happen due to a renaming created by the expander.)
1167 if Nkind (Nam) = N_Type_Conversion
1168 and then not Comes_From_Source (Nam)
1169 and then Is_Anonymous_Access_Type (Etype (Expression (Nam)))
1170 and then not Is_Anonymous_Access_Type (T)
1171 then
1172 Error_Msg_NE
1173 ("cannot rename anonymous access object "
1174 & "as a named access type", Expression (Nam), T);
1175 end if;
1177 -- Check that a class-wide object is not being renamed as an object
1178 -- of a specific type. The test for access types is needed to exclude
1179 -- cases where the renamed object is a dynamically tagged access
1180 -- result, such as occurs in certain expansions.
1182 if Is_Tagged_Type (T) then
1183 Check_Dynamically_Tagged_Expression
1184 (Expr => Nam,
1185 Typ => T,
1186 Related_Nod => N);
1187 end if;
1189 -- Ada 2005 (AI-230/AI-254): Access renaming
1191 else pragma Assert (Present (Access_Definition (N)));
1192 T :=
1193 Access_Definition
1194 (Related_Nod => N,
1195 N => Access_Definition (N));
1197 Analyze (Nam);
1199 -- The object renaming declaration may become Ghost if it renames a
1200 -- Ghost entity.
1202 if Is_Entity_Name (Nam) then
1203 Mark_Ghost_Renaming (N, Entity (Nam));
1204 end if;
1206 -- Ada 2005 AI05-105: if the declaration has an anonymous access
1207 -- type, the renamed object must also have an anonymous type, and
1208 -- this is a name resolution rule. This was implicit in the last part
1209 -- of the first sentence in 8.5.1(3/2), and is made explicit by this
1210 -- recent AI.
1212 if not Is_Overloaded (Nam) then
1213 if Ekind (Etype (Nam)) /= Ekind (T) then
1214 Error_Msg_N
1215 ("expect anonymous access type in object renaming", N);
1216 end if;
1218 else
1219 declare
1220 I : Interp_Index;
1221 It : Interp;
1222 Typ : Entity_Id := Empty;
1223 Seen : Boolean := False;
1225 begin
1226 Get_First_Interp (Nam, I, It);
1227 while Present (It.Typ) loop
1229 -- Renaming is ambiguous if more than one candidate
1230 -- interpretation is type-conformant with the context.
1232 if Ekind (It.Typ) = Ekind (T) then
1233 if Ekind (T) = E_Anonymous_Access_Subprogram_Type
1234 and then
1235 Type_Conformant
1236 (Designated_Type (T), Designated_Type (It.Typ))
1237 then
1238 if not Seen then
1239 Seen := True;
1240 else
1241 Error_Msg_N
1242 ("ambiguous expression in renaming", Nam);
1243 end if;
1245 elsif Ekind (T) = E_Anonymous_Access_Type
1246 and then
1247 Covers (Designated_Type (T), Designated_Type (It.Typ))
1248 then
1249 if not Seen then
1250 Seen := True;
1251 else
1252 Error_Msg_N
1253 ("ambiguous expression in renaming", Nam);
1254 end if;
1255 end if;
1257 if Covers (T, It.Typ) then
1258 Typ := It.Typ;
1259 Set_Etype (Nam, Typ);
1260 Set_Is_Overloaded (Nam, False);
1261 end if;
1262 end if;
1264 Get_Next_Interp (I, It);
1265 end loop;
1266 end;
1267 end if;
1269 Resolve (Nam, T);
1271 -- Do not perform the legality checks below when the resolution of
1272 -- the renaming name failed because the associated type is Any_Type.
1274 if Etype (Nam) = Any_Type then
1275 null;
1277 -- Ada 2005 (AI-231): In the case where the type is defined by an
1278 -- access_definition, the renamed entity shall be of an access-to-
1279 -- constant type if and only if the access_definition defines an
1280 -- access-to-constant type. ARM 8.5.1(4)
1282 elsif Constant_Present (Access_Definition (N))
1283 and then not Is_Access_Constant (Etype (Nam))
1284 then
1285 Error_Msg_N
1286 ("(Ada 2005): the renamed object is not access-to-constant "
1287 & "(RM 8.5.1(6))", N);
1289 elsif not Constant_Present (Access_Definition (N))
1290 and then Is_Access_Constant (Etype (Nam))
1291 then
1292 Error_Msg_N
1293 ("(Ada 2005): the renamed object is not access-to-variable "
1294 & "(RM 8.5.1(6))", N);
1295 end if;
1297 if Is_Access_Subprogram_Type (Etype (Nam)) then
1298 Check_Subtype_Conformant
1299 (Designated_Type (T), Designated_Type (Etype (Nam)));
1301 elsif not Subtypes_Statically_Match
1302 (Designated_Type (T),
1303 Available_View (Designated_Type (Etype (Nam))))
1304 then
1305 Error_Msg_N
1306 ("subtype of renamed object does not statically match", N);
1307 end if;
1308 end if;
1310 -- Special processing for renaming function return object. Some errors
1311 -- and warnings are produced only for calls that come from source.
1313 if Nkind (Nam) = N_Function_Call then
1314 case Ada_Version is
1316 -- Usage is illegal in Ada 83, but renamings are also introduced
1317 -- during expansion, and error does not apply to those.
1319 when Ada_83 =>
1320 if Comes_From_Source (N) then
1321 Error_Msg_N
1322 ("(Ada 83) cannot rename function return object", Nam);
1323 end if;
1325 -- In Ada 95, warn for odd case of renaming parameterless function
1326 -- call if this is not a limited type (where this is useful).
1328 when others =>
1329 if Warn_On_Object_Renames_Function
1330 and then No (Parameter_Associations (Nam))
1331 and then not Is_Limited_Type (Etype (Nam))
1332 and then Comes_From_Source (Nam)
1333 then
1334 Error_Msg_N
1335 ("renaming function result object is suspicious?.r?", Nam);
1336 Error_Msg_NE
1337 ("\function & will be called only once?.r?", Nam,
1338 Entity (Name (Nam)));
1339 Error_Msg_N -- CODEFIX
1340 ("\suggest using an initialized constant object "
1341 & "instead?.r?", Nam);
1342 end if;
1343 end case;
1344 end if;
1346 Check_Constrained_Object;
1348 -- An object renaming requires an exact match of the type. Class-wide
1349 -- matching is not allowed.
1351 if Is_Class_Wide_Type (T)
1352 and then Base_Type (Etype (Nam)) /= Base_Type (T)
1353 then
1354 Wrong_Type (Nam, T);
1355 end if;
1357 -- We must search for an actual subtype here so that the bounds of
1358 -- objects of unconstrained types don't get dropped on the floor - such
1359 -- as with renamings of formal parameters.
1361 T2 := Get_Actual_Subtype_If_Available (Nam);
1363 -- Ada 2005 (AI-326): Handle wrong use of incomplete type
1365 if Nkind (Nam) = N_Explicit_Dereference
1366 and then Ekind (Etype (T2)) = E_Incomplete_Type
1367 then
1368 Error_Msg_NE ("invalid use of incomplete type&", Id, T2);
1369 return;
1371 elsif Ekind (Etype (T)) = E_Incomplete_Type then
1372 Error_Msg_NE ("invalid use of incomplete type&", Id, T);
1373 return;
1374 end if;
1376 if Ada_Version >= Ada_2005 and then Nkind (Nam) in N_Has_Entity then
1377 declare
1378 Nam_Ent : constant Entity_Id := Entity (Get_Object_Name (Nam));
1379 Nam_Decl : constant Node_Id := Declaration_Node (Nam_Ent);
1381 begin
1382 if Has_Null_Exclusion (N)
1383 and then not Has_Null_Exclusion (Nam_Decl)
1384 then
1385 -- Ada 2005 (AI-423): If the object name denotes a generic
1386 -- formal object of a generic unit G, and the object renaming
1387 -- declaration occurs within the body of G or within the body
1388 -- of a generic unit declared within the declarative region
1389 -- of G, then the declaration of the formal object of G must
1390 -- have a null exclusion or a null-excluding subtype.
1392 if Is_Formal_Object (Nam_Ent)
1393 and then In_Generic_Scope (Id)
1394 then
1395 if not Can_Never_Be_Null (Etype (Nam_Ent)) then
1396 Error_Msg_N
1397 ("object does not exclude `NULL` "
1398 & "(RM 8.5.1(4.6/2))", N);
1400 elsif In_Package_Body (Scope (Id)) then
1401 Error_Msg_N
1402 ("formal object does not have a null exclusion"
1403 & "(RM 8.5.1(4.6/2))", N);
1404 end if;
1406 -- Ada 2005 (AI-423): Otherwise, the subtype of the object name
1407 -- shall exclude null.
1409 elsif not Can_Never_Be_Null (Etype (Nam_Ent)) then
1410 Error_Msg_N
1411 ("object does not exclude `NULL` "
1412 & "(RM 8.5.1(4.6/2))", N);
1414 -- An instance is illegal if it contains a renaming that
1415 -- excludes null, and the actual does not. The renaming
1416 -- declaration has already indicated that the declaration
1417 -- of the renamed actual in the instance will raise
1418 -- constraint_error.
1420 elsif Nkind (Nam_Decl) = N_Object_Declaration
1421 and then In_Instance
1422 and then
1423 Present (Corresponding_Generic_Association (Nam_Decl))
1424 and then Nkind (Expression (Nam_Decl)) =
1425 N_Raise_Constraint_Error
1426 then
1427 Error_Msg_N
1428 ("actual does not exclude `NULL` (RM 8.5.1(4.6/2))", N);
1430 -- Finally, if there is a null exclusion, the subtype mark
1431 -- must not be null-excluding.
1433 elsif No (Access_Definition (N))
1434 and then Can_Never_Be_Null (T)
1435 then
1436 Error_Msg_NE
1437 ("`NOT NULL` not allowed (& already excludes null)",
1438 N, T);
1440 end if;
1442 elsif Can_Never_Be_Null (T)
1443 and then not Can_Never_Be_Null (Etype (Nam_Ent))
1444 then
1445 Error_Msg_N
1446 ("object does not exclude `NULL` (RM 8.5.1(4.6/2))", N);
1448 elsif Has_Null_Exclusion (N)
1449 and then No (Access_Definition (N))
1450 and then Can_Never_Be_Null (T)
1451 then
1452 Error_Msg_NE
1453 ("`NOT NULL` not allowed (& already excludes null)", N, T);
1454 end if;
1455 end;
1456 end if;
1458 -- Set the Ekind of the entity, unless it has been set already, as is
1459 -- the case for the iteration object over a container with no variable
1460 -- indexing. In that case it's been marked as a constant, and we do not
1461 -- want to change it to a variable.
1463 if Ekind (Id) /= E_Constant then
1464 Mutate_Ekind (Id, E_Variable);
1465 end if;
1467 Reinit_Object_Size_Align (Id);
1469 -- If N comes from source then check that the original node is an
1470 -- object reference since there may have been several rewritting and
1471 -- folding. Do not do this for N_Function_Call or N_Explicit_Dereference
1472 -- which might correspond to rewrites of e.g. N_Selected_Component
1473 -- (for example Object.Method rewriting).
1474 -- If N does not come from source then assume the tree is properly
1475 -- formed and accept any object reference. In such cases we do support
1476 -- more cases of renamings anyway, so the actual check on which renaming
1477 -- is valid is better left to the code generator as a last sanity
1478 -- check.
1480 if Comes_From_Source (N) then
1481 if Nkind (Nam) in N_Function_Call | N_Explicit_Dereference then
1482 Is_Object_Ref := Is_Object_Reference (Nam);
1483 else
1484 Is_Object_Ref := Is_Object_Reference (Original_Node (Nam));
1485 end if;
1486 else
1487 Is_Object_Ref := True;
1488 end if;
1490 if T = Any_Type or else Etype (Nam) = Any_Type then
1491 return;
1493 -- Verify that the renamed entity is an object or function call
1495 elsif Is_Object_Ref then
1496 if Comes_From_Source (N) then
1497 if Is_Dependent_Component_Of_Mutable_Object (Nam) then
1498 Error_Msg_N
1499 ("illegal renaming of discriminant-dependent component", Nam);
1500 end if;
1502 -- If the renaming comes from source and the renamed object is a
1503 -- dereference, then mark the prefix as needing debug information,
1504 -- since it might have been rewritten hence internally generated
1505 -- and Debug_Renaming_Declaration will link the renaming to it.
1507 if Nkind (Nam) = N_Explicit_Dereference
1508 and then Is_Entity_Name (Prefix (Nam))
1509 then
1510 Set_Debug_Info_Needed (Entity (Prefix (Nam)));
1511 end if;
1512 end if;
1514 -- Weird but legal, equivalent to renaming a function call. Illegal
1515 -- if the literal is the result of constant-folding an attribute
1516 -- reference that is not a function.
1518 elsif Is_Entity_Name (Nam)
1519 and then Ekind (Entity (Nam)) = E_Enumeration_Literal
1520 and then Nkind (Original_Node (Nam)) /= N_Attribute_Reference
1521 then
1522 null;
1524 -- A named number can only be renamed without a subtype mark
1526 elsif Nkind (Nam) in N_Real_Literal | N_Integer_Literal
1527 and then Present (Subtype_Mark (N))
1528 and then Present (Original_Entity (Nam))
1529 then
1530 Error_Msg_N ("incompatible types in renaming", Nam);
1532 -- AI12-0383: Names that denote values can be renamed.
1533 -- Ignore (accept) N_Raise_xxx_Error nodes in this context.
1535 elsif No_Raise_xxx_Error (Nam) = OK then
1536 Error_Msg_Ada_2022_Feature ("value in renaming", Sloc (Nam));
1537 end if;
1539 Set_Etype (Id, T2);
1541 if not Is_Variable (Nam) then
1542 Mutate_Ekind (Id, E_Constant);
1543 Set_Never_Set_In_Source (Id, True);
1544 Set_Is_True_Constant (Id, True);
1545 end if;
1547 -- The entity of the renaming declaration needs to reflect whether the
1548 -- renamed object is atomic, independent, volatile or VFA. These flags
1549 -- are set on the renamed object in the RM legality sense.
1551 Set_Is_Atomic (Id, Is_Atomic_Object (Nam));
1552 Set_Is_Independent (Id, Is_Independent_Object (Nam));
1553 Set_Is_Volatile (Id, Is_Volatile_Object_Ref (Nam));
1554 Set_Is_Volatile_Full_Access
1555 (Id, Is_Volatile_Full_Access_Object_Ref (Nam));
1557 -- Treat as volatile if we just set the Volatile flag
1559 if Is_Volatile (Id)
1561 -- Or if we are renaming an entity which was marked this way
1563 -- Are there more cases, e.g. X(J) where X is Treat_As_Volatile ???
1565 or else (Is_Entity_Name (Nam)
1566 and then Treat_As_Volatile (Entity (Nam)))
1567 then
1568 Set_Treat_As_Volatile (Id, True);
1569 end if;
1571 -- Now make the link to the renamed object
1573 Set_Renamed_Object (Id, Nam);
1575 -- Implementation-defined aspect specifications can appear in a renaming
1576 -- declaration, but not language-defined ones. The call to procedure
1577 -- Analyze_Aspect_Specifications will take care of this error check.
1579 if Has_Aspects (N) then
1580 Analyze_Aspect_Specifications (N, Id);
1581 end if;
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);
1594 Old_P : Entity_Id;
1595 Spec : Node_Id;
1597 begin
1598 if Name (N) = Error then
1599 return;
1600 end if;
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)))
1609 then
1610 null;
1611 else
1612 Check_Text_IO_Special_Unit (Name (N));
1613 end if;
1615 if Current_Scope /= Standard_Standard then
1616 Set_Is_Pure (New_P, Is_Pure (Current_Scope));
1617 end if;
1619 Enter_Name (New_P);
1620 Analyze (Name (N));
1622 if Is_Entity_Name (Name (N)) then
1623 Old_P := Entity (Name (N));
1624 else
1625 Old_P := Any_Id;
1626 end if;
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))
1634 then
1635 if Ekind (Old_P) = E_Generic_Package then
1636 Error_Msg_N
1637 ("generic package cannot be renamed as a package", Name (N));
1638 else
1639 Error_Msg_Sloc := Sloc (Old_P);
1640 Error_Msg_NE
1641 ("expect package name in renaming, found& declared#",
1642 Name (N), Old_P);
1643 end if;
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)))
1653 and then not
1654 Unit_Is_Visible (Cunit (Get_Source_Unit (Renamed_Entity (Old_P))))
1655 then
1656 Error_Msg_NE
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
1667 else
1668 -- Entities in the old package are accessible through the renaming
1669 -- entity. The simplest implementation is to have both packages share
1670 -- the entity list.
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));
1677 else
1678 Set_Renamed_Entity (New_P, Old_P);
1679 end if;
1681 -- The package renaming declaration may become Ghost if it renames a
1682 -- Ghost entity.
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.
1699 declare
1700 Ent : constant Entity_Id := Cunit_Entity (Current_Sem_Unit);
1701 begin
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
1706 then
1707 Set_Renamed_In_Spec (Old_P);
1708 end if;
1709 end;
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
1724 return;
1725 else
1726 Spec := Specification (Unit_Declaration_Node (Old_P));
1727 end if;
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))
1733 then
1734 declare
1735 E : Entity_Id;
1737 begin
1738 E := First_Entity (Old_P);
1739 while Present (E) and then E /= New_P loop
1740 if Is_Type (E)
1741 and then Nkind (Parent (E)) = N_Subtype_Declaration
1742 then
1743 Set_Is_Generic_Actual_Type (E);
1745 if Is_Private_Type (E)
1746 and then Present (Full_View (E))
1747 then
1748 Set_Is_Generic_Actual_Type (Full_View (E));
1749 end if;
1750 end if;
1752 Next_Entity (E);
1753 end loop;
1754 end;
1755 end if;
1756 end if;
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 if Has_Aspects (N) then
1763 Analyze_Aspect_Specifications (N, New_P);
1764 end if;
1765 end Analyze_Package_Renaming;
1767 -------------------------------
1768 -- Analyze_Renamed_Character --
1769 -------------------------------
1771 procedure Analyze_Renamed_Character
1772 (N : Node_Id;
1773 New_S : Entity_Id;
1774 Is_Body : Boolean)
1776 C : constant Node_Id := Name (N);
1778 begin
1779 if Ekind (New_S) = E_Function then
1780 Resolve (C, Etype (New_S));
1782 if Is_Body then
1783 Check_Frozen_Renaming (N, New_S);
1784 end if;
1786 else
1787 Error_Msg_N ("character literal can only be renamed as function", N);
1788 end if;
1789 end Analyze_Renamed_Character;
1791 ---------------------------------
1792 -- Analyze_Renamed_Dereference --
1793 ---------------------------------
1795 procedure Analyze_Renamed_Dereference
1796 (N : Node_Id;
1797 New_S : Entity_Id;
1798 Is_Body : Boolean)
1800 Nam : constant Node_Id := Name (N);
1801 P : constant Node_Id := Prefix (Nam);
1802 Typ : Entity_Id;
1803 Ind : Interp_Index;
1804 It : Interp;
1806 begin
1807 if not Is_Overloaded (P) then
1808 if Ekind (Etype (Nam)) /= E_Subprogram_Type
1809 or else not Type_Conformant (Etype (Nam), New_S)
1810 then
1811 Error_Msg_N ("designated type does not match specification", P);
1812 else
1813 Resolve (P);
1814 end if;
1816 return;
1818 else
1819 Typ := Any_Type;
1820 Get_First_Interp (Nam, Ind, It);
1822 while Present (It.Nam) loop
1824 if Ekind (It.Nam) = E_Subprogram_Type
1825 and then Type_Conformant (It.Nam, New_S)
1826 then
1827 if Typ /= Any_Id then
1828 Error_Msg_N ("ambiguous renaming", P);
1829 return;
1830 else
1831 Typ := It.Nam;
1832 end if;
1833 end if;
1835 Get_Next_Interp (Ind, It);
1836 end loop;
1838 if Typ = Any_Type then
1839 Error_Msg_N ("designated type does not match specification", P);
1840 else
1841 Resolve (N, Typ);
1843 if Is_Body then
1844 Check_Frozen_Renaming (N, New_S);
1845 end if;
1846 end if;
1847 end if;
1848 end Analyze_Renamed_Dereference;
1850 ---------------------------
1851 -- Analyze_Renamed_Entry --
1852 ---------------------------
1854 procedure Analyze_Renamed_Entry
1855 (N : Node_Id;
1856 New_S : Entity_Id;
1857 Is_Body : Boolean)
1859 Nam : constant Node_Id := Name (N);
1860 Sel : constant Node_Id := Selector_Name (Nam);
1861 Is_Actual : constant Boolean := Present (Corresponding_Formal_Spec (N));
1862 Old_S : Entity_Id;
1864 begin
1865 if Entity (Sel) = Any_Id then
1867 -- Selector is undefined on prefix. Error emitted already
1869 Set_Has_Completion (New_S);
1870 return;
1871 end if;
1873 -- Otherwise find renamed entity and build body of New_S as a call to it
1875 Old_S := Find_Renamed_Entity (N, Selector_Name (Nam), New_S);
1877 if Old_S = Any_Id then
1878 Error_Msg_N ("no subprogram or entry matches specification", N);
1879 else
1880 if Is_Body then
1881 Check_Subtype_Conformant (New_S, Old_S, N);
1882 Generate_Reference (New_S, Defining_Entity (N), 'b');
1883 Style.Check_Identifier (Defining_Entity (N), New_S);
1885 else
1886 -- Only mode conformance required for a renaming_as_declaration
1888 Check_Mode_Conformant (New_S, Old_S, N);
1889 end if;
1891 Inherit_Renamed_Profile (New_S, Old_S);
1893 -- The prefix can be an arbitrary expression that yields a task or
1894 -- protected object, so it must be resolved.
1896 if Is_Access_Type (Etype (Prefix (Nam))) then
1897 Insert_Explicit_Dereference (Prefix (Nam));
1898 end if;
1899 Resolve (Prefix (Nam), Scope (Old_S));
1900 end if;
1902 Set_Convention (New_S, Convention (Old_S));
1903 Set_Has_Completion (New_S, Inside_A_Generic);
1905 -- AI05-0225: If the renamed entity is a procedure or entry of a
1906 -- protected object, the target object must be a variable.
1908 if Is_Protected_Type (Scope (Old_S))
1909 and then Ekind (New_S) = E_Procedure
1910 and then not Is_Variable (Prefix (Nam))
1911 then
1912 if Is_Actual then
1913 Error_Msg_N
1914 ("target object of protected operation used as actual for "
1915 & "formal procedure must be a variable", Nam);
1916 else
1917 Error_Msg_N
1918 ("target object of protected operation renamed as procedure, "
1919 & "must be a variable", Nam);
1920 end if;
1921 end if;
1923 if Is_Body then
1924 Check_Frozen_Renaming (N, New_S);
1925 end if;
1926 end Analyze_Renamed_Entry;
1928 -----------------------------------
1929 -- Analyze_Renamed_Family_Member --
1930 -----------------------------------
1932 procedure Analyze_Renamed_Family_Member
1933 (N : Node_Id;
1934 New_S : Entity_Id;
1935 Is_Body : Boolean)
1937 Nam : constant Node_Id := Name (N);
1938 P : constant Node_Id := Prefix (Nam);
1939 Old_S : Entity_Id;
1941 begin
1942 if (Is_Entity_Name (P) and then Ekind (Entity (P)) = E_Entry_Family)
1943 or else (Nkind (P) = N_Selected_Component
1944 and then Ekind (Entity (Selector_Name (P))) = E_Entry_Family)
1945 then
1946 if Is_Entity_Name (P) then
1947 Old_S := Entity (P);
1948 else
1949 Old_S := Entity (Selector_Name (P));
1950 end if;
1952 if not Entity_Matches_Spec (Old_S, New_S) then
1953 Error_Msg_N ("entry family does not match specification", N);
1955 elsif Is_Body then
1956 Check_Subtype_Conformant (New_S, Old_S, N);
1957 Generate_Reference (New_S, Defining_Entity (N), 'b');
1958 Style.Check_Identifier (Defining_Entity (N), New_S);
1959 end if;
1961 else
1962 Error_Msg_N ("no entry family matches specification", N);
1963 end if;
1965 Set_Has_Completion (New_S, Inside_A_Generic);
1967 if Is_Body then
1968 Check_Frozen_Renaming (N, New_S);
1969 end if;
1970 end Analyze_Renamed_Family_Member;
1972 -----------------------------------------
1973 -- Analyze_Renamed_Primitive_Operation --
1974 -----------------------------------------
1976 procedure Analyze_Renamed_Primitive_Operation
1977 (N : Node_Id;
1978 New_S : Entity_Id;
1979 Is_Body : Boolean)
1981 Old_S : Entity_Id;
1982 Nam : Entity_Id;
1984 function Conforms
1985 (Subp : Entity_Id;
1986 Ctyp : Conformance_Type) return Boolean;
1987 -- Verify that the signatures of the renamed entity and the new entity
1988 -- match. The first formal of the renamed entity is skipped because it
1989 -- is the target object in any subsequent call.
1991 --------------
1992 -- Conforms --
1993 --------------
1995 function Conforms
1996 (Subp : Entity_Id;
1997 Ctyp : Conformance_Type) return Boolean
1999 Old_F : Entity_Id;
2000 New_F : Entity_Id;
2002 begin
2003 if Ekind (Subp) /= Ekind (New_S) then
2004 return False;
2005 end if;
2007 Old_F := Next_Formal (First_Formal (Subp));
2008 New_F := First_Formal (New_S);
2009 while Present (Old_F) and then Present (New_F) loop
2010 if not Conforming_Types (Etype (Old_F), Etype (New_F), Ctyp) then
2011 return False;
2012 end if;
2014 if Ctyp >= Mode_Conformant
2015 and then Ekind (Old_F) /= Ekind (New_F)
2016 then
2017 return False;
2018 end if;
2020 Next_Formal (New_F);
2021 Next_Formal (Old_F);
2022 end loop;
2024 return True;
2025 end Conforms;
2027 -- Start of processing for Analyze_Renamed_Primitive_Operation
2029 begin
2030 if not Is_Overloaded (Selector_Name (Name (N))) then
2031 Old_S := Entity (Selector_Name (Name (N)));
2033 if not Conforms (Old_S, Type_Conformant) then
2034 Old_S := Any_Id;
2035 end if;
2037 else
2038 -- Find the operation that matches the given signature
2040 declare
2041 It : Interp;
2042 Ind : Interp_Index;
2044 begin
2045 Old_S := Any_Id;
2046 Get_First_Interp (Selector_Name (Name (N)), Ind, It);
2048 while Present (It.Nam) loop
2049 if Conforms (It.Nam, Type_Conformant) then
2050 Old_S := It.Nam;
2051 end if;
2053 Get_Next_Interp (Ind, It);
2054 end loop;
2055 end;
2056 end if;
2058 if Old_S = Any_Id then
2059 Error_Msg_N ("no subprogram or entry matches specification", N);
2061 else
2062 if Is_Body then
2063 if not Conforms (Old_S, Subtype_Conformant) then
2064 Error_Msg_N ("subtype conformance error in renaming", N);
2065 end if;
2067 Generate_Reference (New_S, Defining_Entity (N), 'b');
2068 Style.Check_Identifier (Defining_Entity (N), New_S);
2070 else
2071 -- Only mode conformance required for a renaming_as_declaration
2073 if not Conforms (Old_S, Mode_Conformant) then
2074 Error_Msg_N ("mode conformance error in renaming", N);
2075 end if;
2077 -- AI12-0204: The prefix of a prefixed view that is renamed or
2078 -- passed as a formal subprogram must be renamable as an object.
2080 Nam := Prefix (Name (N));
2082 if Is_Object_Reference (Nam) then
2083 if Is_Dependent_Component_Of_Mutable_Object (Nam) then
2084 Error_Msg_N
2085 ("illegal renaming of discriminant-dependent component",
2086 Nam);
2087 end if;
2088 else
2089 Error_Msg_N ("expect object name in renaming", Nam);
2090 end if;
2092 -- Enforce the rule given in (RM 6.3.1 (10.1/2)): a prefixed
2093 -- view of a subprogram is intrinsic, because the compiler has
2094 -- to generate a wrapper for any call to it. If the name in a
2095 -- subprogram renaming is a prefixed view, the entity is thus
2096 -- intrinsic, and 'Access cannot be applied to it.
2098 Set_Convention (New_S, Convention_Intrinsic);
2099 end if;
2101 -- Inherit_Renamed_Profile (New_S, Old_S);
2103 -- The prefix can be an arbitrary expression that yields an
2104 -- object, so it must be resolved.
2106 Resolve (Prefix (Name (N)));
2107 end if;
2108 end Analyze_Renamed_Primitive_Operation;
2110 ---------------------------------
2111 -- Analyze_Subprogram_Renaming --
2112 ---------------------------------
2114 procedure Analyze_Subprogram_Renaming (N : Node_Id) is
2115 Formal_Spec : constant Entity_Id := Corresponding_Formal_Spec (N);
2116 Is_Actual : constant Boolean := Present (Formal_Spec);
2117 Nam : constant Node_Id := Name (N);
2118 Save_AV : constant Ada_Version_Type := Ada_Version;
2119 Save_AVP : constant Node_Id := Ada_Version_Pragma;
2120 Save_AV_Exp : constant Ada_Version_Type := Ada_Version_Explicit;
2121 Spec : constant Node_Id := Specification (N);
2123 Old_S : Entity_Id := Empty;
2124 Rename_Spec : Entity_Id;
2126 procedure Check_Null_Exclusion
2127 (Ren : Entity_Id;
2128 Sub : Entity_Id);
2129 -- Ada 2005 (AI-423): Given renaming Ren of subprogram Sub, check the
2130 -- following AI rules:
2132 -- If Ren denotes a generic formal object of a generic unit G, and the
2133 -- renaming (or instantiation containing the actual) occurs within the
2134 -- body of G or within the body of a generic unit declared within the
2135 -- declarative region of G, then the corresponding parameter of G
2136 -- shall have a null_exclusion; Otherwise the subtype of the Sub's
2137 -- formal parameter shall exclude null.
2139 -- Similarly for its return profile.
2141 procedure Check_SPARK_Primitive_Operation (Subp_Id : Entity_Id);
2142 -- Ensure that a SPARK renaming denoted by its entity Subp_Id does not
2143 -- declare a primitive operation of a tagged type (SPARK RM 6.1.1(3)).
2145 procedure Freeze_Actual_Profile;
2146 -- In Ada 2012, enforce the freezing rule concerning formal incomplete
2147 -- types: a callable entity freezes its profile, unless it has an
2148 -- incomplete untagged formal (RM 13.14(10.2/3)).
2150 function Has_Class_Wide_Actual return Boolean;
2151 -- Ada 2012 (AI05-071, AI05-0131) and Ada 2022 (AI12-0165): True if N is
2152 -- the renaming for a defaulted formal subprogram where the actual for
2153 -- the controlling formal type is class-wide.
2155 procedure Handle_Instance_With_Class_Wide_Type
2156 (Inst_Node : Node_Id;
2157 Ren_Id : Entity_Id;
2158 Wrapped_Prim : out Entity_Id;
2159 Wrap_Id : out Entity_Id);
2160 -- Ada 2012 (AI05-0071), Ada 2022 (AI12-0165): when the actual type
2161 -- of an instantiation is a class-wide type T'Class we may need to
2162 -- wrap a primitive operation of T; this routine looks for a suitable
2163 -- primitive to be wrapped and (if the wrapper is required) returns the
2164 -- Id of the wrapped primitive and the Id of the built wrapper. Ren_Id
2165 -- is the defining entity for the renamed subprogram specification.
2167 function Original_Subprogram (Subp : Entity_Id) return Entity_Id;
2168 -- Find renamed entity when the declaration is a renaming_as_body and
2169 -- the renamed entity may itself be a renaming_as_body. Used to enforce
2170 -- rule that a renaming_as_body is illegal if the declaration occurs
2171 -- before the subprogram it completes is frozen, and renaming indirectly
2172 -- renames the subprogram itself.(Defect Report 8652/0027).
2174 --------------------------
2175 -- Check_Null_Exclusion --
2176 --------------------------
2178 procedure Check_Null_Exclusion
2179 (Ren : Entity_Id;
2180 Sub : Entity_Id)
2182 Ren_Formal : Entity_Id;
2183 Sub_Formal : Entity_Id;
2185 function Null_Exclusion_Mismatch
2186 (Renaming : Entity_Id; Renamed : Entity_Id) return Boolean;
2187 -- Return True if there is a null exclusion mismatch between
2188 -- Renaming and Renamed, False otherwise.
2190 -----------------------------
2191 -- Null_Exclusion_Mismatch --
2192 -----------------------------
2194 function Null_Exclusion_Mismatch
2195 (Renaming : Entity_Id; Renamed : Entity_Id) return Boolean is
2196 begin
2197 return Has_Null_Exclusion (Parent (Renaming))
2198 and then
2199 not (Has_Null_Exclusion (Parent (Renamed))
2200 or else (Can_Never_Be_Null (Etype (Renamed))
2201 and then not
2202 (Is_Formal_Subprogram (Sub)
2203 and then In_Generic_Body (Current_Scope))));
2204 end Null_Exclusion_Mismatch;
2206 begin
2207 -- Parameter check
2209 Ren_Formal := First_Formal (Ren);
2210 Sub_Formal := First_Formal (Sub);
2211 while Present (Ren_Formal) and then Present (Sub_Formal) loop
2212 if Null_Exclusion_Mismatch (Ren_Formal, Sub_Formal) then
2213 Error_Msg_Sloc := Sloc (Sub_Formal);
2214 Error_Msg_NE
2215 ("`NOT NULL` required for parameter &#",
2216 Ren_Formal, Sub_Formal);
2217 end if;
2219 Next_Formal (Ren_Formal);
2220 Next_Formal (Sub_Formal);
2221 end loop;
2223 -- Return profile check
2225 if Nkind (Parent (Ren)) = N_Function_Specification
2226 and then Nkind (Parent (Sub)) = N_Function_Specification
2227 and then Null_Exclusion_Mismatch (Ren, Sub)
2228 then
2229 Error_Msg_Sloc := Sloc (Sub);
2230 Error_Msg_N ("return must specify `NOT NULL`#", Ren);
2231 end if;
2232 end Check_Null_Exclusion;
2234 -------------------------------------
2235 -- Check_SPARK_Primitive_Operation --
2236 -------------------------------------
2238 procedure Check_SPARK_Primitive_Operation (Subp_Id : Entity_Id) is
2239 Prag : constant Node_Id := SPARK_Pragma (Subp_Id);
2240 Typ : Entity_Id;
2242 begin
2243 -- Nothing to do when the subprogram is not subject to SPARK_Mode On
2244 -- because this check applies to SPARK code only.
2246 if not (Present (Prag)
2247 and then Get_SPARK_Mode_From_Annotation (Prag) = On)
2248 then
2249 return;
2251 -- Nothing to do when the subprogram is not a primitive operation
2253 elsif not Is_Primitive (Subp_Id) then
2254 return;
2255 end if;
2257 Typ := Find_Dispatching_Type (Subp_Id);
2259 -- Nothing to do when the subprogram is a primitive operation of an
2260 -- untagged type.
2262 if No (Typ) then
2263 return;
2264 end if;
2266 -- At this point a renaming declaration introduces a new primitive
2267 -- operation for a tagged type.
2269 Error_Msg_Node_2 := Typ;
2270 Error_Msg_NE
2271 ("subprogram renaming & cannot declare primitive for type & "
2272 & "(SPARK RM 6.1.1(3))", N, Subp_Id);
2273 end Check_SPARK_Primitive_Operation;
2275 ---------------------------
2276 -- Freeze_Actual_Profile --
2277 ---------------------------
2279 procedure Freeze_Actual_Profile is
2280 F : Entity_Id;
2281 Has_Untagged_Inc : Boolean;
2282 Instantiation_Node : constant Node_Id := Parent (N);
2284 begin
2285 if Ada_Version >= Ada_2012 then
2286 F := First_Formal (Formal_Spec);
2287 Has_Untagged_Inc := False;
2288 while Present (F) loop
2289 if Ekind (Etype (F)) = E_Incomplete_Type
2290 and then not Is_Tagged_Type (Etype (F))
2291 then
2292 Has_Untagged_Inc := True;
2293 exit;
2294 end if;
2296 Next_Formal (F);
2297 end loop;
2299 if Ekind (Formal_Spec) = E_Function
2300 and then not Is_Tagged_Type (Etype (Formal_Spec))
2301 then
2302 Has_Untagged_Inc := True;
2303 end if;
2305 if not Has_Untagged_Inc then
2306 F := First_Formal (Old_S);
2307 while Present (F) loop
2308 Freeze_Before (Instantiation_Node, Etype (F));
2310 if Is_Incomplete_Or_Private_Type (Etype (F))
2311 and then No (Underlying_Type (Etype (F)))
2312 then
2313 -- Exclude generic types, or types derived from them.
2314 -- They will be frozen in the enclosing instance.
2316 if Is_Generic_Type (Etype (F))
2317 or else Is_Generic_Type (Root_Type (Etype (F)))
2318 then
2319 null;
2321 -- A limited view of a type declared elsewhere needs no
2322 -- freezing actions.
2324 elsif From_Limited_With (Etype (F)) then
2325 null;
2327 else
2328 Error_Msg_NE
2329 ("type& must be frozen before this point",
2330 Instantiation_Node, Etype (F));
2331 end if;
2332 end if;
2334 Next_Formal (F);
2335 end loop;
2336 end if;
2337 end if;
2338 end Freeze_Actual_Profile;
2340 ---------------------------
2341 -- Has_Class_Wide_Actual --
2342 ---------------------------
2344 function Has_Class_Wide_Actual return Boolean is
2345 Formal : Entity_Id;
2346 Formal_Typ : Entity_Id;
2348 begin
2349 if Is_Actual then
2350 Formal := First_Formal (Formal_Spec);
2351 while Present (Formal) loop
2352 Formal_Typ := Etype (Formal);
2354 if Has_Unknown_Discriminants (Formal_Typ)
2355 and then not Is_Class_Wide_Type (Formal_Typ)
2356 and then Is_Class_Wide_Type (Get_Instance_Of (Formal_Typ))
2357 then
2358 return True;
2359 end if;
2361 Next_Formal (Formal);
2362 end loop;
2363 end if;
2365 return False;
2366 end Has_Class_Wide_Actual;
2368 ------------------------------------------
2369 -- Handle_Instance_With_Class_Wide_Type --
2370 ------------------------------------------
2372 procedure Handle_Instance_With_Class_Wide_Type
2373 (Inst_Node : Node_Id;
2374 Ren_Id : Entity_Id;
2375 Wrapped_Prim : out Entity_Id;
2376 Wrap_Id : out Entity_Id)
2378 procedure Build_Class_Wide_Wrapper
2379 (Ren_Id : Entity_Id;
2380 Prim_Op : Entity_Id;
2381 Wrap_Id : out Entity_Id);
2382 -- Build a wrapper for the renaming Ren_Id of subprogram Prim_Op.
2384 procedure Find_Suitable_Candidate
2385 (Prim_Op : out Entity_Id;
2386 Is_CW_Prim : out Boolean);
2387 -- Look for a suitable primitive to be wrapped (Prim_Op); Is_CW_Prim
2388 -- indicates that the found candidate is a class-wide primitive (to
2389 -- help the caller decide if the wrapper is required).
2391 ------------------------------
2392 -- Build_Class_Wide_Wrapper --
2393 ------------------------------
2395 procedure Build_Class_Wide_Wrapper
2396 (Ren_Id : Entity_Id;
2397 Prim_Op : Entity_Id;
2398 Wrap_Id : out Entity_Id)
2400 Loc : constant Source_Ptr := Sloc (N);
2402 function Build_Call
2403 (Subp_Id : Entity_Id;
2404 Params : List_Id) return Node_Id;
2405 -- Create a dispatching call to invoke routine Subp_Id with
2406 -- actuals built from the parameter specifications of list Params.
2408 function Build_Expr_Fun_Call
2409 (Subp_Id : Entity_Id;
2410 Params : List_Id) return Node_Id;
2411 -- Create a dispatching call to invoke function Subp_Id with
2412 -- actuals built from the parameter specifications of list Params.
2413 -- Directly return the call, so that it can be used inside an
2414 -- expression function. This is a requirement of GNATprove mode.
2416 function Build_Spec (Subp_Id : Entity_Id) return Node_Id;
2417 -- Create a subprogram specification based on the subprogram
2418 -- profile of Subp_Id.
2420 ----------------
2421 -- Build_Call --
2422 ----------------
2424 function Build_Call
2425 (Subp_Id : Entity_Id;
2426 Params : List_Id) return Node_Id
2428 Actuals : constant List_Id := New_List;
2429 Call_Ref : constant Node_Id := New_Occurrence_Of (Subp_Id, Loc);
2430 Formal : Node_Id;
2432 begin
2433 -- Build the actual parameters of the call
2435 Formal := First (Params);
2436 while Present (Formal) loop
2437 Append_To (Actuals,
2438 Make_Identifier (Loc,
2439 Chars (Defining_Identifier (Formal))));
2440 Next (Formal);
2441 end loop;
2443 -- Generate:
2444 -- return Subp_Id (Actuals);
2446 if Ekind (Subp_Id) in E_Function | E_Operator then
2447 return
2448 Make_Simple_Return_Statement (Loc,
2449 Expression =>
2450 Make_Function_Call (Loc,
2451 Name => Call_Ref,
2452 Parameter_Associations => Actuals));
2454 -- Generate:
2455 -- Subp_Id (Actuals);
2457 else
2458 return
2459 Make_Procedure_Call_Statement (Loc,
2460 Name => Call_Ref,
2461 Parameter_Associations => Actuals);
2462 end if;
2463 end Build_Call;
2465 -------------------------
2466 -- Build_Expr_Fun_Call --
2467 -------------------------
2469 function Build_Expr_Fun_Call
2470 (Subp_Id : Entity_Id;
2471 Params : List_Id) return Node_Id
2473 Actuals : constant List_Id := New_List;
2474 Call_Ref : constant Node_Id := New_Occurrence_Of (Subp_Id, Loc);
2475 Formal : Node_Id;
2477 begin
2478 pragma Assert (Ekind (Subp_Id) in E_Function | E_Operator);
2480 -- Build the actual parameters of the call
2482 Formal := First (Params);
2483 while Present (Formal) loop
2484 Append_To (Actuals,
2485 Make_Identifier (Loc,
2486 Chars (Defining_Identifier (Formal))));
2487 Next (Formal);
2488 end loop;
2490 -- Generate:
2491 -- Subp_Id (Actuals);
2493 return
2494 Make_Function_Call (Loc,
2495 Name => Call_Ref,
2496 Parameter_Associations => Actuals);
2497 end Build_Expr_Fun_Call;
2499 ----------------
2500 -- Build_Spec --
2501 ----------------
2503 function Build_Spec (Subp_Id : Entity_Id) return Node_Id is
2504 Params : constant List_Id := Copy_Parameter_List (Subp_Id);
2505 Spec_Id : constant Entity_Id :=
2506 Make_Defining_Identifier (Loc,
2507 New_External_Name (Chars (Subp_Id), 'R'));
2509 begin
2510 if Ekind (Formal_Spec) = E_Procedure then
2511 return
2512 Make_Procedure_Specification (Loc,
2513 Defining_Unit_Name => Spec_Id,
2514 Parameter_Specifications => Params);
2515 else
2516 return
2517 Make_Function_Specification (Loc,
2518 Defining_Unit_Name => Spec_Id,
2519 Parameter_Specifications => Params,
2520 Result_Definition =>
2521 New_Copy_Tree (Result_Definition (Spec)));
2522 end if;
2523 end Build_Spec;
2525 -- Local variables
2527 Body_Decl : Node_Id;
2528 Spec_Decl : Node_Id;
2529 New_Spec : Node_Id;
2531 -- Start of processing for Build_Class_Wide_Wrapper
2533 begin
2534 pragma Assert (not Error_Posted (Nam));
2536 -- Step 1: Create the declaration and the body of the wrapper,
2537 -- insert all the pieces into the tree.
2539 -- In GNATprove mode, create a function wrapper in the form of an
2540 -- expression function, so that an implicit postcondition relating
2541 -- the result of calling the wrapper function and the result of
2542 -- the dispatching call to the wrapped function is known during
2543 -- proof.
2545 if GNATprove_Mode
2546 and then Ekind (Ren_Id) in E_Function | E_Operator
2547 then
2548 New_Spec := Build_Spec (Ren_Id);
2549 Body_Decl :=
2550 Make_Expression_Function (Loc,
2551 Specification => New_Spec,
2552 Expression =>
2553 Build_Expr_Fun_Call
2554 (Subp_Id => Prim_Op,
2555 Params => Parameter_Specifications (New_Spec)));
2557 Wrap_Id := Defining_Entity (Body_Decl);
2559 -- Otherwise, create separate spec and body for the subprogram
2561 else
2562 Spec_Decl :=
2563 Make_Subprogram_Declaration (Loc,
2564 Specification => Build_Spec (Ren_Id));
2565 Insert_Before_And_Analyze (N, Spec_Decl);
2567 Wrap_Id := Defining_Entity (Spec_Decl);
2569 Body_Decl :=
2570 Make_Subprogram_Body (Loc,
2571 Specification => Build_Spec (Ren_Id),
2572 Declarations => New_List,
2573 Handled_Statement_Sequence =>
2574 Make_Handled_Sequence_Of_Statements (Loc,
2575 Statements => New_List (
2576 Build_Call
2577 (Subp_Id => Prim_Op,
2578 Params =>
2579 Parameter_Specifications
2580 (Specification (Spec_Decl))))));
2582 Set_Corresponding_Body (Spec_Decl, Defining_Entity (Body_Decl));
2583 end if;
2585 Set_Is_Class_Wide_Wrapper (Wrap_Id);
2587 -- If the operator carries an Eliminated pragma, indicate that
2588 -- the wrapper is also to be eliminated, to prevent spurious
2589 -- errors when using gnatelim on programs that include box-
2590 -- defaulted initialization of equality operators.
2592 Set_Is_Eliminated (Wrap_Id, Is_Eliminated (Prim_Op));
2594 -- In GNATprove mode, insert the body in the tree for analysis
2596 if GNATprove_Mode then
2597 Insert_Before_And_Analyze (N, Body_Decl);
2598 end if;
2600 -- The generated body does not freeze and must be analyzed when
2601 -- the class-wide wrapper is frozen. The body is only needed if
2602 -- expansion is enabled.
2604 if Expander_Active then
2605 Append_Freeze_Action (Wrap_Id, Body_Decl);
2606 end if;
2608 -- Step 2: The subprogram renaming aliases the wrapper
2610 Rewrite (Name (N), New_Occurrence_Of (Wrap_Id, Loc));
2611 end Build_Class_Wide_Wrapper;
2613 -----------------------------
2614 -- Find_Suitable_Candidate --
2615 -----------------------------
2617 procedure Find_Suitable_Candidate
2618 (Prim_Op : out Entity_Id;
2619 Is_CW_Prim : out Boolean)
2621 Loc : constant Source_Ptr := Sloc (N);
2623 function Find_Primitive (Typ : Entity_Id) return Entity_Id;
2624 -- Find a primitive subprogram of type Typ which matches the
2625 -- profile of the renaming declaration.
2627 procedure Interpretation_Error (Subp_Id : Entity_Id);
2628 -- Emit a continuation error message suggesting subprogram Subp_Id
2629 -- as a possible interpretation.
2631 function Is_Intrinsic_Equality
2632 (Subp_Id : Entity_Id) return Boolean;
2633 -- Determine whether subprogram Subp_Id denotes the intrinsic "="
2634 -- operator.
2636 function Is_Suitable_Candidate
2637 (Subp_Id : Entity_Id) return Boolean;
2638 -- Determine whether subprogram Subp_Id is a suitable candidate
2639 -- for the role of a wrapped subprogram.
2641 --------------------
2642 -- Find_Primitive --
2643 --------------------
2645 function Find_Primitive (Typ : Entity_Id) return Entity_Id is
2646 procedure Replace_Parameter_Types (Spec : Node_Id);
2647 -- Given a specification Spec, replace all class-wide parameter
2648 -- types with reference to type Typ.
2650 -----------------------------
2651 -- Replace_Parameter_Types --
2652 -----------------------------
2654 procedure Replace_Parameter_Types (Spec : Node_Id) is
2655 Formal : Node_Id;
2656 Formal_Id : Entity_Id;
2657 Formal_Typ : Node_Id;
2659 begin
2660 Formal := First (Parameter_Specifications (Spec));
2661 while Present (Formal) loop
2662 Formal_Id := Defining_Identifier (Formal);
2663 Formal_Typ := Parameter_Type (Formal);
2665 -- Create a new entity for each class-wide formal to
2666 -- prevent aliasing with the original renaming. Replace
2667 -- the type of such a parameter with the candidate type.
2669 if Nkind (Formal_Typ) = N_Identifier
2670 and then Is_Class_Wide_Type (Etype (Formal_Typ))
2671 then
2672 Set_Defining_Identifier (Formal,
2673 Make_Defining_Identifier (Loc, Chars (Formal_Id)));
2675 Set_Parameter_Type (Formal,
2676 New_Occurrence_Of (Typ, Loc));
2677 end if;
2679 Next (Formal);
2680 end loop;
2681 end Replace_Parameter_Types;
2683 -- Local variables
2685 Alt_Ren : constant Node_Id := New_Copy_Tree (N);
2686 Alt_Nam : constant Node_Id := Name (Alt_Ren);
2687 Alt_Spec : constant Node_Id := Specification (Alt_Ren);
2688 Subp_Id : Entity_Id;
2690 -- Start of processing for Find_Primitive
2692 begin
2693 -- Each attempt to find a suitable primitive of a particular
2694 -- type operates on its own copy of the original renaming.
2695 -- As a result the original renaming is kept decoration and
2696 -- side-effect free.
2698 -- Inherit the overloaded status of the renamed subprogram name
2700 if Is_Overloaded (Nam) then
2701 Set_Is_Overloaded (Alt_Nam);
2702 Save_Interps (Nam, Alt_Nam);
2703 end if;
2705 -- The copied renaming is hidden from visibility to prevent the
2706 -- pollution of the enclosing context.
2708 Set_Defining_Unit_Name (Alt_Spec, Make_Temporary (Loc, 'R'));
2710 -- The types of all class-wide parameters must be changed to
2711 -- the candidate type.
2713 Replace_Parameter_Types (Alt_Spec);
2715 -- Try to find a suitable primitive that matches the altered
2716 -- profile of the renaming specification.
2718 Subp_Id :=
2719 Find_Renamed_Entity
2720 (N => Alt_Ren,
2721 Nam => Name (Alt_Ren),
2722 New_S => Analyze_Subprogram_Specification (Alt_Spec),
2723 Is_Actual => Is_Actual);
2725 -- Do not return Any_Id if the resolution of the altered
2726 -- profile failed as this complicates further checks on
2727 -- the caller side; return Empty instead.
2729 if Subp_Id = Any_Id then
2730 return Empty;
2731 else
2732 return Subp_Id;
2733 end if;
2734 end Find_Primitive;
2736 --------------------------
2737 -- Interpretation_Error --
2738 --------------------------
2740 procedure Interpretation_Error (Subp_Id : Entity_Id) is
2741 begin
2742 Error_Msg_Sloc := Sloc (Subp_Id);
2744 if Is_Internal (Subp_Id) then
2745 Error_Msg_NE
2746 ("\\possible interpretation: predefined & #",
2747 Spec, Formal_Spec);
2748 else
2749 Error_Msg_NE
2750 ("\\possible interpretation: & defined #",
2751 Spec, Formal_Spec);
2752 end if;
2753 end Interpretation_Error;
2755 ---------------------------
2756 -- Is_Intrinsic_Equality --
2757 ---------------------------
2759 function Is_Intrinsic_Equality (Subp_Id : Entity_Id) return Boolean
2761 begin
2762 return
2763 Ekind (Subp_Id) = E_Operator
2764 and then Chars (Subp_Id) = Name_Op_Eq
2765 and then Is_Intrinsic_Subprogram (Subp_Id);
2766 end Is_Intrinsic_Equality;
2768 ---------------------------
2769 -- Is_Suitable_Candidate --
2770 ---------------------------
2772 function Is_Suitable_Candidate (Subp_Id : Entity_Id) return Boolean
2774 begin
2775 if No (Subp_Id) then
2776 return False;
2778 -- An intrinsic subprogram is never a good candidate. This
2779 -- is an indication of a missing primitive, either defined
2780 -- directly or inherited from a parent tagged type.
2782 elsif Is_Intrinsic_Subprogram (Subp_Id) then
2783 return False;
2785 else
2786 return True;
2787 end if;
2788 end Is_Suitable_Candidate;
2790 -- Local variables
2792 Actual_Typ : Entity_Id := Empty;
2793 -- The actual class-wide type for Formal_Typ
2795 CW_Prim_OK : Boolean;
2796 CW_Prim_Op : Entity_Id;
2797 -- The class-wide subprogram (if available) that corresponds to
2798 -- the renamed generic formal subprogram.
2800 Formal_Typ : Entity_Id := Empty;
2801 -- The generic formal type with unknown discriminants
2803 Root_Prim_OK : Boolean;
2804 Root_Prim_Op : Entity_Id;
2805 -- The root type primitive (if available) that corresponds to the
2806 -- renamed generic formal subprogram.
2808 Root_Typ : Entity_Id := Empty;
2809 -- The root type of Actual_Typ
2811 Formal : Node_Id;
2813 -- Start of processing for Find_Suitable_Candidate
2815 begin
2816 pragma Assert (not Error_Posted (Nam));
2818 Prim_Op := Empty;
2819 Is_CW_Prim := False;
2821 -- Analyze the renamed name, but do not resolve it. The resolution
2822 -- is completed once a suitable subprogram is found.
2824 Analyze (Nam);
2826 -- When the renamed name denotes the intrinsic operator equals,
2827 -- the name must be treated as overloaded. This allows for a
2828 -- potential match against the root type's predefined equality
2829 -- function.
2831 if Is_Intrinsic_Equality (Entity (Nam)) then
2832 Set_Is_Overloaded (Nam);
2833 Collect_Interps (Nam);
2834 end if;
2836 -- Step 1: Find the generic formal type and its corresponding
2837 -- class-wide actual type from the renamed generic formal
2838 -- subprogram.
2840 Formal := First_Formal (Formal_Spec);
2841 while Present (Formal) loop
2842 if Has_Unknown_Discriminants (Etype (Formal))
2843 and then not Is_Class_Wide_Type (Etype (Formal))
2844 and then Is_Class_Wide_Type (Get_Instance_Of (Etype (Formal)))
2845 then
2846 Formal_Typ := Etype (Formal);
2847 Actual_Typ := Base_Type (Get_Instance_Of (Formal_Typ));
2848 Root_Typ := Root_Type (Actual_Typ);
2849 exit;
2850 end if;
2852 Next_Formal (Formal);
2853 end loop;
2855 -- The specification of the generic formal subprogram should
2856 -- always contain a formal type with unknown discriminants whose
2857 -- actual is a class-wide type; otherwise this indicates a failure
2858 -- in function Has_Class_Wide_Actual.
2860 pragma Assert (Present (Formal_Typ));
2862 -- Step 2: Find the proper class-wide subprogram or primitive
2863 -- that corresponds to the renamed generic formal subprogram.
2865 CW_Prim_Op := Find_Primitive (Actual_Typ);
2866 CW_Prim_OK := Is_Suitable_Candidate (CW_Prim_Op);
2867 Root_Prim_Op := Find_Primitive (Root_Typ);
2868 Root_Prim_OK := Is_Suitable_Candidate (Root_Prim_Op);
2870 -- The class-wide actual type has two subprograms that correspond
2871 -- to the renamed generic formal subprogram:
2873 -- with procedure Prim_Op (Param : Formal_Typ);
2875 -- procedure Prim_Op (Param : Actual_Typ); -- may be inherited
2876 -- procedure Prim_Op (Param : Actual_Typ'Class);
2878 -- Even though the declaration of the two subprograms is legal, a
2879 -- call to either one is ambiguous and therefore illegal.
2881 if CW_Prim_OK and Root_Prim_OK then
2883 -- A user-defined primitive has precedence over a predefined
2884 -- one.
2886 if Is_Internal (CW_Prim_Op)
2887 and then not Is_Internal (Root_Prim_Op)
2888 then
2889 Prim_Op := Root_Prim_Op;
2891 elsif Is_Internal (Root_Prim_Op)
2892 and then not Is_Internal (CW_Prim_Op)
2893 then
2894 Prim_Op := CW_Prim_Op;
2895 Is_CW_Prim := True;
2897 elsif CW_Prim_Op = Root_Prim_Op then
2898 Prim_Op := Root_Prim_Op;
2900 -- The two subprograms are legal but the class-wide subprogram
2901 -- is a class-wide wrapper built for a previous instantiation;
2902 -- the wrapper has precedence.
2904 elsif Present (Alias (CW_Prim_Op))
2905 and then Is_Class_Wide_Wrapper (Ultimate_Alias (CW_Prim_Op))
2906 then
2907 Prim_Op := CW_Prim_Op;
2908 Is_CW_Prim := True;
2910 -- Otherwise both candidate subprograms are user-defined and
2911 -- ambiguous.
2913 else
2914 Error_Msg_NE
2915 ("ambiguous actual for generic subprogram &",
2916 Spec, Formal_Spec);
2917 Interpretation_Error (Root_Prim_Op);
2918 Interpretation_Error (CW_Prim_Op);
2919 return;
2920 end if;
2922 elsif CW_Prim_OK and not Root_Prim_OK then
2923 Prim_Op := CW_Prim_Op;
2924 Is_CW_Prim := True;
2926 elsif not CW_Prim_OK and Root_Prim_OK then
2927 Prim_Op := Root_Prim_Op;
2929 -- An intrinsic equality may act as a suitable candidate in the
2930 -- case of a null type extension where the parent's equality
2931 -- is hidden. A call to an intrinsic equality is expanded as
2932 -- dispatching.
2934 elsif Present (Root_Prim_Op)
2935 and then Is_Intrinsic_Equality (Root_Prim_Op)
2936 then
2937 Prim_Op := Root_Prim_Op;
2939 -- Otherwise there are no candidate subprograms. Let the caller
2940 -- diagnose the error.
2942 else
2943 return;
2944 end if;
2946 -- At this point resolution has taken place and the name is no
2947 -- longer overloaded. Mark the primitive as referenced.
2949 Set_Is_Overloaded (Name (N), False);
2950 Set_Referenced (Prim_Op);
2951 end Find_Suitable_Candidate;
2953 -- Local variables
2955 Is_CW_Prim : Boolean;
2957 -- Start of processing for Handle_Instance_With_Class_Wide_Type
2959 begin
2960 Wrapped_Prim := Empty;
2961 Wrap_Id := Empty;
2963 -- Ada 2012 (AI05-0071): A generic/instance scenario involving a
2964 -- formal type with unknown discriminants and a generic primitive
2965 -- operation of the said type with a box require special processing
2966 -- when the actual is a class-wide type:
2968 -- generic
2969 -- type Formal_Typ (<>) is private;
2970 -- with procedure Prim_Op (Param : Formal_Typ) is <>;
2971 -- package Gen is ...
2973 -- package Inst is new Gen (Actual_Typ'Class);
2975 -- In this case the general renaming mechanism used in the prologue
2976 -- of an instance no longer applies:
2978 -- procedure Prim_Op (Param : Formal_Typ) renames Prim_Op;
2980 -- The above is replaced the following wrapper/renaming combination:
2982 -- procedure Wrapper (Param : Formal_Typ) is -- wrapper
2983 -- begin
2984 -- Prim_Op (Param); -- primitive
2985 -- end Wrapper;
2987 -- procedure Prim_Op (Param : Formal_Typ) renames Wrapper;
2989 -- This transformation applies only if there is no explicit visible
2990 -- class-wide operation at the point of the instantiation. Ren_Id is
2991 -- the entity of the renaming declaration. When the transformation
2992 -- applies, Wrapped_Prim is the entity of the wrapped primitive.
2994 if Box_Present (Inst_Node) then
2995 Find_Suitable_Candidate
2996 (Prim_Op => Wrapped_Prim,
2997 Is_CW_Prim => Is_CW_Prim);
2999 if Present (Wrapped_Prim) then
3000 if not Is_CW_Prim then
3001 Build_Class_Wide_Wrapper (Ren_Id, Wrapped_Prim, Wrap_Id);
3003 -- Small optimization: When the candidate is a class-wide
3004 -- subprogram we don't build the wrapper; we modify the
3005 -- renaming declaration to directly map the actual to the
3006 -- generic formal and discard the candidate.
3008 else
3009 Rewrite (Nam, New_Occurrence_Of (Wrapped_Prim, Sloc (N)));
3010 Wrapped_Prim := Empty;
3011 end if;
3012 end if;
3014 -- Ada 2022 (AI12-0165, RM 12.6(8.5/3)): The actual subprogram for a
3015 -- formal_abstract_subprogram_declaration shall be:
3016 -- a) a dispatching operation of the controlling type; or
3017 -- b) if the controlling type is a formal type, and the actual
3018 -- type corresponding to that formal type is a specific type T,
3019 -- a dispatching operation of type T; or
3020 -- c) if the controlling type is a formal type, and the actual
3021 -- type is a class-wide type T'Class, an implicitly declared
3022 -- subprogram corresponding to a primitive operation of type T.
3024 elsif Nkind (Inst_Node) = N_Formal_Abstract_Subprogram_Declaration
3025 and then Is_Entity_Name (Nam)
3026 then
3027 Find_Suitable_Candidate
3028 (Prim_Op => Wrapped_Prim,
3029 Is_CW_Prim => Is_CW_Prim);
3031 if Present (Wrapped_Prim) then
3033 -- Cases (a) and (b); see previous description.
3035 if not Is_CW_Prim then
3036 Build_Class_Wide_Wrapper (Ren_Id, Wrapped_Prim, Wrap_Id);
3038 -- Case (c); see previous description.
3040 -- Implicit operations of T'Class for subtype declarations
3041 -- are built by Derive_Subprogram, and their Alias attribute
3042 -- references the primitive operation of T.
3044 elsif not Comes_From_Source (Wrapped_Prim)
3045 and then Nkind (Parent (Wrapped_Prim)) = N_Subtype_Declaration
3046 and then Present (Alias (Wrapped_Prim))
3047 then
3048 -- We don't need to build the wrapper; we modify the
3049 -- renaming declaration to directly map the actual to
3050 -- the generic formal and discard the candidate.
3052 Rewrite (Nam,
3053 New_Occurrence_Of (Alias (Wrapped_Prim), Sloc (N)));
3054 Wrapped_Prim := Empty;
3056 -- Legality rules do not apply; discard the candidate.
3058 else
3059 Wrapped_Prim := Empty;
3060 end if;
3061 end if;
3062 end if;
3063 end Handle_Instance_With_Class_Wide_Type;
3065 -------------------------
3066 -- Original_Subprogram --
3067 -------------------------
3069 function Original_Subprogram (Subp : Entity_Id) return Entity_Id is
3070 Orig_Decl : Node_Id;
3071 Orig_Subp : Entity_Id;
3073 begin
3074 -- First case: renamed entity is itself a renaming
3076 if Present (Alias (Subp)) then
3077 return Alias (Subp);
3079 elsif Nkind (Unit_Declaration_Node (Subp)) = N_Subprogram_Declaration
3080 and then Present (Corresponding_Body (Unit_Declaration_Node (Subp)))
3081 then
3082 -- Check if renamed entity is a renaming_as_body
3084 Orig_Decl :=
3085 Unit_Declaration_Node
3086 (Corresponding_Body (Unit_Declaration_Node (Subp)));
3088 if Nkind (Orig_Decl) = N_Subprogram_Renaming_Declaration then
3089 Orig_Subp := Entity (Name (Orig_Decl));
3091 if Orig_Subp = Rename_Spec then
3093 -- Circularity detected
3095 return Orig_Subp;
3097 else
3098 return (Original_Subprogram (Orig_Subp));
3099 end if;
3100 else
3101 return Subp;
3102 end if;
3103 else
3104 return Subp;
3105 end if;
3106 end Original_Subprogram;
3108 -- Local variables
3110 CW_Actual : constant Boolean := Has_Class_Wide_Actual;
3111 -- Ada 2012 (AI05-071, AI05-0131) and Ada 2022 (AI12-0165): True if the
3112 -- renaming is for a defaulted formal subprogram when the actual for a
3113 -- related formal type is class-wide.
3115 Inst_Node : Node_Id := Empty;
3116 New_S : Entity_Id := Empty;
3117 Wrapped_Prim : Entity_Id := Empty;
3119 -- Start of processing for Analyze_Subprogram_Renaming
3121 begin
3122 -- We must test for the attribute renaming case before the Analyze
3123 -- call because otherwise Sem_Attr will complain that the attribute
3124 -- is missing an argument when it is analyzed.
3126 if Nkind (Nam) = N_Attribute_Reference then
3128 -- In the case of an abstract formal subprogram association, rewrite
3129 -- an actual given by a stream or Put_Image attribute as the name of
3130 -- the corresponding stream or Put_Image primitive of the type.
3132 -- In a generic context the stream and Put_Image operations are not
3133 -- generated, and this must be treated as a normal attribute
3134 -- reference, to be expanded in subsequent instantiations.
3136 if Is_Actual
3137 and then Is_Abstract_Subprogram (Formal_Spec)
3138 and then Expander_Active
3139 then
3140 declare
3141 Prefix_Type : constant Entity_Id := Entity (Prefix (Nam));
3142 Prim : Entity_Id;
3144 begin
3145 -- The class-wide forms of the stream and Put_Image attributes
3146 -- are not primitive dispatching operations (even though they
3147 -- internally dispatch).
3149 if Is_Class_Wide_Type (Prefix_Type) then
3150 Error_Msg_N
3151 ("attribute must be a primitive dispatching operation",
3152 Nam);
3153 return;
3154 end if;
3156 -- Retrieve the primitive subprogram associated with the
3157 -- attribute. This can only be a stream attribute, since those
3158 -- are the only ones that are dispatching (and the actual for
3159 -- an abstract formal subprogram must be dispatching
3160 -- operation).
3162 case Attribute_Name (Nam) is
3163 when Name_Input =>
3164 Prim :=
3165 Find_Optional_Prim_Op (Prefix_Type, TSS_Stream_Input);
3167 when Name_Output =>
3168 Prim :=
3169 Find_Optional_Prim_Op (Prefix_Type, TSS_Stream_Output);
3171 when Name_Read =>
3172 Prim :=
3173 Find_Optional_Prim_Op (Prefix_Type, TSS_Stream_Read);
3175 when Name_Write =>
3176 Prim :=
3177 Find_Optional_Prim_Op (Prefix_Type, TSS_Stream_Write);
3179 when Name_Put_Image =>
3180 Prim :=
3181 Find_Optional_Prim_Op (Prefix_Type, TSS_Put_Image);
3183 when others =>
3184 Error_Msg_N
3185 ("attribute must be a primitive dispatching operation",
3186 Nam);
3187 return;
3188 end case;
3190 -- If no stream operation was found, and the type is limited,
3191 -- the user should have defined one. This rule does not apply
3192 -- to Put_Image.
3194 if No (Prim)
3195 and then Attribute_Name (Nam) /= Name_Put_Image
3196 then
3197 if Is_Limited_Type (Prefix_Type) then
3198 Error_Msg_NE
3199 ("stream operation not defined for type&",
3200 N, Prefix_Type);
3201 return;
3203 -- Otherwise, compiler should have generated default
3205 else
3206 raise Program_Error;
3207 end if;
3208 end if;
3210 -- Rewrite the attribute into the name of its corresponding
3211 -- primitive dispatching subprogram. We can then proceed with
3212 -- the usual processing for subprogram renamings.
3214 declare
3215 Prim_Name : constant Node_Id :=
3216 Make_Identifier (Sloc (Nam),
3217 Chars => Chars (Prim));
3218 begin
3219 Set_Entity (Prim_Name, Prim);
3220 Rewrite (Nam, Prim_Name);
3221 Analyze (Nam);
3222 end;
3223 end;
3225 -- Normal processing for a renaming of an attribute
3227 else
3228 Attribute_Renaming (N);
3229 return;
3230 end if;
3231 end if;
3233 -- Check whether this declaration corresponds to the instantiation of a
3234 -- formal subprogram.
3236 -- If this is an instantiation, the corresponding actual is frozen and
3237 -- error messages can be made more precise. If this is a default
3238 -- subprogram, the entity is already established in the generic, and is
3239 -- not retrieved by visibility. If it is a default with a box, the
3240 -- candidate interpretations, if any, have been collected when building
3241 -- the renaming declaration. If overloaded, the proper interpretation is
3242 -- determined in Find_Renamed_Entity. If the entity is an operator,
3243 -- Find_Renamed_Entity applies additional visibility checks.
3245 if Is_Actual then
3246 Inst_Node := Unit_Declaration_Node (Formal_Spec);
3248 -- Ada 2012 (AI05-0071) and Ada 2022 (AI12-0165): when the actual
3249 -- type is a class-wide type T'Class we may need to wrap a primitive
3250 -- operation of T. Search for the wrapped primitive and (if required)
3251 -- build a wrapper whose body consists of a dispatching call to the
3252 -- wrapped primitive of T, with its formal parameters as the actual
3253 -- parameters.
3255 if CW_Actual and then
3257 -- Ada 2012 (AI05-0071): Check whether the renaming is for a
3258 -- defaulted actual subprogram with a class-wide actual.
3260 (Box_Present (Inst_Node)
3262 or else
3264 -- Ada 2022 (AI12-0165): Check whether the renaming is for a formal
3265 -- abstract subprogram declaration with a class-wide actual.
3267 (Nkind (Inst_Node) = N_Formal_Abstract_Subprogram_Declaration
3268 and then Is_Entity_Name (Nam)))
3269 then
3270 New_S := Analyze_Subprogram_Specification (Spec);
3272 -- Do not attempt to build the wrapper if the renaming is in error
3274 if not Error_Posted (Nam) then
3275 Handle_Instance_With_Class_Wide_Type
3276 (Inst_Node => Inst_Node,
3277 Ren_Id => New_S,
3278 Wrapped_Prim => Wrapped_Prim,
3279 Wrap_Id => Old_S);
3281 -- If several candidates were found, then we reported the
3282 -- ambiguity; stop processing the renaming declaration to
3283 -- avoid reporting further (spurious) errors.
3285 if Error_Posted (Spec) then
3286 return;
3287 end if;
3289 end if;
3290 end if;
3292 if Present (Wrapped_Prim) then
3294 -- When the wrapper is built, the subprogram renaming aliases
3295 -- the wrapper.
3297 Analyze (Nam);
3299 pragma Assert (Old_S = Entity (Nam)
3300 and then Is_Class_Wide_Wrapper (Old_S));
3302 -- The subprogram renaming declaration may become Ghost if it
3303 -- renames a wrapper of a Ghost entity.
3305 Mark_Ghost_Renaming (N, Wrapped_Prim);
3307 elsif Is_Entity_Name (Nam)
3308 and then Present (Entity (Nam))
3309 and then not Comes_From_Source (Nam)
3310 and then not Is_Overloaded (Nam)
3311 then
3312 Old_S := Entity (Nam);
3314 -- The subprogram renaming declaration may become Ghost if it
3315 -- renames a Ghost entity.
3317 Mark_Ghost_Renaming (N, Old_S);
3319 New_S := Analyze_Subprogram_Specification (Spec);
3321 -- Operator case
3323 if Ekind (Old_S) = E_Operator then
3325 -- Box present
3327 if Box_Present (Inst_Node) then
3328 Old_S := Find_Renamed_Entity (N, Name (N), New_S, Is_Actual);
3330 -- If there is an immediately visible homonym of the operator
3331 -- and the declaration has a default, this is worth a warning
3332 -- because the user probably did not intend to get the pre-
3333 -- defined operator, visible in the generic declaration. To
3334 -- find if there is an intended candidate, analyze the renaming
3335 -- again in the current context.
3337 elsif Scope (Old_S) = Standard_Standard
3338 and then Present (Default_Name (Inst_Node))
3339 then
3340 declare
3341 Decl : constant Node_Id := New_Copy_Tree (N);
3342 Hidden : Entity_Id;
3344 begin
3345 Set_Entity (Name (Decl), Empty);
3346 Analyze (Name (Decl));
3347 Hidden :=
3348 Find_Renamed_Entity (Decl, Name (Decl), New_S, True);
3350 if Present (Hidden)
3351 and then In_Open_Scopes (Scope (Hidden))
3352 and then Is_Immediately_Visible (Hidden)
3353 and then Comes_From_Source (Hidden)
3354 and then Hidden /= Old_S
3355 then
3356 Error_Msg_Sloc := Sloc (Hidden);
3357 Error_Msg_N
3358 ("default subprogram is resolved in the generic "
3359 & "declaration (RM 12.6(17))??", N);
3360 Error_Msg_NE ("\and will not use & #??", N, Hidden);
3361 end if;
3362 end;
3363 end if;
3364 end if;
3366 else
3367 Analyze (Nam);
3369 -- The subprogram renaming declaration may become Ghost if it
3370 -- renames a Ghost entity.
3372 if Is_Entity_Name (Nam) then
3373 Mark_Ghost_Renaming (N, Entity (Nam));
3374 end if;
3376 New_S := Analyze_Subprogram_Specification (Spec);
3377 end if;
3379 else
3380 -- Renamed entity must be analyzed first, to avoid being hidden by
3381 -- new name (which might be the same in a generic instance).
3383 Analyze (Nam);
3385 -- The subprogram renaming declaration may become Ghost if it renames
3386 -- a Ghost entity.
3388 if Is_Entity_Name (Nam) then
3389 Mark_Ghost_Renaming (N, Entity (Nam));
3390 end if;
3392 -- The renaming defines a new overloaded entity, which is analyzed
3393 -- like a subprogram declaration.
3395 New_S := Analyze_Subprogram_Specification (Spec);
3396 end if;
3398 if Current_Scope /= Standard_Standard then
3399 Set_Is_Pure (New_S, Is_Pure (Current_Scope));
3400 end if;
3402 -- Set SPARK mode from current context
3404 Set_SPARK_Pragma (New_S, SPARK_Mode_Pragma);
3405 Set_SPARK_Pragma_Inherited (New_S);
3407 Rename_Spec := Find_Corresponding_Spec (N);
3409 -- Case of Renaming_As_Body
3411 if Present (Rename_Spec) then
3412 Check_Previous_Null_Procedure (N, Rename_Spec);
3414 -- Renaming declaration is the completion of the declaration of
3415 -- Rename_Spec. We build an actual body for it at the freezing point.
3417 Set_Corresponding_Spec (N, Rename_Spec);
3419 -- Deal with special case of stream functions of abstract types
3420 -- and interfaces.
3422 if Nkind (Unit_Declaration_Node (Rename_Spec)) =
3423 N_Abstract_Subprogram_Declaration
3424 then
3425 -- Input stream functions are abstract if the object type is
3426 -- abstract. Similarly, all default stream functions for an
3427 -- interface type are abstract. However, these subprograms may
3428 -- receive explicit declarations in representation clauses, making
3429 -- the attribute subprograms usable as defaults in subsequent
3430 -- type extensions.
3431 -- In this case we rewrite the declaration to make the subprogram
3432 -- non-abstract. We remove the previous declaration, and insert
3433 -- the new one at the point of the renaming, to prevent premature
3434 -- access to unfrozen types. The new declaration reuses the
3435 -- specification of the previous one, and must not be analyzed.
3437 pragma Assert
3438 (Is_Primitive (Entity (Nam))
3439 and then
3440 Is_Abstract_Type (Find_Dispatching_Type (Entity (Nam))));
3441 declare
3442 Old_Decl : constant Node_Id :=
3443 Unit_Declaration_Node (Rename_Spec);
3444 New_Decl : constant Node_Id :=
3445 Make_Subprogram_Declaration (Sloc (N),
3446 Specification =>
3447 Relocate_Node (Specification (Old_Decl)));
3448 begin
3449 Remove (Old_Decl);
3450 Insert_After (N, New_Decl);
3451 Set_Is_Abstract_Subprogram (Rename_Spec, False);
3452 Set_Analyzed (New_Decl);
3453 end;
3454 end if;
3456 Set_Corresponding_Body (Unit_Declaration_Node (Rename_Spec), New_S);
3458 if Ada_Version = Ada_83 and then Comes_From_Source (N) then
3459 Error_Msg_N ("(Ada 83) renaming cannot serve as a body", N);
3460 end if;
3462 Set_Convention (New_S, Convention (Rename_Spec));
3463 Check_Fully_Conformant (New_S, Rename_Spec);
3464 Set_Public_Status (New_S);
3466 if No_Return (Rename_Spec)
3467 and then not No_Return (Entity (Nam))
3468 then
3469 Error_Msg_NE
3470 ("renamed subprogram & must be No_Return", N, Entity (Nam));
3471 Error_Msg_N
3472 ("\since renaming subprogram is No_Return (RM 6.5.1(7/2))", N);
3473 end if;
3475 -- The specification does not introduce new formals, but only
3476 -- repeats the formals of the original subprogram declaration.
3477 -- For cross-reference purposes, and for refactoring tools, we
3478 -- treat the formals of the renaming declaration as body formals.
3480 Reference_Body_Formals (Rename_Spec, New_S);
3482 -- Indicate that the entity in the declaration functions like the
3483 -- corresponding body, and is not a new entity. The body will be
3484 -- constructed later at the freeze point, so indicate that the
3485 -- completion has not been seen yet.
3487 Reinit_Field_To_Zero (New_S, F_Has_Out_Or_In_Out_Parameter);
3488 Reinit_Field_To_Zero (New_S, F_Needs_No_Actuals,
3489 Old_Ekind => (E_Function | E_Procedure => True, others => False));
3490 Mutate_Ekind (New_S, E_Subprogram_Body);
3491 New_S := Rename_Spec;
3492 Set_Has_Completion (Rename_Spec, False);
3494 -- Ada 2005: check overriding indicator
3496 if Present (Overridden_Operation (Rename_Spec)) then
3497 if Must_Not_Override (Specification (N)) then
3498 Error_Msg_NE
3499 ("subprogram& overrides inherited operation",
3500 N, Rename_Spec);
3502 elsif Style_Check
3503 and then not Must_Override (Specification (N))
3504 then
3505 Style.Missing_Overriding (N, Rename_Spec);
3506 end if;
3508 elsif Must_Override (Specification (N))
3509 and then not Can_Override_Operator (Rename_Spec)
3510 then
3511 Error_Msg_NE ("subprogram& is not overriding", N, Rename_Spec);
3512 end if;
3514 -- AI12-0132: a renames-as-body freezes the expression of any
3515 -- expression function that it renames.
3517 if Is_Entity_Name (Nam)
3518 and then Is_Expression_Function (Entity (Nam))
3519 and then not Inside_A_Generic
3520 then
3521 Freeze_Expr_Types
3522 (Def_Id => Entity (Nam),
3523 Typ => Etype (Entity (Nam)),
3524 Expr =>
3525 Expression
3526 (Original_Node (Unit_Declaration_Node (Entity (Nam)))),
3527 N => N);
3528 end if;
3530 -- Normal subprogram renaming (not renaming as body)
3532 else
3533 Generate_Definition (New_S);
3534 New_Overloaded_Entity (New_S);
3536 if not (Is_Entity_Name (Nam)
3537 and then Is_Intrinsic_Subprogram (Entity (Nam)))
3538 then
3539 Check_Delayed_Subprogram (New_S);
3540 end if;
3542 -- Verify that a SPARK renaming does not declare a primitive
3543 -- operation of a tagged type.
3545 Check_SPARK_Primitive_Operation (New_S);
3546 end if;
3548 -- There is no need for elaboration checks on the new entity, which may
3549 -- be called before the next freezing point where the body will appear.
3550 -- Elaboration checks refer to the real entity, not the one created by
3551 -- the renaming declaration.
3553 Set_Kill_Elaboration_Checks (New_S, True);
3555 -- If we had a previous error, indicate a completion is present to stop
3556 -- junk cascaded messages, but don't take any further action.
3558 if Etype (Nam) = Any_Type then
3559 Set_Has_Completion (New_S);
3560 return;
3562 -- Case where name has the form of a selected component
3564 elsif Nkind (Nam) = N_Selected_Component then
3566 -- A name which has the form A.B can designate an entry of task A, a
3567 -- protected operation of protected object A, or finally a primitive
3568 -- operation of object A. In the later case, A is an object of some
3569 -- tagged type, or an access type that denotes one such. To further
3570 -- distinguish these cases, note that the scope of a task entry or
3571 -- protected operation is type of the prefix.
3573 -- The prefix could be an overloaded function call that returns both
3574 -- kinds of operations. This overloading pathology is left to the
3575 -- dedicated reader ???
3577 declare
3578 T : constant Entity_Id := Etype (Prefix (Nam));
3580 begin
3581 if Present (T)
3582 and then
3583 (Is_Tagged_Type (T)
3584 or else
3585 (Is_Access_Type (T)
3586 and then Is_Tagged_Type (Designated_Type (T))))
3587 and then Scope (Entity (Selector_Name (Nam))) /= T
3588 then
3589 Analyze_Renamed_Primitive_Operation
3590 (N, New_S, Present (Rename_Spec));
3591 return;
3593 else
3594 -- Renamed entity is an entry or protected operation. For those
3595 -- cases an explicit body is built (at the point of freezing of
3596 -- this entity) that contains a call to the renamed entity.
3598 -- This is not allowed for renaming as body if the renamed
3599 -- spec is already frozen (see RM 8.5.4(5) for details).
3601 if Present (Rename_Spec) and then Is_Frozen (Rename_Spec) then
3602 Error_Msg_N
3603 ("renaming-as-body cannot rename entry as subprogram", N);
3604 Error_Msg_NE
3605 ("\since & is already frozen (RM 8.5.4(5))",
3606 N, Rename_Spec);
3607 else
3608 Analyze_Renamed_Entry (N, New_S, Present (Rename_Spec));
3609 end if;
3611 return;
3612 end if;
3613 end;
3615 -- Case where name is an explicit dereference X.all
3617 elsif Nkind (Nam) = N_Explicit_Dereference then
3619 -- Renamed entity is designated by access_to_subprogram expression.
3620 -- Must build body to encapsulate call, as in the entry case.
3622 Analyze_Renamed_Dereference (N, New_S, Present (Rename_Spec));
3623 return;
3625 -- Indexed component
3627 elsif Nkind (Nam) = N_Indexed_Component then
3628 Analyze_Renamed_Family_Member (N, New_S, Present (Rename_Spec));
3629 return;
3631 -- Character literal
3633 elsif Nkind (Nam) = N_Character_Literal then
3634 Analyze_Renamed_Character (N, New_S, Present (Rename_Spec));
3635 return;
3637 -- Only remaining case is where we have a non-entity name, or a renaming
3638 -- of some other non-overloadable entity.
3640 elsif not Is_Entity_Name (Nam)
3641 or else not Is_Overloadable (Entity (Nam))
3642 then
3643 -- Do not mention the renaming if it comes from an instance
3645 if not Is_Actual then
3646 Error_Msg_N ("expect valid subprogram name in renaming", N);
3647 else
3648 Error_Msg_NE ("no visible subprogram for formal&", N, Nam);
3649 end if;
3651 return;
3652 end if;
3654 -- Find the renamed entity that matches the given specification. Disable
3655 -- Ada_83 because there is no requirement of full conformance between
3656 -- renamed entity and new entity, even though the same circuit is used.
3658 -- This is a bit of an odd case, which introduces a really irregular use
3659 -- of Ada_Version[_Explicit]. Would be nice to find cleaner way to do
3660 -- this. ???
3662 Ada_Version := Ada_Version_Type'Max (Ada_Version, Ada_95);
3663 Ada_Version_Pragma := Empty;
3664 Ada_Version_Explicit := Ada_Version;
3666 if No (Old_S) then
3667 Old_S := Find_Renamed_Entity (N, Name (N), New_S, Is_Actual);
3669 -- The visible operation may be an inherited abstract operation that
3670 -- was overridden in the private part, in which case a call will
3671 -- dispatch to the overriding operation. Use the overriding one in
3672 -- the renaming declaration, to prevent spurious errors below.
3674 if Is_Overloadable (Old_S)
3675 and then Is_Abstract_Subprogram (Old_S)
3676 and then No (DTC_Entity (Old_S))
3677 and then Present (Alias (Old_S))
3678 and then not Is_Abstract_Subprogram (Alias (Old_S))
3679 and then Present (Overridden_Operation (Alias (Old_S)))
3680 then
3681 Old_S := Alias (Old_S);
3682 end if;
3684 -- When the renamed subprogram is overloaded and used as an actual
3685 -- of a generic, its entity is set to the first available homonym.
3686 -- We must first disambiguate the name, then set the proper entity.
3688 if Is_Actual and then Is_Overloaded (Nam) then
3689 Set_Entity (Nam, Old_S);
3690 end if;
3691 end if;
3693 -- Most common case: subprogram renames subprogram. No body is generated
3694 -- in this case, so we must indicate the declaration is complete as is.
3695 -- and inherit various attributes of the renamed subprogram.
3697 if No (Rename_Spec) then
3698 Set_Has_Completion (New_S);
3699 Set_Is_Imported (New_S, Is_Imported (Entity (Nam)));
3700 Set_Is_Pure (New_S, Is_Pure (Entity (Nam)));
3701 Set_Is_Preelaborated (New_S, Is_Preelaborated (Entity (Nam)));
3703 -- Ada 2005 (AI-423): Check the consistency of null exclusions
3704 -- between a subprogram and its correct renaming.
3706 -- Note: the Any_Id check is a guard that prevents compiler crashes
3707 -- when performing a null exclusion check between a renaming and a
3708 -- renamed subprogram that has been found to be illegal.
3710 if Ada_Version >= Ada_2005 and then Entity (Nam) /= Any_Id then
3711 Check_Null_Exclusion
3712 (Ren => New_S,
3713 Sub => Entity (Nam));
3714 end if;
3716 -- Enforce the Ada 2005 rule that the renamed entity cannot require
3717 -- overriding. The flag Requires_Overriding is set very selectively
3718 -- and misses some other illegal cases. The additional conditions
3719 -- checked below are sufficient but not necessary ???
3721 -- The rule does not apply to the renaming generated for an actual
3722 -- subprogram in an instance.
3724 if Is_Actual then
3725 null;
3727 -- Guard against previous errors, and omit renamings of predefined
3728 -- operators.
3730 elsif Ekind (Old_S) not in E_Function | E_Procedure then
3731 null;
3733 elsif Requires_Overriding (Old_S)
3734 or else
3735 (Is_Abstract_Subprogram (Old_S)
3736 and then Present (Find_Dispatching_Type (Old_S))
3737 and then not Is_Abstract_Type (Find_Dispatching_Type (Old_S)))
3738 then
3739 Error_Msg_N
3740 ("renamed entity cannot be subprogram that requires overriding "
3741 & "(RM 8.5.4 (5.1))", N);
3742 end if;
3744 declare
3745 Prev : constant Entity_Id := Overridden_Operation (New_S);
3746 begin
3747 if Present (Prev)
3748 and then
3749 (Has_Non_Trivial_Precondition (Prev)
3750 or else Has_Non_Trivial_Precondition (Old_S))
3751 then
3752 Error_Msg_NE
3753 ("conflicting inherited classwide preconditions in renaming "
3754 & "of& (RM 6.1.1 (17)", N, Old_S);
3755 end if;
3756 end;
3757 end if;
3759 if Old_S /= Any_Id then
3760 if Is_Actual and then From_Default (N) then
3762 -- This is an implicit reference to the default actual
3764 Generate_Reference (Old_S, Nam, Typ => 'i', Force => True);
3766 else
3767 Generate_Reference (Old_S, Nam);
3768 end if;
3770 Check_Internal_Protected_Use (N, Old_S);
3772 -- For a renaming-as-body, require subtype conformance, but if the
3773 -- declaration being completed has not been frozen, then inherit the
3774 -- convention of the renamed subprogram prior to checking conformance
3775 -- (unless the renaming has an explicit convention established; the
3776 -- rule stated in the RM doesn't seem to address this ???).
3778 if Present (Rename_Spec) then
3779 Generate_Reference (Rename_Spec, Defining_Entity (Spec), 'b');
3780 Style.Check_Identifier (Defining_Entity (Spec), Rename_Spec);
3782 if not Is_Frozen (Rename_Spec) then
3783 if not Has_Convention_Pragma (Rename_Spec) then
3784 Set_Convention (New_S, Convention (Old_S));
3785 end if;
3787 if Ekind (Old_S) /= E_Operator then
3788 Check_Mode_Conformant (New_S, Old_S, Spec);
3789 end if;
3791 if Original_Subprogram (Old_S) = Rename_Spec then
3792 Error_Msg_N ("unfrozen subprogram cannot rename itself", N);
3793 else
3794 Check_Formal_Subprogram_Conformance (New_S, Old_S, Spec);
3795 end if;
3796 else
3797 Check_Subtype_Conformant (New_S, Old_S, Spec);
3798 end if;
3800 Check_Frozen_Renaming (N, Rename_Spec);
3802 -- Check explicitly that renamed entity is not intrinsic, because
3803 -- in a generic the renamed body is not built. In this case,
3804 -- the renaming_as_body is a completion.
3806 if Inside_A_Generic then
3807 if Is_Frozen (Rename_Spec)
3808 and then Is_Intrinsic_Subprogram (Old_S)
3809 then
3810 Error_Msg_N
3811 ("subprogram in renaming_as_body cannot be intrinsic",
3812 Name (N));
3813 end if;
3815 Set_Has_Completion (Rename_Spec);
3816 end if;
3818 elsif Ekind (Old_S) /= E_Operator then
3820 -- If this a defaulted subprogram for a class-wide actual there is
3821 -- no check for mode conformance, given that the signatures don't
3822 -- match (the source mentions T but the actual mentions T'Class).
3824 if CW_Actual then
3825 null;
3827 -- No need for a redundant error message if this is a nested
3828 -- instance, unless the current instantiation (of a child unit)
3829 -- is a compilation unit, which is not analyzed when the parent
3830 -- generic is analyzed.
3832 elsif not Is_Actual
3833 or else No (Enclosing_Instance)
3834 or else Is_Compilation_Unit (Current_Scope)
3835 then
3836 Check_Mode_Conformant (New_S, Old_S);
3837 end if;
3838 end if;
3840 if No (Rename_Spec) then
3842 -- The parameter profile of the new entity is that of the renamed
3843 -- entity: the subtypes given in the specification are irrelevant.
3845 Inherit_Renamed_Profile (New_S, Old_S);
3847 -- A call to the subprogram is transformed into a call to the
3848 -- renamed entity. This is transitive if the renamed entity is
3849 -- itself a renaming.
3851 if Present (Alias (Old_S)) then
3852 Set_Alias (New_S, Alias (Old_S));
3853 else
3854 Set_Alias (New_S, Old_S);
3855 end if;
3857 -- Note that we do not set Is_Intrinsic_Subprogram if we have a
3858 -- renaming as body, since the entity in this case is not an
3859 -- intrinsic (it calls an intrinsic, but we have a real body for
3860 -- this call, and it is in this body that the required intrinsic
3861 -- processing will take place).
3863 -- Also, if this is a renaming of inequality, the renamed operator
3864 -- is intrinsic, but what matters is the corresponding equality
3865 -- operator, which may be user-defined.
3867 Set_Is_Intrinsic_Subprogram
3868 (New_S,
3869 Is_Intrinsic_Subprogram (Old_S)
3870 and then
3871 (Chars (Old_S) /= Name_Op_Ne
3872 or else Ekind (Old_S) = E_Operator
3873 or else Is_Intrinsic_Subprogram
3874 (Corresponding_Equality (Old_S))));
3876 if Ekind (Alias (New_S)) = E_Operator then
3877 Set_Has_Delayed_Freeze (New_S, False);
3878 end if;
3880 -- If the renaming corresponds to an association for an abstract
3881 -- formal subprogram, then various attributes must be set to
3882 -- indicate that the renaming is an abstract dispatching operation
3883 -- with a controlling type.
3885 -- Skip this decoration when the renaming corresponds to an
3886 -- association with class-wide wrapper (see above) because such
3887 -- wrapper is neither abstract nor a dispatching operation (its
3888 -- body has the dispatching call to the wrapped primitive).
3890 if Is_Actual
3891 and then Is_Abstract_Subprogram (Formal_Spec)
3892 and then No (Wrapped_Prim)
3893 then
3895 -- Mark the renaming as abstract here, so Find_Dispatching_Type
3896 -- see it as corresponding to a generic association for a
3897 -- formal abstract subprogram
3899 Set_Is_Abstract_Subprogram (New_S);
3901 declare
3902 New_S_Ctrl_Type : constant Entity_Id :=
3903 Find_Dispatching_Type (New_S);
3904 Old_S_Ctrl_Type : constant Entity_Id :=
3905 Find_Dispatching_Type (Old_S);
3907 begin
3909 -- The actual must match the (instance of the) formal,
3910 -- and must be a controlling type.
3912 if Old_S_Ctrl_Type /= New_S_Ctrl_Type
3913 or else No (New_S_Ctrl_Type)
3914 then
3915 if No (New_S_Ctrl_Type) then
3916 Error_Msg_N
3917 ("actual must be dispatching subprogram", Nam);
3918 else
3919 Error_Msg_NE
3920 ("actual must be dispatching subprogram for type&",
3921 Nam, New_S_Ctrl_Type);
3922 end if;
3924 else
3925 Set_Is_Dispatching_Operation (New_S);
3926 Check_Controlling_Formals (New_S_Ctrl_Type, New_S);
3928 -- If the actual in the formal subprogram is itself a
3929 -- formal abstract subprogram association, there's no
3930 -- dispatch table component or position to inherit.
3932 if Present (DTC_Entity (Old_S)) then
3933 Set_DTC_Entity (New_S, DTC_Entity (Old_S));
3934 Set_DT_Position_Value (New_S, DT_Position (Old_S));
3935 end if;
3936 end if;
3937 end;
3938 end if;
3939 end if;
3941 if Is_Actual then
3942 null;
3944 -- The following is illegal, because F hides whatever other F may
3945 -- be around:
3946 -- function F (...) renames F;
3948 elsif Old_S = New_S
3949 or else (Nkind (Nam) /= N_Expanded_Name
3950 and then Chars (Old_S) = Chars (New_S))
3951 then
3952 Error_Msg_N ("subprogram cannot rename itself", N);
3954 -- This is illegal even if we use a selector:
3955 -- function F (...) renames Pkg.F;
3956 -- because F is still hidden.
3958 elsif Nkind (Nam) = N_Expanded_Name
3959 and then Entity (Prefix (Nam)) = Current_Scope
3960 and then Chars (Selector_Name (Nam)) = Chars (New_S)
3961 then
3962 -- This is an error, but we overlook the error and accept the
3963 -- renaming if the special Overriding_Renamings mode is in effect.
3965 if not Overriding_Renamings then
3966 Error_Msg_NE
3967 ("implicit operation& is not visible (RM 8.3 (15))",
3968 Nam, Old_S);
3969 end if;
3971 -- Check whether an expanded name used for the renamed subprogram
3972 -- begins with the same name as the renaming itself, and if so,
3973 -- issue an error about the prefix being hidden by the renaming.
3974 -- We exclude generic instances from this checking, since such
3975 -- normally illegal renamings can be constructed when expanding
3976 -- instantiations.
3978 elsif Nkind (Nam) = N_Expanded_Name and then not In_Instance then
3979 declare
3980 function Ult_Expanded_Prefix (N : Node_Id) return Node_Id is
3981 (if Nkind (N) /= N_Expanded_Name
3982 then N
3983 else Ult_Expanded_Prefix (Prefix (N)));
3984 -- Returns the ultimate prefix of an expanded name
3986 begin
3987 if Chars (Entity (Ult_Expanded_Prefix (Nam))) = Chars (New_S)
3988 then
3989 Error_Msg_Sloc := Sloc (N);
3990 Error_Msg_NE
3991 ("& is hidden by declaration#", Nam, New_S);
3992 end if;
3993 end;
3994 end if;
3996 Set_Convention (New_S, Convention (Old_S));
3998 if Is_Abstract_Subprogram (Old_S) then
3999 if Present (Rename_Spec) then
4000 Error_Msg_N
4001 ("a renaming-as-body cannot rename an abstract subprogram",
4003 Set_Has_Completion (Rename_Spec);
4004 else
4005 Set_Is_Abstract_Subprogram (New_S);
4006 end if;
4007 end if;
4009 Check_Library_Unit_Renaming (N, Old_S);
4011 -- Pathological case: procedure renames entry in the scope of its
4012 -- task. Entry is given by simple name, but body must be built for
4013 -- procedure. Of course if called it will deadlock.
4015 if Ekind (Old_S) = E_Entry then
4016 Set_Has_Completion (New_S, False);
4017 Set_Alias (New_S, Empty);
4018 end if;
4020 -- Do not freeze the renaming nor the renamed entity when the context
4021 -- is an enclosing generic. Freezing is an expansion activity, and in
4022 -- addition the renamed entity may depend on the generic formals of
4023 -- the enclosing generic.
4025 if Is_Actual and not Inside_A_Generic then
4026 Freeze_Before (N, Old_S);
4027 Freeze_Actual_Profile;
4028 Set_Has_Delayed_Freeze (New_S, False);
4029 Freeze_Before (N, New_S);
4031 if (Ekind (Old_S) = E_Procedure or else Ekind (Old_S) = E_Function)
4032 and then not Is_Abstract_Subprogram (Formal_Spec)
4033 then
4034 -- An abstract subprogram is only allowed as an actual in the
4035 -- case where the formal subprogram is also abstract.
4037 if Is_Abstract_Subprogram (Old_S) then
4038 Error_Msg_N
4039 ("abstract subprogram not allowed as generic actual", Nam);
4040 end if;
4042 -- AI12-0412: A primitive of an abstract type with Pre'Class
4043 -- or Post'Class aspects specified with nonstatic expressions
4044 -- is not allowed as actual for a nonabstract formal subprogram
4045 -- (see RM 6.1.1(18.2/5).
4047 if Is_Dispatching_Operation (Old_S)
4048 and then
4049 Is_Prim_Of_Abst_Type_With_Nonstatic_CW_Pre_Post (Old_S)
4050 then
4051 Error_Msg_N
4052 ("primitive of abstract type with nonstatic class-wide "
4053 & "pre/postconditions not allowed as actual",
4054 Nam);
4055 end if;
4056 end if;
4057 end if;
4059 else
4060 -- A common error is to assume that implicit operators for types are
4061 -- defined in Standard, or in the scope of a subtype. In those cases
4062 -- where the renamed entity is given with an expanded name, it is
4063 -- worth mentioning that operators for the type are not declared in
4064 -- the scope given by the prefix.
4066 if Nkind (Nam) = N_Expanded_Name
4067 and then Nkind (Selector_Name (Nam)) = N_Operator_Symbol
4068 and then Scope (Entity (Nam)) = Standard_Standard
4069 then
4070 declare
4071 T : constant Entity_Id :=
4072 Base_Type (Etype (First_Formal (New_S)));
4073 begin
4074 Error_Msg_Node_2 := Prefix (Nam);
4075 Error_Msg_NE
4076 ("operator for type& is not declared in&", Prefix (Nam), T);
4077 end;
4079 else
4080 Error_Msg_NE
4081 ("no visible subprogram matches the specification for&",
4082 Spec, New_S);
4083 end if;
4085 if Present (Candidate_Renaming) then
4086 declare
4087 F1 : Entity_Id;
4088 F2 : Entity_Id;
4089 T1 : Entity_Id;
4091 begin
4092 F1 := First_Formal (Candidate_Renaming);
4093 F2 := First_Formal (New_S);
4094 T1 := First_Subtype (Etype (F1));
4095 while Present (F1) and then Present (F2) loop
4096 Next_Formal (F1);
4097 Next_Formal (F2);
4098 end loop;
4100 if Present (F1) and then Present (Default_Value (F1)) then
4101 if Present (Next_Formal (F1)) then
4102 Error_Msg_NE
4103 ("\missing specification for & and other formals with "
4104 & "defaults", Spec, F1);
4105 else
4106 Error_Msg_NE ("\missing specification for &", Spec, F1);
4107 end if;
4108 end if;
4110 if Nkind (Nam) = N_Operator_Symbol
4111 and then From_Default (N)
4112 then
4113 Error_Msg_Node_2 := T1;
4114 Error_Msg_NE
4115 ("default & on & is not directly visible", Nam, Nam);
4116 end if;
4117 end;
4118 end if;
4119 end if;
4121 -- Ada 2005 AI 404: if the new subprogram is dispatching, verify that
4122 -- controlling access parameters are known non-null for the renamed
4123 -- subprogram. Test also applies to a subprogram instantiation that
4124 -- is dispatching. Test is skipped if some previous error was detected
4125 -- that set Old_S to Any_Id.
4127 if Ada_Version >= Ada_2005
4128 and then Old_S /= Any_Id
4129 and then not Is_Dispatching_Operation (Old_S)
4130 and then Is_Dispatching_Operation (New_S)
4131 then
4132 declare
4133 Old_F : Entity_Id;
4134 New_F : Entity_Id;
4136 begin
4137 Old_F := First_Formal (Old_S);
4138 New_F := First_Formal (New_S);
4139 while Present (Old_F) loop
4140 if Ekind (Etype (Old_F)) = E_Anonymous_Access_Type
4141 and then Is_Controlling_Formal (New_F)
4142 and then not Can_Never_Be_Null (Old_F)
4143 then
4144 Error_Msg_N ("access parameter is controlling,", New_F);
4145 Error_Msg_NE
4146 ("\corresponding parameter of& must be explicitly null "
4147 & "excluding", New_F, Old_S);
4148 end if;
4150 Next_Formal (Old_F);
4151 Next_Formal (New_F);
4152 end loop;
4153 end;
4154 end if;
4156 -- A useful warning, suggested by Ada Bug Finder (Ada-Europe 2005)
4157 -- is to warn if an operator is being renamed as a different operator.
4158 -- If the operator is predefined, examine the kind of the entity, not
4159 -- the abbreviated declaration in Standard.
4161 if Comes_From_Source (N)
4162 and then Present (Old_S)
4163 and then (Nkind (Old_S) = N_Defining_Operator_Symbol
4164 or else Ekind (Old_S) = E_Operator)
4165 and then Nkind (New_S) = N_Defining_Operator_Symbol
4166 and then Chars (Old_S) /= Chars (New_S)
4167 then
4168 Error_Msg_NE
4169 ("& is being renamed as a different operator??", N, Old_S);
4170 end if;
4172 -- Check for renaming of obsolescent subprogram
4174 Check_Obsolescent_2005_Entity (Entity (Nam), Nam);
4176 -- Another warning or some utility: if the new subprogram as the same
4177 -- name as the old one, the old one is not hidden by an outer homograph,
4178 -- the new one is not a public symbol, and the old one is otherwise
4179 -- directly visible, the renaming is superfluous.
4181 if Chars (Old_S) = Chars (New_S)
4182 and then Comes_From_Source (N)
4183 and then Scope (Old_S) /= Standard_Standard
4184 and then Warn_On_Redundant_Constructs
4185 and then (Is_Immediately_Visible (Old_S)
4186 or else Is_Potentially_Use_Visible (Old_S))
4187 and then Is_Overloadable (Current_Scope)
4188 and then Chars (Current_Scope) /= Chars (Old_S)
4189 then
4190 Error_Msg_N
4191 ("redundant renaming, entity is directly visible?r?", Name (N));
4192 end if;
4194 -- Implementation-defined aspect specifications can appear in a renaming
4195 -- declaration, but not language-defined ones. The call to procedure
4196 -- Analyze_Aspect_Specifications will take care of this error check.
4198 if Has_Aspects (N) then
4199 Analyze_Aspect_Specifications (N, New_S);
4200 end if;
4202 -- AI12-0279
4204 if Is_Actual
4205 and then Has_Yield_Aspect (Formal_Spec)
4206 and then not Has_Yield_Aspect (Old_S)
4207 then
4208 Error_Msg_Name_1 := Name_Yield;
4209 Error_Msg_N
4210 ("actual subprogram& must have aspect% to match formal", Name (N));
4211 end if;
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
4225 -- formals.
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)
4231 then
4232 Mark_Use_Clauses (New_S);
4234 -- Handle overloaded subprograms
4236 if Present (Alias (New_S)) then
4237 Mark_Use_Clauses (Alias (New_S));
4238 end if;
4239 end if;
4240 end Analyze_Subprogram_Renaming;
4242 -------------------------
4243 -- Analyze_Use_Package --
4244 -------------------------
4246 -- Resolve the package names in the use clause, and make all the visible
4247 -- entities defined in the package potentially use-visible. If the package
4248 -- is already in use from a previous use clause, its visible entities are
4249 -- already use-visible. In that case, mark the occurrence as a redundant
4250 -- use. If the package is an open scope, i.e. if the use clause occurs
4251 -- within the package itself, ignore it.
4253 procedure Analyze_Use_Package (N : Node_Id; Chain : Boolean := True) is
4254 procedure Analyze_Package_Name (Clause : Node_Id);
4255 -- Perform analysis on a package name from a use_package_clause
4257 procedure Analyze_Package_Name_List (Head_Clause : Node_Id);
4258 -- Similar to Analyze_Package_Name but iterates over all the names
4259 -- in a use clause.
4261 --------------------------
4262 -- Analyze_Package_Name --
4263 --------------------------
4265 procedure Analyze_Package_Name (Clause : Node_Id) is
4266 Pack : constant Node_Id := Name (Clause);
4267 Pref : Node_Id;
4269 begin
4270 pragma Assert (Nkind (Clause) = N_Use_Package_Clause);
4271 Analyze (Pack);
4273 -- Verify that the package standard is not directly named in a
4274 -- use_package_clause.
4276 if Nkind (Parent (Clause)) = N_Compilation_Unit
4277 and then Nkind (Pack) = N_Expanded_Name
4278 then
4279 Pref := Prefix (Pack);
4281 while Nkind (Pref) = N_Expanded_Name loop
4282 Pref := Prefix (Pref);
4283 end loop;
4285 if Entity (Pref) = Standard_Standard then
4286 Error_Msg_N
4287 ("predefined package Standard cannot appear in a context "
4288 & "clause", Pref);
4289 end if;
4290 end if;
4291 end Analyze_Package_Name;
4293 -------------------------------
4294 -- Analyze_Package_Name_List --
4295 -------------------------------
4297 procedure Analyze_Package_Name_List (Head_Clause : Node_Id) is
4298 Curr : Node_Id;
4300 begin
4301 -- Due to the way source use clauses are split during parsing we are
4302 -- forced to simply iterate through all entities in scope until the
4303 -- clause representing the last name in the list is found.
4305 Curr := Head_Clause;
4306 while Present (Curr) loop
4307 Analyze_Package_Name (Curr);
4309 -- Stop iterating over the names in the use clause when we are at
4310 -- the last one.
4312 exit when not More_Ids (Curr) and then Prev_Ids (Curr);
4313 Next (Curr);
4314 end loop;
4315 end Analyze_Package_Name_List;
4317 -- Local variables
4319 Pack : Entity_Id;
4321 -- Start of processing for Analyze_Use_Package
4323 begin
4324 Set_Hidden_By_Use_Clause (N, No_Elist);
4326 -- Use clause not allowed in a spec of a predefined package declaration
4327 -- except that packages whose file name starts a-n are OK (these are
4328 -- children of Ada.Numerics, which are never loaded by Rtsfind).
4330 if Is_Predefined_Unit (Current_Sem_Unit)
4331 and then Get_Name_String
4332 (Unit_File_Name (Current_Sem_Unit)) (1 .. 3) /= "a-n"
4333 and then Nkind (Unit (Cunit (Current_Sem_Unit))) =
4334 N_Package_Declaration
4335 then
4336 Error_Msg_N ("use clause not allowed in predefined spec", N);
4337 end if;
4339 -- Loop through all package names from the original use clause in
4340 -- order to analyze referenced packages. A use_package_clause with only
4341 -- one name does not have More_Ids or Prev_Ids set, while a clause with
4342 -- More_Ids only starts the chain produced by the parser.
4344 if not More_Ids (N) and then not Prev_Ids (N) then
4345 Analyze_Package_Name (N);
4347 elsif More_Ids (N) and then not Prev_Ids (N) then
4348 Analyze_Package_Name_List (N);
4349 end if;
4351 if not Is_Entity_Name (Name (N)) then
4352 Error_Msg_N ("& is not a package", Name (N));
4354 return;
4355 end if;
4357 if Chain then
4358 Chain_Use_Clause (N);
4359 end if;
4361 Pack := Entity (Name (N));
4363 -- There are many cases where scopes are manipulated during analysis, so
4364 -- check that Pack's current use clause has not already been chained
4365 -- before setting its previous use clause.
4367 if Ekind (Pack) = E_Package
4368 and then Present (Current_Use_Clause (Pack))
4369 and then Current_Use_Clause (Pack) /= N
4370 and then No (Prev_Use_Clause (N))
4371 and then Prev_Use_Clause (Current_Use_Clause (Pack)) /= N
4372 then
4373 Set_Prev_Use_Clause (N, Current_Use_Clause (Pack));
4374 end if;
4376 -- Mark all entities as potentially use visible
4378 if Ekind (Pack) /= E_Package and then Etype (Pack) /= Any_Type then
4379 if Ekind (Pack) = E_Generic_Package then
4380 Error_Msg_N -- CODEFIX
4381 ("a generic package is not allowed in a use clause", Name (N));
4383 elsif Is_Generic_Subprogram (Pack) then
4384 Error_Msg_N -- CODEFIX
4385 ("a generic subprogram is not allowed in a use clause",
4386 Name (N));
4388 elsif Is_Subprogram (Pack) then
4389 Error_Msg_N -- CODEFIX
4390 ("a subprogram is not allowed in a use clause", Name (N));
4392 else
4393 Error_Msg_N ("& is not allowed in a use clause", Name (N));
4394 end if;
4396 else
4397 if Nkind (Parent (N)) = N_Compilation_Unit then
4398 Check_In_Previous_With_Clause (N, Name (N));
4399 end if;
4401 Use_One_Package (N, Name (N));
4402 end if;
4404 Mark_Ghost_Clause (N);
4405 end Analyze_Use_Package;
4407 ----------------------
4408 -- Analyze_Use_Type --
4409 ----------------------
4411 procedure Analyze_Use_Type (N : Node_Id; Chain : Boolean := True) is
4412 E : Entity_Id;
4413 Id : Node_Id;
4415 begin
4416 Set_Hidden_By_Use_Clause (N, No_Elist);
4418 -- Chain clause to list of use clauses in current scope when flagged
4420 if Chain then
4421 Chain_Use_Clause (N);
4422 end if;
4424 -- Obtain the base type of the type denoted within the use_type_clause's
4425 -- subtype mark.
4427 Id := Subtype_Mark (N);
4428 Find_Type (Id);
4429 E := Base_Type (Entity (Id));
4431 -- There are many cases where a use_type_clause may be reanalyzed due to
4432 -- manipulation of the scope stack so we much guard against those cases
4433 -- here, otherwise, we must add the new use_type_clause to the previous
4434 -- use_type_clause chain in order to mark redundant use_type_clauses as
4435 -- used. When the redundant use-type clauses appear in a parent unit and
4436 -- a child unit we must prevent a circularity in the chain that would
4437 -- otherwise result from the separate steps of analysis and installation
4438 -- of the parent context.
4440 if Present (Current_Use_Clause (E))
4441 and then Current_Use_Clause (E) /= N
4442 and then Prev_Use_Clause (Current_Use_Clause (E)) /= N
4443 and then No (Prev_Use_Clause (N))
4444 then
4445 Set_Prev_Use_Clause (N, Current_Use_Clause (E));
4446 end if;
4448 -- If the Used_Operations list is already initialized, the clause has
4449 -- been analyzed previously, and it is being reinstalled, for example
4450 -- when the clause appears in a package spec and we are compiling the
4451 -- corresponding package body. In that case, make the entities on the
4452 -- existing list use_visible, and mark the corresponding types In_Use.
4454 if Present (Used_Operations (N)) then
4455 declare
4456 Elmt : Elmt_Id;
4458 begin
4459 Use_One_Type (Subtype_Mark (N), Installed => True);
4461 Elmt := First_Elmt (Used_Operations (N));
4462 while Present (Elmt) loop
4463 Set_Is_Potentially_Use_Visible (Node (Elmt));
4464 Next_Elmt (Elmt);
4465 end loop;
4466 end;
4468 return;
4469 end if;
4471 -- Otherwise, create new list and attach to it the operations that are
4472 -- made use-visible by the clause.
4474 Set_Used_Operations (N, New_Elmt_List);
4475 E := Entity (Id);
4477 if E /= Any_Type then
4478 Use_One_Type (Id);
4480 if Nkind (Parent (N)) = N_Compilation_Unit then
4481 if Nkind (Id) = N_Identifier then
4482 Error_Msg_N ("type is not directly visible", Id);
4484 elsif Is_Child_Unit (Scope (E))
4485 and then Scope (E) /= System_Aux_Id
4486 then
4487 Check_In_Previous_With_Clause (N, Prefix (Id));
4488 end if;
4489 end if;
4491 else
4492 -- If the use_type_clause appears in a compilation unit context,
4493 -- check whether it comes from a unit that may appear in a
4494 -- limited_with_clause, for a better error message.
4496 if Nkind (Parent (N)) = N_Compilation_Unit
4497 and then Nkind (Id) /= N_Identifier
4498 then
4499 declare
4500 Item : Node_Id;
4501 Pref : Node_Id;
4503 function Mentioned (Nam : Node_Id) return Boolean;
4504 -- Check whether the prefix of expanded name for the type
4505 -- appears in the prefix of some limited_with_clause.
4507 ---------------
4508 -- Mentioned --
4509 ---------------
4511 function Mentioned (Nam : Node_Id) return Boolean is
4512 begin
4513 return Nkind (Name (Item)) = N_Selected_Component
4514 and then Chars (Prefix (Name (Item))) = Chars (Nam);
4515 end Mentioned;
4517 begin
4518 Pref := Prefix (Id);
4519 Item := First (Context_Items (Parent (N)));
4520 while Present (Item) and then Item /= N loop
4521 if Nkind (Item) = N_With_Clause
4522 and then Limited_Present (Item)
4523 and then Mentioned (Pref)
4524 then
4525 Change_Error_Text
4526 (Get_Msg_Id, "premature usage of incomplete type");
4527 end if;
4529 Next (Item);
4530 end loop;
4531 end;
4532 end if;
4533 end if;
4535 Mark_Ghost_Clause (N);
4536 end Analyze_Use_Type;
4538 ------------------------
4539 -- Attribute_Renaming --
4540 ------------------------
4542 procedure Attribute_Renaming (N : Node_Id) is
4543 Loc : constant Source_Ptr := Sloc (N);
4544 Nam : constant Node_Id := Name (N);
4545 Spec : constant Node_Id := Specification (N);
4546 New_S : constant Entity_Id := Defining_Unit_Name (Spec);
4547 Aname : constant Name_Id := Attribute_Name (Nam);
4549 Form_Num : Nat := 0;
4550 Expr_List : List_Id := No_List;
4552 Attr_Node : Node_Id;
4553 Body_Node : Node_Id;
4554 Param_Spec : Node_Id;
4556 begin
4557 Generate_Definition (New_S);
4559 -- This procedure is called in the context of subprogram renaming, and
4560 -- thus the attribute must be one that is a subprogram. All of those
4561 -- have at least one formal parameter, with the exceptions of the GNAT
4562 -- attribute 'Img, which GNAT treats as renameable.
4564 if Is_Empty_List (Parameter_Specifications (Spec)) then
4565 if Aname /= Name_Img then
4566 Error_Msg_N
4567 ("subprogram renaming an attribute must have formals", N);
4568 return;
4569 end if;
4571 else
4572 Param_Spec := First (Parameter_Specifications (Spec));
4573 while Present (Param_Spec) loop
4574 Form_Num := Form_Num + 1;
4576 if Nkind (Parameter_Type (Param_Spec)) /= N_Access_Definition then
4577 Find_Type (Parameter_Type (Param_Spec));
4579 -- The profile of the new entity denotes the base type (s) of
4580 -- the types given in the specification. For access parameters
4581 -- there are no subtypes involved.
4583 Rewrite (Parameter_Type (Param_Spec),
4584 New_Occurrence_Of
4585 (Base_Type (Entity (Parameter_Type (Param_Spec))), Loc));
4586 end if;
4588 if No (Expr_List) then
4589 Expr_List := New_List;
4590 end if;
4592 Append_To (Expr_List,
4593 Make_Identifier (Loc,
4594 Chars => Chars (Defining_Identifier (Param_Spec))));
4596 -- The expressions in the attribute reference are not freeze
4597 -- points. Neither is the attribute as a whole, see below.
4599 Set_Must_Not_Freeze (Last (Expr_List));
4600 Next (Param_Spec);
4601 end loop;
4602 end if;
4604 -- Immediate error if too many formals. Other mismatches in number or
4605 -- types of parameters are detected when we analyze the body of the
4606 -- subprogram that we construct.
4608 if Form_Num > 2 then
4609 Error_Msg_N ("too many formals for attribute", N);
4611 -- Error if the attribute reference has expressions that look like
4612 -- formal parameters.
4614 elsif Present (Expressions (Nam)) then
4615 Error_Msg_N ("illegal expressions in attribute reference", Nam);
4617 elsif Aname in Name_Compose | Name_Exponent | Name_Leading_Part |
4618 Name_Pos | Name_Round | Name_Scaling |
4619 Name_Val
4620 then
4621 if Nkind (N) = N_Subprogram_Renaming_Declaration
4622 and then Present (Corresponding_Formal_Spec (N))
4623 then
4624 Error_Msg_N
4625 ("generic actual cannot be attribute involving universal type",
4626 Nam);
4627 else
4628 Error_Msg_N
4629 ("attribute involving a universal type cannot be renamed",
4630 Nam);
4631 end if;
4632 end if;
4634 -- Rewrite attribute node to have a list of expressions corresponding to
4635 -- the subprogram formals. A renaming declaration is not a freeze point,
4636 -- and the analysis of the attribute reference should not freeze the
4637 -- type of the prefix. We use the original node in the renaming so that
4638 -- its source location is preserved, and checks on stream attributes are
4639 -- properly applied.
4641 Attr_Node := Relocate_Node (Nam);
4642 Set_Expressions (Attr_Node, Expr_List);
4644 Set_Must_Not_Freeze (Attr_Node);
4645 Set_Must_Not_Freeze (Prefix (Nam));
4647 -- Case of renaming a function
4649 if Nkind (Spec) = N_Function_Specification then
4650 if Is_Procedure_Attribute_Name (Aname) then
4651 Error_Msg_N ("attribute can only be renamed as procedure", Nam);
4652 return;
4653 end if;
4655 Find_Type (Result_Definition (Spec));
4656 Rewrite (Result_Definition (Spec),
4657 New_Occurrence_Of
4658 (Base_Type (Entity (Result_Definition (Spec))), Loc));
4660 Body_Node :=
4661 Make_Subprogram_Body (Loc,
4662 Specification => Spec,
4663 Declarations => New_List,
4664 Handled_Statement_Sequence =>
4665 Make_Handled_Sequence_Of_Statements (Loc,
4666 Statements => New_List (
4667 Make_Simple_Return_Statement (Loc,
4668 Expression => Attr_Node))));
4670 -- Case of renaming a procedure
4672 else
4673 if not Is_Procedure_Attribute_Name (Aname) then
4674 Error_Msg_N ("attribute can only be renamed as function", Nam);
4675 return;
4676 end if;
4678 Body_Node :=
4679 Make_Subprogram_Body (Loc,
4680 Specification => Spec,
4681 Declarations => New_List,
4682 Handled_Statement_Sequence =>
4683 Make_Handled_Sequence_Of_Statements (Loc,
4684 Statements => New_List (Attr_Node)));
4685 end if;
4687 -- Signal the ABE mechanism that the generated subprogram body has not
4688 -- ABE ramifications.
4690 Set_Was_Attribute_Reference (Body_Node);
4692 -- In case of tagged types we add the body of the generated function to
4693 -- the freezing actions of the type (because in the general case such
4694 -- type is still not frozen). We exclude from this processing generic
4695 -- formal subprograms found in instantiations.
4697 -- We must exclude restricted run-time libraries because
4698 -- entity AST_Handler is defined in package System.Aux_Dec which is not
4699 -- available in those platforms. Note that we cannot use the function
4700 -- Restricted_Profile (instead of Configurable_Run_Time_Mode) because
4701 -- the ZFP run-time library is not defined as a profile, and we do not
4702 -- want to deal with AST_Handler in ZFP mode.
4704 if not Configurable_Run_Time_Mode
4705 and then not Present (Corresponding_Formal_Spec (N))
4706 and then not Is_RTE (Etype (Nam), RE_AST_Handler)
4707 then
4708 declare
4709 P : constant Node_Id := Prefix (Nam);
4711 begin
4712 -- The prefix of 'Img is an object that is evaluated for each call
4713 -- of the function that renames it.
4715 if Aname = Name_Img then
4716 Preanalyze_And_Resolve (P);
4718 -- For all other attribute renamings, the prefix is a subtype
4720 else
4721 Find_Type (P);
4722 end if;
4724 -- If the target type is not yet frozen, add the body to the
4725 -- actions to be elaborated at freeze time.
4727 if Is_Tagged_Type (Etype (P))
4728 and then In_Open_Scopes (Scope (Etype (P)))
4729 then
4730 Append_Freeze_Action (Etype (P), Body_Node);
4731 else
4732 Rewrite (N, Body_Node);
4733 Analyze (N);
4734 Set_Etype (New_S, Base_Type (Etype (New_S)));
4735 end if;
4736 end;
4738 -- Generic formal subprograms or AST_Handler renaming
4740 else
4741 Rewrite (N, Body_Node);
4742 Analyze (N);
4743 Set_Etype (New_S, Base_Type (Etype (New_S)));
4744 end if;
4746 if Is_Compilation_Unit (New_S) then
4747 Error_Msg_N
4748 ("a library unit can only rename another library unit", N);
4749 end if;
4751 -- We suppress elaboration warnings for the resulting entity, since
4752 -- clearly they are not needed, and more particularly, in the case
4753 -- of a generic formal subprogram, the resulting entity can appear
4754 -- after the instantiation itself, and thus look like a bogus case
4755 -- of access before elaboration.
4757 if Legacy_Elaboration_Checks then
4758 Set_Suppress_Elaboration_Warnings (New_S);
4759 end if;
4760 end Attribute_Renaming;
4762 ----------------------
4763 -- Chain_Use_Clause --
4764 ----------------------
4766 procedure Chain_Use_Clause (N : Node_Id) is
4767 Level : Int := Scope_Stack.Last;
4768 Pack : Entity_Id;
4770 begin
4771 -- Common case
4773 if not Is_Compilation_Unit (Current_Scope)
4774 or else not Is_Child_Unit (Current_Scope)
4775 then
4776 null;
4778 -- Common case for compilation unit
4780 elsif Defining_Entity (Parent (N)) = Current_Scope then
4781 null;
4783 else
4784 -- If declaration appears in some other scope, it must be in some
4785 -- parent unit when compiling a child.
4787 Pack := Defining_Entity (Parent (N));
4789 if not In_Open_Scopes (Pack) then
4790 null;
4792 -- If the use clause appears in an ancestor and we are in the
4793 -- private part of the immediate parent, the use clauses are
4794 -- already installed.
4796 elsif Pack /= Scope (Current_Scope)
4797 and then In_Private_Part (Scope (Current_Scope))
4798 then
4799 null;
4801 else
4802 -- Find entry for parent unit in scope stack
4804 while Scope_Stack.Table (Level).Entity /= Pack loop
4805 Level := Level - 1;
4806 end loop;
4807 end if;
4808 end if;
4810 Set_Next_Use_Clause (N,
4811 Scope_Stack.Table (Level).First_Use_Clause);
4812 Scope_Stack.Table (Level).First_Use_Clause := N;
4813 end Chain_Use_Clause;
4815 ---------------------------
4816 -- Check_Frozen_Renaming --
4817 ---------------------------
4819 procedure Check_Frozen_Renaming (N : Node_Id; Subp : Entity_Id) is
4820 B_Node : Node_Id;
4821 Old_S : Entity_Id;
4823 begin
4824 if Is_Frozen (Subp) and then not Has_Completion (Subp) then
4825 B_Node :=
4826 Build_Renamed_Body
4827 (Parent (Declaration_Node (Subp)), Defining_Entity (N));
4829 if Is_Entity_Name (Name (N)) then
4830 Old_S := Entity (Name (N));
4832 if not Is_Frozen (Old_S)
4833 and then Operating_Mode /= Check_Semantics
4834 then
4835 Append_Freeze_Action (Old_S, B_Node);
4836 else
4837 Insert_After (N, B_Node);
4838 Analyze (B_Node);
4839 end if;
4841 if Is_Intrinsic_Subprogram (Old_S)
4842 and then not In_Instance
4843 and then not Relaxed_RM_Semantics
4844 then
4845 Error_Msg_N
4846 ("subprogram used in renaming_as_body cannot be intrinsic",
4847 Name (N));
4848 end if;
4850 else
4851 Insert_After (N, B_Node);
4852 Analyze (B_Node);
4853 end if;
4854 end if;
4855 end Check_Frozen_Renaming;
4857 -------------------------------
4858 -- Set_Entity_Or_Discriminal --
4859 -------------------------------
4861 procedure Set_Entity_Or_Discriminal (N : Node_Id; E : Entity_Id) is
4862 P : Node_Id;
4864 begin
4865 -- If the entity is not a discriminant, or else expansion is disabled,
4866 -- simply set the entity.
4868 if not In_Spec_Expression
4869 or else Ekind (E) /= E_Discriminant
4870 or else Inside_A_Generic
4871 then
4872 Set_Entity_With_Checks (N, E);
4874 -- The replacement of a discriminant by the corresponding discriminal
4875 -- is not done for a task discriminant that appears in a default
4876 -- expression of an entry parameter. See Exp_Ch2.Expand_Discriminant
4877 -- for details on their handling.
4879 elsif Is_Concurrent_Type (Scope (E)) then
4880 P := Parent (N);
4881 while Present (P)
4882 and then Nkind (P) not in
4883 N_Parameter_Specification | N_Component_Declaration
4884 loop
4885 P := Parent (P);
4886 end loop;
4888 if Present (P)
4889 and then Nkind (P) = N_Parameter_Specification
4890 then
4891 null;
4893 else
4894 Set_Entity (N, Discriminal (E));
4895 end if;
4897 -- Otherwise, this is a discriminant in a context in which
4898 -- it is a reference to the corresponding parameter of the
4899 -- init proc for the enclosing type.
4901 else
4902 Set_Entity (N, Discriminal (E));
4903 end if;
4904 end Set_Entity_Or_Discriminal;
4906 -----------------------------------
4907 -- Check_In_Previous_With_Clause --
4908 -----------------------------------
4910 procedure Check_In_Previous_With_Clause (N, Nam : Node_Id) is
4911 Pack : constant Entity_Id := Entity (Original_Node (Nam));
4912 Item : Node_Id;
4913 Par : Node_Id;
4915 begin
4916 Item := First (Context_Items (Parent (N)));
4917 while Present (Item) and then Item /= N loop
4918 if Nkind (Item) = N_With_Clause
4920 -- Protect the frontend against previous critical errors
4922 and then Nkind (Name (Item)) /= N_Selected_Component
4923 and then Entity (Name (Item)) = Pack
4924 then
4925 Par := Nam;
4927 -- Find root library unit in with_clause
4929 while Nkind (Par) = N_Expanded_Name loop
4930 Par := Prefix (Par);
4931 end loop;
4933 if Is_Child_Unit (Entity (Original_Node (Par))) then
4934 Error_Msg_NE ("& is not directly visible", Par, Entity (Par));
4935 else
4936 return;
4937 end if;
4938 end if;
4940 Next (Item);
4941 end loop;
4943 -- On exit, package is not mentioned in a previous with_clause.
4944 -- Check if its prefix is.
4946 if Nkind (Nam) = N_Expanded_Name then
4947 Check_In_Previous_With_Clause (N, Prefix (Nam));
4949 elsif Pack /= Any_Id then
4950 Error_Msg_NE ("& is not visible", Nam, Pack);
4951 end if;
4952 end Check_In_Previous_With_Clause;
4954 ---------------------------------
4955 -- Check_Library_Unit_Renaming --
4956 ---------------------------------
4958 procedure Check_Library_Unit_Renaming (N : Node_Id; Old_E : Entity_Id) is
4959 New_E : Entity_Id;
4961 begin
4962 if Nkind (Parent (N)) /= N_Compilation_Unit then
4963 return;
4965 -- Check for library unit. Note that we used to check for the scope
4966 -- being Standard here, but that was wrong for Standard itself.
4968 elsif not Is_Compilation_Unit (Old_E)
4969 and then not Is_Child_Unit (Old_E)
4970 then
4971 Error_Msg_N ("renamed unit must be a library unit", Name (N));
4973 -- Entities defined in Standard (operators and boolean literals) cannot
4974 -- be renamed as library units.
4976 elsif Scope (Old_E) = Standard_Standard
4977 and then Sloc (Old_E) = Standard_Location
4978 then
4979 Error_Msg_N ("renamed unit must be a library unit", Name (N));
4981 elsif Present (Parent_Spec (N))
4982 and then Nkind (Unit (Parent_Spec (N))) = N_Generic_Package_Declaration
4983 and then not Is_Child_Unit (Old_E)
4984 then
4985 Error_Msg_N
4986 ("renamed unit must be a child unit of generic parent", Name (N));
4988 elsif Nkind (N) in N_Generic_Renaming_Declaration
4989 and then Nkind (Name (N)) = N_Expanded_Name
4990 and then Is_Generic_Instance (Entity (Prefix (Name (N))))
4991 and then Is_Generic_Unit (Old_E)
4992 then
4993 Error_Msg_N
4994 ("renamed generic unit must be a library unit", Name (N));
4996 elsif Is_Package_Or_Generic_Package (Old_E) then
4998 -- Inherit categorization flags
5000 New_E := Defining_Entity (N);
5001 Set_Is_Pure (New_E, Is_Pure (Old_E));
5002 Set_Is_Preelaborated (New_E, Is_Preelaborated (Old_E));
5003 Set_Is_Remote_Call_Interface (New_E,
5004 Is_Remote_Call_Interface (Old_E));
5005 Set_Is_Remote_Types (New_E, Is_Remote_Types (Old_E));
5006 Set_Is_Shared_Passive (New_E, Is_Shared_Passive (Old_E));
5007 end if;
5008 end Check_Library_Unit_Renaming;
5010 ------------------------
5011 -- Enclosing_Instance --
5012 ------------------------
5014 function Enclosing_Instance return Entity_Id is
5015 S : Entity_Id;
5017 begin
5018 if not Is_Generic_Instance (Current_Scope) then
5019 return Empty;
5020 end if;
5022 S := Scope (Current_Scope);
5023 while S /= Standard_Standard loop
5024 if Is_Generic_Instance (S) then
5025 return S;
5026 end if;
5028 S := Scope (S);
5029 end loop;
5031 return Empty;
5032 end Enclosing_Instance;
5034 ---------------
5035 -- End_Scope --
5036 ---------------
5038 procedure End_Scope is
5039 Id : Entity_Id;
5040 Prev : Entity_Id;
5041 Outer : Entity_Id;
5043 begin
5044 Id := First_Entity (Current_Scope);
5045 while Present (Id) loop
5046 -- An entity in the current scope is not necessarily the first one
5047 -- on its homonym chain. Find its predecessor if any,
5048 -- If it is an internal entity, it will not be in the visibility
5049 -- chain altogether, and there is nothing to unchain.
5051 if Id /= Current_Entity (Id) then
5052 Prev := Current_Entity (Id);
5053 while Present (Prev)
5054 and then Present (Homonym (Prev))
5055 and then Homonym (Prev) /= Id
5056 loop
5057 Prev := Homonym (Prev);
5058 end loop;
5060 -- Skip to end of loop if Id is not in the visibility chain
5062 if No (Prev) or else Homonym (Prev) /= Id then
5063 goto Next_Ent;
5064 end if;
5066 else
5067 Prev := Empty;
5068 end if;
5070 Set_Is_Immediately_Visible (Id, False);
5072 Outer := Homonym (Id);
5073 while Present (Outer) and then Scope (Outer) = Current_Scope loop
5074 Outer := Homonym (Outer);
5075 end loop;
5077 -- Reset homonym link of other entities, but do not modify link
5078 -- between entities in current scope, so that the back-end can have
5079 -- a proper count of local overloadings.
5081 if No (Prev) then
5082 Set_Name_Entity_Id (Chars (Id), Outer);
5084 elsif Scope (Prev) /= Scope (Id) then
5085 Set_Homonym (Prev, Outer);
5086 end if;
5088 <<Next_Ent>>
5089 Next_Entity (Id);
5090 end loop;
5092 -- If the scope generated freeze actions, place them before the
5093 -- current declaration and analyze them. Type declarations and
5094 -- the bodies of initialization procedures can generate such nodes.
5095 -- We follow the parent chain until we reach a list node, which is
5096 -- the enclosing list of declarations. If the list appears within
5097 -- a protected definition, move freeze nodes outside the protected
5098 -- type altogether.
5100 if Present
5101 (Scope_Stack.Table (Scope_Stack.Last).Pending_Freeze_Actions)
5102 then
5103 declare
5104 Decl : Node_Id;
5105 L : constant List_Id := Scope_Stack.Table
5106 (Scope_Stack.Last).Pending_Freeze_Actions;
5108 begin
5109 if Is_Itype (Current_Scope) then
5110 Decl := Associated_Node_For_Itype (Current_Scope);
5111 else
5112 Decl := Parent (Current_Scope);
5113 end if;
5115 Pop_Scope;
5117 while not Is_List_Member (Decl)
5118 or else Nkind (Parent (Decl)) in N_Protected_Definition
5119 | N_Task_Definition
5120 loop
5121 Decl := Parent (Decl);
5122 end loop;
5124 Insert_List_Before_And_Analyze (Decl, L);
5125 end;
5127 else
5128 Pop_Scope;
5129 end if;
5130 end End_Scope;
5132 ---------------------
5133 -- End_Use_Clauses --
5134 ---------------------
5136 procedure End_Use_Clauses (Clause : Node_Id) is
5137 U : Node_Id;
5139 begin
5140 -- Remove use_type_clauses first, because they affect the visibility of
5141 -- operators in subsequent used packages.
5143 U := Clause;
5144 while Present (U) loop
5145 if Nkind (U) = N_Use_Type_Clause then
5146 End_Use_Type (U);
5147 end if;
5149 Next_Use_Clause (U);
5150 end loop;
5152 U := Clause;
5153 while Present (U) loop
5154 if Nkind (U) = N_Use_Package_Clause then
5155 End_Use_Package (U);
5156 end if;
5158 Next_Use_Clause (U);
5159 end loop;
5160 end End_Use_Clauses;
5162 ---------------------
5163 -- End_Use_Package --
5164 ---------------------
5166 procedure End_Use_Package (N : Node_Id) is
5167 Pack : Entity_Id;
5168 Pack_Name : Node_Id;
5169 Id : Entity_Id;
5170 Elmt : Elmt_Id;
5172 function Is_Primitive_Operator_In_Use
5173 (Op : Entity_Id;
5174 F : Entity_Id) return Boolean;
5175 -- Check whether Op is a primitive operator of a use-visible type
5177 ----------------------------------
5178 -- Is_Primitive_Operator_In_Use --
5179 ----------------------------------
5181 function Is_Primitive_Operator_In_Use
5182 (Op : Entity_Id;
5183 F : Entity_Id) return Boolean
5185 T : constant Entity_Id := Base_Type (Etype (F));
5186 begin
5187 return In_Use (T) and then Scope (T) = Scope (Op);
5188 end Is_Primitive_Operator_In_Use;
5190 -- Start of processing for End_Use_Package
5192 begin
5193 Pack_Name := Name (N);
5195 -- Test that Pack_Name actually denotes a package before processing
5197 if Is_Entity_Name (Pack_Name)
5198 and then Ekind (Entity (Pack_Name)) = E_Package
5199 then
5200 Pack := Entity (Pack_Name);
5202 if In_Open_Scopes (Pack) then
5203 null;
5205 elsif not Redundant_Use (Pack_Name) then
5206 Set_In_Use (Pack, False);
5207 Set_Current_Use_Clause (Pack, Empty);
5209 Id := First_Entity (Pack);
5210 while Present (Id) loop
5212 -- Preserve use-visibility of operators that are primitive
5213 -- operators of a type that is use-visible through an active
5214 -- use_type_clause.
5216 if Nkind (Id) = N_Defining_Operator_Symbol
5217 and then
5218 (Is_Primitive_Operator_In_Use (Id, First_Formal (Id))
5219 or else
5220 (Present (Next_Formal (First_Formal (Id)))
5221 and then
5222 Is_Primitive_Operator_In_Use
5223 (Id, Next_Formal (First_Formal (Id)))))
5224 then
5225 null;
5226 else
5227 Set_Is_Potentially_Use_Visible (Id, False);
5228 end if;
5230 if Is_Private_Type (Id)
5231 and then Present (Full_View (Id))
5232 then
5233 Set_Is_Potentially_Use_Visible (Full_View (Id), False);
5234 end if;
5236 Next_Entity (Id);
5237 end loop;
5239 if Present (Renamed_Entity (Pack)) then
5240 Set_In_Use (Renamed_Entity (Pack), False);
5241 Set_Current_Use_Clause (Renamed_Entity (Pack), Empty);
5242 end if;
5244 if Chars (Pack) = Name_System
5245 and then Scope (Pack) = Standard_Standard
5246 and then Present_System_Aux
5247 then
5248 Id := First_Entity (System_Aux_Id);
5249 while Present (Id) loop
5250 Set_Is_Potentially_Use_Visible (Id, False);
5252 if Is_Private_Type (Id)
5253 and then Present (Full_View (Id))
5254 then
5255 Set_Is_Potentially_Use_Visible (Full_View (Id), False);
5256 end if;
5258 Next_Entity (Id);
5259 end loop;
5261 Set_In_Use (System_Aux_Id, False);
5262 end if;
5263 else
5264 Set_Redundant_Use (Pack_Name, False);
5265 end if;
5266 end if;
5268 if Present (Hidden_By_Use_Clause (N)) then
5269 Elmt := First_Elmt (Hidden_By_Use_Clause (N));
5270 while Present (Elmt) loop
5271 declare
5272 E : constant Entity_Id := Node (Elmt);
5274 begin
5275 -- Reset either Use_Visibility or Direct_Visibility, depending
5276 -- on how the entity was hidden by the use clause.
5278 if In_Use (Scope (E))
5279 and then Used_As_Generic_Actual (Scope (E))
5280 then
5281 Set_Is_Potentially_Use_Visible (Node (Elmt));
5282 else
5283 Set_Is_Immediately_Visible (Node (Elmt));
5284 end if;
5286 Next_Elmt (Elmt);
5287 end;
5288 end loop;
5290 Set_Hidden_By_Use_Clause (N, No_Elist);
5291 end if;
5292 end End_Use_Package;
5294 ------------------
5295 -- End_Use_Type --
5296 ------------------
5298 procedure End_Use_Type (N : Node_Id) is
5299 Elmt : Elmt_Id;
5300 Id : Entity_Id;
5301 T : Entity_Id;
5303 -- Start of processing for End_Use_Type
5305 begin
5306 Id := Subtype_Mark (N);
5308 -- A call to Rtsfind may occur while analyzing a use_type_clause, in
5309 -- which case the type marks are not resolved yet, so guard against that
5310 -- here.
5312 if Is_Entity_Name (Id) and then Present (Entity (Id)) then
5313 T := Entity (Id);
5315 if T = Any_Type or else From_Limited_With (T) then
5316 null;
5318 -- Note that the use_type_clause may mention a subtype of the type
5319 -- whose primitive operations have been made visible. Here as
5320 -- elsewhere, it is the base type that matters for visibility.
5322 elsif In_Open_Scopes (Scope (Base_Type (T))) then
5323 null;
5325 elsif not Redundant_Use (Id) then
5326 Set_In_Use (T, False);
5327 Set_In_Use (Base_Type (T), False);
5328 Set_Current_Use_Clause (T, Empty);
5329 Set_Current_Use_Clause (Base_Type (T), Empty);
5331 -- See Use_One_Type for the rationale. This is a bit on the naive
5332 -- side, but should be good enough in practice.
5334 if Is_Tagged_Type (T) then
5335 Set_In_Use (Class_Wide_Type (T), False);
5336 end if;
5337 end if;
5338 end if;
5340 if Is_Empty_Elmt_List (Used_Operations (N)) then
5341 return;
5343 else
5344 Elmt := First_Elmt (Used_Operations (N));
5345 while Present (Elmt) loop
5346 Set_Is_Potentially_Use_Visible (Node (Elmt), False);
5347 Next_Elmt (Elmt);
5348 end loop;
5349 end if;
5350 end End_Use_Type;
5352 --------------------
5353 -- Entity_Of_Unit --
5354 --------------------
5356 function Entity_Of_Unit (U : Node_Id) return Entity_Id is
5357 begin
5358 if Nkind (U) = N_Package_Instantiation and then Analyzed (U) then
5359 return Defining_Entity (Instance_Spec (U));
5360 else
5361 return Defining_Entity (U);
5362 end if;
5363 end Entity_Of_Unit;
5365 --------------------------------------
5366 -- Error_Missing_With_Of_Known_Unit --
5367 --------------------------------------
5369 procedure Error_Missing_With_Of_Known_Unit (Pkg : Node_Id) is
5370 Selectors : array (1 .. 6) of Node_Id;
5371 -- Contains the chars of the full package name up to maximum number
5372 -- allowed as per Errout.Error_Msg_Name_# variables.
5374 Count : Integer := Selectors'First;
5375 -- Count of selector names forming the full package name
5377 Current_Pkg : Node_Id := Parent (Pkg);
5379 begin
5380 Selectors (Count) := Pkg;
5382 -- Gather all the selectors we can display
5384 while Nkind (Current_Pkg) = N_Selected_Component
5385 and then Is_Known_Unit (Current_Pkg)
5386 and then Count < Selectors'Length
5387 loop
5388 Count := Count + 1;
5389 Selectors (Count) := Selector_Name (Current_Pkg);
5390 Current_Pkg := Parent (Current_Pkg);
5391 end loop;
5393 -- Display the error message based on the number of selectors found
5395 case Count is
5396 when 1 =>
5397 Error_Msg_Node_1 := Selectors (1);
5398 Error_Msg_N -- CODEFIX
5399 ("\\missing `WITH &;`", Pkg);
5400 when 2 =>
5401 Error_Msg_Node_1 := Selectors (1);
5402 Error_Msg_Node_2 := Selectors (2);
5403 Error_Msg_N -- CODEFIX
5404 ("\\missing `WITH &.&;`", Pkg);
5405 when 3 =>
5406 Error_Msg_Node_1 := Selectors (1);
5407 Error_Msg_Node_2 := Selectors (2);
5408 Error_Msg_Node_3 := Selectors (3);
5409 Error_Msg_N -- CODEFIX
5410 ("\\missing `WITH &.&.&;`", Pkg);
5411 when 4 =>
5412 Error_Msg_Node_1 := Selectors (1);
5413 Error_Msg_Node_2 := Selectors (2);
5414 Error_Msg_Node_3 := Selectors (3);
5415 Error_Msg_Node_3 := Selectors (4);
5416 Error_Msg_N -- CODEFIX
5417 ("\\missing `WITH &.&.&.&;`", Pkg);
5418 when 5 =>
5419 Error_Msg_Node_1 := Selectors (1);
5420 Error_Msg_Node_2 := Selectors (2);
5421 Error_Msg_Node_3 := Selectors (3);
5422 Error_Msg_Node_3 := Selectors (4);
5423 Error_Msg_Node_3 := Selectors (5);
5424 Error_Msg_N -- CODEFIX
5425 ("\\missing `WITH &.&.&.&.&;`", Pkg);
5426 when 6 =>
5427 Error_Msg_Node_1 := Selectors (1);
5428 Error_Msg_Node_2 := Selectors (2);
5429 Error_Msg_Node_3 := Selectors (3);
5430 Error_Msg_Node_4 := Selectors (4);
5431 Error_Msg_Node_5 := Selectors (5);
5432 Error_Msg_Node_6 := Selectors (6);
5433 Error_Msg_N -- CODEFIX
5434 ("\\missing `WITH &.&.&.&.&.&;`", Pkg);
5435 when others =>
5436 raise Program_Error;
5437 end case;
5438 end Error_Missing_With_Of_Known_Unit;
5440 ----------------------
5441 -- Find_Direct_Name --
5442 ----------------------
5444 procedure Find_Direct_Name (N : Node_Id) is
5445 E : Entity_Id;
5446 E2 : Entity_Id;
5447 Msg : Boolean;
5449 Homonyms : Entity_Id;
5450 -- Saves start of homonym chain
5452 Inst : Entity_Id := Empty;
5453 -- Enclosing instance, if any
5455 Nvis_Entity : Boolean;
5456 -- Set True to indicate that there is at least one entity on the homonym
5457 -- chain which, while not visible, is visible enough from the user point
5458 -- of view to warrant an error message of "not visible" rather than
5459 -- undefined.
5461 Nvis_Is_Private_Subprg : Boolean := False;
5462 -- Ada 2005 (AI-262): Set True to indicate that a form of Beaujolais
5463 -- effect concerning library subprograms has been detected. Used to
5464 -- generate the precise error message.
5466 function From_Actual_Package (E : Entity_Id) return Boolean;
5467 -- Returns true if the entity is an actual for a package that is itself
5468 -- an actual for a formal package of the current instance. Such an
5469 -- entity requires special handling because it may be use-visible but
5470 -- hides directly visible entities defined outside the instance, because
5471 -- the corresponding formal did so in the generic.
5473 function Is_Actual_Parameter return Boolean;
5474 -- This function checks if the node N is an identifier that is an actual
5475 -- parameter of a procedure call. If so it returns True, otherwise it
5476 -- return False. The reason for this check is that at this stage we do
5477 -- not know what procedure is being called if the procedure might be
5478 -- overloaded, so it is premature to go setting referenced flags or
5479 -- making calls to Generate_Reference. We will wait till Resolve_Actuals
5480 -- for that processing.
5481 -- Note: there is a similar routine Sem_Util.Is_Actual_Parameter, but
5482 -- it works for both function and procedure calls, while here we are
5483 -- only concerned with procedure calls (and with entry calls as well,
5484 -- but they are parsed as procedure calls and only later rewritten to
5485 -- entry calls).
5487 function Known_But_Invisible (E : Entity_Id) return Boolean;
5488 -- This function determines whether a reference to the entity E, which
5489 -- is not visible, can reasonably be considered to be known to the
5490 -- writer of the reference. This is a heuristic test, used only for
5491 -- the purposes of figuring out whether we prefer to complain that an
5492 -- entity is undefined or invisible (and identify the declaration of
5493 -- the invisible entity in the latter case). The point here is that we
5494 -- don't want to complain that something is invisible and then point to
5495 -- something entirely mysterious to the writer.
5497 procedure Nvis_Messages;
5498 -- Called if there are no visible entries for N, but there is at least
5499 -- one non-directly visible, or hidden declaration. This procedure
5500 -- outputs an appropriate set of error messages.
5502 procedure Undefined (Nvis : Boolean);
5503 -- This function is called if the current node has no corresponding
5504 -- visible entity or entities. The value set in Msg indicates whether
5505 -- an error message was generated (multiple error messages for the
5506 -- same variable are generally suppressed, see body for details).
5507 -- Msg is True if an error message was generated, False if not. This
5508 -- value is used by the caller to determine whether or not to output
5509 -- additional messages where appropriate. The parameter is set False
5510 -- to get the message "X is undefined", and True to get the message
5511 -- "X is not visible".
5513 -------------------------
5514 -- From_Actual_Package --
5515 -------------------------
5517 function From_Actual_Package (E : Entity_Id) return Boolean is
5518 Scop : constant Entity_Id := Scope (E);
5519 -- Declared scope of candidate entity
5521 function Declared_In_Actual (Pack : Entity_Id) return Boolean;
5522 -- Recursive function that does the work and examines actuals of
5523 -- actual packages of current instance.
5525 ------------------------
5526 -- Declared_In_Actual --
5527 ------------------------
5529 function Declared_In_Actual (Pack : Entity_Id) return Boolean is
5530 pragma Assert (Ekind (Pack) = E_Package);
5531 Act : Entity_Id;
5532 begin
5533 if No (Associated_Formal_Package (Pack)) then
5534 return False;
5536 else
5537 Act := First_Entity (Pack);
5538 while Present (Act) loop
5539 if Renamed_Entity (Pack) = Scop then
5540 return True;
5542 -- Check for end of list of actuals
5544 elsif Ekind (Act) = E_Package
5545 and then Renamed_Entity (Act) = Pack
5546 then
5547 return False;
5549 elsif Ekind (Act) = E_Package
5550 and then Declared_In_Actual (Act)
5551 then
5552 return True;
5553 end if;
5555 Next_Entity (Act);
5556 end loop;
5558 return False;
5559 end if;
5560 end Declared_In_Actual;
5562 -- Local variables
5564 Act : Entity_Id;
5566 -- Start of processing for From_Actual_Package
5568 begin
5569 if not In_Instance then
5570 return False;
5572 else
5573 Inst := Current_Scope;
5574 while Present (Inst)
5575 and then Ekind (Inst) /= E_Package
5576 and then not Is_Generic_Instance (Inst)
5577 loop
5578 Inst := Scope (Inst);
5579 end loop;
5581 if No (Inst) then
5582 return False;
5583 end if;
5585 Act := First_Entity (Inst);
5586 while Present (Act) loop
5587 if Ekind (Act) = E_Package
5588 and then Declared_In_Actual (Act)
5589 then
5590 return True;
5591 end if;
5593 Next_Entity (Act);
5594 end loop;
5596 return False;
5597 end if;
5598 end From_Actual_Package;
5600 -------------------------
5601 -- Is_Actual_Parameter --
5602 -------------------------
5604 function Is_Actual_Parameter return Boolean is
5605 begin
5606 if Nkind (N) = N_Identifier then
5607 case Nkind (Parent (N)) is
5608 when N_Procedure_Call_Statement =>
5609 return Is_List_Member (N)
5610 and then List_Containing (N) =
5611 Parameter_Associations (Parent (N));
5613 when N_Parameter_Association =>
5614 return N = Explicit_Actual_Parameter (Parent (N))
5615 and then Nkind (Parent (Parent (N))) =
5616 N_Procedure_Call_Statement;
5618 when others =>
5619 return False;
5620 end case;
5621 else
5622 return False;
5623 end if;
5624 end Is_Actual_Parameter;
5626 -------------------------
5627 -- Known_But_Invisible --
5628 -------------------------
5630 function Known_But_Invisible (E : Entity_Id) return Boolean is
5631 Fname : File_Name_Type;
5633 begin
5634 -- Entities in Standard are always considered to be known
5636 if Sloc (E) <= Standard_Location then
5637 return True;
5639 -- An entity that does not come from source is always considered
5640 -- to be unknown, since it is an artifact of code expansion.
5642 elsif not Comes_From_Source (E) then
5643 return False;
5644 end if;
5646 -- Here we have an entity that is not from package Standard, and
5647 -- which comes from Source. See if it comes from an internal file.
5649 Fname := Unit_File_Name (Get_Source_Unit (E));
5651 -- Case of from internal file
5653 if In_Internal_Unit (E) then
5655 -- Private part entities in internal files are never considered
5656 -- to be known to the writer of normal application code.
5658 if Is_Hidden (E) then
5659 return False;
5660 end if;
5662 -- Entities from System packages other than System and
5663 -- System.Storage_Elements are not considered to be known.
5664 -- System.Auxxxx files are also considered known to the user.
5666 -- Should refine this at some point to generally distinguish
5667 -- between known and unknown internal files ???
5669 Get_Name_String (Fname);
5671 return
5672 Name_Len < 2
5673 or else
5674 Name_Buffer (1 .. 2) /= "s-"
5675 or else
5676 Name_Buffer (3 .. 8) = "stoele"
5677 or else
5678 Name_Buffer (3 .. 5) = "aux";
5680 -- If not an internal file, then entity is definitely known, even if
5681 -- it is in a private part (the message generated will note that it
5682 -- is in a private part).
5684 else
5685 return True;
5686 end if;
5687 end Known_But_Invisible;
5689 -------------------
5690 -- Nvis_Messages --
5691 -------------------
5693 procedure Nvis_Messages is
5694 Comp_Unit : Node_Id;
5695 Ent : Entity_Id;
5696 Found : Boolean := False;
5697 Hidden : Boolean := False;
5698 Item : Node_Id;
5700 begin
5701 -- Ada 2005 (AI-262): Generate a precise error concerning the
5702 -- Beaujolais effect that was previously detected
5704 if Nvis_Is_Private_Subprg then
5706 pragma Assert (Nkind (E2) = N_Defining_Identifier
5707 and then Ekind (E2) = E_Function
5708 and then Scope (E2) = Standard_Standard
5709 and then Has_Private_With (E2));
5711 -- Find the sloc corresponding to the private with'ed unit
5713 Comp_Unit := Cunit (Current_Sem_Unit);
5714 Error_Msg_Sloc := No_Location;
5716 Item := First (Context_Items (Comp_Unit));
5717 while Present (Item) loop
5718 if Nkind (Item) = N_With_Clause
5719 and then Private_Present (Item)
5720 and then Entity (Name (Item)) = E2
5721 then
5722 Error_Msg_Sloc := Sloc (Item);
5723 exit;
5724 end if;
5726 Next (Item);
5727 end loop;
5729 pragma Assert (Error_Msg_Sloc /= No_Location);
5731 Error_Msg_N ("(Ada 2005): hidden by private with clause #", N);
5732 return;
5733 end if;
5735 Undefined (Nvis => True);
5737 if Msg then
5739 -- First loop does hidden declarations
5741 Ent := Homonyms;
5742 while Present (Ent) loop
5743 if Is_Potentially_Use_Visible (Ent) then
5744 if not Hidden then
5745 Error_Msg_N -- CODEFIX
5746 ("multiple use clauses cause hiding!", N);
5747 Hidden := True;
5748 end if;
5750 Error_Msg_Sloc := Sloc (Ent);
5751 Error_Msg_N -- CODEFIX
5752 ("hidden declaration#!", N);
5753 end if;
5755 Ent := Homonym (Ent);
5756 end loop;
5758 -- If we found hidden declarations, then that's enough, don't
5759 -- bother looking for non-visible declarations as well.
5761 if Hidden then
5762 return;
5763 end if;
5765 -- Second loop does non-directly visible declarations
5767 Ent := Homonyms;
5768 while Present (Ent) loop
5769 if not Is_Potentially_Use_Visible (Ent) then
5771 -- Do not bother the user with unknown entities
5773 if not Known_But_Invisible (Ent) then
5774 goto Continue;
5775 end if;
5777 Error_Msg_Sloc := Sloc (Ent);
5779 -- Output message noting that there is a non-visible
5780 -- declaration, distinguishing the private part case.
5782 if Is_Hidden (Ent) then
5783 Error_Msg_N ("non-visible (private) declaration#!", N);
5785 -- If the entity is declared in a generic package, it
5786 -- cannot be visible, so there is no point in adding it
5787 -- to the list of candidates if another homograph from a
5788 -- non-generic package has been seen.
5790 elsif Ekind (Scope (Ent)) = E_Generic_Package
5791 and then Found
5792 then
5793 null;
5795 else
5796 -- When the entity comes from a generic instance the
5797 -- normal error message machinery will give the line
5798 -- number of the generic package and the location of
5799 -- the generic instance, but not the name of the
5800 -- the instance.
5802 -- So, in order to give more descriptive error messages
5803 -- in this case, we include the name of the generic
5804 -- package.
5806 if Is_Generic_Instance (Scope (Ent)) then
5807 Error_Msg_Name_1 := Chars (Scope (Ent));
5808 Error_Msg_N -- CODEFIX
5809 ("non-visible declaration from %#!", N);
5811 -- Otherwise print the message normally
5813 else
5814 Error_Msg_N -- CODEFIX
5815 ("non-visible declaration#!", N);
5816 end if;
5818 if Ekind (Scope (Ent)) /= E_Generic_Package then
5819 Found := True;
5820 end if;
5822 if Is_Compilation_Unit (Ent)
5823 and then
5824 Nkind (Parent (Parent (N))) = N_Use_Package_Clause
5825 then
5826 Error_Msg_Qual_Level := 99;
5827 Error_Msg_NE -- CODEFIX
5828 ("\\missing `WITH &;`", N, Ent);
5829 Error_Msg_Qual_Level := 0;
5830 end if;
5832 if Ekind (Ent) = E_Discriminant
5833 and then Present (Corresponding_Discriminant (Ent))
5834 and then Scope (Corresponding_Discriminant (Ent)) =
5835 Etype (Scope (Ent))
5836 then
5837 Error_Msg_N
5838 ("inherited discriminant not allowed here" &
5839 " (RM 3.8 (12), 3.8.1 (6))!", N);
5840 end if;
5841 end if;
5843 -- Set entity and its containing package as referenced. We
5844 -- can't be sure of this, but this seems a better choice
5845 -- to avoid unused entity messages.
5847 if Comes_From_Source (Ent) then
5848 Set_Referenced (Ent);
5849 Set_Referenced (Cunit_Entity (Get_Source_Unit (Ent)));
5850 end if;
5851 end if;
5853 <<Continue>>
5854 Ent := Homonym (Ent);
5855 end loop;
5856 end if;
5857 end Nvis_Messages;
5859 ---------------
5860 -- Undefined --
5861 ---------------
5863 procedure Undefined (Nvis : Boolean) is
5864 Emsg : Error_Msg_Id;
5866 begin
5867 -- We should never find an undefined internal name. If we do, then
5868 -- see if we have previous errors. If so, ignore on the grounds that
5869 -- it is probably a cascaded message (e.g. a block label from a badly
5870 -- formed block). If no previous errors, then we have a real internal
5871 -- error of some kind so raise an exception.
5873 if Is_Internal_Name (Chars (N)) then
5874 if Total_Errors_Detected /= 0 then
5875 return;
5876 else
5877 raise Program_Error;
5878 end if;
5879 end if;
5881 -- A very specialized error check, if the undefined variable is
5882 -- a case tag, and the case type is an enumeration type, check
5883 -- for a possible misspelling, and if so, modify the identifier
5885 -- Named aggregate should also be handled similarly ???
5887 if Nkind (N) = N_Identifier
5888 and then Nkind (Parent (N)) = N_Case_Statement_Alternative
5889 then
5890 declare
5891 Case_Stm : constant Node_Id := Parent (Parent (N));
5892 Case_Typ : constant Entity_Id := Etype (Expression (Case_Stm));
5894 Lit : Node_Id;
5896 begin
5897 if Is_Enumeration_Type (Case_Typ)
5898 and then not Is_Standard_Character_Type (Case_Typ)
5899 then
5900 Lit := First_Literal (Case_Typ);
5901 Get_Name_String (Chars (Lit));
5903 if Chars (Lit) /= Chars (N)
5904 and then Is_Bad_Spelling_Of (Chars (N), Chars (Lit))
5905 then
5906 Error_Msg_Node_2 := Lit;
5907 Error_Msg_N -- CODEFIX
5908 ("& is undefined, assume misspelling of &", N);
5909 Rewrite (N, New_Occurrence_Of (Lit, Sloc (N)));
5910 return;
5911 end if;
5913 Next_Literal (Lit);
5914 end if;
5915 end;
5916 end if;
5918 -- Normal processing
5920 Set_Entity (N, Any_Id);
5921 Set_Etype (N, Any_Type);
5923 -- We use the table Urefs to keep track of entities for which we
5924 -- have issued errors for undefined references. Multiple errors
5925 -- for a single name are normally suppressed, however we modify
5926 -- the error message to alert the programmer to this effect.
5928 for J in Urefs.First .. Urefs.Last loop
5929 if Chars (N) = Chars (Urefs.Table (J).Node) then
5930 if Urefs.Table (J).Err /= No_Error_Msg
5931 and then Sloc (N) /= Urefs.Table (J).Loc
5932 then
5933 Error_Msg_Node_1 := Urefs.Table (J).Node;
5935 if Urefs.Table (J).Nvis then
5936 Change_Error_Text (Urefs.Table (J).Err,
5937 "& is not visible (more references follow)");
5938 else
5939 Change_Error_Text (Urefs.Table (J).Err,
5940 "& is undefined (more references follow)");
5941 end if;
5943 Urefs.Table (J).Err := No_Error_Msg;
5944 end if;
5946 -- Although we will set Msg False, and thus suppress the
5947 -- message, we also set Error_Posted True, to avoid any
5948 -- cascaded messages resulting from the undefined reference.
5950 Msg := False;
5951 Set_Error_Posted (N);
5952 return;
5953 end if;
5954 end loop;
5956 -- If entry not found, this is first undefined occurrence
5958 if Nvis then
5959 Error_Msg_N ("& is not visible!", N);
5960 Emsg := Get_Msg_Id;
5962 else
5963 Error_Msg_N ("& is undefined!", N);
5964 Emsg := Get_Msg_Id;
5966 -- A very bizarre special check, if the undefined identifier
5967 -- is Put or Put_Line, then add a special error message (since
5968 -- this is a very common error for beginners to make).
5970 if Chars (N) in Name_Put | Name_Put_Line then
5971 Error_Msg_N -- CODEFIX
5972 ("\\possible missing `WITH Ada.Text_'I'O; " &
5973 "USE Ada.Text_'I'O`!", N);
5975 -- Another special check if N is the prefix of a selected
5976 -- component which is a known unit: add message complaining
5977 -- about missing with for this unit.
5979 elsif Nkind (Parent (N)) = N_Selected_Component
5980 and then N = Prefix (Parent (N))
5981 and then Is_Known_Unit (Parent (N))
5982 then
5983 Error_Missing_With_Of_Known_Unit (N);
5984 end if;
5986 -- Now check for possible misspellings
5988 declare
5989 E : Entity_Id;
5990 Ematch : Entity_Id := Empty;
5991 begin
5992 for Nam in First_Name_Id .. Last_Name_Id loop
5993 E := Get_Name_Entity_Id (Nam);
5995 if Present (E)
5996 and then (Is_Immediately_Visible (E)
5997 or else
5998 Is_Potentially_Use_Visible (E))
5999 then
6000 if Is_Bad_Spelling_Of (Chars (N), Nam) then
6001 Ematch := E;
6002 exit;
6003 end if;
6004 end if;
6005 end loop;
6007 if Present (Ematch) then
6008 Error_Msg_NE -- CODEFIX
6009 ("\possible misspelling of&", N, Ematch);
6010 end if;
6011 end;
6012 end if;
6014 -- Make entry in undefined references table unless the full errors
6015 -- switch is set, in which case by refraining from generating the
6016 -- table entry we guarantee that we get an error message for every
6017 -- undefined reference. The entry is not added if we are ignoring
6018 -- errors.
6020 if not All_Errors_Mode
6021 and then Ignore_Errors_Enable = 0
6022 and then not Get_Ignore_Errors
6023 then
6024 Urefs.Append (
6025 (Node => N,
6026 Err => Emsg,
6027 Nvis => Nvis,
6028 Loc => Sloc (N)));
6029 end if;
6031 Msg := True;
6032 end Undefined;
6034 -- Local variables
6036 Nested_Inst : Entity_Id := Empty;
6037 -- The entity of a nested instance which appears within Inst (if any)
6039 -- Start of processing for Find_Direct_Name
6041 begin
6042 -- If the entity pointer is already set, this is an internal node, or
6043 -- a node that is analyzed more than once, after a tree modification.
6044 -- In such a case there is no resolution to perform, just set the type.
6046 if Present (Entity (N)) then
6047 if Is_Type (Entity (N)) then
6048 Set_Etype (N, Entity (N));
6050 -- The exception to this general rule are constants associated with
6051 -- discriminals of protected types because for each protected op
6052 -- a new set of discriminals is internally created by the frontend
6053 -- (see Exp_Ch9.Set_Discriminals), and the current decoration of the
6054 -- entity pointer may have been set as part of a preanalysis, where
6055 -- discriminals still reference the first subprogram or entry to be
6056 -- expanded (see Expand_Protected_Body_Declarations).
6058 elsif Full_Analysis
6059 and then Ekind (Entity (N)) = E_Constant
6060 and then Present (Discriminal_Link (Entity (N)))
6061 and then Is_Protected_Type (Scope (Discriminal_Link (Entity (N))))
6062 then
6063 goto Find_Name;
6065 else
6066 declare
6067 Entyp : constant Entity_Id := Etype (Entity (N));
6069 begin
6070 -- One special case here. If the Etype field is already set,
6071 -- and references the packed array type corresponding to the
6072 -- etype of the referenced entity, then leave it alone. This
6073 -- happens for trees generated from Exp_Pakd, where expressions
6074 -- can be deliberately "mis-typed" to the packed array type.
6076 if Is_Packed_Array (Entyp)
6077 and then Present (Etype (N))
6078 and then Etype (N) = Packed_Array_Impl_Type (Entyp)
6079 then
6080 null;
6082 -- If not that special case, then just reset the Etype
6084 else
6085 Set_Etype (N, Entyp);
6086 end if;
6087 end;
6088 end if;
6090 -- Although the marking of use clauses happens at the end of
6091 -- Find_Direct_Name, a certain case where a generic actual satisfies
6092 -- a use clause must be checked here due to how the generic machinery
6093 -- handles the analysis of said actuals.
6095 if In_Instance
6096 and then Nkind (Parent (N)) = N_Generic_Association
6097 then
6098 Mark_Use_Clauses (Entity (N));
6099 end if;
6101 return;
6102 end if;
6104 <<Find_Name>>
6106 -- Preserve relevant elaboration-related attributes of the context which
6107 -- are no longer available or very expensive to recompute once analysis,
6108 -- resolution, and expansion are over.
6110 if Nkind (N) = N_Identifier then
6111 Mark_Elaboration_Attributes
6112 (N_Id => N,
6113 Checks => True,
6114 Modes => True,
6115 Warnings => True);
6116 end if;
6118 -- Here if Entity pointer was not set, we need full visibility analysis
6119 -- First we generate debugging output if the debug E flag is set.
6121 if Debug_Flag_E then
6122 Write_Str ("Looking for ");
6123 Write_Name (Chars (N));
6124 Write_Eol;
6125 end if;
6127 Homonyms := Current_Entity (N);
6128 Nvis_Entity := False;
6130 E := Homonyms;
6131 while Present (E) loop
6133 -- If entity is immediately visible or potentially use visible, then
6134 -- process the entity and we are done.
6136 if Is_Immediately_Visible (E) then
6137 goto Immediately_Visible_Entity;
6139 elsif Is_Potentially_Use_Visible (E) then
6140 goto Potentially_Use_Visible_Entity;
6142 -- Note if a known but invisible entity encountered
6144 elsif Known_But_Invisible (E) then
6145 Nvis_Entity := True;
6146 end if;
6148 -- Move to next entity in chain and continue search
6150 E := Homonym (E);
6151 end loop;
6153 -- If no entries on homonym chain that were potentially visible,
6154 -- and no entities reasonably considered as non-visible, then
6155 -- we have a plain undefined reference, with no additional
6156 -- explanation required.
6158 if not Nvis_Entity then
6159 Undefined (Nvis => False);
6161 -- Otherwise there is at least one entry on the homonym chain that
6162 -- is reasonably considered as being known and non-visible.
6164 else
6165 Nvis_Messages;
6166 end if;
6168 goto Done;
6170 -- Processing for a potentially use visible entry found. We must search
6171 -- the rest of the homonym chain for two reasons. First, if there is a
6172 -- directly visible entry, then none of the potentially use-visible
6173 -- entities are directly visible (RM 8.4(10)). Second, we need to check
6174 -- for the case of multiple potentially use-visible entries hiding one
6175 -- another and as a result being non-directly visible (RM 8.4(11)).
6177 <<Potentially_Use_Visible_Entity>> declare
6178 Only_One_Visible : Boolean := True;
6179 All_Overloadable : Boolean := Is_Overloadable (E);
6181 begin
6182 E2 := Homonym (E);
6183 while Present (E2) loop
6184 if Is_Immediately_Visible (E2) then
6186 -- If the use-visible entity comes from the actual for a
6187 -- formal package, it hides a directly visible entity from
6188 -- outside the instance.
6190 if From_Actual_Package (E)
6191 and then Scope_Depth (Scope (E2)) < Scope_Depth (Inst)
6192 then
6193 goto Found;
6194 else
6195 E := E2;
6196 goto Immediately_Visible_Entity;
6197 end if;
6199 elsif Is_Potentially_Use_Visible (E2) then
6200 Only_One_Visible := False;
6201 All_Overloadable := All_Overloadable and Is_Overloadable (E2);
6203 -- Ada 2005 (AI-262): Protect against a form of Beaujolais effect
6204 -- that can occur in private_with clauses. Example:
6206 -- with A;
6207 -- private with B; package A is
6208 -- package C is function B return Integer;
6209 -- use A; end A;
6210 -- V1 : Integer := B;
6211 -- private function B return Integer;
6212 -- V2 : Integer := B;
6213 -- end C;
6215 -- V1 resolves to A.B, but V2 resolves to library unit B
6217 elsif Ekind (E2) = E_Function
6218 and then Scope (E2) = Standard_Standard
6219 and then Has_Private_With (E2)
6220 then
6221 Only_One_Visible := False;
6222 All_Overloadable := False;
6223 Nvis_Is_Private_Subprg := True;
6224 exit;
6225 end if;
6227 E2 := Homonym (E2);
6228 end loop;
6230 -- On falling through this loop, we have checked that there are no
6231 -- immediately visible entities. Only_One_Visible is set if exactly
6232 -- one potentially use visible entity exists. All_Overloadable is
6233 -- set if all the potentially use visible entities are overloadable.
6234 -- The condition for legality is that either there is one potentially
6235 -- use visible entity, or if there is more than one, then all of them
6236 -- are overloadable.
6238 if Only_One_Visible or All_Overloadable then
6239 goto Found;
6241 -- If there is more than one potentially use-visible entity and at
6242 -- least one of them non-overloadable, we have an error (RM 8.4(11)).
6243 -- Note that E points to the first such entity on the homonym list.
6245 else
6246 -- If one of the entities is declared in an actual package, it
6247 -- was visible in the generic, and takes precedence over other
6248 -- entities that are potentially use-visible. The same applies
6249 -- if the entity is declared in a local instantiation of the
6250 -- current instance.
6252 if In_Instance then
6254 -- Find the current instance
6256 Inst := Current_Scope;
6257 while Present (Inst) and then Inst /= Standard_Standard loop
6258 if Is_Generic_Instance (Inst) then
6259 exit;
6260 end if;
6262 Inst := Scope (Inst);
6263 end loop;
6265 -- Reexamine the candidate entities, giving priority to those
6266 -- that were visible within the generic.
6268 E2 := E;
6269 while Present (E2) loop
6270 Nested_Inst := Nearest_Enclosing_Instance (E2);
6272 -- The entity is declared within an actual package, or in a
6273 -- nested instance. The ">=" accounts for the case where the
6274 -- current instance and the nested instance are the same.
6276 if From_Actual_Package (E2)
6277 or else (Present (Nested_Inst)
6278 and then Scope_Depth (Nested_Inst) >=
6279 Scope_Depth (Inst))
6280 then
6281 E := E2;
6282 goto Found;
6283 end if;
6285 E2 := Homonym (E2);
6286 end loop;
6288 Nvis_Messages;
6289 goto Done;
6291 elsif Is_Predefined_Unit (Current_Sem_Unit) then
6292 -- A use clause in the body of a system file creates conflict
6293 -- with some entity in a user scope, while rtsfind is active.
6294 -- Keep only the entity coming from another predefined unit.
6296 E2 := E;
6297 while Present (E2) loop
6298 if In_Predefined_Unit (E2) then
6299 E := E2;
6300 goto Found;
6301 end if;
6303 E2 := Homonym (E2);
6304 end loop;
6306 -- Entity must exist because predefined unit is correct
6308 raise Program_Error;
6310 else
6311 Nvis_Messages;
6312 goto Done;
6313 end if;
6314 end if;
6315 end;
6317 -- Come here with E set to the first immediately visible entity on
6318 -- the homonym chain. This is the one we want unless there is another
6319 -- immediately visible entity further on in the chain for an inner
6320 -- scope (RM 8.3(8)).
6322 <<Immediately_Visible_Entity>> declare
6323 Level : Int;
6324 Scop : Entity_Id;
6326 begin
6327 -- Find scope level of initial entity. When compiling through
6328 -- Rtsfind, the previous context is not completely invisible, and
6329 -- an outer entity may appear on the chain, whose scope is below
6330 -- the entry for Standard that delimits the current scope stack.
6331 -- Indicate that the level for this spurious entry is outside of
6332 -- the current scope stack.
6334 Level := Scope_Stack.Last;
6335 loop
6336 Scop := Scope_Stack.Table (Level).Entity;
6337 exit when Scop = Scope (E);
6338 Level := Level - 1;
6339 exit when Scop = Standard_Standard;
6340 end loop;
6342 -- Now search remainder of homonym chain for more inner entry
6343 -- If the entity is Standard itself, it has no scope, and we
6344 -- compare it with the stack entry directly.
6346 E2 := Homonym (E);
6347 while Present (E2) loop
6348 if Is_Immediately_Visible (E2) then
6350 -- If a generic package contains a local declaration that
6351 -- has the same name as the generic, there may be a visibility
6352 -- conflict in an instance, where the local declaration must
6353 -- also hide the name of the corresponding package renaming.
6354 -- We check explicitly for a package declared by a renaming,
6355 -- whose renamed entity is an instance that is on the scope
6356 -- stack, and that contains a homonym in the same scope. Once
6357 -- we have found it, we know that the package renaming is not
6358 -- immediately visible, and that the identifier denotes the
6359 -- other entity (and its homonyms if overloaded).
6361 if Scope (E) = Scope (E2)
6362 and then Ekind (E) = E_Package
6363 and then Present (Renamed_Entity (E))
6364 and then Is_Generic_Instance (Renamed_Entity (E))
6365 and then In_Open_Scopes (Renamed_Entity (E))
6366 and then Comes_From_Source (N)
6367 then
6368 Set_Is_Immediately_Visible (E, False);
6369 E := E2;
6371 else
6372 for J in Level + 1 .. Scope_Stack.Last loop
6373 if Scope_Stack.Table (J).Entity = Scope (E2)
6374 or else Scope_Stack.Table (J).Entity = E2
6375 then
6376 Level := J;
6377 E := E2;
6378 exit;
6379 end if;
6380 end loop;
6381 end if;
6382 end if;
6384 E2 := Homonym (E2);
6385 end loop;
6387 -- At the end of that loop, E is the innermost immediately
6388 -- visible entity, so we are all set.
6389 end;
6391 -- Come here with entity found, and stored in E
6393 <<Found>> begin
6395 -- Check violation of No_Wide_Characters restriction
6397 Check_Wide_Character_Restriction (E, N);
6399 -- When distribution features are available (Get_PCS_Name /=
6400 -- Name_No_DSA), a remote access-to-subprogram type is converted
6401 -- into a record type holding whatever information is needed to
6402 -- perform a remote call on an RCI subprogram. In that case we
6403 -- rewrite any occurrence of the RAS type into the equivalent record
6404 -- type here. 'Access attribute references and RAS dereferences are
6405 -- then implemented using specific TSSs. However when distribution is
6406 -- not available (case of Get_PCS_Name = Name_No_DSA), we bypass the
6407 -- generation of these TSSs, and we must keep the RAS type in its
6408 -- original access-to-subprogram form (since all calls through a
6409 -- value of such type will be local anyway in the absence of a PCS).
6411 if Comes_From_Source (N)
6412 and then Is_Remote_Access_To_Subprogram_Type (E)
6413 and then Ekind (E) = E_Access_Subprogram_Type
6414 and then Expander_Active
6415 and then Get_PCS_Name /= Name_No_DSA
6416 then
6417 Rewrite (N, New_Occurrence_Of (Equivalent_Type (E), Sloc (N)));
6418 goto Done;
6419 end if;
6421 -- Set the entity. Note that the reason we call Set_Entity for the
6422 -- overloadable case, as opposed to Set_Entity_With_Checks is
6423 -- that in the overloaded case, the initial call can set the wrong
6424 -- homonym. The call that sets the right homonym is in Sem_Res and
6425 -- that call does use Set_Entity_With_Checks, so we don't miss
6426 -- a style check.
6428 if Is_Overloadable (E) then
6429 Set_Entity (N, E);
6430 else
6431 Set_Entity_With_Checks (N, E);
6432 end if;
6434 if Is_Type (E) then
6435 Set_Etype (N, E);
6436 else
6437 Set_Etype (N, Get_Full_View (Etype (E)));
6438 end if;
6440 if Debug_Flag_E then
6441 Write_Str (" found ");
6442 Write_Entity_Info (E, " ");
6443 end if;
6445 -- If the Ekind of the entity is Void, it means that all homonyms
6446 -- are hidden from all visibility (RM 8.3(5,14-20)). However, this
6447 -- test is skipped if the current scope is a record and the name is
6448 -- a pragma argument expression (case of Atomic and Volatile pragmas
6449 -- and possibly other similar pragmas added later, which are allowed
6450 -- to reference components in the current record).
6452 if Ekind (E) = E_Void
6453 and then
6454 (not Is_Record_Type (Current_Scope)
6455 or else Nkind (Parent (N)) /= N_Pragma_Argument_Association)
6456 then
6457 Premature_Usage (N);
6459 -- If the entity is overloadable, collect all interpretations of the
6460 -- name for subsequent overload resolution. We optimize a bit here to
6461 -- do this only if we have an overloadable entity that is not on its
6462 -- own on the homonym chain.
6464 elsif Is_Overloadable (E)
6465 and then (Present (Homonym (E)) or else Current_Entity (N) /= E)
6466 then
6467 Collect_Interps (N);
6469 -- If no homonyms were visible, the entity is unambiguous
6471 if not Is_Overloaded (N) then
6472 if not Is_Actual_Parameter then
6473 Generate_Reference (E, N);
6474 end if;
6475 end if;
6477 -- Case of non-overloadable entity, set the entity providing that
6478 -- we do not have the case of a discriminant reference within a
6479 -- default expression. Such references are replaced with the
6480 -- corresponding discriminal, which is the formal corresponding to
6481 -- to the discriminant in the initialization procedure.
6483 else
6484 -- Entity is unambiguous, indicate that it is referenced here
6486 -- For a renaming of an object, always generate simple reference,
6487 -- we don't try to keep track of assignments in this case, except
6488 -- in SPARK mode where renamings are traversed for generating
6489 -- local effects of subprograms.
6491 if Is_Object (E)
6492 and then Present (Renamed_Object (E))
6493 and then not GNATprove_Mode
6494 then
6495 Generate_Reference (E, N);
6497 -- If the renamed entity is a private protected component,
6498 -- reference the original component as well. This needs to be
6499 -- done because the private renamings are installed before any
6500 -- analysis has occurred. Reference to a private component will
6501 -- resolve to the renaming and the original component will be
6502 -- left unreferenced, hence the following.
6504 if Is_Prival (E) then
6505 Generate_Reference (Prival_Link (E), N);
6506 end if;
6508 -- One odd case is that we do not want to set the Referenced flag
6509 -- if the entity is a label, and the identifier is the label in
6510 -- the source, since this is not a reference from the point of
6511 -- view of the user.
6513 elsif Nkind (Parent (N)) = N_Label then
6514 declare
6515 R : constant Boolean := Referenced (E);
6517 begin
6518 -- Generate reference unless this is an actual parameter
6519 -- (see comment below).
6521 if not Is_Actual_Parameter then
6522 Generate_Reference (E, N);
6523 Set_Referenced (E, R);
6524 end if;
6525 end;
6527 -- Normal case, not a label: generate reference
6529 else
6530 if not Is_Actual_Parameter then
6532 -- Package or generic package is always a simple reference
6534 if Is_Package_Or_Generic_Package (E) then
6535 Generate_Reference (E, N, 'r');
6537 -- Else see if we have a left hand side
6539 else
6540 case Known_To_Be_Assigned (N, Only_LHS => True) is
6541 when True =>
6542 Generate_Reference (E, N, 'm');
6544 when False =>
6545 Generate_Reference (E, N, 'r');
6547 end case;
6548 end if;
6549 end if;
6550 end if;
6552 Set_Entity_Or_Discriminal (N, E);
6554 -- The name may designate a generalized reference, in which case
6555 -- the dereference interpretation will be included. Context is
6556 -- one in which a name is legal.
6558 if Ada_Version >= Ada_2012
6559 and then
6560 (Nkind (Parent (N)) in N_Subexpr
6561 or else Nkind (Parent (N)) in N_Assignment_Statement
6562 | N_Object_Declaration
6563 | N_Parameter_Association)
6564 then
6565 Check_Implicit_Dereference (N, Etype (E));
6566 end if;
6567 end if;
6568 end;
6570 -- Mark relevant use-type and use-package clauses as effective if the
6571 -- node in question is not overloaded and therefore does not require
6572 -- resolution.
6574 -- Note: Generic actual subprograms do not follow the normal resolution
6575 -- path, so ignore the fact that they are overloaded and mark them
6576 -- anyway.
6578 if Nkind (N) not in N_Subexpr or else not Is_Overloaded (N) then
6579 Mark_Use_Clauses (N);
6580 end if;
6582 -- Come here with entity set
6584 <<Done>>
6585 Check_Restriction_No_Use_Of_Entity (N);
6587 -- Annotate the tree by creating a variable reference marker in case the
6588 -- original variable reference is folded or optimized away. The variable
6589 -- reference marker is automatically saved for later examination by the
6590 -- ABE Processing phase. Variable references which act as actuals in a
6591 -- call require special processing and are left to Resolve_Actuals. The
6592 -- reference is a write when it appears on the left hand side of an
6593 -- assignment.
6595 if Needs_Variable_Reference_Marker (N => N, Calls_OK => False) then
6596 declare
6597 Is_Assignment_LHS : constant Boolean := Known_To_Be_Assigned (N);
6599 begin
6600 Build_Variable_Reference_Marker
6601 (N => N,
6602 Read => not Is_Assignment_LHS,
6603 Write => Is_Assignment_LHS);
6604 end;
6605 end if;
6606 end Find_Direct_Name;
6608 ------------------------
6609 -- Find_Expanded_Name --
6610 ------------------------
6612 -- This routine searches the homonym chain of the entity until it finds
6613 -- an entity declared in the scope denoted by the prefix. If the entity
6614 -- is private, it may nevertheless be immediately visible, if we are in
6615 -- the scope of its declaration.
6617 procedure Find_Expanded_Name (N : Node_Id) is
6618 function In_Abstract_View_Pragma (Nod : Node_Id) return Boolean;
6619 -- Determine whether expanded name Nod appears within a pragma which is
6620 -- a suitable context for an abstract view of a state or variable. The
6621 -- following pragmas fall in this category:
6622 -- Depends
6623 -- Global
6624 -- Initializes
6625 -- Refined_Depends
6626 -- Refined_Global
6628 -- In addition, pragma Abstract_State is also considered suitable even
6629 -- though it is an illegal context for an abstract view as this allows
6630 -- for proper resolution of abstract views of variables. This illegal
6631 -- context is later flagged in the analysis of indicator Part_Of.
6633 -----------------------------
6634 -- In_Abstract_View_Pragma --
6635 -----------------------------
6637 function In_Abstract_View_Pragma (Nod : Node_Id) return Boolean is
6638 Par : Node_Id;
6640 begin
6641 -- Climb the parent chain looking for a pragma
6643 Par := Nod;
6644 while Present (Par) loop
6645 if Nkind (Par) = N_Pragma then
6646 if Pragma_Name_Unmapped (Par)
6647 in Name_Abstract_State
6648 | Name_Depends
6649 | Name_Global
6650 | Name_Initializes
6651 | Name_Refined_Depends
6652 | Name_Refined_Global
6653 then
6654 return True;
6656 -- Otherwise the pragma is not a legal context for an abstract
6657 -- view.
6659 else
6660 exit;
6661 end if;
6663 -- Prevent the search from going too far
6665 elsif Is_Body_Or_Package_Declaration (Par) then
6666 exit;
6667 end if;
6669 Par := Parent (Par);
6670 end loop;
6672 return False;
6673 end In_Abstract_View_Pragma;
6675 -- Local variables
6677 Selector : constant Node_Id := Selector_Name (N);
6679 Candidate : Entity_Id := Empty;
6680 P_Name : Entity_Id;
6681 Id : Entity_Id;
6683 -- Start of processing for Find_Expanded_Name
6685 begin
6686 P_Name := Entity (Prefix (N));
6688 -- If the prefix is a renamed package, look for the entity in the
6689 -- original package.
6691 if Ekind (P_Name) = E_Package
6692 and then Present (Renamed_Entity (P_Name))
6693 then
6694 P_Name := Renamed_Entity (P_Name);
6696 if From_Limited_With (P_Name)
6697 and then not Unit_Is_Visible (Cunit (Get_Source_Unit (P_Name)))
6698 then
6699 Error_Msg_NE
6700 ("renaming of limited view of package & not usable in this"
6701 & " context (RM 8.5.3(3.1/2))", Prefix (N), P_Name);
6703 elsif Has_Limited_View (P_Name)
6704 and then not Unit_Is_Visible (Cunit (Get_Source_Unit (P_Name)))
6705 and then not Is_Visible_Through_Renamings (P_Name)
6706 then
6707 Error_Msg_NE
6708 ("renaming of limited view of package & not usable in this"
6709 & " context (RM 8.5.3(3.1/2))", Prefix (N), P_Name);
6710 end if;
6712 -- Rewrite node with entity field pointing to renamed object
6714 Rewrite (Prefix (N), New_Copy (Prefix (N)));
6715 Set_Entity (Prefix (N), P_Name);
6717 -- If the prefix is an object of a concurrent type, look for
6718 -- the entity in the associated task or protected type.
6720 elsif Is_Concurrent_Type (Etype (P_Name)) then
6721 P_Name := Etype (P_Name);
6722 end if;
6724 Id := Current_Entity (Selector);
6726 declare
6727 Is_New_Candidate : Boolean;
6729 begin
6730 while Present (Id) loop
6731 if Scope (Id) = P_Name then
6732 Candidate := Id;
6733 Is_New_Candidate := True;
6735 -- Handle abstract views of states and variables. These are
6736 -- acceptable candidates only when the reference to the view
6737 -- appears in certain pragmas.
6739 if Ekind (Id) = E_Abstract_State
6740 and then From_Limited_With (Id)
6741 and then Present (Non_Limited_View (Id))
6742 then
6743 if In_Abstract_View_Pragma (N) then
6744 Candidate := Non_Limited_View (Id);
6745 Is_New_Candidate := True;
6747 -- Hide the candidate because it is not used in a proper
6748 -- context.
6750 else
6751 Candidate := Empty;
6752 Is_New_Candidate := False;
6753 end if;
6754 end if;
6756 -- Ada 2005 (AI-217): Handle shadow entities associated with
6757 -- types declared in limited-withed nested packages. We don't need
6758 -- to handle E_Incomplete_Subtype entities because the entities
6759 -- in the limited view are always E_Incomplete_Type and
6760 -- E_Class_Wide_Type entities (see Build_Limited_Views).
6762 -- Regarding the expression used to evaluate the scope, it
6763 -- is important to note that the limited view also has shadow
6764 -- entities associated nested packages. For this reason the
6765 -- correct scope of the entity is the scope of the real entity.
6766 -- The non-limited view may itself be incomplete, in which case
6767 -- get the full view if available.
6769 elsif Ekind (Id) in E_Incomplete_Type | E_Class_Wide_Type
6770 and then From_Limited_With (Id)
6771 and then Present (Non_Limited_View (Id))
6772 and then Scope (Non_Limited_View (Id)) = P_Name
6773 then
6774 Candidate := Get_Full_View (Non_Limited_View (Id));
6775 Is_New_Candidate := True;
6777 -- Handle special case where the prefix is a renaming of a shadow
6778 -- package which is visible. Required to avoid reporting spurious
6779 -- errors.
6781 elsif Ekind (P_Name) = E_Package
6782 and then From_Limited_With (P_Name)
6783 and then not From_Limited_With (Id)
6784 and then Sloc (Scope (Id)) = Sloc (P_Name)
6785 and then Unit_Is_Visible (Cunit (Get_Source_Unit (P_Name)))
6786 then
6787 Candidate := Get_Full_View (Id);
6788 Is_New_Candidate := True;
6790 -- An unusual case arises with a fully qualified name for an
6791 -- entity local to a generic child unit package, within an
6792 -- instantiation of that package. The name of the unit now
6793 -- denotes the renaming created within the instance. This is
6794 -- only relevant in an instance body, see below.
6796 elsif Is_Generic_Instance (Scope (Id))
6797 and then In_Open_Scopes (Scope (Id))
6798 and then In_Instance_Body
6799 and then Ekind (Scope (Id)) = E_Package
6800 and then Ekind (Id) = E_Package
6801 and then Renamed_Entity (Id) = Scope (Id)
6802 and then Is_Immediately_Visible (P_Name)
6803 then
6804 Is_New_Candidate := True;
6806 else
6807 Is_New_Candidate := False;
6808 end if;
6810 if Is_New_Candidate then
6812 -- If entity is a child unit, either it is a visible child of
6813 -- the prefix, or we are in the body of a generic prefix, as
6814 -- will happen when a child unit is instantiated in the body
6815 -- of a generic parent. This is because the instance body does
6816 -- not restore the full compilation context, given that all
6817 -- non-local references have been captured.
6819 if Is_Child_Unit (Id) or else P_Name = Standard_Standard then
6820 exit when Is_Visible_Lib_Unit (Id)
6821 or else (Is_Child_Unit (Id)
6822 and then In_Open_Scopes (Scope (Id))
6823 and then In_Instance_Body);
6824 else
6825 exit when not Is_Hidden (Id);
6826 end if;
6828 exit when Is_Immediately_Visible (Id);
6829 end if;
6831 Id := Homonym (Id);
6832 end loop;
6833 end;
6835 if No (Id)
6836 and then Ekind (P_Name) in E_Procedure | E_Function
6837 and then Is_Generic_Instance (P_Name)
6838 then
6839 -- Expanded name denotes entity in (instance of) generic subprogram.
6840 -- The entity may be in the subprogram instance, or may denote one of
6841 -- the formals, which is declared in the enclosing wrapper package.
6843 P_Name := Scope (P_Name);
6845 Id := Current_Entity (Selector);
6846 while Present (Id) loop
6847 exit when Scope (Id) = P_Name;
6848 Id := Homonym (Id);
6849 end loop;
6850 end if;
6852 if No (Id) or else Chars (Id) /= Chars (Selector) then
6853 Set_Etype (N, Any_Type);
6855 -- If we are looking for an entity defined in System, try to find it
6856 -- in the child package that may have been provided as an extension
6857 -- to System. The Extend_System pragma will have supplied the name of
6858 -- the extension, which may have to be loaded.
6860 if Chars (P_Name) = Name_System
6861 and then Scope (P_Name) = Standard_Standard
6862 and then Present (System_Extend_Unit)
6863 and then Present_System_Aux (N)
6864 then
6865 Set_Entity (Prefix (N), System_Aux_Id);
6866 Find_Expanded_Name (N);
6867 return;
6869 -- There is an implicit instance of the predefined operator in
6870 -- the given scope. The operator entity is defined in Standard.
6871 -- Has_Implicit_Operator makes the node into an Expanded_Name.
6873 elsif Nkind (Selector) = N_Operator_Symbol
6874 and then Has_Implicit_Operator (N)
6875 then
6876 return;
6878 -- If there is no literal defined in the scope denoted by the
6879 -- prefix, the literal may belong to (a type derived from)
6880 -- Standard_Character, for which we have no explicit literals.
6882 elsif Nkind (Selector) = N_Character_Literal
6883 and then Has_Implicit_Character_Literal (N)
6884 then
6885 return;
6887 else
6888 -- If the prefix is a single concurrent object, use its name in
6889 -- the error message, rather than that of the anonymous type.
6891 if Is_Concurrent_Type (P_Name)
6892 and then Is_Internal_Name (Chars (P_Name))
6893 then
6894 Error_Msg_Node_2 := Entity (Prefix (N));
6895 else
6896 Error_Msg_Node_2 := P_Name;
6897 end if;
6899 if P_Name = System_Aux_Id then
6900 P_Name := Scope (P_Name);
6901 Set_Entity (Prefix (N), P_Name);
6902 end if;
6904 if Present (Candidate) then
6906 -- If we know that the unit is a child unit we can give a more
6907 -- accurate error message.
6909 if Is_Child_Unit (Candidate) then
6911 -- If the candidate is a private child unit and we are in
6912 -- the visible part of a public unit, specialize the error
6913 -- message. There might be a private with_clause for it,
6914 -- but it is not currently active.
6916 if Is_Private_Descendant (Candidate)
6917 and then Ekind (Current_Scope) = E_Package
6918 and then not In_Private_Part (Current_Scope)
6919 and then not Is_Private_Descendant (Current_Scope)
6920 then
6921 Error_Msg_N
6922 ("private child unit& is not visible here", Selector);
6924 -- Normal case where we have a missing with for a child unit
6926 else
6927 Error_Msg_Qual_Level := 99;
6928 Error_Msg_NE -- CODEFIX
6929 ("missing `WITH &;`", Selector, Candidate);
6930 Error_Msg_Qual_Level := 0;
6931 end if;
6933 -- Here we don't know that this is a child unit
6935 else
6936 Error_Msg_NE ("& is not a visible entity of&", N, Selector);
6937 end if;
6939 else
6940 -- Within the instantiation of a child unit, the prefix may
6941 -- denote the parent instance, but the selector has the name
6942 -- of the original child. That is to say, when A.B appears
6943 -- within an instantiation of generic child unit B, the scope
6944 -- stack includes an instance of A (P_Name) and an instance
6945 -- of B under some other name. We scan the scope to find this
6946 -- child instance, which is the desired entity.
6947 -- Note that the parent may itself be a child instance, if
6948 -- the reference is of the form A.B.C, in which case A.B has
6949 -- already been rewritten with the proper entity.
6951 if In_Open_Scopes (P_Name)
6952 and then Is_Generic_Instance (P_Name)
6953 then
6954 declare
6955 Gen_Par : constant Entity_Id :=
6956 Generic_Parent (Specification
6957 (Unit_Declaration_Node (P_Name)));
6958 S : Entity_Id := Current_Scope;
6959 P : Entity_Id;
6961 begin
6962 for J in reverse 0 .. Scope_Stack.Last loop
6963 S := Scope_Stack.Table (J).Entity;
6965 exit when S = Standard_Standard;
6967 if Ekind (S) in E_Function | E_Package | E_Procedure
6968 then
6969 P :=
6970 Generic_Parent (Specification
6971 (Unit_Declaration_Node (S)));
6973 -- Check that P is a generic child of the generic
6974 -- parent of the prefix.
6976 if Present (P)
6977 and then Chars (P) = Chars (Selector)
6978 and then Scope (P) = Gen_Par
6979 then
6980 Id := S;
6981 goto Found;
6982 end if;
6983 end if;
6985 end loop;
6986 end;
6987 end if;
6989 -- If this is a selection from Ada, System or Interfaces, then
6990 -- we assume a missing with for the corresponding package.
6992 if Is_Known_Unit (N)
6993 and then not (Present (Entity (Prefix (N)))
6994 and then Scope (Entity (Prefix (N))) /=
6995 Standard_Standard)
6996 then
6997 if not Error_Posted (N) then
6998 Error_Msg_NE
6999 ("& is not a visible entity of&", Prefix (N), Selector);
7000 Error_Missing_With_Of_Known_Unit (Prefix (N));
7001 end if;
7003 -- If this is a selection from a dummy package, then suppress
7004 -- the error message, of course the entity is missing if the
7005 -- package is missing.
7007 elsif Sloc (Error_Msg_Node_2) = No_Location then
7008 null;
7010 -- Here we have the case of an undefined component
7012 else
7013 -- The prefix may hide a homonym in the context that
7014 -- declares the desired entity. This error can use a
7015 -- specialized message.
7017 if In_Open_Scopes (P_Name) then
7018 declare
7019 H : constant Entity_Id := Homonym (P_Name);
7021 begin
7022 if Present (H)
7023 and then Is_Compilation_Unit (H)
7024 and then
7025 (Is_Immediately_Visible (H)
7026 or else Is_Visible_Lib_Unit (H))
7027 then
7028 Id := First_Entity (H);
7029 while Present (Id) loop
7030 if Chars (Id) = Chars (Selector) then
7031 Error_Msg_Qual_Level := 99;
7032 Error_Msg_Name_1 := Chars (Selector);
7033 Error_Msg_NE
7034 ("% not declared in&", N, P_Name);
7035 Error_Msg_NE
7036 ("\use fully qualified name starting with "
7037 & "Standard to make& visible", N, H);
7038 Error_Msg_Qual_Level := 0;
7039 goto Done;
7040 end if;
7042 Next_Entity (Id);
7043 end loop;
7044 end if;
7046 -- If not found, standard error message
7048 Error_Msg_NE ("& not declared in&", N, Selector);
7050 <<Done>> null;
7051 end;
7053 else
7054 -- Might be worth specializing the case when the prefix
7055 -- is a limited view.
7056 -- ... not declared in limited view of...
7058 Error_Msg_NE ("& not declared in&", N, Selector);
7059 end if;
7061 -- Check for misspelling of some entity in prefix
7063 Id := First_Entity (P_Name);
7064 while Present (Id) loop
7065 if Is_Bad_Spelling_Of (Chars (Id), Chars (Selector))
7066 and then not Is_Internal_Name (Chars (Id))
7067 then
7068 Error_Msg_NE -- CODEFIX
7069 ("possible misspelling of&", Selector, Id);
7070 exit;
7071 end if;
7073 Next_Entity (Id);
7074 end loop;
7076 -- Specialize the message if this may be an instantiation
7077 -- of a child unit that was not mentioned in the context.
7079 if Nkind (Parent (N)) = N_Package_Instantiation
7080 and then Is_Generic_Instance (Entity (Prefix (N)))
7081 and then Is_Compilation_Unit
7082 (Generic_Parent (Parent (Entity (Prefix (N)))))
7083 then
7084 Error_Msg_Node_2 := Selector;
7085 Error_Msg_N -- CODEFIX
7086 ("\missing `WITH &.&;`", Prefix (N));
7087 end if;
7088 end if;
7089 end if;
7091 Id := Any_Id;
7092 end if;
7093 end if;
7095 <<Found>>
7096 if Comes_From_Source (N)
7097 and then Is_Remote_Access_To_Subprogram_Type (Id)
7098 and then Ekind (Id) = E_Access_Subprogram_Type
7099 and then Present (Equivalent_Type (Id))
7100 then
7101 -- If we are not actually generating distribution code (i.e. the
7102 -- current PCS is the dummy non-distributed version), then the
7103 -- Equivalent_Type will be missing, and Id should be treated as
7104 -- a regular access-to-subprogram type.
7106 Id := Equivalent_Type (Id);
7107 Set_Chars (Selector, Chars (Id));
7108 end if;
7110 -- Ada 2005 (AI-50217): Check usage of entities in limited withed units
7112 if Ekind (P_Name) = E_Package and then From_Limited_With (P_Name) then
7113 if From_Limited_With (Id)
7114 or else Is_Type (Id)
7115 or else Ekind (Id) = E_Package
7116 then
7117 null;
7118 else
7119 Error_Msg_N
7120 ("limited withed package can only be used to access incomplete "
7121 & "types", N);
7122 end if;
7123 end if;
7125 if Is_Task_Type (P_Name)
7126 and then ((Ekind (Id) = E_Entry
7127 and then Nkind (Parent (N)) /= N_Attribute_Reference)
7128 or else
7129 (Ekind (Id) = E_Entry_Family
7130 and then
7131 Nkind (Parent (Parent (N))) /= N_Attribute_Reference))
7132 then
7133 -- If both the task type and the entry are in scope, this may still
7134 -- be the expanded name of an entry formal.
7136 if In_Open_Scopes (Id)
7137 and then Nkind (Parent (N)) = N_Selected_Component
7138 then
7139 null;
7141 else
7142 -- It is an entry call after all, either to the current task
7143 -- (which will deadlock) or to an enclosing task.
7145 Analyze_Selected_Component (N);
7146 return;
7147 end if;
7148 end if;
7150 case Nkind (N) is
7151 when N_Selected_Component =>
7152 Reinit_Field_To_Zero (N, F_Is_Prefixed_Call);
7153 Change_Selected_Component_To_Expanded_Name (N);
7155 when N_Expanded_Name =>
7156 null;
7158 when others =>
7159 pragma Assert (False);
7160 end case;
7162 -- Preserve relevant elaboration-related attributes of the context which
7163 -- are no longer available or very expensive to recompute once analysis,
7164 -- resolution, and expansion are over.
7166 Mark_Elaboration_Attributes
7167 (N_Id => N,
7168 Checks => True,
7169 Modes => True,
7170 Warnings => True);
7172 -- Set appropriate type
7174 if Is_Type (Id) then
7175 Set_Etype (N, Id);
7176 else
7177 Set_Etype (N, Get_Full_View (Etype (Id)));
7178 end if;
7180 -- Do style check and generate reference, but skip both steps if this
7181 -- entity has homonyms, since we may not have the right homonym set yet.
7182 -- The proper homonym will be set during the resolve phase.
7184 if Has_Homonym (Id) then
7185 Set_Entity (N, Id);
7187 else
7188 Set_Entity_Or_Discriminal (N, Id);
7190 case Known_To_Be_Assigned (N, Only_LHS => True) is
7191 when True =>
7192 Generate_Reference (Id, N, 'm');
7194 when False =>
7195 Generate_Reference (Id, N, 'r');
7197 end case;
7198 end if;
7200 -- Check for violation of No_Wide_Characters
7202 Check_Wide_Character_Restriction (Id, N);
7204 -- If the Ekind of the entity is Void, it means that all homonyms are
7205 -- hidden from all visibility (RM 8.3(5,14-20)).
7207 if Ekind (Id) = E_Void then
7208 Premature_Usage (N);
7210 elsif Is_Overloadable (Id) and then Present (Homonym (Id)) then
7211 declare
7212 H : Entity_Id := Homonym (Id);
7214 begin
7215 while Present (H) loop
7216 if Scope (H) = Scope (Id)
7217 and then (not Is_Hidden (H)
7218 or else Is_Immediately_Visible (H))
7219 then
7220 Collect_Interps (N);
7221 exit;
7222 end if;
7224 H := Homonym (H);
7225 end loop;
7227 -- If an extension of System is present, collect possible explicit
7228 -- overloadings declared in the extension.
7230 if Chars (P_Name) = Name_System
7231 and then Scope (P_Name) = Standard_Standard
7232 and then Present (System_Extend_Unit)
7233 and then Present_System_Aux (N)
7234 then
7235 H := Current_Entity (Id);
7237 while Present (H) loop
7238 if Scope (H) = System_Aux_Id then
7239 Add_One_Interp (N, H, Etype (H));
7240 end if;
7242 H := Homonym (H);
7243 end loop;
7244 end if;
7245 end;
7246 end if;
7248 if Nkind (Selector_Name (N)) = N_Operator_Symbol
7249 and then Scope (Id) /= Standard_Standard
7250 then
7251 -- In addition to user-defined operators in the given scope, there
7252 -- may be an implicit instance of the predefined operator. The
7253 -- operator (defined in Standard) is found in Has_Implicit_Operator,
7254 -- and added to the interpretations. Procedure Add_One_Interp will
7255 -- determine which hides which.
7257 if Has_Implicit_Operator (N) then
7258 null;
7259 end if;
7260 end if;
7262 -- If there is a single interpretation for N we can generate a
7263 -- reference to the unique entity found.
7265 if Is_Overloadable (Id) and then not Is_Overloaded (N) then
7266 Generate_Reference (Id, N);
7267 end if;
7269 -- Mark relevant use-type and use-package clauses as effective if the
7270 -- node in question is not overloaded and therefore does not require
7271 -- resolution.
7273 if Nkind (N) not in N_Subexpr or else not Is_Overloaded (N) then
7274 Mark_Use_Clauses (N);
7275 end if;
7277 Check_Restriction_No_Use_Of_Entity (N);
7279 -- Annotate the tree by creating a variable reference marker in case the
7280 -- original variable reference is folded or optimized away. The variable
7281 -- reference marker is automatically saved for later examination by the
7282 -- ABE Processing phase. Variable references which act as actuals in a
7283 -- call require special processing and are left to Resolve_Actuals. The
7284 -- reference is a write when it appears on the left hand side of an
7285 -- assignment.
7287 if Needs_Variable_Reference_Marker
7288 (N => N,
7289 Calls_OK => False)
7290 then
7291 declare
7292 Is_Assignment_LHS : constant Boolean := Known_To_Be_Assigned (N);
7294 begin
7295 Build_Variable_Reference_Marker
7296 (N => N,
7297 Read => not Is_Assignment_LHS,
7298 Write => Is_Assignment_LHS);
7299 end;
7300 end if;
7301 end Find_Expanded_Name;
7303 --------------------
7304 -- Find_First_Use --
7305 --------------------
7307 function Find_First_Use (Use_Clause : Node_Id) return Node_Id is
7308 Curr : Node_Id;
7310 begin
7311 -- Loop through the Prev_Use_Clause chain
7313 Curr := Use_Clause;
7314 while Present (Prev_Use_Clause (Curr)) loop
7315 Curr := Prev_Use_Clause (Curr);
7316 end loop;
7318 return Curr;
7319 end Find_First_Use;
7321 -------------------------
7322 -- Find_Renamed_Entity --
7323 -------------------------
7325 function Find_Renamed_Entity
7326 (N : Node_Id;
7327 Nam : Node_Id;
7328 New_S : Entity_Id;
7329 Is_Actual : Boolean := False) return Entity_Id
7331 Ind : Interp_Index;
7332 I1 : Interp_Index := 0; -- Suppress junk warnings
7333 It : Interp;
7334 It1 : Interp;
7335 Old_S : Entity_Id;
7336 Inst : Entity_Id;
7338 function Find_Nearer_Entity
7339 (New_S : Entity_Id;
7340 Old1_S : Entity_Id;
7341 Old2_S : Entity_Id) return Entity_Id;
7342 -- Determine whether one of Old_S1 and Old_S2 is nearer to New_S than
7343 -- the other, and return it if so. Return Empty otherwise. We use this
7344 -- in conjunction with Inherit_Renamed_Profile to simplify later type
7345 -- disambiguation for actual subprograms in instances.
7347 function Is_Visible_Operation (Op : Entity_Id) return Boolean;
7348 -- If the renamed entity is an implicit operator, check whether it is
7349 -- visible because its operand type is properly visible. This check
7350 -- applies to explicit renamed entities that appear in the source in a
7351 -- renaming declaration or a formal subprogram instance, but not to
7352 -- default generic actuals with a name.
7354 function Report_Overload return Entity_Id;
7355 -- List possible interpretations, and specialize message in the
7356 -- case of a generic actual.
7358 function Within (Inner, Outer : Entity_Id) return Boolean;
7359 -- Determine whether a candidate subprogram is defined within the
7360 -- enclosing instance. If yes, it has precedence over outer candidates.
7362 --------------------------
7363 -- Find_Nearer_Entity --
7364 --------------------------
7366 function Find_Nearer_Entity
7367 (New_S : Entity_Id;
7368 Old1_S : Entity_Id;
7369 Old2_S : Entity_Id) return Entity_Id
7371 New_F : Entity_Id;
7372 Old1_F : Entity_Id;
7373 Old2_F : Entity_Id;
7374 Anc_T : Entity_Id;
7376 begin
7377 New_F := First_Formal (New_S);
7378 Old1_F := First_Formal (Old1_S);
7379 Old2_F := First_Formal (Old2_S);
7381 -- The criterion is whether the type of the formals of one of Old1_S
7382 -- and Old2_S is an ancestor subtype of the type of the corresponding
7383 -- formals of New_S while the other is not (we already know that they
7384 -- are all subtypes of the same base type).
7386 -- This makes it possible to find the more correct renamed entity in
7387 -- the case of a generic instantiation nested in an enclosing one for
7388 -- which different formal types get the same actual type, which will
7389 -- in turn make it possible for Inherit_Renamed_Profile to preserve
7390 -- types on formal parameters and ultimately simplify disambiguation.
7392 -- Consider the follow package G:
7394 -- generic
7395 -- type Item_T is private;
7396 -- with function Compare (L, R: Item_T) return Boolean is <>;
7398 -- type Bound_T is private;
7399 -- with function Compare (L, R : Bound_T) return Boolean is <>;
7400 -- package G is
7401 -- ...
7402 -- end G;
7404 -- package body G is
7405 -- package My_Inner is Inner_G (Bound_T);
7406 -- ...
7407 -- end G;
7409 -- with the following package Inner_G:
7411 -- generic
7412 -- type T is private;
7413 -- with function Compare (L, R: T) return Boolean is <>;
7414 -- package Inner_G is
7415 -- function "<" (L, R: T) return Boolean is (Compare (L, R));
7416 -- end Inner_G;
7418 -- If G is instantiated on the same actual type with a single Compare
7419 -- function:
7421 -- type T is ...
7422 -- function Compare (L, R : T) return Boolean;
7423 -- package My_G is new (T, T);
7425 -- then the renaming generated for Compare in the inner instantiation
7426 -- is ambiguous: it can rename either of the renamings generated for
7427 -- the outer instantiation. Now if the first one is picked up, then
7428 -- the subtypes of the formal parameters of the renaming will not be
7429 -- preserved in Inherit_Renamed_Profile because they are subtypes of
7430 -- the Bound_T formal type and not of the Item_T formal type, so we
7431 -- need to arrange for the second one to be picked up instead.
7433 while Present (New_F) loop
7434 if Etype (Old1_F) /= Etype (Old2_F) then
7435 Anc_T := Ancestor_Subtype (Etype (New_F));
7437 if Etype (Old1_F) = Anc_T then
7438 return Old1_S;
7439 elsif Etype (Old2_F) = Anc_T then
7440 return Old2_S;
7441 end if;
7442 end if;
7444 Next_Formal (New_F);
7445 Next_Formal (Old1_F);
7446 Next_Formal (Old2_F);
7447 end loop;
7449 pragma Assert (No (Old1_F));
7450 pragma Assert (No (Old2_F));
7452 return Empty;
7453 end Find_Nearer_Entity;
7455 --------------------------
7456 -- Is_Visible_Operation --
7457 --------------------------
7459 function Is_Visible_Operation (Op : Entity_Id) return Boolean is
7460 Scop : Entity_Id;
7461 Typ : Entity_Id;
7462 Btyp : Entity_Id;
7464 begin
7465 if Ekind (Op) /= E_Operator
7466 or else Scope (Op) /= Standard_Standard
7467 or else (In_Instance
7468 and then (not Is_Actual
7469 or else Present (Enclosing_Instance)))
7470 then
7471 return True;
7473 else
7474 -- For a fixed point type operator, check the resulting type,
7475 -- because it may be a mixed mode integer * fixed operation.
7477 if Present (Next_Formal (First_Formal (New_S)))
7478 and then Is_Fixed_Point_Type (Etype (New_S))
7479 then
7480 Typ := Etype (New_S);
7481 else
7482 Typ := Etype (First_Formal (New_S));
7483 end if;
7485 Btyp := Base_Type (Typ);
7487 if Nkind (Nam) /= N_Expanded_Name then
7488 return (In_Open_Scopes (Scope (Btyp))
7489 or else Is_Potentially_Use_Visible (Btyp)
7490 or else In_Use (Btyp)
7491 or else In_Use (Scope (Btyp)));
7493 else
7494 Scop := Entity (Prefix (Nam));
7496 if Ekind (Scop) = E_Package
7497 and then Present (Renamed_Entity (Scop))
7498 then
7499 Scop := Renamed_Entity (Scop);
7500 end if;
7502 -- Operator is visible if prefix of expanded name denotes
7503 -- scope of type, or else type is defined in System_Aux
7504 -- and the prefix denotes System.
7506 return Scope (Btyp) = Scop
7507 or else (Scope (Btyp) = System_Aux_Id
7508 and then Scope (Scope (Btyp)) = Scop);
7509 end if;
7510 end if;
7511 end Is_Visible_Operation;
7513 ------------
7514 -- Within --
7515 ------------
7517 function Within (Inner, Outer : Entity_Id) return Boolean is
7518 Sc : Entity_Id;
7520 begin
7521 Sc := Scope (Inner);
7522 while Sc /= Standard_Standard loop
7523 if Sc = Outer then
7524 return True;
7525 else
7526 Sc := Scope (Sc);
7527 end if;
7528 end loop;
7530 return False;
7531 end Within;
7533 ---------------------
7534 -- Report_Overload --
7535 ---------------------
7537 function Report_Overload return Entity_Id is
7538 begin
7539 if Is_Actual then
7540 Error_Msg_NE -- CODEFIX
7541 ("ambiguous actual subprogram&, " &
7542 "possible interpretations:", N, Nam);
7543 else
7544 Error_Msg_N -- CODEFIX
7545 ("ambiguous subprogram, " &
7546 "possible interpretations:", N);
7547 end if;
7549 List_Interps (Nam, N);
7550 return Old_S;
7551 end Report_Overload;
7553 -- Start of processing for Find_Renamed_Entity
7555 begin
7556 Old_S := Any_Id;
7557 Candidate_Renaming := Empty;
7559 if Is_Overloaded (Nam) then
7560 Get_First_Interp (Nam, Ind, It);
7561 while Present (It.Nam) loop
7562 if Entity_Matches_Spec (It.Nam, New_S)
7563 and then Is_Visible_Operation (It.Nam)
7564 then
7565 if Old_S /= Any_Id then
7567 -- Note: The call to Disambiguate only happens if a
7568 -- previous interpretation was found, in which case I1
7569 -- has received a value.
7571 It1 := Disambiguate (Nam, I1, Ind, Etype (Old_S));
7573 if It1 = No_Interp then
7574 Inst := Enclosing_Instance;
7576 if Present (Inst) then
7577 if Within (It.Nam, Inst) then
7578 if Within (Old_S, Inst) then
7579 declare
7580 It_D : constant Uint :=
7581 Scope_Depth_Default_0 (It.Nam);
7582 Old_D : constant Uint :=
7583 Scope_Depth_Default_0 (Old_S);
7584 N_Ent : Entity_Id;
7585 begin
7586 -- Choose the innermost subprogram, which
7587 -- would hide the outer one in the generic.
7589 if Old_D > It_D then
7590 return Old_S;
7591 elsif It_D > Old_D then
7592 return It.Nam;
7593 end if;
7595 -- Otherwise, if we can determine that one
7596 -- of the entities is nearer to the renaming
7597 -- than the other, choose it. If not, then
7598 -- return the newer one as done historically.
7600 N_Ent :=
7601 Find_Nearer_Entity (New_S, Old_S, It.Nam);
7602 if Present (N_Ent) then
7603 return N_Ent;
7604 else
7605 return It.Nam;
7606 end if;
7607 end;
7608 end if;
7610 elsif Within (Old_S, Inst) then
7611 return Old_S;
7613 else
7614 return Report_Overload;
7615 end if;
7617 -- If not within an instance, ambiguity is real
7619 else
7620 return Report_Overload;
7621 end if;
7623 else
7624 Old_S := It1.Nam;
7625 exit;
7626 end if;
7628 else
7629 I1 := Ind;
7630 Old_S := It.Nam;
7631 end if;
7633 elsif
7634 Present (First_Formal (It.Nam))
7635 and then Present (First_Formal (New_S))
7636 and then (Base_Type (Etype (First_Formal (It.Nam))) =
7637 Base_Type (Etype (First_Formal (New_S))))
7638 then
7639 Candidate_Renaming := It.Nam;
7640 end if;
7642 Get_Next_Interp (Ind, It);
7643 end loop;
7645 Set_Entity (Nam, Old_S);
7647 if Old_S /= Any_Id then
7648 Set_Is_Overloaded (Nam, False);
7649 end if;
7651 -- Non-overloaded case
7653 else
7654 if Is_Actual
7655 and then Present (Enclosing_Instance)
7656 and then Entity_Matches_Spec (Entity (Nam), New_S)
7657 then
7658 Old_S := Entity (Nam);
7660 elsif Entity_Matches_Spec (Entity (Nam), New_S) then
7661 Candidate_Renaming := New_S;
7663 if Is_Visible_Operation (Entity (Nam)) then
7664 Old_S := Entity (Nam);
7665 end if;
7667 elsif Present (First_Formal (Entity (Nam)))
7668 and then Present (First_Formal (New_S))
7669 and then (Base_Type (Etype (First_Formal (Entity (Nam)))) =
7670 Base_Type (Etype (First_Formal (New_S))))
7671 then
7672 Candidate_Renaming := Entity (Nam);
7673 end if;
7674 end if;
7676 return Old_S;
7677 end Find_Renamed_Entity;
7679 -----------------------------
7680 -- Find_Selected_Component --
7681 -----------------------------
7683 procedure Find_Selected_Component (N : Node_Id) is
7684 P : constant Node_Id := Prefix (N);
7686 P_Name : Entity_Id;
7687 -- Entity denoted by prefix
7689 P_Type : Entity_Id;
7690 -- and its type
7692 Nam : Node_Id;
7694 function Available_Subtype return Boolean;
7695 -- A small optimization: if the prefix is constrained and the component
7696 -- is an array type we may already have a usable subtype for it, so we
7697 -- can use it rather than generating a new one, because the bounds
7698 -- will be the values of the discriminants and not discriminant refs.
7699 -- This simplifies value tracing in GNATprove. For consistency, both
7700 -- the entity name and the subtype come from the constrained component.
7702 -- This is only used in GNATprove mode: when generating code it may be
7703 -- necessary to create an itype in the scope of use of the selected
7704 -- component, e.g. in the context of a expanded record equality.
7706 function Is_Reference_In_Subunit return Boolean;
7707 -- In a subunit, the scope depth is not a proper measure of hiding,
7708 -- because the context of the proper body may itself hide entities in
7709 -- parent units. This rare case requires inspecting the tree directly
7710 -- because the proper body is inserted in the main unit and its context
7711 -- is simply added to that of the parent.
7713 -----------------------
7714 -- Available_Subtype --
7715 -----------------------
7717 function Available_Subtype return Boolean is
7718 Comp : Entity_Id;
7720 begin
7721 if GNATprove_Mode then
7722 Comp := First_Entity (Etype (P));
7723 while Present (Comp) loop
7724 if Chars (Comp) = Chars (Selector_Name (N)) then
7725 Set_Etype (N, Etype (Comp));
7726 Set_Entity (Selector_Name (N), Comp);
7727 Set_Etype (Selector_Name (N), Etype (Comp));
7728 return True;
7729 end if;
7731 Next_Component (Comp);
7732 end loop;
7733 end if;
7735 return False;
7736 end Available_Subtype;
7738 -----------------------------
7739 -- Is_Reference_In_Subunit --
7740 -----------------------------
7742 function Is_Reference_In_Subunit return Boolean is
7743 Clause : Node_Id;
7744 Comp_Unit : Node_Id;
7746 begin
7747 Comp_Unit := N;
7748 while Present (Comp_Unit)
7749 and then Nkind (Comp_Unit) /= N_Compilation_Unit
7750 loop
7751 Comp_Unit := Parent (Comp_Unit);
7752 end loop;
7754 if No (Comp_Unit) or else Nkind (Unit (Comp_Unit)) /= N_Subunit then
7755 return False;
7756 end if;
7758 -- Now check whether the package is in the context of the subunit
7760 Clause := First (Context_Items (Comp_Unit));
7761 while Present (Clause) loop
7762 if Nkind (Clause) = N_With_Clause
7763 and then Entity (Name (Clause)) = P_Name
7764 then
7765 return True;
7766 end if;
7768 Next (Clause);
7769 end loop;
7771 return False;
7772 end Is_Reference_In_Subunit;
7774 -- Start of processing for Find_Selected_Component
7776 begin
7777 Analyze (P);
7779 if Nkind (P) = N_Error then
7780 return;
7781 end if;
7783 -- If the selector already has an entity, the node has been constructed
7784 -- in the course of expansion, and is known to be valid. Do not verify
7785 -- that it is defined for the type (it may be a private component used
7786 -- in the expansion of record equality).
7788 if Present (Entity (Selector_Name (N))) then
7789 if No (Etype (N)) or else Etype (N) = Any_Type then
7790 declare
7791 Sel_Name : constant Node_Id := Selector_Name (N);
7792 Selector : constant Entity_Id := Entity (Sel_Name);
7793 C_Etype : Node_Id;
7795 begin
7796 Set_Etype (Sel_Name, Etype (Selector));
7798 if not Is_Entity_Name (P) then
7799 Resolve (P);
7800 end if;
7802 -- Build an actual subtype except for the first parameter
7803 -- of an init proc, where this actual subtype is by
7804 -- definition incorrect, since the object is uninitialized
7805 -- (and does not even have defined discriminants etc.)
7807 if Is_Entity_Name (P)
7808 and then Ekind (Entity (P)) = E_Function
7809 then
7810 Nam := New_Copy (P);
7812 if Is_Overloaded (P) then
7813 Save_Interps (P, Nam);
7814 end if;
7816 Rewrite (P, Make_Function_Call (Sloc (P), Name => Nam));
7817 Analyze_Call (P);
7818 Analyze_Selected_Component (N);
7819 return;
7821 elsif Ekind (Selector) = E_Component
7822 and then (not Is_Entity_Name (P)
7823 or else Chars (Entity (P)) /= Name_uInit)
7824 then
7825 -- Check if we already have an available subtype we can use
7827 if Ekind (Etype (P)) = E_Record_Subtype
7828 and then Nkind (Parent (Etype (P))) = N_Subtype_Declaration
7829 and then Is_Array_Type (Etype (Selector))
7830 and then not Is_Packed (Etype (Selector))
7831 and then Available_Subtype
7832 then
7833 return;
7835 -- Do not build the subtype when referencing components of
7836 -- dispatch table wrappers. Required to avoid generating
7837 -- elaboration code with HI runtimes.
7839 elsif Is_RTE (Scope (Selector), RE_Dispatch_Table_Wrapper)
7840 or else
7841 Is_RTE (Scope (Selector), RE_No_Dispatch_Table_Wrapper)
7842 then
7843 C_Etype := Empty;
7844 else
7845 C_Etype :=
7846 Build_Actual_Subtype_Of_Component
7847 (Etype (Selector), N);
7848 end if;
7850 else
7851 C_Etype := Empty;
7852 end if;
7854 if No (C_Etype) then
7855 C_Etype := Etype (Selector);
7856 else
7857 Insert_Action (N, C_Etype);
7858 C_Etype := Defining_Identifier (C_Etype);
7859 end if;
7861 Set_Etype (N, C_Etype);
7862 end;
7864 -- If the selected component appears within a default expression
7865 -- and it has an actual subtype, the preanalysis has not yet
7866 -- completed its analysis, because Insert_Actions is disabled in
7867 -- that context. Within the init proc of the enclosing type we
7868 -- must complete this analysis, if an actual subtype was created.
7870 elsif Inside_Init_Proc then
7871 declare
7872 Typ : constant Entity_Id := Etype (N);
7873 Decl : constant Node_Id := Declaration_Node (Typ);
7874 begin
7875 if Nkind (Decl) = N_Subtype_Declaration
7876 and then not Analyzed (Decl)
7877 and then Is_List_Member (Decl)
7878 and then No (Parent (Decl))
7879 then
7880 Remove (Decl);
7881 Insert_Action (N, Decl);
7882 end if;
7883 end;
7884 end if;
7886 return;
7888 elsif Is_Entity_Name (P) then
7889 P_Name := Entity (P);
7891 -- The prefix may denote an enclosing type which is the completion
7892 -- of an incomplete type declaration.
7894 if Is_Type (P_Name) then
7895 Set_Entity (P, Get_Full_View (P_Name));
7896 Set_Etype (P, Entity (P));
7897 P_Name := Entity (P);
7898 end if;
7900 P_Type := Base_Type (Etype (P));
7902 if Debug_Flag_E then
7903 Write_Str ("Found prefix type to be ");
7904 Write_Entity_Info (P_Type, " "); Write_Eol;
7905 end if;
7907 -- If the prefix's type is an access type, get to the record type
7909 if Is_Access_Type (P_Type) then
7910 P_Type := Implicitly_Designated_Type (P_Type);
7911 end if;
7913 -- First check for components of a record object (not the result of
7914 -- a call, which is handled below). This also covers the case where
7915 -- the extension feature that supports the prefixed form of calls
7916 -- for primitives of untagged types is enabled (excluding concurrent
7917 -- cases, which are handled further below).
7919 if Is_Type (P_Type)
7920 and then (Has_Components (P_Type)
7921 or else (Extensions_Allowed
7922 and then not Is_Concurrent_Type (P_Type)))
7923 and then not Is_Overloadable (P_Name)
7924 and then not Is_Type (P_Name)
7925 then
7926 -- Selected component of record. Type checking will validate
7927 -- name of selector.
7929 -- ??? Could we rewrite an implicit dereference into an explicit
7930 -- one here?
7932 Analyze_Selected_Component (N);
7934 -- Reference to type name in predicate/invariant expression
7936 elsif Is_Concurrent_Type (P_Type)
7937 and then not In_Open_Scopes (P_Name)
7938 and then (not Is_Concurrent_Type (Etype (P_Name))
7939 or else not In_Open_Scopes (Etype (P_Name)))
7940 then
7941 -- Call to protected operation or entry. Type checking is
7942 -- needed on the prefix.
7944 Analyze_Selected_Component (N);
7946 elsif (In_Open_Scopes (P_Name)
7947 and then Ekind (P_Name) /= E_Void
7948 and then not Is_Overloadable (P_Name))
7949 or else (Is_Concurrent_Type (Etype (P_Name))
7950 and then In_Open_Scopes (Etype (P_Name)))
7951 then
7952 -- Prefix denotes an enclosing loop, block, or task, i.e. an
7953 -- enclosing construct that is not a subprogram or accept.
7955 -- A special case: a protected body may call an operation
7956 -- on an external object of the same type, in which case it
7957 -- is not an expanded name. If the prefix is the type itself,
7958 -- or the context is a single synchronized object it can only
7959 -- be interpreted as an expanded name.
7961 if Is_Concurrent_Type (Etype (P_Name)) then
7962 if Is_Type (P_Name)
7963 or else Present (Anonymous_Object (Etype (P_Name)))
7964 then
7965 Find_Expanded_Name (N);
7967 else
7968 Analyze_Selected_Component (N);
7969 return;
7970 end if;
7972 else
7973 Find_Expanded_Name (N);
7974 end if;
7976 elsif Ekind (P_Name) = E_Package then
7977 Find_Expanded_Name (N);
7979 elsif Is_Overloadable (P_Name) then
7981 -- The subprogram may be a renaming (of an enclosing scope) as
7982 -- in the case of the name of the generic within an instantiation.
7984 if Ekind (P_Name) in E_Procedure | E_Function
7985 and then Present (Alias (P_Name))
7986 and then Is_Generic_Instance (Alias (P_Name))
7987 then
7988 P_Name := Alias (P_Name);
7989 end if;
7991 if Is_Overloaded (P) then
7993 -- The prefix must resolve to a unique enclosing construct
7995 declare
7996 Found : Boolean := False;
7997 Ind : Interp_Index;
7998 It : Interp;
8000 begin
8001 Get_First_Interp (P, Ind, It);
8002 while Present (It.Nam) loop
8003 if In_Open_Scopes (It.Nam) then
8004 if Found then
8005 Error_Msg_N (
8006 "prefix must be unique enclosing scope", N);
8007 Set_Entity (N, Any_Id);
8008 Set_Etype (N, Any_Type);
8009 return;
8011 else
8012 Found := True;
8013 P_Name := It.Nam;
8014 end if;
8015 end if;
8017 Get_Next_Interp (Ind, It);
8018 end loop;
8019 end;
8020 end if;
8022 if In_Open_Scopes (P_Name) then
8023 Set_Entity (P, P_Name);
8024 Set_Is_Overloaded (P, False);
8025 Find_Expanded_Name (N);
8027 else
8028 -- If no interpretation as an expanded name is possible, it
8029 -- must be a selected component of a record returned by a
8030 -- function call. Reformat prefix as a function call, the rest
8031 -- is done by type resolution.
8033 -- Error if the prefix is procedure or entry, as is P.X
8035 if Ekind (P_Name) /= E_Function
8036 and then
8037 (not Is_Overloaded (P)
8038 or else Nkind (Parent (N)) = N_Procedure_Call_Statement)
8039 then
8040 -- Prefix may mention a package that is hidden by a local
8041 -- declaration: let the user know. Scan the full homonym
8042 -- chain, the candidate package may be anywhere on it.
8044 if Present (Homonym (Current_Entity (P_Name))) then
8045 P_Name := Current_Entity (P_Name);
8047 while Present (P_Name) loop
8048 exit when Ekind (P_Name) = E_Package;
8049 P_Name := Homonym (P_Name);
8050 end loop;
8052 if Present (P_Name) then
8053 if not Is_Reference_In_Subunit then
8054 Error_Msg_Sloc := Sloc (Entity (Prefix (N)));
8055 Error_Msg_NE
8056 ("package& is hidden by declaration#", N, P_Name);
8057 end if;
8059 Set_Entity (Prefix (N), P_Name);
8060 Find_Expanded_Name (N);
8061 return;
8063 else
8064 P_Name := Entity (Prefix (N));
8065 end if;
8066 end if;
8068 Error_Msg_NE
8069 ("invalid prefix in selected component&", N, P_Name);
8070 Change_Selected_Component_To_Expanded_Name (N);
8071 Set_Entity (N, Any_Id);
8072 Set_Etype (N, Any_Type);
8074 -- Here we have a function call, so do the reformatting
8076 else
8077 Nam := New_Copy (P);
8078 Save_Interps (P, Nam);
8080 -- We use Replace here because this is one of those cases
8081 -- where the parser has missclassified the node, and we fix
8082 -- things up and then do the semantic analysis on the fixed
8083 -- up node. Normally we do this using one of the Sinfo.CN
8084 -- routines, but this is too tricky for that.
8086 -- Note that using Rewrite would be wrong, because we would
8087 -- have a tree where the original node is unanalyzed.
8089 Replace (P,
8090 Make_Function_Call (Sloc (P), Name => Nam));
8092 -- Now analyze the reformatted node
8094 Analyze_Call (P);
8096 -- If the prefix is illegal after this transformation, there
8097 -- may be visibility errors on the prefix. The safest is to
8098 -- treat the selected component as an error.
8100 if Error_Posted (P) then
8101 Set_Etype (N, Any_Type);
8102 return;
8104 else
8105 Analyze_Selected_Component (N);
8106 end if;
8107 end if;
8108 end if;
8110 -- Remaining cases generate various error messages
8112 else
8113 -- Format node as expanded name, to avoid cascaded errors
8115 Change_Selected_Component_To_Expanded_Name (N);
8116 Set_Entity (N, Any_Id);
8117 Set_Etype (N, Any_Type);
8119 -- Issue error message, but avoid this if error issued already.
8120 -- Use identifier of prefix if one is available.
8122 if P_Name = Any_Id then
8123 null;
8125 -- It is not an error if the prefix is the current instance of
8126 -- type name, e.g. the expression of a type aspect, when it is
8127 -- analyzed within a generic unit. We still have to verify that a
8128 -- component of that name exists, and decorate the node
8129 -- accordingly.
8131 elsif Is_Entity_Name (P) and then Is_Current_Instance (P) then
8132 declare
8133 Comp : Entity_Id;
8135 begin
8136 Comp := First_Entity (Entity (P));
8137 while Present (Comp) loop
8138 if Chars (Comp) = Chars (Selector_Name (N)) then
8139 Set_Entity (N, Comp);
8140 Set_Etype (N, Etype (Comp));
8141 Set_Entity (Selector_Name (N), Comp);
8142 Set_Etype (Selector_Name (N), Etype (Comp));
8143 return;
8144 end if;
8146 Next_Entity (Comp);
8147 end loop;
8148 end;
8150 elsif Ekind (P_Name) = E_Void then
8151 Premature_Usage (P);
8153 elsif Ekind (P_Name) = E_Generic_Package then
8154 Error_Msg_N ("prefix must not be a generic package", N);
8155 Error_Msg_N ("\use package instantiation as prefix instead", N);
8157 elsif Nkind (P) /= N_Attribute_Reference then
8159 -- This may have been meant as a prefixed call to a primitive
8160 -- of an untagged type. If it is a function call check type of
8161 -- its first formal and add explanation.
8163 declare
8164 F : constant Entity_Id :=
8165 Current_Entity (Selector_Name (N));
8166 begin
8167 if Present (F)
8168 and then Is_Overloadable (F)
8169 and then Present (First_Entity (F))
8170 and then not Is_Tagged_Type (Etype (First_Entity (F)))
8171 then
8172 Error_Msg_N
8173 ("prefixed call is only allowed for objects of a "
8174 & "tagged type unless -gnatX is used", N);
8176 if not Extensions_Allowed
8177 and then
8178 Try_Object_Operation (N, Allow_Extensions => True)
8179 then
8180 Error_Msg_N
8181 ("\using -gnatX would make the prefixed call legal",
8183 end if;
8184 end if;
8185 end;
8187 Error_Msg_N ("invalid prefix in selected component&", P);
8189 if Is_Incomplete_Type (P_Type)
8190 and then Is_Access_Type (Etype (P))
8191 then
8192 Error_Msg_N
8193 ("\dereference must not be of an incomplete type "
8194 & "(RM 3.10.1)", P);
8195 end if;
8197 else
8198 Error_Msg_N ("invalid prefix in selected component", P);
8199 end if;
8200 end if;
8201 else
8202 -- If prefix is not the name of an entity, it must be an expression,
8203 -- whose type is appropriate for a record. This is determined by
8204 -- type resolution.
8206 Analyze_Selected_Component (N);
8207 end if;
8209 Analyze_Dimension (N);
8210 end Find_Selected_Component;
8212 ---------------
8213 -- Find_Type --
8214 ---------------
8216 procedure Find_Type (N : Node_Id) is
8217 C : Entity_Id;
8218 Typ : Entity_Id;
8219 T : Entity_Id;
8220 T_Name : Entity_Id;
8222 begin
8223 if N = Error then
8224 return;
8226 elsif Nkind (N) = N_Attribute_Reference then
8228 -- Class attribute. This is not valid in Ada 83 mode, but we do not
8229 -- need to enforce that at this point, since the declaration of the
8230 -- tagged type in the prefix would have been flagged already.
8232 if Attribute_Name (N) = Name_Class then
8233 Check_Restriction (No_Dispatch, N);
8234 Find_Type (Prefix (N));
8236 -- Propagate error from bad prefix
8238 if Etype (Prefix (N)) = Any_Type then
8239 Set_Entity (N, Any_Type);
8240 Set_Etype (N, Any_Type);
8241 return;
8242 end if;
8244 T := Base_Type (Entity (Prefix (N)));
8246 -- Case where type is not known to be tagged. Its appearance in
8247 -- the prefix of the 'Class attribute indicates that the full view
8248 -- will be tagged.
8250 if not Is_Tagged_Type (T) then
8251 if Ekind (T) = E_Incomplete_Type then
8253 -- It is legal to denote the class type of an incomplete
8254 -- type. The full type will have to be tagged, of course.
8255 -- In Ada 2005 this usage is declared obsolescent, so we
8256 -- warn accordingly. This usage is only legal if the type
8257 -- is completed in the current scope, and not for a limited
8258 -- view of a type.
8260 if Ada_Version >= Ada_2005 then
8262 -- Test whether the Available_View of a limited type view
8263 -- is tagged, since the limited view may not be marked as
8264 -- tagged if the type itself has an untagged incomplete
8265 -- type view in its package.
8267 if From_Limited_With (T)
8268 and then not Is_Tagged_Type (Available_View (T))
8269 then
8270 Error_Msg_N
8271 ("prefix of Class attribute must be tagged", N);
8272 Set_Etype (N, Any_Type);
8273 Set_Entity (N, Any_Type);
8274 return;
8276 else
8277 if Restriction_Check_Required (No_Obsolescent_Features)
8278 then
8279 Check_Restriction
8280 (No_Obsolescent_Features, Prefix (N));
8281 end if;
8283 if Warn_On_Obsolescent_Feature then
8284 Error_Msg_N
8285 ("applying ''Class to an untagged incomplete type"
8286 & " is an obsolescent feature (RM J.11)?r?", N);
8287 end if;
8288 end if;
8289 end if;
8291 Set_Is_Tagged_Type (T);
8292 Set_Direct_Primitive_Operations (T, New_Elmt_List);
8293 Make_Class_Wide_Type (T);
8294 Set_Entity (N, Class_Wide_Type (T));
8295 Set_Etype (N, Class_Wide_Type (T));
8297 elsif Ekind (T) = E_Private_Type
8298 and then not Is_Generic_Type (T)
8299 and then In_Private_Part (Scope (T))
8300 then
8301 -- The Class attribute can be applied to an untagged private
8302 -- type fulfilled by a tagged type prior to the full type
8303 -- declaration (but only within the parent package's private
8304 -- part). Create the class-wide type now and check that the
8305 -- full type is tagged later during its analysis. Note that
8306 -- we do not mark the private type as tagged, unlike the
8307 -- case of incomplete types, because the type must still
8308 -- appear untagged to outside units.
8310 if No (Class_Wide_Type (T)) then
8311 Make_Class_Wide_Type (T);
8312 end if;
8314 Set_Entity (N, Class_Wide_Type (T));
8315 Set_Etype (N, Class_Wide_Type (T));
8317 else
8318 -- Should we introduce a type Any_Tagged and use Wrong_Type
8319 -- here, it would be a bit more consistent???
8321 Error_Msg_NE
8322 ("tagged type required, found}",
8323 Prefix (N), First_Subtype (T));
8324 Set_Entity (N, Any_Type);
8325 return;
8326 end if;
8328 -- Case of tagged type
8330 else
8331 if Is_Concurrent_Type (T) then
8332 if No (Corresponding_Record_Type (Entity (Prefix (N)))) then
8334 -- Previous error. Create a class-wide type for the
8335 -- synchronized type itself, with minimal semantic
8336 -- attributes, to catch other errors in some ACATS tests.
8338 pragma Assert (Serious_Errors_Detected /= 0);
8339 Make_Class_Wide_Type (T);
8340 C := Class_Wide_Type (T);
8341 Set_First_Entity (C, First_Entity (T));
8343 else
8344 C := Class_Wide_Type
8345 (Corresponding_Record_Type (Entity (Prefix (N))));
8346 end if;
8348 else
8349 C := Class_Wide_Type (Entity (Prefix (N)));
8350 end if;
8352 Set_Entity_With_Checks (N, C);
8353 Generate_Reference (C, N);
8354 Set_Etype (N, C);
8355 end if;
8357 -- Base attribute, not allowed in Ada 83
8359 elsif Attribute_Name (N) = Name_Base then
8360 if Ada_Version = Ada_83 and then Comes_From_Source (N) then
8361 Error_Msg_N
8362 ("(Ada 83) Base attribute not allowed in subtype mark", N);
8364 else
8365 Find_Type (Prefix (N));
8366 Typ := Entity (Prefix (N));
8368 if Ada_Version >= Ada_95
8369 and then not Is_Scalar_Type (Typ)
8370 and then not Is_Generic_Type (Typ)
8371 then
8372 Error_Msg_N
8373 ("prefix of Base attribute must be scalar type",
8374 Prefix (N));
8376 elsif Warn_On_Redundant_Constructs
8377 and then Base_Type (Typ) = Typ
8378 then
8379 Error_Msg_NE -- CODEFIX
8380 ("redundant attribute, & is its own base type?r?", N, Typ);
8381 end if;
8383 T := Base_Type (Typ);
8385 -- Rewrite attribute reference with type itself (see similar
8386 -- processing in Analyze_Attribute, case Base). Preserve prefix
8387 -- if present, for other legality checks.
8389 if Nkind (Prefix (N)) = N_Expanded_Name then
8390 Rewrite (N,
8391 Make_Expanded_Name (Sloc (N),
8392 Chars => Chars (T),
8393 Prefix => New_Copy (Prefix (Prefix (N))),
8394 Selector_Name => New_Occurrence_Of (T, Sloc (N))));
8396 else
8397 Rewrite (N, New_Occurrence_Of (T, Sloc (N)));
8398 end if;
8400 Set_Entity (N, T);
8401 Set_Etype (N, T);
8402 end if;
8404 elsif Attribute_Name (N) = Name_Stub_Type then
8406 -- This is handled in Analyze_Attribute
8408 Analyze (N);
8410 -- All other attributes are invalid in a subtype mark
8412 else
8413 Error_Msg_N ("invalid attribute in subtype mark", N);
8414 end if;
8416 else
8417 Analyze (N);
8419 if Is_Entity_Name (N) then
8420 T_Name := Entity (N);
8421 else
8422 Error_Msg_N ("subtype mark required in this context", N);
8423 Set_Etype (N, Any_Type);
8424 return;
8425 end if;
8427 if T_Name = Any_Id or else Etype (N) = Any_Type then
8429 -- Undefined id. Make it into a valid type
8431 Set_Entity (N, Any_Type);
8433 elsif not Is_Type (T_Name)
8434 and then T_Name /= Standard_Void_Type
8435 then
8436 Error_Msg_Sloc := Sloc (T_Name);
8437 Error_Msg_N ("subtype mark required in this context", N);
8438 Error_Msg_NE ("\\found & declared#", N, T_Name);
8439 Set_Entity (N, Any_Type);
8441 else
8442 -- If the type is an incomplete type created to handle
8443 -- anonymous access components of a record type, then the
8444 -- incomplete type is the visible entity and subsequent
8445 -- references will point to it. Mark the original full
8446 -- type as referenced, to prevent spurious warnings.
8448 if Is_Incomplete_Type (T_Name)
8449 and then Present (Full_View (T_Name))
8450 and then not Comes_From_Source (T_Name)
8451 then
8452 Set_Referenced (Full_View (T_Name));
8453 end if;
8455 T_Name := Get_Full_View (T_Name);
8457 -- Ada 2005 (AI-251, AI-50217): Handle interfaces visible through
8458 -- limited-with clauses
8460 if From_Limited_With (T_Name)
8461 and then Is_Incomplete_Type (T_Name)
8462 and then Present (Non_Limited_View (T_Name))
8463 and then Is_Interface (Non_Limited_View (T_Name))
8464 then
8465 T_Name := Non_Limited_View (T_Name);
8466 end if;
8468 if In_Open_Scopes (T_Name) then
8469 if Ekind (Base_Type (T_Name)) = E_Task_Type then
8471 -- In Ada 2005, a task name can be used in an access
8472 -- definition within its own body.
8474 if Ada_Version >= Ada_2005
8475 and then Nkind (Parent (N)) = N_Access_Definition
8476 then
8477 Set_Entity (N, T_Name);
8478 Set_Etype (N, T_Name);
8479 return;
8481 else
8482 Error_Msg_N
8483 ("task type cannot be used as type mark " &
8484 "within its own spec or body", N);
8485 end if;
8487 elsif Ekind (Base_Type (T_Name)) = E_Protected_Type then
8489 -- In Ada 2005, a protected name can be used in an access
8490 -- definition within its own body.
8492 if Ada_Version >= Ada_2005
8493 and then Nkind (Parent (N)) = N_Access_Definition
8494 then
8495 Set_Entity (N, T_Name);
8496 Set_Etype (N, T_Name);
8497 return;
8499 else
8500 Error_Msg_N
8501 ("protected type cannot be used as type mark " &
8502 "within its own spec or body", N);
8503 end if;
8505 else
8506 Error_Msg_N ("type declaration cannot refer to itself", N);
8507 end if;
8509 Set_Etype (N, Any_Type);
8510 Set_Entity (N, Any_Type);
8511 Set_Error_Posted (T_Name);
8512 return;
8513 end if;
8515 Set_Entity (N, T_Name);
8516 Set_Etype (N, T_Name);
8517 end if;
8518 end if;
8520 if Present (Etype (N)) and then Comes_From_Source (N) then
8521 if Is_Fixed_Point_Type (Etype (N)) then
8522 Check_Restriction (No_Fixed_Point, N);
8523 elsif Is_Floating_Point_Type (Etype (N)) then
8524 Check_Restriction (No_Floating_Point, N);
8525 end if;
8527 -- A Ghost type must appear in a specific context
8529 if Is_Ghost_Entity (Etype (N)) then
8530 Check_Ghost_Context (Etype (N), N);
8531 end if;
8532 end if;
8533 end Find_Type;
8535 --------------------
8536 -- Has_Components --
8537 --------------------
8539 function Has_Components (Typ : Entity_Id) return Boolean is
8540 begin
8541 return Is_Record_Type (Typ)
8542 or else (Is_Private_Type (Typ) and then Has_Discriminants (Typ))
8543 or else (Is_Task_Type (Typ) and then Has_Discriminants (Typ))
8544 or else (Is_Incomplete_Type (Typ)
8545 and then From_Limited_With (Typ)
8546 and then Is_Record_Type (Available_View (Typ)));
8547 end Has_Components;
8549 ------------------------------------
8550 -- Has_Implicit_Character_Literal --
8551 ------------------------------------
8553 function Has_Implicit_Character_Literal (N : Node_Id) return Boolean is
8554 Id : Entity_Id;
8555 Found : Boolean := False;
8556 P : constant Entity_Id := Entity (Prefix (N));
8557 Priv_Id : Entity_Id := Empty;
8559 begin
8560 if Ekind (P) = E_Package and then not In_Open_Scopes (P) then
8561 Priv_Id := First_Private_Entity (P);
8562 end if;
8564 if P = Standard_Standard then
8565 Change_Selected_Component_To_Expanded_Name (N);
8566 Rewrite (N, Selector_Name (N));
8567 Analyze (N);
8568 Set_Etype (Original_Node (N), Standard_Character);
8569 return True;
8570 end if;
8572 Id := First_Entity (P);
8573 while Present (Id) and then Id /= Priv_Id loop
8574 if Is_Standard_Character_Type (Id) and then Is_Base_Type (Id) then
8576 -- We replace the node with the literal itself, resolve as a
8577 -- character, and set the type correctly.
8579 if not Found then
8580 Change_Selected_Component_To_Expanded_Name (N);
8581 Rewrite (N, Selector_Name (N));
8582 Analyze (N);
8583 Set_Etype (N, Id);
8584 Set_Etype (Original_Node (N), Id);
8585 Found := True;
8587 else
8588 -- More than one type derived from Character in given scope.
8589 -- Collect all possible interpretations.
8591 Add_One_Interp (N, Id, Id);
8592 end if;
8593 end if;
8595 Next_Entity (Id);
8596 end loop;
8598 return Found;
8599 end Has_Implicit_Character_Literal;
8601 ----------------------
8602 -- Has_Private_With --
8603 ----------------------
8605 function Has_Private_With (E : Entity_Id) return Boolean is
8606 Comp_Unit : constant Node_Id := Cunit (Current_Sem_Unit);
8607 Item : Node_Id;
8609 begin
8610 Item := First (Context_Items (Comp_Unit));
8611 while Present (Item) loop
8612 if Nkind (Item) = N_With_Clause
8613 and then Private_Present (Item)
8614 and then Entity (Name (Item)) = E
8615 then
8616 return True;
8617 end if;
8619 Next (Item);
8620 end loop;
8622 return False;
8623 end Has_Private_With;
8625 ---------------------------
8626 -- Has_Implicit_Operator --
8627 ---------------------------
8629 function Has_Implicit_Operator (N : Node_Id) return Boolean is
8630 Op_Id : constant Name_Id := Chars (Selector_Name (N));
8631 P : constant Entity_Id := Entity (Prefix (N));
8632 Id : Entity_Id;
8633 Priv_Id : Entity_Id := Empty;
8635 procedure Add_Implicit_Operator
8636 (T : Entity_Id;
8637 Op_Type : Entity_Id := Empty);
8638 -- Add implicit interpretation to node N, using the type for which a
8639 -- predefined operator exists. If the operator yields a boolean type,
8640 -- the Operand_Type is implicitly referenced by the operator, and a
8641 -- reference to it must be generated.
8643 ---------------------------
8644 -- Add_Implicit_Operator --
8645 ---------------------------
8647 procedure Add_Implicit_Operator
8648 (T : Entity_Id;
8649 Op_Type : Entity_Id := Empty)
8651 Predef_Op : Entity_Id;
8653 begin
8654 Predef_Op := Current_Entity (Selector_Name (N));
8655 while Present (Predef_Op)
8656 and then Scope (Predef_Op) /= Standard_Standard
8657 loop
8658 Predef_Op := Homonym (Predef_Op);
8659 end loop;
8661 if Nkind (N) = N_Selected_Component then
8662 Change_Selected_Component_To_Expanded_Name (N);
8663 end if;
8665 -- If the context is an unanalyzed function call, determine whether
8666 -- a binary or unary interpretation is required.
8668 if Nkind (Parent (N)) = N_Indexed_Component then
8669 declare
8670 Is_Binary_Call : constant Boolean :=
8671 Present
8672 (Next (First (Expressions (Parent (N)))));
8673 Is_Binary_Op : constant Boolean :=
8674 First_Entity
8675 (Predef_Op) /= Last_Entity (Predef_Op);
8676 Predef_Op2 : constant Entity_Id := Homonym (Predef_Op);
8678 begin
8679 if Is_Binary_Call then
8680 if Is_Binary_Op then
8681 Add_One_Interp (N, Predef_Op, T);
8682 else
8683 Add_One_Interp (N, Predef_Op2, T);
8684 end if;
8685 else
8686 if not Is_Binary_Op then
8687 Add_One_Interp (N, Predef_Op, T);
8689 -- Predef_Op2 may be empty in case of previous errors
8691 elsif Present (Predef_Op2) then
8692 Add_One_Interp (N, Predef_Op2, T);
8693 end if;
8694 end if;
8695 end;
8697 else
8698 Add_One_Interp (N, Predef_Op, T);
8700 -- For operators with unary and binary interpretations, if
8701 -- context is not a call, add both
8703 if Present (Homonym (Predef_Op)) then
8704 Add_One_Interp (N, Homonym (Predef_Op), T);
8705 end if;
8706 end if;
8708 -- The node is a reference to a predefined operator, and
8709 -- an implicit reference to the type of its operands.
8711 if Present (Op_Type) then
8712 Generate_Operator_Reference (N, Op_Type);
8713 else
8714 Generate_Operator_Reference (N, T);
8715 end if;
8716 end Add_Implicit_Operator;
8718 -- Start of processing for Has_Implicit_Operator
8720 begin
8721 if Ekind (P) = E_Package and then not In_Open_Scopes (P) then
8722 Priv_Id := First_Private_Entity (P);
8723 end if;
8725 Id := First_Entity (P);
8727 case Op_Id is
8729 -- Boolean operators: an implicit declaration exists if the scope
8730 -- contains a declaration for a derived Boolean type, or for an
8731 -- array of Boolean type.
8733 when Name_Op_And
8734 | Name_Op_Not
8735 | Name_Op_Or
8736 | Name_Op_Xor
8738 while Id /= Priv_Id loop
8739 if Is_Type (Id)
8740 and then Valid_Boolean_Arg (Id)
8741 and then Is_Base_Type (Id)
8742 then
8743 Add_Implicit_Operator (Id);
8744 return True;
8745 end if;
8747 Next_Entity (Id);
8748 end loop;
8750 -- Equality: look for any non-limited type (result is Boolean)
8752 when Name_Op_Eq
8753 | Name_Op_Ne
8755 while Id /= Priv_Id loop
8756 if Is_Type (Id)
8757 and then Valid_Equality_Arg (Id)
8758 and then Is_Base_Type (Id)
8759 then
8760 Add_Implicit_Operator (Standard_Boolean, Id);
8761 return True;
8762 end if;
8764 Next_Entity (Id);
8765 end loop;
8767 -- Comparison operators: scalar type, or array of scalar
8769 when Name_Op_Ge
8770 | Name_Op_Gt
8771 | Name_Op_Le
8772 | Name_Op_Lt
8774 while Id /= Priv_Id loop
8775 if Is_Type (Id)
8776 and then Valid_Comparison_Arg (Id)
8777 and then Is_Base_Type (Id)
8778 then
8779 Add_Implicit_Operator (Standard_Boolean, Id);
8780 return True;
8781 end if;
8783 Next_Entity (Id);
8784 end loop;
8786 -- Arithmetic operators: any numeric type
8788 when Name_Op_Abs
8789 | Name_Op_Add
8790 | Name_Op_Divide
8791 | Name_Op_Expon
8792 | Name_Op_Mod
8793 | Name_Op_Multiply
8794 | Name_Op_Rem
8795 | Name_Op_Subtract
8797 while Id /= Priv_Id loop
8798 if Is_Numeric_Type (Id) and then Is_Base_Type (Id) then
8799 Add_Implicit_Operator (Id);
8800 return True;
8801 end if;
8803 Next_Entity (Id);
8804 end loop;
8806 -- Concatenation: any one-dimensional array type
8808 when Name_Op_Concat =>
8809 while Id /= Priv_Id loop
8810 if Is_Array_Type (Id)
8811 and then Number_Dimensions (Id) = 1
8812 and then Is_Base_Type (Id)
8813 then
8814 Add_Implicit_Operator (Id);
8815 return True;
8816 end if;
8818 Next_Entity (Id);
8819 end loop;
8821 -- What is the others condition here? Should we be using a
8822 -- subtype of Name_Id that would restrict to operators ???
8824 when others =>
8825 null;
8826 end case;
8828 -- If we fall through, then we do not have an implicit operator
8830 return False;
8831 end Has_Implicit_Operator;
8833 -----------------------------------
8834 -- Has_Loop_In_Inner_Open_Scopes --
8835 -----------------------------------
8837 function Has_Loop_In_Inner_Open_Scopes (S : Entity_Id) return Boolean is
8838 begin
8839 -- Several scope stacks are maintained by Scope_Stack. The base of the
8840 -- currently active scope stack is denoted by the Is_Active_Stack_Base
8841 -- flag in the scope stack entry. Note that the scope stacks used to
8842 -- simply be delimited implicitly by the presence of Standard_Standard
8843 -- at their base, but there now are cases where this is not sufficient
8844 -- because Standard_Standard actually may appear in the middle of the
8845 -- active set of scopes.
8847 for J in reverse 0 .. Scope_Stack.Last loop
8849 -- S was reached without seing a loop scope first
8851 if Scope_Stack.Table (J).Entity = S then
8852 return False;
8854 -- S was not yet reached, so it contains at least one inner loop
8856 elsif Ekind (Scope_Stack.Table (J).Entity) = E_Loop then
8857 return True;
8858 end if;
8860 -- Check Is_Active_Stack_Base to tell us when to stop, as there are
8861 -- cases where Standard_Standard appears in the middle of the active
8862 -- set of scopes. This affects the declaration and overriding of
8863 -- private inherited operations in instantiations of generic child
8864 -- units.
8866 pragma Assert (not Scope_Stack.Table (J).Is_Active_Stack_Base);
8867 end loop;
8869 raise Program_Error; -- unreachable
8870 end Has_Loop_In_Inner_Open_Scopes;
8872 --------------------
8873 -- In_Open_Scopes --
8874 --------------------
8876 function In_Open_Scopes (S : Entity_Id) return Boolean is
8877 begin
8878 -- Several scope stacks are maintained by Scope_Stack. The base of the
8879 -- currently active scope stack is denoted by the Is_Active_Stack_Base
8880 -- flag in the scope stack entry. Note that the scope stacks used to
8881 -- simply be delimited implicitly by the presence of Standard_Standard
8882 -- at their base, but there now are cases where this is not sufficient
8883 -- because Standard_Standard actually may appear in the middle of the
8884 -- active set of scopes.
8886 for J in reverse 0 .. Scope_Stack.Last loop
8887 if Scope_Stack.Table (J).Entity = S then
8888 return True;
8889 end if;
8891 -- Check Is_Active_Stack_Base to tell us when to stop, as there are
8892 -- cases where Standard_Standard appears in the middle of the active
8893 -- set of scopes. This affects the declaration and overriding of
8894 -- private inherited operations in instantiations of generic child
8895 -- units.
8897 exit when Scope_Stack.Table (J).Is_Active_Stack_Base;
8898 end loop;
8900 return False;
8901 end In_Open_Scopes;
8903 -----------------------------
8904 -- Inherit_Renamed_Profile --
8905 -----------------------------
8907 procedure Inherit_Renamed_Profile (New_S : Entity_Id; Old_S : Entity_Id) is
8908 New_F : Entity_Id;
8909 Old_F : Entity_Id;
8910 Old_T : Entity_Id;
8911 New_T : Entity_Id;
8913 begin
8914 if Ekind (Old_S) = E_Operator then
8915 New_F := First_Formal (New_S);
8917 while Present (New_F) loop
8918 Set_Etype (New_F, Base_Type (Etype (New_F)));
8919 Next_Formal (New_F);
8920 end loop;
8922 Set_Etype (New_S, Base_Type (Etype (New_S)));
8924 else
8925 New_F := First_Formal (New_S);
8926 Old_F := First_Formal (Old_S);
8928 while Present (New_F) loop
8929 New_T := Etype (New_F);
8930 Old_T := Etype (Old_F);
8932 -- If the new type is a renaming of the old one, as is the case
8933 -- for actuals in instances, retain its name, to simplify later
8934 -- disambiguation.
8936 if Nkind (Parent (New_T)) = N_Subtype_Declaration
8937 and then Is_Entity_Name (Subtype_Indication (Parent (New_T)))
8938 and then Entity (Subtype_Indication (Parent (New_T))) = Old_T
8939 then
8940 null;
8941 else
8942 Set_Etype (New_F, Old_T);
8943 end if;
8945 Next_Formal (New_F);
8946 Next_Formal (Old_F);
8947 end loop;
8949 pragma Assert (No (Old_F));
8951 if Ekind (Old_S) in E_Function | E_Enumeration_Literal then
8952 Set_Etype (New_S, Etype (Old_S));
8953 end if;
8954 end if;
8955 end Inherit_Renamed_Profile;
8957 ----------------
8958 -- Initialize --
8959 ----------------
8961 procedure Initialize is
8962 begin
8963 Urefs.Init;
8964 end Initialize;
8966 -------------------------
8967 -- Install_Use_Clauses --
8968 -------------------------
8970 procedure Install_Use_Clauses
8971 (Clause : Node_Id;
8972 Force_Installation : Boolean := False)
8974 U : Node_Id;
8976 begin
8977 U := Clause;
8978 while Present (U) loop
8980 -- Case of USE package
8982 if Nkind (U) = N_Use_Package_Clause then
8983 Use_One_Package (U, Name (U), True);
8985 -- Case of USE TYPE
8987 else
8988 Use_One_Type (Subtype_Mark (U), Force => Force_Installation);
8990 end if;
8992 Next_Use_Clause (U);
8993 end loop;
8994 end Install_Use_Clauses;
8996 ----------------------
8997 -- Mark_Use_Clauses --
8998 ----------------------
9000 procedure Mark_Use_Clauses (Id : Node_Or_Entity_Id) is
9001 procedure Mark_Parameters (Call : Entity_Id);
9002 -- Perform use_type_clause marking for all parameters in a subprogram
9003 -- or operator call.
9005 procedure Mark_Use_Package (Pak : Entity_Id);
9006 -- Move up the Prev_Use_Clause chain for packages denoted by Pak -
9007 -- marking each clause in the chain as effective in the process.
9009 procedure Mark_Use_Type (E : Entity_Id);
9010 -- Similar to Do_Use_Package_Marking except we move up the
9011 -- Prev_Use_Clause chain for the type denoted by E.
9013 ---------------------
9014 -- Mark_Parameters --
9015 ---------------------
9017 procedure Mark_Parameters (Call : Entity_Id) is
9018 Curr : Node_Id;
9020 begin
9021 -- Move through all of the formals
9023 Curr := First_Formal (Call);
9024 while Present (Curr) loop
9025 Mark_Use_Type (Curr);
9027 Next_Formal (Curr);
9028 end loop;
9030 -- Handle the return type
9032 Mark_Use_Type (Call);
9033 end Mark_Parameters;
9035 ----------------------
9036 -- Mark_Use_Package --
9037 ----------------------
9039 procedure Mark_Use_Package (Pak : Entity_Id) is
9040 Curr : Node_Id;
9042 begin
9043 -- Ignore cases where the scope of the type is not a package (e.g.
9044 -- Standard_Standard).
9046 if Ekind (Pak) /= E_Package then
9047 return;
9048 end if;
9050 Curr := Current_Use_Clause (Pak);
9051 while Present (Curr)
9052 and then not Is_Effective_Use_Clause (Curr)
9053 loop
9054 -- We need to mark the previous use clauses as effective, but
9055 -- each use clause may in turn render other use_package_clauses
9056 -- effective. Additionally, it is possible to have a parent
9057 -- package renamed as a child of itself so we must check the
9058 -- prefix entity is not the same as the package we are marking.
9060 if Nkind (Name (Curr)) /= N_Identifier
9061 and then Present (Prefix (Name (Curr)))
9062 and then Entity (Prefix (Name (Curr))) /= Pak
9063 then
9064 Mark_Use_Package (Entity (Prefix (Name (Curr))));
9066 -- It is also possible to have a child package without a prefix
9067 -- that relies on a previous use_package_clause.
9069 elsif Nkind (Name (Curr)) = N_Identifier
9070 and then Is_Child_Unit (Entity (Name (Curr)))
9071 then
9072 Mark_Use_Package (Scope (Entity (Name (Curr))));
9073 end if;
9075 -- Mark the use_package_clause as effective and move up the chain
9077 Set_Is_Effective_Use_Clause (Curr);
9079 Curr := Prev_Use_Clause (Curr);
9080 end loop;
9081 end Mark_Use_Package;
9083 -------------------
9084 -- Mark_Use_Type --
9085 -------------------
9087 procedure Mark_Use_Type (E : Entity_Id) is
9088 Curr : Node_Id;
9089 Base : Entity_Id;
9091 begin
9092 -- Ignore void types and unresolved string literals and primitives
9094 if Nkind (E) = N_String_Literal
9095 or else Nkind (Etype (E)) not in N_Entity
9096 or else not Is_Type (Etype (E))
9097 then
9098 return;
9099 end if;
9101 -- Primitives with class-wide operands might additionally render
9102 -- their base type's use_clauses effective - so do a recursive check
9103 -- here.
9105 Base := Base_Type (Etype (E));
9107 if Ekind (Base) = E_Class_Wide_Type then
9108 Mark_Use_Type (Base);
9109 end if;
9111 -- The package containing the type or operator function being used
9112 -- may be in use as well, so mark any use_package_clauses for it as
9113 -- effective. There are also additional sanity checks performed here
9114 -- for ignoring previous errors.
9116 Mark_Use_Package (Scope (Base));
9118 if Nkind (E) in N_Op
9119 and then Present (Entity (E))
9120 and then Present (Scope (Entity (E)))
9121 then
9122 Mark_Use_Package (Scope (Entity (E)));
9123 end if;
9125 Curr := Current_Use_Clause (Base);
9126 while Present (Curr)
9127 and then not Is_Effective_Use_Clause (Curr)
9128 loop
9129 -- Current use_type_clause may render other use_package_clauses
9130 -- effective.
9132 if Nkind (Subtype_Mark (Curr)) /= N_Identifier
9133 and then Present (Prefix (Subtype_Mark (Curr)))
9134 then
9135 Mark_Use_Package (Entity (Prefix (Subtype_Mark (Curr))));
9136 end if;
9138 -- Mark the use_type_clause as effective and move up the chain
9140 Set_Is_Effective_Use_Clause (Curr);
9142 Curr := Prev_Use_Clause (Curr);
9143 end loop;
9144 end Mark_Use_Type;
9146 -- Start of processing for Mark_Use_Clauses
9148 begin
9149 -- Use clauses in and of themselves do not count as a "use" of a
9150 -- package.
9152 if Nkind (Parent (Id)) in N_Use_Package_Clause | N_Use_Type_Clause then
9153 return;
9154 end if;
9156 -- Handle entities
9158 if Nkind (Id) in N_Entity then
9160 -- Mark the entity's package
9162 if Is_Potentially_Use_Visible (Id) then
9163 Mark_Use_Package (Scope (Id));
9164 end if;
9166 -- Mark enumeration literals
9168 if Ekind (Id) = E_Enumeration_Literal then
9169 Mark_Use_Type (Id);
9171 -- Mark primitives
9173 elsif (Is_Overloadable (Id)
9174 or else Is_Generic_Subprogram (Id))
9175 and then (Is_Potentially_Use_Visible (Id)
9176 or else Is_Intrinsic_Subprogram (Id)
9177 or else (Ekind (Id) in E_Function | E_Procedure
9178 and then Is_Generic_Actual_Subprogram (Id)))
9179 then
9180 Mark_Parameters (Id);
9181 end if;
9183 -- Handle nodes
9185 else
9186 -- Mark operators
9188 if Nkind (Id) in N_Op then
9190 -- At this point the left operand may not be resolved if we are
9191 -- encountering multiple operators next to eachother in an
9192 -- expression.
9194 if Nkind (Id) in N_Binary_Op
9195 and then not (Nkind (Left_Opnd (Id)) in N_Op)
9196 then
9197 Mark_Use_Type (Left_Opnd (Id));
9198 end if;
9200 Mark_Use_Type (Right_Opnd (Id));
9201 Mark_Use_Type (Id);
9203 -- Mark entity identifiers
9205 elsif Nkind (Id) in N_Has_Entity
9206 and then (Is_Potentially_Use_Visible (Entity (Id))
9207 or else (Is_Generic_Instance (Entity (Id))
9208 and then Is_Immediately_Visible (Entity (Id))))
9209 then
9210 -- Ignore fully qualified names as they do not count as a "use" of
9211 -- a package.
9213 if Nkind (Id) in N_Identifier | N_Operator_Symbol
9214 or else (Present (Prefix (Id))
9215 and then Scope (Entity (Id)) /= Entity (Prefix (Id)))
9216 then
9217 Mark_Use_Clauses (Entity (Id));
9218 end if;
9219 end if;
9220 end if;
9221 end Mark_Use_Clauses;
9223 --------------------------------
9224 -- Most_Descendant_Use_Clause --
9225 --------------------------------
9227 function Most_Descendant_Use_Clause
9228 (Clause1 : Entity_Id;
9229 Clause2 : Entity_Id) return Entity_Id
9231 function Determine_Package_Scope (Clause : Node_Id) return Entity_Id;
9232 -- Given a use clause, determine which package it belongs to
9234 -----------------------------
9235 -- Determine_Package_Scope --
9236 -----------------------------
9238 function Determine_Package_Scope (Clause : Node_Id) return Entity_Id is
9239 begin
9240 -- Check if the clause appears in the context area
9242 -- Note we cannot employ Enclosing_Packge for use clauses within
9243 -- context clauses since they are not actually "enclosed."
9245 if Nkind (Parent (Clause)) = N_Compilation_Unit then
9246 return Entity_Of_Unit (Unit (Parent (Clause)));
9247 end if;
9249 -- Otherwise, obtain the enclosing package normally
9251 return Enclosing_Package (Clause);
9252 end Determine_Package_Scope;
9254 Scope1 : Entity_Id;
9255 Scope2 : Entity_Id;
9257 -- Start of processing for Most_Descendant_Use_Clause
9259 begin
9260 if Clause1 = Clause2 then
9261 return Clause1;
9262 end if;
9264 -- We determine which one is the most descendant by the scope distance
9265 -- to the ultimate parent unit.
9267 Scope1 := Determine_Package_Scope (Clause1);
9268 Scope2 := Determine_Package_Scope (Clause2);
9269 while Scope1 /= Standard_Standard
9270 and then Scope2 /= Standard_Standard
9271 loop
9272 Scope1 := Scope (Scope1);
9273 Scope2 := Scope (Scope2);
9275 if not Present (Scope1) then
9276 return Clause1;
9277 elsif not Present (Scope2) then
9278 return Clause2;
9279 end if;
9280 end loop;
9282 if Scope1 = Standard_Standard then
9283 return Clause1;
9284 end if;
9286 return Clause2;
9287 end Most_Descendant_Use_Clause;
9289 ---------------
9290 -- Pop_Scope --
9291 ---------------
9293 procedure Pop_Scope is
9294 SST : Scope_Stack_Entry renames Scope_Stack.Table (Scope_Stack.Last);
9295 S : constant Entity_Id := SST.Entity;
9297 begin
9298 if Debug_Flag_E then
9299 Write_Info;
9300 end if;
9302 -- Set Default_Storage_Pool field of the library unit if necessary
9304 if Is_Package_Or_Generic_Package (S)
9305 and then
9306 Nkind (Parent (Unit_Declaration_Node (S))) = N_Compilation_Unit
9307 then
9308 declare
9309 Aux : constant Node_Id :=
9310 Aux_Decls_Node (Parent (Unit_Declaration_Node (S)));
9311 begin
9312 if No (Default_Storage_Pool (Aux)) then
9313 Set_Default_Storage_Pool (Aux, Default_Pool);
9314 end if;
9315 end;
9316 end if;
9318 Scope_Suppress := SST.Save_Scope_Suppress;
9319 Local_Suppress_Stack_Top := SST.Save_Local_Suppress_Stack_Top;
9320 Check_Policy_List := SST.Save_Check_Policy_List;
9321 Default_Pool := SST.Save_Default_Storage_Pool;
9322 No_Tagged_Streams := SST.Save_No_Tagged_Streams;
9323 SPARK_Mode := SST.Save_SPARK_Mode;
9324 SPARK_Mode_Pragma := SST.Save_SPARK_Mode_Pragma;
9325 Default_SSO := SST.Save_Default_SSO;
9326 Uneval_Old := SST.Save_Uneval_Old;
9328 if Debug_Flag_W then
9329 Write_Str ("<-- exiting scope: ");
9330 Write_Name (Chars (Current_Scope));
9331 Write_Str (", Depth=");
9332 Write_Int (Int (Scope_Stack.Last));
9333 Write_Eol;
9334 end if;
9336 End_Use_Clauses (SST.First_Use_Clause);
9338 -- If the actions to be wrapped are still there they will get lost
9339 -- causing incomplete code to be generated. It is better to abort in
9340 -- this case (and we do the abort even with assertions off since the
9341 -- penalty is incorrect code generation).
9343 if SST.Actions_To_Be_Wrapped /= Scope_Actions'(others => No_List) then
9344 raise Program_Error;
9345 end if;
9347 -- Free last subprogram name if allocated, and pop scope
9349 Free (SST.Last_Subprogram_Name);
9350 Scope_Stack.Decrement_Last;
9351 end Pop_Scope;
9353 ----------------
9354 -- Push_Scope --
9355 ----------------
9357 procedure Push_Scope (S : Entity_Id) is
9358 E : constant Entity_Id := Scope (S);
9360 function Component_Alignment_Default return Component_Alignment_Kind;
9361 -- Return Component_Alignment_Kind for the newly-pushed scope.
9363 function Component_Alignment_Default return Component_Alignment_Kind is
9364 begin
9365 -- Each new scope pushed onto the scope stack inherits the component
9366 -- alignment of the previous scope. This emulates the "visibility"
9367 -- semantics of pragma Component_Alignment.
9369 if Scope_Stack.Last > Scope_Stack.First then
9370 return Scope_Stack.Table
9371 (Scope_Stack.Last - 1).Component_Alignment_Default;
9373 -- Otherwise, this is the first scope being pushed on the scope
9374 -- stack. Inherit the component alignment from the configuration
9375 -- form of pragma Component_Alignment (if any).
9377 else
9378 return Configuration_Component_Alignment;
9379 end if;
9380 end Component_Alignment_Default;
9382 begin
9383 if Ekind (S) = E_Void then
9384 null;
9386 -- Set scope depth if not a nonconcurrent type, and we have not yet set
9387 -- the scope depth. This means that we have the first occurrence of the
9388 -- scope, and this is where the depth is set.
9390 elsif (not Is_Type (S) or else Is_Concurrent_Type (S))
9391 and then not Scope_Depth_Set (S)
9392 then
9393 if S = Standard_Standard then
9394 Set_Scope_Depth_Value (S, Uint_0);
9396 elsif Is_Child_Unit (S) then
9397 Set_Scope_Depth_Value (S, Uint_1);
9399 elsif not Is_Record_Type (Current_Scope) then
9400 if Scope_Depth_Set (Current_Scope) then
9401 if Ekind (S) = E_Loop then
9402 Set_Scope_Depth_Value (S, Scope_Depth (Current_Scope));
9403 else
9404 Set_Scope_Depth_Value (S, Scope_Depth (Current_Scope) + 1);
9405 end if;
9406 end if;
9407 end if;
9408 end if;
9410 Scope_Stack.Increment_Last;
9412 Scope_Stack.Table (Scope_Stack.Last) :=
9413 (Entity => S,
9414 Save_Scope_Suppress => Scope_Suppress,
9415 Save_Local_Suppress_Stack_Top => Local_Suppress_Stack_Top,
9416 Save_Check_Policy_List => Check_Policy_List,
9417 Save_Default_Storage_Pool => Default_Pool,
9418 Save_No_Tagged_Streams => No_Tagged_Streams,
9419 Save_SPARK_Mode => SPARK_Mode,
9420 Save_SPARK_Mode_Pragma => SPARK_Mode_Pragma,
9421 Save_Default_SSO => Default_SSO,
9422 Save_Uneval_Old => Uneval_Old,
9423 Component_Alignment_Default => Component_Alignment_Default,
9424 Last_Subprogram_Name => null,
9425 Is_Transient => False,
9426 Node_To_Be_Wrapped => Empty,
9427 Pending_Freeze_Actions => No_List,
9428 Actions_To_Be_Wrapped => (others => No_List),
9429 First_Use_Clause => Empty,
9430 Is_Active_Stack_Base => False,
9431 Previous_Visibility => False,
9432 Locked_Shared_Objects => No_Elist);
9434 if Debug_Flag_W then
9435 Write_Str ("--> new scope: ");
9436 Write_Name (Chars (Current_Scope));
9437 Write_Str (", Id=");
9438 Write_Int (Int (Current_Scope));
9439 Write_Str (", Depth=");
9440 Write_Int (Int (Scope_Stack.Last));
9441 Write_Eol;
9442 end if;
9444 -- Deal with copying flags from the previous scope to this one. This is
9445 -- not necessary if either scope is standard, or if the new scope is a
9446 -- child unit.
9448 if S /= Standard_Standard
9449 and then Scope (S) /= Standard_Standard
9450 and then not Is_Child_Unit (S)
9451 then
9452 if Nkind (E) not in N_Entity then
9453 return;
9454 end if;
9456 -- Copy categorization flags from Scope (S) to S, this is not done
9457 -- when Scope (S) is Standard_Standard since propagation is from
9458 -- library unit entity inwards. Copy other relevant attributes as
9459 -- well (Discard_Names in particular).
9461 -- We only propagate inwards for library level entities,
9462 -- inner level subprograms do not inherit the categorization.
9464 if Is_Library_Level_Entity (S) then
9465 Set_Is_Preelaborated (S, Is_Preelaborated (E));
9466 Set_Is_Shared_Passive (S, Is_Shared_Passive (E));
9467 Set_Discard_Names (S, Discard_Names (E));
9468 Set_Suppress_Value_Tracking_On_Call
9469 (S, Suppress_Value_Tracking_On_Call (E));
9470 Set_Categorization_From_Scope (E => S, Scop => E);
9471 end if;
9472 end if;
9474 if Is_Child_Unit (S)
9475 and then Present (E)
9476 and then Is_Package_Or_Generic_Package (E)
9477 and then
9478 Nkind (Parent (Unit_Declaration_Node (E))) = N_Compilation_Unit
9479 then
9480 declare
9481 Aux : constant Node_Id :=
9482 Aux_Decls_Node (Parent (Unit_Declaration_Node (E)));
9483 begin
9484 if Present (Default_Storage_Pool (Aux)) then
9485 Default_Pool := Default_Storage_Pool (Aux);
9486 end if;
9487 end;
9488 end if;
9489 end Push_Scope;
9491 ---------------------
9492 -- Premature_Usage --
9493 ---------------------
9495 procedure Premature_Usage (N : Node_Id) is
9496 Kind : constant Node_Kind := Nkind (Parent (Entity (N)));
9497 E : Entity_Id := Entity (N);
9499 begin
9500 -- Within an instance, the analysis of the actual for a formal object
9501 -- does not see the name of the object itself. This is significant only
9502 -- if the object is an aggregate, where its analysis does not do any
9503 -- name resolution on component associations. (see 4717-008). In such a
9504 -- case, look for the visible homonym on the chain.
9506 if In_Instance and then Present (Homonym (E)) then
9507 E := Homonym (E);
9508 while Present (E) and then not In_Open_Scopes (Scope (E)) loop
9509 E := Homonym (E);
9510 end loop;
9512 if Present (E) then
9513 Set_Entity (N, E);
9514 Set_Etype (N, Etype (E));
9515 return;
9516 end if;
9517 end if;
9519 case Kind is
9520 when N_Component_Declaration =>
9521 Error_Msg_N
9522 ("component&! cannot be used before end of record declaration",
9525 when N_Parameter_Specification =>
9526 Error_Msg_N
9527 ("formal parameter&! cannot be used before end of specification",
9530 when N_Discriminant_Specification =>
9531 Error_Msg_N
9532 ("discriminant&! cannot be used before end of discriminant part",
9535 when N_Procedure_Specification | N_Function_Specification =>
9536 Error_Msg_N
9537 ("subprogram&! cannot be used before end of its declaration",
9540 when N_Full_Type_Declaration | N_Subtype_Declaration =>
9541 Error_Msg_N
9542 ("type& cannot be used before end of its declaration!", N);
9544 when others =>
9545 Error_Msg_N
9546 ("object& cannot be used before end of its declaration!", N);
9548 -- If the premature reference appears as the expression in its own
9549 -- declaration, rewrite it to prevent compiler loops in subsequent
9550 -- uses of this mangled declaration in address clauses.
9552 if Nkind (Parent (N)) = N_Object_Declaration then
9553 Set_Entity (N, Any_Id);
9554 end if;
9555 end case;
9556 end Premature_Usage;
9558 ------------------------
9559 -- Present_System_Aux --
9560 ------------------------
9562 function Present_System_Aux (N : Node_Id := Empty) return Boolean is
9563 Loc : Source_Ptr;
9564 Aux_Name : Unit_Name_Type;
9565 Unum : Unit_Number_Type;
9566 Withn : Node_Id;
9567 With_Sys : Node_Id;
9568 The_Unit : Node_Id;
9570 function Find_System (C_Unit : Node_Id) return Entity_Id;
9571 -- Scan context clause of compilation unit to find with_clause
9572 -- for System.
9574 -----------------
9575 -- Find_System --
9576 -----------------
9578 function Find_System (C_Unit : Node_Id) return Entity_Id is
9579 With_Clause : Node_Id;
9581 begin
9582 With_Clause := First (Context_Items (C_Unit));
9583 while Present (With_Clause) loop
9584 if (Nkind (With_Clause) = N_With_Clause
9585 and then Chars (Name (With_Clause)) = Name_System)
9586 and then Comes_From_Source (With_Clause)
9587 then
9588 return With_Clause;
9589 end if;
9591 Next (With_Clause);
9592 end loop;
9594 return Empty;
9595 end Find_System;
9597 -- Start of processing for Present_System_Aux
9599 begin
9600 -- The child unit may have been loaded and analyzed already
9602 if Present (System_Aux_Id) then
9603 return True;
9605 -- If no previous pragma for System.Aux, nothing to load
9607 elsif No (System_Extend_Unit) then
9608 return False;
9610 -- Use the unit name given in the pragma to retrieve the unit.
9611 -- Verify that System itself appears in the context clause of the
9612 -- current compilation. If System is not present, an error will
9613 -- have been reported already.
9615 else
9616 With_Sys := Find_System (Cunit (Current_Sem_Unit));
9618 The_Unit := Unit (Cunit (Current_Sem_Unit));
9620 if No (With_Sys)
9621 and then
9622 (Nkind (The_Unit) = N_Package_Body
9623 or else (Nkind (The_Unit) = N_Subprogram_Body
9624 and then not Acts_As_Spec (Cunit (Current_Sem_Unit))))
9625 then
9626 With_Sys := Find_System (Library_Unit (Cunit (Current_Sem_Unit)));
9627 end if;
9629 if No (With_Sys) and then Present (N) then
9631 -- If we are compiling a subunit, we need to examine its
9632 -- context as well (Current_Sem_Unit is the parent unit);
9634 The_Unit := Parent (N);
9635 while Nkind (The_Unit) /= N_Compilation_Unit loop
9636 The_Unit := Parent (The_Unit);
9637 end loop;
9639 if Nkind (Unit (The_Unit)) = N_Subunit then
9640 With_Sys := Find_System (The_Unit);
9641 end if;
9642 end if;
9644 if No (With_Sys) then
9645 return False;
9646 end if;
9648 Loc := Sloc (With_Sys);
9649 Get_Name_String (Chars (Expression (System_Extend_Unit)));
9650 Name_Buffer (8 .. Name_Len + 7) := Name_Buffer (1 .. Name_Len);
9651 Name_Buffer (1 .. 7) := "system.";
9652 Name_Buffer (Name_Len + 8) := '%';
9653 Name_Buffer (Name_Len + 9) := 's';
9654 Name_Len := Name_Len + 9;
9655 Aux_Name := Name_Find;
9657 Unum :=
9658 Load_Unit
9659 (Load_Name => Aux_Name,
9660 Required => False,
9661 Subunit => False,
9662 Error_Node => With_Sys);
9664 if Unum /= No_Unit then
9665 Semantics (Cunit (Unum));
9666 System_Aux_Id :=
9667 Defining_Entity (Specification (Unit (Cunit (Unum))));
9669 Withn :=
9670 Make_With_Clause (Loc,
9671 Name =>
9672 Make_Expanded_Name (Loc,
9673 Chars => Chars (System_Aux_Id),
9674 Prefix =>
9675 New_Occurrence_Of (Scope (System_Aux_Id), Loc),
9676 Selector_Name => New_Occurrence_Of (System_Aux_Id, Loc)));
9678 Set_Entity (Name (Withn), System_Aux_Id);
9680 Set_Corresponding_Spec (Withn, System_Aux_Id);
9681 Set_First_Name (Withn);
9682 Set_Implicit_With (Withn);
9683 Set_Library_Unit (Withn, Cunit (Unum));
9685 Insert_After (With_Sys, Withn);
9686 Mark_Rewrite_Insertion (Withn);
9687 Set_Context_Installed (Withn);
9689 return True;
9691 -- Here if unit load failed
9693 else
9694 Error_Msg_Name_1 := Name_System;
9695 Error_Msg_Name_2 := Chars (Expression (System_Extend_Unit));
9696 Error_Msg_N
9697 ("extension package `%.%` does not exist",
9698 Opt.System_Extend_Unit);
9699 return False;
9700 end if;
9701 end if;
9702 end Present_System_Aux;
9704 -------------------------
9705 -- Restore_Scope_Stack --
9706 -------------------------
9708 procedure Restore_Scope_Stack
9709 (List : Elist_Id;
9710 Handle_Use : Boolean := True)
9712 SS_Last : constant Int := Scope_Stack.Last;
9713 Elmt : Elmt_Id;
9715 begin
9716 -- Restore visibility of previous scope stack, if any, using the list
9717 -- we saved (we use Remove, since this list will not be used again).
9719 loop
9720 Elmt := Last_Elmt (List);
9721 exit when Elmt = No_Elmt;
9722 Set_Is_Immediately_Visible (Node (Elmt));
9723 Remove_Last_Elmt (List);
9724 end loop;
9726 -- Restore use clauses
9728 if SS_Last >= Scope_Stack.First
9729 and then Scope_Stack.Table (SS_Last).Entity /= Standard_Standard
9730 and then Handle_Use
9731 then
9732 Install_Use_Clauses
9733 (Scope_Stack.Table (SS_Last).First_Use_Clause,
9734 Force_Installation => True);
9735 end if;
9736 end Restore_Scope_Stack;
9738 ----------------------
9739 -- Save_Scope_Stack --
9740 ----------------------
9742 -- Save_Scope_Stack/Restore_Scope_Stack were originally designed to avoid
9743 -- consuming any memory. That is, Save_Scope_Stack took care of removing
9744 -- from immediate visibility entities and Restore_Scope_Stack took care
9745 -- of restoring their visibility analyzing the context of each entity. The
9746 -- problem of such approach is that it was fragile and caused unexpected
9747 -- visibility problems, and indeed one test was found where there was a
9748 -- real problem.
9750 -- Furthermore, the following experiment was carried out:
9752 -- - Save_Scope_Stack was modified to store in an Elist1 all those
9753 -- entities whose attribute Is_Immediately_Visible is modified
9754 -- from True to False.
9756 -- - Restore_Scope_Stack was modified to store in another Elist2
9757 -- all the entities whose attribute Is_Immediately_Visible is
9758 -- modified from False to True.
9760 -- - Extra code was added to verify that all the elements of Elist1
9761 -- are found in Elist2
9763 -- This test shows that there may be more occurrences of this problem which
9764 -- have not yet been detected. As a result, we replaced that approach by
9765 -- the current one in which Save_Scope_Stack returns the list of entities
9766 -- whose visibility is changed, and that list is passed to Restore_Scope_
9767 -- Stack to undo that change. This approach is simpler and safer, although
9768 -- it consumes more memory.
9770 function Save_Scope_Stack (Handle_Use : Boolean := True) return Elist_Id is
9771 Result : constant Elist_Id := New_Elmt_List;
9772 E : Entity_Id;
9773 S : Entity_Id;
9774 SS_Last : constant Int := Scope_Stack.Last;
9776 procedure Remove_From_Visibility (E : Entity_Id);
9777 -- If E is immediately visible then append it to the result and remove
9778 -- it temporarily from visibility.
9780 ----------------------------
9781 -- Remove_From_Visibility --
9782 ----------------------------
9784 procedure Remove_From_Visibility (E : Entity_Id) is
9785 begin
9786 if Is_Immediately_Visible (E) then
9787 Append_Elmt (E, Result);
9788 Set_Is_Immediately_Visible (E, False);
9789 end if;
9790 end Remove_From_Visibility;
9792 -- Start of processing for Save_Scope_Stack
9794 begin
9795 if SS_Last >= Scope_Stack.First
9796 and then Scope_Stack.Table (SS_Last).Entity /= Standard_Standard
9797 then
9798 if Handle_Use then
9799 End_Use_Clauses (Scope_Stack.Table (SS_Last).First_Use_Clause);
9800 end if;
9802 -- If the call is from within a compilation unit, as when called from
9803 -- Rtsfind, make current entries in scope stack invisible while we
9804 -- analyze the new unit.
9806 for J in reverse 0 .. SS_Last loop
9807 exit when Scope_Stack.Table (J).Entity = Standard_Standard
9808 or else No (Scope_Stack.Table (J).Entity);
9810 S := Scope_Stack.Table (J).Entity;
9812 Remove_From_Visibility (S);
9814 E := First_Entity (S);
9815 while Present (E) loop
9816 Remove_From_Visibility (E);
9817 Next_Entity (E);
9818 end loop;
9819 end loop;
9821 end if;
9823 return Result;
9824 end Save_Scope_Stack;
9826 -------------
9827 -- Set_Use --
9828 -------------
9830 procedure Set_Use (L : List_Id) is
9831 Decl : Node_Id;
9833 begin
9834 Decl := First (L);
9835 while Present (Decl) loop
9836 if Nkind (Decl) = N_Use_Package_Clause then
9837 Chain_Use_Clause (Decl);
9838 Use_One_Package (Decl, Name (Decl));
9840 elsif Nkind (Decl) = N_Use_Type_Clause then
9841 Chain_Use_Clause (Decl);
9842 Use_One_Type (Subtype_Mark (Decl));
9844 end if;
9846 Next (Decl);
9847 end loop;
9848 end Set_Use;
9850 -----------------------------
9851 -- Update_Use_Clause_Chain --
9852 -----------------------------
9854 procedure Update_Use_Clause_Chain is
9856 procedure Update_Chain_In_Scope (Level : Int);
9857 -- Iterate through one level in the scope stack verifying each use-type
9858 -- clause within said level is used then reset the Current_Use_Clause
9859 -- to a redundant use clause outside of the current ending scope if such
9860 -- a clause exists.
9862 ---------------------------
9863 -- Update_Chain_In_Scope --
9864 ---------------------------
9866 procedure Update_Chain_In_Scope (Level : Int) is
9867 Curr : Node_Id;
9868 N : Node_Id;
9870 begin
9871 -- Loop through all use clauses within the scope dictated by Level
9873 Curr := Scope_Stack.Table (Level).First_Use_Clause;
9874 while Present (Curr) loop
9876 -- Retrieve the subtype mark or name within the current current
9877 -- use clause.
9879 if Nkind (Curr) = N_Use_Type_Clause then
9880 N := Subtype_Mark (Curr);
9881 else
9882 N := Name (Curr);
9883 end if;
9885 -- If warnings for unreferenced entities are enabled and the
9886 -- current use clause has not been marked effective.
9888 if Check_Unreferenced
9889 and then Comes_From_Source (Curr)
9890 and then not Is_Effective_Use_Clause (Curr)
9891 and then not In_Instance
9892 and then not In_Inlined_Body
9893 then
9894 -- We are dealing with a potentially unused use_package_clause
9896 if Nkind (Curr) = N_Use_Package_Clause then
9898 -- Renamings and formal subprograms may cause the associated
9899 -- node to be marked as effective instead of the original.
9901 if not (Present (Associated_Node (N))
9902 and then Present
9903 (Current_Use_Clause
9904 (Associated_Node (N)))
9905 and then Is_Effective_Use_Clause
9906 (Current_Use_Clause
9907 (Associated_Node (N))))
9908 then
9909 Error_Msg_Node_1 := Entity (N);
9910 Error_Msg_NE
9911 ("use clause for package & has no effect?u?",
9912 Curr, Entity (N));
9913 end if;
9915 -- We are dealing with an unused use_type_clause
9917 else
9918 Error_Msg_Node_1 := Etype (N);
9919 Error_Msg_NE
9920 ("use clause for } has no effect?u?", Curr, Etype (N));
9921 end if;
9922 end if;
9924 -- Verify that we haven't already processed a redundant
9925 -- use_type_clause within the same scope before we move the
9926 -- current use clause up to a previous one for type T.
9928 if Present (Prev_Use_Clause (Curr)) then
9929 Set_Current_Use_Clause (Entity (N), Prev_Use_Clause (Curr));
9930 end if;
9932 Next_Use_Clause (Curr);
9933 end loop;
9934 end Update_Chain_In_Scope;
9936 -- Start of processing for Update_Use_Clause_Chain
9938 begin
9939 Update_Chain_In_Scope (Scope_Stack.Last);
9941 -- Deal with use clauses within the context area if the current
9942 -- scope is a compilation unit.
9944 if Is_Compilation_Unit (Current_Scope)
9945 and then Sloc (Scope_Stack.Table
9946 (Scope_Stack.Last - 1).Entity) = Standard_Location
9947 then
9948 Update_Chain_In_Scope (Scope_Stack.Last - 1);
9949 end if;
9950 end Update_Use_Clause_Chain;
9952 ---------------------
9953 -- Use_One_Package --
9954 ---------------------
9956 procedure Use_One_Package
9957 (N : Node_Id;
9958 Pack_Name : Entity_Id := Empty;
9959 Force : Boolean := False)
9961 procedure Note_Redundant_Use (Clause : Node_Id);
9962 -- Mark the name in a use clause as redundant if the corresponding
9963 -- entity is already use-visible. Emit a warning if the use clause comes
9964 -- from source and the proper warnings are enabled.
9966 ------------------------
9967 -- Note_Redundant_Use --
9968 ------------------------
9970 procedure Note_Redundant_Use (Clause : Node_Id) is
9971 Decl : constant Node_Id := Parent (Clause);
9972 Pack_Name : constant Entity_Id := Entity (Clause);
9974 Cur_Use : Node_Id := Current_Use_Clause (Pack_Name);
9975 Prev_Use : Node_Id := Empty;
9976 Redundant : Node_Id := Empty;
9977 -- The Use_Clause which is actually redundant. In the simplest case
9978 -- it is Pack itself, but when we compile a body we install its
9979 -- context before that of its spec, in which case it is the
9980 -- use_clause in the spec that will appear to be redundant, and we
9981 -- want the warning to be placed on the body. Similar complications
9982 -- appear when the redundancy is between a child unit and one of its
9983 -- ancestors.
9985 begin
9986 -- Could be renamed...
9988 if No (Cur_Use) then
9989 Cur_Use := Current_Use_Clause (Renamed_Entity (Pack_Name));
9990 end if;
9992 Set_Redundant_Use (Clause, True);
9994 -- Do not check for redundant use if clause is generated, or in an
9995 -- instance, or in a predefined unit to avoid misleading warnings
9996 -- that may occur as part of a rtsfind load.
9998 if not Comes_From_Source (Clause)
9999 or else In_Instance
10000 or else not Warn_On_Redundant_Constructs
10001 or else Is_Predefined_Unit (Current_Sem_Unit)
10002 then
10003 return;
10004 end if;
10006 if not Is_Compilation_Unit (Current_Scope) then
10008 -- If the use_clause is in an inner scope, it is made redundant by
10009 -- some clause in the current context, with one exception: If we
10010 -- are compiling a nested package body, and the use_clause comes
10011 -- from then corresponding spec, the clause is not necessarily
10012 -- fully redundant, so we should not warn. If a warning was
10013 -- warranted, it would have been given when the spec was
10014 -- processed.
10016 if Nkind (Parent (Decl)) = N_Package_Specification then
10017 declare
10018 Package_Spec_Entity : constant Entity_Id :=
10019 Defining_Unit_Name (Parent (Decl));
10020 begin
10021 if In_Package_Body (Package_Spec_Entity) then
10022 return;
10023 end if;
10024 end;
10025 end if;
10027 Redundant := Clause;
10028 Prev_Use := Cur_Use;
10030 elsif Nkind (Unit (Cunit (Current_Sem_Unit))) = N_Package_Body then
10031 declare
10032 Cur_Unit : constant Unit_Number_Type :=
10033 Get_Source_Unit (Cur_Use);
10034 New_Unit : constant Unit_Number_Type :=
10035 Get_Source_Unit (Clause);
10037 Scop : Entity_Id;
10039 begin
10040 if Cur_Unit = New_Unit then
10042 -- Redundant clause in same body
10044 Redundant := Clause;
10045 Prev_Use := Cur_Use;
10047 elsif Cur_Unit = Current_Sem_Unit then
10049 -- If the new clause is not in the current unit it has been
10050 -- analyzed first, and it makes the other one redundant.
10051 -- However, if the new clause appears in a subunit, Cur_Unit
10052 -- is still the parent, and in that case the redundant one
10053 -- is the one appearing in the subunit.
10055 if Nkind (Unit (Cunit (New_Unit))) = N_Subunit then
10056 Redundant := Clause;
10057 Prev_Use := Cur_Use;
10059 -- Most common case: redundant clause in body, original
10060 -- clause in spec. Current scope is spec entity.
10062 elsif Current_Scope = Cunit_Entity (Current_Sem_Unit) then
10063 Redundant := Cur_Use;
10064 Prev_Use := Clause;
10066 else
10067 -- The new clause may appear in an unrelated unit, when
10068 -- the parents of a generic are being installed prior to
10069 -- instantiation. In this case there must be no warning.
10070 -- We detect this case by checking whether the current
10071 -- top of the stack is related to the current
10072 -- compilation.
10074 Scop := Current_Scope;
10075 while Present (Scop)
10076 and then Scop /= Standard_Standard
10077 loop
10078 if Is_Compilation_Unit (Scop)
10079 and then not Is_Child_Unit (Scop)
10080 then
10081 return;
10083 elsif Scop = Cunit_Entity (Current_Sem_Unit) then
10084 exit;
10085 end if;
10087 Scop := Scope (Scop);
10088 end loop;
10090 Redundant := Cur_Use;
10091 Prev_Use := Clause;
10092 end if;
10094 elsif New_Unit = Current_Sem_Unit then
10095 Redundant := Clause;
10096 Prev_Use := Cur_Use;
10098 else
10099 -- Neither is the current unit, so they appear in parent or
10100 -- sibling units. Warning will be emitted elsewhere.
10102 return;
10103 end if;
10104 end;
10106 elsif Nkind (Unit (Cunit (Current_Sem_Unit))) = N_Package_Declaration
10107 and then Present (Parent_Spec (Unit (Cunit (Current_Sem_Unit))))
10108 then
10109 -- Use_clause is in child unit of current unit, and the child unit
10110 -- appears in the context of the body of the parent, so it has
10111 -- been installed first, even though it is the redundant one.
10112 -- Depending on their placement in the context, the visible or the
10113 -- private parts of the two units, either might appear as
10114 -- redundant, but the message has to be on the current unit.
10116 if Get_Source_Unit (Cur_Use) = Current_Sem_Unit then
10117 Redundant := Cur_Use;
10118 Prev_Use := Clause;
10119 else
10120 Redundant := Clause;
10121 Prev_Use := Cur_Use;
10122 end if;
10124 -- If the new use clause appears in the private part of a parent
10125 -- unit it may appear to be redundant w.r.t. a use clause in a
10126 -- child unit, but the previous use clause was needed in the
10127 -- visible part of the child, and no warning should be emitted.
10129 if Nkind (Parent (Decl)) = N_Package_Specification
10130 and then List_Containing (Decl) =
10131 Private_Declarations (Parent (Decl))
10132 then
10133 declare
10134 Par : constant Entity_Id :=
10135 Defining_Entity (Parent (Decl));
10136 Spec : constant Node_Id :=
10137 Specification (Unit (Cunit (Current_Sem_Unit)));
10138 Cur_List : constant List_Id := List_Containing (Cur_Use);
10140 begin
10141 if Is_Compilation_Unit (Par)
10142 and then Par /= Cunit_Entity (Current_Sem_Unit)
10143 then
10144 if Cur_List = Context_Items (Cunit (Current_Sem_Unit))
10145 or else Cur_List = Visible_Declarations (Spec)
10146 then
10147 return;
10148 end if;
10149 end if;
10150 end;
10151 end if;
10153 -- Finally, if the current use clause is in the context then the
10154 -- clause is redundant when it is nested within the unit.
10156 elsif Nkind (Parent (Cur_Use)) = N_Compilation_Unit
10157 and then Nkind (Parent (Parent (Clause))) /= N_Compilation_Unit
10158 and then Get_Source_Unit (Cur_Use) = Get_Source_Unit (Clause)
10159 then
10160 Redundant := Clause;
10161 Prev_Use := Cur_Use;
10162 end if;
10164 if Present (Redundant) and then Parent (Redundant) /= Prev_Use then
10166 -- Make sure we are looking at most-descendant use_package_clause
10167 -- by traversing the chain with Find_First_Use and then verifying
10168 -- there is no scope manipulation via Most_Descendant_Use_Clause.
10170 if Nkind (Prev_Use) = N_Use_Package_Clause
10171 and then
10172 (Nkind (Parent (Prev_Use)) /= N_Compilation_Unit
10173 or else Most_Descendant_Use_Clause
10174 (Prev_Use, Find_First_Use (Prev_Use)) /= Prev_Use)
10175 then
10176 Prev_Use := Find_First_Use (Prev_Use);
10177 end if;
10179 Error_Msg_Sloc := Sloc (Prev_Use);
10180 Error_Msg_NE -- CODEFIX
10181 ("& is already use-visible through previous use_clause #?r?",
10182 Redundant, Pack_Name);
10183 end if;
10184 end Note_Redundant_Use;
10186 -- Local variables
10188 Current_Instance : Entity_Id := Empty;
10189 Id : Entity_Id;
10190 P : Entity_Id;
10191 Prev : Entity_Id;
10192 Private_With_OK : Boolean := False;
10193 Real_P : Entity_Id;
10195 -- Start of processing for Use_One_Package
10197 begin
10198 -- Use_One_Package may have been called recursively to handle an
10199 -- implicit use for a auxiliary system package, so set P accordingly
10200 -- and skip redundancy checks.
10202 if No (Pack_Name) and then Present_System_Aux (N) then
10203 P := System_Aux_Id;
10205 -- Check for redundant use_package_clauses
10207 else
10208 -- Ignore cases where we are dealing with a non user defined package
10209 -- like Standard_Standard or something other than a valid package.
10211 if not Is_Entity_Name (Pack_Name)
10212 or else No (Entity (Pack_Name))
10213 or else Ekind (Entity (Pack_Name)) /= E_Package
10214 then
10215 return;
10216 end if;
10218 -- When a renaming exists we must check it for redundancy. The
10219 -- original package would have already been seen at this point.
10221 if Present (Renamed_Entity (Entity (Pack_Name))) then
10222 P := Renamed_Entity (Entity (Pack_Name));
10223 else
10224 P := Entity (Pack_Name);
10225 end if;
10227 -- Check for redundant clauses then set the current use clause for
10228 -- P if were are not "forcing" an installation from a scope
10229 -- reinstallation that is done throughout analysis for various
10230 -- reasons.
10232 if In_Use (P) then
10233 Note_Redundant_Use (Pack_Name);
10235 if not Force then
10236 Set_Current_Use_Clause (P, N);
10237 end if;
10239 return;
10241 -- Warn about detected redundant clauses
10243 elsif not Force
10244 and then In_Open_Scopes (P)
10245 and then not Is_Hidden_Open_Scope (P)
10246 then
10247 if Warn_On_Redundant_Constructs and then P = Current_Scope then
10248 Error_Msg_NE -- CODEFIX
10249 ("& is already use-visible within itself?r?",
10250 Pack_Name, P);
10251 end if;
10253 return;
10254 end if;
10256 -- Set P back to the non-renamed package so that visibility of the
10257 -- entities within the package can be properly set below.
10259 P := Entity (Pack_Name);
10260 end if;
10262 Set_In_Use (P);
10263 Set_Current_Use_Clause (P, N);
10265 -- Ada 2005 (AI-50217): Check restriction
10267 if From_Limited_With (P) then
10268 Error_Msg_N ("limited withed package cannot appear in use clause", N);
10269 end if;
10271 -- Find enclosing instance, if any
10273 if In_Instance then
10274 Current_Instance := Current_Scope;
10275 while not Is_Generic_Instance (Current_Instance) loop
10276 Current_Instance := Scope (Current_Instance);
10277 end loop;
10279 if No (Hidden_By_Use_Clause (N)) then
10280 Set_Hidden_By_Use_Clause (N, New_Elmt_List);
10281 end if;
10282 end if;
10284 -- If unit is a package renaming, indicate that the renamed package is
10285 -- also in use (the flags on both entities must remain consistent, and a
10286 -- subsequent use of either of them should be recognized as redundant).
10288 if Present (Renamed_Entity (P)) then
10289 Set_In_Use (Renamed_Entity (P));
10290 Set_Current_Use_Clause (Renamed_Entity (P), N);
10291 Real_P := Renamed_Entity (P);
10292 else
10293 Real_P := P;
10294 end if;
10296 -- Ada 2005 (AI-262): Check the use_clause of a private withed package
10297 -- found in the private part of a package specification
10299 if In_Private_Part (Current_Scope)
10300 and then Has_Private_With (P)
10301 and then Is_Child_Unit (Current_Scope)
10302 and then Is_Child_Unit (P)
10303 and then Is_Ancestor_Package (Scope (Current_Scope), P)
10304 then
10305 Private_With_OK := True;
10306 end if;
10308 -- Loop through entities in one package making them potentially
10309 -- use-visible.
10311 Id := First_Entity (P);
10312 while Present (Id)
10313 and then (Id /= First_Private_Entity (P)
10314 or else Private_With_OK) -- Ada 2005 (AI-262)
10315 loop
10316 Prev := Current_Entity (Id);
10317 while Present (Prev) loop
10318 if Is_Immediately_Visible (Prev)
10319 and then (not Is_Overloadable (Prev)
10320 or else not Is_Overloadable (Id)
10321 or else (Type_Conformant (Id, Prev)))
10322 then
10323 if No (Current_Instance) then
10325 -- Potentially use-visible entity remains hidden
10327 if Warn_On_Hiding then
10328 Warn_On_Hiding_Entity (N, Hidden => Id, Visible => Prev,
10329 On_Use_Clause => True);
10330 end if;
10332 goto Next_Usable_Entity;
10334 -- A use clause within an instance hides outer global entities,
10335 -- which are not used to resolve local entities in the
10336 -- instance. Note that the predefined entities in Standard
10337 -- could not have been hidden in the generic by a use clause,
10338 -- and therefore remain visible. Other compilation units whose
10339 -- entities appear in Standard must be hidden in an instance.
10341 -- To determine whether an entity is external to the instance
10342 -- we compare the scope depth of its scope with that of the
10343 -- current instance. However, a generic actual of a subprogram
10344 -- instance is declared in the wrapper package but will not be
10345 -- hidden by a use-visible entity. similarly, an entity that is
10346 -- declared in an enclosing instance will not be hidden by an
10347 -- an entity declared in a generic actual, which can only have
10348 -- been use-visible in the generic and will not have hidden the
10349 -- entity in the generic parent.
10351 -- If Id is called Standard, the predefined package with the
10352 -- same name is in the homonym chain. It has to be ignored
10353 -- because it has no defined scope (being the only entity in
10354 -- the system with this mandated behavior).
10356 elsif not Is_Hidden (Id)
10357 and then Present (Scope (Prev))
10358 and then not Is_Wrapper_Package (Scope (Prev))
10359 and then Scope_Depth (Scope (Prev)) <
10360 Scope_Depth (Current_Instance)
10361 and then (Scope (Prev) /= Standard_Standard
10362 or else Sloc (Prev) > Standard_Location)
10363 then
10364 if In_Open_Scopes (Scope (Prev))
10365 and then Is_Generic_Instance (Scope (Prev))
10366 and then Present (Associated_Formal_Package (P))
10367 then
10368 null;
10370 else
10371 Set_Is_Potentially_Use_Visible (Id);
10372 Set_Is_Immediately_Visible (Prev, False);
10373 Append_Elmt (Prev, Hidden_By_Use_Clause (N));
10374 end if;
10375 end if;
10377 -- A user-defined operator is not use-visible if the predefined
10378 -- operator for the type is immediately visible, which is the case
10379 -- if the type of the operand is in an open scope. This does not
10380 -- apply to user-defined operators that have operands of different
10381 -- types, because the predefined mixed mode operations (multiply
10382 -- and divide) apply to universal types and do not hide anything.
10384 elsif Ekind (Prev) = E_Operator
10385 and then Operator_Matches_Spec (Prev, Id)
10386 and then In_Open_Scopes
10387 (Scope (Base_Type (Etype (First_Formal (Id)))))
10388 and then (No (Next_Formal (First_Formal (Id)))
10389 or else Etype (First_Formal (Id)) =
10390 Etype (Next_Formal (First_Formal (Id)))
10391 or else Chars (Prev) = Name_Op_Expon)
10392 then
10393 goto Next_Usable_Entity;
10395 -- In an instance, two homonyms may become use_visible through the
10396 -- actuals of distinct formal packages. In the generic, only the
10397 -- current one would have been visible, so make the other one
10398 -- not use_visible.
10400 -- In certain pathological cases it is possible that unrelated
10401 -- homonyms from distinct formal packages may exist in an
10402 -- uninstalled scope. We must test for that here.
10404 elsif Present (Current_Instance)
10405 and then Is_Potentially_Use_Visible (Prev)
10406 and then not Is_Overloadable (Prev)
10407 and then Scope (Id) /= Scope (Prev)
10408 and then Used_As_Generic_Actual (Scope (Prev))
10409 and then Used_As_Generic_Actual (Scope (Id))
10410 and then Is_List_Member (Scope (Prev))
10411 and then not In_Same_List (Current_Use_Clause (Scope (Prev)),
10412 Current_Use_Clause (Scope (Id)))
10413 then
10414 Set_Is_Potentially_Use_Visible (Prev, False);
10415 Append_Elmt (Prev, Hidden_By_Use_Clause (N));
10416 end if;
10418 Prev := Homonym (Prev);
10419 end loop;
10421 -- On exit, we know entity is not hidden, unless it is private
10423 if not Is_Hidden (Id)
10424 and then ((not Is_Child_Unit (Id)) or else Is_Visible_Lib_Unit (Id))
10425 then
10426 Set_Is_Potentially_Use_Visible (Id);
10428 if Is_Private_Type (Id) and then Present (Full_View (Id)) then
10429 Set_Is_Potentially_Use_Visible (Full_View (Id));
10430 end if;
10431 end if;
10433 <<Next_Usable_Entity>>
10434 Next_Entity (Id);
10435 end loop;
10437 -- Child units are also made use-visible by a use clause, but they may
10438 -- appear after all visible declarations in the parent entity list.
10440 while Present (Id) loop
10441 if Is_Child_Unit (Id) and then Is_Visible_Lib_Unit (Id) then
10442 Set_Is_Potentially_Use_Visible (Id);
10443 end if;
10445 Next_Entity (Id);
10446 end loop;
10448 if Chars (Real_P) = Name_System
10449 and then Scope (Real_P) = Standard_Standard
10450 and then Present_System_Aux (N)
10451 then
10452 Use_One_Package (N);
10453 end if;
10454 end Use_One_Package;
10456 ------------------
10457 -- Use_One_Type --
10458 ------------------
10460 procedure Use_One_Type
10461 (Id : Node_Id;
10462 Installed : Boolean := False;
10463 Force : Boolean := False)
10465 function Spec_Reloaded_For_Body return Boolean;
10466 -- Determine whether the compilation unit is a package body and the use
10467 -- type clause is in the spec of the same package. Even though the spec
10468 -- was analyzed first, its context is reloaded when analysing the body.
10470 procedure Use_Class_Wide_Operations (Typ : Entity_Id);
10471 -- AI05-150: if the use_type_clause carries the "all" qualifier,
10472 -- class-wide operations of ancestor types are use-visible if the
10473 -- ancestor type is visible.
10475 ----------------------------
10476 -- Spec_Reloaded_For_Body --
10477 ----------------------------
10479 function Spec_Reloaded_For_Body return Boolean is
10480 begin
10481 if Nkind (Unit (Cunit (Current_Sem_Unit))) = N_Package_Body then
10482 declare
10483 Spec : constant Node_Id :=
10484 Parent (List_Containing (Parent (Id)));
10486 begin
10487 -- Check whether type is declared in a package specification,
10488 -- and current unit is the corresponding package body. The
10489 -- use clauses themselves may be within a nested package.
10491 return
10492 Nkind (Spec) = N_Package_Specification
10493 and then In_Same_Source_Unit
10494 (Corresponding_Body (Parent (Spec)),
10495 Cunit_Entity (Current_Sem_Unit));
10496 end;
10497 end if;
10499 return False;
10500 end Spec_Reloaded_For_Body;
10502 -------------------------------
10503 -- Use_Class_Wide_Operations --
10504 -------------------------------
10506 procedure Use_Class_Wide_Operations (Typ : Entity_Id) is
10507 function Is_Class_Wide_Operation_Of
10508 (Op : Entity_Id;
10509 T : Entity_Id) return Boolean;
10510 -- Determine whether a subprogram has a class-wide parameter or
10511 -- result that is T'Class.
10513 ---------------------------------
10514 -- Is_Class_Wide_Operation_Of --
10515 ---------------------------------
10517 function Is_Class_Wide_Operation_Of
10518 (Op : Entity_Id;
10519 T : Entity_Id) return Boolean
10521 Formal : Entity_Id;
10523 begin
10524 Formal := First_Formal (Op);
10525 while Present (Formal) loop
10526 if Etype (Formal) = Class_Wide_Type (T) then
10527 return True;
10528 end if;
10530 Next_Formal (Formal);
10531 end loop;
10533 if Etype (Op) = Class_Wide_Type (T) then
10534 return True;
10535 end if;
10537 return False;
10538 end Is_Class_Wide_Operation_Of;
10540 -- Local variables
10542 Ent : Entity_Id;
10543 Scop : Entity_Id;
10545 -- Start of processing for Use_Class_Wide_Operations
10547 begin
10548 Scop := Scope (Typ);
10549 if not Is_Hidden (Scop) then
10550 Ent := First_Entity (Scop);
10551 while Present (Ent) loop
10552 if Is_Overloadable (Ent)
10553 and then Is_Class_Wide_Operation_Of (Ent, Typ)
10554 and then not Is_Potentially_Use_Visible (Ent)
10555 then
10556 Set_Is_Potentially_Use_Visible (Ent);
10557 Append_Elmt (Ent, Used_Operations (Parent (Id)));
10558 end if;
10560 Next_Entity (Ent);
10561 end loop;
10562 end if;
10564 if Is_Derived_Type (Typ) then
10565 Use_Class_Wide_Operations (Etype (Base_Type (Typ)));
10566 end if;
10567 end Use_Class_Wide_Operations;
10569 -- Local variables
10571 Elmt : Elmt_Id;
10572 Is_Known_Used : Boolean;
10573 Op_List : Elist_Id;
10574 T : Entity_Id;
10576 -- Start of processing for Use_One_Type
10578 begin
10579 if Entity (Id) = Any_Type then
10580 return;
10581 end if;
10583 -- It is the type determined by the subtype mark (8.4(8)) whose
10584 -- operations become potentially use-visible.
10586 T := Base_Type (Entity (Id));
10588 -- Either the type itself is used, the package where it is declared is
10589 -- in use or the entity is declared in the current package, thus
10590 -- use-visible.
10592 Is_Known_Used :=
10593 (In_Use (T)
10594 and then ((Present (Current_Use_Clause (T))
10595 and then All_Present (Current_Use_Clause (T)))
10596 or else not All_Present (Parent (Id))))
10597 or else In_Use (Scope (T))
10598 or else Scope (T) = Current_Scope;
10600 Set_Redundant_Use (Id,
10601 Is_Known_Used or else Is_Potentially_Use_Visible (T));
10603 if Ekind (T) = E_Incomplete_Type then
10604 Error_Msg_N ("premature usage of incomplete type", Id);
10606 elsif In_Open_Scopes (Scope (T)) then
10607 null;
10609 -- A limited view cannot appear in a use_type_clause. However, an access
10610 -- type whose designated type is limited has the flag but is not itself
10611 -- a limited view unless we only have a limited view of its enclosing
10612 -- package.
10614 elsif From_Limited_With (T) and then From_Limited_With (Scope (T)) then
10615 Error_Msg_N
10616 ("incomplete type from limited view cannot appear in use clause",
10617 Id);
10619 -- If the use clause is redundant, Used_Operations will usually be
10620 -- empty, but we need to set it to empty here in one case: If we are
10621 -- instantiating a generic library unit, then we install the ancestors
10622 -- of that unit in the scope stack, which involves reprocessing use
10623 -- clauses in those ancestors. Such a use clause will typically have a
10624 -- nonempty Used_Operations unless it was redundant in the generic unit,
10625 -- even if it is redundant at the place of the instantiation.
10627 elsif Redundant_Use (Id) then
10628 Set_Used_Operations (Parent (Id), New_Elmt_List);
10630 -- If the subtype mark designates a subtype in a different package,
10631 -- we have to check that the parent type is visible, otherwise the
10632 -- use_type_clause is a no-op. Not clear how to do that???
10634 else
10635 Set_Current_Use_Clause (T, Parent (Id));
10636 Set_In_Use (T);
10638 -- If T is tagged, primitive operators on class-wide operands are
10639 -- also deemed available. Note that this is really necessary only
10640 -- in semantics-only mode, because the primitive operators are not
10641 -- fully constructed in this mode, but we do it in all modes for the
10642 -- sake of uniformity, as this should not matter in practice.
10644 if Is_Tagged_Type (T) then
10645 Set_In_Use (Class_Wide_Type (T));
10646 end if;
10648 -- Iterate over primitive operations of the type. If an operation is
10649 -- already use_visible, it is the result of a previous use_clause,
10650 -- and already appears on the corresponding entity chain. If the
10651 -- clause is being reinstalled, operations are already use-visible.
10653 if Installed then
10654 null;
10656 else
10657 Op_List := Collect_Primitive_Operations (T);
10658 Elmt := First_Elmt (Op_List);
10659 while Present (Elmt) loop
10660 if (Nkind (Node (Elmt)) = N_Defining_Operator_Symbol
10661 or else Chars (Node (Elmt)) in Any_Operator_Name)
10662 and then not Is_Hidden (Node (Elmt))
10663 and then not Is_Potentially_Use_Visible (Node (Elmt))
10664 then
10665 Set_Is_Potentially_Use_Visible (Node (Elmt));
10666 Append_Elmt (Node (Elmt), Used_Operations (Parent (Id)));
10668 elsif Ada_Version >= Ada_2012
10669 and then All_Present (Parent (Id))
10670 and then not Is_Hidden (Node (Elmt))
10671 and then not Is_Potentially_Use_Visible (Node (Elmt))
10672 then
10673 Set_Is_Potentially_Use_Visible (Node (Elmt));
10674 Append_Elmt (Node (Elmt), Used_Operations (Parent (Id)));
10675 end if;
10677 Next_Elmt (Elmt);
10678 end loop;
10679 end if;
10681 if Ada_Version >= Ada_2012
10682 and then All_Present (Parent (Id))
10683 and then Is_Tagged_Type (T)
10684 then
10685 Use_Class_Wide_Operations (T);
10686 end if;
10687 end if;
10689 -- If warning on redundant constructs, check for unnecessary WITH
10691 if not Force
10692 and then Warn_On_Redundant_Constructs
10693 and then Is_Known_Used
10695 -- with P; with P; use P;
10696 -- package P is package X is package body X is
10697 -- type T ... use P.T;
10699 -- The compilation unit is the body of X. GNAT first compiles the
10700 -- spec of X, then proceeds to the body. At that point P is marked
10701 -- as use visible. The analysis then reinstalls the spec along with
10702 -- its context. The use clause P.T is now recognized as redundant,
10703 -- but in the wrong context. Do not emit a warning in such cases.
10704 -- Do not emit a warning either if we are in an instance, there is
10705 -- no redundancy between an outer use_clause and one that appears
10706 -- within the generic.
10708 and then not Spec_Reloaded_For_Body
10709 and then not In_Instance
10710 and then not In_Inlined_Body
10711 then
10712 -- The type already has a use clause
10714 if In_Use (T) then
10716 -- Case where we know the current use clause for the type
10718 if Present (Current_Use_Clause (T)) then
10719 Use_Clause_Known : declare
10720 Clause1 : constant Node_Id :=
10721 Find_First_Use (Current_Use_Clause (T));
10722 Clause2 : constant Node_Id := Parent (Id);
10723 Ent1 : Entity_Id;
10724 Ent2 : Entity_Id;
10725 Err_No : Node_Id;
10726 Unit1 : Node_Id;
10727 Unit2 : Node_Id;
10729 -- Start of processing for Use_Clause_Known
10731 begin
10732 -- If the unit is a subprogram body that acts as spec, the
10733 -- context clause is shared with the constructed subprogram
10734 -- spec. Clearly there is no redundancy.
10736 if Clause1 = Clause2 then
10737 return;
10738 end if;
10740 Unit1 := Unit (Enclosing_Comp_Unit_Node (Clause1));
10741 Unit2 := Unit (Enclosing_Comp_Unit_Node (Clause2));
10743 -- If both clauses are on same unit, or one is the body of
10744 -- the other, or one of them is in a subunit, report
10745 -- redundancy on the later one.
10747 if Unit1 = Unit2
10748 or else Nkind (Unit1) = N_Subunit
10749 or else
10750 (Nkind (Unit2) in N_Package_Body | N_Subprogram_Body
10751 and then Nkind (Unit1) /= Nkind (Unit2)
10752 and then Nkind (Unit1) /= N_Subunit)
10753 then
10754 Error_Msg_Sloc := Sloc (Clause1);
10755 Error_Msg_NE -- CODEFIX
10756 ("& is already use-visible through previous "
10757 & "use_type_clause #??", Clause2, T);
10758 return;
10759 end if;
10761 -- If there is a redundant use_type_clause in a child unit
10762 -- determine which of the units is more deeply nested. If a
10763 -- unit is a package instance, retrieve the entity and its
10764 -- scope from the instance spec.
10766 Ent1 := Entity_Of_Unit (Unit1);
10767 Ent2 := Entity_Of_Unit (Unit2);
10769 -- When the scope of both units' entities are
10770 -- Standard_Standard then neither Unit1 or Unit2 are child
10771 -- units - so return in that case.
10773 if Scope (Ent1) = Standard_Standard
10774 and then Scope (Ent2) = Standard_Standard
10775 then
10776 return;
10778 -- Otherwise, determine if one of the units is not a child
10780 elsif Scope (Ent2) = Standard_Standard then
10781 Error_Msg_Sloc := Sloc (Clause2);
10782 Err_No := Clause1;
10784 elsif Scope (Ent1) = Standard_Standard then
10785 Error_Msg_Sloc := Sloc (Id);
10786 Err_No := Clause2;
10788 -- If both units are child units, we determine which one is
10789 -- the descendant by the scope distance to the ultimate
10790 -- parent unit.
10792 else
10793 declare
10794 S1 : Entity_Id;
10795 S2 : Entity_Id;
10797 begin
10798 S1 := Scope (Ent1);
10799 S2 := Scope (Ent2);
10800 while Present (S1)
10801 and then Present (S2)
10802 and then S1 /= Standard_Standard
10803 and then S2 /= Standard_Standard
10804 loop
10805 S1 := Scope (S1);
10806 S2 := Scope (S2);
10807 end loop;
10809 if S1 = Standard_Standard then
10810 Error_Msg_Sloc := Sloc (Id);
10811 Err_No := Clause2;
10812 else
10813 Error_Msg_Sloc := Sloc (Clause2);
10814 Err_No := Clause1;
10815 end if;
10816 end;
10817 end if;
10819 if Parent (Id) /= Err_No then
10820 if Most_Descendant_Use_Clause
10821 (Err_No, Parent (Id)) = Parent (Id)
10822 then
10823 Error_Msg_Sloc := Sloc (Err_No);
10824 Err_No := Parent (Id);
10825 end if;
10827 Error_Msg_NE -- CODEFIX
10828 ("& is already use-visible through previous "
10829 & "use_type_clause #??", Err_No, Id);
10830 end if;
10831 end Use_Clause_Known;
10833 -- Here Current_Use_Clause is not set for T, so we do not have the
10834 -- location information available.
10836 else
10837 Error_Msg_NE -- CODEFIX
10838 ("& is already use-visible through previous "
10839 & "use_type_clause??", Id, T);
10840 end if;
10842 -- The package where T is declared is already used
10844 elsif In_Use (Scope (T)) then
10845 -- Due to expansion of contracts we could be attempting to issue
10846 -- a spurious warning - so verify there is a previous use clause.
10848 if Current_Use_Clause (Scope (T)) /=
10849 Find_First_Use (Current_Use_Clause (Scope (T)))
10850 then
10851 Error_Msg_Sloc :=
10852 Sloc (Find_First_Use (Current_Use_Clause (Scope (T))));
10853 Error_Msg_NE -- CODEFIX
10854 ("& is already use-visible through package use clause #??",
10855 Id, T);
10856 end if;
10858 -- The current scope is the package where T is declared
10860 else
10861 Error_Msg_Node_2 := Scope (T);
10862 Error_Msg_NE -- CODEFIX
10863 ("& is already use-visible inside package &??", Id, T);
10864 end if;
10865 end if;
10866 end Use_One_Type;
10868 ----------------
10869 -- Write_Info --
10870 ----------------
10872 procedure Write_Info is
10873 Id : Entity_Id := First_Entity (Current_Scope);
10875 begin
10876 -- No point in dumping standard entities
10878 if Current_Scope = Standard_Standard then
10879 return;
10880 end if;
10882 Write_Str ("========================================================");
10883 Write_Eol;
10884 Write_Str (" Defined Entities in ");
10885 Write_Name (Chars (Current_Scope));
10886 Write_Eol;
10887 Write_Str ("========================================================");
10888 Write_Eol;
10890 if No (Id) then
10891 Write_Str ("-- none --");
10892 Write_Eol;
10894 else
10895 while Present (Id) loop
10896 Write_Entity_Info (Id, " ");
10897 Next_Entity (Id);
10898 end loop;
10899 end if;
10901 if Scope (Current_Scope) = Standard_Standard then
10903 -- Print information on the current unit itself
10905 Write_Entity_Info (Current_Scope, " ");
10906 end if;
10908 Write_Eol;
10909 end Write_Info;
10911 --------
10912 -- ws --
10913 --------
10915 procedure ws is
10916 S : Entity_Id;
10917 begin
10918 for J in reverse 1 .. Scope_Stack.Last loop
10919 S := Scope_Stack.Table (J).Entity;
10920 Write_Int (Int (S));
10921 Write_Str (" === ");
10922 Write_Name (Chars (S));
10923 Write_Eol;
10924 end loop;
10925 end ws;
10927 --------
10928 -- we --
10929 --------
10931 procedure we (S : Entity_Id) is
10932 E : Entity_Id;
10933 begin
10934 E := First_Entity (S);
10935 while Present (E) loop
10936 Write_Int (Int (E));
10937 Write_Str (" === ");
10938 Write_Name (Chars (E));
10939 Write_Eol;
10940 Next_Entity (E);
10941 end loop;
10942 end we;
10943 end Sem_Ch8;