Merge from mainline (gomp-merge-2005-02-26).
[official-gcc.git] / gcc / ada / sem_ch8.adb
blobf5090e444417776b7499d6098c0b56bde0b362aa
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-2005, 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 2, 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 COPYING. If not, write --
19 -- to the Free Software Foundation, 59 Temple Place - Suite 330, Boston, --
20 -- MA 02111-1307, USA. --
21 -- --
22 -- GNAT was originally developed by the GNAT team at New York University. --
23 -- Extensive contributions were provided by Ada Core Technologies Inc. --
24 -- --
25 ------------------------------------------------------------------------------
27 with Atree; use Atree;
28 with Debug; use Debug;
29 with Einfo; use Einfo;
30 with Elists; use Elists;
31 with Errout; use Errout;
32 with Exp_Util; use Exp_Util;
33 with Fname; use Fname;
34 with Freeze; use Freeze;
35 with Lib; use Lib;
36 with Lib.Load; use Lib.Load;
37 with Lib.Xref; use Lib.Xref;
38 with Namet; use Namet;
39 with Nlists; use Nlists;
40 with Nmake; use Nmake;
41 with Opt; use Opt;
42 with Output; use Output;
43 with Restrict; use Restrict;
44 with Rident; use Rident;
45 with Rtsfind; use Rtsfind;
46 with Sem; use Sem;
47 with Sem_Cat; use Sem_Cat;
48 with Sem_Ch3; use Sem_Ch3;
49 with Sem_Ch4; use Sem_Ch4;
50 with Sem_Ch6; use Sem_Ch6;
51 with Sem_Ch12; use Sem_Ch12;
52 with Sem_Disp; use Sem_Disp;
53 with Sem_Res; use Sem_Res;
54 with Sem_Util; use Sem_Util;
55 with Sem_Type; use Sem_Type;
56 with Stand; use Stand;
57 with Sinfo; use Sinfo;
58 with Sinfo.CN; use Sinfo.CN;
59 with Snames; use Snames;
60 with Style; use Style;
61 with Table;
62 with Tbuild; use Tbuild;
63 with Uintp; use Uintp;
65 with GNAT.Spelling_Checker; use GNAT.Spelling_Checker;
67 package body Sem_Ch8 is
69 ------------------------------------
70 -- Visibility and Name Resolution --
71 ------------------------------------
73 -- This package handles name resolution and the collection of
74 -- interpretations for overloaded names, prior to overload resolution.
76 -- Name resolution is the process that establishes a mapping between source
77 -- identifiers and the entities they denote at each point in the program.
78 -- Each entity is represented by a defining occurrence. Each identifier
79 -- that denotes an entity points to the corresponding defining occurrence.
80 -- This is the entity of the applied occurrence. Each occurrence holds
81 -- an index into the names table, where source identifiers are stored.
83 -- Each entry in the names table for an identifier or designator uses the
84 -- Info pointer to hold a link to the currently visible entity that has
85 -- this name (see subprograms Get_Name_Entity_Id and Set_Name_Entity_Id
86 -- in package Sem_Util). The visibility is initialized at the beginning of
87 -- semantic processing to make entities in package Standard immediately
88 -- visible. The visibility table is used in a more subtle way when
89 -- compiling subunits (see below).
91 -- Entities that have the same name (i.e. homonyms) are chained. In the
92 -- case of overloaded entities, this chain holds all the possible meanings
93 -- of a given identifier. The process of overload resolution uses type
94 -- information to select from this chain the unique meaning of a given
95 -- identifier.
97 -- Entities are also chained in their scope, through the Next_Entity link.
98 -- As a consequence, the name space is organized as a sparse matrix, where
99 -- each row corresponds to a scope, and each column to a source identifier.
100 -- Open scopes, that is to say scopes currently being compiled, have their
101 -- corresponding rows of entities in order, innermost scope first.
103 -- The scopes of packages that are mentioned in context clauses appear in
104 -- no particular order, interspersed among open scopes. This is because
105 -- in the course of analyzing the context of a compilation, a package
106 -- declaration is first an open scope, and subsequently an element of the
107 -- context. If subunits or child units are present, a parent unit may
108 -- appear under various guises at various times in the compilation.
110 -- When the compilation of the innermost scope is complete, the entities
111 -- defined therein are no longer visible. If the scope is not a package
112 -- declaration, these entities are never visible subsequently, and can be
113 -- removed from visibility chains. If the scope is a package declaration,
114 -- its visible declarations may still be accessible. Therefore the entities
115 -- defined in such a scope are left on the visibility chains, and only
116 -- their visibility (immediately visibility or potential use-visibility)
117 -- is affected.
119 -- The ordering of homonyms on their chain does not necessarily follow
120 -- the order of their corresponding scopes on the scope stack. For
121 -- example, if package P and the enclosing scope both contain entities
122 -- named E, then when compiling the package body the chain for E will
123 -- hold the global entity first, and the local one (corresponding to
124 -- the current inner scope) next. As a result, name resolution routines
125 -- do not assume any relative ordering of the homonym chains, either
126 -- for scope nesting or to order of appearance of context clauses.
128 -- When compiling a child unit, entities in the parent scope are always
129 -- immediately visible. When compiling the body of a child unit, private
130 -- entities in the parent must also be made immediately visible. There
131 -- are separate routines to make the visible and private declarations
132 -- visible at various times (see package Sem_Ch7).
134 -- +--------+ +-----+
135 -- | In use |-------->| EU1 |-------------------------->
136 -- +--------+ +-----+
137 -- | |
138 -- +--------+ +-----+ +-----+
139 -- | Stand. |---------------->| ES1 |--------------->| ES2 |--->
140 -- +--------+ +-----+ +-----+
141 -- | |
142 -- +---------+ | +-----+
143 -- | with'ed |------------------------------>| EW2 |--->
144 -- +---------+ | +-----+
145 -- | |
146 -- +--------+ +-----+ +-----+
147 -- | Scope2 |---------------->| E12 |--------------->| E22 |--->
148 -- +--------+ +-----+ +-----+
149 -- | |
150 -- +--------+ +-----+ +-----+
151 -- | Scope1 |---------------->| E11 |--------------->| E12 |--->
152 -- +--------+ +-----+ +-----+
153 -- ^ | |
154 -- | | |
155 -- | +---------+ | |
156 -- | | with'ed |----------------------------------------->
157 -- | +---------+ | |
158 -- | | |
159 -- Scope stack | |
160 -- (innermost first) | |
161 -- +----------------------------+
162 -- Names table => | Id1 | | | | Id2 |
163 -- +----------------------------+
165 -- Name resolution must deal with several syntactic forms: simple names,
166 -- qualified names, indexed names, and various forms of calls.
168 -- Each identifier points to an entry in the names table. The resolution
169 -- of a simple name consists in traversing the homonym chain, starting
170 -- from the names table. If an entry is immediately visible, it is the one
171 -- designated by the identifier. If only potentially use-visible entities
172 -- are on the chain, we must verify that they do not hide each other. If
173 -- the entity we find is overloadable, we collect all other overloadable
174 -- entities on the chain as long as they are not hidden.
176 -- To resolve expanded names, we must find the entity at the intersection
177 -- of the entity chain for the scope (the prefix) and the homonym chain
178 -- for the selector. In general, homonym chains will be much shorter than
179 -- entity chains, so it is preferable to start from the names table as
180 -- well. If the entity found is overloadable, we must collect all other
181 -- interpretations that are defined in the scope denoted by the prefix.
183 -- For records, protected types, and tasks, their local entities are
184 -- removed from visibility chains on exit from the corresponding scope.
185 -- From the outside, these entities are always accessed by selected
186 -- notation, and the entity chain for the record type, protected type,
187 -- etc. is traversed sequentially in order to find the designated entity.
189 -- The discriminants of a type and the operations of a protected type or
190 -- task are unchained on exit from the first view of the type, (such as
191 -- a private or incomplete type declaration, or a protected type speci-
192 -- fication) and re-chained when compiling the second view.
194 -- In the case of operators, we do not make operators on derived types
195 -- explicit. As a result, the notation P."+" may denote either a user-
196 -- defined function with name "+", or else an implicit declaration of the
197 -- operator "+" in package P. The resolution of expanded names always
198 -- tries to resolve an operator name as such an implicitly defined entity,
199 -- in addition to looking for explicit declarations.
201 -- All forms of names that denote entities (simple names, expanded names,
202 -- character literals in some cases) have a Entity attribute, which
203 -- identifies the entity denoted by the name.
205 ---------------------
206 -- The Scope Stack --
207 ---------------------
209 -- The Scope stack keeps track of the scopes currently been compiled.
210 -- Every entity that contains declarations (including records) is placed
211 -- on the scope stack while it is being processed, and removed at the end.
212 -- Whenever a non-package scope is exited, the entities defined therein
213 -- are removed from the visibility table, so that entities in outer scopes
214 -- become visible (see previous description). On entry to Sem, the scope
215 -- stack only contains the package Standard. As usual, subunits complicate
216 -- this picture ever so slightly.
218 -- The Rtsfind mechanism can force a call to Semantics while another
219 -- compilation is in progress. The unit retrieved by Rtsfind must be
220 -- compiled in its own context, and has no access to the visibility of
221 -- the unit currently being compiled. The procedures Save_Scope_Stack and
222 -- Restore_Scope_Stack make entities in current open scopes invisible
223 -- before compiling the retrieved unit, and restore the compilation
224 -- environment afterwards.
226 ------------------------
227 -- Compiling subunits --
228 ------------------------
230 -- Subunits must be compiled in the environment of the corresponding
231 -- stub, that is to say with the same visibility into the parent (and its
232 -- context) that is available at the point of the stub declaration, but
233 -- with the additional visibility provided by the context clause of the
234 -- subunit itself. As a result, compilation of a subunit forces compilation
235 -- of the parent (see description in lib-). At the point of the stub
236 -- declaration, Analyze is called recursively to compile the proper body
237 -- of the subunit, but without reinitializing the names table, nor the
238 -- scope stack (i.e. standard is not pushed on the stack). In this fashion
239 -- the context of the subunit is added to the context of the parent, and
240 -- the subunit is compiled in the correct environment. Note that in the
241 -- course of processing the context of a subunit, Standard will appear
242 -- twice on the scope stack: once for the parent of the subunit, and
243 -- once for the unit in the context clause being compiled. However, the
244 -- two sets of entities are not linked by homonym chains, so that the
245 -- compilation of any context unit happens in a fresh visibility
246 -- environment.
248 -------------------------------
249 -- Processing of USE Clauses --
250 -------------------------------
252 -- Every defining occurrence has a flag indicating if it is potentially use
253 -- visible. Resolution of simple names examines this flag. The processing
254 -- of use clauses consists in setting this flag on all visible entities
255 -- defined in the corresponding package. On exit from the scope of the use
256 -- clause, the corresponding flag must be reset. However, a package may
257 -- appear in several nested use clauses (pathological but legal, alas!)
258 -- which forces us to use a slightly more involved scheme:
260 -- a) The defining occurrence for a package holds a flag -In_Use- to
261 -- indicate that it is currently in the scope of a use clause. If a
262 -- redundant use clause is encountered, then the corresponding occurrence
263 -- of the package name is flagged -Redundant_Use-.
265 -- b) On exit from a scope, the use clauses in its declarative part are
266 -- scanned. The visibility flag is reset in all entities declared in
267 -- package named in a use clause, as long as the package is not flagged
268 -- as being in a redundant use clause (in which case the outer use
269 -- clause is still in effect, and the direct visibility of its entities
270 -- must be retained).
272 -- Note that entities are not removed from their homonym chains on exit
273 -- from the package specification. A subsequent use clause does not need
274 -- to rechain the visible entities, but only to establish their direct
275 -- visibility.
277 -----------------------------------
278 -- Handling private declarations --
279 -----------------------------------
281 -- The principle that each entity has a single defining occurrence clashes
282 -- with the presence of two separate definitions for private types: the
283 -- first is the private type declaration, and second is the full type
284 -- declaration. It is important that all references to the type point to
285 -- the same defining occurrence, namely the first one. To enforce the two
286 -- separate views of the entity, the corresponding information is swapped
287 -- between the two declarations. Outside of the package, the defining
288 -- occurrence only contains the private declaration information, while in
289 -- the private part and the body of the package the defining occurrence
290 -- contains the full declaration. To simplify the swap, the defining
291 -- occurrence that currently holds the private declaration points to the
292 -- full declaration. During semantic processing the defining occurrence
293 -- also points to a list of private dependents, that is to say access
294 -- types or composite types whose designated types or component types are
295 -- subtypes or derived types of the private type in question. After the
296 -- full declaration has been seen, the private dependents are updated to
297 -- indicate that they have full definitions.
299 ------------------------------------
300 -- Handling of Undefined Messages --
301 ------------------------------------
303 -- In normal mode, only the first use of an undefined identifier generates
304 -- a message. The table Urefs is used to record error messages that have
305 -- been issued so that second and subsequent ones do not generate further
306 -- messages. However, the second reference causes text to be added to the
307 -- original undefined message noting "(more references follow)". The
308 -- full error list option (-gnatf) forces messages to be generated for
309 -- every reference and disconnects the use of this table.
311 type Uref_Entry is record
312 Node : Node_Id;
313 -- Node for identifier for which original message was posted. The
314 -- Chars field of this identifier is used to detect later references
315 -- to the same identifier.
317 Err : Error_Msg_Id;
318 -- Records error message Id of original undefined message. Reset to
319 -- No_Error_Msg after the second occurrence, where it is used to add
320 -- text to the original message as described above.
322 Nvis : Boolean;
323 -- Set if the message is not visible rather than undefined
325 Loc : Source_Ptr;
326 -- Records location of error message. Used to make sure that we do
327 -- not consider a, b : undefined as two separate instances, which
328 -- would otherwise happen, since the parser converts this sequence
329 -- to a : undefined; b : undefined.
331 end record;
333 package Urefs is new Table.Table (
334 Table_Component_Type => Uref_Entry,
335 Table_Index_Type => Nat,
336 Table_Low_Bound => 1,
337 Table_Initial => 10,
338 Table_Increment => 100,
339 Table_Name => "Urefs");
341 Candidate_Renaming : Entity_Id;
342 -- Holds a candidate interpretation that appears in a subprogram renaming
343 -- declaration and does not match the given specification, but matches at
344 -- least on the first formal. Allows better error message when given
345 -- specification omits defaulted parameters, a common error.
347 -----------------------
348 -- Local Subprograms --
349 -----------------------
351 procedure Analyze_Generic_Renaming
352 (N : Node_Id;
353 K : Entity_Kind);
354 -- Common processing for all three kinds of generic renaming declarations.
355 -- Enter new name and indicate that it renames the generic unit.
357 procedure Analyze_Renamed_Character
358 (N : Node_Id;
359 New_S : Entity_Id;
360 Is_Body : Boolean);
361 -- Renamed entity is given by a character literal, which must belong
362 -- to the return type of the new entity. Is_Body indicates whether the
363 -- declaration is a renaming_as_body. If the original declaration has
364 -- already been frozen (because of an intervening body, e.g.) the body of
365 -- the function must be built now. The same applies to the following
366 -- various renaming procedures.
368 procedure Analyze_Renamed_Dereference
369 (N : Node_Id;
370 New_S : Entity_Id;
371 Is_Body : Boolean);
372 -- Renamed entity is given by an explicit dereference. Prefix must be a
373 -- conformant access_to_subprogram type.
375 procedure Analyze_Renamed_Entry
376 (N : Node_Id;
377 New_S : Entity_Id;
378 Is_Body : Boolean);
379 -- If the renamed entity in a subprogram renaming is an entry or protected
380 -- subprogram, build a body for the new entity whose only statement is a
381 -- call to the renamed entity.
383 procedure Analyze_Renamed_Family_Member
384 (N : Node_Id;
385 New_S : Entity_Id;
386 Is_Body : Boolean);
387 -- Used when the renamed entity is an indexed component. The prefix must
388 -- denote an entry family.
390 function Applicable_Use (Pack_Name : Node_Id) return Boolean;
391 -- Common code to Use_One_Package and Set_Use, to determine whether
392 -- use clause must be processed. Pack_Name is an entity name that
393 -- references the package in question.
395 procedure Attribute_Renaming (N : Node_Id);
396 -- Analyze renaming of attribute as function. The renaming declaration N
397 -- is rewritten as a function body that returns the attribute reference
398 -- applied to the formals of the function.
400 procedure Check_Frozen_Renaming (N : Node_Id; Subp : Entity_Id);
401 -- A renaming_as_body may occur after the entity of the original decla-
402 -- ration has been frozen. In that case, the body of the new entity must
403 -- be built now, because the usual mechanism of building the renamed
404 -- body at the point of freezing will not work. Subp is the subprogram
405 -- for which N provides the Renaming_As_Body.
407 procedure Check_In_Previous_With_Clause
408 (N : Node_Id;
409 Nam : Node_Id);
410 -- N is a use_package clause and Nam the package name, or N is a use_type
411 -- clause and Nam is the prefix of the type name. In either case, verify
412 -- that the package is visible at that point in the context: either it
413 -- appears in a previous with_clause, or because it is a fully qualified
414 -- name and the root ancestor appears in a previous with_clause.
416 procedure Check_Library_Unit_Renaming (N : Node_Id; Old_E : Entity_Id);
417 -- Verify that the entity in a renaming declaration that is a library unit
418 -- is itself a library unit and not a nested unit or subunit. Also check
419 -- that if the renaming is a child unit of a generic parent, then the
420 -- renamed unit must also be a child unit of that parent. Finally, verify
421 -- that a renamed generic unit is not an implicit child declared within
422 -- an instance of the parent.
424 procedure Chain_Use_Clause (N : Node_Id);
425 -- Chain use clause onto list of uses clauses headed by First_Use_Clause
426 -- in the top scope table entry.
428 function Has_Implicit_Character_Literal (N : Node_Id) return Boolean;
429 -- Find a type derived from Character or Wide_Character in the prefix of N.
430 -- Used to resolved qualified names whose selector is a character literal.
432 function Has_Private_With (E : Entity_Id) return Boolean;
433 -- Ada 2005 (AI-262): Determines if the current compilation unit has a
434 -- private with on E
436 procedure Find_Expanded_Name (N : Node_Id);
437 -- Selected component is known to be expanded name. Verify legality
438 -- of selector given the scope denoted by prefix.
440 function Find_Renamed_Entity
441 (N : Node_Id;
442 Nam : Node_Id;
443 New_S : Entity_Id;
444 Is_Actual : Boolean := False) return Entity_Id;
445 -- Find the renamed entity that corresponds to the given parameter profile
446 -- in a subprogram renaming declaration. The renamed entity may be an
447 -- operator, a subprogram, an entry, or a protected operation. Is_Actual
448 -- indicates that the renaming is the one generated for an actual subpro-
449 -- gram in an instance, for which special visibility checks apply.
451 function Has_Implicit_Operator (N : Node_Id) return Boolean;
452 -- N is an expanded name whose selector is an operator name (eg P."+").
453 -- A declarative part contains an implicit declaration of an operator
454 -- if it has a declaration of a type to which one of the predefined
455 -- operators apply. The existence of this routine is an artifact of
456 -- our implementation: a more straightforward but more space-consuming
457 -- choice would be to make all inherited operators explicit in the
458 -- symbol table.
460 procedure Inherit_Renamed_Profile (New_S : Entity_Id; Old_S : Entity_Id);
461 -- A subprogram defined by a renaming declaration inherits the parameter
462 -- profile of the renamed entity. The subtypes given in the subprogram
463 -- specification are discarded and replaced with those of the renamed
464 -- subprogram, which are then used to recheck the default values.
466 function Is_Appropriate_For_Record (T : Entity_Id) return Boolean;
467 -- Prefix is appropriate for record if it is of a record type, or
468 -- an access to such.
470 function Is_Appropriate_For_Entry_Prefix (T : Entity_Id) return Boolean;
471 -- True if it is of a task type, a protected type, or else an access
472 -- to one of these types.
474 procedure Premature_Usage (N : Node_Id);
475 -- Diagnose usage of an entity before it is visible
477 procedure Use_One_Package (P : Entity_Id; N : Node_Id);
478 -- Make visible entities declared in package P potentially use-visible
479 -- in the current context. Also used in the analysis of subunits, when
480 -- re-installing use clauses of parent units. N is the use_clause that
481 -- names P (and possibly other packages).
483 procedure Use_One_Type (Id : Node_Id);
484 -- Id is the subtype mark from a use type clause. This procedure makes
485 -- the primitive operators of the type potentially use-visible.
487 procedure Write_Info;
488 -- Write debugging information on entities declared in current scope
490 procedure Write_Scopes;
491 pragma Warnings (Off, Write_Scopes);
492 -- Debugging information: dump all entities on scope stack
494 --------------------------------
495 -- Analyze_Exception_Renaming --
496 --------------------------------
498 -- The language only allows a single identifier, but the tree holds
499 -- an identifier list. The parser has already issued an error message
500 -- if there is more than one element in the list.
502 procedure Analyze_Exception_Renaming (N : Node_Id) is
503 Id : constant Node_Id := Defining_Identifier (N);
504 Nam : constant Node_Id := Name (N);
506 begin
507 Enter_Name (Id);
508 Analyze (Nam);
510 Set_Ekind (Id, E_Exception);
511 Set_Exception_Code (Id, Uint_0);
512 Set_Etype (Id, Standard_Exception_Type);
513 Set_Is_Pure (Id, Is_Pure (Current_Scope));
515 if not Is_Entity_Name (Nam) or else
516 Ekind (Entity (Nam)) /= E_Exception
517 then
518 Error_Msg_N ("invalid exception name in renaming", Nam);
519 else
520 if Present (Renamed_Object (Entity (Nam))) then
521 Set_Renamed_Object (Id, Renamed_Object (Entity (Nam)));
522 else
523 Set_Renamed_Object (Id, Entity (Nam));
524 end if;
525 end if;
526 end Analyze_Exception_Renaming;
528 ---------------------------
529 -- Analyze_Expanded_Name --
530 ---------------------------
532 procedure Analyze_Expanded_Name (N : Node_Id) is
533 begin
534 -- If the entity pointer is already set, this is an internal node, or
535 -- a node that is analyzed more than once, after a tree modification.
536 -- In such a case there is no resolution to perform, just set the type.
537 -- For completeness, analyze prefix as well.
539 if Present (Entity (N)) then
540 if Is_Type (Entity (N)) then
541 Set_Etype (N, Entity (N));
542 else
543 Set_Etype (N, Etype (Entity (N)));
544 end if;
546 Analyze (Prefix (N));
547 return;
548 else
549 Find_Expanded_Name (N);
550 end if;
551 end Analyze_Expanded_Name;
553 ---------------------------------------
554 -- Analyze_Generic_Function_Renaming --
555 ---------------------------------------
557 procedure Analyze_Generic_Function_Renaming (N : Node_Id) is
558 begin
559 Analyze_Generic_Renaming (N, E_Generic_Function);
560 end Analyze_Generic_Function_Renaming;
562 --------------------------------------
563 -- Analyze_Generic_Package_Renaming --
564 --------------------------------------
566 procedure Analyze_Generic_Package_Renaming (N : Node_Id) is
567 begin
568 -- Apply the Text_IO Kludge here, since we may be renaming
569 -- one of the subpackages of Text_IO, then join common routine.
571 Text_IO_Kludge (Name (N));
573 Analyze_Generic_Renaming (N, E_Generic_Package);
574 end Analyze_Generic_Package_Renaming;
576 ----------------------------------------
577 -- Analyze_Generic_Procedure_Renaming --
578 ----------------------------------------
580 procedure Analyze_Generic_Procedure_Renaming (N : Node_Id) is
581 begin
582 Analyze_Generic_Renaming (N, E_Generic_Procedure);
583 end Analyze_Generic_Procedure_Renaming;
585 ------------------------------
586 -- Analyze_Generic_Renaming --
587 ------------------------------
589 procedure Analyze_Generic_Renaming
590 (N : Node_Id;
591 K : Entity_Kind)
593 New_P : constant Entity_Id := Defining_Entity (N);
594 Old_P : Entity_Id;
595 Inst : Boolean := False; -- prevent junk warning
597 begin
598 if Name (N) = Error then
599 return;
600 end if;
602 Generate_Definition (New_P);
604 if Current_Scope /= Standard_Standard then
605 Set_Is_Pure (New_P, Is_Pure (Current_Scope));
606 end if;
608 if Nkind (Name (N)) = N_Selected_Component then
609 Check_Generic_Child_Unit (Name (N), Inst);
610 else
611 Analyze (Name (N));
612 end if;
614 if not Is_Entity_Name (Name (N)) then
615 Error_Msg_N ("expect entity name in renaming declaration", Name (N));
616 Old_P := Any_Id;
617 else
618 Old_P := Entity (Name (N));
619 end if;
621 Enter_Name (New_P);
622 Set_Ekind (New_P, K);
624 if Etype (Old_P) = Any_Type then
625 null;
627 elsif Ekind (Old_P) /= K then
628 Error_Msg_N ("invalid generic unit name", Name (N));
630 else
631 if Present (Renamed_Object (Old_P)) then
632 Set_Renamed_Object (New_P, Renamed_Object (Old_P));
633 else
634 Set_Renamed_Object (New_P, Old_P);
635 end if;
637 Set_Etype (New_P, Etype (Old_P));
638 Set_Has_Completion (New_P);
640 if In_Open_Scopes (Old_P) then
641 Error_Msg_N ("within its scope, generic denotes its instance", N);
642 end if;
644 Check_Library_Unit_Renaming (N, Old_P);
645 end if;
647 end Analyze_Generic_Renaming;
649 -----------------------------
650 -- Analyze_Object_Renaming --
651 -----------------------------
653 procedure Analyze_Object_Renaming (N : Node_Id) is
654 Id : constant Entity_Id := Defining_Identifier (N);
655 Dec : Node_Id;
656 Nam : constant Node_Id := Name (N);
657 T : Entity_Id;
658 T2 : Entity_Id;
660 begin
661 if Nam = Error then
662 return;
663 end if;
665 Set_Is_Pure (Id, Is_Pure (Current_Scope));
666 Enter_Name (Id);
668 -- The renaming of a component that depends on a discriminant
669 -- requires an actual subtype, because in subsequent use of the object
670 -- Gigi will be unable to locate the actual bounds. This explicit step
671 -- is required when the renaming is generated in removing side effects
672 -- of an already-analyzed expression.
674 if Nkind (Nam) = N_Selected_Component
675 and then Analyzed (Nam)
676 then
677 T := Etype (Nam);
678 Dec := Build_Actual_Subtype_Of_Component (Etype (Nam), Nam);
680 if Present (Dec) then
681 Insert_Action (N, Dec);
682 T := Defining_Identifier (Dec);
683 Set_Etype (Nam, T);
684 end if;
686 elsif Present (Subtype_Mark (N)) then
687 Find_Type (Subtype_Mark (N));
688 T := Entity (Subtype_Mark (N));
689 Analyze_And_Resolve (Nam, T);
691 -- Ada 2005 (AI-230/AI-254): Access renaming
693 else pragma Assert (Present (Access_Definition (N)));
694 T := Access_Definition
695 (Related_Nod => N,
696 N => Access_Definition (N));
698 Analyze_And_Resolve (Nam, T);
700 -- Ada 2005 (AI-231): "In the case where the type is defined by an
701 -- access_definition, the renamed entity shall be of an access-to-
702 -- constant type if and only if the access_definition defines an
703 -- access-to-constant type" ARM 8.5.1(4)
705 if Constant_Present (Access_Definition (N))
706 and then not Is_Access_Constant (Etype (Nam))
707 then
708 Error_Msg_N ("(Ada 2005): the renamed object is not "
709 & "access-to-constant ('R'M 8.5.1(6))", N);
711 elsif Null_Exclusion_Present (Access_Definition (N)) then
712 Error_Msg_N ("(Ada 2005): null-excluding attribute ignored "
713 & "('R'M 8.5.1(6))?", N);
714 end if;
715 end if;
717 -- An object renaming requires an exact match of the type;
718 -- class-wide matching is not allowed.
720 if Is_Class_Wide_Type (T)
721 and then Base_Type (Etype (Nam)) /= Base_Type (T)
722 then
723 Wrong_Type (Nam, T);
724 end if;
726 T2 := Etype (Nam);
727 Set_Ekind (Id, E_Variable);
728 Init_Size_Align (Id);
730 if T = Any_Type or else Etype (Nam) = Any_Type then
731 return;
733 -- Verify that the renamed entity is an object or a function call.
734 -- It may have been rewritten in several ways.
736 elsif Is_Object_Reference (Nam) then
737 if Comes_From_Source (N)
738 and then Is_Dependent_Component_Of_Mutable_Object (Nam)
739 then
740 Error_Msg_N
741 ("illegal renaming of discriminant-dependent component", Nam);
742 else
743 null;
744 end if;
746 -- A static function call may have been folded into a literal
748 elsif Nkind (Original_Node (Nam)) = N_Function_Call
750 -- When expansion is disabled, attribute reference is not
751 -- rewritten as function call. Otherwise it may be rewritten
752 -- as a conversion, so check original node.
754 or else (Nkind (Original_Node (Nam)) = N_Attribute_Reference
755 and then Is_Function_Attribute_Name
756 (Attribute_Name (Original_Node (Nam))))
758 -- Weird but legal, equivalent to renaming a function call
760 or else (Is_Entity_Name (Nam)
761 and then Ekind (Entity (Nam)) = E_Enumeration_Literal)
763 or else (Nkind (Nam) = N_Type_Conversion
764 and then Is_Tagged_Type (Entity (Subtype_Mark (Nam))))
765 then
766 null;
768 else
769 if Nkind (Nam) = N_Type_Conversion then
770 Error_Msg_N
771 ("renaming of conversion only allowed for tagged types", Nam);
773 else
774 Error_Msg_N ("expect object name in renaming", Nam);
775 end if;
776 end if;
778 Set_Etype (Id, T2);
780 if not Is_Variable (Nam) then
781 Set_Ekind (Id, E_Constant);
782 Set_Never_Set_In_Source (Id, True);
783 Set_Is_True_Constant (Id, True);
784 end if;
786 Set_Renamed_Object (Id, Nam);
787 end Analyze_Object_Renaming;
789 ------------------------------
790 -- Analyze_Package_Renaming --
791 ------------------------------
793 procedure Analyze_Package_Renaming (N : Node_Id) is
794 New_P : constant Entity_Id := Defining_Entity (N);
795 Old_P : Entity_Id;
796 Spec : Node_Id;
798 begin
799 if Name (N) = Error then
800 return;
801 end if;
803 -- Apply Text_IO kludge here, since we may be renaming one of
804 -- the children of Text_IO
806 Text_IO_Kludge (Name (N));
808 if Current_Scope /= Standard_Standard then
809 Set_Is_Pure (New_P, Is_Pure (Current_Scope));
810 end if;
812 Enter_Name (New_P);
813 Analyze (Name (N));
814 if Is_Entity_Name (Name (N)) then
815 Old_P := Entity (Name (N));
816 else
817 Old_P := Any_Id;
818 end if;
820 if Etype (Old_P) = Any_Type then
821 Error_Msg_N
822 ("expect package name in renaming", Name (N));
824 -- Ada 2005 (AI-50217): Limited withed packages can not be renamed
826 elsif Ekind (Old_P) = E_Package
827 and then From_With_Type (Old_P)
828 then
829 Error_Msg_N
830 ("limited withed package cannot be renamed", Name (N));
832 elsif Ekind (Old_P) /= E_Package
833 and then not (Ekind (Old_P) = E_Generic_Package
834 and then In_Open_Scopes (Old_P))
835 then
836 if Ekind (Old_P) = E_Generic_Package then
837 Error_Msg_N
838 ("generic package cannot be renamed as a package", Name (N));
839 else
840 Error_Msg_Sloc := Sloc (Old_P);
841 Error_Msg_NE
842 ("expect package name in renaming, found& declared#",
843 Name (N), Old_P);
844 end if;
846 -- Set basic attributes to minimize cascaded errors
848 Set_Ekind (New_P, E_Package);
849 Set_Etype (New_P, Standard_Void_Type);
851 else
852 -- Entities in the old package are accessible through the
853 -- renaming entity. The simplest implementation is to have
854 -- both packages share the entity list.
856 Set_Ekind (New_P, E_Package);
857 Set_Etype (New_P, Standard_Void_Type);
859 if Present (Renamed_Object (Old_P)) then
860 Set_Renamed_Object (New_P, Renamed_Object (Old_P));
861 else
862 Set_Renamed_Object (New_P, Old_P);
863 end if;
865 Set_Has_Completion (New_P);
867 Set_First_Entity (New_P, First_Entity (Old_P));
868 Set_Last_Entity (New_P, Last_Entity (Old_P));
869 Set_First_Private_Entity (New_P, First_Private_Entity (Old_P));
870 Check_Library_Unit_Renaming (N, Old_P);
871 Generate_Reference (Old_P, Name (N));
873 -- If this is the renaming declaration of a package instantiation
874 -- within itself, it is the declaration that ends the list of actuals
875 -- for the instantiation. At this point, the subtypes that rename
876 -- the actuals are flagged as generic, to avoid spurious ambiguities
877 -- if the actuals for two distinct formals happen to coincide. If
878 -- the actual is a private type, the subtype has a private completion
879 -- that is flagged in the same fashion.
881 -- Resolution is identical to what is was in the original generic.
882 -- On exit from the generic instance, these are turned into regular
883 -- subtypes again, so they are compatible with types in their class.
885 if not Is_Generic_Instance (Old_P) then
886 return;
887 else
888 Spec := Specification (Unit_Declaration_Node (Old_P));
889 end if;
891 if Nkind (Spec) = N_Package_Specification
892 and then Present (Generic_Parent (Spec))
893 and then Old_P = Current_Scope
894 and then Chars (New_P) = Chars (Generic_Parent (Spec))
895 then
896 declare
897 E : Entity_Id := First_Entity (Old_P);
898 begin
899 while Present (E)
900 and then E /= New_P
901 loop
902 if Is_Type (E)
903 and then Nkind (Parent (E)) = N_Subtype_Declaration
904 then
905 Set_Is_Generic_Actual_Type (E);
907 if Is_Private_Type (E)
908 and then Present (Full_View (E))
909 then
910 Set_Is_Generic_Actual_Type (Full_View (E));
911 end if;
912 end if;
914 Next_Entity (E);
915 end loop;
916 end;
917 end if;
918 end if;
920 end Analyze_Package_Renaming;
922 -------------------------------
923 -- Analyze_Renamed_Character --
924 -------------------------------
926 procedure Analyze_Renamed_Character
927 (N : Node_Id;
928 New_S : Entity_Id;
929 Is_Body : Boolean)
931 C : constant Node_Id := Name (N);
933 begin
934 if Ekind (New_S) = E_Function then
935 Resolve (C, Etype (New_S));
937 if Is_Body then
938 Check_Frozen_Renaming (N, New_S);
939 end if;
941 else
942 Error_Msg_N ("character literal can only be renamed as function", N);
943 end if;
944 end Analyze_Renamed_Character;
946 ---------------------------------
947 -- Analyze_Renamed_Dereference --
948 ---------------------------------
950 procedure Analyze_Renamed_Dereference
951 (N : Node_Id;
952 New_S : Entity_Id;
953 Is_Body : Boolean)
955 Nam : constant Node_Id := Name (N);
956 P : constant Node_Id := Prefix (Nam);
957 Typ : Entity_Id;
958 Ind : Interp_Index;
959 It : Interp;
961 begin
962 if not Is_Overloaded (P) then
963 if Ekind (Etype (Nam)) /= E_Subprogram_Type
964 or else not Type_Conformant (Etype (Nam), New_S) then
965 Error_Msg_N ("designated type does not match specification", P);
966 else
967 Resolve (P);
968 end if;
970 return;
972 else
973 Typ := Any_Type;
974 Get_First_Interp (Nam, Ind, It);
976 while Present (It.Nam) loop
978 if Ekind (It.Nam) = E_Subprogram_Type
979 and then Type_Conformant (It.Nam, New_S) then
981 if Typ /= Any_Id then
982 Error_Msg_N ("ambiguous renaming", P);
983 return;
984 else
985 Typ := It.Nam;
986 end if;
987 end if;
989 Get_Next_Interp (Ind, It);
990 end loop;
992 if Typ = Any_Type then
993 Error_Msg_N ("designated type does not match specification", P);
994 else
995 Resolve (N, Typ);
997 if Is_Body then
998 Check_Frozen_Renaming (N, New_S);
999 end if;
1000 end if;
1001 end if;
1002 end Analyze_Renamed_Dereference;
1004 ---------------------------
1005 -- Analyze_Renamed_Entry --
1006 ---------------------------
1008 procedure Analyze_Renamed_Entry
1009 (N : Node_Id;
1010 New_S : Entity_Id;
1011 Is_Body : Boolean)
1013 Nam : constant Node_Id := Name (N);
1014 Sel : constant Node_Id := Selector_Name (Nam);
1015 Old_S : Entity_Id;
1017 begin
1018 if Entity (Sel) = Any_Id then
1020 -- Selector is undefined on prefix. Error emitted already
1022 Set_Has_Completion (New_S);
1023 return;
1024 end if;
1026 -- Otherwise, find renamed entity, and build body of New_S as a call
1027 -- to it.
1029 Old_S := Find_Renamed_Entity (N, Selector_Name (Nam), New_S);
1031 if Old_S = Any_Id then
1032 Error_Msg_N (" no subprogram or entry matches specification", N);
1033 else
1034 if Is_Body then
1035 Check_Subtype_Conformant (New_S, Old_S, N);
1036 Generate_Reference (New_S, Defining_Entity (N), 'b');
1037 Style.Check_Identifier (Defining_Entity (N), New_S);
1038 end if;
1040 Inherit_Renamed_Profile (New_S, Old_S);
1041 end if;
1043 Set_Convention (New_S, Convention (Old_S));
1044 Set_Has_Completion (New_S, Inside_A_Generic);
1046 if Is_Body then
1047 Check_Frozen_Renaming (N, New_S);
1048 end if;
1049 end Analyze_Renamed_Entry;
1051 -----------------------------------
1052 -- Analyze_Renamed_Family_Member --
1053 -----------------------------------
1055 procedure Analyze_Renamed_Family_Member
1056 (N : Node_Id;
1057 New_S : Entity_Id;
1058 Is_Body : Boolean)
1060 Nam : constant Node_Id := Name (N);
1061 P : constant Node_Id := Prefix (Nam);
1062 Old_S : Entity_Id;
1064 begin
1065 if (Is_Entity_Name (P) and then Ekind (Entity (P)) = E_Entry_Family)
1066 or else (Nkind (P) = N_Selected_Component
1067 and then
1068 Ekind (Entity (Selector_Name (P))) = E_Entry_Family)
1069 then
1070 if Is_Entity_Name (P) then
1071 Old_S := Entity (P);
1072 else
1073 Old_S := Entity (Selector_Name (P));
1074 end if;
1076 if not Entity_Matches_Spec (Old_S, New_S) then
1077 Error_Msg_N ("entry family does not match specification", N);
1079 elsif Is_Body then
1080 Check_Subtype_Conformant (New_S, Old_S, N);
1081 Generate_Reference (New_S, Defining_Entity (N), 'b');
1082 Style.Check_Identifier (Defining_Entity (N), New_S);
1083 end if;
1084 else
1085 Error_Msg_N ("no entry family matches specification", N);
1086 end if;
1088 Set_Has_Completion (New_S, Inside_A_Generic);
1090 if Is_Body then
1091 Check_Frozen_Renaming (N, New_S);
1092 end if;
1093 end Analyze_Renamed_Family_Member;
1095 ---------------------------------
1096 -- Analyze_Subprogram_Renaming --
1097 ---------------------------------
1099 procedure Analyze_Subprogram_Renaming (N : Node_Id) is
1100 Spec : constant Node_Id := Specification (N);
1101 Save_AV : constant Ada_Version_Type := Ada_Version;
1102 Nam : constant Node_Id := Name (N);
1103 New_S : Entity_Id;
1104 Old_S : Entity_Id := Empty;
1105 Rename_Spec : Entity_Id;
1106 Is_Actual : Boolean := False;
1107 Inst_Node : Node_Id := Empty;
1109 function Original_Subprogram (Subp : Entity_Id) return Entity_Id;
1110 -- Find renamed entity when the declaration is a renaming_as_body
1111 -- and the renamed entity may itself be a renaming_as_body. Used to
1112 -- enforce rule that a renaming_as_body is illegal if the declaration
1113 -- occurs before the subprogram it completes is frozen, and renaming
1114 -- indirectly renames the subprogram itself.(Defect Report 8652/0027).
1116 -------------------------
1117 -- Original_Subprogram --
1118 -------------------------
1120 function Original_Subprogram (Subp : Entity_Id) return Entity_Id is
1121 Orig_Decl : Node_Id;
1122 Orig_Subp : Entity_Id;
1124 begin
1125 -- First case: renamed entity is itself a renaming
1127 if Present (Alias (Subp)) then
1128 return Alias (Subp);
1130 elsif
1131 Nkind (Unit_Declaration_Node (Subp)) = N_Subprogram_Declaration
1132 and then Present
1133 (Corresponding_Body (Unit_Declaration_Node (Subp)))
1134 then
1135 -- Check if renamed entity is a renaming_as_body
1137 Orig_Decl :=
1138 Unit_Declaration_Node
1139 (Corresponding_Body (Unit_Declaration_Node (Subp)));
1141 if Nkind (Orig_Decl) = N_Subprogram_Renaming_Declaration then
1142 Orig_Subp := Entity (Name (Orig_Decl));
1144 if Orig_Subp = Rename_Spec then
1146 -- Circularity detected
1148 return Orig_Subp;
1150 else
1151 return (Original_Subprogram (Orig_Subp));
1152 end if;
1153 else
1154 return Subp;
1155 end if;
1156 else
1157 return Subp;
1158 end if;
1159 end Original_Subprogram;
1161 -- Start of processing for Analyze_Subprogram_Renaming
1163 begin
1164 -- We must test for the attribute renaming case before the Analyze
1165 -- call because otherwise Sem_Attr will complain that the attribute
1166 -- is missing an argument when it is analyzed.
1168 if Nkind (Nam) = N_Attribute_Reference then
1169 Attribute_Renaming (N);
1170 return;
1171 end if;
1173 -- Check whether this declaration corresponds to the instantiation
1174 -- of a formal subprogram.
1176 -- If this is an instantiation, the corresponding actual is frozen
1177 -- and error messages can be made more precise. If this is a default
1178 -- subprogram, the entity is already established in the generic, and
1179 -- is not retrieved by visibility. If it is a default with a box, the
1180 -- candidate interpretations, if any, have been collected when building
1181 -- the renaming declaration. If overloaded, the proper interpretation
1182 -- is determined in Find_Renamed_Entity. If the entity is an operator,
1183 -- Find_Renamed_Entity applies additional visibility checks.
1185 if Present (Corresponding_Formal_Spec (N)) then
1186 Is_Actual := True;
1187 Inst_Node := Unit_Declaration_Node (Corresponding_Formal_Spec (N));
1189 if Is_Entity_Name (Nam)
1190 and then Present (Entity (Nam))
1191 and then not Comes_From_Source (Nam)
1192 and then not Is_Overloaded (Nam)
1193 then
1194 Old_S := Entity (Nam);
1195 New_S := Analyze_Subprogram_Specification (Spec);
1197 -- Operator case
1199 if Ekind (Entity (Nam)) = E_Operator then
1201 -- Box present
1203 if Box_Present (Inst_Node) then
1204 Old_S := Find_Renamed_Entity (N, Name (N), New_S, Is_Actual);
1206 -- If there is an immediately visible homonym of the operator
1207 -- and the declaration has a default, this is worth a warning
1208 -- because the user probably did not intend to get the pre-
1209 -- defined operator, visible in the generic declaration.
1210 -- To find if there is an intended candidate, analyze the
1211 -- renaming again in the current context.
1213 elsif Scope (Old_S) = Standard_Standard
1214 and then Present (Default_Name (Inst_Node))
1215 then
1216 declare
1217 Decl : constant Node_Id := New_Copy_Tree (N);
1218 Hidden : Entity_Id;
1220 begin
1221 Set_Entity (Name (Decl), Empty);
1222 Analyze (Name (Decl));
1223 Hidden :=
1224 Find_Renamed_Entity (Decl, Name (Decl), New_S, True);
1226 if Present (Hidden)
1227 and then In_Open_Scopes (Scope (Hidden))
1228 and then Is_Immediately_Visible (Hidden)
1229 and then Comes_From_Source (Hidden)
1230 and then Hidden /= Old_S
1231 then
1232 Error_Msg_Sloc := Sloc (Hidden);
1233 Error_Msg_N ("?default subprogram is resolved " &
1234 "in the generic declaration " &
1235 "('R'M 12.6(17))", N);
1236 Error_Msg_NE ("\?and will not use & #", N, Hidden);
1237 end if;
1238 end;
1239 end if;
1240 end if;
1242 else
1243 Analyze (Nam);
1244 New_S := Analyze_Subprogram_Specification (Spec);
1245 end if;
1247 else
1248 -- Renamed entity must be analyzed first, to avoid being hidden by
1249 -- new name (which might be the same in a generic instance).
1251 Analyze (Nam);
1253 -- The renaming defines a new overloaded entity, which is analyzed
1254 -- like a subprogram declaration.
1256 New_S := Analyze_Subprogram_Specification (Spec);
1257 end if;
1259 if Current_Scope /= Standard_Standard then
1260 Set_Is_Pure (New_S, Is_Pure (Current_Scope));
1261 end if;
1263 Rename_Spec := Find_Corresponding_Spec (N);
1265 if Present (Rename_Spec) then
1267 -- Renaming_As_Body. Renaming declaration is the completion of
1268 -- the declaration of Rename_Spec. We will build an actual body
1269 -- for it at the freezing point.
1271 Set_Corresponding_Spec (N, Rename_Spec);
1272 Set_Corresponding_Body (Unit_Declaration_Node (Rename_Spec), New_S);
1274 -- The body is created when the entity is frozen. If the context
1275 -- is generic, freeze_all is not invoked, so we need to indicate
1276 -- that the entity has a completion.
1278 Set_Has_Completion (Rename_Spec, Inside_A_Generic);
1280 if Ada_Version = Ada_83 and then Comes_From_Source (N) then
1281 Error_Msg_N ("(Ada 83) renaming cannot serve as a body", N);
1282 end if;
1284 Set_Convention (New_S, Convention (Rename_Spec));
1285 Check_Fully_Conformant (New_S, Rename_Spec);
1286 Set_Public_Status (New_S);
1288 -- Indicate that the entity in the declaration functions like
1289 -- the corresponding body, and is not a new entity.
1291 Set_Ekind (New_S, E_Subprogram_Body);
1292 New_S := Rename_Spec;
1294 else
1295 Generate_Definition (New_S);
1296 New_Overloaded_Entity (New_S);
1297 if Is_Entity_Name (Nam)
1298 and then Is_Intrinsic_Subprogram (Entity (Nam))
1299 then
1300 null;
1301 else
1302 Check_Delayed_Subprogram (New_S);
1303 end if;
1304 end if;
1306 -- There is no need for elaboration checks on the new entity, which
1307 -- may be called before the next freezing point where the body will
1308 -- appear. Elaboration checks refer to the real entity, not the one
1309 -- created by the renaming declaration.
1311 Set_Kill_Elaboration_Checks (New_S, True);
1313 if Etype (Nam) = Any_Type then
1314 Set_Has_Completion (New_S);
1315 return;
1317 elsif Nkind (Nam) = N_Selected_Component then
1319 -- Renamed entity is an entry or protected subprogram. For those
1320 -- cases an explicit body is built (at the point of freezing of
1321 -- this entity) that contains a call to the renamed entity.
1323 Analyze_Renamed_Entry (N, New_S, Present (Rename_Spec));
1324 return;
1326 elsif Nkind (Nam) = N_Explicit_Dereference then
1328 -- Renamed entity is designated by access_to_subprogram expression.
1329 -- Must build body to encapsulate call, as in the entry case.
1331 Analyze_Renamed_Dereference (N, New_S, Present (Rename_Spec));
1332 return;
1334 elsif Nkind (Nam) = N_Indexed_Component then
1335 Analyze_Renamed_Family_Member (N, New_S, Present (Rename_Spec));
1336 return;
1338 elsif Nkind (Nam) = N_Character_Literal then
1339 Analyze_Renamed_Character (N, New_S, Present (Rename_Spec));
1340 return;
1342 elsif (not Is_Entity_Name (Nam)
1343 and then Nkind (Nam) /= N_Operator_Symbol)
1344 or else not Is_Overloadable (Entity (Nam))
1345 then
1346 Error_Msg_N ("expect valid subprogram name in renaming", N);
1347 return;
1349 end if;
1351 -- Most common case: subprogram renames subprogram. No body is
1352 -- generated in this case, so we must indicate that the declaration
1353 -- is complete as is.
1355 if No (Rename_Spec) then
1356 Set_Has_Completion (New_S);
1357 end if;
1359 -- Find the renamed entity that matches the given specification.
1360 -- Disable Ada_83 because there is no requirement of full conformance
1361 -- between renamed entity and new entity, even though the same circuit
1362 -- is used.
1364 Ada_Version := Ada_Version_Type'Max (Ada_Version, Ada_95);
1366 if No (Old_S) then
1367 Old_S := Find_Renamed_Entity (N, Name (N), New_S, Is_Actual);
1368 end if;
1370 if Old_S /= Any_Id then
1371 if Is_Actual
1372 and then From_Default (N)
1373 then
1374 -- This is an implicit reference to the default actual
1376 Generate_Reference (Old_S, Nam, Typ => 'i', Force => True);
1377 else
1378 Generate_Reference (Old_S, Nam);
1379 end if;
1381 -- For a renaming-as-body, require subtype conformance,
1382 -- but if the declaration being completed has not been
1383 -- frozen, then inherit the convention of the renamed
1384 -- subprogram prior to checking conformance (unless the
1385 -- renaming has an explicit convention established; the
1386 -- rule stated in the RM doesn't seem to address this ???).
1388 if Present (Rename_Spec) then
1389 Generate_Reference (Rename_Spec, Defining_Entity (Spec), 'b');
1390 Style.Check_Identifier (Defining_Entity (Spec), Rename_Spec);
1392 if not Is_Frozen (Rename_Spec) then
1393 if not Has_Convention_Pragma (Rename_Spec) then
1394 Set_Convention (New_S, Convention (Old_S));
1395 end if;
1397 if Ekind (Old_S) /= E_Operator then
1398 Check_Mode_Conformant (New_S, Old_S, Spec);
1399 end if;
1401 if Original_Subprogram (Old_S) = Rename_Spec then
1402 Error_Msg_N ("unfrozen subprogram cannot rename itself ", N);
1403 end if;
1404 else
1405 Check_Subtype_Conformant (New_S, Old_S, Spec);
1406 end if;
1408 Check_Frozen_Renaming (N, Rename_Spec);
1410 elsif Ekind (Old_S) /= E_Operator then
1411 Check_Mode_Conformant (New_S, Old_S);
1413 if Is_Actual
1414 and then Error_Posted (New_S)
1415 then
1416 Error_Msg_NE ("invalid actual subprogram: & #!", N, Old_S);
1417 end if;
1418 end if;
1420 if No (Rename_Spec) then
1422 -- The parameter profile of the new entity is that of the renamed
1423 -- entity: the subtypes given in the specification are irrelevant.
1425 Inherit_Renamed_Profile (New_S, Old_S);
1427 -- A call to the subprogram is transformed into a call to the
1428 -- renamed entity. This is transitive if the renamed entity is
1429 -- itself a renaming.
1431 if Present (Alias (Old_S)) then
1432 Set_Alias (New_S, Alias (Old_S));
1433 else
1434 Set_Alias (New_S, Old_S);
1435 end if;
1437 -- Note that we do not set Is_Intrinsic_Subprogram if we have
1438 -- a renaming as body, since the entity in this case is not an
1439 -- intrinsic (it calls an intrinsic, but we have a real body
1440 -- for this call, and it is in this body that the required
1441 -- intrinsic processing will take place).
1443 -- Also, if this is a renaming of inequality, the renamed
1444 -- operator is intrinsic, but what matters is the corresponding
1445 -- equality operator, which may be user-defined.
1447 Set_Is_Intrinsic_Subprogram
1448 (New_S,
1449 Is_Intrinsic_Subprogram (Old_S)
1450 and then
1451 (Chars (Old_S) /= Name_Op_Ne
1452 or else Ekind (Old_S) = E_Operator
1453 or else
1454 Is_Intrinsic_Subprogram
1455 (Corresponding_Equality (Old_S))));
1457 if Ekind (Alias (New_S)) = E_Operator then
1458 Set_Has_Delayed_Freeze (New_S, False);
1459 end if;
1461 -- If the renaming corresponds to an association for an abstract
1462 -- formal subprogram, then various attributes must be set to
1463 -- indicate that the renaming is an abstract dispatching operation
1464 -- with a controlling type.
1466 if Is_Actual
1467 and then Is_Abstract (Corresponding_Formal_Spec (N))
1468 then
1469 -- Mark the renaming as abstract here, so Find_Dispatching_Type
1470 -- see it as corresponding to a generic association for a
1471 -- formal abstract subprogram
1473 Set_Is_Abstract (New_S);
1475 declare
1476 New_S_Ctrl_Type : constant Entity_Id :=
1477 Find_Dispatching_Type (New_S);
1478 Old_S_Ctrl_Type : constant Entity_Id :=
1479 Find_Dispatching_Type (Old_S);
1481 begin
1482 if Old_S_Ctrl_Type /= New_S_Ctrl_Type then
1483 Error_Msg_NE
1484 ("actual must be dispatching subprogram for type&",
1485 Nam, New_S_Ctrl_Type);
1487 else
1488 Set_Is_Dispatching_Operation (New_S);
1489 Check_Controlling_Formals (New_S_Ctrl_Type, New_S);
1491 -- In the case where the actual in the formal subprogram
1492 -- is itself a formal abstract subprogram association,
1493 -- there's no dispatch table component or position to
1494 -- inherit.
1496 if Present (DTC_Entity (Old_S)) then
1497 Set_DTC_Entity (New_S, DTC_Entity (Old_S));
1498 Set_DT_Position (New_S, DT_Position (Old_S));
1499 end if;
1500 end if;
1501 end;
1502 end if;
1503 end if;
1505 if not Is_Actual
1506 and then (Old_S = New_S
1507 or else (Nkind (Nam) /= N_Expanded_Name
1508 and then Chars (Old_S) = Chars (New_S)))
1509 then
1510 Error_Msg_N ("subprogram cannot rename itself", N);
1511 end if;
1513 Set_Convention (New_S, Convention (Old_S));
1514 Set_Is_Abstract (New_S, Is_Abstract (Old_S));
1515 Check_Library_Unit_Renaming (N, Old_S);
1517 -- Pathological case: procedure renames entry in the scope of
1518 -- its task. Entry is given by simple name, but body must be built
1519 -- for procedure. Of course if called it will deadlock.
1521 if Ekind (Old_S) = E_Entry then
1522 Set_Has_Completion (New_S, False);
1523 Set_Alias (New_S, Empty);
1524 end if;
1526 if Is_Actual then
1527 Freeze_Before (N, Old_S);
1528 Set_Has_Delayed_Freeze (New_S, False);
1529 Freeze_Before (N, New_S);
1531 -- An abstract subprogram is only allowed as an actual in the case
1532 -- where the formal subprogram is also abstract.
1534 if (Ekind (Old_S) = E_Procedure or else Ekind (Old_S) = E_Function)
1535 and then Is_Abstract (Old_S)
1536 and then not Is_Abstract (Corresponding_Formal_Spec (N))
1537 then
1538 Error_Msg_N
1539 ("abstract subprogram not allowed as generic actual", Nam);
1540 end if;
1541 end if;
1543 else
1544 -- A common error is to assume that implicit operators for types
1545 -- are defined in Standard, or in the scope of a subtype. In those
1546 -- cases where the renamed entity is given with an expanded name,
1547 -- it is worth mentioning that operators for the type are not
1548 -- declared in the scope given by the prefix.
1550 if Nkind (Nam) = N_Expanded_Name
1551 and then Nkind (Selector_Name (Nam)) = N_Operator_Symbol
1552 and then Scope (Entity (Nam)) = Standard_Standard
1553 then
1554 declare
1555 T : constant Entity_Id :=
1556 Base_Type (Etype (First_Formal (New_S)));
1558 begin
1559 Error_Msg_Node_2 := Prefix (Nam);
1560 Error_Msg_NE
1561 ("operator for type& is not declared in&", Prefix (Nam), T);
1562 end;
1564 else
1565 Error_Msg_NE
1566 ("no visible subprogram matches the specification for&",
1567 Spec, New_S);
1568 end if;
1570 if Present (Candidate_Renaming) then
1571 declare
1572 F1 : Entity_Id;
1573 F2 : Entity_Id;
1575 begin
1576 F1 := First_Formal (Candidate_Renaming);
1577 F2 := First_Formal (New_S);
1579 while Present (F1) and then Present (F2) loop
1580 Next_Formal (F1);
1581 Next_Formal (F2);
1582 end loop;
1584 if Present (F1) and then Present (Default_Value (F1)) then
1585 if Present (Next_Formal (F1)) then
1586 Error_Msg_NE
1587 ("\missing specification for &" &
1588 " and other formals with defaults", Spec, F1);
1589 else
1590 Error_Msg_NE
1591 ("\missing specification for &", Spec, F1);
1592 end if;
1593 end if;
1594 end;
1595 end if;
1596 end if;
1598 Ada_Version := Save_AV;
1599 end Analyze_Subprogram_Renaming;
1601 -------------------------
1602 -- Analyze_Use_Package --
1603 -------------------------
1605 -- Resolve the package names in the use clause, and make all the visible
1606 -- entities defined in the package potentially use-visible. If the package
1607 -- is already in use from a previous use clause, its visible entities are
1608 -- already use-visible. In that case, mark the occurrence as a redundant
1609 -- use. If the package is an open scope, i.e. if the use clause occurs
1610 -- within the package itself, ignore it.
1612 procedure Analyze_Use_Package (N : Node_Id) is
1613 Pack_Name : Node_Id;
1614 Pack : Entity_Id;
1616 -- Start of processing for Analyze_Use_Package
1618 begin
1619 Set_Hidden_By_Use_Clause (N, No_Elist);
1621 -- Use clause is not allowed in a spec of a predefined package
1622 -- declaration except that packages whose file name starts a-n
1623 -- are OK (these are children of Ada.Numerics, and such packages
1624 -- are never loaded by Rtsfind).
1626 if Is_Predefined_File_Name (Unit_File_Name (Current_Sem_Unit))
1627 and then Name_Buffer (1 .. 3) /= "a-n"
1628 and then
1629 Nkind (Unit (Cunit (Current_Sem_Unit))) = N_Package_Declaration
1630 then
1631 Error_Msg_N ("use clause not allowed in predefined spec", N);
1632 end if;
1634 -- Chain clause to list of use clauses in current scope
1636 if Nkind (Parent (N)) /= N_Compilation_Unit then
1637 Chain_Use_Clause (N);
1638 end if;
1640 -- Loop through package names to identify referenced packages
1642 Pack_Name := First (Names (N));
1644 while Present (Pack_Name) loop
1645 Analyze (Pack_Name);
1647 if Nkind (Parent (N)) = N_Compilation_Unit
1648 and then Nkind (Pack_Name) = N_Expanded_Name
1649 then
1650 declare
1651 Pref : Node_Id := Prefix (Pack_Name);
1653 begin
1654 while Nkind (Pref) = N_Expanded_Name loop
1655 Pref := Prefix (Pref);
1656 end loop;
1658 if Entity (Pref) = Standard_Standard then
1659 Error_Msg_N
1660 ("predefined package Standard cannot appear"
1661 & " in a context clause", Pref);
1662 end if;
1663 end;
1664 end if;
1666 Next (Pack_Name);
1667 end loop;
1669 -- Loop through package names to mark all entities as potentially
1670 -- use visible.
1672 Pack_Name := First (Names (N));
1674 while Present (Pack_Name) loop
1676 if Is_Entity_Name (Pack_Name) then
1677 Pack := Entity (Pack_Name);
1679 if Ekind (Pack) /= E_Package
1680 and then Etype (Pack) /= Any_Type
1681 then
1682 if Ekind (Pack) = E_Generic_Package then
1683 Error_Msg_N
1684 ("a generic package is not allowed in a use clause",
1685 Pack_Name);
1686 else
1687 Error_Msg_N ("& is not a usable package", Pack_Name);
1688 end if;
1690 else
1691 if Nkind (Parent (N)) = N_Compilation_Unit then
1692 Check_In_Previous_With_Clause (N, Pack_Name);
1693 end if;
1695 if Applicable_Use (Pack_Name) then
1696 Use_One_Package (Pack, N);
1697 end if;
1698 end if;
1699 end if;
1701 Next (Pack_Name);
1702 end loop;
1704 end Analyze_Use_Package;
1706 ----------------------
1707 -- Analyze_Use_Type --
1708 ----------------------
1710 procedure Analyze_Use_Type (N : Node_Id) is
1711 Id : Entity_Id;
1713 begin
1714 Set_Hidden_By_Use_Clause (N, No_Elist);
1716 -- Chain clause to list of use clauses in current scope
1718 if Nkind (Parent (N)) /= N_Compilation_Unit then
1719 Chain_Use_Clause (N);
1720 end if;
1722 Id := First (Subtype_Marks (N));
1724 while Present (Id) loop
1725 Find_Type (Id);
1727 if Entity (Id) /= Any_Type then
1728 Use_One_Type (Id);
1730 if Nkind (Parent (N)) = N_Compilation_Unit then
1731 if Nkind (Id) = N_Identifier then
1732 Error_Msg_N ("Type is not directly visible", Id);
1734 elsif Is_Child_Unit (Scope (Entity (Id)))
1735 and then Scope (Entity (Id)) /= System_Aux_Id
1736 then
1737 Check_In_Previous_With_Clause (N, Prefix (Id));
1738 end if;
1739 end if;
1740 end if;
1742 Next (Id);
1743 end loop;
1744 end Analyze_Use_Type;
1746 --------------------
1747 -- Applicable_Use --
1748 --------------------
1750 function Applicable_Use (Pack_Name : Node_Id) return Boolean is
1751 Pack : constant Entity_Id := Entity (Pack_Name);
1753 begin
1754 if In_Open_Scopes (Pack) then
1755 return False;
1757 elsif In_Use (Pack) then
1758 Set_Redundant_Use (Pack_Name, True);
1759 return False;
1761 elsif Present (Renamed_Object (Pack))
1762 and then In_Use (Renamed_Object (Pack))
1763 then
1764 Set_Redundant_Use (Pack_Name, True);
1765 return False;
1767 else
1768 return True;
1769 end if;
1770 end Applicable_Use;
1772 ------------------------
1773 -- Attribute_Renaming --
1774 ------------------------
1776 procedure Attribute_Renaming (N : Node_Id) is
1777 Loc : constant Source_Ptr := Sloc (N);
1778 Nam : constant Node_Id := Name (N);
1779 Spec : constant Node_Id := Specification (N);
1780 New_S : constant Entity_Id := Defining_Unit_Name (Spec);
1781 Aname : constant Name_Id := Attribute_Name (Nam);
1783 Form_Num : Nat := 0;
1784 Expr_List : List_Id := No_List;
1786 Attr_Node : Node_Id;
1787 Body_Node : Node_Id;
1788 Param_Spec : Node_Id;
1790 begin
1791 Generate_Definition (New_S);
1793 -- This procedure is called in the context of subprogram renaming,
1794 -- and thus the attribute must be one that is a subprogram. All of
1795 -- those have at least one formal parameter, with the singular
1796 -- exception of AST_Entry (which is a real oddity, it is odd that
1797 -- this can be renamed at all!)
1799 if not Is_Non_Empty_List (Parameter_Specifications (Spec)) then
1800 if Aname /= Name_AST_Entry then
1801 Error_Msg_N
1802 ("subprogram renaming an attribute must have formals", N);
1803 return;
1804 end if;
1806 else
1807 Param_Spec := First (Parameter_Specifications (Spec));
1809 while Present (Param_Spec) loop
1810 Form_Num := Form_Num + 1;
1812 if Nkind (Parameter_Type (Param_Spec)) /= N_Access_Definition then
1813 Find_Type (Parameter_Type (Param_Spec));
1815 -- The profile of the new entity denotes the base type (s) of
1816 -- the types given in the specification. For access parameters
1817 -- there are no subtypes involved.
1819 Rewrite (Parameter_Type (Param_Spec),
1820 New_Reference_To
1821 (Base_Type (Entity (Parameter_Type (Param_Spec))), Loc));
1822 end if;
1824 if No (Expr_List) then
1825 Expr_List := New_List;
1826 end if;
1828 Append_To (Expr_List,
1829 Make_Identifier (Loc,
1830 Chars => Chars (Defining_Identifier (Param_Spec))));
1832 -- The expressions in the attribute reference are not freeze
1833 -- points. Neither is the attribute as a whole, see below.
1835 Set_Must_Not_Freeze (Last (Expr_List));
1836 Next (Param_Spec);
1837 end loop;
1838 end if;
1840 -- Immediate error if too many formals. Other mismatches in numbers
1841 -- of number of types of parameters are detected when we analyze the
1842 -- body of the subprogram that we construct.
1844 if Form_Num > 2 then
1845 Error_Msg_N ("too many formals for attribute", N);
1847 -- Error if the attribute reference has expressions that look
1848 -- like formal parameters.
1850 elsif Present (Expressions (Nam)) then
1851 Error_Msg_N ("illegal expressions in attribute reference", Nam);
1853 elsif
1854 Aname = Name_Compose or else
1855 Aname = Name_Exponent or else
1856 Aname = Name_Leading_Part or else
1857 Aname = Name_Pos or else
1858 Aname = Name_Round or else
1859 Aname = Name_Scaling or else
1860 Aname = Name_Val
1861 then
1862 if Nkind (N) = N_Subprogram_Renaming_Declaration
1863 and then Present (Corresponding_Formal_Spec (N))
1864 then
1865 Error_Msg_N
1866 ("generic actual cannot be attribute involving universal type",
1867 Nam);
1868 else
1869 Error_Msg_N
1870 ("attribute involving a universal type cannot be renamed",
1871 Nam);
1872 end if;
1873 end if;
1875 -- AST_Entry is an odd case. It doesn't really make much sense to
1876 -- allow it to be renamed, but that's the DEC rule, so we have to
1877 -- do it right. The point is that the AST_Entry call should be made
1878 -- now, and what the function will return is the returned value.
1880 -- Note that there is no Expr_List in this case anyway
1882 if Aname = Name_AST_Entry then
1884 declare
1885 Ent : Entity_Id;
1886 Decl : Node_Id;
1888 begin
1889 Ent := Make_Defining_Identifier (Loc, New_Internal_Name ('R'));
1891 Decl :=
1892 Make_Object_Declaration (Loc,
1893 Defining_Identifier => Ent,
1894 Object_Definition =>
1895 New_Occurrence_Of (RTE (RE_AST_Handler), Loc),
1896 Expression => Nam,
1897 Constant_Present => True);
1899 Set_Assignment_OK (Decl, True);
1900 Insert_Action (N, Decl);
1901 Attr_Node := Make_Identifier (Loc, Chars (Ent));
1902 end;
1904 -- For all other attributes, we rewrite the attribute node to have
1905 -- a list of expressions corresponding to the subprogram formals.
1906 -- A renaming declaration is not a freeze point, and the analysis of
1907 -- the attribute reference should not freeze the type of the prefix.
1909 else
1910 Attr_Node :=
1911 Make_Attribute_Reference (Loc,
1912 Prefix => Prefix (Nam),
1913 Attribute_Name => Aname,
1914 Expressions => Expr_List);
1916 Set_Must_Not_Freeze (Attr_Node);
1917 Set_Must_Not_Freeze (Prefix (Nam));
1918 end if;
1920 -- Case of renaming a function
1922 if Nkind (Spec) = N_Function_Specification then
1924 if Is_Procedure_Attribute_Name (Aname) then
1925 Error_Msg_N ("attribute can only be renamed as procedure", Nam);
1926 return;
1927 end if;
1929 Find_Type (Subtype_Mark (Spec));
1930 Rewrite (Subtype_Mark (Spec),
1931 New_Reference_To (Base_Type (Entity (Subtype_Mark (Spec))), Loc));
1933 Body_Node :=
1934 Make_Subprogram_Body (Loc,
1935 Specification => Spec,
1936 Declarations => New_List,
1937 Handled_Statement_Sequence =>
1938 Make_Handled_Sequence_Of_Statements (Loc,
1939 Statements => New_List (
1940 Make_Return_Statement (Loc,
1941 Expression => Attr_Node))));
1943 -- Case of renaming a procedure
1945 else
1946 if not Is_Procedure_Attribute_Name (Aname) then
1947 Error_Msg_N ("attribute can only be renamed as function", Nam);
1948 return;
1949 end if;
1951 Body_Node :=
1952 Make_Subprogram_Body (Loc,
1953 Specification => Spec,
1954 Declarations => New_List,
1955 Handled_Statement_Sequence =>
1956 Make_Handled_Sequence_Of_Statements (Loc,
1957 Statements => New_List (Attr_Node)));
1958 end if;
1960 Rewrite (N, Body_Node);
1961 Analyze (N);
1963 if Is_Compilation_Unit (New_S) then
1964 Error_Msg_N
1965 ("a library unit can only rename another library unit", N);
1966 end if;
1968 Set_Etype (New_S, Base_Type (Etype (New_S)));
1970 -- We suppress elaboration warnings for the resulting entity, since
1971 -- clearly they are not needed, and more particularly, in the case
1972 -- of a generic formal subprogram, the resulting entity can appear
1973 -- after the instantiation itself, and thus look like a bogus case
1974 -- of access before elaboration.
1976 Set_Suppress_Elaboration_Warnings (New_S);
1978 end Attribute_Renaming;
1980 ----------------------
1981 -- Chain_Use_Clause --
1982 ----------------------
1984 procedure Chain_Use_Clause (N : Node_Id) is
1985 begin
1986 Set_Next_Use_Clause (N,
1987 Scope_Stack.Table (Scope_Stack.Last).First_Use_Clause);
1988 Scope_Stack.Table (Scope_Stack.Last).First_Use_Clause := N;
1989 end Chain_Use_Clause;
1991 ---------------------------
1992 -- Check_Frozen_Renaming --
1993 ---------------------------
1995 procedure Check_Frozen_Renaming (N : Node_Id; Subp : Entity_Id) is
1996 B_Node : Node_Id;
1997 Old_S : Entity_Id;
1999 begin
2000 if Is_Frozen (Subp)
2001 and then not Has_Completion (Subp)
2002 then
2003 B_Node :=
2004 Build_Renamed_Body
2005 (Parent (Declaration_Node (Subp)), Defining_Entity (N));
2007 if Is_Entity_Name (Name (N)) then
2008 Old_S := Entity (Name (N));
2010 if not Is_Frozen (Old_S)
2011 and then Operating_Mode /= Check_Semantics
2012 then
2013 Append_Freeze_Action (Old_S, B_Node);
2014 else
2015 Insert_After (N, B_Node);
2016 Analyze (B_Node);
2017 end if;
2019 if Is_Intrinsic_Subprogram (Old_S)
2020 and then not In_Instance
2021 then
2022 Error_Msg_N
2023 ("subprogram used in renaming_as_body cannot be intrinsic",
2024 Name (N));
2025 end if;
2027 else
2028 Insert_After (N, B_Node);
2029 Analyze (B_Node);
2030 end if;
2031 end if;
2032 end Check_Frozen_Renaming;
2034 -----------------------------------
2035 -- Check_In_Previous_With_Clause --
2036 -----------------------------------
2038 procedure Check_In_Previous_With_Clause
2039 (N : Node_Id;
2040 Nam : Entity_Id)
2042 Pack : constant Entity_Id := Entity (Original_Node (Nam));
2043 Item : Node_Id;
2044 Par : Node_Id;
2046 begin
2047 Item := First (Context_Items (Parent (N)));
2049 while Present (Item)
2050 and then Item /= N
2051 loop
2052 if Nkind (Item) = N_With_Clause
2053 and then Entity (Name (Item)) = Pack
2054 then
2055 Par := Nam;
2057 -- Find root library unit in with_clause
2059 while Nkind (Par) = N_Expanded_Name loop
2060 Par := Prefix (Par);
2061 end loop;
2063 if Is_Child_Unit (Entity (Original_Node (Par))) then
2064 Error_Msg_NE
2065 ("& is not directly visible", Par, Entity (Par));
2066 else
2067 return;
2068 end if;
2069 end if;
2071 Next (Item);
2072 end loop;
2074 -- On exit, package is not mentioned in a previous with_clause.
2075 -- Check if its prefix is.
2077 if Nkind (Nam) = N_Expanded_Name then
2078 Check_In_Previous_With_Clause (N, Prefix (Nam));
2080 elsif Pack /= Any_Id then
2081 Error_Msg_NE ("& is not visible", Nam, Pack);
2082 end if;
2083 end Check_In_Previous_With_Clause;
2085 ---------------------------------
2086 -- Check_Library_Unit_Renaming --
2087 ---------------------------------
2089 procedure Check_Library_Unit_Renaming (N : Node_Id; Old_E : Entity_Id) is
2090 New_E : Entity_Id;
2092 begin
2093 if Nkind (Parent (N)) /= N_Compilation_Unit then
2094 return;
2096 elsif Scope (Old_E) /= Standard_Standard
2097 and then not Is_Child_Unit (Old_E)
2098 then
2099 Error_Msg_N ("renamed unit must be a library unit", Name (N));
2101 -- Entities defined in Standard (operators and boolean literals) cannot
2102 -- be renamed as library units.
2104 elsif Scope (Old_E) = Standard_Standard
2105 and then Sloc (Old_E) = Standard_Location
2106 then
2107 Error_Msg_N ("renamed unit must be a library unit", Name (N));
2109 elsif Present (Parent_Spec (N))
2110 and then Nkind (Unit (Parent_Spec (N))) = N_Generic_Package_Declaration
2111 and then not Is_Child_Unit (Old_E)
2112 then
2113 Error_Msg_N
2114 ("renamed unit must be a child unit of generic parent", Name (N));
2116 elsif Nkind (N) in N_Generic_Renaming_Declaration
2117 and then Nkind (Name (N)) = N_Expanded_Name
2118 and then Is_Generic_Instance (Entity (Prefix (Name (N))))
2119 and then Is_Generic_Unit (Old_E)
2120 then
2121 Error_Msg_N
2122 ("renamed generic unit must be a library unit", Name (N));
2124 elsif Ekind (Old_E) = E_Package
2125 or else Ekind (Old_E) = E_Generic_Package
2126 then
2127 -- Inherit categorization flags
2129 New_E := Defining_Entity (N);
2130 Set_Is_Pure (New_E, Is_Pure (Old_E));
2131 Set_Is_Preelaborated (New_E, Is_Preelaborated (Old_E));
2132 Set_Is_Remote_Call_Interface (New_E,
2133 Is_Remote_Call_Interface (Old_E));
2134 Set_Is_Remote_Types (New_E, Is_Remote_Types (Old_E));
2135 Set_Is_Shared_Passive (New_E, Is_Shared_Passive (Old_E));
2136 end if;
2137 end Check_Library_Unit_Renaming;
2139 ---------------
2140 -- End_Scope --
2141 ---------------
2143 procedure End_Scope is
2144 Id : Entity_Id;
2145 Prev : Entity_Id;
2146 Outer : Entity_Id;
2148 begin
2149 Id := First_Entity (Current_Scope);
2151 while Present (Id) loop
2152 -- An entity in the current scope is not necessarily the first one
2153 -- on its homonym chain. Find its predecessor if any,
2154 -- If it is an internal entity, it will not be in the visibility
2155 -- chain altogether, and there is nothing to unchain.
2157 if Id /= Current_Entity (Id) then
2158 Prev := Current_Entity (Id);
2159 while Present (Prev)
2160 and then Present (Homonym (Prev))
2161 and then Homonym (Prev) /= Id
2162 loop
2163 Prev := Homonym (Prev);
2164 end loop;
2166 -- Skip to end of loop if Id is not in the visibility chain
2168 if No (Prev) or else Homonym (Prev) /= Id then
2169 goto Next_Ent;
2170 end if;
2172 else
2173 Prev := Empty;
2174 end if;
2176 Outer := Homonym (Id);
2177 Set_Is_Immediately_Visible (Id, False);
2179 while Present (Outer) and then Scope (Outer) = Current_Scope loop
2180 Outer := Homonym (Outer);
2181 end loop;
2183 -- Reset homonym link of other entities, but do not modify link
2184 -- between entities in current scope, so that the back-end can have
2185 -- a proper count of local overloadings.
2187 if No (Prev) then
2188 Set_Name_Entity_Id (Chars (Id), Outer);
2190 elsif Scope (Prev) /= Scope (Id) then
2191 Set_Homonym (Prev, Outer);
2192 end if;
2194 <<Next_Ent>>
2195 Next_Entity (Id);
2196 end loop;
2198 -- If the scope generated freeze actions, place them before the
2199 -- current declaration and analyze them. Type declarations and
2200 -- the bodies of initialization procedures can generate such nodes.
2201 -- We follow the parent chain until we reach a list node, which is
2202 -- the enclosing list of declarations. If the list appears within
2203 -- a protected definition, move freeze nodes outside the protected
2204 -- type altogether.
2206 if Present
2207 (Scope_Stack.Table (Scope_Stack.Last).Pending_Freeze_Actions)
2208 then
2209 declare
2210 Decl : Node_Id;
2211 L : constant List_Id := Scope_Stack.Table
2212 (Scope_Stack.Last).Pending_Freeze_Actions;
2214 begin
2215 if Is_Itype (Current_Scope) then
2216 Decl := Associated_Node_For_Itype (Current_Scope);
2217 else
2218 Decl := Parent (Current_Scope);
2219 end if;
2221 Pop_Scope;
2223 while not (Is_List_Member (Decl))
2224 or else Nkind (Parent (Decl)) = N_Protected_Definition
2225 or else Nkind (Parent (Decl)) = N_Task_Definition
2226 loop
2227 Decl := Parent (Decl);
2228 end loop;
2230 Insert_List_Before_And_Analyze (Decl, L);
2231 end;
2233 else
2234 Pop_Scope;
2235 end if;
2237 end End_Scope;
2239 ---------------------
2240 -- End_Use_Clauses --
2241 ---------------------
2243 procedure End_Use_Clauses (Clause : Node_Id) is
2244 U : Node_Id;
2246 begin
2247 -- Remove Use_Type clauses first, because they affect the
2248 -- visibility of operators in subsequent used packages.
2250 U := Clause;
2251 while Present (U) loop
2252 if Nkind (U) = N_Use_Type_Clause then
2253 End_Use_Type (U);
2254 end if;
2256 Next_Use_Clause (U);
2257 end loop;
2259 U := Clause;
2260 while Present (U) loop
2261 if Nkind (U) = N_Use_Package_Clause then
2262 End_Use_Package (U);
2263 end if;
2265 Next_Use_Clause (U);
2266 end loop;
2267 end End_Use_Clauses;
2269 ---------------------
2270 -- End_Use_Package --
2271 ---------------------
2273 procedure End_Use_Package (N : Node_Id) is
2274 Pack_Name : Node_Id;
2275 Pack : Entity_Id;
2276 Id : Entity_Id;
2277 Elmt : Elmt_Id;
2279 function Is_Primitive_Operator
2280 (Op : Entity_Id;
2281 F : Entity_Id) return Boolean;
2282 -- Check whether Op is a primitive operator of a use-visible type
2284 ---------------------------
2285 -- Is_Primitive_Operator --
2286 ---------------------------
2288 function Is_Primitive_Operator
2289 (Op : Entity_Id;
2290 F : Entity_Id) return Boolean
2292 T : constant Entity_Id := Etype (F);
2294 begin
2295 return In_Use (T)
2296 and then Scope (T) = Scope (Op);
2297 end Is_Primitive_Operator;
2299 -- Start of processing for End_Use_Package
2301 begin
2302 Pack_Name := First (Names (N));
2304 while Present (Pack_Name) loop
2305 Pack := Entity (Pack_Name);
2307 if Ekind (Pack) = E_Package then
2309 if In_Open_Scopes (Pack) then
2310 null;
2312 elsif not Redundant_Use (Pack_Name) then
2313 Set_In_Use (Pack, False);
2314 Id := First_Entity (Pack);
2316 while Present (Id) loop
2318 -- Preserve use-visibility of operators that are primitive
2319 -- operators of a type that is use_visible through an active
2320 -- use_type clause.
2322 if Nkind (Id) = N_Defining_Operator_Symbol
2323 and then
2324 (Is_Primitive_Operator (Id, First_Formal (Id))
2325 or else
2326 (Present (Next_Formal (First_Formal (Id)))
2327 and then
2328 Is_Primitive_Operator
2329 (Id, Next_Formal (First_Formal (Id)))))
2330 then
2331 null;
2333 else
2334 Set_Is_Potentially_Use_Visible (Id, False);
2335 end if;
2337 if Is_Private_Type (Id)
2338 and then Present (Full_View (Id))
2339 then
2340 Set_Is_Potentially_Use_Visible (Full_View (Id), False);
2341 end if;
2343 Next_Entity (Id);
2344 end loop;
2346 if Present (Renamed_Object (Pack)) then
2347 Set_In_Use (Renamed_Object (Pack), False);
2348 end if;
2350 if Chars (Pack) = Name_System
2351 and then Scope (Pack) = Standard_Standard
2352 and then Present_System_Aux
2353 then
2354 Id := First_Entity (System_Aux_Id);
2356 while Present (Id) loop
2357 Set_Is_Potentially_Use_Visible (Id, False);
2359 if Is_Private_Type (Id)
2360 and then Present (Full_View (Id))
2361 then
2362 Set_Is_Potentially_Use_Visible (Full_View (Id), False);
2363 end if;
2365 Next_Entity (Id);
2366 end loop;
2368 Set_In_Use (System_Aux_Id, False);
2369 end if;
2371 else
2372 Set_Redundant_Use (Pack_Name, False);
2373 end if;
2375 end if;
2377 Next (Pack_Name);
2378 end loop;
2380 if Present (Hidden_By_Use_Clause (N)) then
2381 Elmt := First_Elmt (Hidden_By_Use_Clause (N));
2383 while Present (Elmt) loop
2384 Set_Is_Immediately_Visible (Node (Elmt));
2385 Next_Elmt (Elmt);
2386 end loop;
2388 Set_Hidden_By_Use_Clause (N, No_Elist);
2389 end if;
2390 end End_Use_Package;
2392 ------------------
2393 -- End_Use_Type --
2394 ------------------
2396 procedure End_Use_Type (N : Node_Id) is
2397 Id : Entity_Id;
2398 Op_List : Elist_Id;
2399 Elmt : Elmt_Id;
2400 T : Entity_Id;
2402 begin
2403 Id := First (Subtype_Marks (N));
2405 while Present (Id) loop
2407 -- A call to rtsfind may occur while analyzing a use_type clause,
2408 -- in which case the type marks are not resolved yet, and there is
2409 -- nothing to remove.
2411 if not Is_Entity_Name (Id)
2412 or else No (Entity (Id))
2413 then
2414 goto Continue;
2415 end if;
2417 T := Entity (Id);
2419 if T = Any_Type then
2420 null;
2422 -- Note that the use_Type clause may mention a subtype of the
2423 -- type whose primitive operations have been made visible. Here
2424 -- as elsewhere, it is the base type that matters for visibility.
2426 elsif In_Open_Scopes (Scope (Base_Type (T))) then
2427 null;
2429 elsif not Redundant_Use (Id) then
2430 Set_In_Use (T, False);
2431 Set_In_Use (Base_Type (T), False);
2432 Op_List := Collect_Primitive_Operations (T);
2433 Elmt := First_Elmt (Op_List);
2435 while Present (Elmt) loop
2437 if Nkind (Node (Elmt)) = N_Defining_Operator_Symbol then
2438 Set_Is_Potentially_Use_Visible (Node (Elmt), False);
2439 end if;
2441 Next_Elmt (Elmt);
2442 end loop;
2443 end if;
2445 <<Continue>>
2446 Next (Id);
2447 end loop;
2448 end End_Use_Type;
2450 ----------------------
2451 -- Find_Direct_Name --
2452 ----------------------
2454 procedure Find_Direct_Name (N : Node_Id) is
2455 E : Entity_Id;
2456 E2 : Entity_Id;
2457 Msg : Boolean;
2459 Inst : Entity_Id := Empty;
2460 -- Enclosing instance, if any
2462 Homonyms : Entity_Id;
2463 -- Saves start of homonym chain
2465 Nvis_Entity : Boolean;
2466 -- Set True to indicate that at there is at least one entity on the
2467 -- homonym chain which, while not visible, is visible enough from the
2468 -- user point of view to warrant an error message of "not visible"
2469 -- rather than undefined.
2471 Nvis_Is_Private_Subprg : Boolean := False;
2472 -- Ada 2005 (AI-262): Set True to indicate that a form of Beaujolais
2473 -- effect concerning library subprograms has been detected. Used to
2474 -- generate the precise error message.
2476 function From_Actual_Package (E : Entity_Id) return Boolean;
2477 -- Returns true if the entity is declared in a package that is
2478 -- an actual for a formal package of the current instance. Such an
2479 -- entity requires special handling because it may be use-visible
2480 -- but hides directly visible entities defined outside the instance.
2482 function Known_But_Invisible (E : Entity_Id) return Boolean;
2483 -- This function determines whether the entity E (which is not
2484 -- visible) can reasonably be considered to be known to the writer
2485 -- of the reference. This is a heuristic test, used only for the
2486 -- purposes of figuring out whether we prefer to complain that an
2487 -- entity is undefined or invisible (and identify the declaration
2488 -- of the invisible entity in the latter case). The point here is
2489 -- that we don't want to complain that something is invisible and
2490 -- then point to something entirely mysterious to the writer.
2492 procedure Nvis_Messages;
2493 -- Called if there are no visible entries for N, but there is at least
2494 -- one non-directly visible, or hidden declaration. This procedure
2495 -- outputs an appropriate set of error messages.
2497 procedure Undefined (Nvis : Boolean);
2498 -- This function is called if the current node has no corresponding
2499 -- visible entity or entities. The value set in Msg indicates whether
2500 -- an error message was generated (multiple error messages for the
2501 -- same variable are generally suppressed, see body for details).
2502 -- Msg is True if an error message was generated, False if not. This
2503 -- value is used by the caller to determine whether or not to output
2504 -- additional messages where appropriate. The parameter is set False
2505 -- to get the message "X is undefined", and True to get the message
2506 -- "X is not visible".
2508 -------------------------
2509 -- From_Actual_Package --
2510 -------------------------
2512 function From_Actual_Package (E : Entity_Id) return Boolean is
2513 Scop : constant Entity_Id := Scope (E);
2514 Act : Entity_Id;
2516 begin
2517 if not In_Instance then
2518 return False;
2519 else
2520 Inst := Current_Scope;
2522 while Present (Inst)
2523 and then Ekind (Inst) /= E_Package
2524 and then not Is_Generic_Instance (Inst)
2525 loop
2526 Inst := Scope (Inst);
2527 end loop;
2529 if No (Inst) then
2530 return False;
2531 end if;
2533 Act := First_Entity (Inst);
2535 while Present (Act) loop
2536 if Ekind (Act) = E_Package then
2538 -- Check for end of actuals list
2540 if Renamed_Object (Act) = Inst then
2541 return False;
2543 elsif Present (Associated_Formal_Package (Act))
2544 and then Renamed_Object (Act) = Scop
2545 then
2546 -- Entity comes from (instance of) formal package
2548 return True;
2550 else
2551 Next_Entity (Act);
2552 end if;
2554 else
2555 Next_Entity (Act);
2556 end if;
2557 end loop;
2559 return False;
2560 end if;
2561 end From_Actual_Package;
2563 -------------------------
2564 -- Known_But_Invisible --
2565 -------------------------
2567 function Known_But_Invisible (E : Entity_Id) return Boolean is
2568 Fname : File_Name_Type;
2570 begin
2571 -- Entities in Standard are always considered to be known
2573 if Sloc (E) <= Standard_Location then
2574 return True;
2576 -- An entity that does not come from source is always considered
2577 -- to be unknown, since it is an artifact of code expansion.
2579 elsif not Comes_From_Source (E) then
2580 return False;
2582 -- In gnat internal mode, we consider all entities known
2584 elsif GNAT_Mode then
2585 return True;
2586 end if;
2588 -- Here we have an entity that is not from package Standard, and
2589 -- which comes from Source. See if it comes from an internal file.
2591 Fname := Unit_File_Name (Get_Source_Unit (E));
2593 -- Case of from internal file
2595 if Is_Internal_File_Name (Fname) then
2597 -- Private part entities in internal files are never considered
2598 -- to be known to the writer of normal application code.
2600 if Is_Hidden (E) then
2601 return False;
2602 end if;
2604 -- Entities from System packages other than System and
2605 -- System.Storage_Elements are not considered to be known.
2606 -- System.Auxxxx files are also considered known to the user.
2608 -- Should refine this at some point to generally distinguish
2609 -- between known and unknown internal files ???
2611 Get_Name_String (Fname);
2613 return
2614 Name_Len < 2
2615 or else
2616 Name_Buffer (1 .. 2) /= "s-"
2617 or else
2618 Name_Buffer (3 .. 8) = "stoele"
2619 or else
2620 Name_Buffer (3 .. 5) = "aux";
2622 -- If not an internal file, then entity is definitely known,
2623 -- even if it is in a private part (the message generated will
2624 -- note that it is in a private part)
2626 else
2627 return True;
2628 end if;
2629 end Known_But_Invisible;
2631 -------------------
2632 -- Nvis_Messages --
2633 -------------------
2635 procedure Nvis_Messages is
2636 Comp_Unit : Node_Id;
2637 Ent : Entity_Id;
2638 Hidden : Boolean := False;
2639 Item : Node_Id;
2641 begin
2642 -- Ada 2005 (AI-262): Generate a precise error concerning the
2643 -- Beaujolais effect that was previously detected
2645 if Nvis_Is_Private_Subprg then
2647 pragma Assert (Nkind (E2) = N_Defining_Identifier
2648 and then Ekind (E2) = E_Function
2649 and then Scope (E2) = Standard_Standard
2650 and then Has_Private_With (E2));
2652 -- Find the sloc corresponding to the private with'ed unit
2654 Comp_Unit := Cunit (Current_Sem_Unit);
2655 Item := First (Context_Items (Comp_Unit));
2656 Error_Msg_Sloc := No_Location;
2658 while Present (Item) loop
2659 if Nkind (Item) = N_With_Clause
2660 and then Private_Present (Item)
2661 and then Entity (Name (Item)) = E2
2662 then
2663 Error_Msg_Sloc := Sloc (Item);
2664 exit;
2665 end if;
2667 Next (Item);
2668 end loop;
2670 pragma Assert (Error_Msg_Sloc /= No_Location);
2672 Error_Msg_N ("(Ada 2005): hidden by private with clause #", N);
2673 return;
2674 end if;
2676 Undefined (Nvis => True);
2678 if Msg then
2680 -- First loop does hidden declarations
2682 Ent := Homonyms;
2683 while Present (Ent) loop
2684 if Is_Potentially_Use_Visible (Ent) then
2686 if not Hidden then
2687 Error_Msg_N ("multiple use clauses cause hiding!", N);
2688 Hidden := True;
2689 end if;
2691 Error_Msg_Sloc := Sloc (Ent);
2692 Error_Msg_N ("hidden declaration#!", N);
2693 end if;
2695 Ent := Homonym (Ent);
2696 end loop;
2698 -- If we found hidden declarations, then that's enough, don't
2699 -- bother looking for non-visible declarations as well.
2701 if Hidden then
2702 return;
2703 end if;
2705 -- Second loop does non-directly visible declarations
2707 Ent := Homonyms;
2708 while Present (Ent) loop
2709 if not Is_Potentially_Use_Visible (Ent) then
2711 -- Do not bother the user with unknown entities
2713 if not Known_But_Invisible (Ent) then
2714 goto Continue;
2715 end if;
2717 Error_Msg_Sloc := Sloc (Ent);
2719 -- Output message noting that there is a non-visible
2720 -- declaration, distinguishing the private part case.
2722 if Is_Hidden (Ent) then
2723 Error_Msg_N ("non-visible (private) declaration#!", N);
2724 else
2725 Error_Msg_N ("non-visible declaration#!", N);
2727 if Is_Compilation_Unit (Ent)
2728 and then
2729 Nkind (Parent (Parent (N))) = N_Use_Package_Clause
2730 then
2731 Error_Msg_NE
2732 ("\possibly missing with_clause for&", N, Ent);
2733 end if;
2734 end if;
2736 -- Set entity and its containing package as referenced. We
2737 -- can't be sure of this, but this seems a better choice
2738 -- to avoid unused entity messages.
2740 if Comes_From_Source (Ent) then
2741 Set_Referenced (Ent);
2742 Set_Referenced (Cunit_Entity (Get_Source_Unit (Ent)));
2743 end if;
2744 end if;
2746 <<Continue>>
2747 Ent := Homonym (Ent);
2748 end loop;
2750 end if;
2751 end Nvis_Messages;
2753 ---------------
2754 -- Undefined --
2755 ---------------
2757 procedure Undefined (Nvis : Boolean) is
2758 Emsg : Error_Msg_Id;
2760 begin
2761 -- We should never find an undefined internal name. If we do, then
2762 -- see if we have previous errors. If so, ignore on the grounds that
2763 -- it is probably a cascaded message (e.g. a block label from a badly
2764 -- formed block). If no previous errors, then we have a real internal
2765 -- error of some kind so raise an exception.
2767 if Is_Internal_Name (Chars (N)) then
2768 if Total_Errors_Detected /= 0 then
2769 return;
2770 else
2771 raise Program_Error;
2772 end if;
2773 end if;
2775 -- A very specialized error check, if the undefined variable is
2776 -- a case tag, and the case type is an enumeration type, check
2777 -- for a possible misspelling, and if so, modify the identifier
2779 -- Named aggregate should also be handled similarly ???
2781 if Nkind (N) = N_Identifier
2782 and then Nkind (Parent (N)) = N_Case_Statement_Alternative
2783 then
2784 Get_Name_String (Chars (N));
2786 declare
2787 Case_Str : constant String := Name_Buffer (1 .. Name_Len);
2788 Case_Stm : constant Node_Id := Parent (Parent (N));
2789 Case_Typ : constant Entity_Id := Etype (Expression (Case_Stm));
2791 Lit : Node_Id;
2793 begin
2794 if Is_Enumeration_Type (Case_Typ)
2795 and then Case_Typ /= Standard_Character
2796 and then Case_Typ /= Standard_Wide_Character
2797 and then Case_Typ /= Standard_Wide_Wide_Character
2798 then
2799 Lit := First_Literal (Case_Typ);
2800 Get_Name_String (Chars (Lit));
2802 if Chars (Lit) /= Chars (N)
2803 and then Is_Bad_Spelling_Of
2804 (Case_Str, Name_Buffer (1 .. Name_Len))
2805 then
2806 Error_Msg_Node_2 := Lit;
2807 Error_Msg_N
2808 ("& is undefined, assume misspelling of &", N);
2809 Rewrite (N, New_Occurrence_Of (Lit, Sloc (N)));
2810 return;
2811 end if;
2813 Lit := Next_Literal (Lit);
2814 end if;
2815 end;
2816 end if;
2818 -- Normal processing
2820 Set_Entity (N, Any_Id);
2821 Set_Etype (N, Any_Type);
2823 -- We use the table Urefs to keep track of entities for which we
2824 -- have issued errors for undefined references. Multiple errors
2825 -- for a single name are normally suppressed, however we modify
2826 -- the error message to alert the programmer to this effect.
2828 for J in Urefs.First .. Urefs.Last loop
2829 if Chars (N) = Chars (Urefs.Table (J).Node) then
2830 if Urefs.Table (J).Err /= No_Error_Msg
2831 and then Sloc (N) /= Urefs.Table (J).Loc
2832 then
2833 Error_Msg_Node_1 := Urefs.Table (J).Node;
2835 if Urefs.Table (J).Nvis then
2836 Change_Error_Text (Urefs.Table (J).Err,
2837 "& is not visible (more references follow)");
2838 else
2839 Change_Error_Text (Urefs.Table (J).Err,
2840 "& is undefined (more references follow)");
2841 end if;
2843 Urefs.Table (J).Err := No_Error_Msg;
2844 end if;
2846 -- Although we will set Msg False, and thus suppress the
2847 -- message, we also set Error_Posted True, to avoid any
2848 -- cascaded messages resulting from the undefined reference.
2850 Msg := False;
2851 Set_Error_Posted (N, True);
2852 return;
2853 end if;
2854 end loop;
2856 -- If entry not found, this is first undefined occurrence
2858 if Nvis then
2859 Error_Msg_N ("& is not visible!", N);
2860 Emsg := Get_Msg_Id;
2862 else
2863 Error_Msg_N ("& is undefined!", N);
2864 Emsg := Get_Msg_Id;
2866 -- A very bizarre special check, if the undefined identifier
2867 -- is put or put_line, then add a special error message (since
2868 -- this is a very common error for beginners to make).
2870 if Chars (N) = Name_Put or else Chars (N) = Name_Put_Line then
2871 Error_Msg_N ("\possible missing with of 'Text_'I'O!", N);
2872 end if;
2874 -- Now check for possible misspellings
2876 Get_Name_String (Chars (N));
2878 declare
2879 E : Entity_Id;
2880 Ematch : Entity_Id := Empty;
2882 Last_Name_Id : constant Name_Id :=
2883 Name_Id (Nat (First_Name_Id) +
2884 Name_Entries_Count - 1);
2886 S : constant String (1 .. Name_Len) :=
2887 Name_Buffer (1 .. Name_Len);
2889 begin
2890 for N in First_Name_Id .. Last_Name_Id loop
2891 E := Get_Name_Entity_Id (N);
2893 if Present (E)
2894 and then (Is_Immediately_Visible (E)
2895 or else
2896 Is_Potentially_Use_Visible (E))
2897 then
2898 Get_Name_String (N);
2900 if Is_Bad_Spelling_Of
2901 (Name_Buffer (1 .. Name_Len), S)
2902 then
2903 Ematch := E;
2904 exit;
2905 end if;
2906 end if;
2907 end loop;
2909 if Present (Ematch) then
2910 Error_Msg_NE ("\possible misspelling of&", N, Ematch);
2911 end if;
2912 end;
2913 end if;
2915 -- Make entry in undefined references table unless the full
2916 -- errors switch is set, in which case by refraining from
2917 -- generating the table entry, we guarantee that we get an
2918 -- error message for every undefined reference.
2920 if not All_Errors_Mode then
2921 Urefs.Increment_Last;
2922 Urefs.Table (Urefs.Last).Node := N;
2923 Urefs.Table (Urefs.Last).Err := Emsg;
2924 Urefs.Table (Urefs.Last).Nvis := Nvis;
2925 Urefs.Table (Urefs.Last).Loc := Sloc (N);
2926 end if;
2928 Msg := True;
2929 end Undefined;
2931 -- Start of processing for Find_Direct_Name
2933 begin
2934 -- If the entity pointer is already set, this is an internal node, or
2935 -- a node that is analyzed more than once, after a tree modification.
2936 -- In such a case there is no resolution to perform, just set the type.
2938 if Present (Entity (N)) then
2939 if Is_Type (Entity (N)) then
2940 Set_Etype (N, Entity (N));
2942 else
2943 declare
2944 Entyp : constant Entity_Id := Etype (Entity (N));
2946 begin
2947 -- One special case here. If the Etype field is already set,
2948 -- and references the packed array type corresponding to the
2949 -- etype of the referenced entity, then leave it alone. This
2950 -- happens for trees generated from Exp_Pakd, where expressions
2951 -- can be deliberately "mis-typed" to the packed array type.
2953 if Is_Array_Type (Entyp)
2954 and then Is_Packed (Entyp)
2955 and then Present (Etype (N))
2956 and then Etype (N) = Packed_Array_Type (Entyp)
2957 then
2958 null;
2960 -- If not that special case, then just reset the Etype
2962 else
2963 Set_Etype (N, Etype (Entity (N)));
2964 end if;
2965 end;
2966 end if;
2968 return;
2969 end if;
2971 -- Here if Entity pointer was not set, we need full visibility analysis
2972 -- First we generate debugging output if the debug E flag is set.
2974 if Debug_Flag_E then
2975 Write_Str ("Looking for ");
2976 Write_Name (Chars (N));
2977 Write_Eol;
2978 end if;
2980 Homonyms := Current_Entity (N);
2981 Nvis_Entity := False;
2983 E := Homonyms;
2984 while Present (E) loop
2986 -- If entity is immediately visible or potentially use
2987 -- visible, then process the entity and we are done.
2989 if Is_Immediately_Visible (E) then
2990 goto Immediately_Visible_Entity;
2992 elsif Is_Potentially_Use_Visible (E) then
2993 goto Potentially_Use_Visible_Entity;
2995 -- Note if a known but invisible entity encountered
2997 elsif Known_But_Invisible (E) then
2998 Nvis_Entity := True;
2999 end if;
3001 -- Move to next entity in chain and continue search
3003 E := Homonym (E);
3004 end loop;
3006 -- If no entries on homonym chain that were potentially visible,
3007 -- and no entities reasonably considered as non-visible, then
3008 -- we have a plain undefined reference, with no additional
3009 -- explanation required!
3011 if not Nvis_Entity then
3012 Undefined (Nvis => False);
3014 -- Otherwise there is at least one entry on the homonym chain that
3015 -- is reasonably considered as being known and non-visible.
3017 else
3018 Nvis_Messages;
3019 end if;
3021 return;
3023 -- Processing for a potentially use visible entry found. We must search
3024 -- the rest of the homonym chain for two reasons. First, if there is a
3025 -- directly visible entry, then none of the potentially use-visible
3026 -- entities are directly visible (RM 8.4(10)). Second, we need to check
3027 -- for the case of multiple potentially use-visible entries hiding one
3028 -- another and as a result being non-directly visible (RM 8.4(11)).
3030 <<Potentially_Use_Visible_Entity>> declare
3031 Only_One_Visible : Boolean := True;
3032 All_Overloadable : Boolean := Is_Overloadable (E);
3034 begin
3035 E2 := Homonym (E);
3037 while Present (E2) loop
3038 if Is_Immediately_Visible (E2) then
3040 -- If the use-visible entity comes from the actual for a
3041 -- formal package, it hides a directly visible entity from
3042 -- outside the instance.
3044 if From_Actual_Package (E)
3045 and then Scope_Depth (E2) < Scope_Depth (Inst)
3046 then
3047 goto Found;
3048 else
3049 E := E2;
3050 goto Immediately_Visible_Entity;
3051 end if;
3053 elsif Is_Potentially_Use_Visible (E2) then
3054 Only_One_Visible := False;
3055 All_Overloadable := All_Overloadable and Is_Overloadable (E2);
3057 -- Ada 2005 (AI-262): Protect against a form of Beujolais effect
3058 -- that can occurr in private_with clauses. Example:
3060 -- with A;
3061 -- private with B; package A is
3062 -- package C is function B return Integer;
3063 -- use A; end A;
3064 -- V1 : Integer := B;
3065 -- private function B return Integer;
3066 -- V2 : Integer := B;
3067 -- end C;
3069 -- V1 resolves to A.B, but V2 resolves to library unit B
3071 elsif Ekind (E2) = E_Function
3072 and then Scope (E2) = Standard_Standard
3073 and then Has_Private_With (E2)
3074 then
3075 Only_One_Visible := False;
3076 All_Overloadable := False;
3077 Nvis_Is_Private_Subprg := True;
3078 exit;
3079 end if;
3081 E2 := Homonym (E2);
3082 end loop;
3084 -- On falling through this loop, we have checked that there are no
3085 -- immediately visible entities. Only_One_Visible is set if exactly
3086 -- one potentially use visible entity exists. All_Overloadable is
3087 -- set if all the potentially use visible entities are overloadable.
3088 -- The condition for legality is that either there is one potentially
3089 -- use visible entity, or if there is more than one, then all of them
3090 -- are overloadable.
3092 if Only_One_Visible or All_Overloadable then
3093 goto Found;
3095 -- If there is more than one potentially use-visible entity and at
3096 -- least one of them non-overloadable, we have an error (RM 8.4(11).
3097 -- Note that E points to the first such entity on the homonym list.
3098 -- Special case: if one of the entities is declared in an actual
3099 -- package, it was visible in the generic, and takes precedence over
3100 -- other entities that are potentially use-visible. Same if it is
3101 -- declared in a local instantiation of the current instance.
3103 else
3104 if In_Instance then
3105 Inst := Current_Scope;
3107 -- Find current instance
3109 while Present (Inst)
3110 and then Inst /= Standard_Standard
3111 loop
3112 if Is_Generic_Instance (Inst) then
3113 exit;
3114 end if;
3116 Inst := Scope (Inst);
3117 end loop;
3119 E2 := E;
3121 while Present (E2) loop
3122 if From_Actual_Package (E2)
3123 or else
3124 (Is_Generic_Instance (Scope (E2))
3125 and then Scope_Depth (Scope (E2)) > Scope_Depth (Inst))
3126 then
3127 E := E2;
3128 goto Found;
3129 end if;
3131 E2 := Homonym (E2);
3132 end loop;
3134 Nvis_Messages;
3135 return;
3137 else
3138 Nvis_Messages;
3139 return;
3140 end if;
3141 end if;
3142 end;
3144 -- Come here with E set to the first immediately visible entity on
3145 -- the homonym chain. This is the one we want unless there is another
3146 -- immediately visible entity further on in the chain for a more
3147 -- inner scope (RM 8.3(8)).
3149 <<Immediately_Visible_Entity>> declare
3150 Level : Int;
3151 Scop : Entity_Id;
3153 begin
3154 -- Find scope level of initial entity. When compiling through
3155 -- Rtsfind, the previous context is not completely invisible, and
3156 -- an outer entity may appear on the chain, whose scope is below
3157 -- the entry for Standard that delimits the current scope stack.
3158 -- Indicate that the level for this spurious entry is outside of
3159 -- the current scope stack.
3161 Level := Scope_Stack.Last;
3162 loop
3163 Scop := Scope_Stack.Table (Level).Entity;
3164 exit when Scop = Scope (E);
3165 Level := Level - 1;
3166 exit when Scop = Standard_Standard;
3167 end loop;
3169 -- Now search remainder of homonym chain for more inner entry
3170 -- If the entity is Standard itself, it has no scope, and we
3171 -- compare it with the stack entry directly.
3173 E2 := Homonym (E);
3174 while Present (E2) loop
3175 if Is_Immediately_Visible (E2) then
3176 for J in Level + 1 .. Scope_Stack.Last loop
3177 if Scope_Stack.Table (J).Entity = Scope (E2)
3178 or else Scope_Stack.Table (J).Entity = E2
3179 then
3180 Level := J;
3181 E := E2;
3182 exit;
3183 end if;
3184 end loop;
3185 end if;
3187 E2 := Homonym (E2);
3188 end loop;
3190 -- At the end of that loop, E is the innermost immediately
3191 -- visible entity, so we are all set.
3192 end;
3194 -- Come here with entity found, and stored in E
3196 <<Found>> begin
3198 if Comes_From_Source (N)
3199 and then Is_Remote_Access_To_Subprogram_Type (E)
3200 and then Expander_Active
3201 then
3202 Rewrite (N,
3203 New_Occurrence_Of (Equivalent_Type (E), Sloc (N)));
3204 return;
3205 end if;
3207 Set_Entity (N, E);
3208 -- Why no Style_Check here???
3210 if Is_Type (E) then
3211 Set_Etype (N, E);
3212 else
3213 Set_Etype (N, Get_Full_View (Etype (E)));
3214 end if;
3216 if Debug_Flag_E then
3217 Write_Str (" found ");
3218 Write_Entity_Info (E, " ");
3219 end if;
3221 -- If the Ekind of the entity is Void, it means that all homonyms
3222 -- are hidden from all visibility (RM 8.3(5,14-20)). However, this
3223 -- test is skipped if the current scope is a record and the name is
3224 -- a pragma argument expression (case of Atomic and Volatile pragmas
3225 -- and possibly other similar pragmas added later, which are allowed
3226 -- to reference components in the current record).
3228 if Ekind (E) = E_Void
3229 and then
3230 (not Is_Record_Type (Current_Scope)
3231 or else Nkind (Parent (N)) /= N_Pragma_Argument_Association)
3232 then
3233 Premature_Usage (N);
3235 -- If the entity is overloadable, collect all interpretations
3236 -- of the name for subsequent overload resolution. We optimize
3237 -- a bit here to do this only if we have an overloadable entity
3238 -- that is not on its own on the homonym chain.
3240 elsif Is_Overloadable (E)
3241 and then (Present (Homonym (E)) or else Current_Entity (N) /= E)
3242 then
3243 Collect_Interps (N);
3245 -- If no homonyms were visible, the entity is unambiguous
3247 if not Is_Overloaded (N) then
3248 Generate_Reference (E, N);
3249 end if;
3251 -- Case of non-overloadable entity, set the entity providing that
3252 -- we do not have the case of a discriminant reference within a
3253 -- default expression. Such references are replaced with the
3254 -- corresponding discriminal, which is the formal corresponding to
3255 -- to the discriminant in the initialization procedure.
3257 else
3258 -- Entity is unambiguous, indicate that it is referenced here
3259 -- One slightly odd case is that we do not want to set the
3260 -- Referenced flag if the entity is a label, and the identifier
3261 -- is the label in the source, since this is not a reference
3262 -- from the point of view of the user
3264 if Nkind (Parent (N)) = N_Label then
3265 declare
3266 R : constant Boolean := Referenced (E);
3268 begin
3269 Generate_Reference (E, N);
3270 Set_Referenced (E, R);
3271 end;
3273 -- Normal case, not a label. Generate reference
3275 else
3276 Generate_Reference (E, N);
3277 end if;
3279 -- Set Entity, with style check if need be. If this is a
3280 -- discriminant reference, it must be replaced by the
3281 -- corresponding discriminal, that is to say the parameter
3282 -- of the initialization procedure that corresponds to the
3283 -- discriminant. If this replacement is being performed, there
3284 -- is no style check to perform.
3286 -- This replacement must not be done if we are currently
3287 -- processing a generic spec or body, because the discriminal
3288 -- has not been not generated in this case.
3290 if not In_Default_Expression
3291 or else Ekind (E) /= E_Discriminant
3292 or else Inside_A_Generic
3293 then
3294 Set_Entity_With_Style_Check (N, E);
3296 -- The replacement is not done either for a task discriminant that
3297 -- appears in a default expression of an entry parameter. See
3298 -- Expand_Discriminant in exp_ch2 for details on their handling.
3300 elsif Is_Concurrent_Type (Scope (E)) then
3301 declare
3302 P : Node_Id := Parent (N);
3304 begin
3305 while Present (P)
3306 and then Nkind (P) /= N_Parameter_Specification
3307 and then Nkind (P) /= N_Component_Declaration
3308 loop
3309 P := Parent (P);
3310 end loop;
3312 if Present (P)
3313 and then Nkind (P) = N_Parameter_Specification
3314 then
3315 null;
3316 else
3317 Set_Entity (N, Discriminal (E));
3318 end if;
3319 end;
3321 -- Otherwise, this is a discriminant in a context in which
3322 -- it is a reference to the corresponding parameter of the
3323 -- init proc for the enclosing type.
3325 else
3326 Set_Entity (N, Discriminal (E));
3327 end if;
3328 end if;
3329 end;
3330 end Find_Direct_Name;
3332 ------------------------
3333 -- Find_Expanded_Name --
3334 ------------------------
3336 -- This routine searches the homonym chain of the entity until it finds
3337 -- an entity declared in the scope denoted by the prefix. If the entity
3338 -- is private, it may nevertheless be immediately visible, if we are in
3339 -- the scope of its declaration.
3341 procedure Find_Expanded_Name (N : Node_Id) is
3342 Selector : constant Node_Id := Selector_Name (N);
3343 Candidate : Entity_Id := Empty;
3344 P_Name : Entity_Id;
3345 O_Name : Entity_Id;
3346 Id : Entity_Id;
3348 begin
3349 P_Name := Entity (Prefix (N));
3350 O_Name := P_Name;
3352 -- If the prefix is a renamed package, look for the entity
3353 -- in the original package.
3355 if Ekind (P_Name) = E_Package
3356 and then Present (Renamed_Object (P_Name))
3357 then
3358 P_Name := Renamed_Object (P_Name);
3360 -- Rewrite node with entity field pointing to renamed object
3362 Rewrite (Prefix (N), New_Copy (Prefix (N)));
3363 Set_Entity (Prefix (N), P_Name);
3365 -- If the prefix is an object of a concurrent type, look for
3366 -- the entity in the associated task or protected type.
3368 elsif Is_Concurrent_Type (Etype (P_Name)) then
3369 P_Name := Etype (P_Name);
3370 end if;
3372 Id := Current_Entity (Selector);
3374 while Present (Id) loop
3376 if Scope (Id) = P_Name then
3377 Candidate := Id;
3379 if Is_Child_Unit (Id) then
3380 exit when Is_Visible_Child_Unit (Id)
3381 or else Is_Immediately_Visible (Id);
3383 else
3384 exit when not Is_Hidden (Id)
3385 or else Is_Immediately_Visible (Id);
3386 end if;
3387 end if;
3389 Id := Homonym (Id);
3390 end loop;
3392 if No (Id)
3393 and then (Ekind (P_Name) = E_Procedure
3394 or else
3395 Ekind (P_Name) = E_Function)
3396 and then Is_Generic_Instance (P_Name)
3397 then
3398 -- Expanded name denotes entity in (instance of) generic subprogram.
3399 -- The entity may be in the subprogram instance, or may denote one of
3400 -- the formals, which is declared in the enclosing wrapper package.
3402 P_Name := Scope (P_Name);
3404 Id := Current_Entity (Selector);
3405 while Present (Id) loop
3406 exit when Scope (Id) = P_Name;
3407 Id := Homonym (Id);
3408 end loop;
3409 end if;
3411 if No (Id) or else Chars (Id) /= Chars (Selector) then
3412 Set_Etype (N, Any_Type);
3414 -- If we are looking for an entity defined in System, try to
3415 -- find it in the child package that may have been provided as
3416 -- an extension to System. The Extend_System pragma will have
3417 -- supplied the name of the extension, which may have to be loaded.
3419 if Chars (P_Name) = Name_System
3420 and then Scope (P_Name) = Standard_Standard
3421 and then Present (System_Extend_Unit)
3422 and then Present_System_Aux (N)
3423 then
3424 Set_Entity (Prefix (N), System_Aux_Id);
3425 Find_Expanded_Name (N);
3426 return;
3428 elsif Nkind (Selector) = N_Operator_Symbol
3429 and then Has_Implicit_Operator (N)
3430 then
3431 -- There is an implicit instance of the predefined operator in
3432 -- the given scope. The operator entity is defined in Standard.
3433 -- Has_Implicit_Operator makes the node into an Expanded_Name.
3435 return;
3437 elsif Nkind (Selector) = N_Character_Literal
3438 and then Has_Implicit_Character_Literal (N)
3439 then
3440 -- If there is no literal defined in the scope denoted by the
3441 -- prefix, the literal may belong to (a type derived from)
3442 -- Standard_Character, for which we have no explicit literals.
3444 return;
3446 else
3447 -- If the prefix is a single concurrent object, use its
3448 -- name in the error message, rather than that of the
3449 -- anonymous type.
3451 if Is_Concurrent_Type (P_Name)
3452 and then Is_Internal_Name (Chars (P_Name))
3453 then
3454 Error_Msg_Node_2 := Entity (Prefix (N));
3455 else
3456 Error_Msg_Node_2 := P_Name;
3457 end if;
3459 if P_Name = System_Aux_Id then
3460 P_Name := Scope (P_Name);
3461 Set_Entity (Prefix (N), P_Name);
3462 end if;
3464 if Present (Candidate) then
3466 if Is_Child_Unit (Candidate) then
3467 Error_Msg_N
3468 ("missing with_clause for child unit &", Selector);
3469 else
3470 Error_Msg_NE ("& is not a visible entity of&", N, Selector);
3471 end if;
3473 else
3474 -- Within the instantiation of a child unit, the prefix may
3475 -- denote the parent instance, but the selector has the
3476 -- name of the original child. Find whether we are within
3477 -- the corresponding instance, and get the proper entity, which
3478 -- can only be an enclosing scope.
3480 if O_Name /= P_Name
3481 and then In_Open_Scopes (P_Name)
3482 and then Is_Generic_Instance (P_Name)
3483 then
3484 declare
3485 S : Entity_Id := Current_Scope;
3486 P : Entity_Id;
3488 begin
3489 for J in reverse 0 .. Scope_Stack.Last loop
3490 S := Scope_Stack.Table (J).Entity;
3492 exit when S = Standard_Standard;
3494 if Ekind (S) = E_Function
3495 or else Ekind (S) = E_Package
3496 or else Ekind (S) = E_Procedure
3497 then
3498 P := Generic_Parent (Specification
3499 (Unit_Declaration_Node (S)));
3501 if Present (P)
3502 and then Chars (Scope (P)) = Chars (O_Name)
3503 and then Chars (P) = Chars (Selector)
3504 then
3505 Id := S;
3506 goto found;
3507 end if;
3508 end if;
3510 end loop;
3511 end;
3512 end if;
3514 if Chars (P_Name) = Name_Ada
3515 and then Scope (P_Name) = Standard_Standard
3516 then
3517 Error_Msg_Node_2 := Selector;
3518 Error_Msg_NE ("missing with for `&.&`", N, P_Name);
3520 -- If this is a selection from a dummy package, then
3521 -- suppress the error message, of course the entity
3522 -- is missing if the package is missing!
3524 elsif Sloc (Error_Msg_Node_2) = No_Location then
3525 null;
3527 -- Here we have the case of an undefined component
3529 else
3531 Error_Msg_NE ("& not declared in&", N, Selector);
3533 -- Check for misspelling of some entity in prefix
3535 Id := First_Entity (P_Name);
3536 Get_Name_String (Chars (Selector));
3538 declare
3539 S : constant String (1 .. Name_Len) :=
3540 Name_Buffer (1 .. Name_Len);
3541 begin
3542 while Present (Id) loop
3543 Get_Name_String (Chars (Id));
3544 if Is_Bad_Spelling_Of
3545 (Name_Buffer (1 .. Name_Len), S)
3546 and then not Is_Internal_Name (Chars (Id))
3547 then
3548 Error_Msg_NE
3549 ("possible misspelling of&", Selector, Id);
3550 exit;
3551 end if;
3553 Next_Entity (Id);
3554 end loop;
3555 end;
3557 -- Specialize the message if this may be an instantiation
3558 -- of a child unit that was not mentioned in the context.
3560 if Nkind (Parent (N)) = N_Package_Instantiation
3561 and then Is_Generic_Instance (Entity (Prefix (N)))
3562 and then Is_Compilation_Unit
3563 (Generic_Parent (Parent (Entity (Prefix (N)))))
3564 then
3565 Error_Msg_NE
3566 ("\possible missing with clause on child unit&",
3567 N, Selector);
3568 end if;
3569 end if;
3570 end if;
3572 Id := Any_Id;
3573 end if;
3574 end if;
3576 <<found>>
3577 if Comes_From_Source (N)
3578 and then Is_Remote_Access_To_Subprogram_Type (Id)
3579 then
3580 Id := Equivalent_Type (Id);
3581 Set_Chars (Selector, Chars (Id));
3582 end if;
3584 -- Ada 2005 (AI-50217): Check usage of entities in limited withed units
3586 if Ekind (P_Name) = E_Package
3587 and then From_With_Type (P_Name)
3588 then
3589 if From_With_Type (Id)
3590 or else Is_Type (Id)
3591 or else Ekind (Id) = E_Package
3592 then
3593 null;
3594 else
3595 Error_Msg_N
3596 ("limited withed package can only be used to access "
3597 & " incomplete types",
3599 end if;
3600 end if;
3602 if Is_Task_Type (P_Name)
3603 and then ((Ekind (Id) = E_Entry
3604 and then Nkind (Parent (N)) /= N_Attribute_Reference)
3605 or else
3606 (Ekind (Id) = E_Entry_Family
3607 and then
3608 Nkind (Parent (Parent (N))) /= N_Attribute_Reference))
3609 then
3610 -- It is an entry call after all, either to the current task
3611 -- (which will deadlock) or to an enclosing task.
3613 Analyze_Selected_Component (N);
3614 return;
3615 end if;
3617 Change_Selected_Component_To_Expanded_Name (N);
3619 -- Do style check and generate reference, but skip both steps if this
3620 -- entity has homonyms, since we may not have the right homonym set
3621 -- yet. The proper homonym will be set during the resolve phase.
3623 if Has_Homonym (Id) then
3624 Set_Entity (N, Id);
3625 else
3626 Set_Entity_With_Style_Check (N, Id);
3627 Generate_Reference (Id, N);
3628 end if;
3630 if Is_Type (Id) then
3631 Set_Etype (N, Id);
3632 else
3633 Set_Etype (N, Get_Full_View (Etype (Id)));
3634 end if;
3636 -- If the Ekind of the entity is Void, it means that all homonyms
3637 -- are hidden from all visibility (RM 8.3(5,14-20)).
3639 if Ekind (Id) = E_Void then
3640 Premature_Usage (N);
3642 elsif Is_Overloadable (Id)
3643 and then Present (Homonym (Id))
3644 then
3645 declare
3646 H : Entity_Id := Homonym (Id);
3648 begin
3649 while Present (H) loop
3650 if Scope (H) = Scope (Id)
3651 and then
3652 (not Is_Hidden (H)
3653 or else Is_Immediately_Visible (H))
3654 then
3655 Collect_Interps (N);
3656 exit;
3657 end if;
3659 H := Homonym (H);
3660 end loop;
3662 -- If an extension of System is present, collect possible
3663 -- explicit overloadings declared in the extension.
3665 if Chars (P_Name) = Name_System
3666 and then Scope (P_Name) = Standard_Standard
3667 and then Present (System_Extend_Unit)
3668 and then Present_System_Aux (N)
3669 then
3670 H := Current_Entity (Id);
3672 while Present (H) loop
3673 if Scope (H) = System_Aux_Id then
3674 Add_One_Interp (N, H, Etype (H));
3675 end if;
3677 H := Homonym (H);
3678 end loop;
3679 end if;
3680 end;
3681 end if;
3683 if Nkind (Selector_Name (N)) = N_Operator_Symbol
3684 and then Scope (Id) /= Standard_Standard
3685 then
3686 -- In addition to user-defined operators in the given scope,
3687 -- there may be an implicit instance of the predefined
3688 -- operator. The operator (defined in Standard) is found
3689 -- in Has_Implicit_Operator, and added to the interpretations.
3690 -- Procedure Add_One_Interp will determine which hides which.
3692 if Has_Implicit_Operator (N) then
3693 null;
3694 end if;
3695 end if;
3696 end Find_Expanded_Name;
3698 -------------------------
3699 -- Find_Renamed_Entity --
3700 -------------------------
3702 function Find_Renamed_Entity
3703 (N : Node_Id;
3704 Nam : Node_Id;
3705 New_S : Entity_Id;
3706 Is_Actual : Boolean := False) return Entity_Id
3708 Ind : Interp_Index;
3709 I1 : Interp_Index := 0; -- Suppress junk warnings
3710 It : Interp;
3711 It1 : Interp;
3712 Old_S : Entity_Id;
3713 Inst : Entity_Id;
3715 function Enclosing_Instance return Entity_Id;
3716 -- If the renaming determines the entity for the default of a formal
3717 -- subprogram nested within another instance, choose the innermost
3718 -- candidate. This is because if the formal has a box, and we are within
3719 -- an enclosing instance where some candidate interpretations are local
3720 -- to this enclosing instance, we know that the default was properly
3721 -- resolved when analyzing the generic, so we prefer the local
3722 -- candidates to those that are external. This is not always the case
3723 -- but is a reasonable heuristic on the use of nested generics.
3724 -- The proper solution requires a full renaming model.
3726 function Within (Inner, Outer : Entity_Id) return Boolean;
3727 -- Determine whether a candidate subprogram is defined within
3728 -- the enclosing instance. If yes, it has precedence over outer
3729 -- candidates.
3731 function Is_Visible_Operation (Op : Entity_Id) return Boolean;
3732 -- If the renamed entity is an implicit operator, check whether it is
3733 -- visible because its operand type is properly visible. This
3734 -- check applies to explicit renamed entities that appear in the
3735 -- source in a renaming declaration or a formal subprogram instance,
3736 -- but not to default generic actuals with a name.
3738 ------------------------
3739 -- Enclosing_Instance --
3740 ------------------------
3742 function Enclosing_Instance return Entity_Id is
3743 S : Entity_Id;
3745 begin
3746 if not Is_Generic_Instance (Current_Scope)
3747 and then not Is_Actual
3748 then
3749 return Empty;
3750 end if;
3752 S := Scope (Current_Scope);
3754 while S /= Standard_Standard loop
3756 if Is_Generic_Instance (S) then
3757 return S;
3758 end if;
3760 S := Scope (S);
3761 end loop;
3763 return Empty;
3764 end Enclosing_Instance;
3766 --------------------------
3767 -- Is_Visible_Operation --
3768 --------------------------
3770 function Is_Visible_Operation (Op : Entity_Id) return Boolean is
3771 Scop : Entity_Id;
3772 Typ : Entity_Id;
3773 Btyp : Entity_Id;
3775 begin
3776 if Ekind (Op) /= E_Operator
3777 or else Scope (Op) /= Standard_Standard
3778 or else (In_Instance
3779 and then
3780 (not Is_Actual
3781 or else Present (Enclosing_Instance)))
3782 then
3783 return True;
3785 else
3786 -- For a fixed point type operator, check the resulting type,
3787 -- because it may be a mixed mode integer * fixed operation.
3789 if Present (Next_Formal (First_Formal (New_S)))
3790 and then Is_Fixed_Point_Type (Etype (New_S))
3791 then
3792 Typ := Etype (New_S);
3793 else
3794 Typ := Etype (First_Formal (New_S));
3795 end if;
3797 Btyp := Base_Type (Typ);
3799 if Nkind (Nam) /= N_Expanded_Name then
3800 return (In_Open_Scopes (Scope (Btyp))
3801 or else Is_Potentially_Use_Visible (Btyp)
3802 or else In_Use (Btyp)
3803 or else In_Use (Scope (Btyp)));
3805 else
3806 Scop := Entity (Prefix (Nam));
3808 if Ekind (Scop) = E_Package
3809 and then Present (Renamed_Object (Scop))
3810 then
3811 Scop := Renamed_Object (Scop);
3812 end if;
3814 -- Operator is visible if prefix of expanded name denotes
3815 -- scope of type, or else type type is defined in System_Aux
3816 -- and the prefix denotes System.
3818 return Scope (Btyp) = Scop
3819 or else (Scope (Btyp) = System_Aux_Id
3820 and then Scope (Scope (Btyp)) = Scop);
3821 end if;
3822 end if;
3823 end Is_Visible_Operation;
3825 ------------
3826 -- Within --
3827 ------------
3829 function Within (Inner, Outer : Entity_Id) return Boolean is
3830 Sc : Entity_Id := Scope (Inner);
3832 begin
3833 while Sc /= Standard_Standard loop
3835 if Sc = Outer then
3836 return True;
3837 else
3838 Sc := Scope (Sc);
3839 end if;
3840 end loop;
3842 return False;
3843 end Within;
3845 function Report_Overload return Entity_Id;
3846 -- List possible interpretations, and specialize message in the
3847 -- case of a generic actual.
3849 function Report_Overload return Entity_Id is
3850 begin
3851 if Is_Actual then
3852 Error_Msg_NE
3853 ("ambiguous actual subprogram&, " &
3854 "possible interpretations: ", N, Nam);
3855 else
3856 Error_Msg_N
3857 ("ambiguous subprogram, " &
3858 "possible interpretations: ", N);
3859 end if;
3861 List_Interps (Nam, N);
3862 return Old_S;
3863 end Report_Overload;
3865 -- Start of processing for Find_Renamed_Entry
3867 begin
3868 Old_S := Any_Id;
3869 Candidate_Renaming := Empty;
3871 if not Is_Overloaded (Nam) then
3872 if Entity_Matches_Spec (Entity (Nam), New_S)
3873 and then Is_Visible_Operation (Entity (Nam))
3874 then
3875 Old_S := Entity (Nam);
3877 elsif
3878 Present (First_Formal (Entity (Nam)))
3879 and then Present (First_Formal (New_S))
3880 and then (Base_Type (Etype (First_Formal (Entity (Nam))))
3881 = Base_Type (Etype (First_Formal (New_S))))
3882 then
3883 Candidate_Renaming := Entity (Nam);
3884 end if;
3886 else
3887 Get_First_Interp (Nam, Ind, It);
3889 while Present (It.Nam) loop
3891 if Entity_Matches_Spec (It.Nam, New_S)
3892 and then Is_Visible_Operation (It.Nam)
3893 then
3894 if Old_S /= Any_Id then
3896 -- Note: The call to Disambiguate only happens if a
3897 -- previous interpretation was found, in which case I1
3898 -- has received a value.
3900 It1 := Disambiguate (Nam, I1, Ind, Etype (Old_S));
3902 if It1 = No_Interp then
3904 Inst := Enclosing_Instance;
3906 if Present (Inst) then
3908 if Within (It.Nam, Inst) then
3909 return (It.Nam);
3911 elsif Within (Old_S, Inst) then
3912 return (Old_S);
3914 else
3915 return Report_Overload;
3916 end if;
3918 else
3919 return Report_Overload;
3920 end if;
3922 else
3923 Old_S := It1.Nam;
3924 exit;
3925 end if;
3927 else
3928 I1 := Ind;
3929 Old_S := It.Nam;
3930 end if;
3932 elsif
3933 Present (First_Formal (It.Nam))
3934 and then Present (First_Formal (New_S))
3935 and then (Base_Type (Etype (First_Formal (It.Nam)))
3936 = Base_Type (Etype (First_Formal (New_S))))
3937 then
3938 Candidate_Renaming := It.Nam;
3939 end if;
3941 Get_Next_Interp (Ind, It);
3942 end loop;
3944 Set_Entity (Nam, Old_S);
3945 Set_Is_Overloaded (Nam, False);
3946 end if;
3948 return Old_S;
3949 end Find_Renamed_Entity;
3951 -----------------------------
3952 -- Find_Selected_Component --
3953 -----------------------------
3955 procedure Find_Selected_Component (N : Node_Id) is
3956 P : constant Node_Id := Prefix (N);
3958 P_Name : Entity_Id;
3959 -- Entity denoted by prefix
3961 P_Type : Entity_Id;
3962 -- and its type
3964 Nam : Node_Id;
3966 begin
3967 Analyze (P);
3969 if Nkind (P) = N_Error then
3970 return;
3972 -- If the selector already has an entity, the node has been
3973 -- constructed in the course of expansion, and is known to be
3974 -- valid. Do not verify that it is defined for the type (it may
3975 -- be a private component used in the expansion of record equality).
3977 elsif Present (Entity (Selector_Name (N))) then
3979 if No (Etype (N))
3980 or else Etype (N) = Any_Type
3981 then
3982 declare
3983 Sel_Name : constant Node_Id := Selector_Name (N);
3984 Selector : constant Entity_Id := Entity (Sel_Name);
3985 C_Etype : Node_Id;
3987 begin
3988 Set_Etype (Sel_Name, Etype (Selector));
3990 if not Is_Entity_Name (P) then
3991 Resolve (P);
3992 end if;
3994 -- Build an actual subtype except for the first parameter
3995 -- of an init proc, where this actual subtype is by
3996 -- definition incorrect, since the object is uninitialized
3997 -- (and does not even have defined discriminants etc.)
3999 if Is_Entity_Name (P)
4000 and then Ekind (Entity (P)) = E_Function
4001 then
4002 Nam := New_Copy (P);
4004 if Is_Overloaded (P) then
4005 Save_Interps (P, Nam);
4006 end if;
4008 Rewrite (P,
4009 Make_Function_Call (Sloc (P), Name => Nam));
4010 Analyze_Call (P);
4011 Analyze_Selected_Component (N);
4012 return;
4014 elsif Ekind (Selector) = E_Component
4015 and then (not Is_Entity_Name (P)
4016 or else Chars (Entity (P)) /= Name_uInit)
4017 then
4018 C_Etype :=
4019 Build_Actual_Subtype_Of_Component (
4020 Etype (Selector), N);
4021 else
4022 C_Etype := Empty;
4023 end if;
4025 if No (C_Etype) then
4026 C_Etype := Etype (Selector);
4027 else
4028 Insert_Action (N, C_Etype);
4029 C_Etype := Defining_Identifier (C_Etype);
4030 end if;
4032 Set_Etype (N, C_Etype);
4033 end;
4035 -- If this is the name of an entry or protected operation, and
4036 -- the prefix is an access type, insert an explicit dereference,
4037 -- so that entry calls are treated uniformly.
4039 if Is_Access_Type (Etype (P))
4040 and then Is_Concurrent_Type (Designated_Type (Etype (P)))
4041 then
4042 declare
4043 New_P : constant Node_Id :=
4044 Make_Explicit_Dereference (Sloc (P),
4045 Prefix => Relocate_Node (P));
4046 begin
4047 Rewrite (P, New_P);
4048 Set_Etype (P, Designated_Type (Etype (Prefix (P))));
4049 end;
4050 end if;
4052 -- If the selected component appears within a default expression
4053 -- and it has an actual subtype, the pre-analysis has not yet
4054 -- completed its analysis, because Insert_Actions is disabled in
4055 -- that context. Within the init proc of the enclosing type we
4056 -- must complete this analysis, if an actual subtype was created.
4058 elsif Inside_Init_Proc then
4059 declare
4060 Typ : constant Entity_Id := Etype (N);
4061 Decl : constant Node_Id := Declaration_Node (Typ);
4063 begin
4064 if Nkind (Decl) = N_Subtype_Declaration
4065 and then not Analyzed (Decl)
4066 and then Is_List_Member (Decl)
4067 and then No (Parent (Decl))
4068 then
4069 Remove (Decl);
4070 Insert_Action (N, Decl);
4071 end if;
4072 end;
4073 end if;
4075 return;
4077 elsif Is_Entity_Name (P) then
4078 P_Name := Entity (P);
4080 -- The prefix may denote an enclosing type which is the completion
4081 -- of an incomplete type declaration.
4083 if Is_Type (P_Name) then
4084 Set_Entity (P, Get_Full_View (P_Name));
4085 Set_Etype (P, Entity (P));
4086 P_Name := Entity (P);
4087 end if;
4089 P_Type := Base_Type (Etype (P));
4091 if Debug_Flag_E then
4092 Write_Str ("Found prefix type to be ");
4093 Write_Entity_Info (P_Type, " "); Write_Eol;
4094 end if;
4096 -- First check for components of a record object (not the
4097 -- result of a call, which is handled below).
4099 if Is_Appropriate_For_Record (P_Type)
4100 and then not Is_Overloadable (P_Name)
4101 and then not Is_Type (P_Name)
4102 then
4103 -- Selected component of record. Type checking will validate
4104 -- name of selector.
4106 Analyze_Selected_Component (N);
4108 elsif Is_Appropriate_For_Entry_Prefix (P_Type)
4109 and then not In_Open_Scopes (P_Name)
4110 and then (not Is_Concurrent_Type (Etype (P_Name))
4111 or else not In_Open_Scopes (Etype (P_Name)))
4112 then
4113 -- Call to protected operation or entry. Type checking is
4114 -- needed on the prefix.
4116 Analyze_Selected_Component (N);
4118 elsif (In_Open_Scopes (P_Name)
4119 and then Ekind (P_Name) /= E_Void
4120 and then not Is_Overloadable (P_Name))
4121 or else (Is_Concurrent_Type (Etype (P_Name))
4122 and then In_Open_Scopes (Etype (P_Name)))
4123 then
4124 -- Prefix denotes an enclosing loop, block, or task, i.e. an
4125 -- enclosing construct that is not a subprogram or accept.
4127 Find_Expanded_Name (N);
4129 elsif Ekind (P_Name) = E_Package then
4130 Find_Expanded_Name (N);
4132 elsif Is_Overloadable (P_Name) then
4134 -- The subprogram may be a renaming (of an enclosing scope) as
4135 -- in the case of the name of the generic within an instantiation.
4137 if (Ekind (P_Name) = E_Procedure
4138 or else Ekind (P_Name) = E_Function)
4139 and then Present (Alias (P_Name))
4140 and then Is_Generic_Instance (Alias (P_Name))
4141 then
4142 P_Name := Alias (P_Name);
4143 end if;
4145 if Is_Overloaded (P) then
4147 -- The prefix must resolve to a unique enclosing construct
4149 declare
4150 Found : Boolean := False;
4151 Ind : Interp_Index;
4152 It : Interp;
4154 begin
4155 Get_First_Interp (P, Ind, It);
4157 while Present (It.Nam) loop
4159 if In_Open_Scopes (It.Nam) then
4160 if Found then
4161 Error_Msg_N (
4162 "prefix must be unique enclosing scope", N);
4163 Set_Entity (N, Any_Id);
4164 Set_Etype (N, Any_Type);
4165 return;
4167 else
4168 Found := True;
4169 P_Name := It.Nam;
4170 end if;
4171 end if;
4173 Get_Next_Interp (Ind, It);
4174 end loop;
4175 end;
4176 end if;
4178 if In_Open_Scopes (P_Name) then
4179 Set_Entity (P, P_Name);
4180 Set_Is_Overloaded (P, False);
4181 Find_Expanded_Name (N);
4183 else
4184 -- If no interpretation as an expanded name is possible, it
4185 -- must be a selected component of a record returned by a
4186 -- function call. Reformat prefix as a function call, the
4187 -- rest is done by type resolution. If the prefix is a
4188 -- procedure or entry, as is P.X; this is an error.
4190 if Ekind (P_Name) /= E_Function
4191 and then (not Is_Overloaded (P)
4192 or else
4193 Nkind (Parent (N)) = N_Procedure_Call_Statement)
4194 then
4196 -- Prefix may mention a package that is hidden by a local
4197 -- declaration: let the user know. Scan the full homonym
4198 -- chain, the candidate package may be anywhere on it.
4200 if Present (Homonym (Current_Entity (P_Name))) then
4202 P_Name := Current_Entity (P_Name);
4204 while Present (P_Name) loop
4205 exit when Ekind (P_Name) = E_Package;
4206 P_Name := Homonym (P_Name);
4207 end loop;
4209 if Present (P_Name) then
4210 Error_Msg_Sloc := Sloc (Entity (Prefix (N)));
4212 Error_Msg_NE
4213 ("package& is hidden by declaration#",
4214 N, P_Name);
4216 Set_Entity (Prefix (N), P_Name);
4217 Find_Expanded_Name (N);
4218 return;
4219 else
4220 P_Name := Entity (Prefix (N));
4221 end if;
4222 end if;
4224 Error_Msg_NE
4225 ("invalid prefix in selected component&", N, P_Name);
4226 Change_Selected_Component_To_Expanded_Name (N);
4227 Set_Entity (N, Any_Id);
4228 Set_Etype (N, Any_Type);
4230 else
4231 Nam := New_Copy (P);
4232 Save_Interps (P, Nam);
4233 Rewrite (P,
4234 Make_Function_Call (Sloc (P), Name => Nam));
4235 Analyze_Call (P);
4236 Analyze_Selected_Component (N);
4237 end if;
4238 end if;
4240 -- Remaining cases generate various error messages
4242 else
4243 -- Format node as expanded name, to avoid cascaded errors
4245 Change_Selected_Component_To_Expanded_Name (N);
4246 Set_Entity (N, Any_Id);
4247 Set_Etype (N, Any_Type);
4249 -- Issue error message, but avoid this if error issued already.
4250 -- Use identifier of prefix if one is available.
4252 if P_Name = Any_Id then
4253 null;
4255 elsif Ekind (P_Name) = E_Void then
4256 Premature_Usage (P);
4258 elsif Nkind (P) /= N_Attribute_Reference then
4259 Error_Msg_N (
4260 "invalid prefix in selected component&", P);
4262 if Is_Access_Type (P_Type)
4263 and then Ekind (Designated_Type (P_Type)) = E_Incomplete_Type
4264 then
4265 Error_Msg_N
4266 ("\dereference must not be of an incomplete type " &
4267 "('R'M 3.10.1)", P);
4268 end if;
4270 else
4271 Error_Msg_N (
4272 "invalid prefix in selected component", P);
4273 end if;
4274 end if;
4276 else
4277 -- If prefix is not the name of an entity, it must be an expression,
4278 -- whose type is appropriate for a record. This is determined by
4279 -- type resolution.
4281 Analyze_Selected_Component (N);
4282 end if;
4283 end Find_Selected_Component;
4285 ---------------
4286 -- Find_Type --
4287 ---------------
4289 procedure Find_Type (N : Node_Id) is
4290 C : Entity_Id;
4291 Typ : Entity_Id;
4292 T : Entity_Id;
4293 T_Name : Entity_Id;
4295 begin
4296 if N = Error then
4297 return;
4299 elsif Nkind (N) = N_Attribute_Reference then
4301 -- Class attribute. This is only valid in Ada 95 mode, but we don't
4302 -- do a check, since the tagged type referenced could only exist if
4303 -- we were in 95 mode when it was declared (or, if we were in Ada
4304 -- 83 mode, then an error message would already have been issued).
4306 if Attribute_Name (N) = Name_Class then
4307 Check_Restriction (No_Dispatch, N);
4308 Find_Type (Prefix (N));
4310 -- Propagate error from bad prefix
4312 if Etype (Prefix (N)) = Any_Type then
4313 Set_Entity (N, Any_Type);
4314 Set_Etype (N, Any_Type);
4315 return;
4316 end if;
4318 T := Base_Type (Entity (Prefix (N)));
4320 -- Case of non-tagged type
4322 if not Is_Tagged_Type (T) then
4323 if Ekind (T) = E_Incomplete_Type then
4325 -- It is legal to denote the class type of an incomplete
4326 -- type. The full type will have to be tagged, of course.
4328 Set_Is_Tagged_Type (T);
4329 Make_Class_Wide_Type (T);
4330 Set_Entity (N, Class_Wide_Type (T));
4331 Set_Etype (N, Class_Wide_Type (T));
4333 elsif Ekind (T) = E_Private_Type
4334 and then not Is_Generic_Type (T)
4335 and then In_Private_Part (Scope (T))
4336 then
4337 -- The Class attribute can be applied to an untagged
4338 -- private type fulfilled by a tagged type prior to
4339 -- the full type declaration (but only within the
4340 -- parent package's private part). Create the class-wide
4341 -- type now and check that the full type is tagged
4342 -- later during its analysis. Note that we do not
4343 -- mark the private type as tagged, unlike the case
4344 -- of incomplete types, because the type must still
4345 -- appear untagged to outside units.
4347 if not Present (Class_Wide_Type (T)) then
4348 Make_Class_Wide_Type (T);
4349 end if;
4351 Set_Entity (N, Class_Wide_Type (T));
4352 Set_Etype (N, Class_Wide_Type (T));
4354 else
4355 -- Should we introduce a type Any_Tagged and use
4356 -- Wrong_Type here, it would be a bit more consistent???
4358 Error_Msg_NE
4359 ("tagged type required, found}",
4360 Prefix (N), First_Subtype (T));
4361 Set_Entity (N, Any_Type);
4362 return;
4363 end if;
4365 -- Case of tagged type
4367 else
4368 C := Class_Wide_Type (Entity (Prefix (N)));
4369 Set_Entity_With_Style_Check (N, C);
4370 Generate_Reference (C, N);
4371 Set_Etype (N, C);
4372 end if;
4374 -- Base attribute, not allowed in Ada 83
4376 elsif Attribute_Name (N) = Name_Base then
4377 if Ada_Version = Ada_83 and then Comes_From_Source (N) then
4378 Error_Msg_N
4379 ("(Ada 83) Base attribute not allowed in subtype mark", N);
4381 else
4382 Find_Type (Prefix (N));
4383 Typ := Entity (Prefix (N));
4385 if Ada_Version >= Ada_95
4386 and then not Is_Scalar_Type (Typ)
4387 and then not Is_Generic_Type (Typ)
4388 then
4389 Error_Msg_N
4390 ("prefix of Base attribute must be scalar type",
4391 Prefix (N));
4393 elsif Sloc (Typ) = Standard_Location
4394 and then Base_Type (Typ) = Typ
4395 and then Warn_On_Redundant_Constructs
4396 then
4397 Error_Msg_NE
4398 ("?redudant attribute, & is its own base type", N, Typ);
4399 end if;
4401 T := Base_Type (Typ);
4403 -- Rewrite attribute reference with type itself (see similar
4404 -- processing in Analyze_Attribute, case Base). Preserve
4405 -- prefix if present, for other legality checks.
4407 if Nkind (Prefix (N)) = N_Expanded_Name then
4408 Rewrite (N,
4409 Make_Expanded_Name (Sloc (N),
4410 Chars => Chars (Entity (N)),
4411 Prefix => New_Copy (Prefix (Prefix (N))),
4412 Selector_Name =>
4413 New_Reference_To (Entity (N), Sloc (N))));
4415 else
4416 Rewrite (N,
4417 New_Reference_To (Entity (N), Sloc (N)));
4418 end if;
4420 Set_Entity (N, T);
4421 Set_Etype (N, T);
4422 end if;
4424 -- All other attributes are invalid in a subtype mark
4426 else
4427 Error_Msg_N ("invalid attribute in subtype mark", N);
4428 end if;
4430 else
4431 Analyze (N);
4433 if Is_Entity_Name (N) then
4434 T_Name := Entity (N);
4435 else
4436 Error_Msg_N ("subtype mark required in this context", N);
4437 Set_Etype (N, Any_Type);
4438 return;
4439 end if;
4441 if T_Name = Any_Id or else Etype (N) = Any_Type then
4443 -- Undefined id. Make it into a valid type
4445 Set_Entity (N, Any_Type);
4447 elsif not Is_Type (T_Name)
4448 and then T_Name /= Standard_Void_Type
4449 then
4450 Error_Msg_Sloc := Sloc (T_Name);
4451 Error_Msg_N ("subtype mark required in this context", N);
4452 Error_Msg_NE ("\found & declared#", N, T_Name);
4453 Set_Entity (N, Any_Type);
4455 else
4456 T_Name := Get_Full_View (T_Name);
4458 if In_Open_Scopes (T_Name) then
4459 if Ekind (Base_Type (T_Name)) = E_Task_Type then
4460 Error_Msg_N ("task type cannot be used as type mark " &
4461 "within its own body", N);
4462 else
4463 Error_Msg_N ("type declaration cannot refer to itself", N);
4464 end if;
4466 Set_Etype (N, Any_Type);
4467 Set_Entity (N, Any_Type);
4468 Set_Error_Posted (T_Name);
4469 return;
4470 end if;
4472 Set_Entity (N, T_Name);
4473 Set_Etype (N, T_Name);
4474 end if;
4475 end if;
4477 if Present (Etype (N)) and then Comes_From_Source (N) then
4478 if Is_Fixed_Point_Type (Etype (N)) then
4479 Check_Restriction (No_Fixed_Point, N);
4480 elsif Is_Floating_Point_Type (Etype (N)) then
4481 Check_Restriction (No_Floating_Point, N);
4482 end if;
4483 end if;
4484 end Find_Type;
4486 -------------------
4487 -- Get_Full_View --
4488 -------------------
4490 function Get_Full_View (T_Name : Entity_Id) return Entity_Id is
4491 begin
4492 if Ekind (T_Name) = E_Incomplete_Type
4493 and then Present (Full_View (T_Name))
4494 then
4495 return Full_View (T_Name);
4497 elsif Is_Class_Wide_Type (T_Name)
4498 and then Ekind (Root_Type (T_Name)) = E_Incomplete_Type
4499 and then Present (Full_View (Root_Type (T_Name)))
4500 then
4501 return Class_Wide_Type (Full_View (Root_Type (T_Name)));
4503 else
4504 return T_Name;
4505 end if;
4506 end Get_Full_View;
4508 ------------------------------------
4509 -- Has_Implicit_Character_Literal --
4510 ------------------------------------
4512 function Has_Implicit_Character_Literal (N : Node_Id) return Boolean is
4513 Id : Entity_Id;
4514 Found : Boolean := False;
4515 P : constant Entity_Id := Entity (Prefix (N));
4516 Priv_Id : Entity_Id := Empty;
4518 begin
4519 if Ekind (P) = E_Package
4520 and then not In_Open_Scopes (P)
4521 then
4522 Priv_Id := First_Private_Entity (P);
4523 end if;
4525 if P = Standard_Standard then
4526 Change_Selected_Component_To_Expanded_Name (N);
4527 Rewrite (N, Selector_Name (N));
4528 Analyze (N);
4529 Set_Etype (Original_Node (N), Standard_Character);
4530 return True;
4531 end if;
4533 Id := First_Entity (P);
4535 while Present (Id)
4536 and then Id /= Priv_Id
4537 loop
4538 if Is_Character_Type (Id)
4539 and then (Root_Type (Id) = Standard_Character
4540 or else Root_Type (Id) = Standard_Wide_Character
4541 or else Root_Type (Id) = Standard_Wide_Wide_Character)
4542 and then Id = Base_Type (Id)
4543 then
4544 -- We replace the node with the literal itself, resolve as a
4545 -- character, and set the type correctly.
4547 if not Found then
4548 Change_Selected_Component_To_Expanded_Name (N);
4549 Rewrite (N, Selector_Name (N));
4550 Analyze (N);
4551 Set_Etype (N, Id);
4552 Set_Etype (Original_Node (N), Id);
4553 Found := True;
4555 else
4556 -- More than one type derived from Character in given scope.
4557 -- Collect all possible interpretations.
4559 Add_One_Interp (N, Id, Id);
4560 end if;
4561 end if;
4563 Next_Entity (Id);
4564 end loop;
4566 return Found;
4567 end Has_Implicit_Character_Literal;
4569 ----------------------
4570 -- Has_Private_With --
4571 ----------------------
4573 function Has_Private_With (E : Entity_Id) return Boolean is
4574 Comp_Unit : constant Node_Id := Cunit (Current_Sem_Unit);
4575 Item : Node_Id;
4577 begin
4578 Item := First (Context_Items (Comp_Unit));
4579 while Present (Item) loop
4580 if Nkind (Item) = N_With_Clause
4581 and then Private_Present (Item)
4582 and then Entity (Name (Item)) = E
4583 then
4584 return True;
4585 end if;
4587 Next (Item);
4588 end loop;
4590 return False;
4591 end Has_Private_With;
4593 ---------------------------
4594 -- Has_Implicit_Operator --
4595 ---------------------------
4597 function Has_Implicit_Operator (N : Node_Id) return Boolean is
4598 Op_Id : constant Name_Id := Chars (Selector_Name (N));
4599 P : constant Entity_Id := Entity (Prefix (N));
4600 Id : Entity_Id;
4601 Priv_Id : Entity_Id := Empty;
4603 procedure Add_Implicit_Operator
4604 (T : Entity_Id;
4605 Op_Type : Entity_Id := Empty);
4606 -- Add implicit interpretation to node N, using the type for which
4607 -- a predefined operator exists. If the operator yields a boolean
4608 -- type, the Operand_Type is implicitly referenced by the operator,
4609 -- and a reference to it must be generated.
4611 ---------------------------
4612 -- Add_Implicit_Operator --
4613 ---------------------------
4615 procedure Add_Implicit_Operator
4616 (T : Entity_Id;
4617 Op_Type : Entity_Id := Empty)
4619 Predef_Op : Entity_Id;
4621 begin
4622 Predef_Op := Current_Entity (Selector_Name (N));
4624 while Present (Predef_Op)
4625 and then Scope (Predef_Op) /= Standard_Standard
4626 loop
4627 Predef_Op := Homonym (Predef_Op);
4628 end loop;
4630 if Nkind (N) = N_Selected_Component then
4631 Change_Selected_Component_To_Expanded_Name (N);
4632 end if;
4634 Add_One_Interp (N, Predef_Op, T);
4636 -- For operators with unary and binary interpretations, add both
4638 if Present (Homonym (Predef_Op)) then
4639 Add_One_Interp (N, Homonym (Predef_Op), T);
4640 end if;
4642 -- The node is a reference to a predefined operator, and
4643 -- an implicit reference to the type of its operands.
4645 if Present (Op_Type) then
4646 Generate_Operator_Reference (N, Op_Type);
4647 else
4648 Generate_Operator_Reference (N, T);
4649 end if;
4650 end Add_Implicit_Operator;
4652 -- Start of processing for Has_Implicit_Operator
4654 begin
4656 if Ekind (P) = E_Package
4657 and then not In_Open_Scopes (P)
4658 then
4659 Priv_Id := First_Private_Entity (P);
4660 end if;
4662 Id := First_Entity (P);
4664 case Op_Id is
4666 -- Boolean operators: an implicit declaration exists if the scope
4667 -- contains a declaration for a derived Boolean type, or for an
4668 -- array of Boolean type.
4670 when Name_Op_And | Name_Op_Not | Name_Op_Or | Name_Op_Xor =>
4672 while Id /= Priv_Id loop
4674 if Valid_Boolean_Arg (Id)
4675 and then Id = Base_Type (Id)
4676 then
4677 Add_Implicit_Operator (Id);
4678 return True;
4679 end if;
4681 Next_Entity (Id);
4682 end loop;
4684 -- Equality: look for any non-limited type (result is Boolean)
4686 when Name_Op_Eq | Name_Op_Ne =>
4688 while Id /= Priv_Id loop
4690 if Is_Type (Id)
4691 and then not Is_Limited_Type (Id)
4692 and then Id = Base_Type (Id)
4693 then
4694 Add_Implicit_Operator (Standard_Boolean, Id);
4695 return True;
4696 end if;
4698 Next_Entity (Id);
4699 end loop;
4701 -- Comparison operators: scalar type, or array of scalar
4703 when Name_Op_Lt | Name_Op_Le | Name_Op_Gt | Name_Op_Ge =>
4705 while Id /= Priv_Id loop
4706 if (Is_Scalar_Type (Id)
4707 or else (Is_Array_Type (Id)
4708 and then Is_Scalar_Type (Component_Type (Id))))
4709 and then Id = Base_Type (Id)
4710 then
4711 Add_Implicit_Operator (Standard_Boolean, Id);
4712 return True;
4713 end if;
4715 Next_Entity (Id);
4716 end loop;
4718 -- Arithmetic operators: any numeric type
4720 when Name_Op_Abs |
4721 Name_Op_Add |
4722 Name_Op_Mod |
4723 Name_Op_Rem |
4724 Name_Op_Subtract |
4725 Name_Op_Multiply |
4726 Name_Op_Divide |
4727 Name_Op_Expon =>
4729 while Id /= Priv_Id loop
4730 if Is_Numeric_Type (Id)
4731 and then Id = Base_Type (Id)
4732 then
4733 Add_Implicit_Operator (Id);
4734 return True;
4735 end if;
4737 Next_Entity (Id);
4738 end loop;
4740 -- Concatenation: any one-dimensional array type
4742 when Name_Op_Concat =>
4744 while Id /= Priv_Id loop
4745 if Is_Array_Type (Id) and then Number_Dimensions (Id) = 1
4746 and then Id = Base_Type (Id)
4747 then
4748 Add_Implicit_Operator (Id);
4749 return True;
4750 end if;
4752 Next_Entity (Id);
4753 end loop;
4755 -- What is the others condition here? Should we be using a
4756 -- subtype of Name_Id that would restrict to operators ???
4758 when others => null;
4760 end case;
4762 -- If we fall through, then we do not have an implicit operator
4764 return False;
4766 end Has_Implicit_Operator;
4768 --------------------
4769 -- In_Open_Scopes --
4770 --------------------
4772 function In_Open_Scopes (S : Entity_Id) return Boolean is
4773 begin
4774 -- Since there are several scope stacks maintained by Scope_Stack each
4775 -- delineated by Standard (see comments by definition of Scope_Stack)
4776 -- it is necessary to end the search when Standard is reached.
4778 for J in reverse 0 .. Scope_Stack.Last loop
4779 if Scope_Stack.Table (J).Entity = S then
4780 return True;
4781 end if;
4783 -- We need Is_Active_Stack_Base to tell us when to stop rather
4784 -- than checking for Standard_Standard because there are cases
4785 -- where Standard_Standard appears in the middle of the active
4786 -- set of scopes. This affects the declaration and overriding
4787 -- of private inherited operations in instantiations of generic
4788 -- child units.
4790 exit when Scope_Stack.Table (J).Is_Active_Stack_Base;
4791 end loop;
4793 return False;
4794 end In_Open_Scopes;
4796 -----------------------------
4797 -- Inherit_Renamed_Profile --
4798 -----------------------------
4800 procedure Inherit_Renamed_Profile (New_S : Entity_Id; Old_S : Entity_Id) is
4801 New_F : Entity_Id;
4802 Old_F : Entity_Id;
4803 Old_T : Entity_Id;
4804 New_T : Entity_Id;
4806 begin
4807 if Ekind (Old_S) = E_Operator then
4809 New_F := First_Formal (New_S);
4811 while Present (New_F) loop
4812 Set_Etype (New_F, Base_Type (Etype (New_F)));
4813 Next_Formal (New_F);
4814 end loop;
4816 Set_Etype (New_S, Base_Type (Etype (New_S)));
4818 else
4819 New_F := First_Formal (New_S);
4820 Old_F := First_Formal (Old_S);
4822 while Present (New_F) loop
4823 New_T := Etype (New_F);
4824 Old_T := Etype (Old_F);
4826 -- If the new type is a renaming of the old one, as is the
4827 -- case for actuals in instances, retain its name, to simplify
4828 -- later disambiguation.
4830 if Nkind (Parent (New_T)) = N_Subtype_Declaration
4831 and then Is_Entity_Name (Subtype_Indication (Parent (New_T)))
4832 and then Entity (Subtype_Indication (Parent (New_T))) = Old_T
4833 then
4834 null;
4835 else
4836 Set_Etype (New_F, Old_T);
4837 end if;
4839 Next_Formal (New_F);
4840 Next_Formal (Old_F);
4841 end loop;
4843 if Ekind (Old_S) = E_Function
4844 or else Ekind (Old_S) = E_Enumeration_Literal
4845 then
4846 Set_Etype (New_S, Etype (Old_S));
4847 end if;
4848 end if;
4849 end Inherit_Renamed_Profile;
4851 ----------------
4852 -- Initialize --
4853 ----------------
4855 procedure Initialize is
4856 begin
4857 Urefs.Init;
4858 end Initialize;
4860 -------------------------
4861 -- Install_Use_Clauses --
4862 -------------------------
4864 procedure Install_Use_Clauses
4865 (Clause : Node_Id;
4866 Force_Installation : Boolean := False)
4868 U : Node_Id := Clause;
4869 P : Node_Id;
4870 Id : Entity_Id;
4872 begin
4873 while Present (U) loop
4875 -- Case of USE package
4877 if Nkind (U) = N_Use_Package_Clause then
4878 P := First (Names (U));
4880 while Present (P) loop
4881 Id := Entity (P);
4883 if Ekind (Id) = E_Package then
4885 if In_Use (Id) then
4886 Set_Redundant_Use (P, True);
4888 elsif Present (Renamed_Object (Id))
4889 and then In_Use (Renamed_Object (Id))
4890 then
4891 Set_Redundant_Use (P, True);
4893 elsif Force_Installation or else Applicable_Use (P) then
4894 Use_One_Package (Id, U);
4896 end if;
4897 end if;
4899 Next (P);
4900 end loop;
4902 -- case of USE TYPE
4904 else
4905 P := First (Subtype_Marks (U));
4907 while Present (P) loop
4908 if not Is_Entity_Name (P)
4909 or else No (Entity (P))
4910 then
4911 null;
4913 elsif Entity (P) /= Any_Type then
4914 Use_One_Type (P);
4915 end if;
4917 Next (P);
4918 end loop;
4919 end if;
4921 Next_Use_Clause (U);
4922 end loop;
4923 end Install_Use_Clauses;
4925 -------------------------------------
4926 -- Is_Appropriate_For_Entry_Prefix --
4927 -------------------------------------
4929 function Is_Appropriate_For_Entry_Prefix (T : Entity_Id) return Boolean is
4930 P_Type : Entity_Id := T;
4932 begin
4933 if Is_Access_Type (P_Type) then
4934 P_Type := Designated_Type (P_Type);
4935 end if;
4937 return Is_Task_Type (P_Type) or else Is_Protected_Type (P_Type);
4938 end Is_Appropriate_For_Entry_Prefix;
4940 -------------------------------
4941 -- Is_Appropriate_For_Record --
4942 -------------------------------
4944 function Is_Appropriate_For_Record (T : Entity_Id) return Boolean is
4946 function Has_Components (T1 : Entity_Id) return Boolean;
4947 -- Determine if given type has components (i.e. is either a record
4948 -- type or a type that has discriminants).
4950 function Has_Components (T1 : Entity_Id) return Boolean is
4951 begin
4952 return Is_Record_Type (T1)
4953 or else (Is_Private_Type (T1) and then Has_Discriminants (T1))
4954 or else (Is_Task_Type (T1) and then Has_Discriminants (T1));
4955 end Has_Components;
4957 -- Start of processing for Is_Appropriate_For_Record
4959 begin
4960 return
4961 Present (T)
4962 and then (Has_Components (T)
4963 or else (Is_Access_Type (T)
4964 and then
4965 Has_Components (Designated_Type (T))));
4966 end Is_Appropriate_For_Record;
4968 ---------------
4969 -- New_Scope --
4970 ---------------
4972 procedure New_Scope (S : Entity_Id) is
4973 E : Entity_Id;
4975 begin
4976 if Ekind (S) = E_Void then
4977 null;
4979 -- Set scope depth if not a non-concurrent type, and we have not
4980 -- yet set the scope depth. This means that we have the first
4981 -- occurrence of the scope, and this is where the depth is set.
4983 elsif (not Is_Type (S) or else Is_Concurrent_Type (S))
4984 and then not Scope_Depth_Set (S)
4985 then
4986 if S = Standard_Standard then
4987 Set_Scope_Depth_Value (S, Uint_0);
4989 elsif Is_Child_Unit (S) then
4990 Set_Scope_Depth_Value (S, Uint_1);
4992 elsif not Is_Record_Type (Current_Scope) then
4993 if Ekind (S) = E_Loop then
4994 Set_Scope_Depth_Value (S, Scope_Depth (Current_Scope));
4995 else
4996 Set_Scope_Depth_Value (S, Scope_Depth (Current_Scope) + 1);
4997 end if;
4998 end if;
4999 end if;
5001 Scope_Stack.Increment_Last;
5003 declare
5004 SST : Scope_Stack_Entry renames Scope_Stack.Table (Scope_Stack.Last);
5006 begin
5007 SST.Entity := S;
5008 SST.Save_Scope_Suppress := Scope_Suppress;
5009 SST.Save_Local_Entity_Suppress := Local_Entity_Suppress.Last;
5011 if Scope_Stack.Last > Scope_Stack.First then
5012 SST.Component_Alignment_Default := Scope_Stack.Table
5013 (Scope_Stack.Last - 1).
5014 Component_Alignment_Default;
5015 end if;
5017 SST.Last_Subprogram_Name := null;
5018 SST.Is_Transient := False;
5019 SST.Node_To_Be_Wrapped := Empty;
5020 SST.Pending_Freeze_Actions := No_List;
5021 SST.Actions_To_Be_Wrapped_Before := No_List;
5022 SST.Actions_To_Be_Wrapped_After := No_List;
5023 SST.First_Use_Clause := Empty;
5024 SST.Is_Active_Stack_Base := False;
5025 end;
5027 if Debug_Flag_W then
5028 Write_Str ("--> new scope: ");
5029 Write_Name (Chars (Current_Scope));
5030 Write_Str (", Id=");
5031 Write_Int (Int (Current_Scope));
5032 Write_Str (", Depth=");
5033 Write_Int (Int (Scope_Stack.Last));
5034 Write_Eol;
5035 end if;
5037 -- Copy from Scope (S) the categorization flags to S, this is not
5038 -- done in case Scope (S) is Standard_Standard since propagation
5039 -- is from library unit entity inwards.
5041 if S /= Standard_Standard
5042 and then Scope (S) /= Standard_Standard
5043 and then not Is_Child_Unit (S)
5044 then
5045 E := Scope (S);
5047 if Nkind (E) not in N_Entity then
5048 return;
5049 end if;
5051 -- We only propagate inwards for library level entities,
5052 -- inner level subprograms do not inherit the categorization.
5054 if Is_Library_Level_Entity (S) then
5055 Set_Is_Preelaborated (S, Is_Preelaborated (E));
5056 Set_Is_Shared_Passive (S, Is_Shared_Passive (E));
5057 Set_Categorization_From_Scope (E => S, Scop => E);
5058 end if;
5059 end if;
5060 end New_Scope;
5062 ---------------
5063 -- Pop_Scope --
5064 ---------------
5066 procedure Pop_Scope is
5067 SST : Scope_Stack_Entry renames Scope_Stack.Table (Scope_Stack.Last);
5069 begin
5070 if Debug_Flag_E then
5071 Write_Info;
5072 end if;
5074 Scope_Suppress := SST.Save_Scope_Suppress;
5075 Local_Entity_Suppress.Set_Last (SST.Save_Local_Entity_Suppress);
5077 if Debug_Flag_W then
5078 Write_Str ("--> exiting scope: ");
5079 Write_Name (Chars (Current_Scope));
5080 Write_Str (", Depth=");
5081 Write_Int (Int (Scope_Stack.Last));
5082 Write_Eol;
5083 end if;
5085 End_Use_Clauses (SST.First_Use_Clause);
5087 -- If the actions to be wrapped are still there they will get lost
5088 -- causing incomplete code to be generated. It is better to abort in
5089 -- this case (and we do the abort even with assertions off since the
5090 -- penalty is incorrect code generation)
5092 if SST.Actions_To_Be_Wrapped_Before /= No_List
5093 or else
5094 SST.Actions_To_Be_Wrapped_After /= No_List
5095 then
5096 return;
5097 end if;
5099 -- Free last subprogram name if allocated, and pop scope
5101 Free (SST.Last_Subprogram_Name);
5102 Scope_Stack.Decrement_Last;
5103 end Pop_Scope;
5105 ---------------------
5106 -- Premature_Usage --
5107 ---------------------
5109 procedure Premature_Usage (N : Node_Id) is
5110 Kind : constant Node_Kind := Nkind (Parent (Entity (N)));
5111 E : Entity_Id := Entity (N);
5113 begin
5114 -- Within an instance, the analysis of the actual for a formal object
5115 -- does not see the name of the object itself. This is significant
5116 -- only if the object is an aggregate, where its analysis does not do
5117 -- any name resolution on component associations. (see 4717-008). In
5118 -- such a case, look for the visible homonym on the chain.
5120 if In_Instance
5121 and then Present (Homonym (E))
5122 then
5123 E := Homonym (E);
5125 while Present (E)
5126 and then not In_Open_Scopes (Scope (E))
5127 loop
5128 E := Homonym (E);
5129 end loop;
5131 if Present (E) then
5132 Set_Entity (N, E);
5133 Set_Etype (N, Etype (E));
5134 return;
5135 end if;
5136 end if;
5138 if Kind = N_Component_Declaration then
5139 Error_Msg_N
5140 ("component&! cannot be used before end of record declaration", N);
5142 elsif Kind = N_Parameter_Specification then
5143 Error_Msg_N
5144 ("formal parameter&! cannot be used before end of specification",
5147 elsif Kind = N_Discriminant_Specification then
5148 Error_Msg_N
5149 ("discriminant&! cannot be used before end of discriminant part",
5152 elsif Kind = N_Procedure_Specification
5153 or else Kind = N_Function_Specification
5154 then
5155 Error_Msg_N
5156 ("subprogram&! cannot be used before end of its declaration",
5158 else
5159 Error_Msg_N
5160 ("object& cannot be used before end of its declaration!", N);
5161 end if;
5162 end Premature_Usage;
5164 ------------------------
5165 -- Present_System_Aux --
5166 ------------------------
5168 function Present_System_Aux (N : Node_Id := Empty) return Boolean is
5169 Loc : Source_Ptr;
5170 Aux_Name : Name_Id;
5171 Unum : Unit_Number_Type;
5172 Withn : Node_Id;
5173 With_Sys : Node_Id;
5174 The_Unit : Node_Id;
5176 function Find_System (C_Unit : Node_Id) return Entity_Id;
5177 -- Scan context clause of compilation unit to find a with_clause
5178 -- for System.
5180 -----------------
5181 -- Find_System --
5182 -----------------
5184 function Find_System (C_Unit : Node_Id) return Entity_Id is
5185 With_Clause : Node_Id;
5187 begin
5188 With_Clause := First (Context_Items (C_Unit));
5190 while Present (With_Clause) loop
5191 if (Nkind (With_Clause) = N_With_Clause
5192 and then Chars (Name (With_Clause)) = Name_System)
5193 and then Comes_From_Source (With_Clause)
5194 then
5195 return With_Clause;
5196 end if;
5198 Next (With_Clause);
5199 end loop;
5201 return Empty;
5202 end Find_System;
5204 -- Start of processing for Present_System_Aux
5206 begin
5207 -- The child unit may have been loaded and analyzed already
5209 if Present (System_Aux_Id) then
5210 return True;
5212 -- If no previous pragma for System.Aux, nothing to load
5214 elsif No (System_Extend_Unit) then
5215 return False;
5217 -- Use the unit name given in the pragma to retrieve the unit.
5218 -- Verify that System itself appears in the context clause of the
5219 -- current compilation. If System is not present, an error will
5220 -- have been reported already.
5222 else
5223 With_Sys := Find_System (Cunit (Current_Sem_Unit));
5225 The_Unit := Unit (Cunit (Current_Sem_Unit));
5227 if No (With_Sys)
5228 and then (Nkind (The_Unit) = N_Package_Body
5229 or else (Nkind (The_Unit) = N_Subprogram_Body
5230 and then not Acts_As_Spec (Cunit (Current_Sem_Unit))))
5231 then
5232 With_Sys := Find_System (Library_Unit (Cunit (Current_Sem_Unit)));
5233 end if;
5235 if No (With_Sys)
5236 and then Present (N)
5237 then
5238 -- If we are compiling a subunit, we need to examine its
5239 -- context as well (Current_Sem_Unit is the parent unit);
5241 The_Unit := Parent (N);
5243 while Nkind (The_Unit) /= N_Compilation_Unit loop
5244 The_Unit := Parent (The_Unit);
5245 end loop;
5247 if Nkind (Unit (The_Unit)) = N_Subunit then
5248 With_Sys := Find_System (The_Unit);
5249 end if;
5250 end if;
5252 if No (With_Sys) then
5253 return False;
5254 end if;
5256 Loc := Sloc (With_Sys);
5257 Get_Name_String (Chars (Expression (System_Extend_Unit)));
5258 Name_Buffer (8 .. Name_Len + 7) := Name_Buffer (1 .. Name_Len);
5259 Name_Buffer (1 .. 7) := "system.";
5260 Name_Buffer (Name_Len + 8) := '%';
5261 Name_Buffer (Name_Len + 9) := 's';
5262 Name_Len := Name_Len + 9;
5263 Aux_Name := Name_Find;
5265 Unum :=
5266 Load_Unit
5267 (Load_Name => Aux_Name,
5268 Required => False,
5269 Subunit => False,
5270 Error_Node => With_Sys);
5272 if Unum /= No_Unit then
5273 Semantics (Cunit (Unum));
5274 System_Aux_Id :=
5275 Defining_Entity (Specification (Unit (Cunit (Unum))));
5277 Withn := Make_With_Clause (Loc,
5278 Name =>
5279 Make_Expanded_Name (Loc,
5280 Chars => Chars (System_Aux_Id),
5281 Prefix =>
5282 New_Reference_To (Scope (System_Aux_Id), Loc),
5283 Selector_Name =>
5284 New_Reference_To (System_Aux_Id, Loc)));
5286 Set_Entity (Name (Withn), System_Aux_Id);
5288 Set_Library_Unit (Withn, Cunit (Unum));
5289 Set_Corresponding_Spec (Withn, System_Aux_Id);
5290 Set_First_Name (Withn, True);
5291 Set_Implicit_With (Withn, True);
5293 Insert_After (With_Sys, Withn);
5294 Mark_Rewrite_Insertion (Withn);
5295 Set_Context_Installed (Withn);
5297 return True;
5299 -- Here if unit load failed
5301 else
5302 Error_Msg_Name_1 := Name_System;
5303 Error_Msg_Name_2 := Chars (Expression (System_Extend_Unit));
5304 Error_Msg_N
5305 ("extension package `%.%` does not exist",
5306 Opt.System_Extend_Unit);
5307 return False;
5308 end if;
5309 end if;
5310 end Present_System_Aux;
5312 -------------------------
5313 -- Restore_Scope_Stack --
5314 -------------------------
5316 procedure Restore_Scope_Stack (Handle_Use : Boolean := True) is
5317 E : Entity_Id;
5318 S : Entity_Id;
5319 Comp_Unit : Node_Id;
5320 In_Child : Boolean := False;
5321 Full_Vis : Boolean := True;
5322 SS_Last : constant Int := Scope_Stack.Last;
5324 begin
5325 -- Restore visibility of previous scope stack, if any
5327 for J in reverse 0 .. Scope_Stack.Last loop
5328 exit when Scope_Stack.Table (J).Entity = Standard_Standard
5329 or else No (Scope_Stack.Table (J).Entity);
5331 S := Scope_Stack.Table (J).Entity;
5333 if not Is_Hidden_Open_Scope (S) then
5335 -- If the parent scope is hidden, its entities are hidden as
5336 -- well, unless the entity is the instantiation currently
5337 -- being analyzed.
5339 if not Is_Hidden_Open_Scope (Scope (S))
5340 or else not Analyzed (Parent (S))
5341 or else Scope (S) = Standard_Standard
5342 then
5343 Set_Is_Immediately_Visible (S, True);
5344 end if;
5346 E := First_Entity (S);
5348 while Present (E) loop
5349 if Is_Child_Unit (E) then
5350 Set_Is_Immediately_Visible (E,
5351 Is_Visible_Child_Unit (E) or else In_Open_Scopes (E));
5352 else
5353 Set_Is_Immediately_Visible (E, True);
5354 end if;
5356 Next_Entity (E);
5358 if not Full_Vis then
5359 exit when E = First_Private_Entity (S);
5360 end if;
5361 end loop;
5363 -- The visibility of child units (siblings of current compilation)
5364 -- must be restored in any case. Their declarations may appear
5365 -- after the private part of the parent.
5367 if not Full_Vis
5368 and then Present (E)
5369 then
5370 while Present (E) loop
5371 if Is_Child_Unit (E) then
5372 Set_Is_Immediately_Visible (E,
5373 Is_Visible_Child_Unit (E) or else In_Open_Scopes (E));
5374 end if;
5376 Next_Entity (E);
5377 end loop;
5378 end if;
5379 end if;
5381 if Is_Child_Unit (S)
5382 and not In_Child -- check only for current unit.
5383 then
5384 In_Child := True;
5386 -- restore visibility of parents according to whether the child
5387 -- is private and whether we are in its visible part.
5389 Comp_Unit := Parent (Unit_Declaration_Node (S));
5391 if Nkind (Comp_Unit) = N_Compilation_Unit
5392 and then Private_Present (Comp_Unit)
5393 then
5394 Full_Vis := True;
5396 elsif (Ekind (S) = E_Package
5397 or else Ekind (S) = E_Generic_Package)
5398 and then (In_Private_Part (S)
5399 or else In_Package_Body (S))
5400 then
5401 Full_Vis := True;
5403 elsif (Ekind (S) = E_Procedure
5404 or else Ekind (S) = E_Function)
5405 and then Has_Completion (S)
5406 then
5407 Full_Vis := True;
5408 else
5409 Full_Vis := False;
5410 end if;
5411 else
5412 Full_Vis := True;
5413 end if;
5414 end loop;
5416 if SS_Last >= Scope_Stack.First
5417 and then Scope_Stack.Table (SS_Last).Entity /= Standard_Standard
5418 and then Handle_Use
5419 then
5420 Install_Use_Clauses (Scope_Stack.Table (SS_Last).First_Use_Clause);
5421 end if;
5422 end Restore_Scope_Stack;
5424 ----------------------
5425 -- Save_Scope_Stack --
5426 ----------------------
5428 procedure Save_Scope_Stack (Handle_Use : Boolean := True) is
5429 E : Entity_Id;
5430 S : Entity_Id;
5431 SS_Last : constant Int := Scope_Stack.Last;
5433 begin
5434 if SS_Last >= Scope_Stack.First
5435 and then Scope_Stack.Table (SS_Last).Entity /= Standard_Standard
5436 then
5437 if Handle_Use then
5438 End_Use_Clauses (Scope_Stack.Table (SS_Last).First_Use_Clause);
5439 end if;
5441 -- If the call is from within a compilation unit, as when
5442 -- called from Rtsfind, make current entries in scope stack
5443 -- invisible while we analyze the new unit.
5445 for J in reverse 0 .. SS_Last loop
5446 exit when Scope_Stack.Table (J).Entity = Standard_Standard
5447 or else No (Scope_Stack.Table (J).Entity);
5449 S := Scope_Stack.Table (J).Entity;
5450 Set_Is_Immediately_Visible (S, False);
5451 E := First_Entity (S);
5453 while Present (E) loop
5454 Set_Is_Immediately_Visible (E, False);
5455 Next_Entity (E);
5456 end loop;
5457 end loop;
5459 end if;
5460 end Save_Scope_Stack;
5462 -------------
5463 -- Set_Use --
5464 -------------
5466 procedure Set_Use (L : List_Id) is
5467 Decl : Node_Id;
5468 Pack_Name : Node_Id;
5469 Pack : Entity_Id;
5470 Id : Entity_Id;
5472 begin
5473 if Present (L) then
5474 Decl := First (L);
5476 while Present (Decl) loop
5477 if Nkind (Decl) = N_Use_Package_Clause then
5478 Chain_Use_Clause (Decl);
5479 Pack_Name := First (Names (Decl));
5481 while Present (Pack_Name) loop
5482 Pack := Entity (Pack_Name);
5484 if Ekind (Pack) = E_Package
5485 and then Applicable_Use (Pack_Name)
5486 then
5487 Use_One_Package (Pack, Decl);
5488 end if;
5490 Next (Pack_Name);
5491 end loop;
5493 elsif Nkind (Decl) = N_Use_Type_Clause then
5494 Chain_Use_Clause (Decl);
5495 Id := First (Subtype_Marks (Decl));
5497 while Present (Id) loop
5498 if Entity (Id) /= Any_Type then
5499 Use_One_Type (Id);
5500 end if;
5502 Next (Id);
5503 end loop;
5504 end if;
5506 Next (Decl);
5507 end loop;
5508 end if;
5509 end Set_Use;
5511 ---------------------
5512 -- Use_One_Package --
5513 ---------------------
5515 procedure Use_One_Package (P : Entity_Id; N : Node_Id) is
5516 Id : Entity_Id;
5517 Prev : Entity_Id;
5518 Current_Instance : Entity_Id := Empty;
5519 Real_P : Entity_Id;
5520 Private_With_OK : Boolean := False;
5522 begin
5523 if Ekind (P) /= E_Package then
5524 return;
5525 end if;
5527 Set_In_Use (P);
5529 -- Ada 2005 (AI-50217): Check restriction
5531 if From_With_Type (P) then
5532 Error_Msg_N ("limited withed package cannot appear in use clause", N);
5533 end if;
5535 -- Find enclosing instance, if any
5537 if In_Instance then
5538 Current_Instance := Current_Scope;
5540 while not Is_Generic_Instance (Current_Instance) loop
5541 Current_Instance := Scope (Current_Instance);
5542 end loop;
5544 if No (Hidden_By_Use_Clause (N)) then
5545 Set_Hidden_By_Use_Clause (N, New_Elmt_List);
5546 end if;
5547 end if;
5549 -- If unit is a package renaming, indicate that the renamed
5550 -- package is also in use (the flags on both entities must
5551 -- remain consistent, and a subsequent use of either of them
5552 -- should be recognized as redundant).
5554 if Present (Renamed_Object (P)) then
5555 Set_In_Use (Renamed_Object (P));
5556 Real_P := Renamed_Object (P);
5557 else
5558 Real_P := P;
5559 end if;
5561 -- Ada 2005 (AI-262): Check the use_clause of a private withed package
5562 -- found in the private part of a package specification
5564 if In_Private_Part (Current_Scope)
5565 and then Has_Private_With (P)
5566 and then Is_Child_Unit (Current_Scope)
5567 and then Is_Child_Unit (P)
5568 and then Is_Ancestor_Package (Scope (Current_Scope), P)
5569 then
5570 Private_With_OK := True;
5571 end if;
5573 -- Loop through entities in one package making them potentially
5574 -- use-visible.
5576 Id := First_Entity (P);
5577 while Present (Id)
5578 and then (Id /= First_Private_Entity (P)
5579 or else Private_With_OK) -- Ada 2005 (AI-262)
5580 loop
5581 Prev := Current_Entity (Id);
5583 while Present (Prev) loop
5584 if Is_Immediately_Visible (Prev)
5585 and then (not Is_Overloadable (Prev)
5586 or else not Is_Overloadable (Id)
5587 or else (Type_Conformant (Id, Prev)))
5588 then
5589 if No (Current_Instance) then
5591 -- Potentially use-visible entity remains hidden
5593 goto Next_Usable_Entity;
5595 -- A use clause within an instance hides outer global
5596 -- entities, which are not used to resolve local entities
5597 -- in the instance. Note that the predefined entities in
5598 -- Standard could not have been hidden in the generic by
5599 -- a use clause, and therefore remain visible. Other
5600 -- compilation units whose entities appear in Standard must
5601 -- be hidden in an instance.
5603 -- To determine whether an entity is external to the instance
5604 -- we compare the scope depth of its scope with that of the
5605 -- current instance. However, a generic actual of a subprogram
5606 -- instance is declared in the wrapper package but will not be
5607 -- hidden by a use-visible entity.
5609 -- If Id is called Standard, the predefined package with the
5610 -- same name is in the homonym chain. It has to be ignored
5611 -- because it has no defined scope (being the only entity in
5612 -- the system with this mandated behavior).
5614 elsif not Is_Hidden (Id)
5615 and then Present (Scope (Prev))
5616 and then not Is_Wrapper_Package (Scope (Prev))
5617 and then Scope_Depth (Scope (Prev)) <
5618 Scope_Depth (Current_Instance)
5619 and then (Scope (Prev) /= Standard_Standard
5620 or else Sloc (Prev) > Standard_Location)
5621 then
5622 Set_Is_Potentially_Use_Visible (Id);
5623 Set_Is_Immediately_Visible (Prev, False);
5624 Append_Elmt (Prev, Hidden_By_Use_Clause (N));
5625 end if;
5627 -- A user-defined operator is not use-visible if the
5628 -- predefined operator for the type is immediately visible,
5629 -- which is the case if the type of the operand is in an open
5630 -- scope. This does not apply to user-defined operators that
5631 -- have operands of different types, because the predefined
5632 -- mixed mode operations (multiplication and division) apply to
5633 -- universal types and do not hide anything.
5635 elsif Ekind (Prev) = E_Operator
5636 and then Operator_Matches_Spec (Prev, Id)
5637 and then In_Open_Scopes
5638 (Scope (Base_Type (Etype (First_Formal (Id)))))
5639 and then (No (Next_Formal (First_Formal (Id)))
5640 or else Etype (First_Formal (Id))
5641 = Etype (Next_Formal (First_Formal (Id)))
5642 or else Chars (Prev) = Name_Op_Expon)
5643 then
5644 goto Next_Usable_Entity;
5645 end if;
5647 Prev := Homonym (Prev);
5648 end loop;
5650 -- On exit, we know entity is not hidden, unless it is private
5652 if not Is_Hidden (Id)
5653 and then ((not Is_Child_Unit (Id))
5654 or else Is_Visible_Child_Unit (Id))
5655 then
5656 Set_Is_Potentially_Use_Visible (Id);
5658 if Is_Private_Type (Id)
5659 and then Present (Full_View (Id))
5660 then
5661 Set_Is_Potentially_Use_Visible (Full_View (Id));
5662 end if;
5663 end if;
5665 <<Next_Usable_Entity>>
5666 Next_Entity (Id);
5667 end loop;
5669 -- Child units are also made use-visible by a use clause, but they
5670 -- may appear after all visible declarations in the parent entity list.
5672 while Present (Id) loop
5674 if Is_Child_Unit (Id)
5675 and then Is_Visible_Child_Unit (Id)
5676 then
5677 Set_Is_Potentially_Use_Visible (Id);
5678 end if;
5680 Next_Entity (Id);
5681 end loop;
5683 if Chars (Real_P) = Name_System
5684 and then Scope (Real_P) = Standard_Standard
5685 and then Present_System_Aux (N)
5686 then
5687 Use_One_Package (System_Aux_Id, N);
5688 end if;
5690 end Use_One_Package;
5692 ------------------
5693 -- Use_One_Type --
5694 ------------------
5696 procedure Use_One_Type (Id : Node_Id) is
5697 T : Entity_Id;
5698 Op_List : Elist_Id;
5699 Elmt : Elmt_Id;
5701 begin
5702 -- It is the type determined by the subtype mark (8.4(8)) whose
5703 -- operations become potentially use-visible.
5705 T := Base_Type (Entity (Id));
5707 Set_Redundant_Use
5708 (Id,
5709 In_Use (T)
5710 or else Is_Potentially_Use_Visible (T)
5711 or else In_Use (Scope (T)));
5713 if In_Open_Scopes (Scope (T)) then
5714 null;
5716 -- If the subtype mark designates a subtype in a different package,
5717 -- we have to check that the parent type is visible, otherwise the
5718 -- use type clause is a noop. Not clear how to do that???
5720 elsif not Redundant_Use (Id) then
5721 Set_In_Use (T);
5722 Op_List := Collect_Primitive_Operations (T);
5723 Elmt := First_Elmt (Op_List);
5725 while Present (Elmt) loop
5727 if (Nkind (Node (Elmt)) = N_Defining_Operator_Symbol
5728 or else Chars (Node (Elmt)) in Any_Operator_Name)
5729 and then not Is_Hidden (Node (Elmt))
5730 then
5731 Set_Is_Potentially_Use_Visible (Node (Elmt));
5732 end if;
5734 Next_Elmt (Elmt);
5735 end loop;
5736 end if;
5737 end Use_One_Type;
5739 ----------------
5740 -- Write_Info --
5741 ----------------
5743 procedure Write_Info is
5744 Id : Entity_Id := First_Entity (Current_Scope);
5746 begin
5747 -- No point in dumping standard entities
5749 if Current_Scope = Standard_Standard then
5750 return;
5751 end if;
5753 Write_Str ("========================================================");
5754 Write_Eol;
5755 Write_Str (" Defined Entities in ");
5756 Write_Name (Chars (Current_Scope));
5757 Write_Eol;
5758 Write_Str ("========================================================");
5759 Write_Eol;
5761 if No (Id) then
5762 Write_Str ("-- none --");
5763 Write_Eol;
5765 else
5766 while Present (Id) loop
5767 Write_Entity_Info (Id, " ");
5768 Next_Entity (Id);
5769 end loop;
5770 end if;
5772 if Scope (Current_Scope) = Standard_Standard then
5774 -- Print information on the current unit itself
5776 Write_Entity_Info (Current_Scope, " ");
5777 end if;
5779 Write_Eol;
5780 end Write_Info;
5782 -----------------
5783 -- Write_Scopes --
5784 -----------------
5786 procedure Write_Scopes is
5787 S : Entity_Id;
5789 begin
5790 for J in reverse 1 .. Scope_Stack.Last loop
5791 S := Scope_Stack.Table (J).Entity;
5792 Write_Int (Int (S));
5793 Write_Str (" === ");
5794 Write_Name (Chars (S));
5795 Write_Eol;
5796 end loop;
5797 end Write_Scopes;
5799 end Sem_Ch8;