OSDN Git Service

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