OSDN Git Service

2008-04-08 Hristian Kirtchev <kirtchev@adacore.com>
[pf3gnuchains/gcc-fork.git] / gcc / ada / sem_ch7.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT COMPILER COMPONENTS                         --
4 --                                                                          --
5 --                              S E M . C H 7                               --
6 --                                                                          --
7 --                                 B o d y                                  --
8 --                                                                          --
9 --          Copyright (C) 1992-2008, 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 --  This package contains the routines to process package specifications and
27 --  bodies. The most important semantic aspects of package processing are the
28 --  handling of private and full declarations, and the construction of
29 --  dispatch tables for tagged types.
30
31 with Atree;    use Atree;
32 with Debug;    use Debug;
33 with Einfo;    use Einfo;
34 with Elists;   use Elists;
35 with Errout;   use Errout;
36 with Exp_Disp; use Exp_Disp;
37 with Exp_Dist; use Exp_Dist;
38 with Exp_Dbug; use Exp_Dbug;
39 with Lib;      use Lib;
40 with Lib.Xref; use Lib.Xref;
41 with Namet;    use Namet;
42 with Nmake;    use Nmake;
43 with Nlists;   use Nlists;
44 with Opt;      use Opt;
45 with Output;   use Output;
46 with Sem;      use Sem;
47 with Sem_Cat;  use Sem_Cat;
48 with Sem_Ch3;  use Sem_Ch3;
49 with Sem_Ch6;  use Sem_Ch6;
50 with Sem_Ch8;  use Sem_Ch8;
51 with Sem_Ch10; use Sem_Ch10;
52 with Sem_Ch12; use Sem_Ch12;
53 with Sem_Disp; use Sem_Disp;
54 with Sem_Util; use Sem_Util;
55 with Sem_Warn; use Sem_Warn;
56 with Snames;   use Snames;
57 with Stand;    use Stand;
58 with Sinfo;    use Sinfo;
59 with Sinput;   use Sinput;
60 with Style;
61 with Uintp;    use Uintp;
62
63 package body Sem_Ch7 is
64
65    -----------------------------------
66    -- Handling private declarations --
67    -----------------------------------
68
69    --  The principle that each entity has a single defining occurrence clashes
70    --  with the presence of two separate definitions for private types: the
71    --  first is the private type declaration, and the second is the full type
72    --  declaration. It is important that all references to the type point to
73    --  the same defining occurrence, namely the first one. To enforce the two
74    --  separate views of the entity, the corresponding information is swapped
75    --  between the two declarations. Outside of the package, the defining
76    --  occurrence only contains the private declaration information, while in
77    --  the private part and the body of the package the defining occurrence
78    --  contains the full declaration. To simplify the swap, the defining
79    --  occurrence that currently holds the private declaration points to the
80    --  full declaration. During semantic processing the defining occurrence
81    --  also points to a list of private dependents, that is to say access types
82    --  or composite types whose designated types or component types are
83    --  subtypes or derived types of the private type in question. After the
84    --  full declaration has been seen, the private dependents are updated to
85    --  indicate that they have full definitions.
86
87    -----------------------
88    -- Local Subprograms --
89    -----------------------
90
91    procedure Check_Anonymous_Access_Types
92      (Spec_Id : Entity_Id;
93       P_Body  : Node_Id);
94    --  If the spec of a package has a limited_with_clause, it may declare
95    --  anonymous access types whose designated type is a limited view, such an
96    --  anonymous access return type for a function. This access type cannot be
97    --  elaborated in the spec itself, but it may need an itype reference if it
98    --  is used within a nested scope. In that case the itype reference is
99    --  created at the beginning of the corresponding package body and inserted
100    --  before other body declarations.
101
102    procedure Inspect_Deferred_Constant_Completion (Decls : List_Id);
103    --  Examines the deferred constants in the private part of the package
104    --  specification, or in a package body. Emits the error message
105    --  "constant declaration requires initialization expression" if not
106    --  completed by an Import pragma.
107
108    procedure Install_Package_Entity (Id : Entity_Id);
109    --  Supporting procedure for Install_{Visible,Private}_Declarations.
110    --  Places one entity on its visibility chain, and recurses on the visible
111    --  part if the entity is an inner package.
112
113    function Is_Private_Base_Type (E : Entity_Id) return Boolean;
114    --  True for a private type that is not a subtype
115
116    function Is_Visible_Dependent (Dep : Entity_Id) return Boolean;
117    --  If the private dependent is a private type whose full view is derived
118    --  from the parent type, its full properties are revealed only if we are in
119    --  the immediate scope of the private dependent. Should this predicate be
120    --  tightened further???
121
122    procedure Declare_Inherited_Private_Subprograms (Id : Entity_Id);
123    --  Called upon entering the private part of a public child package and the
124    --  body of a nested package, to potentially declare certain inherited
125    --  subprograms that were inherited by types in the visible part, but whose
126    --  declaration was deferred because the parent operation was private and
127    --  not visible at that point. These subprograms are located by traversing
128    --  the visible part declarations looking for non-private type extensions
129    --  and then examining each of the primitive operations of such types to
130    --  find those that were inherited but declared with a special internal
131    --  name. Each such operation is now declared as an operation with a normal
132    --  name (using the name of the parent operation) and replaces the previous
133    --  implicit operation in the primitive operations list of the type. If the
134    --  inherited private operation has been overridden, then it's replaced by
135    --  the overriding operation.
136
137    --------------------------
138    -- Analyze_Package_Body --
139    --------------------------
140
141    procedure Analyze_Package_Body (N : Node_Id) is
142       Loc              : constant Source_Ptr := Sloc (N);
143       HSS              : Node_Id;
144       Body_Id          : Entity_Id;
145       Spec_Id          : Entity_Id;
146       Last_Spec_Entity : Entity_Id;
147       New_N            : Node_Id;
148       Pack_Decl        : Node_Id;
149
150       procedure Install_Composite_Operations (P : Entity_Id);
151       --  Composite types declared in the current scope may depend on
152       --  types that were private at the point of declaration, and whose
153       --  full view is now in  scope. Indicate that the corresponding
154       --  operations on the composite type are available.
155
156       ----------------------------------
157       -- Install_Composite_Operations --
158       ----------------------------------
159
160       procedure Install_Composite_Operations (P : Entity_Id) is
161          Id : Entity_Id;
162
163       begin
164          Id := First_Entity (P);
165          while Present (Id) loop
166             if Is_Type (Id)
167               and then (Is_Limited_Composite (Id)
168                          or else Is_Private_Composite (Id))
169               and then No (Private_Component (Id))
170             then
171                Set_Is_Limited_Composite (Id, False);
172                Set_Is_Private_Composite (Id, False);
173             end if;
174
175             Next_Entity (Id);
176          end loop;
177       end Install_Composite_Operations;
178
179    --  Start of processing for Analyze_Package_Body
180
181    begin
182       --  Find corresponding package specification, and establish the
183       --  current scope. The visible defining entity for the package is the
184       --  defining occurrence in the spec. On exit from the package body, all
185       --  body declarations are attached to the defining entity for the body,
186       --  but the later is never used for name resolution. In this fashion
187       --  there is only one visible entity that denotes the package.
188
189       if Debug_Flag_C then
190          Write_Str ("====  Compiling package body ");
191          Write_Name (Chars (Defining_Entity (N)));
192          Write_Str (" from ");
193          Write_Location (Loc);
194          Write_Eol;
195       end if;
196
197       --  Set Body_Id. Note that this Will be reset to point to the
198       --  generic copy later on in the generic case.
199
200       Body_Id := Defining_Entity (N);
201
202       if Present (Corresponding_Spec (N)) then
203
204          --  Body is body of package instantiation. Corresponding spec
205          --  has already been set.
206
207          Spec_Id := Corresponding_Spec (N);
208          Pack_Decl := Unit_Declaration_Node (Spec_Id);
209
210       else
211          Spec_Id := Current_Entity_In_Scope (Defining_Entity (N));
212
213          if Present (Spec_Id)
214            and then Is_Package_Or_Generic_Package (Spec_Id)
215          then
216             Pack_Decl := Unit_Declaration_Node (Spec_Id);
217
218             if Nkind (Pack_Decl) = N_Package_Renaming_Declaration then
219                Error_Msg_N ("cannot supply body for package renaming", N);
220                return;
221
222             elsif Present (Corresponding_Body (Pack_Decl)) then
223                Error_Msg_N ("redefinition of package body", N);
224                return;
225             end if;
226
227          else
228             Error_Msg_N ("missing specification for package body", N);
229             return;
230          end if;
231
232          if Is_Package_Or_Generic_Package (Spec_Id)
233            and then
234              (Scope (Spec_Id) = Standard_Standard
235                or else Is_Child_Unit (Spec_Id))
236            and then not Unit_Requires_Body (Spec_Id)
237          then
238             if Ada_Version = Ada_83 then
239                Error_Msg_N
240                  ("optional package body (not allowed in Ada 95)?", N);
241             else
242                Error_Msg_N
243                  ("spec of this package does not allow a body", N);
244             end if;
245          end if;
246       end if;
247
248       Set_Is_Compilation_Unit (Body_Id, Is_Compilation_Unit (Spec_Id));
249       Style.Check_Identifier (Body_Id, Spec_Id);
250
251       if Is_Child_Unit (Spec_Id) then
252          if Nkind (Parent (N)) /= N_Compilation_Unit then
253             Error_Msg_NE
254               ("body of child unit& cannot be an inner package", N, Spec_Id);
255          end if;
256
257          Set_Is_Child_Unit (Body_Id);
258       end if;
259
260       --  Generic package case
261
262       if Ekind (Spec_Id) = E_Generic_Package then
263
264          --  Disable expansion and perform semantic analysis on copy.
265          --  The unannotated body will be used in all instantiations.
266
267          Body_Id := Defining_Entity (N);
268          Set_Ekind (Body_Id, E_Package_Body);
269          Set_Scope (Body_Id, Scope (Spec_Id));
270          Set_Is_Obsolescent (Body_Id, Is_Obsolescent (Spec_Id));
271          Set_Body_Entity (Spec_Id, Body_Id);
272          Set_Spec_Entity (Body_Id, Spec_Id);
273
274          New_N := Copy_Generic_Node (N, Empty, Instantiating => False);
275          Rewrite (N, New_N);
276
277          --  Update Body_Id to point to the copied node for the remainder
278          --  of the processing.
279
280          Body_Id := Defining_Entity (N);
281          Start_Generic;
282       end if;
283
284       --  The Body_Id is that of the copied node in the generic case, the
285       --  current node otherwise. Note that N was rewritten above, so we
286       --  must be sure to get the latest Body_Id value.
287
288       Set_Ekind (Body_Id, E_Package_Body);
289       Set_Body_Entity (Spec_Id, Body_Id);
290       Set_Spec_Entity (Body_Id, Spec_Id);
291
292       --  Defining name for the package body is not a visible entity: Only
293       --  the defining name for the declaration is visible.
294
295       Set_Etype (Body_Id, Standard_Void_Type);
296       Set_Scope (Body_Id, Scope (Spec_Id));
297       Set_Corresponding_Spec (N, Spec_Id);
298       Set_Corresponding_Body (Pack_Decl, Body_Id);
299
300       --  The body entity is not used for semantics or code generation, but
301       --  it is attached to the entity list of the enclosing scope to simplify
302       --  the listing of back-annotations for the types it main contain.
303
304       if Scope (Spec_Id) /= Standard_Standard then
305          Append_Entity (Body_Id, Scope (Spec_Id));
306       end if;
307
308       --  Indicate that we are currently compiling the body of the package
309
310       Set_In_Package_Body (Spec_Id);
311       Set_Has_Completion (Spec_Id);
312       Last_Spec_Entity := Last_Entity (Spec_Id);
313
314       Push_Scope (Spec_Id);
315
316       Set_Categorization_From_Pragmas (N);
317
318       Install_Visible_Declarations (Spec_Id);
319       Install_Private_Declarations (Spec_Id);
320       Install_Private_With_Clauses (Spec_Id);
321       Install_Composite_Operations (Spec_Id);
322
323       Check_Anonymous_Access_Types (Spec_Id, N);
324
325       if Ekind (Spec_Id) = E_Generic_Package then
326          Set_Use (Generic_Formal_Declarations (Pack_Decl));
327       end if;
328
329       Set_Use (Visible_Declarations (Specification (Pack_Decl)));
330       Set_Use (Private_Declarations (Specification (Pack_Decl)));
331
332       --  This is a nested package, so it may be necessary to declare certain
333       --  inherited subprograms that are not yet visible because the parent
334       --  type's subprograms are now visible.
335
336       if Ekind (Scope (Spec_Id)) = E_Package
337         and then Scope (Spec_Id) /= Standard_Standard
338       then
339          Declare_Inherited_Private_Subprograms (Spec_Id);
340       end if;
341
342       if Present (Declarations (N)) then
343          Analyze_Declarations (Declarations (N));
344          Inspect_Deferred_Constant_Completion (Declarations (N));
345       end if;
346
347       --  Analyze_Declarations has caused freezing of all types; now generate
348       --  bodies for RACW primitives and stream attributes, if any.
349
350       if Ekind (Spec_Id) = E_Package and then Has_RACW (Spec_Id) then
351
352          --  Attach subprogram bodies to support RACWs declared in spec
353
354          Append_RACW_Bodies (Declarations (N), Spec_Id);
355          Analyze_List (Declarations (N));
356       end if;
357
358       HSS := Handled_Statement_Sequence (N);
359
360       if Present (HSS) then
361          Process_End_Label (HSS, 't', Spec_Id);
362          Analyze (HSS);
363
364          --  Check that elaboration code in a preelaborable package body is
365          --  empty other than null statements and labels (RM 10.2.1(6)).
366
367          Validate_Null_Statement_Sequence (N);
368       end if;
369
370       Validate_Categorization_Dependency (N, Spec_Id);
371       Check_Completion (Body_Id);
372
373       --  Generate start of body reference. Note that we do this fairly late,
374       --  because the call will use In_Extended_Main_Source_Unit as a check,
375       --  and we want to make sure that Corresponding_Stub links are set
376
377       Generate_Reference (Spec_Id, Body_Id, 'b', Set_Ref => False);
378
379       --  For a generic package, collect global references and mark them on
380       --  the original body so that they are not resolved again at the point
381       --  of instantiation.
382
383       if Ekind (Spec_Id) /= E_Package then
384          Save_Global_References (Original_Node (N));
385          End_Generic;
386       end if;
387
388       --  The entities of the package body have so far been chained onto the
389       --  declaration chain for the spec. That's been fine while we were in the
390       --  body, since we wanted them to be visible, but now that we are leaving
391       --  the package body, they are no longer visible, so we remove them from
392       --  the entity chain of the package spec entity, and copy them to the
393       --  entity chain of the package body entity, where they will never again
394       --  be visible.
395
396       if Present (Last_Spec_Entity) then
397          Set_First_Entity (Body_Id, Next_Entity (Last_Spec_Entity));
398          Set_Next_Entity (Last_Spec_Entity, Empty);
399          Set_Last_Entity (Body_Id, Last_Entity (Spec_Id));
400          Set_Last_Entity (Spec_Id, Last_Spec_Entity);
401
402       else
403          Set_First_Entity (Body_Id, First_Entity (Spec_Id));
404          Set_Last_Entity  (Body_Id, Last_Entity  (Spec_Id));
405          Set_First_Entity (Spec_Id, Empty);
406          Set_Last_Entity  (Spec_Id, Empty);
407       end if;
408
409       End_Package_Scope (Spec_Id);
410
411       --  All entities declared in body are not visible
412
413       declare
414          E : Entity_Id;
415
416       begin
417          E := First_Entity (Body_Id);
418          while Present (E) loop
419             Set_Is_Immediately_Visible (E, False);
420             Set_Is_Potentially_Use_Visible (E, False);
421             Set_Is_Hidden (E);
422
423             --  Child units may appear on the entity list (for example if
424             --  they appear in the context of a subunit) but they are not
425             --  body entities.
426
427             if not Is_Child_Unit (E) then
428                Set_Is_Package_Body_Entity (E);
429             end if;
430
431             Next_Entity (E);
432          end loop;
433       end;
434
435       Check_References (Body_Id);
436
437       --  For a generic unit, check that the formal parameters are referenced,
438       --  and that local variables are used, as for regular packages.
439
440       if Ekind (Spec_Id) = E_Generic_Package then
441          Check_References (Spec_Id);
442       end if;
443
444       --  The processing so far has made all entities of the package body
445       --  public (i.e. externally visible to the linker). This is in general
446       --  necessary, since inlined or generic bodies, for which code is
447       --  generated in other units, may need to see these entities. The
448       --  following loop runs backwards from the end of the entities of the
449       --  package body making these entities invisible until we reach a
450       --  referencer, i.e. a declaration that could reference a previous
451       --  declaration, a generic body or an inlined body, or a stub (which
452       --  may contain either of these). This is of course an approximation,
453       --  but it is conservative and definitely correct.
454
455       --  We only do this at the outer (library) level non-generic packages.
456       --  The reason is simply to cut down on the number of external symbols
457       --  generated, so this is simply an optimization of the efficiency
458       --  of the compilation process. It has no other effect.
459
460       if (Scope (Spec_Id) = Standard_Standard or else Is_Child_Unit (Spec_Id))
461         and then not Is_Generic_Unit (Spec_Id)
462         and then Present (Declarations (N))
463       then
464          Make_Non_Public_Where_Possible : declare
465
466             function Has_Referencer
467               (L     : List_Id;
468                Outer : Boolean)
469                return  Boolean;
470             --  Traverse the given list of declarations in reverse order.
471             --  Return True as soon as a referencer is reached. Return
472             --  False if none is found. The Outer parameter is True for
473             --  the outer level call, and False for inner level calls for
474             --  nested packages. If Outer is True, then any entities up
475             --  to the point of hitting a referencer get their Is_Public
476             --  flag cleared, so that the entities will be treated as
477             --  static entities in the C sense, and need not have fully
478             --  qualified names. For inner levels, we need all names to
479             --  be fully qualified to deal with the same name appearing
480             --  in parallel packages (right now this is tied to their
481             --  being external).
482
483             --------------------
484             -- Has_Referencer --
485             --------------------
486
487             function Has_Referencer
488               (L     : List_Id;
489                Outer : Boolean)
490                return  Boolean
491             is
492                D : Node_Id;
493                E : Entity_Id;
494                K : Node_Kind;
495                S : Entity_Id;
496
497             begin
498                if No (L) then
499                   return False;
500                end if;
501
502                D := Last (L);
503                while Present (D) loop
504                   K := Nkind (D);
505
506                   if K in N_Body_Stub then
507                      return True;
508
509                   elsif K = N_Subprogram_Body then
510                      if Acts_As_Spec (D) then
511                         E := Defining_Entity (D);
512
513                         --  An inlined body acts as a referencer. Note also
514                         --  that we never reset Is_Public for an inlined
515                         --  subprogram. Gigi requires Is_Public to be set.
516
517                         --  Note that we test Has_Pragma_Inline here rather
518                         --  than Is_Inlined. We are compiling this for a
519                         --  client, and it is the client who will decide
520                         --  if actual inlining should occur, so we need to
521                         --  assume that the procedure could be inlined for
522                         --  the purpose of accessing global entities.
523
524                         if Has_Pragma_Inline (E) then
525                            return True;
526                         else
527                            Set_Is_Public (E, False);
528                         end if;
529
530                      else
531                         E := Corresponding_Spec (D);
532
533                         if Present (E)
534                           and then (Is_Generic_Unit (E)
535                                      or else Has_Pragma_Inline (E)
536                                      or else Is_Inlined (E))
537                         then
538                            return True;
539                         end if;
540                      end if;
541
542                   --  Processing for package bodies
543
544                   elsif K = N_Package_Body
545                     and then Present (Corresponding_Spec (D))
546                   then
547                      E := Corresponding_Spec (D);
548
549                      --  Generic package body is a referencer. It would
550                      --  seem that we only have to consider generics that
551                      --  can be exported, i.e. where the corresponding spec
552                      --  is the spec of the current package, but because of
553                      --  nested instantiations, a fully private generic
554                      --  body may export other private body entities.
555
556                      if Is_Generic_Unit (E) then
557                         return True;
558
559                      --  For non-generic package body, recurse into body
560                      --  unless this is an instance, we ignore instances
561                      --  since they cannot have references that affect
562                      --  outer entities.
563
564                      elsif not Is_Generic_Instance (E) then
565                         if Has_Referencer
566                              (Declarations (D), Outer => False)
567                         then
568                            return True;
569                         end if;
570                      end if;
571
572                   --  Processing for package specs, recurse into declarations.
573                   --  Again we skip this for the case of generic instances.
574
575                   elsif K = N_Package_Declaration then
576                      S := Specification (D);
577
578                      if not Is_Generic_Unit (Defining_Entity (S)) then
579                         if Has_Referencer
580                              (Private_Declarations (S), Outer => False)
581                         then
582                            return True;
583                         elsif Has_Referencer
584                                (Visible_Declarations (S), Outer => False)
585                         then
586                            return True;
587                         end if;
588                      end if;
589
590                   --  Objects and exceptions need not be public if we have
591                   --  not encountered a referencer so far. We only reset
592                   --  the flag for outer level entities that are not
593                   --  imported/exported, and which have no interface name.
594
595                   elsif Nkind_In (K, N_Object_Declaration,
596                                      N_Exception_Declaration,
597                                      N_Subprogram_Declaration)
598                   then
599                      E := Defining_Entity (D);
600
601                      if Outer
602                        and then not Is_Imported (E)
603                        and then not Is_Exported (E)
604                        and then No (Interface_Name (E))
605                      then
606                         Set_Is_Public (E, False);
607                      end if;
608                   end if;
609
610                   Prev (D);
611                end loop;
612
613                return False;
614             end Has_Referencer;
615
616          --  Start of processing for Make_Non_Public_Where_Possible
617
618          begin
619             declare
620                Discard : Boolean;
621                pragma Warnings (Off, Discard);
622
623             begin
624                Discard := Has_Referencer (Declarations (N), Outer => True);
625             end;
626          end Make_Non_Public_Where_Possible;
627       end if;
628
629       --  If expander is not active, then here is where we turn off the
630       --  In_Package_Body flag, otherwise it is turned off at the end of
631       --  the corresponding expansion routine. If this is an instance body,
632       --  we need to qualify names of local entities, because the body may
633       --  have been compiled as a preliminary to another instantiation.
634
635       if not Expander_Active then
636          Set_In_Package_Body (Spec_Id, False);
637
638          if Is_Generic_Instance (Spec_Id)
639            and then Operating_Mode = Generate_Code
640          then
641             Qualify_Entity_Names (N);
642          end if;
643       end if;
644    end Analyze_Package_Body;
645
646    ---------------------------------
647    -- Analyze_Package_Declaration --
648    ---------------------------------
649
650    procedure Analyze_Package_Declaration (N : Node_Id) is
651       Id : constant Node_Id := Defining_Entity (N);
652
653       PF : Boolean;
654       --  True when in the context of a declared pure library unit
655
656       Body_Required : Boolean;
657       --  True when this package declaration requires a corresponding body
658
659       Comp_Unit : Boolean;
660       --  True when this package declaration is not a nested declaration
661
662    begin
663       --  Ada 2005 (AI-217): Check if the package has been erroneously named
664       --  in a limited-with clause of its own context. In this case the error
665       --  has been previously notified by Analyze_Context.
666
667       --     limited with Pkg; -- ERROR
668       --     package Pkg is ...
669
670       if From_With_Type (Id) then
671          return;
672       end if;
673
674       Generate_Definition (Id);
675       Enter_Name (Id);
676       Set_Ekind (Id, E_Package);
677       Set_Etype (Id, Standard_Void_Type);
678
679       Push_Scope (Id);
680
681       PF := Is_Pure (Enclosing_Lib_Unit_Entity);
682       Set_Is_Pure (Id, PF);
683
684       Set_Categorization_From_Pragmas (N);
685
686       if Debug_Flag_C then
687          Write_Str ("====  Compiling package spec ");
688          Write_Name (Chars (Id));
689          Write_Str (" from ");
690          Write_Location (Sloc (N));
691          Write_Eol;
692       end if;
693
694       Analyze (Specification (N));
695       Validate_Categorization_Dependency (N, Id);
696
697       Body_Required := Unit_Requires_Body (Id);
698
699       --  When this spec does not require an explicit body, we know that
700       --  there are no entities requiring completion in the language sense;
701       --  we call Check_Completion here only to ensure that any nested package
702       --  declaration that requires an implicit body gets one. (In the case
703       --  where a body is required, Check_Completion is called at the end of
704       --  the body's declarative part.)
705
706       if not Body_Required then
707          Check_Completion;
708       end if;
709
710       Comp_Unit := Nkind (Parent (N)) = N_Compilation_Unit;
711       if Comp_Unit then
712
713          --  Set Body_Required indication on the compilation unit node, and
714          --  determine whether elaboration warnings may be meaningful on it.
715
716          Set_Body_Required (Parent (N), Body_Required);
717
718          if not Body_Required then
719             Set_Suppress_Elaboration_Warnings (Id);
720          end if;
721
722       end if;
723
724       End_Package_Scope (Id);
725
726       --  For the declaration of a library unit that is a remote types package,
727       --  check legality rules regarding availability of stream attributes for
728       --  types that contain non-remote access values. This subprogram performs
729       --  visibility tests that rely on the fact that we have exited the scope
730       --  of Id.
731
732       if Comp_Unit then
733          Validate_RT_RAT_Component (N);
734       end if;
735    end Analyze_Package_Declaration;
736
737    -----------------------------------
738    -- Analyze_Package_Specification --
739    -----------------------------------
740
741    --  Note that this code is shared for the analysis of generic package
742    --  specs (see Sem_Ch12.Analyze_Generic_Package_Declaration for details).
743
744    procedure Analyze_Package_Specification (N : Node_Id) is
745       Id           : constant Entity_Id  := Defining_Entity (N);
746       Orig_Decl    : constant Node_Id    := Original_Node (Parent (N));
747       Vis_Decls    : constant List_Id    := Visible_Declarations (N);
748       Priv_Decls   : constant List_Id    := Private_Declarations (N);
749       E            : Entity_Id;
750       L            : Entity_Id;
751       Public_Child : Boolean;
752
753       Private_With_Clauses_Installed : Boolean := False;
754       --  In Ada 2005, private with_clauses are visible in the private part
755       --  of a nested package, even if it appears in the public part of the
756       --  enclosing package. This requires a separate step to install these
757       --  private_with_clauses, and remove them at the end of the nested
758       --  package.
759
760       procedure Clear_Constants (Id : Entity_Id; FE : Entity_Id);
761       --  Clears constant indications (Never_Set_In_Source, Constant_Value,
762       --  and Is_True_Constant) on all variables that are entities of Id,
763       --  and on the chain whose first element is FE. A recursive call is
764       --  made for all packages and generic packages.
765
766       procedure Generate_Parent_References;
767       --  For a child unit, generate references to parent units, for
768       --  GPS navigation purposes.
769
770       function Is_Public_Child (Child, Unit : Entity_Id) return Boolean;
771       --  Child and Unit are entities of compilation units. True if Child
772       --  is a public child of Parent as defined in 10.1.1
773
774       procedure Inspect_Unchecked_Union_Completion (Decls : List_Id);
775       --  Detects all incomplete or private type declarations having a known
776       --  discriminant part that are completed by an Unchecked_Union. Emits
777       --  the error message "Unchecked_Union may not complete discriminated
778       --  partial view".
779
780       procedure Install_Parent_Private_Declarations (Inst_Id : Entity_Id);
781       --  Given the package entity of a generic package instantiation or
782       --  formal package whose corresponding generic is a child unit, installs
783       --  the private declarations of each of the child unit's parents.
784       --  This has to be done at the point of entering the instance package's
785       --  private part rather than being done in Sem_Ch12.Install_Parent
786       --  (which is where the parents' visible declarations are installed).
787
788       ---------------------
789       -- Clear_Constants --
790       ---------------------
791
792       procedure Clear_Constants (Id : Entity_Id; FE : Entity_Id) is
793          E : Entity_Id;
794
795       begin
796          --  Ignore package renamings, not interesting and they can
797          --  cause self referential loops in the code below.
798
799          if Nkind (Parent (Id)) = N_Package_Renaming_Declaration then
800             return;
801          end if;
802
803          --  Note: in the loop below, the check for Next_Entity pointing
804          --  back to the package entity may seem odd, but it is needed,
805          --  because a package can contain a renaming declaration to itself,
806          --  and such renamings are generated automatically within package
807          --  instances.
808
809          E := FE;
810          while Present (E) and then E /= Id loop
811             if Is_Assignable (E) then
812                Set_Never_Set_In_Source (E, False);
813                Set_Is_True_Constant    (E, False);
814                Set_Current_Value       (E, Empty);
815                Set_Is_Known_Null       (E, False);
816                Set_Last_Assignment     (E, Empty);
817
818                if not Can_Never_Be_Null (E) then
819                   Set_Is_Known_Non_Null (E, False);
820                end if;
821
822             elsif Ekind (E) = E_Package
823                     or else
824                   Ekind (E) = E_Generic_Package
825             then
826                Clear_Constants (E, First_Entity (E));
827                Clear_Constants (E, First_Private_Entity (E));
828             end if;
829
830             Next_Entity (E);
831          end loop;
832       end Clear_Constants;
833
834       --------------------------------
835       -- Generate_Parent_References --
836       --------------------------------
837
838       procedure Generate_Parent_References is
839          Decl : constant Node_Id := Parent (N);
840
841       begin
842          if Id = Cunit_Entity (Main_Unit)
843            or else Parent (Decl) = Library_Unit (Cunit (Main_Unit))
844          then
845             Generate_Reference (Id, Scope (Id), 'k', False);
846
847          elsif not Nkind_In (Unit (Cunit (Main_Unit)), N_Subprogram_Body,
848                                                        N_Subunit)
849          then
850             --  If current unit is an ancestor of main unit, generate
851             --  a reference to its own parent.
852
853             declare
854                U         : Node_Id;
855                Main_Spec : Node_Id := Unit (Cunit (Main_Unit));
856
857             begin
858                if Nkind (Main_Spec) = N_Package_Body then
859                   Main_Spec := Unit (Library_Unit (Cunit (Main_Unit)));
860                end if;
861
862                U := Parent_Spec (Main_Spec);
863                while Present (U) loop
864                   if U = Parent (Decl) then
865                      Generate_Reference (Id, Scope (Id), 'k',  False);
866                      exit;
867
868                   elsif Nkind (Unit (U)) = N_Package_Body then
869                      exit;
870
871                   else
872                      U := Parent_Spec (Unit (U));
873                   end if;
874                end loop;
875             end;
876          end if;
877       end Generate_Parent_References;
878
879       ---------------------
880       -- Is_Public_Child --
881       ---------------------
882
883       function Is_Public_Child (Child, Unit : Entity_Id) return Boolean is
884       begin
885          if not Is_Private_Descendant (Child) then
886             return True;
887          else
888             if Child = Unit then
889                return not Private_Present (
890                  Parent (Unit_Declaration_Node (Child)));
891             else
892                return Is_Public_Child (Scope (Child), Unit);
893             end if;
894          end if;
895       end Is_Public_Child;
896
897       ----------------------------------------
898       -- Inspect_Unchecked_Union_Completion --
899       ----------------------------------------
900
901       procedure Inspect_Unchecked_Union_Completion (Decls : List_Id) is
902          Decl : Node_Id;
903
904       begin
905          Decl := First (Decls);
906          while Present (Decl) loop
907
908             --  We are looking at an incomplete or private type declaration
909             --  with a known_discriminant_part whose full view is an
910             --  Unchecked_Union.
911
912             if Nkind_In (Decl, N_Incomplete_Type_Declaration,
913                                N_Private_Type_Declaration)
914               and then Has_Discriminants (Defining_Identifier (Decl))
915               and then Present (Full_View (Defining_Identifier (Decl)))
916               and then
917                 Is_Unchecked_Union (Full_View (Defining_Identifier (Decl)))
918             then
919                Error_Msg_N
920                  ("completion of discriminated partial view "
921                   & "cannot be an Unchecked_Union",
922                  Full_View (Defining_Identifier (Decl)));
923             end if;
924
925             Next (Decl);
926          end loop;
927       end Inspect_Unchecked_Union_Completion;
928
929       -----------------------------------------
930       -- Install_Parent_Private_Declarations --
931       -----------------------------------------
932
933       procedure Install_Parent_Private_Declarations (Inst_Id : Entity_Id) is
934          Inst_Par  : Entity_Id;
935          Gen_Par   : Entity_Id;
936          Inst_Node : Node_Id;
937
938       begin
939          Inst_Par := Inst_Id;
940          Gen_Par :=
941            Generic_Parent (Specification (Unit_Declaration_Node (Inst_Par)));
942
943          while Present (Gen_Par) and then Is_Child_Unit (Gen_Par) loop
944             Inst_Node := Get_Package_Instantiation_Node (Inst_Par);
945
946             if Nkind_In (Inst_Node, N_Package_Instantiation,
947                                     N_Formal_Package_Declaration)
948               and then Nkind (Name (Inst_Node)) = N_Expanded_Name
949             then
950                Inst_Par := Entity (Prefix (Name (Inst_Node)));
951
952                if Present (Renamed_Entity (Inst_Par)) then
953                   Inst_Par := Renamed_Entity (Inst_Par);
954                end if;
955
956                Gen_Par :=
957                  Generic_Parent
958                    (Specification (Unit_Declaration_Node (Inst_Par)));
959
960                --  Install the private declarations and private use clauses
961                --  of a parent instance of the child instance, unless the
962                --  parent instance private declarations have already been
963                --  installed earlier in Analyze_Package_Specification, which
964                --  happens when a generic child is instantiated, and the
965                --  instance is a child of the parent instance.
966
967                --  Installing the use clauses of the parent instance twice
968                --  is both unnecessary and wrong, because it would cause the
969                --  clauses to be chained to themselves in the use clauses
970                --  list of the scope stack entry. That in turn would cause
971                --  an endless loop from End_Use_Clauses upon sccope exit.
972
973                --  The parent is now fully visible. It may be a hidden open
974                --  scope if we are currently compiling some child instance
975                --  declared within it, but while the current instance is being
976                --  compiled the parent is immediately visible. In particular
977                --  its entities must remain visible if a stack save/restore
978                --  takes place through a call to Rtsfind.
979
980                if Present (Gen_Par) then
981                   if not In_Private_Part (Inst_Par) then
982                      Install_Private_Declarations (Inst_Par);
983                      Set_Use (Private_Declarations
984                                 (Specification
985                                    (Unit_Declaration_Node (Inst_Par))));
986                      Set_Is_Hidden_Open_Scope (Inst_Par, False);
987                   end if;
988
989                --  If we've reached the end of the generic instance parents,
990                --  then finish off by looping through the nongeneric parents
991                --  and installing their private declarations.
992
993                else
994                   while Present (Inst_Par)
995                     and then Inst_Par /= Standard_Standard
996                     and then (not In_Open_Scopes (Inst_Par)
997                                 or else not In_Private_Part (Inst_Par))
998                   loop
999                      Install_Private_Declarations (Inst_Par);
1000                      Set_Use (Private_Declarations
1001                                 (Specification
1002                                    (Unit_Declaration_Node (Inst_Par))));
1003                      Inst_Par := Scope (Inst_Par);
1004                   end loop;
1005
1006                   exit;
1007                end if;
1008
1009             else
1010                exit;
1011             end if;
1012          end loop;
1013       end Install_Parent_Private_Declarations;
1014
1015    --  Start of processing for Analyze_Package_Specification
1016
1017    begin
1018       if Present (Vis_Decls) then
1019          Analyze_Declarations (Vis_Decls);
1020       end if;
1021
1022       --  Verify that incomplete types have received full declarations
1023
1024       E := First_Entity (Id);
1025       while Present (E) loop
1026          if Ekind (E) = E_Incomplete_Type
1027            and then No (Full_View (E))
1028          then
1029             Error_Msg_N ("no declaration in visible part for incomplete}", E);
1030          end if;
1031
1032          Next_Entity (E);
1033       end loop;
1034
1035       if Is_Remote_Call_Interface (Id)
1036          and then Nkind (Parent (Parent (N))) = N_Compilation_Unit
1037       then
1038          Validate_RCI_Declarations (Id);
1039       end if;
1040
1041       --  Save global references in the visible declarations, before
1042       --  installing private declarations of parent unit if there is one,
1043       --  because the privacy status of types defined in the parent will
1044       --  change. This is only relevant for generic child units, but is
1045       --  done in all cases for uniformity.
1046
1047       if Ekind (Id) = E_Generic_Package
1048         and then Nkind (Orig_Decl) = N_Generic_Package_Declaration
1049       then
1050          declare
1051             Orig_Spec : constant Node_Id := Specification (Orig_Decl);
1052             Save_Priv : constant List_Id := Private_Declarations (Orig_Spec);
1053
1054          begin
1055             Set_Private_Declarations (Orig_Spec, Empty_List);
1056             Save_Global_References   (Orig_Decl);
1057             Set_Private_Declarations (Orig_Spec, Save_Priv);
1058          end;
1059       end if;
1060
1061       --  If package is a public child unit, then make the private declarations
1062       --  of the parent visible.
1063
1064       Public_Child := False;
1065
1066       declare
1067          Par       : Entity_Id;
1068          Pack_Decl : Node_Id;
1069          Par_Spec  : Node_Id;
1070
1071       begin
1072          Par := Id;
1073          Par_Spec := Parent_Spec (Parent (N));
1074
1075          --  If the package is formal package of an enclosing generic, it is
1076          --  transformed into a local generic declaration, and compiled to make
1077          --  its spec available. We need to retrieve the original generic to
1078          --  determine whether it is a child unit, and install its parents.
1079
1080          if No (Par_Spec)
1081            and then
1082              Nkind (Original_Node (Parent (N))) = N_Formal_Package_Declaration
1083          then
1084             Par := Entity (Name (Original_Node (Parent (N))));
1085             Par_Spec := Parent_Spec (Unit_Declaration_Node (Par));
1086          end if;
1087
1088          if Present (Par_Spec) then
1089             Generate_Parent_References;
1090
1091             while Scope (Par) /= Standard_Standard
1092               and then Is_Public_Child (Id, Par)
1093               and then In_Open_Scopes (Par)
1094             loop
1095                Public_Child := True;
1096                Par := Scope (Par);
1097                Install_Private_Declarations (Par);
1098                Install_Private_With_Clauses (Par);
1099                Pack_Decl := Unit_Declaration_Node (Par);
1100                Set_Use (Private_Declarations (Specification (Pack_Decl)));
1101             end loop;
1102          end if;
1103       end;
1104
1105       if Is_Compilation_Unit (Id) then
1106          Install_Private_With_Clauses (Id);
1107       else
1108
1109          --  The current compilation unit may include private with_clauses,
1110          --  which are visible in the private part of the current nested
1111          --  package, and have to be installed now. This is not done for
1112          --  nested instantiations, where the private with_clauses of the
1113          --  enclosing unit have no effect once the instantiation info is
1114          --  established and we start analyzing the package declaration.
1115
1116          declare
1117             Comp_Unit : constant Entity_Id := Cunit_Entity (Current_Sem_Unit);
1118          begin
1119             if (Ekind (Comp_Unit) = E_Package
1120                  or else Ekind (Comp_Unit) = E_Generic_Package)
1121               and then not In_Private_Part (Comp_Unit)
1122               and then not In_Instance
1123             then
1124                Install_Private_With_Clauses (Comp_Unit);
1125                Private_With_Clauses_Installed := True;
1126             end if;
1127          end;
1128       end if;
1129
1130       --  If this is a package associated with a generic instance or formal
1131       --  package, then the private declarations of each of the generic's
1132       --  parents must be installed at this point.
1133
1134       if Is_Generic_Instance (Id) then
1135          Install_Parent_Private_Declarations (Id);
1136       end if;
1137
1138       --  Analyze private part if present. The flag In_Private_Part is reset
1139       --  in End_Package_Scope.
1140
1141       L := Last_Entity (Id);
1142
1143       if Present (Priv_Decls) then
1144          Set_In_Private_Part (Id);
1145
1146          --  Upon entering a public child's private part, it may be necessary
1147          --  to declare subprograms that were derived in the package's visible
1148          --  part but not yet made visible.
1149
1150          if Public_Child then
1151             Declare_Inherited_Private_Subprograms (Id);
1152          end if;
1153
1154          Analyze_Declarations (Priv_Decls);
1155
1156          --  Check the private declarations for incomplete deferred constants
1157
1158          Inspect_Deferred_Constant_Completion (Priv_Decls);
1159
1160          --  The first private entity is the immediate follower of the last
1161          --  visible entity, if there was one.
1162
1163          if Present (L) then
1164             Set_First_Private_Entity (Id, Next_Entity (L));
1165          else
1166             Set_First_Private_Entity (Id, First_Entity (Id));
1167          end if;
1168
1169       --  There may be inherited private subprograms that need to be declared,
1170       --  even in the absence of an explicit private part.  If there are any
1171       --  public declarations in the package and the package is a public child
1172       --  unit, then an implicit private part is assumed.
1173
1174       elsif Present (L) and then Public_Child then
1175          Set_In_Private_Part (Id);
1176          Declare_Inherited_Private_Subprograms (Id);
1177          Set_First_Private_Entity (Id, Next_Entity (L));
1178       end if;
1179
1180       E := First_Entity (Id);
1181       while Present (E) loop
1182
1183          --  Check rule of 3.6(11), which in general requires waiting till all
1184          --  full types have been seen.
1185
1186          if Ekind (E) = E_Record_Type or else Ekind (E) = E_Array_Type then
1187             Check_Aliased_Component_Types (E);
1188          end if;
1189
1190          --  Check preelaborable initialization for full type completing a
1191          --  private type for which pragma Preelaborable_Initialization given.
1192
1193          if Is_Type (E)
1194            and then Must_Have_Preelab_Init (E)
1195            and then not Has_Preelaborable_Initialization (E)
1196          then
1197             Error_Msg_N
1198               ("full view of & does not have preelaborable initialization", E);
1199          end if;
1200
1201          Next_Entity (E);
1202       end loop;
1203
1204       --  Ada 2005 (AI-216): The completion of an incomplete or private type
1205       --  declaration having a known_discriminant_part shall not be an
1206       --  Unchecked_Union type.
1207
1208       if Present (Vis_Decls) then
1209          Inspect_Unchecked_Union_Completion (Vis_Decls);
1210       end if;
1211
1212       if Present (Priv_Decls) then
1213          Inspect_Unchecked_Union_Completion (Priv_Decls);
1214       end if;
1215
1216       if Ekind (Id) = E_Generic_Package
1217         and then Nkind (Orig_Decl) = N_Generic_Package_Declaration
1218         and then Present (Priv_Decls)
1219       then
1220          --  Save global references in private declarations, ignoring the
1221          --  visible declarations that were processed earlier.
1222
1223          declare
1224             Orig_Spec : constant Node_Id := Specification (Orig_Decl);
1225             Save_Vis  : constant List_Id := Visible_Declarations (Orig_Spec);
1226             Save_Form : constant List_Id :=
1227                           Generic_Formal_Declarations (Orig_Decl);
1228
1229          begin
1230             Set_Visible_Declarations        (Orig_Spec, Empty_List);
1231             Set_Generic_Formal_Declarations (Orig_Decl, Empty_List);
1232             Save_Global_References          (Orig_Decl);
1233             Set_Generic_Formal_Declarations (Orig_Decl, Save_Form);
1234             Set_Visible_Declarations        (Orig_Spec, Save_Vis);
1235          end;
1236       end if;
1237
1238       Process_End_Label (N, 'e', Id);
1239
1240       --  Remove private_with_clauses of enclosing compilation unit, if they
1241       --  were installed.
1242
1243       if Private_With_Clauses_Installed then
1244          Remove_Private_With_Clauses (Cunit (Current_Sem_Unit));
1245       end if;
1246
1247       --  For the case of a library level package, we must go through all the
1248       --  entities clearing the indications that the value may be constant and
1249       --  not modified. Why? Because any client of this package may modify
1250       --  these values freely from anywhere. This also applies to any nested
1251       --  packages or generic packages.
1252
1253       --  For now we unconditionally clear constants for packages that are
1254       --  instances of generic packages. The reason is that we do not have the
1255       --  body yet, and we otherwise think things are unreferenced when they
1256       --  are not. This should be fixed sometime (the effect is not terrible,
1257       --  we just lose some warnings, and also some cases of value propagation)
1258       --  ???
1259
1260       if Is_Library_Level_Entity (Id)
1261         or else Is_Generic_Instance (Id)
1262       then
1263          Clear_Constants (Id, First_Entity (Id));
1264          Clear_Constants (Id, First_Private_Entity (Id));
1265       end if;
1266    end Analyze_Package_Specification;
1267
1268    --------------------------------------
1269    -- Analyze_Private_Type_Declaration --
1270    --------------------------------------
1271
1272    procedure Analyze_Private_Type_Declaration (N : Node_Id) is
1273       PF : constant Boolean   := Is_Pure (Enclosing_Lib_Unit_Entity);
1274       Id : constant Entity_Id := Defining_Identifier (N);
1275
1276    begin
1277       Generate_Definition (Id);
1278       Set_Is_Pure         (Id, PF);
1279       Init_Size_Align     (Id);
1280
1281       if (Ekind (Current_Scope) /= E_Package
1282           and then Ekind (Current_Scope) /= E_Generic_Package)
1283         or else In_Private_Part (Current_Scope)
1284       then
1285          Error_Msg_N ("invalid context for private declaration", N);
1286       end if;
1287
1288       New_Private_Type (N, Id, N);
1289       Set_Depends_On_Private (Id);
1290    end Analyze_Private_Type_Declaration;
1291
1292    ----------------------------------
1293    -- Check_Anonymous_Access_Types --
1294    ----------------------------------
1295
1296    procedure Check_Anonymous_Access_Types
1297      (Spec_Id : Entity_Id;
1298       P_Body  : Node_Id)
1299    is
1300       E  : Entity_Id;
1301       IR : Node_Id;
1302
1303    begin
1304       --  Itype references are only needed by gigi, to force elaboration of
1305       --  itypes. In the absence of code generation, they are not needed.
1306
1307       if not Expander_Active then
1308          return;
1309       end if;
1310
1311       E := First_Entity (Spec_Id);
1312       while Present (E) loop
1313          if Ekind (E) = E_Anonymous_Access_Type
1314            and then From_With_Type (E)
1315          then
1316             IR := Make_Itype_Reference (Sloc (P_Body));
1317             Set_Itype (IR, E);
1318
1319             if No (Declarations (P_Body)) then
1320                Set_Declarations (P_Body, New_List (IR));
1321             else
1322                Prepend (IR, Declarations (P_Body));
1323             end if;
1324          end if;
1325
1326          Next_Entity (E);
1327       end loop;
1328    end Check_Anonymous_Access_Types;
1329
1330    -------------------------------------------
1331    -- Declare_Inherited_Private_Subprograms --
1332    -------------------------------------------
1333
1334    procedure Declare_Inherited_Private_Subprograms (Id : Entity_Id) is
1335
1336       function Is_Primitive_Of (T : Entity_Id; S : Entity_Id) return Boolean;
1337       --  Check whether an inherited subprogram is an operation of an
1338       --  untagged derived type.
1339
1340       ---------------------
1341       -- Is_Primitive_Of --
1342       ---------------------
1343
1344       function Is_Primitive_Of (T : Entity_Id; S : Entity_Id) return Boolean is
1345          Formal : Entity_Id;
1346
1347       begin
1348          if Etype (S) = T then
1349             return True;
1350
1351          else
1352             Formal := First_Formal (S);
1353             while Present (Formal) loop
1354                if Etype (Formal) = T then
1355                   return True;
1356                end if;
1357
1358                Next_Formal (Formal);
1359             end loop;
1360
1361             return False;
1362          end if;
1363       end Is_Primitive_Of;
1364
1365       --  Local variables
1366
1367       E           : Entity_Id;
1368       Op_List     : Elist_Id;
1369       Op_Elmt     : Elmt_Id;
1370       Op_Elmt_2   : Elmt_Id;
1371       Prim_Op     : Entity_Id;
1372       New_Op      : Entity_Id := Empty;
1373       Parent_Subp : Entity_Id;
1374       Tag         : Entity_Id;
1375
1376    --  Start of processing for Declare_Inherited_Private_Subprograms
1377
1378    begin
1379       E := First_Entity (Id);
1380       while Present (E) loop
1381
1382          --  If the entity is a nonprivate type extension whose parent
1383          --  type is declared in an open scope, then the type may have
1384          --  inherited operations that now need to be made visible.
1385          --  Ditto if the entity is a formal derived type in a child unit.
1386
1387          if ((Is_Derived_Type (E) and then not Is_Private_Type (E))
1388                or else
1389                  (Nkind (Parent (E)) = N_Private_Extension_Declaration
1390                    and then Is_Generic_Type (E)))
1391            and then In_Open_Scopes (Scope (Etype (E)))
1392            and then E = Base_Type (E)
1393          then
1394             if Is_Tagged_Type (E) then
1395                Op_List := Primitive_Operations (E);
1396                New_Op  := Empty;
1397                Tag     := First_Tag_Component (E);
1398
1399                Op_Elmt := First_Elmt (Op_List);
1400                while Present (Op_Elmt) loop
1401                   Prim_Op := Node (Op_Elmt);
1402
1403                   --  Search primitives that are implicit operations with an
1404                   --  internal name whose parent operation has a normal name.
1405
1406                   if Present (Alias (Prim_Op))
1407                     and then Find_Dispatching_Type (Alias (Prim_Op)) /= E
1408                     and then not Comes_From_Source (Prim_Op)
1409                     and then Is_Internal_Name (Chars (Prim_Op))
1410                     and then not Is_Internal_Name (Chars (Alias (Prim_Op)))
1411                   then
1412                      Parent_Subp := Alias (Prim_Op);
1413
1414                      --  Case 1: Check if the type has also an explicit
1415                      --  overriding for this primitive.
1416
1417                      Op_Elmt_2 := Next_Elmt (Op_Elmt);
1418                      while Present (Op_Elmt_2) loop
1419                         if Chars (Node (Op_Elmt_2)) = Chars (Parent_Subp)
1420                           and then Type_Conformant (Prim_Op, Node (Op_Elmt_2))
1421                         then
1422                            --  The private inherited operation has been
1423                            --  overridden by an explicit subprogram: replace
1424                            --  the former by the latter.
1425
1426                            New_Op := Node (Op_Elmt_2);
1427                            Replace_Elmt (Op_Elmt, New_Op);
1428                            Remove_Elmt  (Op_List, Op_Elmt_2);
1429                            Set_Is_Overriding_Operation (New_Op);
1430
1431                            --  We don't need to inherit its dispatching slot.
1432                            --  Set_All_DT_Position has previously ensured that
1433                            --  the same slot was assigned to the two primitives
1434
1435                            if Present (Tag)
1436                              and then Present (DTC_Entity (New_Op))
1437                              and then Present (DTC_Entity (Prim_Op))
1438                            then
1439                               pragma Assert (DT_Position (New_Op)
1440                                               = DT_Position (Prim_Op));
1441                               null;
1442                            end if;
1443
1444                            goto Next_Primitive;
1445                         end if;
1446
1447                         Next_Elmt (Op_Elmt_2);
1448                      end loop;
1449
1450                      --   Case 2: We have not found any explicit overriding and
1451                      --   hence we need to declare the operation (i.e., make it
1452                      --   visible).
1453
1454                      Derive_Subprogram (New_Op, Alias (Prim_Op), E, Etype (E));
1455
1456                      --  Inherit the dispatching slot if E is already frozen
1457
1458                      if Is_Frozen (E)
1459                        and then Present (DTC_Entity (Alias (Prim_Op)))
1460                      then
1461                         Set_DTC_Entity_Value (E, New_Op);
1462                         Set_DT_Position (New_Op,
1463                           DT_Position (Alias (Prim_Op)));
1464                      end if;
1465
1466                      pragma Assert
1467                        (Is_Dispatching_Operation (New_Op)
1468                          and then Node (Last_Elmt (Op_List)) = New_Op);
1469
1470                      --  Substitute the new operation for the old one
1471                      --  in the type's primitive operations list. Since
1472                      --  the new operation was also just added to the end
1473                      --  of list, the last element must be removed.
1474
1475                      --  (Question: is there a simpler way of declaring
1476                      --  the operation, say by just replacing the name
1477                      --  of the earlier operation, reentering it in the
1478                      --  in the symbol table (how?), and marking it as
1479                      --  private???)
1480
1481                      Replace_Elmt (Op_Elmt, New_Op);
1482                      Remove_Last_Elmt (Op_List);
1483                   end if;
1484
1485                   <<Next_Primitive>>
1486                   Next_Elmt (Op_Elmt);
1487                end loop;
1488
1489                --  Generate listing showing the contents of the dispatch table
1490
1491                if Debug_Flag_ZZ then
1492                   Write_DT (E);
1493                end if;
1494
1495             else
1496                --   Non-tagged type, scan forward to locate
1497                --   inherited hidden operations.
1498
1499                Prim_Op := Next_Entity (E);
1500                while Present (Prim_Op) loop
1501                   if Is_Subprogram (Prim_Op)
1502                     and then Present (Alias (Prim_Op))
1503                     and then not Comes_From_Source (Prim_Op)
1504                     and then Is_Internal_Name (Chars (Prim_Op))
1505                     and then not Is_Internal_Name (Chars (Alias (Prim_Op)))
1506                     and then Is_Primitive_Of (E, Prim_Op)
1507                   then
1508                      Derive_Subprogram (New_Op, Alias (Prim_Op), E, Etype (E));
1509                   end if;
1510
1511                   Next_Entity (Prim_Op);
1512                end loop;
1513             end if;
1514          end if;
1515
1516          Next_Entity (E);
1517       end loop;
1518    end Declare_Inherited_Private_Subprograms;
1519
1520    -----------------------
1521    -- End_Package_Scope --
1522    -----------------------
1523
1524    procedure End_Package_Scope (P : Entity_Id) is
1525    begin
1526       Uninstall_Declarations (P);
1527       Pop_Scope;
1528    end End_Package_Scope;
1529
1530    ---------------------------
1531    -- Exchange_Declarations --
1532    ---------------------------
1533
1534    procedure Exchange_Declarations (Id : Entity_Id) is
1535       Full_Id : constant Entity_Id := Full_View (Id);
1536       H1      : constant Entity_Id := Homonym (Id);
1537       Next1   : constant Entity_Id := Next_Entity (Id);
1538       H2      : Entity_Id;
1539       Next2   : Entity_Id;
1540
1541    begin
1542       --  If missing full declaration for type, nothing to exchange
1543
1544       if No (Full_Id) then
1545          return;
1546       end if;
1547
1548       --  Otherwise complete the exchange, and preserve semantic links
1549
1550       Next2 := Next_Entity (Full_Id);
1551       H2    := Homonym (Full_Id);
1552
1553       --  Reset full declaration pointer to reflect the switched entities
1554       --  and readjust the next entity chains.
1555
1556       Exchange_Entities (Id, Full_Id);
1557
1558       Set_Next_Entity (Id, Next1);
1559       Set_Homonym     (Id, H1);
1560
1561       Set_Full_View   (Full_Id, Id);
1562       Set_Next_Entity (Full_Id, Next2);
1563       Set_Homonym     (Full_Id, H2);
1564    end Exchange_Declarations;
1565
1566    ------------------------------------------
1567    -- Inspect_Deferred_Constant_Completion --
1568    ------------------------------------------
1569
1570    procedure Inspect_Deferred_Constant_Completion (Decls : List_Id) is
1571       Decl   : Node_Id;
1572
1573    begin
1574       Decl := First (Decls);
1575       while Present (Decl) loop
1576
1577          --  Deferred constant signature
1578
1579          if Nkind (Decl) = N_Object_Declaration
1580            and then Constant_Present (Decl)
1581            and then No (Expression (Decl))
1582
1583             --  No need to check internally generated constants
1584
1585            and then Comes_From_Source (Decl)
1586
1587             --  The constant is not completed. A full object declaration
1588             --  or a pragma Import complete a deferred constant.
1589
1590            and then not Has_Completion (Defining_Identifier (Decl))
1591          then
1592             Error_Msg_N
1593               ("constant declaration requires initialization expression",
1594               Defining_Identifier (Decl));
1595          end if;
1596
1597          Decl := Next (Decl);
1598       end loop;
1599    end Inspect_Deferred_Constant_Completion;
1600
1601    ----------------------------
1602    -- Install_Package_Entity --
1603    ----------------------------
1604
1605    procedure Install_Package_Entity (Id : Entity_Id) is
1606    begin
1607       if not Is_Internal (Id) then
1608          if Debug_Flag_E then
1609             Write_Str ("Install: ");
1610             Write_Name (Chars (Id));
1611             Write_Eol;
1612          end if;
1613
1614          if not Is_Child_Unit (Id) then
1615             Set_Is_Immediately_Visible (Id);
1616          end if;
1617
1618       end if;
1619    end Install_Package_Entity;
1620
1621    ----------------------------------
1622    -- Install_Private_Declarations --
1623    ----------------------------------
1624
1625    procedure Install_Private_Declarations (P : Entity_Id) is
1626       Id        : Entity_Id;
1627       Priv_Elmt : Elmt_Id;
1628       Priv      : Entity_Id;
1629       Full      : Entity_Id;
1630
1631    begin
1632       --  First exchange declarations for private types, so that the
1633       --  full declaration is visible. For each private type, we check
1634       --  its Private_Dependents list and also exchange any subtypes of
1635       --  or derived types from it. Finally, if this is a Taft amendment
1636       --  type, the incomplete declaration is irrelevant, and we want to
1637       --  link the eventual full declaration with the original private
1638       --  one so we also skip the exchange.
1639
1640       Id := First_Entity (P);
1641       while Present (Id) and then Id /= First_Private_Entity (P) loop
1642          if Is_Private_Base_Type (Id)
1643            and then Comes_From_Source (Full_View (Id))
1644            and then Present (Full_View (Id))
1645            and then Scope (Full_View (Id)) = Scope (Id)
1646            and then Ekind (Full_View (Id)) /= E_Incomplete_Type
1647          then
1648             --  If there is a use-type clause on the private type, set the
1649             --  full view accordingly.
1650
1651             Set_In_Use (Full_View (Id), In_Use (Id));
1652             Full := Full_View (Id);
1653
1654             if Is_Private_Base_Type (Full)
1655               and then Has_Private_Declaration (Full)
1656               and then Nkind (Parent (Full)) = N_Full_Type_Declaration
1657               and then In_Open_Scopes (Scope (Etype (Full)))
1658               and then In_Package_Body (Current_Scope)
1659               and then not Is_Private_Type (Etype (Full))
1660             then
1661                --  This is the completion of a private type by a derivation
1662                --  from another private type which is not private anymore. This
1663                --  can only happen in a package nested within a child package,
1664                --  when the parent type is defined in the parent unit. At this
1665                --  point the current type is not private either, and we have to
1666                --  install the underlying full view, which is now visible.
1667
1668                if No (Full_View (Full))
1669                  and then Present (Underlying_Full_View (Full))
1670                then
1671                   Set_Full_View (Id, Underlying_Full_View (Full));
1672                   Set_Underlying_Full_View (Full, Empty);
1673                   Set_Is_Frozen (Full_View (Id));
1674                end if;
1675             end if;
1676
1677             Priv_Elmt := First_Elmt (Private_Dependents (Id));
1678
1679             Exchange_Declarations (Id);
1680             Set_Is_Immediately_Visible (Id);
1681
1682             while Present (Priv_Elmt) loop
1683                Priv := Node (Priv_Elmt);
1684
1685                --  Before the exchange, verify that the presence of the
1686                --  Full_View field. It will be empty if the entity
1687                --  has already been installed due to a previous call.
1688
1689                if Present (Full_View (Priv))
1690                  and then Is_Visible_Dependent (Priv)
1691                then
1692
1693                   --  For each subtype that is swapped, we also swap the
1694                   --  reference to it in Private_Dependents, to allow access
1695                   --  to it when we swap them out in End_Package_Scope.
1696
1697                   Replace_Elmt (Priv_Elmt, Full_View (Priv));
1698                   Exchange_Declarations (Priv);
1699                   Set_Is_Immediately_Visible
1700                     (Priv, In_Open_Scopes (Scope (Priv)));
1701                   Set_Is_Potentially_Use_Visible
1702                     (Priv, Is_Potentially_Use_Visible (Node (Priv_Elmt)));
1703                end if;
1704
1705                Next_Elmt (Priv_Elmt);
1706             end loop;
1707          end if;
1708
1709          Next_Entity (Id);
1710       end loop;
1711
1712       --  Next make other declarations in the private part visible as well
1713
1714       Id := First_Private_Entity (P);
1715       while Present (Id) loop
1716          Install_Package_Entity (Id);
1717          Set_Is_Hidden (Id, False);
1718          Next_Entity (Id);
1719       end loop;
1720
1721       --  Indicate that the private part is currently visible, so it can be
1722       --  properly reset on exit.
1723
1724       Set_In_Private_Part (P);
1725    end Install_Private_Declarations;
1726
1727    ----------------------------------
1728    -- Install_Visible_Declarations --
1729    ----------------------------------
1730
1731    procedure Install_Visible_Declarations (P : Entity_Id) is
1732       Id          : Entity_Id;
1733       Last_Entity : Entity_Id;
1734
1735    begin
1736       pragma Assert
1737         (Is_Package_Or_Generic_Package (P) or else Is_Record_Type (P));
1738
1739       if Is_Package_Or_Generic_Package (P) then
1740          Last_Entity := First_Private_Entity (P);
1741       else
1742          Last_Entity := Empty;
1743       end if;
1744
1745       Id := First_Entity (P);
1746       while Present (Id) and then Id /= Last_Entity loop
1747          Install_Package_Entity (Id);
1748          Next_Entity (Id);
1749       end loop;
1750    end Install_Visible_Declarations;
1751
1752    --------------------------
1753    -- Is_Private_Base_Type --
1754    --------------------------
1755
1756    function Is_Private_Base_Type (E : Entity_Id) return Boolean is
1757    begin
1758       return Ekind (E) = E_Private_Type
1759         or else Ekind (E) = E_Limited_Private_Type
1760         or else Ekind (E) = E_Record_Type_With_Private;
1761    end Is_Private_Base_Type;
1762
1763    --------------------------
1764    -- Is_Visible_Dependent --
1765    --------------------------
1766
1767    function Is_Visible_Dependent (Dep : Entity_Id) return Boolean
1768    is
1769       S : constant Entity_Id := Scope (Dep);
1770
1771    begin
1772       --  Renamings created for actual types have the visibility of the
1773       --  actual.
1774
1775       if Ekind (S) = E_Package
1776         and then Is_Generic_Instance (S)
1777         and then (Is_Generic_Actual_Type (Dep)
1778                    or else Is_Generic_Actual_Type (Full_View (Dep)))
1779       then
1780          return True;
1781
1782       elsif not (Is_Derived_Type (Dep))
1783         and then Is_Derived_Type (Full_View (Dep))
1784       then
1785          --  When instantiating a package body, the scope stack is empty,
1786          --  so check instead whether the dependent type is defined in
1787          --  the same scope as the instance itself.
1788
1789          return In_Open_Scopes (S)
1790            or else (Is_Generic_Instance (Current_Scope)
1791               and then Scope (Dep) = Scope (Current_Scope));
1792       else
1793          return True;
1794       end if;
1795    end Is_Visible_Dependent;
1796
1797    ----------------------------
1798    -- May_Need_Implicit_Body --
1799    ----------------------------
1800
1801    procedure May_Need_Implicit_Body (E : Entity_Id) is
1802       P     : constant Node_Id := Unit_Declaration_Node (E);
1803       S     : constant Node_Id := Parent (P);
1804       B     : Node_Id;
1805       Decls : List_Id;
1806
1807    begin
1808       if not Has_Completion (E)
1809         and then Nkind (P) = N_Package_Declaration
1810         and then (Present (Activation_Chain_Entity (P)) or else Has_RACW (E))
1811       then
1812          B :=
1813            Make_Package_Body (Sloc (E),
1814              Defining_Unit_Name => Make_Defining_Identifier (Sloc (E),
1815                Chars => Chars (E)),
1816              Declarations  => New_List);
1817
1818          if Nkind (S) = N_Package_Specification then
1819             if Present (Private_Declarations (S)) then
1820                Decls := Private_Declarations (S);
1821             else
1822                Decls := Visible_Declarations (S);
1823             end if;
1824          else
1825             Decls := Declarations (S);
1826          end if;
1827
1828          Append (B, Decls);
1829          Analyze (B);
1830       end if;
1831    end May_Need_Implicit_Body;
1832
1833    ----------------------
1834    -- New_Private_Type --
1835    ----------------------
1836
1837    procedure New_Private_Type (N : Node_Id; Id : Entity_Id; Def : Node_Id) is
1838    begin
1839       Enter_Name (Id);
1840
1841       if Limited_Present (Def) then
1842          Set_Ekind (Id, E_Limited_Private_Type);
1843       else
1844          Set_Ekind (Id, E_Private_Type);
1845       end if;
1846
1847       Set_Etype              (Id, Id);
1848       Set_Has_Delayed_Freeze (Id);
1849       Set_Is_First_Subtype   (Id);
1850       Init_Size_Align        (Id);
1851
1852       Set_Is_Constrained (Id,
1853         No (Discriminant_Specifications (N))
1854           and then not Unknown_Discriminants_Present (N));
1855
1856       --  Set tagged flag before processing discriminants, to catch
1857       --  illegal usage.
1858
1859       Set_Is_Tagged_Type (Id, Tagged_Present (Def));
1860
1861       Set_Discriminant_Constraint (Id, No_Elist);
1862       Set_Stored_Constraint (Id, No_Elist);
1863
1864       if Present (Discriminant_Specifications (N)) then
1865          Push_Scope (Id);
1866          Process_Discriminants (N);
1867          End_Scope;
1868
1869       elsif Unknown_Discriminants_Present (N) then
1870          Set_Has_Unknown_Discriminants (Id);
1871       end if;
1872
1873       Set_Private_Dependents (Id, New_Elmt_List);
1874
1875       if Tagged_Present (Def) then
1876          Set_Ekind                (Id, E_Record_Type_With_Private);
1877          Make_Class_Wide_Type     (Id);
1878          Set_Primitive_Operations (Id, New_Elmt_List);
1879          Set_Is_Abstract_Type     (Id, Abstract_Present (Def));
1880          Set_Is_Limited_Record    (Id, Limited_Present (Def));
1881          Set_Has_Delayed_Freeze   (Id, True);
1882
1883       elsif Abstract_Present (Def) then
1884          Error_Msg_N ("only a tagged type can be abstract", N);
1885       end if;
1886    end New_Private_Type;
1887
1888    ----------------------------
1889    -- Uninstall_Declarations --
1890    ----------------------------
1891
1892    procedure Uninstall_Declarations (P : Entity_Id) is
1893       Decl      : constant Node_Id := Unit_Declaration_Node (P);
1894       Id        : Entity_Id;
1895       Full      : Entity_Id;
1896       Priv_Elmt : Elmt_Id;
1897       Priv_Sub  : Entity_Id;
1898
1899       procedure Preserve_Full_Attributes (Priv, Full : Entity_Id);
1900       --  Copy to the private declaration the attributes of the full view
1901       --  that need to be available for the partial view also.
1902
1903       function Type_In_Use (T : Entity_Id) return Boolean;
1904       --  Check whether type or base type appear in an active use_type clause
1905
1906       ------------------------------
1907       -- Preserve_Full_Attributes --
1908       ------------------------------
1909
1910       procedure Preserve_Full_Attributes (Priv, Full : Entity_Id) is
1911          Priv_Is_Base_Type : constant Boolean := Priv = Base_Type (Priv);
1912
1913       begin
1914          Set_Size_Info (Priv, (Full));
1915          Set_RM_Size                 (Priv, RM_Size (Full));
1916          Set_Size_Known_At_Compile_Time
1917                                      (Priv, Size_Known_At_Compile_Time (Full));
1918          Set_Is_Volatile             (Priv, Is_Volatile                (Full));
1919          Set_Treat_As_Volatile       (Priv, Treat_As_Volatile          (Full));
1920          Set_Is_Ada_2005_Only        (Priv, Is_Ada_2005_Only           (Full));
1921          Set_Has_Pragma_Unreferenced (Priv, Has_Pragma_Unreferenced    (Full));
1922          Set_Has_Pragma_Unreferenced_Objects
1923                                      (Priv, Has_Pragma_Unreferenced_Objects
1924                                                                        (Full));
1925          if Is_Unchecked_Union (Full) then
1926             Set_Is_Unchecked_Union (Base_Type (Priv));
1927          end if;
1928          --  Why is atomic not copied here ???
1929
1930          if Referenced (Full) then
1931             Set_Referenced (Priv);
1932          end if;
1933
1934          if Priv_Is_Base_Type then
1935             Set_Is_Controlled (Priv, Is_Controlled (Base_Type (Full)));
1936             Set_Finalize_Storage_Only (Priv, Finalize_Storage_Only
1937                                                            (Base_Type (Full)));
1938             Set_Has_Task (Priv, Has_Task (Base_Type (Full)));
1939             Set_Has_Controlled_Component (Priv, Has_Controlled_Component
1940                                                            (Base_Type (Full)));
1941          end if;
1942
1943          Set_Freeze_Node (Priv, Freeze_Node (Full));
1944
1945          if Is_Tagged_Type (Priv)
1946            and then Is_Tagged_Type (Full)
1947            and then not Error_Posted (Full)
1948          then
1949             if Priv_Is_Base_Type then
1950
1951                --  Ada 2005 (AI-345): The full view of a type implementing
1952                --  an interface can be a task type.
1953
1954                --    type T is new I with private;
1955                --  private
1956                --    task type T is new I with ...
1957
1958                if Is_Interface (Etype (Priv))
1959                  and then Is_Concurrent_Type (Base_Type (Full))
1960                then
1961                   --  Protect the frontend against previous errors
1962
1963                   if Present (Corresponding_Record_Type
1964                                (Base_Type (Full)))
1965                   then
1966                      Set_Access_Disp_Table
1967                        (Priv, Access_Disp_Table
1968                                (Corresponding_Record_Type (Base_Type (Full))));
1969
1970                   --  Generic context, or previous errors
1971
1972                   else
1973                      null;
1974                   end if;
1975
1976                else
1977                   Set_Access_Disp_Table
1978                     (Priv, Access_Disp_Table (Base_Type (Full)));
1979                end if;
1980             end if;
1981
1982             if Is_Tagged_Type (Priv) then
1983
1984                --  If the type is tagged, the tag itself must be available
1985                --  on the partial view, for expansion purposes.
1986
1987                Set_First_Entity (Priv, First_Entity (Full));
1988
1989                --  If there are discriminants in the partial view, these remain
1990                --  visible. Otherwise only the tag itself is visible, and there
1991                --  are no nameable components in the partial view.
1992
1993                if No (Last_Entity (Priv)) then
1994                   Set_Last_Entity (Priv, First_Entity (Priv));
1995                end if;
1996             end if;
1997
1998             Set_Has_Discriminants (Priv, Has_Discriminants (Full));
1999          end if;
2000       end Preserve_Full_Attributes;
2001
2002       -----------------
2003       -- Type_In_Use --
2004       -----------------
2005
2006       function Type_In_Use (T : Entity_Id) return Boolean is
2007       begin
2008          return Scope (Base_Type (T)) = P
2009            and then (In_Use (T) or else In_Use (Base_Type (T)));
2010       end Type_In_Use;
2011
2012    --  Start of processing for Uninstall_Declarations
2013
2014    begin
2015       Id := First_Entity (P);
2016       while Present (Id) and then Id /= First_Private_Entity (P) loop
2017          if Debug_Flag_E then
2018             Write_Str ("unlinking visible entity ");
2019             Write_Int (Int (Id));
2020             Write_Eol;
2021          end if;
2022
2023          --  On  exit from the package scope, we must preserve the visibility
2024          --  established by use clauses in the current scope. Two cases:
2025
2026          --  a) If the entity is an operator, it may be a primitive operator of
2027          --  a type for which there is a visible use-type clause.
2028
2029          --  b) for other entities, their use-visibility is determined by a
2030          --  visible use clause for the package itself. For a generic instance,
2031          --  the instantiation of the formals appears in the visible part,
2032          --  but the formals are private and remain so.
2033
2034          if Ekind (Id) = E_Function
2035            and then  Is_Operator_Symbol_Name (Chars (Id))
2036            and then not Is_Hidden (Id)
2037            and then not Error_Posted (Id)
2038          then
2039             Set_Is_Potentially_Use_Visible (Id,
2040               In_Use (P)
2041               or else Type_In_Use (Etype (Id))
2042               or else Type_In_Use (Etype (First_Formal (Id)))
2043               or else (Present (Next_Formal (First_Formal (Id)))
2044                          and then
2045                            Type_In_Use
2046                              (Etype (Next_Formal (First_Formal (Id))))));
2047          else
2048             if In_Use (P) and then not Is_Hidden (Id) then
2049
2050                --  A child unit of a use-visible package remains use-visible
2051                --  only if it is itself a visible child unit. Otherwise it
2052                --  would remain visible in other contexts where P is use-
2053                --  visible, because once compiled it stays in the entity list
2054                --  of its parent unit.
2055
2056                if Is_Child_Unit (Id) then
2057                   Set_Is_Potentially_Use_Visible (Id,
2058                     Is_Visible_Child_Unit (Id));
2059                else
2060                   Set_Is_Potentially_Use_Visible (Id);
2061                end if;
2062
2063             else
2064                Set_Is_Potentially_Use_Visible (Id, False);
2065             end if;
2066          end if;
2067
2068          --  Local entities are not immediately visible outside of the package
2069
2070          Set_Is_Immediately_Visible (Id, False);
2071
2072          --  If this is a private type with a full view (for example a local
2073          --  subtype of a private type declared elsewhere), ensure that the
2074          --  full view is also removed from visibility: it may be exposed when
2075          --  swapping views in an instantiation.
2076
2077          if Is_Type (Id)
2078            and then Present (Full_View (Id))
2079          then
2080             Set_Is_Immediately_Visible (Full_View (Id), False);
2081          end if;
2082
2083          if Is_Tagged_Type (Id) and then Ekind (Id) = E_Record_Type then
2084             Check_Abstract_Overriding (Id);
2085             Check_Conventions (Id);
2086          end if;
2087
2088          if (Ekind (Id) = E_Private_Type
2089                or else Ekind (Id) = E_Limited_Private_Type)
2090            and then No (Full_View (Id))
2091            and then not Is_Generic_Type (Id)
2092            and then not Is_Derived_Type (Id)
2093          then
2094             Error_Msg_N ("missing full declaration for private type&", Id);
2095
2096          elsif Ekind (Id) = E_Record_Type_With_Private
2097            and then not Is_Generic_Type (Id)
2098            and then No (Full_View (Id))
2099          then
2100             if Nkind (Parent (Id)) = N_Private_Type_Declaration then
2101                Error_Msg_N ("missing full declaration for private type&", Id);
2102             else
2103                Error_Msg_N
2104                  ("missing full declaration for private extension", Id);
2105             end if;
2106
2107          elsif Ekind (Id) = E_Constant
2108            and then No (Constant_Value (Id))
2109            and then No (Full_View (Id))
2110            and then not Is_Imported (Id)
2111            and then (Nkind (Parent (Id)) /= N_Object_Declaration
2112                       or else not No_Initialization (Parent (Id)))
2113          then
2114             if not Has_Private_Declaration (Etype (Id)) then
2115
2116                --  We assume that the user did not not intend a deferred
2117                --  constant declaration, and the expression is just missing.
2118
2119                Error_Msg_N
2120                  ("constant declaration requires initialization expression",
2121                    Parent (Id));
2122
2123                if Is_Limited_Type (Etype (Id)) then
2124                   Error_Msg_N
2125                     ("\if variable intended, remove CONSTANT from declaration",
2126                     Parent (Id));
2127                end if;
2128
2129             else
2130                Error_Msg_N
2131                   ("missing full declaration for deferred constant (RM 7.4)",
2132                      Id);
2133
2134                if Is_Limited_Type (Etype (Id)) then
2135                   Error_Msg_N
2136                     ("\if variable intended, remove CONSTANT from declaration",
2137                     Parent (Id));
2138                end if;
2139             end if;
2140          end if;
2141
2142          Next_Entity (Id);
2143       end loop;
2144
2145       --  If the specification was installed as the parent of a public child
2146       --  unit, the private declarations were not installed, and there is
2147       --  nothing to do.
2148
2149       if not In_Private_Part (P) then
2150          return;
2151       else
2152          Set_In_Private_Part (P, False);
2153       end if;
2154
2155       --  Make private entities invisible and exchange full and private
2156       --  declarations for private types.
2157
2158       while Present (Id) loop
2159          if Debug_Flag_E then
2160             Write_Str ("unlinking private entity ");
2161             Write_Int (Int (Id));
2162             Write_Eol;
2163          end if;
2164
2165          if Is_Tagged_Type (Id) and then Ekind (Id) = E_Record_Type then
2166             Check_Abstract_Overriding (Id);
2167             Check_Conventions (Id);
2168          end if;
2169
2170          Set_Is_Immediately_Visible (Id, False);
2171
2172          if Is_Private_Base_Type (Id)
2173            and then Present (Full_View (Id))
2174          then
2175             Full := Full_View (Id);
2176
2177             --  If the partial view is not declared in the visible part
2178             --  of the package (as is the case when it is a type derived
2179             --  from some other private type in the private part of the
2180             --  current package), no exchange takes place.
2181
2182             if No (Parent (Id))
2183               or else List_Containing (Parent (Id))
2184                 /= Visible_Declarations (Specification (Decl))
2185             then
2186                goto Next_Id;
2187             end if;
2188
2189             --  The entry in the private part points to the full declaration,
2190             --  which is currently visible. Exchange them so only the private
2191             --  type declaration remains accessible, and link private and
2192             --  full declaration in the opposite direction. Before the actual
2193             --  exchange, we copy back attributes of the full view that
2194             --  must be available to the partial view too.
2195
2196             Preserve_Full_Attributes (Id, Full);
2197
2198             Set_Is_Potentially_Use_Visible (Id, In_Use (P));
2199
2200             if  Is_Indefinite_Subtype (Full)
2201               and then not Is_Indefinite_Subtype (Id)
2202             then
2203                Error_Msg_N
2204                  ("full view of type must be definite subtype", Full);
2205             end if;
2206
2207             Priv_Elmt := First_Elmt (Private_Dependents (Id));
2208
2209             --  Swap out the subtypes and derived types of Id that were
2210             --  compiled in this scope, or installed previously by
2211             --  Install_Private_Declarations.
2212             --  Before we do the swap, we verify the presence of the
2213             --  Full_View field which may be empty due to a swap by
2214             --  a previous call to End_Package_Scope (e.g. from the
2215             --  freezing mechanism).
2216
2217             while Present (Priv_Elmt) loop
2218                Priv_Sub := Node (Priv_Elmt);
2219
2220                if Present (Full_View (Priv_Sub)) then
2221
2222                   if Scope (Priv_Sub) = P
2223                      or else not In_Open_Scopes (Scope (Priv_Sub))
2224                   then
2225                      Set_Is_Immediately_Visible (Priv_Sub, False);
2226                   end if;
2227
2228                   if Is_Visible_Dependent (Priv_Sub) then
2229                      Preserve_Full_Attributes
2230                        (Priv_Sub, Full_View (Priv_Sub));
2231                      Replace_Elmt (Priv_Elmt, Full_View (Priv_Sub));
2232                      Exchange_Declarations (Priv_Sub);
2233                   end if;
2234                end if;
2235
2236                Next_Elmt (Priv_Elmt);
2237             end loop;
2238
2239             --  Now restore the type itself to its private view
2240
2241             Exchange_Declarations (Id);
2242
2243          elsif Ekind (Id) = E_Incomplete_Type
2244            and then No (Full_View (Id))
2245          then
2246             --  Mark Taft amendment types
2247
2248             Set_Has_Completion_In_Body (Id);
2249
2250          elsif not Is_Child_Unit (Id)
2251            and then (not Is_Private_Type (Id)
2252                       or else No (Full_View (Id)))
2253          then
2254             Set_Is_Hidden (Id);
2255             Set_Is_Potentially_Use_Visible (Id, False);
2256          end if;
2257
2258          <<Next_Id>>
2259             Next_Entity (Id);
2260       end loop;
2261    end Uninstall_Declarations;
2262
2263    ------------------------
2264    -- Unit_Requires_Body --
2265    ------------------------
2266
2267    function Unit_Requires_Body (P : Entity_Id) return Boolean is
2268       E : Entity_Id;
2269
2270    begin
2271       --  Imported entity never requires body. Right now, only
2272       --  subprograms can be imported, but perhaps in the future
2273       --  we will allow import of packages.
2274
2275       if Is_Imported (P) then
2276          return False;
2277
2278       --  Body required if library package with pragma Elaborate_Body
2279
2280       elsif Has_Pragma_Elaborate_Body (P) then
2281          return True;
2282
2283       --  Body required if subprogram
2284
2285       elsif Is_Subprogram (P) or else Is_Generic_Subprogram (P) then
2286          return True;
2287
2288       --  Treat a block as requiring a body
2289
2290       elsif Ekind (P) = E_Block then
2291          return True;
2292
2293       elsif Ekind (P) = E_Package
2294         and then Nkind (Parent (P)) = N_Package_Specification
2295         and then Present (Generic_Parent (Parent (P)))
2296       then
2297          declare
2298             G_P : constant Entity_Id := Generic_Parent (Parent (P));
2299          begin
2300             if Has_Pragma_Elaborate_Body (G_P) then
2301                return True;
2302             end if;
2303          end;
2304       end if;
2305
2306       --  Otherwise search entity chain for entity requiring completion
2307
2308       E := First_Entity (P);
2309       while Present (E) loop
2310
2311          --  Always ignore child units. Child units get added to the entity
2312          --  list of a parent unit, but are not original entities of the
2313          --  parent, and so do not affect whether the parent needs a body.
2314
2315          if Is_Child_Unit (E) then
2316             null;
2317
2318          --  Ignore formal packages and their renamings
2319
2320          elsif Ekind (E) = E_Package
2321            and then Nkind (Original_Node (Unit_Declaration_Node (E))) =
2322                                                 N_Formal_Package_Declaration
2323          then
2324             null;
2325
2326          --  Otherwise test to see if entity requires a completion.
2327          --  Note that subprogram entities whose declaration does not come
2328          --  from source are ignored here on the basis that we assume the
2329          --  expander will provide an implicit completion at some point.
2330
2331          elsif (Is_Overloadable (E)
2332                and then Ekind (E) /= E_Enumeration_Literal
2333                and then Ekind (E) /= E_Operator
2334                and then not Is_Abstract_Subprogram (E)
2335                and then not Has_Completion (E)
2336                and then Comes_From_Source (Parent (E)))
2337
2338            or else
2339              (Ekind (E) = E_Package
2340                and then E /= P
2341                and then not Has_Completion (E)
2342                and then Unit_Requires_Body (E))
2343
2344            or else
2345              (Ekind (E) = E_Incomplete_Type and then No (Full_View (E)))
2346
2347            or else
2348             ((Ekind (E) = E_Task_Type or else
2349               Ekind (E) = E_Protected_Type)
2350                and then not Has_Completion (E))
2351
2352            or else
2353              (Ekind (E) = E_Generic_Package and then E /= P
2354                and then not Has_Completion (E)
2355                and then Unit_Requires_Body (E))
2356
2357            or else
2358              (Is_Generic_Subprogram (E)
2359                and then not Has_Completion (E))
2360
2361          then
2362             return True;
2363
2364          --  Entity that does not require completion
2365
2366          else
2367             null;
2368          end if;
2369
2370          Next_Entity (E);
2371       end loop;
2372
2373       return False;
2374    end Unit_Requires_Body;
2375
2376 end Sem_Ch7;