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