[multiple changes]
[platform/upstream/gcc.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-2016, 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 dispatch
29 --  tables for tagged types.
30
31 with Aspects;   use Aspects;
32 with Atree;     use Atree;
33 with Contracts; use Contracts;
34 with Debug;     use Debug;
35 with Einfo;     use Einfo;
36 with Elists;    use Elists;
37 with Errout;    use Errout;
38 with Exp_Disp;  use Exp_Disp;
39 with Exp_Dist;  use Exp_Dist;
40 with Exp_Dbug;  use Exp_Dbug;
41 with Ghost;     use Ghost;
42 with Lib;       use Lib;
43 with Lib.Xref;  use Lib.Xref;
44 with Namet;     use Namet;
45 with Nmake;     use Nmake;
46 with Nlists;    use Nlists;
47 with Opt;       use Opt;
48 with Output;    use Output;
49 with Restrict;  use Restrict;
50 with Rtsfind;   use Rtsfind;
51 with Sem;       use Sem;
52 with Sem_Aux;   use Sem_Aux;
53 with Sem_Cat;   use Sem_Cat;
54 with Sem_Ch3;   use Sem_Ch3;
55 with Sem_Ch6;   use Sem_Ch6;
56 with Sem_Ch8;   use Sem_Ch8;
57 with Sem_Ch10;  use Sem_Ch10;
58 with Sem_Ch12;  use Sem_Ch12;
59 with Sem_Ch13;  use Sem_Ch13;
60 with Sem_Disp;  use Sem_Disp;
61 with Sem_Eval;  use Sem_Eval;
62 with Sem_Prag;  use Sem_Prag;
63 with Sem_Util;  use Sem_Util;
64 with Sem_Warn;  use Sem_Warn;
65 with Snames;    use Snames;
66 with Stand;     use Stand;
67 with Sinfo;     use Sinfo;
68 with Sinput;    use Sinput;
69 with Style;
70 with Uintp;     use Uintp;
71
72 package body Sem_Ch7 is
73
74    -----------------------------------
75    -- Handling private declarations --
76    -----------------------------------
77
78    --  The principle that each entity has a single defining occurrence clashes
79    --  with the presence of two separate definitions for private types: the
80    --  first is the private type declaration, and the second is the full type
81    --  declaration. It is important that all references to the type point to
82    --  the same defining occurrence, namely the first one. To enforce the two
83    --  separate views of the entity, the corresponding information is swapped
84    --  between the two declarations. Outside of the package, the defining
85    --  occurrence only contains the private declaration information, while in
86    --  the private part and the body of the package the defining occurrence
87    --  contains the full declaration. To simplify the swap, the defining
88    --  occurrence that currently holds the private declaration points to the
89    --  full declaration. During semantic processing the defining occurrence
90    --  also points to a list of private dependents, that is to say access types
91    --  or composite types whose designated types or component types are
92    --  subtypes or derived types of the private type in question. After the
93    --  full declaration has been seen, the private dependents are updated to
94    --  indicate that they have full definitions.
95
96    -----------------------
97    -- Local Subprograms --
98    -----------------------
99
100    procedure Analyze_Package_Body_Helper (N : Node_Id);
101    --  Does all the real work of Analyze_Package_Body
102
103    procedure Check_Anonymous_Access_Types
104      (Spec_Id : Entity_Id;
105       P_Body  : Node_Id);
106    --  If the spec of a package has a limited_with_clause, it may declare
107    --  anonymous access types whose designated type is a limited view, such an
108    --  anonymous access return type for a function. This access type cannot be
109    --  elaborated in the spec itself, but it may need an itype reference if it
110    --  is used within a nested scope. In that case the itype reference is
111    --  created at the beginning of the corresponding package body and inserted
112    --  before other body declarations.
113
114    procedure Declare_Inherited_Private_Subprograms (Id : Entity_Id);
115    --  Called upon entering the private part of a public child package and the
116    --  body of a nested package, to potentially declare certain inherited
117    --  subprograms that were inherited by types in the visible part, but whose
118    --  declaration was deferred because the parent operation was private and
119    --  not visible at that point. These subprograms are located by traversing
120    --  the visible part declarations looking for non-private type extensions
121    --  and then examining each of the primitive operations of such types to
122    --  find those that were inherited but declared with a special internal
123    --  name. Each such operation is now declared as an operation with a normal
124    --  name (using the name of the parent operation) and replaces the previous
125    --  implicit operation in the primitive operations list of the type. If the
126    --  inherited private operation has been overridden, then it's replaced by
127    --  the overriding operation.
128
129    procedure Install_Package_Entity (Id : Entity_Id);
130    --  Supporting procedure for Install_{Visible,Private}_Declarations. Places
131    --  one entity on its visibility chain, and recurses on the visible part if
132    --  the entity is an inner package.
133
134    function Is_Private_Base_Type (E : Entity_Id) return Boolean;
135    --  True for a private type that is not a subtype
136
137    function Is_Visible_Dependent (Dep : Entity_Id) return Boolean;
138    --  If the private dependent is a private type whose full view is derived
139    --  from the parent type, its full properties are revealed only if we are in
140    --  the immediate scope of the private dependent. Should this predicate be
141    --  tightened further???
142
143    function Requires_Completion_In_Body
144      (Id                 : Entity_Id;
145       Pack_Id            : Entity_Id;
146       Do_Abstract_States : Boolean := False) return Boolean;
147    --  Subsidiary to routines Unit_Requires_Body and Unit_Requires_Body_Info.
148    --  Determine whether entity Id declared in package spec Pack_Id requires
149    --  completion in a package body. Flag Do_Abstract_Stats should be set when
150    --  abstract states are to be considered in the completion test.
151
152    procedure Unit_Requires_Body_Info (Pack_Id : Entity_Id);
153    --  Outputs info messages showing why package Pack_Id requires a body. The
154    --  caller has checked that the switch requesting this information is set,
155    --  and that the package does indeed require a body.
156
157    --------------------------
158    -- Analyze_Package_Body --
159    --------------------------
160
161    procedure Analyze_Package_Body (N : Node_Id) is
162       Loc : constant Source_Ptr := Sloc (N);
163
164    begin
165       if Debug_Flag_C then
166          Write_Str ("==> package body ");
167          Write_Name (Chars (Defining_Entity (N)));
168          Write_Str (" from ");
169          Write_Location (Loc);
170          Write_Eol;
171          Indent;
172       end if;
173
174       --  The real work is split out into the helper, so it can do "return;"
175       --  without skipping the debug output.
176
177       Analyze_Package_Body_Helper (N);
178
179       if Debug_Flag_C then
180          Outdent;
181          Write_Str ("<== package body ");
182          Write_Name (Chars (Defining_Entity (N)));
183          Write_Str (" from ");
184          Write_Location (Loc);
185          Write_Eol;
186       end if;
187    end Analyze_Package_Body;
188
189    ---------------------------------
190    -- Analyze_Package_Body_Helper --
191    ---------------------------------
192
193    procedure Analyze_Package_Body_Helper (N : Node_Id) is
194       procedure Hide_Public_Entities (Decls : List_Id);
195       --  Attempt to hide all public entities found in declarative list Decls
196       --  by resetting their Is_Public flag to False depending on whether the
197       --  entities are not referenced by inlined or generic bodies. This kind
198       --  of processing is a conservative approximation and may still leave
199       --  certain entities externally visible.
200
201       procedure Install_Composite_Operations (P : Entity_Id);
202       --  Composite types declared in the current scope may depend on types
203       --  that were private at the point of declaration, and whose full view
204       --  is now in scope. Indicate that the corresponding operations on the
205       --  composite type are available.
206
207       --------------------------
208       -- Hide_Public_Entities --
209       --------------------------
210
211       procedure Hide_Public_Entities (Decls : List_Id) is
212          function Contains_Subp_Or_Const_Refs (N : Node_Id) return Boolean;
213          --  Subsidiary to routine Has_Referencer. Determine whether a node
214          --  contains a reference to a subprogram or a non-static constant.
215          --  WARNING: this is a very expensive routine as it performs a full
216          --  tree traversal.
217
218          function Has_Referencer
219            (Decls     : List_Id;
220             Top_Level : Boolean := False) return Boolean;
221          --  A "referencer" is a construct which may reference a previous
222          --  declaration. Examine all declarations in list Decls in reverse
223          --  and determine whether once such referencer exists. All entities
224          --  in the range Last (Decls) .. Referencer are hidden from external
225          --  visibility.
226
227          ---------------------------------
228          -- Contains_Subp_Or_Const_Refs --
229          ---------------------------------
230
231          function Contains_Subp_Or_Const_Refs (N : Node_Id) return Boolean is
232             Reference_Seen : Boolean := False;
233
234             function Is_Subp_Or_Const_Ref
235               (N : Node_Id) return Traverse_Result;
236             --  Determine whether a node denotes a reference to a subprogram or
237             --  a non-static constant.
238
239             --------------------------
240             -- Is_Subp_Or_Const_Ref --
241             --------------------------
242
243             function Is_Subp_Or_Const_Ref
244               (N : Node_Id) return Traverse_Result
245             is
246                Val : Node_Id;
247
248             begin
249                --  Detect a reference of the form
250                --    Subp_Call
251
252                if Nkind (N) in N_Subprogram_Call
253                  and then Is_Entity_Name (Name (N))
254                then
255                   Reference_Seen := True;
256                   return Abandon;
257
258                --  Detect a reference of the form
259                --    Subp'Some_Attribute
260
261                elsif Nkind (N) = N_Attribute_Reference
262                  and then Is_Entity_Name (Prefix (N))
263                  and then Present (Entity (Prefix (N)))
264                  and then Is_Subprogram (Entity (Prefix (N)))
265                then
266                   Reference_Seen := True;
267                   return Abandon;
268
269                --  Detect the use of a non-static constant
270
271                elsif Is_Entity_Name (N)
272                  and then Present (Entity (N))
273                  and then Ekind (Entity (N)) = E_Constant
274                then
275                   Val := Constant_Value (Entity (N));
276
277                   if Present (Val)
278                     and then not Compile_Time_Known_Value (Val)
279                   then
280                      Reference_Seen := True;
281                      return Abandon;
282                   end if;
283                end if;
284
285                return OK;
286             end Is_Subp_Or_Const_Ref;
287
288             procedure Find_Subp_Or_Const_Ref is
289               new Traverse_Proc (Is_Subp_Or_Const_Ref);
290
291          --  Start of processing for Contains_Subp_Or_Const_Refs
292
293          begin
294             Find_Subp_Or_Const_Ref (N);
295
296             return Reference_Seen;
297          end Contains_Subp_Or_Const_Refs;
298
299          --------------------
300          -- Has_Referencer --
301          --------------------
302
303          function Has_Referencer
304            (Decls     : List_Id;
305             Top_Level : Boolean := False) return Boolean
306          is
307             Decl    : Node_Id;
308             Decl_Id : Entity_Id;
309             Spec    : Node_Id;
310
311             Has_Non_Subp_Const_Referencer : Boolean := False;
312             --  Flag set for inlined subprogram bodies that do not contain
313             --  references to other subprograms or non-static constants.
314
315          begin
316             if No (Decls) then
317                return False;
318             end if;
319
320             --  Examine all declarations in reverse order, hiding all entities
321             --  from external visibility until a referencer has been found. The
322             --  algorithm recurses into nested packages.
323
324             Decl := Last (Decls);
325             while Present (Decl) loop
326
327                --  A stub is always considered a referencer
328
329                if Nkind (Decl) in N_Body_Stub then
330                   return True;
331
332                --  Package declaration
333
334                elsif Nkind (Decl) = N_Package_Declaration
335                  and then not Has_Non_Subp_Const_Referencer
336                then
337                   Spec := Specification (Decl);
338
339                   --  Inspect the declarations of a non-generic package to try
340                   --  and hide more entities from external visibility.
341
342                   if not Is_Generic_Unit (Defining_Entity (Spec)) then
343                      if Has_Referencer (Private_Declarations (Spec))
344                        or else Has_Referencer (Visible_Declarations (Spec))
345                      then
346                         return True;
347                      end if;
348                   end if;
349
350                --  Package body
351
352                elsif Nkind (Decl) = N_Package_Body
353                  and then Present (Corresponding_Spec (Decl))
354                then
355                   Decl_Id := Corresponding_Spec (Decl);
356
357                   --  A generic package body is a referencer. It would seem
358                   --  that we only have to consider generics that can be
359                   --  exported, i.e. where the corresponding spec is the
360                   --  spec of the current package, but because of nested
361                   --  instantiations, a fully private generic body may export
362                   --  other private body entities. Furthermore, regardless of
363                   --  whether there was a previous inlined subprogram, (an
364                   --  instantiation of) the generic package may reference any
365                   --  entity declared before it.
366
367                   if Is_Generic_Unit (Decl_Id) then
368                      return True;
369
370                   --  Inspect the declarations of a non-generic package body to
371                   --  try and hide more entities from external visibility.
372
373                   elsif not Has_Non_Subp_Const_Referencer
374                     and then Has_Referencer (Declarations (Decl))
375                   then
376                      return True;
377                   end if;
378
379                --  Subprogram body
380
381                elsif Nkind (Decl) = N_Subprogram_Body then
382                   if Present (Corresponding_Spec (Decl)) then
383                      Decl_Id := Corresponding_Spec (Decl);
384
385                      --  A generic subprogram body acts as a referencer
386
387                      if Is_Generic_Unit (Decl_Id) then
388                         return True;
389                      end if;
390
391                      --  An inlined subprogram body acts as a referencer
392
393                      if Is_Inlined (Decl_Id)
394                        or else Has_Pragma_Inline (Decl_Id)
395                      then
396                         --  Inspect the statements of the subprogram body
397                         --  to determine whether the body references other
398                         --  subprograms and/or non-static constants.
399
400                         if Top_Level
401                           and then not Contains_Subp_Or_Const_Refs (Decl)
402                         then
403                            Has_Non_Subp_Const_Referencer := True;
404                         else
405                            return True;
406                         end if;
407                      end if;
408
409                   --  Otherwise this is a stand alone subprogram body
410
411                   else
412                      Decl_Id := Defining_Entity (Decl);
413
414                      --  An inlined body acts as a referencer. Note that an
415                      --  inlined subprogram remains Is_Public as gigi requires
416                      --  the flag to be set.
417
418                      --  Note that we test Has_Pragma_Inline here rather than
419                      --  Is_Inlined. We are compiling this for a client, and
420                      --  it is the client who will decide if actual inlining
421                      --  should occur, so we need to assume that the procedure
422                      --  could be inlined for the purpose of accessing global
423                      --  entities.
424
425                      if Has_Pragma_Inline (Decl_Id) then
426                         if Top_Level
427                           and then not Contains_Subp_Or_Const_Refs (Decl)
428                         then
429                            Has_Non_Subp_Const_Referencer := True;
430                         else
431                            return True;
432                         end if;
433                      else
434                         Set_Is_Public (Decl_Id, False);
435                      end if;
436                   end if;
437
438                --  Exceptions, objects and renamings do not need to be public
439                --  if they are not followed by a construct which can reference
440                --  and export them. The Is_Public flag is reset on top level
441                --  entities only as anything nested is local to its context.
442
443                elsif Nkind_In (Decl, N_Exception_Declaration,
444                                      N_Object_Declaration,
445                                      N_Object_Renaming_Declaration,
446                                      N_Subprogram_Declaration,
447                                      N_Subprogram_Renaming_Declaration)
448                then
449                   Decl_Id := Defining_Entity (Decl);
450
451                   if Top_Level
452                     and then not Is_Imported (Decl_Id)
453                     and then not Is_Exported (Decl_Id)
454                     and then No (Interface_Name (Decl_Id))
455                     and then
456                       (not Has_Non_Subp_Const_Referencer
457                         or else Nkind (Decl) = N_Subprogram_Declaration)
458                   then
459                      Set_Is_Public (Decl_Id, False);
460                   end if;
461                end if;
462
463                Prev (Decl);
464             end loop;
465
466             return Has_Non_Subp_Const_Referencer;
467          end Has_Referencer;
468
469          --  Local variables
470
471          Discard : Boolean := True;
472          pragma Unreferenced (Discard);
473
474       --  Start of processing for Hide_Public_Entities
475
476       begin
477          --  The algorithm examines the top level declarations of a package
478          --  body in reverse looking for a construct that may export entities
479          --  declared prior to it. If such a scenario is encountered, then all
480          --  entities in the range Last (Decls) .. construct are hidden from
481          --  external visibility. Consider:
482
483          --    package Pack is
484          --       generic
485          --       package Gen is
486          --       end Gen;
487          --    end Pack;
488
489          --    package body Pack is
490          --       External_Obj : ...;      --  (1)
491
492          --       package body Gen is      --  (2)
493          --          ... External_Obj ...  --  (3)
494          --       end Gen;
495
496          --       Local_Obj : ...;         --  (4)
497          --    end Pack;
498
499          --  In this example Local_Obj (4) must not be externally visible as
500          --  it cannot be exported by anything in Pack. The body of generic
501          --  package Gen (2) on the other hand acts as a "referencer" and may
502          --  export anything declared before it. Since the compiler does not
503          --  perform flow analysis, it is not possible to determine precisely
504          --  which entities will be exported when Gen is instantiated. In the
505          --  example above External_Obj (1) is exported at (3), but this may
506          --  not always be the case. The algorithm takes a conservative stance
507          --  and leaves entity External_Obj public.
508
509          Discard := Has_Referencer (Decls, Top_Level => True);
510       end Hide_Public_Entities;
511
512       ----------------------------------
513       -- Install_Composite_Operations --
514       ----------------------------------
515
516       procedure Install_Composite_Operations (P : Entity_Id) is
517          Id : Entity_Id;
518
519       begin
520          Id := First_Entity (P);
521          while Present (Id) loop
522             if Is_Type (Id)
523               and then (Is_Limited_Composite (Id)
524                          or else Is_Private_Composite (Id))
525               and then No (Private_Component (Id))
526             then
527                Set_Is_Limited_Composite (Id, False);
528                Set_Is_Private_Composite (Id, False);
529             end if;
530
531             Next_Entity (Id);
532          end loop;
533       end Install_Composite_Operations;
534
535       --  Local variables
536
537       Save_Ghost_Mode  : constant Ghost_Mode_Type := Ghost_Mode;
538       Body_Id          : Entity_Id;
539       HSS              : Node_Id;
540       Last_Spec_Entity : Entity_Id;
541       New_N            : Node_Id;
542       Pack_Decl        : Node_Id;
543       Spec_Id          : Entity_Id;
544
545    --  Start of processing for Analyze_Package_Body_Helper
546
547    begin
548       --  Find corresponding package specification, and establish the current
549       --  scope. The visible defining entity for the package is the defining
550       --  occurrence in the spec. On exit from the package body, all body
551       --  declarations are attached to the defining entity for the body, but
552       --  the later is never used for name resolution. In this fashion there
553       --  is only one visible entity that denotes the package.
554
555       --  Set Body_Id. Note that this will be reset to point to the generic
556       --  copy later on in the generic case.
557
558       Body_Id := Defining_Entity (N);
559
560       --  Body is body of package instantiation. Corresponding spec has already
561       --  been set.
562
563       if Present (Corresponding_Spec (N)) then
564          Spec_Id   := Corresponding_Spec (N);
565          Pack_Decl := Unit_Declaration_Node (Spec_Id);
566
567       else
568          Spec_Id := Current_Entity_In_Scope (Defining_Entity (N));
569
570          if Present (Spec_Id)
571            and then Is_Package_Or_Generic_Package (Spec_Id)
572          then
573             Pack_Decl := Unit_Declaration_Node (Spec_Id);
574
575             if Nkind (Pack_Decl) = N_Package_Renaming_Declaration then
576                Error_Msg_N ("cannot supply body for package renaming", N);
577                return;
578
579             elsif Present (Corresponding_Body (Pack_Decl)) then
580                Error_Msg_N ("redefinition of package body", N);
581                return;
582             end if;
583
584          else
585             Error_Msg_N ("missing specification for package body", N);
586             return;
587          end if;
588
589          if Is_Package_Or_Generic_Package (Spec_Id)
590            and then (Scope (Spec_Id) = Standard_Standard
591                       or else Is_Child_Unit (Spec_Id))
592            and then not Unit_Requires_Body (Spec_Id)
593          then
594             if Ada_Version = Ada_83 then
595                Error_Msg_N
596                  ("optional package body (not allowed in Ada 95)??", N);
597             else
598                Error_Msg_N ("spec of this package does not allow a body", N);
599             end if;
600          end if;
601       end if;
602
603       --  A [generic] package body "freezes" the contract of the nearest
604       --  enclosing package body and all other contracts encountered in the
605       --  same declarative part up to and excluding the package body:
606
607       --    package body Nearest_Enclosing_Package
608       --      with Refined_State => (State => Constit)
609       --    is
610       --       Constit : ...;
611
612       --       package body Freezes_Enclosing_Package_Body
613       --         with Refined_State => (State_2 => Constit_2)
614       --       is
615       --          Constit_2 : ...;
616
617       --          procedure Proc
618       --            with Refined_Depends => (Input => (Constit, Constit_2)) ...
619
620       --  This ensures that any annotations referenced by the contract of a
621       --  [generic] subprogram body declared within the current package body
622       --  are available. This form of "freezing" is decoupled from the usual
623       --  Freeze_xxx mechanism because it must also work in the context of
624       --  generics where normal freezing is disabled.
625
626       --  Only bodies coming from source should cause this type of "freezing".
627       --  Instantiated generic bodies are excluded because their processing is
628       --  performed in a separate compilation pass which lacks enough semantic
629       --  information with respect to contract analysis. It is safe to suppress
630       --  the "freezing" of contracts in this case because this action already
631       --  took place at the end of the enclosing declarative part.
632
633       if Comes_From_Source (N)
634         and then not Is_Generic_Instance (Spec_Id)
635       then
636          Analyze_Previous_Contracts (N);
637       end if;
638
639       --  A package body is Ghost when the corresponding spec is Ghost. Set
640       --  the mode now to ensure that any nodes generated during analysis and
641       --  expansion are properly flagged as ignored Ghost.
642
643       Set_Ghost_Mode (N, Spec_Id);
644
645       Set_Is_Compilation_Unit (Body_Id, Is_Compilation_Unit (Spec_Id));
646       Style.Check_Identifier (Body_Id, Spec_Id);
647
648       if Is_Child_Unit (Spec_Id) then
649          if Nkind (Parent (N)) /= N_Compilation_Unit then
650             Error_Msg_NE
651               ("body of child unit& cannot be an inner package", N, Spec_Id);
652          end if;
653
654          Set_Is_Child_Unit (Body_Id);
655       end if;
656
657       --  Generic package case
658
659       if Ekind (Spec_Id) = E_Generic_Package then
660
661          --  Disable expansion and perform semantic analysis on copy. The
662          --  unannotated body will be used in all instantiations.
663
664          Body_Id := Defining_Entity (N);
665          Set_Ekind (Body_Id, E_Package_Body);
666          Set_Scope (Body_Id, Scope (Spec_Id));
667          Set_Is_Obsolescent (Body_Id, Is_Obsolescent (Spec_Id));
668          Set_Body_Entity (Spec_Id, Body_Id);
669          Set_Spec_Entity (Body_Id, Spec_Id);
670
671          New_N := Copy_Generic_Node (N, Empty, Instantiating => False);
672          Rewrite (N, New_N);
673
674          --  Once the contents of the generic copy and the template are
675          --  swapped, do the same for their respective aspect specifications.
676
677          Exchange_Aspects (N, New_N);
678
679          --  Collect all contract-related source pragmas found within the
680          --  template and attach them to the contract of the package body.
681          --  This contract is used in the capture of global references within
682          --  annotations.
683
684          Create_Generic_Contract (N);
685
686          --  Update Body_Id to point to the copied node for the remainder of
687          --  the processing.
688
689          Body_Id := Defining_Entity (N);
690          Start_Generic;
691       end if;
692
693       --  The Body_Id is that of the copied node in the generic case, the
694       --  current node otherwise. Note that N was rewritten above, so we must
695       --  be sure to get the latest Body_Id value.
696
697       Set_Ekind (Body_Id, E_Package_Body);
698       Set_Body_Entity (Spec_Id, Body_Id);
699       Set_Spec_Entity (Body_Id, Spec_Id);
700
701       --  Defining name for the package body is not a visible entity: Only the
702       --  defining name for the declaration is visible.
703
704       Set_Etype (Body_Id, Standard_Void_Type);
705       Set_Scope (Body_Id, Scope (Spec_Id));
706       Set_Corresponding_Spec (N, Spec_Id);
707       Set_Corresponding_Body (Pack_Decl, Body_Id);
708
709       --  The body entity is not used for semantics or code generation, but
710       --  it is attached to the entity list of the enclosing scope to simplify
711       --  the listing of back-annotations for the types it main contain.
712
713       if Scope (Spec_Id) /= Standard_Standard then
714          Append_Entity (Body_Id, Scope (Spec_Id));
715       end if;
716
717       --  Indicate that we are currently compiling the body of the package
718
719       Set_In_Package_Body (Spec_Id);
720       Set_Has_Completion (Spec_Id);
721       Last_Spec_Entity := Last_Entity (Spec_Id);
722
723       if Has_Aspects (N) then
724          Analyze_Aspect_Specifications (N, Body_Id);
725       end if;
726
727       Push_Scope (Spec_Id);
728
729       --  Set SPARK_Mode only for non-generic package
730
731       if Ekind (Spec_Id) = E_Package then
732          Set_SPARK_Pragma               (Body_Id, SPARK_Mode_Pragma);
733          Set_SPARK_Aux_Pragma           (Body_Id, SPARK_Mode_Pragma);
734          Set_SPARK_Pragma_Inherited     (Body_Id);
735          Set_SPARK_Aux_Pragma_Inherited (Body_Id);
736       end if;
737
738       --  Inherit the "ghostness" of the package spec. Note that this property
739       --  is not directly inherited as the body may be subject to a different
740       --  Ghost assertion policy.
741
742       if Ghost_Mode > None or else Is_Ghost_Entity (Spec_Id) then
743          Set_Is_Ghost_Entity (Body_Id);
744
745          --  The Ghost policy in effect at the point of declaration and at the
746          --  point of completion must match (SPARK RM 6.9(14)).
747
748          Check_Ghost_Completion (Spec_Id, Body_Id);
749       end if;
750
751       Set_Categorization_From_Pragmas (N);
752
753       Install_Visible_Declarations (Spec_Id);
754       Install_Private_Declarations (Spec_Id);
755       Install_Private_With_Clauses (Spec_Id);
756       Install_Composite_Operations (Spec_Id);
757
758       Check_Anonymous_Access_Types (Spec_Id, N);
759
760       if Ekind (Spec_Id) = E_Generic_Package then
761          Set_Use (Generic_Formal_Declarations (Pack_Decl));
762       end if;
763
764       Set_Use (Visible_Declarations (Specification (Pack_Decl)));
765       Set_Use (Private_Declarations (Specification (Pack_Decl)));
766
767       --  This is a nested package, so it may be necessary to declare certain
768       --  inherited subprograms that are not yet visible because the parent
769       --  type's subprograms are now visible.
770
771       if Ekind (Scope (Spec_Id)) = E_Package
772         and then Scope (Spec_Id) /= Standard_Standard
773       then
774          Declare_Inherited_Private_Subprograms (Spec_Id);
775       end if;
776
777       --  A package body "freezes" the contract of its initial declaration.
778       --  This analysis depends on attribute Corresponding_Spec being set. Only
779       --  bodies coming from source shuld cause this type of "freezing".
780
781       if Present (Declarations (N)) then
782          Analyze_Declarations (Declarations (N));
783          Inspect_Deferred_Constant_Completion (Declarations (N));
784       end if;
785
786       --  Verify that the SPARK_Mode of the body agrees with that of its spec
787
788       if Present (SPARK_Pragma (Body_Id)) then
789          if Present (SPARK_Aux_Pragma (Spec_Id)) then
790             if Get_SPARK_Mode_From_Annotation (SPARK_Aux_Pragma (Spec_Id)) =
791                  Off
792               and then
793                 Get_SPARK_Mode_From_Annotation (SPARK_Pragma (Body_Id)) = On
794             then
795                Error_Msg_Sloc := Sloc (SPARK_Pragma (Body_Id));
796                Error_Msg_N ("incorrect application of SPARK_Mode#", N);
797                Error_Msg_Sloc := Sloc (SPARK_Aux_Pragma (Spec_Id));
798                Error_Msg_NE
799                  ("\value Off was set for SPARK_Mode on & #", N, Spec_Id);
800             end if;
801
802          else
803             Error_Msg_Sloc := Sloc (SPARK_Pragma (Body_Id));
804             Error_Msg_N ("incorrect application of SPARK_Mode#", N);
805             Error_Msg_Sloc := Sloc (Spec_Id);
806             Error_Msg_NE
807               ("\no value was set for SPARK_Mode on & #", N, Spec_Id);
808          end if;
809       end if;
810
811       --  Analyze_Declarations has caused freezing of all types. Now generate
812       --  bodies for RACW primitives and stream attributes, if any.
813
814       if Ekind (Spec_Id) = E_Package and then Has_RACW (Spec_Id) then
815
816          --  Attach subprogram bodies to support RACWs declared in spec
817
818          Append_RACW_Bodies (Declarations (N), Spec_Id);
819          Analyze_List (Declarations (N));
820       end if;
821
822       HSS := Handled_Statement_Sequence (N);
823
824       if Present (HSS) then
825          Process_End_Label (HSS, 't', Spec_Id);
826          Analyze (HSS);
827
828          --  Check that elaboration code in a preelaborable package body is
829          --  empty other than null statements and labels (RM 10.2.1(6)).
830
831          Validate_Null_Statement_Sequence (N);
832       end if;
833
834       Validate_Categorization_Dependency (N, Spec_Id);
835       Check_Completion (Body_Id);
836
837       --  Generate start of body reference. Note that we do this fairly late,
838       --  because the call will use In_Extended_Main_Source_Unit as a check,
839       --  and we want to make sure that Corresponding_Stub links are set
840
841       Generate_Reference (Spec_Id, Body_Id, 'b', Set_Ref => False);
842
843       --  For a generic package, collect global references and mark them on
844       --  the original body so that they are not resolved again at the point
845       --  of instantiation.
846
847       if Ekind (Spec_Id) /= E_Package then
848          Save_Global_References (Original_Node (N));
849          End_Generic;
850       end if;
851
852       --  The entities of the package body have so far been chained onto the
853       --  declaration chain for the spec. That's been fine while we were in the
854       --  body, since we wanted them to be visible, but now that we are leaving
855       --  the package body, they are no longer visible, so we remove them from
856       --  the entity chain of the package spec entity, and copy them to the
857       --  entity chain of the package body entity, where they will never again
858       --  be visible.
859
860       if Present (Last_Spec_Entity) then
861          Set_First_Entity (Body_Id, Next_Entity (Last_Spec_Entity));
862          Set_Next_Entity (Last_Spec_Entity, Empty);
863          Set_Last_Entity (Body_Id, Last_Entity (Spec_Id));
864          Set_Last_Entity (Spec_Id, Last_Spec_Entity);
865
866       else
867          Set_First_Entity (Body_Id, First_Entity (Spec_Id));
868          Set_Last_Entity  (Body_Id, Last_Entity  (Spec_Id));
869          Set_First_Entity (Spec_Id, Empty);
870          Set_Last_Entity  (Spec_Id, Empty);
871       end if;
872
873       End_Package_Scope (Spec_Id);
874
875       --  All entities declared in body are not visible
876
877       declare
878          E : Entity_Id;
879
880       begin
881          E := First_Entity (Body_Id);
882          while Present (E) loop
883             Set_Is_Immediately_Visible (E, False);
884             Set_Is_Potentially_Use_Visible (E, False);
885             Set_Is_Hidden (E);
886
887             --  Child units may appear on the entity list (e.g. if they appear
888             --  in the context of a subunit) but they are not body entities.
889
890             if not Is_Child_Unit (E) then
891                Set_Is_Package_Body_Entity (E);
892             end if;
893
894             Next_Entity (E);
895          end loop;
896       end;
897
898       Check_References (Body_Id);
899
900       --  For a generic unit, check that the formal parameters are referenced,
901       --  and that local variables are used, as for regular packages.
902
903       if Ekind (Spec_Id) = E_Generic_Package then
904          Check_References (Spec_Id);
905       end if;
906
907       --  At this point all entities of the package body are externally visible
908       --  to the linker as their Is_Public flag is set to True. This proactive
909       --  approach is necessary because an inlined or a generic body for which
910       --  code is generated in other units may need to see these entities. Cut
911       --  down the number of global symbols that do not neet public visibility
912       --  as this has two beneficial effects:
913       --    (1) It makes the compilation process more efficient.
914       --    (2) It gives the code generatormore freedom to optimize within each
915       --        unit, especially subprograms.
916
917       --  This is done only for top level library packages or child units as
918       --  the algorithm does a top down traversal of the package body.
919
920       if (Scope (Spec_Id) = Standard_Standard or else Is_Child_Unit (Spec_Id))
921         and then not Is_Generic_Unit (Spec_Id)
922       then
923          Hide_Public_Entities (Declarations (N));
924       end if;
925
926       --  If expander is not active, then here is where we turn off the
927       --  In_Package_Body flag, otherwise it is turned off at the end of the
928       --  corresponding expansion routine. If this is an instance body, we need
929       --  to qualify names of local entities, because the body may have been
930       --  compiled as a preliminary to another instantiation.
931
932       if not Expander_Active then
933          Set_In_Package_Body (Spec_Id, False);
934
935          if Is_Generic_Instance (Spec_Id)
936            and then Operating_Mode = Generate_Code
937          then
938             Qualify_Entity_Names (N);
939          end if;
940       end if;
941
942       Ghost_Mode := Save_Ghost_Mode;
943    end Analyze_Package_Body_Helper;
944
945    ---------------------------------
946    -- Analyze_Package_Declaration --
947    ---------------------------------
948
949    procedure Analyze_Package_Declaration (N : Node_Id) is
950       Id  : constant Node_Id := Defining_Entity (N);
951       Par : constant Node_Id := Parent_Spec (N);
952
953       Is_Comp_Unit : constant Boolean :=
954                        Nkind (Parent (N)) = N_Compilation_Unit;
955
956       Body_Required : Boolean;
957       --  True when this package declaration requires a corresponding body
958
959    begin
960       if Debug_Flag_C then
961          Write_Str ("==> package spec ");
962          Write_Name (Chars (Id));
963          Write_Str (" from ");
964          Write_Location (Sloc (N));
965          Write_Eol;
966          Indent;
967       end if;
968
969       Generate_Definition (Id);
970       Enter_Name (Id);
971       Set_Ekind  (Id, E_Package);
972       Set_Etype  (Id, Standard_Void_Type);
973
974       --  Set SPARK_Mode from context only for non-generic package
975
976       if Ekind (Id) = E_Package then
977          Set_SPARK_Pragma               (Id, SPARK_Mode_Pragma);
978          Set_SPARK_Aux_Pragma           (Id, SPARK_Mode_Pragma);
979          Set_SPARK_Pragma_Inherited     (Id);
980          Set_SPARK_Aux_Pragma_Inherited (Id);
981       end if;
982
983       --  A package declared within a Ghost refion is automatically Ghost. A
984       --  child package is Ghost when its parent is Ghost (SPARK RM 6.9(2)).
985
986       if Ghost_Mode > None
987         or else (Present (Par)
988                   and then Is_Ghost_Entity (Defining_Entity (Unit (Par))))
989       then
990          Set_Is_Ghost_Entity (Id);
991       end if;
992
993       --  Analyze aspect specifications immediately, since we need to recognize
994       --  things like Pure early enough to diagnose violations during analysis.
995
996       if Has_Aspects (N) then
997          Analyze_Aspect_Specifications (N, Id);
998       end if;
999
1000       --  Ada 2005 (AI-217): Check if the package has been illegally named in
1001       --  a limited-with clause of its own context. In this case the error has
1002       --  been previously notified by Analyze_Context.
1003
1004       --     limited with Pkg; -- ERROR
1005       --     package Pkg is ...
1006
1007       if From_Limited_With (Id) then
1008          return;
1009       end if;
1010
1011       Push_Scope (Id);
1012
1013       Set_Is_Pure (Id, Is_Pure (Enclosing_Lib_Unit_Entity));
1014       Set_Categorization_From_Pragmas (N);
1015
1016       Analyze (Specification (N));
1017       Validate_Categorization_Dependency (N, Id);
1018
1019       --  Determine whether the package requires a body. Abstract states are
1020       --  intentionally ignored because they do require refinement which can
1021       --  only come in a body, but at the same time they do not force the need
1022       --  for a body on their own (SPARK RM 7.1.4(4) and 7.2.2(3)).
1023
1024       Body_Required := Unit_Requires_Body (Id);
1025
1026       if not Body_Required then
1027
1028          --  If the package spec does not require an explicit body, then there
1029          --  are not entities requiring completion in the language sense. Call
1030          --  Check_Completion now to ensure that nested package declarations
1031          --  that require an implicit body get one. (In the case where a body
1032          --  is required, Check_Completion is called at the end of the body's
1033          --  declarative part.)
1034
1035          Check_Completion;
1036
1037          --  If the package spec does not require an explicit body, then all
1038          --  abstract states declared in nested packages cannot possibly get
1039          --  a proper refinement (SPARK RM 7.2.2(3)). This check is performed
1040          --  only when the compilation unit is the main unit to allow for
1041          --  modular SPARK analysis where packages do not necessarily have
1042          --  bodies.
1043
1044          if Is_Comp_Unit then
1045             Check_State_Refinements
1046               (Context      => N,
1047                Is_Main_Unit => Parent (N) = Cunit (Main_Unit));
1048          end if;
1049       end if;
1050
1051       if Is_Comp_Unit then
1052
1053          --  Set Body_Required indication on the compilation unit node, and
1054          --  determine whether elaboration warnings may be meaningful on it.
1055
1056          Set_Body_Required (Parent (N), Body_Required);
1057
1058          if not Body_Required then
1059             Set_Suppress_Elaboration_Warnings (Id);
1060          end if;
1061       end if;
1062
1063       End_Package_Scope (Id);
1064
1065       --  For the declaration of a library unit that is a remote types package,
1066       --  check legality rules regarding availability of stream attributes for
1067       --  types that contain non-remote access values. This subprogram performs
1068       --  visibility tests that rely on the fact that we have exited the scope
1069       --  of Id.
1070
1071       if Is_Comp_Unit then
1072          Validate_RT_RAT_Component (N);
1073       end if;
1074
1075       if Debug_Flag_C then
1076          Outdent;
1077          Write_Str ("<== package spec ");
1078          Write_Name (Chars (Id));
1079          Write_Str (" from ");
1080          Write_Location (Sloc (N));
1081          Write_Eol;
1082       end if;
1083    end Analyze_Package_Declaration;
1084
1085    -----------------------------------
1086    -- Analyze_Package_Specification --
1087    -----------------------------------
1088
1089    --  Note that this code is shared for the analysis of generic package specs
1090    --  (see Sem_Ch12.Analyze_Generic_Package_Declaration for details).
1091
1092    procedure Analyze_Package_Specification (N : Node_Id) is
1093       Id           : constant Entity_Id  := Defining_Entity (N);
1094       Orig_Decl    : constant Node_Id    := Original_Node (Parent (N));
1095       Vis_Decls    : constant List_Id    := Visible_Declarations (N);
1096       Priv_Decls   : constant List_Id    := Private_Declarations (N);
1097       E            : Entity_Id;
1098       L            : Entity_Id;
1099       Public_Child : Boolean;
1100
1101       Private_With_Clauses_Installed : Boolean := False;
1102       --  In Ada 2005, private with_clauses are visible in the private part
1103       --  of a nested package, even if it appears in the public part of the
1104       --  enclosing package. This requires a separate step to install these
1105       --  private_with_clauses, and remove them at the end of the nested
1106       --  package.
1107
1108       procedure Check_One_Tagged_Type_Or_Extension_At_Most;
1109       --  Issue an error in SPARK mode if a package specification contains
1110       --  more than one tagged type or type extension.
1111
1112       procedure Clear_Constants (Id : Entity_Id; FE : Entity_Id);
1113       --  Clears constant indications (Never_Set_In_Source, Constant_Value, and
1114       --  Is_True_Constant) on all variables that are entities of Id, and on
1115       --  the chain whose first element is FE. A recursive call is made for all
1116       --  packages and generic packages.
1117
1118       procedure Generate_Parent_References;
1119       --  For a child unit, generate references to parent units, for
1120       --  GPS navigation purposes.
1121
1122       function Is_Public_Child (Child, Unit : Entity_Id) return Boolean;
1123       --  Child and Unit are entities of compilation units. True if Child
1124       --  is a public child of Parent as defined in 10.1.1
1125
1126       procedure Inspect_Unchecked_Union_Completion (Decls : List_Id);
1127       --  Reject completion of an incomplete or private type declarations
1128       --  having a known discriminant part by an unchecked union.
1129
1130       procedure Install_Parent_Private_Declarations (Inst_Id : Entity_Id);
1131       --  Given the package entity of a generic package instantiation or
1132       --  formal package whose corresponding generic is a child unit, installs
1133       --  the private declarations of each of the child unit's parents.
1134       --  This has to be done at the point of entering the instance package's
1135       --  private part rather than being done in Sem_Ch12.Install_Parent
1136       --  (which is where the parents' visible declarations are installed).
1137
1138       ------------------------------------------------
1139       -- Check_One_Tagged_Type_Or_Extension_At_Most --
1140       ------------------------------------------------
1141
1142       procedure Check_One_Tagged_Type_Or_Extension_At_Most is
1143          Previous : Node_Id;
1144
1145          procedure Check_Decls (Decls : List_Id);
1146          --  Check that either Previous is Empty and Decls does not contain
1147          --  more than one tagged type or type extension, or Previous is
1148          --  already set and Decls contains no tagged type or type extension.
1149
1150          -----------------
1151          -- Check_Decls --
1152          -----------------
1153
1154          procedure Check_Decls (Decls : List_Id) is
1155             Decl : Node_Id;
1156
1157          begin
1158             Decl := First (Decls);
1159             while Present (Decl) loop
1160                if Nkind (Decl) = N_Full_Type_Declaration
1161                  and then Is_Tagged_Type (Defining_Identifier (Decl))
1162                then
1163                   if No (Previous) then
1164                      Previous := Decl;
1165
1166                   else
1167                      Error_Msg_Sloc := Sloc (Previous);
1168                      Check_SPARK_05_Restriction
1169                        ("at most one tagged type or type extension allowed",
1170                         "\\ previous declaration#",
1171                         Decl);
1172                   end if;
1173                end if;
1174
1175                Next (Decl);
1176             end loop;
1177          end Check_Decls;
1178
1179       --  Start of processing for Check_One_Tagged_Type_Or_Extension_At_Most
1180
1181       begin
1182          Previous := Empty;
1183          Check_Decls (Vis_Decls);
1184
1185          if Present (Priv_Decls) then
1186             Check_Decls (Priv_Decls);
1187          end if;
1188       end Check_One_Tagged_Type_Or_Extension_At_Most;
1189
1190       ---------------------
1191       -- Clear_Constants --
1192       ---------------------
1193
1194       procedure Clear_Constants (Id : Entity_Id; FE : Entity_Id) is
1195          E : Entity_Id;
1196
1197       begin
1198          --  Ignore package renamings, not interesting and they can cause self
1199          --  referential loops in the code below.
1200
1201          if Nkind (Parent (Id)) = N_Package_Renaming_Declaration then
1202             return;
1203          end if;
1204
1205          --  Note: in the loop below, the check for Next_Entity pointing back
1206          --  to the package entity may seem odd, but it is needed, because a
1207          --  package can contain a renaming declaration to itself, and such
1208          --  renamings are generated automatically within package instances.
1209
1210          E := FE;
1211          while Present (E) and then E /= Id loop
1212             if Is_Assignable (E) then
1213                Set_Never_Set_In_Source (E, False);
1214                Set_Is_True_Constant    (E, False);
1215                Set_Current_Value       (E, Empty);
1216                Set_Is_Known_Null       (E, False);
1217                Set_Last_Assignment     (E, Empty);
1218
1219                if not Can_Never_Be_Null (E) then
1220                   Set_Is_Known_Non_Null (E, False);
1221                end if;
1222
1223             elsif Is_Package_Or_Generic_Package (E) then
1224                Clear_Constants (E, First_Entity (E));
1225                Clear_Constants (E, First_Private_Entity (E));
1226             end if;
1227
1228             Next_Entity (E);
1229          end loop;
1230       end Clear_Constants;
1231
1232       --------------------------------
1233       -- Generate_Parent_References --
1234       --------------------------------
1235
1236       procedure Generate_Parent_References is
1237          Decl : constant Node_Id := Parent (N);
1238
1239       begin
1240          if Id = Cunit_Entity (Main_Unit)
1241            or else Parent (Decl) = Library_Unit (Cunit (Main_Unit))
1242          then
1243             Generate_Reference (Id, Scope (Id), 'k', False);
1244
1245          elsif not Nkind_In (Unit (Cunit (Main_Unit)), N_Subprogram_Body,
1246                                                        N_Subunit)
1247          then
1248             --  If current unit is an ancestor of main unit, generate a
1249             --  reference to its own parent.
1250
1251             declare
1252                U         : Node_Id;
1253                Main_Spec : Node_Id := Unit (Cunit (Main_Unit));
1254
1255             begin
1256                if Nkind (Main_Spec) = N_Package_Body then
1257                   Main_Spec := Unit (Library_Unit (Cunit (Main_Unit)));
1258                end if;
1259
1260                U := Parent_Spec (Main_Spec);
1261                while Present (U) loop
1262                   if U = Parent (Decl) then
1263                      Generate_Reference (Id, Scope (Id), 'k',  False);
1264                      exit;
1265
1266                   elsif Nkind (Unit (U)) = N_Package_Body then
1267                      exit;
1268
1269                   else
1270                      U := Parent_Spec (Unit (U));
1271                   end if;
1272                end loop;
1273             end;
1274          end if;
1275       end Generate_Parent_References;
1276
1277       ---------------------
1278       -- Is_Public_Child --
1279       ---------------------
1280
1281       function Is_Public_Child (Child, Unit : Entity_Id) return Boolean is
1282       begin
1283          if not Is_Private_Descendant (Child) then
1284             return True;
1285          else
1286             if Child = Unit then
1287                return not Private_Present (
1288                  Parent (Unit_Declaration_Node (Child)));
1289             else
1290                return Is_Public_Child (Scope (Child), Unit);
1291             end if;
1292          end if;
1293       end Is_Public_Child;
1294
1295       ----------------------------------------
1296       -- Inspect_Unchecked_Union_Completion --
1297       ----------------------------------------
1298
1299       procedure Inspect_Unchecked_Union_Completion (Decls : List_Id) is
1300          Decl : Node_Id;
1301
1302       begin
1303          Decl := First (Decls);
1304          while Present (Decl) loop
1305
1306             --  We are looking at an incomplete or private type declaration
1307             --  with a known_discriminant_part whose full view is an
1308             --  Unchecked_Union.
1309
1310             if Nkind_In (Decl, N_Incomplete_Type_Declaration,
1311                                N_Private_Type_Declaration)
1312               and then Has_Discriminants (Defining_Identifier (Decl))
1313               and then Present (Full_View (Defining_Identifier (Decl)))
1314               and then
1315                 Is_Unchecked_Union (Full_View (Defining_Identifier (Decl)))
1316             then
1317                Error_Msg_N
1318                  ("completion of discriminated partial view "
1319                   & "cannot be an unchecked union",
1320                  Full_View (Defining_Identifier (Decl)));
1321             end if;
1322
1323             Next (Decl);
1324          end loop;
1325       end Inspect_Unchecked_Union_Completion;
1326
1327       -----------------------------------------
1328       -- Install_Parent_Private_Declarations --
1329       -----------------------------------------
1330
1331       procedure Install_Parent_Private_Declarations (Inst_Id : Entity_Id) is
1332          Inst_Par  : Entity_Id;
1333          Gen_Par   : Entity_Id;
1334          Inst_Node : Node_Id;
1335
1336       begin
1337          Inst_Par := Inst_Id;
1338
1339          Gen_Par :=
1340            Generic_Parent (Specification (Unit_Declaration_Node (Inst_Par)));
1341          while Present (Gen_Par) and then Is_Child_Unit (Gen_Par) loop
1342             Inst_Node := Get_Package_Instantiation_Node (Inst_Par);
1343
1344             if Nkind_In (Inst_Node, N_Package_Instantiation,
1345                                     N_Formal_Package_Declaration)
1346               and then Nkind (Name (Inst_Node)) = N_Expanded_Name
1347             then
1348                Inst_Par := Entity (Prefix (Name (Inst_Node)));
1349
1350                if Present (Renamed_Entity (Inst_Par)) then
1351                   Inst_Par := Renamed_Entity (Inst_Par);
1352                end if;
1353
1354                Gen_Par :=
1355                  Generic_Parent
1356                    (Specification (Unit_Declaration_Node (Inst_Par)));
1357
1358                --  Install the private declarations and private use clauses
1359                --  of a parent instance of the child instance, unless the
1360                --  parent instance private declarations have already been
1361                --  installed earlier in Analyze_Package_Specification, which
1362                --  happens when a generic child is instantiated, and the
1363                --  instance is a child of the parent instance.
1364
1365                --  Installing the use clauses of the parent instance twice
1366                --  is both unnecessary and wrong, because it would cause the
1367                --  clauses to be chained to themselves in the use clauses
1368                --  list of the scope stack entry. That in turn would cause
1369                --  an endless loop from End_Use_Clauses upon scope exit.
1370
1371                --  The parent is now fully visible. It may be a hidden open
1372                --  scope if we are currently compiling some child instance
1373                --  declared within it, but while the current instance is being
1374                --  compiled the parent is immediately visible. In particular
1375                --  its entities must remain visible if a stack save/restore
1376                --  takes place through a call to Rtsfind.
1377
1378                if Present (Gen_Par) then
1379                   if not In_Private_Part (Inst_Par) then
1380                      Install_Private_Declarations (Inst_Par);
1381                      Set_Use (Private_Declarations
1382                                 (Specification
1383                                    (Unit_Declaration_Node (Inst_Par))));
1384                      Set_Is_Hidden_Open_Scope (Inst_Par, False);
1385                   end if;
1386
1387                --  If we've reached the end of the generic instance parents,
1388                --  then finish off by looping through the nongeneric parents
1389                --  and installing their private declarations.
1390
1391                --  If one of the non-generic parents is itself on the scope
1392                --  stack, do not install its private declarations: they are
1393                --  installed in due time when the private part of that parent
1394                --  is analyzed. This is delicate ???
1395
1396                else
1397                   while Present (Inst_Par)
1398                     and then Inst_Par /= Standard_Standard
1399                     and then (not In_Open_Scopes (Inst_Par)
1400                                or else not In_Private_Part (Inst_Par))
1401                   loop
1402                      Install_Private_Declarations (Inst_Par);
1403                      Set_Use (Private_Declarations
1404                                 (Specification
1405                                    (Unit_Declaration_Node (Inst_Par))));
1406                      Inst_Par := Scope (Inst_Par);
1407                   end loop;
1408
1409                   exit;
1410                end if;
1411
1412             else
1413                exit;
1414             end if;
1415          end loop;
1416       end Install_Parent_Private_Declarations;
1417
1418    --  Start of processing for Analyze_Package_Specification
1419
1420    begin
1421       if Present (Vis_Decls) then
1422          Analyze_Declarations (Vis_Decls);
1423       end if;
1424
1425       --  Inspect the entities defined in the package and ensure that all
1426       --  incomplete types have received full declarations. Build default
1427       --  initial condition and invariant procedures for all qualifying types.
1428
1429       E := First_Entity (Id);
1430       while Present (E) loop
1431
1432          --  Check on incomplete types
1433
1434          --  AI05-0213: A formal incomplete type has no completion
1435
1436          if Ekind (E) = E_Incomplete_Type
1437            and then No (Full_View (E))
1438            and then not Is_Generic_Type (E)
1439          then
1440             Error_Msg_N ("no declaration in visible part for incomplete}", E);
1441          end if;
1442
1443          if Is_Type (E) then
1444
1445             --  Each private type subject to pragma Default_Initial_Condition
1446             --  declares a specialized procedure which verifies the assumption
1447             --  of the pragma. The declaration appears in the visible part of
1448             --  the package to allow for being called from the outside.
1449
1450             if Has_Default_Init_Cond (E) then
1451                Build_Default_Init_Cond_Procedure_Declaration (E);
1452
1453             --  A private extension inherits the default initial condition
1454             --  procedure from its parent type.
1455
1456             elsif Has_Inherited_Default_Init_Cond (E) then
1457                Inherit_Default_Init_Cond_Procedure (E);
1458             end if;
1459
1460             --  If invariants are present, build the invariant procedure for a
1461             --  private type, but not any of its subtypes or interface types.
1462
1463             if Has_Invariants (E) then
1464                if Ekind (E) = E_Private_Subtype then
1465                   null;
1466                else
1467                   Build_Invariant_Procedure (E, N);
1468                end if;
1469             end if;
1470          end if;
1471
1472          Next_Entity (E);
1473       end loop;
1474
1475       if Is_Remote_Call_Interface (Id)
1476          and then Nkind (Parent (Parent (N))) = N_Compilation_Unit
1477       then
1478          Validate_RCI_Declarations (Id);
1479       end if;
1480
1481       --  Save global references in the visible declarations, before installing
1482       --  private declarations of parent unit if there is one, because the
1483       --  privacy status of types defined in the parent will change. This is
1484       --  only relevant for generic child units, but is done in all cases for
1485       --  uniformity.
1486
1487       if Ekind (Id) = E_Generic_Package
1488         and then Nkind (Orig_Decl) = N_Generic_Package_Declaration
1489       then
1490          declare
1491             Orig_Spec : constant Node_Id := Specification (Orig_Decl);
1492             Save_Priv : constant List_Id := Private_Declarations (Orig_Spec);
1493          begin
1494             Set_Private_Declarations (Orig_Spec, Empty_List);
1495             Save_Global_References   (Orig_Decl);
1496             Set_Private_Declarations (Orig_Spec, Save_Priv);
1497          end;
1498       end if;
1499
1500       --  If package is a public child unit, then make the private declarations
1501       --  of the parent visible.
1502
1503       Public_Child := False;
1504
1505       declare
1506          Par       : Entity_Id;
1507          Pack_Decl : Node_Id;
1508          Par_Spec  : Node_Id;
1509
1510       begin
1511          Par := Id;
1512          Par_Spec := Parent_Spec (Parent (N));
1513
1514          --  If the package is formal package of an enclosing generic, it is
1515          --  transformed into a local generic declaration, and compiled to make
1516          --  its spec available. We need to retrieve the original generic to
1517          --  determine whether it is a child unit, and install its parents.
1518
1519          if No (Par_Spec)
1520            and then
1521              Nkind (Original_Node (Parent (N))) = N_Formal_Package_Declaration
1522          then
1523             Par := Entity (Name (Original_Node (Parent (N))));
1524             Par_Spec := Parent_Spec (Unit_Declaration_Node (Par));
1525          end if;
1526
1527          if Present (Par_Spec) then
1528             Generate_Parent_References;
1529
1530             while Scope (Par) /= Standard_Standard
1531               and then Is_Public_Child (Id, Par)
1532               and then In_Open_Scopes (Par)
1533             loop
1534                Public_Child := True;
1535                Par := Scope (Par);
1536                Install_Private_Declarations (Par);
1537                Install_Private_With_Clauses (Par);
1538                Pack_Decl := Unit_Declaration_Node (Par);
1539                Set_Use (Private_Declarations (Specification (Pack_Decl)));
1540             end loop;
1541          end if;
1542       end;
1543
1544       if Is_Compilation_Unit (Id) then
1545          Install_Private_With_Clauses (Id);
1546       else
1547
1548          --  The current compilation unit may include private with_clauses,
1549          --  which are visible in the private part of the current nested
1550          --  package, and have to be installed now. This is not done for
1551          --  nested instantiations, where the private with_clauses of the
1552          --  enclosing unit have no effect once the instantiation info is
1553          --  established and we start analyzing the package declaration.
1554
1555          declare
1556             Comp_Unit : constant Entity_Id := Cunit_Entity (Current_Sem_Unit);
1557          begin
1558             if Is_Package_Or_Generic_Package (Comp_Unit)
1559               and then not In_Private_Part (Comp_Unit)
1560               and then not In_Instance
1561             then
1562                Install_Private_With_Clauses (Comp_Unit);
1563                Private_With_Clauses_Installed := True;
1564             end if;
1565          end;
1566       end if;
1567
1568       --  If this is a package associated with a generic instance or formal
1569       --  package, then the private declarations of each of the generic's
1570       --  parents must be installed at this point.
1571
1572       if Is_Generic_Instance (Id) then
1573          Install_Parent_Private_Declarations (Id);
1574       end if;
1575
1576       --  Analyze private part if present. The flag In_Private_Part is reset
1577       --  in End_Package_Scope.
1578
1579       L := Last_Entity (Id);
1580
1581       if Present (Priv_Decls) then
1582          Set_In_Private_Part (Id);
1583
1584          --  Upon entering a public child's private part, it may be necessary
1585          --  to declare subprograms that were derived in the package's visible
1586          --  part but not yet made visible.
1587
1588          if Public_Child then
1589             Declare_Inherited_Private_Subprograms (Id);
1590          end if;
1591
1592          Analyze_Declarations (Priv_Decls);
1593
1594          --  Check the private declarations for incomplete deferred constants
1595
1596          Inspect_Deferred_Constant_Completion (Priv_Decls);
1597
1598          --  The first private entity is the immediate follower of the last
1599          --  visible entity, if there was one.
1600
1601          if Present (L) then
1602             Set_First_Private_Entity (Id, Next_Entity (L));
1603          else
1604             Set_First_Private_Entity (Id, First_Entity (Id));
1605          end if;
1606
1607       --  There may be inherited private subprograms that need to be declared,
1608       --  even in the absence of an explicit private part.  If there are any
1609       --  public declarations in the package and the package is a public child
1610       --  unit, then an implicit private part is assumed.
1611
1612       elsif Present (L) and then Public_Child then
1613          Set_In_Private_Part (Id);
1614          Declare_Inherited_Private_Subprograms (Id);
1615          Set_First_Private_Entity (Id, Next_Entity (L));
1616       end if;
1617
1618       E := First_Entity (Id);
1619       while Present (E) loop
1620
1621          --  Check rule of 3.6(11), which in general requires waiting till all
1622          --  full types have been seen.
1623
1624          if Ekind (E) = E_Record_Type or else Ekind (E) = E_Array_Type then
1625             Check_Aliased_Component_Types (E);
1626          end if;
1627
1628          --  Check preelaborable initialization for full type completing a
1629          --  private type for which pragma Preelaborable_Initialization given.
1630
1631          if Is_Type (E)
1632            and then Must_Have_Preelab_Init (E)
1633            and then not Has_Preelaborable_Initialization (E)
1634          then
1635             Error_Msg_N
1636               ("full view of & does not have preelaborable initialization", E);
1637          end if;
1638
1639          --  An invariant may appear on a full view of a type
1640
1641          if Is_Type (E)
1642            and then Has_Private_Declaration (E)
1643            and then Nkind (Parent (E)) = N_Full_Type_Declaration
1644          then
1645             declare
1646                IP_Built : Boolean := False;
1647
1648             begin
1649                if Has_Aspects (Parent (E)) then
1650                   declare
1651                      ASN : Node_Id;
1652
1653                   begin
1654                      ASN := First (Aspect_Specifications (Parent (E)));
1655                      while Present (ASN) loop
1656                         if Nam_In (Chars (Identifier (ASN)),
1657                              Name_Invariant,
1658                              Name_Type_Invariant)
1659                         then
1660                            Build_Invariant_Procedure (E, N);
1661                            IP_Built := True;
1662                            exit;
1663                         end if;
1664
1665                         Next (ASN);
1666                      end loop;
1667                   end;
1668                end if;
1669
1670                --  Invariants may have been inherited from progenitors
1671
1672                if not IP_Built
1673                  and then Has_Interfaces (E)
1674                  and then Has_Inheritable_Invariants (E)
1675                  and then not Is_Interface (E)
1676                  and then not Is_Class_Wide_Type (E)
1677                then
1678                   Build_Invariant_Procedure (E, N);
1679                end if;
1680             end;
1681          end if;
1682
1683          Next_Entity (E);
1684       end loop;
1685
1686       --  Ada 2005 (AI-216): The completion of an incomplete or private type
1687       --  declaration having a known_discriminant_part shall not be an
1688       --  unchecked union type.
1689
1690       if Present (Vis_Decls) then
1691          Inspect_Unchecked_Union_Completion (Vis_Decls);
1692       end if;
1693
1694       if Present (Priv_Decls) then
1695          Inspect_Unchecked_Union_Completion (Priv_Decls);
1696       end if;
1697
1698       if Ekind (Id) = E_Generic_Package
1699         and then Nkind (Orig_Decl) = N_Generic_Package_Declaration
1700         and then Present (Priv_Decls)
1701       then
1702          --  Save global references in private declarations, ignoring the
1703          --  visible declarations that were processed earlier.
1704
1705          declare
1706             Orig_Spec : constant Node_Id := Specification (Orig_Decl);
1707             Save_Vis  : constant List_Id := Visible_Declarations (Orig_Spec);
1708             Save_Form : constant List_Id :=
1709                           Generic_Formal_Declarations (Orig_Decl);
1710
1711          begin
1712             Set_Visible_Declarations        (Orig_Spec, Empty_List);
1713             Set_Generic_Formal_Declarations (Orig_Decl, Empty_List);
1714             Save_Global_References          (Orig_Decl);
1715             Set_Generic_Formal_Declarations (Orig_Decl, Save_Form);
1716             Set_Visible_Declarations        (Orig_Spec, Save_Vis);
1717          end;
1718       end if;
1719
1720       Process_End_Label (N, 'e', Id);
1721
1722       --  Remove private_with_clauses of enclosing compilation unit, if they
1723       --  were installed.
1724
1725       if Private_With_Clauses_Installed then
1726          Remove_Private_With_Clauses (Cunit (Current_Sem_Unit));
1727       end if;
1728
1729       --  For the case of a library level package, we must go through all the
1730       --  entities clearing the indications that the value may be constant and
1731       --  not modified. Why? Because any client of this package may modify
1732       --  these values freely from anywhere. This also applies to any nested
1733       --  packages or generic packages.
1734
1735       --  For now we unconditionally clear constants for packages that are
1736       --  instances of generic packages. The reason is that we do not have the
1737       --  body yet, and we otherwise think things are unreferenced when they
1738       --  are not. This should be fixed sometime (the effect is not terrible,
1739       --  we just lose some warnings, and also some cases of value propagation)
1740       --  ???
1741
1742       if Is_Library_Level_Entity (Id)
1743         or else Is_Generic_Instance (Id)
1744       then
1745          Clear_Constants (Id, First_Entity (Id));
1746          Clear_Constants (Id, First_Private_Entity (Id));
1747       end if;
1748
1749       --  Issue an error in SPARK mode if a package specification contains
1750       --  more than one tagged type or type extension.
1751
1752       Check_One_Tagged_Type_Or_Extension_At_Most;
1753
1754       --  If switch set, output information on why body required
1755
1756       if List_Body_Required_Info
1757         and then In_Extended_Main_Source_Unit (Id)
1758         and then Unit_Requires_Body (Id)
1759       then
1760          Unit_Requires_Body_Info (Id);
1761       end if;
1762    end Analyze_Package_Specification;
1763
1764    --------------------------------------
1765    -- Analyze_Private_Type_Declaration --
1766    --------------------------------------
1767
1768    procedure Analyze_Private_Type_Declaration (N : Node_Id) is
1769       Id : constant Entity_Id := Defining_Identifier (N);
1770       PF : constant Boolean   := Is_Pure (Enclosing_Lib_Unit_Entity);
1771
1772    begin
1773       Generate_Definition (Id);
1774       Set_Is_Pure         (Id, PF);
1775       Init_Size_Align     (Id);
1776
1777       if not Is_Package_Or_Generic_Package (Current_Scope)
1778         or else In_Private_Part (Current_Scope)
1779       then
1780          Error_Msg_N ("invalid context for private declaration", N);
1781       end if;
1782
1783       New_Private_Type (N, Id, N);
1784       Set_Depends_On_Private (Id);
1785
1786       --  A type declared within a Ghost region is automatically Ghost
1787       --  (SPARK RM 6.9(2)).
1788
1789       if Ghost_Mode > None then
1790          Set_Is_Ghost_Entity (Id);
1791       end if;
1792
1793       if Has_Aspects (N) then
1794          Analyze_Aspect_Specifications (N, Id);
1795       end if;
1796    end Analyze_Private_Type_Declaration;
1797
1798    ----------------------------------
1799    -- Check_Anonymous_Access_Types --
1800    ----------------------------------
1801
1802    procedure Check_Anonymous_Access_Types
1803      (Spec_Id : Entity_Id;
1804       P_Body  : Node_Id)
1805    is
1806       E  : Entity_Id;
1807       IR : Node_Id;
1808
1809    begin
1810       --  Itype references are only needed by gigi, to force elaboration of
1811       --  itypes. In the absence of code generation, they are not needed.
1812
1813       if not Expander_Active then
1814          return;
1815       end if;
1816
1817       E := First_Entity (Spec_Id);
1818       while Present (E) loop
1819          if Ekind (E) = E_Anonymous_Access_Type
1820            and then From_Limited_With (E)
1821          then
1822             IR := Make_Itype_Reference (Sloc (P_Body));
1823             Set_Itype (IR, E);
1824
1825             if No (Declarations (P_Body)) then
1826                Set_Declarations (P_Body, New_List (IR));
1827             else
1828                Prepend (IR, Declarations (P_Body));
1829             end if;
1830          end if;
1831
1832          Next_Entity (E);
1833       end loop;
1834    end Check_Anonymous_Access_Types;
1835
1836    -------------------------------------------
1837    -- Declare_Inherited_Private_Subprograms --
1838    -------------------------------------------
1839
1840    procedure Declare_Inherited_Private_Subprograms (Id : Entity_Id) is
1841
1842       function Is_Primitive_Of (T : Entity_Id; S : Entity_Id) return Boolean;
1843       --  Check whether an inherited subprogram S is an operation of an
1844       --  untagged derived type T.
1845
1846       ---------------------
1847       -- Is_Primitive_Of --
1848       ---------------------
1849
1850       function Is_Primitive_Of (T : Entity_Id; S : Entity_Id) return Boolean is
1851          Formal : Entity_Id;
1852
1853       begin
1854          --  If the full view is a scalar type, the type is the anonymous base
1855          --  type, but the operation mentions the first subtype, so check the
1856          --  signature against the base type.
1857
1858          if Base_Type (Etype (S)) = Base_Type (T) then
1859             return True;
1860
1861          else
1862             Formal := First_Formal (S);
1863             while Present (Formal) loop
1864                if Base_Type (Etype (Formal)) = Base_Type (T) then
1865                   return True;
1866                end if;
1867
1868                Next_Formal (Formal);
1869             end loop;
1870
1871             return False;
1872          end if;
1873       end Is_Primitive_Of;
1874
1875       --  Local variables
1876
1877       E           : Entity_Id;
1878       Op_List     : Elist_Id;
1879       Op_Elmt     : Elmt_Id;
1880       Op_Elmt_2   : Elmt_Id;
1881       Prim_Op     : Entity_Id;
1882       New_Op      : Entity_Id := Empty;
1883       Parent_Subp : Entity_Id;
1884       Tag         : Entity_Id;
1885
1886    --  Start of processing for Declare_Inherited_Private_Subprograms
1887
1888    begin
1889       E := First_Entity (Id);
1890       while Present (E) loop
1891
1892          --  If the entity is a nonprivate type extension whose parent type
1893          --  is declared in an open scope, then the type may have inherited
1894          --  operations that now need to be made visible. Ditto if the entity
1895          --  is a formal derived type in a child unit.
1896
1897          if ((Is_Derived_Type (E) and then not Is_Private_Type (E))
1898                or else
1899                  (Nkind (Parent (E)) = N_Private_Extension_Declaration
1900                    and then Is_Generic_Type (E)))
1901            and then In_Open_Scopes (Scope (Etype (E)))
1902            and then Is_Base_Type (E)
1903          then
1904             if Is_Tagged_Type (E) then
1905                Op_List := Primitive_Operations (E);
1906                New_Op  := Empty;
1907                Tag     := First_Tag_Component (E);
1908
1909                Op_Elmt := First_Elmt (Op_List);
1910                while Present (Op_Elmt) loop
1911                   Prim_Op := Node (Op_Elmt);
1912
1913                   --  Search primitives that are implicit operations with an
1914                   --  internal name whose parent operation has a normal name.
1915
1916                   if Present (Alias (Prim_Op))
1917                     and then Find_Dispatching_Type (Alias (Prim_Op)) /= E
1918                     and then not Comes_From_Source (Prim_Op)
1919                     and then Is_Internal_Name (Chars (Prim_Op))
1920                     and then not Is_Internal_Name (Chars (Alias (Prim_Op)))
1921                   then
1922                      Parent_Subp := Alias (Prim_Op);
1923
1924                      --  Case 1: Check if the type has also an explicit
1925                      --  overriding for this primitive.
1926
1927                      Op_Elmt_2 := Next_Elmt (Op_Elmt);
1928                      while Present (Op_Elmt_2) loop
1929
1930                         --  Skip entities with attribute Interface_Alias since
1931                         --  they are not overriding primitives (these entities
1932                         --  link an interface primitive with their covering
1933                         --  primitive)
1934
1935                         if Chars (Node (Op_Elmt_2)) = Chars (Parent_Subp)
1936                           and then Type_Conformant (Prim_Op, Node (Op_Elmt_2))
1937                           and then No (Interface_Alias (Node (Op_Elmt_2)))
1938                         then
1939                            --  The private inherited operation has been
1940                            --  overridden by an explicit subprogram:
1941                            --  replace the former by the latter.
1942
1943                            New_Op := Node (Op_Elmt_2);
1944                            Replace_Elmt (Op_Elmt, New_Op);
1945                            Remove_Elmt  (Op_List, Op_Elmt_2);
1946                            Set_Overridden_Operation (New_Op, Parent_Subp);
1947
1948                            --  We don't need to inherit its dispatching slot.
1949                            --  Set_All_DT_Position has previously ensured that
1950                            --  the same slot was assigned to the two primitives
1951
1952                            if Present (Tag)
1953                              and then Present (DTC_Entity (New_Op))
1954                              and then Present (DTC_Entity (Prim_Op))
1955                            then
1956                               pragma Assert
1957                                 (DT_Position (New_Op) = DT_Position (Prim_Op));
1958                               null;
1959                            end if;
1960
1961                            goto Next_Primitive;
1962                         end if;
1963
1964                         Next_Elmt (Op_Elmt_2);
1965                      end loop;
1966
1967                      --  Case 2: We have not found any explicit overriding and
1968                      --  hence we need to declare the operation (i.e., make it
1969                      --  visible).
1970
1971                      Derive_Subprogram (New_Op, Alias (Prim_Op), E, Etype (E));
1972
1973                      --  Inherit the dispatching slot if E is already frozen
1974
1975                      if Is_Frozen (E)
1976                        and then Present (DTC_Entity (Alias (Prim_Op)))
1977                      then
1978                         Set_DTC_Entity_Value (E, New_Op);
1979                         Set_DT_Position_Value (New_Op,
1980                           DT_Position (Alias (Prim_Op)));
1981                      end if;
1982
1983                      pragma Assert
1984                        (Is_Dispatching_Operation (New_Op)
1985                          and then Node (Last_Elmt (Op_List)) = New_Op);
1986
1987                      --  Substitute the new operation for the old one in the
1988                      --  type's primitive operations list. Since the new
1989                      --  operation was also just added to the end of list,
1990                      --  the last element must be removed.
1991
1992                      --  (Question: is there a simpler way of declaring the
1993                      --  operation, say by just replacing the name of the
1994                      --  earlier operation, reentering it in the in the symbol
1995                      --  table (how?), and marking it as private???)
1996
1997                      Replace_Elmt (Op_Elmt, New_Op);
1998                      Remove_Last_Elmt (Op_List);
1999                   end if;
2000
2001                   <<Next_Primitive>>
2002                   Next_Elmt (Op_Elmt);
2003                end loop;
2004
2005                --  Generate listing showing the contents of the dispatch table
2006
2007                if Debug_Flag_ZZ then
2008                   Write_DT (E);
2009                end if;
2010
2011             else
2012                --  For untagged type, scan forward to locate inherited hidden
2013                --  operations.
2014
2015                Prim_Op := Next_Entity (E);
2016                while Present (Prim_Op) loop
2017                   if Is_Subprogram (Prim_Op)
2018                     and then Present (Alias (Prim_Op))
2019                     and then not Comes_From_Source (Prim_Op)
2020                     and then Is_Internal_Name (Chars (Prim_Op))
2021                     and then not Is_Internal_Name (Chars (Alias (Prim_Op)))
2022                     and then Is_Primitive_Of (E, Prim_Op)
2023                   then
2024                      Derive_Subprogram (New_Op, Alias (Prim_Op), E, Etype (E));
2025                   end if;
2026
2027                   Next_Entity (Prim_Op);
2028
2029                   --  Derived operations appear immediately after the type
2030                   --  declaration (or the following subtype indication for
2031                   --  a derived scalar type). Further declarations cannot
2032                   --  include inherited operations of the type.
2033
2034                   if Present (Prim_Op) then
2035                      exit when Ekind (Prim_Op) not in Overloadable_Kind;
2036                   end if;
2037                end loop;
2038             end if;
2039          end if;
2040
2041          Next_Entity (E);
2042       end loop;
2043    end Declare_Inherited_Private_Subprograms;
2044
2045    -----------------------
2046    -- End_Package_Scope --
2047    -----------------------
2048
2049    procedure End_Package_Scope (P : Entity_Id) is
2050    begin
2051       Uninstall_Declarations (P);
2052       Pop_Scope;
2053    end End_Package_Scope;
2054
2055    ---------------------------
2056    -- Exchange_Declarations --
2057    ---------------------------
2058
2059    procedure Exchange_Declarations (Id : Entity_Id) is
2060       Full_Id : constant Entity_Id := Full_View (Id);
2061       H1      : constant Entity_Id := Homonym (Id);
2062       Next1   : constant Entity_Id := Next_Entity (Id);
2063       H2      : Entity_Id;
2064       Next2   : Entity_Id;
2065
2066    begin
2067       --  If missing full declaration for type, nothing to exchange
2068
2069       if No (Full_Id) then
2070          return;
2071       end if;
2072
2073       --  Otherwise complete the exchange, and preserve semantic links
2074
2075       Next2 := Next_Entity (Full_Id);
2076       H2    := Homonym (Full_Id);
2077
2078       --  Reset full declaration pointer to reflect the switched entities and
2079       --  readjust the next entity chains.
2080
2081       Exchange_Entities (Id, Full_Id);
2082
2083       Set_Next_Entity (Id, Next1);
2084       Set_Homonym     (Id, H1);
2085
2086       Set_Full_View   (Full_Id, Id);
2087       Set_Next_Entity (Full_Id, Next2);
2088       Set_Homonym     (Full_Id, H2);
2089    end Exchange_Declarations;
2090
2091    ----------------------------
2092    -- Install_Package_Entity --
2093    ----------------------------
2094
2095    procedure Install_Package_Entity (Id : Entity_Id) is
2096    begin
2097       if not Is_Internal (Id) then
2098          if Debug_Flag_E then
2099             Write_Str ("Install: ");
2100             Write_Name (Chars (Id));
2101             Write_Eol;
2102          end if;
2103
2104          if Is_Child_Unit (Id) then
2105             null;
2106
2107          --  Do not enter implicitly inherited non-overridden subprograms of
2108          --  a tagged type back into visibility if they have non-conformant
2109          --  homographs (Ada RM 8.3 12.3/2).
2110
2111          elsif Is_Hidden_Non_Overridden_Subpgm (Id) then
2112             null;
2113
2114          else
2115             Set_Is_Immediately_Visible (Id);
2116          end if;
2117       end if;
2118    end Install_Package_Entity;
2119
2120    ----------------------------------
2121    -- Install_Private_Declarations --
2122    ----------------------------------
2123
2124    procedure Install_Private_Declarations (P : Entity_Id) is
2125       Id        : Entity_Id;
2126       Full      : Entity_Id;
2127       Priv_Deps : Elist_Id;
2128
2129       procedure Swap_Private_Dependents (Priv_Deps : Elist_Id);
2130       --  When the full view of a private type is made available, we do the
2131       --  same for its private dependents under proper visibility conditions.
2132       --  When compiling a grand-chid unit this needs to be done recursively.
2133
2134       -----------------------------
2135       -- Swap_Private_Dependents --
2136       -----------------------------
2137
2138       procedure Swap_Private_Dependents (Priv_Deps : Elist_Id) is
2139          Deps      : Elist_Id;
2140          Priv      : Entity_Id;
2141          Priv_Elmt : Elmt_Id;
2142          Is_Priv   : Boolean;
2143
2144       begin
2145          Priv_Elmt := First_Elmt (Priv_Deps);
2146          while Present (Priv_Elmt) loop
2147             Priv := Node (Priv_Elmt);
2148
2149             --  Before the exchange, verify that the presence of the Full_View
2150             --  field. This field will be empty if the entity has already been
2151             --  installed due to a previous call.
2152
2153             if Present (Full_View (Priv)) and then Is_Visible_Dependent (Priv)
2154             then
2155                if Is_Private_Type (Priv) then
2156                   Deps := Private_Dependents (Priv);
2157                   Is_Priv := True;
2158                else
2159                   Is_Priv := False;
2160                end if;
2161
2162                --  For each subtype that is swapped, we also swap the reference
2163                --  to it in Private_Dependents, to allow access to it when we
2164                --  swap them out in End_Package_Scope.
2165
2166                Replace_Elmt (Priv_Elmt, Full_View (Priv));
2167
2168                --  Ensure that both views of the dependent private subtype are
2169                --  immediately visible if within some open scope. Check full
2170                --  view before exchanging views.
2171
2172                if In_Open_Scopes (Scope (Full_View (Priv))) then
2173                   Set_Is_Immediately_Visible (Priv);
2174                end if;
2175
2176                Exchange_Declarations (Priv);
2177                Set_Is_Immediately_Visible
2178                  (Priv, In_Open_Scopes (Scope (Priv)));
2179
2180                Set_Is_Potentially_Use_Visible
2181                  (Priv, Is_Potentially_Use_Visible (Node (Priv_Elmt)));
2182
2183                --  Within a child unit, recurse, except in generic child unit,
2184                --  which (unfortunately) handle private_dependents separately.
2185
2186                if Is_Priv
2187                  and then Is_Child_Unit (Cunit_Entity (Current_Sem_Unit))
2188                  and then not Is_Empty_Elmt_List (Deps)
2189                  and then not Inside_A_Generic
2190                then
2191                   Swap_Private_Dependents (Deps);
2192                end if;
2193             end if;
2194
2195             Next_Elmt (Priv_Elmt);
2196          end loop;
2197       end Swap_Private_Dependents;
2198
2199    --  Start of processing for Install_Private_Declarations
2200
2201    begin
2202       --  First exchange declarations for private types, so that the full
2203       --  declaration is visible. For each private type, we check its
2204       --  Private_Dependents list and also exchange any subtypes of or derived
2205       --  types from it. Finally, if this is a Taft amendment type, the
2206       --  incomplete declaration is irrelevant, and we want to link the
2207       --  eventual full declaration with the original private one so we
2208       --  also skip the exchange.
2209
2210       Id := First_Entity (P);
2211       while Present (Id) and then Id /= First_Private_Entity (P) loop
2212          if Is_Private_Base_Type (Id)
2213            and then Present (Full_View (Id))
2214            and then Comes_From_Source (Full_View (Id))
2215            and then Scope (Full_View (Id)) = Scope (Id)
2216            and then Ekind (Full_View (Id)) /= E_Incomplete_Type
2217          then
2218             --  If there is a use-type clause on the private type, set the full
2219             --  view accordingly.
2220
2221             Set_In_Use (Full_View (Id), In_Use (Id));
2222             Full := Full_View (Id);
2223
2224             if Is_Private_Base_Type (Full)
2225               and then Has_Private_Declaration (Full)
2226               and then Nkind (Parent (Full)) = N_Full_Type_Declaration
2227               and then In_Open_Scopes (Scope (Etype (Full)))
2228               and then In_Package_Body (Current_Scope)
2229               and then not Is_Private_Type (Etype (Full))
2230             then
2231                --  This is the completion of a private type by a derivation
2232                --  from another private type which is not private anymore. This
2233                --  can only happen in a package nested within a child package,
2234                --  when the parent type is defined in the parent unit. At this
2235                --  point the current type is not private either, and we have
2236                --  to install the underlying full view, which is now visible.
2237                --  Save the current full view as well, so that all views can be
2238                --  restored on exit. It may seem that after compiling the child
2239                --  body there are not environments to restore, but the back-end
2240                --  expects those links to be valid, and freeze nodes depend on
2241                --  them.
2242
2243                if No (Full_View (Full))
2244                  and then Present (Underlying_Full_View (Full))
2245                then
2246                   Set_Full_View (Id, Underlying_Full_View (Full));
2247                   Set_Underlying_Full_View (Id, Full);
2248
2249                   Set_Underlying_Full_View (Full, Empty);
2250                   Set_Is_Frozen (Full_View (Id));
2251                end if;
2252             end if;
2253
2254             Priv_Deps := Private_Dependents (Id);
2255             Exchange_Declarations (Id);
2256             Set_Is_Immediately_Visible (Id);
2257             Swap_Private_Dependents (Priv_Deps);
2258          end if;
2259
2260          Next_Entity (Id);
2261       end loop;
2262
2263       --  Next make other declarations in the private part visible as well
2264
2265       Id := First_Private_Entity (P);
2266       while Present (Id) loop
2267          Install_Package_Entity (Id);
2268          Set_Is_Hidden (Id, False);
2269          Next_Entity (Id);
2270       end loop;
2271
2272       --  Indicate that the private part is currently visible, so it can be
2273       --  properly reset on exit.
2274
2275       Set_In_Private_Part (P);
2276    end Install_Private_Declarations;
2277
2278    ----------------------------------
2279    -- Install_Visible_Declarations --
2280    ----------------------------------
2281
2282    procedure Install_Visible_Declarations (P : Entity_Id) is
2283       Id          : Entity_Id;
2284       Last_Entity : Entity_Id;
2285
2286    begin
2287       pragma Assert
2288         (Is_Package_Or_Generic_Package (P) or else Is_Record_Type (P));
2289
2290       if Is_Package_Or_Generic_Package (P) then
2291          Last_Entity := First_Private_Entity (P);
2292       else
2293          Last_Entity := Empty;
2294       end if;
2295
2296       Id := First_Entity (P);
2297       while Present (Id) and then Id /= Last_Entity loop
2298          Install_Package_Entity (Id);
2299          Next_Entity (Id);
2300       end loop;
2301    end Install_Visible_Declarations;
2302
2303    --------------------------
2304    -- Is_Private_Base_Type --
2305    --------------------------
2306
2307    function Is_Private_Base_Type (E : Entity_Id) return Boolean is
2308    begin
2309       return Ekind (E) = E_Private_Type
2310         or else Ekind (E) = E_Limited_Private_Type
2311         or else Ekind (E) = E_Record_Type_With_Private;
2312    end Is_Private_Base_Type;
2313
2314    --------------------------
2315    -- Is_Visible_Dependent --
2316    --------------------------
2317
2318    function Is_Visible_Dependent (Dep : Entity_Id) return Boolean
2319    is
2320       S : constant Entity_Id := Scope (Dep);
2321
2322    begin
2323       --  Renamings created for actual types have the visibility of the actual
2324
2325       if Ekind (S) = E_Package
2326         and then Is_Generic_Instance (S)
2327         and then (Is_Generic_Actual_Type (Dep)
2328                    or else Is_Generic_Actual_Type (Full_View (Dep)))
2329       then
2330          return True;
2331
2332       elsif not (Is_Derived_Type (Dep))
2333         and then Is_Derived_Type (Full_View (Dep))
2334       then
2335          --  When instantiating a package body, the scope stack is empty, so
2336          --  check instead whether the dependent type is defined in the same
2337          --  scope as the instance itself.
2338
2339          return In_Open_Scopes (S)
2340            or else (Is_Generic_Instance (Current_Scope)
2341                      and then Scope (Dep) = Scope (Current_Scope));
2342       else
2343          return True;
2344       end if;
2345    end Is_Visible_Dependent;
2346
2347    ----------------------------
2348    -- May_Need_Implicit_Body --
2349    ----------------------------
2350
2351    procedure May_Need_Implicit_Body (E : Entity_Id) is
2352       P     : constant Node_Id := Unit_Declaration_Node (E);
2353       S     : constant Node_Id := Parent (P);
2354       B     : Node_Id;
2355       Decls : List_Id;
2356
2357    begin
2358       if not Has_Completion (E)
2359         and then Nkind (P) = N_Package_Declaration
2360         and then (Present (Activation_Chain_Entity (P)) or else Has_RACW (E))
2361       then
2362          B :=
2363            Make_Package_Body (Sloc (E),
2364              Defining_Unit_Name => Make_Defining_Identifier (Sloc (E),
2365                Chars => Chars (E)),
2366              Declarations  => New_List);
2367
2368          if Nkind (S) = N_Package_Specification then
2369             if Present (Private_Declarations (S)) then
2370                Decls := Private_Declarations (S);
2371             else
2372                Decls := Visible_Declarations (S);
2373             end if;
2374          else
2375             Decls := Declarations (S);
2376          end if;
2377
2378          Append (B, Decls);
2379          Analyze (B);
2380       end if;
2381    end May_Need_Implicit_Body;
2382
2383    ----------------------
2384    -- New_Private_Type --
2385    ----------------------
2386
2387    procedure New_Private_Type (N : Node_Id; Id : Entity_Id; Def : Node_Id) is
2388    begin
2389       --  For other than Ada 2012, enter the name in the current scope
2390
2391       if Ada_Version < Ada_2012 then
2392          Enter_Name (Id);
2393
2394       --  Ada 2012 (AI05-0162): Enter the name in the current scope. Note that
2395       --  there may be an incomplete previous view.
2396
2397       else
2398          declare
2399             Prev : Entity_Id;
2400          begin
2401             Prev := Find_Type_Name (N);
2402             pragma Assert (Prev = Id
2403               or else (Ekind (Prev) = E_Incomplete_Type
2404                         and then Present (Full_View (Prev))
2405                         and then Full_View (Prev) = Id));
2406          end;
2407       end if;
2408
2409       if Limited_Present (Def) then
2410          Set_Ekind (Id, E_Limited_Private_Type);
2411       else
2412          Set_Ekind (Id, E_Private_Type);
2413       end if;
2414
2415       Set_Etype              (Id, Id);
2416       Set_Has_Delayed_Freeze (Id);
2417       Set_Is_First_Subtype   (Id);
2418       Init_Size_Align        (Id);
2419
2420       Set_Is_Constrained (Id,
2421         No (Discriminant_Specifications (N))
2422           and then not Unknown_Discriminants_Present (N));
2423
2424       --  Set tagged flag before processing discriminants, to catch illegal
2425       --  usage.
2426
2427       Set_Is_Tagged_Type (Id, Tagged_Present (Def));
2428
2429       Set_Discriminant_Constraint (Id, No_Elist);
2430       Set_Stored_Constraint (Id, No_Elist);
2431
2432       if Present (Discriminant_Specifications (N)) then
2433          Push_Scope (Id);
2434          Process_Discriminants (N);
2435          End_Scope;
2436
2437       elsif Unknown_Discriminants_Present (N) then
2438          Set_Has_Unknown_Discriminants (Id);
2439       end if;
2440
2441       Set_Private_Dependents (Id, New_Elmt_List);
2442
2443       if Tagged_Present (Def) then
2444          Set_Ekind                       (Id, E_Record_Type_With_Private);
2445          Set_Direct_Primitive_Operations (Id, New_Elmt_List);
2446          Set_Is_Abstract_Type            (Id, Abstract_Present (Def));
2447          Set_Is_Limited_Record           (Id, Limited_Present (Def));
2448          Set_Has_Delayed_Freeze          (Id, True);
2449
2450          --  Recognize Ada.Real_Time.Timing_Events.Timing_Events here
2451
2452          if Is_RTE (Id, RE_Timing_Event) then
2453             Set_Has_Timing_Event (Id);
2454          end if;
2455
2456          --  Create a class-wide type with the same attributes
2457
2458          Make_Class_Wide_Type (Id);
2459
2460       elsif Abstract_Present (Def) then
2461          Error_Msg_N ("only a tagged type can be abstract", N);
2462       end if;
2463    end New_Private_Type;
2464
2465    ---------------------------------
2466    -- Requires_Completion_In_Body --
2467    ---------------------------------
2468
2469    function Requires_Completion_In_Body
2470      (Id                 : Entity_Id;
2471       Pack_Id            : Entity_Id;
2472       Do_Abstract_States : Boolean := False) return Boolean
2473    is
2474    begin
2475       --  Always ignore child units. Child units get added to the entity list
2476       --  of a parent unit, but are not original entities of the parent, and
2477       --  so do not affect whether the parent needs a body.
2478
2479       if Is_Child_Unit (Id) then
2480          return False;
2481
2482       --  Ignore formal packages and their renamings
2483
2484       elsif Ekind (Id) = E_Package
2485         and then Nkind (Original_Node (Unit_Declaration_Node (Id))) =
2486                    N_Formal_Package_Declaration
2487       then
2488          return False;
2489
2490       --  Otherwise test to see if entity requires a completion. Note that
2491       --  subprogram entities whose declaration does not come from source are
2492       --  ignored here on the basis that we assume the expander will provide an
2493       --  implicit completion at some point.
2494
2495       elsif (Is_Overloadable (Id)
2496               and then not Ekind_In (Id, E_Enumeration_Literal, E_Operator)
2497               and then not Is_Abstract_Subprogram (Id)
2498               and then not Has_Completion (Id)
2499               and then Comes_From_Source (Parent (Id)))
2500
2501         or else
2502           (Ekind (Id) = E_Package
2503             and then Id /= Pack_Id
2504             and then not Has_Completion (Id)
2505             and then Unit_Requires_Body (Id, Do_Abstract_States))
2506
2507         or else
2508           (Ekind (Id) = E_Incomplete_Type
2509             and then No (Full_View (Id))
2510             and then not Is_Generic_Type (Id))
2511
2512         or else
2513           (Ekind_In (Id, E_Task_Type, E_Protected_Type)
2514             and then not Has_Completion (Id))
2515
2516         or else
2517           (Ekind (Id) = E_Generic_Package
2518             and then Id /= Pack_Id
2519             and then not Has_Completion (Id)
2520             and then Unit_Requires_Body (Id, Do_Abstract_States))
2521
2522         or else
2523           (Is_Generic_Subprogram (Id)
2524             and then not Has_Completion (Id))
2525       then
2526          return True;
2527
2528       --  Otherwise the entity does not require completion in a package body
2529
2530       else
2531          return False;
2532       end if;
2533    end Requires_Completion_In_Body;
2534
2535    ----------------------------
2536    -- Uninstall_Declarations --
2537    ----------------------------
2538
2539    procedure Uninstall_Declarations (P : Entity_Id) is
2540       Decl      : constant Node_Id := Unit_Declaration_Node (P);
2541       Id        : Entity_Id;
2542       Full      : Entity_Id;
2543       Priv_Elmt : Elmt_Id;
2544       Priv_Sub  : Entity_Id;
2545
2546       procedure Preserve_Full_Attributes (Priv, Full : Entity_Id);
2547       --  Copy to the private declaration the attributes of the full view that
2548       --  need to be available for the partial view also.
2549
2550       function Type_In_Use (T : Entity_Id) return Boolean;
2551       --  Check whether type or base type appear in an active use_type clause
2552
2553       ------------------------------
2554       -- Preserve_Full_Attributes --
2555       ------------------------------
2556
2557       procedure Preserve_Full_Attributes (Priv, Full : Entity_Id) is
2558          Priv_Is_Base_Type : constant Boolean := Is_Base_Type (Priv);
2559
2560       begin
2561          Set_Size_Info (Priv, (Full));
2562          Set_RM_Size                 (Priv, RM_Size (Full));
2563          Set_Size_Known_At_Compile_Time
2564                                      (Priv, Size_Known_At_Compile_Time (Full));
2565          Set_Is_Volatile             (Priv, Is_Volatile                (Full));
2566          Set_Treat_As_Volatile       (Priv, Treat_As_Volatile          (Full));
2567          Set_Is_Ada_2005_Only        (Priv, Is_Ada_2005_Only           (Full));
2568          Set_Is_Ada_2012_Only        (Priv, Is_Ada_2012_Only           (Full));
2569          Set_Has_Pragma_Unmodified   (Priv, Has_Pragma_Unmodified      (Full));
2570          Set_Has_Pragma_Unreferenced (Priv, Has_Pragma_Unreferenced    (Full));
2571          Set_Has_Pragma_Unreferenced_Objects
2572                                      (Priv, Has_Pragma_Unreferenced_Objects
2573                                                                        (Full));
2574          if Is_Unchecked_Union (Full) then
2575             Set_Is_Unchecked_Union (Base_Type (Priv));
2576          end if;
2577          --  Why is atomic not copied here ???
2578
2579          if Referenced (Full) then
2580             Set_Referenced (Priv);
2581          end if;
2582
2583          if Priv_Is_Base_Type then
2584             Set_Is_Controlled (Priv, Is_Controlled (Base_Type (Full)));
2585             Set_Finalize_Storage_Only
2586                               (Priv, Finalize_Storage_Only
2587                                                    (Base_Type (Full)));
2588             Propagate_Concurrent_Flags
2589                               (Priv,                Base_Type (Full));
2590             Set_Has_Controlled_Component
2591                               (Priv, Has_Controlled_Component
2592                                                    (Base_Type (Full)));
2593          end if;
2594
2595          Set_Freeze_Node (Priv, Freeze_Node (Full));
2596
2597          --  Propagate information of type invariants, which may be specified
2598          --  for the full view.
2599
2600          if Has_Invariants (Full) and not Has_Invariants (Priv) then
2601             Set_Has_Invariants (Priv);
2602             Set_Subprograms_For_Type (Priv, Subprograms_For_Type (Full));
2603          end if;
2604
2605          if Is_Tagged_Type (Priv)
2606            and then Is_Tagged_Type (Full)
2607            and then not Error_Posted (Full)
2608          then
2609             if Is_Tagged_Type (Priv) then
2610
2611                --  If the type is tagged, the tag itself must be available on
2612                --  the partial view, for expansion purposes.
2613
2614                Set_First_Entity (Priv, First_Entity (Full));
2615
2616                --  If there are discriminants in the partial view, these remain
2617                --  visible. Otherwise only the tag itself is visible, and there
2618                --  are no nameable components in the partial view.
2619
2620                if No (Last_Entity (Priv)) then
2621                   Set_Last_Entity (Priv, First_Entity (Priv));
2622                end if;
2623             end if;
2624
2625             Set_Has_Discriminants (Priv, Has_Discriminants (Full));
2626
2627             if Has_Discriminants (Full) then
2628                Set_Discriminant_Constraint (Priv,
2629                  Discriminant_Constraint (Full));
2630             end if;
2631          end if;
2632       end Preserve_Full_Attributes;
2633
2634       -----------------
2635       -- Type_In_Use --
2636       -----------------
2637
2638       function Type_In_Use (T : Entity_Id) return Boolean is
2639       begin
2640          return Scope (Base_Type (T)) = P
2641            and then (In_Use (T) or else In_Use (Base_Type (T)));
2642       end Type_In_Use;
2643
2644    --  Start of processing for Uninstall_Declarations
2645
2646    begin
2647       Id := First_Entity (P);
2648       while Present (Id) and then Id /= First_Private_Entity (P) loop
2649          if Debug_Flag_E then
2650             Write_Str ("unlinking visible entity ");
2651             Write_Int (Int (Id));
2652             Write_Eol;
2653          end if;
2654
2655          --  On exit from the package scope, we must preserve the visibility
2656          --  established by use clauses in the current scope. Two cases:
2657
2658          --  a) If the entity is an operator, it may be a primitive operator of
2659          --  a type for which there is a visible use-type clause.
2660
2661          --  b) for other entities, their use-visibility is determined by a
2662          --  visible use clause for the package itself. For a generic instance,
2663          --  the instantiation of the formals appears in the visible part,
2664          --  but the formals are private and remain so.
2665
2666          if Ekind (Id) = E_Function
2667            and then Is_Operator_Symbol_Name (Chars (Id))
2668            and then not Is_Hidden (Id)
2669            and then not Error_Posted (Id)
2670          then
2671             Set_Is_Potentially_Use_Visible (Id,
2672               In_Use (P)
2673               or else Type_In_Use (Etype (Id))
2674               or else Type_In_Use (Etype (First_Formal (Id)))
2675               or else (Present (Next_Formal (First_Formal (Id)))
2676                         and then
2677                           Type_In_Use
2678                             (Etype (Next_Formal (First_Formal (Id))))));
2679          else
2680             if In_Use (P) and then not Is_Hidden (Id) then
2681
2682                --  A child unit of a use-visible package remains use-visible
2683                --  only if it is itself a visible child unit. Otherwise it
2684                --  would remain visible in other contexts where P is use-
2685                --  visible, because once compiled it stays in the entity list
2686                --  of its parent unit.
2687
2688                if Is_Child_Unit (Id) then
2689                   Set_Is_Potentially_Use_Visible
2690                     (Id, Is_Visible_Lib_Unit (Id));
2691                else
2692                   Set_Is_Potentially_Use_Visible (Id);
2693                end if;
2694
2695             else
2696                Set_Is_Potentially_Use_Visible (Id, False);
2697             end if;
2698          end if;
2699
2700          --  Local entities are not immediately visible outside of the package
2701
2702          Set_Is_Immediately_Visible (Id, False);
2703
2704          --  If this is a private type with a full view (for example a local
2705          --  subtype of a private type declared elsewhere), ensure that the
2706          --  full view is also removed from visibility: it may be exposed when
2707          --  swapping views in an instantiation. Similarly, ensure that the
2708          --  use-visibility is properly set on both views.
2709
2710          if Is_Type (Id) and then Present (Full_View (Id)) then
2711             Set_Is_Immediately_Visible     (Full_View (Id), False);
2712             Set_Is_Potentially_Use_Visible (Full_View (Id),
2713               Is_Potentially_Use_Visible (Id));
2714          end if;
2715
2716          if Is_Tagged_Type (Id) and then Ekind (Id) = E_Record_Type then
2717             Check_Abstract_Overriding (Id);
2718             Check_Conventions (Id);
2719          end if;
2720
2721          if Ekind_In (Id, E_Private_Type, E_Limited_Private_Type)
2722            and then No (Full_View (Id))
2723            and then not Is_Generic_Type (Id)
2724            and then not Is_Derived_Type (Id)
2725          then
2726             Error_Msg_N ("missing full declaration for private type&", Id);
2727
2728          elsif Ekind (Id) = E_Record_Type_With_Private
2729            and then not Is_Generic_Type (Id)
2730            and then No (Full_View (Id))
2731          then
2732             if Nkind (Parent (Id)) = N_Private_Type_Declaration then
2733                Error_Msg_N ("missing full declaration for private type&", Id);
2734             else
2735                Error_Msg_N
2736                  ("missing full declaration for private extension", Id);
2737             end if;
2738
2739          --  Case of constant, check for deferred constant declaration with
2740          --  no full view. Likely just a matter of a missing expression, or
2741          --  accidental use of the keyword constant.
2742
2743          elsif Ekind (Id) = E_Constant
2744
2745            --  OK if constant value present
2746
2747            and then No (Constant_Value (Id))
2748
2749            --  OK if full view present
2750
2751            and then No (Full_View (Id))
2752
2753            --  OK if imported, since that provides the completion
2754
2755            and then not Is_Imported (Id)
2756
2757            --  OK if object declaration replaced by renaming declaration as
2758            --  a result of OK_To_Rename processing (e.g. for concatenation)
2759
2760            and then Nkind (Parent (Id)) /= N_Object_Renaming_Declaration
2761
2762            --  OK if object declaration with the No_Initialization flag set
2763
2764            and then not (Nkind (Parent (Id)) = N_Object_Declaration
2765                           and then No_Initialization (Parent (Id)))
2766          then
2767             --  If no private declaration is present, we assume the user did
2768             --  not intend a deferred constant declaration and the problem
2769             --  is simply that the initializing expression is missing.
2770
2771             if not Has_Private_Declaration (Etype (Id)) then
2772
2773                --  We assume that the user did not intend a deferred constant
2774                --  declaration, and the expression is just missing.
2775
2776                Error_Msg_N
2777                  ("constant declaration requires initialization expression",
2778                    Parent (Id));
2779
2780                if Is_Limited_Type (Etype (Id)) then
2781                   Error_Msg_N
2782                     ("\if variable intended, remove CONSTANT from declaration",
2783                     Parent (Id));
2784                end if;
2785
2786             --  Otherwise if a private declaration is present, then we are
2787             --  missing the full declaration for the deferred constant.
2788
2789             else
2790                Error_Msg_N
2791                  ("missing full declaration for deferred constant (RM 7.4)",
2792                   Id);
2793
2794                if Is_Limited_Type (Etype (Id)) then
2795                   Error_Msg_N
2796                     ("\if variable intended, remove CONSTANT from declaration",
2797                      Parent (Id));
2798                end if;
2799             end if;
2800          end if;
2801
2802          Next_Entity (Id);
2803       end loop;
2804
2805       --  If the specification was installed as the parent of a public child
2806       --  unit, the private declarations were not installed, and there is
2807       --  nothing to do.
2808
2809       if not In_Private_Part (P) then
2810          return;
2811       else
2812          Set_In_Private_Part (P, False);
2813       end if;
2814
2815       --  Make private entities invisible and exchange full and private
2816       --  declarations for private types. Id is now the first private entity
2817       --  in the package.
2818
2819       while Present (Id) loop
2820          if Debug_Flag_E then
2821             Write_Str ("unlinking private entity ");
2822             Write_Int (Int (Id));
2823             Write_Eol;
2824          end if;
2825
2826          if Is_Tagged_Type (Id) and then Ekind (Id) = E_Record_Type then
2827             Check_Abstract_Overriding (Id);
2828             Check_Conventions (Id);
2829          end if;
2830
2831          Set_Is_Immediately_Visible (Id, False);
2832
2833          if Is_Private_Base_Type (Id) and then Present (Full_View (Id)) then
2834             Full := Full_View (Id);
2835
2836             --  If the partial view is not declared in the visible part of the
2837             --  package (as is the case when it is a type derived from some
2838             --  other private type in the private part of the current package),
2839             --  no exchange takes place.
2840
2841             if No (Parent (Id))
2842               or else List_Containing (Parent (Id)) /=
2843                                Visible_Declarations (Specification (Decl))
2844             then
2845                goto Next_Id;
2846             end if;
2847
2848             --  The entry in the private part points to the full declaration,
2849             --  which is currently visible. Exchange them so only the private
2850             --  type declaration remains accessible, and link private and full
2851             --  declaration in the opposite direction. Before the actual
2852             --  exchange, we copy back attributes of the full view that must
2853             --  be available to the partial view too.
2854
2855             Preserve_Full_Attributes (Id, Full);
2856
2857             Set_Is_Potentially_Use_Visible (Id, In_Use (P));
2858
2859             --  The following test may be redundant, as this is already
2860             --  diagnosed in sem_ch3. ???
2861
2862             if not Is_Definite_Subtype (Full)
2863               and then Is_Definite_Subtype (Id)
2864             then
2865                Error_Msg_Sloc := Sloc (Parent (Id));
2866                Error_Msg_NE
2867                  ("full view of& not compatible with declaration#", Full, Id);
2868             end if;
2869
2870             --  Swap out the subtypes and derived types of Id that
2871             --  were compiled in this scope, or installed previously
2872             --  by Install_Private_Declarations.
2873
2874             --  Before we do the swap, we verify the presence of the Full_View
2875             --  field which may be empty due to a swap by a previous call to
2876             --  End_Package_Scope (e.g. from the freezing mechanism).
2877
2878             Priv_Elmt := First_Elmt (Private_Dependents (Id));
2879             while Present (Priv_Elmt) loop
2880                Priv_Sub := Node (Priv_Elmt);
2881
2882                if Present (Full_View (Priv_Sub)) then
2883                   if Scope (Priv_Sub) = P
2884                      or else not In_Open_Scopes (Scope (Priv_Sub))
2885                   then
2886                      Set_Is_Immediately_Visible (Priv_Sub, False);
2887                   end if;
2888
2889                   if Is_Visible_Dependent (Priv_Sub) then
2890                      Preserve_Full_Attributes
2891                        (Priv_Sub, Full_View (Priv_Sub));
2892                      Replace_Elmt (Priv_Elmt, Full_View (Priv_Sub));
2893                      Exchange_Declarations (Priv_Sub);
2894                   end if;
2895                end if;
2896
2897                Next_Elmt (Priv_Elmt);
2898             end loop;
2899
2900             --  Now restore the type itself to its private view
2901
2902             Exchange_Declarations (Id);
2903
2904             --  If we have installed an underlying full view for a type derived
2905             --  from a private type in a child unit, restore the proper views
2906             --  of private and full view. See corresponding code in
2907             --  Install_Private_Declarations.
2908
2909             --  After the exchange, Full denotes the private type in the
2910             --  visible part of the package.
2911
2912             if Is_Private_Base_Type (Full)
2913               and then Present (Full_View (Full))
2914               and then Present (Underlying_Full_View (Full))
2915               and then In_Package_Body (Current_Scope)
2916             then
2917                Set_Full_View (Full, Underlying_Full_View (Full));
2918                Set_Underlying_Full_View (Full, Empty);
2919             end if;
2920
2921          elsif Ekind (Id) = E_Incomplete_Type
2922            and then Comes_From_Source (Id)
2923            and then No (Full_View (Id))
2924          then
2925             --  Mark Taft amendment types. Verify that there are no primitive
2926             --  operations declared for the type (3.10.1(9)).
2927
2928             Set_Has_Completion_In_Body (Id);
2929
2930             declare
2931                Elmt : Elmt_Id;
2932                Subp : Entity_Id;
2933
2934             begin
2935                Elmt := First_Elmt (Private_Dependents (Id));
2936                while Present (Elmt) loop
2937                   Subp := Node (Elmt);
2938
2939                   --  Is_Primitive is tested because there can be cases where
2940                   --  nonprimitive subprograms (in nested packages) are added
2941                   --  to the Private_Dependents list.
2942
2943                   if Is_Overloadable (Subp) and then Is_Primitive (Subp) then
2944                      Error_Msg_NE
2945                        ("type& must be completed in the private part",
2946                          Parent (Subp), Id);
2947
2948                   --  The result type of an access-to-function type cannot be a
2949                   --  Taft-amendment type, unless the version is Ada 2012 or
2950                   --  later (see AI05-151).
2951
2952                   elsif Ada_Version < Ada_2012
2953                     and then Ekind (Subp) = E_Subprogram_Type
2954                   then
2955                      if Etype (Subp) = Id
2956                        or else
2957                          (Is_Class_Wide_Type (Etype (Subp))
2958                            and then Etype (Etype (Subp)) = Id)
2959                      then
2960                         Error_Msg_NE
2961                           ("type& must be completed in the private part",
2962                              Associated_Node_For_Itype (Subp), Id);
2963                      end if;
2964                   end if;
2965
2966                   Next_Elmt (Elmt);
2967                end loop;
2968             end;
2969
2970          elsif not Is_Child_Unit (Id)
2971            and then (not Is_Private_Type (Id) or else No (Full_View (Id)))
2972          then
2973             Set_Is_Hidden (Id);
2974             Set_Is_Potentially_Use_Visible (Id, False);
2975          end if;
2976
2977          <<Next_Id>>
2978             Next_Entity (Id);
2979       end loop;
2980    end Uninstall_Declarations;
2981
2982    ------------------------
2983    -- Unit_Requires_Body --
2984    ------------------------
2985
2986    function Unit_Requires_Body
2987      (Pack_Id            : Entity_Id;
2988       Do_Abstract_States : Boolean := False) return Boolean
2989    is
2990       E : Entity_Id;
2991
2992       Requires_Body : Boolean := False;
2993       --  Flag set when the unit has at least one construct that requries
2994       --  completion in a body.
2995
2996    begin
2997       --  Imported entity never requires body. Right now, only subprograms can
2998       --  be imported, but perhaps in the future we will allow import of
2999       --  packages.
3000
3001       if Is_Imported (Pack_Id) then
3002          return False;
3003
3004       --  Body required if library package with pragma Elaborate_Body
3005
3006       elsif Has_Pragma_Elaborate_Body (Pack_Id) then
3007          return True;
3008
3009       --  Body required if subprogram
3010
3011       elsif Is_Subprogram_Or_Generic_Subprogram (Pack_Id) then
3012          return True;
3013
3014       --  Treat a block as requiring a body
3015
3016       elsif Ekind (Pack_Id) = E_Block then
3017          return True;
3018
3019       elsif Ekind (Pack_Id) = E_Package
3020         and then Nkind (Parent (Pack_Id)) = N_Package_Specification
3021         and then Present (Generic_Parent (Parent (Pack_Id)))
3022       then
3023          declare
3024             G_P : constant Entity_Id := Generic_Parent (Parent (Pack_Id));
3025          begin
3026             if Has_Pragma_Elaborate_Body (G_P) then
3027                return True;
3028             end if;
3029          end;
3030       end if;
3031
3032       --  Traverse the entity chain of the package and look for constructs that
3033       --  require a completion in a body.
3034
3035       E := First_Entity (Pack_Id);
3036       while Present (E) loop
3037
3038          --  Skip abstract states because their completion depends on several
3039          --  criteria (see below).
3040
3041          if Ekind (E) = E_Abstract_State then
3042             null;
3043
3044          elsif Requires_Completion_In_Body
3045                  (E, Pack_Id, Do_Abstract_States)
3046          then
3047             Requires_Body := True;
3048             exit;
3049          end if;
3050
3051          Next_Entity (E);
3052       end loop;
3053
3054       --  A [generic] package that defines at least one non-null abstract state
3055       --  requires a completion only when at least one other construct requires
3056       --  a completion in a body (SPARK RM 7.1.4(4) and (6)). This check is not
3057       --  performed if the caller requests this behavior.
3058
3059       if Do_Abstract_States
3060         and then Ekind_In (Pack_Id, E_Generic_Package, E_Package)
3061         and then Has_Non_Null_Abstract_State (Pack_Id)
3062         and then Requires_Body
3063       then
3064          return True;
3065       end if;
3066
3067       return Requires_Body;
3068    end Unit_Requires_Body;
3069
3070    -----------------------------
3071    -- Unit_Requires_Body_Info --
3072    -----------------------------
3073
3074    procedure Unit_Requires_Body_Info (Pack_Id : Entity_Id) is
3075       E : Entity_Id;
3076
3077    begin
3078       --  An imported entity never requires body. Right now, only subprograms
3079       --  can be imported, but perhaps in the future we will allow import of
3080       --  packages.
3081
3082       if Is_Imported (Pack_Id) then
3083          return;
3084
3085       --  Body required if library package with pragma Elaborate_Body
3086
3087       elsif Has_Pragma_Elaborate_Body (Pack_Id) then
3088          Error_Msg_N ("info: & requires body (Elaborate_Body)?Y?", Pack_Id);
3089
3090       --  Body required if subprogram
3091
3092       elsif Is_Subprogram_Or_Generic_Subprogram (Pack_Id) then
3093          Error_Msg_N ("info: & requires body (subprogram case)?Y?", Pack_Id);
3094
3095       --  Body required if generic parent has Elaborate_Body
3096
3097       elsif Ekind (Pack_Id) = E_Package
3098         and then Nkind (Parent (Pack_Id)) = N_Package_Specification
3099         and then Present (Generic_Parent (Parent (Pack_Id)))
3100       then
3101          declare
3102             G_P : constant Entity_Id := Generic_Parent (Parent (Pack_Id));
3103          begin
3104             if Has_Pragma_Elaborate_Body (G_P) then
3105                Error_Msg_N
3106                  ("info: & requires body (generic parent Elaborate_Body)?Y?",
3107                   Pack_Id);
3108             end if;
3109          end;
3110
3111       --  A [generic] package that introduces at least one non-null abstract
3112       --  state requires completion. However, there is a separate rule that
3113       --  requires that such a package have a reason other than this for a
3114       --  body being required (if necessary a pragma Elaborate_Body must be
3115       --  provided). If Ignore_Abstract_State is True, we don't do this check
3116       --  (so we can use Unit_Requires_Body to check for some other reason).
3117
3118       elsif Ekind_In (Pack_Id, E_Generic_Package, E_Package)
3119         and then Present (Abstract_States (Pack_Id))
3120         and then not Is_Null_State
3121                        (Node (First_Elmt (Abstract_States (Pack_Id))))
3122       then
3123          Error_Msg_N
3124            ("info: & requires body (non-null abstract state aspect)?Y?",
3125             Pack_Id);
3126       end if;
3127
3128       --  Otherwise search entity chain for entity requiring completion
3129
3130       E := First_Entity (Pack_Id);
3131       while Present (E) loop
3132          if Requires_Completion_In_Body (E, Pack_Id) then
3133             Error_Msg_Node_2 := E;
3134             Error_Msg_NE
3135               ("info: & requires body (& requires completion)?Y?", E, Pack_Id);
3136          end if;
3137
3138          Next_Entity (E);
3139       end loop;
3140    end Unit_Requires_Body_Info;
3141 end Sem_Ch7;