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