OSDN Git Service

2009-07-07 Manuel López-Ibáñez <manu@gcc.gnu.org>
[pf3gnuchains/gcc-fork.git] / gcc / ada / sem_ch12.adb
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-2009, Free Software Foundation, Inc.         --
10 --                                                                          --
11 -- GNAT is free software;  you can  redistribute it  and/or modify it under --
12 -- terms of the  GNU General Public License as published  by the Free Soft- --
13 -- ware  Foundation;  either version 3,  or (at your option) any later ver- --
14 -- sion.  GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License --
17 -- for  more details.  You should have  received  a copy of the GNU General --
18 -- Public License  distributed with GNAT; see file COPYING3.  If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license.          --
20 --                                                                          --
21 -- GNAT was originally developed  by the GNAT team at  New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc.      --
23 --                                                                          --
24 ------------------------------------------------------------------------------
25
26 with Atree;    use Atree;
27 with Einfo;    use Einfo;
28 with Elists;   use Elists;
29 with Errout;   use Errout;
30 with Expander; use Expander;
31 with Fname;    use Fname;
32 with Fname.UF; use Fname.UF;
33 with Freeze;   use Freeze;
34 with Hostparm;
35 with Itypes;   use Itypes;
36 with Lib;      use Lib;
37 with Lib.Load; use Lib.Load;
38 with Lib.Xref; use Lib.Xref;
39 with Nlists;   use Nlists;
40 with Namet;    use Namet;
41 with Nmake;    use Nmake;
42 with Opt;      use Opt;
43 with Rident;   use Rident;
44 with Restrict; use Restrict;
45 with Rtsfind;  use Rtsfind;
46 with Sem;      use Sem;
47 with Sem_Aux;  use Sem_Aux;
48 with Sem_Cat;  use Sem_Cat;
49 with Sem_Ch3;  use Sem_Ch3;
50 with Sem_Ch6;  use Sem_Ch6;
51 with Sem_Ch7;  use Sem_Ch7;
52 with Sem_Ch8;  use Sem_Ch8;
53 with Sem_Ch10; use Sem_Ch10;
54 with Sem_Ch13; use Sem_Ch13;
55 with Sem_Disp; use Sem_Disp;
56 with Sem_Elab; use Sem_Elab;
57 with Sem_Elim; use Sem_Elim;
58 with Sem_Eval; use Sem_Eval;
59 with Sem_Res;  use Sem_Res;
60 with Sem_Type; use Sem_Type;
61 with Sem_Util; use Sem_Util;
62 with Sem_Warn; use Sem_Warn;
63 with Stand;    use Stand;
64 with Sinfo;    use Sinfo;
65 with Sinfo.CN; use Sinfo.CN;
66 with Sinput;   use Sinput;
67 with Sinput.L; use Sinput.L;
68 with Snames;   use Snames;
69 with Stringt;  use Stringt;
70 with Uname;    use Uname;
71 with Table;
72 with Tbuild;   use Tbuild;
73 with Uintp;    use Uintp;
74 with Urealp;   use Urealp;
75
76 with GNAT.HTable;
77
78 package body Sem_Ch12 is
79
80    ----------------------------------------------------------
81    -- Implementation of Generic Analysis and Instantiation --
82    ----------------------------------------------------------
83
84    --  GNAT implements generics by macro expansion. No attempt is made to share
85    --  generic instantiations (for now). Analysis of a generic definition does
86    --  not perform any expansion action, but the expander must be called on the
87    --  tree for each instantiation, because the expansion may of course depend
88    --  on the generic actuals. All of this is best achieved as follows:
89    --
90    --  a) Semantic analysis of a generic unit is performed on a copy of the
91    --  tree for the generic unit. All tree modifications that follow analysis
92    --  do not affect the original tree. Links are kept between the original
93    --  tree and the copy, in order to recognize non-local references within
94    --  the generic, and propagate them to each instance (recall that name
95    --  resolution is done on the generic declaration: generics are not really
96    --  macros!). This is summarized in the following diagram:
97
98    --              .-----------.               .----------.
99    --              |  semantic |<--------------|  generic |
100    --              |    copy   |               |    unit  |
101    --              |           |==============>|          |
102    --              |___________|    global     |__________|
103    --                             references     |   |  |
104    --                                            |   |  |
105    --                                          .-----|--|.
106    --                                          |  .-----|---.
107    --                                          |  |  .----------.
108    --                                          |  |  |  generic |
109    --                                          |__|  |          |
110    --                                             |__| instance |
111    --                                                |__________|
112
113    --  b) Each instantiation copies the original tree, and inserts into it a
114    --  series of declarations that describe the mapping between generic formals
115    --  and actuals. For example, a generic In OUT parameter is an object
116    --  renaming of the corresponding actual, etc. Generic IN parameters are
117    --  constant declarations.
118
119    --  c) In order to give the right visibility for these renamings, we use
120    --  a different scheme for package and subprogram instantiations. For
121    --  packages, the list of renamings is inserted into the package
122    --  specification, before the visible declarations of the package. The
123    --  renamings are analyzed before any of the text of the instance, and are
124    --  thus visible at the right place. Furthermore, outside of the instance,
125    --  the generic parameters are visible and denote their corresponding
126    --  actuals.
127
128    --  For subprograms, we create a container package to hold the renamings
129    --  and the subprogram instance itself. Analysis of the package makes the
130    --  renaming declarations visible to the subprogram. After analyzing the
131    --  package, the defining entity for the subprogram is touched-up so that
132    --  it appears declared in the current scope, and not inside the container
133    --  package.
134
135    --  If the instantiation is a compilation unit, the container package is
136    --  given the same name as the subprogram instance. This ensures that
137    --  the elaboration procedure called by the binder, using the compilation
138    --  unit name, calls in fact the elaboration procedure for the package.
139
140    --  Not surprisingly, private types complicate this approach. By saving in
141    --  the original generic object the non-local references, we guarantee that
142    --  the proper entities are referenced at the point of instantiation.
143    --  However, for private types, this by itself does not insure that the
144    --  proper VIEW of the entity is used (the full type may be visible at the
145    --  point of generic definition, but not at instantiation, or vice-versa).
146    --  In  order to reference the proper view, we special-case any reference
147    --  to private types in the generic object, by saving both views, one in
148    --  the generic and one in the semantic copy. At time of instantiation, we
149    --  check whether the two views are consistent, and exchange declarations if
150    --  necessary, in order to restore the correct visibility. Similarly, if
151    --  the instance view is private when the generic view was not, we perform
152    --  the exchange. After completing the instantiation, we restore the
153    --  current visibility. The flag Has_Private_View marks identifiers in the
154    --  the generic unit that require checking.
155
156    --  Visibility within nested generic units requires special handling.
157    --  Consider the following scheme:
158
159    --  type Global is ...         --  outside of generic unit.
160    --  generic ...
161    --  package Outer is
162    --     ...
163    --     type Semi_Global is ... --  global to inner.
164
165    --     generic ...                                         -- 1
166    --     procedure inner (X1 : Global;  X2 : Semi_Global);
167
168    --     procedure in2 is new inner (...);                   -- 4
169    --  end Outer;
170
171    --  package New_Outer is new Outer (...);                  -- 2
172    --  procedure New_Inner is new New_Outer.Inner (...);      -- 3
173
174    --  The semantic analysis of Outer captures all occurrences of Global.
175    --  The semantic analysis of Inner (at 1) captures both occurrences of
176    --  Global and Semi_Global.
177
178    --  At point 2 (instantiation of Outer), we also produce a generic copy
179    --  of Inner, even though Inner is, at that point, not being instantiated.
180    --  (This is just part of the semantic analysis of New_Outer).
181
182    --  Critically, references to Global within Inner must be preserved, while
183    --  references to Semi_Global should not preserved, because they must now
184    --  resolve to an entity within New_Outer. To distinguish between these, we
185    --  use a global variable, Current_Instantiated_Parent, which is set when
186    --  performing a generic copy during instantiation (at 2). This variable is
187    --  used when performing a generic copy that is not an instantiation, but
188    --  that is nested within one, as the occurrence of 1 within 2. The analysis
189    --  of a nested generic only preserves references that are global to the
190    --  enclosing Current_Instantiated_Parent. We use the Scope_Depth value to
191    --  determine whether a reference is external to the given parent.
192
193    --  The instantiation at point 3 requires no special treatment. The method
194    --  works as well for further nestings of generic units, but of course the
195    --  variable Current_Instantiated_Parent must be stacked because nested
196    --  instantiations can occur, e.g. the occurrence of 4 within 2.
197
198    --  The instantiation of package and subprogram bodies is handled in a
199    --  similar manner, except that it is delayed until after semantic
200    --  analysis is complete. In this fashion complex cross-dependencies
201    --  between several package declarations and bodies containing generics
202    --  can be compiled which otherwise would diagnose spurious circularities.
203
204    --  For example, it is possible to compile two packages A and B that
205    --  have the following structure:
206
207    --    package A is                         package B is
208    --       generic ...                          generic ...
209    --       package G_A is                       package G_B is
210
211    --    with B;                              with A;
212    --    package body A is                    package body B is
213    --       package N_B is new G_B (..)          package N_A is new G_A (..)
214
215    --  The table Pending_Instantiations in package Inline is used to keep
216    --  track of body instantiations that are delayed in this manner. Inline
217    --  handles the actual calls to do the body instantiations. This activity
218    --  is part of Inline, since the processing occurs at the same point, and
219    --  for essentially the same reason, as the handling of inlined routines.
220
221    ----------------------------------------------
222    -- Detection of Instantiation Circularities --
223    ----------------------------------------------
224
225    --  If we have a chain of instantiations that is circular, this is static
226    --  error which must be detected at compile time. The detection of these
227    --  circularities is carried out at the point that we insert a generic
228    --  instance spec or body. If there is a circularity, then the analysis of
229    --  the offending spec or body will eventually result in trying to load the
230    --  same unit again, and we detect this problem as we analyze the package
231    --  instantiation for the second time.
232
233    --  At least in some cases after we have detected the circularity, we get
234    --  into trouble if we try to keep going. The following flag is set if a
235    --  circularity is detected, and used to abandon compilation after the
236    --  messages have been posted.
237
238    Circularity_Detected : Boolean := False;
239    --  This should really be reset on encountering a new main unit, but in
240    --  practice we are not using multiple main units so it is not critical.
241
242    -------------------------------------------------
243    -- Formal packages and partial parametrization --
244    -------------------------------------------------
245
246    --  When compiling a generic, a formal package is a local instantiation. If
247    --  declared with a box, its generic formals are visible in the enclosing
248    --  generic. If declared with a partial list of actuals, those actuals that
249    --  are defaulted (covered by an Others clause, or given an explicit box
250    --  initialization) are also visible in the enclosing generic, while those
251    --  that have a corresponding actual are not.
252
253    --  In our source model of instantiation, the same visibility must be
254    --  present in the spec and body of an instance: the names of the formals
255    --  that are defaulted must be made visible within the instance, and made
256    --  invisible (hidden) after the instantiation is complete, so that they
257    --  are not accessible outside of the instance.
258
259    --  In a generic, a formal package is treated like a special instantiation.
260    --  Our Ada95 compiler handled formals with and without box in different
261    --  ways. With partial parametrization, we use a single model for both.
262    --  We create a package declaration that consists of the specification of
263    --  the generic package, and a set of declarations that map the actuals
264    --  into local renamings, just as we do for bona fide instantiations. For
265    --  defaulted parameters and formals with a box, we copy directly the
266    --  declarations of the formal into this local package. The result is a
267    --  a package whose visible declarations may include generic formals. This
268    --  package is only used for type checking and visibility analysis, and
269    --  never reaches the back-end, so it can freely violate the placement
270    --  rules for generic formal declarations.
271
272    --  The list of declarations (renamings and copies of formals) is built
273    --  by Analyze_Associations, just as for regular instantiations.
274
275    --  At the point of instantiation, conformance checking must be applied only
276    --  to those parameters that were specified in the formal. We perform this
277    --  checking by creating another internal instantiation, this one including
278    --  only the renamings and the formals (the rest of the package spec is not
279    --  relevant to conformance checking). We can then traverse two lists: the
280    --  list of actuals in the instance that corresponds to the formal package,
281    --  and the list of actuals produced for this bogus instantiation. We apply
282    --  the conformance rules to those actuals that are not defaulted (i.e.
283    --  which still appear as generic formals.
284
285    --  When we compile an instance body we must make the right parameters
286    --  visible again. The predicate Is_Generic_Formal indicates which of the
287    --  formals should have its Is_Hidden flag reset.
288
289    -----------------------
290    -- Local subprograms --
291    -----------------------
292
293    procedure Abandon_Instantiation (N : Node_Id);
294    pragma No_Return (Abandon_Instantiation);
295    --  Posts an error message "instantiation abandoned" at the indicated node
296    --  and then raises the exception Instantiation_Error to do it.
297
298    procedure Analyze_Formal_Array_Type
299      (T   : in out Entity_Id;
300       Def : Node_Id);
301    --  A formal array type is treated like an array type declaration, and
302    --  invokes Array_Type_Declaration (sem_ch3) whose first parameter is
303    --  in-out, because in the case of an anonymous type the entity is
304    --  actually created in the procedure.
305
306    --  The following procedures treat other kinds of formal parameters
307
308    procedure Analyze_Formal_Derived_Interface_Type
309      (N   : Node_Id;
310       T   : Entity_Id;
311       Def : Node_Id);
312
313    procedure Analyze_Formal_Derived_Type
314      (N   : Node_Id;
315       T   : Entity_Id;
316       Def : Node_Id);
317
318    procedure Analyze_Formal_Interface_Type
319      (N   : Node_Id;
320       T   : Entity_Id;
321       Def : Node_Id);
322
323    --  The following subprograms create abbreviated declarations for formal
324    --  scalar types. We introduce an anonymous base of the proper class for
325    --  each of them, and define the formals as constrained first subtypes of
326    --  their bases. The bounds are expressions that are non-static in the
327    --  generic.
328
329    procedure Analyze_Formal_Decimal_Fixed_Point_Type
330                                                 (T : Entity_Id; Def : Node_Id);
331    procedure Analyze_Formal_Discrete_Type       (T : Entity_Id; Def : Node_Id);
332    procedure Analyze_Formal_Floating_Type       (T : Entity_Id; Def : Node_Id);
333    procedure Analyze_Formal_Signed_Integer_Type (T : Entity_Id; Def : Node_Id);
334    procedure Analyze_Formal_Modular_Type        (T : Entity_Id; Def : Node_Id);
335    procedure Analyze_Formal_Ordinary_Fixed_Point_Type
336                                                 (T : Entity_Id; Def : Node_Id);
337
338    procedure Analyze_Formal_Private_Type
339      (N   : Node_Id;
340       T   : Entity_Id;
341       Def : Node_Id);
342    --  Creates a new private type, which does not require completion
343
344    procedure Analyze_Generic_Formal_Part (N : Node_Id);
345
346    procedure Analyze_Generic_Access_Type (T : Entity_Id; Def : Node_Id);
347    --  Create a new access type with the given designated type
348
349    function Analyze_Associations
350      (I_Node  : Node_Id;
351       Formals : List_Id;
352       F_Copy  : List_Id) return List_Id;
353    --  At instantiation time, build the list of associations between formals
354    --  and actuals. Each association becomes a renaming declaration for the
355    --  formal entity. F_Copy is the analyzed list of formals in the generic
356    --  copy. It is used to apply legality checks to the actuals. I_Node is the
357    --  instantiation node itself.
358
359    procedure Analyze_Subprogram_Instantiation
360      (N : Node_Id;
361       K : Entity_Kind);
362
363    procedure Build_Instance_Compilation_Unit_Nodes
364      (N        : Node_Id;
365       Act_Body : Node_Id;
366       Act_Decl : Node_Id);
367    --  This procedure is used in the case where the generic instance of a
368    --  subprogram body or package body is a library unit. In this case, the
369    --  original library unit node for the generic instantiation must be
370    --  replaced by the resulting generic body, and a link made to a new
371    --  compilation unit node for the generic declaration. The argument N is
372    --  the original generic instantiation. Act_Body and Act_Decl are the body
373    --  and declaration of the instance (either package body and declaration
374    --  nodes or subprogram body and declaration nodes depending on the case).
375    --  On return, the node N has been rewritten with the actual body.
376
377    procedure Check_Access_Definition (N : Node_Id);
378    --  Subsidiary routine to null exclusion processing. Perform an assertion
379    --  check on Ada version and the presence of an access definition in N.
380
381    procedure Check_Formal_Packages (P_Id : Entity_Id);
382    --  Apply the following to all formal packages in generic associations
383
384    procedure Check_Formal_Package_Instance
385      (Formal_Pack : Entity_Id;
386       Actual_Pack : Entity_Id);
387    --  Verify that the actuals of the actual instance match the actuals of
388    --  the template for a formal package that is not declared with a box.
389
390    procedure Check_Forward_Instantiation (Decl : Node_Id);
391    --  If the generic is a local entity and the corresponding body has not
392    --  been seen yet, flag enclosing packages to indicate that it will be
393    --  elaborated after the generic body. Subprograms declared in the same
394    --  package cannot be inlined by the front-end because front-end inlining
395    --  requires a strict linear order of elaboration.
396
397    procedure Check_Hidden_Child_Unit
398      (N           : Node_Id;
399       Gen_Unit    : Entity_Id;
400       Act_Decl_Id : Entity_Id);
401    --  If the generic unit is an implicit child instance within a parent
402    --  instance, we need to make an explicit test that it is not hidden by
403    --  a child instance of the same name and parent.
404
405    procedure Check_Generic_Actuals
406      (Instance      : Entity_Id;
407       Is_Formal_Box : Boolean);
408    --  Similar to previous one. Check the actuals in the instantiation,
409    --  whose views can change between the point of instantiation and the point
410    --  of instantiation of the body. In addition, mark the generic renamings
411    --  as generic actuals, so that they are not compatible with other actuals.
412    --  Recurse on an actual that is a formal package whose declaration has
413    --  a box.
414
415    function Contains_Instance_Of
416      (Inner : Entity_Id;
417       Outer : Entity_Id;
418       N     : Node_Id) return Boolean;
419    --  Inner is instantiated within the generic Outer. Check whether Inner
420    --  directly or indirectly contains an instance of Outer or of one of its
421    --  parents, in the case of a subunit. Each generic unit holds a list of
422    --  the entities instantiated within (at any depth). This procedure
423    --  determines whether the set of such lists contains a cycle, i.e. an
424    --  illegal circular instantiation.
425
426    function Denotes_Formal_Package
427      (Pack     : Entity_Id;
428       On_Exit  : Boolean := False;
429       Instance : Entity_Id := Empty) return Boolean;
430    --  Returns True if E is a formal package of an enclosing generic, or
431    --  the actual for such a formal in an enclosing instantiation. If such
432    --  a package is used as a formal in an nested generic, or as an actual
433    --  in a nested instantiation, the visibility of ITS formals should not
434    --  be modified. When called from within Restore_Private_Views, the flag
435    --  On_Exit is true, to indicate that the search for a possible enclosing
436    --  instance should ignore the current one. In that case Instance denotes
437    --  the declaration for which this is an actual. This declaration may be
438    --  an instantiation in the source, or the internal instantiation that
439    --  corresponds to the actual for a formal package.
440
441    function Find_Actual_Type
442      (Typ       : Entity_Id;
443       Gen_Type  : Entity_Id) return Entity_Id;
444    --  When validating the actual types of a child instance, check whether
445    --  the formal is a formal type of the parent unit, and retrieve the current
446    --  actual for it. Typ is the entity in the analyzed formal type declaration
447    --  (component or index type of an array type, or designated type of an
448    --  access formal) and Gen_Type is the enclosing analyzed formal array
449    --  or access type. The desired actual may be a formal of a parent, or may
450    --  be declared in a formal package of a parent. In both cases it is a
451    --  generic actual type because it appears within a visible instance.
452    --  Finally, it may be declared in a parent unit without being a formal
453    --  of that unit, in which case it must be retrieved by visibility.
454    --  Ambiguities may still arise if two homonyms are declared in two formal
455    --  packages, and the prefix of the formal type may be needed to resolve
456    --  the ambiguity in the instance ???
457
458    function In_Same_Declarative_Part
459      (F_Node : Node_Id;
460       Inst   : Node_Id) return Boolean;
461    --  True if the instantiation Inst and the given freeze_node F_Node appear
462    --  within the same declarative part, ignoring subunits, but with no inter-
463    --  vening subprograms or concurrent units. If true, the freeze node
464    --  of the instance can be placed after the freeze node of the parent,
465    --  which it itself an instance.
466
467    function In_Main_Context (E : Entity_Id) return Boolean;
468    --  Check whether an instantiation is in the context of the main unit.
469    --  Used to determine whether its body should be elaborated to allow
470    --  front-end inlining.
471
472    function Is_Generic_Formal (E : Entity_Id) return Boolean;
473    --  Utility to determine whether a given entity is declared by means of
474    --  of a formal parameter declaration. Used to set properly the visibility
475    --  of generic formals of a generic package declared with a box or with
476    --  partial parametrization.
477
478    procedure Set_Instance_Env
479      (Gen_Unit : Entity_Id;
480       Act_Unit : Entity_Id);
481    --  Save current instance on saved environment, to be used to determine
482    --  the global status of entities in nested instances. Part of Save_Env.
483    --  called after verifying that the generic unit is legal for the instance,
484    --  The procedure also examines whether the generic unit is a predefined
485    --  unit, in order to set configuration switches accordingly. As a result
486    --  the procedure must be called after analyzing and freezing the actuals.
487
488    procedure Set_Instance_Of (A : Entity_Id; B : Entity_Id);
489    --  Associate analyzed generic parameter with corresponding
490    --  instance. Used for semantic checks at instantiation time.
491
492    function Has_Been_Exchanged (E : Entity_Id) return Boolean;
493    --  Traverse the Exchanged_Views list to see if a type was private
494    --  and has already been flipped during this phase of instantiation.
495
496    procedure Hide_Current_Scope;
497    --  When instantiating a generic child unit, the parent context must be
498    --  present, but the instance and all entities that may be generated
499    --  must be inserted in the current scope. We leave the current scope
500    --  on the stack, but make its entities invisible to avoid visibility
501    --  problems. This is reversed at the end of the instantiation. This is
502    --  not done for the instantiation of the bodies, which only require the
503    --  instances of the generic parents to be in scope.
504
505    procedure Install_Body
506      (Act_Body : Node_Id;
507       N        : Node_Id;
508       Gen_Body : Node_Id;
509       Gen_Decl : Node_Id);
510    --  If the instantiation happens textually before the body of the generic,
511    --  the instantiation of the body must be analyzed after the generic body,
512    --  and not at the point of instantiation. Such early instantiations can
513    --  happen if the generic and the instance appear in  a package declaration
514    --  because the generic body can only appear in the corresponding package
515    --  body. Early instantiations can also appear if generic, instance and
516    --  body are all in the declarative part of a subprogram or entry. Entities
517    --  of packages that are early instantiations are delayed, and their freeze
518    --  node appears after the generic body.
519
520    procedure Insert_After_Last_Decl (N : Node_Id; F_Node : Node_Id);
521    --  Insert freeze node at the end of the declarative part that includes the
522    --  instance node N. If N is in the visible part of an enclosing package
523    --  declaration, the freeze node has to be inserted at the end of the
524    --  private declarations, if any.
525
526    procedure Freeze_Subprogram_Body
527      (Inst_Node : Node_Id;
528       Gen_Body  : Node_Id;
529       Pack_Id   : Entity_Id);
530    --  The generic body may appear textually after the instance, including
531    --  in the proper body of a stub, or within a different package instance.
532    --  Given that the instance can only be elaborated after the generic, we
533    --  place freeze_nodes for the instance and/or for packages that may enclose
534    --  the instance and the generic, so that the back-end can establish the
535    --  proper order of elaboration.
536
537    procedure Init_Env;
538    --  Establish environment for subsequent instantiation. Separated from
539    --  Save_Env because data-structures for visibility handling must be
540    --  initialized before call to Check_Generic_Child_Unit.
541
542    procedure Install_Formal_Packages (Par : Entity_Id);
543    --  If any of the formals of the parent are formal packages with box,
544    --  their formal parts are visible in the parent and thus in the child
545    --  unit as well. Analogous to what is done in Check_Generic_Actuals
546    --  for the unit itself. This procedure is also used in an instance, to
547    --  make visible the proper entities of the actual for a formal package
548    --  declared with a box.
549
550    procedure Install_Parent (P : Entity_Id; In_Body : Boolean := False);
551    --  When compiling an instance of a child unit the parent (which is
552    --  itself an instance) is an enclosing scope that must be made
553    --  immediately visible. This procedure is also used to install the non-
554    --  generic parent of a generic child unit when compiling its body, so
555    --  that full views of types in the parent are made visible.
556
557    procedure Remove_Parent (In_Body : Boolean := False);
558    --  Reverse effect after instantiation of child is complete
559
560    procedure Inline_Instance_Body
561      (N        : Node_Id;
562       Gen_Unit : Entity_Id;
563       Act_Decl : Node_Id);
564    --  If front-end inlining is requested, instantiate the package body,
565    --  and preserve the visibility of its compilation unit, to insure
566    --  that successive instantiations succeed.
567
568    --  The functions Instantiate_XXX perform various legality checks and build
569    --  the declarations for instantiated generic parameters. In all of these
570    --  Formal is the entity in the generic unit, Actual is the entity of
571    --  expression in the generic associations, and Analyzed_Formal is the
572    --  formal in the generic copy, which contains the semantic information to
573    --  be used to validate the actual.
574
575    function Instantiate_Object
576      (Formal          : Node_Id;
577       Actual          : Node_Id;
578       Analyzed_Formal : Node_Id) return List_Id;
579
580    function Instantiate_Type
581      (Formal          : Node_Id;
582       Actual          : Node_Id;
583       Analyzed_Formal : Node_Id;
584       Actual_Decls    : List_Id) return List_Id;
585
586    function Instantiate_Formal_Subprogram
587      (Formal          : Node_Id;
588       Actual          : Node_Id;
589       Analyzed_Formal : Node_Id) return Node_Id;
590
591    function Instantiate_Formal_Package
592      (Formal          : Node_Id;
593       Actual          : Node_Id;
594       Analyzed_Formal : Node_Id) return List_Id;
595    --  If the formal package is declared with a box, special visibility rules
596    --  apply to its formals: they are in the visible part of the package. This
597    --  is true in the declarative region of the formal package, that is to say
598    --  in the enclosing generic or instantiation. For an instantiation, the
599    --  parameters of the formal package are made visible in an explicit step.
600    --  Furthermore, if the actual has a visible USE clause, these formals must
601    --  be made potentially use-visible as well. On exit from the enclosing
602    --  instantiation, the reverse must be done.
603
604    --  For a formal package declared without a box, there are conformance rules
605    --  that apply to the actuals in the generic declaration and the actuals of
606    --  the actual package in the enclosing instantiation. The simplest way to
607    --  apply these rules is to repeat the instantiation of the formal package
608    --  in the context of the enclosing instance, and compare the generic
609    --  associations of this instantiation with those of the actual package.
610    --  This internal instantiation only needs to contain the renamings of the
611    --  formals: the visible and private declarations themselves need not be
612    --  created.
613
614    --  In Ada 2005, the formal package may be only partially parametrized. In
615    --  that case the visibility step must make visible those actuals whose
616    --  corresponding formals were given with a box. A final complication
617    --  involves inherited operations from formal derived types, which must be
618    --  visible if the type is.
619
620    function Is_In_Main_Unit (N : Node_Id) return Boolean;
621    --  Test if given node is in the main unit
622
623    procedure Load_Parent_Of_Generic
624      (N             : Node_Id;
625       Spec          : Node_Id;
626       Body_Optional : Boolean := False);
627    --  If the generic appears in a separate non-generic library unit, load the
628    --  corresponding body to retrieve the body of the generic. N is the node
629    --  for the generic instantiation, Spec is the generic package declaration.
630    --
631    --  Body_Optional is a flag that indicates that the body is being loaded to
632    --  ensure that temporaries are generated consistently when there are other
633    --  instances in the current declarative part that precede the one being
634    --  loaded. In that case a missing body is acceptable.
635
636    procedure Inherit_Context (Gen_Decl : Node_Id; Inst : Node_Id);
637    --  Add the context clause of the unit containing a generic unit to a
638    --  compilation unit that is, or contains, an instantiation.
639
640    function Get_Associated_Node (N : Node_Id) return Node_Id;
641    --  In order to propagate semantic information back from the analyzed copy
642    --  to the original generic, we maintain links between selected nodes in the
643    --  generic and their corresponding copies. At the end of generic analysis,
644    --  the routine Save_Global_References traverses the generic tree, examines
645    --  the semantic information, and preserves the links to those nodes that
646    --  contain global information. At instantiation, the information from the
647    --  associated node is placed on the new copy, so that name resolution is
648    --  not repeated.
649    --
650    --  Three kinds of source nodes have associated nodes:
651    --
652    --    a) those that can reference (denote) entities, that is identifiers,
653    --       character literals, expanded_names, operator symbols, operators,
654    --       and attribute reference nodes. These nodes have an Entity field
655    --       and are the set of nodes that are in N_Has_Entity.
656    --
657    --    b) aggregates (N_Aggregate and N_Extension_Aggregate)
658    --
659    --    c) selected components (N_Selected_Component)
660    --
661    --  For the first class, the associated node preserves the entity if it is
662    --  global. If the generic contains nested instantiations, the associated
663    --  node itself has been recopied, and a chain of them must be followed.
664    --
665    --  For aggregates, the associated node allows retrieval of the type, which
666    --  may otherwise not appear in the generic. The view of this type may be
667    --  different between generic and instantiation, and the full view can be
668    --  installed before the instantiation is analyzed. For aggregates of type
669    --  extensions, the same view exchange may have to be performed for some of
670    --  the ancestor types, if their view is private at the point of
671    --  instantiation.
672    --
673    --  Nodes that are selected components in the parse tree may be rewritten
674    --  as expanded names after resolution, and must be treated as potential
675    --  entity holders, which is why they also have an Associated_Node.
676    --
677    --  Nodes that do not come from source, such as freeze nodes, do not appear
678    --  in the generic tree, and need not have an associated node.
679    --
680    --  The associated node is stored in the Associated_Node field. Note that
681    --  this field overlaps Entity, which is fine, because the whole point is
682    --  that we don't need or want the normal Entity field in this situation.
683
684    procedure Map_Formal_Package_Entities (Form : Entity_Id; Act : Entity_Id);
685    --  Within the generic part, entities in the formal package are
686    --  visible. To validate subsequent type declarations, indicate
687    --  the correspondence between the entities in the analyzed formal,
688    --  and the entities in  the actual package. There are three packages
689    --  involved in the instantiation of a formal package: the parent
690    --  generic P1 which appears in the generic declaration, the fake
691    --  instantiation P2 which appears in the analyzed generic, and whose
692    --  visible entities may be used in subsequent formals, and the actual
693    --  P3 in the instance. To validate subsequent formals, me indicate
694    --  that the entities in P2 are mapped into those of P3. The mapping of
695    --  entities has to be done recursively for nested packages.
696
697    procedure Move_Freeze_Nodes
698      (Out_Of : Entity_Id;
699       After  : Node_Id;
700       L      : List_Id);
701    --  Freeze nodes can be generated in the analysis of a generic unit, but
702    --  will not be seen by the back-end. It is necessary to move those nodes
703    --  to the enclosing scope if they freeze an outer entity. We place them
704    --  at the end of the enclosing generic package, which is semantically
705    --  neutral.
706
707    procedure Preanalyze_Actuals (N : Node_Id);
708    --  Analyze actuals to perform name resolution. Full resolution is done
709    --  later, when the expected types are known, but names have to be captured
710    --  before installing parents of generics, that are not visible for the
711    --  actuals themselves.
712
713    procedure Valid_Default_Attribute (Nam : Entity_Id; Def : Node_Id);
714    --  Verify that an attribute that appears as the default for a formal
715    --  subprogram is a function or procedure with the correct profile.
716
717    -------------------------------------------
718    -- Data Structures for Generic Renamings --
719    -------------------------------------------
720
721    --  The map Generic_Renamings associates generic entities with their
722    --  corresponding actuals. Currently used to validate type instances. It
723    --  will eventually be used for all generic parameters to eliminate the
724    --  need for overload resolution in the instance.
725
726    type Assoc_Ptr is new Int;
727
728    Assoc_Null : constant Assoc_Ptr := -1;
729
730    type Assoc is record
731       Gen_Id         : Entity_Id;
732       Act_Id         : Entity_Id;
733       Next_In_HTable : Assoc_Ptr;
734    end record;
735
736    package Generic_Renamings is new Table.Table
737      (Table_Component_Type => Assoc,
738       Table_Index_Type     => Assoc_Ptr,
739       Table_Low_Bound      => 0,
740       Table_Initial        => 10,
741       Table_Increment      => 100,
742       Table_Name           => "Generic_Renamings");
743
744    --  Variable to hold enclosing instantiation. When the environment is
745    --  saved for a subprogram inlining, the corresponding Act_Id is empty.
746
747    Current_Instantiated_Parent : Assoc := (Empty, Empty, Assoc_Null);
748
749    --  Hash table for associations
750
751    HTable_Size : constant := 37;
752    type HTable_Range is range 0 .. HTable_Size - 1;
753
754    procedure Set_Next_Assoc (E : Assoc_Ptr; Next : Assoc_Ptr);
755    function  Next_Assoc     (E : Assoc_Ptr) return Assoc_Ptr;
756    function Get_Gen_Id      (E : Assoc_Ptr) return Entity_Id;
757    function Hash            (F : Entity_Id) return HTable_Range;
758
759    package Generic_Renamings_HTable is new GNAT.HTable.Static_HTable (
760       Header_Num => HTable_Range,
761       Element    => Assoc,
762       Elmt_Ptr   => Assoc_Ptr,
763       Null_Ptr   => Assoc_Null,
764       Set_Next   => Set_Next_Assoc,
765       Next       => Next_Assoc,
766       Key        => Entity_Id,
767       Get_Key    => Get_Gen_Id,
768       Hash       => Hash,
769       Equal      => "=");
770
771    Exchanged_Views : Elist_Id;
772    --  This list holds the private views that have been exchanged during
773    --  instantiation to restore the visibility of the generic declaration.
774    --  (see comments above). After instantiation, the current visibility is
775    --  reestablished by means of a traversal of this list.
776
777    Hidden_Entities : Elist_Id;
778    --  This list holds the entities of the current scope that are removed
779    --  from immediate visibility when instantiating a child unit. Their
780    --  visibility is restored in Remove_Parent.
781
782    --  Because instantiations can be recursive, the following must be saved
783    --  on entry and restored on exit from an instantiation (spec or body).
784    --  This is done by the two procedures Save_Env and Restore_Env. For
785    --  package and subprogram instantiations (but not for the body instances)
786    --  the action of Save_Env is done in two steps: Init_Env is called before
787    --  Check_Generic_Child_Unit, because setting the parent instances requires
788    --  that the visibility data structures be properly initialized. Once the
789    --  generic is unit is validated, Set_Instance_Env completes Save_Env.
790
791    Parent_Unit_Visible : Boolean := False;
792    --  Parent_Unit_Visible is used when the generic is a child unit, and
793    --  indicates whether the ultimate parent of the generic is visible in the
794    --  instantiation environment. It is used to reset the visibility of the
795    --  parent at the end of the instantiation (see Remove_Parent).
796
797    Instance_Parent_Unit : Entity_Id := Empty;
798    --  This records the ultimate parent unit of an instance of a generic
799    --  child unit and is used in conjunction with Parent_Unit_Visible to
800    --  indicate the unit to which the Parent_Unit_Visible flag corresponds.
801
802    type Instance_Env is record
803       Instantiated_Parent  : Assoc;
804       Exchanged_Views      : Elist_Id;
805       Hidden_Entities      : Elist_Id;
806       Current_Sem_Unit     : Unit_Number_Type;
807       Parent_Unit_Visible  : Boolean   := False;
808       Instance_Parent_Unit : Entity_Id := Empty;
809       Switches             : Config_Switches_Type;
810    end record;
811
812    package Instance_Envs is new Table.Table (
813      Table_Component_Type => Instance_Env,
814      Table_Index_Type     => Int,
815      Table_Low_Bound      => 0,
816      Table_Initial        => 32,
817      Table_Increment      => 100,
818      Table_Name           => "Instance_Envs");
819
820    procedure Restore_Private_Views
821      (Pack_Id    : Entity_Id;
822       Is_Package : Boolean := True);
823    --  Restore the private views of external types, and unmark the generic
824    --  renamings of actuals, so that they become compatible subtypes again.
825    --  For subprograms, Pack_Id is the package constructed to hold the
826    --  renamings.
827
828    procedure Switch_View (T : Entity_Id);
829    --  Switch the partial and full views of a type and its private
830    --  dependents (i.e. its subtypes and derived types).
831
832    ------------------------------------
833    -- Structures for Error Reporting --
834    ------------------------------------
835
836    Instantiation_Node : Node_Id;
837    --  Used by subprograms that validate instantiation of formal parameters
838    --  where there might be no actual on which to place the error message.
839    --  Also used to locate the instantiation node for generic subunits.
840
841    Instantiation_Error : exception;
842    --  When there is a semantic error in the generic parameter matching,
843    --  there is no point in continuing the instantiation, because the
844    --  number of cascaded errors is unpredictable. This exception aborts
845    --  the instantiation process altogether.
846
847    S_Adjustment : Sloc_Adjustment;
848    --  Offset created for each node in an instantiation, in order to keep
849    --  track of the source position of the instantiation in each of its nodes.
850    --  A subsequent semantic error or warning on a construct of the instance
851    --  points to both places: the original generic node, and the point of
852    --  instantiation. See Sinput and Sinput.L for additional details.
853
854    ------------------------------------------------------------
855    -- Data structure for keeping track when inside a Generic --
856    ------------------------------------------------------------
857
858    --  The following table is used to save values of the Inside_A_Generic
859    --  flag (see spec of Sem) when they are saved by Start_Generic.
860
861    package Generic_Flags is new Table.Table (
862      Table_Component_Type => Boolean,
863      Table_Index_Type     => Int,
864      Table_Low_Bound      => 0,
865      Table_Initial        => 32,
866      Table_Increment      => 200,
867      Table_Name           => "Generic_Flags");
868
869    ---------------------------
870    -- Abandon_Instantiation --
871    ---------------------------
872
873    procedure Abandon_Instantiation (N : Node_Id) is
874    begin
875       Error_Msg_N ("\instantiation abandoned!", N);
876       raise Instantiation_Error;
877    end Abandon_Instantiation;
878
879    --------------------------
880    -- Analyze_Associations --
881    --------------------------
882
883    function Analyze_Associations
884      (I_Node  : Node_Id;
885       Formals : List_Id;
886       F_Copy  : List_Id) return List_Id
887    is
888
889       Actual_Types    : constant Elist_Id  := New_Elmt_List;
890       Assoc           : constant List_Id   := New_List;
891       Default_Actuals : constant Elist_Id  := New_Elmt_List;
892       Gen_Unit        : constant Entity_Id :=
893                           Defining_Entity (Parent (F_Copy));
894
895       Actuals         : List_Id;
896       Actual          : Node_Id;
897       Formal          : Node_Id;
898       Next_Formal     : Node_Id;
899       Temp_Formal     : Node_Id;
900       Analyzed_Formal : Node_Id;
901       Match           : Node_Id;
902       Named           : Node_Id;
903       First_Named     : Node_Id := Empty;
904
905       Default_Formals : constant List_Id := New_List;
906       --  If an Others_Choice is present, some of the formals may be defaulted.
907       --  To simplify the treatment of visibility in an instance, we introduce
908       --  individual defaults for each such formal. These defaults are
909       --  appended to the list of associations and replace the Others_Choice.
910
911       Found_Assoc : Node_Id;
912       --  Association for the current formal being match. Empty if there are
913       --  no remaining actuals, or if there is no named association with the
914       --  name of the formal.
915
916       Is_Named_Assoc : Boolean;
917       Num_Matched    : Int := 0;
918       Num_Actuals    : Int := 0;
919
920       Others_Present : Boolean := False;
921       --  In Ada 2005, indicates partial parametrization of a formal
922       --  package. As usual an other association must be last in the list.
923
924       function Matching_Actual
925         (F   : Entity_Id;
926          A_F : Entity_Id) return Node_Id;
927       --  Find actual that corresponds to a given a formal parameter. If the
928       --  actuals are positional, return the next one, if any. If the actuals
929       --  are named, scan the parameter associations to find the right one.
930       --  A_F is the corresponding entity in the analyzed generic,which is
931       --  placed on the selector name for ASIS use.
932
933       --  In Ada 2005, a named association may be given with a box, in which
934       --  case Matching_Actual sets Found_Assoc to the generic association,
935       --  but return Empty for the actual itself. In this case the code below
936       --  creates a corresponding declaration for the formal.
937
938       function Partial_Parametrization return Boolean;
939       --  Ada 2005: if no match is found for a given formal, check if the
940       --  association for it includes a box, or whether the associations
941       --  include an Others clause.
942
943       procedure Process_Default (F : Entity_Id);
944       --  Add a copy of the declaration of generic formal  F to the list of
945       --  associations, and add an explicit box association for F  if there
946       --  is none yet, and the default comes from an Others_Choice.
947
948       procedure Set_Analyzed_Formal;
949       --  Find the node in the generic copy that corresponds to a given formal.
950       --  The semantic information on this node is used to perform legality
951       --  checks on the actuals. Because semantic analysis can introduce some
952       --  anonymous entities or modify the declaration node itself, the
953       --  correspondence between the two lists is not one-one. In addition to
954       --  anonymous types, the presence a formal equality will introduce an
955       --  implicit declaration for the corresponding inequality.
956
957       ---------------------
958       -- Matching_Actual --
959       ---------------------
960
961       function Matching_Actual
962         (F   : Entity_Id;
963          A_F : Entity_Id) return Node_Id
964       is
965          Prev  : Node_Id;
966          Act   : Node_Id;
967
968       begin
969          Is_Named_Assoc := False;
970
971          --  End of list of purely positional parameters
972
973          if No (Actual) or else Nkind (Actual) = N_Others_Choice then
974             Found_Assoc := Empty;
975             Act         := Empty;
976
977          --  Case of positional parameter corresponding to current formal
978
979          elsif No (Selector_Name (Actual)) then
980             Found_Assoc := Actual;
981             Act :=  Explicit_Generic_Actual_Parameter (Actual);
982             Num_Matched := Num_Matched + 1;
983             Next (Actual);
984
985          --  Otherwise scan list of named actuals to find the one with the
986          --  desired name. All remaining actuals have explicit names.
987
988          else
989             Is_Named_Assoc := True;
990             Found_Assoc := Empty;
991             Act         := Empty;
992             Prev        := Empty;
993
994             while Present (Actual) loop
995                if Chars (Selector_Name (Actual)) = Chars (F) then
996                   Set_Entity (Selector_Name (Actual), A_F);
997                   Set_Etype  (Selector_Name (Actual), Etype (A_F));
998                   Generate_Reference (A_F, Selector_Name (Actual));
999                   Found_Assoc := Actual;
1000                   Act :=  Explicit_Generic_Actual_Parameter (Actual);
1001                   Num_Matched := Num_Matched + 1;
1002                   exit;
1003                end if;
1004
1005                Prev := Actual;
1006                Next (Actual);
1007             end loop;
1008
1009             --  Reset for subsequent searches. In most cases the named
1010             --  associations are in order. If they are not, we reorder them
1011             --  to avoid scanning twice the same actual. This is not just a
1012             --  question of efficiency: there may be multiple defaults with
1013             --  boxes that have the same name. In a nested instantiation we
1014             --  insert actuals for those defaults, and cannot rely on their
1015             --  names to disambiguate them.
1016
1017             if Actual = First_Named  then
1018                Next (First_Named);
1019
1020             elsif Present (Actual) then
1021                Insert_Before (First_Named, Remove_Next (Prev));
1022             end if;
1023
1024             Actual := First_Named;
1025          end if;
1026
1027          if Is_Entity_Name (Act) and then Present (Entity (Act)) then
1028             Set_Used_As_Generic_Actual (Entity (Act));
1029          end if;
1030
1031          return Act;
1032       end Matching_Actual;
1033
1034       -----------------------------
1035       -- Partial_Parametrization --
1036       -----------------------------
1037
1038       function Partial_Parametrization return Boolean is
1039       begin
1040          return Others_Present
1041           or else (Present (Found_Assoc) and then Box_Present (Found_Assoc));
1042       end Partial_Parametrization;
1043
1044       ---------------------
1045       -- Process_Default --
1046       ---------------------
1047
1048       procedure Process_Default (F : Entity_Id)  is
1049          Loc     : constant Source_Ptr := Sloc (I_Node);
1050          F_Id    : constant Entity_Id  := Defining_Entity (F);
1051          Decl    : Node_Id;
1052          Default : Node_Id;
1053          Id      : Entity_Id;
1054
1055       begin
1056          --  Append copy of formal declaration to associations, and create new
1057          --  defining identifier for it.
1058
1059          Decl := New_Copy_Tree (F);
1060          Id := Make_Defining_Identifier (Sloc (F_Id), Chars => Chars (F_Id));
1061
1062          if Nkind (F) in N_Formal_Subprogram_Declaration then
1063             Set_Defining_Unit_Name (Specification (Decl), Id);
1064
1065          else
1066             Set_Defining_Identifier (Decl, Id);
1067          end if;
1068
1069          Append (Decl, Assoc);
1070
1071          if No (Found_Assoc) then
1072             Default :=
1073                Make_Generic_Association (Loc,
1074                  Selector_Name => New_Occurrence_Of (Id, Loc),
1075                  Explicit_Generic_Actual_Parameter => Empty);
1076             Set_Box_Present (Default);
1077             Append (Default, Default_Formals);
1078          end if;
1079       end Process_Default;
1080
1081       -------------------------
1082       -- Set_Analyzed_Formal --
1083       -------------------------
1084
1085       procedure Set_Analyzed_Formal is
1086          Kind : Node_Kind;
1087
1088       begin
1089          while Present (Analyzed_Formal) loop
1090             Kind := Nkind (Analyzed_Formal);
1091
1092             case Nkind (Formal) is
1093
1094                when N_Formal_Subprogram_Declaration =>
1095                   exit when Kind in N_Formal_Subprogram_Declaration
1096                     and then
1097                       Chars
1098                         (Defining_Unit_Name (Specification (Formal))) =
1099                       Chars
1100                         (Defining_Unit_Name (Specification (Analyzed_Formal)));
1101
1102                when N_Formal_Package_Declaration =>
1103                   exit when Nkind_In (Kind, N_Formal_Package_Declaration,
1104                                             N_Generic_Package_Declaration,
1105                                             N_Package_Declaration);
1106
1107                when N_Use_Package_Clause | N_Use_Type_Clause => exit;
1108
1109                when others =>
1110
1111                   --  Skip freeze nodes, and nodes inserted to replace
1112                   --  unrecognized pragmas.
1113
1114                   exit when
1115                     Kind not in N_Formal_Subprogram_Declaration
1116                       and then not Nkind_In (Kind, N_Subprogram_Declaration,
1117                                                    N_Freeze_Entity,
1118                                                    N_Null_Statement,
1119                                                    N_Itype_Reference)
1120                       and then Chars (Defining_Identifier (Formal)) =
1121                                Chars (Defining_Identifier (Analyzed_Formal));
1122             end case;
1123
1124             Next (Analyzed_Formal);
1125          end loop;
1126       end Set_Analyzed_Formal;
1127
1128    --  Start of processing for Analyze_Associations
1129
1130    begin
1131       Actuals := Generic_Associations (I_Node);
1132
1133       if Present (Actuals) then
1134
1135          --  Check for an Others choice, indicating a partial parametrization
1136          --  for a formal package.
1137
1138          Actual := First (Actuals);
1139          while Present (Actual) loop
1140             if Nkind (Actual) = N_Others_Choice then
1141                Others_Present := True;
1142
1143                if Present (Next (Actual)) then
1144                   Error_Msg_N ("others must be last association", Actual);
1145                end if;
1146
1147                --  This subprogram is used both for formal packages and for
1148                --  instantiations. For the latter, associations must all be
1149                --  explicit.
1150
1151                if Nkind (I_Node) /= N_Formal_Package_Declaration
1152                  and then Comes_From_Source (I_Node)
1153                then
1154                   Error_Msg_N
1155                     ("others association not allowed in an instance",
1156                       Actual);
1157                end if;
1158
1159                --  In any case, nothing to do after the others association
1160
1161                exit;
1162
1163             elsif Box_Present (Actual)
1164               and then Comes_From_Source (I_Node)
1165               and then Nkind (I_Node) /= N_Formal_Package_Declaration
1166             then
1167                Error_Msg_N
1168                  ("box association not allowed in an instance", Actual);
1169             end if;
1170
1171             Next (Actual);
1172          end loop;
1173
1174          --  If named associations are present, save first named association
1175          --  (it may of course be Empty) to facilitate subsequent name search.
1176
1177          First_Named := First (Actuals);
1178          while Present (First_Named)
1179            and then Nkind (First_Named) /= N_Others_Choice
1180            and then No (Selector_Name (First_Named))
1181          loop
1182             Num_Actuals := Num_Actuals + 1;
1183             Next (First_Named);
1184          end loop;
1185       end if;
1186
1187       Named := First_Named;
1188       while Present (Named) loop
1189          if Nkind (Named) /= N_Others_Choice
1190            and then  No (Selector_Name (Named))
1191          then
1192             Error_Msg_N ("invalid positional actual after named one", Named);
1193             Abandon_Instantiation (Named);
1194          end if;
1195
1196          --  A named association may lack an actual parameter, if it was
1197          --  introduced for a default subprogram that turns out to be local
1198          --  to the outer instantiation.
1199
1200          if Nkind (Named) /= N_Others_Choice
1201            and then Present (Explicit_Generic_Actual_Parameter (Named))
1202          then
1203             Num_Actuals := Num_Actuals + 1;
1204          end if;
1205
1206          Next (Named);
1207       end loop;
1208
1209       if Present (Formals) then
1210          Formal := First_Non_Pragma (Formals);
1211          Analyzed_Formal := First_Non_Pragma (F_Copy);
1212
1213          if Present (Actuals) then
1214             Actual := First (Actuals);
1215
1216          --  All formals should have default values
1217
1218          else
1219             Actual := Empty;
1220          end if;
1221
1222          while Present (Formal) loop
1223             Set_Analyzed_Formal;
1224             Next_Formal := Next_Non_Pragma (Formal);
1225
1226             case Nkind (Formal) is
1227                when N_Formal_Object_Declaration =>
1228                   Match :=
1229                     Matching_Actual (
1230                       Defining_Identifier (Formal),
1231                       Defining_Identifier (Analyzed_Formal));
1232
1233                   if No (Match) and then Partial_Parametrization then
1234                      Process_Default (Formal);
1235                   else
1236                      Append_List
1237                        (Instantiate_Object (Formal, Match, Analyzed_Formal),
1238                         Assoc);
1239                   end if;
1240
1241                when N_Formal_Type_Declaration =>
1242                   Match :=
1243                     Matching_Actual (
1244                       Defining_Identifier (Formal),
1245                       Defining_Identifier (Analyzed_Formal));
1246
1247                   if No (Match) then
1248                      if Partial_Parametrization then
1249                         Process_Default (Formal);
1250
1251                      else
1252                         Error_Msg_Sloc := Sloc (Gen_Unit);
1253                         Error_Msg_NE
1254                           ("missing actual&",
1255                             Instantiation_Node,
1256                               Defining_Identifier (Formal));
1257                         Error_Msg_NE ("\in instantiation of & declared#",
1258                             Instantiation_Node, Gen_Unit);
1259                         Abandon_Instantiation (Instantiation_Node);
1260                      end if;
1261
1262                   else
1263                      Analyze (Match);
1264                      Append_List
1265                        (Instantiate_Type
1266                          (Formal, Match, Analyzed_Formal, Assoc),
1267                        Assoc);
1268
1269                      --  An instantiation is a freeze point for the actuals,
1270                      --  unless this is a rewritten formal package.
1271
1272                      if Nkind (I_Node) /= N_Formal_Package_Declaration then
1273                         Append_Elmt (Entity (Match), Actual_Types);
1274                      end if;
1275                   end if;
1276
1277                   --  A remote access-to-class-wide type must not be an
1278                   --  actual parameter for a generic formal of an access
1279                   --  type (E.2.2 (17)).
1280
1281                   if Nkind (Analyzed_Formal) = N_Formal_Type_Declaration
1282                     and then
1283                       Nkind (Formal_Type_Definition (Analyzed_Formal)) =
1284                                             N_Access_To_Object_Definition
1285                   then
1286                      Validate_Remote_Access_To_Class_Wide_Type (Match);
1287                   end if;
1288
1289                when N_Formal_Subprogram_Declaration =>
1290                   Match :=
1291                     Matching_Actual (
1292                       Defining_Unit_Name (Specification (Formal)),
1293                       Defining_Unit_Name (Specification (Analyzed_Formal)));
1294
1295                   --  If the formal subprogram has the same name as another
1296                   --  formal subprogram of the generic, then a named
1297                   --  association is illegal (12.3(9)). Exclude named
1298                   --  associations that are generated for a nested instance.
1299
1300                   if Present (Match)
1301                     and then Is_Named_Assoc
1302                     and then Comes_From_Source (Found_Assoc)
1303                   then
1304                      Temp_Formal := First (Formals);
1305                      while Present (Temp_Formal) loop
1306                         if Nkind (Temp_Formal) in
1307                              N_Formal_Subprogram_Declaration
1308                           and then Temp_Formal /= Formal
1309                           and then
1310                             Chars (Selector_Name (Found_Assoc)) =
1311                               Chars (Defining_Unit_Name
1312                                        (Specification (Temp_Formal)))
1313                         then
1314                            Error_Msg_N
1315                              ("name not allowed for overloaded formal",
1316                               Found_Assoc);
1317                            Abandon_Instantiation (Instantiation_Node);
1318                         end if;
1319
1320                         Next (Temp_Formal);
1321                      end loop;
1322                   end if;
1323
1324                   --  If there is no corresponding actual, this may be case of
1325                   --  partial parametrization, or else the formal has a default
1326                   --  or a box.
1327
1328                   if No (Match)
1329                     and then  Partial_Parametrization
1330                   then
1331                      Process_Default (Formal);
1332                   else
1333                      Append_To (Assoc,
1334                        Instantiate_Formal_Subprogram
1335                          (Formal, Match, Analyzed_Formal));
1336                   end if;
1337
1338                   --  If this is a nested generic, preserve default for later
1339                   --  instantiations.
1340
1341                   if No (Match)
1342                     and then Box_Present (Formal)
1343                   then
1344                      Append_Elmt
1345                        (Defining_Unit_Name (Specification (Last (Assoc))),
1346                         Default_Actuals);
1347                   end if;
1348
1349                when N_Formal_Package_Declaration =>
1350                   Match :=
1351                     Matching_Actual (
1352                       Defining_Identifier (Formal),
1353                       Defining_Identifier (Original_Node (Analyzed_Formal)));
1354
1355                   if No (Match) then
1356                      if Partial_Parametrization then
1357                         Process_Default (Formal);
1358
1359                      else
1360                         Error_Msg_Sloc := Sloc (Gen_Unit);
1361                         Error_Msg_NE
1362                           ("missing actual&",
1363                             Instantiation_Node, Defining_Identifier (Formal));
1364                         Error_Msg_NE ("\in instantiation of & declared#",
1365                             Instantiation_Node, Gen_Unit);
1366
1367                         Abandon_Instantiation (Instantiation_Node);
1368                      end if;
1369
1370                   else
1371                      Analyze (Match);
1372                      Append_List
1373                        (Instantiate_Formal_Package
1374                          (Formal, Match, Analyzed_Formal),
1375                         Assoc);
1376                   end if;
1377
1378                --  For use type and use package appearing in the generic part,
1379                --  we have already copied them, so we can just move them where
1380                --  they belong (we mustn't recopy them since this would mess up
1381                --  the Sloc values).
1382
1383                when N_Use_Package_Clause |
1384                     N_Use_Type_Clause    =>
1385                   if Nkind (Original_Node (I_Node)) =
1386                     N_Formal_Package_Declaration
1387                   then
1388                      Append (New_Copy_Tree (Formal), Assoc);
1389                   else
1390                      Remove (Formal);
1391                      Append (Formal, Assoc);
1392                   end if;
1393
1394                when others =>
1395                   raise Program_Error;
1396
1397             end case;
1398
1399             Formal := Next_Formal;
1400             Next_Non_Pragma (Analyzed_Formal);
1401          end loop;
1402
1403          if Num_Actuals > Num_Matched then
1404             Error_Msg_Sloc := Sloc (Gen_Unit);
1405
1406             if Present (Selector_Name (Actual)) then
1407                Error_Msg_NE
1408                  ("unmatched actual&",
1409                     Actual, Selector_Name (Actual));
1410                Error_Msg_NE ("\in instantiation of& declared#",
1411                     Actual, Gen_Unit);
1412             else
1413                Error_Msg_NE
1414                  ("unmatched actual in instantiation of& declared#",
1415                    Actual, Gen_Unit);
1416             end if;
1417          end if;
1418
1419       elsif Present (Actuals) then
1420          Error_Msg_N
1421            ("too many actuals in generic instantiation", Instantiation_Node);
1422       end if;
1423
1424       declare
1425          Elmt : Elmt_Id := First_Elmt (Actual_Types);
1426       begin
1427          while Present (Elmt) loop
1428             Freeze_Before (I_Node, Node (Elmt));
1429             Next_Elmt (Elmt);
1430          end loop;
1431       end;
1432
1433       --  If there are default subprograms, normalize the tree by adding
1434       --  explicit associations for them. This is required if the instance
1435       --  appears within a generic.
1436
1437       declare
1438          Elmt  : Elmt_Id;
1439          Subp  : Entity_Id;
1440          New_D : Node_Id;
1441
1442       begin
1443          Elmt := First_Elmt (Default_Actuals);
1444          while Present (Elmt) loop
1445             if No (Actuals) then
1446                Actuals := New_List;
1447                Set_Generic_Associations (I_Node, Actuals);
1448             end if;
1449
1450             Subp := Node (Elmt);
1451             New_D :=
1452               Make_Generic_Association (Sloc (Subp),
1453                 Selector_Name => New_Occurrence_Of (Subp, Sloc (Subp)),
1454                   Explicit_Generic_Actual_Parameter =>
1455                     New_Occurrence_Of (Subp, Sloc (Subp)));
1456             Mark_Rewrite_Insertion (New_D);
1457             Append_To (Actuals, New_D);
1458             Next_Elmt (Elmt);
1459          end loop;
1460       end;
1461
1462       --  If this is a formal package, normalize the parameter list by adding
1463       --  explicit box associations for the formals that are covered by an
1464       --  Others_Choice.
1465
1466       if not Is_Empty_List (Default_Formals) then
1467          Append_List (Default_Formals, Formals);
1468       end if;
1469
1470       return Assoc;
1471    end Analyze_Associations;
1472
1473    -------------------------------
1474    -- Analyze_Formal_Array_Type --
1475    -------------------------------
1476
1477    procedure Analyze_Formal_Array_Type
1478      (T   : in out Entity_Id;
1479       Def : Node_Id)
1480    is
1481       DSS : Node_Id;
1482
1483    begin
1484       --  Treated like a non-generic array declaration, with additional
1485       --  semantic checks.
1486
1487       Enter_Name (T);
1488
1489       if Nkind (Def) = N_Constrained_Array_Definition then
1490          DSS := First (Discrete_Subtype_Definitions (Def));
1491          while Present (DSS) loop
1492             if Nkind_In (DSS, N_Subtype_Indication,
1493                               N_Range,
1494                               N_Attribute_Reference)
1495             then
1496                Error_Msg_N ("only a subtype mark is allowed in a formal", DSS);
1497             end if;
1498
1499             Next (DSS);
1500          end loop;
1501       end if;
1502
1503       Array_Type_Declaration (T, Def);
1504       Set_Is_Generic_Type (Base_Type (T));
1505
1506       if Ekind (Component_Type (T)) = E_Incomplete_Type
1507         and then No (Full_View (Component_Type (T)))
1508       then
1509          Error_Msg_N ("premature usage of incomplete type", Def);
1510
1511       --  Check that range constraint is not allowed on the component type
1512       --  of a generic formal array type (AARM 12.5.3(3))
1513
1514       elsif Is_Internal (Component_Type (T))
1515         and then Present (Subtype_Indication (Component_Definition (Def)))
1516         and then Nkind (Original_Node
1517                          (Subtype_Indication (Component_Definition (Def)))) =
1518                                                          N_Subtype_Indication
1519       then
1520          Error_Msg_N
1521            ("in a formal, a subtype indication can only be "
1522              & "a subtype mark (RM 12.5.3(3))",
1523              Subtype_Indication (Component_Definition (Def)));
1524       end if;
1525
1526    end Analyze_Formal_Array_Type;
1527
1528    ---------------------------------------------
1529    -- Analyze_Formal_Decimal_Fixed_Point_Type --
1530    ---------------------------------------------
1531
1532    --  As for other generic types, we create a valid type representation with
1533    --  legal but arbitrary attributes, whose values are never considered
1534    --  static. For all scalar types we introduce an anonymous base type, with
1535    --  the same attributes. We choose the corresponding integer type to be
1536    --  Standard_Integer.
1537
1538    procedure Analyze_Formal_Decimal_Fixed_Point_Type
1539      (T   : Entity_Id;
1540       Def : Node_Id)
1541    is
1542       Loc       : constant Source_Ptr := Sloc (Def);
1543       Base      : constant Entity_Id :=
1544                     New_Internal_Entity
1545                       (E_Decimal_Fixed_Point_Type,
1546                        Current_Scope, Sloc (Def), 'G');
1547       Int_Base  : constant Entity_Id := Standard_Integer;
1548       Delta_Val : constant Ureal := Ureal_1;
1549       Digs_Val  : constant Uint  := Uint_6;
1550
1551    begin
1552       Enter_Name (T);
1553
1554       Set_Etype          (Base, Base);
1555       Set_Size_Info      (Base, Int_Base);
1556       Set_RM_Size        (Base, RM_Size (Int_Base));
1557       Set_First_Rep_Item (Base, First_Rep_Item (Int_Base));
1558       Set_Digits_Value   (Base, Digs_Val);
1559       Set_Delta_Value    (Base, Delta_Val);
1560       Set_Small_Value    (Base, Delta_Val);
1561       Set_Scalar_Range   (Base,
1562         Make_Range (Loc,
1563           Low_Bound  => Make_Real_Literal (Loc, Ureal_1),
1564           High_Bound => Make_Real_Literal (Loc, Ureal_1)));
1565
1566       Set_Is_Generic_Type (Base);
1567       Set_Parent          (Base, Parent (Def));
1568
1569       Set_Ekind          (T, E_Decimal_Fixed_Point_Subtype);
1570       Set_Etype          (T, Base);
1571       Set_Size_Info      (T, Int_Base);
1572       Set_RM_Size        (T, RM_Size (Int_Base));
1573       Set_First_Rep_Item (T, First_Rep_Item (Int_Base));
1574       Set_Digits_Value   (T, Digs_Val);
1575       Set_Delta_Value    (T, Delta_Val);
1576       Set_Small_Value    (T, Delta_Val);
1577       Set_Scalar_Range   (T, Scalar_Range (Base));
1578       Set_Is_Constrained (T);
1579
1580       Check_Restriction (No_Fixed_Point, Def);
1581    end Analyze_Formal_Decimal_Fixed_Point_Type;
1582
1583    -------------------------------------------
1584    -- Analyze_Formal_Derived_Interface_Type --
1585    -------------------------------------------
1586
1587    procedure Analyze_Formal_Derived_Interface_Type
1588      (N   : Node_Id;
1589       T   : Entity_Id;
1590       Def : Node_Id)
1591    is
1592       Loc   : constant Source_Ptr := Sloc (Def);
1593
1594    begin
1595       --  Rewrite as a type declaration of a derived type. This ensures that
1596       --  the interface list and primitive operations are properly captured.
1597
1598       Rewrite (N,
1599         Make_Full_Type_Declaration (Loc,
1600           Defining_Identifier => T,
1601           Type_Definition     => Def));
1602       Analyze (N);
1603       Set_Is_Generic_Type (T);
1604    end Analyze_Formal_Derived_Interface_Type;
1605
1606    ---------------------------------
1607    -- Analyze_Formal_Derived_Type --
1608    ---------------------------------
1609
1610    procedure Analyze_Formal_Derived_Type
1611      (N   : Node_Id;
1612       T   : Entity_Id;
1613       Def : Node_Id)
1614    is
1615       Loc      : constant Source_Ptr := Sloc (Def);
1616       Unk_Disc : constant Boolean    := Unknown_Discriminants_Present (N);
1617       New_N    : Node_Id;
1618
1619    begin
1620       Set_Is_Generic_Type (T);
1621
1622       if Private_Present (Def) then
1623          New_N :=
1624            Make_Private_Extension_Declaration (Loc,
1625              Defining_Identifier           => T,
1626              Discriminant_Specifications   => Discriminant_Specifications (N),
1627              Unknown_Discriminants_Present => Unk_Disc,
1628              Subtype_Indication            => Subtype_Mark (Def),
1629              Interface_List                => Interface_List (Def));
1630
1631          Set_Abstract_Present     (New_N, Abstract_Present     (Def));
1632          Set_Limited_Present      (New_N, Limited_Present      (Def));
1633          Set_Synchronized_Present (New_N, Synchronized_Present (Def));
1634
1635       else
1636          New_N :=
1637            Make_Full_Type_Declaration (Loc,
1638              Defining_Identifier => T,
1639              Discriminant_Specifications =>
1640                Discriminant_Specifications (Parent (T)),
1641              Type_Definition =>
1642                Make_Derived_Type_Definition (Loc,
1643                  Subtype_Indication => Subtype_Mark (Def)));
1644
1645          Set_Abstract_Present
1646            (Type_Definition (New_N), Abstract_Present (Def));
1647          Set_Limited_Present
1648            (Type_Definition (New_N), Limited_Present  (Def));
1649       end if;
1650
1651       Rewrite (N, New_N);
1652       Analyze (N);
1653
1654       if Unk_Disc then
1655          if not Is_Composite_Type (T) then
1656             Error_Msg_N
1657               ("unknown discriminants not allowed for elementary types", N);
1658          else
1659             Set_Has_Unknown_Discriminants (T);
1660             Set_Is_Constrained (T, False);
1661          end if;
1662       end if;
1663
1664       --  If the parent type has a known size, so does the formal, which makes
1665       --  legal representation clauses that involve the formal.
1666
1667       Set_Size_Known_At_Compile_Time
1668         (T, Size_Known_At_Compile_Time (Entity (Subtype_Mark (Def))));
1669    end Analyze_Formal_Derived_Type;
1670
1671    ----------------------------------
1672    -- Analyze_Formal_Discrete_Type --
1673    ----------------------------------
1674
1675    --  The operations defined for a discrete types are those of an enumeration
1676    --  type. The size is set to an arbitrary value, for use in analyzing the
1677    --  generic unit.
1678
1679    procedure Analyze_Formal_Discrete_Type (T : Entity_Id; Def : Node_Id) is
1680       Loc : constant Source_Ptr := Sloc (Def);
1681       Lo  : Node_Id;
1682       Hi  : Node_Id;
1683
1684       Base : constant Entity_Id :=
1685                New_Internal_Entity
1686                  (E_Floating_Point_Type, Current_Scope, Sloc (Def), 'G');
1687    begin
1688       Enter_Name          (T);
1689       Set_Ekind           (T, E_Enumeration_Subtype);
1690       Set_Etype           (T, Base);
1691       Init_Size           (T, 8);
1692       Init_Alignment      (T);
1693       Set_Is_Generic_Type (T);
1694       Set_Is_Constrained  (T);
1695
1696       --  For semantic analysis, the bounds of the type must be set to some
1697       --  non-static value. The simplest is to create attribute nodes for those
1698       --  bounds, that refer to the type itself. These bounds are never
1699       --  analyzed but serve as place-holders.
1700
1701       Lo :=
1702         Make_Attribute_Reference (Loc,
1703           Attribute_Name => Name_First,
1704           Prefix => New_Reference_To (T, Loc));
1705       Set_Etype (Lo, T);
1706
1707       Hi :=
1708         Make_Attribute_Reference (Loc,
1709           Attribute_Name => Name_Last,
1710           Prefix => New_Reference_To (T, Loc));
1711       Set_Etype (Hi, T);
1712
1713       Set_Scalar_Range (T,
1714         Make_Range (Loc,
1715           Low_Bound => Lo,
1716           High_Bound => Hi));
1717
1718       Set_Ekind           (Base, E_Enumeration_Type);
1719       Set_Etype           (Base, Base);
1720       Init_Size           (Base, 8);
1721       Init_Alignment      (Base);
1722       Set_Is_Generic_Type (Base);
1723       Set_Scalar_Range    (Base, Scalar_Range (T));
1724       Set_Parent          (Base, Parent (Def));
1725    end Analyze_Formal_Discrete_Type;
1726
1727    ----------------------------------
1728    -- Analyze_Formal_Floating_Type --
1729    ---------------------------------
1730
1731    procedure Analyze_Formal_Floating_Type (T : Entity_Id; Def : Node_Id) is
1732       Base : constant Entity_Id :=
1733                New_Internal_Entity
1734                  (E_Floating_Point_Type, Current_Scope, Sloc (Def), 'G');
1735
1736    begin
1737       --  The various semantic attributes are taken from the predefined type
1738       --  Float, just so that all of them are initialized. Their values are
1739       --  never used because no constant folding or expansion takes place in
1740       --  the generic itself.
1741
1742       Enter_Name (T);
1743       Set_Ekind          (T, E_Floating_Point_Subtype);
1744       Set_Etype          (T, Base);
1745       Set_Size_Info      (T,              (Standard_Float));
1746       Set_RM_Size        (T, RM_Size      (Standard_Float));
1747       Set_Digits_Value   (T, Digits_Value (Standard_Float));
1748       Set_Scalar_Range   (T, Scalar_Range (Standard_Float));
1749       Set_Is_Constrained (T);
1750
1751       Set_Is_Generic_Type (Base);
1752       Set_Etype           (Base, Base);
1753       Set_Size_Info       (Base,              (Standard_Float));
1754       Set_RM_Size         (Base, RM_Size      (Standard_Float));
1755       Set_Digits_Value    (Base, Digits_Value (Standard_Float));
1756       Set_Scalar_Range    (Base, Scalar_Range (Standard_Float));
1757       Set_Parent          (Base, Parent (Def));
1758
1759       Check_Restriction (No_Floating_Point, Def);
1760    end Analyze_Formal_Floating_Type;
1761
1762    -----------------------------------
1763    -- Analyze_Formal_Interface_Type;--
1764    -----------------------------------
1765
1766    procedure Analyze_Formal_Interface_Type
1767       (N   : Node_Id;
1768        T   : Entity_Id;
1769        Def : Node_Id)
1770    is
1771       Loc   : constant Source_Ptr := Sloc (N);
1772       New_N : Node_Id;
1773
1774    begin
1775       New_N :=
1776         Make_Full_Type_Declaration (Loc,
1777           Defining_Identifier => T,
1778           Type_Definition => Def);
1779
1780       Rewrite (N, New_N);
1781       Analyze (N);
1782       Set_Is_Generic_Type (T);
1783    end Analyze_Formal_Interface_Type;
1784
1785    ---------------------------------
1786    -- Analyze_Formal_Modular_Type --
1787    ---------------------------------
1788
1789    procedure Analyze_Formal_Modular_Type (T : Entity_Id; Def : Node_Id) is
1790    begin
1791       --  Apart from their entity kind, generic modular types are treated like
1792       --  signed integer types, and have the same attributes.
1793
1794       Analyze_Formal_Signed_Integer_Type (T, Def);
1795       Set_Ekind (T, E_Modular_Integer_Subtype);
1796       Set_Ekind (Etype (T), E_Modular_Integer_Type);
1797
1798    end Analyze_Formal_Modular_Type;
1799
1800    ---------------------------------------
1801    -- Analyze_Formal_Object_Declaration --
1802    ---------------------------------------
1803
1804    procedure Analyze_Formal_Object_Declaration (N : Node_Id) is
1805       E  : constant Node_Id := Default_Expression (N);
1806       Id : constant Node_Id := Defining_Identifier (N);
1807       K  : Entity_Kind;
1808       T  : Node_Id;
1809
1810    begin
1811       Enter_Name (Id);
1812
1813       --  Determine the mode of the formal object
1814
1815       if Out_Present (N) then
1816          K := E_Generic_In_Out_Parameter;
1817
1818          if not In_Present (N) then
1819             Error_Msg_N ("formal generic objects cannot have mode OUT", N);
1820          end if;
1821
1822       else
1823          K := E_Generic_In_Parameter;
1824       end if;
1825
1826       if Present (Subtype_Mark (N)) then
1827          Find_Type (Subtype_Mark (N));
1828          T := Entity (Subtype_Mark (N));
1829
1830          --  Verify that there is no redundant null exclusion
1831
1832          if Null_Exclusion_Present (N) then
1833             if not Is_Access_Type (T) then
1834                Error_Msg_N
1835                  ("null exclusion can only apply to an access type", N);
1836
1837             elsif Can_Never_Be_Null (T) then
1838                Error_Msg_NE
1839                  ("`NOT NULL` not allowed (& already excludes null)",
1840                     N, T);
1841             end if;
1842          end if;
1843
1844       --  Ada 2005 (AI-423): Formal object with an access definition
1845
1846       else
1847          Check_Access_Definition (N);
1848          T := Access_Definition
1849                 (Related_Nod => N,
1850                  N           => Access_Definition (N));
1851       end if;
1852
1853       if Ekind (T) = E_Incomplete_Type then
1854          declare
1855             Error_Node : Node_Id;
1856
1857          begin
1858             if Present (Subtype_Mark (N)) then
1859                Error_Node := Subtype_Mark (N);
1860             else
1861                Check_Access_Definition (N);
1862                Error_Node := Access_Definition (N);
1863             end if;
1864
1865             Error_Msg_N ("premature usage of incomplete type", Error_Node);
1866          end;
1867       end if;
1868
1869       if K = E_Generic_In_Parameter then
1870
1871          --  Ada 2005 (AI-287): Limited aggregates allowed in generic formals
1872
1873          if Ada_Version < Ada_05 and then Is_Limited_Type (T) then
1874             Error_Msg_N
1875               ("generic formal of mode IN must not be of limited type", N);
1876             Explain_Limited_Type (T, N);
1877          end if;
1878
1879          if Is_Abstract_Type (T) then
1880             Error_Msg_N
1881               ("generic formal of mode IN must not be of abstract type", N);
1882          end if;
1883
1884          if Present (E) then
1885             Preanalyze_Spec_Expression (E, T);
1886
1887             if Is_Limited_Type (T) and then not OK_For_Limited_Init (T, E) then
1888                Error_Msg_N
1889                  ("initialization not allowed for limited types", E);
1890                Explain_Limited_Type (T, E);
1891             end if;
1892          end if;
1893
1894          Set_Ekind (Id, K);
1895          Set_Etype (Id, T);
1896
1897       --  Case of generic IN OUT parameter
1898
1899       else
1900          --  If the formal has an unconstrained type, construct its actual
1901          --  subtype, as is done for subprogram formals. In this fashion, all
1902          --  its uses can refer to specific bounds.
1903
1904          Set_Ekind (Id, K);
1905          Set_Etype (Id, T);
1906
1907          if (Is_Array_Type (T)
1908               and then not Is_Constrained (T))
1909            or else
1910             (Ekind (T) = E_Record_Type
1911               and then Has_Discriminants (T))
1912          then
1913             declare
1914                Non_Freezing_Ref : constant Node_Id :=
1915                                     New_Reference_To (Id, Sloc (Id));
1916                Decl : Node_Id;
1917
1918             begin
1919                --  Make sure the actual subtype doesn't generate bogus freezing
1920
1921                Set_Must_Not_Freeze (Non_Freezing_Ref);
1922                Decl := Build_Actual_Subtype (T, Non_Freezing_Ref);
1923                Insert_Before_And_Analyze (N, Decl);
1924                Set_Actual_Subtype (Id, Defining_Identifier (Decl));
1925             end;
1926          else
1927             Set_Actual_Subtype (Id, T);
1928          end if;
1929
1930          if Present (E) then
1931             Error_Msg_N
1932               ("initialization not allowed for `IN OUT` formals", N);
1933          end if;
1934       end if;
1935    end Analyze_Formal_Object_Declaration;
1936
1937    ----------------------------------------------
1938    -- Analyze_Formal_Ordinary_Fixed_Point_Type --
1939    ----------------------------------------------
1940
1941    procedure Analyze_Formal_Ordinary_Fixed_Point_Type
1942      (T   : Entity_Id;
1943       Def : Node_Id)
1944    is
1945       Loc  : constant Source_Ptr := Sloc (Def);
1946       Base : constant Entity_Id :=
1947                New_Internal_Entity
1948                  (E_Ordinary_Fixed_Point_Type, Current_Scope, Sloc (Def), 'G');
1949    begin
1950       --  The semantic attributes are set for completeness only, their values
1951       --  will never be used, since all properties of the type are non-static.
1952
1953       Enter_Name (T);
1954       Set_Ekind            (T, E_Ordinary_Fixed_Point_Subtype);
1955       Set_Etype            (T, Base);
1956       Set_Size_Info        (T, Standard_Integer);
1957       Set_RM_Size          (T, RM_Size (Standard_Integer));
1958       Set_Small_Value      (T, Ureal_1);
1959       Set_Delta_Value      (T, Ureal_1);
1960       Set_Scalar_Range     (T,
1961         Make_Range (Loc,
1962           Low_Bound  => Make_Real_Literal (Loc, Ureal_1),
1963           High_Bound => Make_Real_Literal (Loc, Ureal_1)));
1964       Set_Is_Constrained   (T);
1965
1966       Set_Is_Generic_Type (Base);
1967       Set_Etype           (Base, Base);
1968       Set_Size_Info       (Base, Standard_Integer);
1969       Set_RM_Size         (Base, RM_Size (Standard_Integer));
1970       Set_Small_Value     (Base, Ureal_1);
1971       Set_Delta_Value     (Base, Ureal_1);
1972       Set_Scalar_Range    (Base, Scalar_Range (T));
1973       Set_Parent          (Base, Parent (Def));
1974
1975       Check_Restriction (No_Fixed_Point, Def);
1976    end Analyze_Formal_Ordinary_Fixed_Point_Type;
1977
1978    ----------------------------
1979    -- Analyze_Formal_Package --
1980    ----------------------------
1981
1982    procedure Analyze_Formal_Package (N : Node_Id) is
1983       Loc              : constant Source_Ptr := Sloc (N);
1984       Pack_Id          : constant Entity_Id  := Defining_Identifier (N);
1985       Formal           : Entity_Id;
1986       Gen_Id           : constant Node_Id    := Name (N);
1987       Gen_Decl         : Node_Id;
1988       Gen_Unit         : Entity_Id;
1989       New_N            : Node_Id;
1990       Parent_Installed : Boolean := False;
1991       Renaming         : Node_Id;
1992       Parent_Instance  : Entity_Id;
1993       Renaming_In_Par  : Entity_Id;
1994       No_Associations  : Boolean := False;
1995
1996       function Build_Local_Package return Node_Id;
1997       --  The formal package is rewritten so that its parameters are replaced
1998       --  with corresponding declarations. For parameters with bona fide
1999       --  associations these declarations are created by Analyze_Associations
2000       --  as for a regular instantiation. For boxed parameters, we preserve
2001       --  the formal declarations and analyze them, in order to introduce
2002       --  entities of the right kind in the environment of the formal.
2003
2004       -------------------------
2005       -- Build_Local_Package --
2006       -------------------------
2007
2008       function Build_Local_Package return Node_Id is
2009          Decls     : List_Id;
2010          Pack_Decl : Node_Id;
2011
2012       begin
2013          --  Within the formal, the name of the generic package is a renaming
2014          --  of the formal (as for a regular instantiation).
2015
2016          Pack_Decl :=
2017            Make_Package_Declaration (Loc,
2018              Specification =>
2019                Copy_Generic_Node
2020                  (Specification (Original_Node (Gen_Decl)),
2021                     Empty, Instantiating => True));
2022
2023          Renaming := Make_Package_Renaming_Declaration (Loc,
2024              Defining_Unit_Name =>
2025                Make_Defining_Identifier (Loc, Chars (Gen_Unit)),
2026              Name => New_Occurrence_Of (Formal, Loc));
2027
2028          if Nkind (Gen_Id) = N_Identifier
2029            and then Chars (Gen_Id) = Chars (Pack_Id)
2030          then
2031             Error_Msg_NE
2032               ("& is hidden within declaration of instance", Gen_Id, Gen_Unit);
2033          end if;
2034
2035          --  If the formal is declared with a box, or with an others choice,
2036          --  create corresponding declarations for all entities in the formal
2037          --  part, so that names with the proper types are available in the
2038          --  specification of the formal package.
2039
2040          --  On the other hand, if there are no associations, then all the
2041          --  formals must have defaults, and this will be checked by the
2042          --  call to Analyze_Associations.
2043
2044          if Box_Present (N)
2045            or else Nkind (First (Generic_Associations (N))) = N_Others_Choice
2046          then
2047             declare
2048                Formal_Decl : Node_Id;
2049
2050             begin
2051                --  TBA : for a formal package, need to recurse ???
2052
2053                Decls := New_List;
2054                Formal_Decl :=
2055                  First
2056                    (Generic_Formal_Declarations (Original_Node (Gen_Decl)));
2057                while Present (Formal_Decl) loop
2058                   Append_To
2059                     (Decls, Copy_Generic_Node (Formal_Decl, Empty, True));
2060                   Next (Formal_Decl);
2061                end loop;
2062             end;
2063
2064          --  If generic associations are present, use Analyze_Associations to
2065          --  create the proper renaming declarations.
2066
2067          else
2068             declare
2069                Act_Tree : constant Node_Id :=
2070                             Copy_Generic_Node
2071                               (Original_Node (Gen_Decl), Empty,
2072                                Instantiating => True);
2073
2074             begin
2075                Generic_Renamings.Set_Last (0);
2076                Generic_Renamings_HTable.Reset;
2077                Instantiation_Node := N;
2078
2079                Decls :=
2080                  Analyze_Associations
2081                    (Original_Node (N),
2082                       Generic_Formal_Declarations (Act_Tree),
2083                       Generic_Formal_Declarations (Gen_Decl));
2084             end;
2085          end if;
2086
2087          Append (Renaming, To => Decls);
2088
2089          --  Add generated declarations ahead of local declarations in
2090          --  the package.
2091
2092          if No (Visible_Declarations (Specification (Pack_Decl))) then
2093             Set_Visible_Declarations (Specification (Pack_Decl), Decls);
2094          else
2095             Insert_List_Before
2096               (First (Visible_Declarations (Specification (Pack_Decl))),
2097                  Decls);
2098          end if;
2099
2100          return Pack_Decl;
2101       end Build_Local_Package;
2102
2103    --  Start of processing for Analyze_Formal_Package
2104
2105    begin
2106       Text_IO_Kludge (Gen_Id);
2107
2108       Init_Env;
2109       Check_Generic_Child_Unit (Gen_Id, Parent_Installed);
2110       Gen_Unit := Entity (Gen_Id);
2111
2112       --  Check for a formal package that is a package renaming
2113
2114       if Present (Renamed_Object (Gen_Unit)) then
2115          Gen_Unit := Renamed_Object (Gen_Unit);
2116       end if;
2117
2118       if Ekind (Gen_Unit) /= E_Generic_Package then
2119          Error_Msg_N ("expect generic package name", Gen_Id);
2120          Restore_Env;
2121          return;
2122
2123       elsif  Gen_Unit = Current_Scope then
2124          Error_Msg_N
2125            ("generic package cannot be used as a formal package of itself",
2126              Gen_Id);
2127          Restore_Env;
2128          return;
2129
2130       elsif In_Open_Scopes (Gen_Unit) then
2131          if Is_Compilation_Unit (Gen_Unit)
2132            and then Is_Child_Unit (Current_Scope)
2133          then
2134             --  Special-case the error when the formal is a parent, and
2135             --  continue analysis to minimize cascaded errors.
2136
2137             Error_Msg_N
2138               ("generic parent cannot be used as formal package "
2139                 & "of a child unit",
2140                 Gen_Id);
2141
2142          else
2143             Error_Msg_N
2144               ("generic package cannot be used as a formal package "
2145                 & "within itself",
2146                 Gen_Id);
2147             Restore_Env;
2148             return;
2149          end if;
2150       end if;
2151
2152       if Box_Present (N)
2153         or else No (Generic_Associations (N))
2154         or else Nkind (First (Generic_Associations (N))) = N_Others_Choice
2155       then
2156          No_Associations := True;
2157       end if;
2158
2159       --  If there are no generic associations, the generic parameters appear
2160       --  as local entities and are instantiated like them. We copy the generic
2161       --  package declaration as if it were an instantiation, and analyze it
2162       --  like a regular package, except that we treat the formals as
2163       --  additional visible components.
2164
2165       Gen_Decl := Unit_Declaration_Node (Gen_Unit);
2166
2167       if In_Extended_Main_Source_Unit (N) then
2168          Set_Is_Instantiated (Gen_Unit);
2169          Generate_Reference  (Gen_Unit, N);
2170       end if;
2171
2172       Formal := New_Copy (Pack_Id);
2173       Create_Instantiation_Source (N, Gen_Unit, False, S_Adjustment);
2174
2175       begin
2176          --  Make local generic without formals. The formals will be replaced
2177          --  with internal declarations.
2178
2179          New_N := Build_Local_Package;
2180
2181          --  If there are errors in the parameter list, Analyze_Associations
2182          --  raises Instantiation_Error. Patch the declaration to prevent
2183          --  further exception propagation.
2184
2185       exception
2186          when Instantiation_Error =>
2187
2188             Enter_Name (Formal);
2189             Set_Ekind  (Formal, E_Variable);
2190             Set_Etype  (Formal, Any_Type);
2191
2192             if Parent_Installed then
2193                Remove_Parent;
2194             end if;
2195
2196             return;
2197       end;
2198
2199       Rewrite (N, New_N);
2200       Set_Defining_Unit_Name (Specification (New_N), Formal);
2201       Set_Generic_Parent (Specification (N), Gen_Unit);
2202       Set_Instance_Env (Gen_Unit, Formal);
2203       Set_Is_Generic_Instance (Formal);
2204
2205       Enter_Name (Formal);
2206       Set_Ekind  (Formal, E_Package);
2207       Set_Etype  (Formal, Standard_Void_Type);
2208       Set_Inner_Instances (Formal, New_Elmt_List);
2209       Push_Scope  (Formal);
2210
2211       if Is_Child_Unit (Gen_Unit)
2212         and then Parent_Installed
2213       then
2214          --  Similarly, we have to make the name of the formal visible in the
2215          --  parent instance, to resolve properly fully qualified names that
2216          --  may appear in the generic unit. The parent instance has been
2217          --  placed on the scope stack ahead of the current scope.
2218
2219          Parent_Instance := Scope_Stack.Table (Scope_Stack.Last - 1).Entity;
2220
2221          Renaming_In_Par :=
2222            Make_Defining_Identifier (Loc, Chars (Gen_Unit));
2223          Set_Ekind (Renaming_In_Par, E_Package);
2224          Set_Etype (Renaming_In_Par, Standard_Void_Type);
2225          Set_Scope (Renaming_In_Par, Parent_Instance);
2226          Set_Parent (Renaming_In_Par, Parent (Formal));
2227          Set_Renamed_Object (Renaming_In_Par, Formal);
2228          Append_Entity (Renaming_In_Par, Parent_Instance);
2229       end if;
2230
2231       Analyze (Specification (N));
2232
2233       --  The formals for which associations are provided are not visible
2234       --  outside of the formal package. The others are still declared by a
2235       --  formal parameter declaration.
2236
2237       if not No_Associations then
2238          declare
2239             E : Entity_Id;
2240
2241          begin
2242             E := First_Entity (Formal);
2243             while Present (E) loop
2244                exit when Ekind (E) = E_Package
2245                  and then Renamed_Entity (E) = Formal;
2246
2247                if not Is_Generic_Formal (E) then
2248                   Set_Is_Hidden (E);
2249                end if;
2250
2251                Next_Entity (E);
2252             end loop;
2253          end;
2254       end if;
2255
2256       End_Package_Scope (Formal);
2257
2258       if Parent_Installed then
2259          Remove_Parent;
2260       end if;
2261
2262       Restore_Env;
2263
2264       --  Inside the generic unit, the formal package is a regular package, but
2265       --  no body is needed for it. Note that after instantiation, the defining
2266       --  unit name we need is in the new tree and not in the original (see
2267       --  Package_Instantiation). A generic formal package is an instance, and
2268       --  can be used as an actual for an inner instance.
2269
2270       Set_Has_Completion (Formal, True);
2271
2272       --  Add semantic information to the original defining identifier.
2273       --  for ASIS use.
2274
2275       Set_Ekind (Pack_Id, E_Package);
2276       Set_Etype (Pack_Id, Standard_Void_Type);
2277       Set_Scope (Pack_Id, Scope (Formal));
2278       Set_Has_Completion (Pack_Id, True);
2279    end Analyze_Formal_Package;
2280
2281    ---------------------------------
2282    -- Analyze_Formal_Private_Type --
2283    ---------------------------------
2284
2285    procedure Analyze_Formal_Private_Type
2286      (N   : Node_Id;
2287       T   : Entity_Id;
2288       Def : Node_Id)
2289    is
2290    begin
2291       New_Private_Type (N, T, Def);
2292
2293       --  Set the size to an arbitrary but legal value
2294
2295       Set_Size_Info (T, Standard_Integer);
2296       Set_RM_Size   (T, RM_Size (Standard_Integer));
2297    end Analyze_Formal_Private_Type;
2298
2299    ----------------------------------------
2300    -- Analyze_Formal_Signed_Integer_Type --
2301    ----------------------------------------
2302
2303    procedure Analyze_Formal_Signed_Integer_Type
2304      (T   : Entity_Id;
2305       Def : Node_Id)
2306    is
2307       Base : constant Entity_Id :=
2308                New_Internal_Entity
2309                  (E_Signed_Integer_Type, Current_Scope, Sloc (Def), 'G');
2310
2311    begin
2312       Enter_Name (T);
2313
2314       Set_Ekind          (T, E_Signed_Integer_Subtype);
2315       Set_Etype          (T, Base);
2316       Set_Size_Info      (T, Standard_Integer);
2317       Set_RM_Size        (T, RM_Size (Standard_Integer));
2318       Set_Scalar_Range   (T, Scalar_Range (Standard_Integer));
2319       Set_Is_Constrained (T);
2320
2321       Set_Is_Generic_Type (Base);
2322       Set_Size_Info       (Base, Standard_Integer);
2323       Set_RM_Size         (Base, RM_Size (Standard_Integer));
2324       Set_Etype           (Base, Base);
2325       Set_Scalar_Range    (Base, Scalar_Range (Standard_Integer));
2326       Set_Parent          (Base, Parent (Def));
2327    end Analyze_Formal_Signed_Integer_Type;
2328
2329    -------------------------------
2330    -- Analyze_Formal_Subprogram --
2331    -------------------------------
2332
2333    procedure Analyze_Formal_Subprogram (N : Node_Id) is
2334       Spec : constant Node_Id   := Specification (N);
2335       Def  : constant Node_Id   := Default_Name (N);
2336       Nam  : constant Entity_Id := Defining_Unit_Name (Spec);
2337       Subp : Entity_Id;
2338
2339    begin
2340       if Nam = Error then
2341          return;
2342       end if;
2343
2344       if Nkind (Nam) = N_Defining_Program_Unit_Name then
2345          Error_Msg_N ("name of formal subprogram must be a direct name", Nam);
2346          return;
2347       end if;
2348
2349       Analyze_Subprogram_Declaration (N);
2350       Set_Is_Formal_Subprogram (Nam);
2351       Set_Has_Completion (Nam);
2352
2353       if Nkind (N) = N_Formal_Abstract_Subprogram_Declaration then
2354          Set_Is_Abstract_Subprogram (Nam);
2355          Set_Is_Dispatching_Operation (Nam);
2356
2357          declare
2358             Ctrl_Type : constant Entity_Id := Find_Dispatching_Type (Nam);
2359          begin
2360             if No (Ctrl_Type) then
2361                Error_Msg_N
2362                  ("abstract formal subprogram must have a controlling type",
2363                   N);
2364             else
2365                Check_Controlling_Formals (Ctrl_Type, Nam);
2366             end if;
2367          end;
2368       end if;
2369
2370       --  Default name is resolved at the point of instantiation
2371
2372       if Box_Present (N) then
2373          null;
2374
2375       --  Else default is bound at the point of generic declaration
2376
2377       elsif Present (Def) then
2378          if Nkind (Def) = N_Operator_Symbol then
2379             Find_Direct_Name (Def);
2380
2381          elsif Nkind (Def) /= N_Attribute_Reference then
2382             Analyze (Def);
2383
2384          else
2385             --  For an attribute reference, analyze the prefix and verify
2386             --  that it has the proper profile for the subprogram.
2387
2388             Analyze (Prefix (Def));
2389             Valid_Default_Attribute (Nam, Def);
2390             return;
2391          end if;
2392
2393          --  Default name may be overloaded, in which case the interpretation
2394          --  with the correct profile must be  selected, as for a renaming.
2395          --  If the definition is an indexed component, it must denote a
2396          --  member of an entry family. If it is a selected component, it
2397          --  can be a protected operation.
2398
2399          if Etype (Def) = Any_Type then
2400             return;
2401
2402          elsif Nkind (Def) = N_Selected_Component then
2403             if not Is_Overloadable (Entity (Selector_Name (Def))) then
2404                Error_Msg_N ("expect valid subprogram name as default", Def);
2405             end if;
2406
2407          elsif Nkind (Def) = N_Indexed_Component then
2408             if Is_Entity_Name (Prefix (Def)) then
2409                if Ekind (Entity (Prefix (Def))) /= E_Entry_Family then
2410                   Error_Msg_N ("expect valid subprogram name as default", Def);
2411                end if;
2412
2413             elsif Nkind (Prefix (Def)) = N_Selected_Component then
2414                if Ekind (Entity (Selector_Name (Prefix (Def))))
2415                  /= E_Entry_Family
2416                then
2417                   Error_Msg_N ("expect valid subprogram name as default", Def);
2418                end if;
2419
2420             else
2421                Error_Msg_N ("expect valid subprogram name as default", Def);
2422                return;
2423             end if;
2424
2425          elsif Nkind (Def) = N_Character_Literal then
2426
2427             --  Needs some type checks: subprogram should be parameterless???
2428
2429             Resolve (Def, (Etype (Nam)));
2430
2431          elsif not Is_Entity_Name (Def)
2432            or else not Is_Overloadable (Entity (Def))
2433          then
2434             Error_Msg_N ("expect valid subprogram name as default", Def);
2435             return;
2436
2437          elsif not Is_Overloaded (Def) then
2438             Subp := Entity (Def);
2439
2440             if Subp = Nam then
2441                Error_Msg_N ("premature usage of formal subprogram", Def);
2442
2443             elsif not Entity_Matches_Spec (Subp, Nam) then
2444                Error_Msg_N ("no visible entity matches specification", Def);
2445             end if;
2446
2447          --  More than one interpretation, so disambiguate as for a renaming
2448
2449          else
2450             declare
2451                I   : Interp_Index;
2452                I1  : Interp_Index := 0;
2453                It  : Interp;
2454                It1 : Interp;
2455
2456             begin
2457                Subp := Any_Id;
2458                Get_First_Interp (Def, I, It);
2459                while Present (It.Nam) loop
2460                   if Entity_Matches_Spec (It.Nam, Nam) then
2461                      if Subp /= Any_Id then
2462                         It1 := Disambiguate (Def, I1, I, Etype (Subp));
2463
2464                         if It1 = No_Interp then
2465                            Error_Msg_N ("ambiguous default subprogram", Def);
2466                         else
2467                            Subp := It1.Nam;
2468                         end if;
2469
2470                         exit;
2471
2472                      else
2473                         I1  := I;
2474                         Subp := It.Nam;
2475                      end if;
2476                   end if;
2477
2478                   Get_Next_Interp (I, It);
2479                end loop;
2480             end;
2481
2482             if Subp /= Any_Id then
2483                Set_Entity (Def, Subp);
2484
2485                if Subp = Nam then
2486                   Error_Msg_N ("premature usage of formal subprogram", Def);
2487
2488                elsif Ekind (Subp) /= E_Operator then
2489                   Check_Mode_Conformant (Subp, Nam);
2490                end if;
2491
2492             else
2493                Error_Msg_N ("no visible subprogram matches specification", N);
2494             end if;
2495          end if;
2496       end if;
2497    end Analyze_Formal_Subprogram;
2498
2499    -------------------------------------
2500    -- Analyze_Formal_Type_Declaration --
2501    -------------------------------------
2502
2503    procedure Analyze_Formal_Type_Declaration (N : Node_Id) is
2504       Def : constant Node_Id := Formal_Type_Definition (N);
2505       T   : Entity_Id;
2506
2507    begin
2508       T := Defining_Identifier (N);
2509
2510       if Present (Discriminant_Specifications (N))
2511         and then Nkind (Def) /= N_Formal_Private_Type_Definition
2512       then
2513          Error_Msg_N
2514            ("discriminants not allowed for this formal type", T);
2515       end if;
2516
2517       --  Enter the new name, and branch to specific routine
2518
2519       case Nkind (Def) is
2520          when N_Formal_Private_Type_Definition         =>
2521             Analyze_Formal_Private_Type (N, T, Def);
2522
2523          when N_Formal_Derived_Type_Definition         =>
2524             Analyze_Formal_Derived_Type (N, T, Def);
2525
2526          when N_Formal_Discrete_Type_Definition        =>
2527             Analyze_Formal_Discrete_Type (T, Def);
2528
2529          when N_Formal_Signed_Integer_Type_Definition  =>
2530             Analyze_Formal_Signed_Integer_Type (T, Def);
2531
2532          when N_Formal_Modular_Type_Definition         =>
2533             Analyze_Formal_Modular_Type (T, Def);
2534
2535          when N_Formal_Floating_Point_Definition       =>
2536             Analyze_Formal_Floating_Type (T, Def);
2537
2538          when N_Formal_Ordinary_Fixed_Point_Definition =>
2539             Analyze_Formal_Ordinary_Fixed_Point_Type (T, Def);
2540
2541          when N_Formal_Decimal_Fixed_Point_Definition  =>
2542             Analyze_Formal_Decimal_Fixed_Point_Type (T, Def);
2543
2544          when N_Array_Type_Definition =>
2545             Analyze_Formal_Array_Type (T, Def);
2546
2547          when N_Access_To_Object_Definition            |
2548               N_Access_Function_Definition             |
2549               N_Access_Procedure_Definition            =>
2550             Analyze_Generic_Access_Type (T, Def);
2551
2552          --  Ada 2005: a interface declaration is encoded as an abstract
2553          --  record declaration or a abstract type derivation.
2554
2555          when N_Record_Definition                      =>
2556             Analyze_Formal_Interface_Type (N, T, Def);
2557
2558          when N_Derived_Type_Definition                =>
2559             Analyze_Formal_Derived_Interface_Type (N, T, Def);
2560
2561          when N_Error                                  =>
2562             null;
2563
2564          when others                                   =>
2565             raise Program_Error;
2566
2567       end case;
2568
2569       Set_Is_Generic_Type (T);
2570    end Analyze_Formal_Type_Declaration;
2571
2572    ------------------------------------
2573    -- Analyze_Function_Instantiation --
2574    ------------------------------------
2575
2576    procedure Analyze_Function_Instantiation (N : Node_Id) is
2577    begin
2578       Analyze_Subprogram_Instantiation (N, E_Function);
2579    end Analyze_Function_Instantiation;
2580
2581    ---------------------------------
2582    -- Analyze_Generic_Access_Type --
2583    ---------------------------------
2584
2585    procedure Analyze_Generic_Access_Type (T : Entity_Id; Def : Node_Id) is
2586    begin
2587       Enter_Name (T);
2588
2589       if Nkind (Def) = N_Access_To_Object_Definition then
2590          Access_Type_Declaration (T, Def);
2591
2592          if Is_Incomplete_Or_Private_Type (Designated_Type (T))
2593            and then No (Full_View (Designated_Type (T)))
2594            and then not Is_Generic_Type (Designated_Type (T))
2595          then
2596             Error_Msg_N ("premature usage of incomplete type", Def);
2597
2598          elsif Is_Internal (Designated_Type (T)) then
2599             Error_Msg_N
2600               ("only a subtype mark is allowed in a formal", Def);
2601          end if;
2602
2603       else
2604          Access_Subprogram_Declaration (T, Def);
2605       end if;
2606    end Analyze_Generic_Access_Type;
2607
2608    ---------------------------------
2609    -- Analyze_Generic_Formal_Part --
2610    ---------------------------------
2611
2612    procedure Analyze_Generic_Formal_Part (N : Node_Id) is
2613       Gen_Parm_Decl : Node_Id;
2614
2615    begin
2616       --  The generic formals are processed in the scope of the generic unit,
2617       --  where they are immediately visible. The scope is installed by the
2618       --  caller.
2619
2620       Gen_Parm_Decl := First (Generic_Formal_Declarations (N));
2621
2622       while Present (Gen_Parm_Decl) loop
2623          Analyze (Gen_Parm_Decl);
2624          Next (Gen_Parm_Decl);
2625       end loop;
2626
2627       Generate_Reference_To_Generic_Formals (Current_Scope);
2628    end Analyze_Generic_Formal_Part;
2629
2630    ------------------------------------------
2631    -- Analyze_Generic_Package_Declaration  --
2632    ------------------------------------------
2633
2634    procedure Analyze_Generic_Package_Declaration (N : Node_Id) is
2635       Loc         : constant Source_Ptr := Sloc (N);
2636       Id          : Entity_Id;
2637       New_N       : Node_Id;
2638       Save_Parent : Node_Id;
2639       Renaming    : Node_Id;
2640       Decls       : constant List_Id :=
2641                       Visible_Declarations (Specification (N));
2642       Decl        : Node_Id;
2643
2644    begin
2645       --  We introduce a renaming of the enclosing package, to have a usable
2646       --  entity as the prefix of an expanded name for a local entity of the
2647       --  form Par.P.Q, where P is the generic package. This is because a local
2648       --  entity named P may hide it, so that the usual visibility rules in
2649       --  the instance will not resolve properly.
2650
2651       Renaming :=
2652         Make_Package_Renaming_Declaration (Loc,
2653           Defining_Unit_Name =>
2654             Make_Defining_Identifier (Loc,
2655              Chars => New_External_Name (Chars (Defining_Entity (N)), "GH")),
2656           Name => Make_Identifier (Loc, Chars (Defining_Entity (N))));
2657
2658       if Present (Decls) then
2659          Decl := First (Decls);
2660          while Present (Decl)
2661            and then Nkind (Decl) = N_Pragma
2662          loop
2663             Next (Decl);
2664          end loop;
2665
2666          if Present (Decl) then
2667             Insert_Before (Decl, Renaming);
2668          else
2669             Append (Renaming, Visible_Declarations (Specification (N)));
2670          end if;
2671
2672       else
2673          Set_Visible_Declarations (Specification (N), New_List (Renaming));
2674       end if;
2675
2676       --  Create copy of generic unit, and save for instantiation. If the unit
2677       --  is a child unit, do not copy the specifications for the parent, which
2678       --  are not part of the generic tree.
2679
2680       Save_Parent := Parent_Spec (N);
2681       Set_Parent_Spec (N, Empty);
2682
2683       New_N := Copy_Generic_Node (N, Empty, Instantiating => False);
2684       Set_Parent_Spec (New_N, Save_Parent);
2685       Rewrite (N, New_N);
2686       Id := Defining_Entity (N);
2687       Generate_Definition (Id);
2688
2689       --  Expansion is not applied to generic units
2690
2691       Start_Generic;
2692
2693       Enter_Name (Id);
2694       Set_Ekind (Id, E_Generic_Package);
2695       Set_Etype (Id, Standard_Void_Type);
2696       Push_Scope (Id);
2697       Enter_Generic_Scope (Id);
2698       Set_Inner_Instances (Id, New_Elmt_List);
2699
2700       Set_Categorization_From_Pragmas (N);
2701       Set_Is_Pure (Id, Is_Pure (Current_Scope));
2702
2703       --  Link the declaration of the generic homonym in the generic copy to
2704       --  the package it renames, so that it is always resolved properly.
2705
2706       Set_Generic_Homonym (Id, Defining_Unit_Name (Renaming));
2707       Set_Entity (Associated_Node (Name (Renaming)), Id);
2708
2709       --  For a library unit, we have reconstructed the entity for the unit,
2710       --  and must reset it in the library tables.
2711
2712       if Nkind (Parent (N)) = N_Compilation_Unit then
2713          Set_Cunit_Entity (Current_Sem_Unit, Id);
2714       end if;
2715
2716       Analyze_Generic_Formal_Part (N);
2717
2718       --  After processing the generic formals, analysis proceeds as for a
2719       --  non-generic package.
2720
2721       Analyze (Specification (N));
2722
2723       Validate_Categorization_Dependency (N, Id);
2724
2725       End_Generic;
2726
2727       End_Package_Scope (Id);
2728       Exit_Generic_Scope (Id);
2729
2730       if Nkind (Parent (N)) /= N_Compilation_Unit then
2731          Move_Freeze_Nodes (Id, N, Visible_Declarations (Specification (N)));
2732          Move_Freeze_Nodes (Id, N, Private_Declarations (Specification (N)));
2733          Move_Freeze_Nodes (Id, N, Generic_Formal_Declarations (N));
2734
2735       else
2736          Set_Body_Required (Parent (N), Unit_Requires_Body (Id));
2737          Validate_RT_RAT_Component (N);
2738
2739          --  If this is a spec without a body, check that generic parameters
2740          --  are referenced.
2741
2742          if not Body_Required (Parent (N)) then
2743             Check_References (Id);
2744          end if;
2745       end if;
2746    end Analyze_Generic_Package_Declaration;
2747
2748    --------------------------------------------
2749    -- Analyze_Generic_Subprogram_Declaration --
2750    --------------------------------------------
2751
2752    procedure Analyze_Generic_Subprogram_Declaration (N : Node_Id) is
2753       Spec        : Node_Id;
2754       Id          : Entity_Id;
2755       Formals     : List_Id;
2756       New_N       : Node_Id;
2757       Result_Type : Entity_Id;
2758       Save_Parent : Node_Id;
2759       Typ         : Entity_Id;
2760
2761    begin
2762       --  Create copy of generic unit, and save for instantiation. If the unit
2763       --  is a child unit, do not copy the specifications for the parent, which
2764       --  are not part of the generic tree.
2765
2766       Save_Parent := Parent_Spec (N);
2767       Set_Parent_Spec (N, Empty);
2768
2769       New_N := Copy_Generic_Node (N, Empty, Instantiating => False);
2770       Set_Parent_Spec (New_N, Save_Parent);
2771       Rewrite (N, New_N);
2772
2773       Spec := Specification (N);
2774       Id := Defining_Entity (Spec);
2775       Generate_Definition (Id);
2776
2777       if Nkind (Id) = N_Defining_Operator_Symbol then
2778          Error_Msg_N
2779            ("operator symbol not allowed for generic subprogram", Id);
2780       end if;
2781
2782       Start_Generic;
2783
2784       Enter_Name (Id);
2785
2786       Set_Scope_Depth_Value (Id, Scope_Depth (Current_Scope) + 1);
2787       Push_Scope (Id);
2788       Enter_Generic_Scope (Id);
2789       Set_Inner_Instances (Id, New_Elmt_List);
2790       Set_Is_Pure (Id, Is_Pure (Current_Scope));
2791
2792       Analyze_Generic_Formal_Part (N);
2793
2794       Formals := Parameter_Specifications (Spec);
2795
2796       if Present (Formals) then
2797          Process_Formals (Formals, Spec);
2798       end if;
2799
2800       if Nkind (Spec) = N_Function_Specification then
2801          Set_Ekind (Id, E_Generic_Function);
2802
2803          if Nkind (Result_Definition (Spec)) = N_Access_Definition then
2804             Result_Type := Access_Definition (Spec, Result_Definition (Spec));
2805             Set_Etype (Id, Result_Type);
2806          else
2807             Find_Type (Result_Definition (Spec));
2808             Typ := Entity (Result_Definition (Spec));
2809
2810             --  If a null exclusion is imposed on the result type, then create
2811             --  a null-excluding itype (an access subtype) and use it as the
2812             --  function's Etype.
2813
2814             if Is_Access_Type (Typ)
2815               and then Null_Exclusion_Present (Spec)
2816             then
2817                Set_Etype  (Id,
2818                  Create_Null_Excluding_Itype
2819                    (T           => Typ,
2820                     Related_Nod => Spec,
2821                     Scope_Id    => Defining_Unit_Name (Spec)));
2822             else
2823                Set_Etype (Id, Typ);
2824             end if;
2825          end if;
2826
2827       else
2828          Set_Ekind (Id, E_Generic_Procedure);
2829          Set_Etype (Id, Standard_Void_Type);
2830       end if;
2831
2832       --  For a library unit, we have reconstructed the entity for the unit,
2833       --  and must reset it in the library tables. We also make sure that
2834       --  Body_Required is set properly in the original compilation unit node.
2835
2836       if Nkind (Parent (N)) = N_Compilation_Unit then
2837          Set_Cunit_Entity (Current_Sem_Unit, Id);
2838          Set_Body_Required (Parent (N), Unit_Requires_Body (Id));
2839       end if;
2840
2841       Set_Categorization_From_Pragmas (N);
2842       Validate_Categorization_Dependency (N, Id);
2843
2844       Save_Global_References (Original_Node (N));
2845
2846       End_Generic;
2847       End_Scope;
2848       Exit_Generic_Scope (Id);
2849       Generate_Reference_To_Formals (Id);
2850    end Analyze_Generic_Subprogram_Declaration;
2851
2852    -----------------------------------
2853    -- Analyze_Package_Instantiation --
2854    -----------------------------------
2855
2856    procedure Analyze_Package_Instantiation (N : Node_Id) is
2857       Loc    : constant Source_Ptr := Sloc (N);
2858       Gen_Id : constant Node_Id    := Name (N);
2859
2860       Act_Decl      : Node_Id;
2861       Act_Decl_Name : Node_Id;
2862       Act_Decl_Id   : Entity_Id;
2863       Act_Spec      : Node_Id;
2864       Act_Tree      : Node_Id;
2865
2866       Gen_Decl : Node_Id;
2867       Gen_Unit : Entity_Id;
2868
2869       Is_Actual_Pack : constant Boolean :=
2870                          Is_Internal (Defining_Entity (N));
2871
2872       Env_Installed    : Boolean := False;
2873       Parent_Installed : Boolean := False;
2874       Renaming_List    : List_Id;
2875       Unit_Renaming    : Node_Id;
2876       Needs_Body       : Boolean;
2877       Inline_Now       : Boolean := False;
2878
2879       procedure Delay_Descriptors (E : Entity_Id);
2880       --  Delay generation of subprogram descriptors for given entity
2881
2882       function Might_Inline_Subp return Boolean;
2883       --  If inlining is active and the generic contains inlined subprograms,
2884       --  we instantiate the body. This may cause superfluous instantiations,
2885       --  but it is simpler than detecting the need for the body at the point
2886       --  of inlining, when the context of the instance is not available.
2887
2888       -----------------------
2889       -- Delay_Descriptors --
2890       -----------------------
2891
2892       procedure Delay_Descriptors (E : Entity_Id) is
2893       begin
2894          if not Delay_Subprogram_Descriptors (E) then
2895             Set_Delay_Subprogram_Descriptors (E);
2896             Pending_Descriptor.Append (E);
2897          end if;
2898       end Delay_Descriptors;
2899
2900       -----------------------
2901       -- Might_Inline_Subp --
2902       -----------------------
2903
2904       function Might_Inline_Subp return Boolean is
2905          E : Entity_Id;
2906
2907       begin
2908          if not Inline_Processing_Required then
2909             return False;
2910
2911          else
2912             E := First_Entity (Gen_Unit);
2913             while Present (E) loop
2914                if Is_Subprogram (E)
2915                  and then Is_Inlined (E)
2916                then
2917                   return True;
2918                end if;
2919
2920                Next_Entity (E);
2921             end loop;
2922          end if;
2923
2924          return False;
2925       end Might_Inline_Subp;
2926
2927    --  Start of processing for Analyze_Package_Instantiation
2928
2929    begin
2930       --  Very first thing: apply the special kludge for Text_IO processing
2931       --  in case we are instantiating one of the children of [Wide_]Text_IO.
2932
2933       Text_IO_Kludge (Name (N));
2934
2935       --  Make node global for error reporting
2936
2937       Instantiation_Node := N;
2938
2939       --  Case of instantiation of a generic package
2940
2941       if Nkind (N) = N_Package_Instantiation then
2942          Act_Decl_Id := New_Copy (Defining_Entity (N));
2943          Set_Comes_From_Source (Act_Decl_Id, True);
2944
2945          if Nkind (Defining_Unit_Name (N)) = N_Defining_Program_Unit_Name then
2946             Act_Decl_Name :=
2947               Make_Defining_Program_Unit_Name (Loc,
2948                 Name => New_Copy_Tree (Name (Defining_Unit_Name (N))),
2949                 Defining_Identifier => Act_Decl_Id);
2950          else
2951             Act_Decl_Name :=  Act_Decl_Id;
2952          end if;
2953
2954       --  Case of instantiation of a formal package
2955
2956       else
2957          Act_Decl_Id   := Defining_Identifier (N);
2958          Act_Decl_Name := Act_Decl_Id;
2959       end if;
2960
2961       Generate_Definition (Act_Decl_Id);
2962       Preanalyze_Actuals (N);
2963
2964       Init_Env;
2965       Env_Installed := True;
2966
2967       --  Reset renaming map for formal types. The mapping is established
2968       --  when analyzing the generic associations, but some mappings are
2969       --  inherited from formal packages of parent units, and these are
2970       --  constructed when the parents are installed.
2971
2972       Generic_Renamings.Set_Last (0);
2973       Generic_Renamings_HTable.Reset;
2974
2975       Check_Generic_Child_Unit (Gen_Id, Parent_Installed);
2976       Gen_Unit := Entity (Gen_Id);
2977
2978       --  Verify that it is the name of a generic package
2979
2980       --  A visibility glitch: if the instance is a child unit and the generic
2981       --  is the generic unit of a parent instance (i.e. both the parent and
2982       --  the child units are instances of the same package) the name now
2983       --  denotes the renaming within the parent, not the intended generic
2984       --  unit. See if there is a homonym that is the desired generic. The
2985       --  renaming declaration must be visible inside the instance of the
2986       --  child, but not when analyzing the name in the instantiation itself.
2987
2988       if Ekind (Gen_Unit) = E_Package
2989         and then Present (Renamed_Entity (Gen_Unit))
2990         and then In_Open_Scopes (Renamed_Entity (Gen_Unit))
2991         and then Is_Generic_Instance (Renamed_Entity (Gen_Unit))
2992         and then Present (Homonym (Gen_Unit))
2993       then
2994          Gen_Unit := Homonym (Gen_Unit);
2995       end if;
2996
2997       if Etype (Gen_Unit) = Any_Type then
2998          Restore_Env;
2999          return;
3000
3001       elsif Ekind (Gen_Unit) /= E_Generic_Package then
3002
3003          --  Ada 2005 (AI-50217): Cannot use instance in limited with_clause
3004
3005          if From_With_Type (Gen_Unit) then
3006             Error_Msg_N
3007               ("cannot instantiate a limited withed package", Gen_Id);
3008          else
3009             Error_Msg_N
3010               ("expect name of generic package in instantiation", Gen_Id);
3011          end if;
3012
3013          Restore_Env;
3014          return;
3015       end if;
3016
3017       if In_Extended_Main_Source_Unit (N) then
3018          Set_Is_Instantiated (Gen_Unit);
3019          Generate_Reference  (Gen_Unit, N);
3020
3021          if Present (Renamed_Object (Gen_Unit)) then
3022             Set_Is_Instantiated (Renamed_Object (Gen_Unit));
3023             Generate_Reference  (Renamed_Object (Gen_Unit), N);
3024          end if;
3025       end if;
3026
3027       if Nkind (Gen_Id) = N_Identifier
3028         and then Chars (Gen_Unit) = Chars (Defining_Entity (N))
3029       then
3030          Error_Msg_NE
3031            ("& is hidden within declaration of instance", Gen_Id, Gen_Unit);
3032
3033       elsif Nkind (Gen_Id) = N_Expanded_Name
3034         and then Is_Child_Unit (Gen_Unit)
3035         and then Nkind (Prefix (Gen_Id)) = N_Identifier
3036         and then Chars (Act_Decl_Id) = Chars (Prefix (Gen_Id))
3037       then
3038          Error_Msg_N
3039            ("& is hidden within declaration of instance ", Prefix (Gen_Id));
3040       end if;
3041
3042       Set_Entity (Gen_Id, Gen_Unit);
3043
3044       --  If generic is a renaming, get original generic unit
3045
3046       if Present (Renamed_Object (Gen_Unit))
3047         and then Ekind (Renamed_Object (Gen_Unit)) = E_Generic_Package
3048       then
3049          Gen_Unit := Renamed_Object (Gen_Unit);
3050       end if;
3051
3052       --  Verify that there are no circular instantiations
3053
3054       if In_Open_Scopes (Gen_Unit) then
3055          Error_Msg_NE ("instantiation of & within itself", N, Gen_Unit);
3056          Restore_Env;
3057          return;
3058
3059       elsif Contains_Instance_Of (Gen_Unit, Current_Scope, Gen_Id) then
3060          Error_Msg_Node_2 := Current_Scope;
3061          Error_Msg_NE
3062            ("circular Instantiation: & instantiated in &!", N, Gen_Unit);
3063          Circularity_Detected := True;
3064          Restore_Env;
3065          return;
3066
3067       else
3068          Gen_Decl := Unit_Declaration_Node (Gen_Unit);
3069
3070          --  Initialize renamings map, for error checking, and the list that
3071          --  holds private entities whose views have changed between generic
3072          --  definition and instantiation. If this is the instance created to
3073          --  validate an actual package, the instantiation environment is that
3074          --  of the enclosing instance.
3075
3076          Create_Instantiation_Source (N, Gen_Unit, False, S_Adjustment);
3077
3078          --  Copy original generic tree, to produce text for instantiation
3079
3080          Act_Tree :=
3081            Copy_Generic_Node
3082              (Original_Node (Gen_Decl), Empty, Instantiating => True);
3083
3084          Act_Spec := Specification (Act_Tree);
3085
3086          --  If this is the instance created to validate an actual package,
3087          --  only the formals matter, do not examine the package spec itself.
3088
3089          if Is_Actual_Pack then
3090             Set_Visible_Declarations (Act_Spec, New_List);
3091             Set_Private_Declarations (Act_Spec, New_List);
3092          end if;
3093
3094          Renaming_List :=
3095            Analyze_Associations
3096              (N,
3097               Generic_Formal_Declarations (Act_Tree),
3098               Generic_Formal_Declarations (Gen_Decl));
3099
3100          Set_Instance_Env (Gen_Unit, Act_Decl_Id);
3101          Set_Defining_Unit_Name (Act_Spec, Act_Decl_Name);
3102          Set_Is_Generic_Instance (Act_Decl_Id);
3103
3104          Set_Generic_Parent (Act_Spec, Gen_Unit);
3105
3106          --  References to the generic in its own declaration or its body are
3107          --  references to the instance. Add a renaming declaration for the
3108          --  generic unit itself. This declaration, as well as the renaming
3109          --  declarations for the generic formals, must remain private to the
3110          --  unit: the formals, because this is the language semantics, and
3111          --  the unit because its use is an artifact of the implementation.
3112
3113          Unit_Renaming :=
3114            Make_Package_Renaming_Declaration (Loc,
3115              Defining_Unit_Name =>
3116                Make_Defining_Identifier (Loc, Chars (Gen_Unit)),
3117              Name => New_Reference_To (Act_Decl_Id, Loc));
3118
3119          Append (Unit_Renaming, Renaming_List);
3120
3121          --  The renaming declarations are the first local declarations of
3122          --  the new unit.
3123
3124          if Is_Non_Empty_List (Visible_Declarations (Act_Spec)) then
3125             Insert_List_Before
3126               (First (Visible_Declarations (Act_Spec)), Renaming_List);
3127          else
3128             Set_Visible_Declarations (Act_Spec, Renaming_List);
3129          end if;
3130
3131          Act_Decl :=
3132            Make_Package_Declaration (Loc,
3133              Specification => Act_Spec);
3134
3135          --  Save the instantiation node, for subsequent instantiation of the
3136          --  body, if there is one and we are generating code for the current
3137          --  unit. Mark the unit as having a body, to avoid a premature error
3138          --  message.
3139
3140          --  We instantiate the body if we are generating code, if we are
3141          --  generating cross-reference information, or if we are building
3142          --  trees for ASIS use.
3143
3144          declare
3145             Enclosing_Body_Present : Boolean := False;
3146             --  If the generic unit is not a compilation unit, then a body may
3147             --  be present in its parent even if none is required. We create a
3148             --  tentative pending instantiation for the body, which will be
3149             --  discarded if none is actually present.
3150
3151             Scop : Entity_Id;
3152
3153          begin
3154             if Scope (Gen_Unit) /= Standard_Standard
3155               and then not Is_Child_Unit (Gen_Unit)
3156             then
3157                Scop := Scope (Gen_Unit);
3158
3159                while Present (Scop)
3160                  and then Scop /= Standard_Standard
3161                loop
3162                   if Unit_Requires_Body (Scop) then
3163                      Enclosing_Body_Present := True;
3164                      exit;
3165
3166                   elsif In_Open_Scopes (Scop)
3167                     and then In_Package_Body (Scop)
3168                   then
3169                      Enclosing_Body_Present := True;
3170                      exit;
3171                   end if;
3172
3173                   exit when Is_Compilation_Unit (Scop);
3174                   Scop := Scope (Scop);
3175                end loop;
3176             end if;
3177
3178             --  If front-end inlining is enabled, and this is a unit for which
3179             --  code will be generated, we instantiate the body at once.
3180
3181             --  This is done if the instance is not the main unit, and if the
3182             --  generic is not a child unit of another generic, to avoid scope
3183             --  problems and the reinstallation of parent instances.
3184
3185             if Expander_Active
3186               and then (not Is_Child_Unit (Gen_Unit)
3187                          or else not Is_Generic_Unit (Scope (Gen_Unit)))
3188               and then Might_Inline_Subp
3189               and then not Is_Actual_Pack
3190             then
3191                if Front_End_Inlining
3192                  and then (Is_In_Main_Unit (N)
3193                             or else In_Main_Context (Current_Scope))
3194                  and then Nkind (Parent (N)) /= N_Compilation_Unit
3195                then
3196                   Inline_Now := True;
3197
3198                --  In configurable_run_time mode we force the inlining of
3199                --  predefined subprograms marked Inline_Always, to minimize
3200                --  the use of the run-time library.
3201
3202                elsif Is_Predefined_File_Name
3203                        (Unit_File_Name (Get_Source_Unit (Gen_Decl)))
3204                  and then Configurable_Run_Time_Mode
3205                  and then Nkind (Parent (N)) /= N_Compilation_Unit
3206                then
3207                   Inline_Now := True;
3208                end if;
3209
3210                --  If the current scope is itself an instance within a child
3211                --  unit, there will be duplications in the scope stack, and the
3212                --  unstacking mechanism in Inline_Instance_Body will fail.
3213                --  This loses some rare cases of optimization, and might be
3214                --  improved some day, if we can find a proper abstraction for
3215                --  "the complete compilation context" that can be saved and
3216                --  restored. ???
3217
3218                if Is_Generic_Instance (Current_Scope) then
3219                   declare
3220                      Curr_Unit : constant Entity_Id :=
3221                                    Cunit_Entity (Current_Sem_Unit);
3222                   begin
3223                      if Curr_Unit /= Current_Scope
3224                        and then Is_Child_Unit (Curr_Unit)
3225                      then
3226                         Inline_Now := False;
3227                      end if;
3228                   end;
3229                end if;
3230             end if;
3231
3232             Needs_Body :=
3233               (Unit_Requires_Body (Gen_Unit)
3234                   or else Enclosing_Body_Present
3235                   or else Present (Corresponding_Body (Gen_Decl)))
3236                 and then (Is_In_Main_Unit (N)
3237                            or else Might_Inline_Subp)
3238                 and then not Is_Actual_Pack
3239                 and then not Inline_Now
3240                 and then (Operating_Mode = Generate_Code
3241                             or else (Operating_Mode = Check_Semantics
3242                                       and then ASIS_Mode));
3243
3244             --  If front_end_inlining is enabled, do not instantiate body if
3245             --  within a generic context.
3246
3247             if (Front_End_Inlining
3248                   and then not Expander_Active)
3249               or else Is_Generic_Unit (Cunit_Entity (Main_Unit))
3250             then
3251                Needs_Body := False;
3252             end if;
3253
3254             --  If the current context is generic, and the package being
3255             --  instantiated is declared within a formal package, there is no
3256             --  body to instantiate until the enclosing generic is instantiated
3257             --  and there is an actual for the formal package. If the formal
3258             --  package has parameters, we build a regular package instance for
3259             --  it, that precedes the original formal package declaration.
3260
3261             if In_Open_Scopes (Scope (Scope (Gen_Unit))) then
3262                declare
3263                   Decl : constant Node_Id :=
3264                            Original_Node
3265                              (Unit_Declaration_Node (Scope (Gen_Unit)));
3266                begin
3267                   if Nkind (Decl) = N_Formal_Package_Declaration
3268                     or else (Nkind (Decl) = N_Package_Declaration
3269                                and then Is_List_Member (Decl)
3270                                and then Present (Next (Decl))
3271                                and then
3272                                  Nkind (Next (Decl)) =
3273                                                 N_Formal_Package_Declaration)
3274                   then
3275                      Needs_Body := False;
3276                   end if;
3277                end;
3278             end if;
3279          end;
3280
3281          --  If we are generating the calling stubs from the instantiation of
3282          --  a generic RCI package, we will not use the body of the generic
3283          --  package.
3284
3285          if Distribution_Stub_Mode = Generate_Caller_Stub_Body
3286            and then Is_Compilation_Unit (Defining_Entity (N))
3287          then
3288             Needs_Body := False;
3289          end if;
3290
3291          if Needs_Body then
3292
3293             --  Here is a defence against a ludicrous number of instantiations
3294             --  caused by a circular set of instantiation attempts.
3295
3296             if Pending_Instantiations.Last >
3297                  Hostparm.Max_Instantiations
3298             then
3299                Error_Msg_N ("too many instantiations", N);
3300                raise Unrecoverable_Error;
3301             end if;
3302
3303             --  Indicate that the enclosing scopes contain an instantiation,
3304             --  and that cleanup actions should be delayed until after the
3305             --  instance body is expanded.
3306
3307             Check_Forward_Instantiation (Gen_Decl);
3308             if Nkind (N) = N_Package_Instantiation then
3309                declare
3310                   Enclosing_Master : Entity_Id;
3311
3312                begin
3313                   --  Loop to search enclosing masters
3314
3315                   Enclosing_Master := Current_Scope;
3316                   Scope_Loop : while Enclosing_Master /= Standard_Standard loop
3317                      if Ekind (Enclosing_Master) = E_Package then
3318                         if Is_Compilation_Unit (Enclosing_Master) then
3319                            if In_Package_Body (Enclosing_Master) then
3320                               Delay_Descriptors
3321                                 (Body_Entity (Enclosing_Master));
3322                            else
3323                               Delay_Descriptors
3324                                 (Enclosing_Master);
3325                            end if;
3326
3327                            exit Scope_Loop;
3328
3329                         else
3330                            Enclosing_Master := Scope (Enclosing_Master);
3331                         end if;
3332
3333                      elsif Ekind (Enclosing_Master) = E_Generic_Package then
3334                         Enclosing_Master := Scope (Enclosing_Master);
3335
3336                      elsif Is_Generic_Subprogram (Enclosing_Master)
3337                        or else Ekind (Enclosing_Master) = E_Void
3338                      then
3339                         --  Cleanup actions will eventually be performed on the
3340                         --  enclosing instance, if any. Enclosing scope is void
3341                         --  in the formal part of a generic subprogram.
3342
3343                         exit Scope_Loop;
3344
3345                      else
3346                         if Ekind (Enclosing_Master) = E_Entry
3347                           and then
3348                             Ekind (Scope (Enclosing_Master)) = E_Protected_Type
3349                         then
3350                            if not Expander_Active then
3351                               exit Scope_Loop;
3352                            else
3353                               Enclosing_Master :=
3354                                 Protected_Body_Subprogram (Enclosing_Master);
3355                            end if;
3356                         end if;
3357
3358                         Set_Delay_Cleanups (Enclosing_Master);
3359
3360                         while Ekind (Enclosing_Master) = E_Block loop
3361                            Enclosing_Master := Scope (Enclosing_Master);
3362                         end loop;
3363
3364                         if Is_Subprogram (Enclosing_Master) then
3365                            Delay_Descriptors (Enclosing_Master);
3366
3367                         elsif Is_Task_Type (Enclosing_Master) then
3368                            declare
3369                               TBP : constant Node_Id :=
3370                                       Get_Task_Body_Procedure
3371                                         (Enclosing_Master);
3372                            begin
3373                               if Present (TBP) then
3374                                  Delay_Descriptors  (TBP);
3375                                  Set_Delay_Cleanups (TBP);
3376                               end if;
3377                            end;
3378                         end if;
3379
3380                         exit Scope_Loop;
3381                      end if;
3382                   end loop Scope_Loop;
3383                end;
3384
3385                --  Make entry in table
3386
3387                Pending_Instantiations.Append
3388                  ((Inst_Node                => N,
3389                    Act_Decl                 => Act_Decl,
3390                    Expander_Status          => Expander_Active,
3391                    Current_Sem_Unit         => Current_Sem_Unit,
3392                    Scope_Suppress           => Scope_Suppress,
3393                    Local_Suppress_Stack_Top => Local_Suppress_Stack_Top));
3394             end if;
3395          end if;
3396
3397          Set_Categorization_From_Pragmas (Act_Decl);
3398
3399          if Parent_Installed then
3400             Hide_Current_Scope;
3401          end if;
3402
3403          Set_Instance_Spec (N, Act_Decl);
3404
3405          --  If not a compilation unit, insert the package declaration before
3406          --  the original instantiation node.
3407
3408          if Nkind (Parent (N)) /= N_Compilation_Unit then
3409             Mark_Rewrite_Insertion (Act_Decl);
3410             Insert_Before (N, Act_Decl);
3411             Analyze (Act_Decl);
3412
3413          --  For an instantiation that is a compilation unit, place declaration
3414          --  on current node so context is complete for analysis (including
3415          --  nested instantiations). If this is the main unit, the declaration
3416          --  eventually replaces the instantiation node. If the instance body
3417          --  is created later, it replaces the instance node, and the
3418          --  declaration is attached to it (see
3419          --  Build_Instance_Compilation_Unit_Nodes).
3420
3421          else
3422             if Cunit_Entity (Current_Sem_Unit) = Defining_Entity (N) then
3423
3424                --  The entity for the current unit is the newly created one,
3425                --  and all semantic information is attached to it.
3426
3427                Set_Cunit_Entity (Current_Sem_Unit, Act_Decl_Id);
3428
3429                --  If this is the main unit, replace the main entity as well
3430
3431                if Current_Sem_Unit = Main_Unit then
3432                   Main_Unit_Entity := Act_Decl_Id;
3433                end if;
3434             end if;
3435
3436             Set_Unit (Parent (N), Act_Decl);
3437             Set_Parent_Spec (Act_Decl, Parent_Spec (N));
3438             Set_Package_Instantiation (Act_Decl_Id, N);
3439             Analyze (Act_Decl);
3440             Set_Unit (Parent (N), N);
3441             Set_Body_Required (Parent (N), False);
3442
3443             --  We never need elaboration checks on instantiations, since by
3444             --  definition, the body instantiation is elaborated at the same
3445             --  time as the spec instantiation.
3446
3447             Set_Suppress_Elaboration_Warnings (Act_Decl_Id);
3448             Set_Kill_Elaboration_Checks       (Act_Decl_Id);
3449          end if;
3450
3451          Check_Elab_Instantiation (N);
3452
3453          if ABE_Is_Certain (N) and then Needs_Body then
3454             Pending_Instantiations.Decrement_Last;
3455          end if;
3456
3457          Check_Hidden_Child_Unit (N, Gen_Unit, Act_Decl_Id);
3458
3459          Set_First_Private_Entity (Defining_Unit_Name (Unit_Renaming),
3460            First_Private_Entity (Act_Decl_Id));
3461
3462          --  If the instantiation will receive a body, the unit will be
3463          --  transformed into a package body, and receive its own elaboration
3464          --  entity. Otherwise, the nature of the unit is now a package
3465          --  declaration.
3466
3467          if Nkind (Parent (N)) = N_Compilation_Unit
3468            and then not Needs_Body
3469          then
3470             Rewrite (N, Act_Decl);
3471          end if;
3472
3473          if Present (Corresponding_Body (Gen_Decl))
3474            or else Unit_Requires_Body (Gen_Unit)
3475          then
3476             Set_Has_Completion (Act_Decl_Id);
3477          end if;
3478
3479          Check_Formal_Packages (Act_Decl_Id);
3480
3481          Restore_Private_Views (Act_Decl_Id);
3482
3483          Inherit_Context (Gen_Decl, N);
3484
3485          if Parent_Installed then
3486             Remove_Parent;
3487          end if;
3488
3489          Restore_Env;
3490          Env_Installed := False;
3491       end if;
3492
3493       Validate_Categorization_Dependency (N, Act_Decl_Id);
3494
3495       --  There used to be a check here to prevent instantiations in local
3496       --  contexts if the No_Local_Allocators restriction was active. This
3497       --  check was removed by a binding interpretation in AI-95-00130/07,
3498       --  but we retain the code for documentation purposes.
3499
3500       --  if Ekind (Act_Decl_Id) /= E_Void
3501       --    and then not Is_Library_Level_Entity (Act_Decl_Id)
3502       --  then
3503       --     Check_Restriction (No_Local_Allocators, N);
3504       --  end if;
3505
3506       if Inline_Now then
3507          Inline_Instance_Body (N, Gen_Unit, Act_Decl);
3508       end if;
3509
3510       --  The following is a tree patch for ASIS: ASIS needs separate nodes to
3511       --  be used as defining identifiers for a formal package and for the
3512       --  corresponding expanded package.
3513
3514       if Nkind (N) = N_Formal_Package_Declaration then
3515          Act_Decl_Id := New_Copy (Defining_Entity (N));
3516          Set_Comes_From_Source (Act_Decl_Id, True);
3517          Set_Is_Generic_Instance (Act_Decl_Id, False);
3518          Set_Defining_Identifier (N, Act_Decl_Id);
3519       end if;
3520
3521    exception
3522       when Instantiation_Error =>
3523          if Parent_Installed then
3524             Remove_Parent;
3525          end if;
3526
3527          if Env_Installed then
3528             Restore_Env;
3529          end if;
3530    end Analyze_Package_Instantiation;
3531
3532    --------------------------
3533    -- Inline_Instance_Body --
3534    --------------------------
3535
3536    procedure Inline_Instance_Body
3537      (N        : Node_Id;
3538       Gen_Unit : Entity_Id;
3539       Act_Decl : Node_Id)
3540    is
3541       Vis          : Boolean;
3542       Gen_Comp     : constant Entity_Id :=
3543                       Cunit_Entity (Get_Source_Unit (Gen_Unit));
3544       Curr_Comp    : constant Node_Id := Cunit (Current_Sem_Unit);
3545       Curr_Scope   : Entity_Id := Empty;
3546       Curr_Unit    : constant Entity_Id :=
3547                        Cunit_Entity (Current_Sem_Unit);
3548       Removed      : Boolean := False;
3549       Num_Scopes   : Int := 0;
3550
3551       Scope_Stack_Depth : constant Int :=
3552                             Scope_Stack.Last - Scope_Stack.First + 1;
3553
3554       Use_Clauses  : array (1 .. Scope_Stack_Depth) of Node_Id;
3555       Instances    : array (1 .. Scope_Stack_Depth) of Entity_Id;
3556       Inner_Scopes : array (1 .. Scope_Stack_Depth) of Entity_Id;
3557       Num_Inner    : Int := 0;
3558       N_Instances  : Int := 0;
3559       S            : Entity_Id;
3560
3561    begin
3562       --  Case of generic unit defined in another unit. We must remove the
3563       --  complete context of the current unit to install that of the generic.
3564
3565       if Gen_Comp /= Cunit_Entity (Current_Sem_Unit) then
3566
3567          --  Add some comments for the following two loops ???
3568
3569          S := Current_Scope;
3570          while Present (S) and then S /= Standard_Standard loop
3571             loop
3572                Num_Scopes := Num_Scopes + 1;
3573
3574                Use_Clauses (Num_Scopes) :=
3575                  (Scope_Stack.Table
3576                     (Scope_Stack.Last - Num_Scopes + 1).
3577                        First_Use_Clause);
3578                End_Use_Clauses (Use_Clauses (Num_Scopes));
3579
3580                exit when Scope_Stack.Last - Num_Scopes + 1 = Scope_Stack.First
3581                  or else Scope_Stack.Table
3582                            (Scope_Stack.Last - Num_Scopes).Entity
3583                              = Scope (S);
3584             end loop;
3585
3586             exit when Is_Generic_Instance (S)
3587               and then (In_Package_Body (S)
3588                           or else Ekind (S) = E_Procedure
3589                           or else Ekind (S) = E_Function);
3590             S := Scope (S);
3591          end loop;
3592
3593          Vis := Is_Immediately_Visible (Gen_Comp);
3594
3595          --  Find and save all enclosing instances
3596
3597          S := Current_Scope;
3598
3599          while Present (S)
3600            and then S /= Standard_Standard
3601          loop
3602             if Is_Generic_Instance (S) then
3603                N_Instances := N_Instances + 1;
3604                Instances (N_Instances) := S;
3605
3606                exit when In_Package_Body (S);
3607             end if;
3608
3609             S := Scope (S);
3610          end loop;
3611
3612          --  Remove context of current compilation unit, unless we are within a
3613          --  nested package instantiation, in which case the context has been
3614          --  removed previously.
3615
3616          --  If current scope is the body of a child unit, remove context of
3617          --  spec as well. If an enclosing scope is an instance body, the
3618          --  context has already been removed, but the entities in the body
3619          --  must be made invisible as well.
3620
3621          S := Current_Scope;
3622
3623          while Present (S)
3624            and then S /= Standard_Standard
3625          loop
3626             if Is_Generic_Instance (S)
3627               and then (In_Package_Body (S)
3628                           or else Ekind (S) = E_Procedure
3629                             or else Ekind (S) = E_Function)
3630             then
3631                --  We still have to remove the entities of the enclosing
3632                --  instance from direct visibility.
3633
3634                declare
3635                   E : Entity_Id;
3636                begin
3637                   E := First_Entity (S);
3638                   while Present (E) loop
3639                      Set_Is_Immediately_Visible (E, False);
3640                      Next_Entity (E);
3641                   end loop;
3642                end;
3643
3644                exit;
3645             end if;
3646
3647             if S = Curr_Unit
3648               or else (Ekind (Curr_Unit) = E_Package_Body
3649                         and then S = Spec_Entity (Curr_Unit))
3650               or else (Ekind (Curr_Unit) = E_Subprogram_Body
3651                         and then S =
3652                           Corresponding_Spec
3653                             (Unit_Declaration_Node (Curr_Unit)))
3654             then
3655                Removed := True;
3656
3657                --  Remove entities in current scopes from visibility, so that
3658                --  instance body is compiled in a clean environment.
3659
3660                Save_Scope_Stack (Handle_Use => False);
3661
3662                if Is_Child_Unit (S) then
3663
3664                   --  Remove child unit from stack, as well as inner scopes.
3665                   --  Removing the context of a child unit removes parent units
3666                   --  as well.
3667
3668                   while Current_Scope /= S loop
3669                      Num_Inner := Num_Inner + 1;
3670                      Inner_Scopes (Num_Inner) := Current_Scope;
3671                      Pop_Scope;
3672                   end loop;
3673
3674                   Pop_Scope;
3675                   Remove_Context (Curr_Comp);
3676                   Curr_Scope := S;
3677
3678                else
3679                   Remove_Context (Curr_Comp);
3680                end if;
3681
3682                if Ekind (Curr_Unit) = E_Package_Body then
3683                   Remove_Context (Library_Unit (Curr_Comp));
3684                end if;
3685             end if;
3686
3687             S := Scope (S);
3688          end loop;
3689          pragma Assert (Num_Inner < Num_Scopes);
3690
3691          Push_Scope (Standard_Standard);
3692          Scope_Stack.Table (Scope_Stack.Last).Is_Active_Stack_Base := True;
3693          Instantiate_Package_Body
3694            (Body_Info =>
3695              ((Inst_Node                => N,
3696                Act_Decl                 => Act_Decl,
3697                Expander_Status          => Expander_Active,
3698                Current_Sem_Unit         => Current_Sem_Unit,
3699                Scope_Suppress           => Scope_Suppress,
3700                Local_Suppress_Stack_Top => Local_Suppress_Stack_Top)),
3701             Inlined_Body => True);
3702
3703          Pop_Scope;
3704
3705          --  Restore context
3706
3707          Set_Is_Immediately_Visible (Gen_Comp, Vis);
3708
3709          --  Reset Generic_Instance flag so that use clauses can be installed
3710          --  in the proper order. (See Use_One_Package for effect of enclosing
3711          --  instances on processing of use clauses).
3712
3713          for J in 1 .. N_Instances loop
3714             Set_Is_Generic_Instance (Instances (J), False);
3715          end loop;
3716
3717          if Removed then
3718             Install_Context (Curr_Comp);
3719
3720             if Present (Curr_Scope)
3721               and then Is_Child_Unit (Curr_Scope)
3722             then
3723                Push_Scope (Curr_Scope);
3724                Set_Is_Immediately_Visible (Curr_Scope);
3725
3726                --  Finally, restore inner scopes as well
3727
3728                for J in reverse 1 .. Num_Inner loop
3729                   Push_Scope (Inner_Scopes (J));
3730                end loop;
3731             end if;
3732
3733             Restore_Scope_Stack (Handle_Use => False);
3734
3735             if Present (Curr_Scope)
3736               and then
3737                 (In_Private_Part (Curr_Scope)
3738                   or else In_Package_Body (Curr_Scope))
3739             then
3740                --  Install private declaration of ancestor units, which are
3741                --  currently available. Restore_Scope_Stack and Install_Context
3742                --  only install the visible part of parents.
3743
3744                declare
3745                   Par : Entity_Id;
3746                begin
3747                   Par := Scope (Curr_Scope);
3748                   while (Present (Par))
3749                     and then Par /= Standard_Standard
3750                   loop
3751                      Install_Private_Declarations (Par);
3752                      Par := Scope (Par);
3753                   end loop;
3754                end;
3755             end if;
3756          end if;
3757
3758          --  Restore use clauses. For a child unit, use clauses in the parents
3759          --  are restored when installing the context, so only those in inner
3760          --  scopes (and those local to the child unit itself) need to be
3761          --  installed explicitly.
3762
3763          if Is_Child_Unit (Curr_Unit)
3764            and then Removed
3765          then
3766             for J in reverse 1 .. Num_Inner + 1 loop
3767                Scope_Stack.Table (Scope_Stack.Last - J + 1).First_Use_Clause :=
3768                  Use_Clauses (J);
3769                Install_Use_Clauses (Use_Clauses (J));
3770             end  loop;
3771
3772          else
3773             for J in reverse 1 .. Num_Scopes loop
3774                Scope_Stack.Table (Scope_Stack.Last - J + 1).First_Use_Clause :=
3775                  Use_Clauses (J);
3776                Install_Use_Clauses (Use_Clauses (J));
3777             end  loop;
3778          end if;
3779
3780          --  Restore status of instances. If one of them is a body, make
3781          --  its local entities visible again.
3782
3783          declare
3784             E    : Entity_Id;
3785             Inst : Entity_Id;
3786
3787          begin
3788             for J in 1 .. N_Instances loop
3789                Inst := Instances (J);
3790                Set_Is_Generic_Instance (Inst, True);
3791
3792                if In_Package_Body (Inst)
3793                  or else Ekind (S) = E_Procedure
3794                  or else Ekind (S) = E_Function
3795                then
3796                   E := First_Entity (Instances (J));
3797                   while Present (E) loop
3798                      Set_Is_Immediately_Visible (E);
3799                      Next_Entity (E);
3800                   end loop;
3801                end if;
3802             end loop;
3803          end;
3804
3805       --  If generic unit is in current unit, current context is correct
3806
3807       else
3808          Instantiate_Package_Body
3809            (Body_Info =>
3810              ((Inst_Node                => N,
3811                Act_Decl                 => Act_Decl,
3812                Expander_Status          => Expander_Active,
3813                Current_Sem_Unit         => Current_Sem_Unit,
3814                Scope_Suppress           => Scope_Suppress,
3815                Local_Suppress_Stack_Top => Local_Suppress_Stack_Top)),
3816             Inlined_Body => True);
3817       end if;
3818    end Inline_Instance_Body;
3819
3820    -------------------------------------
3821    -- Analyze_Procedure_Instantiation --
3822    -------------------------------------
3823
3824    procedure Analyze_Procedure_Instantiation (N : Node_Id) is
3825    begin
3826       Analyze_Subprogram_Instantiation (N, E_Procedure);
3827    end Analyze_Procedure_Instantiation;
3828
3829    -----------------------------------
3830    -- Need_Subprogram_Instance_Body --
3831    -----------------------------------
3832
3833    function Need_Subprogram_Instance_Body
3834      (N    : Node_Id;
3835       Subp : Entity_Id) return Boolean
3836    is
3837    begin
3838       if (Is_In_Main_Unit (N)
3839             or else Is_Inlined (Subp)
3840             or else Is_Inlined (Alias (Subp)))
3841         and then (Operating_Mode = Generate_Code
3842                     or else (Operating_Mode = Check_Semantics
3843                                and then ASIS_Mode))
3844         and then (Expander_Active or else ASIS_Mode)
3845         and then not ABE_Is_Certain (N)
3846         and then not Is_Eliminated (Subp)
3847       then
3848          Pending_Instantiations.Append
3849            ((Inst_Node                => N,
3850              Act_Decl                 => Unit_Declaration_Node (Subp),
3851              Expander_Status          => Expander_Active,
3852              Current_Sem_Unit         => Current_Sem_Unit,
3853              Scope_Suppress           => Scope_Suppress,
3854              Local_Suppress_Stack_Top => Local_Suppress_Stack_Top));
3855          return True;
3856       else
3857          return False;
3858       end if;
3859    end Need_Subprogram_Instance_Body;
3860
3861    --------------------------------------
3862    -- Analyze_Subprogram_Instantiation --
3863    --------------------------------------
3864
3865    procedure Analyze_Subprogram_Instantiation
3866      (N : Node_Id;
3867       K : Entity_Kind)
3868    is
3869       Loc    : constant Source_Ptr := Sloc (N);
3870       Gen_Id : constant Node_Id    := Name (N);
3871
3872       Anon_Id : constant Entity_Id :=
3873                   Make_Defining_Identifier (Sloc (Defining_Entity (N)),
3874                     Chars => New_External_Name
3875                                (Chars (Defining_Entity (N)), 'R'));
3876
3877       Act_Decl_Id : Entity_Id;
3878       Act_Decl    : Node_Id;
3879       Act_Spec    : Node_Id;
3880       Act_Tree    : Node_Id;
3881
3882       Env_Installed    : Boolean := False;
3883       Gen_Unit         : Entity_Id;
3884       Gen_Decl         : Node_Id;
3885       Pack_Id          : Entity_Id;
3886       Parent_Installed : Boolean := False;
3887       Renaming_List    : List_Id;
3888
3889       procedure Analyze_Instance_And_Renamings;
3890       --  The instance must be analyzed in a context that includes the mappings
3891       --  of generic parameters into actuals. We create a package declaration
3892       --  for this purpose, and a subprogram with an internal name within the
3893       --  package. The subprogram instance is simply an alias for the internal
3894       --  subprogram, declared in the current scope.
3895
3896       ------------------------------------
3897       -- Analyze_Instance_And_Renamings --
3898       ------------------------------------
3899
3900       procedure Analyze_Instance_And_Renamings is
3901          Def_Ent   : constant Entity_Id := Defining_Entity (N);
3902          Pack_Decl : Node_Id;
3903
3904       begin
3905          if Nkind (Parent (N)) = N_Compilation_Unit then
3906
3907             --  For the case of a compilation unit, the container package has
3908             --  the same name as the instantiation, to insure that the binder
3909             --  calls the elaboration procedure with the right name. Copy the
3910             --  entity of the instance, which may have compilation level flags
3911             --  (e.g. Is_Child_Unit) set.
3912
3913             Pack_Id := New_Copy (Def_Ent);
3914
3915          else
3916             --  Otherwise we use the name of the instantiation concatenated
3917             --  with its source position to ensure uniqueness if there are
3918             --  several instantiations with the same name.
3919
3920             Pack_Id :=
3921               Make_Defining_Identifier (Loc,
3922                 Chars => New_External_Name
3923                            (Related_Id   => Chars (Def_Ent),
3924                             Suffix       => "GP",
3925                             Suffix_Index => Source_Offset (Sloc (Def_Ent))));
3926          end if;
3927
3928          Pack_Decl := Make_Package_Declaration (Loc,
3929            Specification => Make_Package_Specification (Loc,
3930              Defining_Unit_Name   => Pack_Id,
3931              Visible_Declarations => Renaming_List,
3932              End_Label            => Empty));
3933
3934          Set_Instance_Spec (N, Pack_Decl);
3935          Set_Is_Generic_Instance (Pack_Id);
3936          Set_Debug_Info_Needed (Pack_Id);
3937
3938          --  Case of not a compilation unit
3939
3940          if Nkind (Parent (N)) /= N_Compilation_Unit then
3941             Mark_Rewrite_Insertion (Pack_Decl);
3942             Insert_Before (N, Pack_Decl);
3943             Set_Has_Completion (Pack_Id);
3944
3945          --  Case of an instantiation that is a compilation unit
3946
3947          --  Place declaration on current node so context is complete for
3948          --  analysis (including nested instantiations), and for use in a
3949          --  context_clause (see Analyze_With_Clause).
3950
3951          else
3952             Set_Unit (Parent (N), Pack_Decl);
3953             Set_Parent_Spec (Pack_Decl, Parent_Spec (N));
3954          end if;
3955
3956          Analyze (Pack_Decl);
3957          Check_Formal_Packages (Pack_Id);
3958          Set_Is_Generic_Instance (Pack_Id, False);
3959
3960          --  Body of the enclosing package is supplied when instantiating the
3961          --  subprogram body, after semantic analysis is completed.
3962
3963          if Nkind (Parent (N)) = N_Compilation_Unit then
3964
3965             --  Remove package itself from visibility, so it does not
3966             --  conflict with subprogram.
3967
3968             Set_Name_Entity_Id (Chars (Pack_Id), Homonym (Pack_Id));
3969
3970             --  Set name and scope of internal subprogram so that the proper
3971             --  external name will be generated. The proper scope is the scope
3972             --  of the wrapper package. We need to generate debugging info for
3973             --  the internal subprogram, so set flag accordingly.
3974
3975             Set_Chars (Anon_Id, Chars (Defining_Entity (N)));
3976             Set_Scope (Anon_Id, Scope (Pack_Id));
3977
3978             --  Mark wrapper package as referenced, to avoid spurious warnings
3979             --  if the instantiation appears in various with_ clauses of
3980             --  subunits of the main unit.
3981
3982             Set_Referenced (Pack_Id);
3983          end if;
3984
3985          Set_Is_Generic_Instance (Anon_Id);
3986          Set_Debug_Info_Needed   (Anon_Id);
3987          Act_Decl_Id := New_Copy (Anon_Id);
3988
3989          Set_Parent            (Act_Decl_Id, Parent (Anon_Id));
3990          Set_Chars             (Act_Decl_Id, Chars (Defining_Entity (N)));
3991          Set_Sloc              (Act_Decl_Id, Sloc (Defining_Entity (N)));
3992          Set_Comes_From_Source (Act_Decl_Id, True);
3993
3994          --  The signature may involve types that are not frozen yet, but the
3995          --  subprogram will be frozen at the point the wrapper package is
3996          --  frozen, so it does not need its own freeze node. In fact, if one
3997          --  is created, it might conflict with the freezing actions from the
3998          --  wrapper package.
3999
4000          Set_Has_Delayed_Freeze (Anon_Id, False);
4001
4002          --  If the instance is a child unit, mark the Id accordingly. Mark
4003          --  the anonymous entity as well, which is the real subprogram and
4004          --  which is used when the instance appears in a context clause.
4005
4006          Set_Is_Child_Unit (Act_Decl_Id, Is_Child_Unit (Defining_Entity (N)));
4007          Set_Is_Child_Unit (Anon_Id, Is_Child_Unit (Defining_Entity (N)));
4008          New_Overloaded_Entity (Act_Decl_Id);
4009          Check_Eliminated  (Act_Decl_Id);
4010
4011          --  In compilation unit case, kill elaboration checks on the
4012          --  instantiation, since they are never needed -- the body is
4013          --  instantiated at the same point as the spec.
4014
4015          if Nkind (Parent (N)) = N_Compilation_Unit then
4016             Set_Suppress_Elaboration_Warnings (Act_Decl_Id);
4017             Set_Kill_Elaboration_Checks       (Act_Decl_Id);
4018             Set_Is_Compilation_Unit (Anon_Id);
4019
4020             Set_Cunit_Entity (Current_Sem_Unit, Pack_Id);
4021          end if;
4022
4023          --  The instance is not a freezing point for the new subprogram
4024
4025          Set_Is_Frozen (Act_Decl_Id, False);
4026
4027          if Nkind (Defining_Entity (N)) = N_Defining_Operator_Symbol then
4028             Valid_Operator_Definition (Act_Decl_Id);
4029          end if;
4030
4031          Set_Alias  (Act_Decl_Id, Anon_Id);
4032          Set_Parent (Act_Decl_Id, Parent (Anon_Id));
4033          Set_Has_Completion (Act_Decl_Id);
4034          Set_Related_Instance (Pack_Id, Act_Decl_Id);
4035
4036          if Nkind (Parent (N)) = N_Compilation_Unit then
4037             Set_Body_Required (Parent (N), False);
4038          end if;
4039       end Analyze_Instance_And_Renamings;
4040
4041    --  Start of processing for Analyze_Subprogram_Instantiation
4042
4043    begin
4044       --  Very first thing: apply the special kludge for Text_IO processing
4045       --  in case we are instantiating one of the children of [Wide_]Text_IO.
4046       --  Of course such an instantiation is bogus (these are packages, not
4047       --  subprograms), but we get a better error message if we do this.
4048
4049       Text_IO_Kludge (Gen_Id);
4050
4051       --  Make node global for error reporting
4052
4053       Instantiation_Node := N;
4054       Preanalyze_Actuals (N);
4055
4056       Init_Env;
4057       Env_Installed := True;
4058       Check_Generic_Child_Unit (Gen_Id, Parent_Installed);
4059       Gen_Unit := Entity (Gen_Id);
4060
4061       Generate_Reference (Gen_Unit, Gen_Id);
4062
4063       if Nkind (Gen_Id) = N_Identifier
4064         and then Chars (Gen_Unit) = Chars (Defining_Entity (N))
4065       then
4066          Error_Msg_NE
4067            ("& is hidden within declaration of instance", Gen_Id, Gen_Unit);
4068       end if;
4069
4070       if Etype (Gen_Unit) = Any_Type then
4071          Restore_Env;
4072          return;
4073       end if;
4074
4075       --  Verify that it is a generic subprogram of the right kind, and that
4076       --  it does not lead to a circular instantiation.
4077
4078       if Ekind (Gen_Unit) /= E_Generic_Procedure
4079         and then Ekind (Gen_Unit) /= E_Generic_Function
4080       then
4081          Error_Msg_N ("expect generic subprogram in instantiation", Gen_Id);
4082
4083       elsif In_Open_Scopes (Gen_Unit) then
4084          Error_Msg_NE ("instantiation of & within itself", N, Gen_Unit);
4085
4086       elsif K = E_Procedure
4087         and then Ekind (Gen_Unit) /= E_Generic_Procedure
4088       then
4089          if Ekind (Gen_Unit) = E_Generic_Function then
4090             Error_Msg_N
4091               ("cannot instantiate generic function as procedure", Gen_Id);
4092          else
4093             Error_Msg_N
4094               ("expect name of generic procedure in instantiation", Gen_Id);
4095          end if;
4096
4097       elsif K = E_Function
4098         and then Ekind (Gen_Unit) /= E_Generic_Function
4099       then
4100          if Ekind (Gen_Unit) = E_Generic_Procedure then
4101             Error_Msg_N
4102               ("cannot instantiate generic procedure as function", Gen_Id);
4103          else
4104             Error_Msg_N
4105               ("expect name of generic function in instantiation", Gen_Id);
4106          end if;
4107
4108       else
4109          Set_Entity (Gen_Id, Gen_Unit);
4110          Set_Is_Instantiated (Gen_Unit);
4111
4112          if In_Extended_Main_Source_Unit (N) then
4113             Generate_Reference (Gen_Unit, N);
4114          end if;
4115
4116          --  If renaming, get original unit
4117
4118          if Present (Renamed_Object (Gen_Unit))
4119            and then (Ekind (Renamed_Object (Gen_Unit)) = E_Generic_Procedure
4120                        or else
4121                      Ekind (Renamed_Object (Gen_Unit)) = E_Generic_Function)
4122          then
4123             Gen_Unit := Renamed_Object (Gen_Unit);
4124             Set_Is_Instantiated (Gen_Unit);
4125             Generate_Reference  (Gen_Unit, N);
4126          end if;
4127
4128          if Contains_Instance_Of (Gen_Unit, Current_Scope, Gen_Id) then
4129             Error_Msg_Node_2 := Current_Scope;
4130             Error_Msg_NE
4131               ("circular Instantiation: & instantiated in &!", N, Gen_Unit);
4132             Circularity_Detected := True;
4133             return;
4134          end if;
4135
4136          Gen_Decl := Unit_Declaration_Node (Gen_Unit);
4137
4138          --  Initialize renamings map, for error checking
4139
4140          Generic_Renamings.Set_Last (0);
4141          Generic_Renamings_HTable.Reset;
4142
4143          Create_Instantiation_Source (N, Gen_Unit, False, S_Adjustment);
4144
4145          --  Copy original generic tree, to produce text for instantiation
4146
4147          Act_Tree :=
4148            Copy_Generic_Node
4149              (Original_Node (Gen_Decl), Empty, Instantiating => True);
4150
4151          --  Inherit overriding indicator from instance node
4152
4153          Act_Spec := Specification (Act_Tree);
4154          Set_Must_Override     (Act_Spec, Must_Override (N));
4155          Set_Must_Not_Override (Act_Spec, Must_Not_Override (N));
4156
4157          Renaming_List :=
4158            Analyze_Associations
4159              (N,
4160               Generic_Formal_Declarations (Act_Tree),
4161               Generic_Formal_Declarations (Gen_Decl));
4162
4163          --  The subprogram itself cannot contain a nested instance, so the
4164          --  current parent is left empty.
4165
4166          Set_Instance_Env (Gen_Unit, Empty);
4167
4168          --  Build the subprogram declaration, which does not appear in the
4169          --  generic template, and give it a sloc consistent with that of the
4170          --  template.
4171
4172          Set_Defining_Unit_Name (Act_Spec, Anon_Id);
4173          Set_Generic_Parent (Act_Spec, Gen_Unit);
4174          Act_Decl :=
4175            Make_Subprogram_Declaration (Sloc (Act_Spec),
4176              Specification => Act_Spec);
4177
4178          Set_Categorization_From_Pragmas (Act_Decl);
4179
4180          if Parent_Installed then
4181             Hide_Current_Scope;
4182          end if;
4183
4184          Append (Act_Decl, Renaming_List);
4185          Analyze_Instance_And_Renamings;
4186
4187          --  If the generic is marked Import (Intrinsic), then so is the
4188          --  instance. This indicates that there is no body to instantiate. If
4189          --  generic is marked inline, so it the instance, and the anonymous
4190          --  subprogram it renames. If inlined, or else if inlining is enabled
4191          --  for the compilation, we generate the instance body even if it is
4192          --  not within the main unit.
4193
4194          --  Any other  pragmas might also be inherited ???
4195
4196          if Is_Intrinsic_Subprogram (Gen_Unit) then
4197             Set_Is_Intrinsic_Subprogram (Anon_Id);
4198             Set_Is_Intrinsic_Subprogram (Act_Decl_Id);
4199
4200             if Chars (Gen_Unit) = Name_Unchecked_Conversion then
4201                Validate_Unchecked_Conversion (N, Act_Decl_Id);
4202             end if;
4203          end if;
4204
4205          Generate_Definition (Act_Decl_Id);
4206
4207          Set_Is_Inlined (Act_Decl_Id, Is_Inlined (Gen_Unit));
4208          Set_Is_Inlined (Anon_Id,     Is_Inlined (Gen_Unit));
4209
4210          if not Is_Intrinsic_Subprogram (Gen_Unit) then
4211             Check_Elab_Instantiation (N);
4212          end if;
4213
4214          if Is_Dispatching_Operation (Act_Decl_Id)
4215            and then Ada_Version >= Ada_05
4216          then
4217             declare
4218                Formal : Entity_Id;
4219
4220             begin
4221                Formal := First_Formal (Act_Decl_Id);
4222                while Present (Formal) loop
4223                   if Ekind (Etype (Formal)) = E_Anonymous_Access_Type
4224                     and then Is_Controlling_Formal (Formal)
4225                     and then not Can_Never_Be_Null (Formal)
4226                   then
4227                      Error_Msg_NE ("access parameter& is controlling,",
4228                        N, Formal);
4229                      Error_Msg_NE ("\corresponding parameter of & must be"
4230                        & " explicitly null-excluding", N, Gen_Id);
4231                   end if;
4232
4233                   Next_Formal (Formal);
4234                end loop;
4235             end;
4236          end if;
4237
4238          Check_Hidden_Child_Unit (N, Gen_Unit, Act_Decl_Id);
4239
4240          --  Subject to change, pending on if other pragmas are inherited ???
4241
4242          Validate_Categorization_Dependency (N, Act_Decl_Id);
4243
4244          if not Is_Intrinsic_Subprogram (Act_Decl_Id) then
4245             Inherit_Context (Gen_Decl, N);
4246
4247             Restore_Private_Views (Pack_Id, False);
4248
4249             --  If the context requires a full instantiation, mark node for
4250             --  subsequent construction of the body.
4251
4252             if Need_Subprogram_Instance_Body (N, Act_Decl_Id) then
4253
4254                Check_Forward_Instantiation (Gen_Decl);
4255
4256                --  The wrapper package is always delayed, because it does not
4257                --  constitute a freeze point, but to insure that the freeze
4258                --  node is placed properly, it is created directly when
4259                --  instantiating the body (otherwise the freeze node might
4260                --  appear to early for nested instantiations).
4261
4262             elsif Nkind (Parent (N)) = N_Compilation_Unit then
4263
4264                --  For ASIS purposes, indicate that the wrapper package has
4265                --  replaced the instantiation node.
4266
4267                Rewrite (N, Unit (Parent (N)));
4268                Set_Unit (Parent (N), N);
4269             end if;
4270
4271          elsif Nkind (Parent (N)) = N_Compilation_Unit then
4272
4273                --  Replace instance node for library-level instantiations of
4274                --  intrinsic subprograms, for ASIS use.
4275
4276                Rewrite (N, Unit (Parent (N)));
4277                Set_Unit (Parent (N), N);
4278          end if;
4279
4280          if Parent_Installed then
4281             Remove_Parent;
4282          end if;
4283
4284          Restore_Env;
4285          Env_Installed := False;
4286          Generic_Renamings.Set_Last (0);
4287          Generic_Renamings_HTable.Reset;
4288       end if;
4289
4290    exception
4291       when Instantiation_Error =>
4292          if Parent_Installed then
4293             Remove_Parent;
4294          end if;
4295
4296          if Env_Installed then
4297             Restore_Env;
4298          end if;
4299    end Analyze_Subprogram_Instantiation;
4300
4301    -------------------------
4302    -- Get_Associated_Node --
4303    -------------------------
4304
4305    function Get_Associated_Node (N : Node_Id) return Node_Id is
4306       Assoc : Node_Id;
4307
4308    begin
4309       Assoc := Associated_Node (N);
4310
4311       if Nkind (Assoc) /= Nkind (N) then
4312          return Assoc;
4313
4314       elsif Nkind_In (Assoc, N_Aggregate, N_Extension_Aggregate) then
4315          return Assoc;
4316
4317       else
4318          --  If the node is part of an inner generic, it may itself have been
4319          --  remapped into a further generic copy. Associated_Node is otherwise
4320          --  used for the entity of the node, and will be of a different node
4321          --  kind, or else N has been rewritten as a literal or function call.
4322
4323          while Present (Associated_Node (Assoc))
4324            and then Nkind (Associated_Node (Assoc)) = Nkind (Assoc)
4325          loop
4326             Assoc := Associated_Node (Assoc);
4327          end loop;
4328
4329          --  Follow and additional link in case the final node was rewritten.
4330          --  This can only happen with nested generic units.
4331
4332          if (Nkind (Assoc) = N_Identifier or else Nkind (Assoc) in N_Op)
4333            and then Present (Associated_Node (Assoc))
4334            and then (Nkind_In (Associated_Node (Assoc), N_Function_Call,
4335                                                         N_Explicit_Dereference,
4336                                                         N_Integer_Literal,
4337                                                         N_Real_Literal,
4338                                                         N_String_Literal))
4339          then
4340             Assoc := Associated_Node (Assoc);
4341          end if;
4342
4343          return Assoc;
4344       end if;
4345    end Get_Associated_Node;
4346
4347    -------------------------------------------
4348    -- Build_Instance_Compilation_Unit_Nodes --
4349    -------------------------------------------
4350
4351    procedure Build_Instance_Compilation_Unit_Nodes
4352      (N        : Node_Id;
4353       Act_Body : Node_Id;
4354       Act_Decl : Node_Id)
4355    is
4356       Decl_Cunit : Node_Id;
4357       Body_Cunit : Node_Id;
4358       Citem      : Node_Id;
4359       New_Main   : constant Entity_Id := Defining_Entity (Act_Decl);
4360       Old_Main   : constant Entity_Id := Cunit_Entity (Main_Unit);
4361
4362    begin
4363       --  A new compilation unit node is built for the instance declaration
4364
4365       Decl_Cunit :=
4366         Make_Compilation_Unit (Sloc (N),
4367           Context_Items  => Empty_List,
4368           Unit           => Act_Decl,
4369           Aux_Decls_Node =>
4370             Make_Compilation_Unit_Aux (Sloc (N)));
4371
4372       Set_Parent_Spec   (Act_Decl, Parent_Spec (N));
4373
4374       --  The new compilation unit is linked to its body, but both share the
4375       --  same file, so we do not set Body_Required on the new unit so as not
4376       --  to create a spurious dependency on a non-existent body in the ali.
4377       --  This simplifies Codepeer unit traversal.
4378
4379       --  We use the original instantiation compilation unit as the resulting
4380       --  compilation unit of the instance, since this is the main unit.
4381
4382       Rewrite (N, Act_Body);
4383       Body_Cunit := Parent (N);
4384
4385       --  The two compilation unit nodes are linked by the Library_Unit field
4386
4387       Set_Library_Unit  (Decl_Cunit, Body_Cunit);
4388       Set_Library_Unit  (Body_Cunit, Decl_Cunit);
4389
4390       --  Preserve the private nature of the package if needed
4391
4392       Set_Private_Present (Decl_Cunit, Private_Present (Body_Cunit));
4393
4394       --  If the instance is not the main unit, its context, categorization
4395       --  and elaboration entity are not relevant to the compilation.
4396
4397       if Body_Cunit /= Cunit (Main_Unit) then
4398          Make_Instance_Unit (Body_Cunit, In_Main => False);
4399          return;
4400       end if;
4401
4402       --  The context clause items on the instantiation, which are now attached
4403       --  to the body compilation unit (since the body overwrote the original
4404       --  instantiation node), semantically belong on the spec, so copy them
4405       --  there. It's harmless to leave them on the body as well. In fact one
4406       --  could argue that they belong in both places.
4407
4408       Citem := First (Context_Items (Body_Cunit));
4409       while Present (Citem) loop
4410          Append (New_Copy (Citem), Context_Items (Decl_Cunit));
4411          Next (Citem);
4412       end loop;
4413
4414       --  Propagate categorization flags on packages, so that they appear in
4415       --  the ali file for the spec of the unit.
4416
4417       if Ekind (New_Main) = E_Package then
4418          Set_Is_Pure           (Old_Main, Is_Pure (New_Main));
4419          Set_Is_Preelaborated  (Old_Main, Is_Preelaborated (New_Main));
4420          Set_Is_Remote_Types   (Old_Main, Is_Remote_Types (New_Main));
4421          Set_Is_Shared_Passive (Old_Main, Is_Shared_Passive (New_Main));
4422          Set_Is_Remote_Call_Interface
4423            (Old_Main, Is_Remote_Call_Interface (New_Main));
4424       end if;
4425
4426       --  Make entry in Units table, so that binder can generate call to
4427       --  elaboration procedure for body, if any.
4428
4429       Make_Instance_Unit (Body_Cunit, In_Main => True);
4430       Main_Unit_Entity := New_Main;
4431       Set_Cunit_Entity (Main_Unit, Main_Unit_Entity);
4432
4433       --  Build elaboration entity, since the instance may certainly generate
4434       --  elaboration code requiring a flag for protection.
4435
4436       Build_Elaboration_Entity (Decl_Cunit, New_Main);
4437    end Build_Instance_Compilation_Unit_Nodes;
4438
4439    -----------------------------
4440    -- Check_Access_Definition --
4441    -----------------------------
4442
4443    procedure Check_Access_Definition (N : Node_Id) is
4444    begin
4445       pragma Assert
4446         (Ada_Version >= Ada_05
4447            and then Present (Access_Definition (N)));
4448       null;
4449    end Check_Access_Definition;
4450
4451    -----------------------------------
4452    -- Check_Formal_Package_Instance --
4453    -----------------------------------
4454
4455    --  If the formal has specific parameters, they must match those of the
4456    --  actual. Both of them are instances, and the renaming declarations for
4457    --  their formal parameters appear in the same order in both. The analyzed
4458    --  formal has been analyzed in the context of the current instance.
4459
4460    procedure Check_Formal_Package_Instance
4461      (Formal_Pack : Entity_Id;
4462       Actual_Pack : Entity_Id)
4463    is
4464       E1 : Entity_Id := First_Entity (Actual_Pack);
4465       E2 : Entity_Id := First_Entity (Formal_Pack);
4466
4467       Expr1 : Node_Id;
4468       Expr2 : Node_Id;
4469
4470       procedure Check_Mismatch (B : Boolean);
4471       --  Common error routine for mismatch between the parameters of the
4472       --  actual instance and those of the formal package.
4473
4474       function Same_Instantiated_Constant (E1, E2 : Entity_Id) return Boolean;
4475       --  The formal may come from a nested formal package, and the actual may
4476       --  have been constant-folded. To determine whether the two denote the
4477       --  same entity we may have to traverse several definitions to recover
4478       --  the ultimate entity that they refer to.
4479
4480       function Same_Instantiated_Variable (E1, E2 : Entity_Id) return Boolean;
4481       --  Similarly, if the formal comes from a nested formal package, the
4482       --  actual may designate the formal through multiple renamings, which
4483       --  have to be followed to determine the original variable in question.
4484
4485       --------------------
4486       -- Check_Mismatch --
4487       --------------------
4488
4489       procedure Check_Mismatch (B : Boolean) is
4490          Kind : constant Node_Kind := Nkind (Parent (E2));
4491
4492       begin
4493          if Kind = N_Formal_Type_Declaration then
4494             return;
4495
4496          elsif Nkind_In (Kind, N_Formal_Object_Declaration,
4497                                N_Formal_Package_Declaration)
4498            or else Kind in N_Formal_Subprogram_Declaration
4499          then
4500             null;
4501
4502          elsif B then
4503             Error_Msg_NE
4504               ("actual for & in actual instance does not match formal",
4505                Parent (Actual_Pack), E1);
4506          end if;
4507       end Check_Mismatch;
4508
4509       --------------------------------
4510       -- Same_Instantiated_Constant --
4511       --------------------------------
4512
4513       function Same_Instantiated_Constant
4514         (E1, E2 : Entity_Id) return Boolean
4515       is
4516          Ent : Entity_Id;
4517
4518       begin
4519          Ent := E2;
4520          while Present (Ent) loop
4521             if E1 = Ent then
4522                return True;
4523
4524             elsif Ekind (Ent) /= E_Constant then
4525                return False;
4526
4527             elsif Is_Entity_Name (Constant_Value (Ent)) then
4528                if  Entity (Constant_Value (Ent)) = E1 then
4529                   return True;
4530                else
4531                   Ent := Entity (Constant_Value (Ent));
4532                end if;
4533
4534             --  The actual may be a constant that has been folded. Recover
4535             --  original name.
4536
4537             elsif Is_Entity_Name (Original_Node (Constant_Value (Ent))) then
4538                   Ent := Entity (Original_Node (Constant_Value (Ent)));
4539             else
4540                return False;
4541             end if;
4542          end loop;
4543
4544          return False;
4545       end Same_Instantiated_Constant;
4546
4547       --------------------------------
4548       -- Same_Instantiated_Variable --
4549       --------------------------------
4550
4551       function Same_Instantiated_Variable
4552         (E1, E2 : Entity_Id) return Boolean
4553       is
4554          function Original_Entity (E : Entity_Id) return Entity_Id;
4555          --  Follow chain of renamings to the ultimate ancestor
4556
4557          ---------------------
4558          -- Original_Entity --
4559          ---------------------
4560
4561          function Original_Entity (E : Entity_Id) return Entity_Id is
4562             Orig : Entity_Id;
4563
4564          begin
4565             Orig := E;
4566             while Nkind (Parent (Orig)) = N_Object_Renaming_Declaration
4567               and then Present (Renamed_Object (Orig))
4568               and then Is_Entity_Name (Renamed_Object (Orig))
4569             loop
4570                Orig := Entity (Renamed_Object (Orig));
4571             end loop;
4572
4573             return Orig;
4574          end Original_Entity;
4575
4576       --  Start of processing for Same_Instantiated_Variable
4577
4578       begin
4579          return Ekind (E1) = Ekind (E2)
4580            and then Original_Entity (E1) = Original_Entity (E2);
4581       end Same_Instantiated_Variable;
4582
4583    --  Start of processing for Check_Formal_Package_Instance
4584
4585    begin
4586       while Present (E1)
4587         and then Present (E2)
4588       loop
4589          exit when Ekind (E1) = E_Package
4590            and then Renamed_Entity (E1) = Renamed_Entity (Actual_Pack);
4591
4592          --  If the formal is the renaming of the formal package, this
4593          --  is the end of its formal part, which may occur before the
4594          --  end of the formal part in the actual in the presence of
4595          --  defaulted parameters in the formal package.
4596
4597          exit when Nkind (Parent (E2)) = N_Package_Renaming_Declaration
4598            and then Renamed_Entity (E2) = Scope (E2);
4599
4600          --  The analysis of the actual may generate additional internal
4601          --  entities. If the formal is defaulted, there is no corresponding
4602          --  analysis and the internal entities must be skipped, until we
4603          --  find corresponding entities again.
4604
4605          if Comes_From_Source (E2)
4606            and then not Comes_From_Source (E1)
4607            and then Chars (E1) /= Chars (E2)
4608          then
4609             while Present (E1)
4610               and then  Chars (E1) /= Chars (E2)
4611             loop
4612                Next_Entity (E1);
4613             end loop;
4614          end if;
4615
4616          if No (E1) then
4617             return;
4618
4619          --  If the formal entity comes from a formal declaration, it was
4620          --  defaulted in the formal package, and no check is needed on it.
4621
4622          elsif Nkind (Parent (E2)) =  N_Formal_Object_Declaration then
4623             goto Next_E;
4624
4625          elsif Is_Type (E1) then
4626
4627             --  Subtypes must statically match. E1, E2 are the local entities
4628             --  that are subtypes of the actuals. Itypes generated for other
4629             --  parameters need not be checked, the check will be performed
4630             --  on the parameters themselves.
4631
4632             --  If E2 is a formal type declaration, it is a defaulted parameter
4633             --  and needs no checking.
4634
4635             if not Is_Itype (E1)
4636               and then not Is_Itype (E2)
4637             then
4638                Check_Mismatch
4639                  (not Is_Type (E2)
4640                    or else Etype (E1) /= Etype (E2)
4641                    or else not Subtypes_Statically_Match (E1, E2));
4642             end if;
4643
4644          elsif Ekind (E1) = E_Constant then
4645
4646             --  IN parameters must denote the same static value, or the same
4647             --  constant, or the literal null.
4648
4649             Expr1 := Expression (Parent (E1));
4650
4651             if Ekind (E2) /= E_Constant then
4652                Check_Mismatch (True);
4653                goto Next_E;
4654             else
4655                Expr2 := Expression (Parent (E2));
4656             end if;
4657
4658             if Is_Static_Expression (Expr1) then
4659
4660                if not Is_Static_Expression (Expr2) then
4661                   Check_Mismatch (True);
4662
4663                elsif Is_Discrete_Type (Etype (E1)) then
4664                   declare
4665                      V1 : constant Uint := Expr_Value (Expr1);
4666                      V2 : constant Uint := Expr_Value (Expr2);
4667                   begin
4668                      Check_Mismatch (V1 /= V2);
4669                   end;
4670
4671                elsif Is_Real_Type (Etype (E1)) then
4672                   declare
4673                      V1 : constant Ureal := Expr_Value_R (Expr1);
4674                      V2 : constant Ureal := Expr_Value_R (Expr2);
4675                   begin
4676                      Check_Mismatch (V1 /= V2);
4677                   end;
4678
4679                elsif Is_String_Type (Etype (E1))
4680                  and then Nkind (Expr1) = N_String_Literal
4681                then
4682                   if Nkind (Expr2) /= N_String_Literal then
4683                      Check_Mismatch (True);
4684                   else
4685                      Check_Mismatch
4686                        (not String_Equal (Strval (Expr1), Strval (Expr2)));
4687                   end if;
4688                end if;
4689
4690             elsif Is_Entity_Name (Expr1) then
4691                if Is_Entity_Name (Expr2) then
4692                   if Entity (Expr1) = Entity (Expr2) then
4693                      null;
4694                   else
4695                      Check_Mismatch
4696                        (not Same_Instantiated_Constant
4697                          (Entity (Expr1), Entity (Expr2)));
4698                   end if;
4699                else
4700                   Check_Mismatch (True);
4701                end if;
4702
4703             elsif Is_Entity_Name (Original_Node (Expr1))
4704               and then Is_Entity_Name (Expr2)
4705             and then
4706               Same_Instantiated_Constant
4707                 (Entity (Original_Node (Expr1)), Entity (Expr2))
4708             then
4709                null;
4710
4711             elsif Nkind (Expr1) = N_Null then
4712                Check_Mismatch (Nkind (Expr1) /= N_Null);
4713
4714             else
4715                Check_Mismatch (True);
4716             end if;
4717
4718          elsif Ekind (E1) = E_Variable then
4719             Check_Mismatch (not Same_Instantiated_Variable (E1, E2));
4720
4721          elsif Ekind (E1) = E_Package then
4722             Check_Mismatch
4723               (Ekind (E1) /= Ekind (E2)
4724                 or else Renamed_Object (E1) /= Renamed_Object (E2));
4725
4726          elsif Is_Overloadable (E1) then
4727
4728             --  Verify that the actual subprograms match. Note that actuals
4729             --  that are attributes are rewritten as subprograms. If the
4730             --  subprogram in the formal package is defaulted, no check is
4731             --  needed. Note that this can only happen in Ada 2005 when the
4732             --  formal package can be partially parametrized.
4733
4734             if Nkind (Unit_Declaration_Node (E1)) =
4735                                            N_Subprogram_Renaming_Declaration
4736               and then From_Default (Unit_Declaration_Node (E1))
4737             then
4738                null;
4739
4740             else
4741                Check_Mismatch
4742                  (Ekind (E2) /= Ekind (E1) or else (Alias (E1)) /= Alias (E2));
4743             end if;
4744
4745          else
4746             raise Program_Error;
4747          end if;
4748
4749          <<Next_E>>
4750             Next_Entity (E1);
4751             Next_Entity (E2);
4752       end loop;
4753    end Check_Formal_Package_Instance;
4754
4755    ---------------------------
4756    -- Check_Formal_Packages --
4757    ---------------------------
4758
4759    procedure Check_Formal_Packages (P_Id : Entity_Id) is
4760       E        : Entity_Id;
4761       Formal_P : Entity_Id;
4762
4763    begin
4764       --  Iterate through the declarations in the instance, looking for package
4765       --  renaming declarations that denote instances of formal packages. Stop
4766       --  when we find the renaming of the current package itself. The
4767       --  declaration for a formal package without a box is followed by an
4768       --  internal entity that repeats the instantiation.
4769
4770       E := First_Entity (P_Id);
4771       while Present (E) loop
4772          if Ekind (E) = E_Package then
4773             if Renamed_Object (E) = P_Id then
4774                exit;
4775
4776             elsif Nkind (Parent (E)) /= N_Package_Renaming_Declaration then
4777                null;
4778
4779             elsif not Box_Present (Parent (Associated_Formal_Package (E))) then
4780                Formal_P := Next_Entity (E);
4781                Check_Formal_Package_Instance (Formal_P, E);
4782
4783                --  After checking, remove the internal validating package. It
4784                --  is only needed for semantic checks, and as it may contain
4785                --  generic formal declarations it should not reach gigi.
4786
4787                Remove (Unit_Declaration_Node (Formal_P));
4788             end if;
4789          end if;
4790
4791          Next_Entity (E);
4792       end loop;
4793    end Check_Formal_Packages;
4794
4795    ---------------------------------
4796    -- Check_Forward_Instantiation --
4797    ---------------------------------
4798
4799    procedure Check_Forward_Instantiation (Decl : Node_Id) is
4800       S        : Entity_Id;
4801       Gen_Comp : Entity_Id := Cunit_Entity (Get_Source_Unit (Decl));
4802
4803    begin
4804       --  The instantiation appears before the generic body if we are in the
4805       --  scope of the unit containing the generic, either in its spec or in
4806       --  the package body, and before the generic body.
4807
4808       if Ekind (Gen_Comp) = E_Package_Body then
4809          Gen_Comp := Spec_Entity (Gen_Comp);
4810       end if;
4811
4812       if In_Open_Scopes (Gen_Comp)
4813         and then No (Corresponding_Body (Decl))
4814       then
4815          S := Current_Scope;
4816
4817          while Present (S)
4818            and then not Is_Compilation_Unit (S)
4819            and then not Is_Child_Unit (S)
4820          loop
4821             if Ekind (S) = E_Package then
4822                Set_Has_Forward_Instantiation (S);
4823             end if;
4824
4825             S := Scope (S);
4826          end loop;
4827       end if;
4828    end Check_Forward_Instantiation;
4829
4830    ---------------------------
4831    -- Check_Generic_Actuals --
4832    ---------------------------
4833
4834    --  The visibility of the actuals may be different between the point of
4835    --  generic instantiation and the instantiation of the body.
4836
4837    procedure Check_Generic_Actuals
4838      (Instance      : Entity_Id;
4839       Is_Formal_Box : Boolean)
4840    is
4841       E      : Entity_Id;
4842       Astype : Entity_Id;
4843
4844       function Denotes_Previous_Actual (Typ : Entity_Id) return Boolean;
4845       --  For a formal that is an array type, the component type is often a
4846       --  previous formal in the same unit. The privacy status of the component
4847       --  type will have been examined earlier in the traversal of the
4848       --  corresponding actuals, and this status should not be modified for the
4849       --  array type itself.
4850       --
4851       --  To detect this case we have to rescan the list of formals, which
4852       --  is usually short enough to ignore the resulting inefficiency.
4853
4854       function Denotes_Previous_Actual (Typ : Entity_Id) return Boolean is
4855          Prev : Entity_Id;
4856       begin
4857          Prev := First_Entity (Instance);
4858          while Present (Prev) loop
4859             if Is_Type (Prev)
4860               and then Nkind (Parent (Prev)) = N_Subtype_Declaration
4861               and then Is_Entity_Name (Subtype_Indication (Parent (Prev)))
4862               and then Entity (Subtype_Indication (Parent (Prev))) = Typ
4863             then
4864                return True;
4865             elsif Prev = E then
4866                return False;
4867             else
4868                Next_Entity (Prev);
4869             end if;
4870          end loop;
4871          return False;
4872       end Denotes_Previous_Actual;
4873
4874    --  Start of processing for Check_Generic_Actuals
4875
4876    begin
4877       E := First_Entity (Instance);
4878       while Present (E) loop
4879          if Is_Type (E)
4880            and then Nkind (Parent (E)) = N_Subtype_Declaration
4881            and then Scope (Etype (E)) /= Instance
4882            and then Is_Entity_Name (Subtype_Indication (Parent (E)))
4883          then
4884             if Is_Array_Type (E)
4885               and then Denotes_Previous_Actual (Component_Type (E))
4886             then
4887                null;
4888             else
4889                Check_Private_View (Subtype_Indication (Parent (E)));
4890             end if;
4891             Set_Is_Generic_Actual_Type (E, True);
4892             Set_Is_Hidden (E, False);
4893             Set_Is_Potentially_Use_Visible (E,
4894               In_Use (Instance));
4895
4896             --  We constructed the generic actual type as a subtype of the
4897             --  supplied type. This means that it normally would not inherit
4898             --  subtype specific attributes of the actual, which is wrong for
4899             --  the generic case.
4900
4901             Astype := Ancestor_Subtype (E);
4902
4903             if No (Astype) then
4904
4905                --  This can happen when E is an itype that is the full view of
4906                --  a private type completed, e.g. with a constrained array. In
4907                --  that case, use the first subtype, which will carry size
4908                --  information. The base type itself is unconstrained and will
4909                --  not carry it.
4910
4911                Astype := First_Subtype (E);
4912             end if;
4913
4914             Set_Size_Info      (E,                (Astype));
4915             Set_RM_Size        (E, RM_Size        (Astype));
4916             Set_First_Rep_Item (E, First_Rep_Item (Astype));
4917
4918             if Is_Discrete_Or_Fixed_Point_Type (E) then
4919                Set_RM_Size (E, RM_Size (Astype));
4920
4921             --  In  nested instances, the base type of an access actual
4922             --  may itself be private, and need to be exchanged.
4923
4924             elsif Is_Access_Type (E)
4925               and then Is_Private_Type (Etype (E))
4926             then
4927                Check_Private_View
4928                  (New_Occurrence_Of (Etype (E), Sloc (Instance)));
4929             end if;
4930
4931          elsif Ekind (E) = E_Package then
4932
4933             --  If this is the renaming for the current instance, we're done.
4934             --  Otherwise it is a formal package. If the corresponding formal
4935             --  was declared with a box, the (instantiations of the) generic
4936             --  formal part are also visible. Otherwise, ignore the entity
4937             --  created to validate the actuals.
4938
4939             if Renamed_Object (E) = Instance then
4940                exit;
4941
4942             elsif Nkind (Parent (E)) /= N_Package_Renaming_Declaration then
4943                null;
4944
4945             --  The visibility of a formal of an enclosing generic is already
4946             --  correct.
4947
4948             elsif Denotes_Formal_Package (E) then
4949                null;
4950
4951             elsif Present (Associated_Formal_Package (E))
4952               and then not Is_Generic_Formal (E)
4953             then
4954                if Box_Present (Parent (Associated_Formal_Package (E))) then
4955                   Check_Generic_Actuals (Renamed_Object (E), True);
4956
4957                else
4958                   Check_Generic_Actuals (Renamed_Object (E), False);
4959                end if;
4960
4961                Set_Is_Hidden (E, False);
4962             end if;
4963
4964          --  If this is a subprogram instance (in a wrapper package) the
4965          --  actual is fully visible.
4966
4967          elsif Is_Wrapper_Package (Instance) then
4968             Set_Is_Hidden (E, False);
4969
4970          --  If the formal package is declared with a box, or if the formal
4971          --  parameter is defaulted, it is visible in the body.
4972
4973          elsif Is_Formal_Box
4974            or else Is_Visible_Formal (E)
4975          then
4976             Set_Is_Hidden (E, False);
4977          end if;
4978
4979          Next_Entity (E);
4980       end loop;
4981    end Check_Generic_Actuals;
4982
4983    ------------------------------
4984    -- Check_Generic_Child_Unit --
4985    ------------------------------
4986
4987    procedure Check_Generic_Child_Unit
4988      (Gen_Id           : Node_Id;
4989       Parent_Installed : in out Boolean)
4990    is
4991       Loc      : constant Source_Ptr := Sloc (Gen_Id);
4992       Gen_Par  : Entity_Id := Empty;
4993       E        : Entity_Id;
4994       Inst_Par : Entity_Id;
4995       S        : Node_Id;
4996
4997       function Find_Generic_Child
4998         (Scop : Entity_Id;
4999          Id   : Node_Id) return Entity_Id;
5000       --  Search generic parent for possible child unit with the given name
5001
5002       function In_Enclosing_Instance return Boolean;
5003       --  Within an instance of the parent, the child unit may be denoted
5004       --  by a simple name, or an abbreviated expanded name. Examine enclosing
5005       --  scopes to locate a possible parent instantiation.
5006
5007       ------------------------
5008       -- Find_Generic_Child --
5009       ------------------------
5010
5011       function Find_Generic_Child
5012         (Scop : Entity_Id;
5013          Id   : Node_Id) return Entity_Id
5014       is
5015          E : Entity_Id;
5016
5017       begin
5018          --  If entity of name is already set, instance has already been
5019          --  resolved, e.g. in an enclosing instantiation.
5020
5021          if Present (Entity (Id)) then
5022             if Scope (Entity (Id)) = Scop then
5023                return Entity (Id);
5024             else
5025                return Empty;
5026             end if;
5027
5028          else
5029             E := First_Entity (Scop);
5030             while Present (E) loop
5031                if Chars (E) = Chars (Id)
5032                  and then Is_Child_Unit (E)
5033                then
5034                   if Is_Child_Unit (E)
5035                     and then not Is_Visible_Child_Unit (E)
5036                   then
5037                      Error_Msg_NE
5038                        ("generic child unit& is not visible", Gen_Id, E);
5039                   end if;
5040
5041                   Set_Entity (Id, E);
5042                   return E;
5043                end if;
5044
5045                Next_Entity (E);
5046             end loop;
5047
5048             return Empty;
5049          end if;
5050       end Find_Generic_Child;
5051
5052       ---------------------------
5053       -- In_Enclosing_Instance --
5054       ---------------------------
5055
5056       function In_Enclosing_Instance return Boolean is
5057          Enclosing_Instance : Node_Id;
5058          Instance_Decl      : Node_Id;
5059
5060       begin
5061          --  We do not inline any call that contains instantiations, except
5062          --  for instantiations of Unchecked_Conversion, so if we are within
5063          --  an inlined body the current instance does not require parents.
5064
5065          if In_Inlined_Body then
5066             pragma Assert (Chars (Gen_Id) = Name_Unchecked_Conversion);
5067             return False;
5068          end if;
5069
5070          --  Loop to check enclosing scopes
5071
5072          Enclosing_Instance := Current_Scope;
5073          while Present (Enclosing_Instance) loop
5074             Instance_Decl := Unit_Declaration_Node (Enclosing_Instance);
5075
5076             if Ekind (Enclosing_Instance) = E_Package
5077               and then Is_Generic_Instance (Enclosing_Instance)
5078               and then Present
5079                 (Generic_Parent (Specification (Instance_Decl)))
5080             then
5081                --  Check whether the generic we are looking for is a child of
5082                --  this instance.
5083
5084                E := Find_Generic_Child
5085                       (Generic_Parent (Specification (Instance_Decl)), Gen_Id);
5086                exit when Present (E);
5087
5088             else
5089                E := Empty;
5090             end if;
5091
5092             Enclosing_Instance := Scope (Enclosing_Instance);
5093          end loop;
5094
5095          if No (E) then
5096
5097             --  Not a child unit
5098
5099             Analyze (Gen_Id);
5100             return False;
5101
5102          else
5103             Rewrite (Gen_Id,
5104               Make_Expanded_Name (Loc,
5105                 Chars         => Chars (E),
5106                 Prefix        => New_Occurrence_Of (Enclosing_Instance, Loc),
5107                 Selector_Name => New_Occurrence_Of (E, Loc)));
5108
5109             Set_Entity (Gen_Id, E);
5110             Set_Etype  (Gen_Id, Etype (E));
5111             Parent_Installed := False;      -- Already in scope.
5112             return True;
5113          end if;
5114       end In_Enclosing_Instance;
5115
5116    --  Start of processing for Check_Generic_Child_Unit
5117
5118    begin
5119       --  If the name of the generic is given by a selected component, it may
5120       --  be the name of a generic child unit, and the prefix is the name of an
5121       --  instance of the parent, in which case the child unit must be visible.
5122       --  If this instance is not in scope, it must be placed there and removed
5123       --  after instantiation, because what is being instantiated is not the
5124       --  original child, but the corresponding child present in the instance
5125       --  of the parent.
5126
5127       --  If the child is instantiated within the parent, it can be given by
5128       --  a simple name. In this case the instance is already in scope, but
5129       --  the child generic must be recovered from the generic parent as well.
5130
5131       if Nkind (Gen_Id) = N_Selected_Component then
5132          S := Selector_Name (Gen_Id);
5133          Analyze (Prefix (Gen_Id));
5134          Inst_Par := Entity (Prefix (Gen_Id));
5135
5136          if Ekind (Inst_Par) = E_Package
5137            and then Present (Renamed_Object (Inst_Par))
5138          then
5139             Inst_Par := Renamed_Object (Inst_Par);
5140          end if;
5141
5142          if Ekind (Inst_Par) = E_Package then
5143             if Nkind (Parent (Inst_Par)) = N_Package_Specification then
5144                Gen_Par := Generic_Parent (Parent (Inst_Par));
5145
5146             elsif Nkind (Parent (Inst_Par)) = N_Defining_Program_Unit_Name
5147               and then
5148                 Nkind (Parent (Parent (Inst_Par))) = N_Package_Specification
5149             then
5150                Gen_Par := Generic_Parent (Parent (Parent (Inst_Par)));
5151             end if;
5152
5153          elsif Ekind (Inst_Par) = E_Generic_Package
5154            and then Nkind (Parent (Gen_Id)) = N_Formal_Package_Declaration
5155          then
5156             --  A formal package may be a real child package, and not the
5157             --  implicit instance within a parent. In this case the child is
5158             --  not visible and has to be retrieved explicitly as well.
5159
5160             Gen_Par := Inst_Par;
5161          end if;
5162
5163          if Present (Gen_Par) then
5164
5165             --  The prefix denotes an instantiation. The entity itself may be a
5166             --  nested generic, or a child unit.
5167
5168             E := Find_Generic_Child (Gen_Par, S);
5169
5170             if Present (E) then
5171                Change_Selected_Component_To_Expanded_Name (Gen_Id);
5172                Set_Entity (Gen_Id, E);
5173                Set_Etype (Gen_Id, Etype (E));
5174                Set_Entity (S, E);
5175                Set_Etype (S, Etype (E));
5176
5177                --  Indicate that this is a reference to the parent
5178
5179                if In_Extended_Main_Source_Unit (Gen_Id) then
5180                   Set_Is_Instantiated (Inst_Par);
5181                end if;
5182
5183                --  A common mistake is to replicate the naming scheme of a
5184                --  hierarchy by instantiating a generic child directly, rather
5185                --  than the implicit child in a parent instance:
5186
5187                --  generic .. package Gpar is ..
5188                --  generic .. package Gpar.Child is ..
5189                --  package Par is new Gpar ();
5190
5191                --  with Gpar.Child;
5192                --  package Par.Child is new Gpar.Child ();
5193                --                           rather than Par.Child
5194
5195                --  In this case the instantiation is within Par, which is an
5196                --  instance, but Gpar does not denote Par because we are not IN
5197                --  the instance of Gpar, so this is illegal. The test below
5198                --  recognizes this particular case.
5199
5200                if Is_Child_Unit (E)
5201                  and then not Comes_From_Source (Entity (Prefix (Gen_Id)))
5202                  and then (not In_Instance
5203                              or else Nkind (Parent (Parent (Gen_Id))) =
5204                                                          N_Compilation_Unit)
5205                then
5206                   Error_Msg_N
5207                     ("prefix of generic child unit must be instance of parent",
5208                       Gen_Id);
5209                end if;
5210
5211                if not In_Open_Scopes (Inst_Par)
5212                  and then Nkind (Parent (Gen_Id)) not in
5213                                            N_Generic_Renaming_Declaration
5214                then
5215                   Install_Parent (Inst_Par);
5216                   Parent_Installed := True;
5217
5218                elsif In_Open_Scopes (Inst_Par) then
5219
5220                   --  If the parent is already installed verify that the
5221                   --  actuals for its formal packages declared with a box
5222                   --  are already installed. This is necessary when the
5223                   --  child instance is a child of the parent instance.
5224                   --  In this case the parent is placed on the scope stack
5225                   --  but the formal packages are not made visible.
5226
5227                   Install_Formal_Packages (Inst_Par);
5228                end if;
5229
5230             else
5231                --  If the generic parent does not contain an entity that
5232                --  corresponds to the selector, the instance doesn't either.
5233                --  Analyzing the node will yield the appropriate error message.
5234                --  If the entity is not a child unit, then it is an inner
5235                --  generic in the parent.
5236
5237                Analyze (Gen_Id);
5238             end if;
5239
5240          else
5241             Analyze (Gen_Id);
5242
5243             if Is_Child_Unit (Entity (Gen_Id))
5244               and then
5245                 Nkind (Parent (Gen_Id)) not in N_Generic_Renaming_Declaration
5246               and then not In_Open_Scopes (Inst_Par)
5247             then
5248                Install_Parent (Inst_Par);
5249                Parent_Installed := True;
5250             end if;
5251          end if;
5252
5253       elsif Nkind (Gen_Id) = N_Expanded_Name then
5254
5255          --  Entity already present, analyze prefix, whose meaning may be
5256          --  an instance in the current context. If it is an instance of
5257          --  a relative within another, the proper parent may still have
5258          --  to be installed, if they are not of the same generation.
5259
5260          Analyze (Prefix (Gen_Id));
5261
5262          --  In the unlikely case that a local declaration hides the name
5263          --  of the parent package, locate it on the homonym chain. If the
5264          --  context is an instance of the parent, the renaming entity is
5265          --  flagged as such.
5266
5267          Inst_Par := Entity (Prefix (Gen_Id));
5268          while Present (Inst_Par)
5269            and then not Is_Package_Or_Generic_Package (Inst_Par)
5270          loop
5271             Inst_Par := Homonym (Inst_Par);
5272          end loop;
5273
5274          pragma Assert (Present (Inst_Par));
5275          Set_Entity (Prefix (Gen_Id), Inst_Par);
5276
5277          if In_Enclosing_Instance then
5278             null;
5279
5280          elsif Present (Entity (Gen_Id))
5281            and then Is_Child_Unit (Entity (Gen_Id))
5282            and then not In_Open_Scopes (Inst_Par)
5283          then
5284             Install_Parent (Inst_Par);
5285             Parent_Installed := True;
5286          end if;
5287
5288       elsif In_Enclosing_Instance then
5289
5290          --  The child unit is found in some enclosing scope
5291
5292          null;
5293
5294       else
5295          Analyze (Gen_Id);
5296
5297          --  If this is the renaming of the implicit child in a parent
5298          --  instance, recover the parent name and install it.
5299
5300          if Is_Entity_Name (Gen_Id) then
5301             E := Entity (Gen_Id);
5302
5303             if Is_Generic_Unit (E)
5304               and then Nkind (Parent (E)) in N_Generic_Renaming_Declaration
5305               and then Is_Child_Unit (Renamed_Object (E))
5306               and then Is_Generic_Unit (Scope (Renamed_Object (E)))
5307               and then Nkind (Name (Parent (E))) = N_Expanded_Name
5308             then
5309                Rewrite (Gen_Id,
5310                  New_Copy_Tree (Name (Parent (E))));
5311                Inst_Par := Entity (Prefix (Gen_Id));
5312
5313                if not In_Open_Scopes (Inst_Par) then
5314                   Install_Parent (Inst_Par);
5315                   Parent_Installed := True;
5316                end if;
5317
5318             --  If it is a child unit of a non-generic parent, it may be
5319             --  use-visible and given by a direct name. Install parent as
5320             --  for other cases.
5321
5322             elsif Is_Generic_Unit (E)
5323               and then Is_Child_Unit (E)
5324               and then
5325                 Nkind (Parent (Gen_Id)) not in N_Generic_Renaming_Declaration
5326               and then not Is_Generic_Unit (Scope (E))
5327             then
5328                if not In_Open_Scopes (Scope (E)) then
5329                   Install_Parent (Scope (E));
5330                   Parent_Installed := True;
5331                end if;
5332             end if;
5333          end if;
5334       end if;
5335    end Check_Generic_Child_Unit;
5336
5337    -----------------------------
5338    -- Check_Hidden_Child_Unit --
5339    -----------------------------
5340
5341    procedure Check_Hidden_Child_Unit
5342      (N           : Node_Id;
5343       Gen_Unit    : Entity_Id;
5344       Act_Decl_Id : Entity_Id)
5345    is
5346       Gen_Id : constant Node_Id := Name (N);
5347
5348    begin
5349       if Is_Child_Unit (Gen_Unit)
5350         and then Is_Child_Unit (Act_Decl_Id)
5351         and then Nkind (Gen_Id) = N_Expanded_Name
5352         and then Entity (Prefix (Gen_Id)) = Scope (Act_Decl_Id)
5353         and then Chars (Gen_Unit) = Chars (Act_Decl_Id)
5354       then
5355          Error_Msg_Node_2 := Scope (Act_Decl_Id);
5356          Error_Msg_NE
5357            ("generic unit & is implicitly declared in &",
5358              Defining_Unit_Name (N), Gen_Unit);
5359          Error_Msg_N ("\instance must have different name",
5360            Defining_Unit_Name (N));
5361       end if;
5362    end Check_Hidden_Child_Unit;
5363
5364    ------------------------
5365    -- Check_Private_View --
5366    ------------------------
5367
5368    procedure Check_Private_View (N : Node_Id) is
5369       T : constant Entity_Id := Etype (N);
5370       BT : Entity_Id;
5371
5372    begin
5373       --  Exchange views if the type was not private in the generic but is
5374       --  private at the point of instantiation. Do not exchange views if
5375       --  the scope of the type is in scope. This can happen if both generic
5376       --  and instance are sibling units, or if type is defined in a parent.
5377       --  In this case the visibility of the type will be correct for all
5378       --  semantic checks.
5379
5380       if Present (T) then
5381          BT := Base_Type (T);
5382
5383          if Is_Private_Type (T)
5384            and then not Has_Private_View (N)
5385            and then Present (Full_View (T))
5386            and then not In_Open_Scopes (Scope (T))
5387          then
5388             --  In the generic, the full type was visible. Save the private
5389             --  entity, for subsequent exchange.
5390
5391             Switch_View (T);
5392
5393          elsif Has_Private_View (N)
5394            and then not Is_Private_Type (T)
5395            and then not Has_Been_Exchanged (T)
5396            and then Etype (Get_Associated_Node (N)) /= T
5397          then
5398             --  Only the private declaration was visible in the generic. If
5399             --  the type appears in a subtype declaration, the subtype in the
5400             --  instance must have a view compatible with that of its parent,
5401             --  which must be exchanged (see corresponding code in Restore_
5402             --  Private_Views). Otherwise, if the type is defined in a parent
5403             --  unit, leave full visibility within instance, which is safe.
5404
5405             if In_Open_Scopes (Scope (Base_Type (T)))
5406               and then not Is_Private_Type (Base_Type (T))
5407               and then Comes_From_Source (Base_Type (T))
5408             then
5409                null;
5410
5411             elsif Nkind (Parent (N)) = N_Subtype_Declaration
5412               or else not In_Private_Part (Scope (Base_Type (T)))
5413             then
5414                Prepend_Elmt (T, Exchanged_Views);
5415                Exchange_Declarations (Etype (Get_Associated_Node (N)));
5416             end if;
5417
5418          --  For composite types with inconsistent representation exchange
5419          --  component types accordingly.
5420
5421          elsif Is_Access_Type (T)
5422            and then Is_Private_Type (Designated_Type (T))
5423            and then not Has_Private_View (N)
5424            and then Present (Full_View (Designated_Type (T)))
5425          then
5426             Switch_View (Designated_Type (T));
5427
5428          elsif Is_Array_Type (T) then
5429             if Is_Private_Type (Component_Type (T))
5430               and then not Has_Private_View (N)
5431               and then Present (Full_View (Component_Type (T)))
5432             then
5433                Switch_View (Component_Type (T));
5434             end if;
5435
5436             --  The normal exchange mechanism relies on the setting of a
5437             --  flag on the reference in the generic. However, an additional
5438             --  mechanism is needed for types that are not explicitly mentioned
5439             --  in the generic, but may be needed in expanded code in the
5440             --  instance. This includes component types of arrays and
5441             --  designated types of access types. This processing must also
5442             --  include the index types of arrays which we take care of here.
5443
5444             declare
5445                Indx : Node_Id;
5446                Typ  : Entity_Id;
5447
5448             begin
5449                Indx := First_Index (T);
5450                Typ  := Base_Type (Etype (Indx));
5451                while Present (Indx) loop
5452                   if Is_Private_Type (Typ)
5453                     and then Present (Full_View (Typ))
5454                   then
5455                      Switch_View (Typ);
5456                   end if;
5457
5458                   Next_Index (Indx);
5459                end loop;
5460             end;
5461
5462          elsif Is_Private_Type (T)
5463            and then Present (Full_View (T))
5464            and then Is_Array_Type (Full_View (T))
5465            and then Is_Private_Type (Component_Type (Full_View (T)))
5466          then
5467             Switch_View (T);
5468
5469          --  Finally, a non-private subtype may have a private base type, which
5470          --  must be exchanged for consistency. This can happen when a package
5471          --  body is instantiated, when the scope stack is empty but in fact
5472          --  the subtype and the base type are declared in an enclosing scope.
5473
5474          --  Note that in this case we introduce an inconsistency in the view
5475          --  set, because we switch the base type BT, but there could be some
5476          --  private dependent subtypes of BT which remain unswitched. Such
5477          --  subtypes might need to be switched at a later point (see specific
5478          --  provision for that case in Switch_View).
5479
5480          elsif not Is_Private_Type (T)
5481            and then not Has_Private_View (N)
5482            and then Is_Private_Type (BT)
5483            and then Present (Full_View (BT))
5484            and then not Is_Generic_Type (BT)
5485            and then not In_Open_Scopes (BT)
5486          then
5487             Prepend_Elmt (Full_View (BT), Exchanged_Views);
5488             Exchange_Declarations (BT);
5489          end if;
5490       end if;
5491    end Check_Private_View;
5492
5493    --------------------------
5494    -- Contains_Instance_Of --
5495    --------------------------
5496
5497    function Contains_Instance_Of
5498      (Inner : Entity_Id;
5499       Outer : Entity_Id;
5500       N     : Node_Id) return Boolean
5501    is
5502       Elmt : Elmt_Id;
5503       Scop : Entity_Id;
5504
5505    begin
5506       Scop := Outer;
5507
5508       --  Verify that there are no circular instantiations. We check whether
5509       --  the unit contains an instance of the current scope or some enclosing
5510       --  scope (in case one of the instances appears in a subunit). Longer
5511       --  circularities involving subunits might seem too pathological to
5512       --  consider, but they were not too pathological for the authors of
5513       --  DEC bc30vsq, so we loop over all enclosing scopes, and mark all
5514       --  enclosing generic scopes as containing an instance.
5515
5516       loop
5517          --  Within a generic subprogram body, the scope is not generic, to
5518          --  allow for recursive subprograms. Use the declaration to determine
5519          --  whether this is a generic unit.
5520
5521          if Ekind (Scop) = E_Generic_Package
5522            or else (Is_Subprogram (Scop)
5523                       and then Nkind (Unit_Declaration_Node (Scop)) =
5524                                         N_Generic_Subprogram_Declaration)
5525          then
5526             Elmt := First_Elmt (Inner_Instances (Inner));
5527
5528             while Present (Elmt) loop
5529                if Node (Elmt) = Scop then
5530                   Error_Msg_Node_2 := Inner;
5531                   Error_Msg_NE
5532                     ("circular Instantiation: & instantiated within &!",
5533                        N, Scop);
5534                   return True;
5535
5536                elsif Node (Elmt) = Inner then
5537                   return True;
5538
5539                elsif Contains_Instance_Of (Node (Elmt), Scop, N) then
5540                   Error_Msg_Node_2 := Inner;
5541                   Error_Msg_NE
5542                     ("circular Instantiation: & instantiated within &!",
5543                       N, Node (Elmt));
5544                   return True;
5545                end if;
5546
5547                Next_Elmt (Elmt);
5548             end loop;
5549
5550             --  Indicate that Inner is being instantiated within Scop
5551
5552             Append_Elmt (Inner, Inner_Instances (Scop));
5553          end if;
5554
5555          if Scop = Standard_Standard then
5556             exit;
5557          else
5558             Scop := Scope (Scop);
5559          end if;
5560       end loop;
5561
5562       return False;
5563    end Contains_Instance_Of;
5564
5565    -----------------------
5566    -- Copy_Generic_Node --
5567    -----------------------
5568
5569    function Copy_Generic_Node
5570      (N             : Node_Id;
5571       Parent_Id     : Node_Id;
5572       Instantiating : Boolean) return Node_Id
5573    is
5574       Ent   : Entity_Id;
5575       New_N : Node_Id;
5576
5577       function Copy_Generic_Descendant (D : Union_Id) return Union_Id;
5578       --  Check the given value of one of the Fields referenced by the
5579       --  current node to determine whether to copy it recursively. The
5580       --  field may hold a Node_Id, a List_Id, or an Elist_Id, or a plain
5581       --  value (Sloc, Uint, Char) in which case it need not be copied.
5582
5583       procedure Copy_Descendants;
5584       --  Common utility for various nodes
5585
5586       function Copy_Generic_Elist (E : Elist_Id) return Elist_Id;
5587       --  Make copy of element list
5588
5589       function Copy_Generic_List
5590         (L         : List_Id;
5591          Parent_Id : Node_Id) return List_Id;
5592       --  Apply Copy_Node recursively to the members of a node list
5593
5594       function In_Defining_Unit_Name (Nam : Node_Id) return Boolean;
5595       --  True if an identifier is part of the defining program unit name
5596       --  of a child unit. The entity of such an identifier must be kept
5597       --  (for ASIS use) even though as the name of an enclosing generic
5598       --   it would otherwise not be preserved in the generic tree.
5599
5600       ----------------------
5601       -- Copy_Descendants --
5602       ----------------------
5603
5604       procedure Copy_Descendants is
5605
5606          use Atree.Unchecked_Access;
5607          --  This code section is part of the implementation of an untyped
5608          --  tree traversal, so it needs direct access to node fields.
5609
5610       begin
5611          Set_Field1 (New_N, Copy_Generic_Descendant (Field1 (N)));
5612          Set_Field2 (New_N, Copy_Generic_Descendant (Field2 (N)));
5613          Set_Field3 (New_N, Copy_Generic_Descendant (Field3 (N)));
5614          Set_Field4 (New_N, Copy_Generic_Descendant (Field4 (N)));
5615          Set_Field5 (New_N, Copy_Generic_Descendant (Field5 (N)));
5616       end Copy_Descendants;
5617
5618       -----------------------------
5619       -- Copy_Generic_Descendant --
5620       -----------------------------
5621
5622       function Copy_Generic_Descendant (D : Union_Id) return Union_Id is
5623       begin
5624          if D = Union_Id (Empty) then
5625             return D;
5626
5627          elsif D in Node_Range then
5628             return Union_Id
5629               (Copy_Generic_Node (Node_Id (D), New_N, Instantiating));
5630
5631          elsif D in List_Range then
5632             return Union_Id (Copy_Generic_List (List_Id (D), New_N));
5633
5634          elsif D in Elist_Range then
5635             return Union_Id (Copy_Generic_Elist (Elist_Id (D)));
5636
5637          --  Nothing else is copyable (e.g. Uint values), return as is
5638
5639          else
5640             return D;
5641          end if;
5642       end Copy_Generic_Descendant;
5643
5644       ------------------------
5645       -- Copy_Generic_Elist --
5646       ------------------------
5647
5648       function Copy_Generic_Elist (E : Elist_Id) return Elist_Id is
5649          M : Elmt_Id;
5650          L : Elist_Id;
5651
5652       begin
5653          if Present (E) then
5654             L := New_Elmt_List;
5655             M := First_Elmt (E);
5656             while Present (M) loop
5657                Append_Elmt
5658                  (Copy_Generic_Node (Node (M), Empty, Instantiating), L);
5659                Next_Elmt (M);
5660             end loop;
5661
5662             return L;
5663
5664          else
5665             return No_Elist;
5666          end if;
5667       end Copy_Generic_Elist;
5668
5669       -----------------------
5670       -- Copy_Generic_List --
5671       -----------------------
5672
5673       function Copy_Generic_List
5674         (L         : List_Id;
5675          Parent_Id : Node_Id) return List_Id
5676       is
5677          N     : Node_Id;
5678          New_L : List_Id;
5679
5680       begin
5681          if Present (L) then
5682             New_L := New_List;
5683             Set_Parent (New_L, Parent_Id);
5684
5685             N := First (L);
5686             while Present (N) loop
5687                Append (Copy_Generic_Node (N, Empty, Instantiating), New_L);
5688                Next (N);
5689             end loop;
5690
5691             return New_L;
5692
5693          else
5694             return No_List;
5695          end if;
5696       end Copy_Generic_List;
5697
5698       ---------------------------
5699       -- In_Defining_Unit_Name --
5700       ---------------------------
5701
5702       function In_Defining_Unit_Name (Nam : Node_Id) return Boolean is
5703       begin
5704          return Present (Parent (Nam))
5705            and then (Nkind (Parent (Nam)) = N_Defining_Program_Unit_Name
5706                       or else
5707                         (Nkind (Parent (Nam)) = N_Expanded_Name
5708                           and then In_Defining_Unit_Name (Parent (Nam))));
5709       end In_Defining_Unit_Name;
5710
5711    --  Start of processing for Copy_Generic_Node
5712
5713    begin
5714       if N = Empty then
5715          return N;
5716       end if;
5717
5718       New_N := New_Copy (N);
5719
5720       if Instantiating then
5721          Adjust_Instantiation_Sloc (New_N, S_Adjustment);
5722       end if;
5723
5724       if not Is_List_Member (N) then
5725          Set_Parent (New_N, Parent_Id);
5726       end if;
5727
5728       --  If defining identifier, then all fields have been copied already
5729
5730       if Nkind (New_N) in N_Entity then
5731          null;
5732
5733       --  Special casing for identifiers and other entity names and operators
5734
5735       elsif Nkind_In (New_N, N_Identifier,
5736                              N_Character_Literal,
5737                              N_Expanded_Name,
5738                              N_Operator_Symbol)
5739         or else Nkind (New_N) in N_Op
5740       then
5741          if not Instantiating then
5742
5743             --  Link both nodes in order to assign subsequently the entity of
5744             --  the copy to the original node, in case this is a global
5745             --  reference.
5746
5747             Set_Associated_Node (N, New_N);
5748
5749             --  If we are within an instantiation, this is a nested generic
5750             --  that has already been analyzed at the point of definition. We
5751             --  must preserve references that were global to the enclosing
5752             --  parent at that point. Other occurrences, whether global or
5753             --  local to the current generic, must be resolved anew, so we
5754             --  reset the entity in the generic copy. A global reference has a
5755             --  smaller depth than the parent, or else the same depth in case
5756             --  both are distinct compilation units.
5757             --  A child unit is implicitly declared within the enclosing parent
5758             --  but is in fact global to it, and must be preserved.
5759
5760             --  It is also possible for Current_Instantiated_Parent to be
5761             --  defined, and for this not to be a nested generic, namely if the
5762             --  unit is loaded through Rtsfind. In that case, the entity of
5763             --  New_N is only a link to the associated node, and not a defining
5764             --  occurrence.
5765
5766             --  The entities for parent units in the defining_program_unit of a
5767             --  generic child unit are established when the context of the unit
5768             --  is first analyzed, before the generic copy is made. They are
5769             --  preserved in the copy for use in ASIS queries.
5770
5771             Ent := Entity (New_N);
5772
5773             if No (Current_Instantiated_Parent.Gen_Id) then
5774                if No (Ent)
5775                  or else Nkind (Ent) /= N_Defining_Identifier
5776                  or else not In_Defining_Unit_Name (N)
5777                then
5778                   Set_Associated_Node (New_N, Empty);
5779                end if;
5780
5781             elsif No (Ent)
5782               or else
5783                 not Nkind_In (Ent, N_Defining_Identifier,
5784                                    N_Defining_Character_Literal,
5785                                    N_Defining_Operator_Symbol)
5786               or else No (Scope (Ent))
5787               or else
5788                 (Scope (Ent) = Current_Instantiated_Parent.Gen_Id
5789                   and then not Is_Child_Unit (Ent))
5790               or else
5791                 (Scope_Depth (Scope (Ent)) >
5792                              Scope_Depth (Current_Instantiated_Parent.Gen_Id)
5793                   and then
5794                     Get_Source_Unit (Ent) =
5795                     Get_Source_Unit (Current_Instantiated_Parent.Gen_Id))
5796             then
5797                Set_Associated_Node (New_N, Empty);
5798             end if;
5799
5800          --  Case of instantiating identifier or some other name or operator
5801
5802          else
5803             --  If the associated node is still defined, the entity in it is
5804             --  global, and must be copied to the instance. If this copy is
5805             --  being made for a body to inline, it is applied to an
5806             --  instantiated tree, and the entity is already present and must
5807             --  be also preserved.
5808
5809             declare
5810                Assoc : constant Node_Id := Get_Associated_Node (N);
5811
5812             begin
5813                if Present (Assoc) then
5814                   if Nkind (Assoc) = Nkind (N) then
5815                      Set_Entity (New_N, Entity (Assoc));
5816                      Check_Private_View (N);
5817
5818                   elsif Nkind (Assoc) = N_Function_Call then
5819                      Set_Entity (New_N, Entity (Name (Assoc)));
5820
5821                   elsif Nkind_In (Assoc, N_Defining_Identifier,
5822                                          N_Defining_Character_Literal,
5823                                          N_Defining_Operator_Symbol)
5824                     and then Expander_Active
5825                   then
5826                      --  Inlining case: we are copying a tree that contains
5827                      --  global entities, which are preserved in the copy to be
5828                      --  used for subsequent inlining.
5829
5830                      null;
5831
5832                   else
5833                      Set_Entity (New_N, Empty);
5834                   end if;
5835                end if;
5836             end;
5837          end if;
5838
5839          --  For expanded name, we must copy the Prefix and Selector_Name
5840
5841          if Nkind (N) = N_Expanded_Name then
5842             Set_Prefix
5843               (New_N, Copy_Generic_Node (Prefix (N), New_N, Instantiating));
5844
5845             Set_Selector_Name (New_N,
5846               Copy_Generic_Node (Selector_Name (N), New_N, Instantiating));
5847
5848          --  For operators, we must copy the right operand
5849
5850          elsif Nkind (N) in N_Op then
5851             Set_Right_Opnd (New_N,
5852               Copy_Generic_Node (Right_Opnd (N), New_N, Instantiating));
5853
5854             --  And for binary operators, the left operand as well
5855
5856             if Nkind (N) in N_Binary_Op then
5857                Set_Left_Opnd (New_N,
5858                  Copy_Generic_Node (Left_Opnd (N), New_N, Instantiating));
5859             end if;
5860          end if;
5861
5862       --  Special casing for stubs
5863
5864       elsif Nkind (N) in N_Body_Stub then
5865
5866          --  In any case, we must copy the specification or defining
5867          --  identifier as appropriate.
5868
5869          if Nkind (N) = N_Subprogram_Body_Stub then
5870             Set_Specification (New_N,
5871               Copy_Generic_Node (Specification (N), New_N, Instantiating));
5872
5873          else
5874             Set_Defining_Identifier (New_N,
5875               Copy_Generic_Node
5876                 (Defining_Identifier (N), New_N, Instantiating));
5877          end if;
5878
5879          --  If we are not instantiating, then this is where we load and
5880          --  analyze subunits, i.e. at the point where the stub occurs. A
5881          --  more permissible system might defer this analysis to the point
5882          --  of instantiation, but this seems to complicated for now.
5883
5884          if not Instantiating then
5885             declare
5886                Subunit_Name : constant Unit_Name_Type := Get_Unit_Name (N);
5887                Subunit      : Node_Id;
5888                Unum         : Unit_Number_Type;
5889                New_Body     : Node_Id;
5890
5891             begin
5892                Unum :=
5893                  Load_Unit
5894                    (Load_Name  => Subunit_Name,
5895                     Required   => False,
5896                     Subunit    => True,
5897                     Error_Node => N);
5898
5899                --  If the proper body is not found, a warning message will be
5900                --  emitted when analyzing the stub, or later at the point
5901                --  of instantiation. Here we just leave the stub as is.
5902
5903                if Unum = No_Unit then
5904                   Subunits_Missing := True;
5905                   goto Subunit_Not_Found;
5906                end if;
5907
5908                Subunit := Cunit (Unum);
5909
5910                if Nkind (Unit (Subunit)) /= N_Subunit then
5911                   Error_Msg_N
5912                     ("found child unit instead of expected SEPARATE subunit",
5913                      Subunit);
5914                   Error_Msg_Sloc := Sloc (N);
5915                   Error_Msg_N ("\to complete stub #", Subunit);
5916                   goto Subunit_Not_Found;
5917                end if;
5918
5919                --  We must create a generic copy of the subunit, in order to
5920                --  perform semantic analysis on it, and we must replace the
5921                --  stub in the original generic unit with the subunit, in order
5922                --  to preserve non-local references within.
5923
5924                --  Only the proper body needs to be copied. Library_Unit and
5925                --  context clause are simply inherited by the generic copy.
5926                --  Note that the copy (which may be recursive if there are
5927                --  nested subunits) must be done first, before attaching it to
5928                --  the enclosing generic.
5929
5930                New_Body :=
5931                  Copy_Generic_Node
5932                    (Proper_Body (Unit (Subunit)),
5933                     Empty, Instantiating => False);
5934
5935                --  Now place the original proper body in the original generic
5936                --  unit. This is a body, not a compilation unit.
5937
5938                Rewrite (N, Proper_Body (Unit (Subunit)));
5939                Set_Is_Compilation_Unit (Defining_Entity (N), False);
5940                Set_Was_Originally_Stub (N);
5941
5942                --  Finally replace the body of the subunit with its copy, and
5943                --  make this new subunit into the library unit of the generic
5944                --  copy, which does not have stubs any longer.
5945
5946                Set_Proper_Body (Unit (Subunit), New_Body);
5947                Set_Library_Unit (New_N, Subunit);
5948                Inherit_Context (Unit (Subunit), N);
5949             end;
5950
5951          --  If we are instantiating, this must be an error case, since
5952          --  otherwise we would have replaced the stub node by the proper body
5953          --  that corresponds. So just ignore it in the copy (i.e. we have
5954          --  copied it, and that is good enough).
5955
5956          else
5957             null;
5958          end if;
5959
5960          <<Subunit_Not_Found>> null;
5961
5962       --  If the node is a compilation unit, it is the subunit of a stub, which
5963       --  has been loaded already (see code below). In this case, the library
5964       --  unit field of N points to the parent unit (which is a compilation
5965       --  unit) and need not (and cannot!) be copied.
5966
5967       --  When the proper body of the stub is analyzed, the library_unit link
5968       --  is used to establish the proper context (see sem_ch10).
5969
5970       --  The other fields of a compilation unit are copied as usual
5971
5972       elsif Nkind (N) = N_Compilation_Unit then
5973
5974          --  This code can only be executed when not instantiating, because in
5975          --  the copy made for an instantiation, the compilation unit node has
5976          --  disappeared at the point that a stub is replaced by its proper
5977          --  body.
5978
5979          pragma Assert (not Instantiating);
5980
5981          Set_Context_Items (New_N,
5982            Copy_Generic_List (Context_Items (N), New_N));
5983
5984          Set_Unit (New_N,
5985            Copy_Generic_Node (Unit (N), New_N, False));
5986
5987          Set_First_Inlined_Subprogram (New_N,
5988            Copy_Generic_Node
5989              (First_Inlined_Subprogram (N), New_N, False));
5990
5991          Set_Aux_Decls_Node (New_N,
5992            Copy_Generic_Node (Aux_Decls_Node (N), New_N, False));
5993
5994       --  For an assignment node, the assignment is known to be semantically
5995       --  legal if we are instantiating the template. This avoids incorrect
5996       --  diagnostics in generated code.
5997
5998       elsif Nkind (N) = N_Assignment_Statement then
5999
6000          --  Copy name and expression fields in usual manner
6001
6002          Set_Name (New_N,
6003            Copy_Generic_Node (Name (N), New_N, Instantiating));
6004
6005          Set_Expression (New_N,
6006            Copy_Generic_Node (Expression (N), New_N, Instantiating));
6007
6008          if Instantiating then
6009             Set_Assignment_OK (Name (New_N), True);
6010          end if;
6011
6012       elsif Nkind_In (N, N_Aggregate, N_Extension_Aggregate) then
6013          if not Instantiating then
6014             Set_Associated_Node (N, New_N);
6015
6016          else
6017             if Present (Get_Associated_Node (N))
6018               and then Nkind (Get_Associated_Node (N)) = Nkind (N)
6019             then
6020                --  In the generic the aggregate has some composite type. If at
6021                --  the point of instantiation the type has a private view,
6022                --  install the full view (and that of its ancestors, if any).
6023
6024                declare
6025                   T   : Entity_Id := (Etype (Get_Associated_Node (New_N)));
6026                   Rt  : Entity_Id;
6027
6028                begin
6029                   if Present (T)
6030                     and then Is_Private_Type (T)
6031                   then
6032                      Switch_View (T);
6033                   end if;
6034
6035                   if Present (T)
6036                     and then Is_Tagged_Type (T)
6037                     and then Is_Derived_Type (T)
6038                   then
6039                      Rt := Root_Type (T);
6040
6041                      loop
6042                         T := Etype (T);
6043
6044                         if Is_Private_Type (T) then
6045                            Switch_View (T);
6046                         end if;
6047
6048                         exit when T = Rt;
6049                      end loop;
6050                   end if;
6051                end;
6052             end if;
6053          end if;
6054
6055          --  Do not copy the associated node, which points to
6056          --  the generic copy of the aggregate.
6057
6058          declare
6059             use Atree.Unchecked_Access;
6060             --  This code section is part of the implementation of an untyped
6061             --  tree traversal, so it needs direct access to node fields.
6062
6063          begin
6064             Set_Field1 (New_N, Copy_Generic_Descendant (Field1 (N)));
6065             Set_Field2 (New_N, Copy_Generic_Descendant (Field2 (N)));
6066             Set_Field3 (New_N, Copy_Generic_Descendant (Field3 (N)));
6067             Set_Field5 (New_N, Copy_Generic_Descendant (Field5 (N)));
6068          end;
6069
6070       --  Allocators do not have an identifier denoting the access type,
6071       --  so we must locate it through the expression to check whether
6072       --  the views are consistent.
6073
6074       elsif Nkind (N) = N_Allocator
6075         and then Nkind (Expression (N)) = N_Qualified_Expression
6076         and then Is_Entity_Name (Subtype_Mark (Expression (N)))
6077         and then Instantiating
6078       then
6079          declare
6080             T     : constant Node_Id :=
6081                       Get_Associated_Node (Subtype_Mark (Expression (N)));
6082             Acc_T : Entity_Id;
6083
6084          begin
6085             if Present (T) then
6086
6087                --  Retrieve the allocator node in the generic copy
6088
6089                Acc_T := Etype (Parent (Parent (T)));
6090                if Present (Acc_T)
6091                  and then Is_Private_Type (Acc_T)
6092                then
6093                   Switch_View (Acc_T);
6094                end if;
6095             end if;
6096
6097             Copy_Descendants;
6098          end;
6099
6100       --  For a proper body, we must catch the case of a proper body that
6101       --  replaces a stub. This represents the point at which a separate
6102       --  compilation unit, and hence template file, may be referenced, so we
6103       --  must make a new source instantiation entry for the template of the
6104       --  subunit, and ensure that all nodes in the subunit are adjusted using
6105       --  this new source instantiation entry.
6106
6107       elsif Nkind (N) in N_Proper_Body then
6108          declare
6109             Save_Adjustment : constant Sloc_Adjustment := S_Adjustment;
6110
6111          begin
6112             if Instantiating and then Was_Originally_Stub (N) then
6113                Create_Instantiation_Source
6114                  (Instantiation_Node,
6115                   Defining_Entity (N),
6116                   False,
6117                   S_Adjustment);
6118             end if;
6119
6120             --  Now copy the fields of the proper body, using the new
6121             --  adjustment factor if one was needed as per test above.
6122
6123             Copy_Descendants;
6124
6125             --  Restore the original adjustment factor in case changed
6126
6127             S_Adjustment := Save_Adjustment;
6128          end;
6129
6130       --  Don't copy Ident or Comment pragmas, since the comment belongs to the
6131       --  generic unit, not to the instantiating unit.
6132
6133       elsif Nkind (N) = N_Pragma
6134         and then Instantiating
6135       then
6136          declare
6137             Prag_Id : constant Pragma_Id := Get_Pragma_Id (N);
6138          begin
6139             if Prag_Id = Pragma_Ident
6140               or else Prag_Id = Pragma_Comment
6141             then
6142                New_N := Make_Null_Statement (Sloc (N));
6143             else
6144                Copy_Descendants;
6145             end if;
6146          end;
6147
6148       elsif Nkind_In (N, N_Integer_Literal,
6149                          N_Real_Literal,
6150                          N_String_Literal)
6151       then
6152          --  No descendant fields need traversing
6153
6154          null;
6155
6156       --  For the remaining nodes, copy recursively their descendants
6157
6158       else
6159          Copy_Descendants;
6160
6161          if Instantiating
6162            and then Nkind (N) = N_Subprogram_Body
6163          then
6164             Set_Generic_Parent (Specification (New_N), N);
6165          end if;
6166       end if;
6167
6168       return New_N;
6169    end Copy_Generic_Node;
6170
6171    ----------------------------
6172    -- Denotes_Formal_Package --
6173    ----------------------------
6174
6175    function Denotes_Formal_Package
6176      (Pack     : Entity_Id;
6177       On_Exit  : Boolean := False;
6178       Instance : Entity_Id := Empty) return Boolean
6179    is
6180       Par  : Entity_Id;
6181       Scop : constant Entity_Id := Scope (Pack);
6182       E    : Entity_Id;
6183
6184       function Is_Actual_Of_Previous_Formal (P : Entity_Id) return Boolean;
6185       --  The package in question may be an actual for a previous formal
6186       --  package P of the current instance, so examine its actuals as well.
6187       --  This must be recursive over other formal packages.
6188
6189       ----------------------------------
6190       -- Is_Actual_Of_Previous_Formal --
6191       ----------------------------------
6192
6193       function Is_Actual_Of_Previous_Formal (P : Entity_Id) return Boolean is
6194          E1 : Entity_Id;
6195
6196       begin
6197          E1 := First_Entity (P);
6198          while Present (E1) and then  E1 /= Instance loop
6199             if Ekind (E1) = E_Package
6200               and then Nkind (Parent (E1)) = N_Package_Renaming_Declaration
6201             then
6202                if Renamed_Object (E1) = Pack then
6203                   return True;
6204
6205                elsif E1 = P
6206                  or else  Renamed_Object (E1) = P
6207                then
6208                   return False;
6209
6210                elsif Is_Actual_Of_Previous_Formal (E1) then
6211                   return True;
6212                end if;
6213             end if;
6214
6215             Next_Entity (E1);
6216          end loop;
6217
6218          return False;
6219       end Is_Actual_Of_Previous_Formal;
6220
6221    --  Start of processing for Denotes_Formal_Package
6222
6223    begin
6224       if On_Exit then
6225          Par :=
6226            Instance_Envs.Table
6227              (Instance_Envs.Last).Instantiated_Parent.Act_Id;
6228       else
6229          Par  := Current_Instantiated_Parent.Act_Id;
6230       end if;
6231
6232       if Ekind (Scop) = E_Generic_Package
6233         or else Nkind (Unit_Declaration_Node (Scop)) =
6234                                          N_Generic_Subprogram_Declaration
6235       then
6236          return True;
6237
6238       elsif Nkind (Original_Node (Unit_Declaration_Node (Pack))) =
6239         N_Formal_Package_Declaration
6240       then
6241          return True;
6242
6243       elsif No (Par) then
6244          return False;
6245
6246       else
6247          --  Check whether this package is associated with a formal package of
6248          --  the enclosing instantiation. Iterate over the list of renamings.
6249
6250          E := First_Entity (Par);
6251          while Present (E) loop
6252             if Ekind (E) /= E_Package
6253               or else Nkind (Parent (E)) /= N_Package_Renaming_Declaration
6254             then
6255                null;
6256
6257             elsif Renamed_Object (E) = Par then
6258                return False;
6259
6260             elsif Renamed_Object (E) = Pack then
6261                return True;
6262
6263             elsif Is_Actual_Of_Previous_Formal (E) then
6264                return True;
6265
6266             end if;
6267
6268             Next_Entity (E);
6269          end loop;
6270
6271          return False;
6272       end if;
6273    end Denotes_Formal_Package;
6274
6275    -----------------
6276    -- End_Generic --
6277    -----------------
6278
6279    procedure End_Generic is
6280    begin
6281       --  ??? More things could be factored out in this routine. Should
6282       --  probably be done at a later stage.
6283
6284       Inside_A_Generic := Generic_Flags.Table (Generic_Flags.Last);
6285       Generic_Flags.Decrement_Last;
6286
6287       Expander_Mode_Restore;
6288    end End_Generic;
6289
6290    ----------------------
6291    -- Find_Actual_Type --
6292    ----------------------
6293
6294    function Find_Actual_Type
6295      (Typ      : Entity_Id;
6296       Gen_Type : Entity_Id) return Entity_Id
6297    is
6298       Gen_Scope : constant Entity_Id := Scope (Gen_Type);
6299       T         : Entity_Id;
6300
6301    begin
6302       --  Special processing only applies to child units
6303
6304       if not Is_Child_Unit (Gen_Scope) then
6305          return Get_Instance_Of (Typ);
6306
6307       --  If designated or component type is itself a formal of the child unit,
6308       --  its instance is available.
6309
6310       elsif Scope (Typ) = Gen_Scope then
6311          return Get_Instance_Of (Typ);
6312
6313       --  If the array or access type is not declared in the parent unit,
6314       --  no special processing needed.
6315
6316       elsif not Is_Generic_Type (Typ)
6317         and then Scope (Gen_Scope) /= Scope (Typ)
6318       then
6319          return Get_Instance_Of (Typ);
6320
6321       --  Otherwise, retrieve designated or component type by visibility
6322
6323       else
6324          T := Current_Entity (Typ);
6325          while Present (T) loop
6326             if In_Open_Scopes (Scope (T)) then
6327                return T;
6328
6329             elsif Is_Generic_Actual_Type (T) then
6330                return T;
6331             end if;
6332
6333             T := Homonym (T);
6334          end loop;
6335
6336          return Typ;
6337       end if;
6338    end Find_Actual_Type;
6339
6340    ----------------------------
6341    -- Freeze_Subprogram_Body --
6342    ----------------------------
6343
6344    procedure Freeze_Subprogram_Body
6345      (Inst_Node : Node_Id;
6346       Gen_Body  : Node_Id;
6347       Pack_Id   : Entity_Id)
6348   is
6349       F_Node   : Node_Id;
6350       Gen_Unit : constant Entity_Id := Get_Generic_Entity (Inst_Node);
6351       Par      : constant Entity_Id := Scope (Gen_Unit);
6352       Enc_G    : Entity_Id;
6353       Enc_I    : Node_Id;
6354       E_G_Id   : Entity_Id;
6355
6356       function Earlier (N1, N2 : Node_Id) return Boolean;
6357       --  Yields True if N1 and N2 appear in the same compilation unit,
6358       --  ignoring subunits, and if N1 is to the left of N2 in a left-to-right
6359       --  traversal of the tree for the unit.
6360
6361       function Enclosing_Body (N : Node_Id) return Node_Id;
6362       --  Find innermost package body that encloses the given node, and which
6363       --  is not a compilation unit. Freeze nodes for the instance, or for its
6364       --  enclosing body, may be inserted after the enclosing_body of the
6365       --  generic unit.
6366
6367       function Package_Freeze_Node (B : Node_Id) return Node_Id;
6368       --  Find entity for given package body, and locate or create a freeze
6369       --  node for it.
6370
6371       function True_Parent (N : Node_Id) return Node_Id;
6372       --  For a subunit, return parent of corresponding stub
6373
6374       -------------
6375       -- Earlier --
6376       -------------
6377
6378       function Earlier (N1, N2 : Node_Id) return Boolean is
6379          D1 : Integer := 0;
6380          D2 : Integer := 0;
6381          P1 : Node_Id := N1;
6382          P2 : Node_Id := N2;
6383
6384          procedure Find_Depth (P : in out Node_Id; D : in out Integer);
6385          --  Find distance from given node to enclosing compilation unit
6386
6387          ----------------
6388          -- Find_Depth --
6389          ----------------
6390
6391          procedure Find_Depth (P : in out Node_Id; D : in out Integer) is
6392          begin
6393             while Present (P)
6394               and then Nkind (P) /= N_Compilation_Unit
6395             loop
6396                P := True_Parent (P);
6397                D := D + 1;
6398             end loop;
6399          end Find_Depth;
6400
6401       --  Start of processing for Earlier
6402
6403       begin
6404          Find_Depth (P1, D1);
6405          Find_Depth (P2, D2);
6406
6407          if P1 /= P2 then
6408             return False;
6409          else
6410             P1 := N1;
6411             P2 := N2;
6412          end if;
6413
6414          while D1 > D2 loop
6415             P1 := True_Parent (P1);
6416             D1 := D1 - 1;
6417          end loop;
6418
6419          while D2 > D1 loop
6420             P2 := True_Parent (P2);
6421             D2 := D2 - 1;
6422          end loop;
6423
6424          --  At this point P1 and P2 are at the same distance from the root.
6425          --  We examine their parents until we find a common declarative
6426          --  list, at which point we can establish their relative placement
6427          --  by comparing their ultimate slocs. If we reach the root,
6428          --  N1 and N2 do not descend from the same declarative list (e.g.
6429          --  one is nested in the declarative part and the other is in a block
6430          --  in the statement part) and the earlier one is already frozen.
6431
6432          while not Is_List_Member (P1)
6433            or else not Is_List_Member (P2)
6434            or else List_Containing (P1) /= List_Containing (P2)
6435          loop
6436             P1 := True_Parent (P1);
6437             P2 := True_Parent (P2);
6438
6439             if Nkind (Parent (P1)) = N_Subunit then
6440                P1 := Corresponding_Stub (Parent (P1));
6441             end if;
6442
6443             if Nkind (Parent (P2)) = N_Subunit then
6444                P2 := Corresponding_Stub (Parent (P2));
6445             end if;
6446
6447             if P1 = P2 then
6448                return False;
6449             end if;
6450          end loop;
6451
6452          return
6453            Top_Level_Location (Sloc (P1)) < Top_Level_Location (Sloc (P2));
6454       end Earlier;
6455
6456       --------------------
6457       -- Enclosing_Body --
6458       --------------------
6459
6460       function Enclosing_Body (N : Node_Id) return Node_Id is
6461          P : Node_Id := Parent (N);
6462
6463       begin
6464          while Present (P)
6465            and then Nkind (Parent (P)) /= N_Compilation_Unit
6466          loop
6467             if Nkind (P) = N_Package_Body then
6468
6469                if Nkind (Parent (P)) = N_Subunit then
6470                   return Corresponding_Stub (Parent (P));
6471                else
6472                   return P;
6473                end if;
6474             end if;
6475
6476             P := True_Parent (P);
6477          end loop;
6478
6479          return Empty;
6480       end Enclosing_Body;
6481
6482       -------------------------
6483       -- Package_Freeze_Node --
6484       -------------------------
6485
6486       function Package_Freeze_Node (B : Node_Id) return Node_Id is
6487          Id : Entity_Id;
6488
6489       begin
6490          if Nkind (B) = N_Package_Body then
6491             Id := Corresponding_Spec (B);
6492
6493          else pragma Assert (Nkind (B) = N_Package_Body_Stub);
6494             Id := Corresponding_Spec (Proper_Body (Unit (Library_Unit (B))));
6495          end if;
6496
6497          Ensure_Freeze_Node (Id);
6498          return Freeze_Node (Id);
6499       end Package_Freeze_Node;
6500
6501       -----------------
6502       -- True_Parent --
6503       -----------------
6504
6505       function True_Parent (N : Node_Id) return Node_Id is
6506       begin
6507          if Nkind (Parent (N)) = N_Subunit then
6508             return Parent (Corresponding_Stub (Parent (N)));
6509          else
6510             return Parent (N);
6511          end if;
6512       end True_Parent;
6513
6514    --  Start of processing of Freeze_Subprogram_Body
6515
6516    begin
6517       --  If the instance and the generic body appear within the same unit, and
6518       --  the instance precedes the generic, the freeze node for the instance
6519       --  must appear after that of the generic. If the generic is nested
6520       --  within another instance I2, then current instance must be frozen
6521       --  after I2. In both cases, the freeze nodes are those of enclosing
6522       --  packages. Otherwise, the freeze node is placed at the end of the
6523       --  current declarative part.
6524
6525       Enc_G  := Enclosing_Body (Gen_Body);
6526       Enc_I  := Enclosing_Body (Inst_Node);
6527       Ensure_Freeze_Node (Pack_Id);
6528       F_Node := Freeze_Node (Pack_Id);
6529
6530       if Is_Generic_Instance (Par)
6531         and then Present (Freeze_Node (Par))
6532         and then
6533           In_Same_Declarative_Part (Freeze_Node (Par), Inst_Node)
6534       then
6535          if ABE_Is_Certain (Get_Package_Instantiation_Node (Par)) then
6536
6537             --  The parent was a premature instantiation. Insert freeze node at
6538             --  the end the current declarative part.
6539
6540             Insert_After_Last_Decl (Inst_Node, F_Node);
6541
6542          else
6543             Insert_After (Freeze_Node (Par), F_Node);
6544          end if;
6545
6546       --  The body enclosing the instance should be frozen after the body that
6547       --  includes the generic, because the body of the instance may make
6548       --  references to entities therein. If the two are not in the same
6549       --  declarative part, or if the one enclosing the instance is frozen
6550       --  already, freeze the instance at the end of the current declarative
6551       --  part.
6552
6553       elsif Is_Generic_Instance (Par)
6554         and then Present (Freeze_Node (Par))
6555         and then Present (Enc_I)
6556       then
6557          if In_Same_Declarative_Part (Freeze_Node (Par), Enc_I)
6558            or else
6559              (Nkind (Enc_I) = N_Package_Body
6560                and then
6561                  In_Same_Declarative_Part (Freeze_Node (Par), Parent (Enc_I)))
6562          then
6563             --  The enclosing package may contain several instances. Rather
6564             --  than computing the earliest point at which to insert its
6565             --  freeze node, we place it at the end of the declarative part
6566             --  of the parent of the generic.
6567
6568             Insert_After_Last_Decl
6569               (Freeze_Node (Par), Package_Freeze_Node (Enc_I));
6570          end if;
6571
6572          Insert_After_Last_Decl (Inst_Node, F_Node);
6573
6574       elsif Present (Enc_G)
6575         and then Present (Enc_I)
6576         and then Enc_G /= Enc_I
6577         and then Earlier (Inst_Node, Gen_Body)
6578       then
6579          if Nkind (Enc_G) = N_Package_Body then
6580             E_G_Id := Corresponding_Spec (Enc_G);
6581          else pragma Assert (Nkind (Enc_G) = N_Package_Body_Stub);
6582             E_G_Id :=
6583               Corresponding_Spec (Proper_Body (Unit (Library_Unit (Enc_G))));
6584          end if;
6585
6586          --  Freeze package that encloses instance, and place node after
6587          --  package that encloses generic. If enclosing package is already
6588          --  frozen we have to assume it is at the proper place. This may be
6589          --  a potential ABE that requires dynamic checking. Do not add a
6590          --  freeze node if the package that encloses the generic is inside
6591          --  the body that encloses the instance, because the freeze node
6592          --  would be in the wrong scope. Additional contortions needed if
6593          --  the bodies are within a subunit.
6594
6595          declare
6596             Enclosing_Body : Node_Id;
6597
6598          begin
6599             if Nkind (Enc_I) = N_Package_Body_Stub then
6600                Enclosing_Body := Proper_Body (Unit (Library_Unit (Enc_I)));
6601             else
6602                Enclosing_Body := Enc_I;
6603             end if;
6604
6605             if Parent (List_Containing (Enc_G)) /= Enclosing_Body then
6606                Insert_After_Last_Decl (Enc_G, Package_Freeze_Node (Enc_I));
6607             end if;
6608          end;
6609
6610          --  Freeze enclosing subunit before instance
6611
6612          Ensure_Freeze_Node (E_G_Id);
6613
6614          if not Is_List_Member (Freeze_Node (E_G_Id)) then
6615             Insert_After (Enc_G, Freeze_Node (E_G_Id));
6616          end if;
6617
6618          Insert_After_Last_Decl (Inst_Node, F_Node);
6619
6620       else
6621          --  If none of the above, insert freeze node at the end of the current
6622          --  declarative part.
6623
6624          Insert_After_Last_Decl (Inst_Node, F_Node);
6625       end if;
6626    end Freeze_Subprogram_Body;
6627
6628    ----------------
6629    -- Get_Gen_Id --
6630    ----------------
6631
6632    function Get_Gen_Id (E : Assoc_Ptr) return Entity_Id is
6633    begin
6634       return Generic_Renamings.Table (E).Gen_Id;
6635    end Get_Gen_Id;
6636
6637    ---------------------
6638    -- Get_Instance_Of --
6639    ---------------------
6640
6641    function Get_Instance_Of (A : Entity_Id) return Entity_Id is
6642       Res : constant Assoc_Ptr := Generic_Renamings_HTable.Get (A);
6643
6644    begin
6645       if Res /= Assoc_Null then
6646          return Generic_Renamings.Table (Res).Act_Id;
6647       else
6648          --  On exit, entity is not instantiated: not a generic parameter, or
6649          --  else parameter of an inner generic unit.
6650
6651          return A;
6652       end if;
6653    end Get_Instance_Of;
6654
6655    ------------------------------------
6656    -- Get_Package_Instantiation_Node --
6657    ------------------------------------
6658
6659    function Get_Package_Instantiation_Node (A : Entity_Id) return Node_Id is
6660       Decl : Node_Id := Unit_Declaration_Node (A);
6661       Inst : Node_Id;
6662
6663    begin
6664       --  If the Package_Instantiation attribute has been set on the package
6665       --  entity, then use it directly when it (or its Original_Node) refers
6666       --  to an N_Package_Instantiation node. In principle it should be
6667       --  possible to have this field set in all cases, which should be
6668       --  investigated, and would allow this function to be significantly
6669       --  simplified. ???
6670
6671       if Present (Package_Instantiation (A)) then
6672          if Nkind (Package_Instantiation (A)) = N_Package_Instantiation then
6673             return Package_Instantiation (A);
6674
6675          elsif Nkind (Original_Node (Package_Instantiation (A))) =
6676                                                    N_Package_Instantiation
6677          then
6678             return Original_Node (Package_Instantiation (A));
6679          end if;
6680       end if;
6681
6682       --  If the instantiation is a compilation unit that does not need body
6683       --  then the instantiation node has been rewritten as a package
6684       --  declaration for the instance, and we return the original node.
6685
6686       --  If it is a compilation unit and the instance node has not been
6687       --  rewritten, then it is still the unit of the compilation. Finally, if
6688       --  a body is present, this is a parent of the main unit whose body has
6689       --  been compiled for inlining purposes, and the instantiation node has
6690       --  been rewritten with the instance body.
6691
6692       --  Otherwise the instantiation node appears after the declaration. If
6693       --  the entity is a formal package, the declaration may have been
6694       --  rewritten as a generic declaration (in the case of a formal with box)
6695       --  or left as a formal package declaration if it has actuals, and is
6696       --  found with a forward search.
6697
6698       if Nkind (Parent (Decl)) = N_Compilation_Unit then
6699          if Nkind (Decl) = N_Package_Declaration
6700            and then Present (Corresponding_Body (Decl))
6701          then
6702             Decl := Unit_Declaration_Node (Corresponding_Body (Decl));
6703          end if;
6704
6705          if Nkind (Original_Node (Decl)) = N_Package_Instantiation then
6706             return Original_Node (Decl);
6707          else
6708             return Unit (Parent (Decl));
6709          end if;
6710
6711       elsif Nkind (Decl) = N_Package_Declaration
6712         and then Nkind (Original_Node (Decl)) = N_Formal_Package_Declaration
6713       then
6714          return Original_Node (Decl);
6715
6716       else
6717          Inst := Next (Decl);
6718          while not Nkind_In (Inst, N_Package_Instantiation,
6719                                    N_Formal_Package_Declaration)
6720          loop
6721             Next (Inst);
6722          end loop;
6723
6724          return Inst;
6725       end if;
6726    end Get_Package_Instantiation_Node;
6727
6728    ------------------------
6729    -- Has_Been_Exchanged --
6730    ------------------------
6731
6732    function Has_Been_Exchanged (E : Entity_Id) return Boolean is
6733       Next : Elmt_Id;
6734
6735    begin
6736       Next := First_Elmt (Exchanged_Views);
6737       while Present (Next) loop
6738          if Full_View (Node (Next)) = E then
6739             return True;
6740          end if;
6741
6742          Next_Elmt (Next);
6743       end loop;
6744
6745       return False;
6746    end Has_Been_Exchanged;
6747
6748    ----------
6749    -- Hash --
6750    ----------
6751
6752    function Hash (F : Entity_Id) return HTable_Range is
6753    begin
6754       return HTable_Range (F mod HTable_Size);
6755    end Hash;
6756
6757    ------------------------
6758    -- Hide_Current_Scope --
6759    ------------------------
6760
6761    procedure Hide_Current_Scope is
6762       C : constant Entity_Id := Current_Scope;
6763       E : Entity_Id;
6764
6765    begin
6766       Set_Is_Hidden_Open_Scope (C);
6767
6768       E := First_Entity (C);
6769       while Present (E) loop
6770          if Is_Immediately_Visible (E) then
6771             Set_Is_Immediately_Visible (E, False);
6772             Append_Elmt (E, Hidden_Entities);
6773          end if;
6774
6775          Next_Entity (E);
6776       end loop;
6777
6778       --  Make the scope name invisible as well. This is necessary, but might
6779       --  conflict with calls to Rtsfind later on, in case the scope is a
6780       --  predefined one. There is no clean solution to this problem, so for
6781       --  now we depend on the user not redefining Standard itself in one of
6782       --  the parent units.
6783
6784       if Is_Immediately_Visible (C)
6785         and then C /= Standard_Standard
6786       then
6787          Set_Is_Immediately_Visible (C, False);
6788          Append_Elmt (C, Hidden_Entities);
6789       end if;
6790
6791    end Hide_Current_Scope;
6792
6793    --------------
6794    -- Init_Env --
6795    --------------
6796
6797    procedure Init_Env is
6798       Saved : Instance_Env;
6799
6800    begin
6801       Saved.Instantiated_Parent  := Current_Instantiated_Parent;
6802       Saved.Exchanged_Views      := Exchanged_Views;
6803       Saved.Hidden_Entities      := Hidden_Entities;
6804       Saved.Current_Sem_Unit     := Current_Sem_Unit;
6805       Saved.Parent_Unit_Visible  := Parent_Unit_Visible;
6806       Saved.Instance_Parent_Unit := Instance_Parent_Unit;
6807
6808       --  Save configuration switches. These may be reset if the unit is a
6809       --  predefined unit, and the current mode is not Ada 2005.
6810
6811       Save_Opt_Config_Switches (Saved.Switches);
6812
6813       Instance_Envs.Append (Saved);
6814
6815       Exchanged_Views := New_Elmt_List;
6816       Hidden_Entities := New_Elmt_List;
6817
6818       --  Make dummy entry for Instantiated parent. If generic unit is legal,
6819       --  this is set properly in Set_Instance_Env.
6820
6821       Current_Instantiated_Parent :=
6822         (Current_Scope, Current_Scope, Assoc_Null);
6823    end Init_Env;
6824
6825    ------------------------------
6826    -- In_Same_Declarative_Part --
6827    ------------------------------
6828
6829    function In_Same_Declarative_Part
6830      (F_Node : Node_Id;
6831       Inst   : Node_Id) return Boolean
6832    is
6833       Decls : constant Node_Id := Parent (F_Node);
6834       Nod   : Node_Id := Parent (Inst);
6835
6836    begin
6837       while Present (Nod) loop
6838          if Nod = Decls then
6839             return True;
6840
6841          elsif Nkind_In (Nod, N_Subprogram_Body,
6842                               N_Package_Body,
6843                               N_Task_Body,
6844                               N_Protected_Body,
6845                               N_Block_Statement)
6846          then
6847             return False;
6848
6849          elsif Nkind (Nod) = N_Subunit then
6850             Nod :=  Corresponding_Stub (Nod);
6851
6852          elsif Nkind (Nod) = N_Compilation_Unit then
6853             return False;
6854
6855          else
6856             Nod := Parent (Nod);
6857          end if;
6858       end loop;
6859
6860       return False;
6861    end In_Same_Declarative_Part;
6862
6863    ---------------------
6864    -- In_Main_Context --
6865    ---------------------
6866
6867    function In_Main_Context (E : Entity_Id) return Boolean is
6868       Context : List_Id;
6869       Clause  : Node_Id;
6870       Nam     : Node_Id;
6871
6872    begin
6873       if not Is_Compilation_Unit (E)
6874         or else Ekind (E) /= E_Package
6875         or else In_Private_Part (E)
6876       then
6877          return False;
6878       end if;
6879
6880       Context := Context_Items (Cunit (Main_Unit));
6881
6882       Clause  := First (Context);
6883       while Present (Clause) loop
6884          if Nkind (Clause) = N_With_Clause then
6885             Nam := Name (Clause);
6886
6887             --  If the current scope is part of the context of the main unit,
6888             --  analysis of the corresponding with_clause is not complete, and
6889             --  the entity is not set. We use the Chars field directly, which
6890             --  might produce false positives in rare cases, but guarantees
6891             --  that we produce all the instance bodies we will need.
6892
6893             if (Is_Entity_Name (Nam)
6894                  and then Chars (Nam) = Chars (E))
6895               or else (Nkind (Nam) = N_Selected_Component
6896                         and then Chars (Selector_Name (Nam)) = Chars (E))
6897             then
6898                return True;
6899             end if;
6900          end if;
6901
6902          Next (Clause);
6903       end loop;
6904
6905       return False;
6906    end In_Main_Context;
6907
6908    ---------------------
6909    -- Inherit_Context --
6910    ---------------------
6911
6912    procedure Inherit_Context (Gen_Decl : Node_Id; Inst : Node_Id) is
6913       Current_Context : List_Id;
6914       Current_Unit    : Node_Id;
6915       Item            : Node_Id;
6916       New_I           : Node_Id;
6917
6918    begin
6919       if Nkind (Parent (Gen_Decl)) = N_Compilation_Unit then
6920
6921          --  The inherited context is attached to the enclosing compilation
6922          --  unit. This is either the main unit, or the declaration for the
6923          --  main unit (in case the instantiation appears within the package
6924          --  declaration and the main unit is its body).
6925
6926          Current_Unit := Parent (Inst);
6927          while Present (Current_Unit)
6928            and then Nkind (Current_Unit) /= N_Compilation_Unit
6929          loop
6930             Current_Unit := Parent (Current_Unit);
6931          end loop;
6932
6933          Current_Context := Context_Items (Current_Unit);
6934
6935          Item := First (Context_Items (Parent (Gen_Decl)));
6936          while Present (Item) loop
6937             if Nkind (Item) = N_With_Clause then
6938
6939                --  Take care to prevent direct cyclic with's, which can happen
6940                --  if the generic body with's the current unit. Such a case
6941                --  would result in binder errors (or run-time errors if the
6942                --  -gnatE switch is in effect), but we want to prevent it here,
6943                --  because Sem.Walk_Library_Items doesn't like cycles. Note
6944                --  that we don't bother to detect indirect cycles.
6945
6946                if Library_Unit (Item) /= Current_Unit then
6947                   New_I := New_Copy (Item);
6948                   Set_Implicit_With (New_I, True);
6949                   Append (New_I, Current_Context);
6950                end if;
6951             end if;
6952
6953             Next (Item);
6954          end loop;
6955       end if;
6956    end Inherit_Context;
6957
6958    ----------------
6959    -- Initialize --
6960    ----------------
6961
6962    procedure Initialize is
6963    begin
6964       Generic_Renamings.Init;
6965       Instance_Envs.Init;
6966       Generic_Flags.Init;
6967       Generic_Renamings_HTable.Reset;
6968       Circularity_Detected := False;
6969       Exchanged_Views      := No_Elist;
6970       Hidden_Entities      := No_Elist;
6971    end Initialize;
6972
6973    ----------------------------
6974    -- Insert_After_Last_Decl --
6975    ----------------------------
6976
6977    procedure Insert_After_Last_Decl (N : Node_Id; F_Node : Node_Id) is
6978       L : List_Id          := List_Containing (N);
6979       P : constant Node_Id := Parent (L);
6980
6981    begin
6982       if not Is_List_Member (F_Node) then
6983          if Nkind (P) = N_Package_Specification
6984            and then L = Visible_Declarations (P)
6985            and then Present (Private_Declarations (P))
6986            and then not Is_Empty_List (Private_Declarations (P))
6987          then
6988             L := Private_Declarations (P);
6989          end if;
6990
6991          Insert_After (Last (L), F_Node);
6992       end if;
6993    end Insert_After_Last_Decl;
6994
6995    ------------------
6996    -- Install_Body --
6997    ------------------
6998
6999    procedure Install_Body
7000      (Act_Body : Node_Id;
7001       N        : Node_Id;
7002       Gen_Body : Node_Id;
7003       Gen_Decl : Node_Id)
7004    is
7005       Act_Id    : constant Entity_Id := Corresponding_Spec (Act_Body);
7006       Act_Unit  : constant Node_Id   := Unit (Cunit (Get_Source_Unit (N)));
7007       Gen_Id    : constant Entity_Id := Corresponding_Spec (Gen_Body);
7008       Par       : constant Entity_Id := Scope (Gen_Id);
7009       Gen_Unit  : constant Node_Id   :=
7010                     Unit (Cunit (Get_Source_Unit (Gen_Decl)));
7011       Orig_Body : Node_Id := Gen_Body;
7012       F_Node    : Node_Id;
7013       Body_Unit : Node_Id;
7014
7015       Must_Delay : Boolean;
7016
7017       function Enclosing_Subp (Id : Entity_Id) return Entity_Id;
7018       --  Find subprogram (if any) that encloses instance and/or generic body
7019
7020       function True_Sloc (N : Node_Id) return Source_Ptr;
7021       --  If the instance is nested inside a generic unit, the Sloc of the
7022       --  instance indicates the place of the original definition, not the
7023       --  point of the current enclosing instance. Pending a better usage of
7024       --  Slocs to indicate instantiation places, we determine the place of
7025       --  origin of a node by finding the maximum sloc of any ancestor node.
7026       --  Why is this not equivalent to Top_Level_Location ???
7027
7028       --------------------
7029       -- Enclosing_Subp --
7030       --------------------
7031
7032       function Enclosing_Subp (Id : Entity_Id) return Entity_Id is
7033          Scop : Entity_Id := Scope (Id);
7034
7035       begin
7036          while Scop /= Standard_Standard
7037            and then not Is_Overloadable (Scop)
7038          loop
7039             Scop := Scope (Scop);
7040          end loop;
7041
7042          return Scop;
7043       end Enclosing_Subp;
7044
7045       ---------------
7046       -- True_Sloc --
7047       ---------------
7048
7049       function True_Sloc (N : Node_Id) return Source_Ptr is
7050          Res : Source_Ptr;
7051          N1  : Node_Id;
7052
7053       begin
7054          Res := Sloc (N);
7055          N1 := N;
7056          while Present (N1) and then N1 /= Act_Unit loop
7057             if Sloc (N1) > Res then
7058                Res := Sloc (N1);
7059             end if;
7060
7061             N1 := Parent (N1);
7062          end loop;
7063
7064          return Res;
7065       end True_Sloc;
7066
7067    --  Start of processing for Install_Body
7068
7069    begin
7070
7071       --  If the body is a subunit, the freeze point is the corresponding
7072       --  stub in the current compilation, not the subunit itself.
7073
7074       if Nkind (Parent (Gen_Body)) = N_Subunit then
7075          Orig_Body := Corresponding_Stub (Parent (Gen_Body));
7076       else
7077          Orig_Body := Gen_Body;
7078       end if;
7079
7080       Body_Unit := Unit (Cunit (Get_Source_Unit (Orig_Body)));
7081
7082       --  If the instantiation and the generic definition appear in the same
7083       --  package declaration, this is an early instantiation. If they appear
7084       --  in the same declarative part, it is an early instantiation only if
7085       --  the generic body appears textually later, and the generic body is
7086       --  also in the main unit.
7087
7088       --  If instance is nested within a subprogram, and the generic body is
7089       --  not, the instance is delayed because the enclosing body is. If
7090       --  instance and body are within the same scope, or the same sub-
7091       --  program body, indicate explicitly that the instance is delayed.
7092
7093       Must_Delay :=
7094         (Gen_Unit = Act_Unit
7095           and then (Nkind_In (Gen_Unit, N_Package_Declaration,
7096                                         N_Generic_Package_Declaration)
7097                       or else (Gen_Unit = Body_Unit
7098                                 and then True_Sloc (N) < Sloc (Orig_Body)))
7099           and then Is_In_Main_Unit (Gen_Unit)
7100           and then (Scope (Act_Id) = Scope (Gen_Id)
7101                       or else
7102                     Enclosing_Subp (Act_Id) = Enclosing_Subp (Gen_Id)));
7103
7104       --  If this is an early instantiation, the freeze node is placed after
7105       --  the generic body. Otherwise, if the generic appears in an instance,
7106       --  we cannot freeze the current instance until the outer one is frozen.
7107       --  This is only relevant if the current instance is nested within some
7108       --  inner scope not itself within the outer instance. If this scope is
7109       --  a package body in the same declarative part as the outer instance,
7110       --  then that body needs to be frozen after the outer instance. Finally,
7111       --  if no delay is needed, we place the freeze node at the end of the
7112       --  current declarative part.
7113
7114       if Expander_Active then
7115          Ensure_Freeze_Node (Act_Id);
7116          F_Node := Freeze_Node (Act_Id);
7117
7118          if Must_Delay then
7119             Insert_After (Orig_Body, F_Node);
7120
7121          elsif Is_Generic_Instance (Par)
7122            and then Present (Freeze_Node (Par))
7123            and then Scope (Act_Id) /= Par
7124          then
7125             --  Freeze instance of inner generic after instance of enclosing
7126             --  generic.
7127
7128             if In_Same_Declarative_Part (Freeze_Node (Par), N) then
7129                Insert_After (Freeze_Node (Par), F_Node);
7130
7131             --  Freeze package enclosing instance of inner generic after
7132             --  instance of enclosing generic.
7133
7134             elsif Nkind (Parent (N)) = N_Package_Body
7135               and then In_Same_Declarative_Part (Freeze_Node (Par), Parent (N))
7136             then
7137
7138                declare
7139                   Enclosing : constant Entity_Id :=
7140                                 Corresponding_Spec (Parent (N));
7141
7142                begin
7143                   Insert_After_Last_Decl (N, F_Node);
7144                   Ensure_Freeze_Node (Enclosing);
7145
7146                   if not Is_List_Member (Freeze_Node (Enclosing)) then
7147                      Insert_After (Freeze_Node (Par), Freeze_Node (Enclosing));
7148                   end if;
7149                end;
7150
7151             else
7152                Insert_After_Last_Decl (N, F_Node);
7153             end if;
7154
7155          else
7156             Insert_After_Last_Decl (N, F_Node);
7157          end if;
7158       end if;
7159
7160       Set_Is_Frozen (Act_Id);
7161       Insert_Before (N, Act_Body);
7162       Mark_Rewrite_Insertion (Act_Body);
7163    end Install_Body;
7164
7165    -----------------------------
7166    -- Install_Formal_Packages --
7167    -----------------------------
7168
7169    procedure Install_Formal_Packages (Par : Entity_Id) is
7170       E     : Entity_Id;
7171       Gen   : Entity_Id;
7172       Gen_E : Entity_Id := Empty;
7173
7174    begin
7175       E := First_Entity (Par);
7176
7177       --  In we are installing an instance parent, locate the formal packages
7178       --  of its generic parent.
7179
7180       if Is_Generic_Instance (Par) then
7181          Gen   := Generic_Parent (Specification (Unit_Declaration_Node (Par)));
7182          Gen_E := First_Entity (Gen);
7183       end if;
7184
7185       while Present (E) loop
7186          if Ekind (E) = E_Package
7187            and then Nkind (Parent (E)) = N_Package_Renaming_Declaration
7188          then
7189             --  If this is the renaming for the parent instance, done
7190
7191             if Renamed_Object (E) = Par then
7192                exit;
7193
7194             --  The visibility of a formal of an enclosing generic is
7195             --  already correct.
7196
7197             elsif Denotes_Formal_Package (E) then
7198                null;
7199
7200             elsif Present (Associated_Formal_Package (E))
7201               and then Box_Present (Parent (Associated_Formal_Package (E)))
7202             then
7203                Check_Generic_Actuals (Renamed_Object (E), True);
7204                Set_Is_Hidden (E, False);
7205
7206                --  Find formal package in generic unit that corresponds to
7207                --  (instance of) formal package in instance.
7208
7209                while Present (Gen_E)
7210                  and then  Chars (Gen_E) /= Chars (E)
7211                loop
7212                   Next_Entity (Gen_E);
7213                end loop;
7214
7215                if Present (Gen_E) then
7216                   Map_Formal_Package_Entities (Gen_E, E);
7217                end if;
7218             end if;
7219          end if;
7220
7221          Next_Entity (E);
7222          if Present (Gen_E) then
7223             Next_Entity (Gen_E);
7224          end if;
7225       end loop;
7226    end Install_Formal_Packages;
7227
7228    --------------------
7229    -- Install_Parent --
7230    --------------------
7231
7232    procedure Install_Parent (P : Entity_Id; In_Body : Boolean := False) is
7233       Ancestors : constant Elist_Id  := New_Elmt_List;
7234       S         : constant Entity_Id := Current_Scope;
7235       Inst_Par  : Entity_Id;
7236       First_Par : Entity_Id;
7237       Inst_Node : Node_Id;
7238       Gen_Par   : Entity_Id;
7239       First_Gen : Entity_Id;
7240       Elmt      : Elmt_Id;
7241
7242       procedure Install_Noninstance_Specs (Par : Entity_Id);
7243       --  Install the scopes of noninstance parent units ending with Par
7244
7245       procedure Install_Spec (Par : Entity_Id);
7246       --  The child unit is within the declarative part of the parent, so
7247       --  the declarations within the parent are immediately visible.
7248
7249       -------------------------------
7250       -- Install_Noninstance_Specs --
7251       -------------------------------
7252
7253       procedure Install_Noninstance_Specs (Par : Entity_Id) is
7254       begin
7255          if Present (Par)
7256            and then Par /= Standard_Standard
7257            and then not In_Open_Scopes (Par)
7258          then
7259             Install_Noninstance_Specs (Scope (Par));
7260             Install_Spec (Par);
7261          end if;
7262       end Install_Noninstance_Specs;
7263
7264       ------------------
7265       -- Install_Spec --
7266       ------------------
7267
7268       procedure Install_Spec (Par : Entity_Id) is
7269          Spec : constant Node_Id :=
7270                   Specification (Unit_Declaration_Node (Par));
7271
7272       begin
7273          --  If this parent of the child instance is a top-level unit,
7274          --  then record the unit and its visibility for later resetting
7275          --  in Remove_Parent. We exclude units that are generic instances,
7276          --  as we only want to record this information for the ultimate
7277          --  top-level noninstance parent (is that always correct???).
7278
7279          if Scope (Par) = Standard_Standard
7280            and then not Is_Generic_Instance (Par)
7281          then
7282             Parent_Unit_Visible := Is_Immediately_Visible (Par);
7283             Instance_Parent_Unit := Par;
7284          end if;
7285
7286          --  Open the parent scope and make it and its declarations visible.
7287          --  If this point is not within a body, then only the visible
7288          --  declarations should be made visible, and installation of the
7289          --  private declarations is deferred until the appropriate point
7290          --  within analysis of the spec being instantiated (see the handling
7291          --  of parent visibility in Analyze_Package_Specification). This is
7292          --  relaxed in the case where the parent unit is Ada.Tags, to avoid
7293          --  private view problems that occur when compiling instantiations of
7294          --  a generic child of that package (Generic_Dispatching_Constructor).
7295          --  If the instance freezes a tagged type, inlinings of operations
7296          --  from Ada.Tags may need the full view of type Tag. If inlining took
7297          --  proper account of establishing visibility of inlined subprograms'
7298          --  parents then it should be possible to remove this
7299          --  special check. ???
7300
7301          Push_Scope (Par);
7302          Set_Is_Immediately_Visible   (Par);
7303          Install_Visible_Declarations (Par);
7304          Set_Use (Visible_Declarations (Spec));
7305
7306          if In_Body or else Is_RTU (Par, Ada_Tags) then
7307             Install_Private_Declarations (Par);
7308             Set_Use (Private_Declarations (Spec));
7309          end if;
7310       end Install_Spec;
7311
7312    --  Start of processing for Install_Parent
7313
7314    begin
7315       --  We need to install the parent instance to compile the instantiation
7316       --  of the child, but the child instance must appear in the current
7317       --  scope. Given that we cannot place the parent above the current scope
7318       --  in the scope stack, we duplicate the current scope and unstack both
7319       --  after the instantiation is complete.
7320
7321       --  If the parent is itself the instantiation of a child unit, we must
7322       --  also stack the instantiation of its parent, and so on. Each such
7323       --  ancestor is the prefix of the name in a prior instantiation.
7324
7325       --  If this is a nested instance, the parent unit itself resolves to
7326       --  a renaming of the parent instance, whose declaration we need.
7327
7328       --  Finally, the parent may be a generic (not an instance) when the
7329       --  child unit appears as a formal package.
7330
7331       Inst_Par := P;
7332
7333       if Present (Renamed_Entity (Inst_Par)) then
7334          Inst_Par := Renamed_Entity (Inst_Par);
7335       end if;
7336
7337       First_Par := Inst_Par;
7338
7339       Gen_Par :=
7340         Generic_Parent (Specification (Unit_Declaration_Node (Inst_Par)));
7341
7342       First_Gen := Gen_Par;
7343
7344       while Present (Gen_Par)
7345         and then Is_Child_Unit (Gen_Par)
7346       loop
7347          --  Load grandparent instance as well
7348
7349          Inst_Node := Get_Package_Instantiation_Node (Inst_Par);
7350
7351          if Nkind (Name (Inst_Node)) = N_Expanded_Name then
7352             Inst_Par := Entity (Prefix (Name (Inst_Node)));
7353
7354             if Present (Renamed_Entity (Inst_Par)) then
7355                Inst_Par := Renamed_Entity (Inst_Par);
7356             end if;
7357
7358             Gen_Par :=
7359               Generic_Parent
7360                 (Specification (Unit_Declaration_Node (Inst_Par)));
7361
7362             if Present (Gen_Par) then
7363                Prepend_Elmt (Inst_Par, Ancestors);
7364
7365             else
7366                --  Parent is not the name of an instantiation
7367
7368                Install_Noninstance_Specs (Inst_Par);
7369
7370                exit;
7371             end if;
7372
7373          else
7374             --  Previous error
7375
7376             exit;
7377          end if;
7378       end loop;
7379
7380       if Present (First_Gen) then
7381          Append_Elmt (First_Par, Ancestors);
7382
7383       else
7384          Install_Noninstance_Specs (First_Par);
7385       end if;
7386
7387       if not Is_Empty_Elmt_List (Ancestors) then
7388          Elmt := First_Elmt (Ancestors);
7389
7390          while Present (Elmt) loop
7391             Install_Spec (Node (Elmt));
7392             Install_Formal_Packages (Node (Elmt));
7393
7394             Next_Elmt (Elmt);
7395          end loop;
7396       end if;
7397
7398       if not In_Body then
7399          Push_Scope (S);
7400       end if;
7401    end Install_Parent;
7402
7403    --------------------------------
7404    -- Instantiate_Formal_Package --
7405    --------------------------------
7406
7407    function Instantiate_Formal_Package
7408      (Formal          : Node_Id;
7409       Actual          : Node_Id;
7410       Analyzed_Formal : Node_Id) return List_Id
7411    is
7412       Loc         : constant Source_Ptr := Sloc (Actual);
7413       Actual_Pack : Entity_Id;
7414       Formal_Pack : Entity_Id;
7415       Gen_Parent  : Entity_Id;
7416       Decls       : List_Id;
7417       Nod         : Node_Id;
7418       Parent_Spec : Node_Id;
7419
7420       procedure Find_Matching_Actual
7421        (F    : Node_Id;
7422         Act  : in out Entity_Id);
7423       --  We need to associate each formal entity in the formal package
7424       --  with the corresponding entity in the actual package. The actual
7425       --  package has been analyzed and possibly expanded, and as a result
7426       --  there is no one-to-one correspondence between the two lists (for
7427       --  example, the actual may include subtypes, itypes, and inherited
7428       --  primitive operations, interspersed among the renaming declarations
7429       --  for the actuals) . We retrieve the corresponding actual by name
7430       --  because each actual has the same name as the formal, and they do
7431       --  appear in the same order.
7432
7433       function Get_Formal_Entity (N : Node_Id) return Entity_Id;
7434       --  Retrieve entity of defining entity of  generic formal parameter.
7435       --  Only the declarations of formals need to be considered when
7436       --  linking them to actuals, but the declarative list may include
7437       --  internal entities generated during analysis, and those are ignored.
7438
7439       procedure Match_Formal_Entity
7440         (Formal_Node : Node_Id;
7441          Formal_Ent  : Entity_Id;
7442          Actual_Ent  : Entity_Id);
7443       --  Associates the formal entity with the actual. In the case
7444       --  where Formal_Ent is a formal package, this procedure iterates
7445       --  through all of its formals and enters associations between the
7446       --  actuals occurring in the formal package's corresponding actual
7447       --  package (given by Actual_Ent) and the formal package's formal
7448       --  parameters. This procedure recurses if any of the parameters is
7449       --  itself a package.
7450
7451       function Is_Instance_Of
7452         (Act_Spec : Entity_Id;
7453          Gen_Anc  : Entity_Id) return Boolean;
7454       --  The actual can be an instantiation of a generic within another
7455       --  instance, in which case there is no direct link from it to the
7456       --  original generic ancestor. In that case, we recognize that the
7457       --  ultimate ancestor is the same by examining names and scopes.
7458
7459       procedure Process_Nested_Formal (Formal : Entity_Id);
7460       --  If the current formal is declared with a box, its own formals are
7461       --  visible in the instance, as they were in the generic, and their
7462       --  Hidden flag must be reset. If some of these formals are themselves
7463       --  packages declared with a box, the processing must be recursive.
7464
7465       --------------------------
7466       -- Find_Matching_Actual --
7467       --------------------------
7468
7469       procedure Find_Matching_Actual
7470         (F   : Node_Id;
7471          Act : in out Entity_Id)
7472      is
7473          Formal_Ent : Entity_Id;
7474
7475       begin
7476          case Nkind (Original_Node (F)) is
7477             when N_Formal_Object_Declaration |
7478                  N_Formal_Type_Declaration   =>
7479                Formal_Ent := Defining_Identifier (F);
7480
7481                while Chars (Act) /= Chars (Formal_Ent) loop
7482                   Next_Entity (Act);
7483                end loop;
7484
7485             when N_Formal_Subprogram_Declaration |
7486                  N_Formal_Package_Declaration    |
7487                  N_Package_Declaration           |
7488                  N_Generic_Package_Declaration   =>
7489                Formal_Ent := Defining_Entity (F);
7490
7491                while Chars (Act) /= Chars (Formal_Ent) loop
7492                   Next_Entity (Act);
7493                end loop;
7494
7495             when others =>
7496                raise Program_Error;
7497          end case;
7498       end Find_Matching_Actual;
7499
7500       -------------------------
7501       -- Match_Formal_Entity --
7502       -------------------------
7503
7504       procedure Match_Formal_Entity
7505         (Formal_Node : Node_Id;
7506          Formal_Ent  : Entity_Id;
7507          Actual_Ent  : Entity_Id)
7508       is
7509          Act_Pkg   : Entity_Id;
7510
7511       begin
7512          Set_Instance_Of (Formal_Ent, Actual_Ent);
7513
7514          if Ekind (Actual_Ent) = E_Package then
7515
7516             --  Record associations for each parameter
7517
7518             Act_Pkg := Actual_Ent;
7519
7520             declare
7521                A_Ent  : Entity_Id := First_Entity (Act_Pkg);
7522                F_Ent  : Entity_Id;
7523                F_Node : Node_Id;
7524
7525                Gen_Decl : Node_Id;
7526                Formals  : List_Id;
7527                Actual   : Entity_Id;
7528
7529             begin
7530                --  Retrieve the actual given in the formal package declaration
7531
7532                Actual := Entity (Name (Original_Node (Formal_Node)));
7533
7534                --  The actual in the formal package declaration  may be a
7535                --  renamed generic package, in which case we want to retrieve
7536                --  the original generic in order to traverse its formal part.
7537
7538                if Present (Renamed_Entity (Actual)) then
7539                   Gen_Decl := Unit_Declaration_Node (Renamed_Entity (Actual));
7540                else
7541                   Gen_Decl := Unit_Declaration_Node (Actual);
7542                end if;
7543
7544                Formals := Generic_Formal_Declarations (Gen_Decl);
7545
7546                if Present (Formals) then
7547                   F_Node := First_Non_Pragma (Formals);
7548                else
7549                   F_Node := Empty;
7550                end if;
7551
7552                while Present (A_Ent)
7553                  and then Present (F_Node)
7554                  and then A_Ent /= First_Private_Entity (Act_Pkg)
7555                loop
7556                   F_Ent := Get_Formal_Entity (F_Node);
7557
7558                   if Present (F_Ent) then
7559
7560                      --  This is a formal of the original package. Record
7561                      --  association and recurse.
7562
7563                      Find_Matching_Actual (F_Node, A_Ent);
7564                      Match_Formal_Entity (F_Node, F_Ent, A_Ent);
7565                      Next_Entity (A_Ent);
7566                   end if;
7567
7568                   Next_Non_Pragma (F_Node);
7569                end loop;
7570             end;
7571          end if;
7572       end Match_Formal_Entity;
7573
7574       -----------------------
7575       -- Get_Formal_Entity --
7576       -----------------------
7577
7578       function Get_Formal_Entity (N : Node_Id) return Entity_Id is
7579          Kind : constant Node_Kind := Nkind (Original_Node (N));
7580       begin
7581          case Kind is
7582             when N_Formal_Object_Declaration     =>
7583                return Defining_Identifier (N);
7584
7585             when N_Formal_Type_Declaration       =>
7586                return Defining_Identifier (N);
7587
7588             when N_Formal_Subprogram_Declaration =>
7589                return Defining_Unit_Name (Specification (N));
7590
7591             when N_Formal_Package_Declaration    =>
7592                return Defining_Identifier (Original_Node (N));
7593
7594             when N_Generic_Package_Declaration   =>
7595                return Defining_Identifier (Original_Node (N));
7596
7597             --  All other declarations are introduced by semantic analysis and
7598             --  have no match in the actual.
7599
7600             when others =>
7601                return Empty;
7602          end case;
7603       end Get_Formal_Entity;
7604
7605       --------------------
7606       -- Is_Instance_Of --
7607       --------------------
7608
7609       function Is_Instance_Of
7610         (Act_Spec : Entity_Id;
7611          Gen_Anc  : Entity_Id) return Boolean
7612       is
7613          Gen_Par : constant Entity_Id := Generic_Parent (Act_Spec);
7614
7615       begin
7616          if No (Gen_Par) then
7617             return False;
7618
7619          --  Simplest case: the generic parent of the actual is the formal
7620
7621          elsif Gen_Par = Gen_Anc then
7622             return True;
7623
7624          elsif Chars (Gen_Par) /= Chars (Gen_Anc) then
7625             return False;
7626
7627          --  The actual may be obtained through several instantiations. Its
7628          --  scope must itself be an instance of a generic declared in the
7629          --  same scope as the formal. Any other case is detected above.
7630
7631          elsif not Is_Generic_Instance (Scope (Gen_Par)) then
7632             return False;
7633
7634          else
7635             return Generic_Parent (Parent (Scope (Gen_Par))) = Scope (Gen_Anc);
7636          end if;
7637       end Is_Instance_Of;
7638
7639       ---------------------------
7640       -- Process_Nested_Formal --
7641       ---------------------------
7642
7643       procedure Process_Nested_Formal (Formal : Entity_Id) is
7644          Ent : Entity_Id;
7645
7646       begin
7647          if Present (Associated_Formal_Package (Formal))
7648            and then Box_Present (Parent (Associated_Formal_Package (Formal)))
7649          then
7650             Ent := First_Entity (Formal);
7651             while Present (Ent) loop
7652                Set_Is_Hidden (Ent, False);
7653                Set_Is_Visible_Formal (Ent);
7654                Set_Is_Potentially_Use_Visible
7655                  (Ent, Is_Potentially_Use_Visible (Formal));
7656
7657                if Ekind (Ent) = E_Package then
7658                   exit when Renamed_Entity (Ent) = Renamed_Entity (Formal);
7659                   Process_Nested_Formal (Ent);
7660                end if;
7661
7662                Next_Entity (Ent);
7663             end loop;
7664          end if;
7665       end Process_Nested_Formal;
7666
7667    --  Start of processing for Instantiate_Formal_Package
7668
7669    begin
7670       Analyze (Actual);
7671
7672       if not Is_Entity_Name (Actual)
7673         or else  Ekind (Entity (Actual)) /= E_Package
7674       then
7675          Error_Msg_N
7676            ("expect package instance to instantiate formal", Actual);
7677          Abandon_Instantiation (Actual);
7678          raise Program_Error;
7679
7680       else
7681          Actual_Pack := Entity (Actual);
7682          Set_Is_Instantiated (Actual_Pack);
7683
7684          --  The actual may be a renamed package, or an outer generic formal
7685          --  package whose instantiation is converted into a renaming.
7686
7687          if Present (Renamed_Object (Actual_Pack)) then
7688             Actual_Pack := Renamed_Object (Actual_Pack);
7689          end if;
7690
7691          if Nkind (Analyzed_Formal) = N_Formal_Package_Declaration then
7692             Gen_Parent  := Get_Instance_Of (Entity (Name (Analyzed_Formal)));
7693             Formal_Pack := Defining_Identifier (Analyzed_Formal);
7694          else
7695             Gen_Parent :=
7696               Generic_Parent (Specification (Analyzed_Formal));
7697             Formal_Pack :=
7698               Defining_Unit_Name (Specification (Analyzed_Formal));
7699          end if;
7700
7701          if Nkind (Parent (Actual_Pack)) = N_Defining_Program_Unit_Name then
7702             Parent_Spec := Specification (Unit_Declaration_Node (Actual_Pack));
7703          else
7704             Parent_Spec := Parent (Actual_Pack);
7705          end if;
7706
7707          if Gen_Parent = Any_Id then
7708             Error_Msg_N
7709               ("previous error in declaration of formal package", Actual);
7710             Abandon_Instantiation (Actual);
7711
7712          elsif
7713            Is_Instance_Of (Parent_Spec, Get_Instance_Of (Gen_Parent))
7714          then
7715             null;
7716
7717          else
7718             Error_Msg_NE
7719               ("actual parameter must be instance of&", Actual, Gen_Parent);
7720             Abandon_Instantiation (Actual);
7721          end if;
7722
7723          Set_Instance_Of (Defining_Identifier (Formal), Actual_Pack);
7724          Map_Formal_Package_Entities (Formal_Pack, Actual_Pack);
7725
7726          Nod :=
7727            Make_Package_Renaming_Declaration (Loc,
7728              Defining_Unit_Name => New_Copy (Defining_Identifier (Formal)),
7729              Name               => New_Reference_To (Actual_Pack, Loc));
7730
7731          Set_Associated_Formal_Package (Defining_Unit_Name (Nod),
7732            Defining_Identifier (Formal));
7733          Decls := New_List (Nod);
7734
7735          --  If the formal F has a box, then the generic declarations are
7736          --  visible in the generic G. In an instance of G, the corresponding
7737          --  entities in the actual for F (which are the actuals for the
7738          --  instantiation of the generic that F denotes) must also be made
7739          --  visible for analysis of the current instance. On exit from the
7740          --  current instance, those entities are made private again. If the
7741          --  actual is currently in use, these entities are also use-visible.
7742
7743          --  The loop through the actual entities also steps through the formal
7744          --  entities and enters associations from formals to actuals into the
7745          --  renaming map. This is necessary to properly handle checking of
7746          --  actual parameter associations for later formals that depend on
7747          --  actuals declared in the formal package.
7748
7749          --  In Ada 2005, partial parametrization requires that we make visible
7750          --  the actuals corresponding to formals that were defaulted in the
7751          --  formal package. There formals are identified because they remain
7752          --  formal generics within the formal package, rather than being
7753          --  renamings of the actuals supplied.
7754
7755          declare
7756             Gen_Decl : constant Node_Id :=
7757                          Unit_Declaration_Node (Gen_Parent);
7758             Formals  : constant List_Id :=
7759                          Generic_Formal_Declarations (Gen_Decl);
7760
7761             Actual_Ent       : Entity_Id;
7762             Actual_Of_Formal : Node_Id;
7763             Formal_Node      : Node_Id;
7764             Formal_Ent       : Entity_Id;
7765
7766          begin
7767             if Present (Formals) then
7768                Formal_Node := First_Non_Pragma (Formals);
7769             else
7770                Formal_Node := Empty;
7771             end if;
7772
7773             Actual_Ent := First_Entity (Actual_Pack);
7774             Actual_Of_Formal :=
7775                First (Visible_Declarations (Specification (Analyzed_Formal)));
7776             while Present (Actual_Ent)
7777               and then Actual_Ent /= First_Private_Entity (Actual_Pack)
7778             loop
7779                if Present (Formal_Node) then
7780                   Formal_Ent := Get_Formal_Entity (Formal_Node);
7781
7782                   if Present (Formal_Ent) then
7783                      Find_Matching_Actual (Formal_Node, Actual_Ent);
7784                      Match_Formal_Entity
7785                        (Formal_Node, Formal_Ent, Actual_Ent);
7786
7787                      --  We iterate at the same time over the actuals of the
7788                      --  local package created for the formal, to determine
7789                      --  which one of the formals of the original generic were
7790                      --  defaulted in the formal. The corresponding actual
7791                      --  entities are visible in the enclosing instance.
7792
7793                      if Box_Present (Formal)
7794                        or else
7795                          (Present (Actual_Of_Formal)
7796                            and then
7797                              Is_Generic_Formal
7798                                (Get_Formal_Entity (Actual_Of_Formal)))
7799                      then
7800                         Set_Is_Hidden (Actual_Ent, False);
7801                         Set_Is_Visible_Formal (Actual_Ent);
7802                         Set_Is_Potentially_Use_Visible
7803                           (Actual_Ent, In_Use (Actual_Pack));
7804
7805                         if Ekind (Actual_Ent) = E_Package then
7806                            Process_Nested_Formal (Actual_Ent);
7807                         end if;
7808
7809                      else
7810                         Set_Is_Hidden (Actual_Ent);
7811                         Set_Is_Potentially_Use_Visible (Actual_Ent, False);
7812                      end if;
7813                   end if;
7814
7815                   Next_Non_Pragma (Formal_Node);
7816                   Next (Actual_Of_Formal);
7817
7818                else
7819                   --  No further formals to match, but the generic part may
7820                   --  contain inherited operation that are not hidden in the
7821                   --  enclosing instance.
7822
7823                   Next_Entity (Actual_Ent);
7824                end if;
7825             end loop;
7826
7827             --  Inherited subprograms generated by formal derived types are
7828             --  also visible if the types are.
7829
7830             Actual_Ent := First_Entity (Actual_Pack);
7831             while Present (Actual_Ent)
7832               and then Actual_Ent /= First_Private_Entity (Actual_Pack)
7833             loop
7834                if Is_Overloadable (Actual_Ent)
7835                  and then
7836                    Nkind (Parent (Actual_Ent)) = N_Subtype_Declaration
7837                  and then
7838                    not Is_Hidden (Defining_Identifier (Parent (Actual_Ent)))
7839                then
7840                   Set_Is_Hidden (Actual_Ent, False);
7841                   Set_Is_Potentially_Use_Visible
7842                     (Actual_Ent, In_Use (Actual_Pack));
7843                end if;
7844
7845                Next_Entity (Actual_Ent);
7846             end loop;
7847          end;
7848
7849          --  If the formal is not declared with a box, reanalyze it as an
7850          --  abbreviated instantiation, to verify the matching rules of 12.7.
7851          --  The actual checks are performed after the generic associations
7852          --  have been analyzed, to guarantee the same visibility for this
7853          --  instantiation and for the actuals.
7854
7855          --  In Ada 2005, the generic associations for the formal can include
7856          --  defaulted parameters. These are ignored during check. This
7857          --  internal instantiation is removed from the tree after conformance
7858          --  checking, because it contains formal declarations for those
7859          --  defaulted parameters, and those should not reach the back-end.
7860
7861          if not Box_Present (Formal) then
7862             declare
7863                I_Pack : constant Entity_Id :=
7864                           Make_Defining_Identifier (Sloc (Actual),
7865                             Chars => New_Internal_Name  ('P'));
7866
7867             begin
7868                Set_Is_Internal (I_Pack);
7869
7870                Append_To (Decls,
7871                  Make_Package_Instantiation (Sloc (Actual),
7872                    Defining_Unit_Name => I_Pack,
7873                    Name =>
7874                      New_Occurrence_Of
7875                        (Get_Instance_Of (Gen_Parent), Sloc (Actual)),
7876                    Generic_Associations =>
7877                      Generic_Associations (Formal)));
7878             end;
7879          end if;
7880
7881          return Decls;
7882       end if;
7883    end Instantiate_Formal_Package;
7884
7885    -----------------------------------
7886    -- Instantiate_Formal_Subprogram --
7887    -----------------------------------
7888
7889    function Instantiate_Formal_Subprogram
7890      (Formal          : Node_Id;
7891       Actual          : Node_Id;
7892       Analyzed_Formal : Node_Id) return Node_Id
7893    is
7894       Loc        : Source_Ptr;
7895       Formal_Sub : constant Entity_Id :=
7896                      Defining_Unit_Name (Specification (Formal));
7897       Analyzed_S : constant Entity_Id :=
7898                      Defining_Unit_Name (Specification (Analyzed_Formal));
7899       Decl_Node  : Node_Id;
7900       Nam        : Node_Id;
7901       New_Spec   : Node_Id;
7902
7903       function From_Parent_Scope (Subp : Entity_Id) return Boolean;
7904       --  If the generic is a child unit, the parent has been installed on the
7905       --  scope stack, but a default subprogram cannot resolve to something on
7906       --  the parent because that parent is not really part of the visible
7907       --  context (it is there to resolve explicit local entities). If the
7908       --  default has resolved in this way, we remove the entity from
7909       --  immediate visibility and analyze the node again to emit an error
7910       --  message or find another visible candidate.
7911
7912       procedure Valid_Actual_Subprogram (Act : Node_Id);
7913       --  Perform legality check and raise exception on failure
7914
7915       -----------------------
7916       -- From_Parent_Scope --
7917       -----------------------
7918
7919       function From_Parent_Scope (Subp : Entity_Id) return Boolean is
7920          Gen_Scope : Node_Id;
7921
7922       begin
7923          Gen_Scope := Scope (Analyzed_S);
7924          while Present (Gen_Scope)
7925            and then  Is_Child_Unit (Gen_Scope)
7926          loop
7927             if Scope (Subp) = Scope (Gen_Scope) then
7928                return True;
7929             end if;
7930
7931             Gen_Scope := Scope (Gen_Scope);
7932          end loop;
7933
7934          return False;
7935       end From_Parent_Scope;
7936
7937       -----------------------------
7938       -- Valid_Actual_Subprogram --
7939       -----------------------------
7940
7941       procedure Valid_Actual_Subprogram (Act : Node_Id) is
7942          Act_E : Entity_Id;
7943
7944       begin
7945          if Is_Entity_Name (Act) then
7946             Act_E := Entity (Act);
7947
7948          elsif Nkind (Act) = N_Selected_Component
7949            and then Is_Entity_Name (Selector_Name (Act))
7950          then
7951             Act_E := Entity (Selector_Name (Act));
7952
7953          else
7954             Act_E := Empty;
7955          end if;
7956
7957          if (Present (Act_E) and then Is_Overloadable (Act_E))
7958            or else Nkind_In (Act, N_Attribute_Reference,
7959                                   N_Indexed_Component,
7960                                   N_Character_Literal,
7961                                   N_Explicit_Dereference)
7962          then
7963             return;
7964          end if;
7965
7966          Error_Msg_NE
7967            ("expect subprogram or entry name in instantiation of&",
7968             Instantiation_Node, Formal_Sub);
7969          Abandon_Instantiation (Instantiation_Node);
7970
7971       end Valid_Actual_Subprogram;
7972
7973    --  Start of processing for Instantiate_Formal_Subprogram
7974
7975    begin
7976       New_Spec := New_Copy_Tree (Specification (Formal));
7977
7978       --  The tree copy has created the proper instantiation sloc for the
7979       --  new specification. Use this location for all other constructed
7980       --  declarations.
7981
7982       Loc := Sloc (Defining_Unit_Name (New_Spec));
7983
7984       --  Create new entity for the actual (New_Copy_Tree does not)
7985
7986       Set_Defining_Unit_Name
7987         (New_Spec, Make_Defining_Identifier (Loc, Chars (Formal_Sub)));
7988
7989       --  Create new entities for the each of the formals in the
7990       --  specification of the renaming declaration built for the actual.
7991
7992       if Present (Parameter_Specifications (New_Spec)) then
7993          declare
7994             F : Node_Id;
7995          begin
7996             F := First (Parameter_Specifications (New_Spec));
7997             while Present (F) loop
7998                Set_Defining_Identifier (F,
7999                   Make_Defining_Identifier (Sloc (F),
8000                     Chars => Chars (Defining_Identifier (F))));
8001                Next (F);
8002             end loop;
8003          end;
8004       end if;
8005
8006       --  Find entity of actual. If the actual is an attribute reference, it
8007       --  cannot be resolved here (its formal is missing) but is handled
8008       --  instead in Attribute_Renaming. If the actual is overloaded, it is
8009       --  fully resolved subsequently, when the renaming declaration for the
8010       --  formal is analyzed. If it is an explicit dereference, resolve the
8011       --  prefix but not the actual itself, to prevent interpretation as call.
8012
8013       if Present (Actual) then
8014          Loc := Sloc (Actual);
8015          Set_Sloc (New_Spec, Loc);
8016
8017          if Nkind (Actual) = N_Operator_Symbol then
8018             Find_Direct_Name (Actual);
8019
8020          elsif Nkind (Actual) = N_Explicit_Dereference then
8021             Analyze (Prefix (Actual));
8022
8023          elsif Nkind (Actual) /= N_Attribute_Reference then
8024             Analyze (Actual);
8025          end if;
8026
8027          Valid_Actual_Subprogram (Actual);
8028          Nam := Actual;
8029
8030       elsif Present (Default_Name (Formal)) then
8031          if not Nkind_In (Default_Name (Formal), N_Attribute_Reference,
8032                                                  N_Selected_Component,
8033                                                  N_Indexed_Component,
8034                                                  N_Character_Literal)
8035            and then Present (Entity (Default_Name (Formal)))
8036          then
8037             Nam := New_Occurrence_Of (Entity (Default_Name (Formal)), Loc);
8038          else
8039             Nam := New_Copy (Default_Name (Formal));
8040             Set_Sloc (Nam, Loc);
8041          end if;
8042
8043       elsif Box_Present (Formal) then
8044
8045          --  Actual is resolved at the point of instantiation. Create an
8046          --  identifier or operator with the same name as the formal.
8047
8048          if Nkind (Formal_Sub) = N_Defining_Operator_Symbol then
8049             Nam := Make_Operator_Symbol (Loc,
8050               Chars =>  Chars (Formal_Sub),
8051               Strval => No_String);
8052          else
8053             Nam := Make_Identifier (Loc, Chars (Formal_Sub));
8054          end if;
8055
8056       elsif Nkind (Specification (Formal)) = N_Procedure_Specification
8057         and then Null_Present (Specification (Formal))
8058       then
8059          --  Generate null body for procedure, for use in the instance
8060
8061          Decl_Node :=
8062            Make_Subprogram_Body (Loc,
8063              Specification              => New_Spec,
8064              Declarations               => New_List,
8065              Handled_Statement_Sequence =>
8066                Make_Handled_Sequence_Of_Statements (Loc,
8067                  Statements => New_List (Make_Null_Statement (Loc))));
8068
8069          Set_Is_Intrinsic_Subprogram (Defining_Unit_Name (New_Spec));
8070          return Decl_Node;
8071
8072       else
8073          Error_Msg_Sloc := Sloc (Scope (Analyzed_S));
8074          Error_Msg_NE
8075            ("missing actual&", Instantiation_Node, Formal_Sub);
8076          Error_Msg_NE
8077            ("\in instantiation of & declared#",
8078               Instantiation_Node, Scope (Analyzed_S));
8079          Abandon_Instantiation (Instantiation_Node);
8080       end if;
8081
8082       Decl_Node :=
8083         Make_Subprogram_Renaming_Declaration (Loc,
8084           Specification => New_Spec,
8085           Name          => Nam);
8086
8087       --  If we do not have an actual and the formal specified <> then set to
8088       --  get proper default.
8089
8090       if No (Actual) and then Box_Present (Formal) then
8091          Set_From_Default (Decl_Node);
8092       end if;
8093
8094       --  Gather possible interpretations for the actual before analyzing the
8095       --  instance. If overloaded, it will be resolved when analyzing the
8096       --  renaming declaration.
8097
8098       if Box_Present (Formal)
8099         and then No (Actual)
8100       then
8101          Analyze (Nam);
8102
8103          if Is_Child_Unit (Scope (Analyzed_S))
8104            and then Present (Entity (Nam))
8105          then
8106             if not Is_Overloaded (Nam) then
8107
8108                if From_Parent_Scope (Entity (Nam)) then
8109                   Set_Is_Immediately_Visible (Entity (Nam), False);
8110                   Set_Entity (Nam, Empty);
8111                   Set_Etype (Nam, Empty);
8112
8113                   Analyze (Nam);
8114
8115                   Set_Is_Immediately_Visible (Entity (Nam));
8116                end if;
8117
8118             else
8119                declare
8120                   I  : Interp_Index;
8121                   It : Interp;
8122
8123                begin
8124                   Get_First_Interp (Nam, I, It);
8125
8126                   while Present (It.Nam) loop
8127                      if From_Parent_Scope (It.Nam) then
8128                         Remove_Interp (I);
8129                      end if;
8130
8131                      Get_Next_Interp (I, It);
8132                   end loop;
8133                end;
8134             end if;
8135          end if;
8136       end if;
8137
8138       --  The generic instantiation freezes the actual. This can only be done
8139       --  once the actual is resolved, in the analysis of the renaming
8140       --  declaration. To make the formal subprogram entity available, we set
8141       --  Corresponding_Formal_Spec to point to the formal subprogram entity.
8142       --  This is also needed in Analyze_Subprogram_Renaming for the processing
8143       --  of formal abstract subprograms.
8144
8145       Set_Corresponding_Formal_Spec (Decl_Node, Analyzed_S);
8146
8147       --  We cannot analyze the renaming declaration, and thus find the actual,
8148       --  until all the actuals are assembled in the instance. For subsequent
8149       --  checks of other actuals, indicate the node that will hold the
8150       --  instance of this formal.
8151
8152       Set_Instance_Of (Analyzed_S, Nam);
8153
8154       if Nkind (Actual) = N_Selected_Component
8155         and then Is_Task_Type (Etype (Prefix (Actual)))
8156         and then not Is_Frozen (Etype (Prefix (Actual)))
8157       then
8158          --  The renaming declaration will create a body, which must appear
8159          --  outside of the instantiation, We move the renaming declaration
8160          --  out of the instance, and create an additional renaming inside,
8161          --  to prevent freezing anomalies.
8162
8163          declare
8164             Anon_Id : constant Entity_Id :=
8165                         Make_Defining_Identifier
8166                           (Loc, New_Internal_Name ('E'));
8167          begin
8168             Set_Defining_Unit_Name (New_Spec, Anon_Id);
8169             Insert_Before (Instantiation_Node, Decl_Node);
8170             Analyze (Decl_Node);
8171
8172             --  Now create renaming within the instance
8173
8174             Decl_Node :=
8175               Make_Subprogram_Renaming_Declaration (Loc,
8176                 Specification => New_Copy_Tree (New_Spec),
8177                 Name => New_Occurrence_Of (Anon_Id, Loc));
8178
8179             Set_Defining_Unit_Name (Specification (Decl_Node),
8180               Make_Defining_Identifier (Loc, Chars (Formal_Sub)));
8181          end;
8182       end if;
8183
8184       return Decl_Node;
8185    end Instantiate_Formal_Subprogram;
8186
8187    ------------------------
8188    -- Instantiate_Object --
8189    ------------------------
8190
8191    function Instantiate_Object
8192      (Formal          : Node_Id;
8193       Actual          : Node_Id;
8194       Analyzed_Formal : Node_Id) return List_Id
8195    is
8196       Acc_Def     : Node_Id             := Empty;
8197       Act_Assoc   : constant Node_Id    := Parent (Actual);
8198       Actual_Decl : Node_Id             := Empty;
8199       Formal_Id   : constant Entity_Id  := Defining_Identifier (Formal);
8200       Decl_Node   : Node_Id;
8201       Def         : Node_Id;
8202       Ftyp        : Entity_Id;
8203       List        : constant List_Id    := New_List;
8204       Loc         : constant Source_Ptr := Sloc (Actual);
8205       Orig_Ftyp   : constant Entity_Id  :=
8206                       Etype (Defining_Identifier (Analyzed_Formal));
8207       Subt_Decl   : Node_Id             := Empty;
8208       Subt_Mark   : Node_Id             := Empty;
8209
8210    begin
8211       if Present (Subtype_Mark (Formal)) then
8212          Subt_Mark := Subtype_Mark (Formal);
8213       else
8214          Check_Access_Definition (Formal);
8215          Acc_Def := Access_Definition (Formal);
8216       end if;
8217
8218       --  Sloc for error message on missing actual
8219
8220       Error_Msg_Sloc := Sloc (Scope (Defining_Identifier (Analyzed_Formal)));
8221
8222       if Get_Instance_Of (Formal_Id) /= Formal_Id then
8223          Error_Msg_N ("duplicate instantiation of generic parameter", Actual);
8224       end if;
8225
8226       Set_Parent (List, Parent (Actual));
8227
8228       --  OUT present
8229
8230       if Out_Present (Formal) then
8231
8232          --  An IN OUT generic actual must be a name. The instantiation is a
8233          --  renaming declaration. The actual is the name being renamed. We
8234          --  use the actual directly, rather than a copy, because it is not
8235          --  used further in the list of actuals, and because a copy or a use
8236          --  of relocate_node is incorrect if the instance is nested within a
8237          --  generic. In order to simplify ASIS searches, the Generic_Parent
8238          --  field links the declaration to the generic association.
8239
8240          if No (Actual) then
8241             Error_Msg_NE
8242               ("missing actual&",
8243                Instantiation_Node, Formal_Id);
8244             Error_Msg_NE
8245               ("\in instantiation of & declared#",
8246                  Instantiation_Node,
8247                    Scope (Defining_Identifier (Analyzed_Formal)));
8248             Abandon_Instantiation (Instantiation_Node);
8249          end if;
8250
8251          if Present (Subt_Mark) then
8252             Decl_Node :=
8253               Make_Object_Renaming_Declaration (Loc,
8254                 Defining_Identifier => New_Copy (Formal_Id),
8255                 Subtype_Mark        => New_Copy_Tree (Subt_Mark),
8256                 Name                => Actual);
8257
8258          else pragma Assert (Present (Acc_Def));
8259             Decl_Node :=
8260               Make_Object_Renaming_Declaration (Loc,
8261                 Defining_Identifier => New_Copy (Formal_Id),
8262                 Access_Definition   => New_Copy_Tree (Acc_Def),
8263                 Name                => Actual);
8264          end if;
8265
8266          Set_Corresponding_Generic_Association (Decl_Node, Act_Assoc);
8267
8268          --  The analysis of the actual may produce insert_action nodes, so
8269          --  the declaration must have a context in which to attach them.
8270
8271          Append (Decl_Node, List);
8272          Analyze (Actual);
8273
8274          --  Return if the analysis of the actual reported some error
8275
8276          if Etype (Actual) = Any_Type then
8277             return List;
8278          end if;
8279
8280          --  This check is performed here because Analyze_Object_Renaming will
8281          --  not check it when Comes_From_Source is False. Note though that the
8282          --  check for the actual being the name of an object will be performed
8283          --  in Analyze_Object_Renaming.
8284
8285          if Is_Object_Reference (Actual)
8286            and then Is_Dependent_Component_Of_Mutable_Object (Actual)
8287          then
8288             Error_Msg_N
8289               ("illegal discriminant-dependent component for in out parameter",
8290                Actual);
8291          end if;
8292
8293          --  The actual has to be resolved in order to check that it is a
8294          --  variable (due to cases such as F(1), where F returns
8295          --  access to an array, and for overloaded prefixes).
8296
8297          Ftyp :=
8298            Get_Instance_Of (Etype (Defining_Identifier (Analyzed_Formal)));
8299
8300          if Is_Private_Type (Ftyp)
8301            and then not Is_Private_Type (Etype (Actual))
8302            and then (Base_Type (Full_View (Ftyp)) = Base_Type (Etype (Actual))
8303                       or else Base_Type (Etype (Actual)) = Ftyp)
8304          then
8305             --  If the actual has the type of the full view of the formal, or
8306             --  else a non-private subtype of the formal, then the visibility
8307             --  of the formal type has changed. Add to the actuals a subtype
8308             --  declaration that will force the exchange of views in the body
8309             --  of the instance as well.
8310
8311             Subt_Decl :=
8312               Make_Subtype_Declaration (Loc,
8313                  Defining_Identifier =>
8314                    Make_Defining_Identifier (Loc, New_Internal_Name ('P')),
8315                  Subtype_Indication  => New_Occurrence_Of (Ftyp, Loc));
8316
8317             Prepend (Subt_Decl, List);
8318
8319             Prepend_Elmt (Full_View (Ftyp), Exchanged_Views);
8320             Exchange_Declarations (Ftyp);
8321          end if;
8322
8323          Resolve (Actual, Ftyp);
8324
8325          if not Denotes_Variable (Actual) then
8326             Error_Msg_NE
8327               ("actual for& must be a variable", Actual, Formal_Id);
8328
8329          elsif Base_Type (Ftyp) /= Base_Type (Etype (Actual)) then
8330
8331             --  Ada 2005 (AI-423): For a generic formal object of mode in out,
8332             --  the type of the actual shall resolve to a specific anonymous
8333             --  access type.
8334
8335             if Ada_Version < Ada_05
8336               or else
8337                 Ekind (Base_Type (Ftyp)) /=
8338                   E_Anonymous_Access_Type
8339               or else
8340                 Ekind (Base_Type (Etype (Actual))) /=
8341                   E_Anonymous_Access_Type
8342             then
8343                Error_Msg_NE ("type of actual does not match type of&",
8344                              Actual, Formal_Id);
8345             end if;
8346          end if;
8347
8348          Note_Possible_Modification (Actual, Sure => True);
8349
8350          --  Check for instantiation of atomic/volatile actual for
8351          --  non-atomic/volatile formal (RM C.6 (12)).
8352
8353          if Is_Atomic_Object (Actual)
8354            and then not Is_Atomic (Orig_Ftyp)
8355          then
8356             Error_Msg_N
8357               ("cannot instantiate non-atomic formal object " &
8358                "with atomic actual", Actual);
8359
8360          elsif Is_Volatile_Object (Actual)
8361            and then not Is_Volatile (Orig_Ftyp)
8362          then
8363             Error_Msg_N
8364               ("cannot instantiate non-volatile formal object " &
8365                "with volatile actual", Actual);
8366          end if;
8367
8368       --  formal in-parameter
8369
8370       else
8371          --  The instantiation of a generic formal in-parameter is constant
8372          --  declaration. The actual is the expression for that declaration.
8373
8374          if Present (Actual) then
8375             if Present (Subt_Mark) then
8376                Def := Subt_Mark;
8377             else pragma Assert (Present (Acc_Def));
8378                Def := Acc_Def;
8379             end if;
8380
8381             Decl_Node :=
8382               Make_Object_Declaration (Loc,
8383                 Defining_Identifier    => New_Copy (Formal_Id),
8384                 Constant_Present       => True,
8385                 Null_Exclusion_Present => Null_Exclusion_Present (Formal),
8386                 Object_Definition      => New_Copy_Tree (Def),
8387                 Expression             => Actual);
8388
8389             Set_Corresponding_Generic_Association (Decl_Node, Act_Assoc);
8390
8391             --  A generic formal object of a tagged type is defined to be
8392             --  aliased so the new constant must also be treated as aliased.
8393
8394             if Is_Tagged_Type
8395                  (Etype (Defining_Identifier (Analyzed_Formal)))
8396             then
8397                Set_Aliased_Present (Decl_Node);
8398             end if;
8399
8400             Append (Decl_Node, List);
8401
8402             --  No need to repeat (pre-)analysis of some expression nodes
8403             --  already handled in Preanalyze_Actuals.
8404
8405             if Nkind (Actual) /= N_Allocator then
8406                Analyze (Actual);
8407
8408                --  Return if the analysis of the actual reported some error
8409
8410                if Etype (Actual) = Any_Type then
8411                   return List;
8412                end if;
8413             end if;
8414
8415             declare
8416                Formal_Object : constant Entity_Id :=
8417                                  Defining_Identifier (Analyzed_Formal);
8418                Formal_Type   : constant Entity_Id := Etype (Formal_Object);
8419
8420                Typ : Entity_Id;
8421
8422             begin
8423                Typ := Get_Instance_Of (Formal_Type);
8424
8425                Freeze_Before (Instantiation_Node, Typ);
8426
8427                --  If the actual is an aggregate, perform name resolution on
8428                --  its components (the analysis of an aggregate does not do it)
8429                --  to capture local names that may be hidden if the generic is
8430                --  a child unit.
8431
8432                if Nkind (Actual) = N_Aggregate then
8433                   Preanalyze_And_Resolve (Actual, Typ);
8434                end if;
8435
8436                if Is_Limited_Type (Typ)
8437                  and then not OK_For_Limited_Init (Typ, Actual)
8438                then
8439                   Error_Msg_N
8440                     ("initialization not allowed for limited types", Actual);
8441                   Explain_Limited_Type (Typ, Actual);
8442                end if;
8443             end;
8444
8445          elsif Present (Default_Expression (Formal)) then
8446
8447             --  Use default to construct declaration
8448
8449             if Present (Subt_Mark) then
8450                Def := Subt_Mark;
8451             else pragma Assert (Present (Acc_Def));
8452                Def := Acc_Def;
8453             end if;
8454
8455             Decl_Node :=
8456               Make_Object_Declaration (Sloc (Formal),
8457                 Defining_Identifier    => New_Copy (Formal_Id),
8458                 Constant_Present       => True,
8459                 Null_Exclusion_Present => Null_Exclusion_Present (Formal),
8460                 Object_Definition      => New_Copy (Def),
8461                 Expression             => New_Copy_Tree
8462                                             (Default_Expression (Formal)));
8463
8464             Append (Decl_Node, List);
8465             Set_Analyzed (Expression (Decl_Node), False);
8466
8467          else
8468             Error_Msg_NE
8469               ("missing actual&",
8470                 Instantiation_Node, Formal_Id);
8471             Error_Msg_NE ("\in instantiation of & declared#",
8472               Instantiation_Node,
8473                 Scope (Defining_Identifier (Analyzed_Formal)));
8474
8475             if Is_Scalar_Type
8476                  (Etype (Defining_Identifier (Analyzed_Formal)))
8477             then
8478                --  Create dummy constant declaration so that instance can be
8479                --  analyzed, to minimize cascaded visibility errors.
8480
8481                if Present (Subt_Mark) then
8482                   Def := Subt_Mark;
8483                else pragma Assert (Present (Acc_Def));
8484                   Def := Acc_Def;
8485                end if;
8486
8487                Decl_Node :=
8488                  Make_Object_Declaration (Loc,
8489                    Defining_Identifier    => New_Copy (Formal_Id),
8490                    Constant_Present       => True,
8491                    Null_Exclusion_Present => Null_Exclusion_Present (Formal),
8492                    Object_Definition      => New_Copy (Def),
8493                    Expression             =>
8494                      Make_Attribute_Reference (Sloc (Formal_Id),
8495                        Attribute_Name => Name_First,
8496                        Prefix         => New_Copy (Def)));
8497
8498                Append (Decl_Node, List);
8499
8500             else
8501                Abandon_Instantiation (Instantiation_Node);
8502             end if;
8503          end if;
8504       end if;
8505
8506       if Nkind (Actual) in N_Has_Entity then
8507          Actual_Decl := Parent (Entity (Actual));
8508       end if;
8509
8510       --  Ada 2005 (AI-423): For a formal object declaration with a null
8511       --  exclusion or an access definition that has a null exclusion: If the
8512       --  actual matching the formal object declaration denotes a generic
8513       --  formal object of another generic unit G, and the instantiation
8514       --  containing the actual occurs within the body of G or within the body
8515       --  of a generic unit declared within the declarative region of G, then
8516       --  the declaration of the formal object of G must have a null exclusion.
8517       --  Otherwise, the subtype of the actual matching the formal object
8518       --  declaration shall exclude null.
8519
8520       if Ada_Version >= Ada_05
8521         and then Present (Actual_Decl)
8522         and then
8523           Nkind_In (Actual_Decl, N_Formal_Object_Declaration,
8524                                  N_Object_Declaration)
8525         and then Nkind (Analyzed_Formal) = N_Formal_Object_Declaration
8526         and then not Has_Null_Exclusion (Actual_Decl)
8527         and then Has_Null_Exclusion (Analyzed_Formal)
8528       then
8529          Error_Msg_Sloc := Sloc (Analyzed_Formal);
8530          Error_Msg_N
8531            ("actual must exclude null to match generic formal#", Actual);
8532       end if;
8533
8534       return List;
8535    end Instantiate_Object;
8536
8537    ------------------------------
8538    -- Instantiate_Package_Body --
8539    ------------------------------
8540
8541    procedure Instantiate_Package_Body
8542      (Body_Info     : Pending_Body_Info;
8543       Inlined_Body  : Boolean := False;
8544       Body_Optional : Boolean := False)
8545    is
8546       Act_Decl    : constant Node_Id    := Body_Info.Act_Decl;
8547       Inst_Node   : constant Node_Id    := Body_Info.Inst_Node;
8548       Loc         : constant Source_Ptr := Sloc (Inst_Node);
8549
8550       Gen_Id      : constant Node_Id    := Name (Inst_Node);
8551       Gen_Unit    : constant Entity_Id  := Get_Generic_Entity (Inst_Node);
8552       Gen_Decl    : constant Node_Id    := Unit_Declaration_Node (Gen_Unit);
8553       Act_Spec    : constant Node_Id    := Specification (Act_Decl);
8554       Act_Decl_Id : constant Entity_Id  := Defining_Entity (Act_Spec);
8555
8556       Act_Body_Name : Node_Id;
8557       Gen_Body      : Node_Id;
8558       Gen_Body_Id   : Node_Id;
8559       Act_Body      : Node_Id;
8560       Act_Body_Id   : Entity_Id;
8561
8562       Parent_Installed : Boolean := False;
8563       Save_Style_Check : constant Boolean := Style_Check;
8564
8565       Par_Ent : Entity_Id := Empty;
8566       Par_Vis : Boolean   := False;
8567
8568    begin
8569       Gen_Body_Id := Corresponding_Body (Gen_Decl);
8570
8571       --  The instance body may already have been processed, as the parent of
8572       --  another instance that is inlined (Load_Parent_Of_Generic).
8573
8574       if Present (Corresponding_Body (Instance_Spec (Inst_Node))) then
8575          return;
8576       end if;
8577
8578       Expander_Mode_Save_And_Set (Body_Info.Expander_Status);
8579
8580       --  Re-establish the state of information on which checks are suppressed.
8581       --  This information was set in Body_Info at the point of instantiation,
8582       --  and now we restore it so that the instance is compiled using the
8583       --  check status at the instantiation (RM 11.5 (7.2/2), AI95-00224-01).
8584
8585       Local_Suppress_Stack_Top := Body_Info.Local_Suppress_Stack_Top;
8586       Scope_Suppress           := Body_Info.Scope_Suppress;
8587
8588       if No (Gen_Body_Id) then
8589          Load_Parent_Of_Generic
8590            (Inst_Node, Specification (Gen_Decl), Body_Optional);
8591          Gen_Body_Id := Corresponding_Body (Gen_Decl);
8592       end if;
8593
8594       --  Establish global variable for sloc adjustment and for error recovery
8595
8596       Instantiation_Node := Inst_Node;
8597
8598       if Present (Gen_Body_Id) then
8599          Save_Env (Gen_Unit, Act_Decl_Id);
8600          Style_Check := False;
8601          Current_Sem_Unit := Body_Info.Current_Sem_Unit;
8602
8603          Gen_Body := Unit_Declaration_Node (Gen_Body_Id);
8604
8605          Create_Instantiation_Source
8606            (Inst_Node, Gen_Body_Id, False, S_Adjustment);
8607
8608          Act_Body :=
8609            Copy_Generic_Node
8610              (Original_Node (Gen_Body), Empty, Instantiating => True);
8611
8612          --  Build new name (possibly qualified) for body declaration
8613
8614          Act_Body_Id := New_Copy (Act_Decl_Id);
8615
8616          --  Some attributes of spec entity are not inherited by body entity
8617
8618          Set_Handler_Records (Act_Body_Id, No_List);
8619
8620          if Nkind (Defining_Unit_Name (Act_Spec)) =
8621                                            N_Defining_Program_Unit_Name
8622          then
8623             Act_Body_Name :=
8624               Make_Defining_Program_Unit_Name (Loc,
8625                 Name => New_Copy_Tree (Name (Defining_Unit_Name (Act_Spec))),
8626                 Defining_Identifier => Act_Body_Id);
8627          else
8628             Act_Body_Name :=  Act_Body_Id;
8629          end if;
8630
8631          Set_Defining_Unit_Name (Act_Body, Act_Body_Name);
8632
8633          Set_Corresponding_Spec (Act_Body, Act_Decl_Id);
8634          Check_Generic_Actuals (Act_Decl_Id, False);
8635
8636          --  If it is a child unit, make the parent instance (which is an
8637          --  instance of the parent of the generic) visible. The parent
8638          --  instance is the prefix of the name of the generic unit.
8639
8640          if Ekind (Scope (Gen_Unit)) = E_Generic_Package
8641            and then Nkind (Gen_Id) = N_Expanded_Name
8642          then
8643             Par_Ent := Entity (Prefix (Gen_Id));
8644             Par_Vis := Is_Immediately_Visible (Par_Ent);
8645             Install_Parent (Par_Ent, In_Body => True);
8646             Parent_Installed := True;
8647
8648          elsif Is_Child_Unit (Gen_Unit) then
8649             Par_Ent := Scope (Gen_Unit);
8650             Par_Vis := Is_Immediately_Visible (Par_Ent);
8651             Install_Parent (Par_Ent, In_Body => True);
8652             Parent_Installed := True;
8653          end if;
8654
8655          --  If the instantiation is a library unit, and this is the main unit,
8656          --  then build the resulting compilation unit nodes for the instance.
8657          --  If this is a compilation unit but it is not the main unit, then it
8658          --  is the body of a unit in the context, that is being compiled
8659          --  because it is encloses some inlined unit or another generic unit
8660          --  being instantiated. In that case, this body is not part of the
8661          --  current compilation, and is not attached to the tree, but its
8662          --  parent must be set for analysis.
8663
8664          if Nkind (Parent (Inst_Node)) = N_Compilation_Unit then
8665
8666             --  Replace instance node with body of instance, and create new
8667             --  node for corresponding instance declaration.
8668
8669             Build_Instance_Compilation_Unit_Nodes
8670               (Inst_Node, Act_Body, Act_Decl);
8671             Analyze (Inst_Node);
8672
8673             if Parent (Inst_Node) = Cunit (Main_Unit) then
8674
8675                --  If the instance is a child unit itself, then set the scope
8676                --  of the expanded body to be the parent of the instantiation
8677                --  (ensuring that the fully qualified name will be generated
8678                --  for the elaboration subprogram).
8679
8680                if Nkind (Defining_Unit_Name (Act_Spec)) =
8681                                               N_Defining_Program_Unit_Name
8682                then
8683                   Set_Scope
8684                     (Defining_Entity (Inst_Node), Scope (Act_Decl_Id));
8685                end if;
8686             end if;
8687
8688          --  Case where instantiation is not a library unit
8689
8690          else
8691             --  If this is an early instantiation, i.e. appears textually
8692             --  before the corresponding body and must be elaborated first,
8693             --  indicate that the body instance is to be delayed.
8694
8695             Install_Body (Act_Body, Inst_Node, Gen_Body, Gen_Decl);
8696
8697             --  Now analyze the body. We turn off all checks if this is an
8698             --  internal unit, since there is no reason to have checks on for
8699             --  any predefined run-time library code. All such code is designed
8700             --  to be compiled with checks off.
8701
8702             --  Note that we do NOT apply this criterion to children of GNAT
8703             --  (or on VMS, children of DEC). The latter units must suppress
8704             --  checks explicitly if this is needed.
8705
8706             if Is_Predefined_File_Name
8707                  (Unit_File_Name (Get_Source_Unit (Gen_Decl)))
8708             then
8709                Analyze (Act_Body, Suppress => All_Checks);
8710             else
8711                Analyze (Act_Body);
8712             end if;
8713          end if;
8714
8715          Inherit_Context (Gen_Body, Inst_Node);
8716
8717          --  Remove the parent instances if they have been placed on the scope
8718          --  stack to compile the body.
8719
8720          if Parent_Installed then
8721             Remove_Parent (In_Body => True);
8722
8723             --  Restore the previous visibility of the parent
8724
8725             Set_Is_Immediately_Visible (Par_Ent, Par_Vis);
8726          end if;
8727
8728          Restore_Private_Views (Act_Decl_Id);
8729
8730          --  Remove the current unit from visibility if this is an instance
8731          --  that is not elaborated on the fly for inlining purposes.
8732
8733          if not Inlined_Body then
8734             Set_Is_Immediately_Visible (Act_Decl_Id, False);
8735          end if;
8736
8737          Restore_Env;
8738          Style_Check := Save_Style_Check;
8739
8740       --  If we have no body, and the unit requires a body, then complain. This
8741       --  complaint is suppressed if we have detected other errors (since a
8742       --  common reason for missing the body is that it had errors).
8743
8744       elsif Unit_Requires_Body (Gen_Unit)
8745         and then not Body_Optional
8746       then
8747          if Serious_Errors_Detected = 0 then
8748             Error_Msg_NE
8749               ("cannot find body of generic package &", Inst_Node, Gen_Unit);
8750
8751          --  Don't attempt to perform any cleanup actions if some other error
8752          --  was already detected, since this can cause blowups.
8753
8754          else
8755             return;
8756          end if;
8757
8758       --  Case of package that does not need a body
8759
8760       else
8761          --  If the instantiation of the declaration is a library unit, rewrite
8762          --  the original package instantiation as a package declaration in the
8763          --  compilation unit node.
8764
8765          if Nkind (Parent (Inst_Node)) = N_Compilation_Unit then
8766             Set_Parent_Spec (Act_Decl, Parent_Spec (Inst_Node));
8767             Rewrite (Inst_Node, Act_Decl);
8768
8769             --  Generate elaboration entity, in case spec has elaboration code.
8770             --  This cannot be done when the instance is analyzed, because it
8771             --  is not known yet whether the body exists.
8772
8773             Set_Elaboration_Entity_Required (Act_Decl_Id, False);
8774             Build_Elaboration_Entity (Parent (Inst_Node), Act_Decl_Id);
8775
8776          --  If the instantiation is not a library unit, then append the
8777          --  declaration to the list of implicitly generated entities, unless
8778          --  it is already a list member which means that it was already
8779          --  processed
8780
8781          elsif not Is_List_Member (Act_Decl) then
8782             Mark_Rewrite_Insertion (Act_Decl);
8783             Insert_Before (Inst_Node, Act_Decl);
8784          end if;
8785       end if;
8786
8787       Expander_Mode_Restore;
8788    end Instantiate_Package_Body;
8789
8790    ---------------------------------
8791    -- Instantiate_Subprogram_Body --
8792    ---------------------------------
8793
8794    procedure Instantiate_Subprogram_Body
8795      (Body_Info     : Pending_Body_Info;
8796       Body_Optional : Boolean := False)
8797    is
8798       Act_Decl      : constant Node_Id    := Body_Info.Act_Decl;
8799       Inst_Node     : constant Node_Id    := Body_Info.Inst_Node;
8800       Loc           : constant Source_Ptr := Sloc (Inst_Node);
8801       Gen_Id        : constant Node_Id    := Name (Inst_Node);
8802       Gen_Unit      : constant Entity_Id  := Get_Generic_Entity (Inst_Node);
8803       Gen_Decl      : constant Node_Id    := Unit_Declaration_Node (Gen_Unit);
8804       Anon_Id       : constant Entity_Id  :=
8805                         Defining_Unit_Name (Specification (Act_Decl));
8806       Pack_Id       : constant Entity_Id  :=
8807                         Defining_Unit_Name (Parent (Act_Decl));
8808       Decls         : List_Id;
8809       Gen_Body      : Node_Id;
8810       Gen_Body_Id   : Node_Id;
8811       Act_Body      : Node_Id;
8812       Pack_Body     : Node_Id;
8813       Prev_Formal   : Entity_Id;
8814       Ret_Expr      : Node_Id;
8815       Unit_Renaming : Node_Id;
8816
8817       Parent_Installed : Boolean := False;
8818       Save_Style_Check : constant Boolean := Style_Check;
8819
8820       Par_Ent : Entity_Id := Empty;
8821       Par_Vis : Boolean   := False;
8822
8823    begin
8824       Gen_Body_Id := Corresponding_Body (Gen_Decl);
8825
8826       --  Subprogram body may have been created already because of an inline
8827       --  pragma, or because of multiple elaborations of the enclosing package
8828       --  when several instances of the subprogram appear in the main unit.
8829
8830       if Present (Corresponding_Body (Act_Decl)) then
8831          return;
8832       end if;
8833
8834       Expander_Mode_Save_And_Set (Body_Info.Expander_Status);
8835
8836       --  Re-establish the state of information on which checks are suppressed.
8837       --  This information was set in Body_Info at the point of instantiation,
8838       --  and now we restore it so that the instance is compiled using the
8839       --  check status at the instantiation (RM 11.5 (7.2/2), AI95-00224-01).
8840
8841       Local_Suppress_Stack_Top := Body_Info.Local_Suppress_Stack_Top;
8842       Scope_Suppress           := Body_Info.Scope_Suppress;
8843
8844       if No (Gen_Body_Id) then
8845
8846          --  For imported generic subprogram, no body to compile, complete
8847          --  the spec entity appropriately.
8848
8849          if Is_Imported (Gen_Unit) then
8850             Set_Is_Imported (Anon_Id);
8851             Set_First_Rep_Item (Anon_Id, First_Rep_Item (Gen_Unit));
8852             Set_Interface_Name (Anon_Id, Interface_Name (Gen_Unit));
8853             Set_Convention     (Anon_Id, Convention     (Gen_Unit));
8854             Set_Has_Completion (Anon_Id);
8855             return;
8856
8857          --  For other cases, compile the body
8858
8859          else
8860             Load_Parent_Of_Generic
8861               (Inst_Node, Specification (Gen_Decl), Body_Optional);
8862             Gen_Body_Id := Corresponding_Body (Gen_Decl);
8863          end if;
8864       end if;
8865
8866       Instantiation_Node := Inst_Node;
8867
8868       if Present (Gen_Body_Id) then
8869          Gen_Body := Unit_Declaration_Node (Gen_Body_Id);
8870
8871          if Nkind (Gen_Body) = N_Subprogram_Body_Stub then
8872
8873             --  Either body is not present, or context is non-expanding, as
8874             --  when compiling a subunit. Mark the instance as completed, and
8875             --  diagnose a missing body when needed.
8876
8877             if Expander_Active
8878               and then Operating_Mode = Generate_Code
8879             then
8880                Error_Msg_N
8881                  ("missing proper body for instantiation", Gen_Body);
8882             end if;
8883
8884             Set_Has_Completion (Anon_Id);
8885             return;
8886          end if;
8887
8888          Save_Env (Gen_Unit, Anon_Id);
8889          Style_Check := False;
8890          Current_Sem_Unit := Body_Info.Current_Sem_Unit;
8891          Create_Instantiation_Source
8892            (Inst_Node,
8893             Gen_Body_Id,
8894             False,
8895             S_Adjustment);
8896
8897          Act_Body :=
8898            Copy_Generic_Node
8899              (Original_Node (Gen_Body), Empty, Instantiating => True);
8900
8901          --  Create proper defining name for the body, to correspond to
8902          --  the one in the spec.
8903
8904          Set_Defining_Unit_Name (Specification (Act_Body),
8905            Make_Defining_Identifier
8906              (Sloc (Defining_Entity (Inst_Node)), Chars (Anon_Id)));
8907          Set_Corresponding_Spec (Act_Body, Anon_Id);
8908          Set_Has_Completion (Anon_Id);
8909          Check_Generic_Actuals (Pack_Id, False);
8910
8911          --  Generate a reference to link the visible subprogram instance to
8912          --  the generic body, which for navigation purposes is the only
8913          --  available source for the instance.
8914
8915          Generate_Reference
8916            (Related_Instance (Pack_Id),
8917              Gen_Body_Id, 'b', Set_Ref => False, Force => True);
8918
8919          --  If it is a child unit, make the parent instance (which is an
8920          --  instance of the parent of the generic) visible. The parent
8921          --  instance is the prefix of the name of the generic unit.
8922
8923          if Ekind (Scope (Gen_Unit)) = E_Generic_Package
8924            and then Nkind (Gen_Id) = N_Expanded_Name
8925          then
8926             Par_Ent := Entity (Prefix (Gen_Id));
8927             Par_Vis := Is_Immediately_Visible (Par_Ent);
8928             Install_Parent (Par_Ent, In_Body => True);
8929             Parent_Installed := True;
8930
8931          elsif Is_Child_Unit (Gen_Unit) then
8932             Par_Ent := Scope (Gen_Unit);
8933             Par_Vis := Is_Immediately_Visible (Par_Ent);
8934             Install_Parent (Par_Ent, In_Body => True);
8935             Parent_Installed := True;
8936          end if;
8937
8938          --  Inside its body, a reference to the generic unit is a reference
8939          --  to the instance. The corresponding renaming is the first
8940          --  declaration in the body.
8941
8942          Unit_Renaming :=
8943            Make_Subprogram_Renaming_Declaration (Loc,
8944              Specification =>
8945                Copy_Generic_Node (
8946                  Specification (Original_Node (Gen_Body)),
8947                  Empty,
8948                  Instantiating => True),
8949              Name => New_Occurrence_Of (Anon_Id, Loc));
8950
8951          --  If there is a formal subprogram with the same name as the unit
8952          --  itself, do not add this renaming declaration. This is a temporary
8953          --  fix for one ACVC test. ???
8954
8955          Prev_Formal := First_Entity (Pack_Id);
8956          while Present (Prev_Formal) loop
8957             if Chars (Prev_Formal) = Chars (Gen_Unit)
8958               and then Is_Overloadable (Prev_Formal)
8959             then
8960                exit;
8961             end if;
8962
8963             Next_Entity (Prev_Formal);
8964          end loop;
8965
8966          if Present (Prev_Formal) then
8967             Decls :=  New_List (Act_Body);
8968          else
8969             Decls :=  New_List (Unit_Renaming, Act_Body);
8970          end if;
8971
8972          --  The subprogram body is placed in the body of a dummy package body,
8973          --  whose spec contains the subprogram declaration as well as the
8974          --  renaming declarations for the generic parameters.
8975
8976          Pack_Body := Make_Package_Body (Loc,
8977            Defining_Unit_Name => New_Copy (Pack_Id),
8978            Declarations       => Decls);
8979
8980          Set_Corresponding_Spec (Pack_Body, Pack_Id);
8981
8982          --  If the instantiation is a library unit, then build resulting
8983          --  compilation unit nodes for the instance. The declaration of
8984          --  the enclosing package is the grandparent of the subprogram
8985          --  declaration. First replace the instantiation node as the unit
8986          --  of the corresponding compilation.
8987
8988          if Nkind (Parent (Inst_Node)) = N_Compilation_Unit then
8989             if Parent (Inst_Node) = Cunit (Main_Unit) then
8990                Set_Unit (Parent (Inst_Node), Inst_Node);
8991                Build_Instance_Compilation_Unit_Nodes
8992                  (Inst_Node, Pack_Body, Parent (Parent (Act_Decl)));
8993                Analyze (Inst_Node);
8994             else
8995                Set_Parent (Pack_Body, Parent (Inst_Node));
8996                Analyze (Pack_Body);
8997             end if;
8998
8999          else
9000             Insert_Before (Inst_Node, Pack_Body);
9001             Mark_Rewrite_Insertion (Pack_Body);
9002             Analyze (Pack_Body);
9003
9004             if Expander_Active then
9005                Freeze_Subprogram_Body (Inst_Node, Gen_Body, Pack_Id);
9006             end if;
9007          end if;
9008
9009          Inherit_Context (Gen_Body, Inst_Node);
9010
9011          Restore_Private_Views (Pack_Id, False);
9012
9013          if Parent_Installed then
9014             Remove_Parent (In_Body => True);
9015
9016             --  Restore the previous visibility of the parent
9017
9018             Set_Is_Immediately_Visible (Par_Ent, Par_Vis);
9019          end if;
9020
9021          Restore_Env;
9022          Style_Check := Save_Style_Check;
9023
9024       --  Body not found. Error was emitted already. If there were no previous
9025       --  errors, this may be an instance whose scope is a premature instance.
9026       --  In that case we must insure that the (legal) program does raise
9027       --  program error if executed. We generate a subprogram body for this
9028       --  purpose. See DEC ac30vso.
9029
9030       --  Should not reference proprietary DEC tests in comments ???
9031
9032       elsif Serious_Errors_Detected = 0
9033         and then Nkind (Parent (Inst_Node)) /= N_Compilation_Unit
9034       then
9035          if Body_Optional then
9036             return;
9037
9038          elsif Ekind (Anon_Id) = E_Procedure then
9039             Act_Body :=
9040               Make_Subprogram_Body (Loc,
9041                  Specification              =>
9042                    Make_Procedure_Specification (Loc,
9043                      Defining_Unit_Name         =>
9044                        Make_Defining_Identifier (Loc, Chars (Anon_Id)),
9045                        Parameter_Specifications =>
9046                        New_Copy_List
9047                          (Parameter_Specifications (Parent (Anon_Id)))),
9048
9049                  Declarations               => Empty_List,
9050                  Handled_Statement_Sequence =>
9051                    Make_Handled_Sequence_Of_Statements (Loc,
9052                      Statements =>
9053                        New_List (
9054                          Make_Raise_Program_Error (Loc,
9055                            Reason =>
9056                              PE_Access_Before_Elaboration))));
9057
9058          else
9059             Ret_Expr :=
9060               Make_Raise_Program_Error (Loc,
9061                 Reason => PE_Access_Before_Elaboration);
9062
9063             Set_Etype (Ret_Expr, (Etype (Anon_Id)));
9064             Set_Analyzed (Ret_Expr);
9065
9066             Act_Body :=
9067               Make_Subprogram_Body (Loc,
9068                 Specification =>
9069                   Make_Function_Specification (Loc,
9070                      Defining_Unit_Name         =>
9071                        Make_Defining_Identifier (Loc, Chars (Anon_Id)),
9072                        Parameter_Specifications =>
9073                        New_Copy_List
9074                          (Parameter_Specifications (Parent (Anon_Id))),
9075                      Result_Definition =>
9076                        New_Occurrence_Of (Etype (Anon_Id), Loc)),
9077
9078                   Declarations               => Empty_List,
9079                   Handled_Statement_Sequence =>
9080                     Make_Handled_Sequence_Of_Statements (Loc,
9081                       Statements =>
9082                         New_List
9083                           (Make_Simple_Return_Statement (Loc, Ret_Expr))));
9084          end if;
9085
9086          Pack_Body := Make_Package_Body (Loc,
9087            Defining_Unit_Name => New_Copy (Pack_Id),
9088            Declarations       => New_List (Act_Body));
9089
9090          Insert_After (Inst_Node, Pack_Body);
9091          Set_Corresponding_Spec (Pack_Body, Pack_Id);
9092          Analyze (Pack_Body);
9093       end if;
9094
9095       Expander_Mode_Restore;
9096    end Instantiate_Subprogram_Body;
9097
9098    ----------------------
9099    -- Instantiate_Type --
9100    ----------------------
9101
9102    function Instantiate_Type
9103      (Formal          : Node_Id;
9104       Actual          : Node_Id;
9105       Analyzed_Formal : Node_Id;
9106       Actual_Decls    : List_Id) return List_Id
9107    is
9108       Gen_T      : constant Entity_Id  := Defining_Identifier (Formal);
9109       A_Gen_T    : constant Entity_Id  :=
9110                      Defining_Identifier (Analyzed_Formal);
9111       Ancestor   : Entity_Id := Empty;
9112       Def        : constant Node_Id    := Formal_Type_Definition (Formal);
9113       Act_T      : Entity_Id;
9114       Decl_Node  : Node_Id;
9115       Decl_Nodes : List_Id;
9116       Loc        : Source_Ptr;
9117       Subt       : Entity_Id;
9118
9119       procedure Validate_Array_Type_Instance;
9120       procedure Validate_Access_Subprogram_Instance;
9121       procedure Validate_Access_Type_Instance;
9122       procedure Validate_Derived_Type_Instance;
9123       procedure Validate_Derived_Interface_Type_Instance;
9124       procedure Validate_Interface_Type_Instance;
9125       procedure Validate_Private_Type_Instance;
9126       --  These procedures perform validation tests for the named case
9127
9128       function Subtypes_Match (Gen_T, Act_T : Entity_Id) return Boolean;
9129       --  Check that base types are the same and that the subtypes match
9130       --  statically. Used in several of the above.
9131
9132       --------------------
9133       -- Subtypes_Match --
9134       --------------------
9135
9136       function Subtypes_Match (Gen_T, Act_T : Entity_Id) return Boolean is
9137          T : constant Entity_Id := Get_Instance_Of (Gen_T);
9138
9139       begin
9140          return (Base_Type (T) = Base_Type (Act_T)
9141                   and then Subtypes_Statically_Match (T, Act_T))
9142
9143            or else (Is_Class_Wide_Type (Gen_T)
9144                      and then Is_Class_Wide_Type (Act_T)
9145                      and then
9146                        Subtypes_Match
9147                         (Get_Instance_Of (Root_Type (Gen_T)),
9148                          Root_Type (Act_T)))
9149
9150            or else
9151              ((Ekind (Gen_T) = E_Anonymous_Access_Subprogram_Type
9152                  or else Ekind (Gen_T) = E_Anonymous_Access_Type)
9153                and then Ekind (Act_T) = Ekind (Gen_T)
9154                and then
9155                  Subtypes_Statically_Match
9156                    (Designated_Type (Gen_T), Designated_Type (Act_T)));
9157       end Subtypes_Match;
9158
9159       -----------------------------------------
9160       -- Validate_Access_Subprogram_Instance --
9161       -----------------------------------------
9162
9163       procedure Validate_Access_Subprogram_Instance is
9164       begin
9165          if not Is_Access_Type (Act_T)
9166            or else Ekind (Designated_Type (Act_T)) /= E_Subprogram_Type
9167          then
9168             Error_Msg_NE
9169               ("expect access type in instantiation of &", Actual, Gen_T);
9170             Abandon_Instantiation (Actual);
9171          end if;
9172
9173          Check_Mode_Conformant
9174            (Designated_Type (Act_T),
9175             Designated_Type (A_Gen_T),
9176             Actual,
9177             Get_Inst => True);
9178
9179          if Ekind (Base_Type (Act_T)) = E_Access_Protected_Subprogram_Type then
9180             if Ekind (A_Gen_T) = E_Access_Subprogram_Type then
9181                Error_Msg_NE
9182                  ("protected access type not allowed for formal &",
9183                   Actual, Gen_T);
9184             end if;
9185
9186          elsif Ekind (A_Gen_T) = E_Access_Protected_Subprogram_Type then
9187             Error_Msg_NE
9188               ("expect protected access type for formal &",
9189                Actual, Gen_T);
9190          end if;
9191       end Validate_Access_Subprogram_Instance;
9192
9193       -----------------------------------
9194       -- Validate_Access_Type_Instance --
9195       -----------------------------------
9196
9197       procedure Validate_Access_Type_Instance is
9198          Desig_Type : constant Entity_Id :=
9199                         Find_Actual_Type (Designated_Type (A_Gen_T), A_Gen_T);
9200          Desig_Act  : Entity_Id;
9201
9202       begin
9203          if not Is_Access_Type (Act_T) then
9204             Error_Msg_NE
9205               ("expect access type in instantiation of &", Actual, Gen_T);
9206             Abandon_Instantiation (Actual);
9207          end if;
9208
9209          if Is_Access_Constant (A_Gen_T) then
9210             if not Is_Access_Constant (Act_T) then
9211                Error_Msg_N
9212                  ("actual type must be access-to-constant type", Actual);
9213                Abandon_Instantiation (Actual);
9214             end if;
9215          else
9216             if Is_Access_Constant (Act_T) then
9217                Error_Msg_N
9218                  ("actual type must be access-to-variable type", Actual);
9219                Abandon_Instantiation (Actual);
9220
9221             elsif Ekind (A_Gen_T) = E_General_Access_Type
9222               and then Ekind (Base_Type (Act_T)) /= E_General_Access_Type
9223             then
9224                Error_Msg_N ("actual must be general access type!", Actual);
9225                Error_Msg_NE ("add ALL to }!", Actual, Act_T);
9226                Abandon_Instantiation (Actual);
9227             end if;
9228          end if;
9229
9230          --  The designated subtypes, that is to say the subtypes introduced
9231          --  by an access type declaration (and not by a subtype declaration)
9232          --  must match.
9233
9234          Desig_Act := Designated_Type (Base_Type (Act_T));
9235
9236          --  The designated type may have been introduced through a limited_
9237          --  with clause, in which case retrieve the non-limited view. This
9238          --  applies to incomplete types as well as to class-wide types.
9239
9240          if From_With_Type (Desig_Act) then
9241             Desig_Act := Available_View (Desig_Act);
9242          end if;
9243
9244          if not Subtypes_Match
9245            (Desig_Type, Desig_Act) then
9246             Error_Msg_NE
9247               ("designated type of actual does not match that of formal &",
9248                  Actual, Gen_T);
9249             Abandon_Instantiation (Actual);
9250
9251          elsif Is_Access_Type (Designated_Type (Act_T))
9252            and then Is_Constrained (Designated_Type (Designated_Type (Act_T)))
9253                       /=
9254                   Is_Constrained (Designated_Type (Desig_Type))
9255          then
9256             Error_Msg_NE
9257               ("designated type of actual does not match that of formal &",
9258                  Actual, Gen_T);
9259             Abandon_Instantiation (Actual);
9260          end if;
9261
9262          --  Ada 2005: null-exclusion indicators of the two types must agree
9263
9264          if Can_Never_Be_Null (A_Gen_T) /=  Can_Never_Be_Null (Act_T) then
9265             Error_Msg_NE
9266               ("non null exclusion of actual and formal & do not match",
9267                  Actual, Gen_T);
9268          end if;
9269       end Validate_Access_Type_Instance;
9270
9271       ----------------------------------
9272       -- Validate_Array_Type_Instance --
9273       ----------------------------------
9274
9275       procedure Validate_Array_Type_Instance is
9276          I1 : Node_Id;
9277          I2 : Node_Id;
9278          T2 : Entity_Id;
9279
9280          function Formal_Dimensions return Int;
9281          --  Count number of dimensions in array type formal
9282
9283          -----------------------
9284          -- Formal_Dimensions --
9285          -----------------------
9286
9287          function Formal_Dimensions return Int is
9288             Num   : Int := 0;
9289             Index : Node_Id;
9290
9291          begin
9292             if Nkind (Def) = N_Constrained_Array_Definition then
9293                Index := First (Discrete_Subtype_Definitions (Def));
9294             else
9295                Index := First (Subtype_Marks (Def));
9296             end if;
9297
9298             while Present (Index) loop
9299                Num := Num + 1;
9300                Next_Index (Index);
9301             end loop;
9302
9303             return Num;
9304          end Formal_Dimensions;
9305
9306       --  Start of processing for Validate_Array_Type_Instance
9307
9308       begin
9309          if not Is_Array_Type (Act_T) then
9310             Error_Msg_NE
9311               ("expect array type in instantiation of &", Actual, Gen_T);
9312             Abandon_Instantiation (Actual);
9313
9314          elsif Nkind (Def) = N_Constrained_Array_Definition then
9315             if not (Is_Constrained (Act_T)) then
9316                Error_Msg_NE
9317                  ("expect constrained array in instantiation of &",
9318                   Actual, Gen_T);
9319                Abandon_Instantiation (Actual);
9320             end if;
9321
9322          else
9323             if Is_Constrained (Act_T) then
9324                Error_Msg_NE
9325                  ("expect unconstrained array in instantiation of &",
9326                   Actual, Gen_T);
9327                Abandon_Instantiation (Actual);
9328             end if;
9329          end if;
9330
9331          if Formal_Dimensions /= Number_Dimensions (Act_T) then
9332             Error_Msg_NE
9333               ("dimensions of actual do not match formal &", Actual, Gen_T);
9334             Abandon_Instantiation (Actual);
9335          end if;
9336
9337          I1 := First_Index (A_Gen_T);
9338          I2 := First_Index (Act_T);
9339          for J in 1 .. Formal_Dimensions loop
9340
9341             --  If the indices of the actual were given by a subtype_mark,
9342             --  the index was transformed into a range attribute. Retrieve
9343             --  the original type mark for checking.
9344
9345             if Is_Entity_Name (Original_Node (I2)) then
9346                T2 := Entity (Original_Node (I2));
9347             else
9348                T2 := Etype (I2);
9349             end if;
9350
9351             if not Subtypes_Match
9352                      (Find_Actual_Type (Etype (I1), A_Gen_T), T2)
9353             then
9354                Error_Msg_NE
9355                  ("index types of actual do not match those of formal &",
9356                   Actual, Gen_T);
9357                Abandon_Instantiation (Actual);
9358             end if;
9359
9360             Next_Index (I1);
9361             Next_Index (I2);
9362          end loop;
9363
9364          --  Check matching subtypes. Note that there are complex visibility
9365          --  issues when the generic is a child unit and some aspect of the
9366          --  generic type is declared in a parent unit of the generic. We do
9367          --  the test to handle this special case only after a direct check
9368          --  for static matching has failed.
9369
9370          if Subtypes_Match
9371            (Component_Type (A_Gen_T), Component_Type (Act_T))
9372              or else Subtypes_Match
9373                       (Find_Actual_Type (Component_Type (A_Gen_T), A_Gen_T),
9374                        Component_Type (Act_T))
9375          then
9376             null;
9377          else
9378             Error_Msg_NE
9379               ("component subtype of actual does not match that of formal &",
9380                Actual, Gen_T);
9381             Abandon_Instantiation (Actual);
9382          end if;
9383
9384          if Has_Aliased_Components (A_Gen_T)
9385            and then not Has_Aliased_Components (Act_T)
9386          then
9387             Error_Msg_NE
9388               ("actual must have aliased components to match formal type &",
9389                Actual, Gen_T);
9390          end if;
9391       end Validate_Array_Type_Instance;
9392
9393       -----------------------------------------------
9394       --  Validate_Derived_Interface_Type_Instance --
9395       -----------------------------------------------
9396
9397       procedure Validate_Derived_Interface_Type_Instance is
9398          Par  : constant Entity_Id := Entity (Subtype_Indication (Def));
9399          Elmt : Elmt_Id;
9400
9401       begin
9402          --  First apply interface instance checks
9403
9404          Validate_Interface_Type_Instance;
9405
9406          --  Verify that immediate parent interface is an ancestor of
9407          --  the actual.
9408
9409          if Present (Par)
9410            and then not Interface_Present_In_Ancestor (Act_T, Par)
9411          then
9412             Error_Msg_NE
9413               ("interface actual must include progenitor&", Actual, Par);
9414          end if;
9415
9416          --  Now verify that the actual includes all other ancestors of
9417          --  the formal.
9418
9419          Elmt := First_Elmt (Interfaces (A_Gen_T));
9420          while Present (Elmt) loop
9421             if not Interface_Present_In_Ancestor
9422                      (Act_T, Get_Instance_Of (Node (Elmt)))
9423             then
9424                Error_Msg_NE
9425                  ("interface actual must include progenitor&",
9426                     Actual, Node (Elmt));
9427             end if;
9428
9429             Next_Elmt (Elmt);
9430          end loop;
9431       end Validate_Derived_Interface_Type_Instance;
9432
9433       ------------------------------------
9434       -- Validate_Derived_Type_Instance --
9435       ------------------------------------
9436
9437       procedure Validate_Derived_Type_Instance is
9438          Actual_Discr   : Entity_Id;
9439          Ancestor_Discr : Entity_Id;
9440
9441       begin
9442          --  If the parent type in the generic declaration is itself a previous
9443          --  formal type, then it is local to the generic and absent from the
9444          --  analyzed generic definition. In that case the ancestor is the
9445          --  instance of the formal (which must have been instantiated
9446          --  previously), unless the ancestor is itself a formal derived type.
9447          --  In this latter case (which is the subject of Corrigendum 8652/0038
9448          --  (AI-202) the ancestor of the formals is the ancestor of its
9449          --  parent. Otherwise, the analyzed generic carries the parent type.
9450          --  If the parent type is defined in a previous formal package, then
9451          --  the scope of that formal package is that of the generic type
9452          --  itself, and it has already been mapped into the corresponding type
9453          --  in the actual package.
9454
9455          --  Common case: parent type defined outside of the generic
9456
9457          if Is_Entity_Name (Subtype_Mark (Def))
9458            and then Present (Entity (Subtype_Mark (Def)))
9459          then
9460             Ancestor := Get_Instance_Of (Entity (Subtype_Mark (Def)));
9461
9462          --  Check whether parent is defined in a previous formal package
9463
9464          elsif
9465            Scope (Scope (Base_Type (Etype (A_Gen_T)))) = Scope (A_Gen_T)
9466          then
9467             Ancestor :=
9468               Get_Instance_Of (Base_Type (Etype (A_Gen_T)));
9469
9470          --  The type may be a local derivation, or a type extension of a
9471          --  previous formal, or of a formal of a parent package.
9472
9473          elsif Is_Derived_Type (Get_Instance_Of (A_Gen_T))
9474           or else
9475             Ekind (Get_Instance_Of (A_Gen_T)) = E_Record_Type_With_Private
9476          then
9477             --  Check whether the parent is another derived formal type in the
9478             --  same generic unit.
9479
9480             if Etype (A_Gen_T) /= A_Gen_T
9481               and then Is_Generic_Type (Etype (A_Gen_T))
9482               and then Scope (Etype (A_Gen_T)) = Scope (A_Gen_T)
9483               and then Etype (Etype (A_Gen_T)) /= Etype (A_Gen_T)
9484             then
9485                --  Locate ancestor of parent from the subtype declaration
9486                --  created for the actual.
9487
9488                declare
9489                   Decl : Node_Id;
9490
9491                begin
9492                   Decl := First (Actual_Decls);
9493                   while Present (Decl) loop
9494                      if Nkind (Decl) = N_Subtype_Declaration
9495                        and then Chars (Defining_Identifier (Decl)) =
9496                                                     Chars (Etype (A_Gen_T))
9497                      then
9498                         Ancestor := Generic_Parent_Type (Decl);
9499                         exit;
9500                      else
9501                         Next (Decl);
9502                      end if;
9503                   end loop;
9504                end;
9505
9506                pragma Assert (Present (Ancestor));
9507
9508             else
9509                Ancestor :=
9510                  Get_Instance_Of (Base_Type (Get_Instance_Of (A_Gen_T)));
9511             end if;
9512
9513          else
9514             Ancestor := Get_Instance_Of (Etype (Base_Type (A_Gen_T)));
9515          end if;
9516
9517          --  If the formal derived type has pragma Preelaborable_Initialization
9518          --  then the actual type must have preelaborable initialization.
9519
9520          if Known_To_Have_Preelab_Init (A_Gen_T)
9521            and then not Has_Preelaborable_Initialization (Act_T)
9522          then
9523             Error_Msg_NE
9524               ("actual for & must have preelaborable initialization",
9525                Actual, Gen_T);
9526          end if;
9527
9528          --  Ada 2005 (AI-251)
9529
9530          if Ada_Version >= Ada_05
9531            and then Is_Interface (Ancestor)
9532          then
9533             if not Interface_Present_In_Ancestor (Act_T, Ancestor) then
9534                Error_Msg_NE
9535                  ("(Ada 2005) expected type implementing & in instantiation",
9536                   Actual, Ancestor);
9537             end if;
9538
9539          elsif not Is_Ancestor (Base_Type (Ancestor), Act_T) then
9540             Error_Msg_NE
9541               ("expect type derived from & in instantiation",
9542                Actual, First_Subtype (Ancestor));
9543             Abandon_Instantiation (Actual);
9544          end if;
9545
9546          --  Ada 2005 (AI-443): Synchronized formal derived type checks. Note
9547          --  that the formal type declaration has been rewritten as a private
9548          --  extension.
9549
9550          if Ada_Version >= Ada_05
9551            and then Nkind (Parent (A_Gen_T)) = N_Private_Extension_Declaration
9552            and then Synchronized_Present (Parent (A_Gen_T))
9553          then
9554             --  The actual must be a synchronized tagged type
9555
9556             if not Is_Tagged_Type (Act_T) then
9557                Error_Msg_N
9558                  ("actual of synchronized type must be tagged", Actual);
9559                Abandon_Instantiation (Actual);
9560
9561             elsif Nkind (Parent (Act_T)) = N_Full_Type_Declaration
9562               and then Nkind (Type_Definition (Parent (Act_T))) =
9563                          N_Derived_Type_Definition
9564               and then not Synchronized_Present (Type_Definition
9565                              (Parent (Act_T)))
9566             then
9567                Error_Msg_N
9568                  ("actual of synchronized type must be synchronized", Actual);
9569                Abandon_Instantiation (Actual);
9570             end if;
9571          end if;
9572
9573          --  Perform atomic/volatile checks (RM C.6(12))
9574
9575          if Is_Atomic (Act_T) and then not Is_Atomic (Ancestor) then
9576             Error_Msg_N
9577               ("cannot have atomic actual type for non-atomic formal type",
9578                Actual);
9579
9580          elsif Is_Volatile (Act_T)
9581            and then not Is_Volatile (Ancestor)
9582            and then Is_By_Reference_Type (Ancestor)
9583          then
9584             Error_Msg_N
9585               ("cannot have volatile actual type for non-volatile formal type",
9586                Actual);
9587          end if;
9588
9589          --  It should not be necessary to check for unknown discriminants on
9590          --  Formal, but for some reason Has_Unknown_Discriminants is false for
9591          --  A_Gen_T, so Is_Indefinite_Subtype incorrectly returns False. This
9592          --  needs fixing. ???
9593
9594          if not Is_Indefinite_Subtype (A_Gen_T)
9595            and then not Unknown_Discriminants_Present (Formal)
9596            and then Is_Indefinite_Subtype (Act_T)
9597          then
9598             Error_Msg_N
9599               ("actual subtype must be constrained", Actual);
9600             Abandon_Instantiation (Actual);
9601          end if;
9602
9603          if not Unknown_Discriminants_Present (Formal) then
9604             if Is_Constrained (Ancestor) then
9605                if not Is_Constrained (Act_T) then
9606                   Error_Msg_N
9607                     ("actual subtype must be constrained", Actual);
9608                   Abandon_Instantiation (Actual);
9609                end if;
9610
9611             --  Ancestor is unconstrained, Check if generic formal and actual
9612             --  agree on constrainedness. The check only applies to array types
9613             --  and discriminated types.
9614
9615             elsif Is_Constrained (Act_T) then
9616                if Ekind (Ancestor) = E_Access_Type
9617                  or else
9618                    (not Is_Constrained (A_Gen_T)
9619                      and then Is_Composite_Type (A_Gen_T))
9620                then
9621                   Error_Msg_N
9622                     ("actual subtype must be unconstrained", Actual);
9623                   Abandon_Instantiation (Actual);
9624                end if;
9625
9626             --  A class-wide type is only allowed if the formal has unknown
9627             --  discriminants.
9628
9629             elsif Is_Class_Wide_Type (Act_T)
9630               and then not Has_Unknown_Discriminants (Ancestor)
9631             then
9632                Error_Msg_NE
9633                  ("actual for & cannot be a class-wide type", Actual, Gen_T);
9634                Abandon_Instantiation (Actual);
9635
9636             --  Otherwise, the formal and actual shall have the same number
9637             --  of discriminants and each discriminant of the actual must
9638             --  correspond to a discriminant of the formal.
9639
9640             elsif Has_Discriminants (Act_T)
9641               and then not Has_Unknown_Discriminants (Act_T)
9642               and then Has_Discriminants (Ancestor)
9643             then
9644                Actual_Discr   := First_Discriminant (Act_T);
9645                Ancestor_Discr := First_Discriminant (Ancestor);
9646                while Present (Actual_Discr)
9647                  and then Present (Ancestor_Discr)
9648                loop
9649                   if Base_Type (Act_T) /= Base_Type (Ancestor) and then
9650                     No (Corresponding_Discriminant (Actual_Discr))
9651                   then
9652                      Error_Msg_NE
9653                        ("discriminant & does not correspond " &
9654                         "to ancestor discriminant", Actual, Actual_Discr);
9655                      Abandon_Instantiation (Actual);
9656                   end if;
9657
9658                   Next_Discriminant (Actual_Discr);
9659                   Next_Discriminant (Ancestor_Discr);
9660                end loop;
9661
9662                if Present (Actual_Discr) or else Present (Ancestor_Discr) then
9663                   Error_Msg_NE
9664                     ("actual for & must have same number of discriminants",
9665                      Actual, Gen_T);
9666                   Abandon_Instantiation (Actual);
9667                end if;
9668
9669             --  This case should be caught by the earlier check for
9670             --  constrainedness, but the check here is added for completeness.
9671
9672             elsif Has_Discriminants (Act_T)
9673               and then not Has_Unknown_Discriminants (Act_T)
9674             then
9675                Error_Msg_NE
9676                  ("actual for & must not have discriminants", Actual, Gen_T);
9677                Abandon_Instantiation (Actual);
9678
9679             elsif Has_Discriminants (Ancestor) then
9680                Error_Msg_NE
9681                  ("actual for & must have known discriminants", Actual, Gen_T);
9682                Abandon_Instantiation (Actual);
9683             end if;
9684
9685             if not Subtypes_Statically_Compatible (Act_T, Ancestor) then
9686                Error_Msg_N
9687                  ("constraint on actual is incompatible with formal", Actual);
9688                Abandon_Instantiation (Actual);
9689             end if;
9690          end if;
9691
9692          --  If the formal and actual types are abstract, check that there
9693          --  are no abstract primitives of the actual type that correspond to
9694          --  nonabstract primitives of the formal type (second sentence of
9695          --  RM95-3.9.3(9)).
9696
9697          if Is_Abstract_Type (A_Gen_T) and then Is_Abstract_Type (Act_T) then
9698             Check_Abstract_Primitives : declare
9699                Gen_Prims  : constant Elist_Id :=
9700                              Primitive_Operations (A_Gen_T);
9701                Gen_Elmt   : Elmt_Id;
9702                Gen_Subp   : Entity_Id;
9703                Anc_Subp   : Entity_Id;
9704                Anc_Formal : Entity_Id;
9705                Anc_F_Type : Entity_Id;
9706
9707                Act_Prims  : constant Elist_Id  := Primitive_Operations (Act_T);
9708                Act_Elmt   : Elmt_Id;
9709                Act_Subp   : Entity_Id;
9710                Act_Formal : Entity_Id;
9711                Act_F_Type : Entity_Id;
9712
9713                Subprograms_Correspond : Boolean;
9714
9715                function Is_Tagged_Ancestor (T1, T2 : Entity_Id) return Boolean;
9716                --  Returns true if T2 is derived directly or indirectly from
9717                --  T1, including derivations from interfaces. T1 and T2 are
9718                --  required to be specific tagged base types.
9719
9720                ------------------------
9721                -- Is_Tagged_Ancestor --
9722                ------------------------
9723
9724                function Is_Tagged_Ancestor (T1, T2 : Entity_Id) return Boolean
9725                is
9726                   Intfc_Elmt : Elmt_Id;
9727
9728                begin
9729                   --  The predicate is satisfied if the types are the same
9730
9731                   if T1 = T2 then
9732                      return True;
9733
9734                   --  If we've reached the top of the derivation chain then
9735                   --  we know that T1 is not an ancestor of T2.
9736
9737                   elsif Etype (T2) = T2 then
9738                      return False;
9739
9740                   --  Proceed to check T2's immediate parent
9741
9742                   elsif Is_Ancestor (T1, Base_Type (Etype (T2))) then
9743                      return True;
9744
9745                   --  Finally, check to see if T1 is an ancestor of any of T2's
9746                   --  progenitors.
9747
9748                   else
9749                      Intfc_Elmt := First_Elmt (Interfaces (T2));
9750                      while Present (Intfc_Elmt) loop
9751                         if Is_Ancestor (T1, Node (Intfc_Elmt)) then
9752                            return True;
9753                         end if;
9754
9755                         Next_Elmt (Intfc_Elmt);
9756                      end loop;
9757                   end if;
9758
9759                   return False;
9760                end Is_Tagged_Ancestor;
9761
9762             --  Start of processing for Check_Abstract_Primitives
9763
9764             begin
9765                --  Loop over all of the formal derived type's primitives
9766
9767                Gen_Elmt := First_Elmt (Gen_Prims);
9768                while Present (Gen_Elmt) loop
9769                   Gen_Subp := Node (Gen_Elmt);
9770
9771                   --  If the primitive of the formal is not abstract, then
9772                   --  determine whether there is a corresponding primitive of
9773                   --  the actual type that's abstract.
9774
9775                   if not Is_Abstract_Subprogram (Gen_Subp) then
9776                      Act_Elmt := First_Elmt (Act_Prims);
9777                      while Present (Act_Elmt) loop
9778                         Act_Subp := Node (Act_Elmt);
9779
9780                         --  If we find an abstract primitive of the actual,
9781                         --  then we need to test whether it corresponds to the
9782                         --  subprogram from which the generic formal primitive
9783                         --  is inherited.
9784
9785                         if Is_Abstract_Subprogram (Act_Subp) then
9786                            Anc_Subp := Alias (Gen_Subp);
9787
9788                            --  Test whether we have a corresponding primitive
9789                            --  by comparing names, kinds, formal types, and
9790                            --  result types.
9791
9792                            if Chars (Anc_Subp) = Chars (Act_Subp)
9793                              and then Ekind (Anc_Subp) = Ekind (Act_Subp)
9794                            then
9795                               Anc_Formal := First_Formal (Anc_Subp);
9796                               Act_Formal := First_Formal (Act_Subp);
9797                               while Present (Anc_Formal)
9798                                 and then Present (Act_Formal)
9799                               loop
9800                                  Anc_F_Type := Etype (Anc_Formal);
9801                                  Act_F_Type := Etype (Act_Formal);
9802
9803                                  if Ekind (Anc_F_Type)
9804                                       = E_Anonymous_Access_Type
9805                                  then
9806                                     Anc_F_Type := Designated_Type (Anc_F_Type);
9807
9808                                     if Ekind (Act_F_Type)
9809                                          = E_Anonymous_Access_Type
9810                                     then
9811                                        Act_F_Type :=
9812                                          Designated_Type (Act_F_Type);
9813                                     else
9814                                        exit;
9815                                     end if;
9816
9817                                  elsif
9818                                    Ekind (Act_F_Type) = E_Anonymous_Access_Type
9819                                  then
9820                                     exit;
9821                                  end if;
9822
9823                                  Anc_F_Type := Base_Type (Anc_F_Type);
9824                                  Act_F_Type := Base_Type (Act_F_Type);
9825
9826                                  --  If the formal is controlling, then the
9827                                  --  the type of the actual primitive's formal
9828                                  --  must be derived directly or indirectly
9829                                  --  from the type of the ancestor primitive's
9830                                  --  formal.
9831
9832                                  if Is_Controlling_Formal (Anc_Formal) then
9833                                     if not Is_Tagged_Ancestor
9834                                              (Anc_F_Type, Act_F_Type)
9835                                     then
9836                                        exit;
9837                                     end if;
9838
9839                                  --  Otherwise the types of the formals must
9840                                  --  be the same.
9841
9842                                  elsif Anc_F_Type /= Act_F_Type then
9843                                     exit;
9844                                  end if;
9845
9846                                  Next_Entity (Anc_Formal);
9847                                  Next_Entity (Act_Formal);
9848                               end loop;
9849
9850                               --  If we traversed through all of the formals
9851                               --  then so far the subprograms correspond, so
9852                               --  now check that any result types correspond.
9853
9854                               if No (Anc_Formal)
9855                                 and then No (Act_Formal)
9856                               then
9857                                  Subprograms_Correspond := True;
9858
9859                                  if Ekind (Act_Subp) = E_Function then
9860                                     Anc_F_Type := Etype (Anc_Subp);
9861                                     Act_F_Type := Etype (Act_Subp);
9862
9863                                     if Ekind (Anc_F_Type)
9864                                          = E_Anonymous_Access_Type
9865                                     then
9866                                        Anc_F_Type :=
9867                                          Designated_Type (Anc_F_Type);
9868
9869                                        if Ekind (Act_F_Type)
9870                                             = E_Anonymous_Access_Type
9871                                        then
9872                                           Act_F_Type :=
9873                                             Designated_Type (Act_F_Type);
9874                                        else
9875                                           Subprograms_Correspond := False;
9876                                        end if;
9877
9878                                     elsif
9879                                       Ekind (Act_F_Type)
9880                                         = E_Anonymous_Access_Type
9881                                     then
9882                                        Subprograms_Correspond := False;
9883                                     end if;
9884
9885                                     Anc_F_Type := Base_Type (Anc_F_Type);
9886                                     Act_F_Type := Base_Type (Act_F_Type);
9887
9888                                     --  Now either the result types must be
9889                                     --  the same or, if the result type is
9890                                     --  controlling, the result type of the
9891                                     --  actual primitive must descend from the
9892                                     --  result type of the ancestor primitive.
9893
9894                                     if Subprograms_Correspond
9895                                       and then Anc_F_Type /= Act_F_Type
9896                                       and then
9897                                         Has_Controlling_Result (Anc_Subp)
9898                                       and then
9899                                         not Is_Tagged_Ancestor
9900                                               (Anc_F_Type, Act_F_Type)
9901                                     then
9902                                        Subprograms_Correspond := False;
9903                                     end if;
9904                                  end if;
9905
9906                                  --  Found a matching subprogram belonging to
9907                                  --  formal ancestor type, so actual subprogram
9908                                  --  corresponds and this violates 3.9.3(9).
9909
9910                                  if Subprograms_Correspond then
9911                                     Error_Msg_NE
9912                                       ("abstract subprogram & overrides " &
9913                                        "nonabstract subprogram of ancestor",
9914                                        Actual,
9915                                        Act_Subp);
9916                                  end if;
9917                               end if;
9918                            end if;
9919                         end if;
9920
9921                         Next_Elmt (Act_Elmt);
9922                      end loop;
9923                   end if;
9924
9925                   Next_Elmt (Gen_Elmt);
9926                end loop;
9927             end Check_Abstract_Primitives;
9928          end if;
9929
9930          --  Verify that limitedness matches. If parent is a limited
9931          --  interface then  the generic formal is not unless declared
9932          --  explicitly so. If not declared limited, the actual cannot be
9933          --  limited (see AI05-0087).
9934          --  Disable check for now, limited interfaces implemented by
9935          --  protected types are common, Need to update tests ???
9936
9937          if Is_Limited_Type (Act_T)
9938            and then not Is_Limited_Type (A_Gen_T)
9939            and then False
9940          then
9941             Error_Msg_NE
9942               ("actual for non-limited & cannot be a limited type", Actual,
9943                Gen_T);
9944             Explain_Limited_Type (Act_T, Actual);
9945             Abandon_Instantiation (Actual);
9946          end if;
9947       end Validate_Derived_Type_Instance;
9948
9949       --------------------------------------
9950       -- Validate_Interface_Type_Instance --
9951       --------------------------------------
9952
9953       procedure Validate_Interface_Type_Instance is
9954       begin
9955          if not Is_Interface (Act_T) then
9956             Error_Msg_NE
9957               ("actual for formal interface type must be an interface",
9958                 Actual, Gen_T);
9959
9960          elsif Is_Limited_Type (Act_T) /= Is_Limited_Type (A_Gen_T)
9961            or else
9962              Is_Task_Interface (A_Gen_T) /= Is_Task_Interface (Act_T)
9963            or else
9964              Is_Protected_Interface (A_Gen_T) /=
9965                Is_Protected_Interface (Act_T)
9966            or else
9967              Is_Synchronized_Interface (A_Gen_T) /=
9968                Is_Synchronized_Interface (Act_T)
9969          then
9970             Error_Msg_NE
9971               ("actual for interface& does not match (RM 12.5.5(4))",
9972                Actual, Gen_T);
9973          end if;
9974       end Validate_Interface_Type_Instance;
9975
9976       ------------------------------------
9977       -- Validate_Private_Type_Instance --
9978       ------------------------------------
9979
9980       procedure Validate_Private_Type_Instance is
9981          Formal_Discr : Entity_Id;
9982          Actual_Discr : Entity_Id;
9983          Formal_Subt  : Entity_Id;
9984
9985       begin
9986          if Is_Limited_Type (Act_T)
9987            and then not Is_Limited_Type (A_Gen_T)
9988          then
9989             Error_Msg_NE
9990               ("actual for non-limited & cannot be a limited type", Actual,
9991                Gen_T);
9992             Explain_Limited_Type (Act_T, Actual);
9993             Abandon_Instantiation (Actual);
9994
9995          elsif Known_To_Have_Preelab_Init (A_Gen_T)
9996            and then not Has_Preelaborable_Initialization (Act_T)
9997          then
9998             Error_Msg_NE
9999               ("actual for & must have preelaborable initialization", Actual,
10000                Gen_T);
10001
10002          elsif Is_Indefinite_Subtype (Act_T)
10003             and then not Is_Indefinite_Subtype (A_Gen_T)
10004             and then Ada_Version >= Ada_95
10005          then
10006             Error_Msg_NE
10007               ("actual for & must be a definite subtype", Actual, Gen_T);
10008
10009          elsif not Is_Tagged_Type (Act_T)
10010            and then Is_Tagged_Type (A_Gen_T)
10011          then
10012             Error_Msg_NE
10013               ("actual for & must be a tagged type", Actual, Gen_T);
10014
10015          elsif Has_Discriminants (A_Gen_T) then
10016             if not Has_Discriminants (Act_T) then
10017                Error_Msg_NE
10018                  ("actual for & must have discriminants", Actual, Gen_T);
10019                Abandon_Instantiation (Actual);
10020
10021             elsif Is_Constrained (Act_T) then
10022                Error_Msg_NE
10023                  ("actual for & must be unconstrained", Actual, Gen_T);
10024                Abandon_Instantiation (Actual);
10025
10026             else
10027                Formal_Discr := First_Discriminant (A_Gen_T);
10028                Actual_Discr := First_Discriminant (Act_T);
10029                while Formal_Discr /= Empty loop
10030                   if Actual_Discr = Empty then
10031                      Error_Msg_NE
10032                        ("discriminants on actual do not match formal",
10033                         Actual, Gen_T);
10034                      Abandon_Instantiation (Actual);
10035                   end if;
10036
10037                   Formal_Subt := Get_Instance_Of (Etype (Formal_Discr));
10038
10039                   --  Access discriminants match if designated types do
10040
10041                   if Ekind (Base_Type (Formal_Subt)) = E_Anonymous_Access_Type
10042                     and then (Ekind (Base_Type (Etype (Actual_Discr)))) =
10043                                 E_Anonymous_Access_Type
10044                     and then
10045                       Get_Instance_Of
10046                         (Designated_Type (Base_Type (Formal_Subt))) =
10047                            Designated_Type (Base_Type (Etype (Actual_Discr)))
10048                   then
10049                      null;
10050
10051                   elsif Base_Type (Formal_Subt) /=
10052                           Base_Type (Etype (Actual_Discr))
10053                   then
10054                      Error_Msg_NE
10055                        ("types of actual discriminants must match formal",
10056                         Actual, Gen_T);
10057                      Abandon_Instantiation (Actual);
10058
10059                   elsif not Subtypes_Statically_Match
10060                               (Formal_Subt, Etype (Actual_Discr))
10061                     and then Ada_Version >= Ada_95
10062                   then
10063                      Error_Msg_NE
10064                        ("subtypes of actual discriminants must match formal",
10065                         Actual, Gen_T);
10066                      Abandon_Instantiation (Actual);
10067                   end if;
10068
10069                   Next_Discriminant (Formal_Discr);
10070                   Next_Discriminant (Actual_Discr);
10071                end loop;
10072
10073                if Actual_Discr /= Empty then
10074                   Error_Msg_NE
10075                     ("discriminants on actual do not match formal",
10076                      Actual, Gen_T);
10077                   Abandon_Instantiation (Actual);
10078                end if;
10079             end if;
10080
10081          end if;
10082
10083          Ancestor := Gen_T;
10084       end Validate_Private_Type_Instance;
10085
10086    --  Start of processing for Instantiate_Type
10087
10088    begin
10089       if Get_Instance_Of (A_Gen_T) /= A_Gen_T then
10090          Error_Msg_N ("duplicate instantiation of generic type", Actual);
10091          return New_List (Error);
10092
10093       elsif not Is_Entity_Name (Actual)
10094         or else not Is_Type (Entity (Actual))
10095       then
10096          Error_Msg_NE
10097            ("expect valid subtype mark to instantiate &", Actual, Gen_T);
10098          Abandon_Instantiation (Actual);
10099
10100       else
10101          Act_T := Entity (Actual);
10102
10103          --  Ada 2005 (AI-216): An Unchecked_Union subtype shall only be passed
10104          --  as a generic actual parameter if the corresponding formal type
10105          --  does not have a known_discriminant_part, or is a formal derived
10106          --  type that is an Unchecked_Union type.
10107
10108          if Is_Unchecked_Union (Base_Type (Act_T)) then
10109             if not Has_Discriminants (A_Gen_T)
10110                      or else
10111                    (Is_Derived_Type (A_Gen_T)
10112                      and then
10113                     Is_Unchecked_Union (A_Gen_T))
10114             then
10115                null;
10116             else
10117                Error_Msg_N ("Unchecked_Union cannot be the actual for a" &
10118                  " discriminated formal type", Act_T);
10119
10120             end if;
10121          end if;
10122
10123          --  Deal with fixed/floating restrictions
10124
10125          if Is_Floating_Point_Type (Act_T) then
10126             Check_Restriction (No_Floating_Point, Actual);
10127          elsif Is_Fixed_Point_Type (Act_T) then
10128             Check_Restriction (No_Fixed_Point, Actual);
10129          end if;
10130
10131          --  Deal with error of using incomplete type as generic actual.
10132          --  This includes limited views of a type, even if the non-limited
10133          --  view may be available.
10134
10135          if Ekind (Act_T) = E_Incomplete_Type
10136            or else (Is_Class_Wide_Type (Act_T)
10137                       and then
10138                          Ekind (Root_Type (Act_T)) = E_Incomplete_Type)
10139          then
10140             if Is_Class_Wide_Type (Act_T)
10141               or else No (Full_View (Act_T))
10142             then
10143                Error_Msg_N ("premature use of incomplete type", Actual);
10144                Abandon_Instantiation (Actual);
10145             else
10146                Act_T := Full_View (Act_T);
10147                Set_Entity (Actual, Act_T);
10148
10149                if Has_Private_Component (Act_T) then
10150                   Error_Msg_N
10151                     ("premature use of type with private component", Actual);
10152                end if;
10153             end if;
10154
10155          --  Deal with error of premature use of private type as generic actual
10156
10157          elsif Is_Private_Type (Act_T)
10158            and then Is_Private_Type (Base_Type (Act_T))
10159            and then not Is_Generic_Type (Act_T)
10160            and then not Is_Derived_Type (Act_T)
10161            and then No (Full_View (Root_Type (Act_T)))
10162          then
10163             Error_Msg_N ("premature use of private type", Actual);
10164
10165          elsif Has_Private_Component (Act_T) then
10166             Error_Msg_N
10167               ("premature use of type with private component", Actual);
10168          end if;
10169
10170          Set_Instance_Of (A_Gen_T, Act_T);
10171
10172          --  If the type is generic, the class-wide type may also be used
10173
10174          if Is_Tagged_Type (A_Gen_T)
10175            and then Is_Tagged_Type (Act_T)
10176            and then not Is_Class_Wide_Type (A_Gen_T)
10177          then
10178             Set_Instance_Of (Class_Wide_Type (A_Gen_T),
10179               Class_Wide_Type (Act_T));
10180          end if;
10181
10182          if not Is_Abstract_Type (A_Gen_T)
10183            and then Is_Abstract_Type (Act_T)
10184          then
10185             Error_Msg_N
10186               ("actual of non-abstract formal cannot be abstract", Actual);
10187          end if;
10188
10189          --  A generic scalar type is a first subtype for which we generate
10190          --  an anonymous base type. Indicate that the instance of this base
10191          --  is the base type of the actual.
10192
10193          if Is_Scalar_Type (A_Gen_T) then
10194             Set_Instance_Of (Etype (A_Gen_T), Etype (Act_T));
10195          end if;
10196       end if;
10197
10198       if Error_Posted (Act_T) then
10199          null;
10200       else
10201          case Nkind (Def) is
10202             when N_Formal_Private_Type_Definition =>
10203                Validate_Private_Type_Instance;
10204
10205             when N_Formal_Derived_Type_Definition =>
10206                Validate_Derived_Type_Instance;
10207
10208             when N_Formal_Discrete_Type_Definition =>
10209                if not Is_Discrete_Type (Act_T) then
10210                   Error_Msg_NE
10211                     ("expect discrete type in instantiation of&",
10212                        Actual, Gen_T);
10213                   Abandon_Instantiation (Actual);
10214                end if;
10215
10216             when N_Formal_Signed_Integer_Type_Definition =>
10217                if not Is_Signed_Integer_Type (Act_T) then
10218                   Error_Msg_NE
10219                     ("expect signed integer type in instantiation of&",
10220                      Actual, Gen_T);
10221                   Abandon_Instantiation (Actual);
10222                end if;
10223
10224             when N_Formal_Modular_Type_Definition =>
10225                if not Is_Modular_Integer_Type (Act_T) then
10226                   Error_Msg_NE
10227                     ("expect modular type in instantiation of &",
10228                        Actual, Gen_T);
10229                   Abandon_Instantiation (Actual);
10230                end if;
10231
10232             when N_Formal_Floating_Point_Definition =>
10233                if not Is_Floating_Point_Type (Act_T) then
10234                   Error_Msg_NE
10235                     ("expect float type in instantiation of &", Actual, Gen_T);
10236                   Abandon_Instantiation (Actual);
10237                end if;
10238
10239             when N_Formal_Ordinary_Fixed_Point_Definition =>
10240                if not Is_Ordinary_Fixed_Point_Type (Act_T) then
10241                   Error_Msg_NE
10242                     ("expect ordinary fixed point type in instantiation of &",
10243                      Actual, Gen_T);
10244                   Abandon_Instantiation (Actual);
10245                end if;
10246
10247             when N_Formal_Decimal_Fixed_Point_Definition =>
10248                if not Is_Decimal_Fixed_Point_Type (Act_T) then
10249                   Error_Msg_NE
10250                     ("expect decimal type in instantiation of &",
10251                      Actual, Gen_T);
10252                   Abandon_Instantiation (Actual);
10253                end if;
10254
10255             when N_Array_Type_Definition =>
10256                Validate_Array_Type_Instance;
10257
10258             when N_Access_To_Object_Definition =>
10259                Validate_Access_Type_Instance;
10260
10261             when N_Access_Function_Definition |
10262                  N_Access_Procedure_Definition =>
10263                Validate_Access_Subprogram_Instance;
10264
10265             when N_Record_Definition           =>
10266                Validate_Interface_Type_Instance;
10267
10268             when N_Derived_Type_Definition     =>
10269                Validate_Derived_Interface_Type_Instance;
10270
10271             when others =>
10272                raise Program_Error;
10273
10274          end case;
10275       end if;
10276
10277       Subt := New_Copy (Gen_T);
10278
10279       --  Use adjusted sloc of subtype name as the location for other nodes in
10280       --  the subtype declaration.
10281
10282       Loc  := Sloc (Subt);
10283
10284       Decl_Node :=
10285         Make_Subtype_Declaration (Loc,
10286           Defining_Identifier => Subt,
10287           Subtype_Indication  => New_Reference_To (Act_T, Loc));
10288
10289       if Is_Private_Type (Act_T) then
10290          Set_Has_Private_View (Subtype_Indication (Decl_Node));
10291
10292       elsif Is_Access_Type (Act_T)
10293         and then Is_Private_Type (Designated_Type (Act_T))
10294       then
10295          Set_Has_Private_View (Subtype_Indication (Decl_Node));
10296       end if;
10297
10298       Decl_Nodes := New_List (Decl_Node);
10299
10300       --  Flag actual derived types so their elaboration produces the
10301       --  appropriate renamings for the primitive operations of the ancestor.
10302       --  Flag actual for formal private types as well, to determine whether
10303       --  operations in the private part may override inherited operations.
10304       --  If the formal has an interface list, the ancestor is not the
10305       --  parent, but the analyzed formal that includes the interface
10306       --  operations of all its progenitors.
10307
10308       if Nkind (Def) = N_Formal_Derived_Type_Definition then
10309          if Present (Interface_List (Def)) then
10310             Set_Generic_Parent_Type (Decl_Node, A_Gen_T);
10311          else
10312             Set_Generic_Parent_Type (Decl_Node, Ancestor);
10313          end if;
10314
10315       elsif Nkind (Def) = N_Formal_Private_Type_Definition then
10316          Set_Generic_Parent_Type (Decl_Node, Ancestor);
10317       end if;
10318
10319       --  If the actual is a synchronized type that implements an interface,
10320       --  the primitive operations are attached to the corresponding record,
10321       --  and we have to treat it as an additional generic actual, so that its
10322       --  primitive operations become visible in the instance. The task or
10323       --  protected type itself does not carry primitive operations.
10324
10325       if Is_Concurrent_Type (Act_T)
10326         and then Is_Tagged_Type (Act_T)
10327         and then Present (Corresponding_Record_Type (Act_T))
10328         and then Present (Ancestor)
10329         and then Is_Interface (Ancestor)
10330       then
10331          declare
10332             Corr_Rec  : constant Entity_Id :=
10333                           Corresponding_Record_Type (Act_T);
10334             New_Corr  : Entity_Id;
10335             Corr_Decl : Node_Id;
10336
10337          begin
10338             New_Corr := Make_Defining_Identifier (Loc,
10339                             Chars => New_Internal_Name  ('S'));
10340             Corr_Decl :=
10341               Make_Subtype_Declaration (Loc,
10342                 Defining_Identifier => New_Corr,
10343                 Subtype_Indication  =>
10344                   New_Reference_To (Corr_Rec, Loc));
10345             Append_To (Decl_Nodes, Corr_Decl);
10346
10347             if Ekind (Act_T) = E_Task_Type then
10348                Set_Ekind (Subt, E_Task_Subtype);
10349             else
10350                Set_Ekind (Subt, E_Protected_Subtype);
10351             end if;
10352
10353             Set_Corresponding_Record_Type (Subt, Corr_Rec);
10354             Set_Generic_Parent_Type (Corr_Decl, Ancestor);
10355             Set_Generic_Parent_Type (Decl_Node, Empty);
10356          end;
10357       end if;
10358
10359       return Decl_Nodes;
10360    end Instantiate_Type;
10361
10362    -----------------------
10363    -- Is_Generic_Formal --
10364    -----------------------
10365
10366    function Is_Generic_Formal (E : Entity_Id) return Boolean is
10367       Kind : Node_Kind;
10368    begin
10369       if No (E) then
10370          return False;
10371       else
10372          Kind := Nkind (Parent (E));
10373          return
10374            Nkind_In (Kind, N_Formal_Object_Declaration,
10375                            N_Formal_Package_Declaration,
10376                            N_Formal_Type_Declaration)
10377              or else
10378                (Is_Formal_Subprogram (E)
10379                  and then
10380                    Nkind (Parent (Parent (E))) in
10381                      N_Formal_Subprogram_Declaration);
10382       end if;
10383    end Is_Generic_Formal;
10384
10385    ---------------------
10386    -- Is_In_Main_Unit --
10387    ---------------------
10388
10389    function Is_In_Main_Unit (N : Node_Id) return Boolean is
10390       Unum         : constant Unit_Number_Type := Get_Source_Unit (N);
10391       Current_Unit : Node_Id;
10392
10393    begin
10394       if Unum = Main_Unit then
10395          return True;
10396
10397       --  If the current unit is a subunit then it is either the main unit or
10398       --  is being compiled as part of the main unit.
10399
10400       elsif Nkind (N) = N_Compilation_Unit then
10401          return Nkind (Unit (N)) = N_Subunit;
10402       end if;
10403
10404       Current_Unit := Parent (N);
10405       while Present (Current_Unit)
10406         and then Nkind (Current_Unit) /= N_Compilation_Unit
10407       loop
10408          Current_Unit := Parent (Current_Unit);
10409       end loop;
10410
10411       --  The instantiation node is in the main unit, or else the current node
10412       --  (perhaps as the result of nested instantiations) is in the main unit,
10413       --  or in the declaration of the main unit, which in this last case must
10414       --  be a body.
10415
10416       return Unum = Main_Unit
10417         or else Current_Unit = Cunit (Main_Unit)
10418         or else Current_Unit = Library_Unit (Cunit (Main_Unit))
10419         or else (Present (Library_Unit (Current_Unit))
10420                   and then Is_In_Main_Unit (Library_Unit (Current_Unit)));
10421    end Is_In_Main_Unit;
10422
10423    ----------------------------
10424    -- Load_Parent_Of_Generic --
10425    ----------------------------
10426
10427    procedure Load_Parent_Of_Generic
10428      (N             : Node_Id;
10429       Spec          : Node_Id;
10430       Body_Optional : Boolean := False)
10431    is
10432       Comp_Unit          : constant Node_Id := Cunit (Get_Source_Unit (Spec));
10433       Save_Style_Check   : constant Boolean := Style_Check;
10434       True_Parent        : Node_Id;
10435       Inst_Node          : Node_Id;
10436       OK                 : Boolean;
10437       Previous_Instances : constant Elist_Id := New_Elmt_List;
10438
10439       procedure Collect_Previous_Instances (Decls : List_Id);
10440       --  Collect all instantiations in the given list of declarations, that
10441       --  precede the generic that we need to load. If the bodies of these
10442       --  instantiations are available, we must analyze them, to ensure that
10443       --  the public symbols generated are the same when the unit is compiled
10444       --  to generate code, and when it is compiled in the context of a unit
10445       --  that needs a particular nested instance. This process is applied
10446       --  to both package and subprogram instances.
10447
10448       --------------------------------
10449       -- Collect_Previous_Instances --
10450       --------------------------------
10451
10452       procedure Collect_Previous_Instances (Decls : List_Id) is
10453          Decl : Node_Id;
10454
10455       begin
10456          Decl := First (Decls);
10457          while Present (Decl) loop
10458             if Sloc (Decl) >= Sloc (Inst_Node) then
10459                return;
10460
10461             --  If Decl is an instantiation, then record it as requiring
10462             --  instantiation of the corresponding body, except if it is an
10463             --  abbreviated instantiation generated internally for conformance
10464             --  checking purposes only for the case of a formal package
10465             --  declared without a box (see Instantiate_Formal_Package). Such
10466             --  an instantiation does not generate any code (the actual code
10467             --  comes from actual) and thus does not need to be analyzed here.
10468             --  If the instantiation appears with a generic package body it is
10469             --  not analyzed here either.
10470
10471             elsif Nkind (Decl) = N_Package_Instantiation
10472               and then not Is_Internal (Defining_Entity (Decl))
10473             then
10474                Append_Elmt (Decl, Previous_Instances);
10475
10476             --  For a subprogram instantiation, omit instantiations intrinsic
10477             --  operations (Unchecked_Conversions, etc.) that have no bodies.
10478
10479             elsif Nkind_In (Decl, N_Function_Instantiation,
10480                                   N_Procedure_Instantiation)
10481               and then not Is_Intrinsic_Subprogram (Entity (Name (Decl)))
10482             then
10483                Append_Elmt (Decl, Previous_Instances);
10484
10485             elsif Nkind (Decl) = N_Package_Declaration then
10486                Collect_Previous_Instances
10487                  (Visible_Declarations (Specification (Decl)));
10488                Collect_Previous_Instances
10489                  (Private_Declarations (Specification (Decl)));
10490
10491             elsif Nkind (Decl) = N_Package_Body
10492               and then Ekind (Corresponding_Spec (Decl)) /= E_Generic_Package
10493             then
10494                Collect_Previous_Instances (Declarations (Decl));
10495             end if;
10496
10497             Next (Decl);
10498          end loop;
10499       end Collect_Previous_Instances;
10500
10501    --  Start of processing for Load_Parent_Of_Generic
10502
10503    begin
10504       if not In_Same_Source_Unit (N, Spec)
10505         or else Nkind (Unit (Comp_Unit)) = N_Package_Declaration
10506         or else (Nkind (Unit (Comp_Unit)) = N_Package_Body
10507                    and then not Is_In_Main_Unit (Spec))
10508       then
10509          --  Find body of parent of spec, and analyze it. A special case arises
10510          --  when the parent is an instantiation, that is to say when we are
10511          --  currently instantiating a nested generic. In that case, there is
10512          --  no separate file for the body of the enclosing instance. Instead,
10513          --  the enclosing body must be instantiated as if it were a pending
10514          --  instantiation, in order to produce the body for the nested generic
10515          --  we require now. Note that in that case the generic may be defined
10516          --  in a package body, the instance defined in the same package body,
10517          --  and the original enclosing body may not be in the main unit.
10518
10519          Inst_Node := Empty;
10520
10521          True_Parent := Parent (Spec);
10522          while Present (True_Parent)
10523            and then Nkind (True_Parent) /= N_Compilation_Unit
10524          loop
10525             if Nkind (True_Parent) = N_Package_Declaration
10526                  and then
10527                Nkind (Original_Node (True_Parent)) = N_Package_Instantiation
10528             then
10529                --  Parent is a compilation unit that is an instantiation.
10530                --  Instantiation node has been replaced with package decl.
10531
10532                Inst_Node := Original_Node (True_Parent);
10533                exit;
10534
10535             elsif Nkind (True_Parent) = N_Package_Declaration
10536               and then Present (Generic_Parent (Specification (True_Parent)))
10537               and then Nkind (Parent (True_Parent)) /= N_Compilation_Unit
10538             then
10539                --  Parent is an instantiation within another specification.
10540                --  Declaration for instance has been inserted before original
10541                --  instantiation node. A direct link would be preferable?
10542
10543                Inst_Node := Next (True_Parent);
10544                while Present (Inst_Node)
10545                  and then Nkind (Inst_Node) /= N_Package_Instantiation
10546                loop
10547                   Next (Inst_Node);
10548                end loop;
10549
10550                --  If the instance appears within a generic, and the generic
10551                --  unit is defined within a formal package of the enclosing
10552                --  generic, there is no generic body available, and none
10553                --  needed. A more precise test should be used ???
10554
10555                if No (Inst_Node) then
10556                   return;
10557                end if;
10558
10559                exit;
10560
10561             else
10562                True_Parent := Parent (True_Parent);
10563             end if;
10564          end loop;
10565
10566          --  Case where we are currently instantiating a nested generic
10567
10568          if Present (Inst_Node) then
10569             if Nkind (Parent (True_Parent)) = N_Compilation_Unit then
10570
10571                --  Instantiation node and declaration of instantiated package
10572                --  were exchanged when only the declaration was needed.
10573                --  Restore instantiation node before proceeding with body.
10574
10575                Set_Unit (Parent (True_Parent), Inst_Node);
10576             end if;
10577
10578             --  Now complete instantiation of enclosing body, if it appears in
10579             --  some other unit. If it appears in the current unit, the body
10580             --  will have been instantiated already.
10581
10582             if No (Corresponding_Body (Instance_Spec (Inst_Node))) then
10583
10584                --  We need to determine the expander mode to instantiate the
10585                --  enclosing body. Because the generic body we need may use
10586                --  global entities declared in the enclosing package (including
10587                --  aggregates) it is in general necessary to compile this body
10588                --  with expansion enabled. The exception is if we are within a
10589                --  generic package, in which case the usual generic rule
10590                --  applies.
10591
10592                declare
10593                   Exp_Status         : Boolean := True;
10594                   Scop               : Entity_Id;
10595
10596                begin
10597                   --  Loop through scopes looking for generic package
10598
10599                   Scop := Scope (Defining_Entity (Instance_Spec (Inst_Node)));
10600                   while Present (Scop)
10601                     and then Scop /= Standard_Standard
10602                   loop
10603                      if Ekind (Scop) = E_Generic_Package then
10604                         Exp_Status := False;
10605                         exit;
10606                      end if;
10607
10608                      Scop := Scope (Scop);
10609                   end loop;
10610
10611                   --  Collect previous instantiations in the unit that contains
10612                   --  the desired generic.
10613
10614                   if Nkind (Parent (True_Parent)) /= N_Compilation_Unit
10615                     and then not Body_Optional
10616                   then
10617                      declare
10618                         Decl : Elmt_Id;
10619                         Info : Pending_Body_Info;
10620                         Par  : Node_Id;
10621
10622                      begin
10623                         Par := Parent (Inst_Node);
10624                         while Present (Par) loop
10625                            exit when Nkind (Parent (Par)) = N_Compilation_Unit;
10626                            Par := Parent (Par);
10627                         end loop;
10628
10629                         pragma Assert (Present (Par));
10630
10631                         if Nkind (Par) = N_Package_Body then
10632                            Collect_Previous_Instances (Declarations (Par));
10633
10634                         elsif Nkind (Par) = N_Package_Declaration then
10635                            Collect_Previous_Instances
10636                              (Visible_Declarations (Specification (Par)));
10637                            Collect_Previous_Instances
10638                              (Private_Declarations (Specification (Par)));
10639
10640                         else
10641                            --  Enclosing unit is a subprogram body. In this
10642                            --  case all instance bodies are processed in order
10643                            --  and there is no need to collect them separately.
10644
10645                            null;
10646                         end if;
10647
10648                         Decl := First_Elmt (Previous_Instances);
10649                         while Present (Decl) loop
10650                            Info :=
10651                              (Inst_Node                => Node (Decl),
10652                               Act_Decl                 =>
10653                                 Instance_Spec (Node (Decl)),
10654                               Expander_Status          => Exp_Status,
10655                               Current_Sem_Unit         =>
10656                                 Get_Code_Unit (Sloc (Node (Decl))),
10657                               Scope_Suppress           => Scope_Suppress,
10658                               Local_Suppress_Stack_Top =>
10659                                 Local_Suppress_Stack_Top);
10660
10661                            --  Package instance
10662
10663                            if
10664                              Nkind (Node (Decl)) = N_Package_Instantiation
10665                            then
10666                               Instantiate_Package_Body
10667                                 (Info, Body_Optional => True);
10668
10669                            --  Subprogram instance
10670
10671                            else
10672                               --  The instance_spec is the wrapper package,
10673                               --  and the subprogram declaration is the last
10674                               --  declaration in the wrapper.
10675
10676                               Info.Act_Decl :=
10677                                 Last
10678                                   (Visible_Declarations
10679                                     (Specification (Info.Act_Decl)));
10680
10681                               Instantiate_Subprogram_Body
10682                                 (Info, Body_Optional => True);
10683                            end if;
10684
10685                            Next_Elmt (Decl);
10686                         end loop;
10687                      end;
10688                   end if;
10689
10690                   Instantiate_Package_Body
10691                     (Body_Info =>
10692                        ((Inst_Node                => Inst_Node,
10693                          Act_Decl                 => True_Parent,
10694                          Expander_Status          => Exp_Status,
10695                          Current_Sem_Unit         =>
10696                            Get_Code_Unit (Sloc (Inst_Node)),
10697                          Scope_Suppress           => Scope_Suppress,
10698                          Local_Suppress_Stack_Top =>
10699                            Local_Suppress_Stack_Top)),
10700                      Body_Optional => Body_Optional);
10701                end;
10702             end if;
10703
10704          --  Case where we are not instantiating a nested generic
10705
10706          else
10707             Opt.Style_Check := False;
10708             Expander_Mode_Save_And_Set (True);
10709             Load_Needed_Body (Comp_Unit, OK);
10710             Opt.Style_Check := Save_Style_Check;
10711             Expander_Mode_Restore;
10712
10713             if not OK
10714               and then Unit_Requires_Body (Defining_Entity (Spec))
10715               and then not Body_Optional
10716             then
10717                declare
10718                   Bname : constant Unit_Name_Type :=
10719                             Get_Body_Name (Get_Unit_Name (Unit (Comp_Unit)));
10720
10721                begin
10722                   Error_Msg_Unit_1 := Bname;
10723                   Error_Msg_N ("this instantiation requires$!", N);
10724                   Error_Msg_File_1 := Get_File_Name (Bname, Subunit => False);
10725                   Error_Msg_N ("\but file{ was not found!", N);
10726                   raise Unrecoverable_Error;
10727                end;
10728             end if;
10729          end if;
10730       end if;
10731
10732       --  If loading parent of the generic caused an instantiation circularity,
10733       --  we abandon compilation at this point, because otherwise in some cases
10734       --  we get into trouble with infinite recursions after this point.
10735
10736       if Circularity_Detected then
10737          raise Unrecoverable_Error;
10738       end if;
10739    end Load_Parent_Of_Generic;
10740
10741    ---------------------------------
10742    -- Map_Formal_Package_Entities --
10743    ---------------------------------
10744
10745    procedure Map_Formal_Package_Entities (Form : Entity_Id; Act : Entity_Id) is
10746       E1 : Entity_Id;
10747       E2 : Entity_Id;
10748
10749    begin
10750       Set_Instance_Of (Form, Act);
10751
10752       --  Traverse formal and actual package to map the corresponding entities.
10753       --  We skip over internal entities that may be generated during semantic
10754       --  analysis, and find the matching entities by name, given that they
10755       --  must appear in the same order.
10756
10757       E1 := First_Entity (Form);
10758       E2 := First_Entity (Act);
10759       while Present (E1) and then E1 /= First_Private_Entity (Form) loop
10760          --  Could this test be a single condition???
10761          --  Seems like it could, and isn't FPE (Form) a constant anyway???
10762
10763          if not Is_Internal (E1)
10764            and then Present (Parent (E1))
10765            and then not Is_Class_Wide_Type (E1)
10766            and then not Is_Internal_Name (Chars (E1))
10767          then
10768             while Present (E2) and then Chars (E2) /= Chars (E1) loop
10769                Next_Entity (E2);
10770             end loop;
10771
10772             if No (E2) then
10773                exit;
10774             else
10775                Set_Instance_Of (E1, E2);
10776
10777                if Is_Type (E1) and then Is_Tagged_Type (E2) then
10778                   Set_Instance_Of (Class_Wide_Type (E1), Class_Wide_Type (E2));
10779                end if;
10780
10781                if Is_Constrained (E1) then
10782                   Set_Instance_Of (Base_Type (E1), Base_Type (E2));
10783                end if;
10784
10785                if Ekind (E1) = E_Package and then No (Renamed_Object (E1)) then
10786                   Map_Formal_Package_Entities (E1, E2);
10787                end if;
10788             end if;
10789          end if;
10790
10791          Next_Entity (E1);
10792       end loop;
10793    end Map_Formal_Package_Entities;
10794
10795    -----------------------
10796    -- Move_Freeze_Nodes --
10797    -----------------------
10798
10799    procedure Move_Freeze_Nodes
10800      (Out_Of : Entity_Id;
10801       After  : Node_Id;
10802       L      : List_Id)
10803    is
10804       Decl      : Node_Id;
10805       Next_Decl : Node_Id;
10806       Next_Node : Node_Id := After;
10807       Spec      : Node_Id;
10808
10809       function Is_Outer_Type (T : Entity_Id) return Boolean;
10810       --  Check whether entity is declared in a scope external to that of the
10811       --  generic unit.
10812
10813       -------------------
10814       -- Is_Outer_Type --
10815       -------------------
10816
10817       function Is_Outer_Type (T : Entity_Id) return Boolean is
10818          Scop : Entity_Id := Scope (T);
10819
10820       begin
10821          if Scope_Depth (Scop) < Scope_Depth (Out_Of) then
10822             return True;
10823
10824          else
10825             while Scop /= Standard_Standard loop
10826                if Scop = Out_Of then
10827                   return False;
10828                else
10829                   Scop := Scope (Scop);
10830                end if;
10831             end loop;
10832
10833             return True;
10834          end if;
10835       end Is_Outer_Type;
10836
10837    --  Start of processing for Move_Freeze_Nodes
10838
10839    begin
10840       if No (L) then
10841          return;
10842       end if;
10843
10844       --  First remove the freeze nodes that may appear before all other
10845       --  declarations.
10846
10847       Decl := First (L);
10848       while Present (Decl)
10849         and then Nkind (Decl) = N_Freeze_Entity
10850         and then Is_Outer_Type (Entity (Decl))
10851       loop
10852          Decl := Remove_Head (L);
10853          Insert_After (Next_Node, Decl);
10854          Set_Analyzed (Decl, False);
10855          Next_Node := Decl;
10856          Decl := First (L);
10857       end loop;
10858
10859       --  Next scan the list of declarations and remove each freeze node that
10860       --  appears ahead of the current node.
10861
10862       while Present (Decl) loop
10863          while Present (Next (Decl))
10864            and then Nkind (Next (Decl)) = N_Freeze_Entity
10865            and then Is_Outer_Type (Entity (Next (Decl)))
10866          loop
10867             Next_Decl := Remove_Next (Decl);
10868             Insert_After (Next_Node, Next_Decl);
10869             Set_Analyzed (Next_Decl, False);
10870             Next_Node := Next_Decl;
10871          end loop;
10872
10873          --  If the declaration is a nested package or concurrent type, then
10874          --  recurse. Nested generic packages will have been processed from the
10875          --  inside out.
10876
10877          case Nkind (Decl) is
10878             when N_Package_Declaration =>
10879                Spec := Specification (Decl);
10880
10881             when N_Task_Type_Declaration =>
10882                Spec := Task_Definition (Decl);
10883
10884             when N_Protected_Type_Declaration =>
10885                Spec := Protected_Definition (Decl);
10886
10887             when others =>
10888                Spec := Empty;
10889          end case;
10890
10891          if Present (Spec) then
10892             Move_Freeze_Nodes (Out_Of, Next_Node, Visible_Declarations (Spec));
10893             Move_Freeze_Nodes (Out_Of, Next_Node, Private_Declarations (Spec));
10894          end if;
10895
10896          Next (Decl);
10897       end loop;
10898    end Move_Freeze_Nodes;
10899
10900    ----------------
10901    -- Next_Assoc --
10902    ----------------
10903
10904    function Next_Assoc (E : Assoc_Ptr) return Assoc_Ptr is
10905    begin
10906       return Generic_Renamings.Table (E).Next_In_HTable;
10907    end Next_Assoc;
10908
10909    ------------------------
10910    -- Preanalyze_Actuals --
10911    ------------------------
10912
10913    procedure Preanalyze_Actuals (N : Node_Id) is
10914       Assoc : Node_Id;
10915       Act   : Node_Id;
10916       Errs  : constant Int := Serious_Errors_Detected;
10917
10918       Cur : Entity_Id := Empty;
10919       --  Current homograph of the instance name
10920
10921       Vis : Boolean;
10922       --  Saved visibility status of the current homograph
10923
10924    begin
10925       Assoc := First (Generic_Associations (N));
10926
10927       --  If the instance is a child unit, its name may hide an outer homonym,
10928       --  so make it invisible to perform name resolution on the actuals.
10929
10930       if Nkind (Defining_Unit_Name (N)) = N_Defining_Program_Unit_Name
10931         and then Present
10932           (Current_Entity (Defining_Identifier (Defining_Unit_Name (N))))
10933       then
10934          Cur := Current_Entity (Defining_Identifier (Defining_Unit_Name (N)));
10935
10936          if Is_Compilation_Unit (Cur) then
10937             Vis := Is_Immediately_Visible (Cur);
10938             Set_Is_Immediately_Visible (Cur, False);
10939          else
10940             Cur := Empty;
10941          end if;
10942       end if;
10943
10944       while Present (Assoc) loop
10945          if Nkind (Assoc) /= N_Others_Choice then
10946             Act := Explicit_Generic_Actual_Parameter (Assoc);
10947
10948             --  Within a nested instantiation, a defaulted actual is an empty
10949             --  association, so nothing to analyze. If the subprogram actual
10950             --  is an attribute, analyze prefix only, because actual is not a
10951             --  complete attribute reference.
10952
10953             --  If actual is an allocator, analyze expression only. The full
10954             --  analysis can generate code, and if instance is a compilation
10955             --  unit we have to wait until the package instance is installed
10956             --  to have a proper place to insert this code.
10957
10958             --  String literals may be operators, but at this point we do not
10959             --  know whether the actual is a formal subprogram or a string.
10960
10961             if No (Act) then
10962                null;
10963
10964             elsif Nkind (Act) = N_Attribute_Reference then
10965                Analyze (Prefix (Act));
10966
10967             elsif Nkind (Act) = N_Explicit_Dereference then
10968                Analyze (Prefix (Act));
10969
10970             elsif Nkind (Act) = N_Allocator then
10971                declare
10972                   Expr : constant Node_Id := Expression (Act);
10973
10974                begin
10975                   if Nkind (Expr) = N_Subtype_Indication then
10976                      Analyze (Subtype_Mark (Expr));
10977
10978                      --  Analyze separately each discriminant constraint, when
10979                      --  given with a named association.
10980
10981                      declare
10982                         Constr : Node_Id;
10983
10984                      begin
10985                         Constr := First (Constraints (Constraint (Expr)));
10986                         while Present (Constr) loop
10987                            if Nkind (Constr) = N_Discriminant_Association then
10988                               Analyze (Expression (Constr));
10989                            else
10990                               Analyze (Constr);
10991                            end if;
10992
10993                            Next (Constr);
10994                         end loop;
10995                      end;
10996
10997                   else
10998                      Analyze (Expr);
10999                   end if;
11000                end;
11001
11002             elsif Nkind (Act) /= N_Operator_Symbol then
11003                Analyze (Act);
11004             end if;
11005
11006             if Errs /= Serious_Errors_Detected then
11007
11008                --  Do a minimal analysis of the generic, to prevent spurious
11009                --  warnings complaining about the generic being unreferenced,
11010                --  before abandoning the instantiation.
11011
11012                Analyze (Name (N));
11013
11014                if Is_Entity_Name (Name (N))
11015                  and then Etype (Name (N)) /= Any_Type
11016                then
11017                   Generate_Reference  (Entity (Name (N)), Name (N));
11018                   Set_Is_Instantiated (Entity (Name (N)));
11019                end if;
11020
11021                if Present (Cur) then
11022
11023                   --  For the case of a child instance hiding an outer homonym,
11024                   --  provide additional warning which might explain the error.
11025
11026                   Set_Is_Immediately_Visible (Cur, Vis);
11027                   Error_Msg_NE ("& hides outer unit with the same name?",
11028                     N, Defining_Unit_Name (N));
11029                end if;
11030
11031                Abandon_Instantiation (Act);
11032             end if;
11033          end if;
11034
11035          Next (Assoc);
11036       end loop;
11037
11038       if Present (Cur) then
11039          Set_Is_Immediately_Visible (Cur, Vis);
11040       end if;
11041    end Preanalyze_Actuals;
11042
11043    -------------------
11044    -- Remove_Parent --
11045    -------------------
11046
11047    procedure Remove_Parent (In_Body : Boolean := False) is
11048       S : Entity_Id := Current_Scope;
11049       --  S is the scope containing the instantiation just completed. The scope
11050       --  stack contains the parent instances of the instantiation, followed by
11051       --  the original S.
11052
11053       E      : Entity_Id;
11054       P      : Entity_Id;
11055       Hidden : Elmt_Id;
11056
11057    begin
11058       --  After child instantiation is complete, remove from scope stack the
11059       --  extra copy of the current scope, and then remove parent instances.
11060
11061       if not In_Body then
11062          Pop_Scope;
11063
11064          while Current_Scope /= S loop
11065             P := Current_Scope;
11066             End_Package_Scope (Current_Scope);
11067
11068             if In_Open_Scopes (P) then
11069                E := First_Entity (P);
11070                while Present (E) loop
11071                   Set_Is_Immediately_Visible (E, True);
11072                   Next_Entity (E);
11073                end loop;
11074
11075                if Is_Generic_Instance (Current_Scope)
11076                  and then P /= Current_Scope
11077                then
11078                   --  We are within an instance of some sibling. Retain
11079                   --  visibility of parent, for proper subsequent cleanup, and
11080                   --  reinstall private declarations as well.
11081
11082                   Set_In_Private_Part (P);
11083                   Install_Private_Declarations (P);
11084                end if;
11085
11086             --  If the ultimate parent is a top-level unit recorded in
11087             --  Instance_Parent_Unit, then reset its visibility to what is was
11088             --  before instantiation. (It's not clear what the purpose is of
11089             --  testing whether Scope (P) is In_Open_Scopes, but that test was
11090             --  present before the ultimate parent test was added.???)
11091
11092             elsif not In_Open_Scopes (Scope (P))
11093               or else (P = Instance_Parent_Unit
11094                         and then not Parent_Unit_Visible)
11095             then
11096                Set_Is_Immediately_Visible (P, False);
11097
11098             --  If the current scope is itself an instantiation of a generic
11099             --  nested within P, and we are in the private part of body of this
11100             --  instantiation, restore the full views of P, that were removed
11101             --  in End_Package_Scope above. This obscure case can occur when a
11102             --  subunit of a generic contains an instance of a child unit of
11103             --  its generic parent unit.
11104
11105             elsif S = Current_Scope and then Is_Generic_Instance (S) then
11106                declare
11107                   Par : constant Entity_Id :=
11108                           Generic_Parent
11109                             (Specification (Unit_Declaration_Node (S)));
11110                begin
11111                   if Present (Par)
11112                     and then P = Scope (Par)
11113                     and then (In_Package_Body (S) or else In_Private_Part (S))
11114                   then
11115                      Set_In_Private_Part (P);
11116                      Install_Private_Declarations (P);
11117                   end if;
11118                end;
11119             end if;
11120          end loop;
11121
11122          --  Reset visibility of entities in the enclosing scope
11123
11124          Set_Is_Hidden_Open_Scope (Current_Scope, False);
11125
11126          Hidden := First_Elmt (Hidden_Entities);
11127          while Present (Hidden) loop
11128             Set_Is_Immediately_Visible (Node (Hidden), True);
11129             Next_Elmt (Hidden);
11130          end loop;
11131
11132       else
11133          --  Each body is analyzed separately, and there is no context that
11134          --  needs preserving from one body instance to the next, so remove all
11135          --  parent scopes that have been installed.
11136
11137          while Present (S) loop
11138             End_Package_Scope (S);
11139             Set_Is_Immediately_Visible (S, False);
11140             S := Current_Scope;
11141             exit when S = Standard_Standard;
11142          end loop;
11143       end if;
11144    end Remove_Parent;
11145
11146    -----------------
11147    -- Restore_Env --
11148    -----------------
11149
11150    procedure Restore_Env is
11151       Saved : Instance_Env renames Instance_Envs.Table (Instance_Envs.Last);
11152
11153    begin
11154       if No (Current_Instantiated_Parent.Act_Id) then
11155          --  Restore environment after subprogram inlining
11156
11157          Restore_Private_Views (Empty);
11158       end if;
11159
11160       Current_Instantiated_Parent := Saved.Instantiated_Parent;
11161       Exchanged_Views             := Saved.Exchanged_Views;
11162       Hidden_Entities             := Saved.Hidden_Entities;
11163       Current_Sem_Unit            := Saved.Current_Sem_Unit;
11164       Parent_Unit_Visible         := Saved.Parent_Unit_Visible;
11165       Instance_Parent_Unit        := Saved.Instance_Parent_Unit;
11166
11167       Restore_Opt_Config_Switches (Saved.Switches);
11168
11169       Instance_Envs.Decrement_Last;
11170    end Restore_Env;
11171
11172    ---------------------------
11173    -- Restore_Private_Views --
11174    ---------------------------
11175
11176    procedure Restore_Private_Views
11177      (Pack_Id    : Entity_Id;
11178       Is_Package : Boolean := True)
11179    is
11180       M        : Elmt_Id;
11181       E        : Entity_Id;
11182       Typ      : Entity_Id;
11183       Dep_Elmt : Elmt_Id;
11184       Dep_Typ  : Node_Id;
11185
11186       procedure Restore_Nested_Formal (Formal : Entity_Id);
11187       --  Hide the generic formals of formal packages declared with box which
11188       --  were reachable in the current instantiation.
11189
11190       ---------------------------
11191       -- Restore_Nested_Formal --
11192       ---------------------------
11193
11194       procedure Restore_Nested_Formal (Formal : Entity_Id) is
11195          Ent : Entity_Id;
11196
11197       begin
11198          if Present (Renamed_Object (Formal))
11199            and then Denotes_Formal_Package (Renamed_Object (Formal), True)
11200          then
11201             return;
11202
11203          elsif Present (Associated_Formal_Package (Formal)) then
11204             Ent := First_Entity (Formal);
11205             while Present (Ent) loop
11206                exit when Ekind (Ent) = E_Package
11207                  and then Renamed_Entity (Ent) = Renamed_Entity (Formal);
11208
11209                Set_Is_Hidden (Ent);
11210                Set_Is_Potentially_Use_Visible (Ent, False);
11211
11212                --  If package, then recurse
11213
11214                if Ekind (Ent) = E_Package then
11215                   Restore_Nested_Formal (Ent);
11216                end if;
11217
11218                Next_Entity (Ent);
11219             end loop;
11220          end if;
11221       end Restore_Nested_Formal;
11222
11223    --  Start of processing for Restore_Private_Views
11224
11225    begin
11226       M := First_Elmt (Exchanged_Views);
11227       while Present (M) loop
11228          Typ := Node (M);
11229
11230          --  Subtypes of types whose views have been exchanged, and that
11231          --  are defined within the instance, were not on the list of
11232          --  Private_Dependents on entry to the instance, so they have to be
11233          --  exchanged explicitly now, in order to remain consistent with the
11234          --  view of the parent type.
11235
11236          if Ekind (Typ) = E_Private_Type
11237            or else Ekind (Typ) = E_Limited_Private_Type
11238            or else Ekind (Typ) = E_Record_Type_With_Private
11239          then
11240             Dep_Elmt := First_Elmt (Private_Dependents (Typ));
11241             while Present (Dep_Elmt) loop
11242                Dep_Typ := Node (Dep_Elmt);
11243
11244                if Scope (Dep_Typ) = Pack_Id
11245                  and then Present (Full_View (Dep_Typ))
11246                then
11247                   Replace_Elmt (Dep_Elmt, Full_View (Dep_Typ));
11248                   Exchange_Declarations (Dep_Typ);
11249                end if;
11250
11251                Next_Elmt (Dep_Elmt);
11252             end loop;
11253          end if;
11254
11255          Exchange_Declarations (Node (M));
11256          Next_Elmt (M);
11257       end loop;
11258
11259       if No (Pack_Id) then
11260          return;
11261       end if;
11262
11263       --  Make the generic formal parameters private, and make the formal types
11264       --  into subtypes of the actuals again.
11265
11266       E := First_Entity (Pack_Id);
11267       while Present (E) loop
11268          Set_Is_Hidden (E, True);
11269
11270          if Is_Type (E)
11271            and then Nkind (Parent (E)) = N_Subtype_Declaration
11272          then
11273             Set_Is_Generic_Actual_Type (E, False);
11274
11275             --  An unusual case of aliasing: the actual may also be directly
11276             --  visible in the generic, and be private there, while it is fully
11277             --  visible in the context of the instance. The internal subtype
11278             --  is private in the instance, but has full visibility like its
11279             --  parent in the enclosing scope. This enforces the invariant that
11280             --  the privacy status of all private dependents of a type coincide
11281             --  with that of the parent type. This can only happen when a
11282             --  generic child unit is instantiated within sibling.
11283
11284             if Is_Private_Type (E)
11285               and then not Is_Private_Type (Etype (E))
11286             then
11287                Exchange_Declarations (E);
11288             end if;
11289
11290          elsif Ekind (E) = E_Package then
11291
11292             --  The end of the renaming list is the renaming of the generic
11293             --  package itself. If the instance is a subprogram, all entities
11294             --  in the corresponding package are renamings. If this entity is
11295             --  a formal package, make its own formals private as well. The
11296             --  actual in this case is itself the renaming of an instantiation.
11297             --  If the entity is not a package renaming, it is the entity
11298             --  created to validate formal package actuals: ignore.
11299
11300             --  If the actual is itself a formal package for the enclosing
11301             --  generic, or the actual for such a formal package, it remains
11302             --  visible on exit from the instance, and therefore nothing needs
11303             --  to be done either, except to keep it accessible.
11304
11305             if Is_Package
11306               and then Renamed_Object (E) = Pack_Id
11307             then
11308                exit;
11309
11310             elsif Nkind (Parent (E)) /= N_Package_Renaming_Declaration then
11311                null;
11312
11313             elsif
11314               Denotes_Formal_Package (Renamed_Object (E), True, Pack_Id)
11315             then
11316                Set_Is_Hidden (E, False);
11317
11318             else
11319                declare
11320                   Act_P : constant Entity_Id := Renamed_Object (E);
11321                   Id    : Entity_Id;
11322
11323                begin
11324                   Id := First_Entity (Act_P);
11325                   while Present (Id)
11326                     and then Id /= First_Private_Entity (Act_P)
11327                   loop
11328                      exit when Ekind (Id) = E_Package
11329                                  and then Renamed_Object (Id) = Act_P;
11330
11331                      Set_Is_Hidden (Id, True);
11332                      Set_Is_Potentially_Use_Visible (Id, In_Use (Act_P));
11333
11334                      if Ekind (Id) = E_Package then
11335                         Restore_Nested_Formal (Id);
11336                      end if;
11337
11338                      Next_Entity (Id);
11339                   end loop;
11340                end;
11341             end if;
11342          end if;
11343
11344          Next_Entity (E);
11345       end loop;
11346    end Restore_Private_Views;
11347
11348    --------------
11349    -- Save_Env --
11350    --------------
11351
11352    procedure Save_Env
11353      (Gen_Unit : Entity_Id;
11354       Act_Unit : Entity_Id)
11355    is
11356    begin
11357       Init_Env;
11358       Set_Instance_Env (Gen_Unit, Act_Unit);
11359    end Save_Env;
11360
11361    ----------------------------
11362    -- Save_Global_References --
11363    ----------------------------
11364
11365    procedure Save_Global_References (N : Node_Id) is
11366       Gen_Scope : Entity_Id;
11367       E         : Entity_Id;
11368       N2        : Node_Id;
11369
11370       function Is_Global (E : Entity_Id) return Boolean;
11371       --  Check whether entity is defined outside of generic unit. Examine the
11372       --  scope of an entity, and the scope of the scope, etc, until we find
11373       --  either Standard, in which case the entity is global, or the generic
11374       --  unit itself, which indicates that the entity is local. If the entity
11375       --  is the generic unit itself, as in the case of a recursive call, or
11376       --  the enclosing generic unit, if different from the current scope, then
11377       --  it is local as well, because it will be replaced at the point of
11378       --  instantiation. On the other hand, if it is a reference to a child
11379       --  unit of a common ancestor, which appears in an instantiation, it is
11380       --  global because it is used to denote a specific compilation unit at
11381       --  the time the instantiations will be analyzed.
11382
11383       procedure Reset_Entity (N : Node_Id);
11384       --  Save semantic information on global entity so that it is not resolved
11385       --  again at instantiation time.
11386
11387       procedure Save_Entity_Descendants (N : Node_Id);
11388       --  Apply Save_Global_References to the two syntactic descendants of
11389       --  non-terminal nodes that carry an Associated_Node and are processed
11390       --  through Reset_Entity. Once the global entity (if any) has been
11391       --  captured together with its type, only two syntactic descendants need
11392       --  to be traversed to complete the processing of the tree rooted at N.
11393       --  This applies to Selected_Components, Expanded_Names, and to Operator
11394       --  nodes. N can also be a character literal, identifier, or operator
11395       --  symbol node, but the call has no effect in these cases.
11396
11397       procedure Save_Global_Defaults (N1, N2 : Node_Id);
11398       --  Default actuals in nested instances must be handled specially
11399       --  because there is no link to them from the original tree. When an
11400       --  actual subprogram is given by a default, we add an explicit generic
11401       --  association for it in the instantiation node. When we save the
11402       --  global references on the name of the instance, we recover the list
11403       --  of generic associations, and add an explicit one to the original
11404       --  generic tree, through which a global actual can be preserved.
11405       --  Similarly, if a child unit is instantiated within a sibling, in the
11406       --  context of the parent, we must preserve the identifier of the parent
11407       --  so that it can be properly resolved in a subsequent instantiation.
11408
11409       procedure Save_Global_Descendant (D : Union_Id);
11410       --  Apply Save_Global_References recursively to the descendents of the
11411       --  current node.
11412
11413       procedure Save_References (N : Node_Id);
11414       --  This is the recursive procedure that does the work, once the
11415       --  enclosing generic scope has been established.
11416
11417       ---------------
11418       -- Is_Global --
11419       ---------------
11420
11421       function Is_Global (E : Entity_Id) return Boolean is
11422          Se : Entity_Id;
11423
11424          function Is_Instance_Node (Decl : Node_Id) return Boolean;
11425          --  Determine whether the parent node of a reference to a child unit
11426          --  denotes an instantiation or a formal package, in which case the
11427          --  reference to the child unit is global, even if it appears within
11428          --  the current scope (e.g. when the instance appears within the body
11429          --  of an ancestor).
11430
11431          ----------------------
11432          -- Is_Instance_Node --
11433          ----------------------
11434
11435          function Is_Instance_Node (Decl : Node_Id) return Boolean is
11436          begin
11437             return Nkind (Decl) in N_Generic_Instantiation
11438                      or else
11439                    Nkind (Original_Node (Decl)) = N_Formal_Package_Declaration;
11440          end Is_Instance_Node;
11441
11442       --  Start of processing for Is_Global
11443
11444       begin
11445          if E = Gen_Scope then
11446             return False;
11447
11448          elsif E = Standard_Standard then
11449             return True;
11450
11451          elsif Is_Child_Unit (E)
11452            and then (Is_Instance_Node (Parent (N2))
11453                       or else (Nkind (Parent (N2)) = N_Expanded_Name
11454                                 and then N2 = Selector_Name (Parent (N2))
11455                                 and then
11456                                   Is_Instance_Node (Parent (Parent (N2)))))
11457          then
11458             return True;
11459
11460          else
11461             Se := Scope (E);
11462             while Se /= Gen_Scope loop
11463                if Se = Standard_Standard then
11464                   return True;
11465                else
11466                   Se := Scope (Se);
11467                end if;
11468             end loop;
11469
11470             return False;
11471          end if;
11472       end Is_Global;
11473
11474       ------------------
11475       -- Reset_Entity --
11476       ------------------
11477
11478       procedure Reset_Entity (N : Node_Id) is
11479
11480          procedure Set_Global_Type (N : Node_Id; N2 : Node_Id);
11481          --  If the type of N2 is global to the generic unit. Save the type in
11482          --  the generic node.
11483          --  What does this comment mean???
11484
11485          function Top_Ancestor (E : Entity_Id) return Entity_Id;
11486          --  Find the ultimate ancestor of the current unit. If it is not a
11487          --  generic unit, then the name of the current unit in the prefix of
11488          --  an expanded name must be replaced with its generic homonym to
11489          --  ensure that it will be properly resolved in an instance.
11490
11491          ---------------------
11492          -- Set_Global_Type --
11493          ---------------------
11494
11495          procedure Set_Global_Type (N : Node_Id; N2 : Node_Id) is
11496             Typ : constant Entity_Id := Etype (N2);
11497
11498          begin
11499             Set_Etype (N, Typ);
11500
11501             if Entity (N) /= N2
11502               and then Has_Private_View (Entity (N))
11503             then
11504                --  If the entity of N is not the associated node, this is a
11505                --  nested generic and it has an associated node as well, whose
11506                --  type is already the full view (see below). Indicate that the
11507                --  original node has a private view.
11508
11509                Set_Has_Private_View (N);
11510             end if;
11511
11512             --  If not a private type, nothing else to do
11513
11514             if not Is_Private_Type (Typ) then
11515                if Is_Array_Type (Typ)
11516                  and then Is_Private_Type (Component_Type (Typ))
11517                then
11518                   Set_Has_Private_View (N);
11519                end if;
11520
11521             --  If it is a derivation of a private type in a context where no
11522             --  full view is needed, nothing to do either.
11523
11524             elsif No (Full_View (Typ)) and then Typ /= Etype (Typ) then
11525                null;
11526
11527             --  Otherwise mark the type for flipping and use the full view when
11528             --  available.
11529
11530             else
11531                Set_Has_Private_View (N);
11532
11533                if Present (Full_View (Typ)) then
11534                   Set_Etype (N2, Full_View (Typ));
11535                end if;
11536             end if;
11537          end Set_Global_Type;
11538
11539          ------------------
11540          -- Top_Ancestor --
11541          ------------------
11542
11543          function Top_Ancestor (E : Entity_Id) return Entity_Id is
11544             Par : Entity_Id;
11545
11546          begin
11547             Par := E;
11548             while Is_Child_Unit (Par) loop
11549                Par := Scope (Par);
11550             end loop;
11551
11552             return Par;
11553          end Top_Ancestor;
11554
11555       --  Start of processing for Reset_Entity
11556
11557       begin
11558          N2 := Get_Associated_Node (N);
11559          E := Entity (N2);
11560
11561          if Present (E) then
11562             if Is_Global (E) then
11563                Set_Global_Type (N, N2);
11564
11565             elsif Nkind (N) = N_Op_Concat
11566               and then Is_Generic_Type (Etype (N2))
11567               and then
11568                (Base_Type (Etype (Right_Opnd (N2))) = Etype (N2)
11569                   or else Base_Type (Etype (Left_Opnd (N2))) = Etype (N2))
11570               and then Is_Intrinsic_Subprogram (E)
11571             then
11572                null;
11573
11574             else
11575                --  Entity is local. Mark generic node as unresolved.
11576                --  Note that now it does not have an entity.
11577
11578                Set_Associated_Node (N, Empty);
11579                Set_Etype  (N, Empty);
11580             end if;
11581
11582             if Nkind (Parent (N)) in N_Generic_Instantiation
11583               and then N = Name (Parent (N))
11584             then
11585                Save_Global_Defaults (Parent (N), Parent (N2));
11586             end if;
11587
11588          elsif Nkind (Parent (N)) = N_Selected_Component
11589            and then Nkind (Parent (N2)) = N_Expanded_Name
11590          then
11591             if Is_Global (Entity (Parent (N2))) then
11592                Change_Selected_Component_To_Expanded_Name (Parent (N));
11593                Set_Associated_Node (Parent (N), Parent (N2));
11594                Set_Global_Type (Parent (N), Parent (N2));
11595                Save_Entity_Descendants (N);
11596
11597             --  If this is a reference to the current generic entity, replace
11598             --  by the name of the generic homonym of the current package. This
11599             --  is because in an instantiation Par.P.Q will not resolve to the
11600             --  name of the instance, whose enclosing scope is not necessarily
11601             --  Par. We use the generic homonym rather that the name of the
11602             --  generic itself because it may be hidden by a local declaration.
11603
11604             elsif In_Open_Scopes (Entity (Parent (N2)))
11605               and then not
11606                 Is_Generic_Unit (Top_Ancestor (Entity (Prefix (Parent (N2)))))
11607             then
11608                if Ekind (Entity (Parent (N2))) = E_Generic_Package then
11609                   Rewrite (Parent (N),
11610                     Make_Identifier (Sloc (N),
11611                       Chars =>
11612                         Chars (Generic_Homonym (Entity (Parent (N2))))));
11613                else
11614                   Rewrite (Parent (N),
11615                     Make_Identifier (Sloc (N),
11616                       Chars => Chars (Selector_Name (Parent (N2)))));
11617                end if;
11618             end if;
11619
11620             if Nkind (Parent (Parent (N))) in N_Generic_Instantiation
11621               and then Parent (N) = Name (Parent (Parent (N)))
11622             then
11623                Save_Global_Defaults
11624                  (Parent (Parent (N)), Parent (Parent ((N2))));
11625             end if;
11626
11627          --  A selected component may denote a static constant that has been
11628          --  folded. If the static constant is global to the generic, capture
11629          --  its value. Otherwise the folding will happen in any instantiation.
11630
11631          elsif Nkind (Parent (N)) = N_Selected_Component
11632            and then Nkind_In (Parent (N2), N_Integer_Literal, N_Real_Literal)
11633          then
11634             if Present (Entity (Original_Node (Parent (N2))))
11635               and then Is_Global (Entity (Original_Node (Parent (N2))))
11636             then
11637                Rewrite (Parent (N), New_Copy (Parent (N2)));
11638                Set_Analyzed (Parent (N), False);
11639
11640             else
11641                null;
11642             end if;
11643
11644          --  A selected component may be transformed into a parameterless
11645          --  function call. If the called entity is global, rewrite the node
11646          --  appropriately, i.e. as an extended name for the global entity.
11647
11648          elsif Nkind (Parent (N)) = N_Selected_Component
11649            and then Nkind (Parent (N2)) = N_Function_Call
11650            and then N = Selector_Name (Parent (N))
11651          then
11652             if No (Parameter_Associations (Parent (N2))) then
11653                if Is_Global (Entity (Name (Parent (N2)))) then
11654                   Change_Selected_Component_To_Expanded_Name (Parent (N));
11655                   Set_Associated_Node (Parent (N), Name (Parent (N2)));
11656                   Set_Global_Type (Parent (N), Name (Parent (N2)));
11657                   Save_Entity_Descendants (N);
11658
11659                else
11660                   Set_Associated_Node (N, Empty);
11661                   Set_Etype (N, Empty);
11662                end if;
11663
11664             --  In Ada 2005, X.F may be a call to a primitive operation,
11665             --  rewritten as F (X). This rewriting will be done again in an
11666             --  instance, so keep the original node. Global entities will be
11667             --  captured as for other constructs.
11668
11669             else
11670                null;
11671             end if;
11672
11673          --  Entity is local. Reset in generic unit, so that node is resolved
11674          --  anew at the point of instantiation.
11675
11676          else
11677             Set_Associated_Node (N, Empty);
11678             Set_Etype (N, Empty);
11679          end if;
11680       end Reset_Entity;
11681
11682       -----------------------------
11683       -- Save_Entity_Descendants --
11684       -----------------------------
11685
11686       procedure Save_Entity_Descendants (N : Node_Id) is
11687       begin
11688          case Nkind (N) is
11689             when N_Binary_Op =>
11690                Save_Global_Descendant (Union_Id (Left_Opnd (N)));
11691                Save_Global_Descendant (Union_Id (Right_Opnd (N)));
11692
11693             when N_Unary_Op =>
11694                Save_Global_Descendant (Union_Id (Right_Opnd (N)));
11695
11696             when N_Expanded_Name | N_Selected_Component =>
11697                Save_Global_Descendant (Union_Id (Prefix (N)));
11698                Save_Global_Descendant (Union_Id (Selector_Name (N)));
11699
11700             when N_Identifier | N_Character_Literal | N_Operator_Symbol =>
11701                null;
11702
11703             when others =>
11704                raise Program_Error;
11705          end case;
11706       end Save_Entity_Descendants;
11707
11708       --------------------------
11709       -- Save_Global_Defaults --
11710       --------------------------
11711
11712       procedure Save_Global_Defaults (N1, N2 : Node_Id) is
11713          Loc    : constant Source_Ptr := Sloc (N1);
11714          Assoc2 : constant List_Id    := Generic_Associations (N2);
11715          Gen_Id : constant Entity_Id  := Get_Generic_Entity (N2);
11716          Assoc1 : List_Id;
11717          Act1   : Node_Id;
11718          Act2   : Node_Id;
11719          Def    : Node_Id;
11720          Ndec   : Node_Id;
11721          Subp   : Entity_Id;
11722          Actual : Entity_Id;
11723
11724       begin
11725          Assoc1 := Generic_Associations (N1);
11726
11727          if Present (Assoc1) then
11728             Act1 := First (Assoc1);
11729          else
11730             Act1 := Empty;
11731             Set_Generic_Associations (N1, New_List);
11732             Assoc1 := Generic_Associations (N1);
11733          end if;
11734
11735          if Present (Assoc2) then
11736             Act2 := First (Assoc2);
11737          else
11738             return;
11739          end if;
11740
11741          while Present (Act1) and then Present (Act2) loop
11742             Next (Act1);
11743             Next (Act2);
11744          end loop;
11745
11746          --  Find the associations added for default subprograms
11747
11748          if Present (Act2) then
11749             while Nkind (Act2) /= N_Generic_Association
11750               or else No (Entity (Selector_Name (Act2)))
11751               or else not Is_Overloadable (Entity (Selector_Name (Act2)))
11752             loop
11753                Next (Act2);
11754             end loop;
11755
11756             --  Add a similar association if the default is global. The
11757             --  renaming declaration for the actual has been analyzed, and
11758             --  its alias is the program it renames. Link the actual in the
11759             --  original generic tree with the node in the analyzed tree.
11760
11761             while Present (Act2) loop
11762                Subp := Entity (Selector_Name (Act2));
11763                Def  := Explicit_Generic_Actual_Parameter (Act2);
11764
11765                --  Following test is defence against rubbish errors
11766
11767                if No (Alias (Subp)) then
11768                   return;
11769                end if;
11770
11771                --  Retrieve the resolved actual from the renaming declaration
11772                --  created for the instantiated formal.
11773
11774                Actual := Entity (Name (Parent (Parent (Subp))));
11775                Set_Entity (Def, Actual);
11776                Set_Etype (Def, Etype (Actual));
11777
11778                if Is_Global (Actual) then
11779                   Ndec :=
11780                     Make_Generic_Association (Loc,
11781                       Selector_Name => New_Occurrence_Of (Subp, Loc),
11782                         Explicit_Generic_Actual_Parameter =>
11783                           New_Occurrence_Of (Actual, Loc));
11784
11785                   Set_Associated_Node
11786                     (Explicit_Generic_Actual_Parameter (Ndec), Def);
11787
11788                   Append (Ndec, Assoc1);
11789
11790                --  If there are other defaults, add a dummy association in case
11791                --  there are other defaulted formals with the same name.
11792
11793                elsif Present (Next (Act2)) then
11794                   Ndec :=
11795                     Make_Generic_Association (Loc,
11796                       Selector_Name => New_Occurrence_Of (Subp, Loc),
11797                         Explicit_Generic_Actual_Parameter => Empty);
11798
11799                   Append (Ndec, Assoc1);
11800                end if;
11801
11802                Next (Act2);
11803             end loop;
11804          end if;
11805
11806          if Nkind (Name (N1)) = N_Identifier
11807            and then Is_Child_Unit (Gen_Id)
11808            and then Is_Global (Gen_Id)
11809            and then Is_Generic_Unit (Scope (Gen_Id))
11810            and then In_Open_Scopes (Scope (Gen_Id))
11811          then
11812             --  This is an instantiation of a child unit within a sibling,
11813             --  so that the generic parent is in scope. An eventual instance
11814             --  must occur within the scope of an instance of the parent.
11815             --  Make name in instance into an expanded name, to preserve the
11816             --  identifier of the parent, so it can be resolved subsequently.
11817
11818             Rewrite (Name (N2),
11819               Make_Expanded_Name (Loc,
11820                 Chars         => Chars (Gen_Id),
11821                 Prefix        => New_Occurrence_Of (Scope (Gen_Id), Loc),
11822                 Selector_Name => New_Occurrence_Of (Gen_Id, Loc)));
11823             Set_Entity (Name (N2), Gen_Id);
11824
11825             Rewrite (Name (N1),
11826                Make_Expanded_Name (Loc,
11827                 Chars         => Chars (Gen_Id),
11828                 Prefix        => New_Occurrence_Of (Scope (Gen_Id), Loc),
11829                 Selector_Name => New_Occurrence_Of (Gen_Id, Loc)));
11830
11831             Set_Associated_Node (Name (N1), Name (N2));
11832             Set_Associated_Node (Prefix (Name (N1)), Empty);
11833             Set_Associated_Node
11834               (Selector_Name (Name (N1)), Selector_Name (Name (N2)));
11835             Set_Etype (Name (N1), Etype (Gen_Id));
11836          end if;
11837
11838       end Save_Global_Defaults;
11839
11840       ----------------------------
11841       -- Save_Global_Descendant --
11842       ----------------------------
11843
11844       procedure Save_Global_Descendant (D : Union_Id) is
11845          N1 : Node_Id;
11846
11847       begin
11848          if D in Node_Range then
11849             if D = Union_Id (Empty) then
11850                null;
11851
11852             elsif Nkind (Node_Id (D)) /= N_Compilation_Unit then
11853                Save_References (Node_Id (D));
11854             end if;
11855
11856          elsif D in List_Range then
11857             if D = Union_Id (No_List)
11858               or else Is_Empty_List (List_Id (D))
11859             then
11860                null;
11861
11862             else
11863                N1 := First (List_Id (D));
11864                while Present (N1) loop
11865                   Save_References (N1);
11866                   Next (N1);
11867                end loop;
11868             end if;
11869
11870          --  Element list or other non-node field, nothing to do
11871
11872          else
11873             null;
11874          end if;
11875       end Save_Global_Descendant;
11876
11877       ---------------------
11878       -- Save_References --
11879       ---------------------
11880
11881       --  This is the recursive procedure that does the work once the enclosing
11882       --  generic scope has been established. We have to treat specially a
11883       --  number of node rewritings that are required by semantic processing
11884       --  and which change the kind of nodes in the generic copy: typically
11885       --  constant-folding, replacing an operator node by a string literal, or
11886       --  a selected component by an expanded name. In each of those cases, the
11887       --  transformation is propagated to the generic unit.
11888
11889       procedure Save_References (N : Node_Id) is
11890          Loc : constant Source_Ptr := Sloc (N);
11891
11892       begin
11893          if N = Empty then
11894             null;
11895
11896          elsif Nkind_In (N, N_Character_Literal, N_Operator_Symbol) then
11897             if Nkind (N) = Nkind (Get_Associated_Node (N)) then
11898                Reset_Entity (N);
11899
11900             elsif Nkind (N) = N_Operator_Symbol
11901               and then Nkind (Get_Associated_Node (N)) = N_String_Literal
11902             then
11903                Change_Operator_Symbol_To_String_Literal (N);
11904             end if;
11905
11906          elsif Nkind (N) in N_Op then
11907             if Nkind (N) = Nkind (Get_Associated_Node (N)) then
11908                if Nkind (N) = N_Op_Concat then
11909                   Set_Is_Component_Left_Opnd (N,
11910                     Is_Component_Left_Opnd (Get_Associated_Node (N)));
11911
11912                   Set_Is_Component_Right_Opnd (N,
11913                     Is_Component_Right_Opnd (Get_Associated_Node (N)));
11914                end if;
11915
11916                Reset_Entity (N);
11917
11918             else
11919                --  Node may be transformed into call to a user-defined operator
11920
11921                N2 := Get_Associated_Node (N);
11922
11923                if Nkind (N2) = N_Function_Call then
11924                   E := Entity (Name (N2));
11925
11926                   if Present (E)
11927                     and then Is_Global (E)
11928                   then
11929                      Set_Etype (N, Etype (N2));
11930                   else
11931                      Set_Associated_Node (N, Empty);
11932                      Set_Etype (N, Empty);
11933                   end if;
11934
11935                elsif Nkind_In (N2, N_Integer_Literal,
11936                                    N_Real_Literal,
11937                                    N_String_Literal)
11938                then
11939                   if Present (Original_Node (N2))
11940                     and then Nkind (Original_Node (N2)) = Nkind (N)
11941                   then
11942
11943                      --  Operation was constant-folded. Whenever possible,
11944                      --  recover semantic information from unfolded node,
11945                      --  for ASIS use.
11946
11947                      Set_Associated_Node (N, Original_Node (N2));
11948
11949                      if Nkind (N) = N_Op_Concat then
11950                         Set_Is_Component_Left_Opnd (N,
11951                           Is_Component_Left_Opnd  (Get_Associated_Node (N)));
11952                         Set_Is_Component_Right_Opnd (N,
11953                           Is_Component_Right_Opnd (Get_Associated_Node (N)));
11954                      end if;
11955
11956                      Reset_Entity (N);
11957
11958                   else
11959                      --  If original node is already modified, propagate
11960                      --  constant-folding to template.
11961
11962                      Rewrite (N, New_Copy (N2));
11963                      Set_Analyzed (N, False);
11964                   end if;
11965
11966                elsif Nkind (N2) = N_Identifier
11967                  and then Ekind (Entity (N2)) = E_Enumeration_Literal
11968                then
11969                   --  Same if call was folded into a literal, but in this case
11970                   --  retain the entity to avoid spurious ambiguities if it is
11971                   --  overloaded at the point of instantiation or inlining.
11972
11973                   Rewrite (N, New_Copy (N2));
11974                   Set_Analyzed (N, False);
11975                end if;
11976             end if;
11977
11978             --  Complete operands check if node has not been constant-folded
11979
11980             if Nkind (N) in N_Op then
11981                Save_Entity_Descendants (N);
11982             end if;
11983
11984          elsif Nkind (N) = N_Identifier then
11985             if Nkind (N) = Nkind (Get_Associated_Node (N)) then
11986
11987                --  If this is a discriminant reference, always save it. It is
11988                --  used in the instance to find the corresponding discriminant
11989                --  positionally rather than by name.
11990
11991                Set_Original_Discriminant
11992                  (N, Original_Discriminant (Get_Associated_Node (N)));
11993                Reset_Entity (N);
11994
11995             else
11996                N2 := Get_Associated_Node (N);
11997
11998                if Nkind (N2) = N_Function_Call then
11999                   E := Entity (Name (N2));
12000
12001                   --  Name resolves to a call to parameterless function. If
12002                   --  original entity is global, mark node as resolved.
12003
12004                   if Present (E)
12005                     and then Is_Global (E)
12006                   then
12007                      Set_Etype (N, Etype (N2));
12008                   else
12009                      Set_Associated_Node (N, Empty);
12010                      Set_Etype (N, Empty);
12011                   end if;
12012
12013                elsif Nkind_In (N2, N_Integer_Literal, N_Real_Literal)
12014                  and then Is_Entity_Name (Original_Node (N2))
12015                then
12016                   --  Name resolves to named number that is constant-folded,
12017                   --  We must preserve the original name for ASIS use, and
12018                   --  undo the constant-folding, which will be repeated in
12019                   --  each instance.
12020
12021                   Set_Associated_Node (N, Original_Node (N2));
12022                   Reset_Entity (N);
12023
12024                elsif Nkind (N2) = N_String_Literal then
12025
12026                   --  Name resolves to string literal. Perform the same
12027                   --  replacement in generic.
12028
12029                   Rewrite (N, New_Copy (N2));
12030
12031                elsif Nkind (N2) = N_Explicit_Dereference then
12032
12033                   --  An identifier is rewritten as a dereference if it is the
12034                   --  prefix in an implicit dereference.
12035
12036                   --  Check whether corresponding entity in prefix is global
12037
12038                   if Is_Entity_Name (Prefix (N2))
12039                     and then Present (Entity (Prefix (N2)))
12040                     and then Is_Global (Entity (Prefix (N2)))
12041                   then
12042                      Rewrite (N,
12043                        Make_Explicit_Dereference (Loc,
12044                           Prefix =>
12045                             New_Occurrence_Of (Entity (Prefix (N2)), Loc)));
12046                   elsif Nkind (Prefix (N2)) = N_Function_Call
12047                     and then Is_Global (Entity (Name (Prefix (N2))))
12048                   then
12049                      Rewrite (N,
12050                        Make_Explicit_Dereference (Loc,
12051                           Prefix => Make_Function_Call (Loc,
12052                             Name =>
12053                               New_Occurrence_Of (Entity (Name (Prefix (N2))),
12054                                                  Loc))));
12055
12056                   else
12057                      Set_Associated_Node (N, Empty);
12058                      Set_Etype (N, Empty);
12059                   end if;
12060
12061                --  The subtype mark of a nominally unconstrained object is
12062                --  rewritten as a subtype indication using the bounds of the
12063                --  expression. Recover the original subtype mark.
12064
12065                elsif Nkind (N2) = N_Subtype_Indication
12066                  and then Is_Entity_Name (Original_Node (N2))
12067                then
12068                   Set_Associated_Node (N, Original_Node (N2));
12069                   Reset_Entity (N);
12070
12071                else
12072                   null;
12073                end if;
12074             end if;
12075
12076          elsif Nkind (N) in N_Entity then
12077             null;
12078
12079          else
12080             declare
12081                Qual : Node_Id := Empty;
12082                Typ  : Entity_Id := Empty;
12083                Nam  : Node_Id;
12084
12085                use Atree.Unchecked_Access;
12086                --  This code section is part of implementing an untyped tree
12087                --  traversal, so it needs direct access to node fields.
12088
12089             begin
12090                if Nkind_In (N, N_Aggregate, N_Extension_Aggregate) then
12091                   N2 := Get_Associated_Node (N);
12092
12093                   if No (N2) then
12094                      Typ := Empty;
12095                   else
12096                      Typ := Etype (N2);
12097
12098                      --  In an instance within a generic, use the name of the
12099                      --  actual and not the original generic parameter. If the
12100                      --  actual is global in the current generic it must be
12101                      --  preserved for its instantiation.
12102
12103                      if Nkind (Parent (Typ)) = N_Subtype_Declaration
12104                        and then
12105                          Present (Generic_Parent_Type (Parent (Typ)))
12106                      then
12107                         Typ := Base_Type (Typ);
12108                         Set_Etype (N2, Typ);
12109                      end if;
12110                   end if;
12111
12112                   if No (N2)
12113                     or else No (Typ)
12114                     or else not Is_Global (Typ)
12115                   then
12116                      Set_Associated_Node (N, Empty);
12117
12118                      --  If the aggregate is an actual in a call, it has been
12119                      --  resolved in the current context, to some local type.
12120                      --  The enclosing call may have been disambiguated by the
12121                      --  aggregate, and this disambiguation might fail at
12122                      --  instantiation time because the type to which the
12123                      --  aggregate did resolve is not preserved. In order to
12124                      --  preserve some of this information, we wrap the
12125                      --  aggregate in a qualified expression, using the id of
12126                      --  its type. For further disambiguation we qualify the
12127                      --  type name with its scope (if visible) because both
12128                      --  id's will have corresponding entities in an instance.
12129                      --  This resolves most of the problems with missing type
12130                      --  information on aggregates in instances.
12131
12132                      if Nkind (N2) = Nkind (N)
12133                        and then
12134                          Nkind_In (Parent (N2), N_Procedure_Call_Statement,
12135                                                 N_Function_Call)
12136                        and then Comes_From_Source (Typ)
12137                      then
12138                         if Is_Immediately_Visible (Scope (Typ)) then
12139                            Nam := Make_Selected_Component (Loc,
12140                              Prefix =>
12141                                Make_Identifier (Loc, Chars (Scope (Typ))),
12142                              Selector_Name =>
12143                                Make_Identifier (Loc, Chars (Typ)));
12144                         else
12145                            Nam := Make_Identifier (Loc, Chars (Typ));
12146                         end if;
12147
12148                         Qual :=
12149                           Make_Qualified_Expression (Loc,
12150                             Subtype_Mark => Nam,
12151                             Expression => Relocate_Node (N));
12152                      end if;
12153                   end if;
12154
12155                   Save_Global_Descendant (Field1 (N));
12156                   Save_Global_Descendant (Field2 (N));
12157                   Save_Global_Descendant (Field3 (N));
12158                   Save_Global_Descendant (Field5 (N));
12159
12160                   if Present (Qual) then
12161                      Rewrite (N, Qual);
12162                   end if;
12163
12164                --  All other cases than aggregates
12165
12166                else
12167                   Save_Global_Descendant (Field1 (N));
12168                   Save_Global_Descendant (Field2 (N));
12169                   Save_Global_Descendant (Field3 (N));
12170                   Save_Global_Descendant (Field4 (N));
12171                   Save_Global_Descendant (Field5 (N));
12172                end if;
12173             end;
12174          end if;
12175       end Save_References;
12176
12177    --  Start of processing for Save_Global_References
12178
12179    begin
12180       Gen_Scope := Current_Scope;
12181
12182       --  If the generic unit is a child unit, references to entities in the
12183       --  parent are treated as local, because they will be resolved anew in
12184       --  the context of the instance of the parent.
12185
12186       while Is_Child_Unit (Gen_Scope)
12187         and then Ekind (Scope (Gen_Scope)) = E_Generic_Package
12188       loop
12189          Gen_Scope := Scope (Gen_Scope);
12190       end loop;
12191
12192       Save_References (N);
12193    end Save_Global_References;
12194
12195    --------------------------------------
12196    -- Set_Copied_Sloc_For_Inlined_Body --
12197    --------------------------------------
12198
12199    procedure Set_Copied_Sloc_For_Inlined_Body (N : Node_Id; E : Entity_Id) is
12200    begin
12201       Create_Instantiation_Source (N, E, True, S_Adjustment);
12202    end Set_Copied_Sloc_For_Inlined_Body;
12203
12204    ---------------------
12205    -- Set_Instance_Of --
12206    ---------------------
12207
12208    procedure Set_Instance_Of (A : Entity_Id; B : Entity_Id) is
12209    begin
12210       Generic_Renamings.Table (Generic_Renamings.Last) := (A, B, Assoc_Null);
12211       Generic_Renamings_HTable.Set (Generic_Renamings.Last);
12212       Generic_Renamings.Increment_Last;
12213    end Set_Instance_Of;
12214
12215    --------------------
12216    -- Set_Next_Assoc --
12217    --------------------
12218
12219    procedure Set_Next_Assoc (E : Assoc_Ptr; Next : Assoc_Ptr) is
12220    begin
12221       Generic_Renamings.Table (E).Next_In_HTable := Next;
12222    end Set_Next_Assoc;
12223
12224    -------------------
12225    -- Start_Generic --
12226    -------------------
12227
12228    procedure Start_Generic is
12229    begin
12230       --  ??? More things could be factored out in this routine.
12231       --  Should probably be done at a later stage.
12232
12233       Generic_Flags.Append (Inside_A_Generic);
12234       Inside_A_Generic := True;
12235
12236       Expander_Mode_Save_And_Set (False);
12237    end Start_Generic;
12238
12239    ----------------------
12240    -- Set_Instance_Env --
12241    ----------------------
12242
12243    procedure Set_Instance_Env
12244      (Gen_Unit : Entity_Id;
12245       Act_Unit : Entity_Id)
12246    is
12247    begin
12248       --  Regardless of the current mode, predefined units are analyzed in
12249       --  the most current Ada mode, and earlier version Ada checks do not
12250       --  apply to predefined units. Nothing needs to be done for non-internal
12251       --  units. These are always analyzed in the current mode.
12252
12253       if Is_Internal_File_Name
12254           (Fname => Unit_File_Name (Get_Source_Unit (Gen_Unit)),
12255            Renamings_Included => True)
12256       then
12257          Set_Opt_Config_Switches (True, Current_Sem_Unit = Main_Unit);
12258       end if;
12259
12260       Current_Instantiated_Parent := (Gen_Unit, Act_Unit, Assoc_Null);
12261    end Set_Instance_Env;
12262
12263    -----------------
12264    -- Switch_View --
12265    -----------------
12266
12267    procedure Switch_View (T : Entity_Id) is
12268       BT        : constant Entity_Id := Base_Type (T);
12269       Priv_Elmt : Elmt_Id := No_Elmt;
12270       Priv_Sub  : Entity_Id;
12271
12272    begin
12273       --  T may be private but its base type may have been exchanged through
12274       --  some other occurrence, in which case there is nothing to switch
12275       --  besides T itself. Note that a private dependent subtype of a private
12276       --  type might not have been switched even if the base type has been,
12277       --  because of the last branch of Check_Private_View (see comment there).
12278
12279       if not Is_Private_Type (BT) then
12280          Prepend_Elmt (Full_View (T), Exchanged_Views);
12281          Exchange_Declarations (T);
12282          return;
12283       end if;
12284
12285       Priv_Elmt := First_Elmt (Private_Dependents (BT));
12286
12287       if Present (Full_View (BT)) then
12288          Prepend_Elmt (Full_View (BT), Exchanged_Views);
12289          Exchange_Declarations (BT);
12290       end if;
12291
12292       while Present (Priv_Elmt) loop
12293          Priv_Sub := (Node (Priv_Elmt));
12294
12295          --  We avoid flipping the subtype if the Etype of its full view is
12296          --  private because this would result in a malformed subtype. This
12297          --  occurs when the Etype of the subtype full view is the full view of
12298          --  the base type (and since the base types were just switched, the
12299          --  subtype is pointing to the wrong view). This is currently the case
12300          --  for tagged record types, access types (maybe more?) and needs to
12301          --  be resolved. ???
12302
12303          if Present (Full_View (Priv_Sub))
12304            and then not Is_Private_Type (Etype (Full_View (Priv_Sub)))
12305          then
12306             Prepend_Elmt (Full_View (Priv_Sub), Exchanged_Views);
12307             Exchange_Declarations (Priv_Sub);
12308          end if;
12309
12310          Next_Elmt (Priv_Elmt);
12311       end loop;
12312    end Switch_View;
12313
12314    -----------------------------
12315    -- Valid_Default_Attribute --
12316    -----------------------------
12317
12318    procedure Valid_Default_Attribute (Nam : Entity_Id; Def : Node_Id) is
12319       Attr_Id : constant Attribute_Id :=
12320                   Get_Attribute_Id (Attribute_Name (Def));
12321       T       : constant Entity_Id := Entity (Prefix (Def));
12322       Is_Fun  : constant Boolean := (Ekind (Nam) = E_Function);
12323       F       : Entity_Id;
12324       Num_F   : Int;
12325       OK      : Boolean;
12326
12327    begin
12328       if No (T)
12329         or else T = Any_Id
12330       then
12331          return;
12332       end if;
12333
12334       Num_F := 0;
12335       F := First_Formal (Nam);
12336       while Present (F) loop
12337          Num_F := Num_F + 1;
12338          Next_Formal (F);
12339       end loop;
12340
12341       case Attr_Id is
12342          when Attribute_Adjacent |  Attribute_Ceiling   | Attribute_Copy_Sign |
12343               Attribute_Floor    |  Attribute_Fraction  | Attribute_Machine   |
12344               Attribute_Model    |  Attribute_Remainder | Attribute_Rounding  |
12345               Attribute_Unbiased_Rounding  =>
12346             OK := Is_Fun
12347                     and then Num_F = 1
12348                     and then Is_Floating_Point_Type (T);
12349
12350          when Attribute_Image    | Attribute_Pred       | Attribute_Succ |
12351               Attribute_Value    | Attribute_Wide_Image |
12352               Attribute_Wide_Value  =>
12353             OK := (Is_Fun and then Num_F = 1 and then Is_Scalar_Type (T));
12354
12355          when Attribute_Max      |  Attribute_Min  =>
12356             OK := (Is_Fun and then Num_F = 2 and then Is_Scalar_Type (T));
12357
12358          when Attribute_Input =>
12359             OK := (Is_Fun and then Num_F = 1);
12360
12361          when Attribute_Output | Attribute_Read | Attribute_Write =>
12362             OK := (not Is_Fun and then Num_F = 2);
12363
12364          when others =>
12365             OK := False;
12366       end case;
12367
12368       if not OK then
12369          Error_Msg_N ("attribute reference has wrong profile for subprogram",
12370            Def);
12371       end if;
12372    end Valid_Default_Attribute;
12373
12374 end Sem_Ch12;