Add assember CFI directives to millicode division and remainder routines.
[official-gcc.git] / gcc / ada / sem_ch8.adb
blob6f858eea0f998b4d4fba7da57e066a1fb1671210
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-2023, 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;
79 with Warnsw; use Warnsw;
81 package body Sem_Ch8 is
83 ------------------------------------
84 -- Visibility and Name Resolution --
85 ------------------------------------
87 -- This package handles name resolution and the collection of possible
88 -- interpretations for overloaded names, prior to overload resolution.
90 -- Name resolution is the process that establishes a mapping between source
91 -- identifiers and the entities they denote at each point in the program.
92 -- Each entity is represented by a defining occurrence. Each identifier
93 -- that denotes an entity points to the corresponding defining occurrence.
94 -- This is the entity of the applied occurrence. Each occurrence holds
95 -- an index into the names table, where source identifiers are stored.
97 -- Each entry in the names table for an identifier or designator uses the
98 -- Info pointer to hold a link to the currently visible entity that has
99 -- this name (see subprograms Get_Name_Entity_Id and Set_Name_Entity_Id
100 -- in package Sem_Util). The visibility is initialized at the beginning of
101 -- semantic processing to make entities in package Standard immediately
102 -- visible. The visibility table is used in a more subtle way when
103 -- compiling subunits (see below).
105 -- Entities that have the same name (i.e. homonyms) are chained. In the
106 -- case of overloaded entities, this chain holds all the possible meanings
107 -- of a given identifier. The process of overload resolution uses type
108 -- information to select from this chain the unique meaning of a given
109 -- identifier.
111 -- Entities are also chained in their scope, through the Next_Entity link.
112 -- As a consequence, the name space is organized as a sparse matrix, where
113 -- each row corresponds to a scope, and each column to a source identifier.
114 -- Open scopes, that is to say scopes currently being compiled, have their
115 -- corresponding rows of entities in order, innermost scope first.
117 -- The scopes of packages that are mentioned in context clauses appear in
118 -- no particular order, interspersed among open scopes. This is because
119 -- in the course of analyzing the context of a compilation, a package
120 -- declaration is first an open scope, and subsequently an element of the
121 -- context. If subunits or child units are present, a parent unit may
122 -- appear under various guises at various times in the compilation.
124 -- When the compilation of the innermost scope is complete, the entities
125 -- defined therein are no longer visible. If the scope is not a package
126 -- declaration, these entities are never visible subsequently, and can be
127 -- removed from visibility chains. If the scope is a package declaration,
128 -- its visible declarations may still be accessible. Therefore the entities
129 -- defined in such a scope are left on the visibility chains, and only
130 -- their visibility (immediately visibility or potential use-visibility)
131 -- is affected.
133 -- The ordering of homonyms on their chain does not necessarily follow
134 -- the order of their corresponding scopes on the scope stack. For
135 -- example, if package P and the enclosing scope both contain entities
136 -- named E, then when compiling the package body the chain for E will
137 -- hold the global entity first, and the local one (corresponding to
138 -- the current inner scope) next. As a result, name resolution routines
139 -- do not assume any relative ordering of the homonym chains, either
140 -- for scope nesting or to order of appearance of context clauses.
142 -- When compiling a child unit, entities in the parent scope are always
143 -- immediately visible. When compiling the body of a child unit, private
144 -- entities in the parent must also be made immediately visible. There
145 -- are separate routines to make the visible and private declarations
146 -- visible at various times (see package Sem_Ch7).
148 -- +--------+ +-----+
149 -- | In use |-------->| EU1 |-------------------------->
150 -- +--------+ +-----+
151 -- | |
152 -- +--------+ +-----+ +-----+
153 -- | Stand. |---------------->| ES1 |--------------->| ES2 |--->
154 -- +--------+ +-----+ +-----+
155 -- | |
156 -- +---------+ | +-----+
157 -- | with'ed |------------------------------>| EW2 |--->
158 -- +---------+ | +-----+
159 -- | |
160 -- +--------+ +-----+ +-----+
161 -- | Scope2 |---------------->| E12 |--------------->| E22 |--->
162 -- +--------+ +-----+ +-----+
163 -- | |
164 -- +--------+ +-----+ +-----+
165 -- | Scope1 |---------------->| E11 |--------------->| E12 |--->
166 -- +--------+ +-----+ +-----+
167 -- ^ | |
168 -- | | |
169 -- | +---------+ | |
170 -- | | with'ed |----------------------------------------->
171 -- | +---------+ | |
172 -- | | |
173 -- Scope stack | |
174 -- (innermost first) | |
175 -- +----------------------------+
176 -- Names table => | Id1 | | | | Id2 |
177 -- +----------------------------+
179 -- Name resolution must deal with several syntactic forms: simple names,
180 -- qualified names, indexed names, and various forms of calls.
182 -- Each identifier points to an entry in the names table. The resolution
183 -- of a simple name consists in traversing the homonym chain, starting
184 -- from the names table. If an entry is immediately visible, it is the one
185 -- designated by the identifier. If only potentially use-visible entities
186 -- are on the chain, we must verify that they do not hide each other. If
187 -- the entity we find is overloadable, we collect all other overloadable
188 -- entities on the chain as long as they are not hidden.
190 -- To resolve expanded names, we must find the entity at the intersection
191 -- of the entity chain for the scope (the prefix) and the homonym chain
192 -- for the selector. In general, homonym chains will be much shorter than
193 -- entity chains, so it is preferable to start from the names table as
194 -- well. If the entity found is overloadable, we must collect all other
195 -- interpretations that are defined in the scope denoted by the prefix.
197 -- For records, protected types, and tasks, their local entities are
198 -- removed from visibility chains on exit from the corresponding scope.
199 -- From the outside, these entities are always accessed by selected
200 -- notation, and the entity chain for the record type, protected type,
201 -- etc. is traversed sequentially in order to find the designated entity.
203 -- The discriminants of a type and the operations of a protected type or
204 -- task are unchained on exit from the first view of the type, (such as
205 -- a private or incomplete type declaration, or a protected type speci-
206 -- fication) and re-chained when compiling the second view.
208 -- In the case of operators, we do not make operators on derived types
209 -- explicit. As a result, the notation P."+" may denote either a user-
210 -- defined function with name "+", or else an implicit declaration of the
211 -- operator "+" in package P. The resolution of expanded names always
212 -- tries to resolve an operator name as such an implicitly defined entity,
213 -- in addition to looking for explicit declarations.
215 -- All forms of names that denote entities (simple names, expanded names,
216 -- character literals in some cases) have a Entity attribute, which
217 -- identifies the entity denoted by the name.
219 ---------------------
220 -- The Scope Stack --
221 ---------------------
223 -- The Scope stack keeps track of the scopes currently been compiled.
224 -- Every entity that contains declarations (including records) is placed
225 -- on the scope stack while it is being processed, and removed at the end.
226 -- Whenever a non-package scope is exited, the entities defined therein
227 -- are removed from the visibility table, so that entities in outer scopes
228 -- become visible (see previous description). On entry to Sem, the scope
229 -- stack only contains the package Standard. As usual, subunits complicate
230 -- this picture ever so slightly.
232 -- The Rtsfind mechanism can force a call to Semantics while another
233 -- compilation is in progress. The unit retrieved by Rtsfind must be
234 -- compiled in its own context, and has no access to the visibility of
235 -- the unit currently being compiled. The procedures Save_Scope_Stack and
236 -- Restore_Scope_Stack make entities in current open scopes invisible
237 -- before compiling the retrieved unit, and restore the compilation
238 -- environment afterwards.
240 ------------------------
241 -- Compiling subunits --
242 ------------------------
244 -- Subunits must be compiled in the environment of the corresponding stub,
245 -- that is to say with the same visibility into the parent (and its
246 -- context) that is available at the point of the stub declaration, but
247 -- with the additional visibility provided by the context clause of the
248 -- subunit itself. As a result, compilation of a subunit forces compilation
249 -- of the parent (see description in lib-). At the point of the stub
250 -- declaration, Analyze is called recursively to compile the proper body of
251 -- the subunit, but without reinitializing the names table, nor the scope
252 -- stack (i.e. standard is not pushed on the stack). In this fashion the
253 -- context of the subunit is added to the context of the parent, and the
254 -- subunit is compiled in the correct environment. Note that in the course
255 -- of processing the context of a subunit, Standard will appear twice on
256 -- the scope stack: once for the parent of the subunit, and once for the
257 -- unit in the context clause being compiled. However, the two sets of
258 -- entities are not linked by homonym chains, so that the compilation of
259 -- any context unit happens in a fresh visibility environment.
261 -------------------------------
262 -- Processing of USE Clauses --
263 -------------------------------
265 -- Every defining occurrence has a flag indicating if it is potentially use
266 -- visible. Resolution of simple names examines this flag. The processing
267 -- of use clauses consists in setting this flag on all visible entities
268 -- defined in the corresponding package. On exit from the scope of the use
269 -- clause, the corresponding flag must be reset. However, a package may
270 -- appear in several nested use clauses (pathological but legal, alas)
271 -- which forces us to use a slightly more involved scheme:
273 -- a) The defining occurrence for a package holds a flag -In_Use- to
274 -- indicate that it is currently in the scope of a use clause. If a
275 -- redundant use clause is encountered, then the corresponding occurrence
276 -- of the package name is flagged -Redundant_Use-.
278 -- b) On exit from a scope, the use clauses in its declarative part are
279 -- scanned. The visibility flag is reset in all entities declared in
280 -- package named in a use clause, as long as the package is not flagged
281 -- as being in a redundant use clause (in which case the outer use
282 -- clause is still in effect, and the direct visibility of its entities
283 -- must be retained).
285 -- Note that entities are not removed from their homonym chains on exit
286 -- from the package specification. A subsequent use clause does not need
287 -- to rechain the visible entities, but only to establish their direct
288 -- visibility.
290 -----------------------------------
291 -- Handling private declarations --
292 -----------------------------------
294 -- The principle that each entity has a single defining occurrence clashes
295 -- with the presence of two separate definitions for private types: the
296 -- first is the private type declaration, and second is the full type
297 -- declaration. It is important that all references to the type point to
298 -- the same defining occurrence, namely the first one. To enforce the two
299 -- separate views of the entity, the corresponding information is swapped
300 -- between the two declarations. Outside of the package, the defining
301 -- occurrence only contains the private declaration information, while in
302 -- the private part and the body of the package the defining occurrence
303 -- contains the full declaration. To simplify the swap, the defining
304 -- occurrence that currently holds the private declaration points to the
305 -- full declaration. During semantic processing the defining occurrence
306 -- also points to a list of private dependents, that is to say access types
307 -- or composite types whose designated types or component types are
308 -- subtypes or derived types of the private type in question. After the
309 -- full declaration has been seen, the private dependents are updated to
310 -- indicate that they have full definitions.
312 ------------------------------------
313 -- Handling of Undefined Messages --
314 ------------------------------------
316 -- In normal mode, only the first use of an undefined identifier generates
317 -- a message. The table Urefs is used to record error messages that have
318 -- been issued so that second and subsequent ones do not generate further
319 -- messages. However, the second reference causes text to be added to the
320 -- original undefined message noting "(more references follow)". The
321 -- full error list option (-gnatf) forces messages to be generated for
322 -- every reference and disconnects the use of this table.
324 type Uref_Entry is record
325 Node : Node_Id;
326 -- Node for identifier for which original message was posted. The
327 -- Chars field of this identifier is used to detect later references
328 -- to the same identifier.
330 Err : Error_Msg_Id;
331 -- Records error message Id of original undefined message. Reset to
332 -- No_Error_Msg after the second occurrence, where it is used to add
333 -- text to the original message as described above.
335 Nvis : Boolean;
336 -- Set if the message is not visible rather than undefined
338 Loc : Source_Ptr;
339 -- Records location of error message. Used to make sure that we do
340 -- not consider a, b : undefined as two separate instances, which
341 -- would otherwise happen, since the parser converts this sequence
342 -- to a : undefined; b : undefined.
344 end record;
346 package Urefs is new Table.Table (
347 Table_Component_Type => Uref_Entry,
348 Table_Index_Type => Nat,
349 Table_Low_Bound => 1,
350 Table_Initial => 10,
351 Table_Increment => 100,
352 Table_Name => "Urefs");
354 Candidate_Renaming : Entity_Id;
355 -- Holds a candidate interpretation that appears in a subprogram renaming
356 -- declaration and does not match the given specification, but matches at
357 -- least on the first formal. Allows better error message when given
358 -- specification omits defaulted parameters, a common error.
360 -----------------------
361 -- Local Subprograms --
362 -----------------------
364 procedure Analyze_Generic_Renaming
365 (N : Node_Id;
366 K : Entity_Kind);
367 -- Common processing for all three kinds of generic renaming declarations.
368 -- Enter new name and indicate that it renames the generic unit.
370 procedure Analyze_Renamed_Character
371 (N : Node_Id;
372 New_S : Entity_Id;
373 Is_Body : Boolean);
374 -- Renamed entity is given by a character literal, which must belong
375 -- to the return type of the new entity. Is_Body indicates whether the
376 -- declaration is a renaming_as_body. If the original declaration has
377 -- already been frozen (because of an intervening body, e.g.) the body of
378 -- the function must be built now. The same applies to the following
379 -- various renaming procedures.
381 procedure Analyze_Renamed_Dereference
382 (N : Node_Id;
383 New_S : Entity_Id;
384 Is_Body : Boolean);
385 -- Renamed entity is given by an explicit dereference. Prefix must be a
386 -- conformant access_to_subprogram type.
388 procedure Analyze_Renamed_Entry
389 (N : Node_Id;
390 New_S : Entity_Id;
391 Is_Body : Boolean);
392 -- If the renamed entity in a subprogram renaming is an entry or protected
393 -- subprogram, build a body for the new entity whose only statement is a
394 -- call to the renamed entity.
396 procedure Analyze_Renamed_Family_Member
397 (N : Node_Id;
398 New_S : Entity_Id;
399 Is_Body : Boolean);
400 -- Used when the renamed entity is an indexed component. The prefix must
401 -- denote an entry family.
403 procedure Analyze_Renamed_Primitive_Operation
404 (N : Node_Id;
405 New_S : Entity_Id;
406 Is_Body : Boolean);
407 -- If the renamed entity in a subprogram renaming is a primitive operation
408 -- or a class-wide operation in prefix form, save the target object,
409 -- which must be added to the list of actuals in any subsequent call.
410 -- The renaming operation is intrinsic because the compiler must in
411 -- fact generate a wrapper for it (6.3.1 (10 1/2)).
413 procedure Attribute_Renaming (N : Node_Id);
414 -- Analyze renaming of attribute as subprogram. The renaming declaration N
415 -- is rewritten as a subprogram body that returns the attribute reference
416 -- applied to the formals of the function.
418 procedure Set_Entity_Or_Discriminal (N : Node_Id; E : Entity_Id);
419 -- Set Entity, with style check if need be. For a discriminant reference,
420 -- replace by the corresponding discriminal, i.e. the parameter of the
421 -- initialization procedure that corresponds to the discriminant.
423 procedure Check_Frozen_Renaming (N : Node_Id; Subp : Entity_Id);
424 -- A renaming_as_body may occur after the entity of the original decla-
425 -- ration has been frozen. In that case, the body of the new entity must
426 -- be built now, because the usual mechanism of building the renamed
427 -- body at the point of freezing will not work. Subp is the subprogram
428 -- for which N provides the Renaming_As_Body.
430 procedure Check_In_Previous_With_Clause (N, Nam : Node_Id);
431 -- N is a use_package clause and Nam the package name, or N is a use_type
432 -- clause and Nam is the prefix of the type name. In either case, verify
433 -- that the package is visible at that point in the context: either it
434 -- appears in a previous with_clause, or because it is a fully qualified
435 -- name and the root ancestor appears in a previous with_clause.
437 procedure Check_Library_Unit_Renaming (N : Node_Id; Old_E : Entity_Id);
438 -- Verify that the entity in a renaming declaration that is a library unit
439 -- is itself a library unit and not a nested unit or subunit. Also check
440 -- that if the renaming is a child unit of a generic parent, then the
441 -- renamed unit must also be a child unit of that parent. Finally, verify
442 -- that a renamed generic unit is not an implicit child declared within
443 -- an instance of the parent.
445 procedure Chain_Use_Clause (N : Node_Id);
446 -- Chain use clause onto list of uses clauses headed by First_Use_Clause in
447 -- the proper scope table entry. This is usually the current scope, but it
448 -- will be an inner scope when installing the use clauses of the private
449 -- declarations of a parent unit prior to compiling the private part of a
450 -- child unit. This chain is traversed when installing/removing use clauses
451 -- when compiling a subunit or instantiating a generic body on the fly,
452 -- when it is necessary to save and restore full environments.
454 function Enclosing_Instance return Entity_Id;
455 -- In an instance nested within another one, several semantic checks are
456 -- unnecessary because the legality of the nested instance has been checked
457 -- in the enclosing generic unit. This applies in particular to legality
458 -- checks on actuals for formal subprograms of the inner instance, which
459 -- are checked as subprogram renamings, and may be complicated by confusion
460 -- in private/full views. This function returns the instance enclosing the
461 -- current one if there is such, else it returns Empty.
463 -- If the renaming determines the entity for the default of a formal
464 -- subprogram nested within another instance, choose the innermost
465 -- candidate. This is because if the formal has a box, and we are within
466 -- an enclosing instance where some candidate interpretations are local
467 -- to this enclosing instance, we know that the default was properly
468 -- resolved when analyzing the generic, so we prefer the local
469 -- candidates to those that are external. This is not always the case
470 -- but is a reasonable heuristic on the use of nested generics. The
471 -- proper solution requires a full renaming model.
473 function Entity_Of_Unit (U : Node_Id) return Entity_Id;
474 -- Return the appropriate entity for determining which unit has a deeper
475 -- scope: the defining entity for U, unless U is a package instance, in
476 -- which case we retrieve the entity of the instance spec.
478 procedure Error_Missing_With_Of_Known_Unit (Pkg : Node_Id);
479 -- Display an error message denoting a "with" is missing for a given known
480 -- package Pkg with its full path name.
482 procedure Find_Expanded_Name (N : Node_Id);
483 -- The input is a selected component known to be an expanded name. Verify
484 -- legality of selector given the scope denoted by prefix, and change node
485 -- N into a expanded name with a properly set Entity field.
487 function Find_First_Use (Use_Clause : Node_Id) return Node_Id;
488 -- Find the most previous use clause (that is, the first one to appear in
489 -- the source) by traversing the previous clause chain that exists in both
490 -- N_Use_Package_Clause nodes and N_Use_Type_Clause nodes.
492 function Find_Renamed_Entity
493 (N : Node_Id;
494 Nam : Node_Id;
495 New_S : Entity_Id;
496 Is_Actual : Boolean := False) return Entity_Id;
497 -- Find the renamed entity that corresponds to the given parameter profile
498 -- in a subprogram renaming declaration. The renamed entity may be an
499 -- operator, a subprogram, an entry, or a protected operation. Is_Actual
500 -- indicates that the renaming is the one generated for an actual subpro-
501 -- gram in an instance, for which special visibility checks apply.
503 function Has_Implicit_Character_Literal (N : Node_Id) return Boolean;
504 -- Find a type derived from Character or Wide_Character in the prefix of N.
505 -- Used to resolved qualified names whose selector is a character literal.
507 function Has_Private_With (E : Entity_Id) return Boolean;
508 -- Ada 2005 (AI-262): Determines if the current compilation unit has a
509 -- private with on E.
511 function Has_Components (Typ : Entity_Id) return Boolean;
512 -- Determine if given type has components, i.e. is either a record type or
513 -- type or a type that has discriminants.
515 function Has_Implicit_Operator (N : Node_Id) return Boolean;
516 -- N is an expanded name whose selector is an operator name (e.g. P."+").
517 -- Determine if N denotes an operator implicitly declared in prefix P: P's
518 -- declarative part contains an implicit declaration of an operator if it
519 -- has a declaration of a type to which one of the predefined operators
520 -- apply. The existence of this routine is an implementation artifact. A
521 -- more straightforward but more space-consuming choice would be to make
522 -- all inherited operators explicit in the symbol table.
524 procedure Inherit_Renamed_Profile (New_S : Entity_Id; Old_S : Entity_Id);
525 -- A subprogram defined by a renaming declaration inherits the parameter
526 -- profile of the renamed entity. The subtypes given in the subprogram
527 -- specification are discarded and replaced with those of the renamed
528 -- subprogram, which are then used to recheck the default values.
530 function Most_Descendant_Use_Clause
531 (Clause1 : Entity_Id;
532 Clause2 : Entity_Id) return Entity_Id;
533 -- Determine which use clause parameter is the most descendant in terms of
534 -- scope.
536 procedure Premature_Usage (N : Node_Id);
537 -- Diagnose usage of an entity before it is visible
539 procedure Use_One_Package
540 (N : Node_Id;
541 Pack_Name : Entity_Id := Empty;
542 Force : Boolean := False);
543 -- Make visible entities declared in package P potentially use-visible
544 -- in the current context. Also used in the analysis of subunits, when
545 -- re-installing use clauses of parent units. N is the use_clause that
546 -- names P (and possibly other packages).
548 procedure Use_One_Type
549 (Id : Node_Id;
550 Installed : Boolean := False;
551 Force : Boolean := False);
552 -- Id is the subtype mark from a use_type_clause. This procedure makes
553 -- the primitive operators of the type potentially use-visible. The
554 -- boolean flag Installed indicates that the clause is being reinstalled
555 -- after previous analysis, and primitive operations are already chained
556 -- on the Used_Operations list of the clause.
558 procedure Write_Info;
559 -- Write debugging information on entities declared in current scope
561 --------------------------------
562 -- Analyze_Exception_Renaming --
563 --------------------------------
565 -- The language only allows a single identifier, but the tree holds an
566 -- identifier list. The parser has already issued an error message if
567 -- there is more than one element in the list.
569 procedure Analyze_Exception_Renaming (N : Node_Id) is
570 Id : constant Entity_Id := Defining_Entity (N);
571 Nam : constant Node_Id := Name (N);
573 begin
574 Enter_Name (Id);
575 Analyze (Nam);
577 Mutate_Ekind (Id, E_Exception);
578 Set_Etype (Id, Standard_Exception_Type);
579 Set_Is_Pure (Id, Is_Pure (Current_Scope));
581 if Is_Entity_Name (Nam)
582 and then Present (Entity (Nam))
583 and then Ekind (Entity (Nam)) = E_Exception
584 then
585 if Present (Renamed_Entity (Entity (Nam))) then
586 Set_Renamed_Entity (Id, Renamed_Entity (Entity (Nam)));
587 else
588 Set_Renamed_Entity (Id, Entity (Nam));
589 end if;
591 -- The exception renaming declaration may become Ghost if it renames
592 -- a Ghost entity.
594 Mark_Ghost_Renaming (N, Entity (Nam));
595 else
596 Error_Msg_N ("invalid exception name in renaming", Nam);
597 end if;
599 -- Implementation-defined aspect specifications can appear in a renaming
600 -- declaration, but not language-defined ones. The call to procedure
601 -- Analyze_Aspect_Specifications will take care of this error check.
603 if Has_Aspects (N) then
604 Analyze_Aspect_Specifications (N, Id);
605 end if;
606 end Analyze_Exception_Renaming;
608 ---------------------------
609 -- Analyze_Expanded_Name --
610 ---------------------------
612 procedure Analyze_Expanded_Name (N : Node_Id) is
613 begin
614 -- If the entity pointer is already set, this is an internal node, or a
615 -- node that is analyzed more than once, after a tree modification. In
616 -- such a case there is no resolution to perform, just set the type. In
617 -- either case, start by analyzing the prefix.
619 Analyze (Prefix (N));
621 if Present (Entity (N)) then
622 if Is_Type (Entity (N)) then
623 Set_Etype (N, Entity (N));
624 else
625 Set_Etype (N, Etype (Entity (N)));
626 end if;
628 else
629 Find_Expanded_Name (N);
630 end if;
632 -- In either case, propagate dimension of entity to expanded name
634 Analyze_Dimension (N);
635 end Analyze_Expanded_Name;
637 ---------------------------------------
638 -- Analyze_Generic_Function_Renaming --
639 ---------------------------------------
641 procedure Analyze_Generic_Function_Renaming (N : Node_Id) is
642 begin
643 Analyze_Generic_Renaming (N, E_Generic_Function);
644 end Analyze_Generic_Function_Renaming;
646 --------------------------------------
647 -- Analyze_Generic_Package_Renaming --
648 --------------------------------------
650 procedure Analyze_Generic_Package_Renaming (N : Node_Id) is
651 begin
652 -- Test for the Text_IO special unit case here, since we may be renaming
653 -- one of the subpackages of Text_IO, then join common routine.
655 Check_Text_IO_Special_Unit (Name (N));
657 Analyze_Generic_Renaming (N, E_Generic_Package);
658 end Analyze_Generic_Package_Renaming;
660 ----------------------------------------
661 -- Analyze_Generic_Procedure_Renaming --
662 ----------------------------------------
664 procedure Analyze_Generic_Procedure_Renaming (N : Node_Id) is
665 begin
666 Analyze_Generic_Renaming (N, E_Generic_Procedure);
667 end Analyze_Generic_Procedure_Renaming;
669 ------------------------------
670 -- Analyze_Generic_Renaming --
671 ------------------------------
673 procedure Analyze_Generic_Renaming
674 (N : Node_Id;
675 K : Entity_Kind)
677 New_P : constant Entity_Id := Defining_Entity (N);
678 Inst : Boolean := False;
679 Old_P : Entity_Id;
681 begin
682 if Name (N) = Error then
683 return;
684 end if;
686 Generate_Definition (New_P);
688 if Current_Scope /= Standard_Standard then
689 Set_Is_Pure (New_P, Is_Pure (Current_Scope));
690 end if;
692 if Nkind (Name (N)) = N_Selected_Component then
693 Check_Generic_Child_Unit (Name (N), Inst);
694 else
695 Analyze (Name (N));
696 end if;
698 if not Is_Entity_Name (Name (N)) then
699 Error_Msg_N ("expect entity name in renaming declaration", Name (N));
700 Old_P := Any_Id;
701 else
702 Old_P := Entity (Name (N));
703 end if;
705 Enter_Name (New_P);
706 Mutate_Ekind (New_P, K);
708 if Etype (Old_P) = Any_Type then
709 null;
711 elsif Ekind (Old_P) /= K then
712 Error_Msg_N ("invalid generic unit name", Name (N));
714 else
715 if Present (Renamed_Entity (Old_P)) then
716 Set_Renamed_Entity (New_P, Renamed_Entity (Old_P));
717 else
718 Set_Renamed_Entity (New_P, Old_P);
719 end if;
721 -- The generic renaming declaration may become Ghost if it renames a
722 -- Ghost entity.
724 Mark_Ghost_Renaming (N, Old_P);
726 Set_Is_Pure (New_P, Is_Pure (Old_P));
727 Set_Is_Preelaborated (New_P, Is_Preelaborated (Old_P));
729 Set_Etype (New_P, Etype (Old_P));
730 Set_Has_Completion (New_P);
732 if In_Open_Scopes (Old_P) then
733 Error_Msg_N ("within its scope, generic denotes its instance", N);
734 end if;
736 -- For subprograms, propagate the Intrinsic flag, to allow, e.g.
737 -- renamings and subsequent instantiations of Unchecked_Conversion.
739 if Is_Generic_Subprogram (Old_P) then
740 Set_Is_Intrinsic_Subprogram
741 (New_P, Is_Intrinsic_Subprogram (Old_P));
742 end if;
744 Check_Library_Unit_Renaming (N, Old_P);
745 end if;
747 -- Implementation-defined aspect specifications can appear in a renaming
748 -- declaration, but not language-defined ones. The call to procedure
749 -- Analyze_Aspect_Specifications will take care of this error check.
751 if Has_Aspects (N) then
752 Analyze_Aspect_Specifications (N, New_P);
753 end if;
754 end Analyze_Generic_Renaming;
756 -----------------------------
757 -- Analyze_Object_Renaming --
758 -----------------------------
760 procedure Analyze_Object_Renaming (N : Node_Id) is
761 Id : constant Entity_Id := Defining_Identifier (N);
762 Loc : constant Source_Ptr := Sloc (N);
763 Nam : constant Node_Id := Name (N);
764 Is_Object_Ref : Boolean;
765 Dec : Node_Id;
766 T : Entity_Id;
767 T2 : Entity_Id;
768 Q : Node_Id;
770 procedure Check_Constrained_Object;
771 -- If the nominal type is unconstrained but the renamed object is
772 -- constrained, as can happen with renaming an explicit dereference or
773 -- a function return, build a constrained subtype from the object. If
774 -- the renaming is for a formal in an accept statement, the analysis
775 -- has already established its actual subtype. This is only relevant
776 -- if the renamed object is an explicit dereference.
778 function Get_Object_Name (Nod : Node_Id) return Node_Id;
779 -- Obtain the name of the object from node Nod which is being renamed by
780 -- the object renaming declaration N.
782 function Find_Raise_Node (N : Node_Id) return Traverse_Result;
783 -- Process one node in search for N_Raise_xxx_Error nodes.
784 -- Return Abandon if found, OK otherwise.
786 ---------------------
787 -- Find_Raise_Node --
788 ---------------------
790 function Find_Raise_Node (N : Node_Id) return Traverse_Result is
791 begin
792 if Nkind (N) in N_Raise_xxx_Error then
793 return Abandon;
794 else
795 return OK;
796 end if;
797 end Find_Raise_Node;
799 ------------------------
800 -- No_Raise_xxx_Error --
801 ------------------------
803 function No_Raise_xxx_Error is new Traverse_Func (Find_Raise_Node);
804 -- Traverse tree to look for a N_Raise_xxx_Error node and returns
805 -- Abandon if so and OK if none found.
807 ------------------------------
808 -- Check_Constrained_Object --
809 ------------------------------
811 procedure Check_Constrained_Object is
812 Typ : constant Entity_Id := Etype (Nam);
813 Subt : Entity_Id;
814 Loop_Scheme : Node_Id;
816 begin
817 if Nkind (Nam) in N_Function_Call | N_Explicit_Dereference
818 and then Is_Composite_Type (Typ)
819 and then not Is_Constrained (Typ)
820 and then not Has_Unknown_Discriminants (Typ)
821 and then Expander_Active
822 then
823 -- If Actual_Subtype is already set, nothing to do
825 if Ekind (Id) in E_Variable | E_Constant
826 and then Present (Actual_Subtype (Id))
827 then
828 null;
830 -- A renaming of an unchecked union has no actual subtype
832 elsif Is_Unchecked_Union (Typ) then
833 null;
835 -- If a record is limited its size is invariant. This is the case
836 -- in particular with record types with an access discriminant
837 -- that are used in iterators. This is an optimization, but it
838 -- also prevents typing anomalies when the prefix is further
839 -- expanded.
841 -- Note that we cannot just use the Is_Limited_Record flag because
842 -- it does not apply to records with limited components, for which
843 -- this syntactic flag is not set, but whose size is also fixed.
845 -- Note also that we need to build the constrained subtype for an
846 -- array in order to make the bounds explicit in most cases, but
847 -- not if the object comes from an extended return statement, as
848 -- this would create dangling references to them later on.
850 elsif Is_Limited_Type (Typ)
851 and then (not Is_Array_Type (Typ) or else Is_Return_Object (Id))
852 then
853 null;
855 else
856 Subt := Make_Temporary (Loc, 'T');
857 Remove_Side_Effects (Nam);
858 Insert_Action (N,
859 Make_Subtype_Declaration (Loc,
860 Defining_Identifier => Subt,
861 Subtype_Indication =>
862 Make_Subtype_From_Expr (Nam, Typ)));
863 Rewrite (Subtype_Mark (N), New_Occurrence_Of (Subt, Loc));
864 Set_Etype (Nam, Subt);
866 -- Suppress discriminant checks on this subtype if the original
867 -- type has defaulted discriminants and Id is a "for of" loop
868 -- iterator.
870 if Has_Defaulted_Discriminants (Typ)
871 and then Nkind (Original_Node (Parent (N))) = N_Loop_Statement
872 then
873 Loop_Scheme := Iteration_Scheme (Original_Node (Parent (N)));
875 if Present (Loop_Scheme)
876 and then Present (Iterator_Specification (Loop_Scheme))
877 and then
878 Defining_Identifier
879 (Iterator_Specification (Loop_Scheme)) = Id
880 then
881 Set_Checks_May_Be_Suppressed (Subt);
882 Push_Local_Suppress_Stack_Entry
883 (Entity => Subt,
884 Check => Discriminant_Check,
885 Suppress => True);
886 end if;
887 end if;
889 -- Freeze subtype at once, to prevent order of elaboration
890 -- issues in the backend. The renamed object exists, so its
891 -- type is already frozen in any case.
893 Freeze_Before (N, Subt);
894 end if;
895 end if;
896 end Check_Constrained_Object;
898 ---------------------
899 -- Get_Object_Name --
900 ---------------------
902 function Get_Object_Name (Nod : Node_Id) return Node_Id is
903 Obj_Nam : Node_Id;
905 begin
906 Obj_Nam := Nod;
907 while Present (Obj_Nam) loop
908 case Nkind (Obj_Nam) is
909 when N_Attribute_Reference
910 | N_Explicit_Dereference
911 | N_Indexed_Component
912 | N_Slice
914 Obj_Nam := Prefix (Obj_Nam);
916 when N_Selected_Component =>
917 Obj_Nam := Selector_Name (Obj_Nam);
919 when N_Qualified_Expression | N_Type_Conversion =>
920 Obj_Nam := Expression (Obj_Nam);
922 when others =>
923 exit;
924 end case;
925 end loop;
927 return Obj_Nam;
928 end Get_Object_Name;
930 -- Start of processing for Analyze_Object_Renaming
932 begin
933 if Nam = Error then
934 return;
935 end if;
937 Set_Is_Pure (Id, Is_Pure (Current_Scope));
938 Enter_Name (Id);
940 -- The renaming of a component that depends on a discriminant requires
941 -- an actual subtype, because in subsequent use of the object Gigi will
942 -- be unable to locate the actual bounds. This explicit step is required
943 -- when the renaming is generated in removing side effects of an
944 -- already-analyzed expression.
946 if Nkind (Nam) = N_Selected_Component and then Analyzed (Nam) then
948 -- The object renaming declaration may become Ghost if it renames a
949 -- Ghost entity.
951 if Is_Entity_Name (Nam) then
952 Mark_Ghost_Renaming (N, Entity (Nam));
953 end if;
955 T := Etype (Nam);
956 Dec := Build_Actual_Subtype_Of_Component (Etype (Nam), Nam);
958 if Present (Dec) then
959 Insert_Action (N, Dec);
960 T := Defining_Identifier (Dec);
961 Set_Etype (Nam, T);
962 end if;
963 elsif Present (Subtype_Mark (N))
964 or else No (Access_Definition (N))
965 then
966 if Present (Subtype_Mark (N)) then
967 Find_Type (Subtype_Mark (N));
968 T := Entity (Subtype_Mark (N));
969 Analyze (Nam);
971 -- AI12-0275: Case of object renaming without a subtype_mark
973 else
974 Analyze (Nam);
976 -- Normal case of no overloading in object name
978 if not Is_Overloaded (Nam) then
980 -- Catch error cases (such as attempting to rename a procedure
981 -- or package) using the shorthand form.
983 if No (Etype (Nam))
984 or else Etype (Nam) = Standard_Void_Type
985 then
986 Error_Msg_N
987 ("object name or value expected in renaming", Nam);
989 Mutate_Ekind (Id, E_Variable);
990 Set_Etype (Id, Any_Type);
992 return;
994 else
995 T := Etype (Nam);
996 end if;
998 -- Case of overloaded name, which will be illegal if there's more
999 -- than one acceptable interpretation (such as overloaded function
1000 -- calls).
1002 else
1003 declare
1004 I : Interp_Index;
1005 I1 : Interp_Index;
1006 It : Interp;
1007 It1 : Interp;
1008 Nam1 : Entity_Id;
1010 begin
1011 -- More than one candidate interpretation is available
1013 -- Remove procedure calls, which syntactically cannot appear
1014 -- in this context, but which cannot be removed by type
1015 -- checking, because the context does not impose a type.
1017 Get_First_Interp (Nam, I, It);
1018 while Present (It.Typ) loop
1019 if It.Typ = Standard_Void_Type then
1020 Remove_Interp (I);
1021 end if;
1023 Get_Next_Interp (I, It);
1024 end loop;
1026 Get_First_Interp (Nam, I, It);
1027 I1 := I;
1028 It1 := It;
1030 -- If there's no type present, we have an error case (such
1031 -- as overloaded procedures named in the object renaming).
1033 if No (It.Typ) then
1034 Error_Msg_N
1035 ("object name or value expected in renaming", Nam);
1037 Mutate_Ekind (Id, E_Variable);
1038 Set_Etype (Id, Any_Type);
1040 return;
1041 end if;
1043 Get_Next_Interp (I, It);
1045 if Present (It.Typ) then
1046 Nam1 := It1.Nam;
1047 It1 := Disambiguate (Nam, I1, I, Any_Type);
1049 if It1 = No_Interp then
1050 Error_Msg_N ("ambiguous name in object renaming", Nam);
1052 Error_Msg_Sloc := Sloc (It.Nam);
1053 Error_Msg_N ("\\possible interpretation#!", Nam);
1055 Error_Msg_Sloc := Sloc (Nam1);
1056 Error_Msg_N ("\\possible interpretation#!", Nam);
1058 return;
1059 end if;
1060 end if;
1062 Set_Etype (Nam, It1.Typ);
1063 T := It1.Typ;
1064 end;
1065 end if;
1067 if Etype (Nam) = Standard_Exception_Type then
1068 Error_Msg_N
1069 ("exception requires a subtype mark in renaming", Nam);
1070 return;
1071 end if;
1072 end if;
1074 -- The object renaming declaration may become Ghost if it renames a
1075 -- Ghost entity.
1077 if Is_Entity_Name (Nam) then
1078 Mark_Ghost_Renaming (N, Entity (Nam));
1079 end if;
1081 -- Check against AI12-0401 here before Resolve may rewrite Nam and
1082 -- potentially generate spurious warnings.
1084 -- In the case where the object_name is a qualified_expression with
1085 -- a nominal subtype T and whose expression is a name that denotes
1086 -- an object Q:
1087 -- * if T is an elementary subtype, then:
1088 -- * Q shall be a constant other than a dereference of an access
1089 -- type; or
1090 -- * the nominal subtype of Q shall be statically compatible with
1091 -- T; or
1092 -- * T shall statically match the base subtype of its type if
1093 -- scalar, or the first subtype of its type if an access type.
1094 -- * if T is a composite subtype, then Q shall be known to be
1095 -- constrained or T shall statically match the first subtype of
1096 -- its type.
1098 if Nkind (Nam) = N_Qualified_Expression
1099 and then Is_Object_Reference (Expression (Nam))
1100 then
1101 Q := Expression (Nam);
1103 if (Is_Elementary_Type (T)
1104 and then
1105 not ((not Is_Variable (Q)
1106 and then Nkind (Q) /= N_Explicit_Dereference)
1107 or else Subtypes_Statically_Compatible (Etype (Q), T)
1108 or else (Is_Scalar_Type (T)
1109 and then Subtypes_Statically_Match
1110 (T, Base_Type (T)))
1111 or else (Is_Access_Type (T)
1112 and then Subtypes_Statically_Match
1113 (T, First_Subtype (T)))))
1114 or else (Is_Composite_Type (T)
1115 and then
1117 -- If Q is an aggregate, Is_Constrained may not be set
1118 -- yet and its type may not be resolved yet.
1119 -- This doesn't quite correspond to the complex notion
1120 -- of "known to be constrained" but this is good enough
1121 -- for a rule which is in any case too complex.
1123 not (Is_Constrained (Etype (Q))
1124 or else Nkind (Q) = N_Aggregate
1125 or else Subtypes_Statically_Match
1126 (T, First_Subtype (T))))
1127 then
1128 Error_Msg_N
1129 ("subtype of renamed qualified expression does not " &
1130 "statically match", N);
1131 return;
1132 end if;
1133 end if;
1135 Resolve (Nam, T);
1137 -- If the renamed object is a function call of a limited type,
1138 -- the expansion of the renaming is complicated by the presence
1139 -- of various temporaries and subtypes that capture constraints
1140 -- of the renamed object. Rewrite node as an object declaration,
1141 -- whose expansion is simpler. Given that the object is limited
1142 -- there is no copy involved and no performance hit.
1144 if Nkind (Nam) = N_Function_Call
1145 and then Is_Limited_View (Etype (Nam))
1146 and then not Is_Constrained (Etype (Nam))
1147 and then Comes_From_Source (N)
1148 then
1149 Set_Etype (Id, T);
1150 Mutate_Ekind (Id, E_Constant);
1151 Rewrite (N,
1152 Make_Object_Declaration (Loc,
1153 Defining_Identifier => Id,
1154 Constant_Present => True,
1155 Object_Definition => New_Occurrence_Of (Etype (Nam), Loc),
1156 Expression => Relocate_Node (Nam)));
1157 return;
1158 end if;
1160 -- Ada 2012 (AI05-149): Reject renaming of an anonymous access object
1161 -- when renaming declaration has a named access type. The Ada 2012
1162 -- coverage rules allow an anonymous access type in the context of
1163 -- an expected named general access type, but the renaming rules
1164 -- require the types to be the same. (An exception is when the type
1165 -- of the renaming is also an anonymous access type, which can only
1166 -- happen due to a renaming created by the expander.)
1168 if Nkind (Nam) = N_Type_Conversion
1169 and then not Comes_From_Source (Nam)
1170 and then Is_Anonymous_Access_Type (Etype (Expression (Nam)))
1171 and then not Is_Anonymous_Access_Type (T)
1172 then
1173 Error_Msg_NE
1174 ("cannot rename anonymous access object "
1175 & "as a named access type", Expression (Nam), T);
1176 end if;
1178 -- Check that a class-wide object is not being renamed as an object
1179 -- of a specific type. The test for access types is needed to exclude
1180 -- cases where the renamed object is a dynamically tagged access
1181 -- result, such as occurs in certain expansions.
1183 if Is_Tagged_Type (T) then
1184 Check_Dynamically_Tagged_Expression
1185 (Expr => Nam,
1186 Typ => T,
1187 Related_Nod => N);
1188 end if;
1190 -- Ada 2005 (AI-230/AI-254): Access renaming
1192 else pragma Assert (Present (Access_Definition (N)));
1193 T :=
1194 Access_Definition
1195 (Related_Nod => N,
1196 N => Access_Definition (N));
1198 Analyze (Nam);
1200 -- The object renaming declaration may become Ghost if it renames a
1201 -- Ghost entity.
1203 if Is_Entity_Name (Nam) then
1204 Mark_Ghost_Renaming (N, Entity (Nam));
1205 end if;
1207 -- Ada 2005 AI05-105: if the declaration has an anonymous access
1208 -- type, the renamed object must also have an anonymous type, and
1209 -- this is a name resolution rule. This was implicit in the last part
1210 -- of the first sentence in 8.5.1(3/2), and is made explicit by this
1211 -- recent AI.
1213 if not Is_Overloaded (Nam) then
1214 if Ekind (Etype (Nam)) /= Ekind (T) then
1215 Error_Msg_N
1216 ("expect anonymous access type in object renaming", N);
1217 end if;
1219 else
1220 declare
1221 I : Interp_Index;
1222 It : Interp;
1223 Typ : Entity_Id := Empty;
1224 Seen : Boolean := False;
1226 begin
1227 Get_First_Interp (Nam, I, It);
1228 while Present (It.Typ) loop
1230 -- Renaming is ambiguous if more than one candidate
1231 -- interpretation is type-conformant with the context.
1233 if Ekind (It.Typ) = Ekind (T) then
1234 if Ekind (T) = E_Anonymous_Access_Subprogram_Type
1235 and then
1236 Type_Conformant
1237 (Designated_Type (T), Designated_Type (It.Typ))
1238 then
1239 if not Seen then
1240 Seen := True;
1241 else
1242 Error_Msg_N
1243 ("ambiguous expression in renaming", Nam);
1244 end if;
1246 elsif Ekind (T) = E_Anonymous_Access_Type
1247 and then
1248 Covers (Designated_Type (T), Designated_Type (It.Typ))
1249 then
1250 if not Seen then
1251 Seen := True;
1252 else
1253 Error_Msg_N
1254 ("ambiguous expression in renaming", Nam);
1255 end if;
1256 end if;
1258 if Covers (T, It.Typ) then
1259 Typ := It.Typ;
1260 Set_Etype (Nam, Typ);
1261 Set_Is_Overloaded (Nam, False);
1262 end if;
1263 end if;
1265 Get_Next_Interp (I, It);
1266 end loop;
1267 end;
1268 end if;
1270 Resolve (Nam, T);
1272 -- Do not perform the legality checks below when the resolution of
1273 -- the renaming name failed because the associated type is Any_Type.
1275 if Etype (Nam) = Any_Type then
1276 null;
1278 -- Ada 2005 (AI-231): In the case where the type is defined by an
1279 -- access_definition, the renamed entity shall be of an access-to-
1280 -- constant type if and only if the access_definition defines an
1281 -- access-to-constant type. ARM 8.5.1(4)
1283 elsif Constant_Present (Access_Definition (N))
1284 and then not Is_Access_Constant (Etype (Nam))
1285 then
1286 Error_Msg_N
1287 ("(Ada 2005): the renamed object is not access-to-constant "
1288 & "(RM 8.5.1(6))", N);
1290 elsif not Constant_Present (Access_Definition (N))
1291 and then Is_Access_Constant (Etype (Nam))
1292 then
1293 Error_Msg_N
1294 ("(Ada 2005): the renamed object is not access-to-variable "
1295 & "(RM 8.5.1(6))", N);
1296 end if;
1298 if Is_Access_Subprogram_Type (Etype (Nam)) then
1299 Check_Subtype_Conformant
1300 (Designated_Type (T), Designated_Type (Etype (Nam)));
1302 elsif not Subtypes_Statically_Match
1303 (Designated_Type (T),
1304 Available_View (Designated_Type (Etype (Nam))))
1305 then
1306 Error_Msg_N
1307 ("subtype of renamed object does not statically match", N);
1308 end if;
1309 end if;
1311 -- Special processing for renaming function return object. Some errors
1312 -- and warnings are produced only for calls that come from source.
1314 if Nkind (Nam) = N_Function_Call then
1315 case Ada_Version is
1317 -- Usage is illegal in Ada 83, but renamings are also introduced
1318 -- during expansion, and error does not apply to those.
1320 when Ada_83 =>
1321 if Comes_From_Source (N) then
1322 Error_Msg_N
1323 ("(Ada 83) cannot rename function return object", Nam);
1324 end if;
1326 -- In Ada 95, warn for odd case of renaming parameterless function
1327 -- call if this is not a limited type (where this is useful).
1329 when others =>
1330 if Warn_On_Object_Renames_Function
1331 and then No (Parameter_Associations (Nam))
1332 and then not Is_Limited_Type (Etype (Nam))
1333 and then Comes_From_Source (Nam)
1334 then
1335 Error_Msg_N
1336 ("renaming function result object is suspicious?.r?", Nam);
1337 Error_Msg_NE
1338 ("\function & will be called only once?.r?", Nam,
1339 Entity (Name (Nam)));
1340 Error_Msg_N -- CODEFIX
1341 ("\suggest using an initialized constant object "
1342 & "instead?.r?", Nam);
1343 end if;
1344 end case;
1345 end if;
1347 Check_Constrained_Object;
1349 -- An object renaming requires an exact match of the type. Class-wide
1350 -- matching is not allowed.
1352 if Is_Class_Wide_Type (T)
1353 and then Base_Type (Etype (Nam)) /= Base_Type (T)
1354 then
1355 Wrong_Type (Nam, T);
1356 end if;
1358 -- We must search for an actual subtype here so that the bounds of
1359 -- objects of unconstrained types don't get dropped on the floor - such
1360 -- as with renamings of formal parameters.
1362 T2 := Get_Actual_Subtype_If_Available (Nam);
1364 -- Ada 2005 (AI-326): Handle wrong use of incomplete type
1366 if Nkind (Nam) = N_Explicit_Dereference
1367 and then Ekind (Etype (T2)) = E_Incomplete_Type
1368 then
1369 Error_Msg_NE ("invalid use of incomplete type&", Id, T2);
1370 return;
1372 elsif Ekind (Etype (T)) = E_Incomplete_Type then
1373 Error_Msg_NE ("invalid use of incomplete type&", Id, T);
1374 return;
1375 end if;
1377 if Ada_Version >= Ada_2005 and then Nkind (Nam) in N_Has_Entity then
1378 declare
1379 Nam_Ent : constant Entity_Id := Entity (Get_Object_Name (Nam));
1380 Nam_Decl : constant Node_Id := Declaration_Node (Nam_Ent);
1382 begin
1383 if Has_Null_Exclusion (N)
1384 and then not Has_Null_Exclusion (Nam_Decl)
1385 then
1386 -- Ada 2005 (AI-423): If the object name denotes a generic
1387 -- formal object of a generic unit G, and the object renaming
1388 -- declaration occurs within the body of G or within the body
1389 -- of a generic unit declared within the declarative region
1390 -- of G, then the declaration of the formal object of G must
1391 -- have a null exclusion or a null-excluding subtype.
1393 if Is_Formal_Object (Nam_Ent)
1394 and then In_Generic_Scope (Id)
1395 then
1396 if not Can_Never_Be_Null (Etype (Nam_Ent)) then
1397 Error_Msg_N
1398 ("object does not exclude `NULL` "
1399 & "(RM 8.5.1(4.6/2))", N);
1401 elsif In_Package_Body (Scope (Id)) then
1402 Error_Msg_N
1403 ("formal object does not have a null exclusion"
1404 & "(RM 8.5.1(4.6/2))", N);
1405 end if;
1407 -- Ada 2005 (AI-423): Otherwise, the subtype of the object name
1408 -- shall exclude null.
1410 elsif not Can_Never_Be_Null (Etype (Nam_Ent)) then
1411 Error_Msg_N
1412 ("object does not exclude `NULL` "
1413 & "(RM 8.5.1(4.6/2))", N);
1415 -- An instance is illegal if it contains a renaming that
1416 -- excludes null, and the actual does not. The renaming
1417 -- declaration has already indicated that the declaration
1418 -- of the renamed actual in the instance will raise
1419 -- constraint_error.
1421 elsif Nkind (Nam_Decl) = N_Object_Declaration
1422 and then In_Instance
1423 and then
1424 Present (Corresponding_Generic_Association (Nam_Decl))
1425 and then Nkind (Expression (Nam_Decl)) =
1426 N_Raise_Constraint_Error
1427 then
1428 Error_Msg_N
1429 ("actual does not exclude `NULL` (RM 8.5.1(4.6/2))", N);
1431 -- Finally, if there is a null exclusion, the subtype mark
1432 -- must not be null-excluding.
1434 elsif No (Access_Definition (N))
1435 and then Can_Never_Be_Null (T)
1436 then
1437 Error_Msg_NE
1438 ("`NOT NULL` not allowed (& already excludes null)",
1439 N, T);
1441 end if;
1443 elsif Can_Never_Be_Null (T)
1444 and then not Can_Never_Be_Null (Etype (Nam_Ent))
1445 then
1446 Error_Msg_N
1447 ("object does not exclude `NULL` (RM 8.5.1(4.6/2))", N);
1449 elsif Has_Null_Exclusion (N)
1450 and then No (Access_Definition (N))
1451 and then Can_Never_Be_Null (T)
1452 then
1453 Error_Msg_NE
1454 ("`NOT NULL` not allowed (& already excludes null)", N, T);
1455 end if;
1456 end;
1457 end if;
1459 -- Set the Ekind of the entity, unless it has been set already, as is
1460 -- the case for the iteration object over a container with no variable
1461 -- indexing. In that case it's been marked as a constant, and we do not
1462 -- want to change it to a variable.
1464 if Ekind (Id) /= E_Constant then
1465 Mutate_Ekind (Id, E_Variable);
1466 end if;
1468 Reinit_Object_Size_Align (Id);
1470 -- If N comes from source then check that the original node is an
1471 -- object reference since there may have been several rewritting and
1472 -- folding. Do not do this for N_Function_Call or N_Explicit_Dereference
1473 -- which might correspond to rewrites of e.g. N_Selected_Component
1474 -- (for example Object.Method rewriting).
1475 -- If N does not come from source then assume the tree is properly
1476 -- formed and accept any object reference. In such cases we do support
1477 -- more cases of renamings anyway, so the actual check on which renaming
1478 -- is valid is better left to the code generator as a last sanity
1479 -- check.
1481 if Comes_From_Source (N) then
1482 if Nkind (Nam) in N_Function_Call | N_Explicit_Dereference then
1483 Is_Object_Ref := Is_Object_Reference (Nam);
1484 else
1485 Is_Object_Ref := Is_Object_Reference (Original_Node (Nam));
1486 end if;
1487 else
1488 Is_Object_Ref := True;
1489 end if;
1491 if T = Any_Type or else Etype (Nam) = Any_Type then
1492 return;
1494 -- Verify that the renamed entity is an object or function call
1496 elsif Is_Object_Ref then
1497 if Comes_From_Source (N) then
1498 if Is_Dependent_Component_Of_Mutable_Object (Nam) then
1499 Error_Msg_N
1500 ("illegal renaming of discriminant-dependent component", Nam);
1501 end if;
1503 -- If the renaming comes from source and the renamed object is a
1504 -- dereference, then mark the prefix as needing debug information,
1505 -- since it might have been rewritten hence internally generated
1506 -- and Debug_Renaming_Declaration will link the renaming to it.
1508 if Nkind (Nam) = N_Explicit_Dereference
1509 and then Is_Entity_Name (Prefix (Nam))
1510 then
1511 Set_Debug_Info_Needed (Entity (Prefix (Nam)));
1512 end if;
1513 end if;
1515 -- Weird but legal, equivalent to renaming a function call. Illegal
1516 -- if the literal is the result of constant-folding an attribute
1517 -- reference that is not a function.
1519 elsif Is_Entity_Name (Nam)
1520 and then Ekind (Entity (Nam)) = E_Enumeration_Literal
1521 and then Nkind (Original_Node (Nam)) /= N_Attribute_Reference
1522 then
1523 null;
1525 -- A named number can only be renamed without a subtype mark
1527 elsif Nkind (Nam) in N_Real_Literal | N_Integer_Literal
1528 and then Present (Subtype_Mark (N))
1529 and then Present (Original_Entity (Nam))
1530 then
1531 Error_Msg_N ("incompatible types in renaming", Nam);
1533 -- AI12-0383: Names that denote values can be renamed.
1534 -- Ignore (accept) N_Raise_xxx_Error nodes in this context.
1536 elsif No_Raise_xxx_Error (Nam) = OK then
1537 Error_Msg_Ada_2022_Feature ("value in renaming", Sloc (Nam));
1538 end if;
1540 Set_Etype (Id, T2);
1542 if not Is_Variable (Nam) then
1543 Mutate_Ekind (Id, E_Constant);
1544 Set_Never_Set_In_Source (Id, True);
1545 Set_Is_True_Constant (Id, True);
1546 end if;
1548 -- The entity of the renaming declaration needs to reflect whether the
1549 -- renamed object is atomic, independent, volatile or VFA. These flags
1550 -- are set on the renamed object in the RM legality sense.
1552 Set_Is_Atomic (Id, Is_Atomic_Object (Nam));
1553 Set_Is_Independent (Id, Is_Independent_Object (Nam));
1554 Set_Is_Volatile (Id, Is_Volatile_Object_Ref (Nam));
1555 Set_Is_Volatile_Full_Access
1556 (Id, Is_Volatile_Full_Access_Object_Ref (Nam));
1558 -- Treat as volatile if we just set the Volatile flag
1560 if Is_Volatile (Id)
1562 -- Or if we are renaming an entity which was marked this way
1564 -- Are there more cases, e.g. X(J) where X is Treat_As_Volatile ???
1566 or else (Is_Entity_Name (Nam)
1567 and then Treat_As_Volatile (Entity (Nam)))
1568 then
1569 Set_Treat_As_Volatile (Id, True);
1570 end if;
1572 -- Now make the link to the renamed object
1574 Set_Renamed_Object (Id, Nam);
1576 -- Implementation-defined aspect specifications can appear in a renaming
1577 -- declaration, but not language-defined ones. The call to procedure
1578 -- Analyze_Aspect_Specifications will take care of this error check.
1580 if Has_Aspects (N) then
1581 Analyze_Aspect_Specifications (N, Id);
1582 end if;
1584 -- Deal with dimensions
1586 Analyze_Dimension (N);
1587 end Analyze_Object_Renaming;
1589 ------------------------------
1590 -- Analyze_Package_Renaming --
1591 ------------------------------
1593 procedure Analyze_Package_Renaming (N : Node_Id) is
1594 New_P : constant Entity_Id := Defining_Entity (N);
1595 Old_P : Entity_Id;
1596 Spec : Node_Id;
1598 begin
1599 if Name (N) = Error then
1600 return;
1601 end if;
1603 -- Check for Text_IO special units (we may be renaming a Text_IO child),
1604 -- but make sure not to catch renamings generated for package instances
1605 -- that have nothing to do with them but are nevertheless homonyms.
1607 if Is_Entity_Name (Name (N))
1608 and then Present (Entity (Name (N)))
1609 and then Is_Generic_Instance (Entity (Name (N)))
1610 then
1611 null;
1612 else
1613 Check_Text_IO_Special_Unit (Name (N));
1614 end if;
1616 if Current_Scope /= Standard_Standard then
1617 Set_Is_Pure (New_P, Is_Pure (Current_Scope));
1618 end if;
1620 Enter_Name (New_P);
1621 Analyze (Name (N));
1623 if Is_Entity_Name (Name (N)) then
1624 Old_P := Entity (Name (N));
1625 else
1626 Old_P := Any_Id;
1627 end if;
1629 if Etype (Old_P) = Any_Type then
1630 Error_Msg_N ("expect package name in renaming", Name (N));
1632 elsif Ekind (Old_P) /= E_Package
1633 and then not (Ekind (Old_P) = E_Generic_Package
1634 and then In_Open_Scopes (Old_P))
1635 then
1636 if Ekind (Old_P) = E_Generic_Package then
1637 Error_Msg_N
1638 ("generic package cannot be renamed as a package", Name (N));
1639 else
1640 Error_Msg_Sloc := Sloc (Old_P);
1641 Error_Msg_NE
1642 ("expect package name in renaming, found& declared#",
1643 Name (N), Old_P);
1644 end if;
1646 -- Set basic attributes to minimize cascaded errors
1648 Mutate_Ekind (New_P, E_Package);
1649 Set_Etype (New_P, Standard_Void_Type);
1651 elsif Present (Renamed_Entity (Old_P))
1652 and then (From_Limited_With (Renamed_Entity (Old_P))
1653 or else Has_Limited_View (Renamed_Entity (Old_P)))
1654 and then not
1655 Unit_Is_Visible (Cunit (Get_Source_Unit (Renamed_Entity (Old_P))))
1656 then
1657 Error_Msg_NE
1658 ("renaming of limited view of package & not usable in this context"
1659 & " (RM 8.5.3(3.1/2))", Name (N), Renamed_Entity (Old_P));
1661 -- Set basic attributes to minimize cascaded errors
1663 Mutate_Ekind (New_P, E_Package);
1664 Set_Etype (New_P, Standard_Void_Type);
1666 -- Here for OK package renaming
1668 else
1669 -- Entities in the old package are accessible through the renaming
1670 -- entity. The simplest implementation is to have both packages share
1671 -- the entity list.
1673 Mutate_Ekind (New_P, E_Package);
1674 Set_Etype (New_P, Standard_Void_Type);
1676 if Present (Renamed_Entity (Old_P)) then
1677 Set_Renamed_Entity (New_P, Renamed_Entity (Old_P));
1678 else
1679 Set_Renamed_Entity (New_P, Old_P);
1680 end if;
1682 -- The package renaming declaration may become Ghost if it renames a
1683 -- Ghost entity.
1685 Mark_Ghost_Renaming (N, Old_P);
1687 Set_Has_Completion (New_P);
1688 Set_First_Entity (New_P, First_Entity (Old_P));
1689 Set_Last_Entity (New_P, Last_Entity (Old_P));
1690 Set_First_Private_Entity (New_P, First_Private_Entity (Old_P));
1691 Check_Library_Unit_Renaming (N, Old_P);
1692 Generate_Reference (Old_P, Name (N));
1694 -- If the renaming is in the visible part of a package, then we set
1695 -- Renamed_In_Spec for the renamed package, to prevent giving
1696 -- warnings about no entities referenced. Such a warning would be
1697 -- overenthusiastic, since clients can see entities in the renamed
1698 -- package via the visible package renaming.
1700 declare
1701 Ent : constant Entity_Id := Cunit_Entity (Current_Sem_Unit);
1702 begin
1703 if Ekind (Ent) = E_Package
1704 and then not In_Private_Part (Ent)
1705 and then In_Extended_Main_Source_Unit (N)
1706 and then Ekind (Old_P) = E_Package
1707 then
1708 Set_Renamed_In_Spec (Old_P);
1709 end if;
1710 end;
1712 -- If this is the renaming declaration of a package instantiation
1713 -- within itself, it is the declaration that ends the list of actuals
1714 -- for the instantiation. At this point, the subtypes that rename
1715 -- the actuals are flagged as generic, to avoid spurious ambiguities
1716 -- if the actuals for two distinct formals happen to coincide. If
1717 -- the actual is a private type, the subtype has a private completion
1718 -- that is flagged in the same fashion.
1720 -- Resolution is identical to what is was in the original generic.
1721 -- On exit from the generic instance, these are turned into regular
1722 -- subtypes again, so they are compatible with types in their class.
1724 if not Is_Generic_Instance (Old_P) then
1725 return;
1726 else
1727 Spec := Specification (Unit_Declaration_Node (Old_P));
1728 end if;
1730 if Nkind (Spec) = N_Package_Specification
1731 and then Present (Generic_Parent (Spec))
1732 and then Old_P = Current_Scope
1733 and then Chars (New_P) = Chars (Generic_Parent (Spec))
1734 then
1735 declare
1736 E : Entity_Id;
1738 begin
1739 E := First_Entity (Old_P);
1740 while Present (E) and then E /= New_P loop
1741 if Is_Type (E)
1742 and then Nkind (Parent (E)) = N_Subtype_Declaration
1743 then
1744 Set_Is_Generic_Actual_Type (E);
1746 if Is_Private_Type (E)
1747 and then Present (Full_View (E))
1748 then
1749 Set_Is_Generic_Actual_Type (Full_View (E));
1750 end if;
1751 end if;
1753 Next_Entity (E);
1754 end loop;
1755 end;
1756 end if;
1757 end if;
1759 -- Implementation-defined aspect specifications can appear in a renaming
1760 -- declaration, but not language-defined ones. The call to procedure
1761 -- Analyze_Aspect_Specifications will take care of this error check.
1763 if Has_Aspects (N) then
1764 Analyze_Aspect_Specifications (N, New_P);
1765 end if;
1766 end Analyze_Package_Renaming;
1768 -------------------------------
1769 -- Analyze_Renamed_Character --
1770 -------------------------------
1772 procedure Analyze_Renamed_Character
1773 (N : Node_Id;
1774 New_S : Entity_Id;
1775 Is_Body : Boolean)
1777 C : constant Node_Id := Name (N);
1779 begin
1780 if Ekind (New_S) = E_Function then
1781 Resolve (C, Etype (New_S));
1783 if Is_Body then
1784 Check_Frozen_Renaming (N, New_S);
1785 end if;
1787 else
1788 Error_Msg_N ("character literal can only be renamed as function", N);
1789 end if;
1790 end Analyze_Renamed_Character;
1792 ---------------------------------
1793 -- Analyze_Renamed_Dereference --
1794 ---------------------------------
1796 procedure Analyze_Renamed_Dereference
1797 (N : Node_Id;
1798 New_S : Entity_Id;
1799 Is_Body : Boolean)
1801 Nam : constant Node_Id := Name (N);
1802 P : constant Node_Id := Prefix (Nam);
1803 Typ : Entity_Id;
1804 Ind : Interp_Index;
1805 It : Interp;
1807 begin
1808 if not Is_Overloaded (P) then
1809 if Ekind (Etype (Nam)) /= E_Subprogram_Type
1810 or else not Type_Conformant (Etype (Nam), New_S)
1811 then
1812 Error_Msg_N ("designated type does not match specification", P);
1813 else
1814 Resolve (P);
1815 end if;
1817 return;
1819 else
1820 Typ := Any_Type;
1821 Get_First_Interp (Nam, Ind, It);
1823 while Present (It.Nam) loop
1825 if Ekind (It.Nam) = E_Subprogram_Type
1826 and then Type_Conformant (It.Nam, New_S)
1827 then
1828 if Typ /= Any_Id then
1829 Error_Msg_N ("ambiguous renaming", P);
1830 return;
1831 else
1832 Typ := It.Nam;
1833 end if;
1834 end if;
1836 Get_Next_Interp (Ind, It);
1837 end loop;
1839 if Typ = Any_Type then
1840 Error_Msg_N ("designated type does not match specification", P);
1841 else
1842 Resolve (N, Typ);
1844 if Is_Body then
1845 Check_Frozen_Renaming (N, New_S);
1846 end if;
1847 end if;
1848 end if;
1849 end Analyze_Renamed_Dereference;
1851 ---------------------------
1852 -- Analyze_Renamed_Entry --
1853 ---------------------------
1855 procedure Analyze_Renamed_Entry
1856 (N : Node_Id;
1857 New_S : Entity_Id;
1858 Is_Body : Boolean)
1860 Nam : constant Node_Id := Name (N);
1861 Sel : constant Node_Id := Selector_Name (Nam);
1862 Is_Actual : constant Boolean := Present (Corresponding_Formal_Spec (N));
1863 Old_S : Entity_Id;
1865 begin
1866 if Entity (Sel) = Any_Id then
1868 -- Selector is undefined on prefix. Error emitted already
1870 Set_Has_Completion (New_S);
1871 return;
1872 end if;
1874 -- Otherwise find renamed entity and build body of New_S as a call to it
1876 Old_S := Find_Renamed_Entity (N, Selector_Name (Nam), New_S);
1878 if Old_S = Any_Id then
1879 Error_Msg_N ("no subprogram or entry matches specification", N);
1880 else
1881 if Is_Body then
1882 Check_Subtype_Conformant (New_S, Old_S, N);
1883 Generate_Reference (New_S, Defining_Entity (N), 'b');
1884 Style.Check_Identifier (Defining_Entity (N), New_S);
1886 else
1887 -- Only mode conformance required for a renaming_as_declaration
1889 Check_Mode_Conformant (New_S, Old_S, N);
1890 end if;
1892 Inherit_Renamed_Profile (New_S, Old_S);
1894 -- The prefix can be an arbitrary expression that yields a task or
1895 -- protected object, so it must be resolved.
1897 if Is_Access_Type (Etype (Prefix (Nam))) then
1898 Insert_Explicit_Dereference (Prefix (Nam));
1899 end if;
1900 Resolve (Prefix (Nam), Scope (Old_S));
1901 end if;
1903 Set_Convention (New_S, Convention (Old_S));
1904 Set_Has_Completion (New_S, Inside_A_Generic);
1906 -- AI05-0225: If the renamed entity is a procedure or entry of a
1907 -- protected object, the target object must be a variable.
1909 if Is_Protected_Type (Scope (Old_S))
1910 and then Ekind (New_S) = E_Procedure
1911 and then not Is_Variable (Prefix (Nam))
1912 then
1913 if Is_Actual then
1914 Error_Msg_N
1915 ("target object of protected operation used as actual for "
1916 & "formal procedure must be a variable", Nam);
1917 else
1918 Error_Msg_N
1919 ("target object of protected operation renamed as procedure, "
1920 & "must be a variable", Nam);
1921 end if;
1922 end if;
1924 if Is_Body then
1925 Check_Frozen_Renaming (N, New_S);
1926 end if;
1927 end Analyze_Renamed_Entry;
1929 -----------------------------------
1930 -- Analyze_Renamed_Family_Member --
1931 -----------------------------------
1933 procedure Analyze_Renamed_Family_Member
1934 (N : Node_Id;
1935 New_S : Entity_Id;
1936 Is_Body : Boolean)
1938 Nam : constant Node_Id := Name (N);
1939 P : constant Node_Id := Prefix (Nam);
1940 Old_S : Entity_Id;
1942 begin
1943 if (Is_Entity_Name (P) and then Ekind (Entity (P)) = E_Entry_Family)
1944 or else (Nkind (P) = N_Selected_Component
1945 and then Ekind (Entity (Selector_Name (P))) = E_Entry_Family)
1946 then
1947 if Is_Entity_Name (P) then
1948 Old_S := Entity (P);
1949 else
1950 Old_S := Entity (Selector_Name (P));
1951 end if;
1953 if not Entity_Matches_Spec (Old_S, New_S) then
1954 Error_Msg_N ("entry family does not match specification", N);
1956 elsif Is_Body then
1957 Check_Subtype_Conformant (New_S, Old_S, N);
1958 Generate_Reference (New_S, Defining_Entity (N), 'b');
1959 Style.Check_Identifier (Defining_Entity (N), New_S);
1960 end if;
1962 else
1963 Error_Msg_N ("no entry family matches specification", N);
1964 end if;
1966 Set_Has_Completion (New_S, Inside_A_Generic);
1968 if Is_Body then
1969 Check_Frozen_Renaming (N, New_S);
1970 end if;
1971 end Analyze_Renamed_Family_Member;
1973 -----------------------------------------
1974 -- Analyze_Renamed_Primitive_Operation --
1975 -----------------------------------------
1977 procedure Analyze_Renamed_Primitive_Operation
1978 (N : Node_Id;
1979 New_S : Entity_Id;
1980 Is_Body : Boolean)
1982 Old_S : Entity_Id;
1983 Nam : Entity_Id;
1985 function Conforms
1986 (Subp : Entity_Id;
1987 Ctyp : Conformance_Type) return Boolean;
1988 -- Verify that the signatures of the renamed entity and the new entity
1989 -- match. The first formal of the renamed entity is skipped because it
1990 -- is the target object in any subsequent call.
1992 --------------
1993 -- Conforms --
1994 --------------
1996 function Conforms
1997 (Subp : Entity_Id;
1998 Ctyp : Conformance_Type) return Boolean
2000 Old_F : Entity_Id;
2001 New_F : Entity_Id;
2003 begin
2004 if Ekind (Subp) /= Ekind (New_S) then
2005 return False;
2006 end if;
2008 Old_F := Next_Formal (First_Formal (Subp));
2009 New_F := First_Formal (New_S);
2010 while Present (Old_F) and then Present (New_F) loop
2011 if not Conforming_Types (Etype (Old_F), Etype (New_F), Ctyp) then
2012 return False;
2013 end if;
2015 if Ctyp >= Mode_Conformant
2016 and then Ekind (Old_F) /= Ekind (New_F)
2017 then
2018 return False;
2019 end if;
2021 Next_Formal (New_F);
2022 Next_Formal (Old_F);
2023 end loop;
2025 return True;
2026 end Conforms;
2028 -- Start of processing for Analyze_Renamed_Primitive_Operation
2030 begin
2031 if not Is_Overloaded (Selector_Name (Name (N))) then
2032 Old_S := Entity (Selector_Name (Name (N)));
2034 if not Conforms (Old_S, Type_Conformant) then
2035 Old_S := Any_Id;
2036 end if;
2038 else
2039 -- Find the operation that matches the given signature
2041 declare
2042 It : Interp;
2043 Ind : Interp_Index;
2045 begin
2046 Old_S := Any_Id;
2047 Get_First_Interp (Selector_Name (Name (N)), Ind, It);
2049 while Present (It.Nam) loop
2050 if Conforms (It.Nam, Type_Conformant) then
2051 Old_S := It.Nam;
2052 end if;
2054 Get_Next_Interp (Ind, It);
2055 end loop;
2056 end;
2057 end if;
2059 if Old_S = Any_Id then
2060 Error_Msg_N ("no subprogram or entry matches specification", N);
2062 else
2063 if Is_Body then
2064 if not Conforms (Old_S, Subtype_Conformant) then
2065 Error_Msg_N ("subtype conformance error in renaming", N);
2066 end if;
2068 Generate_Reference (New_S, Defining_Entity (N), 'b');
2069 Style.Check_Identifier (Defining_Entity (N), New_S);
2071 else
2072 -- Only mode conformance required for a renaming_as_declaration
2074 if not Conforms (Old_S, Mode_Conformant) then
2075 Error_Msg_N ("mode conformance error in renaming", N);
2076 end if;
2078 -- AI12-0204: The prefix of a prefixed view that is renamed or
2079 -- passed as a formal subprogram must be renamable as an object.
2081 Nam := Prefix (Name (N));
2083 if Is_Object_Reference (Nam) then
2084 if Is_Dependent_Component_Of_Mutable_Object (Nam) then
2085 Error_Msg_N
2086 ("illegal renaming of discriminant-dependent component",
2087 Nam);
2088 end if;
2089 else
2090 Error_Msg_N ("expect object name in renaming", Nam);
2091 end if;
2093 -- Enforce the rule given in (RM 6.3.1 (10.1/2)): a prefixed
2094 -- view of a subprogram is intrinsic, because the compiler has
2095 -- to generate a wrapper for any call to it. If the name in a
2096 -- subprogram renaming is a prefixed view, the entity is thus
2097 -- intrinsic, and 'Access cannot be applied to it.
2099 Set_Convention (New_S, Convention_Intrinsic);
2100 end if;
2102 -- Inherit_Renamed_Profile (New_S, Old_S);
2104 -- The prefix can be an arbitrary expression that yields an
2105 -- object, so it must be resolved.
2107 Resolve (Prefix (Name (N)));
2108 end if;
2109 end Analyze_Renamed_Primitive_Operation;
2111 ---------------------------------
2112 -- Analyze_Subprogram_Renaming --
2113 ---------------------------------
2115 procedure Analyze_Subprogram_Renaming (N : Node_Id) is
2116 Formal_Spec : constant Entity_Id := Corresponding_Formal_Spec (N);
2117 Is_Actual : constant Boolean := Present (Formal_Spec);
2118 Nam : constant Node_Id := Name (N);
2119 Save_AV : constant Ada_Version_Type := Ada_Version;
2120 Save_AVP : constant Node_Id := Ada_Version_Pragma;
2121 Save_AV_Exp : constant Ada_Version_Type := Ada_Version_Explicit;
2122 Spec : constant Node_Id := Specification (N);
2124 Old_S : Entity_Id := Empty;
2125 Rename_Spec : Entity_Id;
2127 procedure Check_Null_Exclusion
2128 (Ren : Entity_Id;
2129 Sub : Entity_Id);
2130 -- Ada 2005 (AI-423): Given renaming Ren of subprogram Sub, check the
2131 -- following AI rules:
2133 -- If Ren denotes a generic formal object of a generic unit G, and the
2134 -- renaming (or instantiation containing the actual) occurs within the
2135 -- body of G or within the body of a generic unit declared within the
2136 -- declarative region of G, then the corresponding parameter of G
2137 -- shall have a null_exclusion; Otherwise the subtype of the Sub's
2138 -- formal parameter shall exclude null.
2140 -- Similarly for its return profile.
2142 procedure Check_SPARK_Primitive_Operation (Subp_Id : Entity_Id);
2143 -- Ensure that a SPARK renaming denoted by its entity Subp_Id does not
2144 -- declare a primitive operation of a tagged type (SPARK RM 6.1.1(3)).
2146 procedure Freeze_Actual_Profile;
2147 -- In Ada 2012, enforce the freezing rule concerning formal incomplete
2148 -- types: a callable entity freezes its profile, unless it has an
2149 -- incomplete untagged formal (RM 13.14(10.2/3)).
2151 function Has_Class_Wide_Actual return Boolean;
2152 -- Ada 2012 (AI05-071, AI05-0131) and Ada 2022 (AI12-0165): True if N is
2153 -- the renaming for a defaulted formal subprogram where the actual for
2154 -- the controlling formal type is class-wide.
2156 procedure Handle_Instance_With_Class_Wide_Type
2157 (Inst_Node : Node_Id;
2158 Ren_Id : Entity_Id;
2159 Wrapped_Prim : out Entity_Id;
2160 Wrap_Id : out Entity_Id);
2161 -- Ada 2012 (AI05-0071), Ada 2022 (AI12-0165): when the actual type
2162 -- of an instantiation is a class-wide type T'Class we may need to
2163 -- wrap a primitive operation of T; this routine looks for a suitable
2164 -- primitive to be wrapped and (if the wrapper is required) returns the
2165 -- Id of the wrapped primitive and the Id of the built wrapper. Ren_Id
2166 -- is the defining entity for the renamed subprogram specification.
2168 function Original_Subprogram (Subp : Entity_Id) return Entity_Id;
2169 -- Find renamed entity when the declaration is a renaming_as_body and
2170 -- the renamed entity may itself be a renaming_as_body. Used to enforce
2171 -- rule that a renaming_as_body is illegal if the declaration occurs
2172 -- before the subprogram it completes is frozen, and renaming indirectly
2173 -- renames the subprogram itself.(Defect Report 8652/0027).
2175 --------------------------
2176 -- Check_Null_Exclusion --
2177 --------------------------
2179 procedure Check_Null_Exclusion
2180 (Ren : Entity_Id;
2181 Sub : Entity_Id)
2183 Ren_Formal : Entity_Id;
2184 Sub_Formal : Entity_Id;
2186 function Null_Exclusion_Mismatch
2187 (Renaming : Entity_Id; Renamed : Entity_Id) return Boolean;
2188 -- Return True if there is a null exclusion mismatch between
2189 -- Renaming and Renamed, False otherwise.
2191 -----------------------------
2192 -- Null_Exclusion_Mismatch --
2193 -----------------------------
2195 function Null_Exclusion_Mismatch
2196 (Renaming : Entity_Id; Renamed : Entity_Id) return Boolean is
2197 begin
2198 return Has_Null_Exclusion (Parent (Renaming))
2199 and then
2200 not (Has_Null_Exclusion (Parent (Renamed))
2201 or else (Can_Never_Be_Null (Etype (Renamed))
2202 and then not
2203 (Is_Formal_Subprogram (Sub)
2204 and then In_Generic_Body (Current_Scope))));
2205 end Null_Exclusion_Mismatch;
2207 begin
2208 -- Parameter check
2210 Ren_Formal := First_Formal (Ren);
2211 Sub_Formal := First_Formal (Sub);
2212 while Present (Ren_Formal) and then Present (Sub_Formal) loop
2213 if Null_Exclusion_Mismatch (Ren_Formal, Sub_Formal) then
2214 Error_Msg_Sloc := Sloc (Sub_Formal);
2215 Error_Msg_NE
2216 ("`NOT NULL` required for parameter &#",
2217 Ren_Formal, Sub_Formal);
2218 end if;
2220 Next_Formal (Ren_Formal);
2221 Next_Formal (Sub_Formal);
2222 end loop;
2224 -- Return profile check
2226 if Nkind (Parent (Ren)) = N_Function_Specification
2227 and then Nkind (Parent (Sub)) = N_Function_Specification
2228 and then Null_Exclusion_Mismatch (Ren, Sub)
2229 then
2230 Error_Msg_Sloc := Sloc (Sub);
2231 Error_Msg_N ("return must specify `NOT NULL`#", Ren);
2232 end if;
2233 end Check_Null_Exclusion;
2235 -------------------------------------
2236 -- Check_SPARK_Primitive_Operation --
2237 -------------------------------------
2239 procedure Check_SPARK_Primitive_Operation (Subp_Id : Entity_Id) is
2240 Prag : constant Node_Id := SPARK_Pragma (Subp_Id);
2241 Typ : Entity_Id;
2243 begin
2244 -- Nothing to do when the subprogram is not subject to SPARK_Mode On
2245 -- because this check applies to SPARK code only.
2247 if not (Present (Prag)
2248 and then Get_SPARK_Mode_From_Annotation (Prag) = On)
2249 then
2250 return;
2252 -- Nothing to do when the subprogram is not a primitive operation
2254 elsif not Is_Primitive (Subp_Id) then
2255 return;
2256 end if;
2258 Typ := Find_Dispatching_Type (Subp_Id);
2260 -- Nothing to do when the subprogram is a primitive operation of an
2261 -- untagged type.
2263 if No (Typ) then
2264 return;
2265 end if;
2267 -- At this point a renaming declaration introduces a new primitive
2268 -- operation for a tagged type.
2270 Error_Msg_Node_2 := Typ;
2271 Error_Msg_NE
2272 ("subprogram renaming & cannot declare primitive for type & "
2273 & "(SPARK RM 6.1.1(3))", N, Subp_Id);
2274 end Check_SPARK_Primitive_Operation;
2276 ---------------------------
2277 -- Freeze_Actual_Profile --
2278 ---------------------------
2280 procedure Freeze_Actual_Profile is
2281 F : Entity_Id;
2282 Has_Untagged_Inc : Boolean;
2283 Instantiation_Node : constant Node_Id := Parent (N);
2285 begin
2286 if Ada_Version >= Ada_2012 then
2287 F := First_Formal (Formal_Spec);
2288 Has_Untagged_Inc := False;
2289 while Present (F) loop
2290 if Ekind (Etype (F)) = E_Incomplete_Type
2291 and then not Is_Tagged_Type (Etype (F))
2292 then
2293 Has_Untagged_Inc := True;
2294 exit;
2295 end if;
2297 Next_Formal (F);
2298 end loop;
2300 if Ekind (Formal_Spec) = E_Function
2301 and then not Is_Tagged_Type (Etype (Formal_Spec))
2302 then
2303 Has_Untagged_Inc := True;
2304 end if;
2306 if not Has_Untagged_Inc then
2307 F := First_Formal (Old_S);
2308 while Present (F) loop
2309 Freeze_Before (Instantiation_Node, Etype (F));
2311 if Is_Incomplete_Or_Private_Type (Etype (F))
2312 and then No (Underlying_Type (Etype (F)))
2313 then
2314 -- Exclude generic types, or types derived from them.
2315 -- They will be frozen in the enclosing instance.
2317 if Is_Generic_Type (Etype (F))
2318 or else Is_Generic_Type (Root_Type (Etype (F)))
2319 then
2320 null;
2322 -- A limited view of a type declared elsewhere needs no
2323 -- freezing actions.
2325 elsif From_Limited_With (Etype (F)) then
2326 null;
2328 else
2329 Error_Msg_NE
2330 ("type& must be frozen before this point",
2331 Instantiation_Node, Etype (F));
2332 end if;
2333 end if;
2335 Next_Formal (F);
2336 end loop;
2337 end if;
2338 end if;
2339 end Freeze_Actual_Profile;
2341 ---------------------------
2342 -- Has_Class_Wide_Actual --
2343 ---------------------------
2345 function Has_Class_Wide_Actual return Boolean is
2346 Formal : Entity_Id;
2347 Formal_Typ : Entity_Id;
2349 begin
2350 if Is_Actual then
2351 Formal := First_Formal (Formal_Spec);
2352 while Present (Formal) loop
2353 Formal_Typ := Etype (Formal);
2355 if Has_Unknown_Discriminants (Formal_Typ)
2356 and then not Is_Class_Wide_Type (Formal_Typ)
2357 and then Is_Class_Wide_Type (Get_Instance_Of (Formal_Typ))
2358 then
2359 return True;
2360 end if;
2362 Next_Formal (Formal);
2363 end loop;
2364 end if;
2366 return False;
2367 end Has_Class_Wide_Actual;
2369 ------------------------------------------
2370 -- Handle_Instance_With_Class_Wide_Type --
2371 ------------------------------------------
2373 procedure Handle_Instance_With_Class_Wide_Type
2374 (Inst_Node : Node_Id;
2375 Ren_Id : Entity_Id;
2376 Wrapped_Prim : out Entity_Id;
2377 Wrap_Id : out Entity_Id)
2379 procedure Build_Class_Wide_Wrapper
2380 (Ren_Id : Entity_Id;
2381 Prim_Op : Entity_Id;
2382 Wrap_Id : out Entity_Id);
2383 -- Build a wrapper for the renaming Ren_Id of subprogram Prim_Op.
2385 procedure Find_Suitable_Candidate
2386 (Prim_Op : out Entity_Id;
2387 Is_CW_Prim : out Boolean);
2388 -- Look for a suitable primitive to be wrapped (Prim_Op); Is_CW_Prim
2389 -- indicates that the found candidate is a class-wide primitive (to
2390 -- help the caller decide if the wrapper is required).
2392 ------------------------------
2393 -- Build_Class_Wide_Wrapper --
2394 ------------------------------
2396 procedure Build_Class_Wide_Wrapper
2397 (Ren_Id : Entity_Id;
2398 Prim_Op : Entity_Id;
2399 Wrap_Id : out Entity_Id)
2401 Loc : constant Source_Ptr := Sloc (N);
2403 function Build_Call
2404 (Subp_Id : Entity_Id;
2405 Params : List_Id) return Node_Id;
2406 -- Create a dispatching call to invoke routine Subp_Id with
2407 -- actuals built from the parameter specifications of list Params.
2409 function Build_Expr_Fun_Call
2410 (Subp_Id : Entity_Id;
2411 Params : List_Id) return Node_Id;
2412 -- Create a dispatching call to invoke function Subp_Id with
2413 -- actuals built from the parameter specifications of list Params.
2414 -- Directly return the call, so that it can be used inside an
2415 -- expression function. This is a requirement of GNATprove mode.
2417 function Build_Spec (Subp_Id : Entity_Id) return Node_Id;
2418 -- Create a subprogram specification based on the subprogram
2419 -- profile of Subp_Id.
2421 ----------------
2422 -- Build_Call --
2423 ----------------
2425 function Build_Call
2426 (Subp_Id : Entity_Id;
2427 Params : List_Id) return Node_Id
2429 Actuals : constant List_Id := New_List;
2430 Call_Ref : constant Node_Id := New_Occurrence_Of (Subp_Id, Loc);
2431 Formal : Node_Id;
2433 begin
2434 -- Build the actual parameters of the call
2436 Formal := First (Params);
2437 while Present (Formal) loop
2438 Append_To (Actuals,
2439 Make_Identifier (Loc,
2440 Chars (Defining_Identifier (Formal))));
2441 Next (Formal);
2442 end loop;
2444 -- Generate:
2445 -- return Subp_Id (Actuals);
2447 if Ekind (Subp_Id) in E_Function | E_Operator then
2448 return
2449 Make_Simple_Return_Statement (Loc,
2450 Expression =>
2451 Make_Function_Call (Loc,
2452 Name => Call_Ref,
2453 Parameter_Associations => Actuals));
2455 -- Generate:
2456 -- Subp_Id (Actuals);
2458 else
2459 return
2460 Make_Procedure_Call_Statement (Loc,
2461 Name => Call_Ref,
2462 Parameter_Associations => Actuals);
2463 end if;
2464 end Build_Call;
2466 -------------------------
2467 -- Build_Expr_Fun_Call --
2468 -------------------------
2470 function Build_Expr_Fun_Call
2471 (Subp_Id : Entity_Id;
2472 Params : List_Id) return Node_Id
2474 Actuals : constant List_Id := New_List;
2475 Call_Ref : constant Node_Id := New_Occurrence_Of (Subp_Id, Loc);
2476 Formal : Node_Id;
2478 begin
2479 pragma Assert (Ekind (Subp_Id) in E_Function | E_Operator);
2481 -- Build the actual parameters of the call
2483 Formal := First (Params);
2484 while Present (Formal) loop
2485 Append_To (Actuals,
2486 Make_Identifier (Loc,
2487 Chars (Defining_Identifier (Formal))));
2488 Next (Formal);
2489 end loop;
2491 -- Generate:
2492 -- Subp_Id (Actuals);
2494 return
2495 Make_Function_Call (Loc,
2496 Name => Call_Ref,
2497 Parameter_Associations => Actuals);
2498 end Build_Expr_Fun_Call;
2500 ----------------
2501 -- Build_Spec --
2502 ----------------
2504 function Build_Spec (Subp_Id : Entity_Id) return Node_Id is
2505 Params : constant List_Id := Copy_Parameter_List (Subp_Id);
2506 Spec_Id : constant Entity_Id :=
2507 Make_Defining_Identifier (Loc,
2508 New_External_Name (Chars (Subp_Id), 'R'));
2510 begin
2511 if Ekind (Formal_Spec) = E_Procedure then
2512 return
2513 Make_Procedure_Specification (Loc,
2514 Defining_Unit_Name => Spec_Id,
2515 Parameter_Specifications => Params);
2516 else
2517 return
2518 Make_Function_Specification (Loc,
2519 Defining_Unit_Name => Spec_Id,
2520 Parameter_Specifications => Params,
2521 Result_Definition =>
2522 New_Copy_Tree (Result_Definition (Spec)));
2523 end if;
2524 end Build_Spec;
2526 -- Local variables
2528 Body_Decl : Node_Id;
2529 Spec_Decl : Node_Id;
2530 New_Spec : Node_Id;
2532 -- Start of processing for Build_Class_Wide_Wrapper
2534 begin
2535 pragma Assert (not Error_Posted (Nam));
2537 -- Step 1: Create the declaration and the body of the wrapper,
2538 -- insert all the pieces into the tree.
2540 -- In GNATprove mode, create a function wrapper in the form of an
2541 -- expression function, so that an implicit postcondition relating
2542 -- the result of calling the wrapper function and the result of
2543 -- the dispatching call to the wrapped function is known during
2544 -- proof.
2546 if GNATprove_Mode
2547 and then Ekind (Ren_Id) in E_Function | E_Operator
2548 then
2549 New_Spec := Build_Spec (Ren_Id);
2550 Body_Decl :=
2551 Make_Expression_Function (Loc,
2552 Specification => New_Spec,
2553 Expression =>
2554 Build_Expr_Fun_Call
2555 (Subp_Id => Prim_Op,
2556 Params => Parameter_Specifications (New_Spec)));
2558 Wrap_Id := Defining_Entity (Body_Decl);
2560 -- Otherwise, create separate spec and body for the subprogram
2562 else
2563 Spec_Decl :=
2564 Make_Subprogram_Declaration (Loc,
2565 Specification => Build_Spec (Ren_Id));
2566 Insert_Before_And_Analyze (N, Spec_Decl);
2568 Wrap_Id := Defining_Entity (Spec_Decl);
2570 Body_Decl :=
2571 Make_Subprogram_Body (Loc,
2572 Specification => Build_Spec (Ren_Id),
2573 Declarations => New_List,
2574 Handled_Statement_Sequence =>
2575 Make_Handled_Sequence_Of_Statements (Loc,
2576 Statements => New_List (
2577 Build_Call
2578 (Subp_Id => Prim_Op,
2579 Params =>
2580 Parameter_Specifications
2581 (Specification (Spec_Decl))))));
2583 Set_Corresponding_Body (Spec_Decl, Defining_Entity (Body_Decl));
2584 end if;
2586 Set_Is_Class_Wide_Wrapper (Wrap_Id);
2588 -- If the operator carries an Eliminated pragma, indicate that
2589 -- the wrapper is also to be eliminated, to prevent spurious
2590 -- errors when using gnatelim on programs that include box-
2591 -- defaulted initialization of equality operators.
2593 Set_Is_Eliminated (Wrap_Id, Is_Eliminated (Prim_Op));
2595 -- In GNATprove mode, insert the body in the tree for analysis
2597 if GNATprove_Mode then
2598 Insert_Before_And_Analyze (N, Body_Decl);
2599 end if;
2601 -- The generated body does not freeze and must be analyzed when
2602 -- the class-wide wrapper is frozen. The body is only needed if
2603 -- expansion is enabled.
2605 if Expander_Active then
2606 Append_Freeze_Action (Wrap_Id, Body_Decl);
2607 end if;
2609 -- Step 2: The subprogram renaming aliases the wrapper
2611 Rewrite (Name (N), New_Occurrence_Of (Wrap_Id, Loc));
2612 end Build_Class_Wide_Wrapper;
2614 -----------------------------
2615 -- Find_Suitable_Candidate --
2616 -----------------------------
2618 procedure Find_Suitable_Candidate
2619 (Prim_Op : out Entity_Id;
2620 Is_CW_Prim : out Boolean)
2622 Loc : constant Source_Ptr := Sloc (N);
2624 function Find_Primitive (Typ : Entity_Id) return Entity_Id;
2625 -- Find a primitive subprogram of type Typ which matches the
2626 -- profile of the renaming declaration.
2628 procedure Interpretation_Error (Subp_Id : Entity_Id);
2629 -- Emit a continuation error message suggesting subprogram Subp_Id
2630 -- as a possible interpretation.
2632 function Is_Intrinsic_Equality
2633 (Subp_Id : Entity_Id) return Boolean;
2634 -- Determine whether subprogram Subp_Id denotes the intrinsic "="
2635 -- operator.
2637 function Is_Suitable_Candidate
2638 (Subp_Id : Entity_Id) return Boolean;
2639 -- Determine whether subprogram Subp_Id is a suitable candidate
2640 -- for the role of a wrapped subprogram.
2642 --------------------
2643 -- Find_Primitive --
2644 --------------------
2646 function Find_Primitive (Typ : Entity_Id) return Entity_Id is
2647 procedure Replace_Parameter_Types (Spec : Node_Id);
2648 -- Given a specification Spec, replace all class-wide parameter
2649 -- types with reference to type Typ.
2651 -----------------------------
2652 -- Replace_Parameter_Types --
2653 -----------------------------
2655 procedure Replace_Parameter_Types (Spec : Node_Id) is
2656 Formal : Node_Id;
2657 Formal_Id : Entity_Id;
2658 Formal_Typ : Node_Id;
2660 begin
2661 Formal := First (Parameter_Specifications (Spec));
2662 while Present (Formal) loop
2663 Formal_Id := Defining_Identifier (Formal);
2664 Formal_Typ := Parameter_Type (Formal);
2666 -- Create a new entity for each class-wide formal to
2667 -- prevent aliasing with the original renaming. Replace
2668 -- the type of such a parameter with the candidate type.
2670 if Nkind (Formal_Typ) = N_Identifier
2671 and then Is_Class_Wide_Type (Etype (Formal_Typ))
2672 then
2673 Set_Defining_Identifier (Formal,
2674 Make_Defining_Identifier (Loc, Chars (Formal_Id)));
2676 Set_Parameter_Type (Formal,
2677 New_Occurrence_Of (Typ, Loc));
2678 end if;
2680 Next (Formal);
2681 end loop;
2682 end Replace_Parameter_Types;
2684 -- Local variables
2686 Alt_Ren : constant Node_Id := New_Copy_Tree (N);
2687 Alt_Nam : constant Node_Id := Name (Alt_Ren);
2688 Alt_Spec : constant Node_Id := Specification (Alt_Ren);
2689 Subp_Id : Entity_Id;
2691 -- Start of processing for Find_Primitive
2693 begin
2694 -- Each attempt to find a suitable primitive of a particular
2695 -- type operates on its own copy of the original renaming.
2696 -- As a result the original renaming is kept decoration and
2697 -- side-effect free.
2699 -- Inherit the overloaded status of the renamed subprogram name
2701 if Is_Overloaded (Nam) then
2702 Set_Is_Overloaded (Alt_Nam);
2703 Save_Interps (Nam, Alt_Nam);
2704 end if;
2706 -- The copied renaming is hidden from visibility to prevent the
2707 -- pollution of the enclosing context.
2709 Set_Defining_Unit_Name (Alt_Spec, Make_Temporary (Loc, 'R'));
2711 -- The types of all class-wide parameters must be changed to
2712 -- the candidate type.
2714 Replace_Parameter_Types (Alt_Spec);
2716 -- Try to find a suitable primitive that matches the altered
2717 -- profile of the renaming specification.
2719 Subp_Id :=
2720 Find_Renamed_Entity
2721 (N => Alt_Ren,
2722 Nam => Name (Alt_Ren),
2723 New_S => Analyze_Subprogram_Specification (Alt_Spec),
2724 Is_Actual => Is_Actual);
2726 -- Do not return Any_Id if the resolution of the altered
2727 -- profile failed as this complicates further checks on
2728 -- the caller side; return Empty instead.
2730 if Subp_Id = Any_Id then
2731 return Empty;
2732 else
2733 return Subp_Id;
2734 end if;
2735 end Find_Primitive;
2737 --------------------------
2738 -- Interpretation_Error --
2739 --------------------------
2741 procedure Interpretation_Error (Subp_Id : Entity_Id) is
2742 begin
2743 Error_Msg_Sloc := Sloc (Subp_Id);
2745 if Is_Internal (Subp_Id) then
2746 Error_Msg_NE
2747 ("\\possible interpretation: predefined & #",
2748 Spec, Formal_Spec);
2749 else
2750 Error_Msg_NE
2751 ("\\possible interpretation: & defined #",
2752 Spec, Formal_Spec);
2753 end if;
2754 end Interpretation_Error;
2756 ---------------------------
2757 -- Is_Intrinsic_Equality --
2758 ---------------------------
2760 function Is_Intrinsic_Equality (Subp_Id : Entity_Id) return Boolean
2762 begin
2763 return
2764 Ekind (Subp_Id) = E_Operator
2765 and then Chars (Subp_Id) = Name_Op_Eq
2766 and then Is_Intrinsic_Subprogram (Subp_Id);
2767 end Is_Intrinsic_Equality;
2769 ---------------------------
2770 -- Is_Suitable_Candidate --
2771 ---------------------------
2773 function Is_Suitable_Candidate (Subp_Id : Entity_Id) return Boolean
2775 begin
2776 if No (Subp_Id) then
2777 return False;
2779 -- An intrinsic subprogram is never a good candidate. This
2780 -- is an indication of a missing primitive, either defined
2781 -- directly or inherited from a parent tagged type.
2783 elsif Is_Intrinsic_Subprogram (Subp_Id) then
2784 return False;
2786 else
2787 return True;
2788 end if;
2789 end Is_Suitable_Candidate;
2791 -- Local variables
2793 Actual_Typ : Entity_Id := Empty;
2794 -- The actual class-wide type for Formal_Typ
2796 CW_Prim_OK : Boolean;
2797 CW_Prim_Op : Entity_Id;
2798 -- The class-wide subprogram (if available) that corresponds to
2799 -- the renamed generic formal subprogram.
2801 Formal_Typ : Entity_Id := Empty;
2802 -- The generic formal type with unknown discriminants
2804 Root_Prim_OK : Boolean;
2805 Root_Prim_Op : Entity_Id;
2806 -- The root type primitive (if available) that corresponds to the
2807 -- renamed generic formal subprogram.
2809 Root_Typ : Entity_Id := Empty;
2810 -- The root type of Actual_Typ
2812 Formal : Node_Id;
2814 -- Start of processing for Find_Suitable_Candidate
2816 begin
2817 pragma Assert (not Error_Posted (Nam));
2819 Prim_Op := Empty;
2820 Is_CW_Prim := False;
2822 -- Analyze the renamed name, but do not resolve it. The resolution
2823 -- is completed once a suitable subprogram is found.
2825 Analyze (Nam);
2827 -- When the renamed name denotes the intrinsic operator equals,
2828 -- the name must be treated as overloaded. This allows for a
2829 -- potential match against the root type's predefined equality
2830 -- function.
2832 if Is_Intrinsic_Equality (Entity (Nam)) then
2833 Set_Is_Overloaded (Nam);
2834 Collect_Interps (Nam);
2835 end if;
2837 -- Step 1: Find the generic formal type and its corresponding
2838 -- class-wide actual type from the renamed generic formal
2839 -- subprogram.
2841 Formal := First_Formal (Formal_Spec);
2842 while Present (Formal) loop
2843 if Has_Unknown_Discriminants (Etype (Formal))
2844 and then not Is_Class_Wide_Type (Etype (Formal))
2845 and then Is_Class_Wide_Type (Get_Instance_Of (Etype (Formal)))
2846 then
2847 Formal_Typ := Etype (Formal);
2848 Actual_Typ := Base_Type (Get_Instance_Of (Formal_Typ));
2849 Root_Typ := Root_Type (Actual_Typ);
2850 exit;
2851 end if;
2853 Next_Formal (Formal);
2854 end loop;
2856 -- The specification of the generic formal subprogram should
2857 -- always contain a formal type with unknown discriminants whose
2858 -- actual is a class-wide type; otherwise this indicates a failure
2859 -- in function Has_Class_Wide_Actual.
2861 pragma Assert (Present (Formal_Typ));
2863 -- Step 2: Find the proper class-wide subprogram or primitive
2864 -- that corresponds to the renamed generic formal subprogram.
2866 CW_Prim_Op := Find_Primitive (Actual_Typ);
2867 CW_Prim_OK := Is_Suitable_Candidate (CW_Prim_Op);
2868 Root_Prim_Op := Find_Primitive (Root_Typ);
2869 Root_Prim_OK := Is_Suitable_Candidate (Root_Prim_Op);
2871 -- The class-wide actual type has two subprograms that correspond
2872 -- to the renamed generic formal subprogram:
2874 -- with procedure Prim_Op (Param : Formal_Typ);
2876 -- procedure Prim_Op (Param : Actual_Typ); -- may be inherited
2877 -- procedure Prim_Op (Param : Actual_Typ'Class);
2879 -- Even though the declaration of the two subprograms is legal, a
2880 -- call to either one is ambiguous and therefore illegal.
2882 if CW_Prim_OK and Root_Prim_OK then
2884 -- A user-defined primitive has precedence over a predefined
2885 -- one.
2887 if Is_Internal (CW_Prim_Op)
2888 and then not Is_Internal (Root_Prim_Op)
2889 then
2890 Prim_Op := Root_Prim_Op;
2892 elsif Is_Internal (Root_Prim_Op)
2893 and then not Is_Internal (CW_Prim_Op)
2894 then
2895 Prim_Op := CW_Prim_Op;
2896 Is_CW_Prim := True;
2898 elsif CW_Prim_Op = Root_Prim_Op then
2899 Prim_Op := Root_Prim_Op;
2901 -- The two subprograms are legal but the class-wide subprogram
2902 -- is a class-wide wrapper built for a previous instantiation;
2903 -- the wrapper has precedence.
2905 elsif Present (Alias (CW_Prim_Op))
2906 and then Is_Class_Wide_Wrapper (Ultimate_Alias (CW_Prim_Op))
2907 then
2908 Prim_Op := CW_Prim_Op;
2909 Is_CW_Prim := True;
2911 -- Otherwise both candidate subprograms are user-defined and
2912 -- ambiguous.
2914 else
2915 Error_Msg_NE
2916 ("ambiguous actual for generic subprogram &",
2917 Spec, Formal_Spec);
2918 Interpretation_Error (Root_Prim_Op);
2919 Interpretation_Error (CW_Prim_Op);
2920 return;
2921 end if;
2923 elsif CW_Prim_OK and not Root_Prim_OK then
2924 Prim_Op := CW_Prim_Op;
2925 Is_CW_Prim := True;
2927 elsif not CW_Prim_OK and Root_Prim_OK then
2928 Prim_Op := Root_Prim_Op;
2930 -- An intrinsic equality may act as a suitable candidate in the
2931 -- case of a null type extension where the parent's equality
2932 -- is hidden. A call to an intrinsic equality is expanded as
2933 -- dispatching.
2935 elsif Present (Root_Prim_Op)
2936 and then Is_Intrinsic_Equality (Root_Prim_Op)
2937 then
2938 Prim_Op := Root_Prim_Op;
2940 -- Otherwise there are no candidate subprograms. Let the caller
2941 -- diagnose the error.
2943 else
2944 return;
2945 end if;
2947 -- At this point resolution has taken place and the name is no
2948 -- longer overloaded. Mark the primitive as referenced.
2950 Set_Is_Overloaded (Name (N), False);
2951 Set_Referenced (Prim_Op);
2952 end Find_Suitable_Candidate;
2954 -- Local variables
2956 Is_CW_Prim : Boolean;
2958 -- Start of processing for Handle_Instance_With_Class_Wide_Type
2960 begin
2961 Wrapped_Prim := Empty;
2962 Wrap_Id := Empty;
2964 -- Ada 2012 (AI05-0071): A generic/instance scenario involving a
2965 -- formal type with unknown discriminants and a generic primitive
2966 -- operation of the said type with a box require special processing
2967 -- when the actual is a class-wide type:
2969 -- generic
2970 -- type Formal_Typ (<>) is private;
2971 -- with procedure Prim_Op (Param : Formal_Typ) is <>;
2972 -- package Gen is ...
2974 -- package Inst is new Gen (Actual_Typ'Class);
2976 -- In this case the general renaming mechanism used in the prologue
2977 -- of an instance no longer applies:
2979 -- procedure Prim_Op (Param : Formal_Typ) renames Prim_Op;
2981 -- The above is replaced the following wrapper/renaming combination:
2983 -- procedure Wrapper (Param : Formal_Typ) is -- wrapper
2984 -- begin
2985 -- Prim_Op (Param); -- primitive
2986 -- end Wrapper;
2988 -- procedure Prim_Op (Param : Formal_Typ) renames Wrapper;
2990 -- This transformation applies only if there is no explicit visible
2991 -- class-wide operation at the point of the instantiation. Ren_Id is
2992 -- the entity of the renaming declaration. When the transformation
2993 -- applies, Wrapped_Prim is the entity of the wrapped primitive.
2995 if Box_Present (Inst_Node) then
2996 Find_Suitable_Candidate
2997 (Prim_Op => Wrapped_Prim,
2998 Is_CW_Prim => Is_CW_Prim);
3000 if Present (Wrapped_Prim) then
3001 if not Is_CW_Prim then
3002 Build_Class_Wide_Wrapper (Ren_Id, Wrapped_Prim, Wrap_Id);
3004 -- Small optimization: When the candidate is a class-wide
3005 -- subprogram we don't build the wrapper; we modify the
3006 -- renaming declaration to directly map the actual to the
3007 -- generic formal and discard the candidate.
3009 else
3010 Rewrite (Nam, New_Occurrence_Of (Wrapped_Prim, Sloc (N)));
3011 Wrapped_Prim := Empty;
3012 end if;
3013 end if;
3015 -- Ada 2022 (AI12-0165, RM 12.6(8.5/3)): The actual subprogram for a
3016 -- formal_abstract_subprogram_declaration shall be:
3017 -- a) a dispatching operation of the controlling type; or
3018 -- b) if the controlling type is a formal type, and the actual
3019 -- type corresponding to that formal type is a specific type T,
3020 -- a dispatching operation of type T; or
3021 -- c) if the controlling type is a formal type, and the actual
3022 -- type is a class-wide type T'Class, an implicitly declared
3023 -- subprogram corresponding to a primitive operation of type T.
3025 elsif Nkind (Inst_Node) = N_Formal_Abstract_Subprogram_Declaration
3026 and then Is_Entity_Name (Nam)
3027 then
3028 Find_Suitable_Candidate
3029 (Prim_Op => Wrapped_Prim,
3030 Is_CW_Prim => Is_CW_Prim);
3032 if Present (Wrapped_Prim) then
3034 -- Cases (a) and (b); see previous description.
3036 if not Is_CW_Prim then
3037 Build_Class_Wide_Wrapper (Ren_Id, Wrapped_Prim, Wrap_Id);
3039 -- Case (c); see previous description.
3041 -- Implicit operations of T'Class for subtype declarations
3042 -- are built by Derive_Subprogram, and their Alias attribute
3043 -- references the primitive operation of T.
3045 elsif not Comes_From_Source (Wrapped_Prim)
3046 and then Nkind (Parent (Wrapped_Prim)) = N_Subtype_Declaration
3047 and then Present (Alias (Wrapped_Prim))
3048 then
3049 -- We don't need to build the wrapper; we modify the
3050 -- renaming declaration to directly map the actual to
3051 -- the generic formal and discard the candidate.
3053 Rewrite (Nam,
3054 New_Occurrence_Of (Alias (Wrapped_Prim), Sloc (N)));
3055 Wrapped_Prim := Empty;
3057 -- Legality rules do not apply; discard the candidate.
3059 else
3060 Wrapped_Prim := Empty;
3061 end if;
3062 end if;
3063 end if;
3064 end Handle_Instance_With_Class_Wide_Type;
3066 -------------------------
3067 -- Original_Subprogram --
3068 -------------------------
3070 function Original_Subprogram (Subp : Entity_Id) return Entity_Id is
3071 Orig_Decl : Node_Id;
3072 Orig_Subp : Entity_Id;
3074 begin
3075 -- First case: renamed entity is itself a renaming
3077 if Present (Alias (Subp)) then
3078 return Alias (Subp);
3080 elsif Nkind (Unit_Declaration_Node (Subp)) = N_Subprogram_Declaration
3081 and then Present (Corresponding_Body (Unit_Declaration_Node (Subp)))
3082 then
3083 -- Check if renamed entity is a renaming_as_body
3085 Orig_Decl :=
3086 Unit_Declaration_Node
3087 (Corresponding_Body (Unit_Declaration_Node (Subp)));
3089 if Nkind (Orig_Decl) = N_Subprogram_Renaming_Declaration then
3090 Orig_Subp := Entity (Name (Orig_Decl));
3092 if Orig_Subp = Rename_Spec then
3094 -- Circularity detected
3096 return Orig_Subp;
3098 else
3099 return (Original_Subprogram (Orig_Subp));
3100 end if;
3101 else
3102 return Subp;
3103 end if;
3104 else
3105 return Subp;
3106 end if;
3107 end Original_Subprogram;
3109 -- Local variables
3111 CW_Actual : constant Boolean := Has_Class_Wide_Actual;
3112 -- Ada 2012 (AI05-071, AI05-0131) and Ada 2022 (AI12-0165): True if the
3113 -- renaming is for a defaulted formal subprogram when the actual for a
3114 -- related formal type is class-wide.
3116 Inst_Node : Node_Id := Empty;
3117 New_S : Entity_Id := Empty;
3118 Wrapped_Prim : Entity_Id := Empty;
3120 -- Start of processing for Analyze_Subprogram_Renaming
3122 begin
3123 -- We must test for the attribute renaming case before the Analyze
3124 -- call because otherwise Sem_Attr will complain that the attribute
3125 -- is missing an argument when it is analyzed.
3127 if Nkind (Nam) = N_Attribute_Reference then
3129 -- In the case of an abstract formal subprogram association, rewrite
3130 -- an actual given by a stream or Put_Image attribute as the name of
3131 -- the corresponding stream or Put_Image primitive of the type.
3133 -- In a generic context the stream and Put_Image operations are not
3134 -- generated, and this must be treated as a normal attribute
3135 -- reference, to be expanded in subsequent instantiations.
3137 if Is_Actual
3138 and then Is_Abstract_Subprogram (Formal_Spec)
3139 and then Expander_Active
3140 then
3141 declare
3142 Prefix_Type : constant Entity_Id := Entity (Prefix (Nam));
3143 Prim : Entity_Id;
3145 begin
3146 -- The class-wide forms of the stream and Put_Image attributes
3147 -- are not primitive dispatching operations (even though they
3148 -- internally dispatch).
3150 if Is_Class_Wide_Type (Prefix_Type) then
3151 Error_Msg_N
3152 ("attribute must be a primitive dispatching operation",
3153 Nam);
3154 return;
3155 end if;
3157 -- Retrieve the primitive subprogram associated with the
3158 -- attribute. This can only be a stream attribute, since those
3159 -- are the only ones that are dispatching (and the actual for
3160 -- an abstract formal subprogram must be dispatching
3161 -- operation).
3163 case Attribute_Name (Nam) is
3164 when Name_Input =>
3165 Prim :=
3166 Find_Optional_Prim_Op (Prefix_Type, TSS_Stream_Input);
3168 when Name_Output =>
3169 Prim :=
3170 Find_Optional_Prim_Op (Prefix_Type, TSS_Stream_Output);
3172 when Name_Read =>
3173 Prim :=
3174 Find_Optional_Prim_Op (Prefix_Type, TSS_Stream_Read);
3176 when Name_Write =>
3177 Prim :=
3178 Find_Optional_Prim_Op (Prefix_Type, TSS_Stream_Write);
3180 when Name_Put_Image =>
3181 Prim :=
3182 Find_Optional_Prim_Op (Prefix_Type, TSS_Put_Image);
3184 when others =>
3185 Error_Msg_N
3186 ("attribute must be a primitive dispatching operation",
3187 Nam);
3188 return;
3189 end case;
3191 -- If no stream operation was found, and the type is limited,
3192 -- the user should have defined one. This rule does not apply
3193 -- to Put_Image.
3195 if No (Prim)
3196 and then Attribute_Name (Nam) /= Name_Put_Image
3197 then
3198 if Is_Limited_Type (Prefix_Type) then
3199 Error_Msg_NE
3200 ("stream operation not defined for type&",
3201 N, Prefix_Type);
3202 return;
3204 -- Otherwise, compiler should have generated default
3206 else
3207 raise Program_Error;
3208 end if;
3209 end if;
3211 -- Rewrite the attribute into the name of its corresponding
3212 -- primitive dispatching subprogram. We can then proceed with
3213 -- the usual processing for subprogram renamings.
3215 declare
3216 Prim_Name : constant Node_Id :=
3217 Make_Identifier (Sloc (Nam),
3218 Chars => Chars (Prim));
3219 begin
3220 Set_Entity (Prim_Name, Prim);
3221 Rewrite (Nam, Prim_Name);
3222 Analyze (Nam);
3223 end;
3224 end;
3226 -- Normal processing for a renaming of an attribute
3228 else
3229 Attribute_Renaming (N);
3230 return;
3231 end if;
3232 end if;
3234 -- Check whether this declaration corresponds to the instantiation of a
3235 -- formal subprogram.
3237 -- If this is an instantiation, the corresponding actual is frozen and
3238 -- error messages can be made more precise. If this is a default
3239 -- subprogram, the entity is already established in the generic, and is
3240 -- not retrieved by visibility. If it is a default with a box, the
3241 -- candidate interpretations, if any, have been collected when building
3242 -- the renaming declaration. If overloaded, the proper interpretation is
3243 -- determined in Find_Renamed_Entity. If the entity is an operator,
3244 -- Find_Renamed_Entity applies additional visibility checks.
3246 if Is_Actual then
3247 Inst_Node := Unit_Declaration_Node (Formal_Spec);
3249 -- Ada 2012 (AI05-0071) and Ada 2022 (AI12-0165): when the actual
3250 -- type is a class-wide type T'Class we may need to wrap a primitive
3251 -- operation of T. Search for the wrapped primitive and (if required)
3252 -- build a wrapper whose body consists of a dispatching call to the
3253 -- wrapped primitive of T, with its formal parameters as the actual
3254 -- parameters.
3256 if CW_Actual and then
3258 -- Ada 2012 (AI05-0071): Check whether the renaming is for a
3259 -- defaulted actual subprogram with a class-wide actual.
3261 (Box_Present (Inst_Node)
3263 or else
3265 -- Ada 2022 (AI12-0165): Check whether the renaming is for a formal
3266 -- abstract subprogram declaration with a class-wide actual.
3268 (Nkind (Inst_Node) = N_Formal_Abstract_Subprogram_Declaration
3269 and then Is_Entity_Name (Nam)))
3270 then
3271 New_S := Analyze_Subprogram_Specification (Spec);
3273 -- Do not attempt to build the wrapper if the renaming is in error
3275 if not Error_Posted (Nam) then
3276 Handle_Instance_With_Class_Wide_Type
3277 (Inst_Node => Inst_Node,
3278 Ren_Id => New_S,
3279 Wrapped_Prim => Wrapped_Prim,
3280 Wrap_Id => Old_S);
3282 -- If several candidates were found, then we reported the
3283 -- ambiguity; stop processing the renaming declaration to
3284 -- avoid reporting further (spurious) errors.
3286 if Error_Posted (Spec) then
3287 return;
3288 end if;
3290 end if;
3291 end if;
3293 if Present (Wrapped_Prim) then
3295 -- When the wrapper is built, the subprogram renaming aliases
3296 -- the wrapper.
3298 Analyze (Nam);
3300 pragma Assert (Old_S = Entity (Nam)
3301 and then Is_Class_Wide_Wrapper (Old_S));
3303 -- The subprogram renaming declaration may become Ghost if it
3304 -- renames a wrapper of a Ghost entity.
3306 Mark_Ghost_Renaming (N, Wrapped_Prim);
3308 elsif Is_Entity_Name (Nam)
3309 and then Present (Entity (Nam))
3310 and then not Comes_From_Source (Nam)
3311 and then not Is_Overloaded (Nam)
3312 then
3313 Old_S := Entity (Nam);
3315 -- The subprogram renaming declaration may become Ghost if it
3316 -- renames a Ghost entity.
3318 Mark_Ghost_Renaming (N, Old_S);
3320 New_S := Analyze_Subprogram_Specification (Spec);
3322 -- Operator case
3324 if Ekind (Old_S) = E_Operator then
3326 -- Box present
3328 if Box_Present (Inst_Node) then
3329 Old_S := Find_Renamed_Entity (N, Name (N), New_S, Is_Actual);
3331 -- If there is an immediately visible homonym of the operator
3332 -- and the declaration has a default, this is worth a warning
3333 -- because the user probably did not intend to get the pre-
3334 -- defined operator, visible in the generic declaration. To
3335 -- find if there is an intended candidate, analyze the renaming
3336 -- again in the current context.
3338 elsif Scope (Old_S) = Standard_Standard
3339 and then Present (Default_Name (Inst_Node))
3340 then
3341 declare
3342 Decl : constant Node_Id := New_Copy_Tree (N);
3343 Hidden : Entity_Id;
3345 begin
3346 Set_Entity (Name (Decl), Empty);
3347 Analyze (Name (Decl));
3348 Hidden :=
3349 Find_Renamed_Entity (Decl, Name (Decl), New_S, True);
3351 if Present (Hidden)
3352 and then In_Open_Scopes (Scope (Hidden))
3353 and then Is_Immediately_Visible (Hidden)
3354 and then Comes_From_Source (Hidden)
3355 and then Hidden /= Old_S
3356 then
3357 Error_Msg_Sloc := Sloc (Hidden);
3358 Error_Msg_N
3359 ("default subprogram is resolved in the generic "
3360 & "declaration (RM 12.6(17))??", N);
3361 Error_Msg_NE ("\and will not use & #??", N, Hidden);
3362 end if;
3363 end;
3364 end if;
3365 end if;
3367 else
3368 Analyze (Nam);
3370 -- The subprogram renaming declaration may become Ghost if it
3371 -- renames a Ghost entity.
3373 if Is_Entity_Name (Nam) then
3374 Mark_Ghost_Renaming (N, Entity (Nam));
3375 end if;
3377 New_S := Analyze_Subprogram_Specification (Spec);
3378 end if;
3380 else
3381 -- Renamed entity must be analyzed first, to avoid being hidden by
3382 -- new name (which might be the same in a generic instance).
3384 Analyze (Nam);
3386 -- The subprogram renaming declaration may become Ghost if it renames
3387 -- a Ghost entity.
3389 if Is_Entity_Name (Nam) then
3390 Mark_Ghost_Renaming (N, Entity (Nam));
3391 end if;
3393 -- The renaming defines a new overloaded entity, which is analyzed
3394 -- like a subprogram declaration.
3396 New_S := Analyze_Subprogram_Specification (Spec);
3397 end if;
3399 if Current_Scope /= Standard_Standard then
3400 Set_Is_Pure (New_S, Is_Pure (Current_Scope));
3401 end if;
3403 -- Set SPARK mode from current context
3405 Set_SPARK_Pragma (New_S, SPARK_Mode_Pragma);
3406 Set_SPARK_Pragma_Inherited (New_S);
3408 Rename_Spec := Find_Corresponding_Spec (N);
3410 -- Case of Renaming_As_Body
3412 if Present (Rename_Spec) then
3413 Check_Previous_Null_Procedure (N, Rename_Spec);
3415 -- Renaming declaration is the completion of the declaration of
3416 -- Rename_Spec. We build an actual body for it at the freezing point.
3418 Set_Corresponding_Spec (N, Rename_Spec);
3420 -- Deal with special case of stream functions of abstract types
3421 -- and interfaces.
3423 if Nkind (Unit_Declaration_Node (Rename_Spec)) =
3424 N_Abstract_Subprogram_Declaration
3425 then
3426 -- Input stream functions are abstract if the object type is
3427 -- abstract. Similarly, all default stream functions for an
3428 -- interface type are abstract. However, these subprograms may
3429 -- receive explicit declarations in representation clauses, making
3430 -- the attribute subprograms usable as defaults in subsequent
3431 -- type extensions.
3432 -- In this case we rewrite the declaration to make the subprogram
3433 -- non-abstract. We remove the previous declaration, and insert
3434 -- the new one at the point of the renaming, to prevent premature
3435 -- access to unfrozen types. The new declaration reuses the
3436 -- specification of the previous one, and must not be analyzed.
3438 pragma Assert
3439 (Is_Primitive (Entity (Nam))
3440 and then
3441 Is_Abstract_Type (Find_Dispatching_Type (Entity (Nam))));
3442 declare
3443 Old_Decl : constant Node_Id :=
3444 Unit_Declaration_Node (Rename_Spec);
3445 New_Decl : constant Node_Id :=
3446 Make_Subprogram_Declaration (Sloc (N),
3447 Specification =>
3448 Relocate_Node (Specification (Old_Decl)));
3449 begin
3450 Remove (Old_Decl);
3451 Insert_After (N, New_Decl);
3452 Set_Is_Abstract_Subprogram (Rename_Spec, False);
3453 Set_Analyzed (New_Decl);
3454 end;
3455 end if;
3457 Set_Corresponding_Body (Unit_Declaration_Node (Rename_Spec), New_S);
3459 if Ada_Version = Ada_83 and then Comes_From_Source (N) then
3460 Error_Msg_N ("(Ada 83) renaming cannot serve as a body", N);
3461 end if;
3463 Set_Convention (New_S, Convention (Rename_Spec));
3464 Check_Fully_Conformant (New_S, Rename_Spec);
3465 Set_Public_Status (New_S);
3467 if No_Return (Rename_Spec)
3468 and then not No_Return (Entity (Nam))
3469 then
3470 Error_Msg_NE
3471 ("renamed subprogram & must be No_Return", N, Entity (Nam));
3472 Error_Msg_N
3473 ("\since renaming subprogram is No_Return (RM 6.5.1(7/2))", N);
3474 end if;
3476 -- The specification does not introduce new formals, but only
3477 -- repeats the formals of the original subprogram declaration.
3478 -- For cross-reference purposes, and for refactoring tools, we
3479 -- treat the formals of the renaming declaration as body formals.
3481 Reference_Body_Formals (Rename_Spec, New_S);
3483 -- Indicate that the entity in the declaration functions like the
3484 -- corresponding body, and is not a new entity. The body will be
3485 -- constructed later at the freeze point, so indicate that the
3486 -- completion has not been seen yet.
3488 Reinit_Field_To_Zero (New_S, F_Has_Out_Or_In_Out_Parameter);
3489 Reinit_Field_To_Zero (New_S, F_Needs_No_Actuals,
3490 Old_Ekind => (E_Function | E_Procedure => True, others => False));
3491 Mutate_Ekind (New_S, E_Subprogram_Body);
3492 New_S := Rename_Spec;
3493 Set_Has_Completion (Rename_Spec, False);
3495 -- Ada 2005: check overriding indicator
3497 if Present (Overridden_Operation (Rename_Spec)) then
3498 if Must_Not_Override (Specification (N)) then
3499 Error_Msg_NE
3500 ("subprogram& overrides inherited operation",
3501 N, Rename_Spec);
3503 elsif Style_Check
3504 and then not Must_Override (Specification (N))
3505 then
3506 Style.Missing_Overriding (N, Rename_Spec);
3507 end if;
3509 elsif Must_Override (Specification (N))
3510 and then not Can_Override_Operator (Rename_Spec)
3511 then
3512 Error_Msg_NE ("subprogram& is not overriding", N, Rename_Spec);
3513 end if;
3515 -- AI12-0132: a renames-as-body freezes the expression of any
3516 -- expression function that it renames.
3518 if Is_Entity_Name (Nam)
3519 and then Is_Expression_Function (Entity (Nam))
3520 and then not Inside_A_Generic
3521 then
3522 Freeze_Expr_Types
3523 (Def_Id => Entity (Nam),
3524 Typ => Etype (Entity (Nam)),
3525 Expr =>
3526 Expression
3527 (Original_Node (Unit_Declaration_Node (Entity (Nam)))),
3528 N => N);
3529 end if;
3531 -- Normal subprogram renaming (not renaming as body)
3533 else
3534 Generate_Definition (New_S);
3535 New_Overloaded_Entity (New_S);
3537 if not (Is_Entity_Name (Nam)
3538 and then Is_Intrinsic_Subprogram (Entity (Nam)))
3539 then
3540 Check_Delayed_Subprogram (New_S);
3541 end if;
3543 -- Verify that a SPARK renaming does not declare a primitive
3544 -- operation of a tagged type.
3546 Check_SPARK_Primitive_Operation (New_S);
3547 end if;
3549 -- There is no need for elaboration checks on the new entity, which may
3550 -- be called before the next freezing point where the body will appear.
3551 -- Elaboration checks refer to the real entity, not the one created by
3552 -- the renaming declaration.
3554 Set_Kill_Elaboration_Checks (New_S, True);
3556 -- If we had a previous error, indicate a completion is present to stop
3557 -- junk cascaded messages, but don't take any further action.
3559 if Etype (Nam) = Any_Type then
3560 Set_Has_Completion (New_S);
3561 return;
3563 -- Case where name has the form of a selected component
3565 elsif Nkind (Nam) = N_Selected_Component then
3567 -- A name which has the form A.B can designate an entry of task A, a
3568 -- protected operation of protected object A, or finally a primitive
3569 -- operation of object A. In the later case, A is an object of some
3570 -- tagged type, or an access type that denotes one such. To further
3571 -- distinguish these cases, note that the scope of a task entry or
3572 -- protected operation is type of the prefix.
3574 -- The prefix could be an overloaded function call that returns both
3575 -- kinds of operations. This overloading pathology is left to the
3576 -- dedicated reader ???
3578 declare
3579 T : constant Entity_Id := Etype (Prefix (Nam));
3581 begin
3582 if Present (T)
3583 and then
3584 (Is_Tagged_Type (T)
3585 or else
3586 (Is_Access_Type (T)
3587 and then Is_Tagged_Type (Designated_Type (T))))
3588 and then Scope (Entity (Selector_Name (Nam))) /= T
3589 then
3590 Analyze_Renamed_Primitive_Operation
3591 (N, New_S, Present (Rename_Spec));
3592 return;
3594 else
3595 -- Renamed entity is an entry or protected operation. For those
3596 -- cases an explicit body is built (at the point of freezing of
3597 -- this entity) that contains a call to the renamed entity.
3599 -- This is not allowed for renaming as body if the renamed
3600 -- spec is already frozen (see RM 8.5.4(5) for details).
3602 if Present (Rename_Spec) and then Is_Frozen (Rename_Spec) then
3603 Error_Msg_N
3604 ("renaming-as-body cannot rename entry as subprogram", N);
3605 Error_Msg_NE
3606 ("\since & is already frozen (RM 8.5.4(5))",
3607 N, Rename_Spec);
3608 else
3609 Analyze_Renamed_Entry (N, New_S, Present (Rename_Spec));
3610 end if;
3612 return;
3613 end if;
3614 end;
3616 -- Case where name is an explicit dereference X.all
3618 elsif Nkind (Nam) = N_Explicit_Dereference then
3620 -- Renamed entity is designated by access_to_subprogram expression.
3621 -- Must build body to encapsulate call, as in the entry case.
3623 Analyze_Renamed_Dereference (N, New_S, Present (Rename_Spec));
3624 return;
3626 -- Indexed component
3628 elsif Nkind (Nam) = N_Indexed_Component then
3629 Analyze_Renamed_Family_Member (N, New_S, Present (Rename_Spec));
3630 return;
3632 -- Character literal
3634 elsif Nkind (Nam) = N_Character_Literal then
3635 Analyze_Renamed_Character (N, New_S, Present (Rename_Spec));
3636 return;
3638 -- Only remaining case is where we have a non-entity name, or a renaming
3639 -- of some other non-overloadable entity.
3641 elsif not Is_Entity_Name (Nam)
3642 or else not Is_Overloadable (Entity (Nam))
3643 then
3644 -- Do not mention the renaming if it comes from an instance
3646 if not Is_Actual then
3647 Error_Msg_N ("expect valid subprogram name in renaming", N);
3648 else
3649 Error_Msg_NE ("no visible subprogram for formal&", N, Nam);
3650 end if;
3652 return;
3653 end if;
3655 -- Find the renamed entity that matches the given specification. Disable
3656 -- Ada_83 because there is no requirement of full conformance between
3657 -- renamed entity and new entity, even though the same circuit is used.
3659 -- This is a bit of an odd case, which introduces a really irregular use
3660 -- of Ada_Version[_Explicit]. Would be nice to find cleaner way to do
3661 -- this. ???
3663 Ada_Version := Ada_Version_Type'Max (Ada_Version, Ada_95);
3664 Ada_Version_Pragma := Empty;
3665 Ada_Version_Explicit := Ada_Version;
3667 if No (Old_S) then
3668 Old_S := Find_Renamed_Entity (N, Name (N), New_S, Is_Actual);
3670 -- The visible operation may be an inherited abstract operation that
3671 -- was overridden in the private part, in which case a call will
3672 -- dispatch to the overriding operation. Use the overriding one in
3673 -- the renaming declaration, to prevent spurious errors below.
3675 if Is_Overloadable (Old_S)
3676 and then Is_Abstract_Subprogram (Old_S)
3677 and then No (DTC_Entity (Old_S))
3678 and then Present (Alias (Old_S))
3679 and then not Is_Abstract_Subprogram (Alias (Old_S))
3680 and then Present (Overridden_Operation (Alias (Old_S)))
3681 then
3682 Old_S := Alias (Old_S);
3683 end if;
3685 -- When the renamed subprogram is overloaded and used as an actual
3686 -- of a generic, its entity is set to the first available homonym.
3687 -- We must first disambiguate the name, then set the proper entity.
3689 if Is_Actual and then Is_Overloaded (Nam) then
3690 Set_Entity (Nam, Old_S);
3691 end if;
3692 end if;
3694 -- Most common case: subprogram renames subprogram. No body is generated
3695 -- in this case, so we must indicate the declaration is complete as is.
3696 -- and inherit various attributes of the renamed subprogram.
3698 if No (Rename_Spec) then
3699 Set_Has_Completion (New_S);
3700 Set_Is_Imported (New_S, Is_Imported (Entity (Nam)));
3701 Set_Is_Pure (New_S, Is_Pure (Entity (Nam)));
3702 Set_Is_Preelaborated (New_S, Is_Preelaborated (Entity (Nam)));
3704 -- Ada 2005 (AI-423): Check the consistency of null exclusions
3705 -- between a subprogram and its correct renaming.
3707 -- Note: the Any_Id check is a guard that prevents compiler crashes
3708 -- when performing a null exclusion check between a renaming and a
3709 -- renamed subprogram that has been found to be illegal.
3711 if Ada_Version >= Ada_2005 and then Entity (Nam) /= Any_Id then
3712 Check_Null_Exclusion
3713 (Ren => New_S,
3714 Sub => Entity (Nam));
3715 end if;
3717 -- Enforce the Ada 2005 rule that the renamed entity cannot require
3718 -- overriding. The flag Requires_Overriding is set very selectively
3719 -- and misses some other illegal cases. The additional conditions
3720 -- checked below are sufficient but not necessary ???
3722 -- The rule does not apply to the renaming generated for an actual
3723 -- subprogram in an instance.
3725 if Is_Actual then
3726 null;
3728 -- Guard against previous errors, and omit renamings of predefined
3729 -- operators.
3731 elsif Ekind (Old_S) not in E_Function | E_Procedure then
3732 null;
3734 elsif Requires_Overriding (Old_S)
3735 or else
3736 (Is_Abstract_Subprogram (Old_S)
3737 and then Present (Find_Dispatching_Type (Old_S))
3738 and then not Is_Abstract_Type (Find_Dispatching_Type (Old_S)))
3739 then
3740 Error_Msg_N
3741 ("renamed entity cannot be subprogram that requires overriding "
3742 & "(RM 8.5.4 (5.1))", N);
3743 end if;
3745 declare
3746 Prev : constant Entity_Id := Overridden_Operation (New_S);
3747 begin
3748 if Present (Prev)
3749 and then
3750 (Has_Non_Trivial_Precondition (Prev)
3751 or else Has_Non_Trivial_Precondition (Old_S))
3752 then
3753 Error_Msg_NE
3754 ("conflicting inherited classwide preconditions in renaming "
3755 & "of& (RM 6.1.1 (17)", N, Old_S);
3756 end if;
3757 end;
3758 end if;
3760 if Old_S /= Any_Id then
3761 if Is_Actual and then From_Default (N) then
3763 -- This is an implicit reference to the default actual
3765 Generate_Reference (Old_S, Nam, Typ => 'i', Force => True);
3767 else
3768 Generate_Reference (Old_S, Nam);
3769 end if;
3771 Check_Internal_Protected_Use (N, Old_S);
3773 -- For a renaming-as-body, require subtype conformance, but if the
3774 -- declaration being completed has not been frozen, then inherit the
3775 -- convention of the renamed subprogram prior to checking conformance
3776 -- (unless the renaming has an explicit convention established; the
3777 -- rule stated in the RM doesn't seem to address this ???).
3779 if Present (Rename_Spec) then
3780 Generate_Reference (Rename_Spec, Defining_Entity (Spec), 'b');
3781 Style.Check_Identifier (Defining_Entity (Spec), Rename_Spec);
3783 if not Is_Frozen (Rename_Spec) then
3784 if not Has_Convention_Pragma (Rename_Spec) then
3785 Set_Convention (New_S, Convention (Old_S));
3786 end if;
3788 if Ekind (Old_S) /= E_Operator then
3789 Check_Mode_Conformant (New_S, Old_S, Spec);
3790 end if;
3792 if Original_Subprogram (Old_S) = Rename_Spec then
3793 Error_Msg_N ("unfrozen subprogram cannot rename itself", N);
3794 else
3795 Check_Formal_Subprogram_Conformance (New_S, Old_S, Spec);
3796 end if;
3797 else
3798 Check_Subtype_Conformant (New_S, Old_S, Spec);
3799 end if;
3801 Check_Frozen_Renaming (N, Rename_Spec);
3803 -- Check explicitly that renamed entity is not intrinsic, because
3804 -- in a generic the renamed body is not built. In this case,
3805 -- the renaming_as_body is a completion.
3807 if Inside_A_Generic then
3808 if Is_Frozen (Rename_Spec)
3809 and then Is_Intrinsic_Subprogram (Old_S)
3810 then
3811 Error_Msg_N
3812 ("subprogram in renaming_as_body cannot be intrinsic",
3813 Name (N));
3814 end if;
3816 Set_Has_Completion (Rename_Spec);
3817 end if;
3819 elsif Ekind (Old_S) /= E_Operator then
3821 -- If this a defaulted subprogram for a class-wide actual there is
3822 -- no check for mode conformance, given that the signatures don't
3823 -- match (the source mentions T but the actual mentions T'Class).
3825 if CW_Actual then
3826 null;
3828 -- No need for a redundant error message if this is a nested
3829 -- instance, unless the current instantiation (of a child unit)
3830 -- is a compilation unit, which is not analyzed when the parent
3831 -- generic is analyzed.
3833 elsif not Is_Actual
3834 or else No (Enclosing_Instance)
3835 or else Is_Compilation_Unit (Current_Scope)
3836 then
3837 Check_Mode_Conformant (New_S, Old_S);
3838 end if;
3839 end if;
3841 if No (Rename_Spec) then
3843 -- The parameter profile of the new entity is that of the renamed
3844 -- entity: the subtypes given in the specification are irrelevant.
3846 Inherit_Renamed_Profile (New_S, Old_S);
3848 -- A call to the subprogram is transformed into a call to the
3849 -- renamed entity. This is transitive if the renamed entity is
3850 -- itself a renaming.
3852 if Present (Alias (Old_S)) then
3853 Set_Alias (New_S, Alias (Old_S));
3854 else
3855 Set_Alias (New_S, Old_S);
3856 end if;
3858 -- Note that we do not set Is_Intrinsic_Subprogram if we have a
3859 -- renaming as body, since the entity in this case is not an
3860 -- intrinsic (it calls an intrinsic, but we have a real body for
3861 -- this call, and it is in this body that the required intrinsic
3862 -- processing will take place).
3864 -- Also, if this is a renaming of inequality, the renamed operator
3865 -- is intrinsic, but what matters is the corresponding equality
3866 -- operator, which may be user-defined.
3868 Set_Is_Intrinsic_Subprogram
3869 (New_S,
3870 Is_Intrinsic_Subprogram (Old_S)
3871 and then
3872 (Chars (Old_S) /= Name_Op_Ne
3873 or else Ekind (Old_S) = E_Operator
3874 or else Is_Intrinsic_Subprogram
3875 (Corresponding_Equality (Old_S))));
3877 if Ekind (Alias (New_S)) = E_Operator then
3878 Set_Has_Delayed_Freeze (New_S, False);
3879 end if;
3881 -- If the renaming corresponds to an association for an abstract
3882 -- formal subprogram, then various attributes must be set to
3883 -- indicate that the renaming is an abstract dispatching operation
3884 -- with a controlling type.
3886 -- Skip this decoration when the renaming corresponds to an
3887 -- association with class-wide wrapper (see above) because such
3888 -- wrapper is neither abstract nor a dispatching operation (its
3889 -- body has the dispatching call to the wrapped primitive).
3891 if Is_Actual
3892 and then Is_Abstract_Subprogram (Formal_Spec)
3893 and then No (Wrapped_Prim)
3894 then
3896 -- Mark the renaming as abstract here, so Find_Dispatching_Type
3897 -- see it as corresponding to a generic association for a
3898 -- formal abstract subprogram
3900 Set_Is_Abstract_Subprogram (New_S);
3902 declare
3903 New_S_Ctrl_Type : constant Entity_Id :=
3904 Find_Dispatching_Type (New_S);
3905 Old_S_Ctrl_Type : constant Entity_Id :=
3906 Find_Dispatching_Type (Old_S);
3908 begin
3910 -- The actual must match the (instance of the) formal,
3911 -- and must be a controlling type.
3913 if Old_S_Ctrl_Type /= New_S_Ctrl_Type
3914 or else No (New_S_Ctrl_Type)
3915 then
3916 if No (New_S_Ctrl_Type) then
3917 Error_Msg_N
3918 ("actual must be dispatching subprogram", Nam);
3919 else
3920 Error_Msg_NE
3921 ("actual must be dispatching subprogram for type&",
3922 Nam, New_S_Ctrl_Type);
3923 end if;
3925 else
3926 Set_Is_Dispatching_Operation (New_S);
3927 Check_Controlling_Formals (New_S_Ctrl_Type, New_S);
3929 -- If the actual in the formal subprogram is itself a
3930 -- formal abstract subprogram association, there's no
3931 -- dispatch table component or position to inherit.
3933 if Present (DTC_Entity (Old_S)) then
3934 Set_DTC_Entity (New_S, DTC_Entity (Old_S));
3935 Set_DT_Position_Value (New_S, DT_Position (Old_S));
3936 end if;
3937 end if;
3938 end;
3939 end if;
3940 end if;
3942 if Is_Actual then
3943 null;
3945 -- The following is illegal, because F hides whatever other F may
3946 -- be around:
3947 -- function F (...) renames F;
3949 elsif Old_S = New_S
3950 or else (Nkind (Nam) /= N_Expanded_Name
3951 and then Chars (Old_S) = Chars (New_S))
3952 then
3953 Error_Msg_N ("subprogram cannot rename itself", N);
3955 -- This is illegal even if we use a selector:
3956 -- function F (...) renames Pkg.F;
3957 -- because F is still hidden.
3959 elsif Nkind (Nam) = N_Expanded_Name
3960 and then Entity (Prefix (Nam)) = Current_Scope
3961 and then Chars (Selector_Name (Nam)) = Chars (New_S)
3962 then
3963 -- This is an error, but we overlook the error and accept the
3964 -- renaming if the special Overriding_Renamings mode is in effect.
3966 if not Overriding_Renamings then
3967 Error_Msg_NE
3968 ("implicit operation& is not visible (RM 8.3 (15))",
3969 Nam, Old_S);
3970 end if;
3972 -- Check whether an expanded name used for the renamed subprogram
3973 -- begins with the same name as the renaming itself, and if so,
3974 -- issue an error about the prefix being hidden by the renaming.
3975 -- We exclude generic instances from this checking, since such
3976 -- normally illegal renamings can be constructed when expanding
3977 -- instantiations.
3979 elsif Nkind (Nam) = N_Expanded_Name and then not In_Instance then
3980 declare
3981 function Ult_Expanded_Prefix (N : Node_Id) return Node_Id is
3982 (if Nkind (N) /= N_Expanded_Name
3983 then N
3984 else Ult_Expanded_Prefix (Prefix (N)));
3985 -- Returns the ultimate prefix of an expanded name
3987 begin
3988 if Chars (Entity (Ult_Expanded_Prefix (Nam))) = Chars (New_S)
3989 then
3990 Error_Msg_Sloc := Sloc (N);
3991 Error_Msg_NE
3992 ("& is hidden by declaration#", Nam, New_S);
3993 end if;
3994 end;
3995 end if;
3997 Set_Convention (New_S, Convention (Old_S));
3999 if Is_Abstract_Subprogram (Old_S) then
4000 if Present (Rename_Spec) then
4001 Error_Msg_N
4002 ("a renaming-as-body cannot rename an abstract subprogram",
4004 Set_Has_Completion (Rename_Spec);
4005 else
4006 Set_Is_Abstract_Subprogram (New_S);
4007 end if;
4008 end if;
4010 Check_Library_Unit_Renaming (N, Old_S);
4012 -- Pathological case: procedure renames entry in the scope of its
4013 -- task. Entry is given by simple name, but body must be built for
4014 -- procedure. Of course if called it will deadlock.
4016 if Ekind (Old_S) = E_Entry then
4017 Set_Has_Completion (New_S, False);
4018 Set_Alias (New_S, Empty);
4019 end if;
4021 -- Do not freeze the renaming nor the renamed entity when the context
4022 -- is an enclosing generic. Freezing is an expansion activity, and in
4023 -- addition the renamed entity may depend on the generic formals of
4024 -- the enclosing generic.
4026 if Is_Actual and not Inside_A_Generic then
4027 Freeze_Before (N, Old_S);
4028 Freeze_Actual_Profile;
4029 Set_Has_Delayed_Freeze (New_S, False);
4030 Freeze_Before (N, New_S);
4032 if (Ekind (Old_S) = E_Procedure or else Ekind (Old_S) = E_Function)
4033 and then not Is_Abstract_Subprogram (Formal_Spec)
4034 then
4035 -- An abstract subprogram is only allowed as an actual in the
4036 -- case where the formal subprogram is also abstract.
4038 if Is_Abstract_Subprogram (Old_S) then
4039 Error_Msg_N
4040 ("abstract subprogram not allowed as generic actual", Nam);
4041 end if;
4043 -- AI12-0412: A primitive of an abstract type with Pre'Class
4044 -- or Post'Class aspects specified with nonstatic expressions
4045 -- is not allowed as actual for a nonabstract formal subprogram
4046 -- (see RM 6.1.1(18.2/5).
4048 if Is_Dispatching_Operation (Old_S)
4049 and then
4050 Is_Prim_Of_Abst_Type_With_Nonstatic_CW_Pre_Post (Old_S)
4051 then
4052 Error_Msg_N
4053 ("primitive of abstract type with nonstatic class-wide "
4054 & "pre/postconditions not allowed as actual",
4055 Nam);
4056 end if;
4057 end if;
4058 end if;
4060 else
4061 -- A common error is to assume that implicit operators for types are
4062 -- defined in Standard, or in the scope of a subtype. In those cases
4063 -- where the renamed entity is given with an expanded name, it is
4064 -- worth mentioning that operators for the type are not declared in
4065 -- the scope given by the prefix.
4067 if Nkind (Nam) = N_Expanded_Name
4068 and then Nkind (Selector_Name (Nam)) = N_Operator_Symbol
4069 and then Scope (Entity (Nam)) = Standard_Standard
4070 then
4071 declare
4072 T : constant Entity_Id :=
4073 Base_Type (Etype (First_Formal (New_S)));
4074 begin
4075 Error_Msg_Node_2 := Prefix (Nam);
4076 Error_Msg_NE
4077 ("operator for type& is not declared in&", Prefix (Nam), T);
4078 end;
4080 else
4081 Error_Msg_NE
4082 ("no visible subprogram matches the specification for&",
4083 Spec, New_S);
4084 end if;
4086 if Present (Candidate_Renaming) then
4087 declare
4088 F1 : Entity_Id;
4089 F2 : Entity_Id;
4090 T1 : Entity_Id;
4092 begin
4093 F1 := First_Formal (Candidate_Renaming);
4094 F2 := First_Formal (New_S);
4095 T1 := First_Subtype (Etype (F1));
4096 while Present (F1) and then Present (F2) loop
4097 Next_Formal (F1);
4098 Next_Formal (F2);
4099 end loop;
4101 if Present (F1) and then Present (Default_Value (F1)) then
4102 if Present (Next_Formal (F1)) then
4103 Error_Msg_NE
4104 ("\missing specification for & and other formals with "
4105 & "defaults", Spec, F1);
4106 else
4107 Error_Msg_NE ("\missing specification for &", Spec, F1);
4108 end if;
4109 end if;
4111 if Nkind (Nam) = N_Operator_Symbol
4112 and then From_Default (N)
4113 then
4114 Error_Msg_Node_2 := T1;
4115 Error_Msg_NE
4116 ("default & on & is not directly visible", Nam, Nam);
4117 end if;
4118 end;
4119 end if;
4120 end if;
4122 -- Ada 2005 AI 404: if the new subprogram is dispatching, verify that
4123 -- controlling access parameters are known non-null for the renamed
4124 -- subprogram. Test also applies to a subprogram instantiation that
4125 -- is dispatching. Test is skipped if some previous error was detected
4126 -- that set Old_S to Any_Id.
4128 if Ada_Version >= Ada_2005
4129 and then Old_S /= Any_Id
4130 and then not Is_Dispatching_Operation (Old_S)
4131 and then Is_Dispatching_Operation (New_S)
4132 then
4133 declare
4134 Old_F : Entity_Id;
4135 New_F : Entity_Id;
4137 begin
4138 Old_F := First_Formal (Old_S);
4139 New_F := First_Formal (New_S);
4140 while Present (Old_F) loop
4141 if Ekind (Etype (Old_F)) = E_Anonymous_Access_Type
4142 and then Is_Controlling_Formal (New_F)
4143 and then not Can_Never_Be_Null (Old_F)
4144 then
4145 Error_Msg_N ("access parameter is controlling,", New_F);
4146 Error_Msg_NE
4147 ("\corresponding parameter of& must be explicitly null "
4148 & "excluding", New_F, Old_S);
4149 end if;
4151 Next_Formal (Old_F);
4152 Next_Formal (New_F);
4153 end loop;
4154 end;
4155 end if;
4157 -- A useful warning, suggested by Ada Bug Finder (Ada-Europe 2005)
4158 -- is to warn if an operator is being renamed as a different operator.
4159 -- If the operator is predefined, examine the kind of the entity, not
4160 -- the abbreviated declaration in Standard.
4162 if Comes_From_Source (N)
4163 and then Present (Old_S)
4164 and then (Nkind (Old_S) = N_Defining_Operator_Symbol
4165 or else Ekind (Old_S) = E_Operator)
4166 and then Nkind (New_S) = N_Defining_Operator_Symbol
4167 and then Chars (Old_S) /= Chars (New_S)
4168 then
4169 Error_Msg_NE
4170 ("& is being renamed as a different operator??", N, Old_S);
4171 end if;
4173 -- Check for renaming of obsolescent subprogram
4175 Check_Obsolescent_2005_Entity (Entity (Nam), Nam);
4177 -- Another warning or some utility: if the new subprogram as the same
4178 -- name as the old one, the old one is not hidden by an outer homograph,
4179 -- the new one is not a public symbol, and the old one is otherwise
4180 -- directly visible, the renaming is superfluous.
4182 if Chars (Old_S) = Chars (New_S)
4183 and then Comes_From_Source (N)
4184 and then Scope (Old_S) /= Standard_Standard
4185 and then Warn_On_Redundant_Constructs
4186 and then (Is_Immediately_Visible (Old_S)
4187 or else Is_Potentially_Use_Visible (Old_S))
4188 and then Is_Overloadable (Current_Scope)
4189 and then Chars (Current_Scope) /= Chars (Old_S)
4190 then
4191 Error_Msg_N
4192 ("redundant renaming, entity is directly visible?r?", Name (N));
4193 end if;
4195 -- Implementation-defined aspect specifications can appear in a renaming
4196 -- declaration, but not language-defined ones. The call to procedure
4197 -- Analyze_Aspect_Specifications will take care of this error check.
4199 if Has_Aspects (N) then
4200 Analyze_Aspect_Specifications (N, New_S);
4201 end if;
4203 -- AI12-0279
4205 if Is_Actual
4206 and then Has_Yield_Aspect (Formal_Spec)
4207 and then not Has_Yield_Aspect (Old_S)
4208 then
4209 Error_Msg_Name_1 := Name_Yield;
4210 Error_Msg_N
4211 ("actual subprogram& must have aspect% to match formal", Name (N));
4212 end if;
4214 Ada_Version := Save_AV;
4215 Ada_Version_Pragma := Save_AVP;
4216 Ada_Version_Explicit := Save_AV_Exp;
4218 -- Check if we are looking at an Ada 2012 defaulted formal subprogram
4219 -- and mark any use_package_clauses that affect the visibility of the
4220 -- implicit generic actual.
4222 -- Also, we may be looking at an internal renaming of a user-defined
4223 -- subprogram created for a generic formal subprogram association,
4224 -- which will also have to be marked here. This can occur when the
4225 -- corresponding formal subprogram contains references to other generic
4226 -- formals.
4228 if Is_Generic_Actual_Subprogram (New_S)
4229 and then (Is_Intrinsic_Subprogram (New_S)
4230 or else From_Default (N)
4231 or else Nkind (N) = N_Subprogram_Renaming_Declaration)
4232 then
4233 Mark_Use_Clauses (New_S);
4235 -- Handle overloaded subprograms
4237 if Present (Alias (New_S)) then
4238 Mark_Use_Clauses (Alias (New_S));
4239 end if;
4240 end if;
4241 end Analyze_Subprogram_Renaming;
4243 -------------------------
4244 -- Analyze_Use_Package --
4245 -------------------------
4247 -- Resolve the package names in the use clause, and make all the visible
4248 -- entities defined in the package potentially use-visible. If the package
4249 -- is already in use from a previous use clause, its visible entities are
4250 -- already use-visible. In that case, mark the occurrence as a redundant
4251 -- use. If the package is an open scope, i.e. if the use clause occurs
4252 -- within the package itself, ignore it.
4254 procedure Analyze_Use_Package (N : Node_Id; Chain : Boolean := True) is
4255 procedure Analyze_Package_Name (Clause : Node_Id);
4256 -- Perform analysis on a package name from a use_package_clause
4258 procedure Analyze_Package_Name_List (Head_Clause : Node_Id);
4259 -- Similar to Analyze_Package_Name but iterates over all the names
4260 -- in a use clause.
4262 --------------------------
4263 -- Analyze_Package_Name --
4264 --------------------------
4266 procedure Analyze_Package_Name (Clause : Node_Id) is
4267 Pack : constant Node_Id := Name (Clause);
4268 Pref : Node_Id;
4270 begin
4271 pragma Assert (Nkind (Clause) = N_Use_Package_Clause);
4272 Analyze (Pack);
4274 -- Verify that the package standard is not directly named in a
4275 -- use_package_clause.
4277 if Nkind (Parent (Clause)) = N_Compilation_Unit
4278 and then Nkind (Pack) = N_Expanded_Name
4279 then
4280 Pref := Prefix (Pack);
4282 while Nkind (Pref) = N_Expanded_Name loop
4283 Pref := Prefix (Pref);
4284 end loop;
4286 if Entity (Pref) = Standard_Standard then
4287 Error_Msg_N
4288 ("predefined package Standard cannot appear in a context "
4289 & "clause", Pref);
4290 end if;
4291 end if;
4292 end Analyze_Package_Name;
4294 -------------------------------
4295 -- Analyze_Package_Name_List --
4296 -------------------------------
4298 procedure Analyze_Package_Name_List (Head_Clause : Node_Id) is
4299 Curr : Node_Id;
4301 begin
4302 -- Due to the way source use clauses are split during parsing we are
4303 -- forced to simply iterate through all entities in scope until the
4304 -- clause representing the last name in the list is found.
4306 Curr := Head_Clause;
4307 while Present (Curr) loop
4308 Analyze_Package_Name (Curr);
4310 -- Stop iterating over the names in the use clause when we are at
4311 -- the last one.
4313 exit when not More_Ids (Curr) and then Prev_Ids (Curr);
4314 Next (Curr);
4315 end loop;
4316 end Analyze_Package_Name_List;
4318 -- Local variables
4320 Pack : Entity_Id;
4322 -- Start of processing for Analyze_Use_Package
4324 begin
4325 Set_Hidden_By_Use_Clause (N, No_Elist);
4327 -- Use clause not allowed in a spec of a predefined package declaration
4328 -- except that packages whose file name starts a-n are OK (these are
4329 -- children of Ada.Numerics, which are never loaded by Rtsfind).
4331 if Is_Predefined_Unit (Current_Sem_Unit)
4332 and then Get_Name_String
4333 (Unit_File_Name (Current_Sem_Unit)) (1 .. 3) /= "a-n"
4334 and then Nkind (Unit (Cunit (Current_Sem_Unit))) =
4335 N_Package_Declaration
4336 then
4337 Error_Msg_N ("use clause not allowed in predefined spec", N);
4338 end if;
4340 -- Loop through all package names from the original use clause in
4341 -- order to analyze referenced packages. A use_package_clause with only
4342 -- one name does not have More_Ids or Prev_Ids set, while a clause with
4343 -- More_Ids only starts the chain produced by the parser.
4345 if not More_Ids (N) and then not Prev_Ids (N) then
4346 Analyze_Package_Name (N);
4348 elsif More_Ids (N) and then not Prev_Ids (N) then
4349 Analyze_Package_Name_List (N);
4350 end if;
4352 if not Is_Entity_Name (Name (N)) then
4353 Error_Msg_N ("& is not a package", Name (N));
4355 return;
4356 end if;
4358 if Chain then
4359 Chain_Use_Clause (N);
4360 end if;
4362 Pack := Entity (Name (N));
4364 -- There are many cases where scopes are manipulated during analysis, so
4365 -- check that Pack's current use clause has not already been chained
4366 -- before setting its previous use clause.
4368 if Ekind (Pack) = E_Package
4369 and then Present (Current_Use_Clause (Pack))
4370 and then Current_Use_Clause (Pack) /= N
4371 and then No (Prev_Use_Clause (N))
4372 and then Prev_Use_Clause (Current_Use_Clause (Pack)) /= N
4373 then
4374 Set_Prev_Use_Clause (N, Current_Use_Clause (Pack));
4375 end if;
4377 -- Mark all entities as potentially use visible
4379 if Ekind (Pack) /= E_Package and then Etype (Pack) /= Any_Type then
4380 if Ekind (Pack) = E_Generic_Package then
4381 Error_Msg_N -- CODEFIX
4382 ("a generic package is not allowed in a use clause", Name (N));
4384 elsif Is_Generic_Subprogram (Pack) then
4385 Error_Msg_N -- CODEFIX
4386 ("a generic subprogram is not allowed in a use clause",
4387 Name (N));
4389 elsif Is_Subprogram (Pack) then
4390 Error_Msg_N -- CODEFIX
4391 ("a subprogram is not allowed in a use clause", Name (N));
4393 else
4394 Error_Msg_N ("& is not allowed in a use clause", Name (N));
4395 end if;
4397 else
4398 if Nkind (Parent (N)) = N_Compilation_Unit then
4399 Check_In_Previous_With_Clause (N, Name (N));
4400 end if;
4402 Use_One_Package (N, Name (N));
4403 end if;
4405 Mark_Ghost_Clause (N);
4406 end Analyze_Use_Package;
4408 ----------------------
4409 -- Analyze_Use_Type --
4410 ----------------------
4412 procedure Analyze_Use_Type (N : Node_Id; Chain : Boolean := True) is
4413 E : Entity_Id;
4414 Id : Node_Id;
4416 begin
4417 Set_Hidden_By_Use_Clause (N, No_Elist);
4419 -- Chain clause to list of use clauses in current scope when flagged
4421 if Chain then
4422 Chain_Use_Clause (N);
4423 end if;
4425 -- Obtain the base type of the type denoted within the use_type_clause's
4426 -- subtype mark.
4428 Id := Subtype_Mark (N);
4429 Find_Type (Id);
4430 E := Base_Type (Entity (Id));
4432 -- There are many cases where a use_type_clause may be reanalyzed due to
4433 -- manipulation of the scope stack so we much guard against those cases
4434 -- here, otherwise, we must add the new use_type_clause to the previous
4435 -- use_type_clause chain in order to mark redundant use_type_clauses as
4436 -- used. When the redundant use-type clauses appear in a parent unit and
4437 -- a child unit we must prevent a circularity in the chain that would
4438 -- otherwise result from the separate steps of analysis and installation
4439 -- of the parent context.
4441 if Present (Current_Use_Clause (E))
4442 and then Current_Use_Clause (E) /= N
4443 and then Prev_Use_Clause (Current_Use_Clause (E)) /= N
4444 and then No (Prev_Use_Clause (N))
4445 then
4446 Set_Prev_Use_Clause (N, Current_Use_Clause (E));
4447 end if;
4449 -- If the Used_Operations list is already initialized, the clause has
4450 -- been analyzed previously, and it is being reinstalled, for example
4451 -- when the clause appears in a package spec and we are compiling the
4452 -- corresponding package body. In that case, make the entities on the
4453 -- existing list use_visible, and mark the corresponding types In_Use.
4455 if Present (Used_Operations (N)) then
4456 declare
4457 Elmt : Elmt_Id;
4459 begin
4460 Use_One_Type (Subtype_Mark (N), Installed => True);
4462 Elmt := First_Elmt (Used_Operations (N));
4463 while Present (Elmt) loop
4464 Set_Is_Potentially_Use_Visible (Node (Elmt));
4465 Next_Elmt (Elmt);
4466 end loop;
4467 end;
4469 return;
4470 end if;
4472 -- Otherwise, create new list and attach to it the operations that are
4473 -- made use-visible by the clause.
4475 Set_Used_Operations (N, New_Elmt_List);
4476 E := Entity (Id);
4478 if E /= Any_Type then
4479 Use_One_Type (Id);
4481 if Nkind (Parent (N)) = N_Compilation_Unit then
4482 if Nkind (Id) = N_Identifier then
4483 Error_Msg_N ("type is not directly visible", Id);
4485 elsif Is_Child_Unit (Scope (E))
4486 and then Scope (E) /= System_Aux_Id
4487 then
4488 Check_In_Previous_With_Clause (N, Prefix (Id));
4489 end if;
4490 end if;
4492 else
4493 -- If the use_type_clause appears in a compilation unit context,
4494 -- check whether it comes from a unit that may appear in a
4495 -- limited_with_clause, for a better error message.
4497 if Nkind (Parent (N)) = N_Compilation_Unit
4498 and then Nkind (Id) /= N_Identifier
4499 then
4500 declare
4501 Item : Node_Id;
4502 Pref : Node_Id;
4504 function Mentioned (Nam : Node_Id) return Boolean;
4505 -- Check whether the prefix of expanded name for the type
4506 -- appears in the prefix of some limited_with_clause.
4508 ---------------
4509 -- Mentioned --
4510 ---------------
4512 function Mentioned (Nam : Node_Id) return Boolean is
4513 begin
4514 return Nkind (Name (Item)) = N_Selected_Component
4515 and then Chars (Prefix (Name (Item))) = Chars (Nam);
4516 end Mentioned;
4518 begin
4519 Pref := Prefix (Id);
4520 Item := First (Context_Items (Parent (N)));
4521 while Present (Item) and then Item /= N loop
4522 if Nkind (Item) = N_With_Clause
4523 and then Limited_Present (Item)
4524 and then Mentioned (Pref)
4525 then
4526 Change_Error_Text
4527 (Get_Msg_Id, "premature usage of incomplete type");
4528 end if;
4530 Next (Item);
4531 end loop;
4532 end;
4533 end if;
4534 end if;
4536 Mark_Ghost_Clause (N);
4537 end Analyze_Use_Type;
4539 ------------------------
4540 -- Attribute_Renaming --
4541 ------------------------
4543 procedure Attribute_Renaming (N : Node_Id) is
4544 Loc : constant Source_Ptr := Sloc (N);
4545 Nam : constant Node_Id := Name (N);
4546 Spec : constant Node_Id := Specification (N);
4547 New_S : constant Entity_Id := Defining_Unit_Name (Spec);
4548 Aname : constant Name_Id := Attribute_Name (Nam);
4550 Form_Num : Nat := 0;
4551 Expr_List : List_Id := No_List;
4553 Attr_Node : Node_Id;
4554 Body_Node : Node_Id;
4555 Param_Spec : Node_Id;
4557 begin
4558 Generate_Definition (New_S);
4560 -- This procedure is called in the context of subprogram renaming, and
4561 -- thus the attribute must be one that is a subprogram. All of those
4562 -- have at least one formal parameter, with the exceptions of the GNAT
4563 -- attribute 'Img, which GNAT treats as renameable.
4565 if Is_Empty_List (Parameter_Specifications (Spec)) then
4566 if Aname /= Name_Img then
4567 Error_Msg_N
4568 ("subprogram renaming an attribute must have formals", N);
4569 return;
4570 end if;
4572 else
4573 Param_Spec := First (Parameter_Specifications (Spec));
4574 while Present (Param_Spec) loop
4575 Form_Num := Form_Num + 1;
4577 if Nkind (Parameter_Type (Param_Spec)) /= N_Access_Definition then
4578 Find_Type (Parameter_Type (Param_Spec));
4580 -- The profile of the new entity denotes the base type (s) of
4581 -- the types given in the specification. For access parameters
4582 -- there are no subtypes involved.
4584 Rewrite (Parameter_Type (Param_Spec),
4585 New_Occurrence_Of
4586 (Base_Type (Entity (Parameter_Type (Param_Spec))), Loc));
4587 end if;
4589 if No (Expr_List) then
4590 Expr_List := New_List;
4591 end if;
4593 Append_To (Expr_List,
4594 Make_Identifier (Loc,
4595 Chars => Chars (Defining_Identifier (Param_Spec))));
4597 -- The expressions in the attribute reference are not freeze
4598 -- points. Neither is the attribute as a whole, see below.
4600 Set_Must_Not_Freeze (Last (Expr_List));
4601 Next (Param_Spec);
4602 end loop;
4603 end if;
4605 -- Immediate error if too many formals. Other mismatches in number or
4606 -- types of parameters are detected when we analyze the body of the
4607 -- subprogram that we construct.
4609 if Form_Num > 2 then
4610 Error_Msg_N ("too many formals for attribute", N);
4612 -- Error if the attribute reference has expressions that look like
4613 -- formal parameters.
4615 elsif Present (Expressions (Nam)) then
4616 Error_Msg_N ("illegal expressions in attribute reference", Nam);
4618 elsif Aname in Name_Compose | Name_Exponent | Name_Leading_Part |
4619 Name_Pos | Name_Round | Name_Scaling |
4620 Name_Val
4621 then
4622 if Nkind (N) = N_Subprogram_Renaming_Declaration
4623 and then Present (Corresponding_Formal_Spec (N))
4624 then
4625 Error_Msg_N
4626 ("generic actual cannot be attribute involving universal type",
4627 Nam);
4628 else
4629 Error_Msg_N
4630 ("attribute involving a universal type cannot be renamed",
4631 Nam);
4632 end if;
4633 end if;
4635 -- Rewrite attribute node to have a list of expressions corresponding to
4636 -- the subprogram formals. A renaming declaration is not a freeze point,
4637 -- and the analysis of the attribute reference should not freeze the
4638 -- type of the prefix. We use the original node in the renaming so that
4639 -- its source location is preserved, and checks on stream attributes are
4640 -- properly applied.
4642 Attr_Node := Relocate_Node (Nam);
4643 Set_Expressions (Attr_Node, Expr_List);
4645 Set_Must_Not_Freeze (Attr_Node);
4646 Set_Must_Not_Freeze (Prefix (Nam));
4648 -- Case of renaming a function
4650 if Nkind (Spec) = N_Function_Specification then
4651 if Is_Procedure_Attribute_Name (Aname) then
4652 Error_Msg_N ("attribute can only be renamed as procedure", Nam);
4653 return;
4654 end if;
4656 Find_Type (Result_Definition (Spec));
4657 Rewrite (Result_Definition (Spec),
4658 New_Occurrence_Of
4659 (Base_Type (Entity (Result_Definition (Spec))), Loc));
4661 Body_Node :=
4662 Make_Subprogram_Body (Loc,
4663 Specification => Spec,
4664 Declarations => New_List,
4665 Handled_Statement_Sequence =>
4666 Make_Handled_Sequence_Of_Statements (Loc,
4667 Statements => New_List (
4668 Make_Simple_Return_Statement (Loc,
4669 Expression => Attr_Node))));
4671 -- Case of renaming a procedure
4673 else
4674 if not Is_Procedure_Attribute_Name (Aname) then
4675 Error_Msg_N ("attribute can only be renamed as function", Nam);
4676 return;
4677 end if;
4679 Body_Node :=
4680 Make_Subprogram_Body (Loc,
4681 Specification => Spec,
4682 Declarations => New_List,
4683 Handled_Statement_Sequence =>
4684 Make_Handled_Sequence_Of_Statements (Loc,
4685 Statements => New_List (Attr_Node)));
4686 end if;
4688 -- Signal the ABE mechanism that the generated subprogram body has not
4689 -- ABE ramifications.
4691 Set_Was_Attribute_Reference (Body_Node);
4693 -- In case of tagged types we add the body of the generated function to
4694 -- the freezing actions of the type (because in the general case such
4695 -- type is still not frozen). We exclude from this processing generic
4696 -- formal subprograms found in instantiations.
4698 -- We must exclude restricted run-time libraries because
4699 -- entity AST_Handler is defined in package System.Aux_Dec which is not
4700 -- available in those platforms. Note that we cannot use the function
4701 -- Restricted_Profile (instead of Configurable_Run_Time_Mode) because
4702 -- the ZFP run-time library is not defined as a profile, and we do not
4703 -- want to deal with AST_Handler in ZFP mode.
4705 if not Configurable_Run_Time_Mode
4706 and then No (Corresponding_Formal_Spec (N))
4707 and then not Is_RTE (Etype (Nam), RE_AST_Handler)
4708 then
4709 declare
4710 P : constant Node_Id := Prefix (Nam);
4712 begin
4713 -- The prefix of 'Img is an object that is evaluated for each call
4714 -- of the function that renames it.
4716 if Aname = Name_Img then
4717 Preanalyze_And_Resolve (P);
4719 -- For all other attribute renamings, the prefix is a subtype
4721 else
4722 Find_Type (P);
4723 end if;
4725 -- If the target type is not yet frozen, add the body to the
4726 -- actions to be elaborated at freeze time.
4728 if Is_Tagged_Type (Etype (P))
4729 and then In_Open_Scopes (Scope (Etype (P)))
4730 then
4731 Append_Freeze_Action (Etype (P), Body_Node);
4732 else
4733 Rewrite (N, Body_Node);
4734 Analyze (N);
4735 Set_Etype (New_S, Base_Type (Etype (New_S)));
4736 end if;
4737 end;
4739 -- Generic formal subprograms or AST_Handler renaming
4741 else
4742 Rewrite (N, Body_Node);
4743 Analyze (N);
4744 Set_Etype (New_S, Base_Type (Etype (New_S)));
4745 end if;
4747 if Is_Compilation_Unit (New_S) then
4748 Error_Msg_N
4749 ("a library unit can only rename another library unit", N);
4750 end if;
4752 -- We suppress elaboration warnings for the resulting entity, since
4753 -- clearly they are not needed, and more particularly, in the case
4754 -- of a generic formal subprogram, the resulting entity can appear
4755 -- after the instantiation itself, and thus look like a bogus case
4756 -- of access before elaboration.
4758 if Legacy_Elaboration_Checks then
4759 Set_Suppress_Elaboration_Warnings (New_S);
4760 end if;
4761 end Attribute_Renaming;
4763 ----------------------
4764 -- Chain_Use_Clause --
4765 ----------------------
4767 procedure Chain_Use_Clause (N : Node_Id) is
4768 Level : Int := Scope_Stack.Last;
4769 Pack : Entity_Id;
4771 begin
4772 -- Common case
4774 if not Is_Compilation_Unit (Current_Scope)
4775 or else not Is_Child_Unit (Current_Scope)
4776 then
4777 null;
4779 -- Common case for compilation unit
4781 elsif Defining_Entity (Parent (N)) = Current_Scope then
4782 null;
4784 else
4785 -- If declaration appears in some other scope, it must be in some
4786 -- parent unit when compiling a child.
4788 Pack := Defining_Entity (Parent (N));
4790 if not In_Open_Scopes (Pack) then
4791 null;
4793 -- If the use clause appears in an ancestor and we are in the
4794 -- private part of the immediate parent, the use clauses are
4795 -- already installed.
4797 elsif Pack /= Scope (Current_Scope)
4798 and then In_Private_Part (Scope (Current_Scope))
4799 then
4800 null;
4802 else
4803 -- Find entry for parent unit in scope stack
4805 while Scope_Stack.Table (Level).Entity /= Pack loop
4806 Level := Level - 1;
4807 end loop;
4808 end if;
4809 end if;
4811 Set_Next_Use_Clause (N,
4812 Scope_Stack.Table (Level).First_Use_Clause);
4813 Scope_Stack.Table (Level).First_Use_Clause := N;
4814 end Chain_Use_Clause;
4816 ---------------------------
4817 -- Check_Frozen_Renaming --
4818 ---------------------------
4820 procedure Check_Frozen_Renaming (N : Node_Id; Subp : Entity_Id) is
4821 B_Node : Node_Id;
4822 Old_S : Entity_Id;
4824 begin
4825 if Is_Frozen (Subp) and then not Has_Completion (Subp) then
4826 B_Node :=
4827 Build_Renamed_Body
4828 (Parent (Declaration_Node (Subp)), Defining_Entity (N));
4830 if Is_Entity_Name (Name (N)) then
4831 Old_S := Entity (Name (N));
4833 if not Is_Frozen (Old_S)
4834 and then Operating_Mode /= Check_Semantics
4835 then
4836 Append_Freeze_Action (Old_S, B_Node);
4837 else
4838 Insert_After (N, B_Node);
4839 Analyze (B_Node);
4840 end if;
4842 if Is_Intrinsic_Subprogram (Old_S)
4843 and then not In_Instance
4844 and then not Relaxed_RM_Semantics
4845 then
4846 Error_Msg_N
4847 ("subprogram used in renaming_as_body cannot be intrinsic",
4848 Name (N));
4849 end if;
4851 else
4852 Insert_After (N, B_Node);
4853 Analyze (B_Node);
4854 end if;
4855 end if;
4856 end Check_Frozen_Renaming;
4858 -------------------------------
4859 -- Set_Entity_Or_Discriminal --
4860 -------------------------------
4862 procedure Set_Entity_Or_Discriminal (N : Node_Id; E : Entity_Id) is
4863 P : Node_Id;
4865 begin
4866 -- If the entity is not a discriminant, or else expansion is disabled,
4867 -- simply set the entity.
4869 if not In_Spec_Expression
4870 or else Ekind (E) /= E_Discriminant
4871 or else Inside_A_Generic
4872 then
4873 Set_Entity_With_Checks (N, E);
4875 -- The replacement of a discriminant by the corresponding discriminal
4876 -- is not done for a task discriminant that appears in a default
4877 -- expression of an entry parameter. See Exp_Ch2.Expand_Discriminant
4878 -- for details on their handling.
4880 elsif Is_Concurrent_Type (Scope (E)) then
4881 P := Parent (N);
4882 while Present (P)
4883 and then Nkind (P) not in
4884 N_Parameter_Specification | N_Component_Declaration
4885 loop
4886 P := Parent (P);
4887 end loop;
4889 if Present (P)
4890 and then Nkind (P) = N_Parameter_Specification
4891 then
4892 null;
4894 -- Don't replace a non-qualified discriminant in strict preanalysis
4895 -- mode since it can lead to errors during full analysis when the
4896 -- discriminant gets referenced later.
4898 -- This can occur in situations where a protected type contains
4899 -- an expression function which references a non-prefixed
4900 -- discriminant.
4902 elsif No (P)
4903 and then Preanalysis_Active
4904 and then Inside_Preanalysis_Without_Freezing = 0
4905 then
4906 null;
4908 else
4909 Set_Entity (N, Discriminal (E));
4910 end if;
4912 -- Otherwise, this is a discriminant in a context in which
4913 -- it is a reference to the corresponding parameter of the
4914 -- init proc for the enclosing type.
4916 else
4917 Set_Entity (N, Discriminal (E));
4918 end if;
4919 end Set_Entity_Or_Discriminal;
4921 -----------------------------------
4922 -- Check_In_Previous_With_Clause --
4923 -----------------------------------
4925 procedure Check_In_Previous_With_Clause (N, Nam : Node_Id) is
4926 Pack : constant Entity_Id := Entity (Original_Node (Nam));
4927 Item : Node_Id;
4928 Par : Node_Id;
4930 begin
4931 Item := First (Context_Items (Parent (N)));
4932 while Present (Item) and then Item /= N loop
4933 if Nkind (Item) = N_With_Clause
4935 -- Protect the frontend against previous critical errors
4937 and then Nkind (Name (Item)) /= N_Selected_Component
4938 and then Entity (Name (Item)) = Pack
4939 then
4940 Par := Nam;
4942 -- Find root library unit in with_clause
4944 while Nkind (Par) = N_Expanded_Name loop
4945 Par := Prefix (Par);
4946 end loop;
4948 if Is_Child_Unit (Entity (Original_Node (Par))) then
4949 Error_Msg_NE ("& is not directly visible", Par, Entity (Par));
4950 else
4951 return;
4952 end if;
4953 end if;
4955 Next (Item);
4956 end loop;
4958 -- On exit, package is not mentioned in a previous with_clause.
4959 -- Check if its prefix is.
4961 if Nkind (Nam) = N_Expanded_Name then
4962 Check_In_Previous_With_Clause (N, Prefix (Nam));
4964 elsif Pack /= Any_Id then
4965 Error_Msg_NE ("& is not visible", Nam, Pack);
4966 end if;
4967 end Check_In_Previous_With_Clause;
4969 ---------------------------------
4970 -- Check_Library_Unit_Renaming --
4971 ---------------------------------
4973 procedure Check_Library_Unit_Renaming (N : Node_Id; Old_E : Entity_Id) is
4974 New_E : Entity_Id;
4976 begin
4977 if Nkind (Parent (N)) /= N_Compilation_Unit then
4978 return;
4980 -- Check for library unit. Note that we used to check for the scope
4981 -- being Standard here, but that was wrong for Standard itself.
4983 elsif not Is_Compilation_Unit (Old_E)
4984 and then not Is_Child_Unit (Old_E)
4985 then
4986 Error_Msg_N ("renamed unit must be a library unit", Name (N));
4988 -- Entities defined in Standard (operators and boolean literals) cannot
4989 -- be renamed as library units.
4991 elsif Scope (Old_E) = Standard_Standard
4992 and then Sloc (Old_E) = Standard_Location
4993 then
4994 Error_Msg_N ("renamed unit must be a library unit", Name (N));
4996 elsif Present (Parent_Spec (N))
4997 and then Nkind (Unit (Parent_Spec (N))) = N_Generic_Package_Declaration
4998 and then not Is_Child_Unit (Old_E)
4999 then
5000 Error_Msg_N
5001 ("renamed unit must be a child unit of generic parent", Name (N));
5003 elsif Nkind (N) in N_Generic_Renaming_Declaration
5004 and then Nkind (Name (N)) = N_Expanded_Name
5005 and then Is_Generic_Instance (Entity (Prefix (Name (N))))
5006 and then Is_Generic_Unit (Old_E)
5007 then
5008 Error_Msg_N
5009 ("renamed generic unit must be a library unit", Name (N));
5011 elsif Is_Package_Or_Generic_Package (Old_E) then
5013 -- Inherit categorization flags
5015 New_E := Defining_Entity (N);
5016 Set_Is_Pure (New_E, Is_Pure (Old_E));
5017 Set_Is_Preelaborated (New_E, Is_Preelaborated (Old_E));
5018 Set_Is_Remote_Call_Interface (New_E,
5019 Is_Remote_Call_Interface (Old_E));
5020 Set_Is_Remote_Types (New_E, Is_Remote_Types (Old_E));
5021 Set_Is_Shared_Passive (New_E, Is_Shared_Passive (Old_E));
5022 end if;
5023 end Check_Library_Unit_Renaming;
5025 ------------------------
5026 -- Enclosing_Instance --
5027 ------------------------
5029 function Enclosing_Instance return Entity_Id is
5030 S : Entity_Id;
5032 begin
5033 if not Is_Generic_Instance (Current_Scope) then
5034 return Empty;
5035 end if;
5037 S := Scope (Current_Scope);
5038 while S /= Standard_Standard loop
5039 if Is_Generic_Instance (S) then
5040 return S;
5041 end if;
5043 S := Scope (S);
5044 end loop;
5046 return Empty;
5047 end Enclosing_Instance;
5049 ---------------
5050 -- End_Scope --
5051 ---------------
5053 procedure End_Scope is
5054 Id : Entity_Id;
5055 Prev : Entity_Id;
5056 Outer : Entity_Id;
5058 begin
5059 Id := First_Entity (Current_Scope);
5060 while Present (Id) loop
5061 -- An entity in the current scope is not necessarily the first one
5062 -- on its homonym chain. Find its predecessor if any,
5063 -- If it is an internal entity, it will not be in the visibility
5064 -- chain altogether, and there is nothing to unchain.
5066 if Id /= Current_Entity (Id) then
5067 Prev := Current_Entity (Id);
5068 while Present (Prev)
5069 and then Present (Homonym (Prev))
5070 and then Homonym (Prev) /= Id
5071 loop
5072 Prev := Homonym (Prev);
5073 end loop;
5075 -- Skip to end of loop if Id is not in the visibility chain
5077 if No (Prev) or else Homonym (Prev) /= Id then
5078 goto Next_Ent;
5079 end if;
5081 else
5082 Prev := Empty;
5083 end if;
5085 Set_Is_Immediately_Visible (Id, False);
5087 Outer := Homonym (Id);
5088 while Present (Outer) and then Scope (Outer) = Current_Scope loop
5089 Outer := Homonym (Outer);
5090 end loop;
5092 -- Reset homonym link of other entities, but do not modify link
5093 -- between entities in current scope, so that the back-end can have
5094 -- a proper count of local overloadings.
5096 if No (Prev) then
5097 Set_Name_Entity_Id (Chars (Id), Outer);
5099 elsif Scope (Prev) /= Scope (Id) then
5100 Set_Homonym (Prev, Outer);
5101 end if;
5103 <<Next_Ent>>
5104 Next_Entity (Id);
5105 end loop;
5107 -- If the scope generated freeze actions, place them before the
5108 -- current declaration and analyze them. Type declarations and
5109 -- the bodies of initialization procedures can generate such nodes.
5110 -- We follow the parent chain until we reach a list node, which is
5111 -- the enclosing list of declarations. If the list appears within
5112 -- a protected definition, move freeze nodes outside the protected
5113 -- type altogether.
5115 if Present
5116 (Scope_Stack.Table (Scope_Stack.Last).Pending_Freeze_Actions)
5117 then
5118 declare
5119 Decl : Node_Id;
5120 L : constant List_Id := Scope_Stack.Table
5121 (Scope_Stack.Last).Pending_Freeze_Actions;
5123 begin
5124 if Is_Itype (Current_Scope) then
5125 Decl := Associated_Node_For_Itype (Current_Scope);
5126 else
5127 Decl := Parent (Current_Scope);
5128 end if;
5130 Pop_Scope;
5132 while not Is_List_Member (Decl)
5133 or else Nkind (Parent (Decl)) in N_Protected_Definition
5134 | N_Task_Definition
5135 loop
5136 Decl := Parent (Decl);
5137 end loop;
5139 Insert_List_Before_And_Analyze (Decl, L);
5140 end;
5142 else
5143 Pop_Scope;
5144 end if;
5145 end End_Scope;
5147 ---------------------
5148 -- End_Use_Clauses --
5149 ---------------------
5151 procedure End_Use_Clauses (Clause : Node_Id) is
5152 U : Node_Id;
5154 begin
5155 -- Remove use_type_clauses first, because they affect the visibility of
5156 -- operators in subsequent used packages.
5158 U := Clause;
5159 while Present (U) loop
5160 if Nkind (U) = N_Use_Type_Clause then
5161 End_Use_Type (U);
5162 end if;
5164 Next_Use_Clause (U);
5165 end loop;
5167 U := Clause;
5168 while Present (U) loop
5169 if Nkind (U) = N_Use_Package_Clause then
5170 End_Use_Package (U);
5171 end if;
5173 Next_Use_Clause (U);
5174 end loop;
5175 end End_Use_Clauses;
5177 ---------------------
5178 -- End_Use_Package --
5179 ---------------------
5181 procedure End_Use_Package (N : Node_Id) is
5182 Pack : Entity_Id;
5183 Pack_Name : Node_Id;
5184 Id : Entity_Id;
5185 Elmt : Elmt_Id;
5187 function Is_Primitive_Operator_In_Use
5188 (Op : Entity_Id;
5189 F : Entity_Id) return Boolean;
5190 -- Check whether Op is a primitive operator of a use-visible type
5192 ----------------------------------
5193 -- Is_Primitive_Operator_In_Use --
5194 ----------------------------------
5196 function Is_Primitive_Operator_In_Use
5197 (Op : Entity_Id;
5198 F : Entity_Id) return Boolean
5200 T : constant Entity_Id := Base_Type (Etype (F));
5201 begin
5202 return In_Use (T) and then Scope (T) = Scope (Op);
5203 end Is_Primitive_Operator_In_Use;
5205 -- Start of processing for End_Use_Package
5207 begin
5208 Pack_Name := Name (N);
5210 -- Test that Pack_Name actually denotes a package before processing
5212 if Is_Entity_Name (Pack_Name)
5213 and then Ekind (Entity (Pack_Name)) = E_Package
5214 then
5215 Pack := Entity (Pack_Name);
5217 if In_Open_Scopes (Pack) then
5218 null;
5220 elsif not Redundant_Use (Pack_Name) then
5221 Set_In_Use (Pack, False);
5222 Set_Current_Use_Clause (Pack, Empty);
5224 Id := First_Entity (Pack);
5225 while Present (Id) loop
5227 -- Preserve use-visibility of operators that are primitive
5228 -- operators of a type that is use-visible through an active
5229 -- use_type_clause.
5231 if Nkind (Id) = N_Defining_Operator_Symbol
5232 and then
5233 (Is_Primitive_Operator_In_Use (Id, First_Formal (Id))
5234 or else
5235 (Present (Next_Formal (First_Formal (Id)))
5236 and then
5237 Is_Primitive_Operator_In_Use
5238 (Id, Next_Formal (First_Formal (Id)))))
5239 then
5240 null;
5241 else
5242 Set_Is_Potentially_Use_Visible (Id, False);
5243 end if;
5245 if Is_Private_Type (Id)
5246 and then Present (Full_View (Id))
5247 then
5248 Set_Is_Potentially_Use_Visible (Full_View (Id), False);
5249 end if;
5251 Next_Entity (Id);
5252 end loop;
5254 if Present (Renamed_Entity (Pack)) then
5255 Set_In_Use (Renamed_Entity (Pack), False);
5256 Set_Current_Use_Clause (Renamed_Entity (Pack), Empty);
5257 end if;
5259 if Chars (Pack) = Name_System
5260 and then Scope (Pack) = Standard_Standard
5261 and then Present_System_Aux
5262 then
5263 Id := First_Entity (System_Aux_Id);
5264 while Present (Id) loop
5265 Set_Is_Potentially_Use_Visible (Id, False);
5267 if Is_Private_Type (Id)
5268 and then Present (Full_View (Id))
5269 then
5270 Set_Is_Potentially_Use_Visible (Full_View (Id), False);
5271 end if;
5273 Next_Entity (Id);
5274 end loop;
5276 Set_In_Use (System_Aux_Id, False);
5277 end if;
5278 else
5279 Set_Redundant_Use (Pack_Name, False);
5280 end if;
5281 end if;
5283 if Present (Hidden_By_Use_Clause (N)) then
5284 Elmt := First_Elmt (Hidden_By_Use_Clause (N));
5285 while Present (Elmt) loop
5286 declare
5287 E : constant Entity_Id := Node (Elmt);
5289 begin
5290 -- Reset either Use_Visibility or Direct_Visibility, depending
5291 -- on how the entity was hidden by the use clause.
5293 if In_Use (Scope (E))
5294 and then Used_As_Generic_Actual (Scope (E))
5295 then
5296 Set_Is_Potentially_Use_Visible (Node (Elmt));
5297 else
5298 Set_Is_Immediately_Visible (Node (Elmt));
5299 end if;
5301 Next_Elmt (Elmt);
5302 end;
5303 end loop;
5305 Set_Hidden_By_Use_Clause (N, No_Elist);
5306 end if;
5307 end End_Use_Package;
5309 ------------------
5310 -- End_Use_Type --
5311 ------------------
5313 procedure End_Use_Type (N : Node_Id) is
5314 Elmt : Elmt_Id;
5315 Id : Entity_Id;
5316 T : Entity_Id;
5318 -- Start of processing for End_Use_Type
5320 begin
5321 Id := Subtype_Mark (N);
5323 -- A call to Rtsfind may occur while analyzing a use_type_clause, in
5324 -- which case the type marks are not resolved yet, so guard against that
5325 -- here.
5327 if Is_Entity_Name (Id) and then Present (Entity (Id)) then
5328 T := Entity (Id);
5330 if T = Any_Type or else From_Limited_With (T) then
5331 null;
5333 -- Note that the use_type_clause may mention a subtype of the type
5334 -- whose primitive operations have been made visible. Here as
5335 -- elsewhere, it is the base type that matters for visibility.
5337 elsif In_Open_Scopes (Scope (Base_Type (T))) then
5338 null;
5340 elsif not Redundant_Use (Id) then
5341 Set_In_Use (T, False);
5342 Set_In_Use (Base_Type (T), False);
5343 Set_Current_Use_Clause (T, Empty);
5344 Set_Current_Use_Clause (Base_Type (T), Empty);
5346 -- See Use_One_Type for the rationale. This is a bit on the naive
5347 -- side, but should be good enough in practice.
5349 if Is_Tagged_Type (T) then
5350 Set_In_Use (Class_Wide_Type (T), False);
5351 end if;
5352 end if;
5353 end if;
5355 if Is_Empty_Elmt_List (Used_Operations (N)) then
5356 return;
5358 else
5359 Elmt := First_Elmt (Used_Operations (N));
5360 while Present (Elmt) loop
5361 Set_Is_Potentially_Use_Visible (Node (Elmt), False);
5362 Next_Elmt (Elmt);
5363 end loop;
5364 end if;
5365 end End_Use_Type;
5367 --------------------
5368 -- Entity_Of_Unit --
5369 --------------------
5371 function Entity_Of_Unit (U : Node_Id) return Entity_Id is
5372 begin
5373 if Nkind (U) = N_Package_Instantiation and then Analyzed (U) then
5374 return Defining_Entity (Instance_Spec (U));
5375 else
5376 return Defining_Entity (U);
5377 end if;
5378 end Entity_Of_Unit;
5380 --------------------------------------
5381 -- Error_Missing_With_Of_Known_Unit --
5382 --------------------------------------
5384 procedure Error_Missing_With_Of_Known_Unit (Pkg : Node_Id) is
5385 Selectors : array (1 .. 6) of Node_Id;
5386 -- Contains the chars of the full package name up to maximum number
5387 -- allowed as per Errout.Error_Msg_Name_# variables.
5389 Count : Integer := Selectors'First;
5390 -- Count of selector names forming the full package name
5392 Current_Pkg : Node_Id := Parent (Pkg);
5394 begin
5395 Selectors (Count) := Pkg;
5397 -- Gather all the selectors we can display
5399 while Nkind (Current_Pkg) = N_Selected_Component
5400 and then Is_Known_Unit (Current_Pkg)
5401 and then Count < Selectors'Length
5402 loop
5403 Count := Count + 1;
5404 Selectors (Count) := Selector_Name (Current_Pkg);
5405 Current_Pkg := Parent (Current_Pkg);
5406 end loop;
5408 -- Display the error message based on the number of selectors found
5410 case Count is
5411 when 1 =>
5412 Error_Msg_Node_1 := Selectors (1);
5413 Error_Msg_N -- CODEFIX
5414 ("\\missing `WITH &;`", Pkg);
5415 when 2 =>
5416 Error_Msg_Node_1 := Selectors (1);
5417 Error_Msg_Node_2 := Selectors (2);
5418 Error_Msg_N -- CODEFIX
5419 ("\\missing `WITH &.&;`", Pkg);
5420 when 3 =>
5421 Error_Msg_Node_1 := Selectors (1);
5422 Error_Msg_Node_2 := Selectors (2);
5423 Error_Msg_Node_3 := Selectors (3);
5424 Error_Msg_N -- CODEFIX
5425 ("\\missing `WITH &.&.&;`", Pkg);
5426 when 4 =>
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_3 := Selectors (4);
5431 Error_Msg_N -- CODEFIX
5432 ("\\missing `WITH &.&.&.&;`", Pkg);
5433 when 5 =>
5434 Error_Msg_Node_1 := Selectors (1);
5435 Error_Msg_Node_2 := Selectors (2);
5436 Error_Msg_Node_3 := Selectors (3);
5437 Error_Msg_Node_3 := Selectors (4);
5438 Error_Msg_Node_3 := Selectors (5);
5439 Error_Msg_N -- CODEFIX
5440 ("\\missing `WITH &.&.&.&.&;`", Pkg);
5441 when 6 =>
5442 Error_Msg_Node_1 := Selectors (1);
5443 Error_Msg_Node_2 := Selectors (2);
5444 Error_Msg_Node_3 := Selectors (3);
5445 Error_Msg_Node_4 := Selectors (4);
5446 Error_Msg_Node_5 := Selectors (5);
5447 Error_Msg_Node_6 := Selectors (6);
5448 Error_Msg_N -- CODEFIX
5449 ("\\missing `WITH &.&.&.&.&.&;`", Pkg);
5450 when others =>
5451 raise Program_Error;
5452 end case;
5453 end Error_Missing_With_Of_Known_Unit;
5455 ----------------------
5456 -- Find_Direct_Name --
5457 ----------------------
5459 procedure Find_Direct_Name (N : Node_Id) is
5460 E : Entity_Id;
5461 E2 : Entity_Id;
5462 Msg : Boolean;
5464 Homonyms : Entity_Id;
5465 -- Saves start of homonym chain
5467 Inst : Entity_Id := Empty;
5468 -- Enclosing instance, if any
5470 Nvis_Entity : Boolean;
5471 -- Set True to indicate that there is at least one entity on the homonym
5472 -- chain which, while not visible, is visible enough from the user point
5473 -- of view to warrant an error message of "not visible" rather than
5474 -- undefined.
5476 Nvis_Is_Private_Subprg : Boolean := False;
5477 -- Ada 2005 (AI-262): Set True to indicate that a form of Beaujolais
5478 -- effect concerning library subprograms has been detected. Used to
5479 -- generate the precise error message.
5481 function From_Actual_Package (E : Entity_Id) return Boolean;
5482 -- Returns true if the entity is an actual for a package that is itself
5483 -- an actual for a formal package of the current instance. Such an
5484 -- entity requires special handling because it may be use-visible but
5485 -- hides directly visible entities defined outside the instance, because
5486 -- the corresponding formal did so in the generic.
5488 function Is_Actual_Parameter return Boolean;
5489 -- This function checks if the node N is an identifier that is an actual
5490 -- parameter of a procedure call. If so it returns True, otherwise it
5491 -- return False. The reason for this check is that at this stage we do
5492 -- not know what procedure is being called if the procedure might be
5493 -- overloaded, so it is premature to go setting referenced flags or
5494 -- making calls to Generate_Reference. We will wait till Resolve_Actuals
5495 -- for that processing.
5496 -- Note: there is a similar routine Sem_Util.Is_Actual_Parameter, but
5497 -- it works for both function and procedure calls, while here we are
5498 -- only concerned with procedure calls (and with entry calls as well,
5499 -- but they are parsed as procedure calls and only later rewritten to
5500 -- entry calls).
5502 function Known_But_Invisible (E : Entity_Id) return Boolean;
5503 -- This function determines whether a reference to the entity E, which
5504 -- is not visible, can reasonably be considered to be known to the
5505 -- writer of the reference. This is a heuristic test, used only for
5506 -- the purposes of figuring out whether we prefer to complain that an
5507 -- entity is undefined or invisible (and identify the declaration of
5508 -- the invisible entity in the latter case). The point here is that we
5509 -- don't want to complain that something is invisible and then point to
5510 -- something entirely mysterious to the writer.
5512 procedure Nvis_Messages;
5513 -- Called if there are no visible entries for N, but there is at least
5514 -- one non-directly visible, or hidden declaration. This procedure
5515 -- outputs an appropriate set of error messages.
5517 procedure Undefined (Nvis : Boolean);
5518 -- This function is called if the current node has no corresponding
5519 -- visible entity or entities. The value set in Msg indicates whether
5520 -- an error message was generated (multiple error messages for the
5521 -- same variable are generally suppressed, see body for details).
5522 -- Msg is True if an error message was generated, False if not. This
5523 -- value is used by the caller to determine whether or not to output
5524 -- additional messages where appropriate. The parameter is set False
5525 -- to get the message "X is undefined", and True to get the message
5526 -- "X is not visible".
5528 -------------------------
5529 -- From_Actual_Package --
5530 -------------------------
5532 function From_Actual_Package (E : Entity_Id) return Boolean is
5533 Scop : constant Entity_Id := Scope (E);
5534 -- Declared scope of candidate entity
5536 function Declared_In_Actual (Pack : Entity_Id) return Boolean;
5537 -- Recursive function that does the work and examines actuals of
5538 -- actual packages of current instance.
5540 ------------------------
5541 -- Declared_In_Actual --
5542 ------------------------
5544 function Declared_In_Actual (Pack : Entity_Id) return Boolean is
5545 pragma Assert (Ekind (Pack) = E_Package);
5546 Act : Entity_Id;
5547 begin
5548 if No (Associated_Formal_Package (Pack)) then
5549 return False;
5551 else
5552 Act := First_Entity (Pack);
5553 while Present (Act) loop
5554 if Renamed_Entity (Pack) = Scop then
5555 return True;
5557 -- Check for end of list of actuals
5559 elsif Ekind (Act) = E_Package
5560 and then Renamed_Entity (Act) = Pack
5561 then
5562 return False;
5564 elsif Ekind (Act) = E_Package
5565 and then Declared_In_Actual (Act)
5566 then
5567 return True;
5568 end if;
5570 Next_Entity (Act);
5571 end loop;
5573 return False;
5574 end if;
5575 end Declared_In_Actual;
5577 -- Local variables
5579 Act : Entity_Id;
5581 -- Start of processing for From_Actual_Package
5583 begin
5584 if not In_Instance then
5585 return False;
5587 else
5588 Inst := Current_Scope;
5589 while Present (Inst)
5590 and then Ekind (Inst) /= E_Package
5591 and then not Is_Generic_Instance (Inst)
5592 loop
5593 Inst := Scope (Inst);
5594 end loop;
5596 if No (Inst) then
5597 return False;
5598 end if;
5600 Act := First_Entity (Inst);
5601 while Present (Act) loop
5602 if Ekind (Act) = E_Package
5603 and then Declared_In_Actual (Act)
5604 then
5605 return True;
5606 end if;
5608 Next_Entity (Act);
5609 end loop;
5611 return False;
5612 end if;
5613 end From_Actual_Package;
5615 -------------------------
5616 -- Is_Actual_Parameter --
5617 -------------------------
5619 function Is_Actual_Parameter return Boolean is
5620 begin
5621 if Nkind (N) = N_Identifier then
5622 case Nkind (Parent (N)) is
5623 when N_Procedure_Call_Statement =>
5624 return Is_List_Member (N)
5625 and then List_Containing (N) =
5626 Parameter_Associations (Parent (N));
5628 when N_Parameter_Association =>
5629 return N = Explicit_Actual_Parameter (Parent (N))
5630 and then Nkind (Parent (Parent (N))) =
5631 N_Procedure_Call_Statement;
5633 when others =>
5634 return False;
5635 end case;
5636 else
5637 return False;
5638 end if;
5639 end Is_Actual_Parameter;
5641 -------------------------
5642 -- Known_But_Invisible --
5643 -------------------------
5645 function Known_But_Invisible (E : Entity_Id) return Boolean is
5646 Fname : File_Name_Type;
5648 begin
5649 -- Entities in Standard are always considered to be known
5651 if Sloc (E) <= Standard_Location then
5652 return True;
5654 -- An entity that does not come from source is always considered
5655 -- to be unknown, since it is an artifact of code expansion.
5657 elsif not Comes_From_Source (E) then
5658 return False;
5659 end if;
5661 -- Here we have an entity that is not from package Standard, and
5662 -- which comes from Source. See if it comes from an internal file.
5664 Fname := Unit_File_Name (Get_Source_Unit (E));
5666 -- Case of from internal file
5668 if In_Internal_Unit (E) then
5670 -- Private part entities in internal files are never considered
5671 -- to be known to the writer of normal application code.
5673 if Is_Hidden (E) then
5674 return False;
5675 end if;
5677 -- Entities from System packages other than System and
5678 -- System.Storage_Elements are not considered to be known.
5679 -- System.Auxxxx files are also considered known to the user.
5681 -- Should refine this at some point to generally distinguish
5682 -- between known and unknown internal files ???
5684 Get_Name_String (Fname);
5686 return
5687 Name_Len < 2
5688 or else
5689 Name_Buffer (1 .. 2) /= "s-"
5690 or else
5691 Name_Buffer (3 .. 8) = "stoele"
5692 or else
5693 Name_Buffer (3 .. 5) = "aux";
5695 -- If not an internal file, then entity is definitely known, even if
5696 -- it is in a private part (the message generated will note that it
5697 -- is in a private part).
5699 else
5700 return True;
5701 end if;
5702 end Known_But_Invisible;
5704 -------------------
5705 -- Nvis_Messages --
5706 -------------------
5708 procedure Nvis_Messages is
5709 Comp_Unit : Node_Id;
5710 Ent : Entity_Id;
5711 Found : Boolean := False;
5712 Hidden : Boolean := False;
5713 Item : Node_Id;
5715 begin
5716 -- Ada 2005 (AI-262): Generate a precise error concerning the
5717 -- Beaujolais effect that was previously detected
5719 if Nvis_Is_Private_Subprg then
5721 pragma Assert (Nkind (E2) = N_Defining_Identifier
5722 and then Ekind (E2) = E_Function
5723 and then Scope (E2) = Standard_Standard
5724 and then Has_Private_With (E2));
5726 -- Find the sloc corresponding to the private with'ed unit
5728 Comp_Unit := Cunit (Current_Sem_Unit);
5729 Error_Msg_Sloc := No_Location;
5731 Item := First (Context_Items (Comp_Unit));
5732 while Present (Item) loop
5733 if Nkind (Item) = N_With_Clause
5734 and then Private_Present (Item)
5735 and then Entity (Name (Item)) = E2
5736 then
5737 Error_Msg_Sloc := Sloc (Item);
5738 exit;
5739 end if;
5741 Next (Item);
5742 end loop;
5744 pragma Assert (Error_Msg_Sloc /= No_Location);
5746 Error_Msg_N ("(Ada 2005): hidden by private with clause #", N);
5747 return;
5748 end if;
5750 Undefined (Nvis => True);
5752 if Msg then
5754 -- First loop does hidden declarations
5756 Ent := Homonyms;
5757 while Present (Ent) loop
5758 if Is_Potentially_Use_Visible (Ent) then
5759 if not Hidden then
5760 Error_Msg_N -- CODEFIX
5761 ("multiple use clauses cause hiding!", N);
5762 Hidden := True;
5763 end if;
5765 Error_Msg_Sloc := Sloc (Ent);
5766 Error_Msg_N -- CODEFIX
5767 ("hidden declaration#!", N);
5768 end if;
5770 Ent := Homonym (Ent);
5771 end loop;
5773 -- If we found hidden declarations, then that's enough, don't
5774 -- bother looking for non-visible declarations as well.
5776 if Hidden then
5777 return;
5778 end if;
5780 -- Second loop does non-directly visible declarations
5782 Ent := Homonyms;
5783 while Present (Ent) loop
5784 if not Is_Potentially_Use_Visible (Ent) then
5786 -- Do not bother the user with unknown entities
5788 if not Known_But_Invisible (Ent) then
5789 goto Continue;
5790 end if;
5792 Error_Msg_Sloc := Sloc (Ent);
5794 -- Output message noting that there is a non-visible
5795 -- declaration, distinguishing the private part case.
5797 if Is_Hidden (Ent) then
5798 Error_Msg_N ("non-visible (private) declaration#!", N);
5800 -- If the entity is declared in a generic package, it
5801 -- cannot be visible, so there is no point in adding it
5802 -- to the list of candidates if another homograph from a
5803 -- non-generic package has been seen.
5805 elsif Ekind (Scope (Ent)) = E_Generic_Package
5806 and then Found
5807 then
5808 null;
5810 else
5811 -- When the entity comes from a generic instance the
5812 -- normal error message machinery will give the line
5813 -- number of the generic package and the location of
5814 -- the generic instance, but not the name of the
5815 -- the instance.
5817 -- So, in order to give more descriptive error messages
5818 -- in this case, we include the name of the generic
5819 -- package.
5821 if Is_Generic_Instance (Scope (Ent)) then
5822 Error_Msg_Name_1 := Chars (Scope (Ent));
5823 Error_Msg_N -- CODEFIX
5824 ("non-visible declaration from %#!", N);
5826 -- Otherwise print the message normally
5828 else
5829 Error_Msg_N -- CODEFIX
5830 ("non-visible declaration#!", N);
5831 end if;
5833 if Ekind (Scope (Ent)) /= E_Generic_Package then
5834 Found := True;
5835 end if;
5837 if Is_Compilation_Unit (Ent)
5838 and then
5839 Nkind (Parent (Parent (N))) = N_Use_Package_Clause
5840 then
5841 Error_Msg_Qual_Level := 99;
5842 Error_Msg_NE -- CODEFIX
5843 ("\\missing `WITH &;`", N, Ent);
5844 Error_Msg_Qual_Level := 0;
5845 end if;
5847 if Ekind (Ent) = E_Discriminant
5848 and then Present (Corresponding_Discriminant (Ent))
5849 and then Scope (Corresponding_Discriminant (Ent)) =
5850 Etype (Scope (Ent))
5851 then
5852 Error_Msg_N
5853 ("inherited discriminant not allowed here" &
5854 " (RM 3.8 (12), 3.8.1 (6))!", N);
5855 end if;
5856 end if;
5858 -- Set entity and its containing package as referenced. We
5859 -- can't be sure of this, but this seems a better choice
5860 -- to avoid unused entity messages.
5862 if Comes_From_Source (Ent) then
5863 Set_Referenced (Ent);
5864 Set_Referenced (Cunit_Entity (Get_Source_Unit (Ent)));
5865 end if;
5866 end if;
5868 <<Continue>>
5869 Ent := Homonym (Ent);
5870 end loop;
5871 end if;
5872 end Nvis_Messages;
5874 ---------------
5875 -- Undefined --
5876 ---------------
5878 procedure Undefined (Nvis : Boolean) is
5879 Emsg : Error_Msg_Id;
5881 begin
5882 -- We should never find an undefined internal name. If we do, then
5883 -- see if we have previous errors. If so, ignore on the grounds that
5884 -- it is probably a cascaded message (e.g. a block label from a badly
5885 -- formed block). If no previous errors, then we have a real internal
5886 -- error of some kind so raise an exception.
5888 if Is_Internal_Name (Chars (N)) then
5889 if Total_Errors_Detected /= 0 then
5890 return;
5891 else
5892 raise Program_Error;
5893 end if;
5894 end if;
5896 -- A very specialized error check, if the undefined variable is
5897 -- a case tag, and the case type is an enumeration type, check
5898 -- for a possible misspelling, and if so, modify the identifier
5900 -- Named aggregate should also be handled similarly ???
5902 if Nkind (N) = N_Identifier
5903 and then Nkind (Parent (N)) = N_Case_Statement_Alternative
5904 then
5905 declare
5906 Case_Stm : constant Node_Id := Parent (Parent (N));
5907 Case_Typ : constant Entity_Id := Etype (Expression (Case_Stm));
5909 Lit : Node_Id;
5911 begin
5912 if Is_Enumeration_Type (Case_Typ)
5913 and then not Is_Standard_Character_Type (Case_Typ)
5914 then
5915 Lit := First_Literal (Case_Typ);
5916 Get_Name_String (Chars (Lit));
5918 if Chars (Lit) /= Chars (N)
5919 and then Is_Bad_Spelling_Of (Chars (N), Chars (Lit))
5920 then
5921 Error_Msg_Node_2 := Lit;
5922 Error_Msg_N -- CODEFIX
5923 ("& is undefined, assume misspelling of &", N);
5924 Rewrite (N, New_Occurrence_Of (Lit, Sloc (N)));
5925 return;
5926 end if;
5928 Next_Literal (Lit);
5929 end if;
5930 end;
5931 end if;
5933 -- Normal processing
5935 Set_Entity (N, Any_Id);
5936 Set_Etype (N, Any_Type);
5938 -- We use the table Urefs to keep track of entities for which we
5939 -- have issued errors for undefined references. Multiple errors
5940 -- for a single name are normally suppressed, however we modify
5941 -- the error message to alert the programmer to this effect.
5943 for J in Urefs.First .. Urefs.Last loop
5944 if Chars (N) = Chars (Urefs.Table (J).Node) then
5945 if Urefs.Table (J).Err /= No_Error_Msg
5946 and then Sloc (N) /= Urefs.Table (J).Loc
5947 then
5948 Error_Msg_Node_1 := Urefs.Table (J).Node;
5950 if Urefs.Table (J).Nvis then
5951 Change_Error_Text (Urefs.Table (J).Err,
5952 "& is not visible (more references follow)");
5953 else
5954 Change_Error_Text (Urefs.Table (J).Err,
5955 "& is undefined (more references follow)");
5956 end if;
5958 Urefs.Table (J).Err := No_Error_Msg;
5959 end if;
5961 -- Although we will set Msg False, and thus suppress the
5962 -- message, we also set Error_Posted True, to avoid any
5963 -- cascaded messages resulting from the undefined reference.
5965 Msg := False;
5966 Set_Error_Posted (N);
5967 return;
5968 end if;
5969 end loop;
5971 -- If entry not found, this is first undefined occurrence
5973 if Nvis then
5974 Error_Msg_N ("& is not visible!", N);
5975 Emsg := Get_Msg_Id;
5977 else
5978 Error_Msg_N ("& is undefined!", N);
5979 Emsg := Get_Msg_Id;
5981 -- A very bizarre special check, if the undefined identifier
5982 -- is Put or Put_Line, then add a special error message (since
5983 -- this is a very common error for beginners to make).
5985 if Chars (N) in Name_Put | Name_Put_Line then
5986 Error_Msg_N -- CODEFIX
5987 ("\\possible missing `WITH Ada.Text_'I'O; " &
5988 "USE Ada.Text_'I'O`!", N);
5990 -- Another special check if N is the prefix of a selected
5991 -- component which is a known unit: add message complaining
5992 -- about missing with for this unit.
5994 elsif Nkind (Parent (N)) = N_Selected_Component
5995 and then N = Prefix (Parent (N))
5996 and then Is_Known_Unit (Parent (N))
5997 then
5998 Error_Missing_With_Of_Known_Unit (N);
5999 end if;
6001 -- Now check for possible misspellings
6003 declare
6004 E : Entity_Id;
6005 Ematch : Entity_Id := Empty;
6006 begin
6007 for Nam in First_Name_Id .. Last_Name_Id loop
6008 E := Get_Name_Entity_Id (Nam);
6010 if Present (E)
6011 and then (Is_Immediately_Visible (E)
6012 or else
6013 Is_Potentially_Use_Visible (E))
6014 then
6015 if Is_Bad_Spelling_Of (Chars (N), Nam) then
6016 Ematch := E;
6017 exit;
6018 end if;
6019 end if;
6020 end loop;
6022 if Present (Ematch) then
6023 Error_Msg_NE -- CODEFIX
6024 ("\possible misspelling of&", N, Ematch);
6025 end if;
6026 end;
6027 end if;
6029 -- Make entry in undefined references table unless the full errors
6030 -- switch is set, in which case by refraining from generating the
6031 -- table entry we guarantee that we get an error message for every
6032 -- undefined reference. The entry is not added if we are ignoring
6033 -- errors.
6035 if not All_Errors_Mode
6036 and then Ignore_Errors_Enable = 0
6037 and then not Get_Ignore_Errors
6038 then
6039 Urefs.Append (
6040 (Node => N,
6041 Err => Emsg,
6042 Nvis => Nvis,
6043 Loc => Sloc (N)));
6044 end if;
6046 Msg := True;
6047 end Undefined;
6049 -- Local variables
6051 Nested_Inst : Entity_Id := Empty;
6052 -- The entity of a nested instance which appears within Inst (if any)
6054 -- Start of processing for Find_Direct_Name
6056 begin
6057 -- If the entity pointer is already set, this is an internal node, or
6058 -- a node that is analyzed more than once, after a tree modification.
6059 -- In such a case there is no resolution to perform, just set the type.
6061 if Present (Entity (N)) then
6062 if Is_Type (Entity (N)) then
6063 Set_Etype (N, Entity (N));
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 -- Preserve relevant elaboration-related attributes of the context which
6105 -- are no longer available or very expensive to recompute once analysis,
6106 -- resolution, and expansion are over.
6108 if Nkind (N) = N_Identifier then
6109 Mark_Elaboration_Attributes
6110 (N_Id => N,
6111 Checks => True,
6112 Modes => True,
6113 Warnings => True);
6114 end if;
6116 -- Here if Entity pointer was not set, we need full visibility analysis
6117 -- First we generate debugging output if the debug E flag is set.
6119 if Debug_Flag_E then
6120 Write_Str ("Looking for ");
6121 Write_Name (Chars (N));
6122 Write_Eol;
6123 end if;
6125 Homonyms := Current_Entity (N);
6126 Nvis_Entity := False;
6128 E := Homonyms;
6129 while Present (E) loop
6131 -- If entity is immediately visible or potentially use visible, then
6132 -- process the entity and we are done.
6134 if Is_Immediately_Visible (E) then
6135 goto Immediately_Visible_Entity;
6137 elsif Is_Potentially_Use_Visible (E) then
6138 goto Potentially_Use_Visible_Entity;
6140 -- Note if a known but invisible entity encountered
6142 elsif Known_But_Invisible (E) then
6143 Nvis_Entity := True;
6144 end if;
6146 -- Move to next entity in chain and continue search
6148 E := Homonym (E);
6149 end loop;
6151 -- If no entries on homonym chain that were potentially visible,
6152 -- and no entities reasonably considered as non-visible, then
6153 -- we have a plain undefined reference, with no additional
6154 -- explanation required.
6156 if not Nvis_Entity then
6157 Undefined (Nvis => False);
6159 -- Otherwise there is at least one entry on the homonym chain that
6160 -- is reasonably considered as being known and non-visible.
6162 else
6163 Nvis_Messages;
6164 end if;
6166 goto Done;
6168 -- Processing for a potentially use visible entry found. We must search
6169 -- the rest of the homonym chain for two reasons. First, if there is a
6170 -- directly visible entry, then none of the potentially use-visible
6171 -- entities are directly visible (RM 8.4(10)). Second, we need to check
6172 -- for the case of multiple potentially use-visible entries hiding one
6173 -- another and as a result being non-directly visible (RM 8.4(11)).
6175 <<Potentially_Use_Visible_Entity>> declare
6176 Only_One_Visible : Boolean := True;
6177 All_Overloadable : Boolean := Is_Overloadable (E);
6179 begin
6180 E2 := Homonym (E);
6181 while Present (E2) loop
6182 if Is_Immediately_Visible (E2) then
6184 -- If the use-visible entity comes from the actual for a
6185 -- formal package, it hides a directly visible entity from
6186 -- outside the instance.
6188 if From_Actual_Package (E)
6189 and then Scope_Depth (Scope (E2)) < Scope_Depth (Inst)
6190 then
6191 goto Found;
6192 else
6193 E := E2;
6194 goto Immediately_Visible_Entity;
6195 end if;
6197 elsif Is_Potentially_Use_Visible (E2) then
6198 Only_One_Visible := False;
6199 All_Overloadable := All_Overloadable and Is_Overloadable (E2);
6201 -- Ada 2005 (AI-262): Protect against a form of Beaujolais effect
6202 -- that can occur in private_with clauses. Example:
6204 -- with A;
6205 -- private with B; package A is
6206 -- package C is function B return Integer;
6207 -- use A; end A;
6208 -- V1 : Integer := B;
6209 -- private function B return Integer;
6210 -- V2 : Integer := B;
6211 -- end C;
6213 -- V1 resolves to A.B, but V2 resolves to library unit B
6215 elsif Ekind (E2) = E_Function
6216 and then Scope (E2) = Standard_Standard
6217 and then Has_Private_With (E2)
6218 then
6219 Only_One_Visible := False;
6220 All_Overloadable := False;
6221 Nvis_Is_Private_Subprg := True;
6222 exit;
6223 end if;
6225 E2 := Homonym (E2);
6226 end loop;
6228 -- On falling through this loop, we have checked that there are no
6229 -- immediately visible entities. Only_One_Visible is set if exactly
6230 -- one potentially use visible entity exists. All_Overloadable is
6231 -- set if all the potentially use visible entities are overloadable.
6232 -- The condition for legality is that either there is one potentially
6233 -- use visible entity, or if there is more than one, then all of them
6234 -- are overloadable.
6236 if Only_One_Visible or All_Overloadable then
6237 goto Found;
6239 -- If there is more than one potentially use-visible entity and at
6240 -- least one of them non-overloadable, we have an error (RM 8.4(11)).
6241 -- Note that E points to the first such entity on the homonym list.
6243 else
6244 -- If one of the entities is declared in an actual package, it
6245 -- was visible in the generic, and takes precedence over other
6246 -- entities that are potentially use-visible. The same applies
6247 -- if the entity is declared in a local instantiation of the
6248 -- current instance.
6250 if In_Instance then
6252 -- Find the current instance
6254 Inst := Current_Scope;
6255 while Present (Inst) and then Inst /= Standard_Standard loop
6256 if Is_Generic_Instance (Inst) then
6257 exit;
6258 end if;
6260 Inst := Scope (Inst);
6261 end loop;
6263 -- Reexamine the candidate entities, giving priority to those
6264 -- that were visible within the generic.
6266 E2 := E;
6267 while Present (E2) loop
6268 Nested_Inst := Nearest_Enclosing_Instance (E2);
6270 -- The entity is declared within an actual package, or in a
6271 -- nested instance. The ">=" accounts for the case where the
6272 -- current instance and the nested instance are the same.
6274 if From_Actual_Package (E2)
6275 or else (Present (Nested_Inst)
6276 and then Scope_Depth (Nested_Inst) >=
6277 Scope_Depth (Inst))
6278 then
6279 E := E2;
6280 goto Found;
6281 end if;
6283 E2 := Homonym (E2);
6284 end loop;
6286 Nvis_Messages;
6287 goto Done;
6289 elsif Is_Predefined_Unit (Current_Sem_Unit) then
6290 -- A use clause in the body of a system file creates conflict
6291 -- with some entity in a user scope, while rtsfind is active.
6292 -- Keep only the entity coming from another predefined unit.
6294 E2 := E;
6295 while Present (E2) loop
6296 if In_Predefined_Unit (E2) then
6297 E := E2;
6298 goto Found;
6299 end if;
6301 E2 := Homonym (E2);
6302 end loop;
6304 -- Entity must exist because predefined unit is correct
6306 raise Program_Error;
6308 else
6309 Nvis_Messages;
6310 goto Done;
6311 end if;
6312 end if;
6313 end;
6315 -- Come here with E set to the first immediately visible entity on
6316 -- the homonym chain. This is the one we want unless there is another
6317 -- immediately visible entity further on in the chain for an inner
6318 -- scope (RM 8.3(8)).
6320 <<Immediately_Visible_Entity>> declare
6321 Level : Int;
6322 Scop : Entity_Id;
6324 begin
6325 -- Find scope level of initial entity. When compiling through
6326 -- Rtsfind, the previous context is not completely invisible, and
6327 -- an outer entity may appear on the chain, whose scope is below
6328 -- the entry for Standard that delimits the current scope stack.
6329 -- Indicate that the level for this spurious entry is outside of
6330 -- the current scope stack.
6332 Level := Scope_Stack.Last;
6333 loop
6334 Scop := Scope_Stack.Table (Level).Entity;
6335 exit when Scop = Scope (E);
6336 Level := Level - 1;
6337 exit when Scop = Standard_Standard;
6338 end loop;
6340 -- Now search remainder of homonym chain for more inner entry
6341 -- If the entity is Standard itself, it has no scope, and we
6342 -- compare it with the stack entry directly.
6344 E2 := Homonym (E);
6345 while Present (E2) loop
6346 if Is_Immediately_Visible (E2) then
6348 -- If a generic package contains a local declaration that
6349 -- has the same name as the generic, there may be a visibility
6350 -- conflict in an instance, where the local declaration must
6351 -- also hide the name of the corresponding package renaming.
6352 -- We check explicitly for a package declared by a renaming,
6353 -- whose renamed entity is an instance that is on the scope
6354 -- stack, and that contains a homonym in the same scope. Once
6355 -- we have found it, we know that the package renaming is not
6356 -- immediately visible, and that the identifier denotes the
6357 -- other entity (and its homonyms if overloaded).
6359 if Scope (E) = Scope (E2)
6360 and then Ekind (E) = E_Package
6361 and then Present (Renamed_Entity (E))
6362 and then Is_Generic_Instance (Renamed_Entity (E))
6363 and then In_Open_Scopes (Renamed_Entity (E))
6364 and then Comes_From_Source (N)
6365 then
6366 Set_Is_Immediately_Visible (E, False);
6367 E := E2;
6369 else
6370 for J in Level + 1 .. Scope_Stack.Last loop
6371 if Scope_Stack.Table (J).Entity = Scope (E2)
6372 or else Scope_Stack.Table (J).Entity = E2
6373 then
6374 Level := J;
6375 E := E2;
6376 exit;
6377 end if;
6378 end loop;
6379 end if;
6380 end if;
6382 E2 := Homonym (E2);
6383 end loop;
6385 -- At the end of that loop, E is the innermost immediately
6386 -- visible entity, so we are all set.
6387 end;
6389 -- Come here with entity found, and stored in E
6391 <<Found>> begin
6393 -- Check violation of No_Wide_Characters restriction
6395 Check_Wide_Character_Restriction (E, N);
6397 -- When distribution features are available (Get_PCS_Name /=
6398 -- Name_No_DSA), a remote access-to-subprogram type is converted
6399 -- into a record type holding whatever information is needed to
6400 -- perform a remote call on an RCI subprogram. In that case we
6401 -- rewrite any occurrence of the RAS type into the equivalent record
6402 -- type here. 'Access attribute references and RAS dereferences are
6403 -- then implemented using specific TSSs. However when distribution is
6404 -- not available (case of Get_PCS_Name = Name_No_DSA), we bypass the
6405 -- generation of these TSSs, and we must keep the RAS type in its
6406 -- original access-to-subprogram form (since all calls through a
6407 -- value of such type will be local anyway in the absence of a PCS).
6409 if Comes_From_Source (N)
6410 and then Is_Remote_Access_To_Subprogram_Type (E)
6411 and then Ekind (E) = E_Access_Subprogram_Type
6412 and then Expander_Active
6413 and then Get_PCS_Name /= Name_No_DSA
6414 then
6415 Rewrite (N, New_Occurrence_Of (Equivalent_Type (E), Sloc (N)));
6416 goto Done;
6417 end if;
6419 -- Set the entity. Note that the reason we call Set_Entity for the
6420 -- overloadable case, as opposed to Set_Entity_With_Checks is
6421 -- that in the overloaded case, the initial call can set the wrong
6422 -- homonym. The call that sets the right homonym is in Sem_Res and
6423 -- that call does use Set_Entity_With_Checks, so we don't miss
6424 -- a style check.
6426 if Is_Overloadable (E) then
6427 Set_Entity (N, E);
6428 else
6429 Set_Entity_With_Checks (N, E);
6430 end if;
6432 if Is_Type (E) then
6433 Set_Etype (N, E);
6434 else
6435 Set_Etype (N, Get_Full_View (Etype (E)));
6436 end if;
6438 if Debug_Flag_E then
6439 Write_Str (" found ");
6440 Write_Entity_Info (E, " ");
6441 end if;
6443 -- If the Ekind of the entity is Void, it means that all homonyms
6444 -- are hidden from all visibility (RM 8.3(5,14-20)). However, this
6445 -- test is skipped if the current scope is a record and the name is
6446 -- a pragma argument expression (case of Atomic and Volatile pragmas
6447 -- and possibly other similar pragmas added later, which are allowed
6448 -- to reference components in the current record).
6450 if Ekind (E) = E_Void
6451 and then
6452 (not Is_Record_Type (Current_Scope)
6453 or else Nkind (Parent (N)) /= N_Pragma_Argument_Association)
6454 then
6455 Premature_Usage (N);
6457 -- If the entity is overloadable, collect all interpretations of the
6458 -- name for subsequent overload resolution. We optimize a bit here to
6459 -- do this only if we have an overloadable entity that is not on its
6460 -- own on the homonym chain.
6462 elsif Is_Overloadable (E)
6463 and then (Present (Homonym (E)) or else Current_Entity (N) /= E)
6464 then
6465 Collect_Interps (N);
6467 -- If no homonyms were visible, the entity is unambiguous
6469 if not Is_Overloaded (N) then
6470 if not Is_Actual_Parameter then
6471 Generate_Reference (E, N);
6472 end if;
6473 end if;
6475 -- Case of non-overloadable entity, set the entity providing that
6476 -- we do not have the case of a discriminant reference within a
6477 -- default expression. Such references are replaced with the
6478 -- corresponding discriminal, which is the formal corresponding to
6479 -- to the discriminant in the initialization procedure.
6481 else
6482 -- Entity is unambiguous, indicate that it is referenced here
6484 -- For a renaming of an object, always generate simple reference,
6485 -- we don't try to keep track of assignments in this case, except
6486 -- in SPARK mode where renamings are traversed for generating
6487 -- local effects of subprograms.
6489 if Is_Object (E)
6490 and then Present (Renamed_Object (E))
6491 and then not GNATprove_Mode
6492 then
6493 Generate_Reference (E, N);
6495 -- If the renamed entity is a private protected component,
6496 -- reference the original component as well. This needs to be
6497 -- done because the private renamings are installed before any
6498 -- analysis has occurred. Reference to a private component will
6499 -- resolve to the renaming and the original component will be
6500 -- left unreferenced, hence the following.
6502 if Is_Prival (E) then
6503 Generate_Reference (Prival_Link (E), N);
6504 end if;
6506 -- One odd case is that we do not want to set the Referenced flag
6507 -- if the entity is a label, and the identifier is the label in
6508 -- the source, since this is not a reference from the point of
6509 -- view of the user.
6511 elsif Nkind (Parent (N)) = N_Label then
6512 declare
6513 R : constant Boolean := Referenced (E);
6515 begin
6516 -- Generate reference unless this is an actual parameter
6517 -- (see comment below).
6519 if not Is_Actual_Parameter then
6520 Generate_Reference (E, N);
6521 Set_Referenced (E, R);
6522 end if;
6523 end;
6525 -- Normal case, not a label: generate reference
6527 else
6528 if not Is_Actual_Parameter then
6530 -- Package or generic package is always a simple reference
6532 if Is_Package_Or_Generic_Package (E) then
6533 Generate_Reference (E, N, 'r');
6535 -- Else see if we have a left hand side
6537 else
6538 case Known_To_Be_Assigned (N, Only_LHS => True) is
6539 when True =>
6540 Generate_Reference (E, N, 'm');
6542 when False =>
6543 Generate_Reference (E, N, 'r');
6545 end case;
6546 end if;
6547 end if;
6548 end if;
6550 Set_Entity_Or_Discriminal (N, E);
6552 -- The name may designate a generalized reference, in which case
6553 -- the dereference interpretation will be included. Context is
6554 -- one in which a name is legal.
6556 if Ada_Version >= Ada_2012
6557 and then
6558 (Nkind (Parent (N)) in N_Subexpr
6559 or else Nkind (Parent (N)) in N_Assignment_Statement
6560 | N_Object_Declaration
6561 | N_Parameter_Association)
6562 then
6563 Check_Implicit_Dereference (N, Etype (E));
6564 end if;
6565 end if;
6566 end;
6568 -- Mark relevant use-type and use-package clauses as effective if the
6569 -- node in question is not overloaded and therefore does not require
6570 -- resolution.
6572 -- Note: Generic actual subprograms do not follow the normal resolution
6573 -- path, so ignore the fact that they are overloaded and mark them
6574 -- anyway.
6576 if Nkind (N) not in N_Subexpr or else not Is_Overloaded (N) then
6577 Mark_Use_Clauses (N);
6578 end if;
6580 -- Come here with entity set
6582 <<Done>>
6583 Check_Restriction_No_Use_Of_Entity (N);
6585 -- Annotate the tree by creating a variable reference marker in case the
6586 -- original variable reference is folded or optimized away. The variable
6587 -- reference marker is automatically saved for later examination by the
6588 -- ABE Processing phase. Variable references which act as actuals in a
6589 -- call require special processing and are left to Resolve_Actuals. The
6590 -- reference is a write when it appears on the left hand side of an
6591 -- assignment.
6593 if Needs_Variable_Reference_Marker (N => N, Calls_OK => False) then
6594 declare
6595 Is_Assignment_LHS : constant Boolean := Known_To_Be_Assigned (N);
6597 begin
6598 Build_Variable_Reference_Marker
6599 (N => N,
6600 Read => not Is_Assignment_LHS,
6601 Write => Is_Assignment_LHS);
6602 end;
6603 end if;
6604 end Find_Direct_Name;
6606 ------------------------
6607 -- Find_Expanded_Name --
6608 ------------------------
6610 -- This routine searches the homonym chain of the entity until it finds
6611 -- an entity declared in the scope denoted by the prefix. If the entity
6612 -- is private, it may nevertheless be immediately visible, if we are in
6613 -- the scope of its declaration.
6615 procedure Find_Expanded_Name (N : Node_Id) is
6616 function In_Abstract_View_Pragma (Nod : Node_Id) return Boolean;
6617 -- Determine whether expanded name Nod appears within a pragma which is
6618 -- a suitable context for an abstract view of a state or variable. The
6619 -- following pragmas fall in this category:
6620 -- Depends
6621 -- Global
6622 -- Initializes
6623 -- Refined_Depends
6624 -- Refined_Global
6626 -- In addition, pragma Abstract_State is also considered suitable even
6627 -- though it is an illegal context for an abstract view as this allows
6628 -- for proper resolution of abstract views of variables. This illegal
6629 -- context is later flagged in the analysis of indicator Part_Of.
6631 -----------------------------
6632 -- In_Abstract_View_Pragma --
6633 -----------------------------
6635 function In_Abstract_View_Pragma (Nod : Node_Id) return Boolean is
6636 Par : Node_Id;
6638 begin
6639 -- Climb the parent chain looking for a pragma
6641 Par := Nod;
6642 while Present (Par) loop
6643 if Nkind (Par) = N_Pragma then
6644 if Pragma_Name_Unmapped (Par)
6645 in Name_Abstract_State
6646 | Name_Depends
6647 | Name_Global
6648 | Name_Initializes
6649 | Name_Refined_Depends
6650 | Name_Refined_Global
6651 then
6652 return True;
6654 -- Otherwise the pragma is not a legal context for an abstract
6655 -- view.
6657 else
6658 exit;
6659 end if;
6661 -- Prevent the search from going too far
6663 elsif Is_Body_Or_Package_Declaration (Par) then
6664 exit;
6665 end if;
6667 Par := Parent (Par);
6668 end loop;
6670 return False;
6671 end In_Abstract_View_Pragma;
6673 -- Local variables
6675 Selector : constant Node_Id := Selector_Name (N);
6677 Candidate : Entity_Id := Empty;
6678 P_Name : Entity_Id;
6679 Id : Entity_Id;
6681 -- Start of processing for Find_Expanded_Name
6683 begin
6684 P_Name := Entity (Prefix (N));
6686 -- If the prefix is a renamed package, look for the entity in the
6687 -- original package.
6689 if Ekind (P_Name) = E_Package
6690 and then Present (Renamed_Entity (P_Name))
6691 then
6692 P_Name := Renamed_Entity (P_Name);
6694 if From_Limited_With (P_Name)
6695 and then not Unit_Is_Visible (Cunit (Get_Source_Unit (P_Name)))
6696 then
6697 Error_Msg_NE
6698 ("renaming of limited view of package & not usable in this"
6699 & " context (RM 8.5.3(3.1/2))", Prefix (N), P_Name);
6701 elsif Has_Limited_View (P_Name)
6702 and then not Unit_Is_Visible (Cunit (Get_Source_Unit (P_Name)))
6703 and then not Is_Visible_Through_Renamings (P_Name)
6704 then
6705 Error_Msg_NE
6706 ("renaming of limited view of package & not usable in this"
6707 & " context (RM 8.5.3(3.1/2))", Prefix (N), P_Name);
6708 end if;
6710 -- Rewrite node with entity field pointing to renamed object
6712 Rewrite (Prefix (N), New_Copy (Prefix (N)));
6713 Set_Entity (Prefix (N), P_Name);
6715 -- If the prefix is an object of a concurrent type, look for
6716 -- the entity in the associated task or protected type.
6718 elsif Is_Concurrent_Type (Etype (P_Name)) then
6719 P_Name := Etype (P_Name);
6720 end if;
6722 Id := Current_Entity (Selector);
6724 declare
6725 Is_New_Candidate : Boolean;
6727 begin
6728 while Present (Id) loop
6729 if Scope (Id) = P_Name then
6730 Candidate := Id;
6731 Is_New_Candidate := True;
6733 -- Handle abstract views of states and variables. These are
6734 -- acceptable candidates only when the reference to the view
6735 -- appears in certain pragmas.
6737 if Ekind (Id) = E_Abstract_State
6738 and then From_Limited_With (Id)
6739 and then Present (Non_Limited_View (Id))
6740 then
6741 if In_Abstract_View_Pragma (N) then
6742 Candidate := Non_Limited_View (Id);
6743 Is_New_Candidate := True;
6745 -- Hide the candidate because it is not used in a proper
6746 -- context.
6748 else
6749 Candidate := Empty;
6750 Is_New_Candidate := False;
6751 end if;
6752 end if;
6754 -- Ada 2005 (AI-217): Handle shadow entities associated with
6755 -- types declared in limited-withed nested packages. We don't need
6756 -- to handle E_Incomplete_Subtype entities because the entities
6757 -- in the limited view are always E_Incomplete_Type and
6758 -- E_Class_Wide_Type entities (see Build_Limited_Views).
6760 -- Regarding the expression used to evaluate the scope, it
6761 -- is important to note that the limited view also has shadow
6762 -- entities associated nested packages. For this reason the
6763 -- correct scope of the entity is the scope of the real entity.
6764 -- The non-limited view may itself be incomplete, in which case
6765 -- get the full view if available.
6767 elsif Ekind (Id) in E_Incomplete_Type | E_Class_Wide_Type
6768 and then From_Limited_With (Id)
6769 and then Present (Non_Limited_View (Id))
6770 and then Scope (Non_Limited_View (Id)) = P_Name
6771 then
6772 Candidate := Get_Full_View (Non_Limited_View (Id));
6773 Is_New_Candidate := True;
6775 -- Handle special case where the prefix is a renaming of a shadow
6776 -- package which is visible. Required to avoid reporting spurious
6777 -- errors.
6779 elsif Ekind (P_Name) = E_Package
6780 and then From_Limited_With (P_Name)
6781 and then not From_Limited_With (Id)
6782 and then Sloc (Scope (Id)) = Sloc (P_Name)
6783 and then Unit_Is_Visible (Cunit (Get_Source_Unit (P_Name)))
6784 then
6785 Candidate := Get_Full_View (Id);
6786 Is_New_Candidate := True;
6788 -- An unusual case arises with a fully qualified name for an
6789 -- entity local to a generic child unit package, within an
6790 -- instantiation of that package. The name of the unit now
6791 -- denotes the renaming created within the instance. This is
6792 -- only relevant in an instance body, see below.
6794 elsif Is_Generic_Instance (Scope (Id))
6795 and then In_Open_Scopes (Scope (Id))
6796 and then In_Instance_Body
6797 and then Ekind (Scope (Id)) = E_Package
6798 and then Ekind (Id) = E_Package
6799 and then Renamed_Entity (Id) = Scope (Id)
6800 and then Is_Immediately_Visible (P_Name)
6801 then
6802 Is_New_Candidate := True;
6804 else
6805 Is_New_Candidate := False;
6806 end if;
6808 if Is_New_Candidate then
6810 -- If entity is a child unit, either it is a visible child of
6811 -- the prefix, or we are in the body of a generic prefix, as
6812 -- will happen when a child unit is instantiated in the body
6813 -- of a generic parent. This is because the instance body does
6814 -- not restore the full compilation context, given that all
6815 -- non-local references have been captured.
6817 if Is_Child_Unit (Id) or else P_Name = Standard_Standard then
6818 exit when Is_Visible_Lib_Unit (Id)
6819 or else (Is_Child_Unit (Id)
6820 and then In_Open_Scopes (Scope (Id))
6821 and then In_Instance_Body);
6822 else
6823 exit when not Is_Hidden (Id);
6824 end if;
6826 exit when Is_Immediately_Visible (Id);
6827 end if;
6829 Id := Homonym (Id);
6830 end loop;
6831 end;
6833 if No (Id)
6834 and then Ekind (P_Name) in E_Procedure | E_Function
6835 and then Is_Generic_Instance (P_Name)
6836 then
6837 -- Expanded name denotes entity in (instance of) generic subprogram.
6838 -- The entity may be in the subprogram instance, or may denote one of
6839 -- the formals, which is declared in the enclosing wrapper package.
6841 P_Name := Scope (P_Name);
6843 Id := Current_Entity (Selector);
6844 while Present (Id) loop
6845 exit when Scope (Id) = P_Name;
6846 Id := Homonym (Id);
6847 end loop;
6848 end if;
6850 if No (Id) or else Chars (Id) /= Chars (Selector) then
6851 Set_Etype (N, Any_Type);
6853 -- If we are looking for an entity defined in System, try to find it
6854 -- in the child package that may have been provided as an extension
6855 -- to System. The Extend_System pragma will have supplied the name of
6856 -- the extension, which may have to be loaded.
6858 if Chars (P_Name) = Name_System
6859 and then Scope (P_Name) = Standard_Standard
6860 and then Present (System_Extend_Unit)
6861 and then Present_System_Aux (N)
6862 then
6863 Set_Entity (Prefix (N), System_Aux_Id);
6864 Find_Expanded_Name (N);
6865 return;
6867 -- There is an implicit instance of the predefined operator in
6868 -- the given scope. The operator entity is defined in Standard.
6869 -- Has_Implicit_Operator makes the node into an Expanded_Name.
6871 elsif Nkind (Selector) = N_Operator_Symbol
6872 and then Has_Implicit_Operator (N)
6873 then
6874 return;
6876 -- If there is no literal defined in the scope denoted by the
6877 -- prefix, the literal may belong to (a type derived from)
6878 -- Standard_Character, for which we have no explicit literals.
6880 elsif Nkind (Selector) = N_Character_Literal
6881 and then Has_Implicit_Character_Literal (N)
6882 then
6883 return;
6885 else
6886 -- If the prefix is a single concurrent object, use its name in
6887 -- the error message, rather than that of the anonymous type.
6889 if Is_Concurrent_Type (P_Name)
6890 and then Is_Internal_Name (Chars (P_Name))
6891 then
6892 Error_Msg_Node_2 := Entity (Prefix (N));
6893 else
6894 Error_Msg_Node_2 := P_Name;
6895 end if;
6897 if P_Name = System_Aux_Id then
6898 P_Name := Scope (P_Name);
6899 Set_Entity (Prefix (N), P_Name);
6900 end if;
6902 if Present (Candidate) then
6904 -- If we know that the unit is a child unit we can give a more
6905 -- accurate error message.
6907 if Is_Child_Unit (Candidate) then
6909 -- If the candidate is a private child unit and we are in
6910 -- the visible part of a public unit, specialize the error
6911 -- message. There might be a private with_clause for it,
6912 -- but it is not currently active.
6914 if Is_Private_Descendant (Candidate)
6915 and then Ekind (Current_Scope) = E_Package
6916 and then not In_Private_Part (Current_Scope)
6917 and then not Is_Private_Descendant (Current_Scope)
6918 then
6919 Error_Msg_N
6920 ("private child unit& is not visible here", Selector);
6922 -- Normal case where we have a missing with for a child unit
6924 else
6925 Error_Msg_Qual_Level := 99;
6926 Error_Msg_NE -- CODEFIX
6927 ("missing `WITH &;`", Selector, Candidate);
6928 Error_Msg_Qual_Level := 0;
6929 end if;
6931 -- Here we don't know that this is a child unit
6933 else
6934 Error_Msg_NE ("& is not a visible entity of&", N, Selector);
6935 end if;
6937 else
6938 -- Within the instantiation of a child unit, the prefix may
6939 -- denote the parent instance, but the selector has the name
6940 -- of the original child. That is to say, when A.B appears
6941 -- within an instantiation of generic child unit B, the scope
6942 -- stack includes an instance of A (P_Name) and an instance
6943 -- of B under some other name. We scan the scope to find this
6944 -- child instance, which is the desired entity.
6945 -- Note that the parent may itself be a child instance, if
6946 -- the reference is of the form A.B.C, in which case A.B has
6947 -- already been rewritten with the proper entity.
6949 if In_Open_Scopes (P_Name)
6950 and then Is_Generic_Instance (P_Name)
6951 then
6952 declare
6953 Gen_Par : constant Entity_Id :=
6954 Generic_Parent (Specification
6955 (Unit_Declaration_Node (P_Name)));
6956 S : Entity_Id := Current_Scope;
6957 P : Entity_Id;
6959 begin
6960 for J in reverse 0 .. Scope_Stack.Last loop
6961 S := Scope_Stack.Table (J).Entity;
6963 exit when S = Standard_Standard;
6965 if Ekind (S) in E_Function | E_Package | E_Procedure
6966 then
6967 P :=
6968 Generic_Parent (Specification
6969 (Unit_Declaration_Node (S)));
6971 -- Check that P is a generic child of the generic
6972 -- parent of the prefix.
6974 if Present (P)
6975 and then Chars (P) = Chars (Selector)
6976 and then Scope (P) = Gen_Par
6977 then
6978 Id := S;
6979 goto Found;
6980 end if;
6981 end if;
6983 end loop;
6984 end;
6985 end if;
6987 -- If this is a selection from Ada, System or Interfaces, then
6988 -- we assume a missing with for the corresponding package.
6990 if Is_Known_Unit (N)
6991 and then not (Present (Entity (Prefix (N)))
6992 and then Scope (Entity (Prefix (N))) /=
6993 Standard_Standard)
6994 then
6995 if not Error_Posted (N) then
6996 Error_Msg_NE
6997 ("& is not a visible entity of&", Prefix (N), Selector);
6998 Error_Missing_With_Of_Known_Unit (Prefix (N));
6999 end if;
7001 -- If this is a selection from a dummy package, then suppress
7002 -- the error message, of course the entity is missing if the
7003 -- package is missing.
7005 elsif Sloc (Error_Msg_Node_2) = No_Location then
7006 null;
7008 -- Here we have the case of an undefined component
7010 else
7011 -- The prefix may hide a homonym in the context that
7012 -- declares the desired entity. This error can use a
7013 -- specialized message.
7015 if In_Open_Scopes (P_Name) then
7016 declare
7017 H : constant Entity_Id := Homonym (P_Name);
7019 begin
7020 if Present (H)
7021 and then Is_Compilation_Unit (H)
7022 and then
7023 (Is_Immediately_Visible (H)
7024 or else Is_Visible_Lib_Unit (H))
7025 then
7026 Id := First_Entity (H);
7027 while Present (Id) loop
7028 if Chars (Id) = Chars (Selector) then
7029 Error_Msg_Qual_Level := 99;
7030 Error_Msg_Name_1 := Chars (Selector);
7031 Error_Msg_NE
7032 ("% not declared in&", N, P_Name);
7033 Error_Msg_NE
7034 ("\use fully qualified name starting with "
7035 & "Standard to make& visible", N, H);
7036 Error_Msg_Qual_Level := 0;
7037 goto Done;
7038 end if;
7040 Next_Entity (Id);
7041 end loop;
7042 end if;
7044 -- If not found, standard error message
7046 Error_Msg_NE ("& not declared in&", N, Selector);
7048 <<Done>> null;
7049 end;
7051 else
7052 -- Might be worth specializing the case when the prefix
7053 -- is a limited view.
7054 -- ... not declared in limited view of...
7056 Error_Msg_NE ("& not declared in&", N, Selector);
7057 end if;
7059 -- Check for misspelling of some entity in prefix
7061 Id := First_Entity (P_Name);
7062 while Present (Id) loop
7063 if Is_Bad_Spelling_Of (Chars (Id), Chars (Selector))
7064 and then not Is_Internal_Name (Chars (Id))
7065 then
7066 Error_Msg_NE -- CODEFIX
7067 ("possible misspelling of&", Selector, Id);
7068 exit;
7069 end if;
7071 Next_Entity (Id);
7072 end loop;
7074 -- Specialize the message if this may be an instantiation
7075 -- of a child unit that was not mentioned in the context.
7077 if Nkind (Parent (N)) = N_Package_Instantiation
7078 and then Is_Generic_Instance (Entity (Prefix (N)))
7079 and then Is_Compilation_Unit
7080 (Generic_Parent (Parent (Entity (Prefix (N)))))
7081 then
7082 Error_Msg_Node_2 := Selector;
7083 Error_Msg_N -- CODEFIX
7084 ("\missing `WITH &.&;`", Prefix (N));
7085 end if;
7086 end if;
7087 end if;
7089 Id := Any_Id;
7090 end if;
7091 end if;
7093 <<Found>>
7094 if Comes_From_Source (N)
7095 and then Is_Remote_Access_To_Subprogram_Type (Id)
7096 and then Ekind (Id) = E_Access_Subprogram_Type
7097 and then Present (Equivalent_Type (Id))
7098 then
7099 -- If we are not actually generating distribution code (i.e. the
7100 -- current PCS is the dummy non-distributed version), then the
7101 -- Equivalent_Type will be missing, and Id should be treated as
7102 -- a regular access-to-subprogram type.
7104 Id := Equivalent_Type (Id);
7105 Set_Chars (Selector, Chars (Id));
7106 end if;
7108 -- Ada 2005 (AI-50217): Check usage of entities in limited withed units
7110 if Ekind (P_Name) = E_Package and then From_Limited_With (P_Name) then
7111 if From_Limited_With (Id)
7112 or else Is_Type (Id)
7113 or else Ekind (Id) = E_Package
7114 then
7115 null;
7116 else
7117 Error_Msg_N
7118 ("limited withed package can only be used to access incomplete "
7119 & "types", N);
7120 end if;
7121 end if;
7123 if Is_Task_Type (P_Name)
7124 and then ((Ekind (Id) = E_Entry
7125 and then Nkind (Parent (N)) /= N_Attribute_Reference)
7126 or else
7127 (Ekind (Id) = E_Entry_Family
7128 and then
7129 Nkind (Parent (Parent (N))) /= N_Attribute_Reference))
7130 then
7131 -- If both the task type and the entry are in scope, this may still
7132 -- be the expanded name of an entry formal.
7134 if In_Open_Scopes (Id)
7135 and then Nkind (Parent (N)) = N_Selected_Component
7136 then
7137 null;
7139 else
7140 -- It is an entry call after all, either to the current task
7141 -- (which will deadlock) or to an enclosing task.
7143 Analyze_Selected_Component (N);
7144 return;
7145 end if;
7146 end if;
7148 case Nkind (N) is
7149 when N_Selected_Component =>
7150 Reinit_Field_To_Zero (N, F_Is_Prefixed_Call);
7151 Change_Selected_Component_To_Expanded_Name (N);
7153 when N_Expanded_Name =>
7154 null;
7156 when others =>
7157 pragma Assert (False);
7158 end case;
7160 -- Preserve relevant elaboration-related attributes of the context which
7161 -- are no longer available or very expensive to recompute once analysis,
7162 -- resolution, and expansion are over.
7164 Mark_Elaboration_Attributes
7165 (N_Id => N,
7166 Checks => True,
7167 Modes => True,
7168 Warnings => True);
7170 -- Set appropriate type
7172 if Is_Type (Id) then
7173 Set_Etype (N, Id);
7174 else
7175 Set_Etype (N, Get_Full_View (Etype (Id)));
7176 end if;
7178 -- Do style check and generate reference, but skip both steps if this
7179 -- entity has homonyms, since we may not have the right homonym set yet.
7180 -- The proper homonym will be set during the resolve phase.
7182 if Has_Homonym (Id) then
7183 Set_Entity (N, Id);
7185 else
7186 Set_Entity_Or_Discriminal (N, Id);
7188 case Known_To_Be_Assigned (N, Only_LHS => True) is
7189 when True =>
7190 Generate_Reference (Id, N, 'm');
7192 when False =>
7193 Generate_Reference (Id, N, 'r');
7195 end case;
7196 end if;
7198 -- Check for violation of No_Wide_Characters
7200 Check_Wide_Character_Restriction (Id, N);
7202 -- If the Ekind of the entity is Void, it means that all homonyms are
7203 -- hidden from all visibility (RM 8.3(5,14-20)).
7205 if Ekind (Id) = E_Void then
7206 Premature_Usage (N);
7208 elsif Is_Overloadable (Id) and then Present (Homonym (Id)) then
7209 declare
7210 H : Entity_Id := Homonym (Id);
7212 begin
7213 while Present (H) loop
7214 if Scope (H) = Scope (Id)
7215 and then (not Is_Hidden (H)
7216 or else Is_Immediately_Visible (H))
7217 then
7218 Collect_Interps (N);
7219 exit;
7220 end if;
7222 H := Homonym (H);
7223 end loop;
7225 -- If an extension of System is present, collect possible explicit
7226 -- overloadings declared in the extension.
7228 if Chars (P_Name) = Name_System
7229 and then Scope (P_Name) = Standard_Standard
7230 and then Present (System_Extend_Unit)
7231 and then Present_System_Aux (N)
7232 then
7233 H := Current_Entity (Id);
7235 while Present (H) loop
7236 if Scope (H) = System_Aux_Id then
7237 Add_One_Interp (N, H, Etype (H));
7238 end if;
7240 H := Homonym (H);
7241 end loop;
7242 end if;
7243 end;
7244 end if;
7246 if Nkind (Selector_Name (N)) = N_Operator_Symbol
7247 and then Scope (Id) /= Standard_Standard
7248 then
7249 -- In addition to user-defined operators in the given scope, there
7250 -- may be an implicit instance of the predefined operator. The
7251 -- operator (defined in Standard) is found in Has_Implicit_Operator,
7252 -- and added to the interpretations. Procedure Add_One_Interp will
7253 -- determine which hides which.
7255 if Has_Implicit_Operator (N) then
7256 null;
7257 end if;
7258 end if;
7260 -- If there is a single interpretation for N we can generate a
7261 -- reference to the unique entity found.
7263 if Is_Overloadable (Id) and then not Is_Overloaded (N) then
7264 Generate_Reference (Id, N);
7265 end if;
7267 -- Mark relevant use-type and use-package clauses as effective if the
7268 -- node in question is not overloaded and therefore does not require
7269 -- resolution.
7271 if Nkind (N) not in N_Subexpr or else not Is_Overloaded (N) then
7272 Mark_Use_Clauses (N);
7273 end if;
7275 Check_Restriction_No_Use_Of_Entity (N);
7277 -- Annotate the tree by creating a variable reference marker in case the
7278 -- original variable reference is folded or optimized away. The variable
7279 -- reference marker is automatically saved for later examination by the
7280 -- ABE Processing phase. Variable references which act as actuals in a
7281 -- call require special processing and are left to Resolve_Actuals. The
7282 -- reference is a write when it appears on the left hand side of an
7283 -- assignment.
7285 if Needs_Variable_Reference_Marker
7286 (N => N,
7287 Calls_OK => False)
7288 then
7289 declare
7290 Is_Assignment_LHS : constant Boolean := Known_To_Be_Assigned (N);
7292 begin
7293 Build_Variable_Reference_Marker
7294 (N => N,
7295 Read => not Is_Assignment_LHS,
7296 Write => Is_Assignment_LHS);
7297 end;
7298 end if;
7299 end Find_Expanded_Name;
7301 --------------------
7302 -- Find_First_Use --
7303 --------------------
7305 function Find_First_Use (Use_Clause : Node_Id) return Node_Id is
7306 Curr : Node_Id;
7308 begin
7309 -- Loop through the Prev_Use_Clause chain
7311 Curr := Use_Clause;
7312 while Present (Prev_Use_Clause (Curr)) loop
7313 Curr := Prev_Use_Clause (Curr);
7314 end loop;
7316 return Curr;
7317 end Find_First_Use;
7319 -------------------------
7320 -- Find_Renamed_Entity --
7321 -------------------------
7323 function Find_Renamed_Entity
7324 (N : Node_Id;
7325 Nam : Node_Id;
7326 New_S : Entity_Id;
7327 Is_Actual : Boolean := False) return Entity_Id
7329 Ind : Interp_Index;
7330 I1 : Interp_Index := 0; -- Suppress junk warnings
7331 It : Interp;
7332 It1 : Interp;
7333 Old_S : Entity_Id;
7334 Inst : Entity_Id;
7336 function Find_Nearer_Entity
7337 (New_S : Entity_Id;
7338 Old1_S : Entity_Id;
7339 Old2_S : Entity_Id) return Entity_Id;
7340 -- Determine whether one of Old_S1 and Old_S2 is nearer to New_S than
7341 -- the other, and return it if so. Return Empty otherwise. We use this
7342 -- in conjunction with Inherit_Renamed_Profile to simplify later type
7343 -- disambiguation for actual subprograms in instances.
7345 function Is_Visible_Operation (Op : Entity_Id) return Boolean;
7346 -- If the renamed entity is an implicit operator, check whether it is
7347 -- visible because its operand type is properly visible. This check
7348 -- applies to explicit renamed entities that appear in the source in a
7349 -- renaming declaration or a formal subprogram instance, but not to
7350 -- default generic actuals with a name.
7352 function Report_Overload return Entity_Id;
7353 -- List possible interpretations, and specialize message in the
7354 -- case of a generic actual.
7356 function Within (Inner, Outer : Entity_Id) return Boolean;
7357 -- Determine whether a candidate subprogram is defined within the
7358 -- enclosing instance. If yes, it has precedence over outer candidates.
7360 --------------------------
7361 -- Find_Nearer_Entity --
7362 --------------------------
7364 function Find_Nearer_Entity
7365 (New_S : Entity_Id;
7366 Old1_S : Entity_Id;
7367 Old2_S : Entity_Id) return Entity_Id
7369 New_F : Entity_Id;
7370 Old1_F : Entity_Id;
7371 Old2_F : Entity_Id;
7372 Anc_T : Entity_Id;
7374 begin
7375 New_F := First_Formal (New_S);
7376 Old1_F := First_Formal (Old1_S);
7377 Old2_F := First_Formal (Old2_S);
7379 -- The criterion is whether the type of the formals of one of Old1_S
7380 -- and Old2_S is an ancestor subtype of the type of the corresponding
7381 -- formals of New_S while the other is not (we already know that they
7382 -- are all subtypes of the same base type).
7384 -- This makes it possible to find the more correct renamed entity in
7385 -- the case of a generic instantiation nested in an enclosing one for
7386 -- which different formal types get the same actual type, which will
7387 -- in turn make it possible for Inherit_Renamed_Profile to preserve
7388 -- types on formal parameters and ultimately simplify disambiguation.
7390 -- Consider the follow package G:
7392 -- generic
7393 -- type Item_T is private;
7394 -- with function Compare (L, R: Item_T) return Boolean is <>;
7396 -- type Bound_T is private;
7397 -- with function Compare (L, R : Bound_T) return Boolean is <>;
7398 -- package G is
7399 -- ...
7400 -- end G;
7402 -- package body G is
7403 -- package My_Inner is Inner_G (Bound_T);
7404 -- ...
7405 -- end G;
7407 -- with the following package Inner_G:
7409 -- generic
7410 -- type T is private;
7411 -- with function Compare (L, R: T) return Boolean is <>;
7412 -- package Inner_G is
7413 -- function "<" (L, R: T) return Boolean is (Compare (L, R));
7414 -- end Inner_G;
7416 -- If G is instantiated on the same actual type with a single Compare
7417 -- function:
7419 -- type T is ...
7420 -- function Compare (L, R : T) return Boolean;
7421 -- package My_G is new (T, T);
7423 -- then the renaming generated for Compare in the inner instantiation
7424 -- is ambiguous: it can rename either of the renamings generated for
7425 -- the outer instantiation. Now if the first one is picked up, then
7426 -- the subtypes of the formal parameters of the renaming will not be
7427 -- preserved in Inherit_Renamed_Profile because they are subtypes of
7428 -- the Bound_T formal type and not of the Item_T formal type, so we
7429 -- need to arrange for the second one to be picked up instead.
7431 while Present (New_F) loop
7432 if Etype (Old1_F) /= Etype (Old2_F) then
7433 Anc_T := Ancestor_Subtype (Etype (New_F));
7435 if Etype (Old1_F) = Anc_T then
7436 return Old1_S;
7437 elsif Etype (Old2_F) = Anc_T then
7438 return Old2_S;
7439 end if;
7440 end if;
7442 Next_Formal (New_F);
7443 Next_Formal (Old1_F);
7444 Next_Formal (Old2_F);
7445 end loop;
7447 pragma Assert (No (Old1_F));
7448 pragma Assert (No (Old2_F));
7450 return Empty;
7451 end Find_Nearer_Entity;
7453 --------------------------
7454 -- Is_Visible_Operation --
7455 --------------------------
7457 function Is_Visible_Operation (Op : Entity_Id) return Boolean is
7458 Scop : Entity_Id;
7459 Typ : Entity_Id;
7460 Btyp : Entity_Id;
7462 begin
7463 if Ekind (Op) /= E_Operator
7464 or else Scope (Op) /= Standard_Standard
7465 or else (In_Instance
7466 and then (not Is_Actual
7467 or else Present (Enclosing_Instance)))
7468 then
7469 return True;
7471 else
7472 -- For a fixed point type operator, check the resulting type,
7473 -- because it may be a mixed mode integer * fixed operation.
7475 if Present (Next_Formal (First_Formal (New_S)))
7476 and then Is_Fixed_Point_Type (Etype (New_S))
7477 then
7478 Typ := Etype (New_S);
7479 else
7480 Typ := Etype (First_Formal (New_S));
7481 end if;
7483 Btyp := Base_Type (Typ);
7485 if Nkind (Nam) /= N_Expanded_Name then
7486 return (In_Open_Scopes (Scope (Btyp))
7487 or else Is_Potentially_Use_Visible (Btyp)
7488 or else In_Use (Btyp)
7489 or else In_Use (Scope (Btyp)));
7491 else
7492 Scop := Entity (Prefix (Nam));
7494 if Ekind (Scop) = E_Package
7495 and then Present (Renamed_Entity (Scop))
7496 then
7497 Scop := Renamed_Entity (Scop);
7498 end if;
7500 -- Operator is visible if prefix of expanded name denotes
7501 -- scope of type, or else type is defined in System_Aux
7502 -- and the prefix denotes System.
7504 return Scope (Btyp) = Scop
7505 or else (Scope (Btyp) = System_Aux_Id
7506 and then Scope (Scope (Btyp)) = Scop);
7507 end if;
7508 end if;
7509 end Is_Visible_Operation;
7511 ------------
7512 -- Within --
7513 ------------
7515 function Within (Inner, Outer : Entity_Id) return Boolean is
7516 Sc : Entity_Id;
7518 begin
7519 Sc := Scope (Inner);
7520 while Sc /= Standard_Standard loop
7521 if Sc = Outer then
7522 return True;
7523 else
7524 Sc := Scope (Sc);
7525 end if;
7526 end loop;
7528 return False;
7529 end Within;
7531 ---------------------
7532 -- Report_Overload --
7533 ---------------------
7535 function Report_Overload return Entity_Id is
7536 begin
7537 if Is_Actual then
7538 Error_Msg_NE -- CODEFIX
7539 ("ambiguous actual subprogram&, " &
7540 "possible interpretations:", N, Nam);
7541 else
7542 Error_Msg_N -- CODEFIX
7543 ("ambiguous subprogram, " &
7544 "possible interpretations:", N);
7545 end if;
7547 List_Interps (Nam, N);
7548 return Old_S;
7549 end Report_Overload;
7551 -- Start of processing for Find_Renamed_Entity
7553 begin
7554 Old_S := Any_Id;
7555 Candidate_Renaming := Empty;
7557 if Is_Overloaded (Nam) then
7558 Get_First_Interp (Nam, Ind, It);
7559 while Present (It.Nam) loop
7560 if Entity_Matches_Spec (It.Nam, New_S)
7561 and then Is_Visible_Operation (It.Nam)
7562 then
7563 if Old_S /= Any_Id then
7565 -- Note: The call to Disambiguate only happens if a
7566 -- previous interpretation was found, in which case I1
7567 -- has received a value.
7569 It1 := Disambiguate (Nam, I1, Ind, Etype (Old_S));
7571 if It1 = No_Interp then
7572 Inst := Enclosing_Instance;
7574 if Present (Inst) then
7575 if Within (It.Nam, Inst) then
7576 if Within (Old_S, Inst) then
7577 declare
7578 It_D : constant Uint :=
7579 Scope_Depth_Default_0 (It.Nam);
7580 Old_D : constant Uint :=
7581 Scope_Depth_Default_0 (Old_S);
7582 N_Ent : Entity_Id;
7583 begin
7584 -- Choose the innermost subprogram, which
7585 -- would hide the outer one in the generic.
7587 if Old_D > It_D then
7588 return Old_S;
7589 elsif It_D > Old_D then
7590 return It.Nam;
7591 end if;
7593 -- Otherwise, if we can determine that one
7594 -- of the entities is nearer to the renaming
7595 -- than the other, choose it. If not, then
7596 -- return the newer one as done historically.
7598 N_Ent :=
7599 Find_Nearer_Entity (New_S, Old_S, It.Nam);
7600 if Present (N_Ent) then
7601 return N_Ent;
7602 else
7603 return It.Nam;
7604 end if;
7605 end;
7606 end if;
7608 elsif Within (Old_S, Inst) then
7609 return Old_S;
7611 else
7612 return Report_Overload;
7613 end if;
7615 -- If not within an instance, ambiguity is real
7617 else
7618 return Report_Overload;
7619 end if;
7621 else
7622 Old_S := It1.Nam;
7623 exit;
7624 end if;
7626 else
7627 I1 := Ind;
7628 Old_S := It.Nam;
7629 end if;
7631 elsif
7632 Present (First_Formal (It.Nam))
7633 and then Present (First_Formal (New_S))
7634 and then (Base_Type (Etype (First_Formal (It.Nam))) =
7635 Base_Type (Etype (First_Formal (New_S))))
7636 then
7637 Candidate_Renaming := It.Nam;
7638 end if;
7640 Get_Next_Interp (Ind, It);
7641 end loop;
7643 Set_Entity (Nam, Old_S);
7645 if Old_S /= Any_Id then
7646 Set_Is_Overloaded (Nam, False);
7647 end if;
7649 -- Non-overloaded case
7651 else
7652 if Is_Actual
7653 and then Present (Enclosing_Instance)
7654 and then Entity_Matches_Spec (Entity (Nam), New_S)
7655 then
7656 Old_S := Entity (Nam);
7658 elsif Entity_Matches_Spec (Entity (Nam), New_S) then
7659 Candidate_Renaming := New_S;
7661 if Is_Visible_Operation (Entity (Nam)) then
7662 Old_S := Entity (Nam);
7663 end if;
7665 elsif Present (First_Formal (Entity (Nam)))
7666 and then Present (First_Formal (New_S))
7667 and then (Base_Type (Etype (First_Formal (Entity (Nam)))) =
7668 Base_Type (Etype (First_Formal (New_S))))
7669 then
7670 Candidate_Renaming := Entity (Nam);
7671 end if;
7672 end if;
7674 return Old_S;
7675 end Find_Renamed_Entity;
7677 -----------------------------
7678 -- Find_Selected_Component --
7679 -----------------------------
7681 procedure Find_Selected_Component (N : Node_Id) is
7682 P : constant Node_Id := Prefix (N);
7684 P_Name : Entity_Id;
7685 -- Entity denoted by prefix
7687 P_Type : Entity_Id;
7688 -- and its type
7690 Nam : Node_Id;
7692 function Available_Subtype return Boolean;
7693 -- A small optimization: if the prefix is constrained and the component
7694 -- is an array type we may already have a usable subtype for it, so we
7695 -- can use it rather than generating a new one, because the bounds
7696 -- will be the values of the discriminants and not discriminant refs.
7697 -- This simplifies value tracing in GNATprove. For consistency, both
7698 -- the entity name and the subtype come from the constrained component.
7700 -- This is only used in GNATprove mode: when generating code it may be
7701 -- necessary to create an itype in the scope of use of the selected
7702 -- component, e.g. in the context of a expanded record equality.
7704 function Is_Reference_In_Subunit return Boolean;
7705 -- In a subunit, the scope depth is not a proper measure of hiding,
7706 -- because the context of the proper body may itself hide entities in
7707 -- parent units. This rare case requires inspecting the tree directly
7708 -- because the proper body is inserted in the main unit and its context
7709 -- is simply added to that of the parent.
7711 -----------------------
7712 -- Available_Subtype --
7713 -----------------------
7715 function Available_Subtype return Boolean is
7716 Comp : Entity_Id;
7718 begin
7719 if GNATprove_Mode then
7720 Comp := First_Entity (Etype (P));
7721 while Present (Comp) loop
7722 if Chars (Comp) = Chars (Selector_Name (N)) then
7723 Set_Etype (N, Etype (Comp));
7724 Set_Entity (Selector_Name (N), Comp);
7725 Set_Etype (Selector_Name (N), Etype (Comp));
7726 return True;
7727 end if;
7729 Next_Component (Comp);
7730 end loop;
7731 end if;
7733 return False;
7734 end Available_Subtype;
7736 -----------------------------
7737 -- Is_Reference_In_Subunit --
7738 -----------------------------
7740 function Is_Reference_In_Subunit return Boolean is
7741 Clause : Node_Id;
7742 Comp_Unit : Node_Id;
7744 begin
7745 Comp_Unit := N;
7746 while Present (Comp_Unit)
7747 and then Nkind (Comp_Unit) /= N_Compilation_Unit
7748 loop
7749 Comp_Unit := Parent (Comp_Unit);
7750 end loop;
7752 if No (Comp_Unit) or else Nkind (Unit (Comp_Unit)) /= N_Subunit then
7753 return False;
7754 end if;
7756 -- Now check whether the package is in the context of the subunit
7758 Clause := First (Context_Items (Comp_Unit));
7759 while Present (Clause) loop
7760 if Nkind (Clause) = N_With_Clause
7761 and then Entity (Name (Clause)) = P_Name
7762 then
7763 return True;
7764 end if;
7766 Next (Clause);
7767 end loop;
7769 return False;
7770 end Is_Reference_In_Subunit;
7772 -- Start of processing for Find_Selected_Component
7774 begin
7775 Analyze (P);
7777 if Nkind (P) = N_Error then
7778 return;
7779 end if;
7781 -- If the selector already has an entity, the node has been constructed
7782 -- in the course of expansion, and is known to be valid. Do not verify
7783 -- that it is defined for the type (it may be a private component used
7784 -- in the expansion of record equality).
7786 if Present (Entity (Selector_Name (N))) then
7787 if No (Etype (N)) or else Etype (N) = Any_Type then
7788 declare
7789 Sel_Name : constant Node_Id := Selector_Name (N);
7790 Selector : constant Entity_Id := Entity (Sel_Name);
7791 C_Etype : Node_Id;
7793 begin
7794 Set_Etype (Sel_Name, Etype (Selector));
7796 if not Is_Entity_Name (P) then
7797 Resolve (P);
7798 end if;
7800 -- Build an actual subtype except for the first parameter
7801 -- of an init proc, where this actual subtype is by
7802 -- definition incorrect, since the object is uninitialized
7803 -- (and does not even have defined discriminants etc.)
7805 if Is_Entity_Name (P)
7806 and then Ekind (Entity (P)) = E_Function
7807 then
7808 Nam := New_Copy (P);
7810 if Is_Overloaded (P) then
7811 Save_Interps (P, Nam);
7812 end if;
7814 Rewrite (P, Make_Function_Call (Sloc (P), Name => Nam));
7815 Analyze_Call (P);
7816 Analyze_Selected_Component (N);
7817 return;
7819 elsif Ekind (Selector) = E_Component
7820 and then (not Is_Entity_Name (P)
7821 or else Chars (Entity (P)) /= Name_uInit)
7822 then
7823 -- Check if we already have an available subtype we can use
7825 if Ekind (Etype (P)) = E_Record_Subtype
7826 and then Nkind (Parent (Etype (P))) = N_Subtype_Declaration
7827 and then Is_Array_Type (Etype (Selector))
7828 and then not Is_Packed (Etype (Selector))
7829 and then Available_Subtype
7830 then
7831 return;
7833 -- Do not build the subtype when referencing components of
7834 -- dispatch table wrappers. Required to avoid generating
7835 -- elaboration code with HI runtimes.
7837 elsif Is_RTE (Scope (Selector), RE_Dispatch_Table_Wrapper)
7838 or else
7839 Is_RTE (Scope (Selector), RE_No_Dispatch_Table_Wrapper)
7840 then
7841 C_Etype := Empty;
7842 else
7843 C_Etype :=
7844 Build_Actual_Subtype_Of_Component
7845 (Etype (Selector), N);
7846 end if;
7848 else
7849 C_Etype := Empty;
7850 end if;
7852 if No (C_Etype) then
7853 C_Etype := Etype (Selector);
7854 else
7855 Insert_Action (N, C_Etype);
7856 C_Etype := Defining_Identifier (C_Etype);
7857 end if;
7859 Set_Etype (N, C_Etype);
7860 end;
7862 -- If the selected component appears within a default expression
7863 -- and it has an actual subtype, the preanalysis has not yet
7864 -- completed its analysis, because Insert_Actions is disabled in
7865 -- that context. Within the init proc of the enclosing type we
7866 -- must complete this analysis, if an actual subtype was created.
7868 elsif Inside_Init_Proc then
7869 declare
7870 Typ : constant Entity_Id := Etype (N);
7871 Decl : constant Node_Id := Declaration_Node (Typ);
7872 begin
7873 if Nkind (Decl) = N_Subtype_Declaration
7874 and then not Analyzed (Decl)
7875 and then Is_List_Member (Decl)
7876 and then No (Parent (Decl))
7877 then
7878 Remove (Decl);
7879 Insert_Action (N, Decl);
7880 end if;
7881 end;
7882 end if;
7884 return;
7886 elsif Is_Entity_Name (P) then
7887 P_Name := Entity (P);
7889 -- The prefix may denote an enclosing type which is the completion
7890 -- of an incomplete type declaration.
7892 if Is_Type (P_Name) then
7893 Set_Entity (P, Get_Full_View (P_Name));
7894 Set_Etype (P, Entity (P));
7895 P_Name := Entity (P);
7896 end if;
7898 P_Type := Base_Type (Etype (P));
7900 if Debug_Flag_E then
7901 Write_Str ("Found prefix type to be ");
7902 Write_Entity_Info (P_Type, " "); Write_Eol;
7903 end if;
7905 -- If the prefix's type is an access type, get to the record type
7907 if Is_Access_Type (P_Type) then
7908 P_Type := Implicitly_Designated_Type (P_Type);
7909 end if;
7911 -- First check for components of a record object (not the result of
7912 -- a call, which is handled below). This also covers the case where
7913 -- the extension feature that supports the prefixed form of calls
7914 -- for primitives of untagged types is enabled (excluding concurrent
7915 -- cases, which are handled further below).
7917 if Is_Type (P_Type)
7918 and then (Has_Components (P_Type)
7919 or else (Core_Extensions_Allowed
7920 and then not Is_Concurrent_Type (P_Type)))
7921 and then not Is_Overloadable (P_Name)
7922 and then not Is_Type (P_Name)
7923 then
7924 -- Selected component of record. Type checking will validate
7925 -- name of selector.
7927 -- ??? Could we rewrite an implicit dereference into an explicit
7928 -- one here?
7930 Analyze_Selected_Component (N);
7932 -- Reference to type name in predicate/invariant expression
7934 elsif Is_Concurrent_Type (P_Type)
7935 and then not In_Open_Scopes (P_Name)
7936 and then (not Is_Concurrent_Type (Etype (P_Name))
7937 or else not In_Open_Scopes (Etype (P_Name)))
7938 then
7939 -- Call to protected operation or entry. Type checking is
7940 -- needed on the prefix.
7942 Analyze_Selected_Component (N);
7944 elsif (In_Open_Scopes (P_Name)
7945 and then Ekind (P_Name) /= E_Void
7946 and then not Is_Overloadable (P_Name))
7947 or else (Is_Concurrent_Type (Etype (P_Name))
7948 and then In_Open_Scopes (Etype (P_Name)))
7949 then
7950 -- Prefix denotes an enclosing loop, block, or task, i.e. an
7951 -- enclosing construct that is not a subprogram or accept.
7953 -- A special case: a protected body may call an operation
7954 -- on an external object of the same type, in which case it
7955 -- is not an expanded name. If the prefix is the type itself,
7956 -- or the context is a single synchronized object it can only
7957 -- be interpreted as an expanded name.
7959 if Is_Concurrent_Type (Etype (P_Name)) then
7960 if Is_Type (P_Name)
7961 or else Present (Anonymous_Object (Etype (P_Name)))
7962 then
7963 Find_Expanded_Name (N);
7965 else
7966 Analyze_Selected_Component (N);
7967 return;
7968 end if;
7970 else
7971 Find_Expanded_Name (N);
7972 end if;
7974 elsif Ekind (P_Name) = E_Package then
7975 Find_Expanded_Name (N);
7977 elsif Is_Overloadable (P_Name) then
7979 -- The subprogram may be a renaming (of an enclosing scope) as
7980 -- in the case of the name of the generic within an instantiation.
7982 if Ekind (P_Name) in E_Procedure | E_Function
7983 and then Present (Alias (P_Name))
7984 and then Is_Generic_Instance (Alias (P_Name))
7985 then
7986 P_Name := Alias (P_Name);
7987 end if;
7989 if Is_Overloaded (P) then
7991 -- The prefix must resolve to a unique enclosing construct
7993 declare
7994 Found : Boolean := False;
7995 Ind : Interp_Index;
7996 It : Interp;
7998 begin
7999 Get_First_Interp (P, Ind, It);
8000 while Present (It.Nam) loop
8001 if In_Open_Scopes (It.Nam) then
8002 if Found then
8003 Error_Msg_N (
8004 "prefix must be unique enclosing scope", N);
8005 Set_Entity (N, Any_Id);
8006 Set_Etype (N, Any_Type);
8007 return;
8009 else
8010 Found := True;
8011 P_Name := It.Nam;
8012 end if;
8013 end if;
8015 Get_Next_Interp (Ind, It);
8016 end loop;
8017 end;
8018 end if;
8020 if In_Open_Scopes (P_Name) then
8021 Set_Entity (P, P_Name);
8022 Set_Is_Overloaded (P, False);
8023 Find_Expanded_Name (N);
8025 else
8026 -- If no interpretation as an expanded name is possible, it
8027 -- must be a selected component of a record returned by a
8028 -- function call. Reformat prefix as a function call, the rest
8029 -- is done by type resolution.
8031 -- Error if the prefix is procedure or entry, as is P.X
8033 if Ekind (P_Name) /= E_Function
8034 and then
8035 (not Is_Overloaded (P)
8036 or else Nkind (Parent (N)) = N_Procedure_Call_Statement)
8037 then
8038 -- Prefix may mention a package that is hidden by a local
8039 -- declaration: let the user know. Scan the full homonym
8040 -- chain, the candidate package may be anywhere on it.
8042 if Present (Homonym (Current_Entity (P_Name))) then
8043 P_Name := Current_Entity (P_Name);
8045 while Present (P_Name) loop
8046 exit when Ekind (P_Name) = E_Package;
8047 P_Name := Homonym (P_Name);
8048 end loop;
8050 if Present (P_Name) then
8051 if not Is_Reference_In_Subunit then
8052 Error_Msg_Sloc := Sloc (Entity (Prefix (N)));
8053 Error_Msg_NE
8054 ("package& is hidden by declaration#", N, P_Name);
8055 end if;
8057 Set_Entity (Prefix (N), P_Name);
8058 Find_Expanded_Name (N);
8059 return;
8061 else
8062 P_Name := Entity (Prefix (N));
8063 end if;
8064 end if;
8066 Error_Msg_NE
8067 ("invalid prefix in selected component&", N, P_Name);
8068 Change_Selected_Component_To_Expanded_Name (N);
8069 Set_Entity (N, Any_Id);
8070 Set_Etype (N, Any_Type);
8072 -- Here we have a function call, so do the reformatting
8074 else
8075 Nam := New_Copy (P);
8076 Save_Interps (P, Nam);
8078 -- We use Replace here because this is one of those cases
8079 -- where the parser has missclassified the node, and we fix
8080 -- things up and then do the semantic analysis on the fixed
8081 -- up node. Normally we do this using one of the Sinfo.CN
8082 -- routines, but this is too tricky for that.
8084 -- Note that using Rewrite would be wrong, because we would
8085 -- have a tree where the original node is unanalyzed.
8087 Replace (P,
8088 Make_Function_Call (Sloc (P), Name => Nam));
8090 -- Now analyze the reformatted node
8092 Analyze_Call (P);
8094 -- If the prefix is illegal after this transformation, there
8095 -- may be visibility errors on the prefix. The safest is to
8096 -- treat the selected component as an error.
8098 if Error_Posted (P) then
8099 Set_Etype (N, Any_Type);
8100 return;
8102 else
8103 Analyze_Selected_Component (N);
8104 end if;
8105 end if;
8106 end if;
8108 -- Remaining cases generate various error messages
8110 else
8111 -- Format node as expanded name, to avoid cascaded errors
8113 Change_Selected_Component_To_Expanded_Name (N);
8114 Set_Entity (N, Any_Id);
8115 Set_Etype (N, Any_Type);
8117 -- Issue error message, but avoid this if error issued already.
8118 -- Use identifier of prefix if one is available.
8120 if P_Name = Any_Id then
8121 null;
8123 -- It is not an error if the prefix is the current instance of
8124 -- type name, e.g. the expression of a type aspect, when it is
8125 -- analyzed within a generic unit. We still have to verify that a
8126 -- component of that name exists, and decorate the node
8127 -- accordingly.
8129 elsif Is_Entity_Name (P) and then Is_Current_Instance (P) then
8130 declare
8131 Comp : Entity_Id;
8133 begin
8134 Comp := First_Entity (Entity (P));
8135 while Present (Comp) loop
8136 if Chars (Comp) = Chars (Selector_Name (N)) then
8137 Set_Entity (N, Comp);
8138 Set_Etype (N, Etype (Comp));
8139 Set_Entity (Selector_Name (N), Comp);
8140 Set_Etype (Selector_Name (N), Etype (Comp));
8141 return;
8142 end if;
8144 Next_Entity (Comp);
8145 end loop;
8146 end;
8148 elsif Ekind (P_Name) = E_Void then
8149 Premature_Usage (P);
8151 elsif Ekind (P_Name) = E_Generic_Package then
8152 Error_Msg_N ("prefix must not be a generic package", N);
8153 Error_Msg_N ("\use package instantiation as prefix instead", N);
8155 elsif Nkind (P) /= N_Attribute_Reference then
8157 -- This may have been meant as a prefixed call to a primitive
8158 -- of an untagged type. If it is a function call check type of
8159 -- its first formal and add explanation.
8161 declare
8162 F : constant Entity_Id :=
8163 Current_Entity (Selector_Name (N));
8164 begin
8165 if Present (F)
8166 and then Is_Overloadable (F)
8167 and then Present (First_Entity (F))
8168 and then not Is_Tagged_Type (Etype (First_Entity (F)))
8169 then
8170 Error_Msg_N
8171 ("prefixed call is only allowed for objects of a "
8172 & "tagged type unless -gnatX is used", N);
8174 if not Core_Extensions_Allowed
8175 and then
8176 Try_Object_Operation (N, Allow_Extensions => True)
8177 then
8178 Error_Msg_N
8179 ("\using -gnatX would make the prefixed call legal",
8181 end if;
8182 end if;
8183 end;
8185 Error_Msg_N ("invalid prefix in selected component&", P);
8187 if Is_Incomplete_Type (P_Type)
8188 and then Is_Access_Type (Etype (P))
8189 then
8190 Error_Msg_N
8191 ("\dereference must not be of an incomplete type "
8192 & "(RM 3.10.1)", P);
8193 end if;
8195 else
8196 Error_Msg_N ("invalid prefix in selected component", P);
8197 end if;
8198 end if;
8199 else
8200 -- If prefix is not the name of an entity, it must be an expression,
8201 -- whose type is appropriate for a record. This is determined by
8202 -- type resolution.
8204 Analyze_Selected_Component (N);
8205 end if;
8207 Analyze_Dimension (N);
8208 end Find_Selected_Component;
8210 ---------------
8211 -- Find_Type --
8212 ---------------
8214 procedure Find_Type (N : Node_Id) is
8215 C : Entity_Id;
8216 Typ : Entity_Id;
8217 T : Entity_Id;
8218 T_Name : Entity_Id;
8220 begin
8221 if N = Error then
8222 return;
8224 elsif Nkind (N) = N_Attribute_Reference then
8226 -- Class attribute. This is not valid in Ada 83 mode, but we do not
8227 -- need to enforce that at this point, since the declaration of the
8228 -- tagged type in the prefix would have been flagged already.
8230 if Attribute_Name (N) = Name_Class then
8231 Check_Restriction (No_Dispatch, N);
8232 Find_Type (Prefix (N));
8234 -- Propagate error from bad prefix
8236 if Etype (Prefix (N)) = Any_Type then
8237 Set_Entity (N, Any_Type);
8238 Set_Etype (N, Any_Type);
8239 return;
8240 end if;
8242 T := Base_Type (Entity (Prefix (N)));
8244 -- Case where type is not known to be tagged. Its appearance in
8245 -- the prefix of the 'Class attribute indicates that the full view
8246 -- will be tagged.
8248 if not Is_Tagged_Type (T) then
8249 if Ekind (T) = E_Incomplete_Type then
8251 -- It is legal to denote the class type of an incomplete
8252 -- type. The full type will have to be tagged, of course.
8253 -- In Ada 2005 this usage is declared obsolescent, so we
8254 -- warn accordingly. This usage is only legal if the type
8255 -- is completed in the current scope, and not for a limited
8256 -- view of a type.
8258 if Ada_Version >= Ada_2005 then
8260 -- Test whether the Available_View of a limited type view
8261 -- is tagged, since the limited view may not be marked as
8262 -- tagged if the type itself has an untagged incomplete
8263 -- type view in its package.
8265 if From_Limited_With (T)
8266 and then not Is_Tagged_Type (Available_View (T))
8267 then
8268 Error_Msg_N
8269 ("prefix of Class attribute must be tagged", N);
8270 Set_Etype (N, Any_Type);
8271 Set_Entity (N, Any_Type);
8272 return;
8274 else
8275 if Restriction_Check_Required (No_Obsolescent_Features)
8276 then
8277 Check_Restriction
8278 (No_Obsolescent_Features, Prefix (N));
8279 end if;
8281 if Warn_On_Obsolescent_Feature then
8282 Error_Msg_N
8283 ("applying ''Class to an untagged incomplete type"
8284 & " is an obsolescent feature (RM J.11)?r?", N);
8285 end if;
8286 end if;
8287 end if;
8289 Set_Is_Tagged_Type (T);
8290 Set_Direct_Primitive_Operations (T, New_Elmt_List);
8291 Make_Class_Wide_Type (T);
8292 Set_Entity (N, Class_Wide_Type (T));
8293 Set_Etype (N, Class_Wide_Type (T));
8295 elsif Ekind (T) = E_Private_Type
8296 and then not Is_Generic_Type (T)
8297 and then In_Private_Part (Scope (T))
8298 then
8299 -- The Class attribute can be applied to an untagged private
8300 -- type fulfilled by a tagged type prior to the full type
8301 -- declaration (but only within the parent package's private
8302 -- part). Create the class-wide type now and check that the
8303 -- full type is tagged later during its analysis. Note that
8304 -- we do not mark the private type as tagged, unlike the
8305 -- case of incomplete types, because the type must still
8306 -- appear untagged to outside units.
8308 if No (Class_Wide_Type (T)) then
8309 Make_Class_Wide_Type (T);
8310 end if;
8312 Set_Entity (N, Class_Wide_Type (T));
8313 Set_Etype (N, Class_Wide_Type (T));
8315 else
8316 -- Should we introduce a type Any_Tagged and use Wrong_Type
8317 -- here, it would be a bit more consistent???
8319 Error_Msg_NE
8320 ("tagged type required, found}",
8321 Prefix (N), First_Subtype (T));
8322 Set_Entity (N, Any_Type);
8323 return;
8324 end if;
8326 -- Case of tagged type
8328 else
8329 if Is_Concurrent_Type (T) then
8330 if No (Corresponding_Record_Type (Entity (Prefix (N)))) then
8332 -- Previous error. Create a class-wide type for the
8333 -- synchronized type itself, with minimal semantic
8334 -- attributes, to catch other errors in some ACATS tests.
8336 pragma Assert (Serious_Errors_Detected /= 0);
8337 Make_Class_Wide_Type (T);
8338 C := Class_Wide_Type (T);
8339 Set_First_Entity (C, First_Entity (T));
8341 else
8342 C := Class_Wide_Type
8343 (Corresponding_Record_Type (Entity (Prefix (N))));
8344 end if;
8346 else
8347 C := Class_Wide_Type (Entity (Prefix (N)));
8348 end if;
8350 Set_Entity_With_Checks (N, C);
8351 Generate_Reference (C, N);
8352 Set_Etype (N, C);
8353 end if;
8355 -- Base attribute, not allowed in Ada 83
8357 elsif Attribute_Name (N) = Name_Base then
8358 if Ada_Version = Ada_83 and then Comes_From_Source (N) then
8359 Error_Msg_N
8360 ("(Ada 83) Base attribute not allowed in subtype mark", N);
8362 else
8363 Find_Type (Prefix (N));
8364 Typ := Entity (Prefix (N));
8366 if Ada_Version >= Ada_95
8367 and then not Is_Scalar_Type (Typ)
8368 and then not Is_Generic_Type (Typ)
8369 then
8370 Error_Msg_N
8371 ("prefix of Base attribute must be scalar type",
8372 Prefix (N));
8374 elsif Warn_On_Redundant_Constructs
8375 and then Base_Type (Typ) = Typ
8376 then
8377 Error_Msg_NE -- CODEFIX
8378 ("redundant attribute, & is its own base type?r?", N, Typ);
8379 end if;
8381 T := Base_Type (Typ);
8383 -- Rewrite attribute reference with type itself (see similar
8384 -- processing in Analyze_Attribute, case Base). Preserve prefix
8385 -- if present, for other legality checks.
8387 if Nkind (Prefix (N)) = N_Expanded_Name then
8388 Rewrite (N,
8389 Make_Expanded_Name (Sloc (N),
8390 Chars => Chars (T),
8391 Prefix => New_Copy (Prefix (Prefix (N))),
8392 Selector_Name => New_Occurrence_Of (T, Sloc (N))));
8394 else
8395 Rewrite (N, New_Occurrence_Of (T, Sloc (N)));
8396 end if;
8398 Set_Entity (N, T);
8399 Set_Etype (N, T);
8400 end if;
8402 elsif Attribute_Name (N) = Name_Stub_Type then
8404 -- This is handled in Analyze_Attribute
8406 Analyze (N);
8408 -- All other attributes are invalid in a subtype mark
8410 else
8411 Error_Msg_N ("invalid attribute in subtype mark", N);
8412 end if;
8414 else
8415 Analyze (N);
8417 if Is_Entity_Name (N) then
8418 T_Name := Entity (N);
8419 else
8420 Error_Msg_N ("subtype mark required in this context", N);
8421 Set_Etype (N, Any_Type);
8422 return;
8423 end if;
8425 if T_Name = Any_Id or else Etype (N) = Any_Type then
8427 -- Undefined id. Make it into a valid type
8429 Set_Entity (N, Any_Type);
8431 elsif not Is_Type (T_Name)
8432 and then T_Name /= Standard_Void_Type
8433 then
8434 Error_Msg_Sloc := Sloc (T_Name);
8435 Error_Msg_N ("subtype mark required in this context", N);
8436 Error_Msg_NE ("\\found & declared#", N, T_Name);
8437 Set_Entity (N, Any_Type);
8439 else
8440 -- If the type is an incomplete type created to handle
8441 -- anonymous access components of a record type, then the
8442 -- incomplete type is the visible entity and subsequent
8443 -- references will point to it. Mark the original full
8444 -- type as referenced, to prevent spurious warnings.
8446 if Is_Incomplete_Type (T_Name)
8447 and then Present (Full_View (T_Name))
8448 and then not Comes_From_Source (T_Name)
8449 then
8450 Set_Referenced (Full_View (T_Name));
8451 end if;
8453 T_Name := Get_Full_View (T_Name);
8455 -- Ada 2005 (AI-251, AI-50217): Handle interfaces visible through
8456 -- limited-with clauses
8458 if From_Limited_With (T_Name)
8459 and then Is_Incomplete_Type (T_Name)
8460 and then Present (Non_Limited_View (T_Name))
8461 and then Is_Interface (Non_Limited_View (T_Name))
8462 then
8463 T_Name := Non_Limited_View (T_Name);
8464 end if;
8466 if In_Open_Scopes (T_Name) then
8467 if Ekind (Base_Type (T_Name)) = E_Task_Type then
8469 -- In Ada 2005, a task name can be used in an access
8470 -- definition within its own body.
8472 if Ada_Version >= Ada_2005
8473 and then Nkind (Parent (N)) = N_Access_Definition
8474 then
8475 Set_Entity (N, T_Name);
8476 Set_Etype (N, T_Name);
8477 return;
8479 else
8480 Error_Msg_N
8481 ("task type cannot be used as type mark " &
8482 "within its own spec or body", N);
8483 end if;
8485 elsif Ekind (Base_Type (T_Name)) = E_Protected_Type then
8487 -- In Ada 2005, a protected name can be used in an access
8488 -- definition within its own body.
8490 if Ada_Version >= Ada_2005
8491 and then Nkind (Parent (N)) = N_Access_Definition
8492 then
8493 Set_Entity (N, T_Name);
8494 Set_Etype (N, T_Name);
8495 return;
8497 else
8498 Error_Msg_N
8499 ("protected type cannot be used as type mark " &
8500 "within its own spec or body", N);
8501 end if;
8503 else
8504 Error_Msg_N ("type declaration cannot refer to itself", N);
8505 end if;
8507 Set_Etype (N, Any_Type);
8508 Set_Entity (N, Any_Type);
8509 Set_Error_Posted (T_Name);
8510 return;
8511 end if;
8513 Set_Entity (N, T_Name);
8514 Set_Etype (N, T_Name);
8515 end if;
8516 end if;
8518 if Present (Etype (N)) and then Comes_From_Source (N) then
8519 if Is_Fixed_Point_Type (Etype (N)) then
8520 Check_Restriction (No_Fixed_Point, N);
8521 elsif Is_Floating_Point_Type (Etype (N)) then
8522 Check_Restriction (No_Floating_Point, N);
8523 end if;
8525 -- A Ghost type must appear in a specific context
8527 if Is_Ghost_Entity (Etype (N)) then
8528 Check_Ghost_Context (Etype (N), N);
8529 end if;
8530 end if;
8531 end Find_Type;
8533 --------------------
8534 -- Has_Components --
8535 --------------------
8537 function Has_Components (Typ : Entity_Id) return Boolean is
8538 begin
8539 return Is_Record_Type (Typ)
8540 or else (Is_Private_Type (Typ) and then Has_Discriminants (Typ))
8541 or else (Is_Task_Type (Typ) and then Has_Discriminants (Typ))
8542 or else (Is_Incomplete_Type (Typ)
8543 and then From_Limited_With (Typ)
8544 and then Is_Record_Type (Available_View (Typ)));
8545 end Has_Components;
8547 ------------------------------------
8548 -- Has_Implicit_Character_Literal --
8549 ------------------------------------
8551 function Has_Implicit_Character_Literal (N : Node_Id) return Boolean is
8552 Id : Entity_Id;
8553 Found : Boolean := False;
8554 P : constant Entity_Id := Entity (Prefix (N));
8555 Priv_Id : Entity_Id := Empty;
8557 begin
8558 if Ekind (P) = E_Package and then not In_Open_Scopes (P) then
8559 Priv_Id := First_Private_Entity (P);
8560 end if;
8562 if P = Standard_Standard then
8563 Change_Selected_Component_To_Expanded_Name (N);
8564 Rewrite (N, Selector_Name (N));
8565 Analyze (N);
8566 Set_Etype (Original_Node (N), Standard_Character);
8567 return True;
8568 end if;
8570 Id := First_Entity (P);
8571 while Present (Id) and then Id /= Priv_Id loop
8572 if Is_Standard_Character_Type (Id) and then Is_Base_Type (Id) then
8574 -- We replace the node with the literal itself, resolve as a
8575 -- character, and set the type correctly.
8577 if not Found then
8578 Change_Selected_Component_To_Expanded_Name (N);
8579 Rewrite (N, Selector_Name (N));
8580 Analyze (N);
8581 Set_Etype (N, Id);
8582 Set_Etype (Original_Node (N), Id);
8583 Found := True;
8585 else
8586 -- More than one type derived from Character in given scope.
8587 -- Collect all possible interpretations.
8589 Add_One_Interp (N, Id, Id);
8590 end if;
8591 end if;
8593 Next_Entity (Id);
8594 end loop;
8596 return Found;
8597 end Has_Implicit_Character_Literal;
8599 ----------------------
8600 -- Has_Private_With --
8601 ----------------------
8603 function Has_Private_With (E : Entity_Id) return Boolean is
8604 Comp_Unit : constant Node_Id := Cunit (Current_Sem_Unit);
8605 Item : Node_Id;
8607 begin
8608 Item := First (Context_Items (Comp_Unit));
8609 while Present (Item) loop
8610 if Nkind (Item) = N_With_Clause
8611 and then Private_Present (Item)
8612 and then Entity (Name (Item)) = E
8613 then
8614 return True;
8615 end if;
8617 Next (Item);
8618 end loop;
8620 return False;
8621 end Has_Private_With;
8623 ---------------------------
8624 -- Has_Implicit_Operator --
8625 ---------------------------
8627 function Has_Implicit_Operator (N : Node_Id) return Boolean is
8628 Op_Id : constant Name_Id := Chars (Selector_Name (N));
8629 P : constant Entity_Id := Entity (Prefix (N));
8630 Id : Entity_Id;
8631 Priv_Id : Entity_Id := Empty;
8633 procedure Add_Implicit_Operator
8634 (T : Entity_Id;
8635 Op_Type : Entity_Id := Empty);
8636 -- Add implicit interpretation to node N, using the type for which a
8637 -- predefined operator exists. If the operator yields a boolean type,
8638 -- the Operand_Type is implicitly referenced by the operator, and a
8639 -- reference to it must be generated.
8641 ---------------------------
8642 -- Add_Implicit_Operator --
8643 ---------------------------
8645 procedure Add_Implicit_Operator
8646 (T : Entity_Id;
8647 Op_Type : Entity_Id := Empty)
8649 Predef_Op : Entity_Id;
8651 begin
8652 Predef_Op := Current_Entity (Selector_Name (N));
8653 while Present (Predef_Op)
8654 and then Scope (Predef_Op) /= Standard_Standard
8655 loop
8656 Predef_Op := Homonym (Predef_Op);
8657 end loop;
8659 if Nkind (N) = N_Selected_Component then
8660 Change_Selected_Component_To_Expanded_Name (N);
8661 end if;
8663 -- If the context is an unanalyzed function call, determine whether
8664 -- a binary or unary interpretation is required.
8666 if Nkind (Parent (N)) = N_Indexed_Component then
8667 declare
8668 Is_Binary_Call : constant Boolean :=
8669 Present
8670 (Next (First (Expressions (Parent (N)))));
8671 Is_Binary_Op : constant Boolean :=
8672 First_Entity
8673 (Predef_Op) /= Last_Entity (Predef_Op);
8674 Predef_Op2 : constant Entity_Id := Homonym (Predef_Op);
8676 begin
8677 if Is_Binary_Call then
8678 if Is_Binary_Op then
8679 Add_One_Interp (N, Predef_Op, T);
8680 else
8681 Add_One_Interp (N, Predef_Op2, T);
8682 end if;
8683 else
8684 if not Is_Binary_Op then
8685 Add_One_Interp (N, Predef_Op, T);
8687 -- Predef_Op2 may be empty in case of previous errors
8689 elsif Present (Predef_Op2) then
8690 Add_One_Interp (N, Predef_Op2, T);
8691 end if;
8692 end if;
8693 end;
8695 else
8696 Add_One_Interp (N, Predef_Op, T);
8698 -- For operators with unary and binary interpretations, if
8699 -- context is not a call, add both
8701 if Present (Homonym (Predef_Op)) then
8702 Add_One_Interp (N, Homonym (Predef_Op), T);
8703 end if;
8704 end if;
8706 -- The node is a reference to a predefined operator, and
8707 -- an implicit reference to the type of its operands.
8709 if Present (Op_Type) then
8710 Generate_Operator_Reference (N, Op_Type);
8711 else
8712 Generate_Operator_Reference (N, T);
8713 end if;
8714 end Add_Implicit_Operator;
8716 -- Start of processing for Has_Implicit_Operator
8718 begin
8719 if Ekind (P) = E_Package and then not In_Open_Scopes (P) then
8720 Priv_Id := First_Private_Entity (P);
8721 end if;
8723 Id := First_Entity (P);
8725 case Op_Id is
8727 -- Boolean operators: an implicit declaration exists if the scope
8728 -- contains a declaration for a derived Boolean type, or for an
8729 -- array of Boolean type.
8731 when Name_Op_And
8732 | Name_Op_Not
8733 | Name_Op_Or
8734 | Name_Op_Xor
8736 while Id /= Priv_Id loop
8737 if Is_Type (Id)
8738 and then Valid_Boolean_Arg (Id)
8739 and then Is_Base_Type (Id)
8740 then
8741 Add_Implicit_Operator (Id);
8742 return True;
8743 end if;
8745 Next_Entity (Id);
8746 end loop;
8748 -- Equality: look for any non-limited type (result is Boolean)
8750 when Name_Op_Eq
8751 | Name_Op_Ne
8753 while Id /= Priv_Id loop
8754 if Is_Type (Id)
8755 and then Valid_Equality_Arg (Id)
8756 and then Is_Base_Type (Id)
8757 then
8758 Add_Implicit_Operator (Standard_Boolean, Id);
8759 return True;
8760 end if;
8762 Next_Entity (Id);
8763 end loop;
8765 -- Comparison operators: scalar type, or array of scalar
8767 when Name_Op_Ge
8768 | Name_Op_Gt
8769 | Name_Op_Le
8770 | Name_Op_Lt
8772 while Id /= Priv_Id loop
8773 if Is_Type (Id)
8774 and then Valid_Comparison_Arg (Id)
8775 and then Is_Base_Type (Id)
8776 then
8777 Add_Implicit_Operator (Standard_Boolean, Id);
8778 return True;
8779 end if;
8781 Next_Entity (Id);
8782 end loop;
8784 -- Arithmetic operators: any numeric type
8786 when Name_Op_Abs
8787 | Name_Op_Add
8788 | Name_Op_Divide
8789 | Name_Op_Expon
8790 | Name_Op_Mod
8791 | Name_Op_Multiply
8792 | Name_Op_Rem
8793 | Name_Op_Subtract
8795 while Id /= Priv_Id loop
8796 if Is_Numeric_Type (Id) and then Is_Base_Type (Id) then
8797 Add_Implicit_Operator (Id);
8798 return True;
8799 end if;
8801 Next_Entity (Id);
8802 end loop;
8804 -- Concatenation: any one-dimensional array type
8806 when Name_Op_Concat =>
8807 while Id /= Priv_Id loop
8808 if Is_Array_Type (Id)
8809 and then Number_Dimensions (Id) = 1
8810 and then Is_Base_Type (Id)
8811 then
8812 Add_Implicit_Operator (Id);
8813 return True;
8814 end if;
8816 Next_Entity (Id);
8817 end loop;
8819 -- What is the others condition here? Should we be using a
8820 -- subtype of Name_Id that would restrict to operators ???
8822 when others =>
8823 null;
8824 end case;
8826 -- If we fall through, then we do not have an implicit operator
8828 return False;
8829 end Has_Implicit_Operator;
8831 -----------------------------------
8832 -- Has_Loop_In_Inner_Open_Scopes --
8833 -----------------------------------
8835 function Has_Loop_In_Inner_Open_Scopes (S : Entity_Id) return Boolean is
8836 begin
8837 -- Several scope stacks are maintained by Scope_Stack. The base of the
8838 -- currently active scope stack is denoted by the Is_Active_Stack_Base
8839 -- flag in the scope stack entry. Note that the scope stacks used to
8840 -- simply be delimited implicitly by the presence of Standard_Standard
8841 -- at their base, but there now are cases where this is not sufficient
8842 -- because Standard_Standard actually may appear in the middle of the
8843 -- active set of scopes.
8845 for J in reverse 0 .. Scope_Stack.Last loop
8847 -- S was reached without seing a loop scope first
8849 if Scope_Stack.Table (J).Entity = S then
8850 return False;
8852 -- S was not yet reached, so it contains at least one inner loop
8854 elsif Ekind (Scope_Stack.Table (J).Entity) = E_Loop then
8855 return True;
8856 end if;
8858 -- Check Is_Active_Stack_Base to tell us when to stop, as there are
8859 -- cases where Standard_Standard appears in the middle of the active
8860 -- set of scopes. This affects the declaration and overriding of
8861 -- private inherited operations in instantiations of generic child
8862 -- units.
8864 pragma Assert (not Scope_Stack.Table (J).Is_Active_Stack_Base);
8865 end loop;
8867 raise Program_Error; -- unreachable
8868 end Has_Loop_In_Inner_Open_Scopes;
8870 --------------------
8871 -- In_Open_Scopes --
8872 --------------------
8874 function In_Open_Scopes (S : Entity_Id) return Boolean is
8875 begin
8876 -- Several scope stacks are maintained by Scope_Stack. The base of the
8877 -- currently active scope stack is denoted by the Is_Active_Stack_Base
8878 -- flag in the scope stack entry. Note that the scope stacks used to
8879 -- simply be delimited implicitly by the presence of Standard_Standard
8880 -- at their base, but there now are cases where this is not sufficient
8881 -- because Standard_Standard actually may appear in the middle of the
8882 -- active set of scopes.
8884 for J in reverse 0 .. Scope_Stack.Last loop
8885 if Scope_Stack.Table (J).Entity = S then
8886 return True;
8887 end if;
8889 -- Check Is_Active_Stack_Base to tell us when to stop, as there are
8890 -- cases where Standard_Standard appears in the middle of the active
8891 -- set of scopes. This affects the declaration and overriding of
8892 -- private inherited operations in instantiations of generic child
8893 -- units.
8895 exit when Scope_Stack.Table (J).Is_Active_Stack_Base;
8896 end loop;
8898 return False;
8899 end In_Open_Scopes;
8901 -----------------------------
8902 -- Inherit_Renamed_Profile --
8903 -----------------------------
8905 procedure Inherit_Renamed_Profile (New_S : Entity_Id; Old_S : Entity_Id) is
8906 New_F : Entity_Id;
8907 Old_F : Entity_Id;
8908 Old_T : Entity_Id;
8909 New_T : Entity_Id;
8911 begin
8912 if Ekind (Old_S) = E_Operator then
8913 New_F := First_Formal (New_S);
8915 while Present (New_F) loop
8916 Set_Etype (New_F, Base_Type (Etype (New_F)));
8917 Next_Formal (New_F);
8918 end loop;
8920 Set_Etype (New_S, Base_Type (Etype (New_S)));
8922 else
8923 New_F := First_Formal (New_S);
8924 Old_F := First_Formal (Old_S);
8926 while Present (New_F) loop
8927 New_T := Etype (New_F);
8928 Old_T := Etype (Old_F);
8930 -- If the new type is a renaming of the old one, as is the case
8931 -- for actuals in instances, retain its name, to simplify later
8932 -- disambiguation.
8934 if Nkind (Parent (New_T)) = N_Subtype_Declaration
8935 and then Is_Entity_Name (Subtype_Indication (Parent (New_T)))
8936 and then Entity (Subtype_Indication (Parent (New_T))) = Old_T
8937 then
8938 null;
8939 else
8940 Set_Etype (New_F, Old_T);
8941 end if;
8943 Next_Formal (New_F);
8944 Next_Formal (Old_F);
8945 end loop;
8947 pragma Assert (No (Old_F));
8949 if Ekind (Old_S) in E_Function | E_Enumeration_Literal then
8950 Set_Etype (New_S, Etype (Old_S));
8951 end if;
8952 end if;
8953 end Inherit_Renamed_Profile;
8955 ----------------
8956 -- Initialize --
8957 ----------------
8959 procedure Initialize is
8960 begin
8961 Urefs.Init;
8962 end Initialize;
8964 -------------------------
8965 -- Install_Use_Clauses --
8966 -------------------------
8968 procedure Install_Use_Clauses
8969 (Clause : Node_Id;
8970 Force_Installation : Boolean := False)
8972 U : Node_Id;
8974 begin
8975 U := Clause;
8976 while Present (U) loop
8978 -- Case of USE package
8980 if Nkind (U) = N_Use_Package_Clause then
8981 Use_One_Package (U, Name (U), True);
8983 -- Case of USE TYPE
8985 else
8986 Use_One_Type (Subtype_Mark (U), Force => Force_Installation);
8988 end if;
8990 Next_Use_Clause (U);
8991 end loop;
8992 end Install_Use_Clauses;
8994 ----------------------
8995 -- Mark_Use_Clauses --
8996 ----------------------
8998 procedure Mark_Use_Clauses (Id : Node_Or_Entity_Id) is
8999 procedure Mark_Parameters (Call : Entity_Id);
9000 -- Perform use_type_clause marking for all parameters in a subprogram
9001 -- or operator call.
9003 procedure Mark_Use_Package (Pak : Entity_Id);
9004 -- Move up the Prev_Use_Clause chain for packages denoted by Pak -
9005 -- marking each clause in the chain as effective in the process.
9007 procedure Mark_Use_Type (E : Entity_Id);
9008 -- Similar to Do_Use_Package_Marking except we move up the
9009 -- Prev_Use_Clause chain for the type denoted by E.
9011 ---------------------
9012 -- Mark_Parameters --
9013 ---------------------
9015 procedure Mark_Parameters (Call : Entity_Id) is
9016 Curr : Node_Id;
9018 begin
9019 -- Move through all of the formals
9021 Curr := First_Formal (Call);
9022 while Present (Curr) loop
9023 Mark_Use_Type (Curr);
9025 Next_Formal (Curr);
9026 end loop;
9028 -- Handle the return type
9030 Mark_Use_Type (Call);
9031 end Mark_Parameters;
9033 ----------------------
9034 -- Mark_Use_Package --
9035 ----------------------
9037 procedure Mark_Use_Package (Pak : Entity_Id) is
9038 Curr : Node_Id;
9040 begin
9041 -- Ignore cases where the scope of the type is not a package (e.g.
9042 -- Standard_Standard).
9044 if Ekind (Pak) /= E_Package then
9045 return;
9046 end if;
9048 Curr := Current_Use_Clause (Pak);
9049 while Present (Curr)
9050 and then not Is_Effective_Use_Clause (Curr)
9051 loop
9052 -- We need to mark the previous use clauses as effective, but
9053 -- each use clause may in turn render other use_package_clauses
9054 -- effective. Additionally, it is possible to have a parent
9055 -- package renamed as a child of itself so we must check the
9056 -- prefix entity is not the same as the package we are marking.
9058 if Nkind (Name (Curr)) /= N_Identifier
9059 and then Present (Prefix (Name (Curr)))
9060 and then Entity (Prefix (Name (Curr))) /= Pak
9061 then
9062 Mark_Use_Package (Entity (Prefix (Name (Curr))));
9064 -- It is also possible to have a child package without a prefix
9065 -- that relies on a previous use_package_clause.
9067 elsif Nkind (Name (Curr)) = N_Identifier
9068 and then Is_Child_Unit (Entity (Name (Curr)))
9069 then
9070 Mark_Use_Package (Scope (Entity (Name (Curr))));
9071 end if;
9073 -- Mark the use_package_clause as effective and move up the chain
9075 Set_Is_Effective_Use_Clause (Curr);
9077 Curr := Prev_Use_Clause (Curr);
9078 end loop;
9079 end Mark_Use_Package;
9081 -------------------
9082 -- Mark_Use_Type --
9083 -------------------
9085 procedure Mark_Use_Type (E : Entity_Id) is
9086 Curr : Node_Id;
9087 Base : Entity_Id;
9089 begin
9090 -- Ignore void types and unresolved string literals and primitives
9092 if Nkind (E) = N_String_Literal
9093 or else Nkind (Etype (E)) not in N_Entity
9094 or else not Is_Type (Etype (E))
9095 then
9096 return;
9097 end if;
9099 -- Primitives with class-wide operands might additionally render
9100 -- their base type's use_clauses effective - so do a recursive check
9101 -- here.
9103 Base := Base_Type (Etype (E));
9105 if Ekind (Base) = E_Class_Wide_Type then
9106 Mark_Use_Type (Base);
9107 end if;
9109 -- The package containing the type or operator function being used
9110 -- may be in use as well, so mark any use_package_clauses for it as
9111 -- effective. There are also additional sanity checks performed here
9112 -- for ignoring previous errors.
9114 Mark_Use_Package (Scope (Base));
9116 if Nkind (E) in N_Op
9117 and then Present (Entity (E))
9118 and then Present (Scope (Entity (E)))
9119 then
9120 Mark_Use_Package (Scope (Entity (E)));
9121 end if;
9123 Curr := Current_Use_Clause (Base);
9124 while Present (Curr)
9125 and then not Is_Effective_Use_Clause (Curr)
9126 loop
9127 -- Current use_type_clause may render other use_package_clauses
9128 -- effective.
9130 if Nkind (Subtype_Mark (Curr)) /= N_Identifier
9131 and then Present (Prefix (Subtype_Mark (Curr)))
9132 then
9133 Mark_Use_Package (Entity (Prefix (Subtype_Mark (Curr))));
9134 end if;
9136 -- Mark the use_type_clause as effective and move up the chain
9138 Set_Is_Effective_Use_Clause (Curr);
9140 Curr := Prev_Use_Clause (Curr);
9141 end loop;
9142 end Mark_Use_Type;
9144 -- Start of processing for Mark_Use_Clauses
9146 begin
9147 -- Use clauses in and of themselves do not count as a "use" of a
9148 -- package.
9150 if Nkind (Parent (Id)) in N_Use_Package_Clause | N_Use_Type_Clause then
9151 return;
9152 end if;
9154 -- Handle entities
9156 if Nkind (Id) in N_Entity then
9158 -- Mark the entity's package
9160 if Is_Potentially_Use_Visible (Id) then
9161 Mark_Use_Package (Scope (Id));
9162 end if;
9164 -- Mark enumeration literals
9166 if Ekind (Id) = E_Enumeration_Literal then
9167 Mark_Use_Type (Id);
9169 -- Mark primitives
9171 elsif (Is_Overloadable (Id)
9172 or else Is_Generic_Subprogram (Id))
9173 and then (Is_Potentially_Use_Visible (Id)
9174 or else Is_Intrinsic_Subprogram (Id)
9175 or else (Ekind (Id) in E_Function | E_Procedure
9176 and then Is_Generic_Actual_Subprogram (Id)))
9177 then
9178 Mark_Parameters (Id);
9179 end if;
9181 -- Handle nodes
9183 else
9184 -- Mark operators
9186 if Nkind (Id) in N_Op then
9188 -- At this point the left operand may not be resolved if we are
9189 -- encountering multiple operators next to eachother in an
9190 -- expression.
9192 if Nkind (Id) in N_Binary_Op
9193 and then not (Nkind (Left_Opnd (Id)) in N_Op)
9194 then
9195 Mark_Use_Type (Left_Opnd (Id));
9196 end if;
9198 Mark_Use_Type (Right_Opnd (Id));
9199 Mark_Use_Type (Id);
9201 -- Mark entity identifiers
9203 elsif Nkind (Id) in N_Has_Entity
9204 and then (Is_Potentially_Use_Visible (Entity (Id))
9205 or else (Is_Generic_Instance (Entity (Id))
9206 and then Is_Immediately_Visible (Entity (Id))))
9207 then
9208 -- Ignore fully qualified names as they do not count as a "use" of
9209 -- a package.
9211 if Nkind (Id) in N_Identifier | N_Operator_Symbol
9212 or else (Present (Prefix (Id))
9213 and then Scope (Entity (Id)) /= Entity (Prefix (Id)))
9214 then
9215 Mark_Use_Clauses (Entity (Id));
9216 end if;
9217 end if;
9218 end if;
9219 end Mark_Use_Clauses;
9221 --------------------------------
9222 -- Most_Descendant_Use_Clause --
9223 --------------------------------
9225 function Most_Descendant_Use_Clause
9226 (Clause1 : Entity_Id;
9227 Clause2 : Entity_Id) return Entity_Id
9229 function Determine_Package_Scope (Clause : Node_Id) return Entity_Id;
9230 -- Given a use clause, determine which package it belongs to
9232 -----------------------------
9233 -- Determine_Package_Scope --
9234 -----------------------------
9236 function Determine_Package_Scope (Clause : Node_Id) return Entity_Id is
9237 begin
9238 -- Check if the clause appears in the context area
9240 -- Note we cannot employ Enclosing_Packge for use clauses within
9241 -- context clauses since they are not actually "enclosed."
9243 if Nkind (Parent (Clause)) = N_Compilation_Unit then
9244 return Entity_Of_Unit (Unit (Parent (Clause)));
9245 end if;
9247 -- Otherwise, obtain the enclosing package normally
9249 return Enclosing_Package (Clause);
9250 end Determine_Package_Scope;
9252 Scope1 : Entity_Id;
9253 Scope2 : Entity_Id;
9255 -- Start of processing for Most_Descendant_Use_Clause
9257 begin
9258 if Clause1 = Clause2 then
9259 return Clause1;
9260 end if;
9262 -- We determine which one is the most descendant by the scope distance
9263 -- to the ultimate parent unit.
9265 Scope1 := Determine_Package_Scope (Clause1);
9266 Scope2 := Determine_Package_Scope (Clause2);
9267 while Scope1 /= Standard_Standard
9268 and then Scope2 /= Standard_Standard
9269 loop
9270 Scope1 := Scope (Scope1);
9271 Scope2 := Scope (Scope2);
9273 if No (Scope1) then
9274 return Clause1;
9275 elsif No (Scope2) then
9276 return Clause2;
9277 end if;
9278 end loop;
9280 if Scope1 = Standard_Standard then
9281 return Clause1;
9282 end if;
9284 return Clause2;
9285 end Most_Descendant_Use_Clause;
9287 ---------------
9288 -- Pop_Scope --
9289 ---------------
9291 procedure Pop_Scope is
9292 SST : Scope_Stack_Entry renames Scope_Stack.Table (Scope_Stack.Last);
9293 S : constant Entity_Id := SST.Entity;
9295 begin
9296 if Debug_Flag_E then
9297 Write_Info;
9298 end if;
9300 -- Set Default_Storage_Pool field of the library unit if necessary
9302 if Is_Package_Or_Generic_Package (S)
9303 and then
9304 Nkind (Parent (Unit_Declaration_Node (S))) = N_Compilation_Unit
9305 then
9306 declare
9307 Aux : constant Node_Id :=
9308 Aux_Decls_Node (Parent (Unit_Declaration_Node (S)));
9309 begin
9310 if No (Default_Storage_Pool (Aux)) then
9311 Set_Default_Storage_Pool (Aux, Default_Pool);
9312 end if;
9313 end;
9314 end if;
9316 Scope_Suppress := SST.Save_Scope_Suppress;
9317 Local_Suppress_Stack_Top := SST.Save_Local_Suppress_Stack_Top;
9318 Check_Policy_List := SST.Save_Check_Policy_List;
9319 Default_Pool := SST.Save_Default_Storage_Pool;
9320 No_Tagged_Streams := SST.Save_No_Tagged_Streams;
9321 SPARK_Mode := SST.Save_SPARK_Mode;
9322 SPARK_Mode_Pragma := SST.Save_SPARK_Mode_Pragma;
9323 Default_SSO := SST.Save_Default_SSO;
9324 Uneval_Old := SST.Save_Uneval_Old;
9326 if Debug_Flag_W then
9327 Write_Str ("<-- exiting scope: ");
9328 Write_Name (Chars (Current_Scope));
9329 Write_Str (", Depth=");
9330 Write_Int (Int (Scope_Stack.Last));
9331 Write_Eol;
9332 end if;
9334 End_Use_Clauses (SST.First_Use_Clause);
9336 -- If the actions to be wrapped are still there they will get lost
9337 -- causing incomplete code to be generated. It is better to abort in
9338 -- this case (and we do the abort even with assertions off since the
9339 -- penalty is incorrect code generation).
9341 if SST.Actions_To_Be_Wrapped /= Scope_Actions'(others => No_List) then
9342 raise Program_Error;
9343 end if;
9345 -- Free last subprogram name if allocated, and pop scope
9347 Free (SST.Last_Subprogram_Name);
9348 Scope_Stack.Decrement_Last;
9349 end Pop_Scope;
9351 ----------------
9352 -- Push_Scope --
9353 ----------------
9355 procedure Push_Scope (S : Entity_Id) is
9356 E : constant Entity_Id := Scope (S);
9358 function Component_Alignment_Default return Component_Alignment_Kind;
9359 -- Return Component_Alignment_Kind for the newly-pushed scope.
9361 function Component_Alignment_Default return Component_Alignment_Kind is
9362 begin
9363 -- Each new scope pushed onto the scope stack inherits the component
9364 -- alignment of the previous scope. This emulates the "visibility"
9365 -- semantics of pragma Component_Alignment.
9367 if Scope_Stack.Last > Scope_Stack.First then
9368 return Scope_Stack.Table
9369 (Scope_Stack.Last - 1).Component_Alignment_Default;
9371 -- Otherwise, this is the first scope being pushed on the scope
9372 -- stack. Inherit the component alignment from the configuration
9373 -- form of pragma Component_Alignment (if any).
9375 else
9376 return Configuration_Component_Alignment;
9377 end if;
9378 end Component_Alignment_Default;
9380 begin
9381 if Ekind (S) = E_Void then
9382 null;
9384 -- Set scope depth if not a nonconcurrent type, and we have not yet set
9385 -- the scope depth. This means that we have the first occurrence of the
9386 -- scope, and this is where the depth is set.
9388 elsif (not Is_Type (S) or else Is_Concurrent_Type (S))
9389 and then not Scope_Depth_Set (S)
9390 then
9391 if S = Standard_Standard then
9392 Set_Scope_Depth_Value (S, Uint_0);
9394 elsif Is_Child_Unit (S) then
9395 Set_Scope_Depth_Value (S, Uint_1);
9397 elsif not Is_Record_Type (Current_Scope) then
9398 if Scope_Depth_Set (Current_Scope) then
9399 if Ekind (S) = E_Loop then
9400 Set_Scope_Depth_Value (S, Scope_Depth (Current_Scope));
9401 else
9402 Set_Scope_Depth_Value (S, Scope_Depth (Current_Scope) + 1);
9403 end if;
9404 end if;
9405 end if;
9406 end if;
9408 Scope_Stack.Increment_Last;
9410 Scope_Stack.Table (Scope_Stack.Last) :=
9411 (Entity => S,
9412 Save_Scope_Suppress => Scope_Suppress,
9413 Save_Local_Suppress_Stack_Top => Local_Suppress_Stack_Top,
9414 Save_Check_Policy_List => Check_Policy_List,
9415 Save_Default_Storage_Pool => Default_Pool,
9416 Save_No_Tagged_Streams => No_Tagged_Streams,
9417 Save_SPARK_Mode => SPARK_Mode,
9418 Save_SPARK_Mode_Pragma => SPARK_Mode_Pragma,
9419 Save_Default_SSO => Default_SSO,
9420 Save_Uneval_Old => Uneval_Old,
9421 Component_Alignment_Default => Component_Alignment_Default,
9422 Last_Subprogram_Name => null,
9423 Is_Transient => False,
9424 Node_To_Be_Wrapped => Empty,
9425 Pending_Freeze_Actions => No_List,
9426 Actions_To_Be_Wrapped => (others => No_List),
9427 First_Use_Clause => Empty,
9428 Is_Active_Stack_Base => False,
9429 Previous_Visibility => False,
9430 Locked_Shared_Objects => No_Elist);
9432 if Debug_Flag_W then
9433 Write_Str ("--> new scope: ");
9434 Write_Name (Chars (Current_Scope));
9435 Write_Str (", Id=");
9436 Write_Int (Int (Current_Scope));
9437 Write_Str (", Depth=");
9438 Write_Int (Int (Scope_Stack.Last));
9439 Write_Eol;
9440 end if;
9442 -- Deal with copying flags from the previous scope to this one. This is
9443 -- not necessary if either scope is standard, or if the new scope is a
9444 -- child unit.
9446 if S /= Standard_Standard
9447 and then Scope (S) /= Standard_Standard
9448 and then not Is_Child_Unit (S)
9449 then
9450 if Nkind (E) not in N_Entity then
9451 return;
9452 end if;
9454 -- Copy categorization flags from Scope (S) to S, this is not done
9455 -- when Scope (S) is Standard_Standard since propagation is from
9456 -- library unit entity inwards. Copy other relevant attributes as
9457 -- well (Discard_Names in particular).
9459 -- We only propagate inwards for library level entities,
9460 -- inner level subprograms do not inherit the categorization.
9462 if Is_Library_Level_Entity (S) then
9463 Set_Is_Preelaborated (S, Is_Preelaborated (E));
9464 Set_Is_Shared_Passive (S, Is_Shared_Passive (E));
9465 Set_Discard_Names (S, Discard_Names (E));
9466 Set_Suppress_Value_Tracking_On_Call
9467 (S, Suppress_Value_Tracking_On_Call (E));
9468 Set_Categorization_From_Scope (E => S, Scop => E);
9469 end if;
9470 end if;
9472 if Is_Child_Unit (S)
9473 and then Present (E)
9474 and then Is_Package_Or_Generic_Package (E)
9475 and then
9476 Nkind (Parent (Unit_Declaration_Node (E))) = N_Compilation_Unit
9477 then
9478 declare
9479 Aux : constant Node_Id :=
9480 Aux_Decls_Node (Parent (Unit_Declaration_Node (E)));
9481 begin
9482 if Present (Default_Storage_Pool (Aux)) then
9483 Default_Pool := Default_Storage_Pool (Aux);
9484 end if;
9485 end;
9486 end if;
9487 end Push_Scope;
9489 ---------------------
9490 -- Premature_Usage --
9491 ---------------------
9493 procedure Premature_Usage (N : Node_Id) is
9494 Kind : constant Node_Kind := Nkind (Parent (Entity (N)));
9495 E : Entity_Id := Entity (N);
9497 begin
9498 -- Within an instance, the analysis of the actual for a formal object
9499 -- does not see the name of the object itself. This is significant only
9500 -- if the object is an aggregate, where its analysis does not do any
9501 -- name resolution on component associations. (see 4717-008). In such a
9502 -- case, look for the visible homonym on the chain.
9504 if In_Instance and then Present (Homonym (E)) then
9505 E := Homonym (E);
9506 while Present (E) and then not In_Open_Scopes (Scope (E)) loop
9507 E := Homonym (E);
9508 end loop;
9510 if Present (E) then
9511 Set_Entity (N, E);
9512 Set_Etype (N, Etype (E));
9513 return;
9514 end if;
9515 end if;
9517 case Kind is
9518 when N_Component_Declaration =>
9519 Error_Msg_N
9520 ("component&! cannot be used before end of record declaration",
9523 when N_Parameter_Specification =>
9524 Error_Msg_N
9525 ("formal parameter&! cannot be used before end of specification",
9528 when N_Discriminant_Specification =>
9529 Error_Msg_N
9530 ("discriminant&! cannot be used before end of discriminant part",
9533 when N_Procedure_Specification | N_Function_Specification =>
9534 Error_Msg_N
9535 ("subprogram&! cannot be used before end of its declaration",
9538 when N_Full_Type_Declaration | N_Subtype_Declaration =>
9539 Error_Msg_N
9540 ("type& cannot be used before end of its declaration!", N);
9542 when others =>
9543 Error_Msg_N
9544 ("object& cannot be used before end of its declaration!", N);
9546 -- If the premature reference appears as the expression in its own
9547 -- declaration, rewrite it to prevent compiler loops in subsequent
9548 -- uses of this mangled declaration in address clauses.
9550 if Nkind (Parent (N)) = N_Object_Declaration then
9551 Set_Entity (N, Any_Id);
9552 end if;
9553 end case;
9554 end Premature_Usage;
9556 ------------------------
9557 -- Present_System_Aux --
9558 ------------------------
9560 function Present_System_Aux (N : Node_Id := Empty) return Boolean is
9561 Loc : Source_Ptr;
9562 Aux_Name : Unit_Name_Type;
9563 Unum : Unit_Number_Type;
9564 Withn : Node_Id;
9565 With_Sys : Node_Id;
9566 The_Unit : Node_Id;
9568 function Find_System (C_Unit : Node_Id) return Entity_Id;
9569 -- Scan context clause of compilation unit to find with_clause
9570 -- for System.
9572 -----------------
9573 -- Find_System --
9574 -----------------
9576 function Find_System (C_Unit : Node_Id) return Entity_Id is
9577 With_Clause : Node_Id;
9579 begin
9580 With_Clause := First (Context_Items (C_Unit));
9581 while Present (With_Clause) loop
9582 if (Nkind (With_Clause) = N_With_Clause
9583 and then Chars (Name (With_Clause)) = Name_System)
9584 and then Comes_From_Source (With_Clause)
9585 then
9586 return With_Clause;
9587 end if;
9589 Next (With_Clause);
9590 end loop;
9592 return Empty;
9593 end Find_System;
9595 -- Start of processing for Present_System_Aux
9597 begin
9598 -- The child unit may have been loaded and analyzed already
9600 if Present (System_Aux_Id) then
9601 return True;
9603 -- If no previous pragma for System.Aux, nothing to load
9605 elsif No (System_Extend_Unit) then
9606 return False;
9608 -- Use the unit name given in the pragma to retrieve the unit.
9609 -- Verify that System itself appears in the context clause of the
9610 -- current compilation. If System is not present, an error will
9611 -- have been reported already.
9613 else
9614 With_Sys := Find_System (Cunit (Current_Sem_Unit));
9616 The_Unit := Unit (Cunit (Current_Sem_Unit));
9618 if No (With_Sys)
9619 and then
9620 (Nkind (The_Unit) = N_Package_Body
9621 or else (Nkind (The_Unit) = N_Subprogram_Body
9622 and then not Acts_As_Spec (Cunit (Current_Sem_Unit))))
9623 then
9624 With_Sys := Find_System (Library_Unit (Cunit (Current_Sem_Unit)));
9625 end if;
9627 if No (With_Sys) and then Present (N) then
9629 -- If we are compiling a subunit, we need to examine its
9630 -- context as well (Current_Sem_Unit is the parent unit);
9632 The_Unit := Parent (N);
9633 while Nkind (The_Unit) /= N_Compilation_Unit loop
9634 The_Unit := Parent (The_Unit);
9635 end loop;
9637 if Nkind (Unit (The_Unit)) = N_Subunit then
9638 With_Sys := Find_System (The_Unit);
9639 end if;
9640 end if;
9642 if No (With_Sys) then
9643 return False;
9644 end if;
9646 Loc := Sloc (With_Sys);
9647 Get_Name_String (Chars (Expression (System_Extend_Unit)));
9648 Name_Buffer (8 .. Name_Len + 7) := Name_Buffer (1 .. Name_Len);
9649 Name_Buffer (1 .. 7) := "system.";
9650 Name_Buffer (Name_Len + 8) := '%';
9651 Name_Buffer (Name_Len + 9) := 's';
9652 Name_Len := Name_Len + 9;
9653 Aux_Name := Name_Find;
9655 Unum :=
9656 Load_Unit
9657 (Load_Name => Aux_Name,
9658 Required => False,
9659 Subunit => False,
9660 Error_Node => With_Sys);
9662 if Unum /= No_Unit then
9663 Semantics (Cunit (Unum));
9664 System_Aux_Id :=
9665 Defining_Entity (Specification (Unit (Cunit (Unum))));
9667 Withn :=
9668 Make_With_Clause (Loc,
9669 Name =>
9670 Make_Expanded_Name (Loc,
9671 Chars => Chars (System_Aux_Id),
9672 Prefix =>
9673 New_Occurrence_Of (Scope (System_Aux_Id), Loc),
9674 Selector_Name => New_Occurrence_Of (System_Aux_Id, Loc)));
9676 Set_Entity (Name (Withn), System_Aux_Id);
9678 Set_Corresponding_Spec (Withn, System_Aux_Id);
9679 Set_First_Name (Withn);
9680 Set_Implicit_With (Withn);
9681 Set_Library_Unit (Withn, Cunit (Unum));
9683 Insert_After (With_Sys, Withn);
9684 Mark_Rewrite_Insertion (Withn);
9685 Set_Context_Installed (Withn);
9687 return True;
9689 -- Here if unit load failed
9691 else
9692 Error_Msg_Name_1 := Name_System;
9693 Error_Msg_Name_2 := Chars (Expression (System_Extend_Unit));
9694 Error_Msg_N
9695 ("extension package `%.%` does not exist",
9696 Opt.System_Extend_Unit);
9697 return False;
9698 end if;
9699 end if;
9700 end Present_System_Aux;
9702 -------------------------
9703 -- Restore_Scope_Stack --
9704 -------------------------
9706 procedure Restore_Scope_Stack
9707 (List : Elist_Id;
9708 Handle_Use : Boolean := True)
9710 SS_Last : constant Int := Scope_Stack.Last;
9711 Elmt : Elmt_Id;
9713 begin
9714 -- Restore visibility of previous scope stack, if any, using the list
9715 -- we saved (we use Remove, since this list will not be used again).
9717 loop
9718 Elmt := First_Elmt (List);
9719 exit when Elmt = No_Elmt;
9720 Set_Is_Immediately_Visible (Node (Elmt));
9721 Remove_Elmt (List, Elmt);
9722 end loop;
9724 -- Restore use clauses
9726 if SS_Last >= Scope_Stack.First
9727 and then Scope_Stack.Table (SS_Last).Entity /= Standard_Standard
9728 and then Handle_Use
9729 then
9730 Install_Use_Clauses
9731 (Scope_Stack.Table (SS_Last).First_Use_Clause,
9732 Force_Installation => True);
9733 end if;
9734 end Restore_Scope_Stack;
9736 ----------------------
9737 -- Save_Scope_Stack --
9738 ----------------------
9740 -- Save_Scope_Stack/Restore_Scope_Stack were originally designed to avoid
9741 -- consuming any memory. That is, Save_Scope_Stack took care of removing
9742 -- from immediate visibility entities and Restore_Scope_Stack took care
9743 -- of restoring their visibility analyzing the context of each entity. The
9744 -- problem of such approach is that it was fragile and caused unexpected
9745 -- visibility problems, and indeed one test was found where there was a
9746 -- real problem.
9748 -- Furthermore, the following experiment was carried out:
9750 -- - Save_Scope_Stack was modified to store in an Elist1 all those
9751 -- entities whose attribute Is_Immediately_Visible is modified
9752 -- from True to False.
9754 -- - Restore_Scope_Stack was modified to store in another Elist2
9755 -- all the entities whose attribute Is_Immediately_Visible is
9756 -- modified from False to True.
9758 -- - Extra code was added to verify that all the elements of Elist1
9759 -- are found in Elist2
9761 -- This test shows that there may be more occurrences of this problem which
9762 -- have not yet been detected. As a result, we replaced that approach by
9763 -- the current one in which Save_Scope_Stack returns the list of entities
9764 -- whose visibility is changed, and that list is passed to Restore_Scope_
9765 -- Stack to undo that change. This approach is simpler and safer, although
9766 -- it consumes more memory.
9768 function Save_Scope_Stack (Handle_Use : Boolean := True) return Elist_Id is
9769 Result : constant Elist_Id := New_Elmt_List;
9770 E : Entity_Id;
9771 S : Entity_Id;
9772 SS_Last : constant Int := Scope_Stack.Last;
9774 procedure Remove_From_Visibility (E : Entity_Id);
9775 -- If E is immediately visible then append it to the result and remove
9776 -- it temporarily from visibility.
9778 ----------------------------
9779 -- Remove_From_Visibility --
9780 ----------------------------
9782 procedure Remove_From_Visibility (E : Entity_Id) is
9783 begin
9784 if Is_Immediately_Visible (E) then
9785 Append_Elmt (E, Result);
9786 Set_Is_Immediately_Visible (E, False);
9787 end if;
9788 end Remove_From_Visibility;
9790 -- Start of processing for Save_Scope_Stack
9792 begin
9793 if SS_Last >= Scope_Stack.First
9794 and then Scope_Stack.Table (SS_Last).Entity /= Standard_Standard
9795 then
9796 if Handle_Use then
9797 End_Use_Clauses (Scope_Stack.Table (SS_Last).First_Use_Clause);
9798 end if;
9800 -- If the call is from within a compilation unit, as when called from
9801 -- Rtsfind, make current entries in scope stack invisible while we
9802 -- analyze the new unit.
9804 for J in reverse 0 .. SS_Last loop
9805 exit when Scope_Stack.Table (J).Entity = Standard_Standard
9806 or else No (Scope_Stack.Table (J).Entity);
9808 S := Scope_Stack.Table (J).Entity;
9810 Remove_From_Visibility (S);
9812 E := First_Entity (S);
9813 while Present (E) loop
9814 Remove_From_Visibility (E);
9815 Next_Entity (E);
9816 end loop;
9817 end loop;
9819 end if;
9821 return Result;
9822 end Save_Scope_Stack;
9824 -------------
9825 -- Set_Use --
9826 -------------
9828 procedure Set_Use (L : List_Id) is
9829 Decl : Node_Id;
9831 begin
9832 Decl := First (L);
9833 while Present (Decl) loop
9834 if Nkind (Decl) = N_Use_Package_Clause then
9835 Chain_Use_Clause (Decl);
9836 Use_One_Package (Decl, Name (Decl));
9838 elsif Nkind (Decl) = N_Use_Type_Clause then
9839 Chain_Use_Clause (Decl);
9840 Use_One_Type (Subtype_Mark (Decl));
9842 end if;
9844 Next (Decl);
9845 end loop;
9846 end Set_Use;
9848 -----------------------------
9849 -- Update_Use_Clause_Chain --
9850 -----------------------------
9852 procedure Update_Use_Clause_Chain is
9854 procedure Update_Chain_In_Scope (Level : Int);
9855 -- Iterate through one level in the scope stack verifying each use-type
9856 -- clause within said level is used then reset the Current_Use_Clause
9857 -- to a redundant use clause outside of the current ending scope if such
9858 -- a clause exists.
9860 ---------------------------
9861 -- Update_Chain_In_Scope --
9862 ---------------------------
9864 procedure Update_Chain_In_Scope (Level : Int) is
9865 Curr : Node_Id;
9866 N : Node_Id;
9868 begin
9869 -- Loop through all use clauses within the scope dictated by Level
9871 Curr := Scope_Stack.Table (Level).First_Use_Clause;
9872 while Present (Curr) loop
9874 -- Retrieve the subtype mark or name within the current current
9875 -- use clause.
9877 if Nkind (Curr) = N_Use_Type_Clause then
9878 N := Subtype_Mark (Curr);
9879 else
9880 N := Name (Curr);
9881 end if;
9883 -- If warnings for unreferenced entities are enabled and the
9884 -- current use clause has not been marked effective.
9886 if Check_Unreferenced
9887 and then Comes_From_Source (Curr)
9888 and then not Is_Effective_Use_Clause (Curr)
9889 and then not In_Instance
9890 and then not In_Inlined_Body
9891 then
9892 -- We are dealing with a potentially unused use_package_clause
9894 if Nkind (Curr) = N_Use_Package_Clause then
9896 -- Renamings and formal subprograms may cause the associated
9897 -- node to be marked as effective instead of the original.
9899 if not (Present (Associated_Node (N))
9900 and then Present
9901 (Current_Use_Clause
9902 (Associated_Node (N)))
9903 and then Is_Effective_Use_Clause
9904 (Current_Use_Clause
9905 (Associated_Node (N))))
9906 then
9907 Error_Msg_Node_1 := Entity (N);
9908 Error_Msg_NE
9909 ("use clause for package & has no effect?u?",
9910 Curr, Entity (N));
9911 end if;
9913 -- We are dealing with an unused use_type_clause
9915 else
9916 Error_Msg_Node_1 := Etype (N);
9917 Error_Msg_NE
9918 ("use clause for } has no effect?u?", Curr, Etype (N));
9919 end if;
9920 end if;
9922 -- Verify that we haven't already processed a redundant
9923 -- use_type_clause within the same scope before we move the
9924 -- current use clause up to a previous one for type T.
9926 if Present (Prev_Use_Clause (Curr)) then
9927 Set_Current_Use_Clause (Entity (N), Prev_Use_Clause (Curr));
9928 end if;
9930 Next_Use_Clause (Curr);
9931 end loop;
9932 end Update_Chain_In_Scope;
9934 -- Start of processing for Update_Use_Clause_Chain
9936 begin
9937 Update_Chain_In_Scope (Scope_Stack.Last);
9939 -- Deal with use clauses within the context area if the current
9940 -- scope is a compilation unit.
9942 if Is_Compilation_Unit (Current_Scope)
9943 and then Sloc (Scope_Stack.Table
9944 (Scope_Stack.Last - 1).Entity) = Standard_Location
9945 then
9946 Update_Chain_In_Scope (Scope_Stack.Last - 1);
9947 end if;
9948 end Update_Use_Clause_Chain;
9950 ---------------------
9951 -- Use_One_Package --
9952 ---------------------
9954 procedure Use_One_Package
9955 (N : Node_Id;
9956 Pack_Name : Entity_Id := Empty;
9957 Force : Boolean := False)
9959 procedure Note_Redundant_Use (Clause : Node_Id);
9960 -- Mark the name in a use clause as redundant if the corresponding
9961 -- entity is already use-visible. Emit a warning if the use clause comes
9962 -- from source and the proper warnings are enabled.
9964 ------------------------
9965 -- Note_Redundant_Use --
9966 ------------------------
9968 procedure Note_Redundant_Use (Clause : Node_Id) is
9969 Decl : constant Node_Id := Parent (Clause);
9970 Pack_Name : constant Entity_Id := Entity (Clause);
9972 Cur_Use : Node_Id := Current_Use_Clause (Pack_Name);
9973 Prev_Use : Node_Id := Empty;
9974 Redundant : Node_Id := Empty;
9975 -- The Use_Clause which is actually redundant. In the simplest case
9976 -- it is Pack itself, but when we compile a body we install its
9977 -- context before that of its spec, in which case it is the
9978 -- use_clause in the spec that will appear to be redundant, and we
9979 -- want the warning to be placed on the body. Similar complications
9980 -- appear when the redundancy is between a child unit and one of its
9981 -- ancestors.
9983 begin
9984 -- Could be renamed...
9986 if No (Cur_Use) then
9987 Cur_Use := Current_Use_Clause (Renamed_Entity (Pack_Name));
9988 end if;
9990 Set_Redundant_Use (Clause, True);
9992 -- Do not check for redundant use if clause is generated, or in an
9993 -- instance, or in a predefined unit to avoid misleading warnings
9994 -- that may occur as part of a rtsfind load.
9996 if not Comes_From_Source (Clause)
9997 or else In_Instance
9998 or else not Warn_On_Redundant_Constructs
9999 or else Is_Predefined_Unit (Current_Sem_Unit)
10000 then
10001 return;
10002 end if;
10004 if not Is_Compilation_Unit (Current_Scope) then
10006 -- If the use_clause is in an inner scope, it is made redundant by
10007 -- some clause in the current context, with one exception: If we
10008 -- are compiling a nested package body, and the use_clause comes
10009 -- from then corresponding spec, the clause is not necessarily
10010 -- fully redundant, so we should not warn. If a warning was
10011 -- warranted, it would have been given when the spec was
10012 -- processed.
10014 if Nkind (Parent (Decl)) = N_Package_Specification then
10015 declare
10016 Package_Spec_Entity : constant Entity_Id :=
10017 Defining_Unit_Name (Parent (Decl));
10018 begin
10019 if In_Package_Body (Package_Spec_Entity) then
10020 return;
10021 end if;
10022 end;
10023 end if;
10025 Redundant := Clause;
10026 Prev_Use := Cur_Use;
10028 elsif Nkind (Unit (Cunit (Current_Sem_Unit))) = N_Package_Body then
10029 declare
10030 Cur_Unit : constant Unit_Number_Type :=
10031 Get_Source_Unit (Cur_Use);
10032 New_Unit : constant Unit_Number_Type :=
10033 Get_Source_Unit (Clause);
10035 Scop : Entity_Id;
10037 begin
10038 if Cur_Unit = New_Unit then
10040 -- Redundant clause in same body
10042 Redundant := Clause;
10043 Prev_Use := Cur_Use;
10045 elsif Cur_Unit = Current_Sem_Unit then
10047 -- If the new clause is not in the current unit it has been
10048 -- analyzed first, and it makes the other one redundant.
10049 -- However, if the new clause appears in a subunit, Cur_Unit
10050 -- is still the parent, and in that case the redundant one
10051 -- is the one appearing in the subunit.
10053 if Nkind (Unit (Cunit (New_Unit))) = N_Subunit then
10054 Redundant := Clause;
10055 Prev_Use := Cur_Use;
10057 -- Most common case: redundant clause in body, original
10058 -- clause in spec. Current scope is spec entity.
10060 elsif Current_Scope = Cunit_Entity (Current_Sem_Unit) then
10061 Redundant := Cur_Use;
10062 Prev_Use := Clause;
10064 else
10065 -- The new clause may appear in an unrelated unit, when
10066 -- the parents of a generic are being installed prior to
10067 -- instantiation. In this case there must be no warning.
10068 -- We detect this case by checking whether the current
10069 -- top of the stack is related to the current
10070 -- compilation.
10072 Scop := Current_Scope;
10073 while Present (Scop)
10074 and then Scop /= Standard_Standard
10075 loop
10076 if Is_Compilation_Unit (Scop)
10077 and then not Is_Child_Unit (Scop)
10078 then
10079 return;
10081 elsif Scop = Cunit_Entity (Current_Sem_Unit) then
10082 exit;
10083 end if;
10085 Scop := Scope (Scop);
10086 end loop;
10088 Redundant := Cur_Use;
10089 Prev_Use := Clause;
10090 end if;
10092 elsif New_Unit = Current_Sem_Unit then
10093 Redundant := Clause;
10094 Prev_Use := Cur_Use;
10096 else
10097 -- Neither is the current unit, so they appear in parent or
10098 -- sibling units. Warning will be emitted elsewhere.
10100 return;
10101 end if;
10102 end;
10104 elsif Nkind (Unit (Cunit (Current_Sem_Unit))) = N_Package_Declaration
10105 and then Present (Parent_Spec (Unit (Cunit (Current_Sem_Unit))))
10106 then
10107 -- Use_clause is in child unit of current unit, and the child unit
10108 -- appears in the context of the body of the parent, so it has
10109 -- been installed first, even though it is the redundant one.
10110 -- Depending on their placement in the context, the visible or the
10111 -- private parts of the two units, either might appear as
10112 -- redundant, but the message has to be on the current unit.
10114 if Get_Source_Unit (Cur_Use) = Current_Sem_Unit then
10115 Redundant := Cur_Use;
10116 Prev_Use := Clause;
10117 else
10118 Redundant := Clause;
10119 Prev_Use := Cur_Use;
10120 end if;
10122 -- If the new use clause appears in the private part of a parent
10123 -- unit it may appear to be redundant w.r.t. a use clause in a
10124 -- child unit, but the previous use clause was needed in the
10125 -- visible part of the child, and no warning should be emitted.
10127 if Nkind (Parent (Decl)) = N_Package_Specification
10128 and then List_Containing (Decl) =
10129 Private_Declarations (Parent (Decl))
10130 then
10131 declare
10132 Par : constant Entity_Id :=
10133 Defining_Entity (Parent (Decl));
10134 Spec : constant Node_Id :=
10135 Specification (Unit (Cunit (Current_Sem_Unit)));
10136 Cur_List : constant List_Id := List_Containing (Cur_Use);
10138 begin
10139 if Is_Compilation_Unit (Par)
10140 and then Par /= Cunit_Entity (Current_Sem_Unit)
10141 then
10142 if Cur_List = Context_Items (Cunit (Current_Sem_Unit))
10143 or else Cur_List = Visible_Declarations (Spec)
10144 then
10145 return;
10146 end if;
10147 end if;
10148 end;
10149 end if;
10151 -- Finally, if the current use clause is in the context then the
10152 -- clause is redundant when it is nested within the unit.
10154 elsif Nkind (Parent (Cur_Use)) = N_Compilation_Unit
10155 and then Nkind (Parent (Parent (Clause))) /= N_Compilation_Unit
10156 and then Get_Source_Unit (Cur_Use) = Get_Source_Unit (Clause)
10157 then
10158 Redundant := Clause;
10159 Prev_Use := Cur_Use;
10160 end if;
10162 if Present (Redundant) and then Parent (Redundant) /= Prev_Use then
10164 -- Make sure we are looking at most-descendant use_package_clause
10165 -- by traversing the chain with Find_First_Use and then verifying
10166 -- there is no scope manipulation via Most_Descendant_Use_Clause.
10168 if Nkind (Prev_Use) = N_Use_Package_Clause
10169 and then
10170 (Nkind (Parent (Prev_Use)) /= N_Compilation_Unit
10171 or else Most_Descendant_Use_Clause
10172 (Prev_Use, Find_First_Use (Prev_Use)) /= Prev_Use)
10173 then
10174 Prev_Use := Find_First_Use (Prev_Use);
10175 end if;
10177 Error_Msg_Sloc := Sloc (Prev_Use);
10178 Error_Msg_NE -- CODEFIX
10179 ("& is already use-visible through previous use_clause #?r?",
10180 Redundant, Pack_Name);
10181 end if;
10182 end Note_Redundant_Use;
10184 -- Local variables
10186 Current_Instance : Entity_Id := Empty;
10187 Id : Entity_Id;
10188 P : Entity_Id;
10189 Prev : Entity_Id;
10190 Private_With_OK : Boolean := False;
10191 Real_P : Entity_Id;
10193 -- Start of processing for Use_One_Package
10195 begin
10196 -- Use_One_Package may have been called recursively to handle an
10197 -- implicit use for a auxiliary system package, so set P accordingly
10198 -- and skip redundancy checks.
10200 if No (Pack_Name) and then Present_System_Aux (N) then
10201 P := System_Aux_Id;
10203 -- Check for redundant use_package_clauses
10205 else
10206 -- Ignore cases where we are dealing with a non user defined package
10207 -- like Standard_Standard or something other than a valid package.
10209 if not Is_Entity_Name (Pack_Name)
10210 or else No (Entity (Pack_Name))
10211 or else Ekind (Entity (Pack_Name)) /= E_Package
10212 then
10213 return;
10214 end if;
10216 -- When a renaming exists we must check it for redundancy. The
10217 -- original package would have already been seen at this point.
10219 if Present (Renamed_Entity (Entity (Pack_Name))) then
10220 P := Renamed_Entity (Entity (Pack_Name));
10221 else
10222 P := Entity (Pack_Name);
10223 end if;
10225 -- Check for redundant clauses then set the current use clause for
10226 -- P if were are not "forcing" an installation from a scope
10227 -- reinstallation that is done throughout analysis for various
10228 -- reasons.
10230 if In_Use (P) then
10231 Note_Redundant_Use (Pack_Name);
10233 if not Force then
10234 Set_Current_Use_Clause (P, N);
10235 end if;
10237 return;
10239 -- Warn about detected redundant clauses
10241 elsif not Force
10242 and then In_Open_Scopes (P)
10243 and then not Is_Hidden_Open_Scope (P)
10244 then
10245 if Warn_On_Redundant_Constructs and then P = Current_Scope then
10246 Error_Msg_NE -- CODEFIX
10247 ("& is already use-visible within itself?r?",
10248 Pack_Name, P);
10249 end if;
10251 return;
10252 end if;
10254 -- Set P back to the non-renamed package so that visibility of the
10255 -- entities within the package can be properly set below.
10257 P := Entity (Pack_Name);
10258 end if;
10260 Set_In_Use (P);
10261 Set_Current_Use_Clause (P, N);
10263 -- Ada 2005 (AI-50217): Check restriction
10265 if From_Limited_With (P) then
10266 Error_Msg_N ("limited withed package cannot appear in use clause", N);
10267 end if;
10269 -- Find enclosing instance, if any
10271 if In_Instance then
10272 Current_Instance := Current_Scope;
10273 while not Is_Generic_Instance (Current_Instance) loop
10274 Current_Instance := Scope (Current_Instance);
10275 end loop;
10277 if No (Hidden_By_Use_Clause (N)) then
10278 Set_Hidden_By_Use_Clause (N, New_Elmt_List);
10279 end if;
10280 end if;
10282 -- If unit is a package renaming, indicate that the renamed package is
10283 -- also in use (the flags on both entities must remain consistent, and a
10284 -- subsequent use of either of them should be recognized as redundant).
10286 if Present (Renamed_Entity (P)) then
10287 Set_In_Use (Renamed_Entity (P));
10288 Set_Current_Use_Clause (Renamed_Entity (P), N);
10289 Real_P := Renamed_Entity (P);
10290 else
10291 Real_P := P;
10292 end if;
10294 -- Ada 2005 (AI-262): Check the use_clause of a private withed package
10295 -- found in the private part of a package specification
10297 if In_Private_Part (Current_Scope)
10298 and then Has_Private_With (P)
10299 and then Is_Child_Unit (Current_Scope)
10300 and then Is_Child_Unit (P)
10301 and then Is_Ancestor_Package (Scope (Current_Scope), P)
10302 then
10303 Private_With_OK := True;
10304 end if;
10306 -- Loop through entities in one package making them potentially
10307 -- use-visible.
10309 Id := First_Entity (P);
10310 while Present (Id)
10311 and then (Id /= First_Private_Entity (P)
10312 or else Private_With_OK) -- Ada 2005 (AI-262)
10313 loop
10314 Prev := Current_Entity (Id);
10315 while Present (Prev) loop
10316 if Is_Immediately_Visible (Prev)
10317 and then (not Is_Overloadable (Prev)
10318 or else not Is_Overloadable (Id)
10319 or else (Type_Conformant (Id, Prev)))
10320 then
10321 if No (Current_Instance) then
10323 -- Potentially use-visible entity remains hidden
10325 if Warn_On_Hiding then
10326 Warn_On_Hiding_Entity (N, Hidden => Id, Visible => Prev,
10327 On_Use_Clause => True);
10328 end if;
10330 goto Next_Usable_Entity;
10332 -- A use clause within an instance hides outer global entities,
10333 -- which are not used to resolve local entities in the
10334 -- instance. Note that the predefined entities in Standard
10335 -- could not have been hidden in the generic by a use clause,
10336 -- and therefore remain visible. Other compilation units whose
10337 -- entities appear in Standard must be hidden in an instance.
10339 -- To determine whether an entity is external to the instance
10340 -- we compare the scope depth of its scope with that of the
10341 -- current instance. However, a generic actual of a subprogram
10342 -- instance is declared in the wrapper package but will not be
10343 -- hidden by a use-visible entity. similarly, an entity that is
10344 -- declared in an enclosing instance will not be hidden by an
10345 -- an entity declared in a generic actual, which can only have
10346 -- been use-visible in the generic and will not have hidden the
10347 -- entity in the generic parent.
10349 -- If Id is called Standard, the predefined package with the
10350 -- same name is in the homonym chain. It has to be ignored
10351 -- because it has no defined scope (being the only entity in
10352 -- the system with this mandated behavior).
10354 elsif not Is_Hidden (Id)
10355 and then Present (Scope (Prev))
10356 and then not Is_Wrapper_Package (Scope (Prev))
10357 and then Scope_Depth (Scope (Prev)) <
10358 Scope_Depth (Current_Instance)
10359 and then (Scope (Prev) /= Standard_Standard
10360 or else Sloc (Prev) > Standard_Location)
10361 then
10362 if In_Open_Scopes (Scope (Prev))
10363 and then Is_Generic_Instance (Scope (Prev))
10364 and then Present (Associated_Formal_Package (P))
10365 then
10366 null;
10368 else
10369 Set_Is_Potentially_Use_Visible (Id);
10370 Set_Is_Immediately_Visible (Prev, False);
10371 Append_Elmt (Prev, Hidden_By_Use_Clause (N));
10372 end if;
10373 end if;
10375 -- A user-defined operator is not use-visible if the predefined
10376 -- operator for the type is immediately visible, which is the case
10377 -- if the type of the operand is in an open scope. This does not
10378 -- apply to user-defined operators that have operands of different
10379 -- types, because the predefined mixed mode operations (multiply
10380 -- and divide) apply to universal types and do not hide anything.
10382 elsif Ekind (Prev) = E_Operator
10383 and then Operator_Matches_Spec (Prev, Id)
10384 and then In_Open_Scopes
10385 (Scope (Base_Type (Etype (First_Formal (Id)))))
10386 and then (No (Next_Formal (First_Formal (Id)))
10387 or else Etype (First_Formal (Id)) =
10388 Etype (Next_Formal (First_Formal (Id)))
10389 or else Chars (Prev) = Name_Op_Expon)
10390 then
10391 goto Next_Usable_Entity;
10393 -- In an instance, two homonyms may become use_visible through the
10394 -- actuals of distinct formal packages. In the generic, only the
10395 -- current one would have been visible, so make the other one
10396 -- not use_visible.
10398 -- In certain pathological cases it is possible that unrelated
10399 -- homonyms from distinct formal packages may exist in an
10400 -- uninstalled scope. We must test for that here.
10402 elsif Present (Current_Instance)
10403 and then Is_Potentially_Use_Visible (Prev)
10404 and then not Is_Overloadable (Prev)
10405 and then Scope (Id) /= Scope (Prev)
10406 and then Used_As_Generic_Actual (Scope (Prev))
10407 and then Used_As_Generic_Actual (Scope (Id))
10408 and then Is_List_Member (Scope (Prev))
10409 and then not In_Same_List (Current_Use_Clause (Scope (Prev)),
10410 Current_Use_Clause (Scope (Id)))
10411 then
10412 Set_Is_Potentially_Use_Visible (Prev, False);
10413 Append_Elmt (Prev, Hidden_By_Use_Clause (N));
10414 end if;
10416 Prev := Homonym (Prev);
10417 end loop;
10419 -- On exit, we know entity is not hidden, unless it is private
10421 if not Is_Hidden (Id)
10422 and then ((not Is_Child_Unit (Id)) or else Is_Visible_Lib_Unit (Id))
10423 then
10424 Set_Is_Potentially_Use_Visible (Id);
10426 if Is_Private_Type (Id) and then Present (Full_View (Id)) then
10427 Set_Is_Potentially_Use_Visible (Full_View (Id));
10428 end if;
10429 end if;
10431 <<Next_Usable_Entity>>
10432 Next_Entity (Id);
10433 end loop;
10435 -- Child units are also made use-visible by a use clause, but they may
10436 -- appear after all visible declarations in the parent entity list.
10438 while Present (Id) loop
10439 if Is_Child_Unit (Id) and then Is_Visible_Lib_Unit (Id) then
10440 Set_Is_Potentially_Use_Visible (Id);
10441 end if;
10443 Next_Entity (Id);
10444 end loop;
10446 if Chars (Real_P) = Name_System
10447 and then Scope (Real_P) = Standard_Standard
10448 and then Present_System_Aux (N)
10449 then
10450 Use_One_Package (N);
10451 end if;
10452 end Use_One_Package;
10454 ------------------
10455 -- Use_One_Type --
10456 ------------------
10458 procedure Use_One_Type
10459 (Id : Node_Id;
10460 Installed : Boolean := False;
10461 Force : Boolean := False)
10463 function Spec_Reloaded_For_Body return Boolean;
10464 -- Determine whether the compilation unit is a package body and the use
10465 -- type clause is in the spec of the same package. Even though the spec
10466 -- was analyzed first, its context is reloaded when analysing the body.
10468 procedure Use_Class_Wide_Operations (Typ : Entity_Id);
10469 -- AI05-150: if the use_type_clause carries the "all" qualifier,
10470 -- class-wide operations of ancestor types are use-visible if the
10471 -- ancestor type is visible.
10473 ----------------------------
10474 -- Spec_Reloaded_For_Body --
10475 ----------------------------
10477 function Spec_Reloaded_For_Body return Boolean is
10478 begin
10479 if Nkind (Unit (Cunit (Current_Sem_Unit))) = N_Package_Body then
10480 declare
10481 Spec : constant Node_Id :=
10482 Parent (List_Containing (Parent (Id)));
10484 begin
10485 -- Check whether type is declared in a package specification,
10486 -- and current unit is the corresponding package body. The
10487 -- use clauses themselves may be within a nested package.
10489 return
10490 Nkind (Spec) = N_Package_Specification
10491 and then In_Same_Source_Unit
10492 (Corresponding_Body (Parent (Spec)),
10493 Cunit_Entity (Current_Sem_Unit));
10494 end;
10495 end if;
10497 return False;
10498 end Spec_Reloaded_For_Body;
10500 -------------------------------
10501 -- Use_Class_Wide_Operations --
10502 -------------------------------
10504 procedure Use_Class_Wide_Operations (Typ : Entity_Id) is
10505 function Is_Class_Wide_Operation_Of
10506 (Op : Entity_Id;
10507 T : Entity_Id) return Boolean;
10508 -- Determine whether a subprogram has a class-wide parameter or
10509 -- result that is T'Class.
10511 ---------------------------------
10512 -- Is_Class_Wide_Operation_Of --
10513 ---------------------------------
10515 function Is_Class_Wide_Operation_Of
10516 (Op : Entity_Id;
10517 T : Entity_Id) return Boolean
10519 Formal : Entity_Id;
10521 begin
10522 Formal := First_Formal (Op);
10523 while Present (Formal) loop
10524 if Etype (Formal) = Class_Wide_Type (T) then
10525 return True;
10526 end if;
10528 Next_Formal (Formal);
10529 end loop;
10531 if Etype (Op) = Class_Wide_Type (T) then
10532 return True;
10533 end if;
10535 return False;
10536 end Is_Class_Wide_Operation_Of;
10538 -- Local variables
10540 Ent : Entity_Id;
10541 Scop : Entity_Id;
10543 -- Start of processing for Use_Class_Wide_Operations
10545 begin
10546 Scop := Scope (Typ);
10547 if not Is_Hidden (Scop) then
10548 Ent := First_Entity (Scop);
10549 while Present (Ent) loop
10550 if Is_Overloadable (Ent)
10551 and then Is_Class_Wide_Operation_Of (Ent, Typ)
10552 and then not Is_Potentially_Use_Visible (Ent)
10553 then
10554 Set_Is_Potentially_Use_Visible (Ent);
10555 Append_Elmt (Ent, Used_Operations (Parent (Id)));
10556 end if;
10558 Next_Entity (Ent);
10559 end loop;
10560 end if;
10562 if Is_Derived_Type (Typ) then
10563 Use_Class_Wide_Operations (Etype (Base_Type (Typ)));
10564 end if;
10565 end Use_Class_Wide_Operations;
10567 -- Local variables
10569 Elmt : Elmt_Id;
10570 Is_Known_Used : Boolean;
10571 Op_List : Elist_Id;
10572 T : Entity_Id;
10574 -- Start of processing for Use_One_Type
10576 begin
10577 if Entity (Id) = Any_Type then
10578 return;
10579 end if;
10581 -- It is the type determined by the subtype mark (8.4(8)) whose
10582 -- operations become potentially use-visible.
10584 T := Base_Type (Entity (Id));
10586 -- Either the type itself is used, the package where it is declared is
10587 -- in use or the entity is declared in the current package, thus
10588 -- use-visible.
10590 Is_Known_Used :=
10591 (In_Use (T)
10592 and then ((Present (Current_Use_Clause (T))
10593 and then All_Present (Current_Use_Clause (T)))
10594 or else not All_Present (Parent (Id))))
10595 or else In_Use (Scope (T))
10596 or else Scope (T) = Current_Scope;
10598 Set_Redundant_Use (Id,
10599 Is_Known_Used or else Is_Potentially_Use_Visible (T));
10601 if Ekind (T) = E_Incomplete_Type then
10602 Error_Msg_N ("premature usage of incomplete type", Id);
10604 elsif In_Open_Scopes (Scope (T)) then
10605 null;
10607 -- A limited view cannot appear in a use_type_clause. However, an access
10608 -- type whose designated type is limited has the flag but is not itself
10609 -- a limited view unless we only have a limited view of its enclosing
10610 -- package.
10612 elsif From_Limited_With (T) and then From_Limited_With (Scope (T)) then
10613 Error_Msg_N
10614 ("incomplete type from limited view cannot appear in use clause",
10615 Id);
10617 -- If the use clause is redundant, Used_Operations will usually be
10618 -- empty, but we need to set it to empty here in one case: If we are
10619 -- instantiating a generic library unit, then we install the ancestors
10620 -- of that unit in the scope stack, which involves reprocessing use
10621 -- clauses in those ancestors. Such a use clause will typically have a
10622 -- nonempty Used_Operations unless it was redundant in the generic unit,
10623 -- even if it is redundant at the place of the instantiation.
10625 elsif Redundant_Use (Id) then
10626 Set_Used_Operations (Parent (Id), New_Elmt_List);
10628 -- If the subtype mark designates a subtype in a different package,
10629 -- we have to check that the parent type is visible, otherwise the
10630 -- use_type_clause is a no-op. Not clear how to do that???
10632 else
10633 Set_Current_Use_Clause (T, Parent (Id));
10634 Set_In_Use (T);
10636 -- If T is tagged, primitive operators on class-wide operands are
10637 -- also deemed available. Note that this is really necessary only
10638 -- in semantics-only mode, because the primitive operators are not
10639 -- fully constructed in this mode, but we do it in all modes for the
10640 -- sake of uniformity, as this should not matter in practice.
10642 if Is_Tagged_Type (T) then
10643 Set_In_Use (Class_Wide_Type (T));
10644 end if;
10646 -- Iterate over primitive operations of the type. If an operation is
10647 -- already use_visible, it is the result of a previous use_clause,
10648 -- and already appears on the corresponding entity chain. If the
10649 -- clause is being reinstalled, operations are already use-visible.
10651 if Installed then
10652 null;
10654 else
10655 Op_List := Collect_Primitive_Operations (T);
10656 Elmt := First_Elmt (Op_List);
10657 while Present (Elmt) loop
10658 if (Nkind (Node (Elmt)) = N_Defining_Operator_Symbol
10659 or else Chars (Node (Elmt)) in Any_Operator_Name)
10660 and then not Is_Hidden (Node (Elmt))
10661 and then not Is_Potentially_Use_Visible (Node (Elmt))
10662 then
10663 Set_Is_Potentially_Use_Visible (Node (Elmt));
10664 Append_Elmt (Node (Elmt), Used_Operations (Parent (Id)));
10666 elsif Ada_Version >= Ada_2012
10667 and then All_Present (Parent (Id))
10668 and then not Is_Hidden (Node (Elmt))
10669 and then not Is_Potentially_Use_Visible (Node (Elmt))
10670 then
10671 Set_Is_Potentially_Use_Visible (Node (Elmt));
10672 Append_Elmt (Node (Elmt), Used_Operations (Parent (Id)));
10673 end if;
10675 Next_Elmt (Elmt);
10676 end loop;
10677 end if;
10679 if Ada_Version >= Ada_2012
10680 and then All_Present (Parent (Id))
10681 and then Is_Tagged_Type (T)
10682 then
10683 Use_Class_Wide_Operations (T);
10684 end if;
10685 end if;
10687 -- If warning on redundant constructs, check for unnecessary WITH
10689 if not Force
10690 and then Warn_On_Redundant_Constructs
10691 and then Is_Known_Used
10693 -- with P; with P; use P;
10694 -- package P is package X is package body X is
10695 -- type T ... use P.T;
10697 -- The compilation unit is the body of X. GNAT first compiles the
10698 -- spec of X, then proceeds to the body. At that point P is marked
10699 -- as use visible. The analysis then reinstalls the spec along with
10700 -- its context. The use clause P.T is now recognized as redundant,
10701 -- but in the wrong context. Do not emit a warning in such cases.
10702 -- Do not emit a warning either if we are in an instance, there is
10703 -- no redundancy between an outer use_clause and one that appears
10704 -- within the generic.
10706 and then not Spec_Reloaded_For_Body
10707 and then not In_Instance
10708 and then not In_Inlined_Body
10709 then
10710 -- The type already has a use clause
10712 if In_Use (T) then
10714 -- Case where we know the current use clause for the type
10716 if Present (Current_Use_Clause (T)) then
10717 Use_Clause_Known : declare
10718 Clause1 : constant Node_Id :=
10719 Find_First_Use (Current_Use_Clause (T));
10720 Clause2 : constant Node_Id := Parent (Id);
10721 Ent1 : Entity_Id;
10722 Ent2 : Entity_Id;
10723 Err_No : Node_Id;
10724 Unit1 : Node_Id;
10725 Unit2 : Node_Id;
10727 -- Start of processing for Use_Clause_Known
10729 begin
10730 -- If the unit is a subprogram body that acts as spec, the
10731 -- context clause is shared with the constructed subprogram
10732 -- spec. Clearly there is no redundancy.
10734 if Clause1 = Clause2 then
10735 return;
10736 end if;
10738 Unit1 := Unit (Enclosing_Comp_Unit_Node (Clause1));
10739 Unit2 := Unit (Enclosing_Comp_Unit_Node (Clause2));
10741 -- If both clauses are on same unit, or one is the body of
10742 -- the other, or one of them is in a subunit, report
10743 -- redundancy on the later one.
10745 if Unit1 = Unit2
10746 or else Nkind (Unit1) = N_Subunit
10747 or else
10748 (Nkind (Unit2) in N_Package_Body | N_Subprogram_Body
10749 and then Nkind (Unit1) /= Nkind (Unit2)
10750 and then Nkind (Unit1) /= N_Subunit)
10751 then
10752 Error_Msg_Sloc := Sloc (Clause1);
10753 Error_Msg_NE -- CODEFIX
10754 ("& is already use-visible through previous "
10755 & "use_type_clause #??", Clause2, T);
10756 return;
10757 end if;
10759 -- If there is a redundant use_type_clause in a child unit
10760 -- determine which of the units is more deeply nested. If a
10761 -- unit is a package instance, retrieve the entity and its
10762 -- scope from the instance spec.
10764 Ent1 := Entity_Of_Unit (Unit1);
10765 Ent2 := Entity_Of_Unit (Unit2);
10767 -- When the scope of both units' entities are
10768 -- Standard_Standard then neither Unit1 or Unit2 are child
10769 -- units - so return in that case.
10771 if Scope (Ent1) = Standard_Standard
10772 and then Scope (Ent2) = Standard_Standard
10773 then
10774 return;
10776 -- Otherwise, determine if one of the units is not a child
10778 elsif Scope (Ent2) = Standard_Standard then
10779 Error_Msg_Sloc := Sloc (Clause2);
10780 Err_No := Clause1;
10782 elsif Scope (Ent1) = Standard_Standard then
10783 Error_Msg_Sloc := Sloc (Id);
10784 Err_No := Clause2;
10786 -- If both units are child units, we determine which one is
10787 -- the descendant by the scope distance to the ultimate
10788 -- parent unit.
10790 else
10791 declare
10792 S1 : Entity_Id;
10793 S2 : Entity_Id;
10795 begin
10796 S1 := Scope (Ent1);
10797 S2 := Scope (Ent2);
10798 while Present (S1)
10799 and then Present (S2)
10800 and then S1 /= Standard_Standard
10801 and then S2 /= Standard_Standard
10802 loop
10803 S1 := Scope (S1);
10804 S2 := Scope (S2);
10805 end loop;
10807 if S1 = Standard_Standard then
10808 Error_Msg_Sloc := Sloc (Id);
10809 Err_No := Clause2;
10810 else
10811 Error_Msg_Sloc := Sloc (Clause2);
10812 Err_No := Clause1;
10813 end if;
10814 end;
10815 end if;
10817 if Parent (Id) /= Err_No then
10818 if Most_Descendant_Use_Clause
10819 (Err_No, Parent (Id)) = Parent (Id)
10820 then
10821 Error_Msg_Sloc := Sloc (Err_No);
10822 Err_No := Parent (Id);
10823 end if;
10825 Error_Msg_NE -- CODEFIX
10826 ("& is already use-visible through previous "
10827 & "use_type_clause #??", Err_No, Id);
10828 end if;
10829 end Use_Clause_Known;
10831 -- Here Current_Use_Clause is not set for T, so we do not have the
10832 -- location information available.
10834 else
10835 Error_Msg_NE -- CODEFIX
10836 ("& is already use-visible through previous "
10837 & "use_type_clause??", Id, T);
10838 end if;
10840 -- The package where T is declared is already used
10842 elsif In_Use (Scope (T)) then
10843 -- Due to expansion of contracts we could be attempting to issue
10844 -- a spurious warning - so verify there is a previous use clause.
10846 if Current_Use_Clause (Scope (T)) /=
10847 Find_First_Use (Current_Use_Clause (Scope (T)))
10848 then
10849 Error_Msg_Sloc :=
10850 Sloc (Find_First_Use (Current_Use_Clause (Scope (T))));
10851 Error_Msg_NE -- CODEFIX
10852 ("& is already use-visible through package use clause #??",
10853 Id, T);
10854 end if;
10856 -- The current scope is the package where T is declared
10858 else
10859 Error_Msg_Node_2 := Scope (T);
10860 Error_Msg_NE -- CODEFIX
10861 ("& is already use-visible inside package &??", Id, T);
10862 end if;
10863 end if;
10864 end Use_One_Type;
10866 ----------------
10867 -- Write_Info --
10868 ----------------
10870 procedure Write_Info is
10871 Id : Entity_Id := First_Entity (Current_Scope);
10873 begin
10874 -- No point in dumping standard entities
10876 if Current_Scope = Standard_Standard then
10877 return;
10878 end if;
10880 Write_Str ("========================================================");
10881 Write_Eol;
10882 Write_Str (" Defined Entities in ");
10883 Write_Name (Chars (Current_Scope));
10884 Write_Eol;
10885 Write_Str ("========================================================");
10886 Write_Eol;
10888 if No (Id) then
10889 Write_Str ("-- none --");
10890 Write_Eol;
10892 else
10893 while Present (Id) loop
10894 Write_Entity_Info (Id, " ");
10895 Next_Entity (Id);
10896 end loop;
10897 end if;
10899 if Scope (Current_Scope) = Standard_Standard then
10901 -- Print information on the current unit itself
10903 Write_Entity_Info (Current_Scope, " ");
10904 end if;
10906 Write_Eol;
10907 end Write_Info;
10909 --------
10910 -- ws --
10911 --------
10913 procedure ws is
10914 S : Entity_Id;
10915 begin
10916 for J in reverse 1 .. Scope_Stack.Last loop
10917 S := Scope_Stack.Table (J).Entity;
10918 Write_Int (Int (S));
10919 Write_Str (" === ");
10920 Write_Name (Chars (S));
10921 Write_Eol;
10922 end loop;
10923 end ws;
10925 --------
10926 -- we --
10927 --------
10929 procedure we (S : Entity_Id) is
10930 E : Entity_Id;
10931 begin
10932 E := First_Entity (S);
10933 while Present (E) loop
10934 Write_Int (Int (E));
10935 Write_Str (" === ");
10936 Write_Name (Chars (E));
10937 Write_Eol;
10938 Next_Entity (E);
10939 end loop;
10940 end we;
10941 end Sem_Ch8;