OSDN Git Service

2009-07-15 Ed Schonberg <schonberg@adacore.com>
[pf3gnuchains/gcc-fork.git] / gcc / ada / sem_ch10.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT COMPILER COMPONENTS                         --
4 --                                                                          --
5 --                             S E M _ C H 1 0                              --
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 Debug;    use Debug;
28 with Einfo;    use Einfo;
29 with Errout;   use Errout;
30 with Exp_Util; use Exp_Util;
31 with Elists;   use Elists;
32 with Fname;    use Fname;
33 with Fname.UF; use Fname.UF;
34 with Freeze;   use Freeze;
35 with Impunit;  use Impunit;
36 with Inline;   use Inline;
37 with Lib;      use Lib;
38 with Lib.Load; use Lib.Load;
39 with Lib.Xref; use Lib.Xref;
40 with Namet;    use Namet;
41 with Nlists;   use Nlists;
42 with Nmake;    use Nmake;
43 with Opt;      use Opt;
44 with Output;   use Output;
45 with Par_SCO;  use Par_SCO;
46 with Restrict; use Restrict;
47 with Rident;   use Rident;
48 with Rtsfind;  use Rtsfind;
49 with Sem;      use Sem;
50 with Sem_Ch3;  use Sem_Ch3;
51 with Sem_Ch6;  use Sem_Ch6;
52 with Sem_Ch7;  use Sem_Ch7;
53 with Sem_Ch8;  use Sem_Ch8;
54 with Sem_Dist; use Sem_Dist;
55 with Sem_Prag; use Sem_Prag;
56 with Sem_Util; use Sem_Util;
57 with Sem_Warn; use Sem_Warn;
58 with Stand;    use Stand;
59 with Sinfo;    use Sinfo;
60 with Sinfo.CN; use Sinfo.CN;
61 with Sinput;   use Sinput;
62 with Snames;   use Snames;
63 with Style;    use Style;
64 with Stylesw;  use Stylesw;
65 with Tbuild;   use Tbuild;
66 with Uname;    use Uname;
67
68 package body Sem_Ch10 is
69
70    -----------------------
71    -- Local Subprograms --
72    -----------------------
73
74    procedure Analyze_Context (N : Node_Id);
75    --  Analyzes items in the context clause of compilation unit
76
77    procedure Build_Limited_Views (N : Node_Id);
78    --  Build and decorate the list of shadow entities for a package mentioned
79    --  in a limited_with clause. If the package was not previously analyzed
80    --  then it also performs a basic decoration of the real entities; this
81    --  is required to do not pass non-decorated entities to the back-end.
82    --  Implements Ada 2005 (AI-50217).
83
84    procedure Check_Body_Needed_For_SAL (Unit_Name : Entity_Id);
85    --  Check whether the source for the body of a compilation unit must
86    --  be included in a standalone library.
87
88    procedure Check_Private_Child_Unit (N : Node_Id);
89    --  If a with_clause mentions a private child unit, the compilation
90    --  unit must be a member of the same family, as described in 10.1.2.
91
92    procedure Check_Stub_Level (N : Node_Id);
93    --  Verify that a stub is declared immediately within a compilation unit,
94    --  and not in an inner frame.
95
96    procedure Expand_With_Clause (Item : Node_Id; Nam : Node_Id; N : Node_Id);
97    --  When a child unit appears in a context clause, the implicit withs on
98    --  parents are made explicit, and with clauses are inserted in the context
99    --  clause before the one for the child. If a parent in the with_clause
100    --  is a renaming, the implicit with_clause is on the renaming whose name
101    --  is mentioned in the with_clause, and not on the package it renames.
102    --  N is the compilation unit whose list of context items receives the
103    --  implicit with_clauses.
104
105    function Get_Parent_Entity (Unit : Node_Id) return Entity_Id;
106    --  Get defining entity of parent unit of a child unit. In most cases this
107    --  is the defining entity of the unit, but for a child instance whose
108    --  parent needs a body for inlining, the instantiation node of the parent
109    --  has not yet been rewritten as a package declaration, and the entity has
110    --  to be retrieved from the Instance_Spec of the unit.
111
112    function Has_With_Clause
113      (C_Unit     : Node_Id;
114       Pack       : Entity_Id;
115       Is_Limited : Boolean := False) return Boolean;
116    --  Determine whether compilation unit C_Unit contains a [limited] with
117    --  clause for package Pack. Use the flag Is_Limited to designate desired
118    --  clause kind.
119
120    procedure Implicit_With_On_Parent (Child_Unit : Node_Id; N : Node_Id);
121    --  If the main unit is a child unit, implicit withs are also added for
122    --  all its ancestors.
123
124    function In_Chain (E : Entity_Id) return Boolean;
125    --  Check that the shadow entity is not already in the homonym chain, for
126    --  example through a limited_with clause in a parent unit.
127
128    procedure Install_Context_Clauses (N : Node_Id);
129    --  Subsidiary to Install_Context and Install_Parents. Process only with_
130    --  and use_clauses for current unit and its library unit if any.
131
132    procedure Install_Limited_Context_Clauses (N : Node_Id);
133    --  Subsidiary to Install_Context. Process only limited with_clauses
134    --  for current unit. Implements Ada 2005 (AI-50217).
135
136    procedure Install_Limited_Withed_Unit (N : Node_Id);
137    --  Place shadow entities for a limited_with package in the visibility
138    --  structures for the current compilation. Implements Ada 2005 (AI-50217).
139
140    procedure Install_Withed_Unit
141      (With_Clause     : Node_Id;
142       Private_With_OK : Boolean := False);
143    --  If the unit is not a child unit, make unit immediately visible.
144    --  The caller ensures that the unit is not already currently installed.
145    --  The flag Private_With_OK is set true in Install_Private_With_Clauses,
146    --  which is called when compiling the private part of a package, or
147    --  installing the private declarations of a parent unit.
148
149    procedure Install_Parents (Lib_Unit : Node_Id; Is_Private : Boolean);
150    --  This procedure establishes the context for the compilation of a child
151    --  unit. If Lib_Unit is a child library spec then the context of the parent
152    --  is installed, and the parent itself made immediately visible, so that
153    --  the child unit is processed in the declarative region of the parent.
154    --  Install_Parents makes a recursive call to itself to ensure that all
155    --  parents are loaded in the nested case. If Lib_Unit is a library body,
156    --  the only effect of Install_Parents is to install the private decls of
157    --  the parents, because the visible parent declarations will have been
158    --  installed as part of the context of the corresponding spec.
159
160    procedure Install_Siblings (U_Name : Entity_Id; N : Node_Id);
161    --  In the compilation of a child unit, a child of any of the  ancestor
162    --  units is directly visible if it is visible, because the parent is in
163    --  an enclosing scope. Iterate over context to find child units of U_Name
164    --  or of some ancestor of it.
165
166    function Is_Child_Spec (Lib_Unit : Node_Id) return Boolean;
167    --  Lib_Unit is a library unit which may be a spec or a body. Is_Child_Spec
168    --  returns True if Lib_Unit is a library spec which is a child spec, i.e.
169    --  a library spec that has a parent. If the call to Is_Child_Spec returns
170    --  True, then Parent_Spec (Lib_Unit) is non-Empty and points to the
171    --  compilation unit for the parent spec.
172    --
173    --  Lib_Unit can also be a subprogram body that acts as its own spec. If
174    --  the Parent_Spec is  non-empty, this is also a child unit.
175
176    procedure Remove_Context_Clauses (N : Node_Id);
177    --  Subsidiary of previous one. Remove use_ and with_clauses
178
179    procedure Remove_Limited_With_Clause (N : Node_Id);
180    --  Remove from visibility the shadow entities introduced for a package
181    --  mentioned in a limited_with clause. Implements Ada 2005 (AI-50217).
182
183    procedure Remove_Parents (Lib_Unit : Node_Id);
184    --  Remove_Parents checks if Lib_Unit is a child spec. If so then the parent
185    --  contexts established by the corresponding call to Install_Parents are
186    --  removed. Remove_Parents contains a recursive call to itself to ensure
187    --  that all parents are removed in the nested case.
188
189    procedure Remove_Unit_From_Visibility (Unit_Name : Entity_Id);
190    --  Reset all visibility flags on unit after compiling it, either as a
191    --  main unit or as a unit in the context.
192
193    procedure Unchain (E : Entity_Id);
194    --  Remove single entity from visibility list
195
196    procedure Analyze_Proper_Body (N : Node_Id; Nam : Entity_Id);
197    --  Common processing for all stubs (subprograms, tasks, packages, and
198    --  protected cases). N is the stub to be analyzed. Once the subunit
199    --  name is established, load and analyze. Nam is the non-overloadable
200    --  entity for which the proper body provides a completion. Subprogram
201    --  stubs are handled differently because they can be declarations.
202
203    procedure sm;
204    --  A dummy procedure, for debugging use, called just before analyzing the
205    --  main unit (after dealing with any context clauses).
206
207    --------------------------
208    -- Limited_With_Clauses --
209    --------------------------
210
211    --  Limited_With clauses are the mechanism chosen for Ada05 to support
212    --  mutually recursive types declared in different units. A limited_with
213    --  clause that names package P in the context of unit U makes the types
214    --  declared in the visible part of P available within U, but with the
215    --  restriction that these types can only be used as incomplete types.
216    --  The limited_with clause does not impose a semantic dependence on P,
217    --  and it is possible for two packages to have limited_with_clauses on
218    --  each other without creating an elaboration circularity.
219
220    --  To support this feature, the analysis of a limited_with clause must
221    --  create an abbreviated view of the package, without performing any
222    --  semantic analysis on it. This "package abstract" contains shadow
223    --  types that are in one-one correspondence with the real types in the
224    --  package, and that have the properties of incomplete types.
225
226    --  The implementation creates two element lists: one to chain the shadow
227    --  entities, and one to chain the corresponding type entities in the tree
228    --  of the package. Links between corresponding entities in both chains
229    --  allow the compiler to select the proper view of a given type, depending
230    --  on the context. Note that in contrast with the handling of private
231    --  types, the limited view and the non-limited view of a type are treated
232    --  as separate entities, and no entity exchange needs to take place, which
233    --  makes the implementation must simpler than could be feared.
234
235    ------------------------------
236    -- Analyze_Compilation_Unit --
237    ------------------------------
238
239    procedure Analyze_Compilation_Unit (N : Node_Id) is
240       Unit_Node     : constant Node_Id := Unit (N);
241       Lib_Unit      : Node_Id          := Library_Unit (N);
242       Spec_Id       : Entity_Id;
243       Main_Cunit    : constant Node_Id := Cunit (Main_Unit);
244       Par_Spec_Name : Unit_Name_Type;
245       Unum          : Unit_Number_Type;
246
247       procedure Check_Redundant_Withs
248         (Context_Items      : List_Id;
249          Spec_Context_Items : List_Id := No_List);
250       --  Determine whether the context list of a compilation unit contains
251       --  redundant with clauses. When checking body clauses against spec
252       --  clauses, set Context_Items to the context list of the body and
253       --  Spec_Context_Items to that of the spec. Parent packages are not
254       --  examined for documentation purposes.
255
256       procedure Generate_Parent_References (N : Node_Id; P_Id : Entity_Id);
257       --  Generate cross-reference information for the parents of child units.
258       --  N is a defining_program_unit_name, and P_Id is the immediate parent.
259
260       ---------------------------
261       -- Check_Redundant_Withs --
262       ---------------------------
263
264       procedure Check_Redundant_Withs
265         (Context_Items      : List_Id;
266          Spec_Context_Items : List_Id := No_List)
267       is
268          Clause : Node_Id;
269
270          procedure Process_Body_Clauses
271           (Context_List      : List_Id;
272            Clause            : Node_Id;
273            Used              : in out Boolean;
274            Used_Type_Or_Elab : in out Boolean);
275          --  Examine the context clauses of a package body, trying to match
276          --  the name entity of Clause with any list element. If the match
277          --  occurs on a use package clause, set Used to True, for a use
278          --  type clause, pragma Elaborate or pragma Elaborate_All, set
279          --  Used_Type_Or_Elab to True.
280
281          procedure Process_Spec_Clauses
282           (Context_List : List_Id;
283            Clause       : Node_Id;
284            Used         : in out Boolean;
285            Withed       : in out Boolean;
286            Exit_On_Self : Boolean := False);
287          --  Examine the context clauses of a package spec, trying to match
288          --  the name entity of Clause with any list element. If the match
289          --  occurs on a use package clause, set Used to True, for a with
290          --  package clause other than Clause, set Withed to True. Limited
291          --  with clauses, implicitly generated with clauses and withs
292          --  having pragmas Elaborate or Elaborate_All applied to them are
293          --  skipped. Exit_On_Self is used to control the search loop and
294          --  force an exit whenever Clause sees itself in the search.
295
296          --------------------------
297          -- Process_Body_Clauses --
298          --------------------------
299
300          procedure Process_Body_Clauses
301           (Context_List      : List_Id;
302            Clause            : Node_Id;
303            Used              : in out Boolean;
304            Used_Type_Or_Elab : in out Boolean)
305          is
306             Nam_Ent   : constant Entity_Id := Entity (Name (Clause));
307             Cont_Item : Node_Id;
308             Prag_Unit : Node_Id;
309             Subt_Mark : Node_Id;
310             Use_Item  : Node_Id;
311
312             function Same_Unit (N : Node_Id; P : Entity_Id) return Boolean;
313             --  In an expanded name in a use clause, if the prefix is a
314             --  renamed package, the entity is set to the original package
315             --  as a result, when checking whether the package appears in a
316             --  previous with_clause, the renaming has to be taken into
317             --  account, to prevent spurious or incorrect warnings. The
318             --  common case is the use of Text_IO.
319
320             ---------------
321             -- Same_Unit --
322             ---------------
323
324             function Same_Unit (N : Node_Id; P : Entity_Id) return Boolean is
325             begin
326                return Entity (N) = P
327                  or else
328                    (Present (Renamed_Object (P))
329                      and then Entity (N) = Renamed_Object (P));
330             end Same_Unit;
331
332          --  Start of processing for Process_Body_Clauses
333
334          begin
335             Used := False;
336             Used_Type_Or_Elab := False;
337
338             Cont_Item := First (Context_List);
339             while Present (Cont_Item) loop
340
341                --  Package use clause
342
343                if Nkind (Cont_Item) = N_Use_Package_Clause
344                  and then not Used
345                then
346                   --  Search through use clauses
347
348                   Use_Item := First (Names (Cont_Item));
349                   while Present (Use_Item) and then not Used loop
350
351                      --  Case of a direct use of the one we are looking for
352
353                      if Entity (Use_Item) = Nam_Ent then
354                         Used := True;
355
356                      --  Handle nested case, as in "with P; use P.Q.R"
357
358                      else
359                         declare
360                            UE : Node_Id;
361
362                         begin
363                            --  Loop through prefixes looking for match
364
365                            UE := Use_Item;
366                            while Nkind (UE) = N_Expanded_Name loop
367                               if Same_Unit (Prefix (UE), Nam_Ent) then
368                                  Used := True;
369                                  exit;
370                               end if;
371
372                               UE := Prefix (UE);
373                            end loop;
374                         end;
375                      end if;
376
377                      Next (Use_Item);
378                   end loop;
379
380                --  USE TYPE clause
381
382                elsif Nkind (Cont_Item) = N_Use_Type_Clause
383                  and then not Used_Type_Or_Elab
384                then
385                   Subt_Mark := First (Subtype_Marks (Cont_Item));
386                   while Present (Subt_Mark)
387                     and then not Used_Type_Or_Elab
388                   loop
389                      if Same_Unit (Prefix (Subt_Mark), Nam_Ent) then
390                         Used_Type_Or_Elab := True;
391                      end if;
392
393                      Next (Subt_Mark);
394                   end loop;
395
396                --  Pragma Elaborate or Elaborate_All
397
398                elsif Nkind (Cont_Item) = N_Pragma
399                  and then
400                    (Pragma_Name (Cont_Item) = Name_Elaborate
401                       or else
402                     Pragma_Name (Cont_Item) = Name_Elaborate_All)
403                  and then not Used_Type_Or_Elab
404                then
405                   Prag_Unit :=
406                     First (Pragma_Argument_Associations (Cont_Item));
407                   while Present (Prag_Unit)
408                     and then not Used_Type_Or_Elab
409                   loop
410                      if Entity (Expression (Prag_Unit)) = Nam_Ent then
411                         Used_Type_Or_Elab := True;
412                      end if;
413
414                      Next (Prag_Unit);
415                   end loop;
416                end if;
417
418                Next (Cont_Item);
419             end loop;
420          end Process_Body_Clauses;
421
422          --------------------------
423          -- Process_Spec_Clauses --
424          --------------------------
425
426          procedure Process_Spec_Clauses
427           (Context_List : List_Id;
428            Clause       : Node_Id;
429            Used         : in out Boolean;
430            Withed       : in out Boolean;
431            Exit_On_Self : Boolean := False)
432          is
433             Nam_Ent   : constant Entity_Id := Entity (Name (Clause));
434             Cont_Item : Node_Id;
435             Use_Item  : Node_Id;
436
437          begin
438             Used := False;
439             Withed := False;
440
441             Cont_Item := First (Context_List);
442             while Present (Cont_Item) loop
443
444                --  Stop the search since the context items after Cont_Item
445                --  have already been examined in a previous iteration of
446                --  the reverse loop in Check_Redundant_Withs.
447
448                if Exit_On_Self
449                  and Cont_Item = Clause
450                then
451                   exit;
452                end if;
453
454                --  Package use clause
455
456                if Nkind (Cont_Item) = N_Use_Package_Clause
457                  and then not Used
458                then
459                   Use_Item := First (Names (Cont_Item));
460                   while Present (Use_Item) and then not Used loop
461                      if Entity (Use_Item) = Nam_Ent then
462                         Used := True;
463                      end if;
464
465                      Next (Use_Item);
466                   end loop;
467
468                --  Package with clause. Avoid processing self, implicitly
469                --  generated with clauses or limited with clauses. Note
470                --  that we examine with clauses having pragmas Elaborate
471                --  or Elaborate_All applied to them due to cases such as:
472                --
473                --     with Pack;
474                --     with Pack;
475                --     pragma Elaborate (Pack);
476                --
477                --  In this case, the second with clause is redundant since
478                --  the pragma applies only to the first "with Pack;".
479
480                elsif Nkind (Cont_Item) = N_With_Clause
481                  and then not Implicit_With (Cont_Item)
482                  and then not Limited_Present (Cont_Item)
483                  and then Cont_Item /= Clause
484                  and then Entity (Name (Cont_Item)) = Nam_Ent
485                then
486                   Withed := True;
487                end if;
488
489                Next (Cont_Item);
490             end loop;
491          end Process_Spec_Clauses;
492
493       --  Start of processing for Check_Redundant_Withs
494
495       begin
496          Clause := Last (Context_Items);
497          while Present (Clause) loop
498
499             --  Avoid checking implicitly generated with clauses, limited
500             --  with clauses or withs that have pragma Elaborate or
501             --  Elaborate_All applied.
502
503             if Nkind (Clause) = N_With_Clause
504               and then not Implicit_With (Clause)
505               and then not Limited_Present (Clause)
506               and then not Elaborate_Present (Clause)
507             then
508                --  Package body-to-spec check
509
510                if Present (Spec_Context_Items) then
511                   declare
512                      Used_In_Body      : Boolean := False;
513                      Used_In_Spec      : Boolean := False;
514                      Used_Type_Or_Elab : Boolean := False;
515                      Withed_In_Spec    : Boolean := False;
516
517                   begin
518                      Process_Spec_Clauses
519                       (Context_List => Spec_Context_Items,
520                        Clause       => Clause,
521                        Used         => Used_In_Spec,
522                        Withed       => Withed_In_Spec);
523
524                      Process_Body_Clauses
525                       (Context_List      => Context_Items,
526                        Clause            => Clause,
527                        Used              => Used_In_Body,
528                        Used_Type_Or_Elab => Used_Type_Or_Elab);
529
530                      --  "Type Elab" refers to the presence of either a use
531                      --  type clause, pragmas Elaborate or Elaborate_All.
532
533                      --  +---------------+---------------------------+------+
534                      --  | Spec          | Body                      | Warn |
535                      --  +--------+------+--------+------+-----------+------+
536                      --  | Withed | Used | Withed | Used | Type Elab |      |
537                      --  |   X    |      |   X    |      |           |  X   |
538                      --  |   X    |      |   X    |  X   |           |      |
539                      --  |   X    |      |   X    |      |     X     |      |
540                      --  |   X    |      |   X    |  X   |     X     |      |
541                      --  |   X    |  X   |   X    |      |           |  X   |
542                      --  |   X    |  X   |   X    |      |     X     |      |
543                      --  |   X    |  X   |   X    |  X   |           |  X   |
544                      --  |   X    |  X   |   X    |  X   |     X     |      |
545                      --  +--------+------+--------+------+-----------+------+
546
547                      if (Withed_In_Spec
548                            and then not Used_Type_Or_Elab)
549                              and then
550                                ((not Used_In_Spec
551                                    and then not Used_In_Body)
552                                      or else
553                                        Used_In_Spec)
554                      then
555                         Error_Msg_N ("?redundant with clause in body", Clause);
556                      end if;
557
558                      Used_In_Body := False;
559                      Used_In_Spec := False;
560                      Used_Type_Or_Elab := False;
561                      Withed_In_Spec := False;
562                   end;
563
564                --  Standalone package spec or body check
565
566                else
567                   declare
568                      Dont_Care : Boolean := False;
569                      Withed    : Boolean := False;
570
571                   begin
572                      --  The mechanism for examining the context clauses of a
573                      --  package spec can be applied to package body clauses.
574
575                      Process_Spec_Clauses
576                       (Context_List => Context_Items,
577                        Clause       => Clause,
578                        Used         => Dont_Care,
579                        Withed       => Withed,
580                        Exit_On_Self => True);
581
582                      if Withed then
583                         Error_Msg_N ("?redundant with clause", Clause);
584                      end if;
585                   end;
586                end if;
587             end if;
588
589             Prev (Clause);
590          end loop;
591       end Check_Redundant_Withs;
592
593       --------------------------------
594       -- Generate_Parent_References --
595       --------------------------------
596
597       procedure Generate_Parent_References (N : Node_Id; P_Id : Entity_Id) is
598          Pref   : Node_Id;
599          P_Name : Entity_Id := P_Id;
600
601       begin
602          Pref := Name (Parent (Defining_Entity (N)));
603
604          if Nkind (Pref) = N_Expanded_Name then
605
606             --  Done already, if the unit has been compiled indirectly as
607             --  part of the closure of its context because of inlining.
608
609             return;
610          end if;
611
612          while Nkind (Pref) = N_Selected_Component loop
613             Change_Selected_Component_To_Expanded_Name (Pref);
614             Set_Entity (Pref, P_Name);
615             Set_Etype (Pref, Etype (P_Name));
616             Generate_Reference (P_Name, Pref, 'r');
617             Pref   := Prefix (Pref);
618             P_Name := Scope (P_Name);
619          end loop;
620
621          --  The guard here on P_Name is to handle the error condition where
622          --  the parent unit is missing because the file was not found.
623
624          if Present (P_Name) then
625             Set_Entity (Pref, P_Name);
626             Set_Etype (Pref, Etype (P_Name));
627             Generate_Reference (P_Name, Pref, 'r');
628             Style.Check_Identifier (Pref, P_Name);
629          end if;
630       end Generate_Parent_References;
631
632    --  Start of processing for Analyze_Compilation_Unit
633
634    begin
635       Process_Compilation_Unit_Pragmas (N);
636
637       --  If the unit is a subunit whose parent has not been analyzed (which
638       --  indicates that the main unit is a subunit, either the current one or
639       --  one of its descendents) then the subunit is compiled as part of the
640       --  analysis of the parent, which we proceed to do. Basically this gets
641       --  handled from the top down and we don't want to do anything at this
642       --  level (i.e. this subunit will be handled on the way down from the
643       --  parent), so at this level we immediately return. If the subunit
644       --  ends up not analyzed, it means that the parent did not contain a
645       --  stub for it, or that there errors were detected in some ancestor.
646
647       if Nkind (Unit_Node) = N_Subunit
648         and then not Analyzed (Lib_Unit)
649       then
650          Semantics (Lib_Unit);
651
652          if not Analyzed (Proper_Body (Unit_Node)) then
653             if Serious_Errors_Detected > 0 then
654                Error_Msg_N ("subunit not analyzed (errors in parent unit)", N);
655             else
656                Error_Msg_N ("missing stub for subunit", N);
657             end if;
658          end if;
659
660          return;
661       end if;
662
663       --  Analyze context (this will call Sem recursively for with'ed units)
664
665       Analyze_Context (N);
666
667       --  If the unit is a package body, the spec is already loaded and must
668       --  be analyzed first, before we analyze the body.
669
670       if Nkind (Unit_Node) = N_Package_Body then
671
672          --  If no Lib_Unit, then there was a serious previous error, so
673          --  just ignore the entire analysis effort
674
675          if No (Lib_Unit) then
676             return;
677
678          else
679             Semantics (Lib_Unit);
680             Check_Unused_Withs (Get_Cunit_Unit_Number (Lib_Unit));
681
682             --  Verify that the library unit is a package declaration
683
684             if not Nkind_In (Unit (Lib_Unit), N_Package_Declaration,
685                                               N_Generic_Package_Declaration)
686             then
687                Error_Msg_N
688                  ("no legal package declaration for package body", N);
689                return;
690
691             --  Otherwise, the entity in the declaration is visible. Update
692             --  the version to reflect dependence of this body on the spec.
693
694             else
695                Spec_Id := Defining_Entity (Unit (Lib_Unit));
696                Set_Is_Immediately_Visible (Spec_Id, True);
697                Version_Update (N, Lib_Unit);
698
699                if Nkind (Defining_Unit_Name (Unit_Node)) =
700                                              N_Defining_Program_Unit_Name
701                then
702                   Generate_Parent_References (Unit_Node, Scope (Spec_Id));
703                end if;
704             end if;
705          end if;
706
707       --  If the unit is a subprogram body, then we similarly need to analyze
708       --  its spec. However, things are a little simpler in this case, because
709       --  here, this analysis is done only for error checking and consistency
710       --  purposes, so there's nothing else to be done.
711
712       elsif Nkind (Unit_Node) = N_Subprogram_Body then
713          if Acts_As_Spec (N) then
714
715             --  If the subprogram body is a child unit, we must create a
716             --  declaration for it, in order to properly load the parent(s).
717             --  After this, the original unit does not acts as a spec, because
718             --  there is an explicit one. If this unit appears in a context
719             --  clause, then an implicit with on the parent will be added when
720             --  installing the context. If this is the main unit, there is no
721             --  Unit_Table entry for the declaration (it has the unit number
722             --  of the main unit) and code generation is unaffected.
723
724             Unum := Get_Cunit_Unit_Number (N);
725             Par_Spec_Name := Get_Parent_Spec_Name (Unit_Name (Unum));
726
727             if Par_Spec_Name /= No_Unit_Name then
728                Unum :=
729                  Load_Unit
730                    (Load_Name  => Par_Spec_Name,
731                     Required   => True,
732                     Subunit    => False,
733                     Error_Node => N);
734
735                if Unum /= No_Unit then
736
737                   --  Build subprogram declaration and attach parent unit to it
738                   --  This subprogram declaration does not come from source,
739                   --  Nevertheless the backend must generate debugging info for
740                   --  it, and this must be indicated explicitly. We also mark
741                   --  the body entity as a child unit now, to prevent a
742                   --  cascaded error if the spec entity cannot be entered
743                   --  in its scope. Finally we create a Units table entry for
744                   --  the subprogram declaration, to maintain a one-to-one
745                   --  correspondence with compilation unit nodes. This is
746                   --  critical for the tree traversals performed by CodePeer.
747
748                   declare
749                      Loc : constant Source_Ptr := Sloc (N);
750                      SCS : constant Boolean :=
751                              Get_Comes_From_Source_Default;
752
753                   begin
754                      Set_Comes_From_Source_Default (False);
755                      Lib_Unit :=
756                        Make_Compilation_Unit (Loc,
757                          Context_Items => New_Copy_List (Context_Items (N)),
758                          Unit =>
759                            Make_Subprogram_Declaration (Sloc (N),
760                              Specification =>
761                                Copy_Separate_Tree
762                                  (Specification (Unit_Node))),
763                          Aux_Decls_Node =>
764                            Make_Compilation_Unit_Aux (Loc));
765
766                      Set_Library_Unit (N, Lib_Unit);
767                      Set_Parent_Spec (Unit (Lib_Unit), Cunit (Unum));
768                      Make_Child_Decl_Unit (N);
769                      Semantics (Lib_Unit);
770
771                      --  Now that a separate declaration exists, the body
772                      --  of the child unit does not act as spec any longer.
773
774                      Set_Acts_As_Spec (N, False);
775                      Set_Is_Child_Unit (Defining_Entity (Unit_Node));
776                      Set_Debug_Info_Needed (Defining_Entity (Unit (Lib_Unit)));
777                      Set_Comes_From_Source_Default (SCS);
778                   end;
779                end if;
780             end if;
781
782          --  Here for subprogram with separate declaration
783
784          else
785             Semantics (Lib_Unit);
786             Check_Unused_Withs (Get_Cunit_Unit_Number (Lib_Unit));
787             Version_Update (N, Lib_Unit);
788          end if;
789
790          --  If this is a child unit, generate references to the parents
791
792          if Nkind (Defining_Unit_Name (Specification (Unit_Node))) =
793                                              N_Defining_Program_Unit_Name
794          then
795             Generate_Parent_References (
796               Specification (Unit_Node),
797                 Scope (Defining_Entity (Unit (Lib_Unit))));
798          end if;
799       end if;
800
801       --  If it is a child unit, the parent must be elaborated first and we
802       --  update version, since we are dependent on our parent.
803
804       if Is_Child_Spec (Unit_Node) then
805
806          --  The analysis of the parent is done with style checks off
807
808          declare
809             Save_Style_Check : constant Boolean := Style_Check;
810             Save_C_Restrict  : constant Save_Cunit_Boolean_Restrictions :=
811                                  Cunit_Boolean_Restrictions_Save;
812
813          begin
814             if not GNAT_Mode then
815                Style_Check := False;
816             end if;
817
818             Semantics (Parent_Spec (Unit_Node));
819             Version_Update (N, Parent_Spec (Unit_Node));
820             Style_Check := Save_Style_Check;
821             Cunit_Boolean_Restrictions_Restore (Save_C_Restrict);
822          end;
823       end if;
824
825       --  With the analysis done, install the context. Note that we can't
826       --  install the context from the with clauses as we analyze them, because
827       --  each with clause must be analyzed in a clean visibility context, so
828       --  we have to wait and install them all at once.
829
830       Install_Context (N);
831
832       if Is_Child_Spec (Unit_Node) then
833
834          --  Set the entities of all parents in the program_unit_name
835
836          Generate_Parent_References (
837            Unit_Node, Get_Parent_Entity (Unit (Parent_Spec (Unit_Node))));
838       end if;
839
840       --  All components of the context: with-clauses, library unit, ancestors
841       --  if any, (and their context)  are analyzed and installed.
842
843       --  Call special debug routine sm if this is the main unit
844
845       if Current_Sem_Unit = Main_Unit then
846          sm;
847       end if;
848
849       --  Now analyze the unit (package, subprogram spec, body) itself
850
851       Analyze (Unit_Node);
852
853       if Warn_On_Redundant_Constructs then
854          Check_Redundant_Withs (Context_Items (N));
855
856          if Nkind (Unit_Node) = N_Package_Body then
857             Check_Redundant_Withs
858               (Context_Items      => Context_Items (N),
859                Spec_Context_Items => Context_Items (Lib_Unit));
860          end if;
861       end if;
862
863       --  The above call might have made Unit_Node an N_Subprogram_Body from
864       --  something else, so propagate any Acts_As_Spec flag.
865
866       if Nkind (Unit_Node) = N_Subprogram_Body
867         and then Acts_As_Spec (Unit_Node)
868       then
869          Set_Acts_As_Spec (N);
870       end if;
871
872       --  Register predefined units in Rtsfind
873
874       declare
875          Unum : constant Unit_Number_Type := Get_Source_Unit (Sloc (N));
876       begin
877          if Is_Predefined_File_Name (Unit_File_Name (Unum)) then
878             Set_RTU_Loaded (Unit_Node);
879          end if;
880       end;
881
882       --  Treat compilation unit pragmas that appear after the library unit
883
884       if Present (Pragmas_After (Aux_Decls_Node (N))) then
885          declare
886             Prag_Node : Node_Id := First (Pragmas_After (Aux_Decls_Node (N)));
887          begin
888             while Present (Prag_Node) loop
889                Analyze (Prag_Node);
890                Next (Prag_Node);
891             end loop;
892          end;
893       end if;
894
895       --  Generate distribution stubs if requested and no error
896
897       if N = Main_Cunit
898         and then (Distribution_Stub_Mode = Generate_Receiver_Stub_Body
899                     or else
900                   Distribution_Stub_Mode = Generate_Caller_Stub_Body)
901         and then not Fatal_Error (Main_Unit)
902       then
903          if Is_RCI_Pkg_Spec_Or_Body (N) then
904
905             --  Regular RCI package
906
907             Add_Stub_Constructs (N);
908
909          elsif (Nkind (Unit_Node) = N_Package_Declaration
910                  and then Is_Shared_Passive (Defining_Entity
911                                               (Specification (Unit_Node))))
912            or else (Nkind (Unit_Node) = N_Package_Body
913                      and then
914                        Is_Shared_Passive (Corresponding_Spec (Unit_Node)))
915          then
916             --  Shared passive package
917
918             Add_Stub_Constructs (N);
919
920          elsif Nkind (Unit_Node) = N_Package_Instantiation
921            and then
922              Is_Remote_Call_Interface
923                (Defining_Entity (Specification (Instance_Spec (Unit_Node))))
924          then
925             --  Instantiation of a RCI generic package
926
927             Add_Stub_Constructs (N);
928          end if;
929       end if;
930
931       --  Remove unit from visibility, so that environment is clean for
932       --  the next compilation, which is either the main unit or some
933       --  other unit in the context.
934
935       if Nkind_In (Unit_Node, N_Package_Declaration,
936                               N_Package_Renaming_Declaration,
937                               N_Subprogram_Declaration)
938         or else Nkind (Unit_Node) in N_Generic_Declaration
939         or else
940           (Nkind (Unit_Node) = N_Subprogram_Body
941             and then Acts_As_Spec (Unit_Node))
942       then
943          Remove_Unit_From_Visibility (Defining_Entity (Unit_Node));
944
945       --  If the unit is an instantiation whose body will be elaborated for
946       --  inlining purposes, use the proper entity of the instance. The
947       --  entity may be missing if the instantiation was illegal.
948
949       elsif Nkind (Unit_Node) = N_Package_Instantiation
950         and then not Error_Posted (Unit_Node)
951         and then Present (Instance_Spec (Unit_Node))
952       then
953          Remove_Unit_From_Visibility
954            (Defining_Entity (Instance_Spec (Unit_Node)));
955
956       elsif Nkind (Unit_Node) = N_Package_Body
957         or else (Nkind (Unit_Node) = N_Subprogram_Body
958                   and then not Acts_As_Spec (Unit_Node))
959       then
960          --  Bodies that are not the main unit are compiled if they are generic
961          --  or contain generic or inlined units. Their analysis brings in the
962          --  context of the corresponding spec (unit declaration) which must be
963          --  removed as well, to return the compilation environment to its
964          --  proper state.
965
966          Remove_Context (Lib_Unit);
967          Set_Is_Immediately_Visible (Defining_Entity (Unit (Lib_Unit)), False);
968       end if;
969
970       --  Last step is to deinstall the context we just installed as well as
971       --  the unit just compiled.
972
973       Remove_Context (N);
974
975       --  If this is the main unit and we are generating code, we must check
976       --  that all generic units in the context have a body if they need it,
977       --  even if they have not been instantiated. In the absence of .ali files
978       --  for generic units, we must force the load of the body, just to
979       --  produce the proper error if the body is absent. We skip this
980       --  verification if the main unit itself is generic.
981
982       if Get_Cunit_Unit_Number (N) = Main_Unit
983         and then Operating_Mode = Generate_Code
984         and then Expander_Active
985       then
986          --  Check whether the source for the body of the unit must be included
987          --  in a standalone library.
988
989          Check_Body_Needed_For_SAL (Cunit_Entity (Main_Unit));
990
991          --  Indicate that the main unit is now analyzed, to catch possible
992          --  circularities between it and generic bodies. Remove main unit from
993          --  visibility. This might seem superfluous, but the main unit must
994          --  not be visible in the generic body expansions that follow.
995
996          Set_Analyzed (N, True);
997          Set_Is_Immediately_Visible (Cunit_Entity (Main_Unit), False);
998
999          declare
1000             Item  : Node_Id;
1001             Nam   : Entity_Id;
1002             Un    : Unit_Number_Type;
1003
1004             Save_Style_Check : constant Boolean := Style_Check;
1005             Save_C_Restrict  : constant Save_Cunit_Boolean_Restrictions :=
1006                                  Cunit_Boolean_Restrictions_Save;
1007
1008          begin
1009             Item := First (Context_Items (N));
1010             while Present (Item) loop
1011
1012                --  Check for explicit with clause
1013
1014                if Nkind (Item) = N_With_Clause
1015                  and then not Implicit_With (Item)
1016
1017                   --  Ada 2005 (AI-50217): Ignore limited-withed units
1018
1019                  and then not Limited_Present (Item)
1020                then
1021                   Nam := Entity (Name (Item));
1022
1023                   --  Compile generic subprogram, unless it is intrinsic or
1024                   --  imported so no body is required, or generic package body
1025                   --  if the package spec requires a body.
1026
1027                   if (Is_Generic_Subprogram (Nam)
1028                        and then not Is_Intrinsic_Subprogram (Nam)
1029                        and then not Is_Imported (Nam))
1030                     or else (Ekind (Nam) = E_Generic_Package
1031                               and then Unit_Requires_Body (Nam))
1032                   then
1033                      Style_Check := False;
1034
1035                      if Present (Renamed_Object (Nam)) then
1036                         Un :=
1037                            Load_Unit
1038                              (Load_Name  => Get_Body_Name
1039                                               (Get_Unit_Name
1040                                                 (Unit_Declaration_Node
1041                                                   (Renamed_Object (Nam)))),
1042                               Required   => False,
1043                               Subunit    => False,
1044                               Error_Node => N,
1045                               Renamings  => True);
1046                      else
1047                         Un :=
1048                           Load_Unit
1049                             (Load_Name  => Get_Body_Name
1050                                              (Get_Unit_Name (Item)),
1051                              Required   => False,
1052                              Subunit    => False,
1053                              Error_Node => N,
1054                              Renamings  => True);
1055                      end if;
1056
1057                      if Un = No_Unit then
1058                         Error_Msg_NE
1059                           ("body of generic unit& not found", Item, Nam);
1060                         exit;
1061
1062                      elsif not Analyzed (Cunit (Un))
1063                        and then Un /= Main_Unit
1064                        and then not Fatal_Error (Un)
1065                      then
1066                         Style_Check := False;
1067                         Semantics (Cunit (Un));
1068                      end if;
1069                   end if;
1070                end if;
1071
1072                Next (Item);
1073             end loop;
1074
1075             Style_Check := Save_Style_Check;
1076             Cunit_Boolean_Restrictions_Restore (Save_C_Restrict);
1077          end;
1078       end if;
1079
1080       --  Deal with creating elaboration Boolean if needed. We create an
1081       --  elaboration boolean only for units that come from source since
1082       --  units manufactured by the compiler never need elab checks.
1083
1084       if Comes_From_Source (N)
1085         and then Nkind_In (Unit_Node, N_Package_Declaration,
1086                                       N_Generic_Package_Declaration,
1087                                       N_Subprogram_Declaration,
1088                                       N_Generic_Subprogram_Declaration)
1089       then
1090          declare
1091             Loc  : constant Source_Ptr       := Sloc (N);
1092             Unum : constant Unit_Number_Type := Get_Source_Unit (Loc);
1093
1094          begin
1095             Spec_Id := Defining_Entity (Unit_Node);
1096             Generate_Definition (Spec_Id);
1097
1098             --  See if an elaboration entity is required for possible access
1099             --  before elaboration checking. Note that we must allow for this
1100             --  even if -gnatE is not set, since a client may be compiled in
1101             --  -gnatE mode and reference the entity.
1102
1103             --  These entities are also used by the binder to prevent multiple
1104             --  attempts to execute the elaboration code for the library case
1105             --  where the elaboration routine might otherwise be called more
1106             --  than once.
1107
1108             --  Case of units which do not require elaboration checks
1109
1110             if
1111                --  Pure units do not need checks
1112
1113                  Is_Pure (Spec_Id)
1114
1115                --  Preelaborated units do not need checks
1116
1117                  or else Is_Preelaborated (Spec_Id)
1118
1119                --  No checks needed if pragma Elaborate_Body present
1120
1121                  or else Has_Pragma_Elaborate_Body (Spec_Id)
1122
1123                --  No checks needed if unit does not require a body
1124
1125                  or else not Unit_Requires_Body (Spec_Id)
1126
1127                --  No checks needed for predefined files
1128
1129                  or else Is_Predefined_File_Name (Unit_File_Name (Unum))
1130
1131                --  No checks required if no separate spec
1132
1133                  or else Acts_As_Spec (N)
1134             then
1135                --  This is a case where we only need the entity for
1136                --  checking to prevent multiple elaboration checks.
1137
1138                Set_Elaboration_Entity_Required (Spec_Id, False);
1139
1140             --  Case of elaboration entity is required for access before
1141             --  elaboration checking (so certainly we must build it!)
1142
1143             else
1144                Set_Elaboration_Entity_Required (Spec_Id, True);
1145             end if;
1146
1147             Build_Elaboration_Entity (N, Spec_Id);
1148          end;
1149       end if;
1150
1151       --  Freeze the compilation unit entity. This for sure is needed because
1152       --  of some warnings that can be output (see Freeze_Subprogram), but may
1153       --  in general be required. If freezing actions result, place them in the
1154       --  compilation unit actions list, and analyze them.
1155
1156       declare
1157          Loc : constant Source_Ptr := Sloc (N);
1158          L   : constant List_Id :=
1159                  Freeze_Entity (Cunit_Entity (Current_Sem_Unit), Loc);
1160       begin
1161          while Is_Non_Empty_List (L) loop
1162             Insert_Library_Level_Action (Remove_Head (L));
1163          end loop;
1164       end;
1165
1166       Set_Analyzed (N);
1167
1168       if Nkind (Unit_Node) = N_Package_Declaration
1169         and then Get_Cunit_Unit_Number (N) /= Main_Unit
1170         and then Expander_Active
1171       then
1172          declare
1173             Save_Style_Check : constant Boolean := Style_Check;
1174             Save_Warning     : constant Warning_Mode_Type := Warning_Mode;
1175             Options          : Style_Check_Options;
1176
1177          begin
1178             Save_Style_Check_Options (Options);
1179             Reset_Style_Check_Options;
1180             Opt.Warning_Mode := Suppress;
1181             Check_Body_For_Inlining (N, Defining_Entity (Unit_Node));
1182
1183             Reset_Style_Check_Options;
1184             Set_Style_Check_Options (Options);
1185             Style_Check := Save_Style_Check;
1186             Warning_Mode := Save_Warning;
1187          end;
1188       end if;
1189
1190       --  If we are generating obsolescent warnings, then here is where we
1191       --  generate them for the with'ed items. The reason for this special
1192       --  processing is that the normal mechanism of generating the warnings
1193       --  for referenced entities does not work for context clause references.
1194       --  That's because when we first analyze the context, it is too early to
1195       --  know if the with'ing unit is itself obsolescent (which suppresses
1196       --  the warnings).
1197
1198       if not GNAT_Mode and then Warn_On_Obsolescent_Feature then
1199
1200          --  Push current compilation unit as scope, so that the test for
1201          --  being within an obsolescent unit will work correctly.
1202
1203          Push_Scope (Defining_Entity (Unit_Node));
1204
1205          --  Loop through context items to deal with with clauses
1206
1207          declare
1208             Item : Node_Id;
1209             Nam  : Node_Id;
1210             Ent  : Entity_Id;
1211
1212          begin
1213             Item := First (Context_Items (N));
1214             while Present (Item) loop
1215                if Nkind (Item) = N_With_Clause
1216
1217                   --  Suppress this check in limited-withed units. Further work
1218                   --  needed here if we decide to incorporate this check on
1219                   --  limited-withed units.
1220
1221                  and then not Limited_Present (Item)
1222                then
1223                   Nam := Name (Item);
1224                   Ent := Entity (Nam);
1225
1226                   if Is_Obsolescent (Ent) then
1227                      Output_Obsolescent_Entity_Warnings (Nam, Ent);
1228                   end if;
1229                end if;
1230
1231                Next (Item);
1232             end loop;
1233          end;
1234
1235          --  Remove temporary install of current unit as scope
1236
1237          Pop_Scope;
1238       end if;
1239    end Analyze_Compilation_Unit;
1240
1241    ---------------------
1242    -- Analyze_Context --
1243    ---------------------
1244
1245    procedure Analyze_Context (N : Node_Id) is
1246       Ukind : constant Node_Kind := Nkind (Unit (N));
1247       Item  : Node_Id;
1248
1249    begin
1250       --  First process all configuration pragmas at the start of the context
1251       --  items. Strictly these are not part of the context clause, but that
1252       --  is where the parser puts them. In any case for sure we must analyze
1253       --  these before analyzing the actual context items, since they can have
1254       --  an effect on that analysis (e.g. pragma Ada_2005 may allow a unit to
1255       --  be with'ed as a result of changing categorizations in Ada 2005).
1256
1257       Item := First (Context_Items (N));
1258       while Present (Item)
1259         and then Nkind (Item) = N_Pragma
1260         and then Pragma_Name (Item) in Configuration_Pragma_Names
1261       loop
1262          Analyze (Item);
1263          Next (Item);
1264       end loop;
1265
1266       --  This is the point at which we capture the configuration settings
1267       --  for the unit. At the moment only the Optimize_Alignment setting
1268       --  needs to be captured. Probably more later ???
1269
1270       if Optimize_Alignment_Local then
1271          Set_OA_Setting (Current_Sem_Unit, 'L');
1272       else
1273          Set_OA_Setting (Current_Sem_Unit, Optimize_Alignment);
1274       end if;
1275
1276       --  Loop through actual context items. This is done in two passes:
1277
1278       --  a) The first pass analyzes non-limited with-clauses and also any
1279       --     configuration pragmas (we need to get the latter analyzed right
1280       --     away, since they can affect processing of subsequent items.
1281
1282       --  b) The second pass analyzes limited_with clauses (Ada 2005: AI-50217)
1283
1284       while Present (Item) loop
1285
1286          --  For with clause, analyze the with clause, and then update
1287          --  the version, since we are dependent on a unit that we with.
1288
1289          if Nkind (Item) = N_With_Clause
1290            and then not Limited_Present (Item)
1291          then
1292             --  Skip analyzing with clause if no unit, nothing to do (this
1293             --  happens for a with that references a non-existent unit)
1294             --  Skip as well if this is a with_clause for the main unit, which
1295             --  happens if a subunit has a useless with_clause on its parent.
1296
1297             if Present (Library_Unit (Item)) then
1298                if Library_Unit (Item) /= Cunit (Current_Sem_Unit) then
1299                   Analyze (Item);
1300
1301                else
1302                   Set_Entity (Name (Item), Cunit_Entity (Current_Sem_Unit));
1303                end if;
1304             end if;
1305
1306             if not Implicit_With (Item) then
1307                Version_Update (N, Library_Unit (Item));
1308             end if;
1309
1310          --  Skip pragmas. Configuration pragmas at the start were handled in
1311          --  the loop above, and remaining pragmas are not processed until we
1312          --  actually install the context (see Install_Context). We delay the
1313          --  analysis of these pragmas to make sure that we have installed all
1314          --  the implicit with's on parent units.
1315
1316          --  Skip use clauses at this stage, since we don't want to do any
1317          --  installing of potentially use-visible entities until we
1318          --  actually install the complete context (in Install_Context).
1319          --  Otherwise things can get installed in the wrong context.
1320
1321          else
1322             null;
1323          end if;
1324
1325          Next (Item);
1326       end loop;
1327
1328       --  Second pass: examine all limited_with clauses. All other context
1329       --  items are ignored in this pass.
1330
1331       Item := First (Context_Items (N));
1332       while Present (Item) loop
1333          if Nkind (Item) = N_With_Clause
1334            and then Limited_Present (Item)
1335          then
1336             --  No need to check errors on implicitly generated limited-with
1337             --  clauses.
1338
1339             if not Implicit_With (Item) then
1340
1341                --  Verify that the illegal contexts given in 10.1.2 (18/2)
1342                --  are properly rejected, including renaming declarations.
1343
1344                if not Nkind_In (Ukind, N_Package_Declaration,
1345                                        N_Subprogram_Declaration)
1346                  and then Ukind not in N_Generic_Declaration
1347                  and then Ukind not in N_Generic_Instantiation
1348                then
1349                   Error_Msg_N ("limited with_clause not allowed here", Item);
1350
1351                --  Check wrong use of a limited with clause applied to the
1352                --  compilation unit containing the limited-with clause.
1353
1354                --      limited with P.Q;
1355                --      package P.Q is ...
1356
1357                elsif Unit (Library_Unit (Item)) = Unit (N) then
1358                   Error_Msg_N ("wrong use of limited-with clause", Item);
1359
1360                --  Check wrong use of limited-with clause applied to some
1361                --  immediate ancestor.
1362
1363                elsif Is_Child_Spec (Unit (N)) then
1364                   declare
1365                      Lib_U : constant Entity_Id := Unit (Library_Unit (Item));
1366                      P     : Node_Id;
1367
1368                   begin
1369                      P := Parent_Spec (Unit (N));
1370                      loop
1371                         if Unit (P) = Lib_U then
1372                            Error_Msg_N ("limited with_clause of immediate "
1373                                         & "ancestor not allowed", Item);
1374                            exit;
1375                         end if;
1376
1377                         exit when not Is_Child_Spec (Unit (P));
1378                         P := Parent_Spec (Unit (P));
1379                      end loop;
1380                   end;
1381                end if;
1382
1383                --  Check if the limited-withed unit is already visible through
1384                --  some context clause of the current compilation unit or some
1385                --  ancestor of the current compilation unit.
1386
1387                declare
1388                   Lim_Unit_Name : constant Node_Id := Name (Item);
1389                   Comp_Unit     : Node_Id;
1390                   It            : Node_Id;
1391                   Unit_Name     : Node_Id;
1392
1393                begin
1394                   Comp_Unit := N;
1395                   loop
1396                      It := First (Context_Items (Comp_Unit));
1397                      while Present (It) loop
1398                         if Item /= It
1399                           and then Nkind (It) = N_With_Clause
1400                           and then not Limited_Present (It)
1401                           and then
1402                             Nkind_In (Unit (Library_Unit (It)),
1403                                        N_Package_Declaration,
1404                                        N_Package_Renaming_Declaration)
1405                         then
1406                            if Nkind (Unit (Library_Unit (It))) =
1407                                                       N_Package_Declaration
1408                            then
1409                               Unit_Name := Name (It);
1410                            else
1411                               Unit_Name := Name (Unit (Library_Unit (It)));
1412                            end if;
1413
1414                            --  Check if the named package (or some ancestor)
1415                            --  leaves visible the full-view of the unit given
1416                            --  in the limited-with clause
1417
1418                            loop
1419                               if Designate_Same_Unit (Lim_Unit_Name,
1420                                                       Unit_Name)
1421                               then
1422                                  Error_Msg_Sloc := Sloc (It);
1423                                  Error_Msg_N
1424                                    ("simultaneous visibility of limited "
1425                                     & "and unlimited views not allowed",
1426                                     Item);
1427                                  Error_Msg_NE
1428                                    ("\unlimited view visible through "
1429                                     & "context clause #",
1430                                     Item, It);
1431                                  exit;
1432
1433                               elsif Nkind (Unit_Name) = N_Identifier then
1434                                  exit;
1435                               end if;
1436
1437                               Unit_Name := Prefix (Unit_Name);
1438                            end loop;
1439                         end if;
1440
1441                         Next (It);
1442                      end loop;
1443
1444                      exit when not Is_Child_Spec (Unit (Comp_Unit));
1445
1446                      Comp_Unit := Parent_Spec (Unit (Comp_Unit));
1447                   end loop;
1448                end;
1449             end if;
1450
1451             --  Skip analyzing with clause if no unit, see above
1452
1453             if Present (Library_Unit (Item)) then
1454                Analyze (Item);
1455             end if;
1456
1457             --  A limited_with does not impose an elaboration order, but
1458             --  there is a semantic dependency for recompilation purposes.
1459
1460             if not Implicit_With (Item) then
1461                Version_Update (N, Library_Unit (Item));
1462             end if;
1463
1464             --  Pragmas and use clauses and with clauses other than limited
1465             --  with's are ignored in this pass through the context items.
1466
1467          else
1468             null;
1469          end if;
1470
1471          Next (Item);
1472       end loop;
1473    end Analyze_Context;
1474
1475    -------------------------------
1476    -- Analyze_Package_Body_Stub --
1477    -------------------------------
1478
1479    procedure Analyze_Package_Body_Stub (N : Node_Id) is
1480       Id   : constant Entity_Id := Defining_Identifier (N);
1481       Nam  : Entity_Id;
1482
1483    begin
1484       --  The package declaration must be in the current declarative part
1485
1486       Check_Stub_Level (N);
1487       Nam := Current_Entity_In_Scope (Id);
1488
1489       if No (Nam) or else not Is_Package_Or_Generic_Package (Nam) then
1490          Error_Msg_N ("missing specification for package stub", N);
1491
1492       elsif Has_Completion (Nam)
1493         and then Present (Corresponding_Body (Unit_Declaration_Node (Nam)))
1494       then
1495          Error_Msg_N ("duplicate or redundant stub for package", N);
1496
1497       else
1498          --  Indicate that the body of the package exists. If we are doing
1499          --  only semantic analysis, the stub stands for the body. If we are
1500          --  generating code, the existence of the body will be confirmed
1501          --  when we load the proper body.
1502
1503          Set_Has_Completion (Nam);
1504          Set_Scope (Defining_Entity (N), Current_Scope);
1505          Generate_Reference (Nam, Id, 'b');
1506          Analyze_Proper_Body (N, Nam);
1507       end if;
1508    end Analyze_Package_Body_Stub;
1509
1510    -------------------------
1511    -- Analyze_Proper_Body --
1512    -------------------------
1513
1514    procedure Analyze_Proper_Body (N : Node_Id; Nam : Entity_Id) is
1515       Subunit_Name      : constant Unit_Name_Type := Get_Unit_Name (N);
1516       Unum              : Unit_Number_Type;
1517
1518       procedure Optional_Subunit;
1519       --  This procedure is called when the main unit is a stub, or when we
1520       --  are not generating code. In such a case, we analyze the subunit if
1521       --  present, which is user-friendly and in fact required for ASIS, but
1522       --  we don't complain if the subunit is missing.
1523
1524       ----------------------
1525       -- Optional_Subunit --
1526       ----------------------
1527
1528       procedure Optional_Subunit is
1529          Comp_Unit : Node_Id;
1530
1531       begin
1532          --  Try to load subunit, but ignore any errors that occur during
1533          --  the loading of the subunit, by using the special feature in
1534          --  Errout to ignore all errors. Note that Fatal_Error will still
1535          --  be set, so we will be able to check for this case below.
1536
1537          if not ASIS_Mode then
1538             Ignore_Errors_Enable := Ignore_Errors_Enable + 1;
1539          end if;
1540
1541          Unum :=
1542            Load_Unit
1543              (Load_Name  => Subunit_Name,
1544               Required   => False,
1545               Subunit    => True,
1546               Error_Node => N);
1547
1548          if not ASIS_Mode then
1549             Ignore_Errors_Enable := Ignore_Errors_Enable - 1;
1550          end if;
1551
1552          --  All done if we successfully loaded the subunit
1553
1554          if Unum /= No_Unit
1555            and then (not Fatal_Error (Unum) or else Try_Semantics)
1556          then
1557             Comp_Unit := Cunit (Unum);
1558
1559             --  If the file was empty or seriously mangled, the unit
1560             --  itself may be missing.
1561
1562             if No (Unit (Comp_Unit)) then
1563                Error_Msg_N
1564                  ("subunit does not contain expected proper body", N);
1565
1566             elsif Nkind (Unit (Comp_Unit)) /= N_Subunit then
1567                Error_Msg_N
1568                  ("expected SEPARATE subunit, found child unit",
1569                   Cunit_Entity (Unum));
1570             else
1571                Set_Corresponding_Stub (Unit (Comp_Unit), N);
1572                Analyze_Subunit (Comp_Unit);
1573                Set_Library_Unit (N, Comp_Unit);
1574             end if;
1575
1576          elsif Unum = No_Unit
1577            and then Present (Nam)
1578          then
1579             if Is_Protected_Type (Nam) then
1580                Set_Corresponding_Body (Parent (Nam), Defining_Identifier (N));
1581             else
1582                Set_Corresponding_Body (
1583                  Unit_Declaration_Node (Nam), Defining_Identifier (N));
1584             end if;
1585          end if;
1586       end Optional_Subunit;
1587
1588    --  Start of processing for Analyze_Proper_Body
1589
1590    begin
1591       --  If the subunit is already loaded, it means that the main unit
1592       --  is a subunit, and that the current unit is one of its parents
1593       --  which was being analyzed to provide the needed context for the
1594       --  analysis of the subunit. In this case we analyze the subunit and
1595       --  continue with the parent, without looking a subsequent subunits.
1596
1597       if Is_Loaded (Subunit_Name) then
1598
1599          --  If the proper body is already linked to the stub node,
1600          --  the stub is in a generic unit and just needs analyzing.
1601
1602          if Present (Library_Unit (N)) then
1603             Set_Corresponding_Stub (Unit (Library_Unit (N)), N);
1604             Analyze_Subunit (Library_Unit (N));
1605
1606          --  Otherwise we must load the subunit and link to it
1607
1608          else
1609             --  Load the subunit, this must work, since we originally
1610             --  loaded the subunit earlier on. So this will not really
1611             --  load it, just give access to it.
1612
1613             Unum :=
1614               Load_Unit
1615                 (Load_Name  => Subunit_Name,
1616                  Required   => True,
1617                  Subunit    => False,
1618                  Error_Node => N);
1619
1620             --  And analyze the subunit in the parent context (note that we
1621             --  do not call Semantics, since that would remove the parent
1622             --  context). Because of this, we have to manually reset the
1623             --  compiler state to Analyzing since it got destroyed by Load.
1624
1625             if Unum /= No_Unit then
1626                Compiler_State := Analyzing;
1627
1628                --  Check that the proper body is a subunit and not a child
1629                --  unit. If the unit was previously loaded, the error will
1630                --  have been emitted when copying the generic node, so we
1631                --  just return to avoid cascaded errors.
1632
1633                if Nkind (Unit (Cunit (Unum))) /= N_Subunit then
1634                   return;
1635                end if;
1636
1637                Set_Corresponding_Stub (Unit (Cunit (Unum)), N);
1638                Analyze_Subunit (Cunit (Unum));
1639                Set_Library_Unit (N, Cunit (Unum));
1640             end if;
1641          end if;
1642
1643       --  If the main unit is a subunit, then we are just performing semantic
1644       --  analysis on that subunit, and any other subunits of any parent unit
1645       --  should be ignored, except that if we are building trees for ASIS
1646       --  usage we want to annotate the stub properly.
1647
1648       elsif Nkind (Unit (Cunit (Main_Unit))) = N_Subunit
1649         and then Subunit_Name /= Unit_Name (Main_Unit)
1650       then
1651          if ASIS_Mode then
1652             Optional_Subunit;
1653          end if;
1654
1655          --  But before we return, set the flag for unloaded subunits. This
1656          --  will suppress junk warnings of variables in the same declarative
1657          --  part (or a higher level one) that are in danger of looking unused
1658          --  when in fact there might be a declaration in the subunit that we
1659          --  do not intend to load.
1660
1661          Unloaded_Subunits := True;
1662          return;
1663
1664       --  If the subunit is not already loaded, and we are generating code,
1665       --  then this is the case where compilation started from the parent,
1666       --  and we are generating code for an entire subunit tree. In that
1667       --  case we definitely need to load the subunit.
1668
1669       --  In order to continue the analysis with the rest of the parent,
1670       --  and other subunits, we load the unit without requiring its
1671       --  presence, and emit a warning if not found, rather than terminating
1672       --  the compilation abruptly, as for other missing file problems.
1673
1674       elsif Original_Operating_Mode = Generate_Code then
1675
1676          --  If the proper body is already linked to the stub node,
1677          --  the stub is in a generic unit and just needs analyzing.
1678
1679          --  We update the version. Although we are not technically
1680          --  semantically dependent on the subunit, given our approach
1681          --  of macro substitution of subunits, it makes sense to
1682          --  include it in the version identification.
1683
1684          if Present (Library_Unit (N)) then
1685             Set_Corresponding_Stub (Unit (Library_Unit (N)), N);
1686             Analyze_Subunit (Library_Unit (N));
1687             Version_Update (Cunit (Main_Unit), Library_Unit (N));
1688
1689          --  Otherwise we must load the subunit and link to it
1690
1691          else
1692             Unum :=
1693               Load_Unit
1694                 (Load_Name  => Subunit_Name,
1695                  Required   => False,
1696                  Subunit    => True,
1697                  Error_Node => N);
1698
1699             --  Give message if we did not get the unit
1700
1701             if Original_Operating_Mode = Generate_Code
1702               and then Unum = No_Unit
1703             then
1704                Error_Msg_Unit_1 := Subunit_Name;
1705                Error_Msg_File_1 :=
1706                  Get_File_Name (Subunit_Name, Subunit => True);
1707                Error_Msg_N
1708                  ("subunit$$ in file{ not found?", N);
1709                Subunits_Missing := True;
1710             end if;
1711
1712             --  Load_Unit may reset Compiler_State, since it may have been
1713             --  necessary to parse an additional units, so we make sure
1714             --  that we reset it to the Analyzing state.
1715
1716             Compiler_State := Analyzing;
1717
1718             if Unum /= No_Unit then
1719                if Debug_Flag_L then
1720                   Write_Str ("*** Loaded subunit from stub. Analyze");
1721                   Write_Eol;
1722                end if;
1723
1724                declare
1725                   Comp_Unit : constant Node_Id := Cunit (Unum);
1726
1727                begin
1728                   --  Check for child unit instead of subunit
1729
1730                   if Nkind (Unit (Comp_Unit)) /= N_Subunit then
1731                      Error_Msg_N
1732                        ("expected SEPARATE subunit, found child unit",
1733                         Cunit_Entity (Unum));
1734
1735                   --  OK, we have a subunit
1736
1737                   else
1738                      --  Set corresponding stub (even if errors)
1739
1740                      Set_Corresponding_Stub (Unit (Comp_Unit), N);
1741
1742                      --  Collect SCO information for loaded subunit if we are
1743                      --  in the main unit).
1744
1745                      if Generate_SCO
1746                        and then
1747                          In_Extended_Main_Source_Unit
1748                            (Cunit_Entity (Current_Sem_Unit))
1749                      then
1750                         SCO_Record (Unum);
1751                      end if;
1752
1753                      --  Analyze the unit if semantics active
1754
1755                      if not Fatal_Error (Unum) or else Try_Semantics then
1756                         Analyze_Subunit (Comp_Unit);
1757                      end if;
1758
1759                      --  Set the library unit pointer in any case
1760
1761                      Set_Library_Unit (N, Comp_Unit);
1762
1763                      --  We update the version. Although we are not technically
1764                      --  semantically dependent on the subunit, given our
1765                      --  approach of macro substitution of subunits, it makes
1766                      --  sense to include it in the version identification.
1767
1768                      Version_Update (Cunit (Main_Unit), Comp_Unit);
1769                   end if;
1770                end;
1771             end if;
1772          end if;
1773
1774          --  The remaining case is when the subunit is not already loaded and
1775          --  we are not generating code. In this case we are just performing
1776          --  semantic analysis on the parent, and we are not interested in
1777          --  the subunit. For subprograms, analyze the stub as a body. For
1778          --  other entities the stub has already been marked as completed.
1779
1780       else
1781          Optional_Subunit;
1782       end if;
1783    end Analyze_Proper_Body;
1784
1785    ----------------------------------
1786    -- Analyze_Protected_Body_Stub --
1787    ----------------------------------
1788
1789    procedure Analyze_Protected_Body_Stub (N : Node_Id) is
1790       Nam : Entity_Id := Current_Entity_In_Scope (Defining_Identifier (N));
1791
1792    begin
1793       Check_Stub_Level (N);
1794
1795       --  First occurrence of name may have been as an incomplete type
1796
1797       if Present (Nam) and then Ekind (Nam) = E_Incomplete_Type then
1798          Nam := Full_View (Nam);
1799       end if;
1800
1801       if No (Nam)
1802         or else not Is_Protected_Type (Etype (Nam))
1803       then
1804          Error_Msg_N ("missing specification for Protected body", N);
1805       else
1806          Set_Scope (Defining_Entity (N), Current_Scope);
1807          Set_Has_Completion (Etype (Nam));
1808          Generate_Reference (Nam, Defining_Identifier (N), 'b');
1809          Analyze_Proper_Body (N, Etype (Nam));
1810       end if;
1811    end Analyze_Protected_Body_Stub;
1812
1813    ----------------------------------
1814    -- Analyze_Subprogram_Body_Stub --
1815    ----------------------------------
1816
1817    --  A subprogram body stub can appear with or without a previous
1818    --  specification. If there is one, the analysis of the body will
1819    --  find it and verify conformance.  The formals appearing in the
1820    --  specification of the stub play no role, except for requiring an
1821    --  additional conformance check. If there is no previous subprogram
1822    --  declaration, the stub acts as a spec, and provides the defining
1823    --  entity for the subprogram.
1824
1825    procedure Analyze_Subprogram_Body_Stub (N : Node_Id) is
1826       Decl : Node_Id;
1827
1828    begin
1829       Check_Stub_Level (N);
1830
1831       --  Verify that the identifier for the stub is unique within this
1832       --  declarative part.
1833
1834       if Nkind_In (Parent (N), N_Block_Statement,
1835                                N_Package_Body,
1836                                N_Subprogram_Body)
1837       then
1838          Decl := First (Declarations (Parent (N)));
1839          while Present (Decl)
1840            and then Decl /= N
1841          loop
1842             if Nkind (Decl) = N_Subprogram_Body_Stub
1843               and then (Chars (Defining_Unit_Name (Specification (Decl))) =
1844                         Chars (Defining_Unit_Name (Specification (N))))
1845             then
1846                Error_Msg_N ("identifier for stub is not unique", N);
1847             end if;
1848
1849             Next (Decl);
1850          end loop;
1851       end if;
1852
1853       --  Treat stub as a body, which checks conformance if there is a previous
1854       --  declaration, or else introduces entity and its signature.
1855
1856       Analyze_Subprogram_Body (N);
1857       Analyze_Proper_Body (N, Empty);
1858    end Analyze_Subprogram_Body_Stub;
1859
1860    ---------------------
1861    -- Analyze_Subunit --
1862    ---------------------
1863
1864    --  A subunit is compiled either by itself (for semantic checking)
1865    --  or as part of compiling the parent (for code generation). In
1866    --  either case, by the time we actually process the subunit, the
1867    --  parent has already been installed and analyzed. The node N is
1868    --  a compilation unit, whose context needs to be treated here,
1869    --  because we come directly here from the parent without calling
1870    --  Analyze_Compilation_Unit.
1871
1872    --  The compilation context includes the explicit context of the
1873    --  subunit, and the context of the parent, together with the parent
1874    --  itself. In order to compile the current context, we remove the
1875    --  one inherited from the parent, in order to have a clean visibility
1876    --  table. We restore the parent context before analyzing the proper
1877    --  body itself. On exit, we remove only the explicit context of the
1878    --  subunit.
1879
1880    procedure Analyze_Subunit (N : Node_Id) is
1881       Lib_Unit : constant Node_Id   := Library_Unit (N);
1882       Par_Unit : constant Entity_Id := Current_Scope;
1883
1884       Lib_Spec        : Node_Id := Library_Unit (Lib_Unit);
1885       Num_Scopes      : Int := 0;
1886       Use_Clauses     : array (1 .. Scope_Stack.Last) of Node_Id;
1887       Enclosing_Child : Entity_Id := Empty;
1888       Svg             : constant Suppress_Array := Scope_Suppress;
1889
1890       procedure Analyze_Subunit_Context;
1891       --  Capture names in use clauses of the subunit. This must be done
1892       --  before re-installing parent declarations, because items in the
1893       --  context must not be hidden by declarations local to the parent.
1894
1895       procedure Re_Install_Parents (L : Node_Id; Scop : Entity_Id);
1896       --  Recursive procedure to restore scope of all ancestors of subunit,
1897       --  from outermost in. If parent is not a subunit, the call to install
1898       --  context installs context of spec and (if parent is a child unit)
1899       --  the context of its parents as well. It is confusing that parents
1900       --  should be treated differently in both cases, but the semantics are
1901       --  just not identical.
1902
1903       procedure Re_Install_Use_Clauses;
1904       --  As part of the removal of the parent scope, the use clauses are
1905       --  removed, to be reinstalled when the context of the subunit has
1906       --  been analyzed. Use clauses may also have been affected by the
1907       --  analysis of the context of the subunit, so they have to be applied
1908       --  again, to insure that the compilation environment of the rest of
1909       --  the parent unit is identical.
1910
1911       procedure Remove_Scope;
1912       --  Remove current scope from scope stack, and preserve the list
1913       --  of use clauses in it, to be reinstalled after context is analyzed.
1914
1915       -----------------------------
1916       -- Analyze_Subunit_Context --
1917       -----------------------------
1918
1919       procedure Analyze_Subunit_Context is
1920          Item      :  Node_Id;
1921          Nam       :  Node_Id;
1922          Unit_Name : Entity_Id;
1923
1924       begin
1925          Analyze_Context (N);
1926
1927          --  Make withed units immediately visible. If child unit, make the
1928          --  ultimate parent immediately visible.
1929
1930          Item := First (Context_Items (N));
1931          while Present (Item) loop
1932             if Nkind (Item) = N_With_Clause then
1933
1934                --  Protect frontend against previous errors in context clauses
1935
1936                if Nkind (Name (Item)) /= N_Selected_Component then
1937                   if Error_Posted (Item) then
1938                      null;
1939
1940                   else
1941                      Unit_Name := Entity (Name (Item));
1942                      while Is_Child_Unit (Unit_Name) loop
1943                         Set_Is_Visible_Child_Unit (Unit_Name);
1944                         Unit_Name := Scope (Unit_Name);
1945                      end loop;
1946
1947                      if not Is_Immediately_Visible (Unit_Name) then
1948                         Set_Is_Immediately_Visible (Unit_Name);
1949                         Set_Context_Installed (Item);
1950                      end if;
1951                   end if;
1952                end if;
1953
1954             elsif Nkind (Item) = N_Use_Package_Clause then
1955                Nam := First (Names (Item));
1956                while Present (Nam) loop
1957                   Analyze (Nam);
1958                   Next (Nam);
1959                end loop;
1960
1961             elsif Nkind (Item) = N_Use_Type_Clause then
1962                Nam := First (Subtype_Marks (Item));
1963                while Present (Nam) loop
1964                   Analyze (Nam);
1965                   Next (Nam);
1966                end loop;
1967             end if;
1968
1969             Next (Item);
1970          end loop;
1971
1972          --  Reset visibility of withed units. They will be made visible
1973          --  again when we install the subunit context.
1974
1975          Item := First (Context_Items (N));
1976          while Present (Item) loop
1977             if Nkind (Item) = N_With_Clause
1978
1979                --  Protect frontend against previous errors in context clauses
1980
1981               and then Nkind (Name (Item)) /= N_Selected_Component
1982               and then not Error_Posted (Item)
1983             then
1984                Unit_Name := Entity (Name (Item));
1985                while Is_Child_Unit (Unit_Name) loop
1986                   Set_Is_Visible_Child_Unit (Unit_Name, False);
1987                   Unit_Name := Scope (Unit_Name);
1988                end loop;
1989
1990                if Context_Installed (Item) then
1991                   Set_Is_Immediately_Visible (Unit_Name, False);
1992                   Set_Context_Installed (Item, False);
1993                end if;
1994             end if;
1995
1996             Next (Item);
1997          end loop;
1998       end Analyze_Subunit_Context;
1999
2000       ------------------------
2001       -- Re_Install_Parents --
2002       ------------------------
2003
2004       procedure Re_Install_Parents (L : Node_Id; Scop : Entity_Id) is
2005          E : Entity_Id;
2006
2007       begin
2008          if Nkind (Unit (L)) = N_Subunit then
2009             Re_Install_Parents (Library_Unit (L), Scope (Scop));
2010          end if;
2011
2012          Install_Context (L);
2013
2014          --  If the subunit occurs within a child unit, we must restore the
2015          --  immediate visibility of any siblings that may occur in context.
2016
2017          if Present (Enclosing_Child) then
2018             Install_Siblings (Enclosing_Child, L);
2019          end if;
2020
2021          Push_Scope (Scop);
2022
2023          if Scop /= Par_Unit then
2024             Set_Is_Immediately_Visible (Scop);
2025          end if;
2026
2027          --  Make entities in scope visible again. For child units, restore
2028          --  visibility only if they are actually in context.
2029
2030          E := First_Entity (Current_Scope);
2031          while Present (E) loop
2032             if not Is_Child_Unit (E)
2033               or else Is_Visible_Child_Unit (E)
2034             then
2035                Set_Is_Immediately_Visible (E);
2036             end if;
2037
2038             Next_Entity (E);
2039          end loop;
2040
2041          --  A subunit appears within a body, and for a nested subunits
2042          --  all the parents are bodies. Restore full visibility of their
2043          --  private entities.
2044
2045          if Is_Package_Or_Generic_Package (Scop) then
2046             Set_In_Package_Body (Scop);
2047             Install_Private_Declarations (Scop);
2048          end if;
2049       end Re_Install_Parents;
2050
2051       ----------------------------
2052       -- Re_Install_Use_Clauses --
2053       ----------------------------
2054
2055       procedure Re_Install_Use_Clauses is
2056          U  : Node_Id;
2057       begin
2058          for J in reverse 1 .. Num_Scopes loop
2059             U := Use_Clauses (J);
2060             Scope_Stack.Table (Scope_Stack.Last - J + 1).First_Use_Clause := U;
2061             Install_Use_Clauses (U, Force_Installation => True);
2062          end loop;
2063       end Re_Install_Use_Clauses;
2064
2065       ------------------
2066       -- Remove_Scope --
2067       ------------------
2068
2069       procedure Remove_Scope is
2070          E : Entity_Id;
2071
2072       begin
2073          Num_Scopes := Num_Scopes + 1;
2074          Use_Clauses (Num_Scopes) :=
2075            Scope_Stack.Table (Scope_Stack.Last).First_Use_Clause;
2076
2077          E := First_Entity (Current_Scope);
2078          while Present (E) loop
2079             Set_Is_Immediately_Visible (E, False);
2080             Next_Entity (E);
2081          end loop;
2082
2083          if Is_Child_Unit (Current_Scope) then
2084             Enclosing_Child := Current_Scope;
2085          end if;
2086
2087          Pop_Scope;
2088       end Remove_Scope;
2089
2090    --  Start of processing for Analyze_Subunit
2091
2092    begin
2093       if not Is_Empty_List (Context_Items (N)) then
2094
2095          --  Save current use clauses
2096
2097          Remove_Scope;
2098          Remove_Context (Lib_Unit);
2099
2100          --  Now remove parents and their context, including enclosing
2101          --  subunits and the outer parent body which is not a subunit.
2102
2103          if Present (Lib_Spec) then
2104             Remove_Context (Lib_Spec);
2105
2106             while Nkind (Unit (Lib_Spec)) = N_Subunit loop
2107                Lib_Spec := Library_Unit (Lib_Spec);
2108                Remove_Scope;
2109                Remove_Context (Lib_Spec);
2110             end loop;
2111
2112             if Nkind (Unit (Lib_Unit)) = N_Subunit then
2113                Remove_Scope;
2114             end if;
2115
2116             if Nkind (Unit (Lib_Spec)) = N_Package_Body then
2117                Remove_Context (Library_Unit (Lib_Spec));
2118             end if;
2119          end if;
2120
2121          Set_Is_Immediately_Visible (Par_Unit, False);
2122
2123          Analyze_Subunit_Context;
2124
2125          Re_Install_Parents (Lib_Unit, Par_Unit);
2126          Set_Is_Immediately_Visible (Par_Unit);
2127
2128          --  If the context includes a child unit of the parent of the
2129          --  subunit, the parent will have been removed from visibility,
2130          --  after compiling that cousin in the context. The visibility
2131          --  of the parent must be restored now. This also applies if the
2132          --  context includes another subunit of the same parent which in
2133          --  turn includes a child unit in its context.
2134
2135          if Is_Package_Or_Generic_Package (Par_Unit) then
2136             if not Is_Immediately_Visible (Par_Unit)
2137               or else (Present (First_Entity (Par_Unit))
2138                         and then not Is_Immediately_Visible
2139                                       (First_Entity (Par_Unit)))
2140             then
2141                Set_Is_Immediately_Visible   (Par_Unit);
2142                Install_Visible_Declarations (Par_Unit);
2143                Install_Private_Declarations (Par_Unit);
2144             end if;
2145          end if;
2146
2147          Re_Install_Use_Clauses;
2148          Install_Context (N);
2149
2150          --  Restore state of suppress flags for current body
2151
2152          Scope_Suppress := Svg;
2153
2154          --  If the subunit is within a child unit, then siblings of any
2155          --  parent unit that appear in the context clause of the subunit
2156          --  must also be made immediately visible.
2157
2158          if Present (Enclosing_Child) then
2159             Install_Siblings (Enclosing_Child, N);
2160          end if;
2161
2162       end if;
2163
2164       Analyze (Proper_Body (Unit (N)));
2165       Remove_Context (N);
2166
2167       --  The subunit may contain a with_clause on a sibling of some
2168       --  ancestor. Removing the context will remove from visibility those
2169       --  ancestor child units, which must be restored to the visibility
2170       --  they have in the enclosing body.
2171
2172       if Present (Enclosing_Child) then
2173          declare
2174             C : Entity_Id;
2175          begin
2176             C := Current_Scope;
2177             while Present (C)
2178               and then Is_Child_Unit (C)
2179             loop
2180                Set_Is_Immediately_Visible (C);
2181                Set_Is_Visible_Child_Unit (C);
2182                C := Scope (C);
2183             end loop;
2184          end;
2185       end if;
2186    end Analyze_Subunit;
2187
2188    ----------------------------
2189    -- Analyze_Task_Body_Stub --
2190    ----------------------------
2191
2192    procedure Analyze_Task_Body_Stub (N : Node_Id) is
2193       Nam : Entity_Id := Current_Entity_In_Scope (Defining_Identifier (N));
2194       Loc : constant Source_Ptr := Sloc (N);
2195
2196    begin
2197       Check_Stub_Level (N);
2198
2199       --  First occurrence of name may have been as an incomplete type
2200
2201       if Present (Nam) and then Ekind (Nam) = E_Incomplete_Type then
2202          Nam := Full_View (Nam);
2203       end if;
2204
2205       if No (Nam)
2206         or else not Is_Task_Type (Etype (Nam))
2207       then
2208          Error_Msg_N ("missing specification for task body", N);
2209       else
2210          Set_Scope (Defining_Entity (N), Current_Scope);
2211          Generate_Reference (Nam, Defining_Identifier (N), 'b');
2212          Set_Has_Completion (Etype (Nam));
2213          Analyze_Proper_Body (N, Etype (Nam));
2214
2215          --  Set elaboration flag to indicate that entity is callable.
2216          --  This cannot be done in the expansion of the body  itself,
2217          --  because the proper body is not in a declarative part. This
2218          --  is only done if expansion is active, because the context
2219          --  may be generic and the flag not defined yet.
2220
2221          if Expander_Active then
2222             Insert_After (N,
2223               Make_Assignment_Statement (Loc,
2224                 Name =>
2225                   Make_Identifier (Loc,
2226                     New_External_Name (Chars (Etype (Nam)), 'E')),
2227                  Expression => New_Reference_To (Standard_True, Loc)));
2228          end if;
2229
2230       end if;
2231    end Analyze_Task_Body_Stub;
2232
2233    -------------------------
2234    -- Analyze_With_Clause --
2235    -------------------------
2236
2237    --  Analyze the declaration of a unit in a with clause. At end,
2238    --  label the with clause with the defining entity for the unit.
2239
2240    procedure Analyze_With_Clause (N : Node_Id) is
2241
2242       --  Retrieve the original kind of the unit node, before analysis.
2243       --  If it is a subprogram instantiation, its analysis below will
2244       --  rewrite as the declaration of the wrapper package. If the same
2245       --  instantiation appears indirectly elsewhere in the context, it
2246       --  will have been analyzed already.
2247
2248       Unit_Kind : constant Node_Kind :=
2249                     Nkind (Original_Node (Unit (Library_Unit (N))));
2250       Nam       : constant Node_Id := Name (N);
2251       E_Name    : Entity_Id;
2252       Par_Name  : Entity_Id;
2253       Pref      : Node_Id;
2254       U         : Node_Id;
2255
2256       Intunit : Boolean;
2257       --  Set True if the unit currently being compiled is an internal unit
2258
2259       Save_Style_Check : constant Boolean := Opt.Style_Check;
2260       Save_C_Restrict  : constant Save_Cunit_Boolean_Restrictions :=
2261                            Cunit_Boolean_Restrictions_Save;
2262
2263    begin
2264       U := Unit (Library_Unit (N));
2265
2266       --  Several actions are skipped for dummy packages (those supplied for
2267       --  with's where no matching file could be found). Such packages are
2268       --  identified by the Sloc value being set to No_Location.
2269
2270       if Limited_Present (N) then
2271
2272          --  Ada 2005 (AI-50217): Build visibility structures but do not
2273          --  analyze the unit.
2274
2275          if Sloc (U) /= No_Location then
2276             Build_Limited_Views (N);
2277          end if;
2278
2279          return;
2280       end if;
2281
2282       --  We reset ordinary style checking during the analysis of a with'ed
2283       --  unit, but we do NOT reset GNAT special analysis mode (the latter
2284       --  definitely *does* apply to with'ed units).
2285
2286       if not GNAT_Mode then
2287          Style_Check := False;
2288       end if;
2289
2290       --  If the library unit is a predefined unit, and we are in high
2291       --  integrity mode, then temporarily reset Configurable_Run_Time_Mode
2292       --  for the analysis of the with'ed unit. This mode does not prevent
2293       --  explicit with'ing of run-time units.
2294
2295       if Configurable_Run_Time_Mode
2296         and then
2297           Is_Predefined_File_Name
2298             (Unit_File_Name (Get_Source_Unit (Unit (Library_Unit (N)))))
2299       then
2300          Configurable_Run_Time_Mode := False;
2301          Semantics (Library_Unit (N));
2302          Configurable_Run_Time_Mode := True;
2303
2304       else
2305          Semantics (Library_Unit (N));
2306       end if;
2307
2308       Intunit := Is_Internal_File_Name (Unit_File_Name (Current_Sem_Unit));
2309
2310       if Sloc (U) /= No_Location then
2311
2312          --  Check restrictions, except that we skip the check if this is an
2313          --  internal unit unless we are compiling the internal unit as the
2314          --  main unit. We also skip this for dummy packages.
2315
2316          Check_Restriction_No_Dependence (Nam, N);
2317
2318          if not Intunit or else Current_Sem_Unit = Main_Unit then
2319             Check_Restricted_Unit (Unit_Name (Get_Source_Unit (U)), N);
2320          end if;
2321
2322          --  Deal with special case of GNAT.Current_Exceptions which interacts
2323          --  with the optimization of local raise statements into gotos.
2324
2325          if Nkind (Nam) = N_Selected_Component
2326            and then Nkind (Prefix (Nam)) = N_Identifier
2327            and then Chars (Prefix (Nam)) = Name_Gnat
2328            and then (Chars (Selector_Name (Nam)) = Name_Most_Recent_Exception
2329                        or else
2330                      Chars (Selector_Name (Nam)) = Name_Exception_Traces)
2331          then
2332             Check_Restriction (No_Exception_Propagation, N);
2333             Special_Exception_Package_Used := True;
2334          end if;
2335
2336          --  Check for inappropriate with of internal implementation unit if we
2337          --  are currently compiling the main unit and the main unit is itself
2338          --  not an internal unit. We do not issue this message for implicit
2339          --  with's generated by the compiler itself.
2340
2341          if Implementation_Unit_Warnings
2342            and then Current_Sem_Unit = Main_Unit
2343            and then not Intunit
2344            and then not Implicit_With (N)
2345          then
2346             declare
2347                U_Kind : constant Kind_Of_Unit :=
2348                           Get_Kind_Of_Unit (Get_Source_Unit (U));
2349
2350             begin
2351                if U_Kind = Implementation_Unit then
2352                   Error_Msg_F ("& is an internal 'G'N'A'T unit?", Name (N));
2353                   Error_Msg_F
2354                     ("\use of this unit is non-portable " &
2355                      "and version-dependent?",
2356                      Name (N));
2357
2358                elsif U_Kind = Ada_05_Unit
2359                  and then Ada_Version < Ada_05
2360                  and then Warn_On_Ada_2005_Compatibility
2361                then
2362                   Error_Msg_N ("& is an Ada 2005 unit?", Name (N));
2363                end if;
2364             end;
2365          end if;
2366       end if;
2367
2368       --  Semantic analysis of a generic unit is performed on a copy of
2369       --  the original tree. Retrieve the entity on  which semantic info
2370       --  actually appears.
2371
2372       if Unit_Kind in N_Generic_Declaration then
2373          E_Name := Defining_Entity (U);
2374
2375       --  Note: in the following test, Unit_Kind is the original Nkind, but in
2376       --  the case of an instantiation, semantic analysis above will have
2377       --  replaced the unit by its instantiated version. If the instance body
2378       --  has been generated, the instance now denotes the body entity. For
2379       --  visibility purposes we need the entity of its spec.
2380
2381       elsif (Unit_Kind = N_Package_Instantiation
2382               or else Nkind (Original_Node (Unit (Library_Unit (N)))) =
2383                                                   N_Package_Instantiation)
2384         and then Nkind (U) = N_Package_Body
2385       then
2386          E_Name := Corresponding_Spec (U);
2387
2388       elsif Unit_Kind = N_Package_Instantiation
2389         and then Nkind (U) = N_Package_Instantiation
2390       then
2391          --  If the instance has not been rewritten as a package declaration,
2392          --  then it appeared already in a previous with clause. Retrieve
2393          --  the entity from the previous instance.
2394
2395          E_Name := Defining_Entity (Specification (Instance_Spec (U)));
2396
2397       elsif Unit_Kind in N_Subprogram_Instantiation then
2398
2399          --  The visible subprogram is created during instantiation, and is
2400          --  an attribute of the wrapper package. We retrieve the wrapper
2401          --  package directly from the instantiation node. If the instance
2402          --  is inlined the unit is still an instantiation. Otherwise it has
2403          --  been rewritten as the declaration of the wrapper itself.
2404
2405          if Nkind (U) in N_Subprogram_Instantiation then
2406             E_Name :=
2407               Related_Instance
2408                 (Defining_Entity (Specification (Instance_Spec (U))));
2409          else
2410             E_Name := Related_Instance (Defining_Entity (U));
2411          end if;
2412
2413       elsif Unit_Kind = N_Package_Renaming_Declaration
2414         or else Unit_Kind in N_Generic_Renaming_Declaration
2415       then
2416          E_Name := Defining_Entity (U);
2417
2418       elsif Unit_Kind = N_Subprogram_Body
2419         and then Nkind (Name (N)) = N_Selected_Component
2420         and then not Acts_As_Spec (Library_Unit (N))
2421       then
2422          --  For a child unit that has no spec, one has been created and
2423          --  analyzed. The entity required is that of the spec.
2424
2425          E_Name := Corresponding_Spec (U);
2426
2427       else
2428          E_Name := Defining_Entity (U);
2429       end if;
2430
2431       if Nkind (Name (N)) = N_Selected_Component then
2432
2433          --  Child unit in a with clause
2434
2435          Change_Selected_Component_To_Expanded_Name (Name (N));
2436       end if;
2437
2438       --  Restore style checks and restrictions
2439
2440       Style_Check := Save_Style_Check;
2441       Cunit_Boolean_Restrictions_Restore (Save_C_Restrict);
2442
2443       --  Record the reference, but do NOT set the unit as referenced, we want
2444       --  to consider the unit as unreferenced if this is the only reference
2445       --  that occurs.
2446
2447       Set_Entity_With_Style_Check (Name (N), E_Name);
2448       Generate_Reference (E_Name, Name (N), 'w', Set_Ref => False);
2449
2450       --  Generate references and check No_Dependence restriction for parents
2451
2452       if Is_Child_Unit (E_Name) then
2453          Pref     := Prefix (Name (N));
2454          Par_Name := Scope (E_Name);
2455          while Nkind (Pref) = N_Selected_Component loop
2456             Change_Selected_Component_To_Expanded_Name (Pref);
2457             Set_Entity_With_Style_Check (Pref, Par_Name);
2458
2459             Generate_Reference (Par_Name, Pref);
2460             Check_Restriction_No_Dependence (Pref, N);
2461             Pref := Prefix (Pref);
2462
2463             --  If E_Name is the dummy entity for a nonexistent unit, its scope
2464             --  is set to Standard_Standard, and no attempt should be made to
2465             --  further unwind scopes.
2466
2467             if Par_Name /= Standard_Standard then
2468                Par_Name := Scope (Par_Name);
2469             end if;
2470          end loop;
2471
2472          if Present (Entity (Pref))
2473            and then not Analyzed (Parent (Parent (Entity (Pref))))
2474          then
2475             --  If the entity is set without its unit being compiled, the
2476             --  original parent is a renaming, and Par_Name is the renamed
2477             --  entity. For visibility purposes, we need the original entity,
2478             --  which must be analyzed now because Load_Unit directly retrieves
2479             --  the renamed unit, and the renaming declaration itself has not
2480             --  been analyzed.
2481
2482             Analyze (Parent (Parent (Entity (Pref))));
2483             pragma Assert (Renamed_Object (Entity (Pref)) = Par_Name);
2484             Par_Name := Entity (Pref);
2485          end if;
2486
2487          Set_Entity_With_Style_Check (Pref, Par_Name);
2488          Generate_Reference (Par_Name, Pref);
2489       end if;
2490
2491       --  If the withed unit is System, and a system extension pragma is
2492       --  present, compile the extension now, rather than waiting for a
2493       --  visibility check on a specific entity.
2494
2495       if Chars (E_Name) = Name_System
2496         and then Scope (E_Name) = Standard_Standard
2497         and then Present (System_Extend_Unit)
2498         and then Present_System_Aux (N)
2499       then
2500          --  If the extension is not present, an error will have been emitted
2501
2502          null;
2503       end if;
2504
2505       --  Ada 2005 (AI-262): Remove from visibility the entity corresponding
2506       --  to private_with units; they will be made visible later (just before
2507       --  the private part is analyzed)
2508
2509       if Private_Present (N) then
2510          Set_Is_Immediately_Visible (E_Name, False);
2511       end if;
2512    end Analyze_With_Clause;
2513
2514    ------------------------------
2515    -- Check_Private_Child_Unit --
2516    ------------------------------
2517
2518    procedure Check_Private_Child_Unit (N : Node_Id) is
2519       Lib_Unit   : constant Node_Id := Unit (N);
2520       Item       : Node_Id;
2521       Curr_Unit  : Entity_Id;
2522       Sub_Parent : Node_Id;
2523       Priv_Child : Entity_Id;
2524       Par_Lib    : Entity_Id;
2525       Par_Spec   : Node_Id;
2526
2527       function Is_Private_Library_Unit (Unit : Entity_Id) return Boolean;
2528       --  Returns true if and only if the library unit is declared with
2529       --  an explicit designation of private.
2530
2531       function Is_Private_Library_Unit (Unit : Entity_Id) return Boolean is
2532          Comp_Unit : constant Node_Id := Parent (Unit_Declaration_Node (Unit));
2533
2534       begin
2535          return Private_Present (Comp_Unit);
2536       end Is_Private_Library_Unit;
2537
2538    --  Start of processing for Check_Private_Child_Unit
2539
2540    begin
2541       if Nkind_In (Lib_Unit, N_Package_Body, N_Subprogram_Body) then
2542          Curr_Unit := Defining_Entity (Unit (Library_Unit (N)));
2543          Par_Lib   := Curr_Unit;
2544
2545       elsif Nkind (Lib_Unit) = N_Subunit then
2546
2547          --  The parent is itself a body. The parent entity is to be found in
2548          --  the corresponding spec.
2549
2550          Sub_Parent := Library_Unit (N);
2551          Curr_Unit  := Defining_Entity (Unit (Library_Unit (Sub_Parent)));
2552
2553          --  If the parent itself is a subunit, Curr_Unit is the entity
2554          --  of the enclosing body, retrieve the spec entity which is
2555          --  the proper ancestor we need for the following tests.
2556
2557          if Ekind (Curr_Unit) = E_Package_Body then
2558             Curr_Unit := Spec_Entity (Curr_Unit);
2559          end if;
2560
2561          Par_Lib    := Curr_Unit;
2562
2563       else
2564          Curr_Unit := Defining_Entity (Lib_Unit);
2565
2566          Par_Lib := Curr_Unit;
2567          Par_Spec  := Parent_Spec (Lib_Unit);
2568
2569          if No (Par_Spec) then
2570             Par_Lib := Empty;
2571          else
2572             Par_Lib := Defining_Entity (Unit (Par_Spec));
2573          end if;
2574       end if;
2575
2576       --  Loop through context items
2577
2578       Item := First (Context_Items (N));
2579       while Present (Item) loop
2580
2581          --  Ada 2005 (AI-262): Allow private_with of a private child package
2582          --  in public siblings
2583
2584          if Nkind (Item) = N_With_Clause
2585             and then not Implicit_With (Item)
2586             and then not Limited_Present (Item)
2587             and then Is_Private_Descendant (Entity (Name (Item)))
2588          then
2589             Priv_Child := Entity (Name (Item));
2590
2591             declare
2592                Curr_Parent  : Entity_Id := Par_Lib;
2593                Child_Parent : Entity_Id := Scope (Priv_Child);
2594                Prv_Ancestor : Entity_Id := Child_Parent;
2595                Curr_Private : Boolean   := Is_Private_Library_Unit (Curr_Unit);
2596
2597             begin
2598                --  If the child unit is a public child then locate the nearest
2599                --  private ancestor. Child_Parent will then be set to the
2600                --  parent of that ancestor.
2601
2602                if not Is_Private_Library_Unit (Priv_Child) then
2603                   while Present (Prv_Ancestor)
2604                     and then not Is_Private_Library_Unit (Prv_Ancestor)
2605                   loop
2606                      Prv_Ancestor := Scope (Prv_Ancestor);
2607                   end loop;
2608
2609                   if Present (Prv_Ancestor) then
2610                      Child_Parent := Scope (Prv_Ancestor);
2611                   end if;
2612                end if;
2613
2614                while Present (Curr_Parent)
2615                  and then Curr_Parent /= Standard_Standard
2616                  and then Curr_Parent /= Child_Parent
2617                loop
2618                   Curr_Private :=
2619                     Curr_Private or else Is_Private_Library_Unit (Curr_Parent);
2620                   Curr_Parent := Scope (Curr_Parent);
2621                end loop;
2622
2623                if No (Curr_Parent) then
2624                   Curr_Parent := Standard_Standard;
2625                end if;
2626
2627                if Curr_Parent /= Child_Parent then
2628                   if Ekind (Priv_Child) = E_Generic_Package
2629                     and then Chars (Priv_Child) in Text_IO_Package_Name
2630                     and then Chars (Scope (Scope (Priv_Child))) = Name_Ada
2631                   then
2632                      Error_Msg_NE
2633                        ("& is a nested package, not a compilation unit",
2634                        Name (Item), Priv_Child);
2635
2636                   else
2637                      Error_Msg_N
2638                        ("unit in with clause is private child unit!", Item);
2639                      Error_Msg_NE
2640                        ("\current unit must also have parent&!",
2641                         Item, Child_Parent);
2642                   end if;
2643
2644                elsif Curr_Private
2645                  or else Private_Present (Item)
2646                  or else Nkind_In (Lib_Unit, N_Package_Body, N_Subunit)
2647                  or else (Nkind (Lib_Unit) = N_Subprogram_Body
2648                             and then not Acts_As_Spec (Parent (Lib_Unit)))
2649                then
2650                   null;
2651
2652                else
2653                   Error_Msg_NE
2654                     ("current unit must also be private descendant of&",
2655                      Item, Child_Parent);
2656                end if;
2657             end;
2658          end if;
2659
2660          Next (Item);
2661       end loop;
2662
2663    end Check_Private_Child_Unit;
2664
2665    ----------------------
2666    -- Check_Stub_Level --
2667    ----------------------
2668
2669    procedure Check_Stub_Level (N : Node_Id) is
2670       Par  : constant Node_Id   := Parent (N);
2671       Kind : constant Node_Kind := Nkind (Par);
2672
2673    begin
2674       if Nkind_In (Kind, N_Package_Body,
2675                          N_Subprogram_Body,
2676                          N_Task_Body,
2677                          N_Protected_Body)
2678         and then Nkind_In (Parent (Par), N_Compilation_Unit, N_Subunit)
2679       then
2680          null;
2681
2682       --  In an instance, a missing stub appears at any level. A warning
2683       --  message will have been emitted already for the missing file.
2684
2685       elsif not In_Instance then
2686          Error_Msg_N ("stub cannot appear in an inner scope", N);
2687
2688       elsif Expander_Active then
2689          Error_Msg_N ("missing proper body", N);
2690       end if;
2691    end Check_Stub_Level;
2692
2693    ------------------------
2694    -- Expand_With_Clause --
2695    ------------------------
2696
2697    procedure Expand_With_Clause (Item : Node_Id; Nam : Node_Id; N : Node_Id) is
2698       Loc   : constant Source_Ptr := Sloc (Nam);
2699       Ent   : constant Entity_Id := Entity (Nam);
2700       Withn : Node_Id;
2701       P     : Node_Id;
2702
2703       function Build_Unit_Name (Nam : Node_Id) return Node_Id;
2704       --  Build name to be used in implicit with_clause. In most cases this
2705       --  is the source name, but if renamings are present we must make the
2706       --  original unit visible, not the one it renames. The entity in the
2707       --  with clause is the renamed unit, but the identifier is the one from
2708       --  the source, which allows us to recover the unit renaming.
2709
2710       ---------------------
2711       -- Build_Unit_Name --
2712       ---------------------
2713
2714       function Build_Unit_Name (Nam : Node_Id) return Node_Id is
2715          Ent      : Entity_Id;
2716          Renaming : Entity_Id;
2717          Result   : Node_Id;
2718
2719       begin
2720          if Nkind (Nam) = N_Identifier then
2721
2722             --  If the parent unit P in the name of the with_clause for P.Q
2723             --  is a renaming of package R, then the entity of the parent is
2724             --  set to R, but the identifier retains Chars (P) to be consistent
2725             --  with the source (see details in lib-load). However, the
2726             --  implicit_with_clause for the parent must make the entity for
2727             --  P visible, because P.Q may be used as a prefix within the
2728             --  current unit. The entity for P is the current_entity with that
2729             --  name, because the package renaming declaration for it has just
2730             --  been analyzed. Note that this case can only happen if P.Q has
2731             --  already appeared in a previous with_clause in a related unit,
2732             --  such as the library body of the current unit.
2733
2734             if Chars (Nam) /= Chars (Entity (Nam)) then
2735                Renaming := Current_Entity (Nam);
2736                pragma Assert (Renamed_Entity (Renaming) = Entity (Nam));
2737                return New_Occurrence_Of (Renaming, Loc);
2738
2739             else
2740                return New_Occurrence_Of (Entity (Nam), Loc);
2741             end if;
2742
2743          else
2744             Ent := Entity (Nam);
2745
2746             if Present (Entity (Selector_Name (Nam)))
2747               and then Chars (Entity (Selector_Name (Nam))) /= Chars (Ent)
2748               and then
2749                 Nkind (Unit_Declaration_Node (Entity (Selector_Name (Nam))))
2750                   = N_Package_Renaming_Declaration
2751             then
2752                --  The name in the with_clause is of the form A.B.C, and B
2753                --  is given by a renaming declaration. In that case we may
2754                --  not have analyzed the unit for B, but replaced it directly
2755                --  in lib-load with the unit it renames. We have to make A.B
2756                --  visible, so analyze the declaration for B now, in case it
2757                --  has not been done yet.
2758
2759                Ent :=  Entity (Selector_Name (Nam));
2760                Analyze
2761                  (Parent
2762                    (Unit_Declaration_Node (Entity (Selector_Name (Nam)))));
2763             end if;
2764
2765             Result :=
2766               Make_Expanded_Name (Loc,
2767                 Chars  => Chars (Entity (Nam)),
2768                 Prefix => Build_Unit_Name (Prefix (Nam)),
2769                 Selector_Name => New_Occurrence_Of (Ent, Loc));
2770             Set_Entity (Result, Ent);
2771             return Result;
2772          end if;
2773       end Build_Unit_Name;
2774
2775    --  Start of processing for Expand_With_Clause
2776
2777    begin
2778       New_Nodes_OK := New_Nodes_OK + 1;
2779       Withn :=
2780         Make_With_Clause (Loc,
2781           Name => Build_Unit_Name (Nam));
2782
2783       P := Parent (Unit_Declaration_Node (Ent));
2784       Set_Library_Unit       (Withn, P);
2785       Set_Corresponding_Spec (Withn, Ent);
2786       Set_First_Name         (Withn, True);
2787       Set_Implicit_With      (Withn, True);
2788
2789       --  If the unit is a package declaration, a private_with_clause on a
2790       --  child unit implies that the implicit with on the parent is also
2791       --  private.
2792
2793       if Nkind (Unit (N)) = N_Package_Declaration then
2794          Set_Private_Present (Withn, Private_Present (Item));
2795       end if;
2796
2797       Prepend (Withn, Context_Items (N));
2798       Mark_Rewrite_Insertion (Withn);
2799       Install_Withed_Unit (Withn);
2800
2801       if Nkind (Nam) = N_Expanded_Name then
2802          Expand_With_Clause (Item, Prefix (Nam), N);
2803       end if;
2804
2805       New_Nodes_OK := New_Nodes_OK - 1;
2806    end Expand_With_Clause;
2807
2808    -----------------------
2809    -- Get_Parent_Entity --
2810    -----------------------
2811
2812    function Get_Parent_Entity (Unit : Node_Id) return Entity_Id is
2813    begin
2814       if Nkind (Unit) = N_Package_Body
2815         and then Nkind (Original_Node (Unit)) = N_Package_Instantiation
2816       then
2817          return Defining_Entity
2818                  (Specification (Instance_Spec (Original_Node (Unit))));
2819       elsif Nkind (Unit) = N_Package_Instantiation then
2820          return Defining_Entity (Specification (Instance_Spec (Unit)));
2821       else
2822          return Defining_Entity (Unit);
2823       end if;
2824    end Get_Parent_Entity;
2825
2826    ---------------------
2827    -- Has_With_Clause --
2828    ---------------------
2829
2830    function Has_With_Clause
2831      (C_Unit     : Node_Id;
2832       Pack       : Entity_Id;
2833       Is_Limited : Boolean := False) return Boolean
2834    is
2835       Item : Node_Id;
2836
2837       function Named_Unit (Clause : Node_Id) return Entity_Id;
2838       --  Return the entity for the unit named in a [limited] with clause
2839
2840       ----------------
2841       -- Named_Unit --
2842       ----------------
2843
2844       function Named_Unit (Clause : Node_Id) return Entity_Id is
2845       begin
2846          if Nkind (Name (Clause)) = N_Selected_Component then
2847             return Entity (Selector_Name (Name (Clause)));
2848          else
2849             return Entity (Name (Clause));
2850          end if;
2851       end Named_Unit;
2852
2853    --  Start of processing for Has_With_Clause
2854
2855    begin
2856       if Present (Context_Items (C_Unit)) then
2857          Item := First (Context_Items (C_Unit));
2858          while Present (Item) loop
2859             if Nkind (Item) = N_With_Clause
2860               and then Limited_Present (Item) = Is_Limited
2861               and then Named_Unit (Item) = Pack
2862             then
2863                return True;
2864             end if;
2865
2866             Next (Item);
2867          end loop;
2868       end if;
2869
2870       return False;
2871    end Has_With_Clause;
2872
2873    -----------------------------
2874    -- Implicit_With_On_Parent --
2875    -----------------------------
2876
2877    procedure Implicit_With_On_Parent
2878      (Child_Unit : Node_Id;
2879       N          : Node_Id)
2880    is
2881       Loc    : constant Source_Ptr := Sloc (N);
2882       P      : constant Node_Id    := Parent_Spec (Child_Unit);
2883       P_Unit : Node_Id             := Unit (P);
2884       P_Name : constant Entity_Id  := Get_Parent_Entity (P_Unit);
2885       Withn  : Node_Id;
2886
2887       function Build_Ancestor_Name (P : Node_Id) return Node_Id;
2888       --  Build prefix of child unit name. Recurse if needed
2889
2890       function Build_Unit_Name return Node_Id;
2891       --  If the unit is a child unit, build qualified name with all ancestors
2892
2893       -------------------------
2894       -- Build_Ancestor_Name --
2895       -------------------------
2896
2897       function Build_Ancestor_Name (P : Node_Id) return Node_Id is
2898          P_Ref  : constant Node_Id :=
2899                    New_Reference_To (Defining_Entity (P), Loc);
2900          P_Spec : Node_Id := P;
2901
2902       begin
2903          --  Ancestor may have been rewritten as a package body. Retrieve
2904          --  the original spec to trace earlier ancestors.
2905
2906          if Nkind (P) = N_Package_Body
2907            and then Nkind (Original_Node (P)) = N_Package_Instantiation
2908          then
2909             P_Spec := Original_Node (P);
2910          end if;
2911
2912          if No (Parent_Spec (P_Spec)) then
2913             return P_Ref;
2914          else
2915             return
2916               Make_Selected_Component (Loc,
2917                 Prefix => Build_Ancestor_Name (Unit (Parent_Spec (P_Spec))),
2918                 Selector_Name => P_Ref);
2919          end if;
2920       end Build_Ancestor_Name;
2921
2922       ---------------------
2923       -- Build_Unit_Name --
2924       ---------------------
2925
2926       function Build_Unit_Name return Node_Id is
2927          Result : Node_Id;
2928       begin
2929          if No (Parent_Spec (P_Unit)) then
2930             return New_Reference_To (P_Name, Loc);
2931          else
2932             Result :=
2933               Make_Expanded_Name (Loc,
2934                 Chars  => Chars (P_Name),
2935                 Prefix => Build_Ancestor_Name (Unit (Parent_Spec (P_Unit))),
2936                 Selector_Name => New_Reference_To (P_Name, Loc));
2937             Set_Entity (Result, P_Name);
2938             return Result;
2939          end if;
2940       end Build_Unit_Name;
2941
2942    --  Start of processing for Implicit_With_On_Parent
2943
2944    begin
2945       --  The unit of the current compilation may be a package body that
2946       --  replaces an instance node. In this case we need the original instance
2947       --  node to construct the proper parent name.
2948
2949       if Nkind (P_Unit) = N_Package_Body
2950         and then Nkind (Original_Node (P_Unit)) = N_Package_Instantiation
2951       then
2952          P_Unit := Original_Node (P_Unit);
2953       end if;
2954
2955       --  We add the implicit with if the child unit is the current unit being
2956       --  compiled. If the current unit is a body, we do not want to add an
2957       --  implicit_with a second time to the corresponding spec.
2958
2959       if Nkind (Child_Unit) = N_Package_Declaration
2960         and then Child_Unit /= Unit (Cunit (Current_Sem_Unit))
2961       then
2962          return;
2963       end if;
2964
2965       New_Nodes_OK := New_Nodes_OK + 1;
2966       Withn := Make_With_Clause (Loc, Name => Build_Unit_Name);
2967
2968       Set_Library_Unit          (Withn, P);
2969       Set_Corresponding_Spec    (Withn, P_Name);
2970       Set_First_Name            (Withn, True);
2971       Set_Implicit_With         (Withn, True);
2972
2973       --  Node is placed at the beginning of the context items, so that
2974       --  subsequent use clauses on the parent can be validated.
2975
2976       Prepend (Withn, Context_Items (N));
2977       Mark_Rewrite_Insertion (Withn);
2978       Install_Withed_Unit (Withn);
2979
2980       if Is_Child_Spec (P_Unit) then
2981          Implicit_With_On_Parent (P_Unit, N);
2982       end if;
2983
2984       New_Nodes_OK := New_Nodes_OK - 1;
2985    end Implicit_With_On_Parent;
2986
2987    --------------
2988    -- In_Chain --
2989    --------------
2990
2991    function In_Chain (E : Entity_Id) return Boolean is
2992       H : Entity_Id;
2993
2994    begin
2995       H := Current_Entity (E);
2996       while Present (H) loop
2997          if H = E then
2998             return True;
2999          else
3000             H := Homonym (H);
3001          end if;
3002       end loop;
3003
3004       return False;
3005    end In_Chain;
3006
3007    ---------------------
3008    -- Install_Context --
3009    ---------------------
3010
3011    procedure Install_Context (N : Node_Id) is
3012       Lib_Unit : constant Node_Id := Unit (N);
3013
3014    begin
3015       Install_Context_Clauses (N);
3016
3017       if Is_Child_Spec (Lib_Unit) then
3018          Install_Parents (Lib_Unit, Private_Present (Parent (Lib_Unit)));
3019       end if;
3020
3021       Install_Limited_Context_Clauses (N);
3022    end Install_Context;
3023
3024    -----------------------------
3025    -- Install_Context_Clauses --
3026    -----------------------------
3027
3028    procedure Install_Context_Clauses (N : Node_Id) is
3029       Lib_Unit      : constant Node_Id := Unit (N);
3030       Item          : Node_Id;
3031       Uname_Node    : Entity_Id;
3032       Check_Private : Boolean := False;
3033       Decl_Node     : Node_Id;
3034       Lib_Parent    : Entity_Id;
3035
3036    begin
3037       --  First skip configuration pragmas at the start of the context. They
3038       --  are not technically part of the context clause, but that's where the
3039       --  parser puts them. Note they were analyzed in Analyze_Context.
3040
3041       Item := First (Context_Items (N));
3042       while Present (Item)
3043         and then Nkind (Item) = N_Pragma
3044         and then Pragma_Name (Item) in Configuration_Pragma_Names
3045       loop
3046          Next (Item);
3047       end loop;
3048
3049       --  Loop through the actual context clause items. We process everything
3050       --  except Limited_With clauses in this routine. Limited_With clauses
3051       --  are separately installed (see Install_Limited_Context_Clauses).
3052
3053       while Present (Item) loop
3054
3055          --  Case of explicit WITH clause
3056
3057          if Nkind (Item) = N_With_Clause
3058            and then not Implicit_With (Item)
3059          then
3060             if Limited_Present (Item) then
3061
3062                --  Limited withed units will be installed later
3063
3064                goto Continue;
3065
3066             --  If Name (Item) is not an entity name, something is wrong, and
3067             --  this will be detected in due course, for now ignore the item
3068
3069             elsif not Is_Entity_Name (Name (Item)) then
3070                goto Continue;
3071
3072             elsif No (Entity (Name (Item))) then
3073                Set_Entity (Name (Item), Any_Id);
3074                goto Continue;
3075             end if;
3076
3077             Uname_Node := Entity (Name (Item));
3078
3079             if Is_Private_Descendant (Uname_Node) then
3080                Check_Private := True;
3081             end if;
3082
3083             Install_Withed_Unit (Item);
3084
3085             Decl_Node := Unit_Declaration_Node (Uname_Node);
3086
3087             --  If the unit is a subprogram instance, it appears nested within
3088             --  a package that carries the parent information.
3089
3090             if Is_Generic_Instance (Uname_Node)
3091               and then Ekind (Uname_Node) /= E_Package
3092             then
3093                Decl_Node := Parent (Parent (Decl_Node));
3094             end if;
3095
3096             if Is_Child_Spec (Decl_Node) then
3097                if Nkind (Name (Item)) = N_Expanded_Name then
3098                   Expand_With_Clause (Item, Prefix (Name (Item)), N);
3099                else
3100                   --  If not an expanded name, the child unit must be a
3101                   --  renaming, nothing to do.
3102
3103                   null;
3104                end if;
3105
3106             elsif Nkind (Decl_Node) = N_Subprogram_Body
3107               and then not Acts_As_Spec (Parent (Decl_Node))
3108               and then Is_Child_Spec (Unit (Library_Unit (Parent (Decl_Node))))
3109             then
3110                Implicit_With_On_Parent
3111                  (Unit (Library_Unit (Parent (Decl_Node))), N);
3112             end if;
3113
3114             --  Check license conditions unless this is a dummy unit
3115
3116             if Sloc (Library_Unit (Item)) /= No_Location then
3117                License_Check : declare
3118
3119                   Withu : constant Unit_Number_Type :=
3120                             Get_Source_Unit (Library_Unit (Item));
3121
3122                   Withl : constant License_Type :=
3123                             License (Source_Index (Withu));
3124
3125                   Unitl : constant License_Type :=
3126                            License (Source_Index (Current_Sem_Unit));
3127
3128                   procedure License_Error;
3129                   --  Signal error of bad license
3130
3131                   -------------------
3132                   -- License_Error --
3133                   -------------------
3134
3135                   procedure License_Error is
3136                   begin
3137                      Error_Msg_N
3138                        ("?license of with'ed unit & may be inconsistent",
3139                         Name (Item));
3140                   end License_Error;
3141
3142                --  Start of processing for License_Check
3143
3144                begin
3145                   --  Exclude license check if withed unit is an internal unit.
3146                   --  This situation arises e.g. with the GPL version of GNAT.
3147
3148                   if Is_Internal_File_Name (Unit_File_Name (Withu)) then
3149                      null;
3150
3151                      --  Otherwise check various cases
3152                   else
3153                      case Unitl is
3154                         when Unknown =>
3155                            null;
3156
3157                         when Restricted =>
3158                            if Withl = GPL then
3159                               License_Error;
3160                            end if;
3161
3162                         when GPL =>
3163                            if Withl = Restricted then
3164                               License_Error;
3165                            end if;
3166
3167                         when Modified_GPL =>
3168                            if Withl = Restricted or else Withl = GPL then
3169                               License_Error;
3170                            end if;
3171
3172                         when Unrestricted =>
3173                            null;
3174                      end case;
3175                   end if;
3176                end License_Check;
3177             end if;
3178
3179          --  Case of USE PACKAGE clause
3180
3181          elsif Nkind (Item) = N_Use_Package_Clause then
3182             Analyze_Use_Package (Item);
3183
3184          --  Case of USE TYPE clause
3185
3186          elsif Nkind (Item) = N_Use_Type_Clause then
3187             Analyze_Use_Type (Item);
3188
3189          --  case of PRAGMA
3190
3191          elsif Nkind (Item) = N_Pragma then
3192             Analyze (Item);
3193          end if;
3194
3195       <<Continue>>
3196          Next (Item);
3197       end loop;
3198
3199       if Is_Child_Spec (Lib_Unit) then
3200
3201          --  The unit also has implicit with_clauses on its own parents
3202
3203          if No (Context_Items (N)) then
3204             Set_Context_Items (N, New_List);
3205          end if;
3206
3207          Implicit_With_On_Parent (Lib_Unit, N);
3208       end if;
3209
3210       --  If the unit is a body, the context of the specification must also
3211       --  be installed. That includes private with_clauses in that context.
3212
3213       if Nkind (Lib_Unit) = N_Package_Body
3214         or else (Nkind (Lib_Unit) = N_Subprogram_Body
3215                    and then not Acts_As_Spec (N))
3216       then
3217          Install_Context (Library_Unit (N));
3218
3219          --  Only install private with-clauses of a spec that comes from
3220          --  source, excluding specs created for a subprogram body that is
3221          --  a child unit.
3222
3223          if Comes_From_Source (Library_Unit (N)) then
3224             Install_Private_With_Clauses
3225               (Defining_Entity (Unit (Library_Unit (N))));
3226          end if;
3227
3228          if Is_Child_Spec (Unit (Library_Unit (N))) then
3229
3230             --  If the unit is the body of a public child unit, the private
3231             --  declarations of the parent must be made visible. If the child
3232             --  unit is private, the private declarations have been installed
3233             --  already in the call to Install_Parents for the spec. Installing
3234             --  private declarations must be done for all ancestors of public
3235             --  child units. In addition, sibling units mentioned in the
3236             --  context clause of the body are directly visible.
3237
3238             declare
3239                Lib_Spec : Node_Id;
3240                P        : Node_Id;
3241                P_Name   : Entity_Id;
3242
3243             begin
3244                Lib_Spec := Unit (Library_Unit (N));
3245                while Is_Child_Spec (Lib_Spec) loop
3246                   P      := Unit (Parent_Spec (Lib_Spec));
3247                   P_Name := Defining_Entity (P);
3248
3249                   if not (Private_Present (Parent (Lib_Spec)))
3250                     and then not In_Private_Part (P_Name)
3251                   then
3252                      Install_Private_Declarations (P_Name);
3253                      Install_Private_With_Clauses (P_Name);
3254                      Set_Use (Private_Declarations (Specification (P)));
3255                   end if;
3256
3257                   Lib_Spec := P;
3258                end loop;
3259             end;
3260          end if;
3261
3262          --  For a package body, children in context are immediately visible
3263
3264          Install_Siblings (Defining_Entity (Unit (Library_Unit (N))), N);
3265       end if;
3266
3267       if Nkind_In (Lib_Unit, N_Generic_Package_Declaration,
3268                              N_Generic_Subprogram_Declaration,
3269                              N_Package_Declaration,
3270                              N_Subprogram_Declaration)
3271       then
3272          if Is_Child_Spec (Lib_Unit) then
3273             Lib_Parent := Defining_Entity (Unit (Parent_Spec (Lib_Unit)));
3274             Set_Is_Private_Descendant
3275               (Defining_Entity (Lib_Unit),
3276                Is_Private_Descendant (Lib_Parent)
3277                  or else Private_Present (Parent (Lib_Unit)));
3278
3279          else
3280             Set_Is_Private_Descendant
3281               (Defining_Entity (Lib_Unit),
3282                Private_Present (Parent (Lib_Unit)));
3283          end if;
3284       end if;
3285
3286       if Check_Private then
3287          Check_Private_Child_Unit (N);
3288       end if;
3289    end Install_Context_Clauses;
3290
3291    -------------------------------------
3292    -- Install_Limited_Context_Clauses --
3293    -------------------------------------
3294
3295    procedure Install_Limited_Context_Clauses (N : Node_Id) is
3296       Item : Node_Id;
3297
3298       procedure Check_Renamings (P : Node_Id; W : Node_Id);
3299       --  Check that the unlimited view of a given compilation_unit is not
3300       --  already visible through "use + renamings".
3301
3302       procedure Check_Private_Limited_Withed_Unit (Item : Node_Id);
3303       --  Check that if a limited_with clause of a given compilation_unit
3304       --  mentions a descendant of a private child of some library unit,
3305       --  then the given compilation_unit shall be the declaration of a
3306       --  private descendant of that library unit, or a public descendant
3307       --  of such. The code is analogous to that of Check_Private_Child_Unit
3308       --  but we cannot use entities on the limited with_clauses because
3309       --  their units have not been analyzed, so we have to climb the tree
3310       --  of ancestors looking for private keywords.
3311
3312       procedure Expand_Limited_With_Clause
3313         (Comp_Unit : Node_Id;
3314          Nam       : Node_Id;
3315          N         : Node_Id);
3316       --  If a child unit appears in a limited_with clause, there are implicit
3317       --  limited_with clauses on all parents that are not already visible
3318       --  through a regular with clause. This procedure creates the implicit
3319       --  limited with_clauses for the parents and loads the corresponding
3320       --  units. The shadow entities are created when the inserted clause is
3321       --  analyzed. Implements Ada 2005 (AI-50217).
3322
3323       ---------------------
3324       -- Check_Renamings --
3325       ---------------------
3326
3327       procedure Check_Renamings (P : Node_Id; W : Node_Id) is
3328          Item   : Node_Id;
3329          Spec   : Node_Id;
3330          WEnt   : Entity_Id;
3331          Nam    : Node_Id;
3332          E      : Entity_Id;
3333          E2     : Entity_Id;
3334
3335       begin
3336          pragma Assert (Nkind (W) = N_With_Clause);
3337
3338          --  Protect the frontend against previous critical errors
3339
3340          case Nkind (Unit (Library_Unit (W))) is
3341             when N_Subprogram_Declaration         |
3342                  N_Package_Declaration            |
3343                  N_Generic_Subprogram_Declaration |
3344                  N_Generic_Package_Declaration    =>
3345                null;
3346
3347             when others =>
3348                return;
3349          end case;
3350
3351          --  Check "use + renamings"
3352
3353          WEnt := Defining_Unit_Name (Specification (Unit (Library_Unit (W))));
3354          Spec := Specification (Unit (P));
3355
3356          Item := First (Visible_Declarations (Spec));
3357          while Present (Item) loop
3358
3359             --  Look only at use package clauses
3360
3361             if Nkind (Item) = N_Use_Package_Clause then
3362
3363                --  Traverse the list of packages
3364
3365                Nam := First (Names (Item));
3366                while Present (Nam) loop
3367                   E := Entity (Nam);
3368
3369                   pragma Assert (Present (Parent (E)));
3370
3371                   if Nkind (Parent (E)) = N_Package_Renaming_Declaration
3372                     and then Renamed_Entity (E) = WEnt
3373                   then
3374                      --  The unlimited view is visible through use clause and
3375                      --  renamings. There is no need to generate the error
3376                      --  message here because Is_Visible_Through_Renamings
3377                      --  takes care of generating the precise error message.
3378
3379                      return;
3380
3381                   elsif Nkind (Parent (E)) = N_Package_Specification then
3382
3383                      --  The use clause may refer to a local package.
3384                      --  Check all the enclosing scopes.
3385
3386                      E2 := E;
3387                      while E2 /= Standard_Standard
3388                        and then E2 /= WEnt
3389                      loop
3390                         E2 := Scope (E2);
3391                      end loop;
3392
3393                      if E2 = WEnt then
3394                         Error_Msg_N
3395                           ("unlimited view visible through use clause ", W);
3396                         return;
3397                      end if;
3398                   end if;
3399
3400                   Next (Nam);
3401                end loop;
3402             end if;
3403
3404             Next (Item);
3405          end loop;
3406
3407          --  Recursive call to check all the ancestors
3408
3409          if Is_Child_Spec (Unit (P)) then
3410             Check_Renamings (P => Parent_Spec (Unit (P)), W => W);
3411          end if;
3412       end Check_Renamings;
3413
3414       ---------------------------------------
3415       -- Check_Private_Limited_Withed_Unit --
3416       ---------------------------------------
3417
3418       procedure Check_Private_Limited_Withed_Unit (Item : Node_Id) is
3419          Curr_Parent  : Node_Id;
3420          Child_Parent : Node_Id;
3421          Curr_Private : Boolean;
3422
3423       begin
3424          --  Compilation unit of the parent of the withed library unit
3425
3426          Child_Parent := Library_Unit (Item);
3427
3428          --  If the child unit is a public child, then locate its nearest
3429          --  private ancestor, if any; Child_Parent will then be set to
3430          --  the parent of that ancestor.
3431
3432          if not Private_Present (Library_Unit (Item)) then
3433             while Present (Child_Parent)
3434               and then not Private_Present (Child_Parent)
3435             loop
3436                Child_Parent := Parent_Spec (Unit (Child_Parent));
3437             end loop;
3438
3439             if No (Child_Parent) then
3440                return;
3441             end if;
3442          end if;
3443
3444          Child_Parent := Parent_Spec (Unit (Child_Parent));
3445
3446          --  Traverse all the ancestors of the current compilation
3447          --  unit to check if it is a descendant of named library unit.
3448
3449          Curr_Parent := Parent (Item);
3450          Curr_Private := Private_Present (Curr_Parent);
3451
3452          while Present (Parent_Spec (Unit (Curr_Parent)))
3453            and then Curr_Parent /= Child_Parent
3454          loop
3455             Curr_Parent := Parent_Spec (Unit (Curr_Parent));
3456             Curr_Private := Curr_Private or else Private_Present (Curr_Parent);
3457          end loop;
3458
3459          if Curr_Parent /= Child_Parent then
3460             Error_Msg_N
3461               ("unit in with clause is private child unit!", Item);
3462             Error_Msg_NE
3463               ("\current unit must also have parent&!",
3464                Item, Defining_Unit_Name (Specification (Unit (Child_Parent))));
3465
3466          elsif Private_Present (Parent (Item))
3467             or else Curr_Private
3468             or else Private_Present (Item)
3469             or else Nkind_In (Unit (Parent (Item)), N_Package_Body,
3470                                                         N_Subprogram_Body,
3471                                                         N_Subunit)
3472          then
3473             --  Current unit is private, of descendant of a private unit
3474
3475             null;
3476
3477          else
3478             Error_Msg_NE
3479               ("current unit must also be private descendant of&",
3480                Item, Defining_Unit_Name (Specification (Unit (Child_Parent))));
3481          end if;
3482       end Check_Private_Limited_Withed_Unit;
3483
3484       --------------------------------
3485       -- Expand_Limited_With_Clause --
3486       --------------------------------
3487
3488       procedure Expand_Limited_With_Clause
3489         (Comp_Unit : Node_Id;
3490          Nam       : Node_Id;
3491          N         : Node_Id)
3492       is
3493          Loc   : constant Source_Ptr := Sloc (Nam);
3494          Unum  : Unit_Number_Type;
3495          Withn : Node_Id;
3496
3497          function Previous_Withed_Unit (W : Node_Id) return Boolean;
3498          --  Returns true if the context already includes a with_clause for
3499          --  this unit. If the with_clause is non-limited, the unit is fully
3500          --  visible and an implicit limited_with should not be created. If
3501          --  there is already a limited_with clause for W, a second one is
3502          --  simply redundant.
3503
3504          --------------------------
3505          -- Previous_Withed_Unit --
3506          --------------------------
3507
3508          function Previous_Withed_Unit (W : Node_Id) return Boolean is
3509             Item : Node_Id;
3510
3511          begin
3512             --  A limited with_clause cannot appear in the same context_clause
3513             --  as a nonlimited with_clause which mentions the same library.
3514
3515             Item := First (Context_Items (Comp_Unit));
3516             while Present (Item) loop
3517                if Nkind (Item) = N_With_Clause
3518                  and then Library_Unit (Item) = Library_Unit (W)
3519                then
3520                   return True;
3521                end if;
3522
3523                Next (Item);
3524             end loop;
3525
3526             return False;
3527          end Previous_Withed_Unit;
3528
3529       --  Start of processing for Expand_Limited_With_Clause
3530
3531       begin
3532          New_Nodes_OK := New_Nodes_OK + 1;
3533
3534          if Nkind (Nam) = N_Identifier then
3535
3536             --  Create node for name of withed unit
3537
3538             Withn :=
3539               Make_With_Clause (Loc,
3540                 Name => New_Copy (Nam));
3541
3542          else pragma Assert (Nkind (Nam) = N_Selected_Component);
3543             Withn :=
3544               Make_With_Clause (Loc,
3545                 Name => Make_Selected_Component (Loc,
3546                   Prefix        => New_Copy_Tree (Prefix (Nam)),
3547                   Selector_Name => New_Copy (Selector_Name (Nam))));
3548             Set_Parent (Withn, Parent (N));
3549          end if;
3550
3551          Set_Limited_Present (Withn);
3552          Set_First_Name      (Withn);
3553          Set_Implicit_With   (Withn);
3554
3555          Unum :=
3556            Load_Unit
3557              (Load_Name  => Get_Spec_Name (Get_Unit_Name (Nam)),
3558               Required   => True,
3559               Subunit    => False,
3560               Error_Node => Nam);
3561
3562          --  Do not generate a limited_with_clause on the current unit.
3563          --  This path is taken when a unit has a limited_with clause on
3564          --  one of its child units.
3565
3566          if Unum = Current_Sem_Unit then
3567             return;
3568          end if;
3569
3570          Set_Library_Unit (Withn, Cunit (Unum));
3571          Set_Corresponding_Spec
3572            (Withn, Specification (Unit (Cunit (Unum))));
3573
3574          if not Previous_Withed_Unit (Withn) then
3575             Prepend (Withn, Context_Items (Parent (N)));
3576             Mark_Rewrite_Insertion (Withn);
3577
3578             --  Add implicit limited_with_clauses for parents of child units
3579             --  mentioned in limited_with clauses.
3580
3581             if Nkind (Nam) = N_Selected_Component then
3582                Expand_Limited_With_Clause (Comp_Unit, Prefix (Nam), N);
3583             end if;
3584
3585             Analyze (Withn);
3586
3587             if not Limited_View_Installed (Withn) then
3588                Install_Limited_Withed_Unit (Withn);
3589             end if;
3590          end if;
3591
3592          New_Nodes_OK := New_Nodes_OK - 1;
3593       end Expand_Limited_With_Clause;
3594
3595    --  Start of processing for Install_Limited_Context_Clauses
3596
3597    begin
3598       Item := First (Context_Items (N));
3599       while Present (Item) loop
3600          if Nkind (Item) = N_With_Clause
3601            and then Limited_Present (Item)
3602          then
3603             if Nkind (Name (Item)) = N_Selected_Component then
3604                Expand_Limited_With_Clause
3605                  (Comp_Unit => N, Nam => Prefix (Name (Item)), N => Item);
3606             end if;
3607
3608             Check_Private_Limited_Withed_Unit (Item);
3609
3610             if not Implicit_With (Item)
3611               and then Is_Child_Spec (Unit (N))
3612             then
3613                Check_Renamings (Parent_Spec (Unit (N)), Item);
3614             end if;
3615
3616             --  A unit may have a limited with on itself if it has a limited
3617             --  with_clause on one of its child units. In that case it is
3618             --  already being compiled and it makes no sense to install its
3619             --  limited view.
3620
3621             --  If the item is a limited_private_with_clause, install it if the
3622             --  current unit is a body or if it is a private child. Otherwise
3623             --  the private clause is installed before analyzing the private
3624             --  part of the current unit.
3625
3626             if Library_Unit (Item) /= Cunit (Current_Sem_Unit)
3627               and then not Limited_View_Installed (Item)
3628             then
3629                if not Private_Present (Item)
3630                  or else Private_Present (N)
3631                  or else Nkind_In (Unit (N), N_Package_Body,
3632                                              N_Subprogram_Body,
3633                                              N_Subunit)
3634                then
3635                   Install_Limited_Withed_Unit (Item);
3636                end if;
3637             end if;
3638          end if;
3639
3640          Next (Item);
3641       end loop;
3642
3643       --  Ada 2005 (AI-412): Examine the visible declarations of a package
3644       --  spec, looking for incomplete subtype declarations of incomplete
3645       --  types visible through a limited with clause.
3646
3647       if Ada_Version >= Ada_05
3648         and then Analyzed (N)
3649         and then Nkind (Unit (N)) = N_Package_Declaration
3650       then
3651          declare
3652             Decl         : Node_Id;
3653             Def_Id       : Entity_Id;
3654             Non_Lim_View : Entity_Id;
3655
3656          begin
3657             Decl := First (Visible_Declarations (Specification (Unit (N))));
3658             while Present (Decl) loop
3659                if Nkind (Decl) = N_Subtype_Declaration
3660                  and then
3661                    Ekind (Defining_Identifier (Decl)) = E_Incomplete_Subtype
3662                  and then
3663                    From_With_Type (Defining_Identifier (Decl))
3664                then
3665                   Def_Id := Defining_Identifier (Decl);
3666                   Non_Lim_View := Non_Limited_View (Def_Id);
3667
3668                   if not Is_Incomplete_Type (Non_Lim_View) then
3669
3670                      --  Convert an incomplete subtype declaration into a
3671                      --  corresponding non-limited view subtype declaration.
3672                      --  This is usually the case when analyzing a body that
3673                      --  has regular with-clauses, when the spec has limited
3674                      --  ones.
3675
3676                      --  If the non-limited view is still incomplete, it is
3677                      --  the dummy entry already created, and the declaration
3678                      --  cannot be reanalyzed. This is the case when installing
3679                      --  a parent unit that has limited with-clauses.
3680
3681                      Set_Subtype_Indication (Decl,
3682                        New_Reference_To (Non_Lim_View, Sloc (Def_Id)));
3683                      Set_Etype (Def_Id, Non_Lim_View);
3684                      Set_Ekind (Def_Id, Subtype_Kind (Ekind (Non_Lim_View)));
3685                      Set_Analyzed (Decl, False);
3686
3687                      --  Reanalyze the declaration, suppressing the call to
3688                      --  Enter_Name to avoid duplicate names.
3689
3690                      Analyze_Subtype_Declaration
3691                       (N    => Decl,
3692                        Skip => True);
3693                   end if;
3694                end if;
3695
3696                Next (Decl);
3697             end loop;
3698          end;
3699       end if;
3700    end Install_Limited_Context_Clauses;
3701
3702    ---------------------
3703    -- Install_Parents --
3704    ---------------------
3705
3706    procedure Install_Parents (Lib_Unit : Node_Id; Is_Private : Boolean) is
3707       P      : Node_Id;
3708       E_Name : Entity_Id;
3709       P_Name : Entity_Id;
3710       P_Spec : Node_Id;
3711
3712    begin
3713       P := Unit (Parent_Spec (Lib_Unit));
3714       P_Name := Get_Parent_Entity (P);
3715
3716       if Etype (P_Name) = Any_Type then
3717          return;
3718       end if;
3719
3720       if Ekind (P_Name) = E_Generic_Package
3721         and then not Nkind_In (Lib_Unit, N_Generic_Subprogram_Declaration,
3722                                          N_Generic_Package_Declaration)
3723         and then Nkind (Lib_Unit) not in N_Generic_Renaming_Declaration
3724       then
3725          Error_Msg_N
3726            ("child of a generic package must be a generic unit", Lib_Unit);
3727
3728       elsif not Is_Package_Or_Generic_Package (P_Name) then
3729          Error_Msg_N
3730            ("parent unit must be package or generic package", Lib_Unit);
3731          raise Unrecoverable_Error;
3732
3733       elsif Present (Renamed_Object (P_Name)) then
3734          Error_Msg_N ("parent unit cannot be a renaming", Lib_Unit);
3735          raise Unrecoverable_Error;
3736
3737       --  Verify that a child of an instance is itself an instance, or the
3738       --  renaming of one. Given that an instance that is a unit is replaced
3739       --  with a package declaration, check against the original node. The
3740       --  parent may be currently being instantiated, in which case it appears
3741       --  as a declaration, but the generic_parent is already established
3742       --  indicating that we deal with an instance.
3743
3744       elsif Nkind (Original_Node (P)) = N_Package_Instantiation then
3745          if Nkind (Lib_Unit) in N_Renaming_Declaration
3746            or else Nkind (Original_Node (Lib_Unit)) in N_Generic_Instantiation
3747            or else
3748              (Nkind (Lib_Unit) = N_Package_Declaration
3749                 and then Present (Generic_Parent (Specification (Lib_Unit))))
3750          then
3751             null;
3752          else
3753             Error_Msg_N
3754               ("child of an instance must be an instance or renaming",
3755                 Lib_Unit);
3756          end if;
3757       end if;
3758
3759       --  This is the recursive call that ensures all parents are loaded
3760
3761       if Is_Child_Spec (P) then
3762          Install_Parents (P,
3763            Is_Private or else Private_Present (Parent (Lib_Unit)));
3764       end if;
3765
3766       --  Now we can install the context for this parent
3767
3768       Install_Context_Clauses (Parent_Spec (Lib_Unit));
3769       Install_Limited_Context_Clauses (Parent_Spec (Lib_Unit));
3770       Install_Siblings (P_Name, Parent (Lib_Unit));
3771
3772       --  The child unit is in the declarative region of the parent. The parent
3773       --  must therefore appear in the scope stack and be visible, as when
3774       --  compiling the corresponding body. If the child unit is private or it
3775       --  is a package body, private declarations must be accessible as well.
3776       --  Use declarations in the parent must also be installed. Finally, other
3777       --  child units of the same parent that are in the context are
3778       --  immediately visible.
3779
3780       --  Find entity for compilation unit, and set its private descendant
3781       --  status as needed.
3782
3783       E_Name := Defining_Entity (Lib_Unit);
3784
3785       Set_Is_Child_Unit (E_Name);
3786
3787       Set_Is_Private_Descendant (E_Name,
3788          Is_Private_Descendant (P_Name)
3789            or else Private_Present (Parent (Lib_Unit)));
3790
3791       P_Spec := Specification (Unit_Declaration_Node (P_Name));
3792       Push_Scope (P_Name);
3793
3794       --  Save current visibility of unit
3795
3796       Scope_Stack.Table (Scope_Stack.Last).Previous_Visibility :=
3797         Is_Immediately_Visible (P_Name);
3798       Set_Is_Immediately_Visible (P_Name);
3799       Install_Visible_Declarations (P_Name);
3800       Set_Use (Visible_Declarations (P_Spec));
3801
3802       --  If the parent is a generic unit, its formal part may contain formal
3803       --  packages and use clauses for them.
3804
3805       if Ekind (P_Name) = E_Generic_Package then
3806          Set_Use (Generic_Formal_Declarations (Parent (P_Spec)));
3807       end if;
3808
3809       if Is_Private
3810         or else Private_Present (Parent (Lib_Unit))
3811       then
3812          Install_Private_Declarations (P_Name);
3813          Install_Private_With_Clauses (P_Name);
3814          Set_Use (Private_Declarations (P_Spec));
3815       end if;
3816    end Install_Parents;
3817
3818    ----------------------------------
3819    -- Install_Private_With_Clauses --
3820    ----------------------------------
3821
3822    procedure Install_Private_With_Clauses (P : Entity_Id) is
3823       Decl   : constant Node_Id := Unit_Declaration_Node (P);
3824       Item   : Node_Id;
3825
3826    begin
3827       if Debug_Flag_I then
3828          Write_Str ("install private with clauses of ");
3829          Write_Name (Chars (P));
3830          Write_Eol;
3831       end if;
3832
3833       if Nkind (Parent (Decl)) = N_Compilation_Unit then
3834          Item := First (Context_Items (Parent (Decl)));
3835          while Present (Item) loop
3836             if Nkind (Item) = N_With_Clause
3837               and then Private_Present (Item)
3838             then
3839                if Limited_Present (Item) then
3840                   if not Limited_View_Installed (Item) then
3841                      Install_Limited_Withed_Unit (Item);
3842                   end if;
3843                else
3844                   Install_Withed_Unit (Item, Private_With_OK => True);
3845                end if;
3846             end if;
3847
3848             Next (Item);
3849          end loop;
3850       end if;
3851    end Install_Private_With_Clauses;
3852
3853    ----------------------
3854    -- Install_Siblings --
3855    ----------------------
3856
3857    procedure Install_Siblings (U_Name : Entity_Id; N : Node_Id) is
3858       Item : Node_Id;
3859       Id   : Entity_Id;
3860       Prev : Entity_Id;
3861
3862    begin
3863       --  Iterate over explicit with clauses, and check whether the scope of
3864       --  each entity is an ancestor of the current unit, in which case it is
3865       --  immediately visible.
3866
3867       Item := First (Context_Items (N));
3868       while Present (Item) loop
3869
3870          --  Do not install private_with_clauses declaration, unless
3871          --  unit is itself a private child unit, or is a body.
3872          --  Note that for a subprogram body the private_with_clause does
3873          --  not take effect until after the specification.
3874
3875          if Nkind (Item) /= N_With_Clause
3876            or else Implicit_With (Item)
3877            or else Limited_Present (Item)
3878          then
3879             null;
3880
3881          elsif not Private_Present (Item)
3882            or else Private_Present (N)
3883            or else Nkind (Unit (N)) = N_Package_Body
3884          then
3885             Id := Entity (Name (Item));
3886
3887             if Is_Child_Unit (Id)
3888               and then Is_Ancestor_Package (Scope (Id), U_Name)
3889             then
3890                Set_Is_Immediately_Visible (Id);
3891
3892                --  Check for the presence of another unit in the context,
3893                --  that may be inadvertently hidden by the child.
3894
3895                Prev := Current_Entity (Id);
3896
3897                if Present (Prev)
3898                  and then Is_Immediately_Visible (Prev)
3899                  and then not Is_Child_Unit (Prev)
3900                then
3901                   declare
3902                      Clause : Node_Id;
3903
3904                   begin
3905                      Clause := First (Context_Items (N));
3906                      while Present (Clause) loop
3907                         if Nkind (Clause) = N_With_Clause
3908                           and then Entity (Name (Clause)) = Prev
3909                         then
3910                            Error_Msg_NE
3911                               ("child unit& hides compilation unit " &
3912                                "with the same name?",
3913                                  Name (Item), Id);
3914                            exit;
3915                         end if;
3916
3917                         Next (Clause);
3918                      end loop;
3919                   end;
3920                end if;
3921
3922             --  The With_Clause may be on a grand-child or one of its further
3923             --  descendants, which makes a child immediately visible. Examine
3924             --  ancestry to determine whether such a child exists. For example,
3925             --  if current unit is A.C, and with_clause is on A.X.Y.Z, then X
3926             --  is immediately visible.
3927
3928             elsif Is_Child_Unit (Id) then
3929                declare
3930                   Par : Entity_Id;
3931
3932                begin
3933                   Par := Scope (Id);
3934                   while Is_Child_Unit (Par) loop
3935                      if Is_Ancestor_Package (Scope (Par), U_Name) then
3936                         Set_Is_Immediately_Visible (Par);
3937                         exit;
3938                      end if;
3939
3940                      Par := Scope (Par);
3941                   end loop;
3942                end;
3943             end if;
3944
3945          --  If the item is a private with-clause on a child unit, the parent
3946          --  may have been installed already, but the child unit must remain
3947          --  invisible until installed in a private part or body.
3948
3949          elsif Private_Present (Item) then
3950             Id := Entity (Name (Item));
3951
3952             if Is_Child_Unit (Id) then
3953                Set_Is_Visible_Child_Unit (Id, False);
3954             end if;
3955          end if;
3956
3957          Next (Item);
3958       end loop;
3959    end Install_Siblings;
3960
3961    ---------------------------------
3962    -- Install_Limited_Withed_Unit --
3963    ---------------------------------
3964
3965    procedure Install_Limited_Withed_Unit (N : Node_Id) is
3966       P_Unit           : constant Entity_Id := Unit (Library_Unit (N));
3967       E                : Entity_Id;
3968       P                : Entity_Id;
3969       Is_Child_Package : Boolean := False;
3970       Lim_Header       : Entity_Id;
3971       Lim_Typ          : Entity_Id;
3972
3973       procedure Check_Body_Required;
3974       --  A unit mentioned in a limited with_clause may not be mentioned in
3975       --  a regular with_clause, but must still be included in the current
3976       --  partition. We need to determine whether the unit needs a body, so
3977       --  that the binder can determine the name of the file to be compiled.
3978       --  Checking whether a unit needs a body can be done without semantic
3979       --  analysis, by examining the nature of the declarations in the package.
3980
3981       function Has_Limited_With_Clause
3982         (C_Unit : Entity_Id;
3983          Pack   : Entity_Id) return Boolean;
3984       --  Determine whether any package in the ancestor chain starting with
3985       --  C_Unit has a limited with clause for package Pack.
3986
3987       function Is_Visible_Through_Renamings (P : Entity_Id) return Boolean;
3988       --  Check if some package installed though normal with-clauses has a
3989       --  renaming declaration of package P. AARM 10.1.2(21/2).
3990
3991       -------------------------
3992       -- Check_Body_Required --
3993       -------------------------
3994
3995       procedure Check_Body_Required is
3996          PA : constant List_Id :=
3997                 Pragmas_After (Aux_Decls_Node (Parent (P_Unit)));
3998
3999          procedure Check_Declarations (Spec : Node_Id);
4000          --  Recursive procedure that does the work and checks nested packages
4001
4002          ------------------------
4003          -- Check_Declarations --
4004          ------------------------
4005
4006          procedure Check_Declarations (Spec : Node_Id) is
4007             Decl             : Node_Id;
4008             Incomplete_Decls : constant Elist_Id := New_Elmt_List;
4009
4010             Subp_List        : constant Elist_Id := New_Elmt_List;
4011
4012             procedure Check_Pragma_Import (P : Node_Id);
4013             --  If a pragma import applies to a previous subprogram, the
4014             --  enclosing unit may not need a body. The processing is syntactic
4015             --  and does not require a declaration to be analyzed. The code
4016             --  below also handles pragma Import when applied to a subprogram
4017             --  that renames another. In this case the pragma applies to the
4018             --  renamed entity.
4019             --
4020             --  Chains of multiple renames are not handled by the code below.
4021             --  It is probably impossible to handle all cases without proper
4022             --  name resolution. In such cases the algorithm is conservative
4023             --  and will indicate that a body is needed???
4024
4025             -------------------------
4026             -- Check_Pragma_Import --
4027             -------------------------
4028
4029             procedure Check_Pragma_Import (P : Node_Id) is
4030                Arg      : Node_Id;
4031                Prev_Id  : Elmt_Id;
4032                Subp_Id  : Elmt_Id;
4033                Imported : Node_Id;
4034
4035                procedure Remove_Homonyms (E : Node_Id);
4036                --  Make one pass over list of subprograms. Called again if
4037                --  subprogram is a renaming. E is known to be an identifier.
4038
4039                ---------------------
4040                -- Remove_Homonyms --
4041                ---------------------
4042
4043                procedure Remove_Homonyms (E : Node_Id) is
4044                   R : Entity_Id := Empty;
4045                   --  Name of renamed entity, if any
4046
4047                begin
4048                   Subp_Id := First_Elmt (Subp_List);
4049                   while Present (Subp_Id) loop
4050                      if Chars (Node (Subp_Id)) = Chars (E) then
4051                         if Nkind (Parent (Parent (Node (Subp_Id))))
4052                           /=  N_Subprogram_Renaming_Declaration
4053                         then
4054                            Prev_Id := Subp_Id;
4055                            Next_Elmt (Subp_Id);
4056                            Remove_Elmt (Subp_List, Prev_Id);
4057                         else
4058                            R := Name (Parent (Parent (Node (Subp_Id))));
4059                            exit;
4060                         end if;
4061                      else
4062                         Next_Elmt (Subp_Id);
4063                      end if;
4064                   end loop;
4065
4066                   if Present (R) then
4067                      if Nkind (R) = N_Identifier then
4068                         Remove_Homonyms (R);
4069
4070                      elsif Nkind (R) = N_Selected_Component then
4071                         Remove_Homonyms (Selector_Name (R));
4072
4073                      --  Renaming of attribute
4074
4075                      else
4076                         null;
4077                      end if;
4078                   end if;
4079                end Remove_Homonyms;
4080
4081             --  Start of processing for Check_Pragma_Import
4082
4083             begin
4084                --  Find name of entity in Import pragma. We have not analyzed
4085                --  the construct, so we must guard against syntax errors.
4086
4087                Arg := Next (First (Pragma_Argument_Associations (P)));
4088
4089                if No (Arg)
4090                  or else Nkind (Expression (Arg)) /= N_Identifier
4091                then
4092                   return;
4093                else
4094                   Imported := Expression (Arg);
4095                end if;
4096
4097                Remove_Homonyms (Imported);
4098             end Check_Pragma_Import;
4099
4100          --  Start of processing for Check_Declarations
4101
4102          begin
4103             --  Search for Elaborate Body pragma
4104
4105             Decl := First (Visible_Declarations (Spec));
4106             while Present (Decl)
4107               and then Nkind (Decl) = N_Pragma
4108             loop
4109                if Get_Pragma_Id (Decl) = Pragma_Elaborate_Body then
4110                   Set_Body_Required (Library_Unit (N));
4111                   return;
4112                end if;
4113
4114                Next (Decl);
4115             end loop;
4116
4117             --  Look for declarations that require the presence of a body
4118
4119             while Present (Decl) loop
4120
4121                --  Subprogram that comes from source means body may be needed.
4122                --  Save for subsequent examination of import pragmas.
4123
4124                if Comes_From_Source (Decl)
4125                  and then (Nkind_In (Decl, N_Subprogram_Declaration,
4126                                            N_Subprogram_Renaming_Declaration,
4127                                            N_Generic_Subprogram_Declaration))
4128                then
4129                   Append_Elmt (Defining_Entity (Decl), Subp_List);
4130
4131                --  Package declaration of generic package declaration. We need
4132                --  to recursively examine nested declarations.
4133
4134                elsif Nkind_In (Decl, N_Package_Declaration,
4135                                      N_Generic_Package_Declaration)
4136                then
4137                   Check_Declarations (Specification (Decl));
4138
4139                elsif Nkind (Decl) = N_Pragma
4140                  and then Pragma_Name (Decl) = Name_Import
4141                then
4142                   Check_Pragma_Import (Decl);
4143                end if;
4144
4145                Next (Decl);
4146             end loop;
4147
4148             --  Same set of tests for private part. In addition to subprograms
4149             --  detect the presence of Taft Amendment types (incomplete types
4150             --  completed in the body).
4151
4152             Decl := First (Private_Declarations (Spec));
4153             while Present (Decl) loop
4154                if Comes_From_Source (Decl)
4155                  and then (Nkind_In (Decl, N_Subprogram_Declaration,
4156                                            N_Subprogram_Renaming_Declaration,
4157                                            N_Generic_Subprogram_Declaration))
4158                then
4159                   Append_Elmt (Defining_Entity (Decl), Subp_List);
4160
4161                elsif Nkind_In (Decl, N_Package_Declaration,
4162                                      N_Generic_Package_Declaration)
4163                then
4164                   Check_Declarations (Specification (Decl));
4165
4166                --  Collect incomplete type declarations for separate pass
4167
4168                elsif Nkind (Decl) = N_Incomplete_Type_Declaration then
4169                   Append_Elmt (Decl, Incomplete_Decls);
4170
4171                elsif Nkind (Decl) = N_Pragma
4172                  and then Pragma_Name (Decl) = Name_Import
4173                then
4174                   Check_Pragma_Import (Decl);
4175                end if;
4176
4177                Next (Decl);
4178             end loop;
4179
4180             --  Now check incomplete declarations to locate Taft amendment
4181             --  types. This can be done by examining the defining identifiers
4182             --  of  type declarations without real semantic analysis.
4183
4184             declare
4185                Inc : Elmt_Id;
4186
4187             begin
4188                Inc := First_Elmt (Incomplete_Decls);
4189                while Present (Inc) loop
4190                   Decl := Next (Node (Inc));
4191                   while Present (Decl) loop
4192                      if Nkind (Decl) = N_Full_Type_Declaration
4193                        and then Chars (Defining_Identifier (Decl)) =
4194                                 Chars (Defining_Identifier (Node (Inc)))
4195                      then
4196                         exit;
4197                      end if;
4198
4199                      Next (Decl);
4200                   end loop;
4201
4202                   --  If no completion, this is a TAT, and a body is needed
4203
4204                   if No (Decl) then
4205                      Set_Body_Required (Library_Unit (N));
4206                      return;
4207                   end if;
4208
4209                   Next_Elmt (Inc);
4210                end loop;
4211             end;
4212
4213             --  Finally, check whether there are subprograms that still
4214             --  require a body, i.e. are not renamings or null.
4215
4216             if not Is_Empty_Elmt_List (Subp_List) then
4217                declare
4218                   Subp_Id : Elmt_Id;
4219                   Spec    : Node_Id;
4220
4221                begin
4222                   Subp_Id := First_Elmt (Subp_List);
4223                   Spec    := Parent (Node (Subp_Id));
4224
4225                   while Present (Subp_Id) loop
4226                      if Nkind (Parent (Spec))
4227                         = N_Subprogram_Renaming_Declaration
4228                      then
4229                         null;
4230
4231                      elsif Nkind (Spec) = N_Procedure_Specification
4232                        and then Null_Present (Spec)
4233                      then
4234                         null;
4235
4236                      else
4237                         Set_Body_Required (Library_Unit (N));
4238                         return;
4239                      end if;
4240
4241                      Next_Elmt (Subp_Id);
4242                   end loop;
4243                end;
4244             end if;
4245          end Check_Declarations;
4246
4247       --  Start of processing for Check_Body_Required
4248
4249       begin
4250          --  If this is an imported package (Java and CIL usage) no body is
4251          --  needed. Scan list of pragmas that may follow a compilation unit
4252          --  to look for a relevant pragma Import.
4253
4254          if Present (PA) then
4255             declare
4256                Prag : Node_Id;
4257
4258             begin
4259                Prag := First (PA);
4260                while Present (Prag) loop
4261                   if Nkind (Prag) = N_Pragma
4262                     and then Get_Pragma_Id (Prag) = Pragma_Import
4263                   then
4264                      return;
4265                   end if;
4266
4267                   Next (Prag);
4268                end loop;
4269             end;
4270          end if;
4271
4272          Check_Declarations (Specification (P_Unit));
4273       end Check_Body_Required;
4274
4275       -----------------------------
4276       -- Has_Limited_With_Clause --
4277       -----------------------------
4278
4279       function Has_Limited_With_Clause
4280         (C_Unit : Entity_Id;
4281          Pack   : Entity_Id) return Boolean
4282       is
4283          Par      : Entity_Id;
4284          Par_Unit : Node_Id;
4285
4286       begin
4287          Par := C_Unit;
4288          while Present (Par) loop
4289             if Ekind (Par) /= E_Package then
4290                exit;
4291             end if;
4292
4293             --  Retrieve the Compilation_Unit node for Par and determine if
4294             --  its context clauses contain a limited with for Pack.
4295
4296             Par_Unit := Parent (Parent (Parent (Par)));
4297
4298             if Nkind (Par_Unit) = N_Package_Declaration then
4299                Par_Unit := Parent (Par_Unit);
4300             end if;
4301
4302             if Has_With_Clause (Par_Unit, Pack, True) then
4303                return True;
4304             end if;
4305
4306             --  If there are more ancestors, climb up the tree, otherwise
4307             --  we are done.
4308
4309             if Is_Child_Unit (Par) then
4310                Par := Scope (Par);
4311             else
4312                exit;
4313             end if;
4314          end loop;
4315
4316          return False;
4317       end Has_Limited_With_Clause;
4318
4319       ----------------------------------
4320       -- Is_Visible_Through_Renamings --
4321       ----------------------------------
4322
4323       function Is_Visible_Through_Renamings (P : Entity_Id) return Boolean is
4324          Kind     : constant Node_Kind :=
4325                       Nkind (Unit (Cunit (Current_Sem_Unit)));
4326          Aux_Unit : Node_Id;
4327          Item     : Node_Id;
4328          Decl     : Entity_Id;
4329
4330       begin
4331          --  Example of the error detected by this subprogram:
4332
4333          --  package P is
4334          --    type T is ...
4335          --  end P;
4336
4337          --  with P;
4338          --  package Q is
4339          --     package Ren_P renames P;
4340          --  end Q;
4341
4342          --  with Q;
4343          --  package R is ...
4344
4345          --  limited with P; -- ERROR
4346          --  package R.C is ...
4347
4348          Aux_Unit := Cunit (Current_Sem_Unit);
4349
4350          loop
4351             Item := First (Context_Items (Aux_Unit));
4352             while Present (Item) loop
4353                if Nkind (Item) = N_With_Clause
4354                  and then not Limited_Present (Item)
4355                  and then Nkind (Unit (Library_Unit (Item))) =
4356                                                   N_Package_Declaration
4357                then
4358                   Decl :=
4359                     First (Visible_Declarations
4360                             (Specification (Unit (Library_Unit (Item)))));
4361                   while Present (Decl) loop
4362                      if Nkind (Decl) = N_Package_Renaming_Declaration
4363                        and then Entity (Name (Decl)) = P
4364                      then
4365                         --  Generate the error message only if the current unit
4366                         --  is a package declaration; in case of subprogram
4367                         --  bodies and package bodies we just return True to
4368                         --  indicate that the limited view must not be
4369                         --  installed.
4370
4371                         if Kind = N_Package_Declaration then
4372                            Error_Msg_N
4373                              ("simultaneous visibility of the limited and " &
4374                               "unlimited views not allowed", N);
4375                            Error_Msg_Sloc := Sloc (Item);
4376                            Error_Msg_NE
4377                              ("\\  unlimited view of & visible through the " &
4378                               "context clause #", N, P);
4379                            Error_Msg_Sloc := Sloc (Decl);
4380                            Error_Msg_NE ("\\  and the renaming #", N, P);
4381                         end if;
4382
4383                         return True;
4384                      end if;
4385
4386                      Next (Decl);
4387                   end loop;
4388                end if;
4389
4390                Next (Item);
4391             end loop;
4392
4393             --  If it's a body not acting as spec, follow pointer to
4394             --  corresponding spec, otherwise follow pointer to parent spec.
4395
4396             if Present (Library_Unit (Aux_Unit))
4397               and then Nkind_In (Unit (Aux_Unit),
4398                                  N_Package_Body, N_Subprogram_Body)
4399             then
4400                if Aux_Unit = Library_Unit (Aux_Unit) then
4401
4402                   --  Aux_Unit is a body that acts as a spec. Clause has
4403                   --  already been flagged as illegal.
4404
4405                   return False;
4406
4407                else
4408                   Aux_Unit := Library_Unit (Aux_Unit);
4409                end if;
4410
4411             else
4412                Aux_Unit := Parent_Spec (Unit (Aux_Unit));
4413             end if;
4414
4415             exit when No (Aux_Unit);
4416          end loop;
4417
4418          return False;
4419       end Is_Visible_Through_Renamings;
4420
4421    --  Start of processing for Install_Limited_Withed_Unit
4422
4423    begin
4424       pragma Assert (not Limited_View_Installed (N));
4425
4426       --  In case of limited with_clause on subprograms, generics, instances,
4427       --  or renamings, the corresponding error was previously posted and we
4428       --  have nothing to do here. If the file is missing altogether, it has
4429       --  no source location.
4430
4431       if Nkind (P_Unit) /= N_Package_Declaration
4432         or else Sloc (P_Unit) = No_Location
4433       then
4434          return;
4435       end if;
4436
4437       P := Defining_Unit_Name (Specification (P_Unit));
4438
4439       --  Handle child packages
4440
4441       if Nkind (P) = N_Defining_Program_Unit_Name then
4442          Is_Child_Package := True;
4443          P := Defining_Identifier (P);
4444       end if;
4445
4446       --  Do not install the limited-view if the context of the unit is already
4447       --  available through a regular with clause.
4448
4449       if Nkind (Unit (Cunit (Current_Sem_Unit))) = N_Package_Body
4450         and then Has_With_Clause (Cunit (Current_Sem_Unit), P)
4451       then
4452          return;
4453       end if;
4454
4455       --  Do not install the limited-view if the full-view is already visible
4456       --  through renaming declarations.
4457
4458       if Is_Visible_Through_Renamings (P) then
4459          return;
4460       end if;
4461
4462       --  Do not install the limited view if this is the unit being analyzed.
4463       --  This unusual case will happen when a unit has a limited_with clause
4464       --  on one of its children. The compilation of the child forces the
4465       --  load of the parent which tries to install the limited view of the
4466       --  child again. Installing the limited view must also be disabled
4467       --  when compiling the body of the child unit.
4468
4469       if P = Cunit_Entity (Current_Sem_Unit)
4470         or else
4471          (Nkind (Unit (Cunit (Current_Sem_Unit))) = N_Package_Body
4472             and then P = Main_Unit_Entity)
4473       then
4474          return;
4475       end if;
4476
4477       --  This scenario is similar to the one above, the difference is that
4478       --  the compilation of sibling Par.Sib forces the load of parent Par
4479       --  which tries to install the limited view of Lim_Pack [1]. However
4480       --  Par.Sib has a with clause for Lim_Pack [2] in its body, and thus
4481       --  needs the non-limited views of all entities from Lim_Pack.
4482
4483       --     limited with Lim_Pack;   --  [1]
4484       --     package Par is ...           package Lim_Pack is ...
4485
4486       --                                  with Lim_Pack;  --  [2]
4487       --     package Par.Sib is ...       package body Par.Sib is ...
4488
4489       --  In this case Main_Unit_Entity is the spec of Par.Sib and Current_
4490       --  Sem_Unit is the body of Par.Sib.
4491
4492       if Ekind (P) = E_Package
4493         and then Ekind (Main_Unit_Entity) = E_Package
4494         and then Is_Child_Unit (Main_Unit_Entity)
4495
4496          --  The body has a regular with clause
4497
4498         and then Nkind (Unit (Cunit (Current_Sem_Unit))) = N_Package_Body
4499         and then Has_With_Clause (Cunit (Current_Sem_Unit), P)
4500
4501          --  One of the ancestors has a limited with clause
4502
4503         and then Nkind (Parent (Parent (Main_Unit_Entity))) =
4504                    N_Package_Specification
4505         and then Has_Limited_With_Clause (Scope (Main_Unit_Entity), P)
4506       then
4507          return;
4508       end if;
4509
4510       --  A common use of the limited-with is to have a limited-with
4511       --  in the package spec, and a normal with in its package body.
4512       --  For example:
4513
4514       --       limited with X;  -- [1]
4515       --       package A is ...
4516
4517       --       with X;          -- [2]
4518       --       package body A is ...
4519
4520       --  The compilation of A's body installs the context clauses found at [2]
4521       --  and then the context clauses of its specification (found at [1]). As
4522       --  a consequence, at [1] the specification of X has been analyzed and it
4523       --  is immediately visible. According to the semantics of limited-with
4524       --  context clauses we don't install the limited view because the full
4525       --  view of X supersedes its limited view.
4526
4527       if Analyzed (P_Unit)
4528         and then
4529           (Is_Immediately_Visible (P)
4530             or else
4531               (Is_Child_Package and then Is_Visible_Child_Unit (P)))
4532       then
4533          return;
4534       end if;
4535
4536       if Debug_Flag_I then
4537          Write_Str ("install limited view of ");
4538          Write_Name (Chars (P));
4539          Write_Eol;
4540       end if;
4541
4542       --  If the unit has not been analyzed and the limited view has not been
4543       --  already installed then we install it.
4544
4545       if not Analyzed (P_Unit) then
4546          if not In_Chain (P) then
4547
4548             --  Minimum decoration
4549
4550             Set_Ekind (P, E_Package);
4551             Set_Etype (P, Standard_Void_Type);
4552             Set_Scope (P, Standard_Standard);
4553
4554             if Is_Child_Package then
4555                Set_Is_Child_Unit (P);
4556                Set_Is_Visible_Child_Unit (P);
4557                Set_Scope (P, Defining_Entity (Unit (Parent_Spec (P_Unit))));
4558             end if;
4559
4560             --  Place entity on visibility structure
4561
4562             Set_Homonym (P, Current_Entity (P));
4563             Set_Current_Entity (P);
4564
4565             if Debug_Flag_I then
4566                Write_Str ("   (homonym) chain ");
4567                Write_Name (Chars (P));
4568                Write_Eol;
4569             end if;
4570
4571             --  Install the incomplete view. The first element of the limited
4572             --  view is a header (an E_Package entity) used to reference the
4573             --  first shadow entity in the private part of the package.
4574
4575             Lim_Header := Limited_View (P);
4576             Lim_Typ    := First_Entity (Lim_Header);
4577
4578             while Present (Lim_Typ)
4579               and then Lim_Typ /= First_Private_Entity (Lim_Header)
4580             loop
4581                Set_Homonym (Lim_Typ, Current_Entity (Lim_Typ));
4582                Set_Current_Entity (Lim_Typ);
4583
4584                if Debug_Flag_I then
4585                   Write_Str ("   (homonym) chain ");
4586                   Write_Name (Chars (Lim_Typ));
4587                   Write_Eol;
4588                end if;
4589
4590                Next_Entity (Lim_Typ);
4591             end loop;
4592          end if;
4593
4594       --  If the unit appears in a previous regular with_clause, the regular
4595       --  entities of the public part of the withed package must be replaced
4596       --  by the shadow ones.
4597
4598       --  This code must be kept synchronized with the code that replaces the
4599       --  shadow entities by the real entities (see body of Remove_Limited
4600       --  With_Clause); otherwise the contents of the homonym chains are not
4601       --  consistent.
4602
4603       else
4604          --  Hide all the type entities of the public part of the package to
4605          --  avoid its usage. This is needed to cover all the subtype decla-
4606          --  rations because we do not remove them from the homonym chain.
4607
4608          E := First_Entity (P);
4609          while Present (E) and then E /= First_Private_Entity (P) loop
4610             if Is_Type (E) then
4611                Set_Was_Hidden (E, Is_Hidden (E));
4612                Set_Is_Hidden (E);
4613             end if;
4614
4615             Next_Entity (E);
4616          end loop;
4617
4618          --  Replace the real entities by the shadow entities of the limited
4619          --  view. The first element of the limited view is a header that is
4620          --  used to reference the first shadow entity in the private part
4621          --  of the package. Successive elements are the limited views of the
4622          --  type (including regular incomplete types) declared in the package.
4623
4624          Lim_Header := Limited_View (P);
4625
4626          Lim_Typ := First_Entity (Lim_Header);
4627          while Present (Lim_Typ)
4628            and then Lim_Typ /= First_Private_Entity (Lim_Header)
4629          loop
4630             pragma Assert (not In_Chain (Lim_Typ));
4631
4632             --  Do not unchain nested packages and child units
4633
4634             if Ekind (Lim_Typ) /= E_Package
4635               and then not Is_Child_Unit (Lim_Typ)
4636             then
4637                declare
4638                   Prev : Entity_Id;
4639
4640                begin
4641                   Prev := Current_Entity (Lim_Typ);
4642                   E := Prev;
4643
4644                   --  Replace E in the homonyms list, so that the limited
4645                   --  view becomes available.
4646
4647                   if E = Non_Limited_View (Lim_Typ) then
4648                      Set_Homonym (Lim_Typ, Homonym (Prev));
4649                      Set_Current_Entity (Lim_Typ);
4650
4651                   else
4652                      loop
4653                         E := Homonym (Prev);
4654
4655                         --  E may have been removed when installing a
4656                         --  previous limited_with_clause.
4657
4658                         exit when No (E);
4659
4660                         exit when E = Non_Limited_View (Lim_Typ);
4661
4662                         Prev := Homonym (Prev);
4663                      end loop;
4664
4665                      if Present (E) then
4666                         Set_Homonym (Lim_Typ, Homonym (Homonym (Prev)));
4667                         Set_Homonym (Prev, Lim_Typ);
4668                      end if;
4669                   end if;
4670                end;
4671
4672                if Debug_Flag_I then
4673                   Write_Str ("   (homonym) chain ");
4674                   Write_Name (Chars (Lim_Typ));
4675                   Write_Eol;
4676                end if;
4677             end if;
4678
4679             Next_Entity (Lim_Typ);
4680          end loop;
4681       end if;
4682
4683       --  The package must be visible while the limited-with clause is active
4684       --  because references to the type P.T must resolve in the usual way.
4685       --  In addition, we remember that the limited-view has been installed to
4686       --  uninstall it at the point of context removal.
4687
4688       Set_Is_Immediately_Visible (P);
4689       Set_Limited_View_Installed (N);
4690
4691       --  If unit has not been analyzed in some previous context, check
4692       --  (imperfectly ???) whether it might need a body.
4693
4694       if not Analyzed (P_Unit) then
4695          Check_Body_Required;
4696       end if;
4697
4698       --  If the package in the limited_with clause is a child unit, the
4699       --  clause is unanalyzed and appears as a selected component. Recast
4700       --  it as an expanded name so that the entity can be properly set. Use
4701       --  entity of parent, if available, for higher ancestors in the name.
4702
4703       if Nkind (Name (N)) = N_Selected_Component then
4704          declare
4705             Nam : Node_Id;
4706             Ent : Entity_Id;
4707
4708          begin
4709             Nam := Name (N);
4710             Ent := P;
4711             while Nkind (Nam) = N_Selected_Component
4712               and then Present (Ent)
4713             loop
4714                Change_Selected_Component_To_Expanded_Name (Nam);
4715
4716                --  Set entity of parent identifiers if the unit is a child
4717                --  unit. This ensures that the tree is properly formed from
4718                --  semantic point of view (e.g. for ASIS queries).
4719
4720                Set_Entity (Nam, Ent);
4721
4722                Nam := Prefix (Nam);
4723                Ent := Scope (Ent);
4724
4725                --  Set entity of last ancestor
4726
4727                if Nkind (Nam) = N_Identifier then
4728                   Set_Entity (Nam, Ent);
4729                end if;
4730             end loop;
4731          end;
4732       end if;
4733
4734       Set_Entity (Name (N), P);
4735       Set_From_With_Type (P);
4736    end Install_Limited_Withed_Unit;
4737
4738    -------------------------
4739    -- Install_Withed_Unit --
4740    -------------------------
4741
4742    procedure Install_Withed_Unit
4743      (With_Clause     : Node_Id;
4744       Private_With_OK : Boolean := False)
4745    is
4746       Uname : constant Entity_Id := Entity (Name (With_Clause));
4747       P     : constant Entity_Id := Scope (Uname);
4748
4749    begin
4750       --  Ada 2005 (AI-262): Do not install the private withed unit if we are
4751       --  compiling a package declaration and the Private_With_OK flag was not
4752       --  set by the caller. These declarations will be installed later (before
4753       --  analyzing the private part of the package).
4754
4755       if Private_Present (With_Clause)
4756         and then Nkind (Unit (Parent (With_Clause))) = N_Package_Declaration
4757         and then not (Private_With_OK)
4758       then
4759          return;
4760       end if;
4761
4762       if Debug_Flag_I then
4763          if Private_Present (With_Clause) then
4764             Write_Str ("install private withed unit ");
4765          else
4766             Write_Str ("install withed unit ");
4767          end if;
4768
4769          Write_Name (Chars (Uname));
4770          Write_Eol;
4771       end if;
4772
4773       --  We do not apply the restrictions to an internal unit unless
4774       --  we are compiling the internal unit as a main unit. This check
4775       --  is also skipped for dummy units (for missing packages).
4776
4777       if Sloc (Uname) /= No_Location
4778         and then (not Is_Internal_File_Name (Unit_File_Name (Current_Sem_Unit))
4779                     or else Current_Sem_Unit = Main_Unit)
4780       then
4781          Check_Restricted_Unit
4782            (Unit_Name (Get_Source_Unit (Uname)), With_Clause);
4783       end if;
4784
4785       if P /= Standard_Standard then
4786
4787          --  If the unit is not analyzed after analysis of the with clause and
4788          --  it is an instantiation then it awaits a body and is the main unit.
4789          --  Its appearance in the context of some other unit indicates a
4790          --  circular dependency (DEC suite perversity).
4791
4792          if not Analyzed (Uname)
4793            and then Nkind (Parent (Uname)) = N_Package_Instantiation
4794          then
4795             Error_Msg_N
4796               ("instantiation depends on itself", Name (With_Clause));
4797
4798          elsif not Is_Visible_Child_Unit (Uname) then
4799             Set_Is_Visible_Child_Unit (Uname);
4800
4801             --  If the child unit appears in the context of its parent, it is
4802             --  immediately visible.
4803
4804             if In_Open_Scopes (Scope (Uname)) then
4805                Set_Is_Immediately_Visible (Uname);
4806             end if;
4807
4808             if Is_Generic_Instance (Uname)
4809               and then Ekind (Uname) in Subprogram_Kind
4810             then
4811                --  Set flag as well on the visible entity that denotes the
4812                --  instance, which renames the current one.
4813
4814                Set_Is_Visible_Child_Unit
4815                  (Related_Instance
4816                    (Defining_Entity (Unit (Library_Unit (With_Clause)))));
4817             end if;
4818
4819             --  The parent unit may have been installed already, and may have
4820             --  appeared in a use clause.
4821
4822             if In_Use (Scope (Uname)) then
4823                Set_Is_Potentially_Use_Visible (Uname);
4824             end if;
4825
4826             Set_Context_Installed (With_Clause);
4827          end if;
4828
4829       elsif not Is_Immediately_Visible (Uname) then
4830          if not Private_Present (With_Clause)
4831            or else Private_With_OK
4832          then
4833             Set_Is_Immediately_Visible (Uname);
4834          end if;
4835
4836          Set_Context_Installed (With_Clause);
4837       end if;
4838
4839       --   A with-clause overrides a with-type clause: there are no restric-
4840       --   tions on the use of package entities.
4841
4842       if Ekind (Uname) = E_Package then
4843          Set_From_With_Type (Uname, False);
4844       end if;
4845
4846       --  Ada 2005 (AI-377): it is illegal for a with_clause to name a child
4847       --  unit if there is a visible homograph for it declared in the same
4848       --  declarative region. This pathological case can only arise when an
4849       --  instance I1 of a generic unit G1 has an explicit child unit I1.G2,
4850       --  G1 has a generic child also named G2, and the context includes with_
4851       --  clauses for both I1.G2 and for G1.G2, making an implicit declaration
4852       --  of I1.G2 visible as well. If the child unit is named Standard, do
4853       --  not apply the check to the Standard package itself.
4854
4855       if Is_Child_Unit (Uname)
4856         and then Is_Visible_Child_Unit (Uname)
4857         and then Ada_Version >= Ada_05
4858       then
4859          declare
4860             Decl1 : constant Node_Id  := Unit_Declaration_Node (P);
4861             Decl2 : Node_Id;
4862             P2    : Entity_Id;
4863             U2    : Entity_Id;
4864
4865          begin
4866             U2 := Homonym (Uname);
4867             while Present (U2)
4868               and then U2 /= Standard_Standard
4869            loop
4870                P2 := Scope (U2);
4871                Decl2  := Unit_Declaration_Node (P2);
4872
4873                if Is_Child_Unit (U2)
4874                  and then Is_Visible_Child_Unit (U2)
4875                then
4876                   if Is_Generic_Instance (P)
4877                     and then Nkind (Decl1) = N_Package_Declaration
4878                     and then Generic_Parent (Specification (Decl1)) = P2
4879                   then
4880                      Error_Msg_N ("illegal with_clause", With_Clause);
4881                      Error_Msg_N
4882                        ("\child unit has visible homograph" &
4883                            " (RM 8.3(26), 10.1.1(19))",
4884                          With_Clause);
4885                      exit;
4886
4887                   elsif Is_Generic_Instance (P2)
4888                     and then Nkind (Decl2) = N_Package_Declaration
4889                     and then Generic_Parent (Specification (Decl2)) = P
4890                   then
4891                      --  With_clause for child unit of instance appears before
4892                      --  in the context. We want to place the error message on
4893                      --  it, not on the generic child unit itself.
4894
4895                      declare
4896                         Prev_Clause : Node_Id;
4897
4898                      begin
4899                         Prev_Clause := First (List_Containing (With_Clause));
4900                         while Entity (Name (Prev_Clause)) /= U2 loop
4901                            Next (Prev_Clause);
4902                         end loop;
4903
4904                         pragma Assert (Present (Prev_Clause));
4905                         Error_Msg_N ("illegal with_clause", Prev_Clause);
4906                         Error_Msg_N
4907                           ("\child unit has visible homograph" &
4908                               " (RM 8.3(26), 10.1.1(19))",
4909                             Prev_Clause);
4910                         exit;
4911                      end;
4912                   end if;
4913                end if;
4914
4915                U2 := Homonym (U2);
4916             end loop;
4917          end;
4918       end if;
4919    end Install_Withed_Unit;
4920
4921    -------------------
4922    -- Is_Child_Spec --
4923    -------------------
4924
4925    function Is_Child_Spec (Lib_Unit : Node_Id) return Boolean is
4926       K : constant Node_Kind := Nkind (Lib_Unit);
4927
4928    begin
4929       return (K in N_Generic_Declaration              or else
4930               K in N_Generic_Instantiation            or else
4931               K in N_Generic_Renaming_Declaration     or else
4932               K =  N_Package_Declaration              or else
4933               K =  N_Package_Renaming_Declaration     or else
4934               K =  N_Subprogram_Declaration           or else
4935               K =  N_Subprogram_Renaming_Declaration)
4936         and then Present (Parent_Spec (Lib_Unit));
4937    end Is_Child_Spec;
4938
4939    ------------------------------------
4940    -- Is_Legal_Shadow_Entity_In_Body --
4941    ------------------------------------
4942
4943    function Is_Legal_Shadow_Entity_In_Body (T : Entity_Id) return Boolean is
4944       C_Unit : constant Node_Id := Cunit (Current_Sem_Unit);
4945    begin
4946       return Nkind (Unit (C_Unit)) = N_Package_Body
4947         and then Has_With_Clause (C_Unit,
4948                    Cunit_Entity (Get_Source_Unit (Non_Limited_View (T))));
4949    end Is_Legal_Shadow_Entity_In_Body;
4950
4951    -----------------------
4952    -- Load_Needed_Body --
4953    -----------------------
4954
4955    --  N is a generic unit named in a with clause, or else it is a unit that
4956    --  contains a generic unit or an inlined function. In order to perform an
4957    --  instantiation, the body of the unit must be present. If the unit itself
4958    --  is generic, we assume that an instantiation follows, and load & analyze
4959    --  the body unconditionally. This forces analysis of the spec as well.
4960
4961    --  If the unit is not generic, but contains a generic unit, it is loaded on
4962    --  demand, at the point of instantiation (see ch12).
4963
4964    procedure Load_Needed_Body (N : Node_Id; OK : out Boolean) is
4965       Body_Name : Unit_Name_Type;
4966       Unum      : Unit_Number_Type;
4967
4968       Save_Style_Check : constant Boolean := Opt.Style_Check;
4969       --  The loading and analysis is done with style checks off
4970
4971    begin
4972       if not GNAT_Mode then
4973          Style_Check := False;
4974       end if;
4975
4976       Body_Name := Get_Body_Name (Get_Unit_Name (Unit (N)));
4977       Unum :=
4978         Load_Unit
4979           (Load_Name  => Body_Name,
4980            Required   => False,
4981            Subunit    => False,
4982            Error_Node => N,
4983            Renamings  => True);
4984
4985       if Unum = No_Unit then
4986          OK := False;
4987
4988       else
4989          Compiler_State := Analyzing; -- reset after load
4990
4991          if not Fatal_Error (Unum) or else Try_Semantics then
4992             if Debug_Flag_L then
4993                Write_Str ("*** Loaded generic body");
4994                Write_Eol;
4995             end if;
4996
4997             Semantics (Cunit (Unum));
4998          end if;
4999
5000          OK := True;
5001       end if;
5002
5003       Style_Check := Save_Style_Check;
5004    end Load_Needed_Body;
5005
5006    -------------------------
5007    -- Build_Limited_Views --
5008    -------------------------
5009
5010    procedure Build_Limited_Views (N : Node_Id) is
5011       Unum : constant Unit_Number_Type := Get_Source_Unit (Library_Unit (N));
5012       P    : constant Entity_Id        := Cunit_Entity (Unum);
5013
5014       Spec     : Node_Id;            --  To denote a package specification
5015       Lim_Typ  : Entity_Id;          --  To denote shadow entities
5016       Comp_Typ : Entity_Id;          --  To denote real entities
5017
5018       Lim_Header     : Entity_Id;          --  Package entity
5019       Last_Lim_E     : Entity_Id := Empty; --  Last limited entity built
5020       Last_Pub_Lim_E : Entity_Id;          --  To set the first private entity
5021
5022       procedure Decorate_Incomplete_Type
5023         (E    : Entity_Id;
5024          Scop : Entity_Id);
5025       --  Add attributes of an incomplete type to a shadow entity. The same
5026       --  attributes are placed on the real entity, so that gigi receives
5027       --  a consistent view.
5028
5029       procedure Decorate_Package_Specification (P : Entity_Id);
5030       --  Add attributes of a package entity to the entity in a package
5031       --  declaration
5032
5033       procedure Decorate_Tagged_Type
5034         (Loc  : Source_Ptr;
5035          T    : Entity_Id;
5036          Scop : Entity_Id);
5037       --  Set basic attributes of tagged type T, including its class_wide type.
5038       --  The parameters Loc, Scope are used to decorate the class_wide type.
5039
5040       procedure Build_Chain
5041         (Scope      : Entity_Id;
5042          First_Decl : Node_Id);
5043       --  Construct list of shadow entities and attach it to entity of
5044       --  package that is mentioned in a limited_with clause.
5045
5046       function New_Internal_Shadow_Entity
5047         (Kind       : Entity_Kind;
5048          Sloc_Value : Source_Ptr;
5049          Id_Char    : Character) return Entity_Id;
5050       --  Build a new internal entity and append it to the list of shadow
5051       --  entities available through the limited-header
5052
5053       ------------------------------
5054       -- Decorate_Incomplete_Type --
5055       ------------------------------
5056
5057       procedure Decorate_Incomplete_Type
5058         (E    : Entity_Id;
5059          Scop : Entity_Id)
5060       is
5061       begin
5062          Set_Ekind             (E, E_Incomplete_Type);
5063          Set_Scope             (E, Scop);
5064          Set_Etype             (E, E);
5065          Set_Is_First_Subtype  (E, True);
5066          Set_Stored_Constraint (E, No_Elist);
5067          Set_Full_View         (E, Empty);
5068          Init_Size_Align       (E);
5069       end Decorate_Incomplete_Type;
5070
5071       --------------------------
5072       -- Decorate_Tagged_Type --
5073       --------------------------
5074
5075       procedure Decorate_Tagged_Type
5076         (Loc  : Source_Ptr;
5077          T    : Entity_Id;
5078          Scop : Entity_Id)
5079       is
5080          CW : Entity_Id;
5081
5082       begin
5083          Decorate_Incomplete_Type (T, Scop);
5084          Set_Is_Tagged_Type (T);
5085
5086          --  Build corresponding class_wide type, if not previously done
5087
5088          --  Note: The class-wide entity is shared by the limited-view
5089          --  and the full-view.
5090
5091          if No (Class_Wide_Type (T)) then
5092             CW := Make_Defining_Identifier (Loc,  New_Internal_Name ('S'));
5093
5094             --  Set parent to be the same as the parent of the tagged type.
5095             --  We need a parent field set, and it is supposed to point to
5096             --  the declaration of the type. The tagged type declaration
5097             --  essentially declares two separate types, the tagged type
5098             --  itself and the corresponding class-wide type, so it is
5099             --  reasonable for the parent fields to point to the declaration
5100             --  in both cases.
5101
5102             Set_Parent (CW, Parent (T));
5103
5104             --  Set remaining fields of classwide type
5105
5106             Set_Ekind                     (CW, E_Class_Wide_Type);
5107             Set_Etype                     (CW, T);
5108             Set_Scope                     (CW, Scop);
5109             Set_Is_Tagged_Type            (CW);
5110             Set_Is_First_Subtype          (CW, True);
5111             Init_Size_Align               (CW);
5112             Set_Has_Unknown_Discriminants (CW, True);
5113             Set_Class_Wide_Type           (CW, CW);
5114             Set_Equivalent_Type           (CW, Empty);
5115             Set_From_With_Type            (CW, From_With_Type (T));
5116
5117             --  Link type to its class-wide type
5118
5119             Set_Class_Wide_Type           (T, CW);
5120          end if;
5121       end Decorate_Tagged_Type;
5122
5123       ------------------------------------
5124       -- Decorate_Package_Specification --
5125       ------------------------------------
5126
5127       procedure Decorate_Package_Specification (P : Entity_Id) is
5128       begin
5129          --  Place only the most basic attributes
5130
5131          Set_Ekind (P, E_Package);
5132          Set_Etype (P, Standard_Void_Type);
5133       end Decorate_Package_Specification;
5134
5135       --------------------------------
5136       -- New_Internal_Shadow_Entity --
5137       --------------------------------
5138
5139       function New_Internal_Shadow_Entity
5140         (Kind       : Entity_Kind;
5141          Sloc_Value : Source_Ptr;
5142          Id_Char    : Character) return Entity_Id
5143       is
5144          E : constant Entity_Id :=
5145                Make_Defining_Identifier (Sloc_Value,
5146                  Chars => New_Internal_Name (Id_Char));
5147
5148       begin
5149          Set_Ekind       (E, Kind);
5150          Set_Is_Internal (E, True);
5151
5152          if Kind in Type_Kind then
5153             Init_Size_Align (E);
5154          end if;
5155
5156          Append_Entity (E, Lim_Header);
5157          Last_Lim_E := E;
5158          return E;
5159       end New_Internal_Shadow_Entity;
5160
5161       -----------------
5162       -- Build_Chain --
5163       -----------------
5164
5165       procedure Build_Chain
5166         (Scope         : Entity_Id;
5167          First_Decl    : Node_Id)
5168       is
5169          Analyzed_Unit : constant Boolean := Analyzed (Cunit (Unum));
5170          Is_Tagged     : Boolean;
5171          Decl          : Node_Id;
5172
5173       begin
5174          Decl := First_Decl;
5175          while Present (Decl) loop
5176
5177             --  For each library_package_declaration in the environment, there
5178             --  is an implicit declaration of a *limited view* of that library
5179             --  package. The limited view of a package contains:
5180
5181             --   * For each nested package_declaration, a declaration of the
5182             --     limited view of that package, with the same defining-
5183             --     program-unit name.
5184
5185             --   * For each type_declaration in the visible part, an incomplete
5186             --     type-declaration with the same defining_identifier, whose
5187             --     completion is the type_declaration. If the type_declaration
5188             --     is tagged, then the incomplete_type_declaration is tagged
5189             --     incomplete.
5190
5191             --     The partial view is tagged if the declaration has the
5192             --     explicit keyword, or else if it is a type extension, both
5193             --     of which can be ascertained syntactically.
5194
5195             if Nkind (Decl) = N_Full_Type_Declaration then
5196                Is_Tagged :=
5197                   (Nkind (Type_Definition (Decl)) = N_Record_Definition
5198                     and then Tagged_Present (Type_Definition (Decl)))
5199                  or else
5200                    (Nkind (Type_Definition (Decl)) = N_Derived_Type_Definition
5201                      and then
5202                        Present
5203                          (Record_Extension_Part (Type_Definition (Decl))));
5204
5205                Comp_Typ := Defining_Identifier (Decl);
5206
5207                if not Analyzed_Unit then
5208                   if Is_Tagged then
5209                      Decorate_Tagged_Type (Sloc (Decl), Comp_Typ, Scope);
5210                   else
5211                      Decorate_Incomplete_Type (Comp_Typ, Scope);
5212                   end if;
5213                end if;
5214
5215                --  Create shadow entity for type
5216
5217                Lim_Typ := New_Internal_Shadow_Entity
5218                  (Kind       => Ekind (Comp_Typ),
5219                   Sloc_Value => Sloc (Comp_Typ),
5220                   Id_Char    => 'Z');
5221
5222                Set_Chars  (Lim_Typ, Chars (Comp_Typ));
5223                Set_Parent (Lim_Typ, Parent (Comp_Typ));
5224                Set_From_With_Type (Lim_Typ);
5225
5226                if Is_Tagged then
5227                   Decorate_Tagged_Type (Sloc (Decl), Lim_Typ, Scope);
5228                else
5229                   Decorate_Incomplete_Type (Lim_Typ, Scope);
5230                end if;
5231
5232                Set_Non_Limited_View (Lim_Typ, Comp_Typ);
5233
5234             elsif Nkind_In (Decl, N_Private_Type_Declaration,
5235                                   N_Incomplete_Type_Declaration,
5236                                   N_Task_Type_Declaration,
5237                                   N_Protected_Type_Declaration)
5238             then
5239                Comp_Typ := Defining_Identifier (Decl);
5240
5241                Is_Tagged :=
5242                  Nkind_In (Decl, N_Private_Type_Declaration,
5243                                  N_Incomplete_Type_Declaration)
5244                  and then Tagged_Present (Decl);
5245
5246                if not Analyzed_Unit then
5247                   if Is_Tagged then
5248                      Decorate_Tagged_Type (Sloc (Decl), Comp_Typ, Scope);
5249                   else
5250                      Decorate_Incomplete_Type (Comp_Typ, Scope);
5251                   end if;
5252                end if;
5253
5254                Lim_Typ  := New_Internal_Shadow_Entity
5255                  (Kind       => Ekind (Comp_Typ),
5256                   Sloc_Value => Sloc (Comp_Typ),
5257                   Id_Char    => 'Z');
5258
5259                Set_Chars  (Lim_Typ, Chars (Comp_Typ));
5260                Set_Parent (Lim_Typ, Parent (Comp_Typ));
5261                Set_From_With_Type (Lim_Typ);
5262
5263                if Is_Tagged then
5264                   Decorate_Tagged_Type (Sloc (Decl), Lim_Typ, Scope);
5265                else
5266                   Decorate_Incomplete_Type (Lim_Typ, Scope);
5267                end if;
5268
5269                Set_Non_Limited_View (Lim_Typ, Comp_Typ);
5270
5271             elsif Nkind (Decl) = N_Private_Extension_Declaration then
5272                Comp_Typ := Defining_Identifier (Decl);
5273
5274                if not Analyzed_Unit then
5275                   Decorate_Tagged_Type (Sloc (Decl), Comp_Typ, Scope);
5276                end if;
5277
5278                --  Create shadow entity for type
5279
5280                Lim_Typ := New_Internal_Shadow_Entity
5281                  (Kind       => Ekind (Comp_Typ),
5282                   Sloc_Value => Sloc (Comp_Typ),
5283                   Id_Char    => 'Z');
5284
5285                Set_Chars  (Lim_Typ, Chars (Comp_Typ));
5286                Set_Parent (Lim_Typ, Parent (Comp_Typ));
5287                Set_From_With_Type (Lim_Typ);
5288
5289                Decorate_Tagged_Type (Sloc (Decl), Lim_Typ, Scope);
5290                Set_Non_Limited_View (Lim_Typ, Comp_Typ);
5291
5292             elsif Nkind (Decl) = N_Package_Declaration then
5293
5294                --  Local package
5295
5296                declare
5297                   Spec : constant Node_Id := Specification (Decl);
5298
5299                begin
5300                   Comp_Typ := Defining_Unit_Name (Spec);
5301
5302                   if not Analyzed (Cunit (Unum)) then
5303                      Decorate_Package_Specification (Comp_Typ);
5304                      Set_Scope (Comp_Typ, Scope);
5305                   end if;
5306
5307                   Lim_Typ  := New_Internal_Shadow_Entity
5308                     (Kind       => Ekind (Comp_Typ),
5309                      Sloc_Value => Sloc (Comp_Typ),
5310                      Id_Char    => 'Z');
5311
5312                   Decorate_Package_Specification (Lim_Typ);
5313                   Set_Scope (Lim_Typ, Scope);
5314
5315                   Set_Chars  (Lim_Typ, Chars (Comp_Typ));
5316                   Set_Parent (Lim_Typ, Parent (Comp_Typ));
5317                   Set_From_With_Type (Lim_Typ);
5318
5319                   --  Note: The non_limited_view attribute is not used
5320                   --  for local packages.
5321
5322                   Build_Chain
5323                     (Scope      => Lim_Typ,
5324                      First_Decl => First (Visible_Declarations (Spec)));
5325                end;
5326             end if;
5327
5328             Next (Decl);
5329          end loop;
5330       end Build_Chain;
5331
5332    --  Start of processing for Build_Limited_Views
5333
5334    begin
5335       pragma Assert (Limited_Present (N));
5336
5337       --  A library_item mentioned in a limited_with_clause is a package
5338       --  declaration, not a subprogram declaration, generic declaration,
5339       --  generic instantiation, or package renaming declaration.
5340
5341       case Nkind (Unit (Library_Unit (N))) is
5342          when N_Package_Declaration =>
5343             null;
5344
5345          when N_Subprogram_Declaration =>
5346             Error_Msg_N ("subprograms not allowed in "
5347                          & "limited with_clauses", N);
5348             return;
5349
5350          when N_Generic_Package_Declaration |
5351               N_Generic_Subprogram_Declaration =>
5352             Error_Msg_N ("generics not allowed in "
5353                          & "limited with_clauses", N);
5354             return;
5355
5356          when N_Generic_Instantiation =>
5357             Error_Msg_N ("generic instantiations not allowed in "
5358                          & "limited with_clauses", N);
5359             return;
5360
5361          when N_Generic_Renaming_Declaration =>
5362             Error_Msg_N ("generic renamings not allowed in "
5363                          & "limited with_clauses", N);
5364             return;
5365
5366          when N_Subprogram_Renaming_Declaration =>
5367             Error_Msg_N ("renamed subprograms not allowed in "
5368                          & "limited with_clauses", N);
5369             return;
5370
5371          when N_Package_Renaming_Declaration =>
5372             Error_Msg_N ("renamed packages not allowed in "
5373                          & "limited with_clauses", N);
5374             return;
5375
5376          when others =>
5377             raise Program_Error;
5378       end case;
5379
5380       --  Check if the chain is already built
5381
5382       Spec := Specification (Unit (Library_Unit (N)));
5383
5384       if Limited_View_Installed (Spec) then
5385          return;
5386       end if;
5387
5388       Set_Ekind (P, E_Package);
5389
5390       --  Build the header of the limited_view
5391
5392       Lim_Header :=
5393         Make_Defining_Identifier (Sloc (N),
5394           Chars => New_Internal_Name (Id_Char => 'Z'));
5395       Set_Ekind (Lim_Header, E_Package);
5396       Set_Is_Internal (Lim_Header);
5397       Set_Limited_View (P, Lim_Header);
5398
5399       --  Create the auxiliary chain. All the shadow entities are appended to
5400       --  the list of entities of the limited-view header
5401
5402       Build_Chain
5403         (Scope      => P,
5404          First_Decl => First (Visible_Declarations (Spec)));
5405
5406       --  Save the last built shadow entity. It is needed later to set the
5407       --  reference to the first shadow entity in the private part
5408
5409       Last_Pub_Lim_E := Last_Lim_E;
5410
5411       --  Ada 2005 (AI-262): Add the limited view of the private declarations
5412       --  Required to give support to limited-private-with clauses
5413
5414       Build_Chain (Scope      => P,
5415                    First_Decl => First (Private_Declarations (Spec)));
5416
5417       if Last_Pub_Lim_E /= Empty then
5418          Set_First_Private_Entity (Lim_Header,
5419                                    Next_Entity (Last_Pub_Lim_E));
5420       else
5421          Set_First_Private_Entity (Lim_Header,
5422                                    First_Entity (P));
5423       end if;
5424
5425       Set_Limited_View_Installed (Spec);
5426    end Build_Limited_Views;
5427
5428    -------------------------------
5429    -- Check_Body_Needed_For_SAL --
5430    -------------------------------
5431
5432    procedure Check_Body_Needed_For_SAL (Unit_Name : Entity_Id) is
5433
5434       function Entity_Needs_Body (E : Entity_Id) return Boolean;
5435       --  Determine whether use of entity E might require the presence of its
5436       --  body. For a package this requires a recursive traversal of all nested
5437       --  declarations.
5438
5439       ---------------------------
5440       -- Entity_Needed_For_SAL --
5441       ---------------------------
5442
5443       function Entity_Needs_Body (E : Entity_Id) return Boolean is
5444          Ent : Entity_Id;
5445
5446       begin
5447          if Is_Subprogram (E)
5448            and then Has_Pragma_Inline (E)
5449          then
5450             return True;
5451
5452          elsif Ekind (E) = E_Generic_Function
5453            or else Ekind (E) = E_Generic_Procedure
5454          then
5455             return True;
5456
5457          elsif Ekind (E) = E_Generic_Package
5458            and then
5459              Nkind (Unit_Declaration_Node (E)) = N_Generic_Package_Declaration
5460            and then Present (Corresponding_Body (Unit_Declaration_Node (E)))
5461          then
5462             return True;
5463
5464          elsif Ekind (E) = E_Package
5465            and then
5466              Nkind (Unit_Declaration_Node (E)) = N_Package_Declaration
5467            and then Present (Corresponding_Body (Unit_Declaration_Node (E)))
5468          then
5469             Ent := First_Entity (E);
5470             while Present (Ent) loop
5471                if Entity_Needs_Body (Ent) then
5472                   return True;
5473                end if;
5474
5475                Next_Entity (Ent);
5476             end loop;
5477
5478             return False;
5479
5480          else
5481             return False;
5482          end if;
5483       end Entity_Needs_Body;
5484
5485    --  Start of processing for Check_Body_Needed_For_SAL
5486
5487    begin
5488       if Ekind (Unit_Name) = E_Generic_Package
5489         and then
5490           Nkind (Unit_Declaration_Node (Unit_Name)) =
5491                                             N_Generic_Package_Declaration
5492         and then
5493           Present (Corresponding_Body (Unit_Declaration_Node (Unit_Name)))
5494       then
5495          Set_Body_Needed_For_SAL (Unit_Name);
5496
5497       elsif Ekind (Unit_Name) = E_Generic_Procedure
5498         or else Ekind (Unit_Name) = E_Generic_Function
5499       then
5500          Set_Body_Needed_For_SAL (Unit_Name);
5501
5502       elsif Is_Subprogram (Unit_Name)
5503         and then Nkind (Unit_Declaration_Node (Unit_Name)) =
5504                                             N_Subprogram_Declaration
5505         and then Has_Pragma_Inline (Unit_Name)
5506       then
5507          Set_Body_Needed_For_SAL (Unit_Name);
5508
5509       elsif Ekind (Unit_Name) = E_Subprogram_Body then
5510          Check_Body_Needed_For_SAL
5511            (Corresponding_Spec (Unit_Declaration_Node (Unit_Name)));
5512
5513       elsif Ekind (Unit_Name) = E_Package
5514         and then Entity_Needs_Body (Unit_Name)
5515       then
5516          Set_Body_Needed_For_SAL (Unit_Name);
5517
5518       elsif Ekind (Unit_Name) = E_Package_Body
5519         and then Nkind (Unit_Declaration_Node (Unit_Name)) = N_Package_Body
5520       then
5521          Check_Body_Needed_For_SAL
5522            (Corresponding_Spec (Unit_Declaration_Node (Unit_Name)));
5523       end if;
5524    end Check_Body_Needed_For_SAL;
5525
5526    --------------------
5527    -- Remove_Context --
5528    --------------------
5529
5530    procedure Remove_Context (N : Node_Id) is
5531       Lib_Unit : constant Node_Id := Unit (N);
5532
5533    begin
5534       --  If this is a child unit, first remove the parent units
5535
5536       if Is_Child_Spec (Lib_Unit) then
5537          Remove_Parents (Lib_Unit);
5538       end if;
5539
5540       Remove_Context_Clauses (N);
5541    end Remove_Context;
5542
5543    ----------------------------
5544    -- Remove_Context_Clauses --
5545    ----------------------------
5546
5547    procedure Remove_Context_Clauses (N : Node_Id) is
5548       Item      : Node_Id;
5549       Unit_Name : Entity_Id;
5550
5551    begin
5552       --  Ada 2005 (AI-50217): We remove the context clauses in two phases:
5553       --  limited-views first and regular-views later (to maintain the
5554       --  stack model).
5555
5556       --  First Phase: Remove limited_with context clauses
5557
5558       Item := First (Context_Items (N));
5559       while Present (Item) loop
5560
5561          --  We are interested only in with clauses which got installed
5562          --  on entry.
5563
5564          if Nkind (Item) = N_With_Clause
5565            and then Limited_Present (Item)
5566            and then Limited_View_Installed (Item)
5567          then
5568             Remove_Limited_With_Clause (Item);
5569          end if;
5570
5571          Next (Item);
5572       end loop;
5573
5574       --  Second Phase: Loop through context items and undo regular
5575       --  with_clauses and use_clauses.
5576
5577       Item := First (Context_Items (N));
5578       while Present (Item) loop
5579
5580          --  We are interested only in with clauses which got installed on
5581          --  entry, as indicated by their Context_Installed flag set
5582
5583          if Nkind (Item) = N_With_Clause
5584            and then Limited_Present (Item)
5585            and then Limited_View_Installed (Item)
5586          then
5587             null;
5588
5589          elsif Nkind (Item) = N_With_Clause
5590             and then Context_Installed (Item)
5591          then
5592             --  Remove items from one with'ed unit
5593
5594             Unit_Name := Entity (Name (Item));
5595             Remove_Unit_From_Visibility (Unit_Name);
5596             Set_Context_Installed (Item, False);
5597
5598          elsif Nkind (Item) = N_Use_Package_Clause then
5599             End_Use_Package (Item);
5600
5601          elsif Nkind (Item) = N_Use_Type_Clause then
5602             End_Use_Type (Item);
5603          end if;
5604
5605          Next (Item);
5606       end loop;
5607    end Remove_Context_Clauses;
5608
5609    --------------------------------
5610    -- Remove_Limited_With_Clause --
5611    --------------------------------
5612
5613    procedure Remove_Limited_With_Clause (N : Node_Id) is
5614       P_Unit     : constant Entity_Id := Unit (Library_Unit (N));
5615       E          : Entity_Id;
5616       P          : Entity_Id;
5617       Lim_Header : Entity_Id;
5618       Lim_Typ    : Entity_Id;
5619       Prev       : Entity_Id;
5620
5621    begin
5622       pragma Assert (Limited_View_Installed (N));
5623
5624       --  In case of limited with_clause on subprograms, generics, instances,
5625       --  or renamings, the corresponding error was previously posted and we
5626       --  have nothing to do here.
5627
5628       if Nkind (P_Unit) /= N_Package_Declaration then
5629          return;
5630       end if;
5631
5632       P := Defining_Unit_Name (Specification (P_Unit));
5633
5634       --  Handle child packages
5635
5636       if Nkind (P) = N_Defining_Program_Unit_Name then
5637          P := Defining_Identifier (P);
5638       end if;
5639
5640       if Debug_Flag_I then
5641          Write_Str ("remove limited view of ");
5642          Write_Name (Chars (P));
5643          Write_Str (" from visibility");
5644          Write_Eol;
5645       end if;
5646
5647       --  Prepare the removal of the shadow entities from visibility. The
5648       --  first element of the limited view is a header (an E_Package
5649       --  entity) that is used to reference the first shadow entity in the
5650       --  private part of the package
5651
5652       Lim_Header := Limited_View (P);
5653       Lim_Typ    := First_Entity (Lim_Header);
5654
5655       --  Remove package and shadow entities from visibility if it has not
5656       --  been analyzed
5657
5658       if not Analyzed (P_Unit) then
5659          Unchain (P);
5660          Set_Is_Immediately_Visible (P, False);
5661
5662          while Present (Lim_Typ) loop
5663             Unchain (Lim_Typ);
5664             Next_Entity (Lim_Typ);
5665          end loop;
5666
5667       --  Otherwise this package has already appeared in the closure and its
5668       --  shadow entities must be replaced by its real entities. This code
5669       --  must be kept synchronized with the complementary code in Install
5670       --  Limited_Withed_Unit.
5671
5672       else
5673          --  Real entities that are type or subtype declarations were hidden
5674          --  from visibility at the point of installation of the limited-view.
5675          --  Now we recover the previous value of the hidden attribute.
5676
5677          E := First_Entity (P);
5678          while Present (E) and then E /= First_Private_Entity (P) loop
5679             if Is_Type (E) then
5680                Set_Is_Hidden (E, Was_Hidden (E));
5681             end if;
5682
5683             Next_Entity (E);
5684          end loop;
5685
5686          while Present (Lim_Typ)
5687            and then Lim_Typ /= First_Private_Entity (Lim_Header)
5688          loop
5689             --  Nested packages and child units were not unchained
5690
5691             if Ekind (Lim_Typ) /= E_Package
5692               and then not Is_Child_Unit (Non_Limited_View (Lim_Typ))
5693             then
5694
5695                --  If the package has incomplete types, the limited view
5696                --  of the incomplete type is in fact never visible (AI05-129)
5697                --  but we have created a shadow entity E1 for it, that points
5698                --  to E2, a non-limited incomplete type. This in turn has a
5699                --  full view E3 that is the full declaration. There is a
5700                --  corresponding shadow entity E4. When reinstalling the
5701                --  non-limited view, E2 must become the current entity and
5702                --  E3 must be ignored.
5703
5704                E := Non_Limited_View (Lim_Typ);
5705
5706                if Present (Current_Entity (E))
5707                  and then Ekind (Current_Entity (E)) = E_Incomplete_Type
5708                  and then Full_View (Current_Entity (E)) = E
5709                then
5710
5711                   --  Lim_Typ is the limited view of a full type declaration
5712                   --  that has a previous incomplete declaration, i.e. E3
5713                   --  from the previous description. Nothing to insert.
5714
5715                   null;
5716
5717                else
5718                   pragma Assert (not In_Chain (E));
5719
5720                   Prev := Current_Entity (Lim_Typ);
5721
5722                   if Prev = Lim_Typ then
5723                      Set_Current_Entity (E);
5724
5725                   else
5726                      while Present (Prev)
5727                        and then Homonym (Prev) /= Lim_Typ
5728                      loop
5729                         Prev := Homonym (Prev);
5730                      end loop;
5731
5732                      if Present (Prev) then
5733                         Set_Homonym (Prev, E);
5734                      end if;
5735                   end if;
5736
5737                   --  Preserve structure of homonym chain
5738
5739                   Set_Homonym (E, Homonym (Lim_Typ));
5740                end if;
5741             end if;
5742
5743             Next_Entity (Lim_Typ);
5744          end loop;
5745       end if;
5746
5747       --  Indicate that the limited view of the package is not installed
5748
5749       Set_From_With_Type         (P, False);
5750       Set_Limited_View_Installed (N, False);
5751    end Remove_Limited_With_Clause;
5752
5753    --------------------
5754    -- Remove_Parents --
5755    --------------------
5756
5757    procedure Remove_Parents (Lib_Unit : Node_Id) is
5758       P      : Node_Id;
5759       P_Name : Entity_Id;
5760       P_Spec : Node_Id := Empty;
5761       E      : Entity_Id;
5762       Vis    : constant Boolean :=
5763                  Scope_Stack.Table (Scope_Stack.Last).Previous_Visibility;
5764
5765    begin
5766       if Is_Child_Spec (Lib_Unit) then
5767          P_Spec := Parent_Spec (Lib_Unit);
5768
5769       elsif Nkind (Lib_Unit) = N_Package_Body
5770         and then Nkind (Original_Node (Lib_Unit)) = N_Package_Instantiation
5771       then
5772          P_Spec := Parent_Spec (Original_Node (Lib_Unit));
5773       end if;
5774
5775       if Present (P_Spec) then
5776
5777          P := Unit (P_Spec);
5778          P_Name := Get_Parent_Entity (P);
5779          Remove_Context_Clauses (P_Spec);
5780          End_Package_Scope (P_Name);
5781          Set_Is_Immediately_Visible (P_Name, Vis);
5782
5783          --  Remove from visibility the siblings as well, which are directly
5784          --  visible while the parent is in scope.
5785
5786          E := First_Entity (P_Name);
5787          while Present (E) loop
5788             if Is_Child_Unit (E) then
5789                Set_Is_Immediately_Visible (E, False);
5790             end if;
5791
5792             Next_Entity (E);
5793          end loop;
5794
5795          Set_In_Package_Body (P_Name, False);
5796
5797          --  This is the recursive call to remove the context of any
5798          --  higher level parent. This recursion ensures that all parents
5799          --  are removed in the reverse order of their installation.
5800
5801          Remove_Parents (P);
5802       end if;
5803    end Remove_Parents;
5804
5805    ---------------------------------
5806    -- Remove_Private_With_Clauses --
5807    ---------------------------------
5808
5809    procedure Remove_Private_With_Clauses (Comp_Unit : Node_Id) is
5810       Item : Node_Id;
5811
5812       function In_Regular_With_Clause (E : Entity_Id) return Boolean;
5813       --  Check whether a given unit appears in a regular with_clause.
5814       --  Used to determine whether a private_with_clause, implicit or
5815       --  explicit, should be ignored.
5816
5817       ----------------------------
5818       -- In_Regular_With_Clause --
5819       ----------------------------
5820
5821       function In_Regular_With_Clause (E : Entity_Id) return Boolean
5822       is
5823          Item : Node_Id;
5824
5825       begin
5826          Item := First (Context_Items (Comp_Unit));
5827          while Present (Item) loop
5828             if Nkind (Item) = N_With_Clause
5829               and then Entity (Name (Item)) = E
5830               and then not Private_Present (Item)
5831             then
5832                return True;
5833             end if;
5834             Next (Item);
5835          end loop;
5836
5837          return False;
5838       end In_Regular_With_Clause;
5839
5840    --  Start of processing for Remove_Private_With_Clauses
5841
5842    begin
5843       Item := First (Context_Items (Comp_Unit));
5844       while Present (Item) loop
5845          if Nkind (Item) = N_With_Clause
5846            and then Private_Present (Item)
5847          then
5848             --  If private_with_clause is redundant, remove it from
5849             --  context, as a small optimization to subsequent handling
5850             --  of private_with clauses in other nested packages..
5851
5852             if In_Regular_With_Clause (Entity (Name (Item))) then
5853                declare
5854                   Nxt : constant Node_Id := Next (Item);
5855                begin
5856                   Remove (Item);
5857                   Item := Nxt;
5858                end;
5859
5860             elsif Limited_Present (Item) then
5861                if not Limited_View_Installed (Item) then
5862                   Remove_Limited_With_Clause (Item);
5863                end if;
5864
5865                Next (Item);
5866
5867             else
5868                Remove_Unit_From_Visibility (Entity (Name (Item)));
5869                Set_Context_Installed (Item, False);
5870                Next (Item);
5871             end if;
5872
5873          else
5874             Next (Item);
5875          end if;
5876       end loop;
5877    end Remove_Private_With_Clauses;
5878
5879    ---------------------------------
5880    -- Remove_Unit_From_Visibility --
5881    ---------------------------------
5882
5883    procedure Remove_Unit_From_Visibility (Unit_Name : Entity_Id) is
5884       P : constant Entity_Id := Scope (Unit_Name);
5885
5886    begin
5887       if Debug_Flag_I then
5888          Write_Str ("remove unit ");
5889          Write_Name (Chars (Unit_Name));
5890          Write_Str (" from visibility");
5891          Write_Eol;
5892       end if;
5893
5894       if P /= Standard_Standard then
5895          Set_Is_Visible_Child_Unit (Unit_Name, False);
5896       end if;
5897
5898       Set_Is_Potentially_Use_Visible (Unit_Name, False);
5899       Set_Is_Immediately_Visible     (Unit_Name, False);
5900    end Remove_Unit_From_Visibility;
5901
5902    --------
5903    -- sm --
5904    --------
5905
5906    procedure sm is
5907    begin
5908       null;
5909    end sm;
5910
5911    -------------
5912    -- Unchain --
5913    -------------
5914
5915    procedure Unchain (E : Entity_Id) is
5916       Prev : Entity_Id;
5917
5918    begin
5919       Prev := Current_Entity (E);
5920
5921       if No (Prev) then
5922          return;
5923
5924       elsif Prev = E then
5925          Set_Name_Entity_Id (Chars (E), Homonym (E));
5926
5927       else
5928          while Present (Prev)
5929            and then Homonym (Prev) /= E
5930          loop
5931             Prev := Homonym (Prev);
5932          end loop;
5933
5934          if Present (Prev) then
5935             Set_Homonym (Prev, Homonym (E));
5936          end if;
5937       end if;
5938
5939       if Debug_Flag_I then
5940          Write_Str ("   (homonym) unchain ");
5941          Write_Name (Chars (E));
5942          Write_Eol;
5943       end if;
5944    end Unchain;
5945
5946 end Sem_Ch10;