1------------------------------------------------------------------------------
2--                                                                          --
3--                         GNAT COMPILER COMPONENTS                         --
4--                                                                          --
5--                             S E M _ C H 1 2                              --
6--                                                                          --
7--                                 B o d y                                  --
8--                                                                          --
9--          Copyright (C) 1992-2004, Free Software Foundation, Inc.         --
10--                                                                          --
11-- GNAT is free software;  you can  redistribute it  and/or modify it under --
12-- terms of the  GNU General Public License as published  by the Free Soft- --
13-- ware  Foundation;  either version 2,  or (at your option) any later ver- --
14-- sion.  GNAT is distributed in the hope that it will be useful, but WITH- --
15-- OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY --
16-- or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License --
17-- for  more details.  You should have  received  a copy of the GNU General --
18-- Public License  distributed with GNAT;  see file COPYING.  If not, write --
19-- to  the Free Software Foundation,  59 Temple Place - Suite 330,  Boston, --
20-- MA 02111-1307, USA.                                                      --
21--                                                                          --
22-- GNAT was originally developed  by the GNAT team at  New York University. --
23-- Extensive contributions were provided by Ada Core Technologies Inc.      --
24--                                                                          --
25------------------------------------------------------------------------------
26
27with Atree;    use Atree;
28with Einfo;    use Einfo;
29with Elists;   use Elists;
30with Errout;   use Errout;
31with Expander; use Expander;
32with Fname;    use Fname;
33with Fname.UF; use Fname.UF;
34with Freeze;   use Freeze;
35with Hostparm;
36with Inline;   use Inline;
37with Lib;      use Lib;
38with Lib.Load; use Lib.Load;
39with Lib.Xref; use Lib.Xref;
40with Nlists;   use Nlists;
41with Nmake;    use Nmake;
42with Opt;      use Opt;
43with Restrict; use Restrict;
44with Rtsfind;  use Rtsfind;
45with Sem;      use Sem;
46with Sem_Cat;  use Sem_Cat;
47with Sem_Ch3;  use Sem_Ch3;
48with Sem_Ch6;  use Sem_Ch6;
49with Sem_Ch7;  use Sem_Ch7;
50with Sem_Ch8;  use Sem_Ch8;
51with Sem_Ch10; use Sem_Ch10;
52with Sem_Ch13; use Sem_Ch13;
53with Sem_Elab; use Sem_Elab;
54with Sem_Elim; use Sem_Elim;
55with Sem_Eval; use Sem_Eval;
56with Sem_Res;  use Sem_Res;
57with Sem_Type; use Sem_Type;
58with Sem_Util; use Sem_Util;
59with Sem_Warn; use Sem_Warn;
60with Stand;    use Stand;
61with Sinfo;    use Sinfo;
62with Sinfo.CN; use Sinfo.CN;
63with Sinput;   use Sinput;
64with Sinput.L; use Sinput.L;
65with Snames;   use Snames;
66with Stringt;  use Stringt;
67with Uname;    use Uname;
68with Table;
69with Tbuild;   use Tbuild;
70with Uintp;    use Uintp;
71with Urealp;   use Urealp;
72
73with GNAT.HTable;
74
75package body Sem_Ch12 is
76
77   ----------------------------------------------------------
78   -- Implementation of Generic Analysis and Instantiation --
79   -----------------------------------------------------------
80
81   --  GNAT implements generics by macro expansion. No attempt is made to
82   --  share generic instantiations (for now). Analysis of a generic definition
83   --  does not perform any expansion action, but the expander must be called
84   --  on the tree for each instantiation, because the expansion may of course
85   --  depend on the generic actuals. All of this is best achieved as follows:
86   --
87   --  a) Semantic analysis of a generic unit is performed on a copy of the
88   --  tree for the generic unit. All tree modifications that follow analysis
89   --  do not affect the original tree. Links are kept between the original
90   --  tree and the copy, in order to recognize non-local references within
91   --  the generic, and propagate them to each instance (recall that name
92   --  resolution is done on the generic declaration: generics are not really
93   --  macros!). This is summarized in the following diagram:
94   --
95   --              .-----------.               .----------.
96   --              |  semantic |<--------------|  generic |
97   --              |    copy   |               |    unit  |
98   --              |           |==============>|          |
99   --              |___________|    global     |__________|
100   --                             references     |   |  |
101   --                                            |   |  |
102   --                                          .-----|--|.
103   --                                          |  .-----|---.
104   --                                          |  |  .----------.
105   --                                          |  |  |  generic |
106   --                                          |__|  |          |
107   --                                             |__| instance |
108   --                                                |__________|
109   --
110   --  b) Each instantiation copies the original tree, and inserts into it a
111   --  series of declarations that describe the mapping between generic formals
112   --  and actuals. For example, a generic In OUT parameter is an object
113   --  renaming of the corresponing actual, etc. Generic IN parameters are
114   --  constant declarations.
115   --
116   --  c) In order to give the right visibility for these renamings, we use
117   --  a different scheme for package and subprogram instantiations. For
118   --  packages, the list of renamings is inserted into the package
119   --  specification, before the visible declarations of the package. The
120   --  renamings are analyzed before any of the text of the instance, and are
121   --  thus visible at the right place. Furthermore, outside of the instance,
122   --  the generic parameters are visible and denote their corresponding
123   --  actuals.
124
125   --  For subprograms, we create a container package to hold the renamings
126   --  and the subprogram instance itself. Analysis of the package makes the
127   --  renaming declarations visible to the subprogram. After analyzing the
128   --  package, the defining entity for the subprogram is touched-up so that
129   --  it appears declared in the current scope, and not inside the container
130   --  package.
131
132   --  If the instantiation is a compilation unit, the container package is
133   --  given the same name as the subprogram instance. This ensures that
134   --  the elaboration procedure called by the binder, using the compilation
135   --  unit name, calls in fact the elaboration procedure for the package.
136
137   --  Not surprisingly, private types complicate this approach. By saving in
138   --  the original generic object the non-local references, we guarantee that
139   --  the proper entities are referenced at the point of instantiation.
140   --  However, for private types, this by itself does not insure that the
141   --  proper VIEW of the entity is used (the full type may be visible at the
142   --  point of generic definition, but not at instantiation, or vice-versa).
143   --  In  order to reference the proper view, we special-case any reference
144   --  to private types in the generic object, by saving both views, one in
145   --  the generic and one in the semantic copy. At time of instantiation, we
146   --  check whether the two views are consistent, and exchange declarations if
147   --  necessary, in order to restore the correct visibility. Similarly, if
148   --  the instance view is private when the generic view was not, we perform
149   --  the exchange. After completing the instantiation, we restore the
150   --  current visibility. The flag Has_Private_View marks identifiers in the
151   --  the generic unit that require checking.
152
153   --  Visibility within nested generic units requires special handling.
154   --  Consider the following scheme:
155   --
156   --  type Global is ...         --  outside of generic unit.
157   --  generic ...
158   --  package Outer is
159   --     ...
160   --     type Semi_Global is ... --  global to inner.
161   --
162   --     generic ...                                         -- 1
163   --     procedure inner (X1 : Global;  X2 : Semi_Global);
164   --
165   --     procedure in2 is new inner (...);                   -- 4
166   --  end Outer;
167
168   --  package New_Outer is new Outer (...);                  -- 2
169   --  procedure New_Inner is new New_Outer.Inner (...);      -- 3
170
171   --  The semantic analysis of Outer captures all occurrences of Global.
172   --  The semantic analysis of Inner (at 1) captures both occurrences of
173   --  Global and Semi_Global.
174
175   --  At point 2 (instantiation of Outer), we also produce a generic copy
176   --  of Inner, even though Inner is, at that point, not being instantiated.
177   --  (This is just part of the semantic analysis of New_Outer).
178
179   --  Critically, references to Global within Inner must be preserved, while
180   --  references to Semi_Global should not preserved, because they must now
181   --  resolve to an entity within New_Outer. To distinguish between these, we
182   --  use a global variable, Current_Instantiated_Parent, which is set when
183   --  performing a generic copy during instantiation (at 2). This variable is
184   --  used when performing a generic copy that is not an instantiation, but
185   --  that is nested within one, as the occurrence of 1 within 2. The analysis
186   --  of a nested generic only preserves references that are global to the
187   --  enclosing Current_Instantiated_Parent. We use the Scope_Depth value to
188   --  determine whether a reference is external to the given parent.
189
190   --  The instantiation at point 3 requires no special treatment. The method
191   --  works as well for further nestings of generic units, but of course the
192   --  variable Current_Instantiated_Parent must be stacked because nested
193   --  instantiations can occur, e.g. the occurrence of 4 within 2.
194
195   --  The instantiation of package and subprogram bodies is handled in a
196   --  similar manner, except that it is delayed until after semantic
197   --  analysis is complete. In this fashion complex cross-dependencies
198   --  between several package declarations and bodies containing generics
199   --  can be compiled which otherwise would diagnose spurious circularities.
200
201   --  For example, it is possible to compile two packages A and B that
202   --  have the following structure:
203
204   --    package A is                         package B is
205   --       generic ...                          generic ...
206   --       package G_A is                       package G_B is
207
208   --    with B;                              with A;
209   --    package body A is                    package body B is
210   --       package N_B is new G_B (..)          package N_A is new G_A (..)
211
212   --  The table Pending_Instantiations in package Inline is used to keep
213   --  track of body instantiations that are delayed in this manner. Inline
214   --  handles the actual calls to do the body instantiations. This activity
215   --  is part of Inline, since the processing occurs at the same point, and
216   --  for essentially the same reason, as the handling of inlined routines.
217
218   ----------------------------------------------
219   -- Detection of Instantiation Circularities --
220   ----------------------------------------------
221
222   --  If we have a chain of instantiations that is circular, this is a
223   --  static error which must be detected at compile time. The detection
224   --  of these circularities is carried out at the point that we insert
225   --  a generic instance spec or body. If there is a circularity, then
226   --  the analysis of the offending spec or body will eventually result
227   --  in trying to load the same unit again, and we detect this problem
228   --  as we analyze the package instantiation for the second time.
229
230   --  At least in some cases after we have detected the circularity, we
231   --  get into trouble if we try to keep going. The following flag is
232   --  set if a circularity is detected, and used to abandon compilation
233   --  after the messages have been posted.
234
235   Circularity_Detected : Boolean := False;
236   --  This should really be reset on encountering a new main unit, but in
237   --  practice we are not using multiple main units so it is not critical.
238
239   -----------------------
240   -- Local subprograms --
241   -----------------------
242
243   procedure Abandon_Instantiation (N : Node_Id);
244   pragma No_Return (Abandon_Instantiation);
245   --  Posts an error message "instantiation abandoned" at the indicated
246   --  node and then raises the exception Instantiation_Error to do it.
247
248   procedure Analyze_Formal_Array_Type
249     (T   : in out Entity_Id;
250      Def : Node_Id);
251   --  A formal array type is treated like an array type declaration, and
252   --  invokes Array_Type_Declaration (sem_ch3) whose first parameter is
253   --  in-out, because in the case of an anonymous type the entity is
254   --  actually created in the procedure.
255
256   --  The following procedures treat other kinds of formal parameters.
257
258   procedure Analyze_Formal_Derived_Type
259     (N   : Node_Id;
260      T   : Entity_Id;
261      Def : Node_Id);
262
263   --  All the following need comments???
264
265   procedure Analyze_Formal_Decimal_Fixed_Point_Type
266                                                (T : Entity_Id; Def : Node_Id);
267   procedure Analyze_Formal_Discrete_Type       (T : Entity_Id; Def : Node_Id);
268   procedure Analyze_Formal_Floating_Type       (T : Entity_Id; Def : Node_Id);
269   procedure Analyze_Formal_Signed_Integer_Type (T : Entity_Id; Def : Node_Id);
270   procedure Analyze_Formal_Modular_Type        (T : Entity_Id; Def : Node_Id);
271   procedure Analyze_Formal_Ordinary_Fixed_Point_Type
272                                                (T : Entity_Id; Def : Node_Id);
273
274   procedure Analyze_Formal_Private_Type
275     (N   : Node_Id;
276      T   : Entity_Id;
277      Def : Node_Id);
278   --  This needs comments???
279
280   procedure Analyze_Generic_Formal_Part (N : Node_Id);
281
282   procedure Analyze_Generic_Access_Type (T : Entity_Id; Def : Node_Id);
283   --  This needs comments ???
284
285   function Analyze_Associations
286     (I_Node  : Node_Id;
287      Formals : List_Id;
288      F_Copy  : List_Id)
289      return    List_Id;
290   --  At instantiation time, build the list of associations between formals
291   --  and actuals. Each association becomes a renaming declaration for the
292   --  formal entity. F_Copy is the analyzed list of formals in the generic
293   --  copy. It is used to apply legality checks to the actuals. I_Node is the
294   --  instantiation node itself.
295
296   procedure Analyze_Subprogram_Instantiation
297     (N : Node_Id;
298      K : Entity_Kind);
299
300   procedure Build_Instance_Compilation_Unit_Nodes
301     (N        : Node_Id;
302      Act_Body : Node_Id;
303      Act_Decl : Node_Id);
304   --  This procedure is used in the case where the generic instance of a
305   --  subprogram body or package body is a library unit. In this case, the
306   --  original library unit node for the generic instantiation must be
307   --  replaced by the resulting generic body, and a link made to a new
308   --  compilation unit node for the generic declaration. The argument N is
309   --  the original generic instantiation. Act_Body and Act_Decl are the body
310   --  and declaration of the instance (either package body and declaration
311   --  nodes or subprogram body and declaration nodes depending on the case).
312   --  On return, the node N has been rewritten with the actual body.
313
314   procedure Check_Formal_Packages (P_Id : Entity_Id);
315   --  Apply the following to all formal packages in generic associations.
316
317   procedure Check_Formal_Package_Instance
318     (Formal_Pack : Entity_Id;
319      Actual_Pack : Entity_Id);
320   --  Verify that the actuals of the actual instance match the actuals of
321   --  the template for a formal package that is not declared with a box.
322
323   procedure Check_Forward_Instantiation (Decl : Node_Id);
324   --  If the generic is a local entity and the corresponding body has not
325   --  been seen yet, flag enclosing packages to indicate that it will be
326   --  elaborated after the generic body. Subprograms declared in the same
327   --  package cannot be inlined by the front-end because front-end inlining
328   --  requires a strict linear order of elaboration.
329
330   procedure Check_Hidden_Child_Unit
331     (N           : Node_Id;
332      Gen_Unit    : Entity_Id;
333      Act_Decl_Id : Entity_Id);
334   --  If the generic unit is an implicit child instance within a parent
335   --  instance, we need to make an explicit test that it is not hidden by
336   --  a child instance of the same name and parent.
337
338   procedure Check_Private_View (N : Node_Id);
339   --  Check whether the type of a generic entity has a different view between
340   --  the point of generic analysis and the point of instantiation. If the
341   --  view has changed, then at the point of instantiation we restore the
342   --  correct view to perform semantic analysis of the instance, and reset
343   --  the current view after instantiation. The processing is driven by the
344   --  current private status of the type of the node, and Has_Private_View,
345   --  a flag that is set at the point of generic compilation. If view and
346   --  flag are inconsistent then the type is updated appropriately.
347
348   procedure Check_Generic_Actuals
349     (Instance      : Entity_Id;
350      Is_Formal_Box : Boolean);
351   --  Similar to previous one. Check the actuals in the instantiation,
352   --  whose views can change between the point of instantiation and the point
353   --  of instantiation of the body. In addition, mark the generic renamings
354   --  as generic actuals, so that they are not compatible with other actuals.
355   --  Recurse on an actual that is a formal package whose declaration has
356   --  a box.
357
358   function Contains_Instance_Of
359     (Inner : Entity_Id;
360      Outer : Entity_Id;
361      N     : Node_Id)
362      return  Boolean;
363   --  Inner is instantiated within the generic Outer. Check whether Inner
364   --  directly or indirectly contains an instance of Outer or of one of its
365   --  parents, in the case of a subunit. Each generic unit holds a list of
366   --  the entities instantiated within (at any depth). This procedure
367   --  determines whether the set of such lists contains a cycle, i.e. an
368   --  illegal circular instantiation.
369
370   function Denotes_Formal_Package (Pack : Entity_Id) return Boolean;
371   --  Returns True if E is a formal package of an enclosing generic, or
372   --  the actual for such a formal in an enclosing instantiation. Used in
373   --  Restore_Private_Views, to keep the formals of such a package visible
374   --  on exit from an inner instantiation.
375
376   function Find_Actual_Type
377     (Typ       : Entity_Id;
378      Gen_Scope : Entity_Id)
379      return      Entity_Id;
380   --  When validating the actual types of a child instance, check whether
381   --  the formal is a formal type of the parent unit, and retrieve the current
382   --  actual for it. Typ is the entity in the analyzed formal type declaration
383   --  (component or index type of an array type) and Gen_Scope is the scope of
384   --  the analyzed formal array type.
385
386   function Get_Package_Instantiation_Node (A : Entity_Id) return Node_Id;
387   --  Given the entity of a unit that is an instantiation, retrieve the
388   --  original instance node. This is used when loading the instantiations
389   --  of the ancestors of a child generic that is being instantiated.
390
391   function In_Same_Declarative_Part
392     (F_Node : Node_Id;
393      Inst   : Node_Id)
394      return   Boolean;
395   --  True if the instantiation Inst and the given freeze_node F_Node appear
396   --  within the same declarative part, ignoring subunits, but with no inter-
397   --  vening suprograms or concurrent units. If true, the freeze node
398   --  of the instance can be placed after the freeze node of the parent,
399   --  which it itself an instance.
400
401   procedure Set_Instance_Env
402     (Gen_Unit : Entity_Id;
403      Act_Unit : Entity_Id);
404   --  Save current instance on saved environment, to be used to determine
405   --  the global status of entities in nested instances. Part of Save_Env.
406   --  called after verifying that the generic unit is legal for the instance.
407
408   procedure Set_Instance_Of (A : Entity_Id; B : Entity_Id);
409   --  Associate analyzed generic parameter with corresponding
410   --  instance. Used for semantic checks at instantiation time.
411
412   function Has_Been_Exchanged (E : Entity_Id) return Boolean;
413   --  Traverse the Exchanged_Views list to see if a type was private
414   --  and has already been flipped during this phase of instantiation.
415
416   procedure Hide_Current_Scope;
417   --  When compiling a generic child unit, the parent context must be
418   --  present, but the instance and all entities that may be generated
419   --  must be inserted in the current scope. We leave the current scope
420   --  on the stack, but make its entities invisible to avoid visibility
421   --  problems. This is reversed at the end of instantiations. This is
422   --  not done for the instantiation of the bodies, which only require the
423   --  instances of the generic parents to be in scope.
424
425   procedure Install_Body
426     (Act_Body : Node_Id;
427      N        : Node_Id;
428      Gen_Body : Node_Id;
429      Gen_Decl : Node_Id);
430   --  If the instantiation happens textually before the body of the generic,
431   --  the instantiation of the body must be analyzed after the generic body,
432   --  and not at the point of instantiation. Such early instantiations can
433   --  happen if the generic and the instance appear in  a package declaration
434   --  because the generic body can only appear in the corresponding package
435   --  body. Early instantiations can also appear if generic, instance and
436   --  body are all in the declarative part of a subprogram or entry. Entities
437   --  of packages that are early instantiations are delayed, and their freeze
438   --  node appears after the generic body.
439
440   procedure Insert_After_Last_Decl (N : Node_Id; F_Node : Node_Id);
441   --  Insert freeze node at the end of the declarative part that includes the
442   --  instance node N. If N is in the visible part of an enclosing package
443   --  declaration, the freeze node has to be inserted at the end of the
444   --  private declarations, if any.
445
446   procedure Freeze_Subprogram_Body
447     (Inst_Node : Node_Id;
448      Gen_Body  : Node_Id;
449      Pack_Id   : Entity_Id);
450   --  The generic body may appear textually after the instance, including
451   --  in the proper body of a stub, or within a different package instance.
452   --  Given that the instance can only be elaborated after the generic, we
453   --  place freeze_nodes for the instance and/or for packages that may enclose
454   --  the instance and the generic, so that the back-end can establish the
455   --  proper order of elaboration.
456
457   procedure Init_Env;
458   --  Establish environment for subsequent instantiation. Separated from
459   --  Save_Env because data-structures for visibility handling must be
460   --  initialized before call to Check_Generic_Child_Unit.
461
462   procedure Install_Parent (P : Entity_Id; In_Body : Boolean := False);
463   --  When compiling an instance of a child unit the parent (which is
464   --  itself an instance) is an enclosing scope that must be made
465   --  immediately visible. This procedure is also used to install the non-
466   --  generic parent of a generic child unit when compiling its body, so that
467   --  full views of types in the parent are made visible.
468
469   procedure Remove_Parent (In_Body : Boolean := False);
470   --  Reverse effect after instantiation of child is complete.
471
472   procedure Inline_Instance_Body
473     (N        : Node_Id;
474      Gen_Unit : Entity_Id;
475      Act_Decl : Node_Id);
476   --  If front-end inlining is requested, instantiate the package body,
477   --  and preserve the visibility of its compilation unit, to insure
478   --  that successive instantiations succeed.
479
480   --  The functions Instantiate_XXX perform various legality checks and build
481   --  the declarations for instantiated generic parameters.
482   --  Need to describe what the parameters are ???
483
484   function Instantiate_Object
485     (Formal          : Node_Id;
486      Actual          : Node_Id;
487      Analyzed_Formal : Node_Id)
488      return            List_Id;
489
490   function Instantiate_Type
491     (Formal          : Node_Id;
492      Actual          : Node_Id;
493      Analyzed_Formal : Node_Id;
494      Actual_Decls    : List_Id)
495      return            Node_Id;
496
497   function Instantiate_Formal_Subprogram
498     (Formal          : Node_Id;
499      Actual          : Node_Id;
500      Analyzed_Formal : Node_Id)
501      return            Node_Id;
502
503   function Instantiate_Formal_Package
504     (Formal          : Node_Id;
505      Actual          : Node_Id;
506      Analyzed_Formal : Node_Id)
507      return            List_Id;
508   --  If the formal package is declared with a box, special visibility rules
509   --  apply to its formals: they are in the visible part of the package. This
510   --  is true in the declarative region of the formal package, that is to say
511   --  in the enclosing generic or instantiation. For an instantiation, the
512   --  parameters of the formal package are made visible in an explicit step.
513   --  Furthermore, if the actual is a visible use_clause, these formals must
514   --  be made potentially use_visible as well. On exit from the enclosing
515   --  instantiation, the reverse must be done.
516
517   --  For a formal package declared without a box, there are conformance rules
518   --  that apply to the actuals in the generic declaration and the actuals of
519   --  the actual package in the enclosing instantiation. The simplest way to
520   --  apply these rules is to repeat the instantiation of the formal package
521   --  in the context of the enclosing instance, and compare the generic
522   --  associations of this instantiation with those of the actual package.
523
524   function Is_In_Main_Unit (N : Node_Id) return Boolean;
525   --  Test if given node is in the main unit
526
527   procedure Load_Parent_Of_Generic (N : Node_Id; Spec : Node_Id);
528   --  If the generic appears in a separate non-generic library unit,
529   --  load the corresponding body to retrieve the body of the generic.
530   --  N is the node for the generic instantiation, Spec is the generic
531   --  package declaration.
532
533   procedure Inherit_Context (Gen_Decl : Node_Id; Inst : Node_Id);
534   --  Add the context clause of the unit containing a generic unit to
535   --  an instantiation that is a compilation unit.
536
537   function Get_Associated_Node (N : Node_Id) return Node_Id;
538   --  In order to propagate semantic information back from the analyzed
539   --  copy to the original generic, we maintain links between selected nodes
540   --  in the generic and their corresponding copies. At the end of generic
541   --  analysis, the routine Save_Global_References traverses the generic
542   --  tree, examines the semantic information, and preserves the links to
543   --  those nodes that contain global information. At instantiation, the
544   --  information from the associated node is placed on the new copy, so
545   --  that name resolution is not repeated.
546   --
547   --  Three kinds of source nodes have associated nodes:
548   --
549   --    a) those that can reference (denote) entities, that is identifiers,
550   --       character literals, expanded_names, operator symbols, operators,
551   --       and attribute reference nodes. These nodes have an Entity field
552   --       and are the set of nodes that are in N_Has_Entity.
553   --
554   --    b) aggregates (N_Aggregate and N_Extension_Aggregate)
555   --
556   --    c) selected components (N_Selected_Component)
557   --
558   --  For the first class, the associated node preserves the entity if it is
559   --  global. If the generic contains nested instantiations, the associated
560   --  node itself has been recopied, and a chain of them must be followed.
561   --
562   --  For aggregates, the associated node allows retrieval of the type, which
563   --  may otherwise not appear in the generic. The view of this type may be
564   --  different between generic and instantiation, and the full view can be
565   --  installed before the instantiation is analyzed. For aggregates of
566   --  type extensions, the same view exchange may have to be performed for
567   --  some of the ancestor types, if their view is private at the point of
568   --  instantiation.
569   --
570   --  Nodes that are selected components in the parse tree may be rewritten
571   --  as expanded names after resolution, and must be treated as potential
572   --  entity holders. which is why they also have an Associated_Node.
573   --
574   --  Nodes that do not come from source, such as freeze nodes, do not appear
575   --  in the generic tree, and need not have an associated node.
576   --
577   --  The associated node is stored in the Associated_Node field. Note that
578   --  this field overlaps Entity, which is fine, because the whole point is
579   --  that we don't need or want the normal Entity field in this situation.
580
581   procedure Move_Freeze_Nodes
582     (Out_Of : Entity_Id;
583      After  : Node_Id;
584      L      : List_Id);
585   --  Freeze nodes can be generated in the analysis of a generic unit, but
586   --  will not be seen by the back-end. It is necessary to move those nodes
587   --  to the enclosing scope if they freeze an outer entity. We place them
588   --  at the end of the enclosing generic package, which is semantically
589   --  neutral.
590
591   procedure Pre_Analyze_Actuals (N : Node_Id);
592   --  Analyze actuals to perform name resolution. Full resolution is done
593   --  later, when the expected types are known, but names have to be captured
594   --  before installing parents of generics, that are not visible for the
595   --  actuals themselves.
596
597   procedure Valid_Default_Attribute (Nam : Entity_Id; Def : Node_Id);
598   --  Verify that an attribute that appears as the default for a formal
599   --  subprogram is a function or procedure with the correct profile.
600
601   -------------------------------------------
602   -- Data Structures for Generic Renamings --
603   -------------------------------------------
604
605   --  The map Generic_Renamings associates generic entities with their
606   --  corresponding actuals. Currently used to validate type instances.
607   --  It will eventually be used for all generic parameters to eliminate
608   --  the need for overload resolution in the instance.
609
610   type Assoc_Ptr is new Int;
611
612   Assoc_Null : constant Assoc_Ptr := -1;
613
614   type Assoc is record
615      Gen_Id         : Entity_Id;
616      Act_Id         : Entity_Id;
617      Next_In_HTable : Assoc_Ptr;
618   end record;
619
620   package Generic_Renamings is new Table.Table
621     (Table_Component_Type => Assoc,
622      Table_Index_Type     => Assoc_Ptr,
623      Table_Low_Bound      => 0,
624      Table_Initial        => 10,
625      Table_Increment      => 100,
626      Table_Name           => "Generic_Renamings");
627
628   --  Variable to hold enclosing instantiation. When the environment is
629   --  saved for a subprogram inlining, the corresponding Act_Id is empty.
630
631   Current_Instantiated_Parent : Assoc := (Empty, Empty, Assoc_Null);
632
633   --  Hash table for associations
634
635   HTable_Size : constant := 37;
636   type HTable_Range is range 0 .. HTable_Size - 1;
637
638   procedure Set_Next_Assoc (E : Assoc_Ptr; Next : Assoc_Ptr);
639   function  Next_Assoc     (E : Assoc_Ptr) return Assoc_Ptr;
640   function Get_Gen_Id      (E : Assoc_Ptr) return Entity_Id;
641   function Hash            (F : Entity_Id)   return HTable_Range;
642
643   package Generic_Renamings_HTable is new GNAT.HTable.Static_HTable (
644      Header_Num => HTable_Range,
645      Element    => Assoc,
646      Elmt_Ptr   => Assoc_Ptr,
647      Null_Ptr   => Assoc_Null,
648      Set_Next   => Set_Next_Assoc,
649      Next       => Next_Assoc,
650      Key        => Entity_Id,
651      Get_Key    => Get_Gen_Id,
652      Hash       => Hash,
653      Equal      => "=");
654
655   Exchanged_Views : Elist_Id;
656   --  This list holds the private views that have been exchanged during
657   --  instantiation to restore the visibility of the generic declaration.
658   --  (see comments above). After instantiation, the current visibility is
659   --  reestablished by means of a traversal of this list.
660
661   Hidden_Entities : Elist_Id;
662   --  This list holds the entities of the current scope that are removed
663   --  from immediate visibility when instantiating a child unit. Their
664   --  visibility is restored in Remove_Parent.
665
666   --  Because instantiations can be recursive, the following must be saved
667   --  on entry and restored on exit from an instantiation (spec or body).
668   --  This is done by the two procedures Save_Env and Restore_Env. For
669   --  package and subprogram instantiations (but not for the body instances)
670   --  the action of Save_Env is done in two steps: Init_Env is called before
671   --  Check_Generic_Child_Unit, because setting the parent instances requires
672   --  that the visibility data structures be properly initialized. Once the
673   --  generic is unit is validated, Set_Instance_Env completes Save_Env.
674
675   type Instance_Env is record
676      Ada_83              : Boolean;
677      Instantiated_Parent : Assoc;
678      Exchanged_Views     : Elist_Id;
679      Hidden_Entities     : Elist_Id;
680      Current_Sem_Unit    : Unit_Number_Type;
681   end record;
682
683   package Instance_Envs is new Table.Table (
684     Table_Component_Type => Instance_Env,
685     Table_Index_Type     => Int,
686     Table_Low_Bound      => 0,
687     Table_Initial        => 32,
688     Table_Increment      => 100,
689     Table_Name           => "Instance_Envs");
690
691   procedure Restore_Private_Views
692     (Pack_Id    : Entity_Id;
693      Is_Package : Boolean := True);
694   --  Restore the private views of external types, and unmark the generic
695   --  renamings of actuals, so that they become comptible subtypes again.
696   --  For subprograms, Pack_Id is the package constructed to hold the
697   --  renamings.
698
699   procedure Switch_View (T : Entity_Id);
700   --  Switch the partial and full views of a type and its private
701   --  dependents (i.e. its subtypes and derived types).
702
703   ------------------------------------
704   -- Structures for Error Reporting --
705   ------------------------------------
706
707   Instantiation_Node : Node_Id;
708   --  Used by subprograms that validate instantiation of formal parameters
709   --  where there might be no actual on which to place the error message.
710   --  Also used to locate the instantiation node for generic subunits.
711
712   Instantiation_Error : exception;
713   --  When there is a semantic error in the generic parameter matching,
714   --  there is no point in continuing the instantiation, because the
715   --  number of cascaded errors is unpredictable. This exception aborts
716   --  the instantiation process altogether.
717
718   S_Adjustment : Sloc_Adjustment;
719   --  Offset created for each node in an instantiation, in order to keep
720   --  track of the source position of the instantiation in each of its nodes.
721   --  A subsequent semantic error or warning on a construct of the instance
722   --  points to both places: the original generic node, and the point of
723   --  instantiation. See Sinput and Sinput.L for additional details.
724
725   ------------------------------------------------------------
726   -- Data structure for keeping track when inside a Generic --
727   ------------------------------------------------------------
728
729   --  The following table is used to save values of the Inside_A_Generic
730   --  flag (see spec of Sem) when they are saved by Start_Generic.
731
732   package Generic_Flags is new Table.Table (
733     Table_Component_Type => Boolean,
734     Table_Index_Type     => Int,
735     Table_Low_Bound      => 0,
736     Table_Initial        => 32,
737     Table_Increment      => 200,
738     Table_Name           => "Generic_Flags");
739
740   ---------------------------
741   -- Abandon_Instantiation --
742   ---------------------------
743
744   procedure Abandon_Instantiation (N : Node_Id) is
745   begin
746      Error_Msg_N ("instantiation abandoned!", N);
747      raise Instantiation_Error;
748   end Abandon_Instantiation;
749
750   --------------------------
751   -- Analyze_Associations --
752   --------------------------
753
754   function Analyze_Associations
755     (I_Node  : Node_Id;
756      Formals : List_Id;
757      F_Copy  : List_Id)
758      return    List_Id
759   is
760      Actual_Types    : constant Elist_Id  := New_Elmt_List;
761      Assoc           : constant List_Id   := New_List;
762      Defaults        : constant Elist_Id  := New_Elmt_List;
763      Gen_Unit        : constant Entity_Id := Defining_Entity
764                                                (Parent (F_Copy));
765      Actuals         : List_Id;
766      Actual          : Node_Id;
767      Formal          : Node_Id;
768      Next_Formal     : Node_Id;
769      Temp_Formal     : Node_Id;
770      Analyzed_Formal : Node_Id;
771      Match           : Node_Id;
772      Named           : Node_Id;
773      First_Named     : Node_Id := Empty;
774      Found_Assoc     : Node_Id;
775      Is_Named_Assoc  : Boolean;
776      Num_Matched     : Int := 0;
777      Num_Actuals     : Int := 0;
778
779      function Matching_Actual
780        (F    : Entity_Id;
781         A_F  : Entity_Id)
782         return Node_Id;
783      --  Find actual that corresponds to a given a formal parameter. If the
784      --  actuals are positional, return the next one, if any. If the actuals
785      --  are named, scan the parameter associations to find the right one.
786      --  A_F is the corresponding entity in the analyzed generic,which is
787      --  placed on the selector name for ASIS use.
788
789      procedure Set_Analyzed_Formal;
790      --  Find the node in the generic copy that corresponds to a given formal.
791      --  The semantic information on this node is used to perform legality
792      --  checks on the actuals. Because semantic analysis can introduce some
793      --  anonymous entities or modify the declaration node itself, the
794      --  correspondence between the two lists is not one-one. In addition to
795      --  anonymous types, the presence a formal equality will introduce an
796      --  implicit declaration for the corresponding inequality.
797
798      ---------------------
799      -- Matching_Actual --
800      ---------------------
801
802      function Matching_Actual
803        (F    : Entity_Id;
804         A_F  : Entity_Id)
805         return Node_Id
806      is
807         Found : Node_Id;
808         Prev  : Node_Id;
809
810      begin
811         Is_Named_Assoc := False;
812
813         --  End of list of purely positional parameters
814
815         if No (Actual) then
816            Found := Empty;
817
818         --  Case of positional parameter corresponding to current formal
819
820         elsif No (Selector_Name (Actual)) then
821            Found := Explicit_Generic_Actual_Parameter (Actual);
822            Found_Assoc := Actual;
823            Num_Matched := Num_Matched + 1;
824            Next (Actual);
825
826         --  Otherwise scan list of named actuals to find the one with the
827         --  desired name. All remaining actuals have explicit names.
828
829         else
830            Is_Named_Assoc := True;
831            Found := Empty;
832            Prev  := Empty;
833
834            while Present (Actual) loop
835               if Chars (Selector_Name (Actual)) = Chars (F) then
836                  Found := Explicit_Generic_Actual_Parameter (Actual);
837                  Set_Entity (Selector_Name (Actual), A_F);
838                  Set_Etype  (Selector_Name (Actual), Etype (A_F));
839                  Generate_Reference (A_F, Selector_Name (Actual));
840                  Found_Assoc := Actual;
841                  Num_Matched := Num_Matched + 1;
842                  exit;
843               end if;
844
845               Prev := Actual;
846               Next (Actual);
847            end loop;
848
849            --  Reset for subsequent searches. In most cases the named
850            --  associations are in order. If they are not, we reorder them
851            --  to avoid scanning twice the same actual. This is not just a
852            --  question of efficiency: there may be multiple defaults with
853            --  boxes that have the same name. In a nested instantiation we
854            --  insert actuals for those defaults, and cannot rely on their
855            --  names to disambiguate them.
856
857            if Actual = First_Named  then
858               Next (First_Named);
859
860            elsif Present (Actual) then
861               Insert_Before (First_Named, Remove_Next (Prev));
862            end if;
863
864            Actual := First_Named;
865         end if;
866
867         return Found;
868      end Matching_Actual;
869
870      -------------------------
871      -- Set_Analyzed_Formal --
872      -------------------------
873
874      procedure Set_Analyzed_Formal is
875         Kind : Node_Kind;
876      begin
877         while Present (Analyzed_Formal) loop
878            Kind := Nkind (Analyzed_Formal);
879
880            case Nkind (Formal) is
881
882               when N_Formal_Subprogram_Declaration =>
883                  exit when Kind = N_Formal_Subprogram_Declaration
884                    and then
885                      Chars
886                        (Defining_Unit_Name (Specification (Formal))) =
887                      Chars
888                        (Defining_Unit_Name (Specification (Analyzed_Formal)));
889
890               when N_Formal_Package_Declaration =>
891                  exit when
892                    Kind = N_Formal_Package_Declaration
893                      or else
894                    Kind = N_Generic_Package_Declaration;
895
896               when N_Use_Package_Clause | N_Use_Type_Clause => exit;
897
898               when others =>
899
900                  --  Skip freeze nodes, and nodes inserted to replace
901                  --  unrecognized pragmas.
902
903                  exit when
904                    Kind /= N_Formal_Subprogram_Declaration
905                      and then Kind /= N_Subprogram_Declaration
906                      and then Kind /= N_Freeze_Entity
907                      and then Kind /= N_Null_Statement
908                      and then Kind /= N_Itype_Reference
909                      and then Chars (Defining_Identifier (Formal)) =
910                               Chars (Defining_Identifier (Analyzed_Formal));
911            end case;
912
913            Next (Analyzed_Formal);
914         end loop;
915
916      end Set_Analyzed_Formal;
917
918   --  Start of processing for Analyze_Associations
919
920   begin
921      --  If named associations are present, save the first named association
922      --  (it may of course be Empty) to facilitate subsequent name search.
923
924      Actuals := Generic_Associations (I_Node);
925
926      if Present (Actuals) then
927         First_Named := First (Actuals);
928
929         while Present (First_Named)
930           and then No (Selector_Name (First_Named))
931         loop
932            Num_Actuals := Num_Actuals + 1;
933            Next (First_Named);
934         end loop;
935      end if;
936
937      Named := First_Named;
938      while Present (Named) loop
939         if No (Selector_Name (Named)) then
940            Error_Msg_N ("invalid positional actual after named one", Named);
941            Abandon_Instantiation (Named);
942         end if;
943
944         --  A named association may lack an actual parameter, if it was
945         --  introduced for a default subprogram that turns out to be local
946         --  to the outer instantiation.
947
948         if Present (Explicit_Generic_Actual_Parameter (Named)) then
949            Num_Actuals := Num_Actuals + 1;
950         end if;
951
952         Next (Named);
953      end loop;
954
955      if Present (Formals) then
956         Formal := First_Non_Pragma (Formals);
957         Analyzed_Formal := First_Non_Pragma (F_Copy);
958
959         if Present (Actuals) then
960            Actual := First (Actuals);
961
962         --  All formals should have default values
963
964         else
965            Actual := Empty;
966         end if;
967
968         while Present (Formal) loop
969            Set_Analyzed_Formal;
970            Next_Formal := Next_Non_Pragma (Formal);
971
972            case Nkind (Formal) is
973               when N_Formal_Object_Declaration =>
974                  Match :=
975                    Matching_Actual (
976                      Defining_Identifier (Formal),
977                      Defining_Identifier (Analyzed_Formal));
978
979                  Append_List
980                    (Instantiate_Object (Formal, Match, Analyzed_Formal),
981                     Assoc);
982
983               when N_Formal_Type_Declaration =>
984                  Match :=
985                    Matching_Actual (
986                      Defining_Identifier (Formal),
987                      Defining_Identifier (Analyzed_Formal));
988
989                  if No (Match) then
990                     Error_Msg_Sloc := Sloc (Gen_Unit);
991                     Error_Msg_NE
992                       ("missing actual&",
993                         Instantiation_Node, Defining_Identifier (Formal));
994                     Error_Msg_NE ("\in instantiation of & declared#",
995                         Instantiation_Node, Gen_Unit);
996                     Abandon_Instantiation (Instantiation_Node);
997
998                  else
999                     Analyze (Match);
1000                     Append_To (Assoc,
1001                       Instantiate_Type
1002                         (Formal, Match, Analyzed_Formal, Assoc));
1003
1004                     --  an instantiation is a freeze point for the actuals,
1005                     --  unless this is a rewritten formal package.
1006
1007                     if Nkind (I_Node) /= N_Formal_Package_Declaration then
1008                        Append_Elmt (Entity (Match), Actual_Types);
1009                     end if;
1010                  end if;
1011
1012                  --  A remote access-to-class-wide type must not be an
1013                  --  actual parameter for a generic formal of an access
1014                  --  type (E.2.2 (17)).
1015
1016                  if Nkind (Analyzed_Formal) = N_Formal_Type_Declaration
1017                    and then
1018                      Nkind (Formal_Type_Definition (Analyzed_Formal)) =
1019                                            N_Access_To_Object_Definition
1020                  then
1021                     Validate_Remote_Access_To_Class_Wide_Type (Match);
1022                  end if;
1023
1024               when N_Formal_Subprogram_Declaration =>
1025                  Match :=
1026                    Matching_Actual (
1027                      Defining_Unit_Name (Specification (Formal)),
1028                      Defining_Unit_Name (Specification (Analyzed_Formal)));
1029
1030                  --  If the formal subprogram has the same name as
1031                  --  another formal subprogram of the generic, then
1032                  --  a named association is illegal (12.3(9)). Exclude
1033                  --  named associations that are generated for a nested
1034                  --  instance.
1035
1036                  if Present (Match)
1037                    and then Is_Named_Assoc
1038                    and then Comes_From_Source (Found_Assoc)
1039                  then
1040                     Temp_Formal := First (Formals);
1041                     while Present (Temp_Formal) loop
1042                        if Nkind (Temp_Formal) =
1043                             N_Formal_Subprogram_Declaration
1044                          and then Temp_Formal /= Formal
1045                          and then
1046                            Chars (Selector_Name (Found_Assoc)) =
1047                              Chars (Defining_Unit_Name
1048                                       (Specification (Temp_Formal)))
1049                        then
1050                           Error_Msg_N
1051                             ("name not allowed for overloaded formal",
1052                              Found_Assoc);
1053                           Abandon_Instantiation (Instantiation_Node);
1054                        end if;
1055
1056                        Next (Temp_Formal);
1057                     end loop;
1058                  end if;
1059
1060                  Append_To (Assoc,
1061                    Instantiate_Formal_Subprogram
1062                      (Formal, Match, Analyzed_Formal));
1063
1064                  if No (Match)
1065                    and then Box_Present (Formal)
1066                  then
1067                     Append_Elmt
1068                       (Defining_Unit_Name (Specification (Last (Assoc))),
1069                         Defaults);
1070                  end if;
1071
1072               when N_Formal_Package_Declaration =>
1073                  Match :=
1074                    Matching_Actual (
1075                      Defining_Identifier (Formal),
1076                      Defining_Identifier (Original_Node (Analyzed_Formal)));
1077
1078                  if No (Match) then
1079                     Error_Msg_Sloc := Sloc (Gen_Unit);
1080                     Error_Msg_NE
1081                       ("missing actual&",
1082                         Instantiation_Node, Defining_Identifier (Formal));
1083                     Error_Msg_NE ("\in instantiation of & declared#",
1084                         Instantiation_Node, Gen_Unit);
1085
1086                     Abandon_Instantiation (Instantiation_Node);
1087
1088                  else
1089                     Analyze (Match);
1090                     Append_List
1091                       (Instantiate_Formal_Package
1092                         (Formal, Match, Analyzed_Formal),
1093                        Assoc);
1094                  end if;
1095
1096               --  For use type and use package appearing in the context
1097               --  clause, we have already copied them, so we can just
1098               --  move them where they belong (we mustn't recopy them
1099               --  since this would mess up the Sloc values).
1100
1101               when N_Use_Package_Clause |
1102                    N_Use_Type_Clause    =>
1103                  Remove (Formal);
1104                  Append (Formal, Assoc);
1105
1106               when others =>
1107                  raise Program_Error;
1108
1109            end case;
1110
1111            Formal := Next_Formal;
1112            Next_Non_Pragma (Analyzed_Formal);
1113         end loop;
1114
1115         if Num_Actuals > Num_Matched then
1116            Error_Msg_Sloc := Sloc (Gen_Unit);
1117
1118            if Present (Selector_Name (Actual)) then
1119               Error_Msg_NE
1120                 ("unmatched actual&",
1121                    Actual, Selector_Name (Actual));
1122               Error_Msg_NE ("\in instantiation of& declared#",
1123                    Actual, Gen_Unit);
1124            else
1125               Error_Msg_NE
1126                 ("unmatched actual in instantiation of& declared#",
1127                   Actual, Gen_Unit);
1128            end if;
1129         end if;
1130
1131      elsif Present (Actuals) then
1132         Error_Msg_N
1133           ("too many actuals in generic instantiation", Instantiation_Node);
1134      end if;
1135
1136      declare
1137         Elmt : Elmt_Id := First_Elmt (Actual_Types);
1138
1139      begin
1140         while Present (Elmt) loop
1141            Freeze_Before (I_Node, Node (Elmt));
1142            Next_Elmt (Elmt);
1143         end loop;
1144      end;
1145
1146      --  If there are default subprograms, normalize the tree by adding
1147      --  explicit associations for them. This is required if the instance
1148      --  appears within a generic.
1149
1150      declare
1151         Elmt  : Elmt_Id;
1152         Subp  : Entity_Id;
1153         New_D : Node_Id;
1154
1155      begin
1156         Elmt := First_Elmt (Defaults);
1157         while Present (Elmt) loop
1158            if No (Actuals) then
1159               Actuals := New_List;
1160               Set_Generic_Associations (I_Node, Actuals);
1161            end if;
1162
1163            Subp := Node (Elmt);
1164            New_D :=
1165              Make_Generic_Association (Sloc (Subp),
1166                Selector_Name => New_Occurrence_Of (Subp, Sloc (Subp)),
1167                  Explicit_Generic_Actual_Parameter =>
1168                    New_Occurrence_Of (Subp, Sloc (Subp)));
1169            Mark_Rewrite_Insertion (New_D);
1170            Append_To (Actuals, New_D);
1171            Next_Elmt (Elmt);
1172         end loop;
1173      end;
1174
1175      return Assoc;
1176   end Analyze_Associations;
1177
1178   -------------------------------
1179   -- Analyze_Formal_Array_Type --
1180   -------------------------------
1181
1182   procedure Analyze_Formal_Array_Type
1183     (T   : in out Entity_Id;
1184      Def : Node_Id)
1185   is
1186      DSS : Node_Id;
1187
1188   begin
1189      --  Treated like a non-generic array declaration, with
1190      --  additional semantic checks.
1191
1192      Enter_Name (T);
1193
1194      if Nkind (Def) = N_Constrained_Array_Definition then
1195         DSS := First (Discrete_Subtype_Definitions (Def));
1196         while Present (DSS) loop
1197            if Nkind (DSS) = N_Subtype_Indication
1198              or else Nkind (DSS) = N_Range
1199              or else Nkind (DSS) = N_Attribute_Reference
1200            then
1201               Error_Msg_N ("only a subtype mark is allowed in a formal", DSS);
1202            end if;
1203
1204            Next (DSS);
1205         end loop;
1206      end if;
1207
1208      Array_Type_Declaration (T, Def);
1209      Set_Is_Generic_Type (Base_Type (T));
1210
1211      if Ekind (Component_Type (T)) = E_Incomplete_Type
1212        and then No (Full_View (Component_Type (T)))
1213      then
1214         Error_Msg_N ("premature usage of incomplete type", Def);
1215
1216      elsif Is_Internal (Component_Type (T))
1217        and then Nkind (Original_Node
1218                        (Subtype_Indication (Component_Definition (Def))))
1219          /= N_Attribute_Reference
1220      then
1221         Error_Msg_N
1222           ("only a subtype mark is allowed in a formal",
1223              Subtype_Indication (Component_Definition (Def)));
1224      end if;
1225
1226   end Analyze_Formal_Array_Type;
1227
1228   ---------------------------------------------
1229   -- Analyze_Formal_Decimal_Fixed_Point_Type --
1230   ---------------------------------------------
1231
1232   --  As for other generic types, we create a valid type representation
1233   --  with legal but arbitrary attributes, whose values are never considered
1234   --  static. For all scalar types we introduce an anonymous base type, with
1235   --  the same attributes. We choose the corresponding integer type to be
1236   --  Standard_Integer.
1237
1238   procedure Analyze_Formal_Decimal_Fixed_Point_Type
1239     (T   : Entity_Id;
1240      Def : Node_Id)
1241   is
1242      Loc       : constant Source_Ptr := Sloc (Def);
1243      Base      : constant Entity_Id :=
1244                    New_Internal_Entity
1245                      (E_Decimal_Fixed_Point_Type,
1246                       Current_Scope, Sloc (Def), 'G');
1247      Int_Base  : constant Entity_Id := Standard_Integer;
1248      Delta_Val : constant Ureal := Ureal_1;
1249      Digs_Val  : constant Uint  := Uint_6;
1250
1251   begin
1252      Enter_Name (T);
1253
1254      Set_Etype          (Base, Base);
1255      Set_Size_Info      (Base, Int_Base);
1256      Set_RM_Size        (Base, RM_Size (Int_Base));
1257      Set_First_Rep_Item (Base, First_Rep_Item (Int_Base));
1258      Set_Digits_Value   (Base, Digs_Val);
1259      Set_Delta_Value    (Base, Delta_Val);
1260      Set_Small_Value    (Base, Delta_Val);
1261      Set_Scalar_Range   (Base,
1262        Make_Range (Loc,
1263          Low_Bound  => Make_Real_Literal (Loc, Ureal_1),
1264          High_Bound => Make_Real_Literal (Loc, Ureal_1)));
1265
1266      Set_Is_Generic_Type (Base);
1267      Set_Parent          (Base, Parent (Def));
1268
1269      Set_Ekind          (T, E_Decimal_Fixed_Point_Subtype);
1270      Set_Etype          (T, Base);
1271      Set_Size_Info      (T, Int_Base);
1272      Set_RM_Size        (T, RM_Size (Int_Base));
1273      Set_First_Rep_Item (T, First_Rep_Item (Int_Base));
1274      Set_Digits_Value   (T, Digs_Val);
1275      Set_Delta_Value    (T, Delta_Val);
1276      Set_Small_Value    (T, Delta_Val);
1277      Set_Scalar_Range   (T, Scalar_Range (Base));
1278
1279      Check_Restriction (No_Fixed_Point, Def);
1280   end Analyze_Formal_Decimal_Fixed_Point_Type;
1281
1282   ---------------------------------
1283   -- Analyze_Formal_Derived_Type --
1284   ---------------------------------
1285
1286   procedure Analyze_Formal_Derived_Type
1287     (N   : Node_Id;
1288      T   : Entity_Id;
1289      Def : Node_Id)
1290   is
1291      Loc      : constant Source_Ptr := Sloc (Def);
1292      Unk_Disc : constant Boolean    := Unknown_Discriminants_Present (N);
1293      New_N    : Node_Id;
1294
1295   begin
1296      Set_Is_Generic_Type (T);
1297
1298      if Private_Present (Def) then
1299         New_N :=
1300           Make_Private_Extension_Declaration (Loc,
1301             Defining_Identifier           => T,
1302             Discriminant_Specifications   => Discriminant_Specifications (N),
1303             Unknown_Discriminants_Present => Unk_Disc,
1304             Subtype_Indication            => Subtype_Mark (Def));
1305
1306         Set_Abstract_Present (New_N, Abstract_Present (Def));
1307
1308      else
1309         New_N :=
1310           Make_Full_Type_Declaration (Loc,
1311             Defining_Identifier => T,
1312             Discriminant_Specifications =>
1313               Discriminant_Specifications (Parent (T)),
1314              Type_Definition =>
1315                Make_Derived_Type_Definition (Loc,
1316                  Subtype_Indication => Subtype_Mark (Def)));
1317
1318         Set_Abstract_Present
1319           (Type_Definition (New_N), Abstract_Present (Def));
1320      end if;
1321
1322      Rewrite (N, New_N);
1323      Analyze (N);
1324
1325      if Unk_Disc then
1326         if not Is_Composite_Type (T) then
1327            Error_Msg_N
1328              ("unknown discriminants not allowed for elementary types", N);
1329         else
1330            Set_Has_Unknown_Discriminants (T);
1331            Set_Is_Constrained (T, False);
1332         end if;
1333      end if;
1334
1335      --  If the parent type has a known size, so does the formal, which
1336      --  makes legal representation clauses that involve the formal.
1337
1338      Set_Size_Known_At_Compile_Time
1339        (T, Size_Known_At_Compile_Time (Entity (Subtype_Mark (Def))));
1340
1341   end Analyze_Formal_Derived_Type;
1342
1343   ----------------------------------
1344   -- Analyze_Formal_Discrete_Type --
1345   ----------------------------------
1346
1347   --  The operations defined for a discrete types are those of an
1348   --  enumeration type. The size is set to an arbitrary value, for use
1349   --  in analyzing the generic unit.
1350
1351   procedure Analyze_Formal_Discrete_Type (T : Entity_Id; Def : Node_Id) is
1352      Loc : constant Source_Ptr := Sloc (Def);
1353      Lo  : Node_Id;
1354      Hi  : Node_Id;
1355
1356   begin
1357      Enter_Name     (T);
1358      Set_Ekind      (T, E_Enumeration_Type);
1359      Set_Etype      (T, T);
1360      Init_Size      (T, 8);
1361      Init_Alignment (T);
1362
1363      --  For semantic analysis, the bounds of the type must be set to some
1364      --  non-static value. The simplest is to create attribute nodes for
1365      --  those bounds, that refer to the type itself. These bounds are never
1366      --  analyzed but serve as place-holders.
1367
1368      Lo :=
1369        Make_Attribute_Reference (Loc,
1370          Attribute_Name => Name_First,
1371          Prefix => New_Reference_To (T, Loc));
1372      Set_Etype (Lo, T);
1373
1374      Hi :=
1375        Make_Attribute_Reference (Loc,
1376          Attribute_Name => Name_Last,
1377          Prefix => New_Reference_To (T, Loc));
1378      Set_Etype (Hi, T);
1379
1380      Set_Scalar_Range (T,
1381        Make_Range (Loc,
1382          Low_Bound => Lo,
1383          High_Bound => Hi));
1384
1385   end Analyze_Formal_Discrete_Type;
1386
1387   ----------------------------------
1388   -- Analyze_Formal_Floating_Type --
1389   ---------------------------------
1390
1391   procedure Analyze_Formal_Floating_Type (T : Entity_Id; Def : Node_Id) is
1392      Base : constant Entity_Id :=
1393               New_Internal_Entity
1394                 (E_Floating_Point_Type, Current_Scope, Sloc (Def), 'G');
1395
1396   begin
1397      --  The various semantic attributes are taken from the predefined type
1398      --  Float, just so that all of them are initialized. Their values are
1399      --  never used because no constant folding or expansion takes place in
1400      --  the generic itself.
1401
1402      Enter_Name (T);
1403      Set_Ekind        (T, E_Floating_Point_Subtype);
1404      Set_Etype        (T, Base);
1405      Set_Size_Info    (T,              (Standard_Float));
1406      Set_RM_Size      (T, RM_Size      (Standard_Float));
1407      Set_Digits_Value (T, Digits_Value (Standard_Float));
1408      Set_Scalar_Range (T, Scalar_Range (Standard_Float));
1409
1410      Set_Is_Generic_Type (Base);
1411      Set_Etype           (Base, Base);
1412      Set_Size_Info       (Base,              (Standard_Float));
1413      Set_RM_Size         (Base, RM_Size      (Standard_Float));
1414      Set_Digits_Value    (Base, Digits_Value (Standard_Float));
1415      Set_Scalar_Range    (Base, Scalar_Range (Standard_Float));
1416      Set_Parent          (Base, Parent (Def));
1417
1418      Check_Restriction (No_Floating_Point, Def);
1419   end Analyze_Formal_Floating_Type;
1420
1421   ---------------------------------
1422   -- Analyze_Formal_Modular_Type --
1423   ---------------------------------
1424
1425   procedure Analyze_Formal_Modular_Type (T : Entity_Id; Def : Node_Id) is
1426   begin
1427      --  Apart from their entity kind, generic modular types are treated
1428      --  like signed integer types, and have the same attributes.
1429
1430      Analyze_Formal_Signed_Integer_Type (T, Def);
1431      Set_Ekind (T, E_Modular_Integer_Subtype);
1432      Set_Ekind (Etype (T), E_Modular_Integer_Type);
1433
1434   end Analyze_Formal_Modular_Type;
1435
1436   ---------------------------------------
1437   -- Analyze_Formal_Object_Declaration --
1438   ---------------------------------------
1439
1440   procedure Analyze_Formal_Object_Declaration (N : Node_Id) is
1441      E  : constant Node_Id := Expression (N);
1442      Id : constant Node_Id := Defining_Identifier (N);
1443      K  : Entity_Kind;
1444      T  : Node_Id;
1445
1446   begin
1447      Enter_Name (Id);
1448
1449      --  Determine the mode of the formal object
1450
1451      if Out_Present (N) then
1452         K := E_Generic_In_Out_Parameter;
1453
1454         if not In_Present (N) then
1455            Error_Msg_N ("formal generic objects cannot have mode OUT", N);
1456         end if;
1457
1458      else
1459         K := E_Generic_In_Parameter;
1460      end if;
1461
1462      Find_Type (Subtype_Mark (N));
1463      T  := Entity (Subtype_Mark (N));
1464
1465      if Ekind (T) = E_Incomplete_Type then
1466         Error_Msg_N ("premature usage of incomplete type", Subtype_Mark (N));
1467      end if;
1468
1469      if K = E_Generic_In_Parameter then
1470
1471         --  Ada0Y (AI-287): Limited aggregates allowed in generic formals
1472
1473         if not Extensions_Allowed and then Is_Limited_Type (T) then
1474            Error_Msg_N
1475              ("generic formal of mode IN must not be of limited type", N);
1476            Explain_Limited_Type (T, N);
1477         end if;
1478
1479         if Is_Abstract (T) then
1480            Error_Msg_N
1481              ("generic formal of mode IN must not be of abstract type", N);
1482         end if;
1483
1484         if Present (E) then
1485            Analyze_Per_Use_Expression (E, T);
1486         end if;
1487
1488         Set_Ekind (Id, K);
1489         Set_Etype (Id, T);
1490
1491      --  Case of generic IN OUT parameter.
1492
1493      else
1494         --  If the formal has an unconstrained type, construct its
1495         --  actual subtype, as is done for subprogram formals. In this
1496         --  fashion, all its uses can refer to specific bounds.
1497
1498         Set_Ekind (Id, K);
1499         Set_Etype (Id, T);
1500
1501         if (Is_Array_Type (T)
1502              and then not Is_Constrained (T))
1503           or else
1504            (Ekind (T) = E_Record_Type
1505              and then Has_Discriminants (T))
1506         then
1507            declare
1508               Non_Freezing_Ref : constant Node_Id :=
1509                                    New_Reference_To (Id, Sloc (Id));
1510               Decl : Node_Id;
1511
1512            begin
1513               --  Make sure that the actual subtype doesn't generate
1514               --  bogus freezing.
1515
1516               Set_Must_Not_Freeze (Non_Freezing_Ref);
1517               Decl := Build_Actual_Subtype (T, Non_Freezing_Ref);
1518               Insert_Before_And_Analyze (N, Decl);
1519               Set_Actual_Subtype (Id, Defining_Identifier (Decl));
1520            end;
1521         else
1522            Set_Actual_Subtype (Id, T);
1523         end if;
1524
1525         if Present (E) then
1526            Error_Msg_N
1527              ("initialization not allowed for `IN OUT` formals", N);
1528         end if;
1529      end if;
1530
1531   end Analyze_Formal_Object_Declaration;
1532
1533   ----------------------------------------------
1534   -- Analyze_Formal_Ordinary_Fixed_Point_Type --
1535   ----------------------------------------------
1536
1537   procedure Analyze_Formal_Ordinary_Fixed_Point_Type
1538     (T   : Entity_Id;
1539      Def : Node_Id)
1540   is
1541      Loc  : constant Source_Ptr := Sloc (Def);
1542      Base : constant Entity_Id :=
1543               New_Internal_Entity
1544                 (E_Ordinary_Fixed_Point_Type, Current_Scope, Sloc (Def), 'G');
1545   begin
1546      --  The semantic attributes are set for completeness only, their
1547      --  values will never be used, because all properties of the type
1548      --  are non-static.
1549
1550      Enter_Name (T);
1551      Set_Ekind            (T, E_Ordinary_Fixed_Point_Subtype);
1552      Set_Etype            (T, Base);
1553      Set_Size_Info        (T, Standard_Integer);
1554      Set_RM_Size          (T, RM_Size (Standard_Integer));
1555      Set_Small_Value      (T, Ureal_1);
1556      Set_Delta_Value      (T, Ureal_1);
1557      Set_Scalar_Range     (T,
1558        Make_Range (Loc,
1559          Low_Bound  => Make_Real_Literal (Loc, Ureal_1),
1560          High_Bound => Make_Real_Literal (Loc, Ureal_1)));
1561
1562      Set_Is_Generic_Type (Base);
1563      Set_Etype           (Base, Base);
1564      Set_Size_Info       (Base, Standard_Integer);
1565      Set_RM_Size         (Base, RM_Size (Standard_Integer));
1566      Set_Small_Value     (Base, Ureal_1);
1567      Set_Delta_Value     (Base, Ureal_1);
1568      Set_Scalar_Range    (Base, Scalar_Range (T));
1569      Set_Parent          (Base, Parent (Def));
1570
1571      Check_Restriction (No_Fixed_Point, Def);
1572   end Analyze_Formal_Ordinary_Fixed_Point_Type;
1573
1574   ----------------------------
1575   -- Analyze_Formal_Package --
1576   ----------------------------
1577
1578   procedure Analyze_Formal_Package (N : Node_Id) is
1579      Loc              : constant Source_Ptr := Sloc (N);
1580      Formal           : constant Entity_Id  := Defining_Identifier (N);
1581      Gen_Id           : constant Node_Id    := Name (N);
1582      Gen_Decl         : Node_Id;
1583      Gen_Unit         : Entity_Id;
1584      New_N            : Node_Id;
1585      Parent_Installed : Boolean := False;
1586      Renaming         : Node_Id;
1587      Parent_Instance  : Entity_Id;
1588      Renaming_In_Par  : Entity_Id;
1589
1590   begin
1591      Text_IO_Kludge (Gen_Id);
1592
1593      Init_Env;
1594      Check_Generic_Child_Unit (Gen_Id, Parent_Installed);
1595      Gen_Unit := Entity (Gen_Id);
1596
1597      if Ekind (Gen_Unit) /= E_Generic_Package then
1598         Error_Msg_N ("expect generic package name", Gen_Id);
1599         Restore_Env;
1600         return;
1601
1602      elsif  Gen_Unit = Current_Scope then
1603         Error_Msg_N
1604           ("generic package cannot be used as a formal package of itself",
1605             Gen_Id);
1606         Restore_Env;
1607         return;
1608
1609      elsif In_Open_Scopes (Gen_Unit) then
1610         if Is_Compilation_Unit (Gen_Unit)
1611           and then Is_Child_Unit (Current_Scope)
1612         then
1613            --  Special-case the error when the formal is a parent, and
1614            --  continue analysis to minimize cascaded errors.
1615
1616            Error_Msg_N
1617              ("generic parent cannot be used as formal package "
1618                & "of a child unit",
1619                Gen_Id);
1620
1621         else
1622            Error_Msg_N
1623              ("generic package cannot be used as a formal package "
1624                & "within itself",
1625                Gen_Id);
1626            Restore_Env;
1627            return;
1628         end if;
1629      end if;
1630
1631      --  Check for a formal package that is a package renaming.
1632
1633      if Present (Renamed_Object (Gen_Unit)) then
1634         Gen_Unit := Renamed_Object (Gen_Unit);
1635      end if;
1636
1637      --  The formal package is treated like a regular instance, but only
1638      --  the specification needs to be instantiated, to make entities visible.
1639
1640      if not Box_Present (N) then
1641         Hidden_Entities := New_Elmt_List;
1642         Analyze_Package_Instantiation (N);
1643
1644         if Parent_Installed then
1645            Remove_Parent;
1646         end if;
1647
1648      else
1649         --  If there are no generic associations, the generic parameters
1650         --  appear as local entities and are instantiated like them. We copy
1651         --  the generic package declaration as if it were an instantiation,
1652         --  and analyze it like a regular package, except that we treat the
1653         --  formals as additional visible components.
1654
1655         Set_Instance_Env (Gen_Unit, Formal);
1656
1657         Gen_Decl := Unit_Declaration_Node (Gen_Unit);
1658
1659         if In_Extended_Main_Source_Unit (N) then
1660            Set_Is_Instantiated (Gen_Unit);
1661            Generate_Reference  (Gen_Unit, N);
1662         end if;
1663
1664         New_N :=
1665           Copy_Generic_Node
1666             (Original_Node (Gen_Decl), Empty, Instantiating => True);
1667         Set_Defining_Unit_Name (Specification (New_N), Formal);
1668         Rewrite (N, New_N);
1669
1670         Enter_Name (Formal);
1671         Set_Ekind  (Formal, E_Generic_Package);
1672         Set_Etype  (Formal, Standard_Void_Type);
1673         Set_Inner_Instances (Formal, New_Elmt_List);
1674         New_Scope  (Formal);
1675
1676         --  Within the formal, the name of the generic package is a renaming
1677         --  of the formal (as for a regular instantiation).
1678
1679         Renaming := Make_Package_Renaming_Declaration (Loc,
1680             Defining_Unit_Name =>
1681               Make_Defining_Identifier (Loc, Chars (Gen_Unit)),
1682             Name => New_Reference_To (Formal, Loc));
1683
1684         if Present (Visible_Declarations (Specification (N))) then
1685            Prepend (Renaming, To => Visible_Declarations (Specification (N)));
1686         elsif Present (Private_Declarations (Specification (N))) then
1687            Prepend (Renaming, To => Private_Declarations (Specification (N)));
1688         end if;
1689
1690         if Is_Child_Unit (Gen_Unit)
1691           and then Parent_Installed
1692         then
1693            --  Similarly, we have to make the name of the formal visible in
1694            --  the parent instance, to resolve properly fully qualified names
1695            --  that may appear in the generic unit. The parent instance has
1696            --  been placed on the scope stack ahead of the current scope.
1697
1698            Parent_Instance := Scope_Stack.Table (Scope_Stack.Last - 1).Entity;
1699
1700            Renaming_In_Par :=
1701              Make_Defining_Identifier (Loc, Chars (Gen_Unit));
1702            Set_Ekind (Renaming_In_Par, E_Package);
1703            Set_Etype (Renaming_In_Par, Standard_Void_Type);
1704            Set_Scope (Renaming_In_Par, Parent_Instance);
1705            Set_Parent (Renaming_In_Par, Parent (Formal));
1706            Set_Renamed_Object (Renaming_In_Par, Formal);
1707            Append_Entity (Renaming_In_Par, Parent_Instance);
1708         end if;
1709
1710         Analyze_Generic_Formal_Part (N);
1711         Analyze (Specification (N));
1712         End_Package_Scope (Formal);
1713
1714         if Parent_Installed then
1715            Remove_Parent;
1716         end if;
1717
1718         Restore_Env;
1719
1720         --  Inside the generic unit, the formal package is a regular
1721         --  package, but no body is needed for it. Note that after
1722         --  instantiation, the defining_unit_name we need is in the
1723         --  new tree and not in the original. (see Package_Instantiation).
1724         --  A generic formal package is an instance, and can be used as
1725         --  an actual for an inner instance. Mark its generic parent.
1726
1727         Set_Ekind (Formal, E_Package);
1728         Set_Generic_Parent (Specification (N), Gen_Unit);
1729         Set_Has_Completion (Formal, True);
1730      end if;
1731   end Analyze_Formal_Package;
1732
1733   ---------------------------------
1734   -- Analyze_Formal_Private_Type --
1735   ---------------------------------
1736
1737   procedure Analyze_Formal_Private_Type
1738     (N   : Node_Id;
1739      T   : Entity_Id;
1740      Def : Node_Id)
1741   is
1742   begin
1743      New_Private_Type (N, T, Def);
1744
1745      --  Set the size to an arbitrary but legal value.
1746
1747      Set_Size_Info (T, Standard_Integer);
1748      Set_RM_Size   (T, RM_Size (Standard_Integer));
1749   end Analyze_Formal_Private_Type;
1750
1751   ----------------------------------------
1752   -- Analyze_Formal_Signed_Integer_Type --
1753   ----------------------------------------
1754
1755   procedure Analyze_Formal_Signed_Integer_Type
1756     (T   : Entity_Id;
1757      Def : Node_Id)
1758   is
1759      Base : constant Entity_Id :=
1760               New_Internal_Entity
1761                 (E_Signed_Integer_Type, Current_Scope, Sloc (Def), 'G');
1762
1763   begin
1764      Enter_Name (T);
1765
1766      Set_Ekind        (T, E_Signed_Integer_Subtype);
1767      Set_Etype        (T, Base);
1768      Set_Size_Info    (T, Standard_Integer);
1769      Set_RM_Size      (T, RM_Size (Standard_Integer));
1770      Set_Scalar_Range (T, Scalar_Range (Standard_Integer));
1771
1772      Set_Is_Generic_Type (Base);
1773      Set_Size_Info       (Base, Standard_Integer);
1774      Set_RM_Size         (Base, RM_Size (Standard_Integer));
1775      Set_Etype           (Base, Base);
1776      Set_Scalar_Range    (Base, Scalar_Range (Standard_Integer));
1777      Set_Parent          (Base, Parent (Def));
1778   end Analyze_Formal_Signed_Integer_Type;
1779
1780   -------------------------------
1781   -- Analyze_Formal_Subprogram --
1782   -------------------------------
1783
1784   procedure Analyze_Formal_Subprogram (N : Node_Id) is
1785      Spec : constant Node_Id   := Specification (N);
1786      Def  : constant Node_Id   := Default_Name (N);
1787      Nam  : constant Entity_Id := Defining_Unit_Name (Spec);
1788      Subp : Entity_Id;
1789
1790   begin
1791      if Nam = Error then
1792         return;
1793      end if;
1794
1795      if Nkind (Nam) = N_Defining_Program_Unit_Name then
1796         Error_Msg_N ("name of formal subprogram must be a direct name", Nam);
1797         return;
1798      end if;
1799
1800      Analyze_Subprogram_Declaration (N);
1801      Set_Is_Formal_Subprogram (Nam);
1802      Set_Has_Completion (Nam);
1803
1804      --  Default name is resolved at the point of instantiation
1805
1806      if Box_Present (N) then
1807         null;
1808
1809      --  Else default is bound at the point of generic declaration
1810
1811      elsif Present (Def) then
1812         if Nkind (Def) = N_Operator_Symbol then
1813            Find_Direct_Name (Def);
1814
1815         elsif Nkind (Def) /= N_Attribute_Reference then
1816            Analyze (Def);
1817
1818         else
1819            --  For an attribute reference, analyze the prefix and verify
1820            --  that it has the proper profile for the subprogram.
1821
1822            Analyze (Prefix (Def));
1823            Valid_Default_Attribute (Nam, Def);
1824            return;
1825         end if;
1826
1827         --  Default name may be overloaded, in which case the interpretation
1828         --  with the correct profile must be  selected, as for a renaming.
1829
1830         if Etype (Def) = Any_Type then
1831            return;
1832
1833         elsif Nkind (Def) = N_Selected_Component then
1834            Subp := Entity (Selector_Name (Def));
1835
1836            if Ekind (Subp) /= E_Entry then
1837               Error_Msg_N ("expect valid subprogram name as default", Def);
1838               return;
1839            end if;
1840
1841         elsif Nkind (Def) = N_Indexed_Component then
1842
1843            if  Nkind (Prefix (Def)) /= N_Selected_Component then
1844               Error_Msg_N ("expect valid subprogram name as default", Def);
1845               return;
1846
1847            else
1848               Subp := Entity (Selector_Name (Prefix (Def)));
1849
1850               if Ekind (Subp) /= E_Entry_Family then
1851                  Error_Msg_N ("expect valid subprogram name as default", Def);
1852                  return;
1853               end if;
1854            end if;
1855
1856         elsif Nkind (Def) = N_Character_Literal then
1857
1858            --  Needs some type checks: subprogram should be parameterless???
1859
1860            Resolve (Def, (Etype (Nam)));
1861
1862         elsif not Is_Entity_Name (Def)
1863           or else not Is_Overloadable (Entity (Def))
1864         then
1865            Error_Msg_N ("expect valid subprogram name as default", Def);
1866            return;
1867
1868         elsif not Is_Overloaded (Def) then
1869            Subp := Entity (Def);
1870
1871            if Subp = Nam then
1872               Error_Msg_N ("premature usage of formal subprogram", Def);
1873
1874            elsif not Entity_Matches_Spec (Subp, Nam) then
1875               Error_Msg_N ("no visible entity matches specification", Def);
1876            end if;
1877
1878         else
1879            declare
1880               I   : Interp_Index;
1881               I1  : Interp_Index := 0;
1882               It  : Interp;
1883               It1 : Interp;
1884
1885            begin
1886               Subp := Any_Id;
1887               Get_First_Interp (Def, I, It);
1888               while Present (It.Nam) loop
1889
1890                  if Entity_Matches_Spec (It.Nam, Nam) then
1891                     if Subp /= Any_Id then
1892                        It1 := Disambiguate (Def, I1, I, Etype (Subp));
1893
1894                        if It1 = No_Interp then
1895                           Error_Msg_N ("ambiguous default subprogram", Def);
1896                        else
1897                           Subp := It1.Nam;
1898                        end if;
1899
1900                        exit;
1901
1902                     else
1903                        I1  := I;
1904                        Subp := It.Nam;
1905                     end if;
1906                  end if;
1907
1908                  Get_Next_Interp (I, It);
1909               end loop;
1910            end;
1911
1912            if Subp /= Any_Id then
1913               Set_Entity (Def, Subp);
1914
1915               if Subp = Nam then
1916                  Error_Msg_N ("premature usage of formal subprogram", Def);
1917
1918               elsif Ekind (Subp) /= E_Operator then
1919                  Check_Mode_Conformant (Subp, Nam);
1920               end if;
1921
1922            else
1923               Error_Msg_N ("no visible subprogram matches specification", N);
1924            end if;
1925         end if;
1926      end if;
1927   end Analyze_Formal_Subprogram;
1928
1929   -------------------------------------
1930   -- Analyze_Formal_Type_Declaration --
1931   -------------------------------------
1932
1933   procedure Analyze_Formal_Type_Declaration (N : Node_Id) is
1934      Def : constant Node_Id := Formal_Type_Definition (N);
1935      T   : Entity_Id;
1936
1937   begin
1938      T := Defining_Identifier (N);
1939
1940      if Present (Discriminant_Specifications (N))
1941        and then Nkind (Def) /= N_Formal_Private_Type_Definition
1942      then
1943         Error_Msg_N
1944           ("discriminants not allowed for this formal type",
1945            Defining_Identifier (First (Discriminant_Specifications (N))));
1946      end if;
1947
1948      --  Enter the new name, and branch to specific routine.
1949
1950      case Nkind (Def) is
1951         when N_Formal_Private_Type_Definition         =>
1952            Analyze_Formal_Private_Type (N, T, Def);
1953
1954         when N_Formal_Derived_Type_Definition         =>
1955            Analyze_Formal_Derived_Type (N, T, Def);
1956
1957         when N_Formal_Discrete_Type_Definition        =>
1958            Analyze_Formal_Discrete_Type (T, Def);
1959
1960         when N_Formal_Signed_Integer_Type_Definition  =>
1961            Analyze_Formal_Signed_Integer_Type (T, Def);
1962
1963         when N_Formal_Modular_Type_Definition         =>
1964            Analyze_Formal_Modular_Type (T, Def);
1965
1966         when N_Formal_Floating_Point_Definition       =>
1967            Analyze_Formal_Floating_Type (T, Def);
1968
1969         when N_Formal_Ordinary_Fixed_Point_Definition =>
1970            Analyze_Formal_Ordinary_Fixed_Point_Type (T, Def);
1971
1972         when N_Formal_Decimal_Fixed_Point_Definition  =>
1973            Analyze_Formal_Decimal_Fixed_Point_Type (T, Def);
1974
1975         when N_Array_Type_Definition =>
1976            Analyze_Formal_Array_Type (T, Def);
1977
1978         when N_Access_To_Object_Definition            |
1979              N_Access_Function_Definition             |
1980              N_Access_Procedure_Definition            =>
1981            Analyze_Generic_Access_Type (T, Def);
1982
1983         when N_Error                                  =>
1984            null;
1985
1986         when others                                   =>
1987            raise Program_Error;
1988
1989      end case;
1990
1991      Set_Is_Generic_Type (T);
1992   end Analyze_Formal_Type_Declaration;
1993
1994   ------------------------------------
1995   -- Analyze_Function_Instantiation --
1996   ------------------------------------
1997
1998   procedure Analyze_Function_Instantiation (N : Node_Id) is
1999   begin
2000      Analyze_Subprogram_Instantiation (N, E_Function);
2001   end Analyze_Function_Instantiation;
2002
2003   ---------------------------------
2004   -- Analyze_Generic_Access_Type --
2005   ---------------------------------
2006
2007   procedure Analyze_Generic_Access_Type (T : Entity_Id; Def : Node_Id) is
2008   begin
2009      Enter_Name (T);
2010
2011      if Nkind (Def) = N_Access_To_Object_Definition then
2012         Access_Type_Declaration (T, Def);
2013
2014         if Is_Incomplete_Or_Private_Type (Designated_Type (T))
2015           and then No (Full_View (Designated_Type (T)))
2016           and then not Is_Generic_Type (Designated_Type (T))
2017         then
2018            Error_Msg_N ("premature usage of incomplete type", Def);
2019
2020         elsif Is_Internal (Designated_Type (T)) then
2021            Error_Msg_N
2022              ("only a subtype mark is allowed in a formal", Def);
2023         end if;
2024
2025      else
2026         Access_Subprogram_Declaration (T, Def);
2027      end if;
2028   end Analyze_Generic_Access_Type;
2029
2030   ---------------------------------
2031   -- Analyze_Generic_Formal_Part --
2032   ---------------------------------
2033
2034   procedure Analyze_Generic_Formal_Part (N : Node_Id) is
2035      Gen_Parm_Decl : Node_Id;
2036
2037   begin
2038      --  The generic formals are processed in the scope of the generic
2039      --  unit, where they are immediately visible. The scope is installed
2040      --  by the caller.
2041
2042      Gen_Parm_Decl := First (Generic_Formal_Declarations (N));
2043
2044      while Present (Gen_Parm_Decl) loop
2045         Analyze (Gen_Parm_Decl);
2046         Next (Gen_Parm_Decl);
2047      end loop;
2048
2049      Generate_Reference_To_Generic_Formals (Current_Scope);
2050   end Analyze_Generic_Formal_Part;
2051
2052   ------------------------------------------
2053   -- Analyze_Generic_Package_Declaration  --
2054   ------------------------------------------
2055
2056   procedure Analyze_Generic_Package_Declaration (N : Node_Id) is
2057      Loc         : constant Source_Ptr := Sloc (N);
2058      Id          : Entity_Id;
2059      New_N       : Node_Id;
2060      Save_Parent : Node_Id;
2061      Renaming    : Node_Id;
2062      Decls       : constant List_Id :=
2063                      Visible_Declarations (Specification (N));
2064      Decl        : Node_Id;
2065
2066   begin
2067      --  We introduce a renaming of the enclosing package, to have a usable
2068      --  entity as the prefix of an expanded name for a local entity of the
2069      --  form Par.P.Q, where P is the generic package. This is because a local
2070      --  entity named P may hide it, so that the usual visibility rules in
2071      --  the instance will not resolve properly.
2072
2073      Renaming :=
2074        Make_Package_Renaming_Declaration (Loc,
2075          Defining_Unit_Name =>
2076            Make_Defining_Identifier (Loc,
2077             Chars => New_External_Name (Chars (Defining_Entity (N)), "GH")),
2078          Name => Make_Identifier (Loc, Chars (Defining_Entity (N))));
2079
2080      if Present (Decls) then
2081         Decl := First (Decls);
2082         while Present (Decl)
2083           and then Nkind (Decl) = N_Pragma
2084         loop
2085            Next (Decl);
2086         end loop;
2087
2088         if Present (Decl) then
2089            Insert_Before (Decl, Renaming);
2090         else
2091            Append (Renaming, Visible_Declarations (Specification (N)));
2092         end if;
2093
2094      else
2095         Set_Visible_Declarations (Specification (N), New_List (Renaming));
2096      end if;
2097
2098      --  Create copy of generic unit, and save for instantiation.
2099      --  If the unit is a child unit, do not copy the specifications
2100      --  for the parent, which are not part of the generic tree.
2101
2102      Save_Parent := Parent_Spec (N);
2103      Set_Parent_Spec (N, Empty);
2104
2105      New_N := Copy_Generic_Node (N, Empty, Instantiating => False);
2106      Set_Parent_Spec (New_N, Save_Parent);
2107      Rewrite (N, New_N);
2108      Id := Defining_Entity (N);
2109      Generate_Definition (Id);
2110
2111      --  Expansion is not applied to generic units.
2112
2113      Start_Generic;
2114
2115      Enter_Name (Id);
2116      Set_Ekind (Id, E_Generic_Package);
2117      Set_Etype (Id, Standard_Void_Type);
2118      New_Scope (Id);
2119      Enter_Generic_Scope (Id);
2120      Set_Inner_Instances (Id, New_Elmt_List);
2121
2122      Set_Categorization_From_Pragmas (N);
2123      Set_Is_Pure (Id, Is_Pure (Current_Scope));
2124
2125      --  Link the declaration of the generic homonym in the generic copy
2126      --  to the package it renames, so that it is always resolved properly.
2127
2128      Set_Generic_Homonym (Id, Defining_Unit_Name (Renaming));
2129      Set_Entity (Associated_Node (Name (Renaming)), Id);
2130
2131      --  For a library unit, we have reconstructed the entity for the
2132      --  unit, and must reset it in the library tables.
2133
2134      if Nkind (Parent (N)) = N_Compilation_Unit then
2135         Set_Cunit_Entity (Current_Sem_Unit, Id);
2136      end if;
2137
2138      Analyze_Generic_Formal_Part (N);
2139
2140      --  After processing the generic formals, analysis proceeds
2141      --  as for a non-generic package.
2142
2143      Analyze (Specification (N));
2144
2145      Validate_Categorization_Dependency (N, Id);
2146
2147      End_Generic;
2148
2149      End_Package_Scope (Id);
2150      Exit_Generic_Scope (Id);
2151
2152      if Nkind (Parent (N)) /= N_Compilation_Unit then
2153         Move_Freeze_Nodes (Id, N, Visible_Declarations (Specification (N)));
2154         Move_Freeze_Nodes (Id, N, Private_Declarations (Specification (N)));
2155         Move_Freeze_Nodes (Id, N, Generic_Formal_Declarations (N));
2156
2157      else
2158         Set_Body_Required (Parent (N), Unit_Requires_Body (Id));
2159         Validate_RT_RAT_Component (N);
2160
2161         --  If this is a spec without a body, check that generic parameters
2162         --  are referenced.
2163
2164         if not Body_Required (Parent (N)) then
2165            Check_References (Id);
2166         end if;
2167      end if;
2168   end Analyze_Generic_Package_Declaration;
2169
2170   --------------------------------------------
2171   -- Analyze_Generic_Subprogram_Declaration --
2172   --------------------------------------------
2173
2174   procedure Analyze_Generic_Subprogram_Declaration (N : Node_Id) is
2175      Spec        : Node_Id;
2176      Id          : Entity_Id;
2177      Formals     : List_Id;
2178      New_N       : Node_Id;
2179      Save_Parent : Node_Id;
2180
2181   begin
2182      --  Create copy of generic unit,and save for instantiation.
2183      --  If the unit is a child unit, do not copy the specifications
2184      --  for the parent, which are not part of the generic tree.
2185
2186      Save_Parent := Parent_Spec (N);
2187      Set_Parent_Spec (N, Empty);
2188
2189      New_N := Copy_Generic_Node (N, Empty, Instantiating => False);
2190      Set_Parent_Spec (New_N, Save_Parent);
2191      Rewrite (N, New_N);
2192
2193      Spec := Specification (N);
2194      Id := Defining_Entity (Spec);
2195      Generate_Definition (Id);
2196
2197      if Nkind (Id) = N_Defining_Operator_Symbol then
2198         Error_Msg_N
2199           ("operator symbol not allowed for generic subprogram", Id);
2200      end if;
2201
2202      Start_Generic;
2203
2204      Enter_Name (Id);
2205
2206      Set_Scope_Depth_Value (Id, Scope_Depth (Current_Scope) + 1);
2207      New_Scope (Id);
2208      Enter_Generic_Scope (Id);
2209      Set_Inner_Instances (Id, New_Elmt_List);
2210      Set_Is_Pure (Id, Is_Pure (Current_Scope));
2211
2212      Analyze_Generic_Formal_Part (N);
2213
2214      Formals := Parameter_Specifications (Spec);
2215
2216      if Present (Formals) then
2217         Process_Formals (Formals, Spec);
2218      end if;
2219
2220      if Nkind (Spec) = N_Function_Specification then
2221         Set_Ekind (Id, E_Generic_Function);
2222         Find_Type (Subtype_Mark (Spec));
2223         Set_Etype (Id, Entity (Subtype_Mark (Spec)));
2224      else
2225         Set_Ekind (Id, E_Generic_Procedure);
2226         Set_Etype (Id, Standard_Void_Type);
2227      end if;
2228
2229      --  For a library unit, we have reconstructed the entity for the
2230      --  unit, and must reset it in the library tables. We also need
2231      --  to make sure that Body_Required is set properly in the original
2232      --  compilation unit node.
2233
2234      if Nkind (Parent (N)) = N_Compilation_Unit then
2235         Set_Cunit_Entity (Current_Sem_Unit, Id);
2236         Set_Body_Required (Parent (N), Unit_Requires_Body (Id));
2237      end if;
2238
2239      Set_Categorization_From_Pragmas (N);
2240      Validate_Categorization_Dependency (N, Id);
2241
2242      Save_Global_References (Original_Node (N));
2243
2244      End_Generic;
2245      End_Scope;
2246      Exit_Generic_Scope (Id);
2247      Generate_Reference_To_Formals (Id);
2248   end Analyze_Generic_Subprogram_Declaration;
2249
2250   -----------------------------------
2251   -- Analyze_Package_Instantiation --
2252   -----------------------------------
2253
2254   --  Note: this procedure is also used for formal package declarations,
2255   --  in which case the argument N is an N_Formal_Package_Declaration
2256   --  node. This should really be noted in the spec! ???
2257
2258   procedure Analyze_Package_Instantiation (N : Node_Id) is
2259      Loc    : constant Source_Ptr := Sloc (N);
2260      Gen_Id : constant Node_Id    := Name (N);
2261
2262      Act_Decl      : Node_Id;
2263      Act_Decl_Name : Node_Id;
2264      Act_Decl_Id   : Entity_Id;
2265      Act_Spec      : Node_Id;
2266      Act_Tree      : Node_Id;
2267
2268      Gen_Decl : Node_Id;
2269      Gen_Unit : Entity_Id;
2270
2271      Is_Actual_Pack : constant Boolean :=
2272                         Is_Internal (Defining_Entity (N));
2273
2274      Parent_Installed : Boolean := False;
2275      Renaming_List    : List_Id;
2276      Unit_Renaming    : Node_Id;
2277      Needs_Body       : Boolean;
2278      Inline_Now       : Boolean := False;
2279
2280      procedure Delay_Descriptors (E : Entity_Id);
2281      --  Delay generation of subprogram descriptors for given entity
2282
2283      function Might_Inline_Subp return Boolean;
2284      --  If inlining is active and the generic contains inlined subprograms,
2285      --  we instantiate the body. This may cause superfluous instantiations,
2286      --  but it is simpler than detecting the need for the body at the point
2287      --  of inlining, when the context of the instance is not available.
2288
2289      -----------------------
2290      -- Delay_Descriptors --
2291      -----------------------
2292
2293      procedure Delay_Descriptors (E : Entity_Id) is
2294      begin
2295         if not Delay_Subprogram_Descriptors (E) then
2296            Set_Delay_Subprogram_Descriptors (E);
2297            Pending_Descriptor.Increment_Last;
2298            Pending_Descriptor.Table (Pending_Descriptor.Last) := E;
2299         end if;
2300      end Delay_Descriptors;
2301
2302      -----------------------
2303      -- Might_Inline_Subp --
2304      -----------------------
2305
2306      function Might_Inline_Subp return Boolean is
2307         E : Entity_Id;
2308
2309      begin
2310         if not Inline_Processing_Required then
2311            return False;
2312
2313         else
2314            E := First_Entity (Gen_Unit);
2315
2316            while Present (E) loop
2317
2318               if Is_Subprogram (E)
2319                 and then Is_Inlined (E)
2320               then
2321                  return True;
2322               end if;
2323
2324               Next_Entity (E);
2325            end loop;
2326         end if;
2327
2328         return False;
2329      end Might_Inline_Subp;
2330
2331   --  Start of processing for Analyze_Package_Instantiation
2332
2333   begin
2334      --  Very first thing: apply the special kludge for Text_IO processing
2335      --  in case we are instantiating one of the children of [Wide_]Text_IO.
2336
2337      Text_IO_Kludge (Name (N));
2338
2339      --  Make node global for error reporting.
2340
2341      Instantiation_Node := N;
2342
2343      --  Case of instantiation of a generic package
2344
2345      if Nkind (N) = N_Package_Instantiation then
2346         Act_Decl_Id := New_Copy (Defining_Entity (N));
2347         Set_Comes_From_Source (Act_Decl_Id, True);
2348
2349         if Nkind (Defining_Unit_Name (N)) = N_Defining_Program_Unit_Name then
2350            Act_Decl_Name :=
2351              Make_Defining_Program_Unit_Name (Loc,
2352                Name => New_Copy_Tree (Name (Defining_Unit_Name (N))),
2353                Defining_Identifier => Act_Decl_Id);
2354         else
2355            Act_Decl_Name :=  Act_Decl_Id;
2356         end if;
2357
2358      --  Case of instantiation of a formal package
2359
2360      else
2361         Act_Decl_Id   := Defining_Identifier (N);
2362         Act_Decl_Name := Act_Decl_Id;
2363      end if;
2364
2365      Generate_Definition (Act_Decl_Id);
2366      Pre_Analyze_Actuals (N);
2367
2368      Init_Env;
2369      Check_Generic_Child_Unit (Gen_Id, Parent_Installed);
2370      Gen_Unit := Entity (Gen_Id);
2371
2372      --  Verify that it is the name of a generic package
2373
2374      if Etype (Gen_Unit) = Any_Type then
2375         Restore_Env;
2376         return;
2377
2378      elsif Ekind (Gen_Unit) /= E_Generic_Package then
2379
2380         --  Ada0Y (AI-50217): Instance can not be used in limited with_clause
2381
2382         if From_With_Type (Gen_Unit) then
2383            Error_Msg_N
2384              ("cannot instantiate a limited withed package", Gen_Id);
2385         else
2386            Error_Msg_N
2387              ("expect name of generic package in instantiation", Gen_Id);
2388         end if;
2389
2390         Restore_Env;
2391         return;
2392      end if;
2393
2394      if In_Extended_Main_Source_Unit (N) then
2395         Set_Is_Instantiated (Gen_Unit);
2396         Generate_Reference  (Gen_Unit, N);
2397
2398         if Present (Renamed_Object (Gen_Unit)) then
2399            Set_Is_Instantiated (Renamed_Object (Gen_Unit));
2400            Generate_Reference  (Renamed_Object (Gen_Unit), N);
2401         end if;
2402      end if;
2403
2404      if Nkind (Gen_Id) = N_Identifier
2405        and then Chars (Gen_Unit) = Chars (Defining_Entity (N))
2406      then
2407         Error_Msg_NE
2408           ("& is hidden within declaration of instance", Gen_Id, Gen_Unit);
2409
2410      elsif Nkind (Gen_Id) = N_Expanded_Name
2411        and then Is_Child_Unit (Gen_Unit)
2412        and then Nkind (Prefix (Gen_Id)) = N_Identifier
2413        and then Chars (Act_Decl_Id) = Chars (Prefix (Gen_Id))
2414      then
2415         Error_Msg_N
2416           ("& is hidden within declaration of instance ", Prefix (Gen_Id));
2417      end if;
2418
2419      Set_Entity (Gen_Id, Gen_Unit);
2420
2421      --  If generic is a renaming, get original generic unit.
2422
2423      if Present (Renamed_Object (Gen_Unit))
2424        and then Ekind (Renamed_Object (Gen_Unit)) = E_Generic_Package
2425      then
2426         Gen_Unit := Renamed_Object (Gen_Unit);
2427      end if;
2428
2429      --  Verify that there are no circular instantiations.
2430
2431      if In_Open_Scopes (Gen_Unit) then
2432         Error_Msg_NE ("instantiation of & within itself", N, Gen_Unit);
2433         Restore_Env;
2434         return;
2435
2436      elsif Contains_Instance_Of (Gen_Unit, Current_Scope, Gen_Id) then
2437         Error_Msg_Node_2 := Current_Scope;
2438         Error_Msg_NE
2439           ("circular Instantiation: & instantiated in &!", N, Gen_Unit);
2440         Circularity_Detected := True;
2441         Restore_Env;
2442         return;
2443
2444      else
2445         Set_Instance_Env (Gen_Unit, Act_Decl_Id);
2446         Gen_Decl := Unit_Declaration_Node (Gen_Unit);
2447
2448         --  Initialize renamings map, for error checking, and the list
2449         --  that holds private entities whose views have changed between
2450         --  generic definition and instantiation. If this is the instance
2451         --  created to validate an actual package, the instantiation
2452         --  environment is that of the enclosing instance.
2453
2454         Generic_Renamings.Set_Last (0);
2455         Generic_Renamings_HTable.Reset;
2456
2457         Create_Instantiation_Source (N, Gen_Unit, False, S_Adjustment);
2458
2459         --  Copy original generic tree, to produce text for instantiation.
2460
2461         Act_Tree :=
2462           Copy_Generic_Node
2463             (Original_Node (Gen_Decl), Empty, Instantiating => True);
2464
2465         Act_Spec := Specification (Act_Tree);
2466
2467         --  If this is the instance created to validate an actual package,
2468         --  only the formals matter, do not examine the package spec itself.
2469
2470         if Is_Actual_Pack then
2471            Set_Visible_Declarations (Act_Spec, New_List);
2472            Set_Private_Declarations (Act_Spec, New_List);
2473         end if;
2474
2475         Renaming_List :=
2476           Analyze_Associations
2477             (N,
2478              Generic_Formal_Declarations (Act_Tree),
2479              Generic_Formal_Declarations (Gen_Decl));
2480
2481         Set_Defining_Unit_Name (Act_Spec, Act_Decl_Name);
2482         Set_Is_Generic_Instance (Act_Decl_Id);
2483
2484         Set_Generic_Parent (Act_Spec, Gen_Unit);
2485
2486         --  References to the generic in its own declaration or its body
2487         --  are references to the instance. Add a renaming declaration for
2488         --  the generic unit itself. This declaration, as well as the renaming
2489         --  declarations for the generic formals, must remain private to the
2490         --  unit: the formals, because this is the language semantics, and
2491         --  the unit because its use is an artifact of the implementation.
2492
2493         Unit_Renaming :=
2494           Make_Package_Renaming_Declaration (Loc,
2495             Defining_Unit_Name =>
2496               Make_Defining_Identifier (Loc, Chars (Gen_Unit)),
2497             Name => New_Reference_To (Act_Decl_Id, Loc));
2498
2499         Append (Unit_Renaming, Renaming_List);
2500
2501         --  The renaming declarations are the first local declarations of
2502         --  the new unit.
2503
2504         if Is_Non_Empty_List (Visible_Declarations (Act_Spec)) then
2505            Insert_List_Before
2506              (First (Visible_Declarations (Act_Spec)), Renaming_List);
2507         else
2508            Set_Visible_Declarations (Act_Spec, Renaming_List);
2509         end if;
2510
2511         Act_Decl :=
2512           Make_Package_Declaration (Loc,
2513             Specification => Act_Spec);
2514
2515         --  Save the instantiation node, for subsequent instantiation
2516         --  of the body, if there is one and we are generating code for
2517         --  the current unit. Mark the unit as having a body, to avoid
2518         --  a premature error message.
2519
2520         --  We instantiate the body if we are generating code, if we are
2521         --  generating cross-reference information, or if we are building
2522         --  trees for ASIS use.
2523
2524         declare
2525            Enclosing_Body_Present : Boolean := False;
2526            --  If the generic unit is not a compilation unit, then a body
2527            --  may be present in its parent even if none is required. We
2528            --  create a tentative pending instantiation for the body, which
2529            --  will be discarded if none is actually present.
2530
2531            Scop : Entity_Id;
2532
2533         begin
2534            if Scope (Gen_Unit) /= Standard_Standard
2535              and then not Is_Child_Unit (Gen_Unit)
2536            then
2537               Scop := Scope (Gen_Unit);
2538
2539               while Present (Scop)
2540                 and then Scop /= Standard_Standard
2541               loop
2542                  if Unit_Requires_Body (Scop) then
2543                     Enclosing_Body_Present := True;
2544                     exit;
2545                  end if;
2546
2547                  exit when Is_Compilation_Unit (Scop);
2548                  Scop := Scope (Scop);
2549               end loop;
2550            end if;
2551
2552            --  If front-end inlining is enabled, and this is a unit for which
2553            --  code will be generated, we instantiate the body at once.
2554            --  This is done if the instance is not the main unit, and if the
2555            --  generic is not a child unit of another generic, to avoid scope
2556            --  problems and the reinstallation of parent instances.
2557
2558            if Front_End_Inlining
2559              and then Expander_Active
2560              and then (not Is_Child_Unit (Gen_Unit)
2561                         or else not Is_Generic_Unit (Scope (Gen_Unit)))
2562              and then Is_In_Main_Unit (N)
2563              and then Nkind (Parent (N)) /= N_Compilation_Unit
2564              and then Might_Inline_Subp
2565              and then not Is_Actual_Pack
2566            then
2567               Inline_Now := True;
2568            end if;
2569
2570            Needs_Body :=
2571              (Unit_Requires_Body (Gen_Unit)
2572                  or else Enclosing_Body_Present
2573                  or else Present (Corresponding_Body (Gen_Decl)))
2574                and then (Is_In_Main_Unit (N)
2575                           or else Might_Inline_Subp)
2576                and then not Is_Actual_Pack
2577                and then not Inline_Now
2578
2579                and then (Operating_Mode = Generate_Code
2580                            or else (Operating_Mode = Check_Semantics
2581                                      and then ASIS_Mode));
2582
2583            --  If front_end_inlining is enabled, do not instantiate a
2584            --  body if within a generic context.
2585
2586            if Front_End_Inlining
2587              and then not Expander_Active
2588            then
2589               Needs_Body := False;
2590            end if;
2591
2592            --  If the current context is generic, and the package being
2593            --  instantiated is declared within a formal package, there
2594            --  is no body to instantiate until the enclosing generic is
2595            --  instantiated, and there is an actual for the formal
2596            --  package. If the formal package has parameters, we build a
2597            --  regular package instance for it, that preceeds the original
2598            --  formal package declaration.
2599
2600            if In_Open_Scopes (Scope (Scope (Gen_Unit))) then
2601               declare
2602                  Decl : constant Node_Id :=
2603                           Original_Node
2604                             (Unit_Declaration_Node (Scope (Gen_Unit)));
2605               begin
2606                  if Nkind (Decl) = N_Formal_Package_Declaration
2607                    or else (Nkind (Decl) = N_Package_Declaration
2608                      and then Is_List_Member (Decl)
2609                      and then Present (Next (Decl))
2610                      and then
2611                        Nkind (Next (Decl)) = N_Formal_Package_Declaration)
2612                  then
2613                     Needs_Body := False;
2614                  end if;
2615               end;
2616            end if;
2617         end;
2618
2619         --  If we are generating the calling stubs from the instantiation
2620         --  of a generic RCI package, we will not use the body of the
2621         --  generic package.
2622
2623         if Distribution_Stub_Mode = Generate_Caller_Stub_Body
2624           and then Is_Compilation_Unit (Defining_Entity (N))
2625         then
2626            Needs_Body := False;
2627         end if;
2628
2629         if Needs_Body then
2630
2631            --  Here is a defence against a ludicrous number of instantiations
2632            --  caused by a circular set of instantiation attempts.
2633
2634            if Pending_Instantiations.Last >
2635                 Hostparm.Max_Instantiations
2636            then
2637               Error_Msg_N ("too many instantiations", N);
2638               raise Unrecoverable_Error;
2639            end if;
2640
2641            --  Indicate that the enclosing scopes contain an instantiation,
2642            --  and that cleanup actions should be delayed until after the
2643            --  instance body is expanded.
2644
2645            Check_Forward_Instantiation (Gen_Decl);
2646            if Nkind (N) = N_Package_Instantiation then
2647               declare
2648                  Enclosing_Master : Entity_Id := Current_Scope;
2649
2650               begin
2651                  while Enclosing_Master /= Standard_Standard loop
2652
2653                     if Ekind (Enclosing_Master) = E_Package then
2654                        if Is_Compilation_Unit (Enclosing_Master) then
2655                           if In_Package_Body (Enclosing_Master) then
2656                              Delay_Descriptors
2657                                (Body_Entity (Enclosing_Master));
2658                           else
2659                              Delay_Descriptors
2660                                (Enclosing_Master);
2661                           end if;
2662
2663                           exit;
2664
2665                        else
2666                           Enclosing_Master := Scope (Enclosing_Master);
2667                        end if;
2668
2669                     elsif Ekind (Enclosing_Master) = E_Generic_Package then
2670                        Enclosing_Master := Scope (Enclosing_Master);
2671
2672                     elsif Is_Generic_Subprogram (Enclosing_Master)
2673                       or else Ekind (Enclosing_Master) = E_Void
2674                     then
2675                        --  Cleanup actions will eventually be performed on
2676                        --  the enclosing instance, if any. enclosing scope
2677                        --  is void in the formal part of a generic subp.
2678
2679                        exit;
2680
2681                     else
2682                        if Ekind (Enclosing_Master) = E_Entry
2683                          and then
2684                            Ekind (Scope (Enclosing_Master)) = E_Protected_Type
2685                        then
2686                           Enclosing_Master :=
2687                             Protected_Body_Subprogram (Enclosing_Master);
2688                        end if;
2689
2690                        Set_Delay_Cleanups (Enclosing_Master);
2691
2692                        while Ekind (Enclosing_Master) = E_Block loop
2693                           Enclosing_Master := Scope (Enclosing_Master);
2694                        end loop;
2695
2696                        if Is_Subprogram (Enclosing_Master) then
2697                           Delay_Descriptors (Enclosing_Master);
2698
2699                        elsif Is_Task_Type (Enclosing_Master) then
2700                           declare
2701                              TBP : constant Node_Id :=
2702                                      Get_Task_Body_Procedure
2703                                        (Enclosing_Master);
2704
2705                           begin
2706                              if Present (TBP) then
2707                                 Delay_Descriptors  (TBP);
2708                                 Set_Delay_Cleanups (TBP);
2709                              end if;
2710                           end;
2711                        end if;
2712
2713                        exit;
2714                     end if;
2715                  end loop;
2716               end;
2717
2718               --  Make entry in table
2719
2720               Pending_Instantiations.Increment_Last;
2721               Pending_Instantiations.Table (Pending_Instantiations.Last) :=
2722                 (N, Act_Decl, Expander_Active, Current_Sem_Unit);
2723            end if;
2724         end if;
2725
2726         Set_Categorization_From_Pragmas (Act_Decl);
2727
2728         if Parent_Installed then
2729            Hide_Current_Scope;
2730         end if;
2731
2732         Set_Instance_Spec (N, Act_Decl);
2733
2734         --  If not a compilation unit, insert the package declaration
2735         --  before the original instantiation node.
2736
2737         if Nkind (Parent (N)) /= N_Compilation_Unit then
2738            Mark_Rewrite_Insertion (Act_Decl);
2739            Insert_Before (N, Act_Decl);
2740            Analyze (Act_Decl);
2741
2742         --  For an instantiation that is a compilation unit, place
2743         --  declaration on current node so context is complete
2744         --  for analysis (including nested instantiations). It this
2745         --  is the main unit, the declaration eventually replaces the
2746         --  instantiation node. If the instance body is later created, it
2747         --  replaces the instance node, and the declation is attached to
2748         --  it (see Build_Instance_Compilation_Unit_Nodes).
2749
2750         else
2751            if Cunit_Entity (Current_Sem_Unit) = Defining_Entity (N) then
2752
2753               --  The entity for the current unit is the newly created one,
2754               --  and all semantic information is attached to it.
2755
2756               Set_Cunit_Entity (Current_Sem_Unit, Act_Decl_Id);
2757
2758               --  If this is the main unit, replace the main entity as well.
2759
2760               if Current_Sem_Unit = Main_Unit then
2761                  Main_Unit_Entity := Act_Decl_Id;
2762               end if;
2763            end if;
2764
2765            Set_Unit (Parent (N), Act_Decl);
2766            Set_Parent_Spec (Act_Decl, Parent_Spec (N));
2767            Analyze (Act_Decl);
2768            Set_Unit (Parent (N), N);
2769            Set_Body_Required (Parent (N), False);
2770
2771            --  We never need elaboration checks on instantiations, since
2772            --  by definition, the body instantiation is elaborated at the
2773            --  same time as the spec instantiation.
2774
2775            Set_Suppress_Elaboration_Warnings (Act_Decl_Id);
2776            Set_Kill_Elaboration_Checks       (Act_Decl_Id);
2777         end if;
2778
2779         Check_Elab_Instantiation (N);
2780
2781         if ABE_Is_Certain (N) and then Needs_Body then
2782            Pending_Instantiations.Decrement_Last;
2783         end if;
2784         Check_Hidden_Child_Unit (N, Gen_Unit, Act_Decl_Id);
2785
2786         Set_First_Private_Entity (Defining_Unit_Name (Unit_Renaming),
2787           First_Private_Entity (Act_Decl_Id));
2788
2789         --  If the instantiation will receive a body, the unit will
2790         --  be transformed into a package body, and receive its own
2791         --  elaboration entity. Otherwise, the nature of the unit is
2792         --  now a package declaration.
2793
2794         if Nkind (Parent (N)) = N_Compilation_Unit
2795           and then not Needs_Body
2796         then
2797            Rewrite (N, Act_Decl);
2798         end if;
2799
2800         if Present (Corresponding_Body (Gen_Decl))
2801           or else Unit_Requires_Body (Gen_Unit)
2802         then
2803            Set_Has_Completion (Act_Decl_Id);
2804         end if;
2805
2806         Check_Formal_Packages (Act_Decl_Id);
2807
2808         Restore_Private_Views (Act_Decl_Id);
2809
2810         if not Generic_Separately_Compiled (Gen_Unit) then
2811            Inherit_Context (Gen_Decl, N);
2812         end if;
2813
2814         if Parent_Installed then
2815            Remove_Parent;
2816         end if;
2817
2818         Restore_Env;
2819      end if;
2820
2821      Validate_Categorization_Dependency (N, Act_Decl_Id);
2822
2823      --  Check restriction, but skip this if something went wrong in
2824      --  the above analysis, indicated by Act_Decl_Id being void.
2825
2826      if Ekind (Act_Decl_Id) /= E_Void
2827        and then not Is_Library_Level_Entity (Act_Decl_Id)
2828      then
2829         Check_Restriction (No_Local_Allocators, N);
2830      end if;
2831
2832      if Inline_Now then
2833         Inline_Instance_Body (N, Gen_Unit, Act_Decl);
2834      end if;
2835
2836   exception
2837      when Instantiation_Error =>
2838         if Parent_Installed then
2839            Remove_Parent;
2840         end if;
2841   end Analyze_Package_Instantiation;
2842
2843   ---------------------------
2844   --  Inline_Instance_Body --
2845   ---------------------------
2846
2847   procedure Inline_Instance_Body
2848     (N        : Node_Id;
2849      Gen_Unit : Entity_Id;
2850      Act_Decl : Node_Id)
2851   is
2852      Vis          : Boolean;
2853      Gen_Comp     : constant Entity_Id :=
2854                      Cunit_Entity (Get_Source_Unit (Gen_Unit));
2855      Curr_Comp    : constant Node_Id := Cunit (Current_Sem_Unit);
2856      Curr_Scope   : Entity_Id := Empty;
2857      Curr_Unit    : constant Entity_Id :=
2858                       Cunit_Entity (Current_Sem_Unit);
2859      Removed      : Boolean := False;
2860      Num_Scopes   : Int := 0;
2861      Use_Clauses  : array (1 .. Scope_Stack.Last) of Node_Id;
2862      Instances    : array (1 .. Scope_Stack.Last) of Entity_Id;
2863      Inner_Scopes : array (1 .. Scope_Stack.Last) of Entity_Id;
2864      Num_Inner    : Int := 0;
2865      N_Instances  : Int := 0;
2866      S            : Entity_Id;
2867
2868   begin
2869      --  Case of generic unit defined in another unit. We must remove
2870      --  the complete context of the current unit to install that of
2871      --  the generic.
2872
2873      if Gen_Comp /= Cunit_Entity (Current_Sem_Unit) then
2874         S := Current_Scope;
2875
2876         while Present (S)
2877           and then S /= Standard_Standard
2878         loop
2879            Num_Scopes := Num_Scopes + 1;
2880
2881            Use_Clauses (Num_Scopes) :=
2882              (Scope_Stack.Table
2883                 (Scope_Stack.Last - Num_Scopes + 1).
2884                    First_Use_Clause);
2885            End_Use_Clauses (Use_Clauses (Num_Scopes));
2886
2887            exit when Is_Generic_Instance (S)
2888              and then (In_Package_Body (S)
2889                          or else Ekind (S) = E_Procedure
2890                          or else Ekind (S) = E_Function);
2891            S := Scope (S);
2892         end loop;
2893
2894         Vis := Is_Immediately_Visible (Gen_Comp);
2895
2896         --  Find and save all enclosing instances
2897
2898         S := Current_Scope;
2899
2900         while Present (S)
2901           and then S /= Standard_Standard
2902         loop
2903            if Is_Generic_Instance (S) then
2904               N_Instances := N_Instances + 1;
2905               Instances (N_Instances) := S;
2906
2907               exit when In_Package_Body (S);
2908            end if;
2909
2910            S := Scope (S);
2911         end loop;
2912
2913         --  Remove context of current compilation unit, unless we
2914         --  are within a nested package instantiation, in which case
2915         --  the context has been removed previously.
2916
2917         --  If current scope is the body of a child unit, remove context
2918         --  of spec as well.
2919
2920         S := Current_Scope;
2921
2922         while Present (S)
2923           and then S /= Standard_Standard
2924         loop
2925            exit when Is_Generic_Instance (S)
2926                 and then (In_Package_Body (S)
2927                            or else Ekind (S) = E_Procedure
2928                            or else Ekind (S) = E_Function);
2929
2930            if S = Curr_Unit
2931              or else (Ekind (Curr_Unit) = E_Package_Body
2932                        and then S = Spec_Entity (Curr_Unit))
2933              or else (Ekind (Curr_Unit) = E_Subprogram_Body
2934                        and then S =
2935                          Corresponding_Spec
2936                            (Unit_Declaration_Node (Curr_Unit)))
2937            then
2938               Removed := True;
2939
2940               --  Remove entities in current scopes from visibility, so
2941               --  than instance body is compiled in a clean environment.
2942
2943               Save_Scope_Stack (Handle_Use => False);
2944
2945               if Is_Child_Unit (S) then
2946
2947                  --  Remove child unit from stack, as well as inner scopes.
2948                  --  Removing the context of a child unit removes parent
2949                  --  units as well.
2950
2951                  while Current_Scope /= S loop
2952                     Num_Inner := Num_Inner + 1;
2953                     Inner_Scopes (Num_Inner) := Current_Scope;
2954                     Pop_Scope;
2955                  end loop;
2956
2957                  Pop_Scope;
2958                  Remove_Context (Curr_Comp);
2959                  Curr_Scope := S;
2960
2961               else
2962                  Remove_Context (Curr_Comp);
2963               end if;
2964
2965               if Ekind (Curr_Unit) = E_Package_Body then
2966                  Remove_Context (Library_Unit (Curr_Comp));
2967               end if;
2968            end if;
2969
2970            S := Scope (S);
2971         end loop;
2972
2973         New_Scope (Standard_Standard);
2974         Scope_Stack.Table (Scope_Stack.Last).Is_Active_Stack_Base := True;
2975         Instantiate_Package_Body
2976           ((N, Act_Decl, Expander_Active, Current_Sem_Unit), True);
2977         Pop_Scope;
2978
2979         --  Restore context
2980
2981         Set_Is_Immediately_Visible (Gen_Comp, Vis);
2982
2983         --  Reset Generic_Instance flag so that use clauses can be installed
2984         --  in the proper order. (See Use_One_Package for effect of enclosing
2985         --  instances on processing of use clauses).
2986
2987         for J in 1 .. N_Instances loop
2988            Set_Is_Generic_Instance (Instances (J), False);
2989         end loop;
2990
2991         if Removed then
2992            Install_Context (Curr_Comp);
2993
2994            if Present (Curr_Scope)
2995              and then Is_Child_Unit (Curr_Scope)
2996            then
2997               New_Scope (Curr_Scope);
2998               Set_Is_Immediately_Visible (Curr_Scope);
2999
3000               --  Finally, restore inner scopes as well.
3001
3002               for J in reverse 1 .. Num_Inner loop
3003                  New_Scope (Inner_Scopes (J));
3004               end loop;
3005            end if;
3006
3007            Restore_Scope_Stack (Handle_Use => False);
3008         end if;
3009
3010         --  Restore use clauses. For a child unit, use clauses in the
3011         --  parents are restored when installing the context, so only
3012         --  those in inner scopes (and those local to the child unit itself)
3013         --  need to be installed explicitly.
3014
3015         if Is_Child_Unit (Curr_Unit)
3016           and then Removed
3017         then
3018            for J in reverse 1 .. Num_Inner + 1 loop
3019               Scope_Stack.Table (Scope_Stack.Last - J + 1).First_Use_Clause :=
3020                 Use_Clauses (J);
3021               Install_Use_Clauses (Use_Clauses (J));
3022            end  loop;
3023
3024         else
3025            for J in reverse 1 .. Num_Scopes loop
3026               Scope_Stack.Table (Scope_Stack.Last - J + 1).First_Use_Clause :=
3027                 Use_Clauses (J);
3028               Install_Use_Clauses (Use_Clauses (J));
3029            end  loop;
3030         end if;
3031
3032         for J in 1 .. N_Instances loop
3033            Set_Is_Generic_Instance (Instances (J), True);
3034         end loop;
3035
3036      --  If generic unit is in current unit, current context is correct.
3037
3038      else
3039         Instantiate_Package_Body
3040           ((N, Act_Decl, Expander_Active, Current_Sem_Unit), True);
3041      end if;
3042   end Inline_Instance_Body;
3043
3044   -------------------------------------
3045   -- Analyze_Procedure_Instantiation --
3046   -------------------------------------
3047
3048   procedure Analyze_Procedure_Instantiation (N : Node_Id) is
3049   begin
3050      Analyze_Subprogram_Instantiation (N, E_Procedure);
3051   end Analyze_Procedure_Instantiation;
3052
3053   --------------------------------------
3054   -- Analyze_Subprogram_Instantiation --
3055   --------------------------------------
3056
3057   procedure Analyze_Subprogram_Instantiation
3058     (N : Node_Id;
3059      K : Entity_Kind)
3060   is
3061      Loc    : constant Source_Ptr := Sloc (N);
3062      Gen_Id : constant Node_Id    := Name (N);
3063
3064      Anon_Id : constant Entity_Id :=
3065                  Make_Defining_Identifier (Sloc (Defining_Entity (N)),
3066                    Chars => New_External_Name
3067                               (Chars (Defining_Entity (N)), 'R'));
3068
3069      Act_Decl_Id : Entity_Id;
3070      Act_Decl    : Node_Id;
3071      Act_Spec    : Node_Id;
3072      Act_Tree    : Node_Id;
3073
3074      Gen_Unit         : Entity_Id;
3075      Gen_Decl         : Node_Id;
3076      Pack_Id          : Entity_Id;
3077      Parent_Installed : Boolean := False;
3078      Renaming_List    : List_Id;
3079
3080      procedure Analyze_Instance_And_Renamings;
3081      --  The instance must be analyzed in a context that includes the
3082      --  mappings of generic parameters into actuals. We create a package
3083      --  declaration for this purpose, and a subprogram with an internal
3084      --  name within the package. The subprogram instance is simply an
3085      --  alias for the internal subprogram, declared in the current scope.
3086
3087      ------------------------------------
3088      -- Analyze_Instance_And_Renamings --
3089      ------------------------------------
3090
3091      procedure Analyze_Instance_And_Renamings is
3092         Def_Ent   : constant Entity_Id := Defining_Entity (N);
3093         Pack_Decl : Node_Id;
3094
3095      begin
3096         if Nkind (Parent (N)) = N_Compilation_Unit then
3097
3098            --  For the case of a compilation unit, the container package
3099            --  has the same name as the instantiation, to insure that the
3100            --  binder calls the elaboration procedure with the right name.
3101            --  Copy the entity of the instance, which may have compilation
3102            --  level flags (e.g. Is_Child_Unit) set.
3103
3104            Pack_Id := New_Copy (Def_Ent);
3105
3106         else
3107            --  Otherwise we use the name of the instantiation concatenated
3108            --  with its source position to ensure uniqueness if there are
3109            --  several instantiations with the same name.
3110
3111            Pack_Id :=
3112              Make_Defining_Identifier (Loc,
3113                Chars => New_External_Name
3114                           (Related_Id   => Chars (Def_Ent),
3115                            Suffix       => "GP",
3116                            Suffix_Index => Source_Offset (Sloc (Def_Ent))));
3117         end if;
3118
3119         Pack_Decl := Make_Package_Declaration (Loc,
3120           Specification => Make_Package_Specification (Loc,
3121             Defining_Unit_Name   => Pack_Id,
3122             Visible_Declarations => Renaming_List,
3123             End_Label            => Empty));
3124
3125         Set_Instance_Spec (N, Pack_Decl);
3126         Set_Is_Generic_Instance (Pack_Id);
3127         Set_Needs_Debug_Info (Pack_Id);
3128
3129         --  Case of not a compilation unit
3130
3131         if Nkind (Parent (N)) /= N_Compilation_Unit then
3132            Mark_Rewrite_Insertion (Pack_Decl);
3133            Insert_Before (N, Pack_Decl);
3134            Set_Has_Completion (Pack_Id);
3135
3136         --  Case of an instantiation that is a compilation unit
3137
3138         --  Place declaration on current node so context is complete
3139         --  for analysis (including nested instantiations), and for
3140         --  use in a context_clause (see Analyze_With_Clause).
3141
3142         else
3143            Set_Unit (Parent (N), Pack_Decl);
3144            Set_Parent_Spec (Pack_Decl, Parent_Spec (N));
3145         end if;
3146
3147         Analyze (Pack_Decl);
3148         Check_Formal_Packages (Pack_Id);
3149         Set_Is_Generic_Instance (Pack_Id, False);
3150
3151         --  Body of the enclosing package is supplied when instantiating
3152         --  the subprogram body, after semantic  analysis is completed.
3153
3154         if Nkind (Parent (N)) = N_Compilation_Unit then
3155
3156            --  Remove package itself from visibility, so it does not
3157            --  conflict with subprogram.
3158
3159            Set_Name_Entity_Id (Chars (Pack_Id), Homonym (Pack_Id));
3160
3161            --  Set name and scope of internal subprogram so that the
3162            --  proper external name will be generated. The proper scope
3163            --  is the scope of the wrapper package. We need to generate
3164            --  debugging information for the internal subprogram, so set
3165            --  flag accordingly.
3166
3167            Set_Chars (Anon_Id, Chars (Defining_Entity (N)));
3168            Set_Scope (Anon_Id, Scope (Pack_Id));
3169
3170            --  Mark wrapper package as referenced, to avoid spurious
3171            --  warnings if the instantiation appears in various with_
3172            --  clauses of subunits of the main unit.
3173
3174            Set_Referenced (Pack_Id);
3175         end if;
3176
3177         Set_Is_Generic_Instance (Anon_Id);
3178         Set_Needs_Debug_Info    (Anon_Id);
3179         Act_Decl_Id := New_Copy (Anon_Id);
3180
3181         Set_Parent            (Act_Decl_Id, Parent (Anon_Id));
3182         Set_Chars             (Act_Decl_Id, Chars (Defining_Entity (N)));
3183         Set_Sloc              (Act_Decl_Id, Sloc (Defining_Entity (N)));
3184         Set_Comes_From_Source (Act_Decl_Id, True);
3185
3186         --  The signature may involve types that are not frozen yet, but
3187         --  the subprogram will be frozen at the point the wrapper package
3188         --  is frozen, so it does not need its own freeze node. In fact, if
3189         --  one is created, it might conflict with the freezing actions from
3190         --  the wrapper package (see 7206-013).
3191
3192         Set_Has_Delayed_Freeze (Anon_Id, False);
3193
3194         --  If the instance is a child unit, mark the Id accordingly. Mark
3195         --  the anonymous entity as well, which is the real subprogram and
3196         --  which is used when the instance appears in a context clause.
3197
3198         Set_Is_Child_Unit (Act_Decl_Id, Is_Child_Unit (Defining_Entity (N)));
3199         Set_Is_Child_Unit (Anon_Id, Is_Child_Unit (Defining_Entity (N)));
3200         New_Overloaded_Entity (Act_Decl_Id);
3201         Check_Eliminated  (Act_Decl_Id);
3202
3203         --  In compilation unit case, kill elaboration checks on the
3204         --  instantiation, since they are never needed -- the body is
3205         --  instantiated at the same point as the spec.
3206
3207         if Nkind (Parent (N)) = N_Compilation_Unit then
3208            Set_Suppress_Elaboration_Warnings (Act_Decl_Id);
3209            Set_Kill_Elaboration_Checks       (Act_Decl_Id);
3210            Set_Is_Compilation_Unit (Anon_Id);
3211
3212            Set_Cunit_Entity (Current_Sem_Unit, Pack_Id);
3213         end if;
3214
3215         --  The instance is not a freezing point for the new subprogram.
3216
3217         Set_Is_Frozen (Act_Decl_Id, False);
3218
3219         if Nkind (Defining_Entity (N)) = N_Defining_Operator_Symbol then
3220            Valid_Operator_Definition (Act_Decl_Id);
3221         end if;
3222
3223         Set_Alias  (Act_Decl_Id, Anon_Id);
3224         Set_Parent (Act_Decl_Id, Parent (Anon_Id));
3225         Set_Has_Completion (Act_Decl_Id);
3226         Set_Related_Instance (Pack_Id, Act_Decl_Id);
3227
3228         if Nkind (Parent (N)) = N_Compilation_Unit then
3229            Set_Body_Required (Parent (N), False);
3230         end if;
3231
3232      end Analyze_Instance_And_Renamings;
3233
3234   --  Start of processing for Analyze_Subprogram_Instantiation
3235
3236   begin
3237      --  Very first thing: apply the special kludge for Text_IO processing
3238      --  in case we are instantiating one of the children of [Wide_]Text_IO.
3239      --  Of course such an instantiation is bogus (these are packages, not
3240      --  subprograms), but we get a better error message if we do this.
3241
3242      Text_IO_Kludge (Gen_Id);
3243
3244      --  Make node global for error reporting.
3245
3246      Instantiation_Node := N;
3247      Pre_Analyze_Actuals (N);
3248
3249      Init_Env;
3250      Check_Generic_Child_Unit (Gen_Id, Parent_Installed);
3251      Gen_Unit := Entity (Gen_Id);
3252
3253      Generate_Reference (Gen_Unit, Gen_Id);
3254
3255      if Nkind (Gen_Id) = N_Identifier
3256        and then Chars (Gen_Unit) = Chars (Defining_Entity (N))
3257      then
3258         Error_Msg_NE
3259           ("& is hidden within declaration of instance", Gen_Id, Gen_Unit);
3260      end if;
3261
3262      if Etype (Gen_Unit) = Any_Type then
3263         Restore_Env;
3264         return;
3265      end if;
3266
3267      --  Verify that it is a generic subprogram of the right kind, and that
3268      --  it does not lead to a circular instantiation.
3269
3270      if Ekind (Gen_Unit) /= E_Generic_Procedure
3271        and then Ekind (Gen_Unit) /= E_Generic_Function
3272      then
3273         Error_Msg_N ("expect generic subprogram in instantiation", Gen_Id);
3274
3275      elsif In_Open_Scopes (Gen_Unit) then
3276         Error_Msg_NE ("instantiation of & within itself", N, Gen_Unit);
3277
3278      elsif K = E_Procedure
3279        and then Ekind (Gen_Unit) /= E_Generic_Procedure
3280      then
3281         if Ekind (Gen_Unit) = E_Generic_Function then
3282            Error_Msg_N
3283              ("cannot instantiate generic function as procedure", Gen_Id);
3284         else
3285            Error_Msg_N
3286              ("expect name of generic procedure in instantiation", Gen_Id);
3287         end if;
3288
3289      elsif K = E_Function
3290        and then Ekind (Gen_Unit) /= E_Generic_Function
3291      then
3292         if Ekind (Gen_Unit) = E_Generic_Procedure then
3293            Error_Msg_N
3294              ("cannot instantiate generic procedure as function", Gen_Id);
3295         else
3296            Error_Msg_N
3297              ("expect name of generic function in instantiation", Gen_Id);
3298         end if;
3299
3300      else
3301         Set_Entity (Gen_Id, Gen_Unit);
3302         Set_Is_Instantiated (Gen_Unit);
3303
3304         if In_Extended_Main_Source_Unit (N) then
3305            Generate_Reference (Gen_Unit, N);
3306         end if;
3307
3308         --  If renaming, get original unit
3309
3310         if Present (Renamed_Object (Gen_Unit))
3311           and then (Ekind (Renamed_Object (Gen_Unit)) = E_Generic_Procedure
3312                       or else
3313                     Ekind (Renamed_Object (Gen_Unit)) = E_Generic_Function)
3314         then
3315            Gen_Unit := Renamed_Object (Gen_Unit);
3316            Set_Is_Instantiated (Gen_Unit);
3317            Generate_Reference  (Gen_Unit, N);
3318         end if;
3319
3320         if Contains_Instance_Of (Gen_Unit, Current_Scope, Gen_Id) then
3321            Error_Msg_Node_2 := Current_Scope;
3322            Error_Msg_NE
3323              ("circular Instantiation: & instantiated in &!", N, Gen_Unit);
3324            Circularity_Detected := True;
3325            return;
3326         end if;
3327
3328         Gen_Decl := Unit_Declaration_Node (Gen_Unit);
3329
3330         --  The subprogram itself cannot contain a nested instance, so
3331         --  the current parent is left empty.
3332
3333         Set_Instance_Env (Gen_Unit, Empty);
3334
3335         --  Initialize renamings map, for error checking.
3336
3337         Generic_Renamings.Set_Last (0);
3338         Generic_Renamings_HTable.Reset;
3339
3340         Create_Instantiation_Source (N, Gen_Unit, False, S_Adjustment);
3341
3342         --  Copy original generic tree, to produce text for instantiation.
3343
3344         Act_Tree :=
3345           Copy_Generic_Node
3346             (Original_Node (Gen_Decl), Empty, Instantiating => True);
3347
3348         Act_Spec := Specification (Act_Tree);
3349         Renaming_List :=
3350           Analyze_Associations
3351             (N,
3352              Generic_Formal_Declarations (Act_Tree),
3353              Generic_Formal_Declarations (Gen_Decl));
3354
3355         --  Build the subprogram declaration, which does not appear
3356         --  in the generic template, and give it a sloc consistent
3357         --  with that of the template.
3358
3359         Set_Defining_Unit_Name (Act_Spec, Anon_Id);
3360         Set_Generic_Parent (Act_Spec, Gen_Unit);
3361         Act_Decl :=
3362           Make_Subprogram_Declaration (Sloc (Act_Spec),
3363             Specification => Act_Spec);
3364
3365         Set_Categorization_From_Pragmas (Act_Decl);
3366
3367         if Parent_Installed then
3368            Hide_Current_Scope;
3369         end if;
3370
3371         Append (Act_Decl, Renaming_List);
3372         Analyze_Instance_And_Renamings;
3373
3374         --  If the generic is marked Import (Intrinsic), then so is the
3375         --  instance. This indicates that there is no body to instantiate.
3376         --  If generic is marked inline, so it the instance, and the
3377         --  anonymous subprogram it renames. If inlined, or else if inlining
3378         --  is enabled for the compilation, we generate the instance body
3379         --  even if it is not within the main unit.
3380
3381         --  Any other  pragmas might also be inherited ???
3382
3383         if Is_Intrinsic_Subprogram (Gen_Unit) then
3384            Set_Is_Intrinsic_Subprogram (Anon_Id);
3385            Set_Is_Intrinsic_Subprogram (Act_Decl_Id);
3386
3387            if Chars (Gen_Unit) = Name_Unchecked_Conversion then
3388               Validate_Unchecked_Conversion (N, Act_Decl_Id);
3389            end if;
3390         end if;
3391
3392         Generate_Definition (Act_Decl_Id);
3393
3394         Set_Is_Inlined (Act_Decl_Id, Is_Inlined (Gen_Unit));
3395         Set_Is_Inlined (Anon_Id,     Is_Inlined (Gen_Unit));
3396
3397         if not Is_Intrinsic_Subprogram (Gen_Unit) then
3398            Check_Elab_Instantiation (N);
3399         end if;
3400
3401         Check_Hidden_Child_Unit (N, Gen_Unit, Act_Decl_Id);
3402
3403         --  Subject to change, pending on if other pragmas are inherited ???
3404
3405         Validate_Categorization_Dependency (N, Act_Decl_Id);
3406
3407         if not Is_Intrinsic_Subprogram (Act_Decl_Id) then
3408
3409            if not Generic_Separately_Compiled (Gen_Unit) then
3410               Inherit_Context (Gen_Decl, N);
3411            end if;
3412
3413            Restore_Private_Views (Pack_Id, False);
3414
3415            --  If the context requires a full instantiation, mark node for
3416            --  subsequent construction of the body.
3417
3418            if (Is_In_Main_Unit (N)
3419                  or else Is_Inlined (Act_Decl_Id))
3420              and then (Operating_Mode = Generate_Code
3421                          or else (Operating_Mode = Check_Semantics
3422                                    and then ASIS_Mode))
3423              and then (Expander_Active or else ASIS_Mode)
3424              and then not ABE_Is_Certain (N)
3425              and then not Is_Eliminated (Act_Decl_Id)
3426            then
3427               Pending_Instantiations.Increment_Last;
3428               Pending_Instantiations.Table (Pending_Instantiations.Last) :=
3429                 (N, Act_Decl, Expander_Active, Current_Sem_Unit);
3430               Check_Forward_Instantiation (Gen_Decl);
3431
3432               --  The wrapper package is always delayed, because it does
3433               --  not constitute a freeze point, but to insure that the
3434               --  freeze node is placed properly, it is created directly
3435               --  when instantiating the body (otherwise the freeze node
3436               --  might appear to early for nested instantiations).
3437
3438            elsif Nkind (Parent (N)) = N_Compilation_Unit then
3439
3440               --  For ASIS purposes, indicate that the wrapper package has
3441               --  replaced the instantiation node.
3442
3443               Rewrite (N, Unit (Parent (N)));
3444               Set_Unit (Parent (N), N);
3445            end if;
3446
3447         elsif Nkind (Parent (N)) = N_Compilation_Unit then
3448
3449               --  Replace instance node for library-level instantiations
3450               --  of intrinsic subprograms, for ASIS use.
3451
3452               Rewrite (N, Unit (Parent (N)));
3453               Set_Unit (Parent (N), N);
3454         end if;
3455
3456         if Parent_Installed then
3457            Remove_Parent;
3458         end if;
3459
3460         Restore_Env;
3461         Generic_Renamings.Set_Last (0);
3462         Generic_Renamings_HTable.Reset;
3463      end if;
3464
3465   exception
3466      when Instantiation_Error =>
3467         if Parent_Installed then
3468            Remove_Parent;
3469         end if;
3470   end Analyze_Subprogram_Instantiation;
3471
3472   -------------------------
3473   -- Get_Associated_Node --
3474   -------------------------
3475
3476   function Get_Associated_Node (N : Node_Id) return Node_Id is
3477      Assoc : Node_Id := Associated_Node (N);
3478
3479   begin
3480      if Nkind (Assoc) /= Nkind (N) then
3481         return Assoc;
3482
3483      elsif Nkind (Assoc) = N_Aggregate
3484        or else Nkind (Assoc) = N_Extension_Aggregate
3485      then
3486         return Assoc;
3487      else
3488         --  If the node is part of an inner generic, it may itself have been
3489         --  remapped into a further generic copy. Associated_Node is otherwise
3490         --  used for the entity of the node, and will be of a different node
3491         --  kind, or else N has been rewritten as a literal or function call.
3492
3493         while Present (Associated_Node (Assoc))
3494           and then Nkind (Associated_Node (Assoc)) = Nkind (Assoc)
3495         loop
3496            Assoc := Associated_Node (Assoc);
3497         end loop;
3498
3499         --  Follow and additional link in case the final node was rewritten.
3500         --  This can only happen with nested generic units.
3501
3502         if (Nkind (Assoc) = N_Identifier or else Nkind (Assoc) in N_Op)
3503           and then Present (Associated_Node (Assoc))
3504           and then (Nkind (Associated_Node (Assoc)) = N_Function_Call
3505                       or else
3506                     Nkind (Associated_Node (Assoc)) = N_Explicit_Dereference
3507                       or else
3508                     Nkind (Associated_Node (Assoc)) = N_Integer_Literal
3509                       or else
3510                     Nkind (Associated_Node (Assoc)) = N_Real_Literal
3511                       or else
3512                     Nkind (Associated_Node (Assoc)) = N_String_Literal)
3513         then
3514            Assoc := Associated_Node (Assoc);
3515         end if;
3516
3517         return Assoc;
3518      end if;
3519   end Get_Associated_Node;
3520
3521   -------------------------------------------
3522   -- Build_Instance_Compilation_Unit_Nodes --
3523   -------------------------------------------
3524
3525   procedure Build_Instance_Compilation_Unit_Nodes
3526     (N        : Node_Id;
3527      Act_Body : Node_Id;
3528      Act_Decl : Node_Id)
3529   is
3530      Decl_Cunit : Node_Id;
3531      Body_Cunit : Node_Id;
3532      Citem      : Node_Id;
3533      New_Main   : constant Entity_Id := Defining_Entity (Act_Decl);
3534      Old_Main   : constant Entity_Id := Cunit_Entity (Main_Unit);
3535
3536   begin
3537      --  A new compilation unit node is built for the instance declaration
3538
3539      Decl_Cunit :=
3540        Make_Compilation_Unit (Sloc (N),
3541          Context_Items  => Empty_List,
3542          Unit           => Act_Decl,
3543          Aux_Decls_Node =>
3544            Make_Compilation_Unit_Aux (Sloc (N)));
3545
3546      Set_Parent_Spec   (Act_Decl, Parent_Spec (N));
3547      Set_Body_Required (Decl_Cunit, True);
3548
3549      --  We use the original instantiation compilation unit as the resulting
3550      --  compilation unit of the instance, since this is the main unit.
3551
3552      Rewrite (N, Act_Body);
3553      Body_Cunit := Parent (N);
3554
3555      --  The two compilation unit nodes are linked by the Library_Unit field
3556
3557      Set_Library_Unit  (Decl_Cunit, Body_Cunit);
3558      Set_Library_Unit  (Body_Cunit, Decl_Cunit);
3559
3560      --  Preserve the private nature of the package if needed.
3561
3562      Set_Private_Present (Decl_Cunit, Private_Present (Body_Cunit));
3563
3564      --  If the instance is not the main unit, its context, categorization,
3565      --  and elaboration entity are not relevant to the compilation.
3566
3567      if Parent (N) /= Cunit (Main_Unit) then
3568         return;
3569      end if;
3570
3571      --  The context clause items on the instantiation, which are now
3572      --  attached to the body compilation unit (since the body overwrote
3573      --  the original instantiation node), semantically belong on the spec,
3574      --  so copy them there. It's harmless to leave them on the body as well.
3575      --  In fact one could argue that they belong in both places.
3576
3577      Citem := First (Context_Items (Body_Cunit));
3578      while Present (Citem) loop
3579         Append (New_Copy (Citem), Context_Items (Decl_Cunit));
3580         Next (Citem);
3581      end loop;
3582
3583      --  Propagate categorization flags on packages, so that they appear
3584      --  in ali file for the spec of the unit.
3585
3586      if Ekind (New_Main) = E_Package then
3587         Set_Is_Pure           (Old_Main, Is_Pure (New_Main));
3588         Set_Is_Preelaborated  (Old_Main, Is_Preelaborated (New_Main));
3589         Set_Is_Remote_Types   (Old_Main, Is_Remote_Types (New_Main));
3590         Set_Is_Shared_Passive (Old_Main, Is_Shared_Passive (New_Main));
3591         Set_Is_Remote_Call_Interface
3592           (Old_Main, Is_Remote_Call_Interface (New_Main));
3593      end if;
3594
3595      --  Make entry in Units table, so that binder can generate call to
3596      --  elaboration procedure for body, if any.
3597
3598      Make_Instance_Unit (Body_Cunit);
3599      Main_Unit_Entity := New_Main;
3600      Set_Cunit_Entity (Main_Unit, Main_Unit_Entity);
3601
3602      --  Build elaboration entity, since the instance may certainly
3603      --  generate elaboration code requiring a flag for protection.
3604
3605      Build_Elaboration_Entity (Decl_Cunit, New_Main);
3606   end Build_Instance_Compilation_Unit_Nodes;
3607
3608   -----------------------------------
3609   -- Check_Formal_Package_Instance --
3610   -----------------------------------
3611
3612   --  If the formal has specific parameters, they must match those of the
3613   --  actual. Both of them are instances, and the renaming declarations
3614   --  for their formal parameters appear in the same order in both. The
3615   --  analyzed formal has been analyzed in the context of the current
3616   --  instance.
3617
3618   procedure Check_Formal_Package_Instance
3619     (Formal_Pack : Entity_Id;
3620      Actual_Pack : Entity_Id)
3621   is
3622      E1 : Entity_Id := First_Entity (Actual_Pack);
3623      E2 : Entity_Id := First_Entity (Formal_Pack);
3624
3625      Expr1 : Node_Id;
3626      Expr2 : Node_Id;
3627
3628      procedure Check_Mismatch (B : Boolean);
3629      --  Common error routine for mismatch between the parameters of
3630      --  the actual instance and those of the formal package.
3631
3632      procedure Check_Mismatch (B : Boolean) is
3633      begin
3634         if B then
3635            Error_Msg_NE
3636              ("actual for & in actual instance does not match formal",
3637               Parent (Actual_Pack), E1);
3638         end if;
3639      end Check_Mismatch;
3640
3641   --  Start of processing for Check_Formal_Package_Instance
3642
3643   begin
3644      while Present (E1)
3645        and then Present (E2)
3646      loop
3647         exit when Ekind (E1) = E_Package
3648           and then Renamed_Entity (E1) = Renamed_Entity (Actual_Pack);
3649
3650         if Is_Type (E1) then
3651
3652            --  Subtypes must statically match. E1 and E2 are the
3653            --  local entities that are subtypes of the actuals.
3654            --  Itypes generated for other parameters need not be checked,
3655            --  the check will be performed on the parameters themselves.
3656
3657            if not Is_Itype (E1)
3658              and then not Is_Itype (E2)
3659            then
3660               Check_Mismatch
3661                 (not Is_Type (E2)
3662                   or else Etype (E1) /= Etype (E2)
3663                   or else not Subtypes_Statically_Match (E1, E2));
3664            end if;
3665
3666         elsif Ekind (E1) = E_Constant then
3667
3668            --  IN parameters must denote the same static value, or
3669            --  the same constant, or the literal null.
3670
3671            Expr1 := Expression (Parent (E1));
3672
3673            if Ekind (E2) /= E_Constant then
3674               Check_Mismatch (True);
3675               goto Next_E;
3676            else
3677               Expr2 := Expression (Parent (E2));
3678            end if;
3679
3680            if Is_Static_Expression (Expr1) then
3681
3682               if not Is_Static_Expression (Expr2) then
3683                  Check_Mismatch (True);
3684
3685               elsif Is_Integer_Type (Etype (E1)) then
3686
3687                  declare
3688                     V1 : constant Uint := Expr_Value (Expr1);
3689                     V2 : constant Uint := Expr_Value (Expr2);
3690                  begin
3691                     Check_Mismatch (V1 /= V2);
3692                  end;
3693
3694               elsif Is_Real_Type (Etype (E1)) then
3695                  declare
3696                     V1 : constant Ureal := Expr_Value_R (Expr1);
3697                     V2 : constant Ureal := Expr_Value_R (Expr2);
3698                  begin
3699                     Check_Mismatch (V1 /= V2);
3700                  end;
3701
3702               elsif Is_String_Type (Etype (E1))
3703                 and then Nkind (Expr1) = N_String_Literal
3704               then
3705
3706                  if Nkind (Expr2) /= N_String_Literal then
3707                     Check_Mismatch (True);
3708                  else
3709                     Check_Mismatch
3710                       (not String_Equal (Strval (Expr1), Strval (Expr2)));
3711                  end if;
3712               end if;
3713
3714            elsif Is_Entity_Name (Expr1) then
3715               if Is_Entity_Name (Expr2) then
3716                  if Entity (Expr1) = Entity (Expr2) then
3717                     null;
3718
3719                  elsif Ekind (Entity (Expr2)) = E_Constant
3720                     and then Is_Entity_Name (Constant_Value (Entity (Expr2)))
3721                     and then
3722                      Entity (Constant_Value (Entity (Expr2))) = Entity (Expr1)
3723                  then
3724                     null;
3725                  else
3726                     Check_Mismatch (True);
3727                  end if;
3728               else
3729                  Check_Mismatch (True);
3730               end if;
3731
3732            elsif Nkind (Expr1) = N_Null then
3733               Check_Mismatch (Nkind (Expr1) /= N_Null);
3734
3735            else
3736               Check_Mismatch (True);
3737            end if;
3738
3739         elsif Ekind (E1) = E_Variable
3740           or else Ekind (E1) = E_Package
3741         then
3742            Check_Mismatch
3743              (Ekind (E1) /= Ekind (E2)
3744                or else Renamed_Object (E1) /= Renamed_Object (E2));
3745
3746         elsif Is_Overloadable (E1) then
3747
3748            --  Verify that the names of the  entities match.
3749            --  What if actual is an attribute ???
3750
3751            Check_Mismatch
3752              (Ekind (E2) /= Ekind (E1) or else (Alias (E1)) /= Alias (E2));
3753
3754         else
3755            raise Program_Error;
3756         end if;
3757
3758         <<Next_E>>
3759            Next_Entity (E1);
3760            Next_Entity (E2);
3761      end loop;
3762   end Check_Formal_Package_Instance;
3763
3764   ---------------------------
3765   -- Check_Formal_Packages --
3766   ---------------------------
3767
3768   procedure Check_Formal_Packages (P_Id : Entity_Id) is
3769      E        : Entity_Id;
3770      Formal_P : Entity_Id;
3771
3772   begin
3773      --  Iterate through the declarations in the instance, looking for
3774      --  package renaming declarations that denote instances of formal
3775      --  packages. Stop when we find the renaming of the current package
3776      --  itself. The declaration for a formal package without a box is
3777      --  followed by an internal entity that repeats the instantiation.
3778
3779      E := First_Entity (P_Id);
3780      while Present (E) loop
3781         if Ekind (E) = E_Package then
3782            if Renamed_Object (E) = P_Id then
3783               exit;
3784
3785            elsif Nkind (Parent (E)) /= N_Package_Renaming_Declaration then
3786               null;
3787
3788            elsif not Box_Present (Parent (Associated_Formal_Package (E))) then
3789               Formal_P := Next_Entity (E);
3790               Check_Formal_Package_Instance (Formal_P, E);
3791            end if;
3792         end if;
3793
3794         Next_Entity (E);
3795      end loop;
3796   end Check_Formal_Packages;
3797
3798   ---------------------------------
3799   -- Check_Forward_Instantiation --
3800   ---------------------------------
3801
3802   procedure Check_Forward_Instantiation (Decl : Node_Id) is
3803      S        : Entity_Id;
3804      Gen_Comp : Entity_Id := Cunit_Entity (Get_Source_Unit (Decl));
3805
3806   begin
3807      --  The instantiation appears before the generic body if we are in the
3808      --  scope of the unit containing the generic, either in its spec or in
3809      --  the package body. and before the generic body.
3810
3811      if Ekind (Gen_Comp) = E_Package_Body then
3812         Gen_Comp := Spec_Entity (Gen_Comp);
3813      end if;
3814
3815      if In_Open_Scopes (Gen_Comp)
3816        and then No (Corresponding_Body (Decl))
3817      then
3818         S := Current_Scope;
3819
3820         while Present (S)
3821           and then not Is_Compilation_Unit (S)
3822           and then not Is_Child_Unit (S)
3823         loop
3824            if Ekind (S) = E_Package then
3825               Set_Has_Forward_Instantiation (S);
3826            end if;
3827
3828            S := Scope (S);
3829         end loop;
3830      end if;
3831   end Check_Forward_Instantiation;
3832
3833   ---------------------------
3834   -- Check_Generic_Actuals --
3835   ---------------------------
3836
3837   --  The visibility of the actuals may be different between the
3838   --  point of generic instantiation and the instantiation of the body.
3839
3840   procedure Check_Generic_Actuals
3841     (Instance      : Entity_Id;
3842      Is_Formal_Box : Boolean)
3843   is
3844      E      : Entity_Id;
3845      Astype : Entity_Id;
3846
3847   begin
3848      E := First_Entity (Instance);
3849      while Present (E) loop
3850         if Is_Type (E)
3851           and then Nkind (Parent (E)) = N_Subtype_Declaration
3852           and then Scope (Etype (E)) /= Instance
3853           and then Is_Entity_Name (Subtype_Indication (Parent (E)))
3854         then
3855            Check_Private_View (Subtype_Indication (Parent (E)));
3856            Set_Is_Generic_Actual_Type (E, True);
3857            Set_Is_Hidden (E, False);
3858
3859            --  We constructed the generic actual type as a subtype of
3860            --  the supplied type. This means that it normally would not
3861            --  inherit subtype specific attributes of the actual, which
3862            --  is wrong for the generic case.
3863
3864            Astype := Ancestor_Subtype (E);
3865
3866            if No (Astype) then
3867
3868               --  can happen when E is an itype that is the full view of
3869               --  a private type completed, e.g. with a constrained array.
3870
3871               Astype := Base_Type (E);
3872            end if;
3873
3874            Set_Size_Info      (E,                (Astype));
3875            Set_RM_Size        (E, RM_Size        (Astype));
3876            Set_First_Rep_Item (E, First_Rep_Item (Astype));
3877
3878            if Is_Discrete_Or_Fixed_Point_Type (E) then
3879               Set_RM_Size (E, RM_Size (Astype));
3880
3881            --  In  nested instances, the base type of an access actual
3882            --  may itself be private, and need to be exchanged.
3883
3884            elsif Is_Access_Type (E)
3885              and then Is_Private_Type (Etype (E))
3886            then
3887               Check_Private_View
3888                 (New_Occurrence_Of (Etype (E), Sloc (Instance)));
3889            end if;
3890
3891         elsif Ekind (E) = E_Package then
3892
3893            --  If this is the renaming for the current instance, we're done.
3894            --  Otherwise it is a formal package. If the corresponding formal
3895            --  was declared with a box, the (instantiations of the) generic
3896            --  formal part are also visible. Otherwise, ignore the entity
3897            --  created to validate the actuals.
3898
3899            if Renamed_Object (E) = Instance then
3900               exit;
3901
3902            elsif Nkind (Parent (E)) /= N_Package_Renaming_Declaration then
3903               null;
3904
3905            --  The visibility of a formal of an enclosing generic is already
3906            --  correct.
3907
3908            elsif Denotes_Formal_Package (E) then
3909               null;
3910
3911            elsif Present (Associated_Formal_Package (E))
3912              and then Box_Present (Parent (Associated_Formal_Package (E)))
3913            then
3914               Check_Generic_Actuals (Renamed_Object (E), True);
3915               Set_Is_Hidden (E, False);
3916            end if;
3917
3918         --  If this is a subprogram instance (in a wrapper package) the
3919         --  actual is fully visible.
3920
3921         elsif Is_Wrapper_Package (Instance) then
3922            Set_Is_Hidden (E, False);
3923
3924         else
3925            Set_Is_Hidden (E, not Is_Formal_Box);
3926         end if;
3927
3928         Next_Entity (E);
3929      end loop;
3930   end Check_Generic_Actuals;
3931
3932   ------------------------------
3933   -- Check_Generic_Child_Unit --
3934   ------------------------------
3935
3936   procedure Check_Generic_Child_Unit
3937     (Gen_Id           : Node_Id;
3938      Parent_Installed : in out Boolean)
3939   is
3940      Loc      : constant Source_Ptr := Sloc (Gen_Id);
3941      Gen_Par  : Entity_Id := Empty;
3942      Inst_Par : Entity_Id;
3943      E        : Entity_Id;
3944      S        : Node_Id;
3945
3946      function Find_Generic_Child
3947        (Scop : Entity_Id;
3948         Id   : Node_Id)
3949         return Entity_Id;
3950      --  Search generic parent for possible child unit with the given name.
3951
3952      function In_Enclosing_Instance return Boolean;
3953      --  Within an instance of the parent, the child unit may be denoted
3954      --  by a simple name, or an abbreviated expanded name. Examine enclosing
3955      --  scopes to locate a possible parent instantiation.
3956
3957      ------------------------
3958      -- Find_Generic_Child --
3959      ------------------------
3960
3961      function Find_Generic_Child
3962        (Scop : Entity_Id;
3963         Id   : Node_Id)
3964         return Entity_Id
3965      is
3966         E : Entity_Id;
3967
3968      begin
3969         --  If entity of name is already set, instance has already been
3970         --  resolved, e.g. in an enclosing instantiation.
3971
3972         if Present (Entity (Id)) then
3973            if Scope (Entity (Id)) = Scop then
3974               return Entity (Id);
3975            else
3976               return Empty;
3977            end if;
3978
3979         else
3980            E := First_Entity (Scop);
3981            while Present (E) loop
3982               if Chars (E) = Chars (Id)
3983                 and then Is_Child_Unit (E)
3984               then
3985                  if Is_Child_Unit (E)
3986                    and then not Is_Visible_Child_Unit (E)
3987                  then
3988                     Error_Msg_NE
3989                       ("generic child unit& is not visible", Gen_Id, E);
3990                  end if;
3991
3992                  Set_Entity (Id, E);
3993                  return E;
3994               end if;
3995
3996               Next_Entity (E);
3997            end loop;
3998
3999            return Empty;
4000         end if;
4001      end Find_Generic_Child;
4002
4003      ---------------------------
4004      -- In_Enclosing_Instance --
4005      ---------------------------
4006
4007      function In_Enclosing_Instance return Boolean is
4008         Enclosing_Instance : Node_Id;
4009         Instance_Decl      : Node_Id;
4010
4011      begin
4012         Enclosing_Instance := Current_Scope;
4013
4014         while Present (Enclosing_Instance) loop
4015            Instance_Decl := Unit_Declaration_Node (Enclosing_Instance);
4016
4017            if Ekind (Enclosing_Instance) = E_Package
4018              and then Is_Generic_Instance (Enclosing_Instance)
4019              and then Present
4020                (Generic_Parent (Specification (Instance_Decl)))
4021            then
4022               --  Check whether the generic we are looking for is a child
4023               --  of this instance.
4024
4025               E := Find_Generic_Child
4026                      (Generic_Parent (Specification (Instance_Decl)), Gen_Id);
4027               exit when Present (E);
4028
4029            else
4030               E := Empty;
4031            end if;
4032
4033            Enclosing_Instance := Scope (Enclosing_Instance);
4034         end loop;
4035
4036         if No (E) then
4037
4038            --  Not a child unit
4039
4040            Analyze (Gen_Id);
4041            return False;
4042
4043         else
4044            Rewrite (Gen_Id,
4045              Make_Expanded_Name (Loc,
4046                Chars         => Chars (E),
4047                Prefix        => New_Occurrence_Of (Enclosing_Instance, Loc),
4048                Selector_Name => New_Occurrence_Of (E, Loc)));
4049
4050            Set_Entity (Gen_Id, E);
4051            Set_Etype  (Gen_Id, Etype (E));
4052            Parent_Installed := False;      -- Already in scope.
4053            return True;
4054         end if;
4055      end In_Enclosing_Instance;
4056
4057   --  Start of processing for Check_Generic_Child_Unit
4058
4059   begin
4060      --  If the name of the generic is given by a selected component, it
4061      --  may be the name of a generic child unit, and the prefix is the name
4062      --  of an instance of the parent, in which case the child unit must be
4063      --  visible. If this instance is not in scope, it must be placed there
4064      --  and removed after instantiation, because what is being instantiated
4065      --  is not the original child, but the corresponding child present in
4066      --  the instance of the parent.
4067
4068      --  If the child is instantiated within the parent, it can be given by
4069      --  a simple name. In this case the instance is already in scope, but
4070      --  the child generic must be recovered from the generic parent as well.
4071
4072      if Nkind (Gen_Id) = N_Selected_Component then
4073         S := Selector_Name (Gen_Id);
4074         Analyze (Prefix (Gen_Id));
4075         Inst_Par := Entity (Prefix (Gen_Id));
4076
4077         if Ekind (Inst_Par) = E_Package
4078           and then Present (Renamed_Object (Inst_Par))
4079         then
4080            Inst_Par := Renamed_Object (Inst_Par);
4081         end if;
4082
4083         if Ekind (Inst_Par) = E_Package then
4084            if Nkind (Parent (Inst_Par)) = N_Package_Specification then
4085               Gen_Par := Generic_Parent (Parent (Inst_Par));
4086
4087            elsif Nkind (Parent (Inst_Par)) = N_Defining_Program_Unit_Name
4088              and then
4089                Nkind (Parent (Parent (Inst_Par))) = N_Package_Specification
4090            then
4091               Gen_Par := Generic_Parent (Parent (Parent (Inst_Par)));
4092            end if;
4093
4094         elsif Ekind (Inst_Par) = E_Generic_Package
4095           and then Nkind (Parent (Gen_Id)) = N_Formal_Package_Declaration
4096         then
4097            --  A formal package may be a real child package, and not the
4098            --  implicit instance within a parent. In this case the child is
4099            --  not visible and has to be retrieved explicitly as well.
4100
4101            Gen_Par := Inst_Par;
4102         end if;
4103
4104         if Present (Gen_Par) then
4105
4106            --  The prefix denotes an instantiation. The entity itself
4107            --  may be a nested generic, or a child unit.
4108
4109            E := Find_Generic_Child (Gen_Par, S);
4110
4111            if Present (E) then
4112               Change_Selected_Component_To_Expanded_Name (Gen_Id);
4113               Set_Entity (Gen_Id, E);
4114               Set_Etype (Gen_Id, Etype (E));
4115               Set_Entity (S, E);
4116               Set_Etype (S, Etype (E));
4117
4118               --  Indicate that this is a reference to the parent.
4119
4120               if In_Extended_Main_Source_Unit (Gen_Id) then
4121                  Set_Is_Instantiated (Inst_Par);
4122               end if;
4123
4124               --  A common mistake is to replicate the naming scheme of
4125               --  a hierarchy by instantiating a generic child directly,
4126               --  rather than the implicit child in a parent instance:
4127
4128               --  generic .. package Gpar is ..
4129               --  generic .. package Gpar.Child is ..
4130               --  package Par is new Gpar ();
4131
4132               --  with Gpar.Child;
4133               --  package Par.Child is new Gpar.Child ();
4134               --                           rather than Par.Child
4135
4136               --  In this case the instantiation is within Par, which is
4137               --  an instance, but Gpar does not denote Par because we are
4138               --  not IN the instance of Gpar, so this is illegal. The test
4139               --  below recognizes this particular case.
4140
4141               if Is_Child_Unit (E)
4142                 and then not Comes_From_Source (Entity (Prefix (Gen_Id)))
4143                 and then (not In_Instance
4144                             or else Nkind (Parent (Parent (Gen_Id))) =
4145                                                         N_Compilation_Unit)
4146               then
4147                  Error_Msg_N
4148                    ("prefix of generic child unit must be instance of parent",
4149                      Gen_Id);
4150               end if;
4151
4152               if not In_Open_Scopes (Inst_Par)
4153                 and then Nkind (Parent (Gen_Id)) not in
4154                                           N_Generic_Renaming_Declaration
4155               then
4156                  Install_Parent (Inst_Par);
4157                  Parent_Installed := True;
4158               end if;
4159
4160            else
4161               --  If the generic parent does not contain an entity that
4162               --  corresponds to the selector, the instance doesn't either.
4163               --  Analyzing the node will yield the appropriate error message.
4164               --  If the entity is not a child unit, then it is an inner
4165               --  generic in the parent.
4166
4167               Analyze (Gen_Id);
4168            end if;
4169
4170         else
4171            Analyze (Gen_Id);
4172
4173            if Is_Child_Unit (Entity (Gen_Id))
4174              and then
4175                Nkind (Parent (Gen_Id)) not in N_Generic_Renaming_Declaration
4176              and then not In_Open_Scopes (Inst_Par)
4177            then
4178               Install_Parent (Inst_Par);
4179               Parent_Installed := True;
4180            end if;
4181         end if;
4182
4183      elsif Nkind (Gen_Id) = N_Expanded_Name then
4184
4185         --  Entity already present, analyze prefix, whose meaning may be
4186         --  an instance in the current context. If it is an instance of
4187         --  a relative within another, the proper parent may still have
4188         --  to be installed, if they are not of the same generation.
4189
4190         Analyze (Prefix (Gen_Id));
4191         Inst_Par := Entity (Prefix (Gen_Id));
4192
4193         if In_Enclosing_Instance then
4194            null;
4195
4196         elsif Present (Entity (Gen_Id))
4197           and then Is_Child_Unit (Entity (Gen_Id))
4198           and then not In_Open_Scopes (Inst_Par)
4199         then
4200            Install_Parent (Inst_Par);
4201            Parent_Installed := True;
4202         end if;
4203
4204      elsif In_Enclosing_Instance then
4205
4206         --  The child unit is found in some enclosing scope
4207
4208         null;
4209
4210      else
4211         Analyze (Gen_Id);
4212
4213         --  If this is the renaming of the implicit child in a parent
4214         --  instance, recover the parent name and install it.
4215
4216         if Is_Entity_Name (Gen_Id) then
4217            E := Entity (Gen_Id);
4218
4219            if Is_Generic_Unit (E)
4220              and then Nkind (Parent (E)) in N_Generic_Renaming_Declaration
4221              and then Is_Child_Unit (Renamed_Object (E))
4222              and then Is_Generic_Unit (Scope (Renamed_Object (E)))
4223              and then Nkind (Name (Parent (E))) = N_Expanded_Name
4224            then
4225               Rewrite (Gen_Id,
4226                 New_Copy_Tree (Name (Parent (E))));
4227               Inst_Par := Entity (Prefix (Gen_Id));
4228
4229               if not In_Open_Scopes (Inst_Par) then
4230                  Install_Parent (Inst_Par);
4231                  Parent_Installed := True;
4232               end if;
4233
4234            --  If it is a child unit of a non-generic parent, it may be
4235            --  use-visible and given by a direct name. Install parent as
4236            --  for other cases.
4237
4238            elsif Is_Generic_Unit (E)
4239              and then Is_Child_Unit (E)
4240              and then
4241                Nkind (Parent (Gen_Id)) not in N_Generic_Renaming_Declaration
4242              and then not Is_Generic_Unit (Scope (E))
4243            then
4244               if not In_Open_Scopes (Scope (E)) then
4245                  Install_Parent (Scope (E));
4246                  Parent_Installed := True;
4247               end if;
4248            end if;
4249         end if;
4250      end if;
4251   end Check_Generic_Child_Unit;
4252
4253   -----------------------------
4254   -- Check_Hidden_Child_Unit --
4255   -----------------------------
4256
4257   procedure Check_Hidden_Child_Unit
4258     (N           : Node_Id;
4259      Gen_Unit    : Entity_Id;
4260      Act_Decl_Id : Entity_Id)
4261   is
4262      Gen_Id : constant Node_Id := Name (N);
4263
4264   begin
4265      if Is_Child_Unit (Gen_Unit)
4266        and then Is_Child_Unit (Act_Decl_Id)
4267        and then Nkind (Gen_Id) = N_Expanded_Name
4268        and then Entity (Prefix (Gen_Id)) = Scope (Act_Decl_Id)
4269        and then Chars (Gen_Unit) = Chars (Act_Decl_Id)
4270      then
4271         Error_Msg_Node_2 := Scope (Act_Decl_Id);
4272         Error_Msg_NE
4273           ("generic unit & is implicitly declared in &",
4274             Defining_Unit_Name (N), Gen_Unit);
4275         Error_Msg_N ("\instance must have different name",
4276           Defining_Unit_Name (N));
4277      end if;
4278   end Check_Hidden_Child_Unit;
4279
4280   ------------------------
4281   -- Check_Private_View --
4282   ------------------------
4283
4284   procedure Check_Private_View (N : Node_Id) is
4285      T : constant Entity_Id := Etype (N);
4286      BT : Entity_Id;
4287
4288   begin
4289      --  Exchange views if the type was not private in the generic but is
4290      --  private at the point of instantiation. Do not exchange views if
4291      --  the scope of the type is in scope. This can happen if both generic
4292      --  and instance are sibling units, or if type is defined in a parent.
4293      --  In this case the visibility of the type will be correct for all
4294      --  semantic checks.
4295
4296      if Present (T) then
4297         BT := Base_Type (T);
4298
4299         if Is_Private_Type (T)
4300           and then not Has_Private_View (N)
4301           and then Present (Full_View (T))
4302           and then not In_Open_Scopes (Scope (T))
4303         then
4304            --  In the generic, the full type was visible. Save the
4305            --  private entity, for subsequent exchange.
4306
4307            Switch_View (T);
4308
4309         elsif Has_Private_View (N)
4310           and then not Is_Private_Type (T)
4311           and then not Has_Been_Exchanged (T)
4312           and then Etype (Get_Associated_Node (N)) /= T
4313         then
4314            --  Only the private declaration was visible in the generic. If
4315            --  the type appears in a subtype declaration, the subtype in the
4316            --  instance must have a view compatible with that of its parent,
4317            --  which must be exchanged (see corresponding code in Restore_
4318            --  Private_Views). Otherwise, if the type is defined in a parent
4319            --  unit, leave full visibility within instance, which is safe.
4320
4321            if In_Open_Scopes (Scope (Base_Type (T)))
4322              and then not Is_Private_Type (Base_Type (T))
4323              and then Comes_From_Source (Base_Type (T))
4324            then
4325               null;
4326
4327            elsif Nkind (Parent (N)) = N_Subtype_Declaration
4328              or else not In_Private_Part (Scope (Base_Type (T)))
4329            then
4330               Append_Elmt (T, Exchanged_Views);
4331               Exchange_Declarations (Etype (Get_Associated_Node (N)));
4332            end if;
4333
4334         --  For composite types with inconsistent representation
4335         --  exchange component types accordingly.
4336
4337         elsif Is_Access_Type (T)
4338           and then Is_Private_Type (Designated_Type (T))
4339           and then not Has_Private_View (N)
4340           and then Present (Full_View (Designated_Type (T)))
4341         then
4342            Switch_View (Designated_Type (T));
4343
4344         elsif Is_Array_Type (T)
4345           and then Is_Private_Type (Component_Type (T))
4346           and then not Has_Private_View (N)
4347           and then Present (Full_View (Component_Type (T)))
4348         then
4349            Switch_View (Component_Type (T));
4350
4351         elsif Is_Private_Type (T)
4352           and then Present (Full_View (T))
4353           and then Is_Array_Type (Full_View (T))
4354           and then Is_Private_Type (Component_Type (Full_View (T)))
4355         then
4356            Switch_View (T);
4357
4358         --  Finally, a non-private subtype may have a private base type,
4359         --  which must be exchanged for consistency. This can happen when
4360         --  instantiating a package body, when the scope stack is empty
4361         --  but in fact the subtype and the base type are declared in an
4362         --  enclosing scope.
4363
4364         elsif not Is_Private_Type (T)
4365           and then not Has_Private_View (N)
4366           and then Is_Private_Type (Base_Type (T))
4367           and then Present (Full_View (BT))
4368           and then not Is_Generic_Type (BT)
4369           and then not In_Open_Scopes (BT)
4370         then
4371            Append_Elmt (Full_View (BT), Exchanged_Views);
4372            Exchange_Declarations (BT);
4373         end if;
4374      end if;
4375   end Check_Private_View;
4376
4377   --------------------------
4378   -- Contains_Instance_Of --
4379   --------------------------
4380
4381   function Contains_Instance_Of
4382     (Inner : Entity_Id;
4383      Outer : Entity_Id;
4384      N     : Node_Id)
4385      return  Boolean
4386   is
4387      Elmt : Elmt_Id;
4388      Scop : Entity_Id;
4389
4390   begin
4391      Scop := Outer;
4392
4393      --  Verify that there are no circular instantiations. We check whether
4394      --  the unit contains an instance of the current scope or some enclosing
4395      --  scope (in case one of the instances appears in a subunit). Longer
4396      --  circularities involving subunits might seem too pathological to
4397      --  consider, but they were not too pathological for the authors of
4398      --  DEC bc30vsq, so we loop over all enclosing scopes, and mark all
4399      --  enclosing generic scopes as containing an instance.
4400
4401      loop
4402         --  Within a generic subprogram body, the scope is not generic, to
4403         --  allow for recursive subprograms. Use the declaration to determine
4404         --  whether this is a generic unit.
4405
4406         if Ekind (Scop) = E_Generic_Package
4407           or else (Is_Subprogram (Scop)
4408                      and then Nkind (Unit_Declaration_Node (Scop)) =
4409                                        N_Generic_Subprogram_Declaration)
4410         then
4411            Elmt := First_Elmt (Inner_Instances (Inner));
4412
4413            while Present (Elmt) loop
4414               if Node (Elmt) = Scop then
4415                  Error_Msg_Node_2 := Inner;
4416                  Error_Msg_NE
4417                    ("circular Instantiation: & instantiated within &!",
4418                       N, Scop);
4419                  return True;
4420
4421               elsif Node (Elmt) = Inner then
4422                  return True;
4423
4424               elsif Contains_Instance_Of (Node (Elmt), Scop, N) then
4425                  Error_Msg_Node_2 := Inner;
4426                  Error_Msg_NE
4427                    ("circular Instantiation: & instantiated within &!",
4428                      N, Node (Elmt));
4429                  return True;
4430               end if;
4431
4432               Next_Elmt (Elmt);
4433            end loop;
4434
4435            --  Indicate that Inner is being instantiated within  Scop.
4436
4437            Append_Elmt (Inner, Inner_Instances (Scop));
4438         end if;
4439
4440         if Scop = Standard_Standard then
4441            exit;
4442         else
4443            Scop := Scope (Scop);
4444         end if;
4445      end loop;
4446
4447      return False;
4448   end Contains_Instance_Of;
4449
4450   -----------------------
4451   -- Copy_Generic_Node --
4452   -----------------------
4453
4454   function Copy_Generic_Node
4455     (N             : Node_Id;
4456      Parent_Id     : Node_Id;
4457      Instantiating : Boolean)
4458      return          Node_Id
4459   is
4460      Ent   : Entity_Id;
4461      New_N : Node_Id;
4462
4463      function Copy_Generic_Descendant (D : Union_Id) return Union_Id;
4464      --  Check the given value of one of the Fields referenced by the
4465      --  current node to determine whether to copy it recursively. The
4466      --  field may hold a Node_Id, a List_Id, or an Elist_Id, or a plain
4467      --  value (Sloc, Uint, Char) in which case it need not be copied.
4468
4469      procedure Copy_Descendants;
4470      --  Common utility for various nodes.
4471
4472      function Copy_Generic_Elist (E : Elist_Id) return Elist_Id;
4473      --  Make copy of element list.
4474
4475      function Copy_Generic_List
4476        (L         : List_Id;
4477         Parent_Id : Node_Id)
4478         return      List_Id;
4479      --  Apply Copy_Node recursively to the members of a node list.
4480
4481      function In_Defining_Unit_Name (Nam : Node_Id) return Boolean;
4482      --  True if an identifier is part of the defining program unit name
4483      --  of a child unit. The entity of such an identifier must be kept
4484      --  (for ASIS use) even though as the name of an enclosing generic
4485      --   it would otherwise not be preserved in the generic tree.
4486
4487      -----------------------
4488      --  Copy_Descendants --
4489      -----------------------
4490
4491      procedure Copy_Descendants is
4492
4493         use Atree.Unchecked_Access;
4494         --  This code section is part of the implementation of an untyped
4495         --  tree traversal, so it needs direct access to node fields.
4496
4497      begin
4498         Set_Field1 (New_N, Copy_Generic_Descendant (Field1 (N)));
4499         Set_Field2 (New_N, Copy_Generic_Descendant (Field2 (N)));
4500         Set_Field3 (New_N, Copy_Generic_Descendant (Field3 (N)));
4501         Set_Field4 (New_N, Copy_Generic_Descendant (Field4 (N)));
4502         Set_Field5 (New_N, Copy_Generic_Descendant (Field5 (N)));
4503      end Copy_Descendants;
4504
4505      -----------------------------
4506      -- Copy_Generic_Descendant --
4507      -----------------------------
4508
4509      function Copy_Generic_Descendant (D : Union_Id) return Union_Id is
4510      begin
4511         if D = Union_Id (Empty) then
4512            return D;
4513
4514         elsif D in Node_Range then
4515            return Union_Id
4516              (Copy_Generic_Node (Node_Id (D), New_N, Instantiating));
4517
4518         elsif D in List_Range then
4519            return Union_Id (Copy_Generic_List (List_Id (D), New_N));
4520
4521         elsif D in Elist_Range then
4522            return Union_Id (Copy_Generic_Elist (Elist_Id (D)));
4523
4524         --  Nothing else is copyable (e.g. Uint values), return as is
4525
4526         else
4527            return D;
4528         end if;
4529      end Copy_Generic_Descendant;
4530
4531      ------------------------
4532      -- Copy_Generic_Elist --
4533      ------------------------
4534
4535      function Copy_Generic_Elist (E : Elist_Id) return Elist_Id is
4536         M : Elmt_Id;
4537         L : Elist_Id;
4538
4539      begin
4540         if Present (E) then
4541            L := New_Elmt_List;
4542            M := First_Elmt (E);
4543            while Present (M) loop
4544               Append_Elmt
4545                 (Copy_Generic_Node (Node (M), Empty, Instantiating), L);
4546               Next_Elmt (M);
4547            end loop;
4548
4549            return L;
4550
4551         else
4552            return No_Elist;
4553         end if;
4554      end Copy_Generic_Elist;
4555
4556      -----------------------
4557      -- Copy_Generic_List --
4558      -----------------------
4559
4560      function Copy_Generic_List
4561        (L         : List_Id;
4562         Parent_Id : Node_Id)
4563         return      List_Id
4564      is
4565         N     : Node_Id;
4566         New_L : List_Id;
4567
4568      begin
4569         if Present (L) then
4570            New_L := New_List;
4571            Set_Parent (New_L, Parent_Id);
4572
4573            N := First (L);
4574            while Present (N) loop
4575               Append (Copy_Generic_Node (N, Empty, Instantiating), New_L);
4576               Next (N);
4577            end loop;
4578
4579            return New_L;
4580
4581         else
4582            return No_List;
4583         end if;
4584      end Copy_Generic_List;
4585
4586      ---------------------------
4587      -- In_Defining_Unit_Name --
4588      ---------------------------
4589
4590      function In_Defining_Unit_Name (Nam : Node_Id) return Boolean is
4591      begin
4592         return Present (Parent (Nam))
4593           and then (Nkind (Parent (Nam)) = N_Defining_Program_Unit_Name
4594                      or else
4595                        (Nkind (Parent (Nam)) = N_Expanded_Name
4596                          and then In_Defining_Unit_Name (Parent (Nam))));
4597      end In_Defining_Unit_Name;
4598
4599   --  Start of processing for Copy_Generic_Node
4600
4601   begin
4602      if N = Empty then
4603         return N;
4604      end if;
4605
4606      New_N := New_Copy (N);
4607
4608      if Instantiating then
4609         Adjust_Instantiation_Sloc (New_N, S_Adjustment);
4610      end if;
4611
4612      if not Is_List_Member (N) then
4613         Set_Parent (New_N, Parent_Id);
4614      end if;
4615
4616      --  If defining identifier, then all fields have been copied already
4617
4618      if Nkind (New_N) in N_Entity then
4619         null;
4620
4621      --  Special casing for identifiers and other entity names and operators
4622
4623      elsif     Nkind (New_N) = N_Identifier
4624        or else Nkind (New_N) = N_Character_Literal
4625        or else Nkind (New_N) = N_Expanded_Name
4626        or else Nkind (New_N) = N_Operator_Symbol
4627        or else Nkind (New_N) in N_Op
4628      then
4629         if not Instantiating then
4630
4631            --  Link both nodes in order to assign subsequently the
4632            --  entity of the copy to the original node, in case this
4633            --  is a global reference.
4634
4635            Set_Associated_Node (N, New_N);
4636
4637            --  If we are within an instantiation, this is a nested generic
4638            --  that has already been analyzed at the point of definition. We
4639            --  must preserve references that were global to the enclosing
4640            --  parent at that point. Other occurrences, whether global or
4641            --  local to the current generic, must be resolved anew, so we
4642            --  reset the entity in the generic copy. A global reference has
4643            --  a smaller depth than the parent, or else the same depth in
4644            --  case both are distinct compilation units.
4645
4646            --  It is also possible for Current_Instantiated_Parent to be
4647            --  defined, and for this not to be a nested generic, namely
4648            --  if the unit is loaded through Rtsfind. In that case, the
4649            --  entity of New_N is only a link to the associated node, and
4650            --  not a defining occurrence.
4651
4652            --  The entities for parent units in the defining_program_unit
4653            --  of a generic child unit are established when the context of
4654            --  the unit is first analyzed, before the generic copy is made.
4655            --  They are preserved in the copy for use in ASIS queries.
4656
4657            Ent := Entity (New_N);
4658
4659            if No (Current_Instantiated_Parent.Gen_Id) then
4660               if No (Ent)
4661                 or else Nkind (Ent) /= N_Defining_Identifier
4662                 or else not In_Defining_Unit_Name (N)
4663               then
4664                  Set_Associated_Node (New_N, Empty);
4665               end if;
4666
4667            elsif No (Ent)
4668              or else
4669                not (Nkind (Ent) = N_Defining_Identifier
4670                       or else
4671                     Nkind (Ent) = N_Defining_Character_Literal
4672                       or else
4673                     Nkind (Ent) = N_Defining_Operator_Symbol)
4674              or else No (Scope (Ent))
4675              or else Scope (Ent) = Current_Instantiated_Parent.Gen_Id
4676              or else (Scope_Depth (Scope (Ent)) >
4677                             Scope_Depth (Current_Instantiated_Parent.Gen_Id)
4678                         and then
4679                       Get_Source_Unit (Ent) =
4680                       Get_Source_Unit (Current_Instantiated_Parent.Gen_Id))
4681            then
4682               Set_Associated_Node (New_N, Empty);
4683            end if;
4684
4685         --  Case of instantiating identifier or some other name or operator
4686
4687         else
4688            --  If the associated node is still defined, the entity in
4689            --  it is global, and must be copied to the instance.
4690            --  If this copy is being made for a body to inline, it is
4691            --  applied to an instantiated tree, and the entity is already
4692            --  present and must be also preserved.
4693
4694            declare
4695               Assoc : constant Node_Id := Get_Associated_Node (N);
4696            begin
4697               if Present (Assoc) then
4698                  if Nkind (Assoc) = Nkind (N) then
4699                     Set_Entity (New_N, Entity (Assoc));
4700                     Check_Private_View (N);
4701
4702                  elsif Nkind (Assoc) = N_Function_Call then
4703                     Set_Entity (New_N, Entity (Name (Assoc)));
4704
4705                  elsif (Nkind (Assoc) = N_Defining_Identifier
4706                          or else Nkind (Assoc) = N_Defining_Character_Literal
4707                          or else Nkind (Assoc) = N_Defining_Operator_Symbol)
4708                    and then Expander_Active
4709                  then
4710                     --  Inlining case: we are copying a tree that contains
4711                     --  global entities, which are preserved in the copy
4712                     --  to be used for subsequent inlining.
4713
4714                     null;
4715
4716                  else
4717                     Set_Entity (New_N, Empty);
4718                  end if;
4719               end if;
4720            end;
4721         end if;
4722
4723         --  For expanded name, we must copy the Prefix and Selector_Name
4724
4725         if Nkind (N) = N_Expanded_Name then
4726            Set_Prefix
4727              (New_N, Copy_Generic_Node (Prefix (N), New_N, Instantiating));
4728
4729            Set_Selector_Name (New_N,
4730              Copy_Generic_Node (Selector_Name (N), New_N, Instantiating));
4731
4732         --  For operators, we must copy the right operand
4733
4734         elsif Nkind (N) in N_Op then
4735            Set_Right_Opnd (New_N,
4736              Copy_Generic_Node (Right_Opnd (N), New_N, Instantiating));
4737
4738            --  And for binary operators, the left operand as well
4739
4740            if Nkind (N) in N_Binary_Op then
4741               Set_Left_Opnd (New_N,
4742                 Copy_Generic_Node (Left_Opnd (N), New_N, Instantiating));
4743            end if;
4744         end if;
4745
4746      --  Special casing for stubs
4747
4748      elsif Nkind (N) in N_Body_Stub then
4749
4750         --  In any case, we must copy the specification or defining
4751         --  identifier as appropriate.
4752
4753         if Nkind (N) = N_Subprogram_Body_Stub then
4754            Set_Specification (New_N,
4755              Copy_Generic_Node (Specification (N), New_N, Instantiating));
4756
4757         else
4758            Set_Defining_Identifier (New_N,
4759              Copy_Generic_Node
4760                (Defining_Identifier (N), New_N, Instantiating));
4761         end if;
4762
4763         --  If we are not instantiating, then this is where we load and
4764         --  analyze subunits, i.e. at the point where the stub occurs. A
4765         --  more permissivle system might defer this analysis to the point
4766         --  of instantiation, but this seems to complicated for now.
4767
4768         if not Instantiating then
4769            declare
4770               Subunit_Name : constant Unit_Name_Type := Get_Unit_Name (N);
4771               Subunit      : Node_Id;
4772               Unum         : Unit_Number_Type;
4773               New_Body     : Node_Id;
4774
4775            begin
4776               Unum :=
4777                 Load_Unit
4778                   (Load_Name  => Subunit_Name,
4779                    Required   => False,
4780                    Subunit    => True,
4781                    Error_Node => N);
4782
4783               --  If the proper body is not found, a warning message will
4784               --  be emitted when analyzing the stub, or later at the the
4785               --  point of instantiation. Here we just leave the stub as is.
4786
4787               if Unum = No_Unit then
4788                  Subunits_Missing := True;
4789                  goto Subunit_Not_Found;
4790               end if;
4791
4792               Subunit := Cunit (Unum);
4793
4794               if Nkind (Unit (Subunit)) /= N_Subunit then
4795                  Error_Msg_Sloc := Sloc (N);
4796                  Error_Msg_N
4797                    ("expected SEPARATE subunit to complete stub at#,"
4798                       & " found child unit", Subunit);
4799                  goto Subunit_Not_Found;
4800               end if;
4801
4802               --  We must create a generic copy of the subunit, in order
4803               --  to perform semantic analysis on it, and we must replace
4804               --  the stub in the original generic unit with the subunit,
4805               --  in order to preserve non-local references within.
4806
4807               --  Only the proper body needs to be copied. Library_Unit and
4808               --  context clause are simply inherited by the generic copy.
4809               --  Note that the copy (which may be recursive if there are
4810               --  nested subunits) must be done first, before attaching it
4811               --  to the enclosing generic.
4812
4813               New_Body :=
4814                 Copy_Generic_Node
4815                   (Proper_Body (Unit (Subunit)),
4816                    Empty, Instantiating => False);
4817
4818               --  Now place the original proper body in the original
4819               --  generic unit. This is a body, not a compilation unit.
4820
4821               Rewrite (N, Proper_Body (Unit (Subunit)));
4822               Set_Is_Compilation_Unit (Defining_Entity (N), False);
4823               Set_Was_Originally_Stub (N);
4824
4825               --  Finally replace the body of the subunit with its copy,
4826               --  and make this new subunit into the library unit of the
4827               --  generic copy, which does not have stubs any longer.
4828
4829               Set_Proper_Body (Unit (Subunit), New_Body);
4830               Set_Library_Unit (New_N, Subunit);
4831               Inherit_Context (Unit (Subunit), N);
4832            end;
4833
4834         --  If we are instantiating, this must be an error case, since
4835         --  otherwise we would have replaced the stub node by the proper
4836         --  body that corresponds. So just ignore it in the copy (i.e.
4837         --  we have copied it, and that is good enough).
4838
4839         else
4840            null;
4841         end if;
4842
4843         <<Subunit_Not_Found>> null;
4844
4845      --  If the node is a compilation unit, it is the subunit of a stub,
4846      --  which has been loaded already (see code below). In this case,
4847      --  the library unit field of N points to the parent unit (which
4848      --  is a compilation unit) and need not (and cannot!) be copied.
4849
4850      --  When the proper body of the stub is analyzed, thie library_unit
4851      --  link is used to establish the proper context (see sem_ch10).
4852
4853      --  The other fields of a compilation unit are copied as usual
4854
4855      elsif Nkind (N) = N_Compilation_Unit then
4856
4857         --  This code can only be executed when not instantiating, because
4858         --  in the copy made for an instantiation, the compilation unit
4859         --  node has disappeared at the point that a stub is replaced by
4860         --  its proper body.
4861
4862         pragma Assert (not Instantiating);
4863
4864         Set_Context_Items (New_N,
4865           Copy_Generic_List (Context_Items (N), New_N));
4866
4867         Set_Unit (New_N,
4868           Copy_Generic_Node (Unit (N), New_N, False));
4869
4870         Set_First_Inlined_Subprogram (New_N,
4871           Copy_Generic_Node
4872             (First_Inlined_Subprogram (N), New_N, False));
4873
4874         Set_Aux_Decls_Node (New_N,
4875           Copy_Generic_Node (Aux_Decls_Node (N), New_N, False));
4876
4877      --  For an assignment node, the assignment is known to be semantically
4878      --  legal if we are instantiating the template. This avoids incorrect
4879      --  diagnostics in generated code.
4880
4881      elsif Nkind (N) = N_Assignment_Statement then
4882
4883         --  Copy name and expression fields in usual manner
4884
4885         Set_Name (New_N,
4886           Copy_Generic_Node (Name (N), New_N, Instantiating));
4887
4888         Set_Expression (New_N,
4889           Copy_Generic_Node (Expression (N), New_N, Instantiating));
4890
4891         if Instantiating then
4892            Set_Assignment_OK (Name (New_N), True);
4893         end if;
4894
4895      elsif Nkind (N) = N_Aggregate
4896              or else Nkind (N) = N_Extension_Aggregate
4897      then
4898
4899         if not Instantiating then
4900            Set_Associated_Node (N, New_N);
4901
4902         else
4903            if Present (Get_Associated_Node (N))
4904              and then Nkind (Get_Associated_Node (N)) = Nkind (N)
4905            then
4906               --  In the generic the aggregate has some composite type. If at
4907               --  the point of instantiation the type has a private view,
4908               --  install the full view (and that of its ancestors, if any).
4909
4910               declare
4911                  T   : Entity_Id := (Etype (Get_Associated_Node (New_N)));
4912                  Rt  : Entity_Id;
4913
4914               begin
4915                  if Present (T)
4916                    and then Is_Private_Type (T)
4917                  then
4918                     Switch_View (T);
4919                  end if;
4920
4921                  if Present (T)
4922                    and then Is_Tagged_Type (T)
4923                    and then Is_Derived_Type (T)
4924                  then
4925                     Rt := Root_Type (T);
4926
4927                     loop
4928                        T := Etype (T);
4929
4930                        if Is_Private_Type (T) then
4931                           Switch_View (T);
4932                        end if;
4933
4934                        exit when T = Rt;
4935                     end loop;
4936                  end if;
4937               end;
4938            end if;
4939         end if;
4940
4941         --  Do not copy the associated node, which points to
4942         --  the generic copy of the aggregate.
4943
4944         declare
4945            use Atree.Unchecked_Access;
4946            --  This code section is part of the implementation of an untyped
4947            --  tree traversal, so it needs direct access to node fields.
4948
4949         begin
4950            Set_Field1 (New_N, Copy_Generic_Descendant (Field1 (N)));
4951            Set_Field2 (New_N, Copy_Generic_Descendant (Field2 (N)));
4952            Set_Field3 (New_N, Copy_Generic_Descendant (Field3 (N)));
4953            Set_Field5 (New_N, Copy_Generic_Descendant (Field5 (N)));
4954         end;
4955
4956      --  Allocators do not have an identifier denoting the access type,
4957      --  so we must locate it through the expression to check whether
4958      --  the views are consistent.
4959
4960      elsif Nkind (N) = N_Allocator
4961        and then Nkind (Expression (N)) = N_Qualified_Expression
4962        and then Is_Entity_Name (Subtype_Mark (Expression (N)))
4963        and then Instantiating
4964      then
4965         declare
4966            T     : constant Node_Id :=
4967                      Get_Associated_Node (Subtype_Mark (Expression (N)));
4968            Acc_T : Entity_Id;
4969
4970         begin
4971            if Present (T) then
4972               --  Retrieve the allocator node in the generic copy.
4973
4974               Acc_T := Etype (Parent (Parent (T)));
4975               if Present (Acc_T)
4976                 and then Is_Private_Type (Acc_T)
4977               then
4978                  Switch_View (Acc_T);
4979               end if;
4980            end if;
4981
4982            Copy_Descendants;
4983         end;
4984
4985      --  For a proper body, we must catch the case of a proper body that
4986      --  replaces a stub. This represents the point at which a separate
4987      --  compilation unit, and hence template file, may be referenced, so
4988      --  we must make a new source instantiation entry for the template
4989      --  of the subunit, and ensure that all nodes in the subunit are
4990      --  adjusted using this new source instantiation entry.
4991
4992      elsif Nkind (N) in N_Proper_Body then
4993         declare
4994            Save_Adjustment : constant Sloc_Adjustment := S_Adjustment;
4995
4996         begin
4997            if Instantiating and then Was_Originally_Stub (N) then
4998               Create_Instantiation_Source
4999                 (Instantiation_Node,
5000                  Defining_Entity (N),
5001                  False,
5002                  S_Adjustment);
5003            end if;
5004
5005            --  Now copy the fields of the proper body, using the new
5006            --  adjustment factor if one was needed as per test above.
5007
5008            Copy_Descendants;
5009
5010            --  Restore the original adjustment factor in case changed
5011
5012            S_Adjustment := Save_Adjustment;
5013         end;
5014
5015      --  Don't copy Ident or Comment pragmas, since the comment belongs
5016      --  to the generic unit, not to the instantiating unit.
5017
5018      elsif Nkind (N) = N_Pragma
5019        and then Instantiating
5020      then
5021         declare
5022            Prag_Id : constant Pragma_Id := Get_Pragma_Id (Chars (N));
5023
5024         begin
5025            if Prag_Id = Pragma_Ident
5026              or else Prag_Id = Pragma_Comment
5027            then
5028               New_N := Make_Null_Statement (Sloc (N));
5029
5030            else
5031               Copy_Descendants;
5032            end if;
5033         end;
5034
5035      elsif Nkind (N) = N_Integer_Literal
5036        or else Nkind (N) = N_Real_Literal
5037      then
5038         --  No descendant fields need traversing
5039
5040         null;
5041
5042      --  For the remaining nodes, copy recursively their descendants
5043
5044      else
5045         Copy_Descendants;
5046
5047         if Instantiating
5048           and then Nkind (N) = N_Subprogram_Body
5049         then
5050            Set_Generic_Parent (Specification (New_N), N);
5051         end if;
5052      end if;
5053
5054      return New_N;
5055   end Copy_Generic_Node;
5056
5057   ----------------------------
5058   -- Denotes_Formal_Package --
5059   ----------------------------
5060
5061   function Denotes_Formal_Package (Pack : Entity_Id) return Boolean is
5062      Par  : constant Entity_Id := Current_Instantiated_Parent.Act_Id;
5063      Scop : constant Entity_Id := Scope (Pack);
5064      E    : Entity_Id;
5065
5066   begin
5067      if Ekind (Scop) = E_Generic_Package
5068        or else Nkind (Unit_Declaration_Node (Scop)) =
5069                                         N_Generic_Subprogram_Declaration
5070      then
5071         return True;
5072
5073      elsif Nkind (Parent (Pack)) = N_Formal_Package_Declaration then
5074         return True;
5075
5076      elsif No (Par) then
5077         return False;
5078
5079      else
5080         --  Check whether this package is associated with a formal
5081         --  package of the enclosing instantiation. Iterate over the
5082         --  list of renamings.
5083
5084         E := First_Entity (Par);
5085         while Present (E) loop
5086            if Ekind (E) /= E_Package
5087              or else Nkind (Parent (E)) /= N_Package_Renaming_Declaration
5088            then
5089               null;
5090            elsif Renamed_Object (E) = Par then
5091               return False;
5092
5093            elsif Renamed_Object (E) = Pack then
5094               return True;
5095            end if;
5096
5097            Next_Entity (E);
5098         end loop;
5099
5100         return False;
5101      end if;
5102   end Denotes_Formal_Package;
5103
5104   -----------------
5105   -- End_Generic --
5106   -----------------
5107
5108   procedure End_Generic is
5109   begin
5110      --  ??? More things could be factored out in this
5111      --  routine. Should probably be done at a later stage.
5112
5113      Inside_A_Generic := Generic_Flags.Table (Generic_Flags.Last);
5114      Generic_Flags.Decrement_Last;
5115
5116      Expander_Mode_Restore;
5117   end End_Generic;
5118
5119   ----------------------
5120   -- Find_Actual_Type --
5121   ----------------------
5122
5123   function Find_Actual_Type
5124     (Typ       : Entity_Id;
5125      Gen_Scope : Entity_Id)
5126      return      Entity_Id
5127   is
5128      T : Entity_Id;
5129
5130   begin
5131      if not Is_Child_Unit (Gen_Scope) then
5132         return Get_Instance_Of (Typ);
5133
5134      elsif not Is_Generic_Type (Typ)
5135        or else Scope (Typ) = Gen_Scope
5136      then
5137         return Get_Instance_Of (Typ);
5138
5139      else
5140         T := Current_Entity (Typ);
5141         while Present (T) loop
5142            if In_Open_Scopes (Scope (T)) then
5143               return T;
5144            end if;
5145
5146            T := Homonym (T);
5147         end loop;
5148
5149         return Typ;
5150      end if;
5151   end Find_Actual_Type;
5152
5153   ----------------------------
5154   -- Freeze_Subprogram_Body --
5155   ----------------------------
5156
5157   procedure Freeze_Subprogram_Body
5158     (Inst_Node : Node_Id;
5159      Gen_Body  : Node_Id;
5160      Pack_Id   : Entity_Id)
5161  is
5162      F_Node   : Node_Id;
5163      Gen_Unit : constant Entity_Id := Get_Generic_Entity (Inst_Node);
5164      Par      : constant Entity_Id := Scope (Gen_Unit);
5165      Enc_G    : Entity_Id;
5166      Enc_I    : Node_Id;
5167      E_G_Id   : Entity_Id;
5168
5169      function Earlier (N1, N2 : Node_Id) return Boolean;
5170      --  Yields True if N1 and N2 appear in the same compilation unit,
5171      --  ignoring subunits, and if N1 is to the left of N2 in a left-to-right
5172      --  traversal of the tree for the unit.
5173
5174      function Enclosing_Body (N : Node_Id) return Node_Id;
5175      --  Find innermost package body that encloses the given node, and which
5176      --  is not a compilation unit. Freeze nodes for the instance, or for its
5177      --  enclosing body, may be inserted after the enclosing_body of the
5178      --  generic unit.
5179
5180      function Package_Freeze_Node (B : Node_Id) return Node_Id;
5181      --  Find entity for given package body, and locate or create a freeze
5182      --  node for it.
5183
5184      function True_Parent (N : Node_Id) return Node_Id;
5185      --  For a subunit, return parent of corresponding stub.
5186
5187      -------------
5188      -- Earlier --
5189      -------------
5190
5191      function Earlier (N1, N2 : Node_Id) return Boolean is
5192         D1 : Integer := 0;
5193         D2 : Integer := 0;
5194         P1 : Node_Id := N1;
5195         P2 : Node_Id := N2;
5196
5197         procedure Find_Depth (P : in out Node_Id; D : in out Integer);
5198         --  Find distance from given node to enclosing compilation unit.
5199
5200         ----------------
5201         -- Find_Depth --
5202         ----------------
5203
5204         procedure Find_Depth (P : in out Node_Id; D : in out Integer) is
5205         begin
5206            while Present (P)
5207              and then Nkind (P) /= N_Compilation_Unit
5208            loop
5209               P := True_Parent (P);
5210               D := D + 1;
5211            end loop;
5212         end Find_Depth;
5213
5214      --  Start of procesing for Earlier
5215
5216      begin
5217         Find_Depth (P1, D1);
5218         Find_Depth (P2, D2);
5219
5220         if P1 /= P2 then
5221            return False;
5222         else
5223            P1 := N1;
5224            P2 := N2;
5225         end if;
5226
5227         while D1 > D2 loop
5228            P1 := True_Parent (P1);
5229            D1 := D1 - 1;
5230         end loop;
5231
5232         while D2 > D1 loop
5233            P2 := True_Parent (P2);
5234            D2 := D2 - 1;
5235         end loop;
5236
5237         --  At this point P1 and P2 are at the same distance from the root.
5238         --  We examine their parents until we find a common declarative
5239         --  list, at which point we can establish their relative placement
5240         --  by comparing their ultimate slocs. If we reach the root,
5241         --  N1 and N2 do not descend from the same declarative list (e.g.
5242         --  one is nested in the declarative part and the other is in a block
5243         --  in the statement part) and the earlier one is already frozen.
5244
5245         while not Is_List_Member (P1)
5246           or else not Is_List_Member (P2)
5247           or else List_Containing (P1) /= List_Containing (P2)
5248         loop
5249            P1 := True_Parent (P1);
5250            P2 := True_Parent (P2);
5251
5252            if Nkind (Parent (P1)) = N_Subunit then
5253               P1 := Corresponding_Stub (Parent (P1));
5254            end if;
5255
5256            if Nkind (Parent (P2)) = N_Subunit then
5257               P2 := Corresponding_Stub (Parent (P2));
5258            end if;
5259
5260            if P1 = P2 then
5261               return False;
5262            end if;
5263         end loop;
5264
5265         return
5266           Top_Level_Location (Sloc (P1)) < Top_Level_Location (Sloc (P2));
5267      end Earlier;
5268
5269      --------------------
5270      -- Enclosing_Body --
5271      --------------------
5272
5273      function Enclosing_Body (N : Node_Id) return Node_Id is
5274         P : Node_Id := Parent (N);
5275
5276      begin
5277         while Present (P)
5278           and then Nkind (Parent (P)) /= N_Compilation_Unit
5279         loop
5280            if Nkind (P) = N_Package_Body then
5281
5282               if Nkind (Parent (P)) = N_Subunit then
5283                  return Corresponding_Stub (Parent (P));
5284               else
5285                  return P;
5286               end if;
5287            end if;
5288
5289            P := True_Parent (P);
5290         end loop;
5291
5292         return Empty;
5293      end Enclosing_Body;
5294
5295      -------------------------
5296      -- Package_Freeze_Node --
5297      -------------------------
5298
5299      function Package_Freeze_Node (B : Node_Id) return Node_Id is
5300         Id : Entity_Id;
5301
5302      begin
5303         if Nkind (B) = N_Package_Body then
5304            Id := Corresponding_Spec (B);
5305
5306         else pragma Assert (Nkind (B) = N_Package_Body_Stub);
5307            Id := Corresponding_Spec (Proper_Body (Unit (Library_Unit (B))));
5308         end if;
5309
5310         Ensure_Freeze_Node (Id);
5311         return Freeze_Node (Id);
5312      end Package_Freeze_Node;
5313
5314      -----------------
5315      -- True_Parent --
5316      -----------------
5317
5318      function True_Parent (N : Node_Id) return Node_Id is
5319      begin
5320         if Nkind (Parent (N)) = N_Subunit then
5321            return Parent (Corresponding_Stub (Parent (N)));
5322         else
5323            return Parent (N);
5324         end if;
5325      end True_Parent;
5326
5327   --  Start of processing of Freeze_Subprogram_Body
5328
5329   begin
5330      --  If the instance and the generic body appear within the same
5331      --  unit, and the instance preceeds the generic, the freeze node for
5332      --  the instance must appear after that of the generic. If the generic
5333      --  is nested within another instance I2, then current instance must
5334      --  be frozen after I2. In both cases, the freeze nodes are those of
5335      --  enclosing packages. Otherwise, the freeze node is placed at the end
5336      --  of the current declarative part.
5337
5338      Enc_G  := Enclosing_Body (Gen_Body);
5339      Enc_I  := Enclosing_Body (Inst_Node);
5340      Ensure_Freeze_Node (Pack_Id);
5341      F_Node := Freeze_Node (Pack_Id);
5342
5343      if Is_Generic_Instance (Par)
5344        and then Present (Freeze_Node (Par))
5345        and then
5346          In_Same_Declarative_Part (Freeze_Node (Par), Inst_Node)
5347      then
5348         if ABE_Is_Certain (Get_Package_Instantiation_Node (Par)) then
5349
5350            --  The parent was a premature instantiation. Insert freeze
5351            --  node at the end the current declarative part.
5352
5353            Insert_After_Last_Decl (Inst_Node, F_Node);
5354
5355         else
5356            Insert_After (Freeze_Node (Par), F_Node);
5357         end if;
5358
5359      --  The body enclosing the instance should be frozen after the body
5360      --  that includes the generic, because the body of the instance may
5361      --  make references to entities therein. If the two are not in the
5362      --  same declarative part, or if the one enclosing the instance is
5363      --  frozen already, freeze the instance at the end of the current
5364      --  declarative part.
5365
5366      elsif Is_Generic_Instance (Par)
5367        and then Present (Freeze_Node (Par))
5368        and then Present (Enc_I)
5369      then
5370         if In_Same_Declarative_Part (Freeze_Node (Par), Enc_I)
5371           or else
5372             (Nkind (Enc_I) = N_Package_Body
5373               and then
5374             In_Same_Declarative_Part (Freeze_Node (Par), Parent (Enc_I)))
5375         then
5376            --  The enclosing package may contain several instances. Rather
5377            --  than computing the earliest point at which to insert its
5378            --  freeze node, we place it at the end of the declarative part
5379            --  of the parent of the generic.
5380
5381            Insert_After_Last_Decl
5382              (Freeze_Node (Par), Package_Freeze_Node (Enc_I));
5383         end if;
5384
5385         Insert_After_Last_Decl (Inst_Node, F_Node);
5386
5387      elsif Present (Enc_G)
5388        and then Present (Enc_I)
5389        and then Enc_G /= Enc_I
5390        and then Earlier (Inst_Node, Gen_Body)
5391      then
5392         if Nkind (Enc_G) = N_Package_Body then
5393            E_G_Id := Corresponding_Spec (Enc_G);
5394         else pragma Assert (Nkind (Enc_G) = N_Package_Body_Stub);
5395            E_G_Id :=
5396              Corresponding_Spec (Proper_Body (Unit (Library_Unit (Enc_G))));
5397         end if;
5398
5399         --  Freeze package that encloses instance, and place node after
5400         --  package that encloses generic. If enclosing package is already
5401         --  frozen we have to assume it is at the proper place. This may
5402         --  be a potential ABE that requires dynamic checking.
5403
5404         Insert_After_Last_Decl (Enc_G, Package_Freeze_Node (Enc_I));
5405
5406         --  Freeze enclosing subunit before instance
5407
5408         Ensure_Freeze_Node (E_G_Id);
5409
5410         if not Is_List_Member (Freeze_Node (E_G_Id)) then
5411            Insert_After (Enc_G, Freeze_Node (E_G_Id));
5412         end if;
5413
5414         Insert_After_Last_Decl (Inst_Node, F_Node);
5415
5416      else
5417         --  If none of the above, insert freeze node at the end of the
5418         --  current declarative part.
5419
5420         Insert_After_Last_Decl (Inst_Node, F_Node);
5421      end if;
5422   end Freeze_Subprogram_Body;
5423
5424   ----------------
5425   -- Get_Gen_Id --
5426   ----------------
5427
5428   function Get_Gen_Id (E : Assoc_Ptr) return Entity_Id is
5429   begin
5430      return Generic_Renamings.Table (E).Gen_Id;
5431   end Get_Gen_Id;
5432
5433   ---------------------
5434   -- Get_Instance_Of --
5435   ---------------------
5436
5437   function Get_Instance_Of (A : Entity_Id) return Entity_Id is
5438      Res : constant Assoc_Ptr := Generic_Renamings_HTable.Get (A);
5439
5440   begin
5441      if Res /= Assoc_Null then
5442         return Generic_Renamings.Table (Res).Act_Id;
5443      else
5444         --  On exit, entity is not instantiated: not a generic parameter,
5445         --  or else parameter of an inner generic unit.
5446
5447         return A;
5448      end if;
5449   end Get_Instance_Of;
5450
5451   ------------------------------------
5452   -- Get_Package_Instantiation_Node --
5453   ------------------------------------
5454
5455   function Get_Package_Instantiation_Node (A : Entity_Id) return Node_Id is
5456      Decl : Node_Id := Unit_Declaration_Node (A);
5457      Inst : Node_Id;
5458
5459   begin
5460      --  If the instantiation is a compilation unit that does not need a
5461      --  body then the instantiation node has been rewritten as a package
5462      --  declaration for the instance, and we return the original node.
5463
5464      --  If it is a compilation unit and the instance node has not been
5465      --  rewritten, then it is still the unit of the compilation. Finally,
5466      --  if a body is present, this is a parent of the main unit whose body
5467      --  has been compiled for inlining purposes, and the instantiation node
5468      --  has been rewritten with the instance body.
5469
5470      --  Otherwise the instantiation node appears after the declaration.
5471      --  If the entity is a formal package, the declaration may have been
5472      --  rewritten as a generic declaration (in the case of a formal with a
5473      --  box) or left as a formal package declaration if it has actuals, and
5474      --  is found with a forward search.
5475
5476      if Nkind (Parent (Decl)) = N_Compilation_Unit then
5477         if Nkind (Decl) = N_Package_Declaration
5478           and then Present (Corresponding_Body (Decl))
5479         then
5480            Decl := Unit_Declaration_Node (Corresponding_Body (Decl));
5481         end if;
5482
5483         if Nkind (Original_Node (Decl)) = N_Package_Instantiation then
5484            return Original_Node (Decl);
5485         else
5486            return Unit (Parent (Decl));
5487         end if;
5488
5489      elsif Nkind (Decl) = N_Generic_Package_Declaration
5490        and then Nkind (Original_Node (Decl)) = N_Formal_Package_Declaration
5491      then
5492         return Original_Node (Decl);
5493
5494      else
5495         Inst := Next (Decl);
5496         while Nkind (Inst) /= N_Package_Instantiation
5497           and then Nkind (Inst) /= N_Formal_Package_Declaration
5498         loop
5499            Next (Inst);
5500         end loop;
5501
5502         return Inst;
5503      end if;
5504   end Get_Package_Instantiation_Node;
5505
5506   ------------------------
5507   -- Has_Been_Exchanged --
5508   ------------------------
5509
5510   function Has_Been_Exchanged (E : Entity_Id) return Boolean is
5511      Next : Elmt_Id := First_Elmt (Exchanged_Views);
5512
5513   begin
5514      while Present (Next) loop
5515         if Full_View (Node (Next)) = E then
5516            return True;
5517         end if;
5518
5519         Next_Elmt (Next);
5520      end loop;
5521
5522      return False;
5523   end Has_Been_Exchanged;
5524
5525   ----------
5526   -- Hash --
5527   ----------
5528
5529   function Hash (F : Entity_Id) return HTable_Range is
5530   begin
5531      return HTable_Range (F mod HTable_Size);
5532   end Hash;
5533
5534   ------------------------
5535   -- Hide_Current_Scope --
5536   ------------------------
5537
5538   procedure Hide_Current_Scope is
5539      C : constant Entity_Id := Current_Scope;
5540      E : Entity_Id;
5541
5542   begin
5543      Set_Is_Hidden_Open_Scope (C);
5544      E := First_Entity (C);
5545
5546      while Present (E) loop
5547         if Is_Immediately_Visible (E) then
5548            Set_Is_Immediately_Visible (E, False);
5549            Append_Elmt (E, Hidden_Entities);
5550         end if;
5551
5552         Next_Entity (E);
5553      end loop;
5554
5555      --  Make the scope name invisible as well. This is necessary, but
5556      --  might conflict with calls to Rtsfind later on, in case the scope
5557      --  is a predefined one. There is no clean solution to this problem, so
5558      --  for now we depend on the user not redefining Standard itself in one
5559      --  of the parent units.
5560
5561      if Is_Immediately_Visible (C)
5562        and then C /= Standard_Standard
5563      then
5564         Set_Is_Immediately_Visible (C, False);
5565         Append_Elmt (C, Hidden_Entities);
5566      end if;
5567
5568   end Hide_Current_Scope;
5569
5570   --------------
5571   -- Init_Env --
5572   --------------
5573
5574   procedure Init_Env is
5575      Saved : Instance_Env;
5576
5577   begin
5578      Saved.Ada_83              := Ada_83;
5579      Saved.Instantiated_Parent := Current_Instantiated_Parent;
5580      Saved.Exchanged_Views     := Exchanged_Views;
5581      Saved.Hidden_Entities     := Hidden_Entities;
5582      Saved.Current_Sem_Unit    := Current_Sem_Unit;
5583      Instance_Envs.Increment_Last;
5584      Instance_Envs.Table (Instance_Envs.Last) := Saved;
5585
5586      Exchanged_Views := New_Elmt_List;
5587      Hidden_Entities := New_Elmt_List;
5588
5589      --  Make dummy entry for Instantiated parent. If generic unit is
5590      --  legal, this is set properly in Set_Instance_Env.
5591
5592      Current_Instantiated_Parent :=
5593        (Current_Scope, Current_Scope, Assoc_Null);
5594   end Init_Env;
5595
5596   ------------------------------
5597   -- In_Same_Declarative_Part --
5598   ------------------------------
5599
5600   function In_Same_Declarative_Part
5601     (F_Node : Node_Id;
5602      Inst   : Node_Id)
5603      return   Boolean
5604   is
5605      Decls : constant Node_Id := Parent (F_Node);
5606      Nod   : Node_Id := Parent (Inst);
5607
5608   begin
5609      while Present (Nod) loop
5610         if Nod = Decls then
5611            return True;
5612
5613         elsif Nkind (Nod) = N_Subprogram_Body
5614           or else Nkind (Nod) = N_Package_Body
5615           or else Nkind (Nod) = N_Task_Body
5616           or else Nkind (Nod) = N_Protected_Body
5617           or else Nkind (Nod) = N_Block_Statement
5618         then
5619            return False;
5620
5621         elsif Nkind (Nod) = N_Subunit then
5622            Nod :=  Corresponding_Stub (Nod);
5623
5624         elsif Nkind (Nod) = N_Compilation_Unit then
5625            return False;
5626         else
5627            Nod := Parent (Nod);
5628         end if;
5629      end loop;
5630
5631      return False;
5632   end In_Same_Declarative_Part;
5633
5634   ---------------------
5635   -- Inherit_Context --
5636   ---------------------
5637
5638   procedure Inherit_Context (Gen_Decl : Node_Id; Inst : Node_Id) is
5639      Current_Context : List_Id;
5640      Current_Unit    : Node_Id;
5641      Item            : Node_Id;
5642      New_I           : Node_Id;
5643
5644   begin
5645      if Nkind (Parent (Gen_Decl)) = N_Compilation_Unit then
5646
5647         --  The inherited context is attached to the enclosing compilation
5648         --  unit. This is either the main unit, or the declaration for the
5649         --  main unit (in case the instantation appears within the package
5650         --  declaration and the main unit is its body).
5651
5652         Current_Unit := Parent (Inst);
5653         while Present (Current_Unit)
5654           and then Nkind (Current_Unit) /= N_Compilation_Unit
5655         loop
5656            Current_Unit := Parent (Current_Unit);
5657         end loop;
5658
5659         Current_Context := Context_Items (Current_Unit);
5660
5661         Item := First (Context_Items (Parent (Gen_Decl)));
5662         while Present (Item) loop
5663            if Nkind (Item) = N_With_Clause then
5664               New_I := New_Copy (Item);
5665               Set_Implicit_With (New_I, True);
5666               Append (New_I, Current_Context);
5667            end if;
5668
5669            Next (Item);
5670         end loop;
5671      end if;
5672   end Inherit_Context;
5673
5674   ----------------
5675   -- Initialize --
5676   ----------------
5677
5678   procedure Initialize is
5679   begin
5680      Generic_Renamings.Init;
5681      Instance_Envs.Init;
5682      Generic_Flags.Init;
5683      Generic_Renamings_HTable.Reset;
5684      Circularity_Detected := False;
5685      Exchanged_Views      := No_Elist;
5686      Hidden_Entities      := No_Elist;
5687   end Initialize;
5688
5689   ----------------------------
5690   -- Insert_After_Last_Decl --
5691   ----------------------------
5692
5693   procedure Insert_After_Last_Decl (N : Node_Id; F_Node : Node_Id) is
5694      L : List_Id          := List_Containing (N);
5695      P : constant Node_Id := Parent (L);
5696
5697   begin
5698      if not Is_List_Member (F_Node) then
5699         if Nkind (P) = N_Package_Specification
5700           and then L = Visible_Declarations (P)
5701           and then Present (Private_Declarations (P))
5702           and then not Is_Empty_List (Private_Declarations (P))
5703         then
5704            L := Private_Declarations (P);
5705         end if;
5706
5707         Insert_After (Last (L), F_Node);
5708      end if;
5709   end Insert_After_Last_Decl;
5710
5711   ------------------
5712   -- Install_Body --
5713   ------------------
5714
5715   procedure Install_Body
5716     (Act_Body : Node_Id;
5717      N        : Node_Id;
5718      Gen_Body : Node_Id;
5719      Gen_Decl : Node_Id)
5720   is
5721      Act_Id    : constant Entity_Id := Corresponding_Spec (Act_Body);
5722      Act_Unit  : constant Node_Id   := Unit (Cunit (Get_Source_Unit (N)));
5723      Gen_Id    : constant Entity_Id := Corresponding_Spec (Gen_Body);
5724      Par       : constant Entity_Id := Scope (Gen_Id);
5725      Gen_Unit  : constant Node_Id :=
5726                    Unit (Cunit (Get_Source_Unit (Gen_Decl)));
5727      Orig_Body : Node_Id := Gen_Body;
5728      F_Node    : Node_Id;
5729      Body_Unit : Node_Id;
5730
5731      Must_Delay : Boolean;
5732
5733      function Enclosing_Subp (Id : Entity_Id) return Entity_Id;
5734      --  Find subprogram (if any) that encloses instance and/or generic body.
5735
5736      function True_Sloc (N : Node_Id) return Source_Ptr;
5737      --  If the instance is nested inside a generic unit, the Sloc of the
5738      --  instance indicates the place of the original definition, not the
5739      --  point of the current enclosing instance. Pending a better usage of
5740      --  Slocs to indicate instantiation places, we determine the place of
5741      --  origin of a node by finding the maximum sloc of any ancestor node.
5742      --  Why is this not equivalent fo Top_Level_Location ???
5743
5744      function Enclosing_Subp (Id : Entity_Id) return Entity_Id is
5745         Scop : Entity_Id := Scope (Id);
5746
5747      begin
5748         while Scop /= Standard_Standard
5749           and then not Is_Overloadable (Scop)
5750         loop
5751            Scop := Scope (Scop);
5752         end loop;
5753
5754         return Scop;
5755      end Enclosing_Subp;
5756
5757      function True_Sloc (N : Node_Id) return Source_Ptr is
5758         Res : Source_Ptr;
5759         N1  : Node_Id;
5760
5761      begin
5762         Res := Sloc (N);
5763         N1 := N;
5764         while Present (N1) and then N1 /= Act_Unit loop
5765            if Sloc (N1) > Res then
5766               Res := Sloc (N1);
5767            end if;
5768
5769            N1 := Parent (N1);
5770         end loop;
5771
5772         return Res;
5773      end True_Sloc;
5774
5775   --  Start of processing for Install_Body
5776
5777   begin
5778      --  If the body is a subunit, the freeze point is the corresponding
5779      --  stub in the current compilation, not the subunit itself.
5780
5781      if Nkind (Parent (Gen_Body)) = N_Subunit then
5782         Orig_Body :=  Corresponding_Stub (Parent (Gen_Body));
5783      else
5784         Orig_Body := Gen_Body;
5785      end if;
5786
5787      Body_Unit := Unit (Cunit (Get_Source_Unit (Orig_Body)));
5788
5789      --  If the instantiation and the generic definition appear in the
5790      --  same package declaration, this is an early instantiation.
5791      --  If they appear in the same declarative part, it is an early
5792      --  instantiation only if the generic body appears textually later,
5793      --  and the generic body is also in the main unit.
5794
5795      --  If instance is nested within a subprogram, and the generic body is
5796      --  not, the instance is delayed because the enclosing body is. If
5797      --  instance and body are within the same scope, or the same sub-
5798      --  program body, indicate explicitly that the instance is delayed.
5799
5800      Must_Delay :=
5801        (Gen_Unit = Act_Unit
5802          and then ((Nkind (Gen_Unit) = N_Package_Declaration)
5803                      or else Nkind (Gen_Unit) = N_Generic_Package_Declaration
5804                      or else (Gen_Unit = Body_Unit
5805                                and then True_Sloc (N) < Sloc (Orig_Body)))
5806          and then Is_In_Main_Unit (Gen_Unit)
5807          and then (Scope (Act_Id) = Scope (Gen_Id)
5808                      or else
5809                    Enclosing_Subp (Act_Id) = Enclosing_Subp (Gen_Id)));
5810
5811      --  If this is an early instantiation, the freeze node is placed after
5812      --  the generic body. Otherwise, if the generic appears in an instance,
5813      --  we cannot freeze the current instance until the outer one is frozen.
5814      --  This is only relevant if the current instance is nested within some
5815      --  inner scope not itself within the outer instance. If this scope is
5816      --  a package body in the same declarative part as the outer instance,
5817      --  then that body needs to be frozen after the outer instance. Finally,
5818      --  if no delay is needed, we place the freeze node at the end of the
5819      --  current declarative part.
5820
5821      if Expander_Active then
5822         Ensure_Freeze_Node (Act_Id);
5823         F_Node := Freeze_Node (Act_Id);
5824
5825         if Must_Delay then
5826            Insert_After (Orig_Body, F_Node);
5827
5828         elsif Is_Generic_Instance (Par)
5829           and then Present (Freeze_Node (Par))
5830           and then Scope (Act_Id) /= Par
5831         then
5832            --  Freeze instance of inner generic after instance of enclosing
5833            --  generic.
5834
5835            if In_Same_Declarative_Part (Freeze_Node (Par), N) then
5836               Insert_After (Freeze_Node (Par), F_Node);
5837
5838            --  Freeze package enclosing instance of inner generic after
5839            --  instance of enclosing generic.
5840
5841            elsif Nkind (Parent (N)) = N_Package_Body
5842              and then In_Same_Declarative_Part (Freeze_Node (Par), Parent (N))
5843            then
5844
5845               declare
5846                  Enclosing : constant Entity_Id :=
5847                                Corresponding_Spec (Parent (N));
5848
5849               begin
5850                  Insert_After_Last_Decl (N, F_Node);
5851                  Ensure_Freeze_Node (Enclosing);
5852
5853                  if not Is_List_Member (Freeze_Node (Enclosing)) then
5854                     Insert_After (Freeze_Node (Par), Freeze_Node (Enclosing));
5855                  end if;
5856               end;
5857
5858            else
5859               Insert_After_Last_Decl (N, F_Node);
5860            end if;
5861
5862         else
5863            Insert_After_Last_Decl (N, F_Node);
5864         end if;
5865      end if;
5866
5867      Set_Is_Frozen (Act_Id);
5868      Insert_Before (N, Act_Body);
5869      Mark_Rewrite_Insertion (Act_Body);
5870   end Install_Body;
5871
5872   --------------------
5873   -- Install_Parent --
5874   --------------------
5875
5876   procedure Install_Parent (P : Entity_Id; In_Body : Boolean := False) is
5877      Ancestors : constant Elist_Id  := New_Elmt_List;
5878      S         : constant Entity_Id := Current_Scope;
5879      Inst_Par  : Entity_Id;
5880      First_Par : Entity_Id;
5881      Inst_Node : Node_Id;
5882      Gen_Par   : Entity_Id;
5883      First_Gen : Entity_Id;
5884      Elmt      : Elmt_Id;
5885
5886      procedure Install_Formal_Packages (Par : Entity_Id);
5887      --  If any of the formals of the parent are formal packages with box,
5888      --  their formal parts are visible in the parent and thus in the child
5889      --  unit as well. Analogous to what is done in Check_Generic_Actuals
5890      --  for the unit itself.
5891
5892      procedure Install_Noninstance_Specs (Par : Entity_Id);
5893      --  Install the scopes of noninstance parent units ending with Par.
5894
5895      procedure Install_Spec (Par : Entity_Id);
5896      --  The child unit is within the declarative part of the parent, so
5897      --  the declarations within the parent are immediately visible.
5898
5899      -----------------------------
5900      -- Install_Formal_Packages --
5901      -----------------------------
5902
5903      procedure Install_Formal_Packages (Par : Entity_Id) is
5904         E : Entity_Id;
5905
5906      begin
5907         E := First_Entity (Par);
5908
5909         while Present (E) loop
5910
5911            if Ekind (E) = E_Package
5912              and then Nkind (Parent (E)) = N_Package_Renaming_Declaration
5913            then
5914               --  If this is the renaming for the parent instance, done.
5915
5916               if Renamed_Object (E) = Par then
5917                  exit;
5918
5919               --  The visibility of a formal of an enclosing generic is
5920               --  already correct.
5921
5922               elsif Denotes_Formal_Package (E) then
5923                  null;
5924
5925               elsif Present (Associated_Formal_Package (E))
5926                 and then Box_Present (Parent (Associated_Formal_Package (E)))
5927               then
5928                  Check_Generic_Actuals (Renamed_Object (E), True);
5929                  Set_Is_Hidden (E, False);
5930               end if;
5931            end if;
5932
5933            Next_Entity (E);
5934         end loop;
5935      end Install_Formal_Packages;
5936
5937      -------------------------------
5938      -- Install_Noninstance_Specs --
5939      -------------------------------
5940
5941      procedure Install_Noninstance_Specs (Par : Entity_Id) is
5942      begin
5943         if Present (Par)
5944           and then Par /= Standard_Standard
5945           and then not In_Open_Scopes (Par)
5946         then
5947            Install_Noninstance_Specs (Scope (Par));
5948            Install_Spec (Par);
5949         end if;
5950      end Install_Noninstance_Specs;
5951
5952      ------------------
5953      -- Install_Spec --
5954      ------------------
5955
5956      procedure Install_Spec (Par : Entity_Id) is
5957         Spec : constant Node_Id :=
5958                  Specification (Unit_Declaration_Node (Par));
5959
5960      begin
5961         New_Scope (Par);
5962         Set_Is_Immediately_Visible   (Par);
5963         Install_Visible_Declarations (Par);
5964         Install_Private_Declarations (Par);
5965         Set_Use (Visible_Declarations (Spec));
5966         Set_Use (Private_Declarations (Spec));
5967      end Install_Spec;
5968
5969   --  Start of processing for Install_Parent
5970
5971   begin
5972      --  We need to install the parent instance to compile the instantiation
5973      --  of the child, but the child instance must appear in the current
5974      --  scope. Given that we cannot place the parent above the current
5975      --  scope in the scope stack, we duplicate the current scope and unstack
5976      --  both after the instantiation is complete.
5977
5978      --  If the parent is itself the instantiation of a child unit, we must
5979      --  also stack the instantiation of its parent, and so on. Each such
5980      --  ancestor is the prefix of the name in a prior instantiation.
5981
5982      --  If this is a nested instance, the parent unit itself resolves to
5983      --  a renaming of the parent instance, whose declaration we need.
5984
5985      --  Finally, the parent may be a generic (not an instance) when the
5986      --  child unit appears as a formal package.
5987
5988      Inst_Par := P;
5989
5990      if Present (Renamed_Entity (Inst_Par)) then
5991         Inst_Par := Renamed_Entity (Inst_Par);
5992      end if;
5993
5994      First_Par := Inst_Par;
5995
5996      Gen_Par :=
5997        Generic_Parent (Specification (Unit_Declaration_Node (Inst_Par)));
5998
5999      First_Gen := Gen_Par;
6000
6001      while Present (Gen_Par)
6002        and then Is_Child_Unit (Gen_Par)
6003      loop
6004         --  Load grandparent instance as well
6005
6006         Inst_Node := Get_Package_Instantiation_Node (Inst_Par);
6007
6008         if Nkind (Name (Inst_Node)) = N_Expanded_Name then
6009            Inst_Par := Entity (Prefix (Name (Inst_Node)));
6010
6011            if Present (Renamed_Entity (Inst_Par)) then
6012               Inst_Par := Renamed_Entity (Inst_Par);
6013            end if;
6014
6015            Gen_Par :=
6016              Generic_Parent
6017                (Specification (Unit_Declaration_Node (Inst_Par)));
6018
6019            if Present (Gen_Par) then
6020               Prepend_Elmt (Inst_Par, Ancestors);
6021
6022            else
6023               --  Parent is not the name of an instantiation
6024
6025               Install_Noninstance_Specs (Inst_Par);
6026
6027               exit;
6028            end if;
6029
6030         else
6031            --  Previous error
6032
6033            exit;
6034         end if;
6035      end loop;
6036
6037      if Present (First_Gen) then
6038         Append_Elmt (First_Par, Ancestors);
6039
6040      else
6041         Install_Noninstance_Specs (First_Par);
6042      end if;
6043
6044      if not Is_Empty_Elmt_List (Ancestors) then
6045         Elmt := First_Elmt (Ancestors);
6046
6047         while Present (Elmt) loop
6048            Install_Spec (Node (Elmt));
6049            Install_Formal_Packages (Node (Elmt));
6050
6051            Next_Elmt (Elmt);
6052         end loop;
6053      end if;
6054
6055      if not In_Body then
6056         New_Scope (S);
6057      end if;
6058   end Install_Parent;
6059
6060   --------------------------------
6061   -- Instantiate_Formal_Package --
6062   --------------------------------
6063
6064   function Instantiate_Formal_Package
6065     (Formal          : Node_Id;
6066      Actual          : Node_Id;
6067      Analyzed_Formal : Node_Id)
6068      return            List_Id
6069   is
6070      Loc         : constant Source_Ptr := Sloc (Actual);
6071      Actual_Pack : Entity_Id;
6072      Formal_Pack : Entity_Id;
6073      Gen_Parent  : Entity_Id;
6074      Decls       : List_Id;
6075      Nod         : Node_Id;
6076      Parent_Spec : Node_Id;
6077
6078      procedure Find_Matching_Actual
6079       (F    : Node_Id;
6080        Act  : in out Entity_Id);
6081      --  We need to associate each formal entity in the formal package
6082      --  with the corresponding entity in the actual package. The actual
6083      --  package has been analyzed and possibly expanded, and as a result
6084      --  there is no one-to-one correspondence between the two lists (for
6085      --  example, the actual may include subtypes, itypes, and inherited
6086      --  primitive operations, interspersed among the renaming declarations
6087      --  for the actuals) . We retrieve the corresponding actual by name
6088      --  because each actual has the same name as the formal, and they do
6089      --  appear in the same order.
6090
6091      function Formal_Entity
6092        (F       : Node_Id;
6093         Act_Ent : Entity_Id)
6094         return    Entity_Id;
6095      --  Returns the entity associated with the given formal F. In the
6096      --  case where F is a formal package, this function will iterate
6097      --  through all of F's formals and enter map associations from the
6098      --  actuals occurring in the formal package's corresponding actual
6099      --  package (obtained via Act_Ent) to the formal package's formal
6100      --  parameters. This function is called recursively for arbitrary
6101      --  levels of formal packages.
6102
6103      function Is_Instance_Of
6104        (Act_Spec : Entity_Id;
6105         Gen_Anc  : Entity_Id)
6106         return     Boolean;
6107      --  The actual can be an instantiation of a generic within another
6108      --  instance, in which case there is no direct link from it to the
6109      --  original generic ancestor. In that case, we recognize that the
6110      --  ultimate ancestor is the same by examining names and scopes.
6111
6112      procedure Map_Entities (Form : Entity_Id; Act : Entity_Id);
6113      --  Within the generic part, entities in the formal package are
6114      --  visible. To validate subsequent type declarations, indicate
6115      --  the correspondence betwen the entities in the analyzed formal,
6116      --  and the entities in  the actual package. There are three packages
6117      --  involved in the instantiation of a formal package: the parent
6118      --  generic P1 which appears in the generic declaration, the fake
6119      --  instantiation P2 which appears in the analyzed generic, and whose
6120      --  visible entities may be used in subsequent formals, and the actual
6121      --  P3 in the instance. To validate subsequent formals, me indicate
6122      --  that the entities in P2 are mapped into those of P3. The mapping of
6123      --  entities has to be done recursively for nested packages.
6124
6125      --------------------------
6126      -- Find_Matching_Actual --
6127      --------------------------
6128
6129      procedure Find_Matching_Actual
6130        (F   : Node_Id;
6131         Act : in out Entity_Id)
6132     is
6133         Formal_Ent : Entity_Id;
6134
6135      begin
6136         case Nkind (Original_Node (F)) is
6137            when N_Formal_Object_Declaration |
6138                 N_Formal_Type_Declaration   =>
6139               Formal_Ent := Defining_Identifier (F);
6140
6141               while Chars (Act) /= Chars (Formal_Ent) loop
6142                  Next_Entity (Act);
6143               end loop;
6144
6145            when N_Formal_Subprogram_Declaration |
6146                 N_Formal_Package_Declaration    |
6147                 N_Package_Declaration           |
6148                 N_Generic_Package_Declaration   =>
6149               Formal_Ent := Defining_Entity (F);
6150
6151               while Chars (Act) /= Chars (Formal_Ent) loop
6152                  Next_Entity (Act);
6153               end loop;
6154
6155            when others =>
6156               null;
6157               pragma Assert (False);
6158         end case;
6159      end Find_Matching_Actual;
6160
6161      -------------------
6162      -- Formal_Entity --
6163      -------------------
6164
6165      function Formal_Entity
6166        (F       : Node_Id;
6167         Act_Ent : Entity_Id)
6168         return    Entity_Id
6169      is
6170         Orig_Node : Node_Id := F;
6171         Act_Pkg   : Entity_Id;
6172
6173      begin
6174         case Nkind (Original_Node (F)) is
6175            when N_Formal_Object_Declaration     =>
6176               return Defining_Identifier (F);
6177
6178            when N_Formal_Type_Declaration       =>
6179               return Defining_Identifier (F);
6180
6181            when N_Formal_Subprogram_Declaration =>
6182               return Defining_Unit_Name (Specification (F));
6183
6184            when N_Package_Declaration           =>
6185               return Defining_Unit_Name (Specification (F));
6186
6187            when N_Formal_Package_Declaration |
6188                 N_Generic_Package_Declaration   =>
6189
6190               if Nkind (F) = N_Generic_Package_Declaration then
6191                  Orig_Node := Original_Node (F);
6192               end if;
6193
6194               Act_Pkg := Act_Ent;
6195
6196               --  Find matching actual package, skipping over itypes and
6197               --  other entities generated when analyzing the formal. We
6198               --  know that if the instantiation is legal then there is
6199               --  a matching package for the formal.
6200
6201               while Ekind (Act_Pkg) /= E_Package loop
6202                  Act_Pkg := Next_Entity (Act_Pkg);
6203               end loop;
6204
6205               declare
6206                  Actual_Ent  : Entity_Id := First_Entity (Act_Pkg);
6207                  Formal_Node : Node_Id;
6208                  Formal_Ent  : Entity_Id;
6209
6210                  Gen_Decl : constant Node_Id :=
6211                               Unit_Declaration_Node
6212                                 (Entity (Name (Orig_Node)));
6213
6214                  Formals : constant List_Id :=
6215                              Generic_Formal_Declarations (Gen_Decl);
6216
6217               begin
6218                  if Present (Formals) then
6219                     Formal_Node := First_Non_Pragma (Formals);
6220                  else
6221                     Formal_Node := Empty;
6222                  end if;
6223
6224                  while Present (Actual_Ent)
6225                    and then Present (Formal_Node)
6226                    and then Actual_Ent /= First_Private_Entity (Act_Ent)
6227                  loop
6228                     --  ???  Are the following calls also needed here:
6229                     --
6230                     --  Set_Is_Hidden (Actual_Ent, False);
6231                     --  Set_Is_Potentially_Use_Visible
6232                     --    (Actual_Ent, In_Use (Act_Ent));
6233
6234                     Formal_Ent := Formal_Entity (Formal_Node, Actual_Ent);
6235                     if Present (Formal_Ent) then
6236                        Set_Instance_Of (Formal_Ent, Actual_Ent);
6237                     end if;
6238                     Next_Non_Pragma (Formal_Node);
6239
6240                     Next_Entity (Actual_Ent);
6241                  end loop;
6242               end;
6243
6244               return Defining_Identifier (Orig_Node);
6245
6246            when N_Use_Package_Clause =>
6247               return Empty;
6248
6249            when N_Use_Type_Clause =>
6250               return Empty;
6251
6252            --  We return Empty for all other encountered forms of
6253            --  declarations because there are some cases of nonformal
6254            --  sorts of declaration that can show up (e.g., when array
6255            --  formals are present). Since it's not clear what kinds
6256            --  can appear among the formals, we won't raise failure here.
6257
6258            when others =>
6259               return Empty;
6260
6261         end case;
6262      end Formal_Entity;
6263
6264      --------------------
6265      -- Is_Instance_Of --
6266      --------------------
6267
6268      function Is_Instance_Of
6269        (Act_Spec : Entity_Id;
6270         Gen_Anc  : Entity_Id)
6271         return     Boolean
6272      is
6273         Gen_Par : constant Entity_Id := Generic_Parent (Act_Spec);
6274
6275      begin
6276         if No (Gen_Par) then
6277            return False;
6278
6279         --  Simplest case: the generic parent of the actual is the formal.
6280
6281         elsif Gen_Par = Gen_Anc then
6282            return True;
6283
6284         elsif Chars (Gen_Par) /= Chars (Gen_Anc) then
6285            return False;
6286
6287         --  The actual may be obtained through several instantiations. Its
6288         --  scope must itself be an instance of a generic declared in the
6289         --  same scope as the formal. Any other case is detected above.
6290
6291         elsif not Is_Generic_Instance (Scope (Gen_Par)) then
6292            return False;
6293
6294         else
6295            return Generic_Parent (Parent (Scope (Gen_Par))) = Scope (Gen_Anc);
6296         end if;
6297      end Is_Instance_Of;
6298
6299      ------------------
6300      -- Map_Entities --
6301      ------------------
6302
6303      procedure Map_Entities (Form : Entity_Id; Act : Entity_Id) is
6304         E1 : Entity_Id;
6305         E2 : Entity_Id;
6306
6307      begin
6308         Set_Instance_Of (Form, Act);
6309
6310         --  Traverse formal and actual package to map the corresponding
6311         --  entities. We skip over internal entities that may be generated
6312         --  during semantic analysis, and find the matching entities by
6313         --  name, given that they must appear in the same order.
6314
6315         E1 := First_Entity (Form);
6316         E2 := First_Entity (Act);
6317         while Present (E1)
6318           and then E1 /= First_Private_Entity (Form)
6319         loop
6320            if not Is_Internal (E1)
6321              and then not Is_Class_Wide_Type (E1)
6322              and then Present (Parent (E1))
6323            then
6324               while Present (E2)
6325                 and then Chars (E2) /= Chars (E1)
6326               loop
6327                  Next_Entity (E2);
6328               end loop;
6329
6330               if No (E2) then
6331                  exit;
6332               else
6333                  Set_Instance_Of (E1, E2);
6334
6335                  if Is_Type (E1)
6336                    and then Is_Tagged_Type (E2)
6337                  then
6338                     Set_Instance_Of
6339                       (Class_Wide_Type (E1), Class_Wide_Type (E2));
6340                  end if;
6341
6342                  if Ekind (E1) = E_Package
6343                    and then No (Renamed_Object (E1))
6344                  then
6345                     Map_Entities (E1, E2);
6346                  end if;
6347               end if;
6348            end if;
6349
6350            Next_Entity (E1);
6351         end loop;
6352      end Map_Entities;
6353
6354   --  Start of processing for Instantiate_Formal_Package
6355
6356   begin
6357      Analyze (Actual);
6358
6359      if not Is_Entity_Name (Actual)
6360        or else  Ekind (Entity (Actual)) /= E_Package
6361      then
6362         Error_Msg_N
6363           ("expect package instance to instantiate formal", Actual);
6364         Abandon_Instantiation (Actual);
6365         raise Program_Error;
6366
6367      else
6368         Actual_Pack := Entity (Actual);
6369         Set_Is_Instantiated (Actual_Pack);
6370
6371         --  The actual may be a renamed package, or an outer generic
6372         --  formal package whose instantiation is converted into a renaming.
6373
6374         if Present (Renamed_Object (Actual_Pack)) then
6375            Actual_Pack := Renamed_Object (Actual_Pack);
6376         end if;
6377
6378         if Nkind (Analyzed_Formal) = N_Formal_Package_Declaration then
6379            Gen_Parent  := Get_Instance_Of (Entity (Name (Analyzed_Formal)));
6380            Formal_Pack := Defining_Identifier (Analyzed_Formal);
6381         else
6382            Gen_Parent :=
6383              Generic_Parent (Specification (Analyzed_Formal));
6384            Formal_Pack :=
6385              Defining_Unit_Name (Specification (Analyzed_Formal));
6386         end if;
6387
6388         if Nkind (Parent (Actual_Pack)) = N_Defining_Program_Unit_Name then
6389            Parent_Spec := Specification (Unit_Declaration_Node (Actual_Pack));
6390         else
6391            Parent_Spec := Parent (Actual_Pack);
6392         end if;
6393
6394         if Gen_Parent = Any_Id then
6395            Error_Msg_N
6396              ("previous error in declaration of formal package", Actual);
6397            Abandon_Instantiation (Actual);
6398
6399         elsif
6400           Is_Instance_Of (Parent_Spec, Get_Instance_Of (Gen_Parent))
6401         then
6402            null;
6403
6404         else
6405            Error_Msg_NE
6406              ("actual parameter must be instance of&", Actual, Gen_Parent);
6407            Abandon_Instantiation (Actual);
6408         end if;
6409
6410         Set_Instance_Of (Defining_Identifier (Formal), Actual_Pack);
6411         Map_Entities (Formal_Pack, Actual_Pack);
6412
6413         Nod :=
6414           Make_Package_Renaming_Declaration (Loc,
6415             Defining_Unit_Name => New_Copy (Defining_Identifier (Formal)),
6416             Name               => New_Reference_To (Actual_Pack, Loc));
6417
6418         Set_Associated_Formal_Package (Defining_Unit_Name (Nod),
6419           Defining_Identifier (Formal));
6420         Decls := New_List (Nod);
6421
6422         --  If the formal F has a box, then the generic declarations are
6423         --  visible in the generic G. In an instance of G, the corresponding
6424         --  entities in the actual for F (which are the actuals for the
6425         --  instantiation of the generic that F denotes) must also be made
6426         --  visible for analysis of the current instance. On exit from the
6427         --  current instance, those entities are made private again. If the
6428         --  actual is currently in use, these entities are also use-visible.
6429
6430         --  The loop through the actual entities also steps through the
6431         --  formal entities and enters associations from formals to
6432         --  actuals into the renaming map. This is necessary to properly
6433         --  handle checking of actual parameter associations for later
6434         --  formals that depend on actuals declared in the formal package.
6435
6436         if Box_Present (Formal) then
6437            declare
6438               Gen_Decl    : constant Node_Id :=
6439                               Unit_Declaration_Node (Gen_Parent);
6440               Formals     : constant List_Id :=
6441                               Generic_Formal_Declarations (Gen_Decl);
6442               Actual_Ent  : Entity_Id;
6443               Formal_Node : Node_Id;
6444               Formal_Ent  : Entity_Id;
6445
6446            begin
6447               if Present (Formals) then
6448                  Formal_Node := First_Non_Pragma (Formals);
6449               else
6450                  Formal_Node := Empty;
6451               end if;
6452
6453               Actual_Ent := First_Entity (Actual_Pack);
6454
6455               while Present (Actual_Ent)
6456                 and then Actual_Ent /= First_Private_Entity (Actual_Pack)
6457               loop
6458                  Set_Is_Hidden (Actual_Ent, False);
6459                  Set_Is_Potentially_Use_Visible
6460                    (Actual_Ent, In_Use (Actual_Pack));
6461
6462                  if Present (Formal_Node) then
6463                     Formal_Ent := Formal_Entity (Formal_Node, Actual_Ent);
6464
6465                     if Present (Formal_Ent) then
6466                        Find_Matching_Actual (Formal_Node, Actual_Ent);
6467                        Set_Instance_Of (Formal_Ent, Actual_Ent);
6468                     end if;
6469
6470                     Next_Non_Pragma (Formal_Node);
6471
6472                  else
6473                     --  No further formals to match.
6474
6475                     exit;
6476                  end if;
6477
6478               end loop;
6479            end;
6480
6481         --  If the formal is not declared with a box, reanalyze it as
6482         --  an instantiation, to verify the matching rules of 12.7. The
6483         --  actual checks are performed after the generic associations
6484         --  been analyzed.
6485
6486         else
6487            declare
6488               I_Pack : constant Entity_Id :=
6489                          Make_Defining_Identifier (Sloc (Actual),
6490                            Chars => New_Internal_Name  ('P'));
6491
6492            begin
6493               Set_Is_Internal (I_Pack);
6494
6495               Append_To (Decls,
6496                 Make_Package_Instantiation (Sloc (Actual),
6497                   Defining_Unit_Name => I_Pack,
6498                   Name => New_Occurrence_Of (Gen_Parent, Sloc (Actual)),
6499                   Generic_Associations =>
6500                     Generic_Associations (Formal)));
6501            end;
6502         end if;
6503
6504         return Decls;
6505      end if;
6506   end Instantiate_Formal_Package;
6507
6508   -----------------------------------
6509   -- Instantiate_Formal_Subprogram --
6510   -----------------------------------
6511
6512   function Instantiate_Formal_Subprogram
6513     (Formal          : Node_Id;
6514      Actual          : Node_Id;
6515      Analyzed_Formal : Node_Id)
6516      return            Node_Id
6517   is
6518      Loc        : Source_Ptr := Sloc (Instantiation_Node);
6519      Formal_Sub : constant Entity_Id :=
6520                     Defining_Unit_Name (Specification (Formal));
6521      Analyzed_S : constant Entity_Id :=
6522                     Defining_Unit_Name (Specification (Analyzed_Formal));
6523      Decl_Node  : Node_Id;
6524      Nam        : Node_Id;
6525      New_Spec   : Node_Id;
6526
6527      function From_Parent_Scope (Subp : Entity_Id) return Boolean;
6528      --  If the generic is a child unit, the parent has been installed
6529      --  on the scope stack, but a default subprogram cannot resolve to
6530      --  something on the parent because that parent is not really part
6531      --  of the visible context (it is there to resolve explicit local
6532      --  entities). If the default has resolved in this way, we remove
6533      --  the entity from immediate visibility and analyze the node again
6534      --  to emit an error message or find another visible candidate.
6535
6536      procedure Valid_Actual_Subprogram (Act : Node_Id);
6537      --  Perform legality check and raise exception on failure.
6538
6539      -----------------------
6540      -- From_Parent_Scope --
6541      -----------------------
6542
6543      function From_Parent_Scope (Subp : Entity_Id) return Boolean is
6544         Gen_Scope : Node_Id := Scope (Analyzed_S);
6545
6546      begin
6547         while Present (Gen_Scope)
6548           and then  Is_Child_Unit (Gen_Scope)
6549         loop
6550            if Scope (Subp) = Scope (Gen_Scope) then
6551               return True;
6552            end if;
6553
6554            Gen_Scope := Scope (Gen_Scope);
6555         end loop;
6556
6557         return False;
6558      end From_Parent_Scope;
6559
6560      -----------------------------
6561      -- Valid_Actual_Subprogram --
6562      -----------------------------
6563
6564      procedure Valid_Actual_Subprogram (Act : Node_Id) is
6565         Act_E : Entity_Id := Empty;
6566
6567      begin
6568         if Is_Entity_Name (Act) then
6569            Act_E := Entity (Act);
6570         elsif Nkind (Act) = N_Selected_Component
6571           and then Is_Entity_Name (Selector_Name (Act))
6572         then
6573            Act_E := Entity (Selector_Name (Act));
6574         end if;
6575
6576         if (Present (Act_E) and then Is_Overloadable (Act_E))
6577           or else Nkind (Act) = N_Attribute_Reference
6578           or else Nkind (Act) = N_Indexed_Component
6579           or else Nkind (Act) = N_Character_Literal
6580           or else Nkind (Act) = N_Explicit_Dereference
6581         then
6582            return;
6583         end if;
6584
6585         Error_Msg_NE
6586           ("expect subprogram or entry name in instantiation of&",
6587            Instantiation_Node, Formal_Sub);
6588         Abandon_Instantiation (Instantiation_Node);
6589
6590      end Valid_Actual_Subprogram;
6591
6592   --  Start of processing for Instantiate_Formal_Subprogram
6593
6594   begin
6595      New_Spec := New_Copy_Tree (Specification (Formal));
6596
6597      --  Create new entity for the actual (New_Copy_Tree does not).
6598
6599      Set_Defining_Unit_Name
6600        (New_Spec, Make_Defining_Identifier (Loc, Chars (Formal_Sub)));
6601
6602      --  Find entity of actual. If the actual is an attribute reference, it
6603      --  cannot be resolved here (its formal is missing) but is handled
6604      --  instead in Attribute_Renaming. If the actual is overloaded, it is
6605      --  fully resolved subsequently, when the renaming declaration for the
6606      --  formal is analyzed. If it is an explicit dereference, resolve the
6607      --  prefix but not the actual itself, to prevent interpretation as a
6608      --  call.
6609
6610      if Present (Actual) then
6611         Loc := Sloc (Actual);
6612         Set_Sloc (New_Spec, Loc);
6613
6614         if Nkind (Actual) = N_Operator_Symbol then
6615            Find_Direct_Name (Actual);
6616
6617         elsif Nkind (Actual) = N_Explicit_Dereference then
6618            Analyze (Prefix (Actual));
6619
6620         elsif Nkind (Actual) /= N_Attribute_Reference then
6621            Analyze (Actual);
6622         end if;
6623
6624         Valid_Actual_Subprogram (Actual);
6625         Nam := Actual;
6626
6627      elsif Present (Default_Name (Formal)) then
6628         if Nkind (Default_Name (Formal)) /= N_Attribute_Reference
6629           and then Nkind (Default_Name (Formal)) /= N_Selected_Component
6630           and then Nkind (Default_Name (Formal)) /= N_Indexed_Component
6631           and then Nkind (Default_Name (Formal)) /= N_Character_Literal
6632           and then Present (Entity (Default_Name (Formal)))
6633         then
6634            Nam := New_Occurrence_Of (Entity (Default_Name (Formal)), Loc);
6635         else
6636            Nam := New_Copy (Default_Name (Formal));
6637            Set_Sloc (Nam, Loc);
6638         end if;
6639
6640      elsif Box_Present (Formal) then
6641
6642         --  Actual is resolved at the point of instantiation. Create
6643         --  an identifier or operator with the same name as the formal.
6644
6645         if Nkind (Formal_Sub) = N_Defining_Operator_Symbol then
6646            Nam := Make_Operator_Symbol (Loc,
6647              Chars =>  Chars (Formal_Sub),
6648              Strval => No_String);
6649         else
6650            Nam := Make_Identifier (Loc, Chars (Formal_Sub));
6651         end if;
6652
6653      else
6654         Error_Msg_Sloc := Sloc (Scope (Analyzed_S));
6655         Error_Msg_NE
6656           ("missing actual&", Instantiation_Node, Formal_Sub);
6657         Error_Msg_NE
6658           ("\in instantiation of & declared#",
6659              Instantiation_Node, Scope (Analyzed_S));
6660         Abandon_Instantiation (Instantiation_Node);
6661      end if;
6662
6663      Decl_Node :=
6664        Make_Subprogram_Renaming_Declaration (Loc,
6665          Specification => New_Spec,
6666          Name => Nam);
6667
6668      --  Gather possible interpretations for the actual before analyzing the
6669      --  instance. If overloaded, it will be resolved when analyzing the
6670      --  renaming declaration.
6671
6672      if Box_Present (Formal)
6673        and then No (Actual)
6674      then
6675         Analyze (Nam);
6676
6677         if Is_Child_Unit (Scope (Analyzed_S))
6678           and then Present (Entity (Nam))
6679         then
6680            if not Is_Overloaded (Nam) then
6681
6682               if From_Parent_Scope (Entity (Nam)) then
6683                  Set_Is_Immediately_Visible (Entity (Nam), False);
6684                  Set_Entity (Nam, Empty);
6685                  Set_Etype (Nam, Empty);
6686
6687                  Analyze (Nam);
6688
6689                  Set_Is_Immediately_Visible (Entity (Nam));
6690               end if;
6691
6692            else
6693               declare
6694                  I  : Interp_Index;
6695                  It : Interp;
6696
6697               begin
6698                  Get_First_Interp (Nam, I, It);
6699
6700                  while Present (It.Nam) loop
6701                     if From_Parent_Scope (It.Nam) then
6702                        Remove_Interp (I);
6703                     end if;
6704
6705                     Get_Next_Interp (I, It);
6706                  end loop;
6707               end;
6708            end if;
6709         end if;
6710      end if;
6711
6712      --  The generic instantiation freezes the actual. This can only be
6713      --  done once the actual is resolved, in the analysis of the renaming
6714      --  declaration. To indicate that must be done, we set the corresponding
6715      --  spec of the node to point to the formal subprogram entity.
6716
6717      Set_Corresponding_Spec (Decl_Node, Analyzed_S);
6718
6719      --  We cannot analyze the renaming declaration, and thus find the
6720      --  actual, until the all the actuals are assembled in the instance.
6721      --  For subsequent checks of other actuals, indicate the node that
6722      --  will hold the instance of this formal.
6723
6724      Set_Instance_Of (Analyzed_S, Nam);
6725
6726      if Nkind (Actual) = N_Selected_Component
6727        and then Is_Task_Type (Etype (Prefix (Actual)))
6728        and then not Is_Frozen (Etype (Prefix (Actual)))
6729      then
6730         --  The renaming declaration will create a body, which must appear
6731         --  outside of the instantiation, We move the renaming declaration
6732         --  out of the instance, and create an additional renaming inside,
6733         --  to prevent freezing anomalies.
6734
6735         declare
6736            Anon_Id : constant Entity_Id :=
6737                        Make_Defining_Identifier
6738                          (Loc, New_Internal_Name ('E'));
6739         begin
6740            Set_Defining_Unit_Name (New_Spec, Anon_Id);
6741            Insert_Before (Instantiation_Node, Decl_Node);
6742            Analyze (Decl_Node);
6743
6744            --  Now create renaming within the instance
6745
6746            Decl_Node :=
6747              Make_Subprogram_Renaming_Declaration (Loc,
6748                Specification => New_Copy_Tree (New_Spec),
6749                Name => New_Occurrence_Of (Anon_Id, Loc));
6750
6751            Set_Defining_Unit_Name (Specification (Decl_Node),
6752              Make_Defining_Identifier (Loc, Chars (Formal_Sub)));
6753         end;
6754      end if;
6755
6756      return Decl_Node;
6757   end Instantiate_Formal_Subprogram;
6758
6759   ------------------------
6760   -- Instantiate_Object --
6761   ------------------------
6762
6763   function Instantiate_Object
6764     (Formal          : Node_Id;
6765      Actual          : Node_Id;
6766      Analyzed_Formal : Node_Id)
6767      return            List_Id
6768   is
6769      Formal_Id : constant Entity_Id  := Defining_Identifier (Formal);
6770      Type_Id   : constant Node_Id    := Subtype_Mark (Formal);
6771      Loc       : constant Source_Ptr := Sloc (Actual);
6772      Act_Assoc : constant Node_Id    := Parent (Actual);
6773      Orig_Ftyp : constant Entity_Id  :=
6774                    Etype (Defining_Identifier (Analyzed_Formal));
6775      List      : constant List_Id    := New_List;
6776      Ftyp      : Entity_Id;
6777      Decl_Node : Node_Id;
6778      Subt_Decl : Node_Id := Empty;
6779
6780   begin
6781      --  Sloc for error message on missing actual.
6782      Error_Msg_Sloc := Sloc (Scope (Defining_Identifier (Analyzed_Formal)));
6783
6784      if Get_Instance_Of (Formal_Id) /= Formal_Id then
6785         Error_Msg_N ("duplicate instantiation of generic parameter", Actual);
6786      end if;
6787
6788      Set_Parent (List, Parent (Actual));
6789
6790      --  OUT present
6791
6792      if Out_Present (Formal) then
6793
6794         --  An IN OUT generic actual must be a name. The instantiation is
6795         --  a renaming declaration. The actual is the name being renamed.
6796         --  We use the actual directly, rather than a copy, because it is not
6797         --  used further in the list of actuals, and because a copy or a use
6798         --  of relocate_node is incorrect if the instance is nested within
6799         --  a generic. In order to simplify ASIS searches, the Generic_Parent
6800         --  field links the declaration to the generic association.
6801
6802         if No (Actual) then
6803            Error_Msg_NE
6804              ("missing actual&",
6805               Instantiation_Node, Formal_Id);
6806            Error_Msg_NE
6807              ("\in instantiation of & declared#",
6808                 Instantiation_Node,
6809                   Scope (Defining_Identifier (Analyzed_Formal)));
6810            Abandon_Instantiation (Instantiation_Node);
6811         end if;
6812
6813         Decl_Node :=
6814           Make_Object_Renaming_Declaration (Loc,
6815             Defining_Identifier => New_Copy (Formal_Id),
6816             Subtype_Mark        => New_Copy_Tree (Type_Id),
6817             Name                => Actual);
6818
6819         Set_Corresponding_Generic_Association (Decl_Node, Act_Assoc);
6820
6821         --  The analysis of the actual may produce insert_action nodes, so
6822         --  the declaration must have a context in which to attach them.
6823
6824         Append (Decl_Node, List);
6825         Analyze (Actual);
6826
6827         --  This check is performed here because Analyze_Object_Renaming
6828         --  will not check it when Comes_From_Source is False. Note
6829         --  though that the check for the actual being the name of an
6830         --  object will be performed in Analyze_Object_Renaming.
6831
6832         if Is_Object_Reference (Actual)
6833           and then Is_Dependent_Component_Of_Mutable_Object (Actual)
6834         then
6835            Error_Msg_N
6836              ("illegal discriminant-dependent component for in out parameter",
6837               Actual);
6838         end if;
6839
6840         --  The actual has to be resolved in order to check that it is
6841         --  a variable (due to cases such as F(1), where F returns
6842         --  access to an array, and for overloaded prefixes).
6843
6844         Ftyp :=
6845           Get_Instance_Of (Etype (Defining_Identifier (Analyzed_Formal)));
6846
6847         if Is_Private_Type (Ftyp)
6848           and then not Is_Private_Type (Etype (Actual))
6849           and then (Base_Type (Full_View (Ftyp)) = Base_Type (Etype (Actual))
6850                      or else Base_Type (Etype (Actual)) = Ftyp)
6851         then
6852            --  If the actual has the type of the full view of the formal,
6853            --  or else a non-private subtype of the formal, then
6854            --  the visibility of the formal type has changed. Add to the
6855            --  actuals a subtype declaration that will force the exchange
6856            --  of views in the body of the instance as well.
6857
6858            Subt_Decl :=
6859              Make_Subtype_Declaration (Loc,
6860                 Defining_Identifier =>
6861                   Make_Defining_Identifier (Loc, New_Internal_Name ('P')),
6862                 Subtype_Indication  => New_Occurrence_Of (Ftyp, Loc));
6863
6864            Prepend (Subt_Decl, List);
6865
6866            Append_Elmt (Full_View (Ftyp), Exchanged_Views);
6867            Exchange_Declarations (Ftyp);
6868         end if;
6869
6870         Resolve (Actual, Ftyp);
6871
6872         if not Is_Variable (Actual) or else Paren_Count (Actual) > 0 then
6873            Error_Msg_NE
6874              ("actual for& must be a variable", Actual, Formal_Id);
6875
6876         elsif Base_Type (Ftyp) /= Base_Type (Etype (Actual)) then
6877            Error_Msg_NE (
6878              "type of actual does not match type of&", Actual, Formal_Id);
6879
6880         end if;
6881
6882         Note_Possible_Modification (Actual);
6883
6884         --  Check for instantiation of atomic/volatile actual for
6885         --  non-atomic/volatile formal (RM C.6 (12)).
6886
6887         if Is_Atomic_Object (Actual)
6888           and then not Is_Atomic (Orig_Ftyp)
6889         then
6890            Error_Msg_N
6891              ("cannot instantiate non-atomic formal object " &
6892               "with atomic actual", Actual);
6893
6894         elsif Is_Volatile_Object (Actual)
6895           and then not Is_Volatile (Orig_Ftyp)
6896         then
6897            Error_Msg_N
6898              ("cannot instantiate non-volatile formal object " &
6899               "with volatile actual", Actual);
6900         end if;
6901
6902      --  OUT not present
6903
6904      else
6905         --  The instantiation of a generic formal in-parameter
6906         --  is a constant declaration. The actual is the expression for
6907         --  that declaration.
6908
6909         if Present (Actual) then
6910
6911            Decl_Node := Make_Object_Declaration (Loc,
6912              Defining_Identifier => New_Copy (Formal_Id),
6913              Constant_Present => True,
6914              Object_Definition => New_Copy_Tree (Type_Id),
6915              Expression => Actual);
6916
6917            Set_Corresponding_Generic_Association (Decl_Node, Act_Assoc);
6918
6919            --  A generic formal object of a tagged type is defined
6920            --  to be aliased so the new constant must also be treated
6921            --  as aliased.
6922
6923            if Is_Tagged_Type
6924                 (Etype (Defining_Identifier (Analyzed_Formal)))
6925            then
6926               Set_Aliased_Present (Decl_Node);
6927            end if;
6928
6929            Append (Decl_Node, List);
6930
6931            --  No need to repeat (pre-)analysis of some expression nodes
6932            --  already handled in Pre_Analyze_Actuals.
6933
6934            if Nkind (Actual) /= N_Allocator then
6935               Analyze (Actual);
6936            end if;
6937
6938            declare
6939               Typ : constant Entity_Id :=
6940                       Get_Instance_Of
6941                         (Etype (Defining_Identifier (Analyzed_Formal)));
6942
6943            begin
6944               Freeze_Before (Instantiation_Node, Typ);
6945
6946               --  If the actual is an aggregate, perform name resolution
6947               --  on its components (the analysis of an aggregate does not
6948               --  do it) to capture local names that may be hidden if the
6949               --  generic is a child unit.
6950
6951               if Nkind (Actual) = N_Aggregate then
6952                     Pre_Analyze_And_Resolve (Actual, Typ);
6953               end if;
6954            end;
6955
6956         elsif Present (Expression (Formal)) then
6957
6958            --  Use default to construct declaration.
6959
6960            Decl_Node :=
6961              Make_Object_Declaration (Sloc (Formal),
6962                Defining_Identifier => New_Copy (Formal_Id),
6963                Constant_Present    => True,
6964                Object_Definition   => New_Copy (Type_Id),
6965                Expression          => New_Copy_Tree (Expression (Formal)));
6966
6967            Append (Decl_Node, List);
6968            Set_Analyzed (Expression (Decl_Node), False);
6969
6970         else
6971            Error_Msg_NE
6972              ("missing actual&",
6973                Instantiation_Node, Formal_Id);
6974            Error_Msg_NE ("\in instantiation of & declared#",
6975              Instantiation_Node,
6976                Scope (Defining_Identifier (Analyzed_Formal)));
6977
6978            if Is_Scalar_Type
6979                 (Etype (Defining_Identifier (Analyzed_Formal)))
6980            then
6981               --  Create dummy constant declaration so that instance can
6982               --  be analyzed, to minimize cascaded visibility errors.
6983
6984               Decl_Node :=
6985                 Make_Object_Declaration (Loc,
6986                   Defining_Identifier => New_Copy (Formal_Id),
6987                   Constant_Present    => True,
6988                   Object_Definition   => New_Copy (Type_Id),
6989                   Expression          =>
6990                      Make_Attribute_Reference (Sloc (Formal_Id),
6991                        Attribute_Name => Name_First,
6992                        Prefix         => New_Copy (Type_Id)));
6993
6994               Append (Decl_Node, List);
6995
6996            else
6997               Abandon_Instantiation (Instantiation_Node);
6998            end if;
6999         end if;
7000
7001      end if;
7002
7003      return List;
7004   end Instantiate_Object;
7005
7006   ------------------------------
7007   -- Instantiate_Package_Body --
7008   ------------------------------
7009
7010   procedure Instantiate_Package_Body
7011     (Body_Info    : Pending_Body_Info;
7012      Inlined_Body : Boolean := False)
7013   is
7014      Act_Decl    : constant Node_Id    := Body_Info.Act_Decl;
7015      Inst_Node   : constant Node_Id    := Body_Info.Inst_Node;
7016      Loc         : constant Source_Ptr := Sloc (Inst_Node);
7017
7018      Gen_Id      : constant Node_Id    := Name (Inst_Node);
7019      Gen_Unit    : constant Entity_Id  := Get_Generic_Entity (Inst_Node);
7020      Gen_Decl    : constant Node_Id    := Unit_Declaration_Node (Gen_Unit);
7021      Act_Spec    : constant Node_Id    := Specification (Act_Decl);
7022      Act_Decl_Id : constant Entity_Id  := Defining_Entity (Act_Spec);
7023
7024      Act_Body_Name : Node_Id;
7025      Gen_Body      : Node_Id;
7026      Gen_Body_Id   : Node_Id;
7027      Act_Body      : Node_Id;
7028      Act_Body_Id   : Entity_Id;
7029
7030      Parent_Installed : Boolean := False;
7031      Save_Style_Check : constant Boolean := Style_Check;
7032
7033   begin
7034      Gen_Body_Id := Corresponding_Body (Gen_Decl);
7035
7036      --  The instance body may already have been processed, as the parent
7037      --  of another instance that is inlined. (Load_Parent_Of_Generic).
7038
7039      if Present (Corresponding_Body (Instance_Spec (Inst_Node))) then
7040         return;
7041      end if;
7042
7043      Expander_Mode_Save_And_Set (Body_Info.Expander_Status);
7044
7045      if No (Gen_Body_Id) then
7046         Load_Parent_Of_Generic (Inst_Node, Specification (Gen_Decl));
7047         Gen_Body_Id := Corresponding_Body (Gen_Decl);
7048      end if;
7049
7050      --  Establish global variable for sloc adjustment and for error
7051      --  recovery.
7052
7053      Instantiation_Node := Inst_Node;
7054
7055      if Present (Gen_Body_Id) then
7056         Save_Env (Gen_Unit, Act_Decl_Id);
7057         Style_Check := False;
7058         Current_Sem_Unit := Body_Info.Current_Sem_Unit;
7059
7060         Gen_Body := Unit_Declaration_Node (Gen_Body_Id);
7061
7062         Create_Instantiation_Source
7063          (Inst_Node, Gen_Body_Id, False, S_Adjustment);
7064
7065         Act_Body :=
7066           Copy_Generic_Node
7067             (Original_Node (Gen_Body), Empty, Instantiating => True);
7068
7069         --  Build new name (possibly qualified) for body declaration
7070
7071         Act_Body_Id := New_Copy (Act_Decl_Id);
7072
7073         --  Some attributes of the spec entity are not inherited by the
7074         --  body entity.
7075
7076         Set_Handler_Records (Act_Body_Id, No_List);
7077
7078         if Nkind (Defining_Unit_Name (Act_Spec)) =
7079                                           N_Defining_Program_Unit_Name
7080         then
7081            Act_Body_Name :=
7082              Make_Defining_Program_Unit_Name (Loc,
7083                Name => New_Copy_Tree (Name (Defining_Unit_Name (Act_Spec))),
7084                Defining_Identifier => Act_Body_Id);
7085         else
7086            Act_Body_Name :=  Act_Body_Id;
7087         end if;
7088
7089         Set_Defining_Unit_Name (Act_Body, Act_Body_Name);
7090
7091         Set_Corresponding_Spec (Act_Body, Act_Decl_Id);
7092         Check_Generic_Actuals (Act_Decl_Id, False);
7093
7094         --  If it is a child unit, make the parent instance (which is an
7095         --  instance of the parent of the generic) visible. The parent
7096         --  instance is the prefix of the name of the generic unit.
7097
7098         if Ekind (Scope (Gen_Unit)) = E_Generic_Package
7099           and then Nkind (Gen_Id) = N_Expanded_Name
7100         then
7101            Install_Parent (Entity (Prefix (Gen_Id)), In_Body => True);
7102            Parent_Installed := True;
7103
7104         elsif Is_Child_Unit (Gen_Unit) then
7105            Install_Parent (Scope (Gen_Unit), In_Body => True);
7106            Parent_Installed := True;
7107         end if;
7108
7109         --  If the instantiation is a library unit, and this is the main
7110         --  unit, then build the resulting compilation unit nodes for the
7111         --  instance. If this is a compilation unit but it is not the main
7112         --  unit, then it is the body of a unit in the context, that is being
7113         --  compiled because it is encloses some inlined unit or another
7114         --  generic unit being instantiated. In that case, this body is not
7115         --  part of the current compilation, and is not attached to the tree,
7116         --  but its parent must be set for analysis.
7117
7118         if Nkind (Parent (Inst_Node)) = N_Compilation_Unit then
7119
7120            --  Replace instance node with body of instance, and create
7121            --  new node for corresponding instance declaration.
7122
7123            Build_Instance_Compilation_Unit_Nodes
7124              (Inst_Node, Act_Body, Act_Decl);
7125            Analyze (Inst_Node);
7126
7127            if Parent (Inst_Node) = Cunit (Main_Unit) then
7128
7129               --  If the instance is a child unit itself, then set the
7130               --  scope of the expanded body to be the parent of the
7131               --  instantiation (ensuring that the fully qualified name
7132               --  will be generated for the elaboration subprogram).
7133
7134               if Nkind (Defining_Unit_Name (Act_Spec)) =
7135                                              N_Defining_Program_Unit_Name
7136               then
7137                  Set_Scope
7138                    (Defining_Entity (Inst_Node), Scope (Act_Decl_Id));
7139               end if;
7140            end if;
7141
7142         --  Case where instantiation is not a library unit
7143
7144         else
7145            --  If this is an early instantiation, i.e. appears textually
7146            --  before the corresponding body and must be elaborated first,
7147            --  indicate that the body instance is to be delayed.
7148
7149            Install_Body (Act_Body, Inst_Node, Gen_Body, Gen_Decl);
7150
7151            --  Now analyze the body. We turn off all checks if this is
7152            --  an internal unit, since there is no reason to have checks
7153            --  on for any predefined run-time library code. All such
7154            --  code is designed to be compiled with checks off.
7155
7156            --  Note that we do NOT apply this criterion to children of
7157            --  GNAT (or on VMS, children of DEC). The latter units must
7158            --  suppress checks explicitly if this is needed.
7159
7160            if Is_Predefined_File_Name
7161                 (Unit_File_Name (Get_Source_Unit (Gen_Decl)))
7162            then
7163               Analyze (Act_Body, Suppress => All_Checks);
7164            else
7165               Analyze (Act_Body);
7166            end if;
7167         end if;
7168
7169         if not Generic_Separately_Compiled (Gen_Unit) then
7170            Inherit_Context (Gen_Body, Inst_Node);
7171         end if;
7172
7173         --  Remove the parent instances if they have been placed on the
7174         --  scope stack to compile the body.
7175
7176         if Parent_Installed then
7177            Remove_Parent (In_Body => True);
7178         end if;
7179
7180         Restore_Private_Views (Act_Decl_Id);
7181
7182         --  Remove the current unit from visibility if this is an instance
7183         --  that is not elaborated on the fly for inlining purposes.
7184
7185         if not Inlined_Body then
7186            Set_Is_Immediately_Visible (Act_Decl_Id, False);
7187         end if;
7188
7189         Restore_Env;
7190         Style_Check := Save_Style_Check;
7191
7192      --  If we have no body, and the unit requires a body, then complain.
7193      --  This complaint is suppressed if we have detected other errors
7194      --  (since a common reason for missing the body is that it had errors).
7195
7196      elsif Unit_Requires_Body (Gen_Unit) then
7197         if Serious_Errors_Detected = 0 then
7198            Error_Msg_NE
7199              ("cannot find body of generic package &", Inst_Node, Gen_Unit);
7200
7201         --  Don't attempt to perform any cleanup actions if some other
7202         --  error was aready detected, since this can cause blowups.
7203
7204         else
7205            return;
7206         end if;
7207
7208      --  Case of package that does not need a body
7209
7210      else
7211         --  If the instantiation of the declaration is a library unit,
7212         --  rewrite the original package instantiation as a package
7213         --  declaration in the compilation unit node.
7214
7215         if Nkind (Parent (Inst_Node)) = N_Compilation_Unit then
7216            Set_Parent_Spec (Act_Decl, Parent_Spec (Inst_Node));
7217            Rewrite (Inst_Node, Act_Decl);
7218
7219            --  Generate elaboration entity, in case spec has elaboration
7220            --  code. This cannot be done when the instance is analyzed,
7221            --  because it is not known yet whether the body exists.
7222
7223            Set_Elaboration_Entity_Required (Act_Decl_Id, False);
7224            Build_Elaboration_Entity (Parent (Inst_Node), Act_Decl_Id);
7225
7226         --  If the instantiation is not a library unit, then append the
7227         --  declaration to the list of implicitly generated entities.
7228         --  unless it is already a list member which means that it was
7229         --  already processed
7230
7231         elsif not Is_List_Member (Act_Decl) then
7232            Mark_Rewrite_Insertion (Act_Decl);
7233            Insert_Before (Inst_Node, Act_Decl);
7234         end if;
7235      end if;
7236
7237      Expander_Mode_Restore;
7238   end Instantiate_Package_Body;
7239
7240   ---------------------------------
7241   -- Instantiate_Subprogram_Body --
7242   ---------------------------------
7243
7244   procedure Instantiate_Subprogram_Body
7245     (Body_Info : Pending_Body_Info)
7246   is
7247      Act_Decl      : constant Node_Id    := Body_Info.Act_Decl;
7248      Inst_Node     : constant Node_Id    := Body_Info.Inst_Node;
7249      Loc           : constant Source_Ptr := Sloc (Inst_Node);
7250      Gen_Id        : constant Node_Id   := Name (Inst_Node);
7251      Gen_Unit      : constant Entity_Id := Get_Generic_Entity (Inst_Node);
7252      Gen_Decl      : constant Node_Id   := Unit_Declaration_Node (Gen_Unit);
7253      Anon_Id       : constant Entity_Id :=
7254                        Defining_Unit_Name (Specification (Act_Decl));
7255      Pack_Id       : constant Entity_Id :=
7256                        Defining_Unit_Name (Parent (Act_Decl));
7257      Decls         : List_Id;
7258      Gen_Body      : Node_Id;
7259      Gen_Body_Id   : Node_Id;
7260      Act_Body      : Node_Id;
7261      Act_Body_Id   : Entity_Id;
7262      Pack_Body     : Node_Id;
7263      Prev_Formal   : Entity_Id;
7264      Ret_Expr      : Node_Id;
7265      Unit_Renaming : Node_Id;
7266
7267      Parent_Installed : Boolean := False;
7268      Save_Style_Check : constant Boolean := Style_Check;
7269
7270   begin
7271      Gen_Body_Id := Corresponding_Body (Gen_Decl);
7272
7273      Expander_Mode_Save_And_Set (Body_Info.Expander_Status);
7274
7275      if No (Gen_Body_Id) then
7276         Load_Parent_Of_Generic (Inst_Node, Specification (Gen_Decl));
7277         Gen_Body_Id := Corresponding_Body (Gen_Decl);
7278      end if;
7279
7280      Instantiation_Node := Inst_Node;
7281
7282      if Present (Gen_Body_Id) then
7283         Gen_Body := Unit_Declaration_Node (Gen_Body_Id);
7284
7285         if Nkind (Gen_Body) = N_Subprogram_Body_Stub then
7286
7287            --  Either body is not present, or context is non-expanding, as
7288            --  when compiling a subunit. Mark the instance as completed.
7289
7290            Set_Has_Completion (Anon_Id);
7291            return;
7292         end if;
7293
7294         Save_Env (Gen_Unit, Anon_Id);
7295         Style_Check := False;
7296         Current_Sem_Unit := Body_Info.Current_Sem_Unit;
7297         Create_Instantiation_Source
7298           (Inst_Node,
7299            Gen_Body_Id,
7300            False,
7301            S_Adjustment);
7302
7303         Act_Body :=
7304           Copy_Generic_Node
7305             (Original_Node (Gen_Body), Empty, Instantiating => True);
7306         Act_Body_Id := Defining_Entity (Act_Body);
7307         Set_Chars (Act_Body_Id, Chars (Anon_Id));
7308         Set_Sloc (Act_Body_Id, Sloc (Defining_Entity (Inst_Node)));
7309         Set_Corresponding_Spec (Act_Body, Anon_Id);
7310         Set_Has_Completion (Anon_Id);
7311         Check_Generic_Actuals (Pack_Id, False);
7312
7313         --  If it is a child unit, make the parent instance (which is an
7314         --  instance of the parent of the generic) visible. The parent
7315         --  instance is the prefix of the name of the generic unit.
7316
7317         if Ekind (Scope (Gen_Unit)) = E_Generic_Package
7318           and then Nkind (Gen_Id) = N_Expanded_Name
7319         then
7320            Install_Parent (Entity (Prefix (Gen_Id)), In_Body => True);
7321            Parent_Installed := True;
7322
7323         elsif Is_Child_Unit (Gen_Unit) then
7324            Install_Parent (Scope (Gen_Unit), In_Body => True);
7325            Parent_Installed := True;
7326         end if;
7327
7328         --  Inside its body, a reference to the generic unit is a reference
7329         --  to the instance. The corresponding renaming is the first
7330         --  declaration in the body.
7331
7332         Unit_Renaming :=
7333           Make_Subprogram_Renaming_Declaration (Loc,
7334             Specification =>
7335               Copy_Generic_Node (
7336                 Specification (Original_Node (Gen_Body)),
7337                 Empty,
7338                 Instantiating => True),
7339             Name => New_Occurrence_Of (Anon_Id, Loc));
7340
7341         --  If there is a formal subprogram with the same name as the
7342         --  unit itself, do not add this renaming declaration. This is
7343         --  a temporary fix for one ACVC test. ???
7344
7345         Prev_Formal := First_Entity (Pack_Id);
7346         while Present (Prev_Formal) loop
7347            if Chars (Prev_Formal) = Chars (Gen_Unit)
7348              and then Is_Overloadable (Prev_Formal)
7349            then
7350               exit;
7351            end if;
7352
7353            Next_Entity (Prev_Formal);
7354         end loop;
7355
7356         if Present (Prev_Formal) then
7357            Decls :=  New_List (Act_Body);
7358         else
7359            Decls :=  New_List (Unit_Renaming, Act_Body);
7360         end if;
7361
7362         --  The subprogram body is placed in the body of a dummy package
7363         --  body, whose spec contains the subprogram declaration as well
7364         --  as the renaming declarations for the generic parameters.
7365
7366         Pack_Body := Make_Package_Body (Loc,
7367           Defining_Unit_Name => New_Copy (Pack_Id),
7368           Declarations       => Decls);
7369
7370         Set_Corresponding_Spec (Pack_Body, Pack_Id);
7371
7372         --  If the instantiation is a library unit, then build resulting
7373         --  compilation unit nodes for the instance. The declaration of
7374         --  the enclosing package is the grandparent of the subprogram
7375         --  declaration. First replace the instantiation node as the unit
7376         --  of the corresponding compilation.
7377
7378         if Nkind (Parent (Inst_Node)) = N_Compilation_Unit then
7379            if Parent (Inst_Node) = Cunit (Main_Unit) then
7380               Set_Unit (Parent (Inst_Node), Inst_Node);
7381               Build_Instance_Compilation_Unit_Nodes
7382                 (Inst_Node, Pack_Body, Parent (Parent (Act_Decl)));
7383               Analyze (Inst_Node);
7384            else
7385               Set_Parent (Pack_Body, Parent (Inst_Node));
7386               Analyze (Pack_Body);
7387            end if;
7388
7389         else
7390            Insert_Before (Inst_Node, Pack_Body);
7391            Mark_Rewrite_Insertion (Pack_Body);
7392            Analyze (Pack_Body);
7393
7394            if Expander_Active then
7395               Freeze_Subprogram_Body (Inst_Node, Gen_Body, Pack_Id);
7396            end if;
7397         end if;
7398
7399         if not Generic_Separately_Compiled (Gen_Unit) then
7400            Inherit_Context (Gen_Body, Inst_Node);
7401         end if;
7402
7403         Restore_Private_Views (Pack_Id, False);
7404
7405         if Parent_Installed then
7406            Remove_Parent (In_Body => True);
7407         end if;
7408
7409         Restore_Env;
7410         Style_Check := Save_Style_Check;
7411
7412      --  Body not found. Error was emitted already. If there were no
7413      --  previous errors, this may be an instance whose scope is a premature
7414      --  instance. In that case we must insure that the (legal) program does
7415      --  raise program error if executed. We generate a subprogram body for
7416      --  this purpose. See DEC ac30vso.
7417
7418      elsif Serious_Errors_Detected = 0
7419        and then Nkind (Parent (Inst_Node)) /= N_Compilation_Unit
7420      then
7421         if Ekind (Anon_Id) = E_Procedure then
7422            Act_Body :=
7423              Make_Subprogram_Body (Loc,
7424                 Specification              =>
7425                   Make_Procedure_Specification (Loc,
7426                     Defining_Unit_Name         => New_Copy (Anon_Id),
7427                       Parameter_Specifications =>
7428                       New_Copy_List
7429                         (Parameter_Specifications (Parent (Anon_Id)))),
7430
7431                 Declarations               => Empty_List,
7432                 Handled_Statement_Sequence =>
7433                   Make_Handled_Sequence_Of_Statements (Loc,
7434                     Statements =>
7435                       New_List (
7436                         Make_Raise_Program_Error (Loc,
7437                           Reason =>
7438                             PE_Access_Before_Elaboration))));
7439
7440         else
7441            Ret_Expr :=
7442              Make_Raise_Program_Error (Loc,
7443                Reason => PE_Access_Before_Elaboration);
7444
7445            Set_Etype (Ret_Expr, (Etype (Anon_Id)));
7446            Set_Analyzed (Ret_Expr);
7447
7448            Act_Body :=
7449              Make_Subprogram_Body (Loc,
7450                Specification =>
7451                  Make_Function_Specification (Loc,
7452                     Defining_Unit_Name         => New_Copy (Anon_Id),
7453                       Parameter_Specifications =>
7454                       New_Copy_List
7455                         (Parameter_Specifications (Parent (Anon_Id))),
7456                     Subtype_Mark =>
7457                       New_Occurrence_Of (Etype (Anon_Id), Loc)),
7458
7459                  Declarations               => Empty_List,
7460                  Handled_Statement_Sequence =>
7461                    Make_Handled_Sequence_Of_Statements (Loc,
7462                      Statements =>
7463                        New_List (Make_Return_Statement (Loc, Ret_Expr))));
7464         end if;
7465
7466         Pack_Body := Make_Package_Body (Loc,
7467           Defining_Unit_Name => New_Copy (Pack_Id),
7468           Declarations       => New_List (Act_Body));
7469
7470         Insert_After (Inst_Node, Pack_Body);
7471         Set_Corresponding_Spec (Pack_Body, Pack_Id);
7472         Analyze (Pack_Body);
7473      end if;
7474
7475      Expander_Mode_Restore;
7476   end Instantiate_Subprogram_Body;
7477
7478   ----------------------
7479   -- Instantiate_Type --
7480   ----------------------
7481
7482   function Instantiate_Type
7483     (Formal          : Node_Id;
7484      Actual          : Node_Id;
7485      Analyzed_Formal : Node_Id;
7486      Actual_Decls    : List_Id)
7487      return            Node_Id
7488   is
7489      Loc       : constant Source_Ptr := Sloc (Actual);
7490      Gen_T     : constant Entity_Id  := Defining_Identifier (Formal);
7491      A_Gen_T   : constant Entity_Id  := Defining_Identifier (Analyzed_Formal);
7492      Ancestor  : Entity_Id := Empty;
7493      Def       : constant Node_Id    := Formal_Type_Definition (Formal);
7494      Act_T     : Entity_Id;
7495      Decl_Node : Node_Id;
7496
7497      procedure Validate_Array_Type_Instance;
7498      procedure Validate_Access_Subprogram_Instance;
7499      procedure Validate_Access_Type_Instance;
7500      procedure Validate_Derived_Type_Instance;
7501      procedure Validate_Private_Type_Instance;
7502      --  These procedures perform validation tests for the named case
7503
7504      function Subtypes_Match (Gen_T, Act_T : Entity_Id) return Boolean;
7505      --  Check that base types are the same and that the subtypes match
7506      --  statically. Used in several of the above.
7507
7508      --------------------
7509      -- Subtypes_Match --
7510      --------------------
7511
7512      function Subtypes_Match (Gen_T, Act_T : Entity_Id) return Boolean is
7513         T : constant Entity_Id := Get_Instance_Of (Gen_T);
7514
7515      begin
7516         return (Base_Type (T) = Base_Type (Act_T)
7517--  why is the and then commented out here???
7518--                  and then Is_Constrained (T) = Is_Constrained (Act_T)
7519                  and then Subtypes_Statically_Match (T, Act_T))
7520
7521           or else (Is_Class_Wide_Type (Gen_T)
7522                     and then Is_Class_Wide_Type (Act_T)
7523                     and then
7524                       Subtypes_Match (
7525                         Get_Instance_Of (Root_Type (Gen_T)),
7526                         Root_Type (Act_T)));
7527      end Subtypes_Match;
7528
7529      -----------------------------------------
7530      -- Validate_Access_Subprogram_Instance --
7531      -----------------------------------------
7532
7533      procedure Validate_Access_Subprogram_Instance is
7534      begin
7535         if not Is_Access_Type (Act_T)
7536           or else Ekind (Designated_Type (Act_T)) /= E_Subprogram_Type
7537         then
7538            Error_Msg_NE
7539              ("expect access type in instantiation of &", Actual, Gen_T);
7540            Abandon_Instantiation (Actual);
7541         end if;
7542
7543         Check_Mode_Conformant
7544           (Designated_Type (Act_T),
7545            Designated_Type (A_Gen_T),
7546            Actual,
7547            Get_Inst => True);
7548
7549         if Ekind (Base_Type (Act_T)) = E_Access_Protected_Subprogram_Type then
7550            if Ekind (A_Gen_T) = E_Access_Subprogram_Type then
7551               Error_Msg_NE
7552                 ("protected access type not allowed for formal &",
7553                  Actual, Gen_T);
7554            end if;
7555
7556         elsif Ekind (A_Gen_T) = E_Access_Protected_Subprogram_Type then
7557            Error_Msg_NE
7558              ("expect protected access type for formal &",
7559               Actual, Gen_T);
7560         end if;
7561      end Validate_Access_Subprogram_Instance;
7562
7563      -----------------------------------
7564      -- Validate_Access_Type_Instance --
7565      -----------------------------------
7566
7567      procedure Validate_Access_Type_Instance is
7568         Desig_Type : constant Entity_Id :=
7569                        Find_Actual_Type
7570                          (Designated_Type (A_Gen_T), Scope (A_Gen_T));
7571
7572      begin
7573         if not Is_Access_Type (Act_T) then
7574            Error_Msg_NE
7575              ("expect access type in instantiation of &", Actual, Gen_T);
7576            Abandon_Instantiation (Actual);
7577         end if;
7578
7579         if Is_Access_Constant (A_Gen_T) then
7580            if not Is_Access_Constant (Act_T) then
7581               Error_Msg_N
7582                 ("actual type must be access-to-constant type", Actual);
7583               Abandon_Instantiation (Actual);
7584            end if;
7585         else
7586            if Is_Access_Constant (Act_T) then
7587               Error_Msg_N
7588                 ("actual type must be access-to-variable type", Actual);
7589               Abandon_Instantiation (Actual);
7590
7591            elsif Ekind (A_Gen_T) = E_General_Access_Type
7592              and then Ekind (Base_Type (Act_T)) /= E_General_Access_Type
7593            then
7594               Error_Msg_N ("actual must be general access type!", Actual);
7595               Error_Msg_NE ("add ALL to }!", Actual, Act_T);
7596               Abandon_Instantiation (Actual);
7597            end if;
7598         end if;
7599
7600         --  The designated subtypes, that is to say the subtypes introduced
7601         --  by an access type declaration (and not by a subtype declaration)
7602         --  must match.
7603
7604         if not Subtypes_Match
7605           (Desig_Type, Designated_Type (Base_Type (Act_T)))
7606         then
7607            Error_Msg_NE
7608              ("designated type of actual does not match that of formal &",
7609                 Actual, Gen_T);
7610            Abandon_Instantiation (Actual);
7611
7612         elsif Is_Access_Type (Designated_Type (Act_T))
7613           and then Is_Constrained (Designated_Type (Designated_Type (Act_T)))
7614                      /=
7615                  Is_Constrained (Designated_Type (Desig_Type))
7616         then
7617            Error_Msg_NE
7618              ("designated type of actual does not match that of formal &",
7619                 Actual, Gen_T);
7620            Abandon_Instantiation (Actual);
7621         end if;
7622      end Validate_Access_Type_Instance;
7623
7624      ----------------------------------
7625      -- Validate_Array_Type_Instance --
7626      ----------------------------------
7627
7628      procedure Validate_Array_Type_Instance is
7629         I1 : Node_Id;
7630         I2 : Node_Id;
7631         T2 : Entity_Id;
7632
7633         function Formal_Dimensions return Int;
7634         --  Count number of dimensions in array type formal
7635
7636         function Formal_Dimensions return Int is
7637            Num   : Int := 0;
7638            Index : Node_Id;
7639
7640         begin
7641            if Nkind (Def) = N_Constrained_Array_Definition then
7642               Index := First (Discrete_Subtype_Definitions (Def));
7643            else
7644               Index := First (Subtype_Marks (Def));
7645            end if;
7646
7647            while Present (Index) loop
7648               Num := Num + 1;
7649               Next_Index (Index);
7650            end loop;
7651
7652            return Num;
7653         end Formal_Dimensions;
7654
7655      --  Start of processing for Validate_Array_Type_Instance
7656
7657      begin
7658         if not Is_Array_Type (Act_T) then
7659            Error_Msg_NE
7660              ("expect array type in instantiation of &", Actual, Gen_T);
7661            Abandon_Instantiation (Actual);
7662
7663         elsif Nkind (Def) = N_Constrained_Array_Definition then
7664            if not (Is_Constrained (Act_T)) then
7665               Error_Msg_NE
7666                 ("expect constrained array in instantiation of &",
7667                  Actual, Gen_T);
7668               Abandon_Instantiation (Actual);
7669            end if;
7670
7671         else
7672            if Is_Constrained (Act_T) then
7673               Error_Msg_NE
7674                 ("expect unconstrained array in instantiation of &",
7675                  Actual, Gen_T);
7676               Abandon_Instantiation (Actual);
7677            end if;
7678         end if;
7679
7680         if Formal_Dimensions /= Number_Dimensions (Act_T) then
7681            Error_Msg_NE
7682              ("dimensions of actual do not match formal &", Actual, Gen_T);
7683            Abandon_Instantiation (Actual);
7684         end if;
7685
7686         I1 := First_Index (A_Gen_T);
7687         I2 := First_Index (Act_T);
7688         for J in 1 .. Formal_Dimensions loop
7689
7690            --  If the indices of the actual were given by a subtype_mark,
7691            --  the index was transformed into a range attribute. Retrieve
7692            --  the original type mark for checking.
7693
7694            if Is_Entity_Name (Original_Node (I2)) then
7695               T2 := Entity (Original_Node (I2));
7696            else
7697               T2 := Etype (I2);
7698            end if;
7699
7700            if not Subtypes_Match
7701              (Find_Actual_Type (Etype (I1), Scope (A_Gen_T)), T2)
7702            then
7703               Error_Msg_NE
7704                 ("index types of actual do not match those of formal &",
7705                  Actual, Gen_T);
7706               Abandon_Instantiation (Actual);
7707            end if;
7708
7709            Next_Index (I1);
7710            Next_Index (I2);
7711         end loop;
7712
7713         if not Subtypes_Match (
7714            Find_Actual_Type (Component_Type (A_Gen_T), Scope (A_Gen_T)),
7715            Component_Type (Act_T))
7716         then
7717            Error_Msg_NE
7718              ("component subtype of actual does not match that of formal &",
7719               Actual, Gen_T);
7720            Abandon_Instantiation (Actual);
7721         end if;
7722
7723         if Has_Aliased_Components (A_Gen_T)
7724           and then not Has_Aliased_Components (Act_T)
7725         then
7726            Error_Msg_NE
7727              ("actual must have aliased components to match formal type &",
7728               Actual, Gen_T);
7729         end if;
7730
7731      end Validate_Array_Type_Instance;
7732
7733      ------------------------------------
7734      -- Validate_Derived_Type_Instance --
7735      ------------------------------------
7736
7737      procedure Validate_Derived_Type_Instance is
7738         Actual_Discr   : Entity_Id;
7739         Ancestor_Discr : Entity_Id;
7740
7741      begin
7742         --  If the parent type in the generic declaration is itself
7743         --  a previous formal type, then it is local to the generic
7744         --  and absent from the analyzed generic definition. In  that
7745         --  case the ancestor is the instance of the formal (which must
7746         --  have been instantiated previously), unless the ancestor is
7747         --  itself a formal derived type. In this latter case (which is the
7748         --  subject of Corrigendum 8652/0038 (AI-202) the ancestor of the
7749         --  formals is the ancestor of its parent. Otherwise, the analyzed
7750         --  generic carries the parent type. If the parent type is defined
7751         --  in a previous formal package, then the scope of that formal
7752         --  package is that of the generic type itself, and it has already
7753         --  been mapped into the corresponding type in the actual package.
7754
7755         --  Common case: parent type defined outside of the generic
7756
7757         if Is_Entity_Name (Subtype_Mark (Def))
7758           and then Present (Entity (Subtype_Mark (Def)))
7759         then
7760            Ancestor := Get_Instance_Of (Entity (Subtype_Mark (Def)));
7761
7762         --  Check whether parent is defined in a previous formal package
7763
7764         elsif
7765           Scope (Scope (Base_Type (Etype (A_Gen_T)))) = Scope (A_Gen_T)
7766         then
7767            Ancestor :=
7768              Get_Instance_Of (Base_Type (Etype (A_Gen_T)));
7769
7770         --  The type may be a local derivation, or a type extension of
7771         --  a previous formal, or of a formal of a parent package.
7772
7773         elsif Is_Derived_Type (Get_Instance_Of (A_Gen_T))
7774          or else
7775            Ekind (Get_Instance_Of (A_Gen_T)) = E_Record_Type_With_Private
7776         then
7777            --  Check whether the parent is another derived formal type
7778            --  in the same generic unit.
7779
7780            if Etype (A_Gen_T) /= A_Gen_T
7781              and then Is_Generic_Type (Etype (A_Gen_T))
7782              and then Scope (Etype (A_Gen_T)) = Scope (A_Gen_T)
7783              and then Etype (Etype (A_Gen_T)) /= Etype (A_Gen_T)
7784            then
7785               --  Locate ancestor of parent from the subtype declaration
7786               --  created for the actual.
7787
7788               declare
7789                  Decl : Node_Id;
7790
7791               begin
7792                  Decl := First (Actual_Decls);
7793                  while Present (Decl) loop
7794                     if Nkind (Decl) = N_Subtype_Declaration
7795                       and then Chars (Defining_Identifier (Decl)) =
7796                                                    Chars (Etype (A_Gen_T))
7797                     then
7798                        Ancestor := Generic_Parent_Type (Decl);
7799                        exit;
7800                     else
7801                        Next (Decl);
7802                     end if;
7803                  end loop;
7804               end;
7805
7806               pragma Assert (Present (Ancestor));
7807
7808            else
7809               Ancestor :=
7810                 Get_Instance_Of (Base_Type (Get_Instance_Of (A_Gen_T)));
7811            end if;
7812
7813         else
7814            Ancestor := Get_Instance_Of (Etype (Base_Type (A_Gen_T)));
7815         end if;
7816
7817         if not Is_Ancestor (Base_Type (Ancestor), Act_T) then
7818            Error_Msg_NE
7819              ("expect type derived from & in instantiation",
7820               Actual, First_Subtype (Ancestor));
7821            Abandon_Instantiation (Actual);
7822         end if;
7823
7824         --  Perform atomic/volatile checks (RM C.6(12))
7825
7826         if Is_Atomic (Act_T) and then not Is_Atomic (Ancestor) then
7827            Error_Msg_N
7828              ("cannot have atomic actual type for non-atomic formal type",
7829               Actual);
7830
7831         elsif Is_Volatile (Act_T)
7832           and then not Is_Volatile (Ancestor)
7833           and then Is_By_Reference_Type (Ancestor)
7834         then
7835            Error_Msg_N
7836              ("cannot have volatile actual type for non-volatile formal type",
7837               Actual);
7838         end if;
7839
7840         --  It should not be necessary to check for unknown discriminants
7841         --  on Formal, but for some reason Has_Unknown_Discriminants is
7842         --  false for A_Gen_T, so Is_Indefinite_Subtype incorrectly
7843         --  returns False. This needs fixing. ???
7844
7845         if not Is_Indefinite_Subtype (A_Gen_T)
7846           and then not Unknown_Discriminants_Present (Formal)
7847           and then Is_Indefinite_Subtype (Act_T)
7848         then
7849            Error_Msg_N
7850              ("actual subtype must be constrained", Actual);
7851            Abandon_Instantiation (Actual);
7852         end if;
7853
7854         if not Unknown_Discriminants_Present (Formal) then
7855            if Is_Constrained (Ancestor) then
7856               if not Is_Constrained (Act_T) then
7857                  Error_Msg_N
7858                    ("actual subtype must be constrained", Actual);
7859                  Abandon_Instantiation (Actual);
7860               end if;
7861
7862            --  Ancestor is unconstrained
7863
7864            elsif Is_Constrained (Act_T) then
7865               if Ekind (Ancestor) = E_Access_Type
7866                 or else Is_Composite_Type (Ancestor)
7867               then
7868                  Error_Msg_N
7869                    ("actual subtype must be unconstrained", Actual);
7870                  Abandon_Instantiation (Actual);
7871               end if;
7872
7873            --  A class-wide type is only allowed if the formal has
7874            --  unknown discriminants.
7875
7876            elsif Is_Class_Wide_Type (Act_T)
7877              and then not Has_Unknown_Discriminants (Ancestor)
7878            then
7879               Error_Msg_NE
7880                 ("actual for & cannot be a class-wide type", Actual, Gen_T);
7881               Abandon_Instantiation (Actual);
7882
7883            --  Otherwise, the formal and actual shall have the same
7884            --  number of discriminants and each discriminant of the
7885            --  actual must correspond to a discriminant of the formal.
7886
7887            elsif Has_Discriminants (Act_T)
7888              and then Has_Discriminants (Ancestor)
7889            then
7890               Actual_Discr   := First_Discriminant (Act_T);
7891               Ancestor_Discr := First_Discriminant (Ancestor);
7892               while Present (Actual_Discr)
7893                 and then Present (Ancestor_Discr)
7894               loop
7895                  if Base_Type (Act_T) /= Base_Type (Ancestor) and then
7896                    not Present (Corresponding_Discriminant (Actual_Discr))
7897                  then
7898                     Error_Msg_NE
7899                       ("discriminant & does not correspond " &
7900                        "to ancestor discriminant", Actual, Actual_Discr);
7901                     Abandon_Instantiation (Actual);
7902                  end if;
7903
7904                  Next_Discriminant (Actual_Discr);
7905                  Next_Discriminant (Ancestor_Discr);
7906               end loop;
7907
7908               if Present (Actual_Discr) or else Present (Ancestor_Discr) then
7909                  Error_Msg_NE
7910                    ("actual for & must have same number of discriminants",
7911                     Actual, Gen_T);
7912                  Abandon_Instantiation (Actual);
7913               end if;
7914
7915            --  This case should be caught by the earlier check for
7916            --  for constrainedness, but the check here is added for
7917            --  completeness.
7918
7919            elsif Has_Discriminants (Act_T) then
7920               Error_Msg_NE
7921                 ("actual for & must not have discriminants", Actual, Gen_T);
7922               Abandon_Instantiation (Actual);
7923
7924            elsif Has_Discriminants (Ancestor) then
7925               Error_Msg_NE
7926                 ("actual for & must have known discriminants", Actual, Gen_T);
7927               Abandon_Instantiation (Actual);
7928            end if;
7929
7930            if not Subtypes_Statically_Compatible (Act_T, Ancestor) then
7931               Error_Msg_N
7932                 ("constraint on actual is incompatible with formal", Actual);
7933               Abandon_Instantiation (Actual);
7934            end if;
7935         end if;
7936      end Validate_Derived_Type_Instance;
7937
7938      ------------------------------------
7939      -- Validate_Private_Type_Instance --
7940      ------------------------------------
7941
7942      procedure Validate_Private_Type_Instance is
7943         Formal_Discr : Entity_Id;
7944         Actual_Discr : Entity_Id;
7945         Formal_Subt  : Entity_Id;
7946
7947      begin
7948         if Is_Limited_Type (Act_T)
7949           and then not Is_Limited_Type (A_Gen_T)
7950         then
7951            Error_Msg_NE
7952              ("actual for non-limited  & cannot be a limited type", Actual,
7953               Gen_T);
7954            Explain_Limited_Type (Act_T, Actual);
7955            Abandon_Instantiation (Actual);
7956
7957         elsif Is_Indefinite_Subtype (Act_T)
7958            and then not Is_Indefinite_Subtype (A_Gen_T)
7959            and then Ada_95
7960         then
7961            Error_Msg_NE
7962              ("actual for & must be a definite subtype", Actual, Gen_T);
7963
7964         elsif not Is_Tagged_Type (Act_T)
7965           and then Is_Tagged_Type (A_Gen_T)
7966         then
7967            Error_Msg_NE
7968              ("actual for & must be a tagged type", Actual, Gen_T);
7969
7970         elsif Has_Discriminants (A_Gen_T) then
7971            if not Has_Discriminants (Act_T) then
7972               Error_Msg_NE
7973                 ("actual for & must have discriminants", Actual, Gen_T);
7974               Abandon_Instantiation (Actual);
7975
7976            elsif Is_Constrained (Act_T) then
7977               Error_Msg_NE
7978                 ("actual for & must be unconstrained", Actual, Gen_T);
7979               Abandon_Instantiation (Actual);
7980
7981            else
7982               Formal_Discr := First_Discriminant (A_Gen_T);
7983               Actual_Discr := First_Discriminant (Act_T);
7984               while Formal_Discr /= Empty loop
7985                  if Actual_Discr = Empty then
7986                     Error_Msg_NE
7987                       ("discriminants on actual do not match formal",
7988                        Actual, Gen_T);
7989                     Abandon_Instantiation (Actual);
7990                  end if;
7991
7992                  Formal_Subt := Get_Instance_Of (Etype (Formal_Discr));
7993
7994                  --  access discriminants match if designated types do.
7995
7996                  if Ekind (Base_Type (Formal_Subt)) = E_Anonymous_Access_Type
7997                    and then (Ekind (Base_Type (Etype (Actual_Discr))))
7998                      = E_Anonymous_Access_Type
7999                    and then Get_Instance_Of (
8000                      Designated_Type (Base_Type (Formal_Subt)))
8001                      = Designated_Type (Base_Type (Etype (Actual_Discr)))
8002                  then
8003                     null;
8004
8005                  elsif Base_Type (Formal_Subt) /=
8006                                       Base_Type (Etype (Actual_Discr))
8007                  then
8008                     Error_Msg_NE
8009                       ("types of actual discriminants must match formal",
8010                        Actual, Gen_T);
8011                     Abandon_Instantiation (Actual);
8012
8013                  elsif not Subtypes_Statically_Match
8014                              (Formal_Subt, Etype (Actual_Discr))
8015                    and then Ada_95
8016                  then
8017                     Error_Msg_NE
8018                       ("subtypes of actual discriminants must match formal",
8019                        Actual, Gen_T);
8020                     Abandon_Instantiation (Actual);
8021                  end if;
8022
8023                  Next_Discriminant (Formal_Discr);
8024                  Next_Discriminant (Actual_Discr);
8025               end loop;
8026
8027               if Actual_Discr /= Empty then
8028                  Error_Msg_NE
8029                    ("discriminants on actual do not match formal",
8030                     Actual, Gen_T);
8031                  Abandon_Instantiation (Actual);
8032               end if;
8033            end if;
8034
8035         end if;
8036
8037         Ancestor := Gen_T;
8038      end Validate_Private_Type_Instance;
8039
8040   --  Start of processing for Instantiate_Type
8041
8042   begin
8043      if Get_Instance_Of (A_Gen_T) /= A_Gen_T then
8044         Error_Msg_N ("duplicate instantiation of generic type", Actual);
8045         return Error;
8046
8047      elsif not Is_Entity_Name (Actual)
8048        or else not Is_Type (Entity (Actual))
8049      then
8050         Error_Msg_NE
8051           ("expect valid subtype mark to instantiate &", Actual, Gen_T);
8052         Abandon_Instantiation (Actual);
8053
8054      else
8055         Act_T := Entity (Actual);
8056
8057         --  Deal with fixed/floating restrictions
8058
8059         if Is_Floating_Point_Type (Act_T) then
8060            Check_Restriction (No_Floating_Point, Actual);
8061         elsif Is_Fixed_Point_Type (Act_T) then
8062            Check_Restriction (No_Fixed_Point, Actual);
8063         end if;
8064
8065         --  Deal with error of using incomplete type as generic actual
8066
8067         if Ekind (Act_T) = E_Incomplete_Type then
8068            if No (Underlying_Type (Act_T)) then
8069               Error_Msg_N ("premature use of incomplete type", Actual);
8070               Abandon_Instantiation (Actual);
8071            else
8072               Act_T := Full_View (Act_T);
8073               Set_Entity (Actual, Act_T);
8074
8075               if Has_Private_Component (Act_T) then
8076                  Error_Msg_N
8077                    ("premature use of type with private component", Actual);
8078               end if;
8079            end if;
8080
8081         --  Deal with error of premature use of private type as generic actual
8082
8083         elsif Is_Private_Type (Act_T)
8084           and then Is_Private_Type (Base_Type (Act_T))
8085           and then not Is_Generic_Type (Act_T)
8086           and then not Is_Derived_Type (Act_T)
8087           and then No (Full_View (Root_Type (Act_T)))
8088         then
8089            Error_Msg_N ("premature use of private type", Actual);
8090
8091         elsif Has_Private_Component (Act_T) then
8092            Error_Msg_N
8093              ("premature use of type with private component", Actual);
8094         end if;
8095
8096         Set_Instance_Of (A_Gen_T, Act_T);
8097
8098         --  If the type is generic, the class-wide type may also be used
8099
8100         if Is_Tagged_Type (A_Gen_T)
8101           and then Is_Tagged_Type (Act_T)
8102           and then not Is_Class_Wide_Type (A_Gen_T)
8103         then
8104            Set_Instance_Of (Class_Wide_Type (A_Gen_T),
8105              Class_Wide_Type (Act_T));
8106         end if;
8107
8108         if not Is_Abstract (A_Gen_T)
8109           and then Is_Abstract (Act_T)
8110         then
8111            Error_Msg_N
8112              ("actual of non-abstract formal cannot be abstract", Actual);
8113         end if;
8114
8115         if Is_Scalar_Type (Gen_T) then
8116            Set_Instance_Of (Etype (A_Gen_T), Etype (Act_T));
8117         end if;
8118      end if;
8119
8120      case Nkind (Def) is
8121         when N_Formal_Private_Type_Definition =>
8122            Validate_Private_Type_Instance;
8123
8124         when N_Formal_Derived_Type_Definition =>
8125            Validate_Derived_Type_Instance;
8126
8127         when N_Formal_Discrete_Type_Definition =>
8128            if not Is_Discrete_Type (Act_T) then
8129               Error_Msg_NE
8130                 ("expect discrete type in instantiation of&", Actual, Gen_T);
8131               Abandon_Instantiation (Actual);
8132            end if;
8133
8134         when N_Formal_Signed_Integer_Type_Definition =>
8135            if not Is_Signed_Integer_Type (Act_T) then
8136               Error_Msg_NE
8137                 ("expect signed integer type in instantiation of&",
8138                  Actual, Gen_T);
8139               Abandon_Instantiation (Actual);
8140            end if;
8141
8142         when N_Formal_Modular_Type_Definition =>
8143            if not Is_Modular_Integer_Type (Act_T) then
8144               Error_Msg_NE
8145                 ("expect modular type in instantiation of &", Actual, Gen_T);
8146               Abandon_Instantiation (Actual);
8147            end if;
8148
8149         when N_Formal_Floating_Point_Definition =>
8150            if not Is_Floating_Point_Type (Act_T) then
8151               Error_Msg_NE
8152                 ("expect float type in instantiation of &", Actual, Gen_T);
8153               Abandon_Instantiation (Actual);
8154            end if;
8155
8156         when N_Formal_Ordinary_Fixed_Point_Definition =>
8157            if not Is_Ordinary_Fixed_Point_Type (Act_T) then
8158               Error_Msg_NE
8159                 ("expect ordinary fixed point type in instantiation of &",
8160                  Actual, Gen_T);
8161               Abandon_Instantiation (Actual);
8162            end if;
8163
8164         when N_Formal_Decimal_Fixed_Point_Definition =>
8165            if not Is_Decimal_Fixed_Point_Type (Act_T) then
8166               Error_Msg_NE
8167                 ("expect decimal type in instantiation of &",
8168                  Actual, Gen_T);
8169               Abandon_Instantiation (Actual);
8170            end if;
8171
8172         when N_Array_Type_Definition =>
8173            Validate_Array_Type_Instance;
8174
8175         when N_Access_To_Object_Definition =>
8176            Validate_Access_Type_Instance;
8177
8178         when N_Access_Function_Definition |
8179              N_Access_Procedure_Definition =>
8180            Validate_Access_Subprogram_Instance;
8181
8182         when others =>
8183            raise Program_Error;
8184
8185      end case;
8186
8187      Decl_Node :=
8188        Make_Subtype_Declaration (Loc,
8189          Defining_Identifier => New_Copy (Gen_T),
8190          Subtype_Indication  => New_Reference_To (Act_T, Loc));
8191
8192      if Is_Private_Type (Act_T) then
8193         Set_Has_Private_View (Subtype_Indication (Decl_Node));
8194
8195      elsif Is_Access_Type (Act_T)
8196        and then Is_Private_Type (Designated_Type (Act_T))
8197      then
8198         Set_Has_Private_View (Subtype_Indication (Decl_Node));
8199      end if;
8200
8201      --  Flag actual derived types so their elaboration produces the
8202      --  appropriate renamings for the primitive operations of the ancestor.
8203      --  Flag actual for formal private types as well, to determine whether
8204      --  operations in the private part may override inherited operations.
8205
8206      if Nkind (Def) = N_Formal_Derived_Type_Definition
8207        or else Nkind (Def) = N_Formal_Private_Type_Definition
8208      then
8209         Set_Generic_Parent_Type (Decl_Node, Ancestor);
8210      end if;
8211
8212      return Decl_Node;
8213   end Instantiate_Type;
8214
8215   ---------------------
8216   -- Is_In_Main_Unit --
8217   ---------------------
8218
8219   function Is_In_Main_Unit (N : Node_Id) return Boolean is
8220      Unum : constant Unit_Number_Type := Get_Source_Unit (N);
8221
8222      Current_Unit : Node_Id;
8223
8224   begin
8225      if Unum = Main_Unit then
8226         return True;
8227
8228      --  If the current unit is a subunit then it is either the main unit
8229      --  or is being compiled as part of the main unit.
8230
8231      elsif Nkind (N) = N_Compilation_Unit then
8232         return Nkind (Unit (N)) = N_Subunit;
8233      end if;
8234
8235      Current_Unit := Parent (N);
8236      while Present (Current_Unit)
8237        and then Nkind (Current_Unit) /= N_Compilation_Unit
8238      loop
8239         Current_Unit := Parent (Current_Unit);
8240      end loop;
8241
8242      --  The instantiation node is in the main unit, or else the current
8243      --  node (perhaps as the result of nested instantiations) is in the
8244      --  main unit, or in the declaration of the main unit, which in this
8245      --  last case must be a body.
8246
8247      return Unum = Main_Unit
8248        or else Current_Unit = Cunit (Main_Unit)
8249        or else Current_Unit = Library_Unit (Cunit (Main_Unit))
8250        or else (Present (Library_Unit (Current_Unit))
8251                  and then Is_In_Main_Unit (Library_Unit (Current_Unit)));
8252   end Is_In_Main_Unit;
8253
8254   ----------------------------
8255   -- Load_Parent_Of_Generic --
8256   ----------------------------
8257
8258   procedure Load_Parent_Of_Generic (N : Node_Id; Spec : Node_Id) is
8259      Comp_Unit        : constant Node_Id := Cunit (Get_Source_Unit (Spec));
8260      Save_Style_Check : constant Boolean := Style_Check;
8261      True_Parent      : Node_Id;
8262      Inst_Node        : Node_Id;
8263      OK               : Boolean;
8264
8265   begin
8266      if not In_Same_Source_Unit (N, Spec)
8267        or else Nkind (Unit (Comp_Unit)) = N_Package_Declaration
8268        or else (Nkind (Unit (Comp_Unit)) = N_Package_Body
8269                   and then not Is_In_Main_Unit (Spec))
8270      then
8271         --  Find body of parent of spec, and analyze it. A special case
8272         --  arises when the parent is an instantiation, that is to say when
8273         --  we are currently instantiating a nested generic. In that case,
8274         --  there is no separate file for the body of the enclosing instance.
8275         --  Instead, the enclosing body must be instantiated as if it were
8276         --  a pending instantiation, in order to produce the body for the
8277         --  nested generic we require now. Note that in that case the
8278         --  generic may be defined in a package body, the instance defined
8279         --  in the same package body, and the original enclosing body may not
8280         --  be in the main unit.
8281
8282         True_Parent := Parent (Spec);
8283         Inst_Node   := Empty;
8284
8285         while Present (True_Parent)
8286           and then Nkind (True_Parent) /= N_Compilation_Unit
8287         loop
8288            if Nkind (True_Parent) = N_Package_Declaration
8289              and then
8290                Nkind (Original_Node (True_Parent)) = N_Package_Instantiation
8291            then
8292               --  Parent is a compilation unit that is an instantiation.
8293               --  Instantiation node has been replaced with package decl.
8294
8295               Inst_Node := Original_Node (True_Parent);
8296               exit;
8297
8298            elsif Nkind (True_Parent) = N_Package_Declaration
8299              and then Present (Generic_Parent (Specification (True_Parent)))
8300              and then Nkind (Parent (True_Parent)) /= N_Compilation_Unit
8301            then
8302               --  Parent is an instantiation within another specification.
8303               --  Declaration for instance has been inserted before original
8304               --  instantiation node. A direct link would be preferable?
8305
8306               Inst_Node := Next (True_Parent);
8307
8308               while Present (Inst_Node)
8309                 and then Nkind (Inst_Node) /= N_Package_Instantiation
8310               loop
8311                  Next (Inst_Node);
8312               end loop;
8313
8314               --  If the instance appears within a generic, and the generic
8315               --  unit is defined within a formal package of the enclosing
8316               --  generic, there is no generic body available, and none
8317               --  needed. A more precise test should be used ???
8318
8319               if No (Inst_Node) then
8320                  return;
8321               end if;
8322
8323               exit;
8324            else
8325               True_Parent := Parent (True_Parent);
8326            end if;
8327         end loop;
8328
8329         --  Case where we are currently instantiating a nested generic
8330
8331         if Present (Inst_Node) then
8332            if Nkind (Parent (True_Parent)) = N_Compilation_Unit then
8333
8334               --  Instantiation node and declaration of instantiated package
8335               --  were exchanged when only the declaration was needed.
8336               --  Restore instantiation node before proceeding with body.
8337
8338               Set_Unit (Parent (True_Parent), Inst_Node);
8339            end if;
8340
8341            --  Now complete instantiation of enclosing body, if it appears
8342            --  in some other unit. If it appears in the current unit, the
8343            --  body will have been instantiated already.
8344
8345            if No (Corresponding_Body (Instance_Spec (Inst_Node))) then
8346
8347               --  We need to determine the expander mode to instantiate
8348               --  the enclosing body. Because the generic body we need
8349               --  may use global entities declared in the enclosing package
8350               --  (including aggregates) it is in general necessary to
8351               --  compile this body with expansion enabled. The exception
8352               --  is if we are within a generic package, in which case
8353               --  the usual generic rule applies.
8354
8355               declare
8356                  Exp_Status : Boolean := True;
8357                  Scop       : Entity_Id;
8358
8359               begin
8360                  --  Loop through scopes looking for generic package
8361
8362                  Scop := Scope (Defining_Entity (Instance_Spec (Inst_Node)));
8363                  while Present (Scop)
8364                    and then Scop /= Standard_Standard
8365                  loop
8366                     if Ekind (Scop) = E_Generic_Package then
8367                        Exp_Status := False;
8368                        exit;
8369                     end if;
8370
8371                     Scop := Scope (Scop);
8372                  end loop;
8373
8374                  Instantiate_Package_Body
8375                    (Pending_Body_Info'(
8376                       Inst_Node, True_Parent, Exp_Status,
8377                         Get_Code_Unit (Sloc (Inst_Node))));
8378               end;
8379            end if;
8380
8381         --  Case where we are not instantiating a nested generic
8382
8383         else
8384            Opt.Style_Check := False;
8385            Expander_Mode_Save_And_Set (True);
8386            Load_Needed_Body (Comp_Unit, OK);
8387            Opt.Style_Check := Save_Style_Check;
8388            Expander_Mode_Restore;
8389
8390            if not OK
8391              and then Unit_Requires_Body (Defining_Entity (Spec))
8392            then
8393               declare
8394                  Bname : constant Unit_Name_Type :=
8395                            Get_Body_Name (Get_Unit_Name (Unit (Comp_Unit)));
8396
8397               begin
8398                  Error_Msg_Unit_1 := Bname;
8399                  Error_Msg_N ("this instantiation requires$!", N);
8400                  Error_Msg_Name_1 :=
8401                    Get_File_Name (Bname, Subunit => False);
8402                  Error_Msg_N ("\but file{ was not found!", N);
8403                  raise Unrecoverable_Error;
8404               end;
8405            end if;
8406         end if;
8407      end if;
8408
8409      --  If loading the parent of the generic caused an instantiation
8410      --  circularity, we abandon compilation at this point, because
8411      --  otherwise in some cases we get into trouble with infinite
8412      --  recursions after this point.
8413
8414      if Circularity_Detected then
8415         raise Unrecoverable_Error;
8416      end if;
8417   end Load_Parent_Of_Generic;
8418
8419   -----------------------
8420   -- Move_Freeze_Nodes --
8421   -----------------------
8422
8423   procedure Move_Freeze_Nodes
8424     (Out_Of : Entity_Id;
8425      After  : Node_Id;
8426      L      : List_Id)
8427   is
8428      Decl      : Node_Id;
8429      Next_Decl : Node_Id;
8430      Next_Node : Node_Id := After;
8431      Spec      : Node_Id;
8432
8433      function Is_Outer_Type (T : Entity_Id) return Boolean;
8434      --  Check whether entity is declared in a scope external to that
8435      --  of the generic unit.
8436
8437      -------------------
8438      -- Is_Outer_Type --
8439      -------------------
8440
8441      function Is_Outer_Type (T : Entity_Id) return Boolean is
8442         Scop : Entity_Id := Scope (T);
8443
8444      begin
8445         if Scope_Depth (Scop) < Scope_Depth (Out_Of) then
8446            return True;
8447
8448         else
8449            while Scop /= Standard_Standard loop
8450
8451               if Scop = Out_Of then
8452                  return False;
8453               else
8454                  Scop := Scope (Scop);
8455               end if;
8456            end loop;
8457
8458            return True;
8459         end if;
8460      end Is_Outer_Type;
8461
8462   --  Start of processing for Move_Freeze_Nodes
8463
8464   begin
8465      if No (L) then
8466         return;
8467      end if;
8468
8469      --  First remove the freeze nodes that may appear before all other
8470      --  declarations.
8471
8472      Decl := First (L);
8473      while Present (Decl)
8474        and then Nkind (Decl) = N_Freeze_Entity
8475        and then Is_Outer_Type (Entity (Decl))
8476      loop
8477         Decl := Remove_Head (L);
8478         Insert_After (Next_Node, Decl);
8479         Set_Analyzed (Decl, False);
8480         Next_Node := Decl;
8481         Decl := First (L);
8482      end loop;
8483
8484      --  Next scan the list of declarations and remove each freeze node that
8485      --  appears ahead of the current node.
8486
8487      while Present (Decl) loop
8488         while Present (Next (Decl))
8489           and then Nkind (Next (Decl)) = N_Freeze_Entity
8490           and then Is_Outer_Type (Entity (Next (Decl)))
8491         loop
8492            Next_Decl := Remove_Next (Decl);
8493            Insert_After (Next_Node, Next_Decl);
8494            Set_Analyzed (Next_Decl, False);
8495            Next_Node := Next_Decl;
8496         end loop;
8497
8498         --  If the declaration is a nested package or concurrent type, then
8499         --  recurse. Nested generic packages will have been processed from the
8500         --  inside out.
8501
8502         if Nkind (Decl) = N_Package_Declaration then
8503            Spec := Specification (Decl);
8504
8505         elsif Nkind (Decl) = N_Task_Type_Declaration then
8506            Spec := Task_Definition (Decl);
8507
8508         elsif Nkind (Decl) = N_Protected_Type_Declaration then
8509            Spec := Protected_Definition (Decl);
8510
8511         else
8512            Spec := Empty;
8513         end if;
8514
8515         if Present (Spec) then
8516            Move_Freeze_Nodes (Out_Of, Next_Node,
8517              Visible_Declarations (Spec));
8518            Move_Freeze_Nodes (Out_Of, Next_Node,
8519              Private_Declarations (Spec));
8520         end if;
8521
8522         Next (Decl);
8523      end loop;
8524   end Move_Freeze_Nodes;
8525
8526   ----------------
8527   -- Next_Assoc --
8528   ----------------
8529
8530   function Next_Assoc (E : Assoc_Ptr) return Assoc_Ptr is
8531   begin
8532      return Generic_Renamings.Table (E).Next_In_HTable;
8533   end Next_Assoc;
8534
8535   ------------------------
8536   -- Preanalyze_Actuals --
8537   ------------------------
8538
8539   procedure Pre_Analyze_Actuals (N : Node_Id) is
8540      Assoc : Node_Id;
8541      Act   : Node_Id;
8542      Errs  : constant Int := Serious_Errors_Detected;
8543
8544   begin
8545      Assoc := First (Generic_Associations (N));
8546
8547      while Present (Assoc) loop
8548         Act := Explicit_Generic_Actual_Parameter (Assoc);
8549
8550         --  Within a nested instantiation, a defaulted actual is an
8551         --  empty association, so nothing to analyze. If the actual for
8552         --  a subprogram is an attribute, analyze prefix only, because
8553         --  actual is not a complete attribute reference.
8554
8555         --  If actual is an allocator, analyze expression only. The full
8556         --  analysis can generate code, and if the instance is a compilation
8557         --  unit we have to wait until the package instance is installed to
8558         --  have a proper place to insert this code.
8559
8560         --  String literals may be operators, but at this point we do not
8561         --  know whether the actual is a formal subprogram or a string.
8562
8563         if No (Act) then
8564            null;
8565
8566         elsif Nkind (Act) = N_Attribute_Reference then
8567            Analyze (Prefix (Act));
8568
8569         elsif Nkind (Act) = N_Explicit_Dereference then
8570            Analyze (Prefix (Act));
8571
8572         elsif Nkind (Act) = N_Allocator then
8573            declare
8574               Expr : constant Node_Id := Expression (Act);
8575
8576            begin
8577               if Nkind (Expr) = N_Subtype_Indication then
8578                  Analyze (Subtype_Mark (Expr));
8579                  Analyze_List (Constraints (Constraint (Expr)));
8580               else
8581                  Analyze (Expr);
8582               end if;
8583            end;
8584
8585         elsif Nkind (Act) /= N_Operator_Symbol then
8586            Analyze (Act);
8587         end if;
8588
8589         if Errs /= Serious_Errors_Detected then
8590            Abandon_Instantiation (Act);
8591         end if;
8592
8593         Next (Assoc);
8594      end loop;
8595   end Pre_Analyze_Actuals;
8596
8597   -------------------
8598   -- Remove_Parent --
8599   -------------------
8600
8601   procedure Remove_Parent (In_Body : Boolean := False) is
8602      S      : Entity_Id := Current_Scope;
8603      E      : Entity_Id;
8604      P      : Entity_Id;
8605      Hidden : Elmt_Id;
8606
8607   begin
8608      --  After child instantiation is complete, remove from scope stack
8609      --  the extra copy of the current scope, and then remove parent
8610      --  instances.
8611
8612      if not In_Body then
8613         Pop_Scope;
8614
8615         while Current_Scope /= S loop
8616            P := Current_Scope;
8617            End_Package_Scope (Current_Scope);
8618
8619            if In_Open_Scopes (P) then
8620               E := First_Entity (P);
8621
8622               while Present (E) loop
8623                  Set_Is_Immediately_Visible (E, True);
8624                  Next_Entity (E);
8625               end loop;
8626
8627               if Is_Generic_Instance (Current_Scope)
8628                 and then P /= Current_Scope
8629               then
8630                  --  We are within an instance of some sibling. Retain
8631                  --  visibility of parent, for proper subsequent cleanup.
8632
8633                  Set_In_Private_Part (P);
8634               end if;
8635
8636            elsif not In_Open_Scopes (Scope (P)) then
8637               Set_Is_Immediately_Visible (P, False);
8638            end if;
8639         end loop;
8640
8641         --  Reset visibility of entities in the enclosing scope.
8642
8643         Set_Is_Hidden_Open_Scope (Current_Scope, False);
8644         Hidden := First_Elmt (Hidden_Entities);
8645
8646         while Present (Hidden) loop
8647            Set_Is_Immediately_Visible (Node (Hidden), True);
8648            Next_Elmt (Hidden);
8649         end loop;
8650
8651      else
8652         --  Each body is analyzed separately, and there is no context
8653         --  that needs preserving from one body instance to the next,
8654         --  so remove all parent scopes that have been installed.
8655
8656         while Present (S) loop
8657            End_Package_Scope (S);
8658            Set_Is_Immediately_Visible (S, False);
8659            S := Current_Scope;
8660            exit when S = Standard_Standard;
8661         end loop;
8662      end if;
8663
8664   end Remove_Parent;
8665
8666   -----------------
8667   -- Restore_Env --
8668   -----------------
8669
8670   procedure Restore_Env is
8671      Saved : Instance_Env renames Instance_Envs.Table (Instance_Envs.Last);
8672
8673   begin
8674      Ada_83                       := Saved.Ada_83;
8675
8676      if No (Current_Instantiated_Parent.Act_Id) then
8677
8678         --  Restore environment after subprogram inlining
8679
8680         Restore_Private_Views (Empty);
8681      end if;
8682
8683      Current_Instantiated_Parent  := Saved.Instantiated_Parent;
8684      Exchanged_Views              := Saved.Exchanged_Views;
8685      Hidden_Entities              := Saved.Hidden_Entities;
8686      Current_Sem_Unit             := Saved.Current_Sem_Unit;
8687
8688      Instance_Envs.Decrement_Last;
8689   end Restore_Env;
8690
8691   ---------------------------
8692   -- Restore_Private_Views --
8693   ---------------------------
8694
8695   procedure Restore_Private_Views
8696     (Pack_Id    : Entity_Id;
8697      Is_Package : Boolean := True)
8698   is
8699      M        : Elmt_Id;
8700      E        : Entity_Id;
8701      Typ      : Entity_Id;
8702      Dep_Elmt : Elmt_Id;
8703      Dep_Typ  : Node_Id;
8704
8705   begin
8706      M := First_Elmt (Exchanged_Views);
8707      while Present (M) loop
8708         Typ := Node (M);
8709
8710         --  Subtypes of types whose views have been exchanged, and that
8711         --  are defined within the instance, were not on the list of
8712         --  Private_Dependents on entry to the instance, so they have to
8713         --  be exchanged explicitly now, in order to remain consistent with
8714         --  the view of the parent type.
8715
8716         if Ekind (Typ) = E_Private_Type
8717           or else Ekind (Typ) = E_Limited_Private_Type
8718           or else Ekind (Typ) = E_Record_Type_With_Private
8719         then
8720            Dep_Elmt := First_Elmt (Private_Dependents (Typ));
8721
8722            while Present (Dep_Elmt) loop
8723               Dep_Typ := Node (Dep_Elmt);
8724
8725               if Scope (Dep_Typ) = Pack_Id
8726                 and then Present (Full_View (Dep_Typ))
8727               then
8728                  Replace_Elmt (Dep_Elmt, Full_View (Dep_Typ));
8729                  Exchange_Declarations (Dep_Typ);
8730               end if;
8731
8732               Next_Elmt (Dep_Elmt);
8733            end loop;
8734         end if;
8735
8736         Exchange_Declarations (Node (M));
8737         Next_Elmt (M);
8738      end loop;
8739
8740      if No (Pack_Id) then
8741         return;
8742      end if;
8743
8744      --  Make the generic formal parameters private, and make the formal
8745      --  types into subtypes of the actuals again.
8746
8747      E := First_Entity (Pack_Id);
8748
8749      while Present (E) loop
8750         Set_Is_Hidden (E, True);
8751
8752         if Is_Type (E)
8753           and then Nkind (Parent (E)) = N_Subtype_Declaration
8754         then
8755            Set_Is_Generic_Actual_Type (E, False);
8756
8757            --  An unusual case of aliasing: the actual may also be directly
8758            --  visible in the generic, and be private there, while it is
8759            --  fully visible in the context of the instance. The internal
8760            --  subtype is private in the instance, but has full visibility
8761            --  like its parent in the enclosing scope. This enforces the
8762            --  invariant that the privacy status of all private dependents of
8763            --  a type coincide with that of the parent type. This can only
8764            --  happen when a generic child unit is instantiated within a
8765            --  sibling.
8766
8767            if Is_Private_Type (E)
8768              and then not Is_Private_Type (Etype (E))
8769            then
8770               Exchange_Declarations (E);
8771            end if;
8772
8773         elsif Ekind (E) = E_Package then
8774
8775            --  The end of the renaming list is the renaming of the generic
8776            --  package itself. If the instance is a subprogram, all entities
8777            --  in the corresponding package are renamings. If this entity is
8778            --  a formal package, make its own formals private as well. The
8779            --  actual in this case is itself the renaming of an instantation.
8780            --  If the entity is not a package renaming, it is the entity
8781            --  created to validate formal package actuals: ignore.
8782
8783            --  If the actual is itself a formal package for the enclosing
8784            --  generic, or the actual for such a formal package, it remains
8785            --  visible after the current instance, and therefore nothing
8786            --  needs to be done either, except to keep it accessible.
8787
8788            if Is_Package
8789              and then Renamed_Object (E) = Pack_Id
8790            then
8791               exit;
8792
8793            elsif Nkind (Parent (E)) /= N_Package_Renaming_Declaration then
8794               null;
8795
8796            elsif Denotes_Formal_Package (Renamed_Object (E)) then
8797               Set_Is_Hidden (E, False);
8798
8799            else
8800               declare
8801                  Act_P : constant Entity_Id := Renamed_Object (E);
8802                  Id    : Entity_Id;
8803
8804               begin
8805                  Id := First_Entity (Act_P);
8806                  while Present (Id)
8807                    and then Id /= First_Private_Entity (Act_P)
8808                  loop
8809                     Set_Is_Hidden (Id, True);
8810                     Set_Is_Potentially_Use_Visible (Id, In_Use (Act_P));
8811                     exit when Ekind (Id) = E_Package
8812                                 and then Renamed_Object (Id) = Act_P;
8813
8814                     Next_Entity (Id);
8815                  end loop;
8816               end;
8817               null;
8818            end if;
8819         end if;
8820
8821         Next_Entity (E);
8822      end loop;
8823   end Restore_Private_Views;
8824
8825   --------------
8826   -- Save_Env --
8827   --------------
8828
8829   procedure Save_Env
8830     (Gen_Unit : Entity_Id;
8831      Act_Unit : Entity_Id)
8832   is
8833   begin
8834      Init_Env;
8835      Set_Instance_Env (Gen_Unit, Act_Unit);
8836   end Save_Env;
8837
8838   ----------------------------
8839   -- Save_Global_References --
8840   ----------------------------
8841
8842   procedure Save_Global_References (N : Node_Id) is
8843      Gen_Scope : Entity_Id;
8844      E         : Entity_Id;
8845      N2        : Node_Id;
8846
8847      function Is_Global (E : Entity_Id) return Boolean;
8848      --  Check whether entity is defined outside of generic unit.
8849      --  Examine the scope of an entity, and the scope of the scope,
8850      --  etc, until we find either Standard, in which case the entity
8851      --  is global, or the generic unit itself, which indicates that
8852      --  the entity is local. If the entity is the generic unit itself,
8853      --  as in the case of a recursive call, or the enclosing generic unit,
8854      --  if different from the current scope, then it is local as well,
8855      --  because it will be replaced at the point of instantiation. On
8856      --  the other hand, if it is a reference to a child unit of a common
8857      --  ancestor, which appears in an instantiation, it is global because
8858      --  it is used to denote a specific compilation unit at the time the
8859      --  instantiations will be analyzed.
8860
8861      procedure Reset_Entity (N : Node_Id);
8862      --  Save semantic information on global entity, so that it is not
8863      --  resolved again at instantiation time.
8864
8865      procedure Save_Entity_Descendants (N : Node_Id);
8866      --  Apply Save_Global_References to the two syntactic descendants of
8867      --  non-terminal nodes that carry an Associated_Node and are processed
8868      --  through Reset_Entity. Once the global entity (if any) has been
8869      --  captured together with its type, only two syntactic descendants
8870      --  need to be traversed to complete the processing of the tree rooted
8871      --  at N. This applies to Selected_Components, Expanded_Names, and to
8872      --  Operator nodes. N can also be a character literal, identifier, or
8873      --  operator symbol node, but the call has no effect in these cases.
8874
8875      procedure Save_Global_Defaults (N1, N2 : Node_Id);
8876      --  Default actuals in nested instances must be handled specially
8877      --  because there is no link to them from the original tree. When an
8878      --  actual subprogram is given by a default, we add an explicit generic
8879      --  association for it in the instantiation node. When we save the
8880      --  global references on the name of the instance, we recover the list
8881      --  of generic associations, and add an explicit one to the original
8882      --  generic tree, through which a global actual can be preserved.
8883      --  Similarly, if a child unit is instantiated within a sibling, in the
8884      --  context of the parent, we must preserve the identifier of the parent
8885      --  so that it can be properly resolved in a subsequent instantiation.
8886
8887      procedure Save_Global_Descendant (D : Union_Id);
8888      --  Apply Save_Global_References recursively to the descendents of
8889      --  current node.
8890
8891      procedure Save_References (N : Node_Id);
8892      --  This is the recursive procedure that does the work, once the
8893      --  enclosing generic scope has been established.
8894
8895      ---------------
8896      -- Is_Global --
8897      ---------------
8898
8899      function Is_Global (E : Entity_Id) return Boolean is
8900         Se  : Entity_Id := Scope (E);
8901
8902         function Is_Instance_Node (Decl : Node_Id) return Boolean;
8903         --  Determine whether the parent node of a reference to a child unit
8904         --  denotes an instantiation or a formal package, in which case the
8905         --  reference to the child unit is global, even if it appears within
8906         --  the current scope (e.g. when the instance appears within the body
8907         --  of an ancestor).
8908
8909         function Is_Instance_Node (Decl : Node_Id) return Boolean is
8910         begin
8911            return (Nkind (Decl) in N_Generic_Instantiation
8912              or else
8913                Nkind (Original_Node (Decl)) = N_Formal_Package_Declaration);
8914         end Is_Instance_Node;
8915
8916      --  Start of processing for Is_Global
8917
8918      begin
8919         if E = Gen_Scope then
8920            return False;
8921
8922         elsif E = Standard_Standard then
8923            return True;
8924
8925         elsif Is_Child_Unit (E)
8926           and then (Is_Instance_Node (Parent (N2))
8927             or else (Nkind (Parent (N2)) = N_Expanded_Name
8928                       and then N2 = Selector_Name (Parent (N2))
8929                       and then Is_Instance_Node (Parent (Parent (N2)))))
8930         then
8931            return True;
8932
8933         else
8934            while Se /= Gen_Scope loop
8935               if Se = Standard_Standard then
8936                  return True;
8937               else
8938                  Se := Scope (Se);
8939               end if;
8940            end loop;
8941
8942            return False;
8943         end if;
8944      end Is_Global;
8945
8946      ------------------
8947      -- Reset_Entity --
8948      ------------------
8949
8950      procedure Reset_Entity (N : Node_Id) is
8951
8952         procedure Set_Global_Type (N : Node_Id; N2 : Node_Id);
8953         --  The type of N2 is global to the generic unit. Save the
8954         --  type in the generic node.
8955
8956         function Top_Ancestor (E : Entity_Id) return Entity_Id;
8957         --  Find the ultimate ancestor of the current unit. If it is
8958         --  not a generic unit, then the name of the current unit
8959         --  in the prefix of an expanded name must be replaced with
8960         --  its generic homonym to ensure that it will be properly
8961         --  resolved in an instance.
8962
8963         ---------------------
8964         -- Set_Global_Type --
8965         ---------------------
8966
8967         procedure Set_Global_Type (N : Node_Id; N2 : Node_Id) is
8968            Typ : constant Entity_Id := Etype (N2);
8969
8970         begin
8971            Set_Etype (N, Typ);
8972
8973            if Entity (N) /= N2
8974              and then Has_Private_View (Entity (N))
8975            then
8976               --  If the entity of N is not the associated node, this is
8977               --  a nested generic and it has an associated node as well,
8978               --  whose type is already the full view (see below). Indicate
8979               --  that the original node has a private view.
8980
8981               Set_Has_Private_View (N);
8982            end if;
8983
8984            --  If not a private type, nothing else to do
8985
8986            if not Is_Private_Type (Typ) then
8987               if Is_Array_Type (Typ)
8988                 and then Is_Private_Type (Component_Type (Typ))
8989               then
8990                  Set_Has_Private_View (N);
8991               end if;
8992
8993            --  If it is a derivation of a private type in a context where
8994            --  no full view is needed, nothing to do either.
8995
8996            elsif No (Full_View (Typ)) and then Typ /= Etype (Typ) then
8997               null;
8998
8999            --  Otherwise mark the type for flipping and use the full_view
9000            --  when available.
9001
9002            else
9003               Set_Has_Private_View (N);
9004
9005               if Present (Full_View (Typ)) then
9006                  Set_Etype (N2, Full_View (Typ));
9007               end if;
9008            end if;
9009         end Set_Global_Type;
9010
9011         ------------------
9012         -- Top_Ancestor --
9013         ------------------
9014
9015         function Top_Ancestor (E : Entity_Id) return Entity_Id is
9016            Par : Entity_Id := E;
9017
9018         begin
9019            while Is_Child_Unit (Par) loop
9020               Par := Scope (Par);
9021            end loop;
9022
9023            return Par;
9024         end Top_Ancestor;
9025
9026      --  Start of processing for Reset_Entity
9027
9028      begin
9029         N2 := Get_Associated_Node (N);
9030         E := Entity (N2);
9031
9032         if Present (E) then
9033            if Is_Global (E) then
9034               Set_Global_Type (N, N2);
9035
9036            elsif Nkind (N) = N_Op_Concat
9037              and then Is_Generic_Type (Etype (N2))
9038              and then
9039               (Base_Type (Etype (Right_Opnd (N2))) = Etype (N2)
9040                  or else Base_Type (Etype (Left_Opnd (N2))) = Etype (N2))
9041              and then Is_Intrinsic_Subprogram (E)
9042            then
9043               null;
9044
9045            else
9046               --  Entity is local. Mark generic node as unresolved.
9047               --  Note that now it does not have an entity.
9048
9049               Set_Associated_Node (N, Empty);
9050               Set_Etype  (N, Empty);
9051            end if;
9052
9053            if (Nkind (Parent (N)) = N_Package_Instantiation
9054                 or else Nkind (Parent (N)) = N_Function_Instantiation
9055                 or else Nkind (Parent (N)) = N_Procedure_Instantiation)
9056              and then N = Name (Parent (N))
9057            then
9058               Save_Global_Defaults (Parent (N), Parent (N2));
9059            end if;
9060
9061         elsif Nkind (Parent (N)) = N_Selected_Component
9062           and then Nkind (Parent (N2)) = N_Expanded_Name
9063         then
9064
9065            if Is_Global (Entity (Parent (N2))) then
9066               Change_Selected_Component_To_Expanded_Name (Parent (N));
9067               Set_Associated_Node (Parent (N), Parent (N2));
9068               Set_Global_Type (Parent (N), Parent (N2));
9069               Save_Entity_Descendants (N);
9070
9071            --  If this is a reference to the current generic entity,
9072            --  replace by the name of the generic homonym of the current
9073            --  package. This is because in an instantiation  Par.P.Q will
9074            --  not resolve to the name of the instance, whose enclosing
9075            --  scope is not necessarily Par. We use the generic homonym
9076            --  rather that the name of the generic itself, because it may
9077            --  be hidden by a local declaration.
9078
9079            elsif In_Open_Scopes (Entity (Parent (N2)))
9080              and then not
9081                Is_Generic_Unit (Top_Ancestor (Entity (Prefix (Parent (N2)))))
9082            then
9083               if Ekind (Entity (Parent (N2))) = E_Generic_Package then
9084                  Rewrite (Parent (N),
9085                    Make_Identifier (Sloc (N),
9086                      Chars =>
9087                        Chars (Generic_Homonym (Entity (Parent (N2))))));
9088               else
9089                  Rewrite (Parent (N),
9090                    Make_Identifier (Sloc (N),
9091                      Chars => Chars (Selector_Name (Parent (N2)))));
9092               end if;
9093            end if;
9094
9095            if (Nkind (Parent (Parent (N))) = N_Package_Instantiation
9096                 or else Nkind (Parent (Parent (N)))
9097                   = N_Function_Instantiation
9098                 or else Nkind (Parent (Parent (N)))
9099                   = N_Procedure_Instantiation)
9100              and then Parent (N) = Name (Parent (Parent (N)))
9101            then
9102               Save_Global_Defaults
9103                 (Parent (Parent (N)), Parent (Parent ((N2))));
9104            end if;
9105
9106         --  A selected component may denote a static constant that has
9107         --  been folded. Make the same replacement in original tree.
9108
9109         elsif Nkind (Parent (N)) = N_Selected_Component
9110           and then (Nkind (Parent (N2)) = N_Integer_Literal
9111                      or else Nkind (Parent (N2)) = N_Real_Literal)
9112         then
9113            Rewrite (Parent (N),
9114              New_Copy (Parent (N2)));
9115            Set_Analyzed (Parent (N), False);
9116
9117         --  A selected component may be transformed into a parameterless
9118         --  function call. If the called entity is global, rewrite the
9119         --  node appropriately, i.e. as an extended name for the global
9120         --  entity.
9121
9122         elsif Nkind (Parent (N)) = N_Selected_Component
9123           and then Nkind (Parent (N2)) = N_Function_Call
9124           and then Is_Global (Entity (Name (Parent (N2))))
9125         then
9126            Change_Selected_Component_To_Expanded_Name (Parent (N));
9127            Set_Associated_Node (Parent (N), Name (Parent (N2)));
9128            Set_Global_Type (Parent (N), Name (Parent (N2)));
9129            Save_Entity_Descendants (N);
9130
9131         else
9132            --  Entity is local. Reset in generic unit, so that node
9133            --  is resolved anew at the point of instantiation.
9134
9135            Set_Associated_Node (N, Empty);
9136            Set_Etype (N, Empty);
9137         end if;
9138      end Reset_Entity;
9139
9140      -----------------------------
9141      -- Save_Entity_Descendants --
9142      -----------------------------
9143
9144      procedure Save_Entity_Descendants (N : Node_Id) is
9145      begin
9146         case Nkind (N) is
9147            when N_Binary_Op =>
9148               Save_Global_Descendant (Union_Id (Left_Opnd (N)));
9149               Save_Global_Descendant (Union_Id (Right_Opnd (N)));
9150
9151            when N_Unary_Op =>
9152               Save_Global_Descendant (Union_Id (Right_Opnd (N)));
9153
9154            when N_Expanded_Name | N_Selected_Component =>
9155               Save_Global_Descendant (Union_Id (Prefix (N)));
9156               Save_Global_Descendant (Union_Id (Selector_Name (N)));
9157
9158            when N_Identifier | N_Character_Literal | N_Operator_Symbol =>
9159               null;
9160
9161            when others =>
9162               raise Program_Error;
9163         end case;
9164      end Save_Entity_Descendants;
9165
9166      --------------------------
9167      -- Save_Global_Defaults --
9168      --------------------------
9169
9170      procedure Save_Global_Defaults (N1, N2 : Node_Id) is
9171         Loc    : constant Source_Ptr := Sloc (N1);
9172         Assoc2 : constant List_Id    := Generic_Associations (N2);
9173         Gen_Id : constant Entity_Id  := Get_Generic_Entity (N2);
9174         Assoc1 : List_Id;
9175         Act1   : Node_Id;
9176         Act2   : Node_Id;
9177         Def    : Node_Id;
9178         Ndec   : Node_Id;
9179         Subp   : Entity_Id;
9180         Actual : Entity_Id;
9181
9182      begin
9183         Assoc1 := Generic_Associations (N1);
9184
9185         if Present (Assoc1) then
9186            Act1 := First (Assoc1);
9187         else
9188            Act1 := Empty;
9189            Set_Generic_Associations (N1, New_List);
9190            Assoc1 := Generic_Associations (N1);
9191         end if;
9192
9193         if Present (Assoc2) then
9194            Act2 := First (Assoc2);
9195         else
9196            return;
9197         end if;
9198
9199         while Present (Act1) and then Present (Act2) loop
9200            Next (Act1);
9201            Next (Act2);
9202         end loop;
9203
9204         --  Find the associations added for default suprograms.
9205
9206         if Present (Act2) then
9207            while Nkind (Act2) /= N_Generic_Association
9208              or else No (Entity (Selector_Name (Act2)))
9209              or else not Is_Overloadable (Entity (Selector_Name (Act2)))
9210            loop
9211               Next (Act2);
9212            end loop;
9213
9214            --  Add a similar association if the default is global. The
9215            --  renaming declaration for the actual has been analyzed, and
9216            --  its alias is the program it renames. Link the actual in the
9217            --  original generic tree with the node in the analyzed tree.
9218
9219            while Present (Act2) loop
9220               Subp := Entity (Selector_Name (Act2));
9221               Def  := Explicit_Generic_Actual_Parameter (Act2);
9222
9223               --  Following test is defence against rubbish errors
9224
9225               if No (Alias (Subp)) then
9226                  return;
9227               end if;
9228
9229               --  Retrieve the resolved actual from the renaming declaration
9230               --  created for the instantiated formal.
9231
9232               Actual := Entity (Name (Parent (Parent (Subp))));
9233               Set_Entity (Def, Actual);
9234               Set_Etype (Def, Etype (Actual));
9235
9236               if Is_Global (Actual) then
9237                  Ndec :=
9238                    Make_Generic_Association (Loc,
9239                      Selector_Name => New_Occurrence_Of (Subp, Loc),
9240                        Explicit_Generic_Actual_Parameter =>
9241                          New_Occurrence_Of (Actual, Loc));
9242
9243                  Set_Associated_Node
9244                    (Explicit_Generic_Actual_Parameter (Ndec), Def);
9245
9246                  Append (Ndec, Assoc1);
9247
9248               --  If there are other defaults, add a dummy association
9249               --  in case there are other defaulted formals with the same
9250               --  name.
9251
9252               elsif Present (Next (Act2)) then
9253                  Ndec :=
9254                    Make_Generic_Association (Loc,
9255                      Selector_Name => New_Occurrence_Of (Subp, Loc),
9256                        Explicit_Generic_Actual_Parameter => Empty);
9257
9258                  Append (Ndec, Assoc1);
9259               end if;
9260
9261               Next (Act2);
9262            end loop;
9263         end if;
9264
9265         if Nkind (Name (N1)) = N_Identifier
9266           and then Is_Child_Unit (Gen_Id)
9267           and then Is_Global (Gen_Id)
9268           and then Is_Generic_Unit (Scope (Gen_Id))
9269           and then In_Open_Scopes (Scope (Gen_Id))
9270         then
9271            --  This is an instantiation of a child unit within a sibling,
9272            --  so that the generic parent is in scope. An eventual instance
9273            --  must occur within the scope of an instance of the parent.
9274            --  Make name in instance into an expanded name, to preserve the
9275            --  identifier of the parent, so it can be resolved subsequently.
9276
9277            Rewrite (Name (N2),
9278              Make_Expanded_Name (Loc,
9279                Chars         => Chars (Gen_Id),
9280                Prefix        => New_Occurrence_Of (Scope (Gen_Id), Loc),
9281                Selector_Name => New_Occurrence_Of (Gen_Id, Loc)));
9282            Set_Entity (Name (N2), Gen_Id);
9283
9284            Rewrite (Name (N1),
9285               Make_Expanded_Name (Loc,
9286                Chars         => Chars (Gen_Id),
9287                Prefix        => New_Occurrence_Of (Scope (Gen_Id), Loc),
9288                Selector_Name => New_Occurrence_Of (Gen_Id, Loc)));
9289
9290            Set_Associated_Node (Name (N1), Name (N2));
9291            Set_Associated_Node (Prefix (Name (N1)), Empty);
9292            Set_Associated_Node
9293              (Selector_Name (Name (N1)), Selector_Name (Name (N2)));
9294            Set_Etype (Name (N1), Etype (Gen_Id));
9295         end if;
9296
9297      end Save_Global_Defaults;
9298
9299      ----------------------------
9300      -- Save_Global_Descendant --
9301      ----------------------------
9302
9303      procedure Save_Global_Descendant (D : Union_Id) is
9304         N1 : Node_Id;
9305
9306      begin
9307         if D in Node_Range then
9308            if D = Union_Id (Empty) then
9309               null;
9310
9311            elsif Nkind (Node_Id (D)) /= N_Compilation_Unit then
9312               Save_References (Node_Id (D));
9313            end if;
9314
9315         elsif D in List_Range then
9316            if D = Union_Id (No_List)
9317              or else Is_Empty_List (List_Id (D))
9318            then
9319               null;
9320
9321            else
9322               N1 := First (List_Id (D));
9323               while Present (N1) loop
9324                  Save_References (N1);
9325                  Next (N1);
9326               end loop;
9327            end if;
9328
9329         --  Element list or other non-node field, nothing to do
9330
9331         else
9332            null;
9333         end if;
9334      end Save_Global_Descendant;
9335
9336      ---------------------
9337      -- Save_References --
9338      ---------------------
9339
9340      --  This is the recursive procedure that does the work, once the
9341      --  enclosing generic scope has been established. We have to treat
9342      --  specially a number of node rewritings that are required by semantic
9343      --  processing and which change the kind of nodes in the generic copy:
9344      --  typically constant-folding, replacing an operator node by a string
9345      --  literal, or a selected component by an expanded name. In  each of
9346      --  those cases, the transformation is propagated to the generic unit.
9347
9348      procedure Save_References (N : Node_Id) is
9349      begin
9350         if N = Empty then
9351            null;
9352
9353         elsif Nkind (N) = N_Character_Literal
9354           or else Nkind (N) = N_Operator_Symbol
9355         then
9356            if Nkind (N) = Nkind (Get_Associated_Node (N)) then
9357               Reset_Entity (N);
9358
9359            elsif Nkind (N) = N_Operator_Symbol
9360              and then Nkind (Get_Associated_Node (N)) = N_String_Literal
9361            then
9362               Change_Operator_Symbol_To_String_Literal (N);
9363            end if;
9364
9365         elsif Nkind (N) in N_Op then
9366
9367            if Nkind (N) = Nkind (Get_Associated_Node (N)) then
9368
9369               if Nkind (N) = N_Op_Concat then
9370                  Set_Is_Component_Left_Opnd (N,
9371                    Is_Component_Left_Opnd (Get_Associated_Node (N)));
9372
9373                  Set_Is_Component_Right_Opnd (N,
9374                    Is_Component_Right_Opnd (Get_Associated_Node (N)));
9375               end if;
9376
9377               Reset_Entity (N);
9378            else
9379               --  Node may be transformed into call to a user-defined operator
9380
9381               N2 := Get_Associated_Node (N);
9382
9383               if Nkind (N2) = N_Function_Call then
9384                  E := Entity (Name (N2));
9385
9386                  if Present (E)
9387                    and then Is_Global (E)
9388                  then
9389                     Set_Etype (N, Etype (N2));
9390                  else
9391                     Set_Associated_Node (N, Empty);
9392                     Set_Etype (N, Empty);
9393                  end if;
9394
9395               elsif Nkind (N2) = N_Integer_Literal
9396                 or else Nkind (N2) = N_Real_Literal
9397                 or else Nkind (N2) = N_String_Literal
9398               then
9399                  --  Operation was constant-folded, perform the same
9400                  --  replacement in generic.
9401
9402                  Rewrite (N, New_Copy (N2));
9403                  Set_Analyzed (N, False);
9404
9405               elsif Nkind (N2) = N_Identifier
9406                 and then Ekind (Entity (N2)) = E_Enumeration_Literal
9407               then
9408                  --  Same if call was folded into a literal, but in this
9409                  --  case retain the entity to avoid spurious ambiguities
9410                  --  if id is overloaded at the point of instantiation or
9411                  --  inlining.
9412
9413                  Rewrite (N, New_Copy (N2));
9414                  Set_Associated_Node (N, N2);
9415                  Set_Analyzed (N, False);
9416               end if;
9417            end if;
9418
9419            --  Complete the check on operands, if node has not been
9420            --  constant-folded.
9421
9422            if Nkind (N) in N_Op then
9423               Save_Entity_Descendants (N);
9424            end if;
9425
9426         elsif Nkind (N) = N_Identifier then
9427            if Nkind (N) = Nkind (Get_Associated_Node (N)) then
9428
9429               --  If this is a discriminant reference, always save it.
9430               --  It is used in the instance to find the corresponding
9431               --  discriminant positionally rather than  by name.
9432
9433               Set_Original_Discriminant
9434                 (N, Original_Discriminant (Get_Associated_Node (N)));
9435               Reset_Entity (N);
9436
9437            else
9438               N2 := Get_Associated_Node (N);
9439
9440               if Nkind (N2) = N_Function_Call then
9441                  E := Entity (Name (N2));
9442
9443                  --  Name resolves to a call to parameterless function.
9444                  --  If original entity is global, mark node as resolved.
9445
9446                  if Present (E)
9447                    and then Is_Global (E)
9448                  then
9449                     Set_Etype (N, Etype (N2));
9450                  else
9451                     Set_Associated_Node (N, Empty);
9452                     Set_Etype (N, Empty);
9453                  end if;
9454
9455               elsif
9456                 Nkind (N2) = N_Integer_Literal or else
9457                 Nkind (N2) = N_Real_Literal    or else
9458                 Nkind (N2) = N_String_Literal
9459               then
9460                  --  Name resolves to named number that is constant-folded,
9461                  --  or to string literal from concatenation.
9462                  --  Perform the same replacement in generic.
9463
9464                  Rewrite (N, New_Copy (N2));
9465                  Set_Analyzed (N, False);
9466
9467               elsif Nkind (N2) = N_Explicit_Dereference then
9468
9469                  --  An identifier is rewritten as a dereference if it is
9470                  --  the prefix in a selected component, and it denotes an
9471                  --  access to a composite type, or a parameterless function
9472                  --  call that returns an access type.
9473
9474                  --  Check whether corresponding entity in prefix is global.
9475
9476                  if Is_Entity_Name (Prefix (N2))
9477                    and then Present (Entity (Prefix (N2)))
9478                    and then Is_Global (Entity (Prefix (N2)))
9479                  then
9480                     Rewrite (N,
9481                       Make_Explicit_Dereference (Sloc (N),
9482                          Prefix => Make_Identifier (Sloc (N),
9483                            Chars => Chars (N))));
9484                     Set_Associated_Node (Prefix (N), Prefix (N2));
9485
9486                  elsif Nkind (Prefix (N2)) = N_Function_Call
9487                    and then Is_Global (Entity (Name (Prefix (N2))))
9488                  then
9489                     Rewrite (N,
9490                       Make_Explicit_Dereference (Sloc (N),
9491                          Prefix => Make_Function_Call (Sloc (N),
9492                            Name  =>
9493                              Make_Identifier (Sloc (N),
9494                              Chars => Chars (N)))));
9495
9496                     Set_Associated_Node
9497                      (Name (Prefix (N)), Name (Prefix (N2)));
9498
9499                  else
9500                     Set_Associated_Node (N, Empty);
9501                     Set_Etype (N, Empty);
9502                  end if;
9503
9504               --  The subtype mark of a nominally unconstrained object
9505               --  is rewritten as a subtype indication using the bounds
9506               --  of the expression. Recover the original subtype mark.
9507
9508               elsif Nkind (N2) = N_Subtype_Indication
9509                 and then Is_Entity_Name (Original_Node (N2))
9510               then
9511                  Set_Associated_Node (N, Original_Node (N2));
9512                  Reset_Entity (N);
9513
9514               else
9515                  null;
9516               end if;
9517            end if;
9518
9519         elsif Nkind (N) in N_Entity then
9520            null;
9521
9522         else
9523            declare
9524               use Atree.Unchecked_Access;
9525               --  This code section is part of implementing an untyped tree
9526               --  traversal, so it needs direct access to node fields.
9527
9528            begin
9529               if Nkind (N) = N_Aggregate
9530                    or else
9531                  Nkind (N) = N_Extension_Aggregate
9532               then
9533                  N2 := Get_Associated_Node (N);
9534
9535                  if No (N2)
9536                    or else No (Etype (N2))
9537                    or else not Is_Global (Etype (N2))
9538                  then
9539                     Set_Associated_Node (N, Empty);
9540                  end if;
9541
9542                  Save_Global_Descendant (Field1 (N));
9543                  Save_Global_Descendant (Field2 (N));
9544                  Save_Global_Descendant (Field3 (N));
9545                  Save_Global_Descendant (Field5 (N));
9546
9547               --  All other cases than aggregates
9548
9549               else
9550                  Save_Global_Descendant (Field1 (N));
9551                  Save_Global_Descendant (Field2 (N));
9552                  Save_Global_Descendant (Field3 (N));
9553                  Save_Global_Descendant (Field4 (N));
9554                  Save_Global_Descendant (Field5 (N));
9555               end if;
9556            end;
9557         end if;
9558      end Save_References;
9559
9560   --  Start of processing for Save_Global_References
9561
9562   begin
9563      Gen_Scope := Current_Scope;
9564
9565      --  If the generic unit is a child unit, references to entities in
9566      --  the parent are treated as local, because they will be resolved
9567      --  anew in the context of the instance of the parent.
9568
9569      while Is_Child_Unit (Gen_Scope)
9570        and then Ekind (Scope (Gen_Scope)) = E_Generic_Package
9571      loop
9572         Gen_Scope := Scope (Gen_Scope);
9573      end loop;
9574
9575      Save_References (N);
9576   end Save_Global_References;
9577
9578   --------------------------------------
9579   -- Set_Copied_Sloc_For_Inlined_Body --
9580   --------------------------------------
9581
9582   procedure Set_Copied_Sloc_For_Inlined_Body (N : Node_Id; E : Entity_Id) is
9583   begin
9584      Create_Instantiation_Source (N, E, True, S_Adjustment);
9585   end Set_Copied_Sloc_For_Inlined_Body;
9586
9587   ---------------------
9588   -- Set_Instance_Of --
9589   ---------------------
9590
9591   procedure Set_Instance_Of (A : Entity_Id; B : Entity_Id) is
9592   begin
9593      Generic_Renamings.Table (Generic_Renamings.Last) := (A, B, Assoc_Null);
9594      Generic_Renamings_HTable.Set (Generic_Renamings.Last);
9595      Generic_Renamings.Increment_Last;
9596   end Set_Instance_Of;
9597
9598   --------------------
9599   -- Set_Next_Assoc --
9600   --------------------
9601
9602   procedure Set_Next_Assoc (E : Assoc_Ptr; Next : Assoc_Ptr) is
9603   begin
9604      Generic_Renamings.Table (E).Next_In_HTable := Next;
9605   end Set_Next_Assoc;
9606
9607   -------------------
9608   -- Start_Generic --
9609   -------------------
9610
9611   procedure Start_Generic is
9612   begin
9613      --  ??? I am sure more things could be factored out in this
9614      --  routine. Should probably be done at a later stage.
9615
9616      Generic_Flags.Increment_Last;
9617      Generic_Flags.Table (Generic_Flags.Last) := Inside_A_Generic;
9618      Inside_A_Generic := True;
9619
9620      Expander_Mode_Save_And_Set (False);
9621   end Start_Generic;
9622
9623   ----------------------
9624   -- Set_Instance_Env --
9625   ----------------------
9626
9627   procedure Set_Instance_Env
9628     (Gen_Unit : Entity_Id;
9629      Act_Unit : Entity_Id)
9630   is
9631
9632   begin
9633      --  Regardless of the current mode, predefined units are analyzed in
9634      --  Ada95 mode, and Ada83 checks don't apply.
9635
9636      if Is_Internal_File_Name
9637          (Fname => Unit_File_Name (Get_Source_Unit (Gen_Unit)),
9638           Renamings_Included => True) then
9639         Ada_83 := False;
9640      end if;
9641
9642      Current_Instantiated_Parent := (Gen_Unit, Act_Unit, Assoc_Null);
9643   end Set_Instance_Env;
9644
9645   -----------------
9646   -- Switch_View --
9647   -----------------
9648
9649   procedure Switch_View (T : Entity_Id) is
9650      BT        : constant Entity_Id := Base_Type (T);
9651      Priv_Elmt : Elmt_Id := No_Elmt;
9652      Priv_Sub  : Entity_Id;
9653
9654   begin
9655      --  T may be private but its base type may have been exchanged through
9656      --  some other occurrence, in which case there is nothing to switch.
9657
9658      if not Is_Private_Type (BT) then
9659         return;
9660      end if;
9661
9662      Priv_Elmt := First_Elmt (Private_Dependents (BT));
9663
9664      if Present (Full_View (BT)) then
9665         Append_Elmt (Full_View (BT), Exchanged_Views);
9666         Exchange_Declarations (BT);
9667      end if;
9668
9669      while Present (Priv_Elmt) loop
9670         Priv_Sub := (Node (Priv_Elmt));
9671
9672         --  We avoid flipping the subtype if the Etype of its full
9673         --  view is private because this would result in a malformed
9674         --  subtype. This occurs when the Etype of the subtype full
9675         --  view is the full view of the base type (and since the
9676         --  base types were just switched, the subtype is pointing
9677         --  to the wrong view). This is currently the case for
9678         --  tagged record types, access types (maybe more?) and
9679         --  needs to be resolved. ???
9680
9681         if Present (Full_View (Priv_Sub))
9682           and then not Is_Private_Type (Etype (Full_View (Priv_Sub)))
9683         then
9684            Append_Elmt (Full_View (Priv_Sub), Exchanged_Views);
9685            Exchange_Declarations (Priv_Sub);
9686         end if;
9687
9688         Next_Elmt (Priv_Elmt);
9689      end loop;
9690   end Switch_View;
9691
9692   -----------------------------
9693   -- Valid_Default_Attribute --
9694   -----------------------------
9695
9696   procedure Valid_Default_Attribute (Nam : Entity_Id; Def : Node_Id) is
9697      Attr_Id : constant Attribute_Id :=
9698                  Get_Attribute_Id (Attribute_Name (Def));
9699      T       : constant Entity_Id := Entity (Prefix (Def));
9700      Is_Fun  : constant Boolean := (Ekind (Nam) = E_Function);
9701      F       : Entity_Id;
9702      Num_F   : Int;
9703      OK      : Boolean;
9704
9705   begin
9706      if No (T)
9707        or else T = Any_Id
9708      then
9709         return;
9710      end if;
9711
9712      Num_F := 0;
9713      F := First_Formal (Nam);
9714      while Present (F) loop
9715         Num_F := Num_F + 1;
9716         Next_Formal (F);
9717      end loop;
9718
9719      case Attr_Id is
9720         when Attribute_Adjacent |  Attribute_Ceiling   | Attribute_Copy_Sign |
9721              Attribute_Floor    |  Attribute_Fraction  | Attribute_Machine   |
9722              Attribute_Model    |  Attribute_Remainder | Attribute_Rounding  |
9723              Attribute_Unbiased_Rounding  =>
9724            OK := Is_Fun
9725                    and then Num_F = 1
9726                    and then Is_Floating_Point_Type (T);
9727
9728         when Attribute_Image    | Attribute_Pred       | Attribute_Succ |
9729              Attribute_Value    | Attribute_Wide_Image |
9730              Attribute_Wide_Value  =>
9731            OK := (Is_Fun and then Num_F = 1 and then Is_Scalar_Type (T));
9732
9733         when Attribute_Max      |  Attribute_Min  =>
9734            OK := (Is_Fun and then Num_F = 2 and then Is_Scalar_Type (T));
9735
9736         when Attribute_Input =>
9737            OK := (Is_Fun and then Num_F = 1);
9738
9739         when Attribute_Output | Attribute_Read | Attribute_Write =>
9740            OK := (not Is_Fun and then Num_F = 2);
9741
9742         when others =>
9743            OK := False;
9744      end case;
9745
9746      if not OK then
9747         Error_Msg_N ("attribute reference has wrong profile for subprogram",
9748           Def);
9749      end if;
9750   end Valid_Default_Attribute;
9751
9752end Sem_Ch12;
9753