OSDN Git Service

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