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