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