OSDN Git Service

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