1------------------------------------------------------------------------------
2--                                                                          --
3--                         GNAT COMPILER COMPONENTS                         --
4--                                                                          --
5--                              S E M _ C H 3                               --
6--                                                                          --
7--                                 B o d y                                  --
8--                                                                          --
9--          Copyright (C) 1992-2019, 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
26with Aspects;   use Aspects;
27with Atree;     use Atree;
28with Checks;    use Checks;
29with Contracts; use Contracts;
30with Debug;     use Debug;
31with Elists;    use Elists;
32with Einfo;     use Einfo;
33with Errout;    use Errout;
34with Eval_Fat;  use Eval_Fat;
35with Exp_Ch3;   use Exp_Ch3;
36with Exp_Ch9;   use Exp_Ch9;
37with Exp_Disp;  use Exp_Disp;
38with Exp_Dist;  use Exp_Dist;
39with Exp_Tss;   use Exp_Tss;
40with Exp_Util;  use Exp_Util;
41with Freeze;    use Freeze;
42with Ghost;     use Ghost;
43with Itypes;    use Itypes;
44with Layout;    use Layout;
45with Lib;       use Lib;
46with Lib.Xref;  use Lib.Xref;
47with Namet;     use Namet;
48with Nmake;     use Nmake;
49with Opt;       use Opt;
50with Restrict;  use Restrict;
51with Rident;    use Rident;
52with Rtsfind;   use Rtsfind;
53with Sem;       use Sem;
54with Sem_Aux;   use Sem_Aux;
55with Sem_Case;  use Sem_Case;
56with Sem_Cat;   use Sem_Cat;
57with Sem_Ch6;   use Sem_Ch6;
58with Sem_Ch7;   use Sem_Ch7;
59with Sem_Ch8;   use Sem_Ch8;
60with Sem_Ch13;  use Sem_Ch13;
61with Sem_Dim;   use Sem_Dim;
62with Sem_Disp;  use Sem_Disp;
63with Sem_Dist;  use Sem_Dist;
64with Sem_Elab;  use Sem_Elab;
65with Sem_Elim;  use Sem_Elim;
66with Sem_Eval;  use Sem_Eval;
67with Sem_Mech;  use Sem_Mech;
68with Sem_Res;   use Sem_Res;
69with Sem_Smem;  use Sem_Smem;
70with Sem_Type;  use Sem_Type;
71with Sem_Util;  use Sem_Util;
72with Sem_Warn;  use Sem_Warn;
73with Stand;     use Stand;
74with Sinfo;     use Sinfo;
75with Sinput;    use Sinput;
76with Snames;    use Snames;
77with Targparm;  use Targparm;
78with Tbuild;    use Tbuild;
79with Ttypes;    use Ttypes;
80with Uintp;     use Uintp;
81with Urealp;    use Urealp;
82
83package body Sem_Ch3 is
84
85   -----------------------
86   -- Local Subprograms --
87   -----------------------
88
89   procedure Add_Interface_Tag_Components (N : Node_Id; Typ : Entity_Id);
90   --  Ada 2005 (AI-251): Add the tag components corresponding to all the
91   --  abstract interface types implemented by a record type or a derived
92   --  record type.
93
94   procedure Build_Derived_Type
95     (N             : Node_Id;
96      Parent_Type   : Entity_Id;
97      Derived_Type  : Entity_Id;
98      Is_Completion : Boolean;
99      Derive_Subps  : Boolean := True);
100   --  Create and decorate a Derived_Type given the Parent_Type entity. N is
101   --  the N_Full_Type_Declaration node containing the derived type definition.
102   --  Parent_Type is the entity for the parent type in the derived type
103   --  definition and Derived_Type the actual derived type. Is_Completion must
104   --  be set to False if Derived_Type is the N_Defining_Identifier node in N
105   --  (i.e. Derived_Type = Defining_Identifier (N)). In this case N is not the
106   --  completion of a private type declaration. If Is_Completion is set to
107   --  True, N is the completion of a private type declaration and Derived_Type
108   --  is different from the defining identifier inside N (i.e. Derived_Type /=
109   --  Defining_Identifier (N)). Derive_Subps indicates whether the parent
110   --  subprograms should be derived. The only case where this parameter is
111   --  False is when Build_Derived_Type is recursively called to process an
112   --  implicit derived full type for a type derived from a private type (in
113   --  that case the subprograms must only be derived for the private view of
114   --  the type).
115   --
116   --  ??? These flags need a bit of re-examination and re-documentation:
117   --  ???  are they both necessary (both seem related to the recursion)?
118
119   procedure Build_Derived_Access_Type
120     (N            : Node_Id;
121      Parent_Type  : Entity_Id;
122      Derived_Type : Entity_Id);
123   --  Subsidiary procedure to Build_Derived_Type. For a derived access type,
124   --  create an implicit base if the parent type is constrained or if the
125   --  subtype indication has a constraint.
126
127   procedure Build_Derived_Array_Type
128     (N            : Node_Id;
129      Parent_Type  : Entity_Id;
130      Derived_Type : Entity_Id);
131   --  Subsidiary procedure to Build_Derived_Type. For a derived array type,
132   --  create an implicit base if the parent type is constrained or if the
133   --  subtype indication has a constraint.
134
135   procedure Build_Derived_Concurrent_Type
136     (N            : Node_Id;
137      Parent_Type  : Entity_Id;
138      Derived_Type : Entity_Id);
139   --  Subsidiary procedure to Build_Derived_Type. For a derived task or
140   --  protected type, inherit entries and protected subprograms, check
141   --  legality of discriminant constraints if any.
142
143   procedure Build_Derived_Enumeration_Type
144     (N            : Node_Id;
145      Parent_Type  : Entity_Id;
146      Derived_Type : Entity_Id);
147   --  Subsidiary procedure to Build_Derived_Type. For a derived enumeration
148   --  type, we must create a new list of literals. Types derived from
149   --  Character and [Wide_]Wide_Character are special-cased.
150
151   procedure Build_Derived_Numeric_Type
152     (N            : Node_Id;
153      Parent_Type  : Entity_Id;
154      Derived_Type : Entity_Id);
155   --  Subsidiary procedure to Build_Derived_Type. For numeric types, create
156   --  an anonymous base type, and propagate constraint to subtype if needed.
157
158   procedure Build_Derived_Private_Type
159     (N             : Node_Id;
160      Parent_Type   : Entity_Id;
161      Derived_Type  : Entity_Id;
162      Is_Completion : Boolean;
163      Derive_Subps  : Boolean := True);
164   --  Subsidiary procedure to Build_Derived_Type. This procedure is complex
165   --  because the parent may or may not have a completion, and the derivation
166   --  may itself be a completion.
167
168   procedure Build_Derived_Record_Type
169     (N            : Node_Id;
170      Parent_Type  : Entity_Id;
171      Derived_Type : Entity_Id;
172      Derive_Subps : Boolean := True);
173   --  Subsidiary procedure used for tagged and untagged record types
174   --  by Build_Derived_Type and Analyze_Private_Extension_Declaration.
175   --  All parameters are as in Build_Derived_Type except that N, in
176   --  addition to being an N_Full_Type_Declaration node, can also be an
177   --  N_Private_Extension_Declaration node. See the definition of this routine
178   --  for much more info. Derive_Subps indicates whether subprograms should be
179   --  derived from the parent type. The only case where Derive_Subps is False
180   --  is for an implicit derived full type for a type derived from a private
181   --  type (see Build_Derived_Type).
182
183   procedure Build_Discriminal (Discrim : Entity_Id);
184   --  Create the discriminal corresponding to discriminant Discrim, that is
185   --  the parameter corresponding to Discrim to be used in initialization
186   --  procedures for the type where Discrim is a discriminant. Discriminals
187   --  are not used during semantic analysis, and are not fully defined
188   --  entities until expansion. Thus they are not given a scope until
189   --  initialization procedures are built.
190
191   function Build_Discriminant_Constraints
192     (T           : Entity_Id;
193      Def         : Node_Id;
194      Derived_Def : Boolean := False) return Elist_Id;
195   --  Validate discriminant constraints and return the list of the constraints
196   --  in order of discriminant declarations, where T is the discriminated
197   --  unconstrained type. Def is the N_Subtype_Indication node where the
198   --  discriminants constraints for T are specified. Derived_Def is True
199   --  when building the discriminant constraints in a derived type definition
200   --  of the form "type D (...) is new T (xxx)". In this case T is the parent
201   --  type and Def is the constraint "(xxx)" on T and this routine sets the
202   --  Corresponding_Discriminant field of the discriminants in the derived
203   --  type D to point to the corresponding discriminants in the parent type T.
204
205   procedure Build_Discriminated_Subtype
206     (T           : Entity_Id;
207      Def_Id      : Entity_Id;
208      Elist       : Elist_Id;
209      Related_Nod : Node_Id;
210      For_Access  : Boolean := False);
211   --  Subsidiary procedure to Constrain_Discriminated_Type and to
212   --  Process_Incomplete_Dependents. Given
213   --
214   --     T (a possibly discriminated base type)
215   --     Def_Id (a very partially built subtype for T),
216   --
217   --  the call completes Def_Id to be the appropriate E_*_Subtype.
218   --
219   --  The Elist is the list of discriminant constraints if any (it is set
220   --  to No_Elist if T is not a discriminated type, and to an empty list if
221   --  T has discriminants but there are no discriminant constraints). The
222   --  Related_Nod is the same as Decl_Node in Create_Constrained_Components.
223   --  The For_Access says whether or not this subtype is really constraining
224   --  an access type. That is its sole purpose is the designated type of an
225   --  access type -- in which case a Private_Subtype Is_For_Access_Subtype
226   --  is built to avoid freezing T when the access subtype is frozen.
227
228   function Build_Scalar_Bound
229     (Bound : Node_Id;
230      Par_T : Entity_Id;
231      Der_T : Entity_Id) return Node_Id;
232   --  The bounds of a derived scalar type are conversions of the bounds of
233   --  the parent type. Optimize the representation if the bounds are literals.
234   --  Needs a more complete spec--what are the parameters exactly, and what
235   --  exactly is the returned value, and how is Bound affected???
236
237   procedure Build_Underlying_Full_View
238     (N   : Node_Id;
239      Typ : Entity_Id;
240      Par : Entity_Id);
241   --  If the completion of a private type is itself derived from a private
242   --  type, or if the full view of a private subtype is itself private, the
243   --  back-end has no way to compute the actual size of this type. We build
244   --  an internal subtype declaration of the proper parent type to convey
245   --  this information. This extra mechanism is needed because a full
246   --  view cannot itself have a full view (it would get clobbered during
247   --  view exchanges).
248
249   procedure Check_Access_Discriminant_Requires_Limited
250     (D   : Node_Id;
251      Loc : Node_Id);
252   --  Check the restriction that the type to which an access discriminant
253   --  belongs must be a concurrent type or a descendant of a type with
254   --  the reserved word 'limited' in its declaration.
255
256   procedure Check_Anonymous_Access_Components
257      (Typ_Decl  : Node_Id;
258       Typ       : Entity_Id;
259       Prev      : Entity_Id;
260       Comp_List : Node_Id);
261   --  Ada 2005 AI-382: an access component in a record definition can refer to
262   --  the enclosing record, in which case it denotes the type itself, and not
263   --  the current instance of the type. We create an anonymous access type for
264   --  the component, and flag it as an access to a component, so accessibility
265   --  checks are properly performed on it. The declaration of the access type
266   --  is placed ahead of that of the record to prevent order-of-elaboration
267   --  circularity issues in Gigi. We create an incomplete type for the record
268   --  declaration, which is the designated type of the anonymous access.
269
270   procedure Check_Delta_Expression (E : Node_Id);
271   --  Check that the expression represented by E is suitable for use as a
272   --  delta expression, i.e. it is of real type and is static.
273
274   procedure Check_Digits_Expression (E : Node_Id);
275   --  Check that the expression represented by E is suitable for use as a
276   --  digits expression, i.e. it is of integer type, positive and static.
277
278   procedure Check_Initialization (T : Entity_Id; Exp : Node_Id);
279   --  Validate the initialization of an object declaration. T is the required
280   --  type, and Exp is the initialization expression.
281
282   procedure Check_Interfaces (N : Node_Id; Def : Node_Id);
283   --  Check ARM rules 3.9.4 (15/2), 9.1 (9.d/2) and 9.4 (11.d/2)
284
285   procedure Check_Or_Process_Discriminants
286     (N    : Node_Id;
287      T    : Entity_Id;
288      Prev : Entity_Id := Empty);
289   --  If N is the full declaration of the completion T of an incomplete or
290   --  private type, check its discriminants (which are already known to be
291   --  conformant with those of the partial view, see Find_Type_Name),
292   --  otherwise process them. Prev is the entity of the partial declaration,
293   --  if any.
294
295   procedure Check_Real_Bound (Bound : Node_Id);
296   --  Check given bound for being of real type and static. If not, post an
297   --  appropriate message, and rewrite the bound with the real literal zero.
298
299   procedure Constant_Redeclaration
300     (Id : Entity_Id;
301      N  : Node_Id;
302      T  : out Entity_Id);
303   --  Various checks on legality of full declaration of deferred constant.
304   --  Id is the entity for the redeclaration, N is the N_Object_Declaration,
305   --  node. The caller has not yet set any attributes of this entity.
306
307   function Contain_Interface
308     (Iface  : Entity_Id;
309      Ifaces : Elist_Id) return Boolean;
310   --  Ada 2005: Determine whether Iface is present in the list Ifaces
311
312   procedure Convert_Scalar_Bounds
313     (N            : Node_Id;
314      Parent_Type  : Entity_Id;
315      Derived_Type : Entity_Id;
316      Loc          : Source_Ptr);
317   --  For derived scalar types, convert the bounds in the type definition to
318   --  the derived type, and complete their analysis. Given a constraint of the
319   --  form ".. new T range Lo .. Hi", Lo and Hi are analyzed and resolved with
320   --  T'Base, the parent_type. The bounds of the derived type (the anonymous
321   --  base) are copies of Lo and Hi. Finally, the bounds of the derived
322   --  subtype are conversions of those bounds to the derived_type, so that
323   --  their typing is consistent.
324
325   procedure Copy_Array_Base_Type_Attributes (T1, T2 : Entity_Id);
326   --  Copies attributes from array base type T2 to array base type T1. Copies
327   --  only attributes that apply to base types, but not subtypes.
328
329   procedure Copy_Array_Subtype_Attributes (T1, T2 : Entity_Id);
330   --  Copies attributes from array subtype T2 to array subtype T1. Copies
331   --  attributes that apply to both subtypes and base types.
332
333   procedure Create_Constrained_Components
334     (Subt        : Entity_Id;
335      Decl_Node   : Node_Id;
336      Typ         : Entity_Id;
337      Constraints : Elist_Id);
338   --  Build the list of entities for a constrained discriminated record
339   --  subtype. If a component depends on a discriminant, replace its subtype
340   --  using the discriminant values in the discriminant constraint. Subt
341   --  is the defining identifier for the subtype whose list of constrained
342   --  entities we will create. Decl_Node is the type declaration node where
343   --  we will attach all the itypes created. Typ is the base discriminated
344   --  type for the subtype Subt. Constraints is the list of discriminant
345   --  constraints for Typ.
346
347   function Constrain_Component_Type
348     (Comp            : Entity_Id;
349      Constrained_Typ : Entity_Id;
350      Related_Node    : Node_Id;
351      Typ             : Entity_Id;
352      Constraints     : Elist_Id) return Entity_Id;
353   --  Given a discriminated base type Typ, a list of discriminant constraints,
354   --  Constraints, for Typ and a component Comp of Typ, create and return the
355   --  type corresponding to Etype (Comp) where all discriminant references
356   --  are replaced with the corresponding constraint. If Etype (Comp) contains
357   --  no discriminant references then it is returned as-is. Constrained_Typ
358   --  is the final constrained subtype to which the constrained component
359   --  belongs. Related_Node is the node where we attach all created itypes.
360
361   procedure Constrain_Access
362     (Def_Id      : in out Entity_Id;
363      S           : Node_Id;
364      Related_Nod : Node_Id);
365   --  Apply a list of constraints to an access type. If Def_Id is empty, it is
366   --  an anonymous type created for a subtype indication. In that case it is
367   --  created in the procedure and attached to Related_Nod.
368
369   procedure Constrain_Array
370     (Def_Id      : in out Entity_Id;
371      SI          : Node_Id;
372      Related_Nod : Node_Id;
373      Related_Id  : Entity_Id;
374      Suffix      : Character);
375   --  Apply a list of index constraints to an unconstrained array type. The
376   --  first parameter is the entity for the resulting subtype. A value of
377   --  Empty for Def_Id indicates that an implicit type must be created, but
378   --  creation is delayed (and must be done by this procedure) because other
379   --  subsidiary implicit types must be created first (which is why Def_Id
380   --  is an in/out parameter). The second parameter is a subtype indication
381   --  node for the constrained array to be created (e.g. something of the
382   --  form string (1 .. 10)). Related_Nod gives the place where this type
383   --  has to be inserted in the tree. The Related_Id and Suffix parameters
384   --  are used to build the associated Implicit type name.
385
386   procedure Constrain_Concurrent
387     (Def_Id      : in out Entity_Id;
388      SI          : Node_Id;
389      Related_Nod : Node_Id;
390      Related_Id  : Entity_Id;
391      Suffix      : Character);
392   --  Apply list of discriminant constraints to an unconstrained concurrent
393   --  type.
394   --
395   --    SI is the N_Subtype_Indication node containing the constraint and
396   --    the unconstrained type to constrain.
397   --
398   --    Def_Id is the entity for the resulting constrained subtype. A value
399   --    of Empty for Def_Id indicates that an implicit type must be created,
400   --    but creation is delayed (and must be done by this procedure) because
401   --    other subsidiary implicit types must be created first (which is why
402   --    Def_Id is an in/out parameter).
403   --
404   --    Related_Nod gives the place where this type has to be inserted
405   --    in the tree.
406   --
407   --  The last two arguments are used to create its external name if needed.
408
409   function Constrain_Corresponding_Record
410     (Prot_Subt   : Entity_Id;
411      Corr_Rec    : Entity_Id;
412      Related_Nod : Node_Id) return Entity_Id;
413   --  When constraining a protected type or task type with discriminants,
414   --  constrain the corresponding record with the same discriminant values.
415
416   procedure Constrain_Decimal (Def_Id : Node_Id; S : Node_Id);
417   --  Constrain a decimal fixed point type with a digits constraint and/or a
418   --  range constraint, and build E_Decimal_Fixed_Point_Subtype entity.
419
420   procedure Constrain_Discriminated_Type
421     (Def_Id      : Entity_Id;
422      S           : Node_Id;
423      Related_Nod : Node_Id;
424      For_Access  : Boolean := False);
425   --  Process discriminant constraints of composite type. Verify that values
426   --  have been provided for all discriminants, that the original type is
427   --  unconstrained, and that the types of the supplied expressions match
428   --  the discriminant types. The first three parameters are like in routine
429   --  Constrain_Concurrent. See Build_Discriminated_Subtype for an explanation
430   --  of For_Access.
431
432   procedure Constrain_Enumeration (Def_Id : Node_Id; S : Node_Id);
433   --  Constrain an enumeration type with a range constraint. This is identical
434   --  to Constrain_Integer, but for the Ekind of the resulting subtype.
435
436   procedure Constrain_Float (Def_Id : Node_Id; S : Node_Id);
437   --  Constrain a floating point type with either a digits constraint
438   --  and/or a range constraint, building a E_Floating_Point_Subtype.
439
440   procedure Constrain_Index
441     (Index        : Node_Id;
442      S            : Node_Id;
443      Related_Nod  : Node_Id;
444      Related_Id   : Entity_Id;
445      Suffix       : Character;
446      Suffix_Index : Nat);
447   --  Process an index constraint S in a constrained array declaration. The
448   --  constraint can be a subtype name, or a range with or without an explicit
449   --  subtype mark. The index is the corresponding index of the unconstrained
450   --  array. The Related_Id and Suffix parameters are used to build the
451   --  associated Implicit type name.
452
453   procedure Constrain_Integer (Def_Id : Node_Id; S : Node_Id);
454   --  Build subtype of a signed or modular integer type
455
456   procedure Constrain_Ordinary_Fixed (Def_Id : Node_Id; S : Node_Id);
457   --  Constrain an ordinary fixed point type with a range constraint, and
458   --  build an E_Ordinary_Fixed_Point_Subtype entity.
459
460   procedure Copy_And_Swap (Priv, Full : Entity_Id);
461   --  Copy the Priv entity into the entity of its full declaration then swap
462   --  the two entities in such a manner that the former private type is now
463   --  seen as a full type.
464
465   procedure Decimal_Fixed_Point_Type_Declaration
466     (T   : Entity_Id;
467      Def : Node_Id);
468   --  Create a new decimal fixed point type, and apply the constraint to
469   --  obtain a subtype of this new type.
470
471   procedure Complete_Private_Subtype
472     (Priv        : Entity_Id;
473      Full        : Entity_Id;
474      Full_Base   : Entity_Id;
475      Related_Nod : Node_Id);
476   --  Complete the implicit full view of a private subtype by setting the
477   --  appropriate semantic fields. If the full view of the parent is a record
478   --  type, build constrained components of subtype.
479
480   procedure Derive_Progenitor_Subprograms
481     (Parent_Type : Entity_Id;
482      Tagged_Type : Entity_Id);
483   --  Ada 2005 (AI-251): To complete type derivation, collect the primitive
484   --  operations of progenitors of Tagged_Type, and replace the subsidiary
485   --  subtypes with Tagged_Type, to build the specs of the inherited interface
486   --  primitives. The derived primitives are aliased to those of the
487   --  interface. This routine takes care also of transferring to the full view
488   --  subprograms associated with the partial view of Tagged_Type that cover
489   --  interface primitives.
490
491   procedure Derived_Standard_Character
492     (N             : Node_Id;
493      Parent_Type   : Entity_Id;
494      Derived_Type  : Entity_Id);
495   --  Subsidiary procedure to Build_Derived_Enumeration_Type which handles
496   --  derivations from types Standard.Character and Standard.Wide_Character.
497
498   procedure Derived_Type_Declaration
499     (T             : Entity_Id;
500      N             : Node_Id;
501      Is_Completion : Boolean);
502   --  Process a derived type declaration. Build_Derived_Type is invoked
503   --  to process the actual derived type definition. Parameters N and
504   --  Is_Completion have the same meaning as in Build_Derived_Type.
505   --  T is the N_Defining_Identifier for the entity defined in the
506   --  N_Full_Type_Declaration node N, that is T is the derived type.
507
508   procedure Enumeration_Type_Declaration (T : Entity_Id; Def : Node_Id);
509   --  Insert each literal in symbol table, as an overloadable identifier. Each
510   --  enumeration type is mapped into a sequence of integers, and each literal
511   --  is defined as a constant with integer value. If any of the literals are
512   --  character literals, the type is a character type, which means that
513   --  strings are legal aggregates for arrays of components of the type.
514
515   function Expand_To_Stored_Constraint
516     (Typ        : Entity_Id;
517      Constraint : Elist_Id) return Elist_Id;
518   --  Given a constraint (i.e. a list of expressions) on the discriminants of
519   --  Typ, expand it into a constraint on the stored discriminants and return
520   --  the new list of expressions constraining the stored discriminants.
521
522   function Find_Type_Of_Object
523     (Obj_Def     : Node_Id;
524      Related_Nod : Node_Id) return Entity_Id;
525   --  Get type entity for object referenced by Obj_Def, attaching the implicit
526   --  types generated to Related_Nod.
527
528   procedure Floating_Point_Type_Declaration (T : Entity_Id; Def : Node_Id);
529   --  Create a new float and apply the constraint to obtain subtype of it
530
531   function Has_Range_Constraint (N : Node_Id) return Boolean;
532   --  Given an N_Subtype_Indication node N, return True if a range constraint
533   --  is present, either directly, or as part of a digits or delta constraint.
534   --  In addition, a digits constraint in the decimal case returns True, since
535   --  it establishes a default range if no explicit range is present.
536
537   function Inherit_Components
538     (N             : Node_Id;
539      Parent_Base   : Entity_Id;
540      Derived_Base  : Entity_Id;
541      Is_Tagged     : Boolean;
542      Inherit_Discr : Boolean;
543      Discs         : Elist_Id) return Elist_Id;
544   --  Called from Build_Derived_Record_Type to inherit the components of
545   --  Parent_Base (a base type) into the Derived_Base (the derived base type).
546   --  For more information on derived types and component inheritance please
547   --  consult the comment above the body of Build_Derived_Record_Type.
548   --
549   --    N is the original derived type declaration
550   --
551   --    Is_Tagged is set if we are dealing with tagged types
552   --
553   --    If Inherit_Discr is set, Derived_Base inherits its discriminants from
554   --    Parent_Base, otherwise no discriminants are inherited.
555   --
556   --    Discs gives the list of constraints that apply to Parent_Base in the
557   --    derived type declaration. If Discs is set to No_Elist, then we have
558   --    the following situation:
559   --
560   --      type Parent (D1..Dn : ..) is [tagged] record ...;
561   --      type Derived is new Parent [with ...];
562   --
563   --    which gets treated as
564   --
565   --      type Derived (D1..Dn : ..) is new Parent (D1,..,Dn) [with ...];
566   --
567   --  For untagged types the returned value is an association list. The list
568   --  starts from the association (Parent_Base => Derived_Base), and then it
569   --  contains a sequence of the associations of the form
570   --
571   --    (Old_Component => New_Component),
572   --
573   --  where Old_Component is the Entity_Id of a component in Parent_Base and
574   --  New_Component is the Entity_Id of the corresponding component in
575   --  Derived_Base. For untagged records, this association list is needed when
576   --  copying the record declaration for the derived base. In the tagged case
577   --  the value returned is irrelevant.
578
579   procedure Inherit_Predicate_Flags (Subt, Par : Entity_Id);
580   --  Propagate static and dynamic predicate flags from a parent to the
581   --  subtype in a subtype declaration with and without constraints.
582
583   function Is_EVF_Procedure (Subp : Entity_Id) return Boolean;
584   --  Subsidiary to Check_Abstract_Overriding and Derive_Subprogram.
585   --  Determine whether subprogram Subp is a procedure subject to pragma
586   --  Extensions_Visible with value False and has at least one controlling
587   --  parameter of mode OUT.
588
589   function Is_Valid_Constraint_Kind
590     (T_Kind          : Type_Kind;
591      Constraint_Kind : Node_Kind) return Boolean;
592   --  Returns True if it is legal to apply the given kind of constraint to the
593   --  given kind of type (index constraint to an array type, for example).
594
595   procedure Modular_Type_Declaration (T : Entity_Id; Def : Node_Id);
596   --  Create new modular type. Verify that modulus is in bounds
597
598   procedure New_Concatenation_Op (Typ : Entity_Id);
599   --  Create an abbreviated declaration for an operator in order to
600   --  materialize concatenation on array types.
601
602   procedure Ordinary_Fixed_Point_Type_Declaration
603     (T   : Entity_Id;
604      Def : Node_Id);
605   --  Create a new ordinary fixed point type, and apply the constraint to
606   --  obtain subtype of it.
607
608   procedure Preanalyze_Default_Expression (N : Node_Id; T : Entity_Id);
609   --  Wrapper on Preanalyze_Spec_Expression for default expressions, so that
610   --  In_Default_Expr can be properly adjusted.
611
612   procedure Prepare_Private_Subtype_Completion
613     (Id          : Entity_Id;
614      Related_Nod : Node_Id);
615   --  Id is a subtype of some private type. Creates the full declaration
616   --  associated with Id whenever possible, i.e. when the full declaration
617   --  of the base type is already known. Records each subtype into
618   --  Private_Dependents of the base type.
619
620   procedure Process_Incomplete_Dependents
621     (N      : Node_Id;
622      Full_T : Entity_Id;
623      Inc_T  : Entity_Id);
624   --  Process all entities that depend on an incomplete type. There include
625   --  subtypes, subprogram types that mention the incomplete type in their
626   --  profiles, and subprogram with access parameters that designate the
627   --  incomplete type.
628
629   --  Inc_T is the defining identifier of an incomplete type declaration, its
630   --  Ekind is E_Incomplete_Type.
631   --
632   --    N is the corresponding N_Full_Type_Declaration for Inc_T.
633   --
634   --    Full_T is N's defining identifier.
635   --
636   --  Subtypes of incomplete types with discriminants are completed when the
637   --  parent type is. This is simpler than private subtypes, because they can
638   --  only appear in the same scope, and there is no need to exchange views.
639   --  Similarly, access_to_subprogram types may have a parameter or a return
640   --  type that is an incomplete type, and that must be replaced with the
641   --  full type.
642   --
643   --  If the full type is tagged, subprogram with access parameters that
644   --  designated the incomplete may be primitive operations of the full type,
645   --  and have to be processed accordingly.
646
647   procedure Process_Real_Range_Specification (Def : Node_Id);
648   --  Given the type definition for a real type, this procedure processes and
649   --  checks the real range specification of this type definition if one is
650   --  present. If errors are found, error messages are posted, and the
651   --  Real_Range_Specification of Def is reset to Empty.
652
653   procedure Record_Type_Declaration
654     (T    : Entity_Id;
655      N    : Node_Id;
656      Prev : Entity_Id);
657   --  Process a record type declaration (for both untagged and tagged
658   --  records). Parameters T and N are exactly like in procedure
659   --  Derived_Type_Declaration, except that no flag Is_Completion is needed
660   --  for this routine. If this is the completion of an incomplete type
661   --  declaration, Prev is the entity of the incomplete declaration, used for
662   --  cross-referencing. Otherwise Prev = T.
663
664   procedure Record_Type_Definition (Def : Node_Id; Prev_T : Entity_Id);
665   --  This routine is used to process the actual record type definition (both
666   --  for untagged and tagged records). Def is a record type definition node.
667   --  This procedure analyzes the components in this record type definition.
668   --  Prev_T is the entity for the enclosing record type. It is provided so
669   --  that its Has_Task flag can be set if any of the component have Has_Task
670   --  set. If the declaration is the completion of an incomplete type
671   --  declaration, Prev_T is the original incomplete type, whose full view is
672   --  the record type.
673
674   procedure Replace_Components (Typ : Entity_Id; Decl : Node_Id);
675   --  Subsidiary to Build_Derived_Record_Type. For untagged records, we
676   --  build a copy of the declaration tree of the parent, and we create
677   --  independently the list of components for the derived type. Semantic
678   --  information uses the component entities, but record representation
679   --  clauses are validated on the declaration tree. This procedure replaces
680   --  discriminants and components in the declaration with those that have
681   --  been created by Inherit_Components.
682
683   procedure Set_Fixed_Range
684     (E   : Entity_Id;
685      Loc : Source_Ptr;
686      Lo  : Ureal;
687      Hi  : Ureal);
688   --  Build a range node with the given bounds and set it as the Scalar_Range
689   --  of the given fixed-point type entity. Loc is the source location used
690   --  for the constructed range. See body for further details.
691
692   procedure Set_Scalar_Range_For_Subtype
693     (Def_Id : Entity_Id;
694      R      : Node_Id;
695      Subt   : Entity_Id);
696   --  This routine is used to set the scalar range field for a subtype given
697   --  Def_Id, the entity for the subtype, and R, the range expression for the
698   --  scalar range. Subt provides the parent subtype to be used to analyze,
699   --  resolve, and check the given range.
700
701   procedure Set_Default_SSO (T : Entity_Id);
702   --  T is the entity for an array or record being declared. This procedure
703   --  sets the flags SSO_Set_Low_By_Default/SSO_Set_High_By_Default according
704   --  to the setting of Opt.Default_SSO.
705
706   procedure Signed_Integer_Type_Declaration (T : Entity_Id; Def : Node_Id);
707   --  Create a new signed integer entity, and apply the constraint to obtain
708   --  the required first named subtype of this type.
709
710   procedure Set_Stored_Constraint_From_Discriminant_Constraint
711     (E : Entity_Id);
712   --  E is some record type. This routine computes E's Stored_Constraint
713   --  from its Discriminant_Constraint.
714
715   procedure Diagnose_Interface (N : Node_Id;  E : Entity_Id);
716   --  Check that an entity in a list of progenitors is an interface,
717   --  emit error otherwise.
718
719   -----------------------
720   -- Access_Definition --
721   -----------------------
722
723   function Access_Definition
724     (Related_Nod : Node_Id;
725      N           : Node_Id) return Entity_Id
726   is
727      Anon_Type           : Entity_Id;
728      Anon_Scope          : Entity_Id;
729      Desig_Type          : Entity_Id;
730      Enclosing_Prot_Type : Entity_Id := Empty;
731
732   begin
733      Check_SPARK_05_Restriction ("access type is not allowed", N);
734
735      if Is_Entry (Current_Scope)
736        and then Is_Task_Type (Etype (Scope (Current_Scope)))
737      then
738         Error_Msg_N ("task entries cannot have access parameters", N);
739         return Empty;
740      end if;
741
742      --  Ada 2005: For an object declaration the corresponding anonymous
743      --  type is declared in the current scope.
744
745      --  If the access definition is the return type of another access to
746      --  function, scope is the current one, because it is the one of the
747      --  current type declaration, except for the pathological case below.
748
749      if Nkind_In (Related_Nod, N_Object_Declaration,
750                                N_Access_Function_Definition)
751      then
752         Anon_Scope := Current_Scope;
753
754         --  A pathological case: function returning access functions that
755         --  return access functions, etc. Each anonymous access type created
756         --  is in the enclosing scope of the outermost function.
757
758         declare
759            Par : Node_Id;
760
761         begin
762            Par := Related_Nod;
763            while Nkind_In (Par, N_Access_Function_Definition,
764                                 N_Access_Definition)
765            loop
766               Par := Parent (Par);
767            end loop;
768
769            if Nkind (Par) = N_Function_Specification then
770               Anon_Scope := Scope (Defining_Entity (Par));
771            end if;
772         end;
773
774      --  For the anonymous function result case, retrieve the scope of the
775      --  function specification's associated entity rather than using the
776      --  current scope. The current scope will be the function itself if the
777      --  formal part is currently being analyzed, but will be the parent scope
778      --  in the case of a parameterless function, and we always want to use
779      --  the function's parent scope. Finally, if the function is a child
780      --  unit, we must traverse the tree to retrieve the proper entity.
781
782      elsif Nkind (Related_Nod) = N_Function_Specification
783        and then Nkind (Parent (N)) /= N_Parameter_Specification
784      then
785         --  If the current scope is a protected type, the anonymous access
786         --  is associated with one of the protected operations, and must
787         --  be available in the scope that encloses the protected declaration.
788         --  Otherwise the type is in the scope enclosing the subprogram.
789
790         --  If the function has formals, The return type of a subprogram
791         --  declaration is analyzed in the scope of the subprogram (see
792         --  Process_Formals) and thus the protected type, if present, is
793         --  the scope of the current function scope.
794
795         if Ekind (Current_Scope) = E_Protected_Type then
796            Enclosing_Prot_Type := Current_Scope;
797
798         elsif Ekind (Current_Scope) = E_Function
799           and then Ekind (Scope (Current_Scope)) = E_Protected_Type
800         then
801            Enclosing_Prot_Type := Scope (Current_Scope);
802         end if;
803
804         if Present (Enclosing_Prot_Type) then
805            Anon_Scope := Scope (Enclosing_Prot_Type);
806
807         else
808            Anon_Scope := Scope (Defining_Entity (Related_Nod));
809         end if;
810
811      --  For an access type definition, if the current scope is a child
812      --  unit it is the scope of the type.
813
814      elsif Is_Compilation_Unit (Current_Scope) then
815         Anon_Scope := Current_Scope;
816
817      --  For access formals, access components, and access discriminants, the
818      --  scope is that of the enclosing declaration,
819
820      else
821         Anon_Scope := Scope (Current_Scope);
822      end if;
823
824      Anon_Type :=
825        Create_Itype
826          (E_Anonymous_Access_Type, Related_Nod, Scope_Id => Anon_Scope);
827
828      if All_Present (N)
829        and then Ada_Version >= Ada_2005
830      then
831         Error_Msg_N ("ALL is not permitted for anonymous access types", N);
832      end if;
833
834      --  Ada 2005 (AI-254): In case of anonymous access to subprograms call
835      --  the corresponding semantic routine
836
837      if Present (Access_To_Subprogram_Definition (N)) then
838
839         --  Compiler runtime units are compiled in Ada 2005 mode when building
840         --  the runtime library but must also be compilable in Ada 95 mode
841         --  (when bootstrapping the compiler).
842
843         Check_Compiler_Unit ("anonymous access to subprogram", N);
844
845         Access_Subprogram_Declaration
846           (T_Name => Anon_Type,
847            T_Def  => Access_To_Subprogram_Definition (N));
848
849         if Ekind (Anon_Type) = E_Access_Protected_Subprogram_Type then
850            Set_Ekind
851              (Anon_Type, E_Anonymous_Access_Protected_Subprogram_Type);
852         else
853            Set_Ekind (Anon_Type, E_Anonymous_Access_Subprogram_Type);
854         end if;
855
856         Set_Can_Use_Internal_Rep
857           (Anon_Type, not Always_Compatible_Rep_On_Target);
858
859         --  If the anonymous access is associated with a protected operation,
860         --  create a reference to it after the enclosing protected definition
861         --  because the itype will be used in the subsequent bodies.
862
863         --  If the anonymous access itself is protected, a full type
864         --  declaratiton will be created for it, so that the equivalent
865         --  record type can be constructed. For further details, see
866         --  Replace_Anonymous_Access_To_Protected-Subprogram.
867
868         if Ekind (Current_Scope) = E_Protected_Type
869           and then not Protected_Present (Access_To_Subprogram_Definition (N))
870         then
871            Build_Itype_Reference (Anon_Type, Parent (Current_Scope));
872         end if;
873
874         return Anon_Type;
875      end if;
876
877      Find_Type (Subtype_Mark (N));
878      Desig_Type := Entity (Subtype_Mark (N));
879
880      Set_Directly_Designated_Type (Anon_Type, Desig_Type);
881      Set_Etype (Anon_Type, Anon_Type);
882
883      --  Make sure the anonymous access type has size and alignment fields
884      --  set, as required by gigi. This is necessary in the case of the
885      --  Task_Body_Procedure.
886
887      if not Has_Private_Component (Desig_Type) then
888         Layout_Type (Anon_Type);
889      end if;
890
891      --  Ada 2005 (AI-231): Ada 2005 semantics for anonymous access differs
892      --  from Ada 95 semantics. In Ada 2005, anonymous access must specify if
893      --  the null value is allowed. In Ada 95 the null value is never allowed.
894
895      if Ada_Version >= Ada_2005 then
896         Set_Can_Never_Be_Null (Anon_Type, Null_Exclusion_Present (N));
897      else
898         Set_Can_Never_Be_Null (Anon_Type, True);
899      end if;
900
901      --  The anonymous access type is as public as the discriminated type or
902      --  subprogram that defines it. It is imported (for back-end purposes)
903      --  if the designated type is.
904
905      Set_Is_Public (Anon_Type, Is_Public (Scope (Anon_Type)));
906
907      --  Ada 2005 (AI-231): Propagate the access-constant attribute
908
909      Set_Is_Access_Constant (Anon_Type, Constant_Present (N));
910
911      --  The context is either a subprogram declaration, object declaration,
912      --  or an access discriminant, in a private or a full type declaration.
913      --  In the case of a subprogram, if the designated type is incomplete,
914      --  the operation will be a primitive operation of the full type, to be
915      --  updated subsequently. If the type is imported through a limited_with
916      --  clause, the subprogram is not a primitive operation of the type
917      --  (which is declared elsewhere in some other scope).
918
919      if Ekind (Desig_Type) = E_Incomplete_Type
920        and then not From_Limited_With (Desig_Type)
921        and then Is_Overloadable (Current_Scope)
922      then
923         Append_Elmt (Current_Scope, Private_Dependents (Desig_Type));
924         Set_Has_Delayed_Freeze (Current_Scope);
925      end if;
926
927      --  Ada 2005: If the designated type is an interface that may contain
928      --  tasks, create a Master entity for the declaration. This must be done
929      --  before expansion of the full declaration, because the declaration may
930      --  include an expression that is an allocator, whose expansion needs the
931      --  proper Master for the created tasks.
932
933      if Nkind (Related_Nod) = N_Object_Declaration and then Expander_Active
934      then
935         if Is_Interface (Desig_Type) and then Is_Limited_Record (Desig_Type)
936         then
937            Build_Class_Wide_Master (Anon_Type);
938
939         --  Similarly, if the type is an anonymous access that designates
940         --  tasks, create a master entity for it in the current context.
941
942         elsif Has_Task (Desig_Type) and then Comes_From_Source (Related_Nod)
943         then
944            Build_Master_Entity (Defining_Identifier (Related_Nod));
945            Build_Master_Renaming (Anon_Type);
946         end if;
947      end if;
948
949      --  For a private component of a protected type, it is imperative that
950      --  the back-end elaborate the type immediately after the protected
951      --  declaration, because this type will be used in the declarations
952      --  created for the component within each protected body, so we must
953      --  create an itype reference for it now.
954
955      if Nkind (Parent (Related_Nod)) = N_Protected_Definition then
956         Build_Itype_Reference (Anon_Type, Parent (Parent (Related_Nod)));
957
958      --  Similarly, if the access definition is the return result of a
959      --  function, create an itype reference for it because it will be used
960      --  within the function body. For a regular function that is not a
961      --  compilation unit, insert reference after the declaration. For a
962      --  protected operation, insert it after the enclosing protected type
963      --  declaration. In either case, do not create a reference for a type
964      --  obtained through a limited_with clause, because this would introduce
965      --  semantic dependencies.
966
967      --  Similarly, do not create a reference if the designated type is a
968      --  generic formal, because no use of it will reach the backend.
969
970      elsif Nkind (Related_Nod) = N_Function_Specification
971        and then not From_Limited_With (Desig_Type)
972        and then not Is_Generic_Type (Desig_Type)
973      then
974         if Present (Enclosing_Prot_Type) then
975            Build_Itype_Reference (Anon_Type, Parent (Enclosing_Prot_Type));
976
977         elsif Is_List_Member (Parent (Related_Nod))
978           and then Nkind (Parent (N)) /= N_Parameter_Specification
979         then
980            Build_Itype_Reference (Anon_Type, Parent (Related_Nod));
981         end if;
982
983      --  Finally, create an itype reference for an object declaration of an
984      --  anonymous access type. This is strictly necessary only for deferred
985      --  constants, but in any case will avoid out-of-scope problems in the
986      --  back-end.
987
988      elsif Nkind (Related_Nod) = N_Object_Declaration then
989         Build_Itype_Reference (Anon_Type, Related_Nod);
990      end if;
991
992      return Anon_Type;
993   end Access_Definition;
994
995   -----------------------------------
996   -- Access_Subprogram_Declaration --
997   -----------------------------------
998
999   procedure Access_Subprogram_Declaration
1000     (T_Name : Entity_Id;
1001      T_Def  : Node_Id)
1002   is
1003      procedure Check_For_Premature_Usage (Def : Node_Id);
1004      --  Check that type T_Name is not used, directly or recursively, as a
1005      --  parameter or a return type in Def. Def is either a subtype, an
1006      --  access_definition, or an access_to_subprogram_definition.
1007
1008      -------------------------------
1009      -- Check_For_Premature_Usage --
1010      -------------------------------
1011
1012      procedure Check_For_Premature_Usage (Def : Node_Id) is
1013         Param : Node_Id;
1014
1015      begin
1016         --  Check for a subtype mark
1017
1018         if Nkind (Def) in N_Has_Etype then
1019            if Etype (Def) = T_Name then
1020               Error_Msg_N
1021                 ("type& cannot be used before end of its declaration", Def);
1022            end if;
1023
1024         --  If this is not a subtype, then this is an access_definition
1025
1026         elsif Nkind (Def) = N_Access_Definition then
1027            if Present (Access_To_Subprogram_Definition (Def)) then
1028               Check_For_Premature_Usage
1029                 (Access_To_Subprogram_Definition (Def));
1030            else
1031               Check_For_Premature_Usage (Subtype_Mark (Def));
1032            end if;
1033
1034         --  The only cases left are N_Access_Function_Definition and
1035         --  N_Access_Procedure_Definition.
1036
1037         else
1038            if Present (Parameter_Specifications (Def)) then
1039               Param := First (Parameter_Specifications (Def));
1040               while Present (Param) loop
1041                  Check_For_Premature_Usage (Parameter_Type (Param));
1042                  Param := Next (Param);
1043               end loop;
1044            end if;
1045
1046            if Nkind (Def) = N_Access_Function_Definition then
1047               Check_For_Premature_Usage (Result_Definition (Def));
1048            end if;
1049         end if;
1050      end Check_For_Premature_Usage;
1051
1052      --  Local variables
1053
1054      Formals    : constant List_Id := Parameter_Specifications (T_Def);
1055      Formal     : Entity_Id;
1056      D_Ityp     : Node_Id;
1057      Desig_Type : constant Entity_Id :=
1058                     Create_Itype (E_Subprogram_Type, Parent (T_Def));
1059
1060   --  Start of processing for Access_Subprogram_Declaration
1061
1062   begin
1063      Check_SPARK_05_Restriction ("access type is not allowed", T_Def);
1064
1065      --  Associate the Itype node with the inner full-type declaration or
1066      --  subprogram spec or entry body. This is required to handle nested
1067      --  anonymous declarations. For example:
1068
1069      --      procedure P
1070      --       (X : access procedure
1071      --                     (Y : access procedure
1072      --                                   (Z : access T)))
1073
1074      D_Ityp := Associated_Node_For_Itype (Desig_Type);
1075      while not (Nkind_In (D_Ityp, N_Full_Type_Declaration,
1076                                   N_Private_Type_Declaration,
1077                                   N_Private_Extension_Declaration,
1078                                   N_Procedure_Specification,
1079                                   N_Function_Specification,
1080                                   N_Entry_Body)
1081
1082                   or else
1083                 Nkind_In (D_Ityp, N_Object_Declaration,
1084                                   N_Object_Renaming_Declaration,
1085                                   N_Formal_Object_Declaration,
1086                                   N_Formal_Type_Declaration,
1087                                   N_Task_Type_Declaration,
1088                                   N_Protected_Type_Declaration))
1089      loop
1090         D_Ityp := Parent (D_Ityp);
1091         pragma Assert (D_Ityp /= Empty);
1092      end loop;
1093
1094      Set_Associated_Node_For_Itype (Desig_Type, D_Ityp);
1095
1096      if Nkind_In (D_Ityp, N_Procedure_Specification,
1097                           N_Function_Specification)
1098      then
1099         Set_Scope (Desig_Type, Scope (Defining_Entity (D_Ityp)));
1100
1101      elsif Nkind_In (D_Ityp, N_Full_Type_Declaration,
1102                              N_Object_Declaration,
1103                              N_Object_Renaming_Declaration,
1104                              N_Formal_Type_Declaration)
1105      then
1106         Set_Scope (Desig_Type, Scope (Defining_Identifier (D_Ityp)));
1107      end if;
1108
1109      if Nkind (T_Def) = N_Access_Function_Definition then
1110         if Nkind (Result_Definition (T_Def)) = N_Access_Definition then
1111            declare
1112               Acc : constant Node_Id := Result_Definition (T_Def);
1113
1114            begin
1115               if Present (Access_To_Subprogram_Definition (Acc))
1116                 and then
1117                   Protected_Present (Access_To_Subprogram_Definition (Acc))
1118               then
1119                  Set_Etype
1120                    (Desig_Type,
1121                       Replace_Anonymous_Access_To_Protected_Subprogram
1122                         (T_Def));
1123
1124               else
1125                  Set_Etype
1126                    (Desig_Type,
1127                       Access_Definition (T_Def, Result_Definition (T_Def)));
1128               end if;
1129            end;
1130
1131         else
1132            Analyze (Result_Definition (T_Def));
1133
1134            declare
1135               Typ : constant Entity_Id := Entity (Result_Definition (T_Def));
1136
1137            begin
1138               --  If a null exclusion is imposed on the result type, then
1139               --  create a null-excluding itype (an access subtype) and use
1140               --  it as the function's Etype.
1141
1142               if Is_Access_Type (Typ)
1143                 and then Null_Exclusion_In_Return_Present (T_Def)
1144               then
1145                  Set_Etype (Desig_Type,
1146                    Create_Null_Excluding_Itype
1147                      (T           => Typ,
1148                       Related_Nod => T_Def,
1149                       Scope_Id    => Current_Scope));
1150
1151               else
1152                  if From_Limited_With (Typ) then
1153
1154                     --  AI05-151: Incomplete types are allowed in all basic
1155                     --  declarations, including access to subprograms.
1156
1157                     if Ada_Version >= Ada_2012 then
1158                        null;
1159
1160                     else
1161                        Error_Msg_NE
1162                         ("illegal use of incomplete type&",
1163                          Result_Definition (T_Def), Typ);
1164                     end if;
1165
1166                  elsif Ekind (Current_Scope) = E_Package
1167                    and then In_Private_Part (Current_Scope)
1168                  then
1169                     if Ekind (Typ) = E_Incomplete_Type then
1170                        Append_Elmt (Desig_Type, Private_Dependents (Typ));
1171
1172                     elsif Is_Class_Wide_Type (Typ)
1173                       and then Ekind (Etype (Typ)) = E_Incomplete_Type
1174                     then
1175                        Append_Elmt
1176                          (Desig_Type, Private_Dependents (Etype (Typ)));
1177                     end if;
1178                  end if;
1179
1180                  Set_Etype (Desig_Type, Typ);
1181               end if;
1182            end;
1183         end if;
1184
1185         if not (Is_Type (Etype (Desig_Type))) then
1186            Error_Msg_N
1187              ("expect type in function specification",
1188               Result_Definition (T_Def));
1189         end if;
1190
1191      else
1192         Set_Etype (Desig_Type, Standard_Void_Type);
1193      end if;
1194
1195      if Present (Formals) then
1196         Push_Scope (Desig_Type);
1197
1198         --  Some special tests here. These special tests can be removed
1199         --  if and when Itypes always have proper parent pointers to their
1200         --  declarations???
1201
1202         --  Special test 1) Link defining_identifier of formals. Required by
1203         --  First_Formal to provide its functionality.
1204
1205         declare
1206            F : Node_Id;
1207
1208         begin
1209            F := First (Formals);
1210
1211            --  In ASIS mode, the access_to_subprogram may be analyzed twice,
1212            --  when it is part of an unconstrained type and subtype expansion
1213            --  is disabled. To avoid back-end problems with shared profiles,
1214            --  use previous subprogram type as the designated type, and then
1215            --  remove scope added above.
1216
1217            if ASIS_Mode and then Present (Scope (Defining_Identifier (F)))
1218            then
1219               Set_Etype                    (T_Name, T_Name);
1220               Init_Size_Align              (T_Name);
1221               Set_Directly_Designated_Type (T_Name,
1222                 Scope (Defining_Identifier (F)));
1223               End_Scope;
1224               return;
1225            end if;
1226
1227            while Present (F) loop
1228               if No (Parent (Defining_Identifier (F))) then
1229                  Set_Parent (Defining_Identifier (F), F);
1230               end if;
1231
1232               Next (F);
1233            end loop;
1234         end;
1235
1236         Process_Formals (Formals, Parent (T_Def));
1237
1238         --  Special test 2) End_Scope requires that the parent pointer be set
1239         --  to something reasonable, but Itypes don't have parent pointers. So
1240         --  we set it and then unset it ???
1241
1242         Set_Parent (Desig_Type, T_Name);
1243         End_Scope;
1244         Set_Parent (Desig_Type, Empty);
1245      end if;
1246
1247      --  Check for premature usage of the type being defined
1248
1249      Check_For_Premature_Usage (T_Def);
1250
1251      --  The return type and/or any parameter type may be incomplete. Mark the
1252      --  subprogram_type as depending on the incomplete type, so that it can
1253      --  be updated when the full type declaration is seen. This only applies
1254      --  to incomplete types declared in some enclosing scope, not to limited
1255      --  views from other packages.
1256
1257      --  Prior to Ada 2012, access to functions can only have in_parameters.
1258
1259      if Present (Formals) then
1260         Formal := First_Formal (Desig_Type);
1261         while Present (Formal) loop
1262            if Ekind (Formal) /= E_In_Parameter
1263              and then Nkind (T_Def) = N_Access_Function_Definition
1264              and then Ada_Version < Ada_2012
1265            then
1266               Error_Msg_N ("functions can only have IN parameters", Formal);
1267            end if;
1268
1269            if Ekind (Etype (Formal)) = E_Incomplete_Type
1270              and then In_Open_Scopes (Scope (Etype (Formal)))
1271            then
1272               Append_Elmt (Desig_Type, Private_Dependents (Etype (Formal)));
1273               Set_Has_Delayed_Freeze (Desig_Type);
1274            end if;
1275
1276            Next_Formal (Formal);
1277         end loop;
1278      end if;
1279
1280      --  Check whether an indirect call without actuals may be possible. This
1281      --  is used when resolving calls whose result is then indexed.
1282
1283      May_Need_Actuals (Desig_Type);
1284
1285      --  If the return type is incomplete, this is legal as long as the type
1286      --  is declared in the current scope and will be completed in it (rather
1287      --  than being part of limited view).
1288
1289      if Ekind (Etype (Desig_Type)) = E_Incomplete_Type
1290        and then not Has_Delayed_Freeze (Desig_Type)
1291        and then In_Open_Scopes (Scope (Etype (Desig_Type)))
1292      then
1293         Append_Elmt (Desig_Type, Private_Dependents (Etype (Desig_Type)));
1294         Set_Has_Delayed_Freeze (Desig_Type);
1295      end if;
1296
1297      Check_Delayed_Subprogram (Desig_Type);
1298
1299      if Protected_Present (T_Def) then
1300         Set_Ekind (T_Name, E_Access_Protected_Subprogram_Type);
1301         Set_Convention (Desig_Type, Convention_Protected);
1302      else
1303         Set_Ekind (T_Name, E_Access_Subprogram_Type);
1304      end if;
1305
1306      Set_Can_Use_Internal_Rep     (T_Name,
1307                                      not Always_Compatible_Rep_On_Target);
1308      Set_Etype                    (T_Name, T_Name);
1309      Init_Size_Align              (T_Name);
1310      Set_Directly_Designated_Type (T_Name, Desig_Type);
1311
1312      --  If the access_to_subprogram is not declared at the library level,
1313      --  it can only point to subprograms that are at the same or deeper
1314      --  accessibility level. The corresponding subprogram type might
1315      --  require an activation record when compiling for C.
1316
1317      Set_Needs_Activation_Record  (Desig_Type,
1318                                      not Is_Library_Level_Entity (T_Name));
1319
1320      Generate_Reference_To_Formals (T_Name);
1321
1322      --  Ada 2005 (AI-231): Propagate the null-excluding attribute
1323
1324      Set_Can_Never_Be_Null (T_Name, Null_Exclusion_Present (T_Def));
1325
1326      Check_Restriction (No_Access_Subprograms, T_Def);
1327   end Access_Subprogram_Declaration;
1328
1329   ----------------------------
1330   -- Access_Type_Declaration --
1331   ----------------------------
1332
1333   procedure Access_Type_Declaration (T : Entity_Id; Def : Node_Id) is
1334      P : constant Node_Id := Parent (Def);
1335      S : constant Node_Id := Subtype_Indication (Def);
1336
1337      Full_Desig : Entity_Id;
1338
1339   begin
1340      Check_SPARK_05_Restriction ("access type is not allowed", Def);
1341
1342      --  Check for permissible use of incomplete type
1343
1344      if Nkind (S) /= N_Subtype_Indication then
1345         Analyze (S);
1346
1347         if Present (Entity (S))
1348           and then Ekind (Root_Type (Entity (S))) = E_Incomplete_Type
1349         then
1350            Set_Directly_Designated_Type (T, Entity (S));
1351
1352            --  If the designated type is a limited view, we cannot tell if
1353            --  the full view contains tasks, and there is no way to handle
1354            --  that full view in a client. We create a master entity for the
1355            --  scope, which will be used when a client determines that one
1356            --  is needed.
1357
1358            if From_Limited_With (Entity (S))
1359              and then not Is_Class_Wide_Type (Entity (S))
1360            then
1361               Set_Ekind (T, E_Access_Type);
1362               Build_Master_Entity (T);
1363               Build_Master_Renaming (T);
1364            end if;
1365
1366         else
1367            Set_Directly_Designated_Type (T, Process_Subtype (S, P, T, 'P'));
1368         end if;
1369
1370         --  If the access definition is of the form: ACCESS NOT NULL ..
1371         --  the subtype indication must be of an access type. Create
1372         --  a null-excluding subtype of it.
1373
1374         if Null_Excluding_Subtype (Def) then
1375            if not Is_Access_Type (Entity (S)) then
1376               Error_Msg_N ("null exclusion must apply to access type", Def);
1377
1378            else
1379               declare
1380                  Loc  : constant Source_Ptr := Sloc (S);
1381                  Decl : Node_Id;
1382                  Nam  : constant Entity_Id := Make_Temporary (Loc, 'S');
1383
1384               begin
1385                  Decl :=
1386                    Make_Subtype_Declaration (Loc,
1387                      Defining_Identifier => Nam,
1388                      Subtype_Indication  =>
1389                        New_Occurrence_Of (Entity (S), Loc));
1390                  Set_Null_Exclusion_Present (Decl);
1391                  Insert_Before (Parent (Def), Decl);
1392                  Analyze (Decl);
1393                  Set_Entity (S, Nam);
1394               end;
1395            end if;
1396         end if;
1397
1398      else
1399         Set_Directly_Designated_Type (T,
1400           Process_Subtype (S, P, T, 'P'));
1401      end if;
1402
1403      if All_Present (Def) or Constant_Present (Def) then
1404         Set_Ekind (T, E_General_Access_Type);
1405      else
1406         Set_Ekind (T, E_Access_Type);
1407      end if;
1408
1409      Full_Desig := Designated_Type (T);
1410
1411      if Base_Type (Full_Desig) = T then
1412         Error_Msg_N ("access type cannot designate itself", S);
1413
1414      --  In Ada 2005, the type may have a limited view through some unit in
1415      --  its own context, allowing the following circularity that cannot be
1416      --  detected earlier.
1417
1418      elsif Is_Class_Wide_Type (Full_Desig) and then Etype (Full_Desig) = T
1419      then
1420         Error_Msg_N
1421           ("access type cannot designate its own class-wide type", S);
1422
1423         --  Clean up indication of tagged status to prevent cascaded errors
1424
1425         Set_Is_Tagged_Type (T, False);
1426      end if;
1427
1428      Set_Etype (T, T);
1429
1430      --  If the type has appeared already in a with_type clause, it is frozen
1431      --  and the pointer size is already set. Else, initialize.
1432
1433      if not From_Limited_With (T) then
1434         Init_Size_Align (T);
1435      end if;
1436
1437      --  Note that Has_Task is always false, since the access type itself
1438      --  is not a task type. See Einfo for more description on this point.
1439      --  Exactly the same consideration applies to Has_Controlled_Component
1440      --  and to Has_Protected.
1441
1442      Set_Has_Task                 (T, False);
1443      Set_Has_Protected            (T, False);
1444      Set_Has_Timing_Event         (T, False);
1445      Set_Has_Controlled_Component (T, False);
1446
1447      --  Initialize field Finalization_Master explicitly to Empty, to avoid
1448      --  problems where an incomplete view of this entity has been previously
1449      --  established by a limited with and an overlaid version of this field
1450      --  (Stored_Constraint) was initialized for the incomplete view.
1451
1452      --  This reset is performed in most cases except where the access type
1453      --  has been created for the purposes of allocating or deallocating a
1454      --  build-in-place object. Such access types have explicitly set pools
1455      --  and finalization masters.
1456
1457      if No (Associated_Storage_Pool (T)) then
1458         Set_Finalization_Master (T, Empty);
1459      end if;
1460
1461      --  Ada 2005 (AI-231): Propagate the null-excluding and access-constant
1462      --  attributes
1463
1464      Set_Can_Never_Be_Null  (T, Null_Exclusion_Present (Def));
1465      Set_Is_Access_Constant (T, Constant_Present (Def));
1466   end Access_Type_Declaration;
1467
1468   ----------------------------------
1469   -- Add_Interface_Tag_Components --
1470   ----------------------------------
1471
1472   procedure Add_Interface_Tag_Components (N : Node_Id; Typ : Entity_Id) is
1473      Loc      : constant Source_Ptr := Sloc (N);
1474      L        : List_Id;
1475      Last_Tag : Node_Id;
1476
1477      procedure Add_Tag (Iface : Entity_Id);
1478      --  Add tag for one of the progenitor interfaces
1479
1480      -------------
1481      -- Add_Tag --
1482      -------------
1483
1484      procedure Add_Tag (Iface : Entity_Id) is
1485         Decl   : Node_Id;
1486         Def    : Node_Id;
1487         Tag    : Entity_Id;
1488         Offset : Entity_Id;
1489
1490      begin
1491         pragma Assert (Is_Tagged_Type (Iface) and then Is_Interface (Iface));
1492
1493         --  This is a reasonable place to propagate predicates
1494
1495         if Has_Predicates (Iface) then
1496            Set_Has_Predicates (Typ);
1497         end if;
1498
1499         Def :=
1500           Make_Component_Definition (Loc,
1501             Aliased_Present    => True,
1502             Subtype_Indication =>
1503               New_Occurrence_Of (RTE (RE_Interface_Tag), Loc));
1504
1505         Tag := Make_Temporary (Loc, 'V');
1506
1507         Decl :=
1508           Make_Component_Declaration (Loc,
1509             Defining_Identifier  => Tag,
1510             Component_Definition => Def);
1511
1512         Analyze_Component_Declaration (Decl);
1513
1514         Set_Analyzed (Decl);
1515         Set_Ekind               (Tag, E_Component);
1516         Set_Is_Tag              (Tag);
1517         Set_Is_Aliased          (Tag);
1518         Set_Related_Type        (Tag, Iface);
1519         Init_Component_Location (Tag);
1520
1521         pragma Assert (Is_Frozen (Iface));
1522
1523         Set_DT_Entry_Count    (Tag,
1524           DT_Entry_Count (First_Entity (Iface)));
1525
1526         if No (Last_Tag) then
1527            Prepend (Decl, L);
1528         else
1529            Insert_After (Last_Tag, Decl);
1530         end if;
1531
1532         Last_Tag := Decl;
1533
1534         --  If the ancestor has discriminants we need to give special support
1535         --  to store the offset_to_top value of the secondary dispatch tables.
1536         --  For this purpose we add a supplementary component just after the
1537         --  field that contains the tag associated with each secondary DT.
1538
1539         if Typ /= Etype (Typ) and then Has_Discriminants (Etype (Typ)) then
1540            Def :=
1541              Make_Component_Definition (Loc,
1542                Subtype_Indication =>
1543                  New_Occurrence_Of (RTE (RE_Storage_Offset), Loc));
1544
1545            Offset := Make_Temporary (Loc, 'V');
1546
1547            Decl :=
1548              Make_Component_Declaration (Loc,
1549                Defining_Identifier  => Offset,
1550                Component_Definition => Def);
1551
1552            Analyze_Component_Declaration (Decl);
1553
1554            Set_Analyzed (Decl);
1555            Set_Ekind               (Offset, E_Component);
1556            Set_Is_Aliased          (Offset);
1557            Set_Related_Type        (Offset, Iface);
1558            Init_Component_Location (Offset);
1559            Insert_After (Last_Tag, Decl);
1560            Last_Tag := Decl;
1561         end if;
1562      end Add_Tag;
1563
1564      --  Local variables
1565
1566      Elmt : Elmt_Id;
1567      Ext  : Node_Id;
1568      Comp : Node_Id;
1569
1570   --  Start of processing for Add_Interface_Tag_Components
1571
1572   begin
1573      if not RTE_Available (RE_Interface_Tag) then
1574         Error_Msg
1575           ("(Ada 2005) interface types not supported by this run-time!",
1576            Sloc (N));
1577         return;
1578      end if;
1579
1580      if Ekind (Typ) /= E_Record_Type
1581        or else (Is_Concurrent_Record_Type (Typ)
1582                  and then Is_Empty_List (Abstract_Interface_List (Typ)))
1583        or else (not Is_Concurrent_Record_Type (Typ)
1584                  and then No (Interfaces (Typ))
1585                  and then Is_Empty_Elmt_List (Interfaces (Typ)))
1586      then
1587         return;
1588      end if;
1589
1590      --  Find the current last tag
1591
1592      if Nkind (Type_Definition (N)) = N_Derived_Type_Definition then
1593         Ext := Record_Extension_Part (Type_Definition (N));
1594      else
1595         pragma Assert (Nkind (Type_Definition (N)) = N_Record_Definition);
1596         Ext := Type_Definition (N);
1597      end if;
1598
1599      Last_Tag := Empty;
1600
1601      if not (Present (Component_List (Ext))) then
1602         Set_Null_Present (Ext, False);
1603         L := New_List;
1604         Set_Component_List (Ext,
1605           Make_Component_List (Loc,
1606             Component_Items => L,
1607             Null_Present => False));
1608      else
1609         if Nkind (Type_Definition (N)) = N_Derived_Type_Definition then
1610            L := Component_Items
1611                   (Component_List
1612                     (Record_Extension_Part
1613                       (Type_Definition (N))));
1614         else
1615            L := Component_Items
1616                   (Component_List
1617                     (Type_Definition (N)));
1618         end if;
1619
1620         --  Find the last tag component
1621
1622         Comp := First (L);
1623         while Present (Comp) loop
1624            if Nkind (Comp) = N_Component_Declaration
1625              and then Is_Tag (Defining_Identifier (Comp))
1626            then
1627               Last_Tag := Comp;
1628            end if;
1629
1630            Next (Comp);
1631         end loop;
1632      end if;
1633
1634      --  At this point L references the list of components and Last_Tag
1635      --  references the current last tag (if any). Now we add the tag
1636      --  corresponding with all the interfaces that are not implemented
1637      --  by the parent.
1638
1639      if Present (Interfaces (Typ)) then
1640         Elmt := First_Elmt (Interfaces (Typ));
1641         while Present (Elmt) loop
1642            Add_Tag (Node (Elmt));
1643            Next_Elmt (Elmt);
1644         end loop;
1645      end if;
1646   end Add_Interface_Tag_Components;
1647
1648   -------------------------------------
1649   -- Add_Internal_Interface_Entities --
1650   -------------------------------------
1651
1652   procedure Add_Internal_Interface_Entities (Tagged_Type : Entity_Id) is
1653      Elmt          : Elmt_Id;
1654      Iface         : Entity_Id;
1655      Iface_Elmt    : Elmt_Id;
1656      Iface_Prim    : Entity_Id;
1657      Ifaces_List   : Elist_Id;
1658      New_Subp      : Entity_Id := Empty;
1659      Prim          : Entity_Id;
1660      Restore_Scope : Boolean := False;
1661
1662   begin
1663      pragma Assert (Ada_Version >= Ada_2005
1664        and then Is_Record_Type (Tagged_Type)
1665        and then Is_Tagged_Type (Tagged_Type)
1666        and then Has_Interfaces (Tagged_Type)
1667        and then not Is_Interface (Tagged_Type));
1668
1669      --  Ensure that the internal entities are added to the scope of the type
1670
1671      if Scope (Tagged_Type) /= Current_Scope then
1672         Push_Scope (Scope (Tagged_Type));
1673         Restore_Scope := True;
1674      end if;
1675
1676      Collect_Interfaces (Tagged_Type, Ifaces_List);
1677
1678      Iface_Elmt := First_Elmt (Ifaces_List);
1679      while Present (Iface_Elmt) loop
1680         Iface := Node (Iface_Elmt);
1681
1682         --  Originally we excluded here from this processing interfaces that
1683         --  are parents of Tagged_Type because their primitives are located
1684         --  in the primary dispatch table (and hence no auxiliary internal
1685         --  entities are required to handle secondary dispatch tables in such
1686         --  case). However, these auxiliary entities are also required to
1687         --  handle derivations of interfaces in formals of generics (see
1688         --  Derive_Subprograms).
1689
1690         Elmt := First_Elmt (Primitive_Operations (Iface));
1691         while Present (Elmt) loop
1692            Iface_Prim := Node (Elmt);
1693
1694            if not Is_Predefined_Dispatching_Operation (Iface_Prim) then
1695               Prim :=
1696                 Find_Primitive_Covering_Interface
1697                   (Tagged_Type => Tagged_Type,
1698                    Iface_Prim  => Iface_Prim);
1699
1700               if No (Prim) and then Serious_Errors_Detected > 0 then
1701                  goto Continue;
1702               end if;
1703
1704               pragma Assert (Present (Prim));
1705
1706               --  Ada 2012 (AI05-0197): If the name of the covering primitive
1707               --  differs from the name of the interface primitive then it is
1708               --  a private primitive inherited from a parent type. In such
1709               --  case, given that Tagged_Type covers the interface, the
1710               --  inherited private primitive becomes visible. For such
1711               --  purpose we add a new entity that renames the inherited
1712               --  private primitive.
1713
1714               if Chars (Prim) /= Chars (Iface_Prim) then
1715                  pragma Assert (Has_Suffix (Prim, 'P'));
1716                  Derive_Subprogram
1717                    (New_Subp     => New_Subp,
1718                     Parent_Subp  => Iface_Prim,
1719                     Derived_Type => Tagged_Type,
1720                     Parent_Type  => Iface);
1721                  Set_Alias (New_Subp, Prim);
1722                  Set_Is_Abstract_Subprogram
1723                    (New_Subp, Is_Abstract_Subprogram (Prim));
1724               end if;
1725
1726               Derive_Subprogram
1727                 (New_Subp     => New_Subp,
1728                  Parent_Subp  => Iface_Prim,
1729                  Derived_Type => Tagged_Type,
1730                  Parent_Type  => Iface);
1731
1732               declare
1733                  Anc : Entity_Id;
1734               begin
1735                  if Is_Inherited_Operation (Prim)
1736                    and then Present (Alias (Prim))
1737                  then
1738                     Anc := Alias (Prim);
1739                  else
1740                     Anc := Overridden_Operation (Prim);
1741                  end if;
1742
1743                  --  Apply legality checks in RM 6.1.1 (10-13) concerning
1744                  --  nonconforming preconditions in both an ancestor and
1745                  --  a progenitor operation.
1746
1747                  --  If the operation is a primitive wrapper it is an explicit
1748                  --  (overriding) operqtion and all is fine.
1749
1750                  if Present (Anc)
1751                    and then Has_Non_Trivial_Precondition (Anc)
1752                    and then Has_Non_Trivial_Precondition (Iface_Prim)
1753                  then
1754                     if Is_Abstract_Subprogram (Prim)
1755                       or else
1756                         (Ekind (Prim) = E_Procedure
1757                           and then Nkind (Parent (Prim)) =
1758                                      N_Procedure_Specification
1759                           and then Null_Present (Parent (Prim)))
1760                       or else Is_Primitive_Wrapper (Prim)
1761                     then
1762                        null;
1763
1764                     --  The operation is inherited and must be overridden
1765
1766                     elsif not Comes_From_Source (Prim) then
1767                        Error_Msg_NE
1768                          ("&inherits non-conforming preconditions and must "
1769                           & "be overridden (RM 6.1.1 (10-16)",
1770                           Parent (Tagged_Type), Prim);
1771                     end if;
1772                  end if;
1773               end;
1774
1775               --  Ada 2005 (AI-251): Decorate internal entity Iface_Subp
1776               --  associated with interface types. These entities are
1777               --  only registered in the list of primitives of its
1778               --  corresponding tagged type because they are only used
1779               --  to fill the contents of the secondary dispatch tables.
1780               --  Therefore they are removed from the homonym chains.
1781
1782               Set_Is_Hidden (New_Subp);
1783               Set_Is_Internal (New_Subp);
1784               Set_Alias (New_Subp, Prim);
1785               Set_Is_Abstract_Subprogram
1786                 (New_Subp, Is_Abstract_Subprogram (Prim));
1787               Set_Interface_Alias (New_Subp, Iface_Prim);
1788
1789               --  If the returned type is an interface then propagate it to
1790               --  the returned type. Needed by the thunk to generate the code
1791               --  which displaces "this" to reference the corresponding
1792               --  secondary dispatch table in the returned object.
1793
1794               if Is_Interface (Etype (Iface_Prim)) then
1795                  Set_Etype (New_Subp, Etype (Iface_Prim));
1796               end if;
1797
1798               --  Internal entities associated with interface types are only
1799               --  registered in the list of primitives of the tagged type.
1800               --  They are only used to fill the contents of the secondary
1801               --  dispatch tables. Therefore they are not needed in the
1802               --  homonym chains.
1803
1804               Remove_Homonym (New_Subp);
1805
1806               --  Hidden entities associated with interfaces must have set
1807               --  the Has_Delay_Freeze attribute to ensure that, in case
1808               --  of locally defined tagged types (or compiling with static
1809               --  dispatch tables generation disabled) the corresponding
1810               --  entry of the secondary dispatch table is filled when such
1811               --  an entity is frozen. This is an expansion activity that must
1812               --  be suppressed for ASIS because it leads to gigi elaboration
1813               --  issues in annotate mode.
1814
1815               if not ASIS_Mode then
1816                  Set_Has_Delayed_Freeze (New_Subp);
1817               end if;
1818            end if;
1819
1820            <<Continue>>
1821            Next_Elmt (Elmt);
1822         end loop;
1823
1824         Next_Elmt (Iface_Elmt);
1825      end loop;
1826
1827      if Restore_Scope then
1828         Pop_Scope;
1829      end if;
1830   end Add_Internal_Interface_Entities;
1831
1832   -----------------------------------
1833   -- Analyze_Component_Declaration --
1834   -----------------------------------
1835
1836   procedure Analyze_Component_Declaration (N : Node_Id) is
1837      Loc : constant Source_Ptr := Sloc (Component_Definition (N));
1838      Id  : constant Entity_Id  := Defining_Identifier (N);
1839      E   : constant Node_Id    := Expression (N);
1840      Typ : constant Node_Id    :=
1841              Subtype_Indication (Component_Definition (N));
1842      T   : Entity_Id;
1843      P   : Entity_Id;
1844
1845      function Contains_POC (Constr : Node_Id) return Boolean;
1846      --  Determines whether a constraint uses the discriminant of a record
1847      --  type thus becoming a per-object constraint (POC).
1848
1849      function Is_Known_Limited (Typ : Entity_Id) return Boolean;
1850      --  Typ is the type of the current component, check whether this type is
1851      --  a limited type. Used to validate declaration against that of
1852      --  enclosing record.
1853
1854      ------------------
1855      -- Contains_POC --
1856      ------------------
1857
1858      function Contains_POC (Constr : Node_Id) return Boolean is
1859      begin
1860         --  Prevent cascaded errors
1861
1862         if Error_Posted (Constr) then
1863            return False;
1864         end if;
1865
1866         case Nkind (Constr) is
1867            when N_Attribute_Reference =>
1868               return Attribute_Name (Constr) = Name_Access
1869                 and then Prefix (Constr) = Scope (Entity (Prefix (Constr)));
1870
1871            when N_Discriminant_Association =>
1872               return Denotes_Discriminant (Expression (Constr));
1873
1874            when N_Identifier =>
1875               return Denotes_Discriminant (Constr);
1876
1877            when N_Index_Or_Discriminant_Constraint =>
1878               declare
1879                  IDC : Node_Id;
1880
1881               begin
1882                  IDC := First (Constraints (Constr));
1883                  while Present (IDC) loop
1884
1885                     --  One per-object constraint is sufficient
1886
1887                     if Contains_POC (IDC) then
1888                        return True;
1889                     end if;
1890
1891                     Next (IDC);
1892                  end loop;
1893
1894                  return False;
1895               end;
1896
1897            when N_Range =>
1898               return Denotes_Discriminant (Low_Bound (Constr))
1899                        or else
1900                      Denotes_Discriminant (High_Bound (Constr));
1901
1902            when N_Range_Constraint =>
1903               return Denotes_Discriminant (Range_Expression (Constr));
1904
1905            when others =>
1906               return False;
1907         end case;
1908      end Contains_POC;
1909
1910      ----------------------
1911      -- Is_Known_Limited --
1912      ----------------------
1913
1914      function Is_Known_Limited (Typ : Entity_Id) return Boolean is
1915         P : constant Entity_Id := Etype (Typ);
1916         R : constant Entity_Id := Root_Type (Typ);
1917
1918      begin
1919         if Is_Limited_Record (Typ) then
1920            return True;
1921
1922         --  If the root type is limited (and not a limited interface) so is
1923         --  the current type.
1924
1925         elsif Is_Limited_Record (R)
1926           and then (not Is_Interface (R) or else not Is_Limited_Interface (R))
1927         then
1928            return True;
1929
1930         --  Else the type may have a limited interface progenitor, but a
1931         --  limited record parent that is not an interface.
1932
1933         elsif R /= P
1934           and then Is_Limited_Record (P)
1935           and then not Is_Interface (P)
1936         then
1937            return True;
1938
1939         else
1940            return False;
1941         end if;
1942      end Is_Known_Limited;
1943
1944   --  Start of processing for Analyze_Component_Declaration
1945
1946   begin
1947      Generate_Definition (Id);
1948      Enter_Name (Id);
1949
1950      if Present (Typ) then
1951         T := Find_Type_Of_Object
1952                (Subtype_Indication (Component_Definition (N)), N);
1953
1954         if not Nkind_In (Typ, N_Identifier, N_Expanded_Name) then
1955            Check_SPARK_05_Restriction ("subtype mark required", Typ);
1956         end if;
1957
1958      --  Ada 2005 (AI-230): Access Definition case
1959
1960      else
1961         pragma Assert (Present
1962                          (Access_Definition (Component_Definition (N))));
1963
1964         T := Access_Definition
1965                (Related_Nod => N,
1966                 N => Access_Definition (Component_Definition (N)));
1967         Set_Is_Local_Anonymous_Access (T);
1968
1969         --  Ada 2005 (AI-254)
1970
1971         if Present (Access_To_Subprogram_Definition
1972                      (Access_Definition (Component_Definition (N))))
1973           and then Protected_Present (Access_To_Subprogram_Definition
1974                                        (Access_Definition
1975                                          (Component_Definition (N))))
1976         then
1977            T := Replace_Anonymous_Access_To_Protected_Subprogram (N);
1978         end if;
1979      end if;
1980
1981      --  If the subtype is a constrained subtype of the enclosing record,
1982      --  (which must have a partial view) the back-end does not properly
1983      --  handle the recursion. Rewrite the component declaration with an
1984      --  explicit subtype indication, which is acceptable to Gigi. We can copy
1985      --  the tree directly because side effects have already been removed from
1986      --  discriminant constraints.
1987
1988      if Ekind (T) = E_Access_Subtype
1989        and then Is_Entity_Name (Subtype_Indication (Component_Definition (N)))
1990        and then Comes_From_Source (T)
1991        and then Nkind (Parent (T)) = N_Subtype_Declaration
1992        and then Etype (Directly_Designated_Type (T)) = Current_Scope
1993      then
1994         Rewrite
1995           (Subtype_Indication (Component_Definition (N)),
1996             New_Copy_Tree (Subtype_Indication (Parent (T))));
1997         T := Find_Type_Of_Object
1998                 (Subtype_Indication (Component_Definition (N)), N);
1999      end if;
2000
2001      --  If the component declaration includes a default expression, then we
2002      --  check that the component is not of a limited type (RM 3.7(5)),
2003      --  and do the special preanalysis of the expression (see section on
2004      --  "Handling of Default and Per-Object Expressions" in the spec of
2005      --  package Sem).
2006
2007      if Present (E) then
2008         Check_SPARK_05_Restriction ("default expression is not allowed", E);
2009         Preanalyze_Default_Expression (E, T);
2010         Check_Initialization (T, E);
2011
2012         if Ada_Version >= Ada_2005
2013           and then Ekind (T) = E_Anonymous_Access_Type
2014           and then Etype (E) /= Any_Type
2015         then
2016            --  Check RM 3.9.2(9): "if the expected type for an expression is
2017            --  an anonymous access-to-specific tagged type, then the object
2018            --  designated by the expression shall not be dynamically tagged
2019            --  unless it is a controlling operand in a call on a dispatching
2020            --  operation"
2021
2022            if Is_Tagged_Type (Directly_Designated_Type (T))
2023              and then
2024                Ekind (Directly_Designated_Type (T)) /= E_Class_Wide_Type
2025              and then
2026                Ekind (Directly_Designated_Type (Etype (E))) =
2027                  E_Class_Wide_Type
2028            then
2029               Error_Msg_N
2030                 ("access to specific tagged type required (RM 3.9.2(9))", E);
2031            end if;
2032
2033            --  (Ada 2005: AI-230): Accessibility check for anonymous
2034            --  components
2035
2036            if Type_Access_Level (Etype (E)) >
2037               Deepest_Type_Access_Level (T)
2038            then
2039               Error_Msg_N
2040                 ("expression has deeper access level than component " &
2041                  "(RM 3.10.2 (12.2))", E);
2042            end if;
2043
2044            --  The initialization expression is a reference to an access
2045            --  discriminant. The type of the discriminant is always deeper
2046            --  than any access type.
2047
2048            if Ekind (Etype (E)) = E_Anonymous_Access_Type
2049              and then Is_Entity_Name (E)
2050              and then Ekind (Entity (E)) = E_In_Parameter
2051              and then Present (Discriminal_Link (Entity (E)))
2052            then
2053               Error_Msg_N
2054                 ("discriminant has deeper accessibility level than target",
2055                  E);
2056            end if;
2057         end if;
2058      end if;
2059
2060      --  The parent type may be a private view with unknown discriminants,
2061      --  and thus unconstrained. Regular components must be constrained.
2062
2063      if not Is_Definite_Subtype (T) and then Chars (Id) /= Name_uParent then
2064         if Is_Class_Wide_Type (T) then
2065            Error_Msg_N
2066               ("class-wide subtype with unknown discriminants" &
2067                 " in component declaration",
2068                 Subtype_Indication (Component_Definition (N)));
2069         else
2070            Error_Msg_N
2071              ("unconstrained subtype in component declaration",
2072               Subtype_Indication (Component_Definition (N)));
2073         end if;
2074
2075      --  Components cannot be abstract, except for the special case of
2076      --  the _Parent field (case of extending an abstract tagged type)
2077
2078      elsif Is_Abstract_Type (T) and then Chars (Id) /= Name_uParent then
2079         Error_Msg_N ("type of a component cannot be abstract", N);
2080      end if;
2081
2082      Set_Etype (Id, T);
2083      Set_Is_Aliased (Id, Aliased_Present (Component_Definition (N)));
2084
2085      --  The component declaration may have a per-object constraint, set
2086      --  the appropriate flag in the defining identifier of the subtype.
2087
2088      if Present (Subtype_Indication (Component_Definition (N))) then
2089         declare
2090            Sindic : constant Node_Id :=
2091                       Subtype_Indication (Component_Definition (N));
2092         begin
2093            if Nkind (Sindic) = N_Subtype_Indication
2094              and then Present (Constraint (Sindic))
2095              and then Contains_POC (Constraint (Sindic))
2096            then
2097               Set_Has_Per_Object_Constraint (Id);
2098            end if;
2099         end;
2100      end if;
2101
2102      --  Ada 2005 (AI-231): Propagate the null-excluding attribute and carry
2103      --  out some static checks.
2104
2105      if Ada_Version >= Ada_2005 and then Can_Never_Be_Null (T) then
2106         Null_Exclusion_Static_Checks (N);
2107      end if;
2108
2109      --  If this component is private (or depends on a private type), flag the
2110      --  record type to indicate that some operations are not available.
2111
2112      P := Private_Component (T);
2113
2114      if Present (P) then
2115
2116         --  Check for circular definitions
2117
2118         if P = Any_Type then
2119            Set_Etype (Id, Any_Type);
2120
2121         --  There is a gap in the visibility of operations only if the
2122         --  component type is not defined in the scope of the record type.
2123
2124         elsif Scope (P) = Scope (Current_Scope) then
2125            null;
2126
2127         elsif Is_Limited_Type (P) then
2128            Set_Is_Limited_Composite (Current_Scope);
2129
2130         else
2131            Set_Is_Private_Composite (Current_Scope);
2132         end if;
2133      end if;
2134
2135      if P /= Any_Type
2136        and then Is_Limited_Type (T)
2137        and then Chars (Id) /= Name_uParent
2138        and then Is_Tagged_Type (Current_Scope)
2139      then
2140         if Is_Derived_Type (Current_Scope)
2141           and then not Is_Known_Limited (Current_Scope)
2142         then
2143            Error_Msg_N
2144              ("extension of nonlimited type cannot have limited components",
2145               N);
2146
2147            if Is_Interface (Root_Type (Current_Scope)) then
2148               Error_Msg_N
2149                 ("\limitedness is not inherited from limited interface", N);
2150               Error_Msg_N ("\add LIMITED to type indication", N);
2151            end if;
2152
2153            Explain_Limited_Type (T, N);
2154            Set_Etype (Id, Any_Type);
2155            Set_Is_Limited_Composite (Current_Scope, False);
2156
2157         elsif not Is_Derived_Type (Current_Scope)
2158           and then not Is_Limited_Record (Current_Scope)
2159           and then not Is_Concurrent_Type (Current_Scope)
2160         then
2161            Error_Msg_N
2162              ("nonlimited tagged type cannot have limited components", N);
2163            Explain_Limited_Type (T, N);
2164            Set_Etype (Id, Any_Type);
2165            Set_Is_Limited_Composite (Current_Scope, False);
2166         end if;
2167      end if;
2168
2169      --  If the component is an unconstrained task or protected type with
2170      --  discriminants, the component and the enclosing record are limited
2171      --  and the component is constrained by its default values. Compute
2172      --  its actual subtype, else it may be allocated the maximum size by
2173      --  the backend, and possibly overflow.
2174
2175      if Is_Concurrent_Type (T)
2176        and then not Is_Constrained (T)
2177        and then Has_Discriminants (T)
2178        and then not Has_Discriminants (Current_Scope)
2179      then
2180         declare
2181            Act_T : constant Entity_Id := Build_Default_Subtype (T, N);
2182
2183         begin
2184            Set_Etype (Id, Act_T);
2185
2186            --  Rewrite component definition to use the constrained subtype
2187
2188            Rewrite (Component_Definition (N),
2189              Make_Component_Definition (Loc,
2190                Subtype_Indication => New_Occurrence_Of (Act_T, Loc)));
2191         end;
2192      end if;
2193
2194      Set_Original_Record_Component (Id, Id);
2195
2196      if Has_Aspects (N) then
2197         Analyze_Aspect_Specifications (N, Id);
2198      end if;
2199
2200      Analyze_Dimension (N);
2201   end Analyze_Component_Declaration;
2202
2203   --------------------------
2204   -- Analyze_Declarations --
2205   --------------------------
2206
2207   procedure Analyze_Declarations (L : List_Id) is
2208      Decl : Node_Id;
2209
2210      procedure Adjust_Decl;
2211      --  Adjust Decl not to include implicit label declarations, since these
2212      --  have strange Sloc values that result in elaboration check problems.
2213      --  (They have the sloc of the label as found in the source, and that
2214      --  is ahead of the current declarative part).
2215
2216      procedure Build_Assertion_Bodies (Decls : List_Id; Context : Node_Id);
2217      --  Create the subprogram bodies which verify the run-time semantics of
2218      --  the pragmas listed below for each elibigle type found in declarative
2219      --  list Decls. The pragmas are:
2220      --
2221      --    Default_Initial_Condition
2222      --    Invariant
2223      --    Type_Invariant
2224      --
2225      --  Context denotes the owner of the declarative list.
2226
2227      procedure Check_Entry_Contracts;
2228      --  Perform a preanalysis of the pre- and postconditions of an entry
2229      --  declaration. This must be done before full resolution and creation
2230      --  of the parameter block, etc. to catch illegal uses within the
2231      --  contract expression. Full analysis of the expression is done when
2232      --  the contract is processed.
2233
2234      function Contains_Lib_Incomplete_Type (Pkg : Entity_Id) return Boolean;
2235      --  Check if a nested package has entities within it that rely on library
2236      --  level private types where the full view has not been completed for
2237      --  the purposes of checking if it is acceptable to freeze an expression
2238      --  function at the point of declaration.
2239
2240      procedure Handle_Late_Controlled_Primitive (Body_Decl : Node_Id);
2241      --  Determine whether Body_Decl denotes the body of a late controlled
2242      --  primitive (either Initialize, Adjust or Finalize). If this is the
2243      --  case, add a proper spec if the body lacks one. The spec is inserted
2244      --  before Body_Decl and immediately analyzed.
2245
2246      procedure Remove_Partial_Visible_Refinements (Spec_Id : Entity_Id);
2247      --  Spec_Id is the entity of a package that may define abstract states,
2248      --  and in the case of a child unit, whose ancestors may define abstract
2249      --  states. If the states have partial visible refinement, remove the
2250      --  partial visibility of each constituent at the end of the package
2251      --  spec and body declarations.
2252
2253      procedure Remove_Visible_Refinements (Spec_Id : Entity_Id);
2254      --  Spec_Id is the entity of a package that may define abstract states.
2255      --  If the states have visible refinement, remove the visibility of each
2256      --  constituent at the end of the package body declaration.
2257
2258      procedure Resolve_Aspects;
2259      --  Utility to resolve the expressions of aspects at the end of a list of
2260      --  declarations, or before a declaration that freezes previous entities,
2261      --  such as in a subprogram body.
2262
2263      -----------------
2264      -- Adjust_Decl --
2265      -----------------
2266
2267      procedure Adjust_Decl is
2268      begin
2269         while Present (Prev (Decl))
2270           and then Nkind (Decl) = N_Implicit_Label_Declaration
2271         loop
2272            Prev (Decl);
2273         end loop;
2274      end Adjust_Decl;
2275
2276      ----------------------------
2277      -- Build_Assertion_Bodies --
2278      ----------------------------
2279
2280      procedure Build_Assertion_Bodies (Decls : List_Id; Context : Node_Id) is
2281         procedure Build_Assertion_Bodies_For_Type (Typ : Entity_Id);
2282         --  Create the subprogram bodies which verify the run-time semantics
2283         --  of the pragmas listed below for type Typ. The pragmas are:
2284         --
2285         --    Default_Initial_Condition
2286         --    Invariant
2287         --    Type_Invariant
2288
2289         -------------------------------------
2290         -- Build_Assertion_Bodies_For_Type --
2291         -------------------------------------
2292
2293         procedure Build_Assertion_Bodies_For_Type (Typ : Entity_Id) is
2294         begin
2295            --  Preanalyze and resolve the Default_Initial_Condition assertion
2296            --  expression at the end of the declarations to catch any errors.
2297
2298            if Has_DIC (Typ) then
2299               Build_DIC_Procedure_Body (Typ);
2300            end if;
2301
2302            if Nkind (Context) = N_Package_Specification then
2303
2304               --  Preanalyze and resolve the class-wide invariants of an
2305               --  interface at the end of whichever declarative part has the
2306               --  interface type. Note that an interface may be declared in
2307               --  any non-package declarative part, but reaching the end of
2308               --  such a declarative part will always freeze the type and
2309               --  generate the invariant procedure (see Freeze_Type).
2310
2311               if Is_Interface (Typ) then
2312
2313                  --  Interfaces are treated as the partial view of a private
2314                  --  type, in order to achieve uniformity with the general
2315                  --  case. As a result, an interface receives only a "partial"
2316                  --  invariant procedure, which is never called.
2317
2318                  if Has_Own_Invariants (Typ) then
2319                     Build_Invariant_Procedure_Body
2320                       (Typ               => Typ,
2321                        Partial_Invariant => True);
2322                  end if;
2323
2324               --  Preanalyze and resolve the invariants of a private type
2325               --  at the end of the visible declarations to catch potential
2326               --  errors. Inherited class-wide invariants are not included
2327               --  because they have already been resolved.
2328
2329               elsif Decls = Visible_Declarations (Context)
2330                 and then Ekind_In (Typ, E_Limited_Private_Type,
2331                                         E_Private_Type,
2332                                         E_Record_Type_With_Private)
2333                 and then Has_Own_Invariants (Typ)
2334               then
2335                  Build_Invariant_Procedure_Body
2336                    (Typ               => Typ,
2337                     Partial_Invariant => True);
2338
2339               --  Preanalyze and resolve the invariants of a private type's
2340               --  full view at the end of the private declarations to catch
2341               --  potential errors.
2342
2343               elsif Decls = Private_Declarations (Context)
2344                 and then not Is_Private_Type (Typ)
2345                 and then Has_Private_Declaration (Typ)
2346                 and then Has_Invariants (Typ)
2347               then
2348                  Build_Invariant_Procedure_Body (Typ);
2349               end if;
2350            end if;
2351         end Build_Assertion_Bodies_For_Type;
2352
2353         --  Local variables
2354
2355         Decl    : Node_Id;
2356         Decl_Id : Entity_Id;
2357
2358      --  Start of processing for Build_Assertion_Bodies
2359
2360      begin
2361         Decl := First (Decls);
2362         while Present (Decl) loop
2363            if Is_Declaration (Decl) then
2364               Decl_Id := Defining_Entity (Decl);
2365
2366               if Is_Type (Decl_Id) then
2367                  Build_Assertion_Bodies_For_Type (Decl_Id);
2368               end if;
2369            end if;
2370
2371            Next (Decl);
2372         end loop;
2373      end Build_Assertion_Bodies;
2374
2375      ---------------------------
2376      -- Check_Entry_Contracts --
2377      ---------------------------
2378
2379      procedure Check_Entry_Contracts is
2380         ASN : Node_Id;
2381         Ent : Entity_Id;
2382         Exp : Node_Id;
2383
2384      begin
2385         Ent := First_Entity (Current_Scope);
2386         while Present (Ent) loop
2387
2388            --  This only concerns entries with pre/postconditions
2389
2390            if Ekind (Ent) = E_Entry
2391              and then Present (Contract (Ent))
2392              and then Present (Pre_Post_Conditions (Contract (Ent)))
2393            then
2394               ASN := Pre_Post_Conditions (Contract (Ent));
2395               Push_Scope (Ent);
2396               Install_Formals (Ent);
2397
2398               --  Pre/postconditions are rewritten as Check pragmas. Analysis
2399               --  is performed on a copy of the pragma expression, to prevent
2400               --  modifying the original expression.
2401
2402               while Present (ASN) loop
2403                  if Nkind (ASN) = N_Pragma then
2404                     Exp :=
2405                       New_Copy_Tree
2406                         (Expression
2407                           (First (Pragma_Argument_Associations (ASN))));
2408                     Set_Parent (Exp, ASN);
2409
2410                     Preanalyze_Assert_Expression (Exp, Standard_Boolean);
2411                  end if;
2412
2413                  ASN := Next_Pragma (ASN);
2414               end loop;
2415
2416               End_Scope;
2417            end if;
2418
2419            Next_Entity (Ent);
2420         end loop;
2421      end Check_Entry_Contracts;
2422
2423      ----------------------------------
2424      -- Contains_Lib_Incomplete_Type --
2425      ----------------------------------
2426
2427      function Contains_Lib_Incomplete_Type (Pkg : Entity_Id) return Boolean is
2428         Curr : Entity_Id;
2429
2430      begin
2431         --  Avoid looking through scopes that do not meet the precondition of
2432         --  Pkg not being within a library unit spec.
2433
2434         if not Is_Compilation_Unit (Pkg)
2435           and then not Is_Generic_Instance (Pkg)
2436           and then not In_Package_Body (Enclosing_Lib_Unit_Entity (Pkg))
2437         then
2438            --  Loop through all entities in the current scope to identify
2439            --  an entity that depends on a private type.
2440
2441            Curr := First_Entity (Pkg);
2442            loop
2443               if Nkind (Curr) in N_Entity
2444                 and then Depends_On_Private (Curr)
2445               then
2446                  return True;
2447               end if;
2448
2449               exit when Last_Entity (Current_Scope) = Curr;
2450               Curr := Next_Entity (Curr);
2451            end loop;
2452         end if;
2453
2454         return False;
2455      end Contains_Lib_Incomplete_Type;
2456
2457      --------------------------------------
2458      -- Handle_Late_Controlled_Primitive --
2459      --------------------------------------
2460
2461      procedure Handle_Late_Controlled_Primitive (Body_Decl : Node_Id) is
2462         Body_Spec : constant Node_Id    := Specification (Body_Decl);
2463         Body_Id   : constant Entity_Id  := Defining_Entity (Body_Spec);
2464         Loc       : constant Source_Ptr := Sloc (Body_Id);
2465         Params    : constant List_Id    :=
2466                       Parameter_Specifications (Body_Spec);
2467         Spec      : Node_Id;
2468         Spec_Id   : Entity_Id;
2469         Typ       : Node_Id;
2470
2471      begin
2472         --  Consider only procedure bodies whose name matches one of the three
2473         --  controlled primitives.
2474
2475         if Nkind (Body_Spec) /= N_Procedure_Specification
2476           or else not Nam_In (Chars (Body_Id), Name_Adjust,
2477                                                Name_Finalize,
2478                                                Name_Initialize)
2479         then
2480            return;
2481
2482         --  A controlled primitive must have exactly one formal which is not
2483         --  an anonymous access type.
2484
2485         elsif List_Length (Params) /= 1 then
2486            return;
2487         end if;
2488
2489         Typ := Parameter_Type (First (Params));
2490
2491         if Nkind (Typ) = N_Access_Definition then
2492            return;
2493         end if;
2494
2495         Find_Type (Typ);
2496
2497         --  The type of the formal must be derived from [Limited_]Controlled
2498
2499         if not Is_Controlled (Entity (Typ)) then
2500            return;
2501         end if;
2502
2503         --  Check whether a specification exists for this body. We do not
2504         --  analyze the spec of the body in full, because it will be analyzed
2505         --  again when the body is properly analyzed, and we cannot create
2506         --  duplicate entries in the formals chain. We look for an explicit
2507         --  specification because the body may be an overriding operation and
2508         --  an inherited spec may be present.
2509
2510         Spec_Id := Current_Entity (Body_Id);
2511
2512         while Present (Spec_Id) loop
2513            if Ekind_In (Spec_Id, E_Procedure, E_Generic_Procedure)
2514              and then Scope (Spec_Id) = Current_Scope
2515              and then Present (First_Formal (Spec_Id))
2516              and then No (Next_Formal (First_Formal (Spec_Id)))
2517              and then Etype (First_Formal (Spec_Id)) = Entity (Typ)
2518              and then Comes_From_Source (Spec_Id)
2519            then
2520               return;
2521            end if;
2522
2523            Spec_Id := Homonym (Spec_Id);
2524         end loop;
2525
2526         --  At this point the body is known to be a late controlled primitive.
2527         --  Generate a matching spec and insert it before the body. Note the
2528         --  use of Copy_Separate_Tree - we want an entirely separate semantic
2529         --  tree in this case.
2530
2531         Spec := Copy_Separate_Tree (Body_Spec);
2532
2533         --  Ensure that the subprogram declaration does not inherit the null
2534         --  indicator from the body as we now have a proper spec/body pair.
2535
2536         Set_Null_Present (Spec, False);
2537
2538         --  Ensure that the freeze node is inserted after the declaration of
2539         --  the primitive since its expansion will freeze the primitive.
2540
2541         Decl := Make_Subprogram_Declaration (Loc, Specification => Spec);
2542
2543         Insert_Before_And_Analyze (Body_Decl, Decl);
2544      end Handle_Late_Controlled_Primitive;
2545
2546      ----------------------------------------
2547      -- Remove_Partial_Visible_Refinements --
2548      ----------------------------------------
2549
2550      procedure Remove_Partial_Visible_Refinements (Spec_Id : Entity_Id) is
2551         State_Elmt : Elmt_Id;
2552      begin
2553         if Present (Abstract_States (Spec_Id)) then
2554            State_Elmt := First_Elmt (Abstract_States (Spec_Id));
2555            while Present (State_Elmt) loop
2556               Set_Has_Partial_Visible_Refinement (Node (State_Elmt), False);
2557               Next_Elmt (State_Elmt);
2558            end loop;
2559         end if;
2560
2561         --  For a child unit, also hide the partial state refinement from
2562         --  ancestor packages.
2563
2564         if Is_Child_Unit (Spec_Id) then
2565            Remove_Partial_Visible_Refinements (Scope (Spec_Id));
2566         end if;
2567      end Remove_Partial_Visible_Refinements;
2568
2569      --------------------------------
2570      -- Remove_Visible_Refinements --
2571      --------------------------------
2572
2573      procedure Remove_Visible_Refinements (Spec_Id : Entity_Id) is
2574         State_Elmt : Elmt_Id;
2575      begin
2576         if Present (Abstract_States (Spec_Id)) then
2577            State_Elmt := First_Elmt (Abstract_States (Spec_Id));
2578            while Present (State_Elmt) loop
2579               Set_Has_Visible_Refinement (Node (State_Elmt), False);
2580               Next_Elmt (State_Elmt);
2581            end loop;
2582         end if;
2583      end Remove_Visible_Refinements;
2584
2585      ---------------------
2586      -- Resolve_Aspects --
2587      ---------------------
2588
2589      procedure Resolve_Aspects is
2590         E : Entity_Id;
2591
2592      begin
2593         E := First_Entity (Current_Scope);
2594         while Present (E) loop
2595            Resolve_Aspect_Expressions (E);
2596            Next_Entity (E);
2597         end loop;
2598      end Resolve_Aspects;
2599
2600      --  Local variables
2601
2602      Context     : Node_Id   := Empty;
2603      Freeze_From : Entity_Id := Empty;
2604      Next_Decl   : Node_Id;
2605
2606      Body_Seen : Boolean := False;
2607      --  Flag set when the first body [stub] is encountered
2608
2609   --  Start of processing for Analyze_Declarations
2610
2611   begin
2612      if Restriction_Check_Required (SPARK_05) then
2613         Check_Later_Vs_Basic_Declarations (L, During_Parsing => False);
2614      end if;
2615
2616      Decl := First (L);
2617      while Present (Decl) loop
2618
2619         --  Package spec cannot contain a package declaration in SPARK
2620
2621         if Nkind (Decl) = N_Package_Declaration
2622           and then Nkind (Parent (L)) = N_Package_Specification
2623         then
2624            Check_SPARK_05_Restriction
2625              ("package specification cannot contain a package declaration",
2626               Decl);
2627         end if;
2628
2629         --  Complete analysis of declaration
2630
2631         Analyze (Decl);
2632         Next_Decl := Next (Decl);
2633
2634         if No (Freeze_From) then
2635            Freeze_From := First_Entity (Current_Scope);
2636         end if;
2637
2638         --  At the end of a declarative part, freeze remaining entities
2639         --  declared in it. The end of the visible declarations of package
2640         --  specification is not the end of a declarative part if private
2641         --  declarations are present. The end of a package declaration is a
2642         --  freezing point only if it a library package. A task definition or
2643         --  protected type definition is not a freeze point either. Finally,
2644         --  we do not freeze entities in generic scopes, because there is no
2645         --  code generated for them and freeze nodes will be generated for
2646         --  the instance.
2647
2648         --  The end of a package instantiation is not a freeze point, but
2649         --  for now we make it one, because the generic body is inserted
2650         --  (currently) immediately after. Generic instantiations will not
2651         --  be a freeze point once delayed freezing of bodies is implemented.
2652         --  (This is needed in any case for early instantiations ???).
2653
2654         if No (Next_Decl) then
2655            if Nkind (Parent (L)) = N_Component_List then
2656               null;
2657
2658            elsif Nkind_In (Parent (L), N_Protected_Definition,
2659                                        N_Task_Definition)
2660            then
2661               Check_Entry_Contracts;
2662
2663            elsif Nkind (Parent (L)) /= N_Package_Specification then
2664               if Nkind (Parent (L)) = N_Package_Body then
2665                  Freeze_From := First_Entity (Current_Scope);
2666               end if;
2667
2668               --  There may have been several freezing points previously,
2669               --  for example object declarations or subprogram bodies, but
2670               --  at the end of a declarative part we check freezing from
2671               --  the beginning, even though entities may already be frozen,
2672               --  in order to perform visibility checks on delayed aspects.
2673
2674               Adjust_Decl;
2675
2676               --  If the current scope is a generic subprogram body. Skip the
2677               --  generic formal parameters that are not frozen here.
2678
2679               if Is_Subprogram (Current_Scope)
2680                 and then Nkind (Unit_Declaration_Node (Current_Scope)) =
2681                            N_Generic_Subprogram_Declaration
2682                 and then Present (First_Entity (Current_Scope))
2683               then
2684                  while Is_Generic_Formal (Freeze_From) loop
2685                     Freeze_From := Next_Entity (Freeze_From);
2686                  end loop;
2687
2688                  Freeze_All (Freeze_From, Decl);
2689                  Freeze_From := Last_Entity (Current_Scope);
2690
2691               else
2692                  --  For declarations in a subprogram body there is no issue
2693                  --  with name resolution in aspect specifications, but in
2694                  --  ASIS mode we need to preanalyze aspect specifications
2695                  --  that may otherwise only be analyzed during expansion
2696                  --  (e.g. during generation of a related subprogram).
2697
2698                  if ASIS_Mode then
2699                     Resolve_Aspects;
2700                  end if;
2701
2702                  Freeze_All (First_Entity (Current_Scope), Decl);
2703                  Freeze_From := Last_Entity (Current_Scope);
2704               end if;
2705
2706            --  Current scope is a package specification
2707
2708            elsif Scope (Current_Scope) /= Standard_Standard
2709              and then not Is_Child_Unit (Current_Scope)
2710              and then No (Generic_Parent (Parent (L)))
2711            then
2712               --  ARM rule 13.1.1(11/3): usage names in aspect definitions are
2713               --  resolved at the end of the immediately enclosing declaration
2714               --  list (AI05-0183-1).
2715
2716               Resolve_Aspects;
2717
2718            elsif L /= Visible_Declarations (Parent (L))
2719              or else No (Private_Declarations (Parent (L)))
2720              or else Is_Empty_List (Private_Declarations (Parent (L)))
2721            then
2722               Adjust_Decl;
2723
2724               --  End of a package declaration
2725
2726               --  In compilation mode the expansion of freeze node takes care
2727               --  of resolving expressions of all aspects in the list. In ASIS
2728               --  mode this must be done explicitly.
2729
2730               if ASIS_Mode
2731                 and then Scope (Current_Scope) = Standard_Standard
2732               then
2733                  Resolve_Aspects;
2734               end if;
2735
2736               --  This is a freeze point because it is the end of a
2737               --  compilation unit.
2738
2739               Freeze_All (First_Entity (Current_Scope), Decl);
2740               Freeze_From := Last_Entity (Current_Scope);
2741
2742            --  At the end of the visible declarations the expressions in
2743            --  aspects of all entities declared so far must be resolved.
2744            --  The entities themselves might be frozen later, and the
2745            --  generated pragmas and attribute definition clauses analyzed
2746            --  in full at that point, but name resolution must take place
2747            --  now.
2748            --  In addition to being the proper semantics, this is mandatory
2749            --  within generic units, because global name capture requires
2750            --  those expressions to be analyzed, given that the generated
2751            --  pragmas do not appear in the original generic tree.
2752
2753            elsif Serious_Errors_Detected = 0 then
2754               Resolve_Aspects;
2755            end if;
2756
2757         --  If next node is a body then freeze all types before the body.
2758         --  An exception occurs for some expander-generated bodies. If these
2759         --  are generated at places where in general language rules would not
2760         --  allow a freeze point, then we assume that the expander has
2761         --  explicitly checked that all required types are properly frozen,
2762         --  and we do not cause general freezing here. This special circuit
2763         --  is used when the encountered body is marked as having already
2764         --  been analyzed.
2765
2766         --  In all other cases (bodies that come from source, and expander
2767         --  generated bodies that have not been analyzed yet), freeze all
2768         --  types now. Note that in the latter case, the expander must take
2769         --  care to attach the bodies at a proper place in the tree so as to
2770         --  not cause unwanted freezing at that point.
2771
2772         --  It is also necessary to check for a case where both an expression
2773         --  function is used and the current scope depends on an incomplete
2774         --  private type from a library unit, otherwise premature freezing of
2775         --  the private type will occur.
2776
2777         elsif not Analyzed (Next_Decl) and then Is_Body (Next_Decl)
2778           and then ((Nkind (Next_Decl) /= N_Subprogram_Body
2779                       or else not Was_Expression_Function (Next_Decl))
2780                      or else (not Is_Ignored_Ghost_Entity (Current_Scope)
2781                                and then not Contains_Lib_Incomplete_Type
2782                                               (Current_Scope)))
2783         then
2784            --  When a controlled type is frozen, the expander generates stream
2785            --  and controlled-type support routines. If the freeze is caused
2786            --  by the stand-alone body of Initialize, Adjust, or Finalize, the
2787            --  expander will end up using the wrong version of these routines,
2788            --  as the body has not been processed yet. To remedy this, detect
2789            --  a late controlled primitive and create a proper spec for it.
2790            --  This ensures that the primitive will override its inherited
2791            --  counterpart before the freeze takes place.
2792
2793            --  If the declaration we just processed is a body, do not attempt
2794            --  to examine Next_Decl as the late primitive idiom can only apply
2795            --  to the first encountered body.
2796
2797            --  The spec of the late primitive is not generated in ASIS mode to
2798            --  ensure a consistent list of primitives that indicates the true
2799            --  semantic structure of the program (which is not relevant when
2800            --  generating executable code).
2801
2802            --  ??? A cleaner approach may be possible and/or this solution
2803            --  could be extended to general-purpose late primitives, TBD.
2804
2805            if not ASIS_Mode
2806              and then not Body_Seen
2807              and then not Is_Body (Decl)
2808            then
2809               Body_Seen := True;
2810
2811               if Nkind (Next_Decl) = N_Subprogram_Body then
2812                  Handle_Late_Controlled_Primitive (Next_Decl);
2813               end if;
2814
2815            else
2816               --  In ASIS mode, if the next declaration is a body, complete
2817               --  the analysis of declarations so far.
2818
2819               Resolve_Aspects;
2820            end if;
2821
2822            Adjust_Decl;
2823
2824            --  The generated body of an expression function does not freeze,
2825            --  unless it is a completion, in which case only the expression
2826            --  itself freezes. This is handled when the body itself is
2827            --  analyzed (see Freeze_Expr_Types, sem_ch6.adb).
2828
2829            Freeze_All (Freeze_From, Decl);
2830            Freeze_From := Last_Entity (Current_Scope);
2831         end if;
2832
2833         Decl := Next_Decl;
2834      end loop;
2835
2836      --  Post-freezing actions
2837
2838      if Present (L) then
2839         Context := Parent (L);
2840
2841         --  Certain contract annocations have forward visibility semantics and
2842         --  must be analyzed after all declarative items have been processed.
2843         --  This timing ensures that entities referenced by such contracts are
2844         --  visible.
2845
2846         --  Analyze the contract of an immediately enclosing package spec or
2847         --  body first because other contracts may depend on its information.
2848
2849         if Nkind (Context) = N_Package_Body then
2850            Analyze_Package_Body_Contract (Defining_Entity (Context));
2851
2852         elsif Nkind (Context) = N_Package_Specification then
2853            Analyze_Package_Contract (Defining_Entity (Context));
2854         end if;
2855
2856         --  Analyze the contracts of various constructs in the declarative
2857         --  list.
2858
2859         Analyze_Contracts (L);
2860
2861         if Nkind (Context) = N_Package_Body then
2862
2863            --  Ensure that all abstract states and objects declared in the
2864            --  state space of a package body are utilized as constituents.
2865
2866            Check_Unused_Body_States (Defining_Entity (Context));
2867
2868            --  State refinements are visible up to the end of the package body
2869            --  declarations. Hide the state refinements from visibility to
2870            --  restore the original state conditions.
2871
2872            Remove_Visible_Refinements (Corresponding_Spec (Context));
2873            Remove_Partial_Visible_Refinements (Corresponding_Spec (Context));
2874
2875         elsif Nkind (Context) = N_Package_Specification then
2876
2877            --  Partial state refinements are visible up to the end of the
2878            --  package spec declarations. Hide the partial state refinements
2879            --  from visibility to restore the original state conditions.
2880
2881            Remove_Partial_Visible_Refinements (Defining_Entity (Context));
2882         end if;
2883
2884         --  Verify that all abstract states found in any package declared in
2885         --  the input declarative list have proper refinements. The check is
2886         --  performed only when the context denotes a block, entry, package,
2887         --  protected, subprogram, or task body (SPARK RM 7.2.2(3)).
2888
2889         Check_State_Refinements (Context);
2890
2891         --  Create the subprogram bodies which verify the run-time semantics
2892         --  of pragmas Default_Initial_Condition and [Type_]Invariant for all
2893         --  types within the current declarative list. This ensures that all
2894         --  assertion expressions are preanalyzed and resolved at the end of
2895         --  the declarative part. Note that the resolution happens even when
2896         --  freezing does not take place.
2897
2898         Build_Assertion_Bodies (L, Context);
2899      end if;
2900   end Analyze_Declarations;
2901
2902   -----------------------------------
2903   -- Analyze_Full_Type_Declaration --
2904   -----------------------------------
2905
2906   procedure Analyze_Full_Type_Declaration (N : Node_Id) is
2907      Def    : constant Node_Id   := Type_Definition (N);
2908      Def_Id : constant Entity_Id := Defining_Identifier (N);
2909      T      : Entity_Id;
2910      Prev   : Entity_Id;
2911
2912      Is_Remote : constant Boolean :=
2913                    (Is_Remote_Types (Current_Scope)
2914                       or else Is_Remote_Call_Interface (Current_Scope))
2915                      and then not (In_Private_Part (Current_Scope)
2916                                     or else In_Package_Body (Current_Scope));
2917
2918      procedure Check_Nonoverridable_Aspects;
2919      --  Apply the rule in RM 13.1.1(18.4/4) on iterator aspects that cannot
2920      --  be overridden, and can only be confirmed on derivation.
2921
2922      procedure Check_Ops_From_Incomplete_Type;
2923      --  If there is a tagged incomplete partial view of the type, traverse
2924      --  the primitives of the incomplete view and change the type of any
2925      --  controlling formals and result to indicate the full view. The
2926      --  primitives will be added to the full type's primitive operations
2927      --  list later in Sem_Disp.Check_Operation_From_Incomplete_Type (which
2928      --  is called from Process_Incomplete_Dependents).
2929
2930      ----------------------------------
2931      -- Check_Nonoverridable_Aspects --
2932      ----------------------------------
2933
2934      procedure Check_Nonoverridable_Aspects is
2935         function Get_Aspect_Spec
2936           (Specs       : List_Id;
2937            Aspect_Name : Name_Id) return Node_Id;
2938         --  Check whether a list of aspect specifications includes an entry
2939         --  for a specific aspect. The list is either that of a partial or
2940         --  a full view.
2941
2942         ---------------------
2943         -- Get_Aspect_Spec --
2944         ---------------------
2945
2946         function Get_Aspect_Spec
2947           (Specs       : List_Id;
2948            Aspect_Name : Name_Id) return Node_Id
2949         is
2950            Spec : Node_Id;
2951
2952         begin
2953            Spec := First (Specs);
2954            while Present (Spec) loop
2955               if Chars (Identifier (Spec)) = Aspect_Name then
2956                  return Spec;
2957               end if;
2958               Next (Spec);
2959            end loop;
2960
2961            return Empty;
2962         end Get_Aspect_Spec;
2963
2964         --  Local variables
2965
2966         Prev_Aspects   : constant List_Id :=
2967                            Aspect_Specifications (Parent (Def_Id));
2968         Par_Type       : Entity_Id;
2969         Prev_Aspect    : Node_Id;
2970
2971      --  Start of processing for Check_Nonoverridable_Aspects
2972
2973      begin
2974         --  Get parent type of derived type. Note that Prev is the entity in
2975         --  the partial declaration, but its contents are now those of full
2976         --  view, while Def_Id reflects the partial view.
2977
2978         if Is_Private_Type (Def_Id) then
2979            Par_Type := Etype (Full_View (Def_Id));
2980         else
2981            Par_Type := Etype (Def_Id);
2982         end if;
2983
2984         --  If there is an inherited Implicit_Dereference, verify that it is
2985         --  made explicit in the partial view.
2986
2987         if Has_Discriminants (Base_Type (Par_Type))
2988           and then Nkind (Parent (Prev)) = N_Full_Type_Declaration
2989           and then Present (Discriminant_Specifications (Parent (Prev)))
2990           and then Present (Get_Reference_Discriminant (Par_Type))
2991         then
2992            Prev_Aspect :=
2993              Get_Aspect_Spec (Prev_Aspects, Name_Implicit_Dereference);
2994
2995            if No (Prev_Aspect)
2996              and then Present
2997                         (Discriminant_Specifications
2998                           (Original_Node (Parent (Prev))))
2999            then
3000               Error_Msg_N
3001                 ("type does not inherit implicit dereference", Prev);
3002
3003            else
3004               --  If one of the views has the aspect specified, verify that it
3005               --  is consistent with that of the parent.
3006
3007               declare
3008                  Par_Discr  : constant Entity_Id :=
3009                                Get_Reference_Discriminant (Par_Type);
3010                  Cur_Discr  : constant Entity_Id :=
3011                                Get_Reference_Discriminant (Prev);
3012
3013               begin
3014                  if Corresponding_Discriminant (Cur_Discr) /= Par_Discr then
3015                     Error_Msg_N ("aspect incosistent with that of parent", N);
3016                  end if;
3017
3018                  --  Check that specification in partial view matches the
3019                  --  inherited aspect. Compare names directly because aspect
3020                  --  expression may not be analyzed.
3021
3022                  if Present (Prev_Aspect)
3023                    and then Nkind (Expression (Prev_Aspect)) = N_Identifier
3024                    and then Chars (Expression (Prev_Aspect)) /=
3025                               Chars (Cur_Discr)
3026                  then
3027                     Error_Msg_N
3028                       ("aspect incosistent with that of parent", N);
3029                  end if;
3030               end;
3031            end if;
3032         end if;
3033
3034         --  TBD : other nonoverridable aspects.
3035      end Check_Nonoverridable_Aspects;
3036
3037      ------------------------------------
3038      -- Check_Ops_From_Incomplete_Type --
3039      ------------------------------------
3040
3041      procedure Check_Ops_From_Incomplete_Type is
3042         Elmt   : Elmt_Id;
3043         Formal : Entity_Id;
3044         Op     : Entity_Id;
3045
3046      begin
3047         if Prev /= T
3048           and then Ekind (Prev) = E_Incomplete_Type
3049           and then Is_Tagged_Type (Prev)
3050           and then Is_Tagged_Type (T)
3051         then
3052            Elmt := First_Elmt (Primitive_Operations (Prev));
3053            while Present (Elmt) loop
3054               Op := Node (Elmt);
3055
3056               Formal := First_Formal (Op);
3057               while Present (Formal) loop
3058                  if Etype (Formal) = Prev then
3059                     Set_Etype (Formal, T);
3060                  end if;
3061
3062                  Next_Formal (Formal);
3063               end loop;
3064
3065               if Etype (Op) = Prev then
3066                  Set_Etype (Op, T);
3067               end if;
3068
3069               Next_Elmt (Elmt);
3070            end loop;
3071         end if;
3072      end Check_Ops_From_Incomplete_Type;
3073
3074   --  Start of processing for Analyze_Full_Type_Declaration
3075
3076   begin
3077      Prev := Find_Type_Name (N);
3078
3079      --  The full view, if present, now points to the current type. If there
3080      --  is an incomplete partial view, set a link to it, to simplify the
3081      --  retrieval of primitive operations of the type.
3082
3083      --  Ada 2005 (AI-50217): If the type was previously decorated when
3084      --  imported through a LIMITED WITH clause, it appears as incomplete
3085      --  but has no full view.
3086
3087      if Ekind (Prev) = E_Incomplete_Type
3088        and then Present (Full_View (Prev))
3089      then
3090         T := Full_View (Prev);
3091         Set_Incomplete_View (N, Parent (Prev));
3092      else
3093         T := Prev;
3094      end if;
3095
3096      Set_Is_Pure (T, Is_Pure (Current_Scope));
3097
3098      --  We set the flag Is_First_Subtype here. It is needed to set the
3099      --  corresponding flag for the Implicit class-wide-type created
3100      --  during tagged types processing.
3101
3102      Set_Is_First_Subtype (T, True);
3103
3104      --  Only composite types other than array types are allowed to have
3105      --  discriminants.
3106
3107      case Nkind (Def) is
3108
3109         --  For derived types, the rule will be checked once we've figured
3110         --  out the parent type.
3111
3112         when N_Derived_Type_Definition =>
3113            null;
3114
3115         --  For record types, discriminants are allowed, unless we are in
3116         --  SPARK.
3117
3118         when N_Record_Definition =>
3119            if Present (Discriminant_Specifications (N)) then
3120               Check_SPARK_05_Restriction
3121                 ("discriminant type is not allowed",
3122                  Defining_Identifier
3123                    (First (Discriminant_Specifications (N))));
3124            end if;
3125
3126         when others =>
3127            if Present (Discriminant_Specifications (N)) then
3128               Error_Msg_N
3129                 ("elementary or array type cannot have discriminants",
3130                  Defining_Identifier
3131                    (First (Discriminant_Specifications (N))));
3132            end if;
3133      end case;
3134
3135      --  Elaborate the type definition according to kind, and generate
3136      --  subsidiary (implicit) subtypes where needed. We skip this if it was
3137      --  already done (this happens during the reanalysis that follows a call
3138      --  to the high level optimizer).
3139
3140      if not Analyzed (T) then
3141         Set_Analyzed (T);
3142
3143         --  Set the SPARK mode from the current context
3144
3145         Set_SPARK_Pragma           (T, SPARK_Mode_Pragma);
3146         Set_SPARK_Pragma_Inherited (T);
3147
3148         case Nkind (Def) is
3149            when N_Access_To_Subprogram_Definition =>
3150               Access_Subprogram_Declaration (T, Def);
3151
3152               --  If this is a remote access to subprogram, we must create the
3153               --  equivalent fat pointer type, and related subprograms.
3154
3155               if Is_Remote then
3156                  Process_Remote_AST_Declaration (N);
3157               end if;
3158
3159               --  Validate categorization rule against access type declaration
3160               --  usually a violation in Pure unit, Shared_Passive unit.
3161
3162               Validate_Access_Type_Declaration (T, N);
3163
3164            when N_Access_To_Object_Definition =>
3165               Access_Type_Declaration (T, Def);
3166
3167               --  Validate categorization rule against access type declaration
3168               --  usually a violation in Pure unit, Shared_Passive unit.
3169
3170               Validate_Access_Type_Declaration (T, N);
3171
3172               --  If we are in a Remote_Call_Interface package and define a
3173               --  RACW, then calling stubs and specific stream attributes
3174               --  must be added.
3175
3176               if Is_Remote
3177                 and then Is_Remote_Access_To_Class_Wide_Type (Def_Id)
3178               then
3179                  Add_RACW_Features (Def_Id);
3180               end if;
3181
3182            when N_Array_Type_Definition =>
3183               Array_Type_Declaration (T, Def);
3184
3185            when N_Derived_Type_Definition =>
3186               Derived_Type_Declaration (T, N, T /= Def_Id);
3187
3188               --  Inherit predicates from parent, and protect against illegal
3189               --  derivations.
3190
3191               if Is_Type (T) and then Has_Predicates (T) then
3192                  Set_Has_Predicates (Def_Id);
3193               end if;
3194
3195               --  Save the scenario for examination by the ABE Processing
3196               --  phase.
3197
3198               Record_Elaboration_Scenario (N);
3199
3200            when N_Enumeration_Type_Definition =>
3201               Enumeration_Type_Declaration (T, Def);
3202
3203            when N_Floating_Point_Definition =>
3204               Floating_Point_Type_Declaration (T, Def);
3205
3206            when N_Decimal_Fixed_Point_Definition =>
3207               Decimal_Fixed_Point_Type_Declaration (T, Def);
3208
3209            when N_Ordinary_Fixed_Point_Definition =>
3210               Ordinary_Fixed_Point_Type_Declaration (T, Def);
3211
3212            when N_Signed_Integer_Type_Definition =>
3213               Signed_Integer_Type_Declaration (T, Def);
3214
3215            when N_Modular_Type_Definition =>
3216               Modular_Type_Declaration (T, Def);
3217
3218            when N_Record_Definition =>
3219               Record_Type_Declaration (T, N, Prev);
3220
3221            --  If declaration has a parse error, nothing to elaborate.
3222
3223            when N_Error =>
3224               null;
3225
3226            when others =>
3227               raise Program_Error;
3228         end case;
3229      end if;
3230
3231      if Etype (T) = Any_Type then
3232         return;
3233      end if;
3234
3235      --  Controlled type is not allowed in SPARK
3236
3237      if Is_Visibly_Controlled (T) then
3238         Check_SPARK_05_Restriction ("controlled type is not allowed", N);
3239      end if;
3240
3241      --  Some common processing for all types
3242
3243      Set_Depends_On_Private (T, Has_Private_Component (T));
3244      Check_Ops_From_Incomplete_Type;
3245
3246      --  Both the declared entity, and its anonymous base type if one was
3247      --  created, need freeze nodes allocated.
3248
3249      declare
3250         B : constant Entity_Id := Base_Type (T);
3251
3252      begin
3253         --  In the case where the base type differs from the first subtype, we
3254         --  pre-allocate a freeze node, and set the proper link to the first
3255         --  subtype. Freeze_Entity will use this preallocated freeze node when
3256         --  it freezes the entity.
3257
3258         --  This does not apply if the base type is a generic type, whose
3259         --  declaration is independent of the current derived definition.
3260
3261         if B /= T and then not Is_Generic_Type (B) then
3262            Ensure_Freeze_Node (B);
3263            Set_First_Subtype_Link (Freeze_Node (B), T);
3264         end if;
3265
3266         --  A type that is imported through a limited_with clause cannot
3267         --  generate any code, and thus need not be frozen. However, an access
3268         --  type with an imported designated type needs a finalization list,
3269         --  which may be referenced in some other package that has non-limited
3270         --  visibility on the designated type. Thus we must create the
3271         --  finalization list at the point the access type is frozen, to
3272         --  prevent unsatisfied references at link time.
3273
3274         if not From_Limited_With (T) or else Is_Access_Type (T) then
3275            Set_Has_Delayed_Freeze (T);
3276         end if;
3277      end;
3278
3279      --  Case where T is the full declaration of some private type which has
3280      --  been swapped in Defining_Identifier (N).
3281
3282      if T /= Def_Id and then Is_Private_Type (Def_Id) then
3283         Process_Full_View (N, T, Def_Id);
3284
3285         --  Record the reference. The form of this is a little strange, since
3286         --  the full declaration has been swapped in. So the first parameter
3287         --  here represents the entity to which a reference is made which is
3288         --  the "real" entity, i.e. the one swapped in, and the second
3289         --  parameter provides the reference location.
3290
3291         --  Also, we want to kill Has_Pragma_Unreferenced temporarily here
3292         --  since we don't want a complaint about the full type being an
3293         --  unwanted reference to the private type
3294
3295         declare
3296            B : constant Boolean := Has_Pragma_Unreferenced (T);
3297         begin
3298            Set_Has_Pragma_Unreferenced (T, False);
3299            Generate_Reference (T, T, 'c');
3300            Set_Has_Pragma_Unreferenced (T, B);
3301         end;
3302
3303         Set_Completion_Referenced (Def_Id);
3304
3305      --  For completion of incomplete type, process incomplete dependents
3306      --  and always mark the full type as referenced (it is the incomplete
3307      --  type that we get for any real reference).
3308
3309      elsif Ekind (Prev) = E_Incomplete_Type then
3310         Process_Incomplete_Dependents (N, T, Prev);
3311         Generate_Reference (Prev, Def_Id, 'c');
3312         Set_Completion_Referenced (Def_Id);
3313
3314      --  If not private type or incomplete type completion, this is a real
3315      --  definition of a new entity, so record it.
3316
3317      else
3318         Generate_Definition (Def_Id);
3319      end if;
3320
3321      --  Propagate any pending access types whose finalization masters need to
3322      --  be fully initialized from the partial to the full view. Guard against
3323      --  an illegal full view that remains unanalyzed.
3324
3325      if Is_Type (Def_Id) and then Is_Incomplete_Or_Private_Type (Prev) then
3326         Set_Pending_Access_Types (Def_Id, Pending_Access_Types (Prev));
3327      end if;
3328
3329      if Chars (Scope (Def_Id)) = Name_System
3330        and then Chars (Def_Id) = Name_Address
3331        and then In_Predefined_Unit (N)
3332      then
3333         Set_Is_Descendant_Of_Address (Def_Id);
3334         Set_Is_Descendant_Of_Address (Base_Type (Def_Id));
3335         Set_Is_Descendant_Of_Address (Prev);
3336      end if;
3337
3338      Set_Optimize_Alignment_Flags (Def_Id);
3339      Check_Eliminated (Def_Id);
3340
3341      --  If the declaration is a completion and aspects are present, apply
3342      --  them to the entity for the type which is currently the partial
3343      --  view, but which is the one that will be frozen.
3344
3345      if Has_Aspects (N) then
3346
3347         --  In most cases the partial view is a private type, and both views
3348         --  appear in different declarative parts. In the unusual case where
3349         --  the partial view is incomplete, perform the analysis on the
3350         --  full view, to prevent freezing anomalies with the corresponding
3351         --  class-wide type, which otherwise might be frozen before the
3352         --  dispatch table is built.
3353
3354         if Prev /= Def_Id
3355           and then Ekind (Prev) /= E_Incomplete_Type
3356         then
3357            Analyze_Aspect_Specifications (N, Prev);
3358
3359         --  Normal case
3360
3361         else
3362            Analyze_Aspect_Specifications (N, Def_Id);
3363         end if;
3364      end if;
3365
3366      if Is_Derived_Type (Prev)
3367        and then Def_Id /= Prev
3368      then
3369         Check_Nonoverridable_Aspects;
3370      end if;
3371   end Analyze_Full_Type_Declaration;
3372
3373   ----------------------------------
3374   -- Analyze_Incomplete_Type_Decl --
3375   ----------------------------------
3376
3377   procedure Analyze_Incomplete_Type_Decl (N : Node_Id) is
3378      F : constant Boolean := Is_Pure (Current_Scope);
3379      T : Entity_Id;
3380
3381   begin
3382      Check_SPARK_05_Restriction ("incomplete type is not allowed", N);
3383
3384      Generate_Definition (Defining_Identifier (N));
3385
3386      --  Process an incomplete declaration. The identifier must not have been
3387      --  declared already in the scope. However, an incomplete declaration may
3388      --  appear in the private part of a package, for a private type that has
3389      --  already been declared.
3390
3391      --  In this case, the discriminants (if any) must match
3392
3393      T := Find_Type_Name (N);
3394
3395      Set_Ekind            (T, E_Incomplete_Type);
3396      Set_Etype            (T, T);
3397      Set_Is_First_Subtype (T);
3398      Init_Size_Align      (T);
3399
3400      --  Set the SPARK mode from the current context
3401
3402      Set_SPARK_Pragma           (T, SPARK_Mode_Pragma);
3403      Set_SPARK_Pragma_Inherited (T);
3404
3405      --  Ada 2005 (AI-326): Minimum decoration to give support to tagged
3406      --  incomplete types.
3407
3408      if Tagged_Present (N) then
3409         Set_Is_Tagged_Type (T, True);
3410         Set_No_Tagged_Streams_Pragma (T, No_Tagged_Streams);
3411         Make_Class_Wide_Type (T);
3412         Set_Direct_Primitive_Operations (T, New_Elmt_List);
3413      end if;
3414
3415      Set_Stored_Constraint (T, No_Elist);
3416
3417      if Present (Discriminant_Specifications (N)) then
3418         Push_Scope (T);
3419         Process_Discriminants (N);
3420         End_Scope;
3421      end if;
3422
3423      --  If the type has discriminants, nontrivial subtypes may be declared
3424      --  before the full view of the type. The full views of those subtypes
3425      --  will be built after the full view of the type.
3426
3427      Set_Private_Dependents (T, New_Elmt_List);
3428      Set_Is_Pure            (T, F);
3429   end Analyze_Incomplete_Type_Decl;
3430
3431   -----------------------------------
3432   -- Analyze_Interface_Declaration --
3433   -----------------------------------
3434
3435   procedure Analyze_Interface_Declaration (T : Entity_Id; Def : Node_Id) is
3436      CW : constant Entity_Id := Class_Wide_Type (T);
3437
3438   begin
3439      Set_Is_Tagged_Type (T);
3440      Set_No_Tagged_Streams_Pragma (T, No_Tagged_Streams);
3441
3442      Set_Is_Limited_Record (T, Limited_Present (Def)
3443                                  or else Task_Present (Def)
3444                                  or else Protected_Present (Def)
3445                                  or else Synchronized_Present (Def));
3446
3447      --  Type is abstract if full declaration carries keyword, or if previous
3448      --  partial view did.
3449
3450      Set_Is_Abstract_Type (T);
3451      Set_Is_Interface (T);
3452
3453      --  Type is a limited interface if it includes the keyword limited, task,
3454      --  protected, or synchronized.
3455
3456      Set_Is_Limited_Interface
3457        (T, Limited_Present (Def)
3458              or else Protected_Present (Def)
3459              or else Synchronized_Present (Def)
3460              or else Task_Present (Def));
3461
3462      Set_Interfaces (T, New_Elmt_List);
3463      Set_Direct_Primitive_Operations (T, New_Elmt_List);
3464
3465      --  Complete the decoration of the class-wide entity if it was already
3466      --  built (i.e. during the creation of the limited view)
3467
3468      if Present (CW) then
3469         Set_Is_Interface (CW);
3470         Set_Is_Limited_Interface      (CW, Is_Limited_Interface (T));
3471      end if;
3472
3473      --  Check runtime support for synchronized interfaces
3474
3475      if (Is_Task_Interface (T)
3476           or else Is_Protected_Interface (T)
3477           or else Is_Synchronized_Interface (T))
3478        and then not RTE_Available (RE_Select_Specific_Data)
3479      then
3480         Error_Msg_CRT ("synchronized interfaces", T);
3481      end if;
3482   end Analyze_Interface_Declaration;
3483
3484   -----------------------------
3485   -- Analyze_Itype_Reference --
3486   -----------------------------
3487
3488   --  Nothing to do. This node is placed in the tree only for the benefit of
3489   --  back end processing, and has no effect on the semantic processing.
3490
3491   procedure Analyze_Itype_Reference (N : Node_Id) is
3492   begin
3493      pragma Assert (Is_Itype (Itype (N)));
3494      null;
3495   end Analyze_Itype_Reference;
3496
3497   --------------------------------
3498   -- Analyze_Number_Declaration --
3499   --------------------------------
3500
3501   procedure Analyze_Number_Declaration (N : Node_Id) is
3502      E     : constant Node_Id   := Expression (N);
3503      Id    : constant Entity_Id := Defining_Identifier (N);
3504      Index : Interp_Index;
3505      It    : Interp;
3506      T     : Entity_Id;
3507
3508   begin
3509      Generate_Definition (Id);
3510      Enter_Name (Id);
3511
3512      --  This is an optimization of a common case of an integer literal
3513
3514      if Nkind (E) = N_Integer_Literal then
3515         Set_Is_Static_Expression (E, True);
3516         Set_Etype                (E, Universal_Integer);
3517
3518         Set_Etype     (Id, Universal_Integer);
3519         Set_Ekind     (Id, E_Named_Integer);
3520         Set_Is_Frozen (Id, True);
3521         return;
3522      end if;
3523
3524      Set_Is_Pure (Id, Is_Pure (Current_Scope));
3525
3526      --  Process expression, replacing error by integer zero, to avoid
3527      --  cascaded errors or aborts further along in the processing
3528
3529      --  Replace Error by integer zero, which seems least likely to cause
3530      --  cascaded errors.
3531
3532      if E = Error then
3533         Rewrite (E, Make_Integer_Literal (Sloc (E), Uint_0));
3534         Set_Error_Posted (E);
3535      end if;
3536
3537      Analyze (E);
3538
3539      --  Verify that the expression is static and numeric. If
3540      --  the expression is overloaded, we apply the preference
3541      --  rule that favors root numeric types.
3542
3543      if not Is_Overloaded (E) then
3544         T := Etype (E);
3545         if Has_Dynamic_Predicate_Aspect (T) then
3546            Error_Msg_N
3547              ("subtype has dynamic predicate, "
3548               & "not allowed in number declaration", N);
3549         end if;
3550
3551      else
3552         T := Any_Type;
3553
3554         Get_First_Interp (E, Index, It);
3555         while Present (It.Typ) loop
3556            if (Is_Integer_Type (It.Typ) or else Is_Real_Type (It.Typ))
3557              and then (Scope (Base_Type (It.Typ))) = Standard_Standard
3558            then
3559               if T = Any_Type then
3560                  T := It.Typ;
3561
3562               elsif It.Typ = Universal_Real
3563                       or else
3564                     It.Typ = Universal_Integer
3565               then
3566                  --  Choose universal interpretation over any other
3567
3568                  T := It.Typ;
3569                  exit;
3570               end if;
3571            end if;
3572
3573            Get_Next_Interp (Index, It);
3574         end loop;
3575      end if;
3576
3577      if Is_Integer_Type (T) then
3578         Resolve (E, T);
3579         Set_Etype (Id, Universal_Integer);
3580         Set_Ekind (Id, E_Named_Integer);
3581
3582      elsif Is_Real_Type (T) then
3583
3584         --  Because the real value is converted to universal_real, this is a
3585         --  legal context for a universal fixed expression.
3586
3587         if T = Universal_Fixed then
3588            declare
3589               Loc  : constant Source_Ptr := Sloc (N);
3590               Conv : constant Node_Id := Make_Type_Conversion (Loc,
3591                        Subtype_Mark =>
3592                          New_Occurrence_Of (Universal_Real, Loc),
3593                        Expression => Relocate_Node (E));
3594
3595            begin
3596               Rewrite (E, Conv);
3597               Analyze (E);
3598            end;
3599
3600         elsif T = Any_Fixed then
3601            Error_Msg_N ("illegal context for mixed mode operation", E);
3602
3603            --  Expression is of the form : universal_fixed * integer. Try to
3604            --  resolve as universal_real.
3605
3606            T := Universal_Real;
3607            Set_Etype (E, T);
3608         end if;
3609
3610         Resolve (E, T);
3611         Set_Etype (Id, Universal_Real);
3612         Set_Ekind (Id, E_Named_Real);
3613
3614      else
3615         Wrong_Type (E, Any_Numeric);
3616         Resolve (E, T);
3617
3618         Set_Etype               (Id, T);
3619         Set_Ekind               (Id, E_Constant);
3620         Set_Never_Set_In_Source (Id, True);
3621         Set_Is_True_Constant    (Id, True);
3622         return;
3623      end if;
3624
3625      if Nkind_In (E, N_Integer_Literal, N_Real_Literal) then
3626         Set_Etype (E, Etype (Id));
3627      end if;
3628
3629      if not Is_OK_Static_Expression (E) then
3630         Flag_Non_Static_Expr
3631           ("non-static expression used in number declaration!", E);
3632         Rewrite (E, Make_Integer_Literal (Sloc (N), 1));
3633         Set_Etype (E, Any_Type);
3634      end if;
3635
3636      Analyze_Dimension (N);
3637   end Analyze_Number_Declaration;
3638
3639   --------------------------------
3640   -- Analyze_Object_Declaration --
3641   --------------------------------
3642
3643   --  WARNING: This routine manages Ghost regions. Return statements must be
3644   --  replaced by gotos which jump to the end of the routine and restore the
3645   --  Ghost mode.
3646
3647   procedure Analyze_Object_Declaration (N : Node_Id) is
3648      Loc   : constant Source_Ptr := Sloc (N);
3649      Id    : constant Entity_Id  := Defining_Identifier (N);
3650      Act_T : Entity_Id;
3651      T     : Entity_Id;
3652
3653      E : Node_Id := Expression (N);
3654      --  E is set to Expression (N) throughout this routine. When Expression
3655      --  (N) is modified, E is changed accordingly.
3656
3657      Prev_Entity : Entity_Id := Empty;
3658
3659      procedure Check_Dynamic_Object (Typ : Entity_Id);
3660      --  A library-level object with nonstatic discriminant constraints may
3661      --  require dynamic allocation. The declaration is illegal if the
3662      --  profile includes the restriction No_Implicit_Heap_Allocations.
3663
3664      procedure Check_For_Null_Excluding_Components
3665        (Obj_Typ  : Entity_Id;
3666         Obj_Decl : Node_Id);
3667      --  Verify that each null-excluding component of object declaration
3668      --  Obj_Decl carrying type Obj_Typ has explicit initialization. Emit
3669      --  a compile-time warning if this is not the case.
3670
3671      function Count_Tasks (T : Entity_Id) return Uint;
3672      --  This function is called when a non-generic library level object of a
3673      --  task type is declared. Its function is to count the static number of
3674      --  tasks declared within the type (it is only called if Has_Task is set
3675      --  for T). As a side effect, if an array of tasks with nonstatic bounds
3676      --  or a variant record type is encountered, Check_Restriction is called
3677      --  indicating the count is unknown.
3678
3679      function Delayed_Aspect_Present return Boolean;
3680      --  If the declaration has an expression that is an aggregate, and it
3681      --  has aspects that require delayed analysis, the resolution of the
3682      --  aggregate must be deferred to the freeze point of the object. This
3683      --  special processing was created for address clauses, but it must
3684      --  also apply to Alignment. This must be done before the aspect
3685      --  specifications are analyzed because we must handle the aggregate
3686      --  before the analysis of the object declaration is complete.
3687
3688      --  Any other relevant delayed aspects on object declarations ???
3689
3690      --------------------------
3691      -- Check_Dynamic_Object --
3692      --------------------------
3693
3694      procedure Check_Dynamic_Object (Typ : Entity_Id) is
3695         Comp     : Entity_Id;
3696         Obj_Type : Entity_Id;
3697
3698      begin
3699         Obj_Type := Typ;
3700
3701         if Is_Private_Type (Obj_Type)
3702            and then Present (Full_View (Obj_Type))
3703         then
3704            Obj_Type := Full_View (Obj_Type);
3705         end if;
3706
3707         if Known_Static_Esize (Obj_Type) then
3708            return;
3709         end if;
3710
3711         if Restriction_Active (No_Implicit_Heap_Allocations)
3712           and then Expander_Active
3713           and then Has_Discriminants (Obj_Type)
3714         then
3715            Comp := First_Component (Obj_Type);
3716            while Present (Comp) loop
3717               if Known_Static_Esize (Etype (Comp))
3718                 or else Size_Known_At_Compile_Time (Etype (Comp))
3719               then
3720                  null;
3721
3722               elsif not Discriminated_Size (Comp)
3723                 and then Comes_From_Source (Comp)
3724               then
3725                  Error_Msg_NE
3726                    ("component& of non-static size will violate restriction "
3727                     & "No_Implicit_Heap_Allocation?", N, Comp);
3728
3729               elsif Is_Record_Type (Etype (Comp)) then
3730                  Check_Dynamic_Object (Etype (Comp));
3731               end if;
3732
3733               Next_Component (Comp);
3734            end loop;
3735         end if;
3736      end Check_Dynamic_Object;
3737
3738      -----------------------------------------
3739      -- Check_For_Null_Excluding_Components --
3740      -----------------------------------------
3741
3742      procedure Check_For_Null_Excluding_Components
3743        (Obj_Typ  : Entity_Id;
3744         Obj_Decl : Node_Id)
3745      is
3746         procedure Check_Component
3747           (Comp_Typ   : Entity_Id;
3748            Comp_Decl  : Node_Id := Empty;
3749            Array_Comp : Boolean := False);
3750         --  Apply a compile-time null-exclusion check on a component denoted
3751         --  by its declaration Comp_Decl and type Comp_Typ, and all of its
3752         --  subcomponents (if any).
3753
3754         ---------------------
3755         -- Check_Component --
3756         ---------------------
3757
3758         procedure Check_Component
3759           (Comp_Typ  : Entity_Id;
3760            Comp_Decl : Node_Id := Empty;
3761            Array_Comp : Boolean := False)
3762         is
3763            Comp : Entity_Id;
3764            T    : Entity_Id;
3765
3766         begin
3767            --  Do not consider internally-generated components or those that
3768            --  are already initialized.
3769
3770            if Present (Comp_Decl)
3771              and then (not Comes_From_Source (Comp_Decl)
3772                         or else Present (Expression (Comp_Decl)))
3773            then
3774               return;
3775            end if;
3776
3777            if Is_Incomplete_Or_Private_Type (Comp_Typ)
3778              and then Present (Full_View (Comp_Typ))
3779            then
3780               T := Full_View (Comp_Typ);
3781            else
3782               T := Comp_Typ;
3783            end if;
3784
3785            --  Verify a component of a null-excluding access type
3786
3787            if Is_Access_Type (T)
3788              and then Can_Never_Be_Null (T)
3789            then
3790               if Comp_Decl = Obj_Decl then
3791                  Null_Exclusion_Static_Checks
3792                    (N          => Obj_Decl,
3793                     Comp       => Empty,
3794                     Array_Comp => Array_Comp);
3795
3796               else
3797                  Null_Exclusion_Static_Checks
3798                    (N          => Obj_Decl,
3799                     Comp       => Comp_Decl,
3800                     Array_Comp => Array_Comp);
3801               end if;
3802
3803            --  Check array components
3804
3805            elsif Is_Array_Type (T) then
3806
3807               --  There is no suitable component when the object is of an
3808               --  array type. However, a namable component may appear at some
3809               --  point during the recursive inspection, but not at the top
3810               --  level. At the top level just indicate array component case.
3811
3812               if Comp_Decl = Obj_Decl then
3813                  Check_Component (Component_Type (T), Array_Comp => True);
3814               else
3815                  Check_Component (Component_Type (T), Comp_Decl);
3816               end if;
3817
3818            --  Verify all components of type T
3819
3820            --  Note: No checks are performed on types with discriminants due
3821            --  to complexities involving variants. ???
3822
3823            elsif (Is_Concurrent_Type (T)
3824                    or else Is_Incomplete_Or_Private_Type (T)
3825                    or else Is_Record_Type (T))
3826               and then not Has_Discriminants (T)
3827            then
3828               Comp := First_Component (T);
3829               while Present (Comp) loop
3830                  Check_Component (Etype (Comp), Parent (Comp));
3831
3832                  Comp := Next_Component (Comp);
3833               end loop;
3834            end if;
3835         end Check_Component;
3836
3837      --  Start processing for Check_For_Null_Excluding_Components
3838
3839      begin
3840         Check_Component (Obj_Typ, Obj_Decl);
3841      end Check_For_Null_Excluding_Components;
3842
3843      -----------------
3844      -- Count_Tasks --
3845      -----------------
3846
3847      function Count_Tasks (T : Entity_Id) return Uint is
3848         C : Entity_Id;
3849         X : Node_Id;
3850         V : Uint;
3851
3852      begin
3853         if Is_Task_Type (T) then
3854            return Uint_1;
3855
3856         elsif Is_Record_Type (T) then
3857            if Has_Discriminants (T) then
3858               Check_Restriction (Max_Tasks, N);
3859               return Uint_0;
3860
3861            else
3862               V := Uint_0;
3863               C := First_Component (T);
3864               while Present (C) loop
3865                  V := V + Count_Tasks (Etype (C));
3866                  Next_Component (C);
3867               end loop;
3868
3869               return V;
3870            end if;
3871
3872         elsif Is_Array_Type (T) then
3873            X := First_Index (T);
3874            V := Count_Tasks (Component_Type (T));
3875            while Present (X) loop
3876               C := Etype (X);
3877
3878               if not Is_OK_Static_Subtype (C) then
3879                  Check_Restriction (Max_Tasks, N);
3880                  return Uint_0;
3881               else
3882                  V := V * (UI_Max (Uint_0,
3883                                    Expr_Value (Type_High_Bound (C)) -
3884                                    Expr_Value (Type_Low_Bound (C)) + Uint_1));
3885               end if;
3886
3887               Next_Index (X);
3888            end loop;
3889
3890            return V;
3891
3892         else
3893            return Uint_0;
3894         end if;
3895      end Count_Tasks;
3896
3897      ----------------------------
3898      -- Delayed_Aspect_Present --
3899      ----------------------------
3900
3901      function Delayed_Aspect_Present return Boolean is
3902         A    : Node_Id;
3903         A_Id : Aspect_Id;
3904
3905      begin
3906         if Present (Aspect_Specifications (N)) then
3907            A    := First (Aspect_Specifications (N));
3908            A_Id := Get_Aspect_Id (Chars (Identifier (A)));
3909            while Present (A) loop
3910               if A_Id = Aspect_Alignment or else A_Id = Aspect_Address then
3911                  return True;
3912               end if;
3913
3914               Next (A);
3915            end loop;
3916         end if;
3917
3918         return False;
3919      end Delayed_Aspect_Present;
3920
3921      --  Local variables
3922
3923      Saved_GM  : constant Ghost_Mode_Type := Ghost_Mode;
3924      Saved_IGR : constant Node_Id         := Ignored_Ghost_Region;
3925      --  Save the Ghost-related attributes to restore on exit
3926
3927      Related_Id : Entity_Id;
3928
3929   --  Start of processing for Analyze_Object_Declaration
3930
3931   begin
3932      --  There are three kinds of implicit types generated by an
3933      --  object declaration:
3934
3935      --   1. Those generated by the original Object Definition
3936
3937      --   2. Those generated by the Expression
3938
3939      --   3. Those used to constrain the Object Definition with the
3940      --      expression constraints when the definition is unconstrained.
3941
3942      --  They must be generated in this order to avoid order of elaboration
3943      --  issues. Thus the first step (after entering the name) is to analyze
3944      --  the object definition.
3945
3946      if Constant_Present (N) then
3947         Prev_Entity := Current_Entity_In_Scope (Id);
3948
3949         if Present (Prev_Entity)
3950           and then
3951             --  If the homograph is an implicit subprogram, it is overridden
3952             --  by the current declaration.
3953
3954             ((Is_Overloadable (Prev_Entity)
3955                and then Is_Inherited_Operation (Prev_Entity))
3956
3957               --  The current object is a discriminal generated for an entry
3958               --  family index. Even though the index is a constant, in this
3959               --  particular context there is no true constant redeclaration.
3960               --  Enter_Name will handle the visibility.
3961
3962               or else
3963                 (Is_Discriminal (Id)
3964                   and then Ekind (Discriminal_Link (Id)) =
3965                                              E_Entry_Index_Parameter)
3966
3967               --  The current object is the renaming for a generic declared
3968               --  within the instance.
3969
3970               or else
3971                 (Ekind (Prev_Entity) = E_Package
3972                   and then Nkind (Parent (Prev_Entity)) =
3973                                               N_Package_Renaming_Declaration
3974                   and then not Comes_From_Source (Prev_Entity)
3975                   and then
3976                     Is_Generic_Instance (Renamed_Entity (Prev_Entity)))
3977
3978               --  The entity may be a homonym of a private component of the
3979               --  enclosing protected object, for which we create a local
3980               --  renaming declaration. The declaration is legal, even if
3981               --  useless when it just captures that component.
3982
3983               or else
3984                 (Ekind (Scope (Current_Scope)) = E_Protected_Type
3985                   and then Nkind (Parent (Prev_Entity)) =
3986                              N_Object_Renaming_Declaration))
3987         then
3988            Prev_Entity := Empty;
3989         end if;
3990      end if;
3991
3992      if Present (Prev_Entity) then
3993
3994         --  The object declaration is Ghost when it completes a deferred Ghost
3995         --  constant.
3996
3997         Mark_And_Set_Ghost_Completion (N, Prev_Entity);
3998
3999         Constant_Redeclaration (Id, N, T);
4000
4001         Generate_Reference (Prev_Entity, Id, 'c');
4002         Set_Completion_Referenced (Id);
4003
4004         if Error_Posted (N) then
4005
4006            --  Type mismatch or illegal redeclaration; do not analyze
4007            --  expression to avoid cascaded errors.
4008
4009            T := Find_Type_Of_Object (Object_Definition (N), N);
4010            Set_Etype (Id, T);
4011            Set_Ekind (Id, E_Variable);
4012            goto Leave;
4013         end if;
4014
4015      --  In the normal case, enter identifier at the start to catch premature
4016      --  usage in the initialization expression.
4017
4018      else
4019         Generate_Definition (Id);
4020         Enter_Name (Id);
4021
4022         Mark_Coextensions (N, Object_Definition (N));
4023
4024         T := Find_Type_Of_Object (Object_Definition (N), N);
4025
4026         if Nkind (Object_Definition (N)) = N_Access_Definition
4027           and then Present
4028                      (Access_To_Subprogram_Definition (Object_Definition (N)))
4029           and then Protected_Present
4030                      (Access_To_Subprogram_Definition (Object_Definition (N)))
4031         then
4032            T := Replace_Anonymous_Access_To_Protected_Subprogram (N);
4033         end if;
4034
4035         if Error_Posted (Id) then
4036            Set_Etype (Id, T);
4037            Set_Ekind (Id, E_Variable);
4038            goto Leave;
4039         end if;
4040      end if;
4041
4042      --  Ada 2005 (AI-231): Propagate the null-excluding attribute and carry
4043      --  out some static checks.
4044
4045      if Ada_Version >= Ada_2005 then
4046
4047         --  In case of aggregates we must also take care of the correct
4048         --  initialization of nested aggregates bug this is done at the
4049         --  point of the analysis of the aggregate (see sem_aggr.adb) ???
4050
4051         if Can_Never_Be_Null (T) then
4052            if Present (Expression (N))
4053              and then Nkind (Expression (N)) = N_Aggregate
4054            then
4055               null;
4056
4057            else
4058               declare
4059                  Save_Typ : constant Entity_Id := Etype (Id);
4060               begin
4061                  Set_Etype (Id, T); --  Temp. decoration for static checks
4062                  Null_Exclusion_Static_Checks (N);
4063                  Set_Etype (Id, Save_Typ);
4064               end;
4065            end if;
4066
4067         --  We might be dealing with an object of a composite type containing
4068         --  null-excluding components without an aggregate, so we must verify
4069         --  that such components have default initialization.
4070
4071         else
4072            Check_For_Null_Excluding_Components (T, N);
4073         end if;
4074      end if;
4075
4076      --  Object is marked pure if it is in a pure scope
4077
4078      Set_Is_Pure (Id, Is_Pure (Current_Scope));
4079
4080      --  If deferred constant, make sure context is appropriate. We detect
4081      --  a deferred constant as a constant declaration with no expression.
4082      --  A deferred constant can appear in a package body if its completion
4083      --  is by means of an interface pragma.
4084
4085      if Constant_Present (N) and then No (E) then
4086
4087         --  A deferred constant may appear in the declarative part of the
4088         --  following constructs:
4089
4090         --     blocks
4091         --     entry bodies
4092         --     extended return statements
4093         --     package specs
4094         --     package bodies
4095         --     subprogram bodies
4096         --     task bodies
4097
4098         --  When declared inside a package spec, a deferred constant must be
4099         --  completed by a full constant declaration or pragma Import. In all
4100         --  other cases, the only proper completion is pragma Import. Extended
4101         --  return statements are flagged as invalid contexts because they do
4102         --  not have a declarative part and so cannot accommodate the pragma.
4103
4104         if Ekind (Current_Scope) = E_Return_Statement then
4105            Error_Msg_N
4106              ("invalid context for deferred constant declaration (RM 7.4)",
4107               N);
4108            Error_Msg_N
4109              ("\declaration requires an initialization expression",
4110                N);
4111            Set_Constant_Present (N, False);
4112
4113         --  In Ada 83, deferred constant must be of private type
4114
4115         elsif not Is_Private_Type (T) then
4116            if Ada_Version = Ada_83 and then Comes_From_Source (N) then
4117               Error_Msg_N
4118                 ("(Ada 83) deferred constant must be private type", N);
4119            end if;
4120         end if;
4121
4122      --  If not a deferred constant, then the object declaration freezes
4123      --  its type, unless the object is of an anonymous type and has delayed
4124      --  aspects. In that case the type is frozen when the object itself is.
4125
4126      else
4127         Check_Fully_Declared (T, N);
4128
4129         if Has_Delayed_Aspects (Id)
4130           and then Is_Array_Type (T)
4131           and then Is_Itype (T)
4132         then
4133            Set_Has_Delayed_Freeze (T);
4134         else
4135            Freeze_Before (N, T);
4136         end if;
4137      end if;
4138
4139      --  If the object was created by a constrained array definition, then
4140      --  set the link in both the anonymous base type and anonymous subtype
4141      --  that are built to represent the array type to point to the object.
4142
4143      if Nkind (Object_Definition (Declaration_Node (Id))) =
4144                        N_Constrained_Array_Definition
4145      then
4146         Set_Related_Array_Object (T, Id);
4147         Set_Related_Array_Object (Base_Type (T), Id);
4148      end if;
4149
4150      --  Special checks for protected objects not at library level
4151
4152      if Has_Protected (T) and then not Is_Library_Level_Entity (Id) then
4153         Check_Restriction (No_Local_Protected_Objects, Id);
4154
4155         --  Protected objects with interrupt handlers must be at library level
4156
4157         --  Ada 2005: This test is not needed (and the corresponding clause
4158         --  in the RM is removed) because accessibility checks are sufficient
4159         --  to make handlers not at the library level illegal.
4160
4161         --  AI05-0303: The AI is in fact a binding interpretation, and thus
4162         --  applies to the '95 version of the language as well.
4163
4164         if Is_Protected_Type (T)
4165           and then Has_Interrupt_Handler (T)
4166           and then Ada_Version < Ada_95
4167         then
4168            Error_Msg_N
4169              ("interrupt object can only be declared at library level", Id);
4170         end if;
4171      end if;
4172
4173      --  Check for violation of No_Local_Timing_Events
4174
4175      if Has_Timing_Event (T) and then not Is_Library_Level_Entity (Id) then
4176         Check_Restriction (No_Local_Timing_Events, Id);
4177      end if;
4178
4179      --  The actual subtype of the object is the nominal subtype, unless
4180      --  the nominal one is unconstrained and obtained from the expression.
4181
4182      Act_T := T;
4183
4184      --  These checks should be performed before the initialization expression
4185      --  is considered, so that the Object_Definition node is still the same
4186      --  as in source code.
4187
4188      --  In SPARK, the nominal subtype is always given by a subtype mark
4189      --  and must not be unconstrained. (The only exception to this is the
4190      --  acceptance of declarations of constants of type String.)
4191
4192      if not Nkind_In (Object_Definition (N), N_Expanded_Name, N_Identifier)
4193      then
4194         Check_SPARK_05_Restriction
4195           ("subtype mark required", Object_Definition (N));
4196
4197      elsif Is_Array_Type (T)
4198        and then not Is_Constrained (T)
4199        and then T /= Standard_String
4200      then
4201         Check_SPARK_05_Restriction
4202           ("subtype mark of constrained type expected",
4203            Object_Definition (N));
4204      end if;
4205
4206      if Is_Library_Level_Entity (Id) then
4207         Check_Dynamic_Object (T);
4208      end if;
4209
4210      --  There are no aliased objects in SPARK
4211
4212      if Aliased_Present (N) then
4213         Check_SPARK_05_Restriction ("aliased object is not allowed", N);
4214      end if;
4215
4216      --  Process initialization expression if present and not in error
4217
4218      if Present (E) and then E /= Error then
4219
4220         --  Generate an error in case of CPP class-wide object initialization.
4221         --  Required because otherwise the expansion of the class-wide
4222         --  assignment would try to use 'size to initialize the object
4223         --  (primitive that is not available in CPP tagged types).
4224
4225         if Is_Class_Wide_Type (Act_T)
4226           and then
4227             (Is_CPP_Class (Root_Type (Etype (Act_T)))
4228               or else
4229                 (Present (Full_View (Root_Type (Etype (Act_T))))
4230                   and then
4231                     Is_CPP_Class (Full_View (Root_Type (Etype (Act_T))))))
4232         then
4233            Error_Msg_N
4234              ("predefined assignment not available for 'C'P'P tagged types",
4235               E);
4236         end if;
4237
4238         Mark_Coextensions (N, E);
4239         Analyze (E);
4240
4241         --  In case of errors detected in the analysis of the expression,
4242         --  decorate it with the expected type to avoid cascaded errors
4243
4244         if No (Etype (E)) then
4245            Set_Etype (E, T);
4246         end if;
4247
4248         --  If an initialization expression is present, then we set the
4249         --  Is_True_Constant flag. It will be reset if this is a variable
4250         --  and it is indeed modified.
4251
4252         Set_Is_True_Constant (Id, True);
4253
4254         --  If we are analyzing a constant declaration, set its completion
4255         --  flag after analyzing and resolving the expression.
4256
4257         if Constant_Present (N) then
4258            Set_Has_Completion (Id);
4259         end if;
4260
4261         --  Set type and resolve (type may be overridden later on). Note:
4262         --  Ekind (Id) must still be E_Void at this point so that incorrect
4263         --  early usage within E is properly diagnosed.
4264
4265         Set_Etype (Id, T);
4266
4267         --  If the expression is an aggregate we must look ahead to detect
4268         --  the possible presence of an address clause, and defer resolution
4269         --  and expansion of the aggregate to the freeze point of the entity.
4270
4271         --  This is not always legal because the aggregate may contain other
4272         --  references that need freezing, e.g. references to other entities
4273         --  with address clauses. In any case, when compiling with -gnatI the
4274         --  presence of the address clause must be ignored.
4275
4276         if Comes_From_Source (N)
4277           and then Expander_Active
4278           and then Nkind (E) = N_Aggregate
4279           and then
4280             ((Present (Following_Address_Clause (N))
4281                 and then not Ignore_Rep_Clauses)
4282              or else Delayed_Aspect_Present)
4283         then
4284            Set_Etype (E, T);
4285
4286            --  If the aggregate is limited it will be built in place, and its
4287            --  expansion is deferred until the object declaration is expanded.
4288
4289            if Is_Limited_Type (T) then
4290               Set_Expansion_Delayed (E);
4291            end if;
4292
4293         else
4294            --  If the expression is a formal that is a "subprogram pointer"
4295            --  this is illegal in accessibility terms (see RM 3.10.2 (13.1/2)
4296            --  and AARM 3.10.2 (13.b/2)). Add an explicit conversion to force
4297            --  the corresponding check, as is done for assignments.
4298
4299            if Is_Entity_Name (E)
4300              and then Present (Entity (E))
4301              and then Is_Formal (Entity (E))
4302              and then
4303                Ekind (Etype (Entity (E))) = E_Anonymous_Access_Subprogram_Type
4304              and then Ekind (T) /= E_Anonymous_Access_Subprogram_Type
4305            then
4306               Rewrite (E, Convert_To (T, Relocate_Node (E)));
4307            end if;
4308
4309            Resolve (E, T);
4310         end if;
4311
4312         --  No further action needed if E is a call to an inlined function
4313         --  which returns an unconstrained type and it has been expanded into
4314         --  a procedure call. In that case N has been replaced by an object
4315         --  declaration without initializing expression and it has been
4316         --  analyzed (see Expand_Inlined_Call).
4317
4318         if Back_End_Inlining
4319           and then Expander_Active
4320           and then Nkind (E) = N_Function_Call
4321           and then Nkind (Name (E)) in N_Has_Entity
4322           and then Is_Inlined (Entity (Name (E)))
4323           and then not Is_Constrained (Etype (E))
4324           and then Analyzed (N)
4325           and then No (Expression (N))
4326         then
4327            goto Leave;
4328         end if;
4329
4330         --  If E is null and has been replaced by an N_Raise_Constraint_Error
4331         --  node (which was marked already-analyzed), we need to set the type
4332         --  to something other than Any_Access in order to keep gigi happy.
4333
4334         if Etype (E) = Any_Access then
4335            Set_Etype (E, T);
4336         end if;
4337
4338         --  If the object is an access to variable, the initialization
4339         --  expression cannot be an access to constant.
4340
4341         if Is_Access_Type (T)
4342           and then not Is_Access_Constant (T)
4343           and then Is_Access_Type (Etype (E))
4344           and then Is_Access_Constant (Etype (E))
4345         then
4346            Error_Msg_N
4347              ("access to variable cannot be initialized with an "
4348               & "access-to-constant expression", E);
4349         end if;
4350
4351         if not Assignment_OK (N) then
4352            Check_Initialization (T, E);
4353         end if;
4354
4355         Check_Unset_Reference (E);
4356
4357         --  If this is a variable, then set current value. If this is a
4358         --  declared constant of a scalar type with a static expression,
4359         --  indicate that it is always valid.
4360
4361         if not Constant_Present (N) then
4362            if Compile_Time_Known_Value (E) then
4363               Set_Current_Value (Id, E);
4364            end if;
4365
4366         elsif Is_Scalar_Type (T) and then Is_OK_Static_Expression (E) then
4367            Set_Is_Known_Valid (Id);
4368
4369         --  If it is a constant initialized with a valid nonstatic entity,
4370         --  the constant is known valid as well, and can inherit the subtype
4371         --  of the entity if it is a subtype of the given type. This info
4372         --  is preserved on the actual subtype of the constant.
4373
4374         elsif Is_Scalar_Type (T)
4375           and then Is_Entity_Name (E)
4376           and then Is_Known_Valid (Entity (E))
4377           and then In_Subrange_Of (Etype (Entity (E)), T)
4378         then
4379            Set_Is_Known_Valid (Id);
4380            Set_Ekind (Id, E_Constant);
4381            Set_Actual_Subtype (Id, Etype (Entity (E)));
4382         end if;
4383
4384         --  Deal with setting of null flags
4385
4386         if Is_Access_Type (T) then
4387            if Known_Non_Null (E) then
4388               Set_Is_Known_Non_Null (Id, True);
4389            elsif Known_Null (E) and then not Can_Never_Be_Null (Id) then
4390               Set_Is_Known_Null (Id, True);
4391            end if;
4392         end if;
4393
4394         --  Check incorrect use of dynamically tagged expressions
4395
4396         if Is_Tagged_Type (T) then
4397            Check_Dynamically_Tagged_Expression
4398              (Expr        => E,
4399               Typ         => T,
4400               Related_Nod => N);
4401         end if;
4402
4403         Apply_Scalar_Range_Check (E, T);
4404         Apply_Static_Length_Check (E, T);
4405
4406         if Nkind (Original_Node (N)) = N_Object_Declaration
4407           and then Comes_From_Source (Original_Node (N))
4408
4409           --  Only call test if needed
4410
4411           and then Restriction_Check_Required (SPARK_05)
4412           and then not Is_SPARK_05_Initialization_Expr (Original_Node (E))
4413         then
4414            Check_SPARK_05_Restriction
4415              ("initialization expression is not appropriate", E);
4416         end if;
4417
4418         --  A formal parameter of a specific tagged type whose related
4419         --  subprogram is subject to pragma Extensions_Visible with value
4420         --  "False" cannot be implicitly converted to a class-wide type by
4421         --  means of an initialization expression (SPARK RM 6.1.7(3)). Do
4422         --  not consider internally generated expressions.
4423
4424         if Is_Class_Wide_Type (T)
4425           and then Comes_From_Source (E)
4426           and then Is_EVF_Expression (E)
4427         then
4428            Error_Msg_N
4429              ("formal parameter cannot be implicitly converted to "
4430               & "class-wide type when Extensions_Visible is False", E);
4431         end if;
4432      end if;
4433
4434      --  If the No_Streams restriction is set, check that the type of the
4435      --  object is not, and does not contain, any subtype derived from
4436      --  Ada.Streams.Root_Stream_Type. Note that we guard the call to
4437      --  Has_Stream just for efficiency reasons. There is no point in
4438      --  spending time on a Has_Stream check if the restriction is not set.
4439
4440      if Restriction_Check_Required (No_Streams) then
4441         if Has_Stream (T) then
4442            Check_Restriction (No_Streams, N);
4443         end if;
4444      end if;
4445
4446      --  Deal with predicate check before we start to do major rewriting. It
4447      --  is OK to initialize and then check the initialized value, since the
4448      --  object goes out of scope if we get a predicate failure. Note that we
4449      --  do this in the analyzer and not the expander because the analyzer
4450      --  does some substantial rewriting in some cases.
4451
4452      --  We need a predicate check if the type has predicates that are not
4453      --  ignored, and if either there is an initializing expression, or for
4454      --  default initialization when we have at least one case of an explicit
4455      --  default initial value and then this is not an internal declaration
4456      --  whose initialization comes later (as for an aggregate expansion).
4457      --  If expression is an aggregate it may be expanded into assignments
4458      --  and the declaration itself is marked with No_Initialization, but
4459      --  the predicate still applies.
4460
4461      if not Suppress_Assignment_Checks (N)
4462        and then Present (Predicate_Function (T))
4463        and then not Predicates_Ignored (T)
4464        and then
4465          (not No_Initialization (N)
4466            or else (Present (E) and then Nkind (E) = N_Aggregate))
4467        and then
4468          (Present (E)
4469            or else
4470              Is_Partially_Initialized_Type (T, Include_Implicit => False))
4471      then
4472         --  If the type has a static predicate and the expression is known at
4473         --  compile time, see if the expression satisfies the predicate.
4474
4475         if Present (E) then
4476            Check_Expression_Against_Static_Predicate (E, T);
4477         end if;
4478
4479         --  If the type is a null record and there is no explicit initial
4480         --  expression, no predicate check applies.
4481
4482         if No (E) and then Is_Null_Record_Type (T) then
4483            null;
4484
4485         --  Do not generate a predicate check if the initialization expression
4486         --  is a type conversion because the conversion has been subjected to
4487         --  the same check. This is a small optimization which avoid redundant
4488         --  checks.
4489
4490         elsif Present (E) and then Nkind (E) = N_Type_Conversion then
4491            null;
4492
4493         else
4494            Insert_After (N,
4495              Make_Predicate_Check (T, New_Occurrence_Of (Id, Loc)));
4496         end if;
4497      end if;
4498
4499      --  Case of unconstrained type
4500
4501      if not Is_Definite_Subtype (T) then
4502
4503         --  In SPARK, a declaration of unconstrained type is allowed
4504         --  only for constants of type string.
4505
4506         if Is_String_Type (T) and then not Constant_Present (N) then
4507            Check_SPARK_05_Restriction
4508              ("declaration of object of unconstrained type not allowed", N);
4509         end if;
4510
4511         --  Nothing to do in deferred constant case
4512
4513         if Constant_Present (N) and then No (E) then
4514            null;
4515
4516         --  Case of no initialization present
4517
4518         elsif No (E) then
4519            if No_Initialization (N) then
4520               null;
4521
4522            elsif Is_Class_Wide_Type (T) then
4523               Error_Msg_N
4524                 ("initialization required in class-wide declaration ", N);
4525
4526            else
4527               Error_Msg_N
4528                 ("unconstrained subtype not allowed (need initialization)",
4529                  Object_Definition (N));
4530
4531               if Is_Record_Type (T) and then Has_Discriminants (T) then
4532                  Error_Msg_N
4533                    ("\provide initial value or explicit discriminant values",
4534                     Object_Definition (N));
4535
4536                  Error_Msg_NE
4537                    ("\or give default discriminant values for type&",
4538                     Object_Definition (N), T);
4539
4540               elsif Is_Array_Type (T) then
4541                  Error_Msg_N
4542                    ("\provide initial value or explicit array bounds",
4543                     Object_Definition (N));
4544               end if;
4545            end if;
4546
4547         --  Case of initialization present but in error. Set initial
4548         --  expression as absent (but do not make above complaints)
4549
4550         elsif E = Error then
4551            Set_Expression (N, Empty);
4552            E := Empty;
4553
4554         --  Case of initialization present
4555
4556         else
4557            --  Check restrictions in Ada 83
4558
4559            if not Constant_Present (N) then
4560
4561               --  Unconstrained variables not allowed in Ada 83 mode
4562
4563               if Ada_Version = Ada_83
4564                 and then Comes_From_Source (Object_Definition (N))
4565               then
4566                  Error_Msg_N
4567                    ("(Ada 83) unconstrained variable not allowed",
4568                     Object_Definition (N));
4569               end if;
4570            end if;
4571
4572            --  Now we constrain the variable from the initializing expression
4573
4574            --  If the expression is an aggregate, it has been expanded into
4575            --  individual assignments. Retrieve the actual type from the
4576            --  expanded construct.
4577
4578            if Is_Array_Type (T)
4579              and then No_Initialization (N)
4580              and then Nkind (Original_Node (E)) = N_Aggregate
4581            then
4582               Act_T := Etype (E);
4583
4584            --  In case of class-wide interface object declarations we delay
4585            --  the generation of the equivalent record type declarations until
4586            --  its expansion because there are cases in they are not required.
4587
4588            elsif Is_Interface (T) then
4589               null;
4590
4591            --  In GNATprove mode, Expand_Subtype_From_Expr does nothing. Thus,
4592            --  we should prevent the generation of another Itype with the
4593            --  same name as the one already generated, or we end up with
4594            --  two identical types in GNATprove.
4595
4596            elsif GNATprove_Mode then
4597               null;
4598
4599            --  If the type is an unchecked union, no subtype can be built from
4600            --  the expression. Rewrite declaration as a renaming, which the
4601            --  back-end can handle properly. This is a rather unusual case,
4602            --  because most unchecked_union declarations have default values
4603            --  for discriminants and are thus not indefinite.
4604
4605            elsif Is_Unchecked_Union (T) then
4606               if Constant_Present (N) or else Nkind (E) = N_Function_Call then
4607                  Set_Ekind (Id, E_Constant);
4608               else
4609                  Set_Ekind (Id, E_Variable);
4610               end if;
4611
4612               Rewrite (N,
4613                 Make_Object_Renaming_Declaration (Loc,
4614                   Defining_Identifier => Id,
4615                   Subtype_Mark        => New_Occurrence_Of (T, Loc),
4616                   Name                => E));
4617
4618               Set_Renamed_Object (Id, E);
4619               Freeze_Before (N, T);
4620               Set_Is_Frozen (Id);
4621               goto Leave;
4622
4623            else
4624               --  Ensure that the generated subtype has a unique external name
4625               --  when the related object is public. This guarantees that the
4626               --  subtype and its bounds will not be affected by switches or
4627               --  pragmas that may offset the internal counter due to extra
4628               --  generated code.
4629
4630               if Is_Public (Id) then
4631                  Related_Id := Id;
4632               else
4633                  Related_Id := Empty;
4634               end if;
4635
4636               Expand_Subtype_From_Expr
4637                 (N             => N,
4638                  Unc_Type      => T,
4639                  Subtype_Indic => Object_Definition (N),
4640                  Exp           => E,
4641                  Related_Id    => Related_Id);
4642
4643               Act_T := Find_Type_Of_Object (Object_Definition (N), N);
4644            end if;
4645
4646            Set_Is_Constr_Subt_For_U_Nominal (Act_T);
4647
4648            if Aliased_Present (N) then
4649               Set_Is_Constr_Subt_For_UN_Aliased (Act_T);
4650            end if;
4651
4652            Freeze_Before (N, Act_T);
4653            Freeze_Before (N, T);
4654         end if;
4655
4656      elsif Is_Array_Type (T)
4657        and then No_Initialization (N)
4658        and then (Nkind (Original_Node (E)) = N_Aggregate
4659                   or else (Nkind (Original_Node (E)) = N_Qualified_Expression
4660                             and then Nkind (Original_Node (Expression
4661                                        (Original_Node (E)))) = N_Aggregate))
4662      then
4663         if not Is_Entity_Name (Object_Definition (N)) then
4664            Act_T := Etype (E);
4665            Check_Compile_Time_Size (Act_T);
4666
4667            if Aliased_Present (N) then
4668               Set_Is_Constr_Subt_For_UN_Aliased (Act_T);
4669            end if;
4670         end if;
4671
4672         --  When the given object definition and the aggregate are specified
4673         --  independently, and their lengths might differ do a length check.
4674         --  This cannot happen if the aggregate is of the form (others =>...)
4675
4676         if not Is_Constrained (T) then
4677            null;
4678
4679         elsif Nkind (E) = N_Raise_Constraint_Error then
4680
4681            --  Aggregate is statically illegal. Place back in declaration
4682
4683            Set_Expression (N, E);
4684            Set_No_Initialization (N, False);
4685
4686         elsif T = Etype (E) then
4687            null;
4688
4689         elsif Nkind (E) = N_Aggregate
4690           and then Present (Component_Associations (E))
4691           and then Present (Choice_List (First (Component_Associations (E))))
4692           and then
4693             Nkind (First (Choice_List (First (Component_Associations (E))))) =
4694               N_Others_Choice
4695         then
4696            null;
4697
4698         else
4699            Apply_Length_Check (E, T);
4700         end if;
4701
4702      --  If the type is limited unconstrained with defaulted discriminants and
4703      --  there is no expression, then the object is constrained by the
4704      --  defaults, so it is worthwhile building the corresponding subtype.
4705
4706      elsif (Is_Limited_Record (T) or else Is_Concurrent_Type (T))
4707        and then not Is_Constrained (T)
4708        and then Has_Discriminants (T)
4709      then
4710         if No (E) then
4711            Act_T := Build_Default_Subtype (T, N);
4712         else
4713            --  Ada 2005: A limited object may be initialized by means of an
4714            --  aggregate. If the type has default discriminants it has an
4715            --  unconstrained nominal type, Its actual subtype will be obtained
4716            --  from the aggregate, and not from the default discriminants.
4717
4718            Act_T := Etype (E);
4719         end if;
4720
4721         Rewrite (Object_Definition (N), New_Occurrence_Of (Act_T, Loc));
4722
4723      elsif Nkind (E) = N_Function_Call
4724        and then Constant_Present (N)
4725        and then Has_Unconstrained_Elements (Etype (E))
4726      then
4727         --  The back-end has problems with constants of a discriminated type
4728         --  with defaults, if the initial value is a function call. We
4729         --  generate an intermediate temporary that will receive a reference
4730         --  to the result of the call. The initialization expression then
4731         --  becomes a dereference of that temporary.
4732
4733         Remove_Side_Effects (E);
4734
4735      --  If this is a constant declaration of an unconstrained type and
4736      --  the initialization is an aggregate, we can use the subtype of the
4737      --  aggregate for the declared entity because it is immutable.
4738
4739      elsif not Is_Constrained (T)
4740        and then Has_Discriminants (T)
4741        and then Constant_Present (N)
4742        and then not Has_Unchecked_Union (T)
4743        and then Nkind (E) = N_Aggregate
4744      then
4745         Act_T := Etype (E);
4746      end if;
4747
4748      --  Check No_Wide_Characters restriction
4749
4750      Check_Wide_Character_Restriction (T, Object_Definition (N));
4751
4752      --  Indicate this is not set in source. Certainly true for constants, and
4753      --  true for variables so far (will be reset for a variable if and when
4754      --  we encounter a modification in the source).
4755
4756      Set_Never_Set_In_Source (Id);
4757
4758      --  Now establish the proper kind and type of the object
4759
4760      if Constant_Present (N) then
4761         Set_Ekind            (Id, E_Constant);
4762         Set_Is_True_Constant (Id);
4763
4764      else
4765         Set_Ekind (Id, E_Variable);
4766
4767         --  A variable is set as shared passive if it appears in a shared
4768         --  passive package, and is at the outer level. This is not done for
4769         --  entities generated during expansion, because those are always
4770         --  manipulated locally.
4771
4772         if Is_Shared_Passive (Current_Scope)
4773           and then Is_Library_Level_Entity (Id)
4774           and then Comes_From_Source (Id)
4775         then
4776            Set_Is_Shared_Passive (Id);
4777            Check_Shared_Var (Id, T, N);
4778         end if;
4779
4780         --  Set Has_Initial_Value if initializing expression present. Note
4781         --  that if there is no initializing expression, we leave the state
4782         --  of this flag unchanged (usually it will be False, but notably in
4783         --  the case of exception choice variables, it will already be true).
4784
4785         if Present (E) then
4786            Set_Has_Initial_Value (Id);
4787         end if;
4788      end if;
4789
4790      --  Set the SPARK mode from the current context (may be overwritten later
4791      --  with explicit pragma).
4792
4793      Set_SPARK_Pragma           (Id, SPARK_Mode_Pragma);
4794      Set_SPARK_Pragma_Inherited (Id);
4795
4796      --  Preserve relevant elaboration-related attributes of the context which
4797      --  are no longer available or very expensive to recompute once analysis,
4798      --  resolution, and expansion are over.
4799
4800      Mark_Elaboration_Attributes
4801        (N_Id     => Id,
4802         Checks   => True,
4803         Warnings => True);
4804
4805      --  Initialize alignment and size and capture alignment setting
4806
4807      Init_Alignment               (Id);
4808      Init_Esize                   (Id);
4809      Set_Optimize_Alignment_Flags (Id);
4810
4811      --  Deal with aliased case
4812
4813      if Aliased_Present (N) then
4814         Set_Is_Aliased (Id);
4815
4816         --  If the object is aliased and the type is unconstrained with
4817         --  defaulted discriminants and there is no expression, then the
4818         --  object is constrained by the defaults, so it is worthwhile
4819         --  building the corresponding subtype.
4820
4821         --  Ada 2005 (AI-363): If the aliased object is discriminated and
4822         --  unconstrained, then only establish an actual subtype if the
4823         --  nominal subtype is indefinite. In definite cases the object is
4824         --  unconstrained in Ada 2005.
4825
4826         if No (E)
4827           and then Is_Record_Type (T)
4828           and then not Is_Constrained (T)
4829           and then Has_Discriminants (T)
4830           and then (Ada_Version < Ada_2005
4831                      or else not Is_Definite_Subtype (T))
4832         then
4833            Set_Actual_Subtype (Id, Build_Default_Subtype (T, N));
4834         end if;
4835      end if;
4836
4837      --  Now we can set the type of the object
4838
4839      Set_Etype (Id, Act_T);
4840
4841      --  Non-constant object is marked to be treated as volatile if type is
4842      --  volatile and we clear the Current_Value setting that may have been
4843      --  set above. Doing so for constants isn't required and might interfere
4844      --  with possible uses of the object as a static expression in contexts
4845      --  incompatible with volatility (e.g. as a case-statement alternative).
4846
4847      if Ekind (Id) /= E_Constant and then Treat_As_Volatile (Etype (Id)) then
4848         Set_Treat_As_Volatile (Id);
4849         Set_Current_Value (Id, Empty);
4850      end if;
4851
4852      --  Deal with controlled types
4853
4854      if Has_Controlled_Component (Etype (Id))
4855        or else Is_Controlled (Etype (Id))
4856      then
4857         if not Is_Library_Level_Entity (Id) then
4858            Check_Restriction (No_Nested_Finalization, N);
4859         else
4860            Validate_Controlled_Object (Id);
4861         end if;
4862      end if;
4863
4864      if Has_Task (Etype (Id)) then
4865         Check_Restriction (No_Tasking, N);
4866
4867         --  Deal with counting max tasks
4868
4869         --  Nothing to do if inside a generic
4870
4871         if Inside_A_Generic then
4872            null;
4873
4874         --  If library level entity, then count tasks
4875
4876         elsif Is_Library_Level_Entity (Id) then
4877            Check_Restriction (Max_Tasks, N, Count_Tasks (Etype (Id)));
4878
4879         --  If not library level entity, then indicate we don't know max
4880         --  tasks and also check task hierarchy restriction and blocking
4881         --  operation (since starting a task is definitely blocking).
4882
4883         else
4884            Check_Restriction (Max_Tasks, N);
4885            Check_Restriction (No_Task_Hierarchy, N);
4886            Check_Potentially_Blocking_Operation (N);
4887         end if;
4888
4889         --  A rather specialized test. If we see two tasks being declared
4890         --  of the same type in the same object declaration, and the task
4891         --  has an entry with an address clause, we know that program error
4892         --  will be raised at run time since we can't have two tasks with
4893         --  entries at the same address.
4894
4895         if Is_Task_Type (Etype (Id)) and then More_Ids (N) then
4896            declare
4897               E : Entity_Id;
4898
4899            begin
4900               E := First_Entity (Etype (Id));
4901               while Present (E) loop
4902                  if Ekind (E) = E_Entry
4903                    and then Present (Get_Attribute_Definition_Clause
4904                                        (E, Attribute_Address))
4905                  then
4906                     Error_Msg_Warn := SPARK_Mode /= On;
4907                     Error_Msg_N
4908                       ("more than one task with same entry address<<", N);
4909                     Error_Msg_N ("\Program_Error [<<", N);
4910                     Insert_Action (N,
4911                       Make_Raise_Program_Error (Loc,
4912                         Reason => PE_Duplicated_Entry_Address));
4913                     exit;
4914                  end if;
4915
4916                  Next_Entity (E);
4917               end loop;
4918            end;
4919         end if;
4920      end if;
4921
4922      --  Some simple constant-propagation: if the expression is a constant
4923      --  string initialized with a literal, share the literal. This avoids
4924      --  a run-time copy.
4925
4926      if Present (E)
4927        and then Is_Entity_Name (E)
4928        and then Ekind (Entity (E)) = E_Constant
4929        and then Base_Type (Etype (E)) = Standard_String
4930      then
4931         declare
4932            Val : constant Node_Id := Constant_Value (Entity (E));
4933         begin
4934            if Present (Val) and then Nkind (Val) = N_String_Literal then
4935               Rewrite (E, New_Copy (Val));
4936            end if;
4937         end;
4938      end if;
4939
4940      --  Another optimization: if the nominal subtype is unconstrained and
4941      --  the expression is a function call that returns an unconstrained
4942      --  type, rewrite the declaration as a renaming of the result of the
4943      --  call. The exceptions below are cases where the copy is expected,
4944      --  either by the back end (Aliased case) or by the semantics, as for
4945      --  initializing controlled types or copying tags for class-wide types.
4946
4947      if Present (E)
4948        and then Nkind (E) = N_Explicit_Dereference
4949        and then Nkind (Original_Node (E)) = N_Function_Call
4950        and then not Is_Library_Level_Entity (Id)
4951        and then not Is_Constrained (Underlying_Type (T))
4952        and then not Is_Aliased (Id)
4953        and then not Is_Class_Wide_Type (T)
4954        and then not Is_Controlled (T)
4955        and then not Has_Controlled_Component (Base_Type (T))
4956        and then Expander_Active
4957      then
4958         Rewrite (N,
4959           Make_Object_Renaming_Declaration (Loc,
4960             Defining_Identifier => Id,
4961             Access_Definition   => Empty,
4962             Subtype_Mark        => New_Occurrence_Of
4963                                      (Base_Type (Etype (Id)), Loc),
4964             Name                => E));
4965
4966         Set_Renamed_Object (Id, E);
4967
4968         --  Force generation of debugging information for the constant and for
4969         --  the renamed function call.
4970
4971         Set_Debug_Info_Needed (Id);
4972         Set_Debug_Info_Needed (Entity (Prefix (E)));
4973      end if;
4974
4975      if Present (Prev_Entity)
4976        and then Is_Frozen (Prev_Entity)
4977        and then not Error_Posted (Id)
4978      then
4979         Error_Msg_N ("full constant declaration appears too late", N);
4980      end if;
4981
4982      Check_Eliminated (Id);
4983
4984      --  Deal with setting In_Private_Part flag if in private part
4985
4986      if Ekind (Scope (Id)) = E_Package
4987        and then In_Private_Part (Scope (Id))
4988      then
4989         Set_In_Private_Part (Id);
4990      end if;
4991
4992   <<Leave>>
4993      --  Initialize the refined state of a variable here because this is a
4994      --  common destination for legal and illegal object declarations.
4995
4996      if Ekind (Id) = E_Variable then
4997         Set_Encapsulating_State (Id, Empty);
4998      end if;
4999
5000      if Has_Aspects (N) then
5001         Analyze_Aspect_Specifications (N, Id);
5002      end if;
5003
5004      Analyze_Dimension (N);
5005
5006      --  Verify whether the object declaration introduces an illegal hidden
5007      --  state within a package subject to a null abstract state.
5008
5009      if Ekind (Id) = E_Variable then
5010         Check_No_Hidden_State (Id);
5011      end if;
5012
5013      Restore_Ghost_Region (Saved_GM, Saved_IGR);
5014   end Analyze_Object_Declaration;
5015
5016   ---------------------------
5017   -- Analyze_Others_Choice --
5018   ---------------------------
5019
5020   --  Nothing to do for the others choice node itself, the semantic analysis
5021   --  of the others choice will occur as part of the processing of the parent
5022
5023   procedure Analyze_Others_Choice (N : Node_Id) is
5024      pragma Warnings (Off, N);
5025   begin
5026      null;
5027   end Analyze_Others_Choice;
5028
5029   -------------------------------------------
5030   -- Analyze_Private_Extension_Declaration --
5031   -------------------------------------------
5032
5033   procedure Analyze_Private_Extension_Declaration (N : Node_Id) is
5034      Indic       : constant Node_Id   := Subtype_Indication (N);
5035      T           : constant Entity_Id := Defining_Identifier (N);
5036      Iface       : Entity_Id;
5037      Iface_Elmt  : Elmt_Id;
5038      Parent_Base : Entity_Id;
5039      Parent_Type : Entity_Id;
5040
5041   begin
5042      --  Ada 2005 (AI-251): Decorate all names in list of ancestor interfaces
5043
5044      if Is_Non_Empty_List (Interface_List (N)) then
5045         declare
5046            Intf : Node_Id;
5047            T    : Entity_Id;
5048
5049         begin
5050            Intf := First (Interface_List (N));
5051            while Present (Intf) loop
5052               T := Find_Type_Of_Subtype_Indic (Intf);
5053
5054               Diagnose_Interface (Intf, T);
5055               Next (Intf);
5056            end loop;
5057         end;
5058      end if;
5059
5060      Generate_Definition (T);
5061
5062      --  For other than Ada 2012, just enter the name in the current scope
5063
5064      if Ada_Version < Ada_2012 then
5065         Enter_Name (T);
5066
5067      --  Ada 2012 (AI05-0162): Enter the name in the current scope handling
5068      --  case of private type that completes an incomplete type.
5069
5070      else
5071         declare
5072            Prev : Entity_Id;
5073
5074         begin
5075            Prev := Find_Type_Name (N);
5076
5077            pragma Assert (Prev = T
5078              or else (Ekind (Prev) = E_Incomplete_Type
5079                        and then Present (Full_View (Prev))
5080                        and then Full_View (Prev) = T));
5081         end;
5082      end if;
5083
5084      Parent_Type := Find_Type_Of_Subtype_Indic (Indic);
5085      Parent_Base := Base_Type (Parent_Type);
5086
5087      if Parent_Type = Any_Type or else Etype (Parent_Type) = Any_Type then
5088         Set_Ekind (T, Ekind (Parent_Type));
5089         Set_Etype (T, Any_Type);
5090         goto Leave;
5091
5092      elsif not Is_Tagged_Type (Parent_Type) then
5093         Error_Msg_N
5094           ("parent of type extension must be a tagged type ", Indic);
5095         goto Leave;
5096
5097      elsif Ekind_In (Parent_Type, E_Void, E_Incomplete_Type) then
5098         Error_Msg_N ("premature derivation of incomplete type", Indic);
5099         goto Leave;
5100
5101      elsif Is_Concurrent_Type (Parent_Type) then
5102         Error_Msg_N
5103           ("parent type of a private extension cannot be a synchronized "
5104            & "tagged type (RM 3.9.1 (3/1))", N);
5105
5106         Set_Etype              (T, Any_Type);
5107         Set_Ekind              (T, E_Limited_Private_Type);
5108         Set_Private_Dependents (T, New_Elmt_List);
5109         Set_Error_Posted       (T);
5110         goto Leave;
5111      end if;
5112
5113      --  Perhaps the parent type should be changed to the class-wide type's
5114      --  specific type in this case to prevent cascading errors ???
5115
5116      if Is_Class_Wide_Type (Parent_Type) then
5117         Error_Msg_N
5118           ("parent of type extension must not be a class-wide type", Indic);
5119         goto Leave;
5120      end if;
5121
5122      if (not Is_Package_Or_Generic_Package (Current_Scope)
5123           and then Nkind (Parent (N)) /= N_Generic_Subprogram_Declaration)
5124        or else In_Private_Part (Current_Scope)
5125      then
5126         Error_Msg_N ("invalid context for private extension", N);
5127      end if;
5128
5129      --  Set common attributes
5130
5131      Set_Is_Pure          (T, Is_Pure (Current_Scope));
5132      Set_Scope            (T, Current_Scope);
5133      Set_Ekind            (T, E_Record_Type_With_Private);
5134      Init_Size_Align      (T);
5135      Set_Default_SSO      (T);
5136      Set_No_Reordering    (T, No_Component_Reordering);
5137
5138      Set_Etype            (T,                Parent_Base);
5139      Propagate_Concurrent_Flags (T, Parent_Base);
5140
5141      Set_Convention       (T, Convention     (Parent_Type));
5142      Set_First_Rep_Item   (T, First_Rep_Item (Parent_Type));
5143      Set_Is_First_Subtype (T);
5144      Make_Class_Wide_Type (T);
5145
5146      --  Set the SPARK mode from the current context
5147
5148      Set_SPARK_Pragma           (T, SPARK_Mode_Pragma);
5149      Set_SPARK_Pragma_Inherited (T);
5150
5151      if Unknown_Discriminants_Present (N) then
5152         Set_Discriminant_Constraint (T, No_Elist);
5153      end if;
5154
5155      Build_Derived_Record_Type (N, Parent_Type, T);
5156
5157      --  A private extension inherits the Default_Initial_Condition pragma
5158      --  coming from any parent type within the derivation chain.
5159
5160      if Has_DIC (Parent_Type) then
5161         Set_Has_Inherited_DIC (T);
5162      end if;
5163
5164      --  A private extension inherits any class-wide invariants coming from a
5165      --  parent type or an interface. Note that the invariant procedure of the
5166      --  parent type should not be inherited because the private extension may
5167      --  define invariants of its own.
5168
5169      if Has_Inherited_Invariants (Parent_Type)
5170        or else Has_Inheritable_Invariants (Parent_Type)
5171      then
5172         Set_Has_Inherited_Invariants (T);
5173
5174      elsif Present (Interfaces (T)) then
5175         Iface_Elmt := First_Elmt (Interfaces (T));
5176         while Present (Iface_Elmt) loop
5177            Iface := Node (Iface_Elmt);
5178
5179            if Has_Inheritable_Invariants (Iface) then
5180               Set_Has_Inherited_Invariants (T);
5181               exit;
5182            end if;
5183
5184            Next_Elmt (Iface_Elmt);
5185         end loop;
5186      end if;
5187
5188      --  Ada 2005 (AI-443): Synchronized private extension or a rewritten
5189      --  synchronized formal derived type.
5190
5191      if Ada_Version >= Ada_2005 and then Synchronized_Present (N) then
5192         Set_Is_Limited_Record (T);
5193
5194         --  Formal derived type case
5195
5196         if Is_Generic_Type (T) then
5197
5198            --  The parent must be a tagged limited type or a synchronized
5199            --  interface.
5200
5201            if (not Is_Tagged_Type (Parent_Type)
5202                 or else not Is_Limited_Type (Parent_Type))
5203              and then
5204                (not Is_Interface (Parent_Type)
5205                  or else not Is_Synchronized_Interface (Parent_Type))
5206            then
5207               Error_Msg_NE
5208                 ("parent type of & must be tagged limited or synchronized",
5209                  N, T);
5210            end if;
5211
5212            --  The progenitors (if any) must be limited or synchronized
5213            --  interfaces.
5214
5215            if Present (Interfaces (T)) then
5216               Iface_Elmt := First_Elmt (Interfaces (T));
5217               while Present (Iface_Elmt) loop
5218                  Iface := Node (Iface_Elmt);
5219
5220                  if not Is_Limited_Interface (Iface)
5221                    and then not Is_Synchronized_Interface (Iface)
5222                  then
5223                     Error_Msg_NE
5224                       ("progenitor & must be limited or synchronized",
5225                        N, Iface);
5226                  end if;
5227
5228                  Next_Elmt (Iface_Elmt);
5229               end loop;
5230            end if;
5231
5232         --  Regular derived extension, the parent must be a limited or
5233         --  synchronized interface.
5234
5235         else
5236            if not Is_Interface (Parent_Type)
5237              or else (not Is_Limited_Interface (Parent_Type)
5238                        and then not Is_Synchronized_Interface (Parent_Type))
5239            then
5240               Error_Msg_NE
5241                 ("parent type of & must be limited interface", N, T);
5242            end if;
5243         end if;
5244
5245      --  A consequence of 3.9.4 (6/2) and 7.3 (7.2/2) is that a private
5246      --  extension with a synchronized parent must be explicitly declared
5247      --  synchronized, because the full view will be a synchronized type.
5248      --  This must be checked before the check for limited types below,
5249      --  to ensure that types declared limited are not allowed to extend
5250      --  synchronized interfaces.
5251
5252      elsif Is_Interface (Parent_Type)
5253        and then Is_Synchronized_Interface (Parent_Type)
5254        and then not Synchronized_Present (N)
5255      then
5256         Error_Msg_NE
5257           ("private extension of& must be explicitly synchronized",
5258             N, Parent_Type);
5259
5260      elsif Limited_Present (N) then
5261         Set_Is_Limited_Record (T);
5262
5263         if not Is_Limited_Type (Parent_Type)
5264           and then
5265             (not Is_Interface (Parent_Type)
5266               or else not Is_Limited_Interface (Parent_Type))
5267         then
5268            Error_Msg_NE ("parent type& of limited extension must be limited",
5269              N, Parent_Type);
5270         end if;
5271      end if;
5272
5273      --  Remember that its parent type has a private extension. Used to warn
5274      --  on public primitives of the parent type defined after its private
5275      --  extensions (see Check_Dispatching_Operation).
5276
5277      Set_Has_Private_Extension (Parent_Type);
5278
5279   <<Leave>>
5280      if Has_Aspects (N) then
5281         Analyze_Aspect_Specifications (N, T);
5282      end if;
5283   end Analyze_Private_Extension_Declaration;
5284
5285   ---------------------------------
5286   -- Analyze_Subtype_Declaration --
5287   ---------------------------------
5288
5289   procedure Analyze_Subtype_Declaration
5290     (N    : Node_Id;
5291      Skip : Boolean := False)
5292   is
5293      Id       : constant Entity_Id := Defining_Identifier (N);
5294      R_Checks : Check_Result;
5295      T        : Entity_Id;
5296
5297   begin
5298      Generate_Definition (Id);
5299      Set_Is_Pure (Id, Is_Pure (Current_Scope));
5300      Init_Size_Align (Id);
5301
5302      --  The following guard condition on Enter_Name is to handle cases where
5303      --  the defining identifier has already been entered into the scope but
5304      --  the declaration as a whole needs to be analyzed.
5305
5306      --  This case in particular happens for derived enumeration types. The
5307      --  derived enumeration type is processed as an inserted enumeration type
5308      --  declaration followed by a rewritten subtype declaration. The defining
5309      --  identifier, however, is entered into the name scope very early in the
5310      --  processing of the original type declaration and therefore needs to be
5311      --  avoided here, when the created subtype declaration is analyzed. (See
5312      --  Build_Derived_Types)
5313
5314      --  This also happens when the full view of a private type is derived
5315      --  type with constraints. In this case the entity has been introduced
5316      --  in the private declaration.
5317
5318      --  Finally this happens in some complex cases when validity checks are
5319      --  enabled, where the same subtype declaration may be analyzed twice.
5320      --  This can happen if the subtype is created by the preanalysis of
5321      --  an attribute tht gives the range of a loop statement, and the loop
5322      --  itself appears within an if_statement that will be rewritten during
5323      --  expansion.
5324
5325      if Skip
5326        or else (Present (Etype (Id))
5327                  and then (Is_Private_Type (Etype (Id))
5328                             or else Is_Task_Type (Etype (Id))
5329                             or else Is_Rewrite_Substitution (N)))
5330      then
5331         null;
5332
5333      elsif Current_Entity (Id) = Id then
5334         null;
5335
5336      else
5337         Enter_Name (Id);
5338      end if;
5339
5340      T := Process_Subtype (Subtype_Indication (N), N, Id, 'P');
5341
5342      --  Class-wide equivalent types of records with unknown discriminants
5343      --  involve the generation of an itype which serves as the private view
5344      --  of a constrained record subtype. In such cases the base type of the
5345      --  current subtype we are processing is the private itype. Use the full
5346      --  of the private itype when decorating various attributes.
5347
5348      if Is_Itype (T)
5349        and then Is_Private_Type (T)
5350        and then Present (Full_View (T))
5351      then
5352         T := Full_View (T);
5353      end if;
5354
5355      --  Inherit common attributes
5356
5357      Set_Is_Volatile       (Id, Is_Volatile       (T));
5358      Set_Treat_As_Volatile (Id, Treat_As_Volatile (T));
5359      Set_Is_Generic_Type   (Id, Is_Generic_Type   (Base_Type (T)));
5360      Set_Convention        (Id, Convention        (T));
5361
5362      --  If ancestor has predicates then so does the subtype, and in addition
5363      --  we must delay the freeze to properly arrange predicate inheritance.
5364
5365      --  The Ancestor_Type test is really unpleasant, there seem to be cases
5366      --  in which T = ID, so the above tests and assignments do nothing???
5367
5368      if Has_Predicates (T)
5369        or else (Present (Ancestor_Subtype (T))
5370                  and then Has_Predicates (Ancestor_Subtype (T)))
5371      then
5372         Set_Has_Predicates (Id);
5373         Set_Has_Delayed_Freeze (Id);
5374
5375         --  Generated subtypes inherit the predicate function from the parent
5376         --  (no aspects to examine on the generated declaration).
5377
5378         if not Comes_From_Source (N) then
5379            Set_Ekind (Id, Ekind (T));
5380
5381            if Present (Predicate_Function (Id)) then
5382               null;
5383
5384            elsif Present (Predicate_Function (T)) then
5385               Set_Predicate_Function (Id, Predicate_Function (T));
5386
5387            elsif Present (Ancestor_Subtype (T))
5388              and then Present (Predicate_Function (Ancestor_Subtype (T)))
5389            then
5390               Set_Predicate_Function (Id,
5391                 Predicate_Function (Ancestor_Subtype (T)));
5392            end if;
5393         end if;
5394      end if;
5395
5396      --  Subtype of Boolean cannot have a constraint in SPARK
5397
5398      if Is_Boolean_Type (T)
5399        and then Nkind (Subtype_Indication (N)) = N_Subtype_Indication
5400      then
5401         Check_SPARK_05_Restriction
5402           ("subtype of Boolean cannot have constraint", N);
5403      end if;
5404
5405      if Nkind (Subtype_Indication (N)) = N_Subtype_Indication then
5406         declare
5407            Cstr     : constant Node_Id := Constraint (Subtype_Indication (N));
5408            One_Cstr : Node_Id;
5409            Low      : Node_Id;
5410            High     : Node_Id;
5411
5412         begin
5413            if Nkind (Cstr) = N_Index_Or_Discriminant_Constraint then
5414               One_Cstr := First (Constraints (Cstr));
5415               while Present (One_Cstr) loop
5416
5417                  --  Index or discriminant constraint in SPARK must be a
5418                  --  subtype mark.
5419
5420                  if not
5421                    Nkind_In (One_Cstr, N_Identifier, N_Expanded_Name)
5422                  then
5423                     Check_SPARK_05_Restriction
5424                       ("subtype mark required", One_Cstr);
5425
5426                  --  String subtype must have a lower bound of 1 in SPARK.
5427                  --  Note that we do not need to test for the nonstatic case
5428                  --  here, since that was already taken care of in
5429                  --  Process_Range_Expr_In_Decl.
5430
5431                  elsif Base_Type (T) = Standard_String then
5432                     Get_Index_Bounds (One_Cstr, Low, High);
5433
5434                     if Is_OK_Static_Expression (Low)
5435                       and then Expr_Value (Low) /= 1
5436                     then
5437                        Check_SPARK_05_Restriction
5438                          ("String subtype must have lower bound of 1", N);
5439                     end if;
5440                  end if;
5441
5442                  Next (One_Cstr);
5443               end loop;
5444            end if;
5445         end;
5446      end if;
5447
5448      --  In the case where there is no constraint given in the subtype
5449      --  indication, Process_Subtype just returns the Subtype_Mark, so its
5450      --  semantic attributes must be established here.
5451
5452      if Nkind (Subtype_Indication (N)) /= N_Subtype_Indication then
5453         Set_Etype (Id, Base_Type (T));
5454
5455         --  Subtype of unconstrained array without constraint is not allowed
5456         --  in SPARK.
5457
5458         if Is_Array_Type (T) and then not Is_Constrained (T) then
5459            Check_SPARK_05_Restriction
5460              ("subtype of unconstrained array must have constraint", N);
5461         end if;
5462
5463         case Ekind (T) is
5464            when Array_Kind =>
5465               Set_Ekind                     (Id, E_Array_Subtype);
5466               Copy_Array_Subtype_Attributes (Id, T);
5467
5468            when Decimal_Fixed_Point_Kind =>
5469               Set_Ekind                (Id, E_Decimal_Fixed_Point_Subtype);
5470               Set_Digits_Value         (Id, Digits_Value       (T));
5471               Set_Delta_Value          (Id, Delta_Value        (T));
5472               Set_Scale_Value          (Id, Scale_Value        (T));
5473               Set_Small_Value          (Id, Small_Value        (T));
5474               Set_Scalar_Range         (Id, Scalar_Range       (T));
5475               Set_Machine_Radix_10     (Id, Machine_Radix_10   (T));
5476               Set_Is_Constrained       (Id, Is_Constrained     (T));
5477               Set_Is_Known_Valid       (Id, Is_Known_Valid     (T));
5478               Set_RM_Size              (Id, RM_Size            (T));
5479
5480            when Enumeration_Kind =>
5481               Set_Ekind                (Id, E_Enumeration_Subtype);
5482               Set_First_Literal        (Id, First_Literal (Base_Type (T)));
5483               Set_Scalar_Range         (Id, Scalar_Range       (T));
5484               Set_Is_Character_Type    (Id, Is_Character_Type  (T));
5485               Set_Is_Constrained       (Id, Is_Constrained     (T));
5486               Set_Is_Known_Valid       (Id, Is_Known_Valid     (T));
5487               Set_RM_Size              (Id, RM_Size            (T));
5488
5489            when Ordinary_Fixed_Point_Kind =>
5490               Set_Ekind                (Id, E_Ordinary_Fixed_Point_Subtype);
5491               Set_Scalar_Range         (Id, Scalar_Range       (T));
5492               Set_Small_Value          (Id, Small_Value        (T));
5493               Set_Delta_Value          (Id, Delta_Value        (T));
5494               Set_Is_Constrained       (Id, Is_Constrained     (T));
5495               Set_Is_Known_Valid       (Id, Is_Known_Valid     (T));
5496               Set_RM_Size              (Id, RM_Size            (T));
5497
5498            when Float_Kind =>
5499               Set_Ekind                (Id, E_Floating_Point_Subtype);
5500               Set_Scalar_Range         (Id, Scalar_Range       (T));
5501               Set_Digits_Value         (Id, Digits_Value       (T));
5502               Set_Is_Constrained       (Id, Is_Constrained     (T));
5503
5504               --  If the floating point type has dimensions, these will be
5505               --  inherited subsequently when Analyze_Dimensions is called.
5506
5507            when Signed_Integer_Kind =>
5508               Set_Ekind                (Id, E_Signed_Integer_Subtype);
5509               Set_Scalar_Range         (Id, Scalar_Range       (T));
5510               Set_Is_Constrained       (Id, Is_Constrained     (T));
5511               Set_Is_Known_Valid       (Id, Is_Known_Valid     (T));
5512               Set_RM_Size              (Id, RM_Size            (T));
5513
5514            when Modular_Integer_Kind =>
5515               Set_Ekind                (Id, E_Modular_Integer_Subtype);
5516               Set_Scalar_Range         (Id, Scalar_Range       (T));
5517               Set_Is_Constrained       (Id, Is_Constrained     (T));
5518               Set_Is_Known_Valid       (Id, Is_Known_Valid     (T));
5519               Set_RM_Size              (Id, RM_Size            (T));
5520
5521            when Class_Wide_Kind =>
5522               Set_Ekind                (Id, E_Class_Wide_Subtype);
5523               Set_Class_Wide_Type      (Id, Class_Wide_Type    (T));
5524               Set_Cloned_Subtype       (Id, T);
5525               Set_Is_Tagged_Type       (Id, True);
5526               Set_Has_Unknown_Discriminants
5527                                        (Id, True);
5528               Set_No_Tagged_Streams_Pragma
5529                                        (Id, No_Tagged_Streams_Pragma (T));
5530
5531               if Ekind (T) = E_Class_Wide_Subtype then
5532                  Set_Equivalent_Type   (Id, Equivalent_Type    (T));
5533               end if;
5534
5535            when E_Record_Subtype
5536               | E_Record_Type
5537            =>
5538               Set_Ekind                (Id, E_Record_Subtype);
5539
5540               if Ekind (T) = E_Record_Subtype
5541                 and then Present (Cloned_Subtype (T))
5542               then
5543                  Set_Cloned_Subtype    (Id, Cloned_Subtype (T));
5544               else
5545                  Set_Cloned_Subtype    (Id, T);
5546               end if;
5547
5548               Set_First_Entity         (Id, First_Entity       (T));
5549               Set_Last_Entity          (Id, Last_Entity        (T));
5550               Set_Has_Discriminants    (Id, Has_Discriminants  (T));
5551               Set_Is_Constrained       (Id, Is_Constrained     (T));
5552               Set_Is_Limited_Record    (Id, Is_Limited_Record  (T));
5553               Set_Has_Implicit_Dereference
5554                                        (Id, Has_Implicit_Dereference (T));
5555               Set_Has_Unknown_Discriminants
5556                                        (Id, Has_Unknown_Discriminants (T));
5557
5558               if Has_Discriminants (T) then
5559                  Set_Discriminant_Constraint
5560                                        (Id, Discriminant_Constraint (T));
5561                  Set_Stored_Constraint_From_Discriminant_Constraint (Id);
5562
5563               elsif Has_Unknown_Discriminants (Id) then
5564                  Set_Discriminant_Constraint (Id, No_Elist);
5565               end if;
5566
5567               if Is_Tagged_Type (T) then
5568                  Set_Is_Tagged_Type    (Id, True);
5569                  Set_No_Tagged_Streams_Pragma
5570                                        (Id, No_Tagged_Streams_Pragma (T));
5571                  Set_Is_Abstract_Type  (Id, Is_Abstract_Type (T));
5572                  Set_Direct_Primitive_Operations
5573                                        (Id, Direct_Primitive_Operations (T));
5574                  Set_Class_Wide_Type   (Id, Class_Wide_Type (T));
5575
5576                  if Is_Interface (T) then
5577                     Set_Is_Interface (Id);
5578                     Set_Is_Limited_Interface (Id, Is_Limited_Interface (T));
5579                  end if;
5580               end if;
5581
5582            when Private_Kind =>
5583               Set_Ekind              (Id, Subtype_Kind (Ekind        (T)));
5584               Set_Has_Discriminants  (Id, Has_Discriminants          (T));
5585               Set_Is_Constrained     (Id, Is_Constrained             (T));
5586               Set_First_Entity       (Id, First_Entity               (T));
5587               Set_Last_Entity        (Id, Last_Entity                (T));
5588               Set_Private_Dependents (Id, New_Elmt_List);
5589               Set_Is_Limited_Record  (Id, Is_Limited_Record          (T));
5590               Set_Has_Implicit_Dereference
5591                                      (Id, Has_Implicit_Dereference   (T));
5592               Set_Has_Unknown_Discriminants
5593                                      (Id, Has_Unknown_Discriminants  (T));
5594               Set_Known_To_Have_Preelab_Init
5595                                      (Id, Known_To_Have_Preelab_Init (T));
5596
5597               if Is_Tagged_Type (T) then
5598                  Set_Is_Tagged_Type              (Id);
5599                  Set_No_Tagged_Streams_Pragma    (Id,
5600                    No_Tagged_Streams_Pragma (T));
5601                  Set_Is_Abstract_Type            (Id, Is_Abstract_Type (T));
5602                  Set_Class_Wide_Type             (Id, Class_Wide_Type  (T));
5603                  Set_Direct_Primitive_Operations (Id,
5604                    Direct_Primitive_Operations (T));
5605               end if;
5606
5607               --  In general the attributes of the subtype of a private type
5608               --  are the attributes of the partial view of parent. However,
5609               --  the full view may be a discriminated type, and the subtype
5610               --  must share the discriminant constraint to generate correct
5611               --  calls to initialization procedures.
5612
5613               if Has_Discriminants (T) then
5614                  Set_Discriminant_Constraint
5615                    (Id, Discriminant_Constraint (T));
5616                  Set_Stored_Constraint_From_Discriminant_Constraint (Id);
5617
5618               elsif Present (Full_View (T))
5619                 and then Has_Discriminants (Full_View (T))
5620               then
5621                  Set_Discriminant_Constraint
5622                    (Id, Discriminant_Constraint (Full_View (T)));
5623                  Set_Stored_Constraint_From_Discriminant_Constraint (Id);
5624
5625                  --  This would seem semantically correct, but apparently
5626                  --  generates spurious errors about missing components ???
5627
5628                  --  Set_Has_Discriminants (Id);
5629               end if;
5630
5631               Prepare_Private_Subtype_Completion (Id, N);
5632
5633               --  If this is the subtype of a constrained private type with
5634               --  discriminants that has got a full view and we also have
5635               --  built a completion just above, show that the completion
5636               --  is a clone of the full view to the back-end.
5637
5638               if Has_Discriminants (T)
5639                  and then not Has_Unknown_Discriminants (T)
5640                  and then not Is_Empty_Elmt_List (Discriminant_Constraint (T))
5641                  and then Present (Full_View (T))
5642                  and then Present (Full_View (Id))
5643               then
5644                  Set_Cloned_Subtype (Full_View (Id), Full_View (T));
5645               end if;
5646
5647            when Access_Kind =>
5648               Set_Ekind             (Id, E_Access_Subtype);
5649               Set_Is_Constrained    (Id, Is_Constrained        (T));
5650               Set_Is_Access_Constant
5651                                     (Id, Is_Access_Constant    (T));
5652               Set_Directly_Designated_Type
5653                                     (Id, Designated_Type       (T));
5654               Set_Can_Never_Be_Null (Id, Can_Never_Be_Null     (T));
5655
5656               --  A Pure library_item must not contain the declaration of a
5657               --  named access type, except within a subprogram, generic
5658               --  subprogram, task unit, or protected unit, or if it has
5659               --  a specified Storage_Size of zero (RM05-10.2.1(15.4-15.5)).
5660
5661               if Comes_From_Source (Id)
5662                 and then In_Pure_Unit
5663                 and then not In_Subprogram_Task_Protected_Unit
5664                 and then not No_Pool_Assigned (Id)
5665               then
5666                  Error_Msg_N
5667                    ("named access types not allowed in pure unit", N);
5668               end if;
5669
5670            when Concurrent_Kind =>
5671               Set_Ekind                (Id, Subtype_Kind (Ekind   (T)));
5672               Set_Corresponding_Record_Type (Id,
5673                                         Corresponding_Record_Type (T));
5674               Set_First_Entity         (Id, First_Entity          (T));
5675               Set_First_Private_Entity (Id, First_Private_Entity  (T));
5676               Set_Has_Discriminants    (Id, Has_Discriminants     (T));
5677               Set_Is_Constrained       (Id, Is_Constrained        (T));
5678               Set_Is_Tagged_Type       (Id, Is_Tagged_Type        (T));
5679               Set_Last_Entity          (Id, Last_Entity           (T));
5680
5681               if Is_Tagged_Type (T) then
5682                  Set_No_Tagged_Streams_Pragma
5683                    (Id, No_Tagged_Streams_Pragma (T));
5684               end if;
5685
5686               if Has_Discriminants (T) then
5687                  Set_Discriminant_Constraint
5688                    (Id, Discriminant_Constraint (T));
5689                  Set_Stored_Constraint_From_Discriminant_Constraint (Id);
5690               end if;
5691
5692            when Incomplete_Kind =>
5693               if Ada_Version >= Ada_2005 then
5694
5695                  --  In Ada 2005 an incomplete type can be explicitly tagged:
5696                  --  propagate indication. Note that we also have to include
5697                  --  subtypes for Ada 2012 extended use of incomplete types.
5698
5699                  Set_Ekind              (Id, E_Incomplete_Subtype);
5700                  Set_Is_Tagged_Type     (Id, Is_Tagged_Type (T));
5701                  Set_Private_Dependents (Id, New_Elmt_List);
5702
5703                  if Is_Tagged_Type (Id) then
5704                     Set_No_Tagged_Streams_Pragma
5705                       (Id, No_Tagged_Streams_Pragma (T));
5706                     Set_Direct_Primitive_Operations (Id, New_Elmt_List);
5707                  end if;
5708
5709                  --  Ada 2005 (AI-412): Decorate an incomplete subtype of an
5710                  --  incomplete type visible through a limited with clause.
5711
5712                  if From_Limited_With (T)
5713                    and then Present (Non_Limited_View (T))
5714                  then
5715                     Set_From_Limited_With (Id);
5716                     Set_Non_Limited_View  (Id, Non_Limited_View (T));
5717
5718                  --  Ada 2005 (AI-412): Add the regular incomplete subtype
5719                  --  to the private dependents of the original incomplete
5720                  --  type for future transformation.
5721
5722                  else
5723                     Append_Elmt (Id, Private_Dependents (T));
5724                  end if;
5725
5726               --  If the subtype name denotes an incomplete type an error
5727               --  was already reported by Process_Subtype.
5728
5729               else
5730                  Set_Etype (Id, Any_Type);
5731               end if;
5732
5733            when others =>
5734               raise Program_Error;
5735         end case;
5736
5737         --  If there is no constraint in the subtype indication, the
5738         --  declared entity inherits predicates from the parent.
5739
5740         Inherit_Predicate_Flags (Id, T);
5741      end if;
5742
5743      if Etype (Id) = Any_Type then
5744         goto Leave;
5745      end if;
5746
5747      --  Some common processing on all types
5748
5749      Set_Size_Info      (Id, T);
5750      Set_First_Rep_Item (Id, First_Rep_Item (T));
5751
5752      --  If the parent type is a generic actual, so is the subtype. This may
5753      --  happen in a nested instance. Why Comes_From_Source test???
5754
5755      if not Comes_From_Source (N) then
5756         Set_Is_Generic_Actual_Type (Id, Is_Generic_Actual_Type (T));
5757      end if;
5758
5759      --  If this is a subtype declaration for an actual in an instance,
5760      --  inherit static and dynamic predicates if any.
5761
5762      --  If declaration has no aspect specifications, inherit predicate
5763      --  info as well. Unclear how to handle the case of both specified
5764      --  and inherited predicates ??? Other inherited aspects, such as
5765      --  invariants, should be OK, but the combination with later pragmas
5766      --  may also require special merging.
5767
5768      if Has_Predicates (T)
5769        and then Present (Predicate_Function (T))
5770        and then
5771          ((In_Instance and then not Comes_From_Source (N))
5772             or else No (Aspect_Specifications (N)))
5773      then
5774         Set_Subprograms_For_Type (Id, Subprograms_For_Type (T));
5775
5776         if Has_Static_Predicate (T) then
5777            Set_Has_Static_Predicate (Id);
5778            Set_Static_Discrete_Predicate (Id, Static_Discrete_Predicate (T));
5779         end if;
5780      end if;
5781
5782      --  Remaining processing depends on characteristics of base type
5783
5784      T := Etype (Id);
5785
5786      Set_Is_Immediately_Visible   (Id, True);
5787      Set_Depends_On_Private       (Id, Has_Private_Component (T));
5788      Set_Is_Descendant_Of_Address (Id, Is_Descendant_Of_Address (T));
5789
5790      if Is_Interface (T) then
5791         Set_Is_Interface (Id);
5792      end if;
5793
5794      if Present (Generic_Parent_Type (N))
5795        and then
5796          (Nkind (Parent (Generic_Parent_Type (N))) /=
5797                                              N_Formal_Type_Declaration
5798            or else Nkind (Formal_Type_Definition
5799                            (Parent (Generic_Parent_Type (N)))) /=
5800                                              N_Formal_Private_Type_Definition)
5801      then
5802         if Is_Tagged_Type (Id) then
5803
5804            --  If this is a generic actual subtype for a synchronized type,
5805            --  the primitive operations are those of the corresponding record
5806            --  for which there is a separate subtype declaration.
5807
5808            if Is_Concurrent_Type (Id) then
5809               null;
5810            elsif Is_Class_Wide_Type (Id) then
5811               Derive_Subprograms (Generic_Parent_Type (N), Id, Etype (T));
5812            else
5813               Derive_Subprograms (Generic_Parent_Type (N), Id, T);
5814            end if;
5815
5816         elsif Scope (Etype (Id)) /= Standard_Standard then
5817            Derive_Subprograms (Generic_Parent_Type (N), Id);
5818         end if;
5819      end if;
5820
5821      if Is_Private_Type (T) and then Present (Full_View (T)) then
5822         Conditional_Delay (Id, Full_View (T));
5823
5824      --  The subtypes of components or subcomponents of protected types
5825      --  do not need freeze nodes, which would otherwise appear in the
5826      --  wrong scope (before the freeze node for the protected type). The
5827      --  proper subtypes are those of the subcomponents of the corresponding
5828      --  record.
5829
5830      elsif Ekind (Scope (Id)) /= E_Protected_Type
5831        and then Present (Scope (Scope (Id))) -- error defense
5832        and then Ekind (Scope (Scope (Id))) /= E_Protected_Type
5833      then
5834         Conditional_Delay (Id, T);
5835      end if;
5836
5837      --  If we have a subtype of an incomplete type whose full type is a
5838      --  derived numeric type, we need to have a freeze node for the subtype.
5839      --  Otherwise gigi will complain while computing the (static) bounds of
5840      --  the subtype.
5841
5842      if Is_Itype (T)
5843        and then Is_Elementary_Type (Id)
5844        and then Etype (Id) /= Id
5845      then
5846         declare
5847            Partial : constant Entity_Id :=
5848                        Incomplete_Or_Partial_View (First_Subtype (Id));
5849         begin
5850            if Present (Partial)
5851              and then Ekind (Partial) = E_Incomplete_Type
5852            then
5853               Set_Has_Delayed_Freeze (Id);
5854            end if;
5855         end;
5856      end if;
5857
5858      --  Check that Constraint_Error is raised for a scalar subtype indication
5859      --  when the lower or upper bound of a non-null range lies outside the
5860      --  range of the type mark.
5861
5862      if Nkind (Subtype_Indication (N)) = N_Subtype_Indication then
5863         if Is_Scalar_Type (Etype (Id))
5864           and then Scalar_Range (Id) /=
5865                    Scalar_Range
5866                      (Etype (Subtype_Mark (Subtype_Indication (N))))
5867         then
5868            Apply_Range_Check
5869              (Scalar_Range (Id),
5870               Etype (Subtype_Mark (Subtype_Indication (N))));
5871
5872         --  In the array case, check compatibility for each index
5873
5874         elsif Is_Array_Type (Etype (Id)) and then Present (First_Index (Id))
5875         then
5876            --  This really should be a subprogram that finds the indications
5877            --  to check???
5878
5879            declare
5880               Subt_Index   : Node_Id := First_Index (Id);
5881               Target_Index : Node_Id :=
5882                                First_Index (Etype
5883                                  (Subtype_Mark (Subtype_Indication (N))));
5884               Has_Dyn_Chk  : Boolean := Has_Dynamic_Range_Check (N);
5885
5886            begin
5887               while Present (Subt_Index) loop
5888                  if ((Nkind (Subt_Index) = N_Identifier
5889                        and then Ekind (Entity (Subt_Index)) in Scalar_Kind)
5890                       or else Nkind (Subt_Index) = N_Subtype_Indication)
5891                    and then
5892                      Nkind (Scalar_Range (Etype (Subt_Index))) = N_Range
5893                  then
5894                     declare
5895                        Target_Typ : constant Entity_Id :=
5896                                       Etype (Target_Index);
5897                     begin
5898                        R_Checks :=
5899                          Get_Range_Checks
5900                            (Scalar_Range (Etype (Subt_Index)),
5901                             Target_Typ,
5902                             Etype (Subt_Index),
5903                             Defining_Identifier (N));
5904
5905                        --  Reset Has_Dynamic_Range_Check on the subtype to
5906                        --  prevent elision of the index check due to a dynamic
5907                        --  check generated for a preceding index (needed since
5908                        --  Insert_Range_Checks tries to avoid generating
5909                        --  redundant checks on a given declaration).
5910
5911                        Set_Has_Dynamic_Range_Check (N, False);
5912
5913                        Insert_Range_Checks
5914                          (R_Checks,
5915                           N,
5916                           Target_Typ,
5917                           Sloc (Defining_Identifier (N)));
5918
5919                        --  Record whether this index involved a dynamic check
5920
5921                        Has_Dyn_Chk :=
5922                          Has_Dyn_Chk or else Has_Dynamic_Range_Check (N);
5923                     end;
5924                  end if;
5925
5926                  Next_Index (Subt_Index);
5927                  Next_Index (Target_Index);
5928               end loop;
5929
5930               --  Finally, mark whether the subtype involves dynamic checks
5931
5932               Set_Has_Dynamic_Range_Check (N, Has_Dyn_Chk);
5933            end;
5934         end if;
5935      end if;
5936
5937      Set_Optimize_Alignment_Flags (Id);
5938      Check_Eliminated (Id);
5939
5940   <<Leave>>
5941      if Has_Aspects (N) then
5942         Analyze_Aspect_Specifications (N, Id);
5943      end if;
5944
5945      Analyze_Dimension (N);
5946
5947      --  Check No_Dynamic_Sized_Objects restriction, which disallows subtype
5948      --  indications on composite types where the constraints are dynamic.
5949      --  Note that object declarations and aggregates generate implicit
5950      --  subtype declarations, which this covers. One special case is that the
5951      --  implicitly generated "=" for discriminated types includes an
5952      --  offending subtype declaration, which is harmless, so we ignore it
5953      --  here.
5954
5955      if Nkind (Subtype_Indication (N)) = N_Subtype_Indication then
5956         declare
5957            Cstr : constant Node_Id := Constraint (Subtype_Indication (N));
5958         begin
5959            if Nkind (Cstr) = N_Index_Or_Discriminant_Constraint
5960              and then not (Is_Internal (Id)
5961                             and then Is_TSS (Scope (Id),
5962                                              TSS_Composite_Equality))
5963              and then not Within_Init_Proc
5964              and then not All_Composite_Constraints_Static (Cstr)
5965            then
5966               Check_Restriction (No_Dynamic_Sized_Objects, Cstr);
5967            end if;
5968         end;
5969      end if;
5970   end Analyze_Subtype_Declaration;
5971
5972   --------------------------------
5973   -- Analyze_Subtype_Indication --
5974   --------------------------------
5975
5976   procedure Analyze_Subtype_Indication (N : Node_Id) is
5977      T : constant Entity_Id := Subtype_Mark (N);
5978      R : constant Node_Id   := Range_Expression (Constraint (N));
5979
5980   begin
5981      Analyze (T);
5982
5983      if R /= Error then
5984         Analyze (R);
5985         Set_Etype (N, Etype (R));
5986         Resolve (R, Entity (T));
5987      else
5988         Set_Error_Posted (R);
5989         Set_Error_Posted (T);
5990      end if;
5991   end Analyze_Subtype_Indication;
5992
5993   --------------------------
5994   -- Analyze_Variant_Part --
5995   --------------------------
5996
5997   procedure Analyze_Variant_Part (N : Node_Id) is
5998      Discr_Name : Node_Id;
5999      Discr_Type : Entity_Id;
6000
6001      procedure Process_Variant (A : Node_Id);
6002      --  Analyze declarations for a single variant
6003
6004      package Analyze_Variant_Choices is
6005        new Generic_Analyze_Choices (Process_Variant);
6006      use Analyze_Variant_Choices;
6007
6008      ---------------------
6009      -- Process_Variant --
6010      ---------------------
6011
6012      procedure Process_Variant (A : Node_Id) is
6013         CL : constant Node_Id := Component_List (A);
6014      begin
6015         if not Null_Present (CL) then
6016            Analyze_Declarations (Component_Items (CL));
6017
6018            if Present (Variant_Part (CL)) then
6019               Analyze (Variant_Part (CL));
6020            end if;
6021         end if;
6022      end Process_Variant;
6023
6024   --  Start of processing for Analyze_Variant_Part
6025
6026   begin
6027      Discr_Name := Name (N);
6028      Analyze (Discr_Name);
6029
6030      --  If Discr_Name bad, get out (prevent cascaded errors)
6031
6032      if Etype (Discr_Name) = Any_Type then
6033         return;
6034      end if;
6035
6036      --  Check invalid discriminant in variant part
6037
6038      if Ekind (Entity (Discr_Name)) /= E_Discriminant then
6039         Error_Msg_N ("invalid discriminant name in variant part", Discr_Name);
6040      end if;
6041
6042      Discr_Type := Etype (Entity (Discr_Name));
6043
6044      if not Is_Discrete_Type (Discr_Type) then
6045         Error_Msg_N
6046           ("discriminant in a variant part must be of a discrete type",
6047             Name (N));
6048         return;
6049      end if;
6050
6051      --  Now analyze the choices, which also analyzes the declarations that
6052      --  are associated with each choice.
6053
6054      Analyze_Choices (Variants (N), Discr_Type);
6055
6056      --  Note: we used to instantiate and call Check_Choices here to check
6057      --  that the choices covered the discriminant, but it's too early to do
6058      --  that because of statically predicated subtypes, whose analysis may
6059      --  be deferred to their freeze point which may be as late as the freeze
6060      --  point of the containing record. So this call is now to be found in
6061      --  Freeze_Record_Declaration.
6062
6063   end Analyze_Variant_Part;
6064
6065   ----------------------------
6066   -- Array_Type_Declaration --
6067   ----------------------------
6068
6069   procedure Array_Type_Declaration (T : in out Entity_Id; Def : Node_Id) is
6070      Component_Def : constant Node_Id := Component_Definition (Def);
6071      Component_Typ : constant Node_Id := Subtype_Indication (Component_Def);
6072      P             : constant Node_Id := Parent (Def);
6073      Element_Type  : Entity_Id;
6074      Implicit_Base : Entity_Id;
6075      Index         : Node_Id;
6076      Nb_Index      : Nat;
6077      Priv          : Entity_Id;
6078      Related_Id    : Entity_Id := Empty;
6079
6080   begin
6081      if Nkind (Def) = N_Constrained_Array_Definition then
6082         Index := First (Discrete_Subtype_Definitions (Def));
6083      else
6084         Index := First (Subtype_Marks (Def));
6085      end if;
6086
6087      --  Find proper names for the implicit types which may be public. In case
6088      --  of anonymous arrays we use the name of the first object of that type
6089      --  as prefix.
6090
6091      if No (T) then
6092         Related_Id := Defining_Identifier (P);
6093      else
6094         Related_Id := T;
6095      end if;
6096
6097      Nb_Index := 1;
6098      while Present (Index) loop
6099         Analyze (Index);
6100
6101         --  Test for odd case of trying to index a type by the type itself
6102
6103         if Is_Entity_Name (Index) and then Entity (Index) = T then
6104            Error_Msg_N ("type& cannot be indexed by itself", Index);
6105            Set_Entity (Index, Standard_Boolean);
6106            Set_Etype (Index, Standard_Boolean);
6107         end if;
6108
6109         --  Check SPARK restriction requiring a subtype mark
6110
6111         if not Nkind_In (Index, N_Identifier, N_Expanded_Name) then
6112            Check_SPARK_05_Restriction ("subtype mark required", Index);
6113         end if;
6114
6115         --  Add a subtype declaration for each index of private array type
6116         --  declaration whose etype is also private. For example:
6117
6118         --     package Pkg is
6119         --        type Index is private;
6120         --     private
6121         --        type Table is array (Index) of ...
6122         --     end;
6123
6124         --  This is currently required by the expander for the internally
6125         --  generated equality subprogram of records with variant parts in
6126         --  which the etype of some component is such private type.
6127
6128         if Ekind (Current_Scope) = E_Package
6129           and then In_Private_Part (Current_Scope)
6130           and then Has_Private_Declaration (Etype (Index))
6131         then
6132            declare
6133               Loc   : constant Source_Ptr := Sloc (Def);
6134               Decl  : Entity_Id;
6135               New_E : Entity_Id;
6136
6137            begin
6138               New_E := Make_Temporary (Loc, 'T');
6139               Set_Is_Internal (New_E);
6140
6141               Decl :=
6142                 Make_Subtype_Declaration (Loc,
6143                   Defining_Identifier => New_E,
6144                   Subtype_Indication  =>
6145                     New_Occurrence_Of (Etype (Index), Loc));
6146
6147               Insert_Before (Parent (Def), Decl);
6148               Analyze (Decl);
6149               Set_Etype (Index, New_E);
6150
6151               --  If the index is a range or a subtype indication it carries
6152               --  no entity. Example:
6153
6154               --     package Pkg is
6155               --        type T is private;
6156               --     private
6157               --        type T is new Natural;
6158               --        Table : array (T(1) .. T(10)) of Boolean;
6159               --     end Pkg;
6160
6161               --  Otherwise the type of the reference is its entity.
6162
6163               if Is_Entity_Name (Index) then
6164                  Set_Entity (Index, New_E);
6165               end if;
6166            end;
6167         end if;
6168
6169         Make_Index (Index, P, Related_Id, Nb_Index);
6170
6171         --  Check error of subtype with predicate for index type
6172
6173         Bad_Predicated_Subtype_Use
6174           ("subtype& has predicate, not allowed as index subtype",
6175            Index, Etype (Index));
6176
6177         --  Move to next index
6178
6179         Next_Index (Index);
6180         Nb_Index := Nb_Index + 1;
6181      end loop;
6182
6183      --  Process subtype indication if one is present
6184
6185      if Present (Component_Typ) then
6186         Element_Type := Process_Subtype (Component_Typ, P, Related_Id, 'C');
6187
6188         Set_Etype (Component_Typ, Element_Type);
6189
6190         if not Nkind_In (Component_Typ, N_Identifier, N_Expanded_Name) then
6191            Check_SPARK_05_Restriction
6192              ("subtype mark required", Component_Typ);
6193         end if;
6194
6195      --  Ada 2005 (AI-230): Access Definition case
6196
6197      else pragma Assert (Present (Access_Definition (Component_Def)));
6198
6199         --  Indicate that the anonymous access type is created by the
6200         --  array type declaration.
6201
6202         Element_Type := Access_Definition
6203                           (Related_Nod => P,
6204                            N           => Access_Definition (Component_Def));
6205         Set_Is_Local_Anonymous_Access (Element_Type);
6206
6207         --  Propagate the parent. This field is needed if we have to generate
6208         --  the master_id associated with an anonymous access to task type
6209         --  component (see Expand_N_Full_Type_Declaration.Build_Master)
6210
6211         Set_Parent (Element_Type, Parent (T));
6212
6213         --  Ada 2005 (AI-230): In case of components that are anonymous access
6214         --  types the level of accessibility depends on the enclosing type
6215         --  declaration
6216
6217         Set_Scope (Element_Type, Current_Scope); -- Ada 2005 (AI-230)
6218
6219         --  Ada 2005 (AI-254)
6220
6221         declare
6222            CD : constant Node_Id :=
6223                   Access_To_Subprogram_Definition
6224                     (Access_Definition (Component_Def));
6225         begin
6226            if Present (CD) and then Protected_Present (CD) then
6227               Element_Type :=
6228                 Replace_Anonymous_Access_To_Protected_Subprogram (Def);
6229            end if;
6230         end;
6231      end if;
6232
6233      --  Constrained array case
6234
6235      if No (T) then
6236         T := Create_Itype (E_Void, P, Related_Id, 'T');
6237      end if;
6238
6239      if Nkind (Def) = N_Constrained_Array_Definition then
6240
6241         --  Establish Implicit_Base as unconstrained base type
6242
6243         Implicit_Base := Create_Itype (E_Array_Type, P, Related_Id, 'B');
6244
6245         Set_Etype              (Implicit_Base, Implicit_Base);
6246         Set_Scope              (Implicit_Base, Current_Scope);
6247         Set_Has_Delayed_Freeze (Implicit_Base);
6248         Set_Default_SSO        (Implicit_Base);
6249
6250         --  The constrained array type is a subtype of the unconstrained one
6251
6252         Set_Ekind              (T, E_Array_Subtype);
6253         Init_Size_Align        (T);
6254         Set_Etype              (T, Implicit_Base);
6255         Set_Scope              (T, Current_Scope);
6256         Set_Is_Constrained     (T);
6257         Set_First_Index        (T,
6258           First (Discrete_Subtype_Definitions (Def)));
6259         Set_Has_Delayed_Freeze (T);
6260
6261         --  Complete setup of implicit base type
6262
6263         Set_Component_Size (Implicit_Base, Uint_0);
6264         Set_Component_Type (Implicit_Base, Element_Type);
6265         Set_Finalize_Storage_Only
6266                            (Implicit_Base,
6267                              Finalize_Storage_Only (Element_Type));
6268         Set_First_Index    (Implicit_Base, First_Index (T));
6269         Set_Has_Controlled_Component
6270                            (Implicit_Base,
6271                              Has_Controlled_Component (Element_Type)
6272                                or else Is_Controlled (Element_Type));
6273         Set_Packed_Array_Impl_Type
6274                            (Implicit_Base, Empty);
6275
6276         Propagate_Concurrent_Flags (Implicit_Base, Element_Type);
6277
6278      --  Unconstrained array case
6279
6280      else
6281         Set_Ekind                    (T, E_Array_Type);
6282         Init_Size_Align              (T);
6283         Set_Etype                    (T, T);
6284         Set_Scope                    (T, Current_Scope);
6285         Set_Component_Size           (T, Uint_0);
6286         Set_Is_Constrained           (T, False);
6287         Set_First_Index              (T, First (Subtype_Marks (Def)));
6288         Set_Has_Delayed_Freeze       (T, True);
6289         Propagate_Concurrent_Flags   (T, Element_Type);
6290         Set_Has_Controlled_Component (T, Has_Controlled_Component
6291                                                        (Element_Type)
6292                                            or else
6293                                          Is_Controlled (Element_Type));
6294         Set_Finalize_Storage_Only    (T, Finalize_Storage_Only
6295                                                        (Element_Type));
6296         Set_Default_SSO              (T);
6297      end if;
6298
6299      --  Common attributes for both cases
6300
6301      Set_Component_Type (Base_Type (T), Element_Type);
6302      Set_Packed_Array_Impl_Type (T, Empty);
6303
6304      if Aliased_Present (Component_Definition (Def)) then
6305         Check_SPARK_05_Restriction
6306           ("aliased is not allowed", Component_Definition (Def));
6307         Set_Has_Aliased_Components (Etype (T));
6308      end if;
6309
6310      --  Ada 2005 (AI-231): Propagate the null-excluding attribute to the
6311      --  array type to ensure that objects of this type are initialized.
6312
6313      if Ada_Version >= Ada_2005 and then Can_Never_Be_Null (Element_Type) then
6314         Set_Can_Never_Be_Null (T);
6315
6316         if Null_Exclusion_Present (Component_Definition (Def))
6317
6318            --  No need to check itypes because in their case this check was
6319            --  done at their point of creation
6320
6321           and then not Is_Itype (Element_Type)
6322         then
6323            Error_Msg_N
6324              ("`NOT NULL` not allowed (null already excluded)",
6325               Subtype_Indication (Component_Definition (Def)));
6326         end if;
6327      end if;
6328
6329      Priv := Private_Component (Element_Type);
6330
6331      if Present (Priv) then
6332
6333         --  Check for circular definitions
6334
6335         if Priv = Any_Type then
6336            Set_Component_Type (Etype (T), Any_Type);
6337
6338         --  There is a gap in the visibility of operations on the composite
6339         --  type only if the component type is defined in a different scope.
6340
6341         elsif Scope (Priv) = Current_Scope then
6342            null;
6343
6344         elsif Is_Limited_Type (Priv) then
6345            Set_Is_Limited_Composite (Etype (T));
6346            Set_Is_Limited_Composite (T);
6347         else
6348            Set_Is_Private_Composite (Etype (T));
6349            Set_Is_Private_Composite (T);
6350         end if;
6351      end if;
6352
6353      --  A syntax error in the declaration itself may lead to an empty index
6354      --  list, in which case do a minimal patch.
6355
6356      if No (First_Index (T)) then
6357         Error_Msg_N ("missing index definition in array type declaration", T);
6358
6359         declare
6360            Indexes : constant List_Id :=
6361                        New_List (New_Occurrence_Of (Any_Id, Sloc (T)));
6362         begin
6363            Set_Discrete_Subtype_Definitions (Def, Indexes);
6364            Set_First_Index (T, First (Indexes));
6365            return;
6366         end;
6367      end if;
6368
6369      --  Create a concatenation operator for the new type. Internal array
6370      --  types created for packed entities do not need such, they are
6371      --  compatible with the user-defined type.
6372
6373      if Number_Dimensions (T) = 1
6374        and then not Is_Packed_Array_Impl_Type (T)
6375      then
6376         New_Concatenation_Op (T);
6377      end if;
6378
6379      --  In the case of an unconstrained array the parser has already verified
6380      --  that all the indexes are unconstrained but we still need to make sure
6381      --  that the element type is constrained.
6382
6383      if not Is_Definite_Subtype (Element_Type) then
6384         Error_Msg_N
6385           ("unconstrained element type in array declaration",
6386            Subtype_Indication (Component_Def));
6387
6388      elsif Is_Abstract_Type (Element_Type) then
6389         Error_Msg_N
6390           ("the type of a component cannot be abstract",
6391            Subtype_Indication (Component_Def));
6392      end if;
6393
6394      --  There may be an invariant declared for the component type, but
6395      --  the construction of the component invariant checking procedure
6396      --  takes place during expansion.
6397   end Array_Type_Declaration;
6398
6399   ------------------------------------------------------
6400   -- Replace_Anonymous_Access_To_Protected_Subprogram --
6401   ------------------------------------------------------
6402
6403   function Replace_Anonymous_Access_To_Protected_Subprogram
6404     (N : Node_Id) return Entity_Id
6405   is
6406      Loc : constant Source_Ptr := Sloc (N);
6407
6408      Curr_Scope : constant Scope_Stack_Entry :=
6409                     Scope_Stack.Table (Scope_Stack.Last);
6410
6411      Anon : constant Entity_Id := Make_Temporary (Loc, 'S');
6412
6413      Acc : Node_Id;
6414      --  Access definition in declaration
6415
6416      Comp : Node_Id;
6417      --  Object definition or formal definition with an access definition
6418
6419      Decl : Node_Id;
6420      --  Declaration of anonymous access to subprogram type
6421
6422      Spec : Node_Id;
6423      --  Original specification in access to subprogram
6424
6425      P : Node_Id;
6426
6427   begin
6428      Set_Is_Internal (Anon);
6429
6430      case Nkind (N) is
6431         when N_Constrained_Array_Definition
6432            | N_Component_Declaration
6433            | N_Unconstrained_Array_Definition
6434         =>
6435            Comp := Component_Definition (N);
6436            Acc  := Access_Definition (Comp);
6437
6438         when N_Discriminant_Specification =>
6439            Comp := Discriminant_Type (N);
6440            Acc  := Comp;
6441
6442         when N_Parameter_Specification =>
6443            Comp := Parameter_Type (N);
6444            Acc  := Comp;
6445
6446         when N_Access_Function_Definition  =>
6447            Comp := Result_Definition (N);
6448            Acc  := Comp;
6449
6450         when N_Object_Declaration  =>
6451            Comp := Object_Definition (N);
6452            Acc  := Comp;
6453
6454         when N_Function_Specification =>
6455            Comp := Result_Definition (N);
6456            Acc  := Comp;
6457
6458         when others =>
6459            raise Program_Error;
6460      end case;
6461
6462      Spec := Access_To_Subprogram_Definition (Acc);
6463
6464      Decl :=
6465        Make_Full_Type_Declaration (Loc,
6466          Defining_Identifier => Anon,
6467          Type_Definition     => Copy_Separate_Tree (Spec));
6468
6469      Mark_Rewrite_Insertion (Decl);
6470
6471      --  In ASIS mode, analyze the profile on the original node, because
6472      --  the separate copy does not provide enough links to recover the
6473      --  original tree. Analysis is limited to type annotations, within
6474      --  a temporary scope that serves as an anonymous subprogram to collect
6475      --  otherwise useless temporaries and itypes.
6476
6477      if ASIS_Mode then
6478         declare
6479            Typ : constant Entity_Id := Make_Temporary (Loc, 'S');
6480
6481         begin
6482            if Nkind (Spec) = N_Access_Function_Definition then
6483               Set_Ekind (Typ, E_Function);
6484            else
6485               Set_Ekind (Typ, E_Procedure);
6486            end if;
6487
6488            Set_Parent (Typ, N);
6489            Set_Scope  (Typ, Current_Scope);
6490            Push_Scope (Typ);
6491
6492            --  Nothing to do if procedure is parameterless
6493
6494            if Present (Parameter_Specifications (Spec)) then
6495               Process_Formals (Parameter_Specifications (Spec), Spec);
6496            end if;
6497
6498            if Nkind (Spec) = N_Access_Function_Definition then
6499               declare
6500                  Def : constant Node_Id := Result_Definition (Spec);
6501
6502               begin
6503                  --  The result might itself be an anonymous access type, so
6504                  --  have to recurse.
6505
6506                  if Nkind (Def) = N_Access_Definition then
6507                     if Present (Access_To_Subprogram_Definition (Def)) then
6508                        Set_Etype
6509                          (Def,
6510                           Replace_Anonymous_Access_To_Protected_Subprogram
6511                            (Spec));
6512                     else
6513                        Find_Type (Subtype_Mark (Def));
6514                     end if;
6515
6516                  else
6517                     Find_Type (Def);
6518                  end if;
6519               end;
6520            end if;
6521
6522            End_Scope;
6523         end;
6524      end if;
6525
6526      --  Insert the new declaration in the nearest enclosing scope. If the
6527      --  parent is a body and N is its return type, the declaration belongs
6528      --  in the enclosing scope. Likewise if N is the type of a parameter.
6529
6530      P := Parent (N);
6531
6532      if Nkind (N) = N_Function_Specification
6533        and then Nkind (P) = N_Subprogram_Body
6534      then
6535         P := Parent (P);
6536      elsif Nkind (N) = N_Parameter_Specification
6537        and then Nkind (P) in N_Subprogram_Specification
6538        and then Nkind (Parent (P)) = N_Subprogram_Body
6539      then
6540         P := Parent (Parent (P));
6541      end if;
6542
6543      while Present (P) and then not Has_Declarations (P) loop
6544         P := Parent (P);
6545      end loop;
6546
6547      pragma Assert (Present (P));
6548
6549      if Nkind (P) = N_Package_Specification then
6550         Prepend (Decl, Visible_Declarations (P));
6551      else
6552         Prepend (Decl, Declarations (P));
6553      end if;
6554
6555      --  Replace the anonymous type with an occurrence of the new declaration.
6556      --  In all cases the rewritten node does not have the null-exclusion
6557      --  attribute because (if present) it was already inherited by the
6558      --  anonymous entity (Anon). Thus, in case of components we do not
6559      --  inherit this attribute.
6560
6561      if Nkind (N) = N_Parameter_Specification then
6562         Rewrite (Comp, New_Occurrence_Of (Anon, Loc));
6563         Set_Etype (Defining_Identifier (N), Anon);
6564         Set_Null_Exclusion_Present (N, False);
6565
6566      elsif Nkind (N) = N_Object_Declaration then
6567         Rewrite (Comp, New_Occurrence_Of (Anon, Loc));
6568         Set_Etype (Defining_Identifier (N), Anon);
6569
6570      elsif Nkind (N) = N_Access_Function_Definition then
6571         Rewrite (Comp, New_Occurrence_Of (Anon, Loc));
6572
6573      elsif Nkind (N) = N_Function_Specification then
6574         Rewrite (Comp, New_Occurrence_Of (Anon, Loc));
6575         Set_Etype (Defining_Unit_Name (N), Anon);
6576
6577      else
6578         Rewrite (Comp,
6579           Make_Component_Definition (Loc,
6580             Subtype_Indication => New_Occurrence_Of (Anon, Loc)));
6581      end if;
6582
6583      Mark_Rewrite_Insertion (Comp);
6584
6585      if Nkind_In (N, N_Object_Declaration, N_Access_Function_Definition)
6586        or else (Nkind (Parent (N)) = N_Full_Type_Declaration
6587                  and then not Is_Type (Current_Scope))
6588      then
6589
6590         --  Declaration can be analyzed in the current scope.
6591
6592         Analyze (Decl);
6593
6594      else
6595         --  Temporarily remove the current scope (record or subprogram) from
6596         --  the stack to add the new declarations to the enclosing scope.
6597         --  The anonymous entity is an Itype with the proper attributes.
6598
6599         Scope_Stack.Decrement_Last;
6600         Analyze (Decl);
6601         Set_Is_Itype (Anon);
6602         Set_Associated_Node_For_Itype (Anon, N);
6603         Scope_Stack.Append (Curr_Scope);
6604      end if;
6605
6606      Set_Ekind (Anon, E_Anonymous_Access_Protected_Subprogram_Type);
6607      Set_Can_Use_Internal_Rep (Anon, not Always_Compatible_Rep_On_Target);
6608      return Anon;
6609   end Replace_Anonymous_Access_To_Protected_Subprogram;
6610
6611   -------------------------------
6612   -- Build_Derived_Access_Type --
6613   -------------------------------
6614
6615   procedure Build_Derived_Access_Type
6616     (N            : Node_Id;
6617      Parent_Type  : Entity_Id;
6618      Derived_Type : Entity_Id)
6619   is
6620      S : constant Node_Id := Subtype_Indication (Type_Definition (N));
6621
6622      Desig_Type      : Entity_Id;
6623      Discr           : Entity_Id;
6624      Discr_Con_Elist : Elist_Id;
6625      Discr_Con_El    : Elmt_Id;
6626      Subt            : Entity_Id;
6627
6628   begin
6629      --  Set the designated type so it is available in case this is an access
6630      --  to a self-referential type, e.g. a standard list type with a next
6631      --  pointer. Will be reset after subtype is built.
6632
6633      Set_Directly_Designated_Type
6634        (Derived_Type, Designated_Type (Parent_Type));
6635
6636      Subt := Process_Subtype (S, N);
6637
6638      if Nkind (S) /= N_Subtype_Indication
6639        and then Subt /= Base_Type (Subt)
6640      then
6641         Set_Ekind (Derived_Type, E_Access_Subtype);
6642      end if;
6643
6644      if Ekind (Derived_Type) = E_Access_Subtype then
6645         declare
6646            Pbase      : constant Entity_Id := Base_Type (Parent_Type);
6647            Ibase      : constant Entity_Id :=
6648                           Create_Itype (Ekind (Pbase), N, Derived_Type, 'B');
6649            Svg_Chars  : constant Name_Id   := Chars (Ibase);
6650            Svg_Next_E : constant Entity_Id := Next_Entity (Ibase);
6651            Svg_Prev_E : constant Entity_Id := Prev_Entity (Ibase);
6652
6653         begin
6654            Copy_Node (Pbase, Ibase);
6655
6656            --  Restore Itype status after Copy_Node
6657
6658            Set_Is_Itype (Ibase);
6659            Set_Associated_Node_For_Itype (Ibase, N);
6660
6661            Set_Chars             (Ibase, Svg_Chars);
6662            Set_Prev_Entity       (Ibase, Svg_Prev_E);
6663            Set_Next_Entity       (Ibase, Svg_Next_E);
6664            Set_Sloc              (Ibase, Sloc (Derived_Type));
6665            Set_Scope             (Ibase, Scope (Derived_Type));
6666            Set_Freeze_Node       (Ibase, Empty);
6667            Set_Is_Frozen         (Ibase, False);
6668            Set_Comes_From_Source (Ibase, False);
6669            Set_Is_First_Subtype  (Ibase, False);
6670
6671            Set_Etype (Ibase, Pbase);
6672            Set_Etype (Derived_Type, Ibase);
6673         end;
6674      end if;
6675
6676      Set_Directly_Designated_Type
6677        (Derived_Type, Designated_Type (Subt));
6678
6679      Set_Is_Constrained     (Derived_Type, Is_Constrained (Subt));
6680      Set_Is_Access_Constant (Derived_Type, Is_Access_Constant (Parent_Type));
6681      Set_Size_Info          (Derived_Type,                     Parent_Type);
6682      Set_RM_Size            (Derived_Type, RM_Size            (Parent_Type));
6683      Set_Depends_On_Private (Derived_Type,
6684                              Has_Private_Component (Derived_Type));
6685      Conditional_Delay      (Derived_Type, Subt);
6686
6687      --  Ada 2005 (AI-231): Set the null-exclusion attribute, and verify
6688      --  that it is not redundant.
6689
6690      if Null_Exclusion_Present (Type_Definition (N)) then
6691         Set_Can_Never_Be_Null (Derived_Type);
6692
6693      elsif Can_Never_Be_Null (Parent_Type) then
6694         Set_Can_Never_Be_Null (Derived_Type);
6695      end if;
6696
6697      --  Note: we do not copy the Storage_Size_Variable, since we always go to
6698      --  the root type for this information.
6699
6700      --  Apply range checks to discriminants for derived record case
6701      --  ??? THIS CODE SHOULD NOT BE HERE REALLY.
6702
6703      Desig_Type := Designated_Type (Derived_Type);
6704
6705      if Is_Composite_Type (Desig_Type)
6706        and then (not Is_Array_Type (Desig_Type))
6707        and then Has_Discriminants (Desig_Type)
6708        and then Base_Type (Desig_Type) /= Desig_Type
6709      then
6710         Discr_Con_Elist := Discriminant_Constraint (Desig_Type);
6711         Discr_Con_El := First_Elmt (Discr_Con_Elist);
6712
6713         Discr := First_Discriminant (Base_Type (Desig_Type));
6714         while Present (Discr_Con_El) loop
6715            Apply_Range_Check (Node (Discr_Con_El), Etype (Discr));
6716            Next_Elmt (Discr_Con_El);
6717            Next_Discriminant (Discr);
6718         end loop;
6719      end if;
6720   end Build_Derived_Access_Type;
6721
6722   ------------------------------
6723   -- Build_Derived_Array_Type --
6724   ------------------------------
6725
6726   procedure Build_Derived_Array_Type
6727     (N            : Node_Id;
6728      Parent_Type  : Entity_Id;
6729      Derived_Type : Entity_Id)
6730   is
6731      Loc           : constant Source_Ptr := Sloc (N);
6732      Tdef          : constant Node_Id    := Type_Definition (N);
6733      Indic         : constant Node_Id    := Subtype_Indication (Tdef);
6734      Parent_Base   : constant Entity_Id  := Base_Type (Parent_Type);
6735      Implicit_Base : Entity_Id           := Empty;
6736      New_Indic     : Node_Id;
6737
6738      procedure Make_Implicit_Base;
6739      --  If the parent subtype is constrained, the derived type is a subtype
6740      --  of an implicit base type derived from the parent base.
6741
6742      ------------------------
6743      -- Make_Implicit_Base --
6744      ------------------------
6745
6746      procedure Make_Implicit_Base is
6747      begin
6748         Implicit_Base :=
6749           Create_Itype (Ekind (Parent_Base), N, Derived_Type, 'B');
6750
6751         Set_Ekind (Implicit_Base, Ekind (Parent_Base));
6752         Set_Etype (Implicit_Base, Parent_Base);
6753
6754         Copy_Array_Subtype_Attributes   (Implicit_Base, Parent_Base);
6755         Copy_Array_Base_Type_Attributes (Implicit_Base, Parent_Base);
6756
6757         Set_Has_Delayed_Freeze (Implicit_Base, True);
6758      end Make_Implicit_Base;
6759
6760   --  Start of processing for Build_Derived_Array_Type
6761
6762   begin
6763      if not Is_Constrained (Parent_Type) then
6764         if Nkind (Indic) /= N_Subtype_Indication then
6765            Set_Ekind (Derived_Type, E_Array_Type);
6766
6767            Copy_Array_Subtype_Attributes   (Derived_Type, Parent_Type);
6768            Copy_Array_Base_Type_Attributes (Derived_Type, Parent_Type);
6769
6770            Set_Has_Delayed_Freeze (Derived_Type, True);
6771
6772         else
6773            Make_Implicit_Base;
6774            Set_Etype (Derived_Type, Implicit_Base);
6775
6776            New_Indic :=
6777              Make_Subtype_Declaration (Loc,
6778                Defining_Identifier => Derived_Type,
6779                Subtype_Indication  =>
6780                  Make_Subtype_Indication (Loc,
6781                    Subtype_Mark => New_Occurrence_Of (Implicit_Base, Loc),
6782                    Constraint => Constraint (Indic)));
6783
6784            Rewrite (N, New_Indic);
6785            Analyze (N);
6786         end if;
6787
6788      else
6789         if Nkind (Indic) /= N_Subtype_Indication then
6790            Make_Implicit_Base;
6791
6792            Set_Ekind                     (Derived_Type, Ekind (Parent_Type));
6793            Set_Etype                     (Derived_Type, Implicit_Base);
6794            Copy_Array_Subtype_Attributes (Derived_Type, Parent_Type);
6795
6796         else
6797            Error_Msg_N ("illegal constraint on constrained type", Indic);
6798         end if;
6799      end if;
6800
6801      --  If parent type is not a derived type itself, and is declared in
6802      --  closed scope (e.g. a subprogram), then we must explicitly introduce
6803      --  the new type's concatenation operator since Derive_Subprograms
6804      --  will not inherit the parent's operator. If the parent type is
6805      --  unconstrained, the operator is of the unconstrained base type.
6806
6807      if Number_Dimensions (Parent_Type) = 1
6808        and then not Is_Limited_Type (Parent_Type)
6809        and then not Is_Derived_Type (Parent_Type)
6810        and then not Is_Package_Or_Generic_Package
6811                       (Scope (Base_Type (Parent_Type)))
6812      then
6813         if not Is_Constrained (Parent_Type)
6814           and then Is_Constrained (Derived_Type)
6815         then
6816            New_Concatenation_Op (Implicit_Base);
6817         else
6818            New_Concatenation_Op (Derived_Type);
6819         end if;
6820      end if;
6821   end Build_Derived_Array_Type;
6822
6823   -----------------------------------
6824   -- Build_Derived_Concurrent_Type --
6825   -----------------------------------
6826
6827   procedure Build_Derived_Concurrent_Type
6828     (N            : Node_Id;
6829      Parent_Type  : Entity_Id;
6830      Derived_Type : Entity_Id)
6831   is
6832      Loc : constant Source_Ptr := Sloc (N);
6833
6834      Corr_Record      : constant Entity_Id := Make_Temporary (Loc, 'C');
6835      Corr_Decl        : Node_Id;
6836      Corr_Decl_Needed : Boolean;
6837      --  If the derived type has fewer discriminants than its parent, the
6838      --  corresponding record is also a derived type, in order to account for
6839      --  the bound discriminants. We create a full type declaration for it in
6840      --  this case.
6841
6842      Constraint_Present : constant Boolean :=
6843                             Nkind (Subtype_Indication (Type_Definition (N))) =
6844                                                          N_Subtype_Indication;
6845
6846      D_Constraint   : Node_Id;
6847      New_Constraint : Elist_Id := No_Elist;
6848      Old_Disc       : Entity_Id;
6849      New_Disc       : Entity_Id;
6850      New_N          : Node_Id;
6851
6852   begin
6853      Set_Stored_Constraint (Derived_Type, No_Elist);
6854      Corr_Decl_Needed := False;
6855      Old_Disc := Empty;
6856
6857      if Present (Discriminant_Specifications (N))
6858        and then Constraint_Present
6859      then
6860         Old_Disc := First_Discriminant (Parent_Type);
6861         New_Disc := First (Discriminant_Specifications (N));
6862         while Present (New_Disc) and then Present (Old_Disc) loop
6863            Next_Discriminant (Old_Disc);
6864            Next (New_Disc);
6865         end loop;
6866      end if;
6867
6868      if Present (Old_Disc) and then Expander_Active then
6869
6870         --  The new type has fewer discriminants, so we need to create a new
6871         --  corresponding record, which is derived from the corresponding
6872         --  record of the parent, and has a stored constraint that captures
6873         --  the values of the discriminant constraints. The corresponding
6874         --  record is needed only if expander is active and code generation is
6875         --  enabled.
6876
6877         --  The type declaration for the derived corresponding record has the
6878         --  same discriminant part and constraints as the current declaration.
6879         --  Copy the unanalyzed tree to build declaration.
6880
6881         Corr_Decl_Needed := True;
6882         New_N := Copy_Separate_Tree (N);
6883
6884         Corr_Decl :=
6885           Make_Full_Type_Declaration (Loc,
6886             Defining_Identifier         => Corr_Record,
6887             Discriminant_Specifications =>
6888                Discriminant_Specifications (New_N),
6889             Type_Definition             =>
6890               Make_Derived_Type_Definition (Loc,
6891                 Subtype_Indication =>
6892                   Make_Subtype_Indication (Loc,
6893                     Subtype_Mark =>
6894                        New_Occurrence_Of
6895                          (Corresponding_Record_Type (Parent_Type), Loc),
6896                     Constraint   =>
6897                       Constraint
6898                         (Subtype_Indication (Type_Definition (New_N))))));
6899      end if;
6900
6901      --  Copy Storage_Size and Relative_Deadline variables if task case
6902
6903      if Is_Task_Type (Parent_Type) then
6904         Set_Storage_Size_Variable (Derived_Type,
6905           Storage_Size_Variable (Parent_Type));
6906         Set_Relative_Deadline_Variable (Derived_Type,
6907           Relative_Deadline_Variable (Parent_Type));
6908      end if;
6909
6910      if Present (Discriminant_Specifications (N)) then
6911         Push_Scope (Derived_Type);
6912         Check_Or_Process_Discriminants (N, Derived_Type);
6913
6914         if Constraint_Present then
6915            New_Constraint :=
6916              Expand_To_Stored_Constraint
6917                (Parent_Type,
6918                 Build_Discriminant_Constraints
6919                   (Parent_Type,
6920                    Subtype_Indication (Type_Definition (N)), True));
6921         end if;
6922
6923         End_Scope;
6924
6925      elsif Constraint_Present then
6926
6927         --  Build constrained subtype, copying the constraint, and derive
6928         --  from it to create a derived constrained type.
6929
6930         declare
6931            Loc  : constant Source_Ptr := Sloc (N);
6932            Anon : constant Entity_Id :=
6933                     Make_Defining_Identifier (Loc,
6934                       Chars => New_External_Name (Chars (Derived_Type), 'T'));
6935            Decl : Node_Id;
6936
6937         begin
6938            Decl :=
6939              Make_Subtype_Declaration (Loc,
6940                Defining_Identifier => Anon,
6941                Subtype_Indication =>
6942                  New_Copy_Tree (Subtype_Indication (Type_Definition (N))));
6943            Insert_Before (N, Decl);
6944            Analyze (Decl);
6945
6946            Rewrite (Subtype_Indication (Type_Definition (N)),
6947              New_Occurrence_Of (Anon, Loc));
6948            Set_Analyzed (Derived_Type, False);
6949            Analyze (N);
6950            return;
6951         end;
6952      end if;
6953
6954      --  By default, operations and private data are inherited from parent.
6955      --  However, in the presence of bound discriminants, a new corresponding
6956      --  record will be created, see below.
6957
6958      Set_Has_Discriminants
6959        (Derived_Type, Has_Discriminants         (Parent_Type));
6960      Set_Corresponding_Record_Type
6961        (Derived_Type, Corresponding_Record_Type (Parent_Type));
6962
6963      --  Is_Constrained is set according the parent subtype, but is set to
6964      --  False if the derived type is declared with new discriminants.
6965
6966      Set_Is_Constrained
6967        (Derived_Type,
6968         (Is_Constrained (Parent_Type) or else Constraint_Present)
6969           and then not Present (Discriminant_Specifications (N)));
6970
6971      if Constraint_Present then
6972         if not Has_Discriminants (Parent_Type) then
6973            Error_Msg_N ("untagged parent must have discriminants", N);
6974
6975         elsif Present (Discriminant_Specifications (N)) then
6976
6977            --  Verify that new discriminants are used to constrain old ones
6978
6979            D_Constraint :=
6980              First
6981                (Constraints
6982                  (Constraint (Subtype_Indication (Type_Definition (N)))));
6983
6984            Old_Disc := First_Discriminant (Parent_Type);
6985
6986            while Present (D_Constraint) loop
6987               if Nkind (D_Constraint) /= N_Discriminant_Association then
6988
6989                  --  Positional constraint. If it is a reference to a new
6990                  --  discriminant, it constrains the corresponding old one.
6991
6992                  if Nkind (D_Constraint) = N_Identifier then
6993                     New_Disc := First_Discriminant (Derived_Type);
6994                     while Present (New_Disc) loop
6995                        exit when Chars (New_Disc) = Chars (D_Constraint);
6996                        Next_Discriminant (New_Disc);
6997                     end loop;
6998
6999                     if Present (New_Disc) then
7000                        Set_Corresponding_Discriminant (New_Disc, Old_Disc);
7001                     end if;
7002                  end if;
7003
7004                  Next_Discriminant (Old_Disc);
7005
7006                  --  if this is a named constraint, search by name for the old
7007                  --  discriminants constrained by the new one.
7008
7009               elsif Nkind (Expression (D_Constraint)) = N_Identifier then
7010
7011                  --  Find new discriminant with that name
7012
7013                  New_Disc := First_Discriminant (Derived_Type);
7014                  while Present (New_Disc) loop
7015                     exit when
7016                       Chars (New_Disc) = Chars (Expression (D_Constraint));
7017                     Next_Discriminant (New_Disc);
7018                  end loop;
7019
7020                  if Present (New_Disc) then
7021
7022                     --  Verify that new discriminant renames some discriminant
7023                     --  of the parent type, and associate the new discriminant
7024                     --  with one or more old ones that it renames.
7025
7026                     declare
7027                        Selector : Node_Id;
7028
7029                     begin
7030                        Selector := First (Selector_Names (D_Constraint));
7031                        while Present (Selector) loop
7032                           Old_Disc := First_Discriminant (Parent_Type);
7033                           while Present (Old_Disc) loop
7034                              exit when Chars (Old_Disc) = Chars (Selector);
7035                              Next_Discriminant (Old_Disc);
7036                           end loop;
7037
7038                           if Present (Old_Disc) then
7039                              Set_Corresponding_Discriminant
7040                                (New_Disc, Old_Disc);
7041                           end if;
7042
7043                           Next (Selector);
7044                        end loop;
7045                     end;
7046                  end if;
7047               end if;
7048
7049               Next (D_Constraint);
7050            end loop;
7051
7052            New_Disc := First_Discriminant (Derived_Type);
7053            while Present (New_Disc) loop
7054               if No (Corresponding_Discriminant (New_Disc)) then
7055                  Error_Msg_NE
7056                    ("new discriminant& must constrain old one", N, New_Disc);
7057
7058               elsif not
7059                 Subtypes_Statically_Compatible
7060                   (Etype (New_Disc),
7061                    Etype (Corresponding_Discriminant (New_Disc)))
7062               then
7063                  Error_Msg_NE
7064                    ("& not statically compatible with parent discriminant",
7065                      N, New_Disc);
7066               end if;
7067
7068               Next_Discriminant (New_Disc);
7069            end loop;
7070         end if;
7071
7072      elsif Present (Discriminant_Specifications (N)) then
7073         Error_Msg_N
7074           ("missing discriminant constraint in untagged derivation", N);
7075      end if;
7076
7077      --  The entity chain of the derived type includes the new discriminants
7078      --  but shares operations with the parent.
7079
7080      if Present (Discriminant_Specifications (N)) then
7081         Old_Disc := First_Discriminant (Parent_Type);
7082         while Present (Old_Disc) loop
7083            if No (Next_Entity (Old_Disc))
7084              or else Ekind (Next_Entity (Old_Disc)) /= E_Discriminant
7085            then
7086               Link_Entities
7087                 (Last_Entity (Derived_Type), Next_Entity (Old_Disc));
7088               exit;
7089            end if;
7090
7091            Next_Discriminant (Old_Disc);
7092         end loop;
7093
7094      else
7095         Set_First_Entity (Derived_Type, First_Entity (Parent_Type));
7096         if Has_Discriminants (Parent_Type) then
7097            Set_Is_Constrained (Derived_Type, Is_Constrained (Parent_Type));
7098            Set_Discriminant_Constraint (
7099              Derived_Type, Discriminant_Constraint (Parent_Type));
7100         end if;
7101      end if;
7102
7103      Set_Last_Entity  (Derived_Type, Last_Entity  (Parent_Type));
7104
7105      Set_Has_Completion (Derived_Type);
7106
7107      if Corr_Decl_Needed then
7108         Set_Stored_Constraint (Derived_Type, New_Constraint);
7109         Insert_After (N, Corr_Decl);
7110         Analyze (Corr_Decl);
7111         Set_Corresponding_Record_Type (Derived_Type, Corr_Record);
7112      end if;
7113   end Build_Derived_Concurrent_Type;
7114
7115   ------------------------------------
7116   -- Build_Derived_Enumeration_Type --
7117   ------------------------------------
7118
7119   procedure Build_Derived_Enumeration_Type
7120     (N            : Node_Id;
7121      Parent_Type  : Entity_Id;
7122      Derived_Type : Entity_Id)
7123   is
7124      Loc           : constant Source_Ptr := Sloc (N);
7125      Def           : constant Node_Id    := Type_Definition (N);
7126      Indic         : constant Node_Id    := Subtype_Indication (Def);
7127      Implicit_Base : Entity_Id;
7128      Literal       : Entity_Id;
7129      New_Lit       : Entity_Id;
7130      Literals_List : List_Id;
7131      Type_Decl     : Node_Id;
7132      Hi, Lo        : Node_Id;
7133      Rang_Expr     : Node_Id;
7134
7135   begin
7136      --  Since types Standard.Character and Standard.[Wide_]Wide_Character do
7137      --  not have explicit literals lists we need to process types derived
7138      --  from them specially. This is handled by Derived_Standard_Character.
7139      --  If the parent type is a generic type, there are no literals either,
7140      --  and we construct the same skeletal representation as for the generic
7141      --  parent type.
7142
7143      if Is_Standard_Character_Type (Parent_Type) then
7144         Derived_Standard_Character (N, Parent_Type, Derived_Type);
7145
7146      elsif Is_Generic_Type (Root_Type (Parent_Type)) then
7147         declare
7148            Lo : Node_Id;
7149            Hi : Node_Id;
7150
7151         begin
7152            if Nkind (Indic) /= N_Subtype_Indication then
7153               Lo :=
7154                  Make_Attribute_Reference (Loc,
7155                    Attribute_Name => Name_First,
7156                    Prefix         => New_Occurrence_Of (Derived_Type, Loc));
7157               Set_Etype (Lo, Derived_Type);
7158
7159               Hi :=
7160                  Make_Attribute_Reference (Loc,
7161                    Attribute_Name => Name_Last,
7162                    Prefix         => New_Occurrence_Of (Derived_Type, Loc));
7163               Set_Etype (Hi, Derived_Type);
7164
7165               Set_Scalar_Range (Derived_Type,
7166                  Make_Range (Loc,
7167                    Low_Bound  => Lo,
7168                    High_Bound => Hi));
7169            else
7170
7171               --   Analyze subtype indication and verify compatibility
7172               --   with parent type.
7173
7174               if Base_Type (Process_Subtype (Indic, N)) /=
7175                  Base_Type (Parent_Type)
7176               then
7177                  Error_Msg_N
7178                    ("illegal constraint for formal discrete type", N);
7179               end if;
7180            end if;
7181         end;
7182
7183      else
7184         --  If a constraint is present, analyze the bounds to catch
7185         --  premature usage of the derived literals.
7186
7187         if Nkind (Indic) = N_Subtype_Indication
7188           and then Nkind (Range_Expression (Constraint (Indic))) = N_Range
7189         then
7190            Analyze (Low_Bound  (Range_Expression (Constraint (Indic))));
7191            Analyze (High_Bound (Range_Expression (Constraint (Indic))));
7192         end if;
7193
7194         --  Introduce an implicit base type for the derived type even if there
7195         --  is no constraint attached to it, since this seems closer to the
7196         --  Ada semantics. Build a full type declaration tree for the derived
7197         --  type using the implicit base type as the defining identifier. The
7198         --  build a subtype declaration tree which applies the constraint (if
7199         --  any) have it replace the derived type declaration.
7200
7201         Literal := First_Literal (Parent_Type);
7202         Literals_List := New_List;
7203         while Present (Literal)
7204           and then Ekind (Literal) = E_Enumeration_Literal
7205         loop
7206            --  Literals of the derived type have the same representation as
7207            --  those of the parent type, but this representation can be
7208            --  overridden by an explicit representation clause. Indicate
7209            --  that there is no explicit representation given yet. These
7210            --  derived literals are implicit operations of the new type,
7211            --  and can be overridden by explicit ones.
7212
7213            if Nkind (Literal) = N_Defining_Character_Literal then
7214               New_Lit :=
7215                 Make_Defining_Character_Literal (Loc, Chars (Literal));
7216            else
7217               New_Lit := Make_Defining_Identifier (Loc, Chars (Literal));
7218            end if;
7219
7220            Set_Ekind                (New_Lit, E_Enumeration_Literal);
7221            Set_Enumeration_Pos      (New_Lit, Enumeration_Pos (Literal));
7222            Set_Enumeration_Rep      (New_Lit, Enumeration_Rep (Literal));
7223            Set_Enumeration_Rep_Expr (New_Lit, Empty);
7224            Set_Alias                (New_Lit, Literal);
7225            Set_Is_Known_Valid       (New_Lit, True);
7226
7227            Append (New_Lit, Literals_List);
7228            Next_Literal (Literal);
7229         end loop;
7230
7231         Implicit_Base :=
7232           Make_Defining_Identifier (Sloc (Derived_Type),
7233             Chars => New_External_Name (Chars (Derived_Type), 'B'));
7234
7235         --  Indicate the proper nature of the derived type. This must be done
7236         --  before analysis of the literals, to recognize cases when a literal
7237         --  may be hidden by a previous explicit function definition (cf.
7238         --  c83031a).
7239
7240         Set_Ekind (Derived_Type, E_Enumeration_Subtype);
7241         Set_Etype (Derived_Type, Implicit_Base);
7242
7243         Type_Decl :=
7244           Make_Full_Type_Declaration (Loc,
7245             Defining_Identifier => Implicit_Base,
7246             Discriminant_Specifications => No_List,
7247             Type_Definition =>
7248               Make_Enumeration_Type_Definition (Loc, Literals_List));
7249
7250         Mark_Rewrite_Insertion (Type_Decl);
7251         Insert_Before (N, Type_Decl);
7252         Analyze (Type_Decl);
7253
7254         --  The anonymous base now has a full declaration, but this base
7255         --  is not a first subtype.
7256
7257         Set_Is_First_Subtype (Implicit_Base, False);
7258
7259         --  After the implicit base is analyzed its Etype needs to be changed
7260         --  to reflect the fact that it is derived from the parent type which
7261         --  was ignored during analysis. We also set the size at this point.
7262
7263         Set_Etype (Implicit_Base, Parent_Type);
7264
7265         Set_Size_Info      (Implicit_Base,                 Parent_Type);
7266         Set_RM_Size        (Implicit_Base, RM_Size        (Parent_Type));
7267         Set_First_Rep_Item (Implicit_Base, First_Rep_Item (Parent_Type));
7268
7269         --  Copy other flags from parent type
7270
7271         Set_Has_Non_Standard_Rep
7272                            (Implicit_Base, Has_Non_Standard_Rep
7273                                                           (Parent_Type));
7274         Set_Has_Pragma_Ordered
7275                            (Implicit_Base, Has_Pragma_Ordered
7276                                                           (Parent_Type));
7277         Set_Has_Delayed_Freeze (Implicit_Base);
7278
7279         --  Process the subtype indication including a validation check on the
7280         --  constraint, if any. If a constraint is given, its bounds must be
7281         --  implicitly converted to the new type.
7282
7283         if Nkind (Indic) = N_Subtype_Indication then
7284            declare
7285               R : constant Node_Id :=
7286                     Range_Expression (Constraint (Indic));
7287
7288            begin
7289               if Nkind (R) = N_Range then
7290                  Hi := Build_Scalar_Bound
7291                          (High_Bound (R), Parent_Type, Implicit_Base);
7292                  Lo := Build_Scalar_Bound
7293                          (Low_Bound  (R), Parent_Type, Implicit_Base);
7294
7295               else
7296                  --  Constraint is a Range attribute. Replace with explicit
7297                  --  mention of the bounds of the prefix, which must be a
7298                  --  subtype.
7299
7300                  Analyze (Prefix (R));
7301                  Hi :=
7302                    Convert_To (Implicit_Base,
7303                      Make_Attribute_Reference (Loc,
7304                        Attribute_Name => Name_Last,
7305                        Prefix =>
7306                          New_Occurrence_Of (Entity (Prefix (R)), Loc)));
7307
7308                  Lo :=
7309                    Convert_To (Implicit_Base,
7310                      Make_Attribute_Reference (Loc,
7311                        Attribute_Name => Name_First,
7312                        Prefix =>
7313                          New_Occurrence_Of (Entity (Prefix (R)), Loc)));
7314               end if;
7315            end;
7316
7317         else
7318            Hi :=
7319              Build_Scalar_Bound
7320                (Type_High_Bound (Parent_Type),
7321                 Parent_Type, Implicit_Base);
7322            Lo :=
7323               Build_Scalar_Bound
7324                 (Type_Low_Bound (Parent_Type),
7325                  Parent_Type, Implicit_Base);
7326         end if;
7327
7328         Rang_Expr :=
7329           Make_Range (Loc,
7330             Low_Bound  => Lo,
7331             High_Bound => Hi);
7332
7333         --  If we constructed a default range for the case where no range
7334         --  was given, then the expressions in the range must not freeze
7335         --  since they do not correspond to expressions in the source.
7336         --  However, if the type inherits predicates the expressions will
7337         --  be elaborated earlier and must freeze.
7338
7339         if Nkind (Indic) /= N_Subtype_Indication
7340           and then not Has_Predicates (Derived_Type)
7341         then
7342            Set_Must_Not_Freeze (Lo);
7343            Set_Must_Not_Freeze (Hi);
7344            Set_Must_Not_Freeze (Rang_Expr);
7345         end if;
7346
7347         Rewrite (N,
7348           Make_Subtype_Declaration (Loc,
7349             Defining_Identifier => Derived_Type,
7350             Subtype_Indication =>
7351               Make_Subtype_Indication (Loc,
7352                 Subtype_Mark => New_Occurrence_Of (Implicit_Base, Loc),
7353                 Constraint =>
7354                   Make_Range_Constraint (Loc,
7355                     Range_Expression => Rang_Expr))));
7356
7357         Analyze (N);
7358
7359         --  Propagate the aspects from the original type declaration to the
7360         --  declaration of the implicit base.
7361
7362         Move_Aspects (From => Original_Node (N), To => Type_Decl);
7363
7364         --  Apply a range check. Since this range expression doesn't have an
7365         --  Etype, we have to specifically pass the Source_Typ parameter. Is
7366         --  this right???
7367
7368         if Nkind (Indic) = N_Subtype_Indication then
7369            Apply_Range_Check
7370              (Range_Expression (Constraint (Indic)), Parent_Type,
7371               Source_Typ => Entity (Subtype_Mark (Indic)));
7372         end if;
7373      end if;
7374   end Build_Derived_Enumeration_Type;
7375
7376   --------------------------------
7377   -- Build_Derived_Numeric_Type --
7378   --------------------------------
7379
7380   procedure Build_Derived_Numeric_Type
7381     (N            : Node_Id;
7382      Parent_Type  : Entity_Id;
7383      Derived_Type : Entity_Id)
7384   is
7385      Loc           : constant Source_Ptr := Sloc (N);
7386      Tdef          : constant Node_Id    := Type_Definition (N);
7387      Indic         : constant Node_Id    := Subtype_Indication (Tdef);
7388      Parent_Base   : constant Entity_Id  := Base_Type (Parent_Type);
7389      No_Constraint : constant Boolean    := Nkind (Indic) /=
7390                                                  N_Subtype_Indication;
7391      Implicit_Base : Entity_Id;
7392
7393      Lo : Node_Id;
7394      Hi : Node_Id;
7395
7396   begin
7397      --  Process the subtype indication including a validation check on
7398      --  the constraint if any.
7399
7400      Discard_Node (Process_Subtype (Indic, N));
7401
7402      --  Introduce an implicit base type for the derived type even if there
7403      --  is no constraint attached to it, since this seems closer to the Ada
7404      --  semantics.
7405
7406      Implicit_Base :=
7407        Create_Itype (Ekind (Parent_Base), N, Derived_Type, 'B');
7408
7409      Set_Etype          (Implicit_Base, Parent_Base);
7410      Set_Ekind          (Implicit_Base, Ekind          (Parent_Base));
7411      Set_Size_Info      (Implicit_Base,                 Parent_Base);
7412      Set_First_Rep_Item (Implicit_Base, First_Rep_Item (Parent_Base));
7413      Set_Parent         (Implicit_Base, Parent (Derived_Type));
7414      Set_Is_Known_Valid (Implicit_Base, Is_Known_Valid (Parent_Base));
7415
7416      --  Set RM Size for discrete type or decimal fixed-point type
7417      --  Ordinary fixed-point is excluded, why???
7418
7419      if Is_Discrete_Type (Parent_Base)
7420        or else Is_Decimal_Fixed_Point_Type (Parent_Base)
7421      then
7422         Set_RM_Size (Implicit_Base, RM_Size (Parent_Base));
7423      end if;
7424
7425      Set_Has_Delayed_Freeze (Implicit_Base);
7426
7427      Lo := New_Copy_Tree (Type_Low_Bound  (Parent_Base));
7428      Hi := New_Copy_Tree (Type_High_Bound (Parent_Base));
7429
7430      Set_Scalar_Range (Implicit_Base,
7431        Make_Range (Loc,
7432          Low_Bound  => Lo,
7433          High_Bound => Hi));
7434
7435      if Has_Infinities (Parent_Base) then
7436         Set_Includes_Infinities (Scalar_Range (Implicit_Base));
7437      end if;
7438
7439      --  The Derived_Type, which is the entity of the declaration, is a
7440      --  subtype of the implicit base. Its Ekind is a subtype, even in the
7441      --  absence of an explicit constraint.
7442
7443      Set_Etype (Derived_Type, Implicit_Base);
7444
7445      --  If we did not have a constraint, then the Ekind is set from the
7446      --  parent type (otherwise Process_Subtype has set the bounds)
7447
7448      if No_Constraint then
7449         Set_Ekind (Derived_Type, Subtype_Kind (Ekind (Parent_Type)));
7450      end if;
7451
7452      --  If we did not have a range constraint, then set the range from the
7453      --  parent type. Otherwise, the Process_Subtype call has set the bounds.
7454
7455      if No_Constraint or else not Has_Range_Constraint (Indic) then
7456         Set_Scalar_Range (Derived_Type,
7457           Make_Range (Loc,
7458             Low_Bound  => New_Copy_Tree (Type_Low_Bound  (Parent_Type)),
7459             High_Bound => New_Copy_Tree (Type_High_Bound (Parent_Type))));
7460         Set_Is_Constrained (Derived_Type, Is_Constrained (Parent_Type));
7461
7462         if Has_Infinities (Parent_Type) then
7463            Set_Includes_Infinities (Scalar_Range (Derived_Type));
7464         end if;
7465
7466         Set_Is_Known_Valid (Derived_Type, Is_Known_Valid (Parent_Type));
7467      end if;
7468
7469      Set_Is_Descendant_Of_Address (Derived_Type,
7470        Is_Descendant_Of_Address (Parent_Type));
7471      Set_Is_Descendant_Of_Address (Implicit_Base,
7472        Is_Descendant_Of_Address (Parent_Type));
7473
7474      --  Set remaining type-specific fields, depending on numeric type
7475
7476      if Is_Modular_Integer_Type (Parent_Type) then
7477         Set_Modulus (Implicit_Base, Modulus (Parent_Base));
7478
7479         Set_Non_Binary_Modulus
7480           (Implicit_Base, Non_Binary_Modulus (Parent_Base));
7481
7482         Set_Is_Known_Valid
7483           (Implicit_Base, Is_Known_Valid (Parent_Base));
7484
7485      elsif Is_Floating_Point_Type (Parent_Type) then
7486
7487         --  Digits of base type is always copied from the digits value of
7488         --  the parent base type, but the digits of the derived type will
7489         --  already have been set if there was a constraint present.
7490
7491         Set_Digits_Value (Implicit_Base, Digits_Value (Parent_Base));
7492         Set_Float_Rep    (Implicit_Base, Float_Rep    (Parent_Base));
7493
7494         if No_Constraint then
7495            Set_Digits_Value (Derived_Type, Digits_Value (Parent_Type));
7496         end if;
7497
7498      elsif Is_Fixed_Point_Type (Parent_Type) then
7499
7500         --  Small of base type and derived type are always copied from the
7501         --  parent base type, since smalls never change. The delta of the
7502         --  base type is also copied from the parent base type. However the
7503         --  delta of the derived type will have been set already if a
7504         --  constraint was present.
7505
7506         Set_Small_Value (Derived_Type,  Small_Value (Parent_Base));
7507         Set_Small_Value (Implicit_Base, Small_Value (Parent_Base));
7508         Set_Delta_Value (Implicit_Base, Delta_Value (Parent_Base));
7509
7510         if No_Constraint then
7511            Set_Delta_Value (Derived_Type,  Delta_Value (Parent_Type));
7512         end if;
7513
7514         --  The scale and machine radix in the decimal case are always
7515         --  copied from the parent base type.
7516
7517         if Is_Decimal_Fixed_Point_Type (Parent_Type) then
7518            Set_Scale_Value (Derived_Type,  Scale_Value (Parent_Base));
7519            Set_Scale_Value (Implicit_Base, Scale_Value (Parent_Base));
7520
7521            Set_Machine_Radix_10
7522              (Derived_Type,  Machine_Radix_10 (Parent_Base));
7523            Set_Machine_Radix_10
7524              (Implicit_Base, Machine_Radix_10 (Parent_Base));
7525
7526            Set_Digits_Value (Implicit_Base, Digits_Value (Parent_Base));
7527
7528            if No_Constraint then
7529               Set_Digits_Value (Derived_Type, Digits_Value (Parent_Base));
7530
7531            else
7532               --  the analysis of the subtype_indication sets the
7533               --  digits value of the derived type.
7534
7535               null;
7536            end if;
7537         end if;
7538      end if;
7539
7540      if Is_Integer_Type (Parent_Type) then
7541         Set_Has_Shift_Operator
7542           (Implicit_Base, Has_Shift_Operator (Parent_Type));
7543      end if;
7544
7545      --  The type of the bounds is that of the parent type, and they
7546      --  must be converted to the derived type.
7547
7548      Convert_Scalar_Bounds (N, Parent_Type, Derived_Type, Loc);
7549
7550      --  The implicit_base should be frozen when the derived type is frozen,
7551      --  but note that it is used in the conversions of the bounds. For fixed
7552      --  types we delay the determination of the bounds until the proper
7553      --  freezing point. For other numeric types this is rejected by GCC, for
7554      --  reasons that are currently unclear (???), so we choose to freeze the
7555      --  implicit base now. In the case of integers and floating point types
7556      --  this is harmless because subsequent representation clauses cannot
7557      --  affect anything, but it is still baffling that we cannot use the
7558      --  same mechanism for all derived numeric types.
7559
7560      --  There is a further complication: actually some representation
7561      --  clauses can affect the implicit base type. For example, attribute
7562      --  definition clauses for stream-oriented attributes need to set the
7563      --  corresponding TSS entries on the base type, and this normally
7564      --  cannot be done after the base type is frozen, so the circuitry in
7565      --  Sem_Ch13.New_Stream_Subprogram must account for this possibility
7566      --  and not use Set_TSS in this case.
7567
7568      --  There are also consequences for the case of delayed representation
7569      --  aspects for some cases. For example, a Size aspect is delayed and
7570      --  should not be evaluated to the freeze point. This early freezing
7571      --  means that the size attribute evaluation happens too early???
7572
7573      if Is_Fixed_Point_Type (Parent_Type) then
7574         Conditional_Delay (Implicit_Base, Parent_Type);
7575      else
7576         Freeze_Before (N, Implicit_Base);
7577      end if;
7578   end Build_Derived_Numeric_Type;
7579
7580   --------------------------------
7581   -- Build_Derived_Private_Type --
7582   --------------------------------
7583
7584   procedure Build_Derived_Private_Type
7585     (N             : Node_Id;
7586      Parent_Type   : Entity_Id;
7587      Derived_Type  : Entity_Id;
7588      Is_Completion : Boolean;
7589      Derive_Subps  : Boolean := True)
7590   is
7591      Loc       : constant Source_Ptr := Sloc (N);
7592      Par_Base  : constant Entity_Id  := Base_Type (Parent_Type);
7593      Par_Scope : constant Entity_Id  := Scope (Par_Base);
7594      Full_N    : constant Node_Id    := New_Copy_Tree (N);
7595      Full_Der  : Entity_Id           := New_Copy (Derived_Type);
7596      Full_P    : Entity_Id;
7597
7598      procedure Build_Full_Derivation;
7599      --  Build full derivation, i.e. derive from the full view
7600
7601      procedure Copy_And_Build;
7602      --  Copy derived type declaration, replace parent with its full view,
7603      --  and build derivation
7604
7605      ---------------------------
7606      -- Build_Full_Derivation --
7607      ---------------------------
7608
7609      procedure Build_Full_Derivation is
7610      begin
7611         --  If parent scope is not open, install the declarations
7612
7613         if not In_Open_Scopes (Par_Scope) then
7614            Install_Private_Declarations (Par_Scope);
7615            Install_Visible_Declarations (Par_Scope);
7616            Copy_And_Build;
7617            Uninstall_Declarations (Par_Scope);
7618
7619         --  If parent scope is open and in another unit, and parent has a
7620         --  completion, then the derivation is taking place in the visible
7621         --  part of a child unit. In that case retrieve the full view of
7622         --  the parent momentarily.
7623
7624         elsif not In_Same_Source_Unit (N, Parent_Type) then
7625            Full_P := Full_View (Parent_Type);
7626            Exchange_Declarations (Parent_Type);
7627            Copy_And_Build;
7628            Exchange_Declarations (Full_P);
7629
7630         --  Otherwise it is a local derivation
7631
7632         else
7633            Copy_And_Build;
7634         end if;
7635      end Build_Full_Derivation;
7636
7637      --------------------
7638      -- Copy_And_Build --
7639      --------------------
7640
7641      procedure Copy_And_Build is
7642         Full_Parent : Entity_Id := Parent_Type;
7643
7644      begin
7645         --  If the parent is itself derived from another private type,
7646         --  installing the private declarations has not affected its
7647         --  privacy status, so use its own full view explicitly.
7648
7649         if Is_Private_Type (Full_Parent)
7650           and then Present (Full_View (Full_Parent))
7651         then
7652            Full_Parent := Full_View (Full_Parent);
7653         end if;
7654
7655         --  And its underlying full view if necessary
7656
7657         if Is_Private_Type (Full_Parent)
7658           and then Present (Underlying_Full_View (Full_Parent))
7659         then
7660            Full_Parent := Underlying_Full_View (Full_Parent);
7661         end if;
7662
7663         --  For record, access and most enumeration types, derivation from
7664         --  the full view requires a fully-fledged declaration. In the other
7665         --  cases, just use an itype.
7666
7667         if Ekind (Full_Parent) in Record_Kind
7668           or else Ekind (Full_Parent) in Access_Kind
7669           or else
7670             (Ekind (Full_Parent) in Enumeration_Kind
7671               and then not Is_Standard_Character_Type (Full_Parent)
7672               and then not Is_Generic_Type (Root_Type (Full_Parent)))
7673         then
7674            --  Copy and adjust declaration to provide a completion for what
7675            --  is originally a private declaration. Indicate that full view
7676            --  is internally generated.
7677
7678            Set_Comes_From_Source (Full_N, False);
7679            Set_Comes_From_Source (Full_Der, False);
7680            Set_Parent (Full_Der, Full_N);
7681            Set_Defining_Identifier (Full_N, Full_Der);
7682
7683            --  If there are no constraints, adjust the subtype mark
7684
7685            if Nkind (Subtype_Indication (Type_Definition (Full_N))) /=
7686                                                       N_Subtype_Indication
7687            then
7688               Set_Subtype_Indication
7689                 (Type_Definition (Full_N),
7690                  New_Occurrence_Of (Full_Parent, Sloc (Full_N)));
7691            end if;
7692
7693            Insert_After (N, Full_N);
7694
7695            --  Build full view of derived type from full view of parent which
7696            --  is now installed. Subprograms have been derived on the partial
7697            --  view, the completion does not derive them anew.
7698
7699            if Ekind (Full_Parent) in Record_Kind then
7700
7701               --  If parent type is tagged, the completion inherits the proper
7702               --  primitive operations.
7703
7704               if Is_Tagged_Type (Parent_Type) then
7705                  Build_Derived_Record_Type
7706                    (Full_N, Full_Parent, Full_Der, Derive_Subps);
7707               else
7708                  Build_Derived_Record_Type
7709                    (Full_N, Full_Parent, Full_Der, Derive_Subps => False);
7710               end if;
7711
7712            else
7713               Build_Derived_Type
7714                 (Full_N, Full_Parent, Full_Der,
7715                  Is_Completion => False, Derive_Subps => False);
7716            end if;
7717
7718            --  The full declaration has been introduced into the tree and
7719            --  processed in the step above. It should not be analyzed again
7720            --  (when encountered later in the current list of declarations)
7721            --  to prevent spurious name conflicts. The full entity remains
7722            --  invisible.
7723
7724            Set_Analyzed (Full_N);
7725
7726         else
7727            Full_Der :=
7728              Make_Defining_Identifier (Sloc (Derived_Type),
7729                Chars => Chars (Derived_Type));
7730            Set_Is_Itype (Full_Der);
7731            Set_Associated_Node_For_Itype (Full_Der, N);
7732            Set_Parent (Full_Der, N);
7733            Build_Derived_Type
7734              (N, Full_Parent, Full_Der,
7735               Is_Completion => False, Derive_Subps => False);
7736         end if;
7737
7738         Set_Has_Private_Declaration (Full_Der);
7739         Set_Has_Private_Declaration (Derived_Type);
7740
7741         Set_Scope                (Full_Der, Scope (Derived_Type));
7742         Set_Is_First_Subtype     (Full_Der, Is_First_Subtype (Derived_Type));
7743         Set_Has_Size_Clause      (Full_Der, False);
7744         Set_Has_Alignment_Clause (Full_Der, False);
7745         Set_Has_Delayed_Freeze   (Full_Der);
7746         Set_Is_Frozen            (Full_Der, False);
7747         Set_Freeze_Node          (Full_Der, Empty);
7748         Set_Depends_On_Private   (Full_Der, Has_Private_Component (Full_Der));
7749         Set_Is_Public            (Full_Der, Is_Public (Derived_Type));
7750
7751         --  The convention on the base type may be set in the private part
7752         --  and not propagated to the subtype until later, so we obtain the
7753         --  convention from the base type of the parent.
7754
7755         Set_Convention (Full_Der, Convention (Base_Type (Full_Parent)));
7756      end Copy_And_Build;
7757
7758   --  Start of processing for Build_Derived_Private_Type
7759
7760   begin
7761      if Is_Tagged_Type (Parent_Type) then
7762         Full_P := Full_View (Parent_Type);
7763
7764         --  A type extension of a type with unknown discriminants is an
7765         --  indefinite type that the back-end cannot handle directly.
7766         --  We treat it as a private type, and build a completion that is
7767         --  derived from the full view of the parent, and hopefully has
7768         --  known discriminants.
7769
7770         --  If the full view of the parent type has an underlying record view,
7771         --  use it to generate the underlying record view of this derived type
7772         --  (required for chains of derivations with unknown discriminants).
7773
7774         --  Minor optimization: we avoid the generation of useless underlying
7775         --  record view entities if the private type declaration has unknown
7776         --  discriminants but its corresponding full view has no
7777         --  discriminants.
7778
7779         if Has_Unknown_Discriminants (Parent_Type)
7780           and then Present (Full_P)
7781           and then (Has_Discriminants (Full_P)
7782                      or else Present (Underlying_Record_View (Full_P)))
7783           and then not In_Open_Scopes (Par_Scope)
7784           and then Expander_Active
7785         then
7786            declare
7787               Full_Der : constant Entity_Id := Make_Temporary (Loc, 'T');
7788               New_Ext  : constant Node_Id :=
7789                            Copy_Separate_Tree
7790                              (Record_Extension_Part (Type_Definition (N)));
7791               Decl     : Node_Id;
7792
7793            begin
7794               Build_Derived_Record_Type
7795                 (N, Parent_Type, Derived_Type, Derive_Subps);
7796
7797               --  Build anonymous completion, as a derivation from the full
7798               --  view of the parent. This is not a completion in the usual
7799               --  sense, because the current type is not private.
7800
7801               Decl :=
7802                 Make_Full_Type_Declaration (Loc,
7803                   Defining_Identifier => Full_Der,
7804                   Type_Definition     =>
7805                     Make_Derived_Type_Definition (Loc,
7806                       Subtype_Indication =>
7807                         New_Copy_Tree
7808                           (Subtype_Indication (Type_Definition (N))),
7809                       Record_Extension_Part => New_Ext));
7810
7811               --  If the parent type has an underlying record view, use it
7812               --  here to build the new underlying record view.
7813
7814               if Present (Underlying_Record_View (Full_P)) then
7815                  pragma Assert
7816                    (Nkind (Subtype_Indication (Type_Definition (Decl)))
7817                       = N_Identifier);
7818                  Set_Entity (Subtype_Indication (Type_Definition (Decl)),
7819                    Underlying_Record_View (Full_P));
7820               end if;
7821
7822               Install_Private_Declarations (Par_Scope);
7823               Install_Visible_Declarations (Par_Scope);
7824               Insert_Before (N, Decl);
7825
7826               --  Mark entity as an underlying record view before analysis,
7827               --  to avoid generating the list of its primitive operations
7828               --  (which is not really required for this entity) and thus
7829               --  prevent spurious errors associated with missing overriding
7830               --  of abstract primitives (overridden only for Derived_Type).
7831
7832               Set_Ekind (Full_Der, E_Record_Type);
7833               Set_Is_Underlying_Record_View (Full_Der);
7834               Set_Default_SSO (Full_Der);
7835               Set_No_Reordering (Full_Der, No_Component_Reordering);
7836
7837               Analyze (Decl);
7838
7839               pragma Assert (Has_Discriminants (Full_Der)
7840                 and then not Has_Unknown_Discriminants (Full_Der));
7841
7842               Uninstall_Declarations (Par_Scope);
7843
7844               --  Freeze the underlying record view, to prevent generation of
7845               --  useless dispatching information, which is simply shared with
7846               --  the real derived type.
7847
7848               Set_Is_Frozen (Full_Der);
7849
7850               --  If the derived type has access discriminants, create
7851               --  references to their anonymous types now, to prevent
7852               --  back-end problems when their first use is in generated
7853               --  bodies of primitives.
7854
7855               declare
7856                  E : Entity_Id;
7857
7858               begin
7859                  E := First_Entity (Full_Der);
7860
7861                  while Present (E) loop
7862                     if Ekind (E) = E_Discriminant
7863                       and then Ekind (Etype (E)) = E_Anonymous_Access_Type
7864                     then
7865                        Build_Itype_Reference (Etype (E), Decl);
7866                     end if;
7867
7868                     Next_Entity (E);
7869                  end loop;
7870               end;
7871
7872               --  Set up links between real entity and underlying record view
7873
7874               Set_Underlying_Record_View (Derived_Type, Base_Type (Full_Der));
7875               Set_Underlying_Record_View (Base_Type (Full_Der), Derived_Type);
7876            end;
7877
7878         --  If discriminants are known, build derived record
7879
7880         else
7881            Build_Derived_Record_Type
7882              (N, Parent_Type, Derived_Type, Derive_Subps);
7883         end if;
7884
7885         return;
7886
7887      elsif Has_Discriminants (Parent_Type) then
7888
7889         --  Build partial view of derived type from partial view of parent.
7890         --  This must be done before building the full derivation because the
7891         --  second derivation will modify the discriminants of the first and
7892         --  the discriminants are chained with the rest of the components in
7893         --  the full derivation.
7894
7895         Build_Derived_Record_Type
7896           (N, Parent_Type, Derived_Type, Derive_Subps);
7897
7898         --  Build the full derivation if this is not the anonymous derived
7899         --  base type created by Build_Derived_Record_Type in the constrained
7900         --  case (see point 5. of its head comment) since we build it for the
7901         --  derived subtype. And skip it for synchronized types altogether, as
7902         --  gigi does not use these types directly.
7903
7904         if Present (Full_View (Parent_Type))
7905           and then not Is_Itype (Derived_Type)
7906           and then not Is_Concurrent_Type (Full_View (Parent_Type))
7907         then
7908            declare
7909               Der_Base   : constant Entity_Id := Base_Type (Derived_Type);
7910               Discr      : Entity_Id;
7911               Last_Discr : Entity_Id;
7912
7913            begin
7914               --  If this is not a completion, construct the implicit full
7915               --  view by deriving from the full view of the parent type.
7916               --  But if this is a completion, the derived private type
7917               --  being built is a full view and the full derivation can
7918               --  only be its underlying full view.
7919
7920               Build_Full_Derivation;
7921
7922               if not Is_Completion then
7923                  Set_Full_View (Derived_Type, Full_Der);
7924               else
7925                  Set_Underlying_Full_View (Derived_Type, Full_Der);
7926                  Set_Is_Underlying_Full_View (Full_Der);
7927               end if;
7928
7929               if not Is_Base_Type (Derived_Type) then
7930                  Set_Full_View (Der_Base, Base_Type (Full_Der));
7931               end if;
7932
7933               --  Copy the discriminant list from full view to the partial
7934               --  view (base type and its subtype). Gigi requires that the
7935               --  partial and full views have the same discriminants.
7936
7937               --  Note that since the partial view points to discriminants
7938               --  in the full view, their scope will be that of the full
7939               --  view. This might cause some front end problems and need
7940               --  adjustment???
7941
7942               Discr := First_Discriminant (Base_Type (Full_Der));
7943               Set_First_Entity (Der_Base, Discr);
7944
7945               loop
7946                  Last_Discr := Discr;
7947                  Next_Discriminant (Discr);
7948                  exit when No (Discr);
7949               end loop;
7950
7951               Set_Last_Entity (Der_Base, Last_Discr);
7952               Set_First_Entity (Derived_Type, First_Entity (Der_Base));
7953               Set_Last_Entity  (Derived_Type, Last_Entity  (Der_Base));
7954            end;
7955         end if;
7956
7957      elsif Present (Full_View (Parent_Type))
7958        and then Has_Discriminants (Full_View (Parent_Type))
7959      then
7960         if Has_Unknown_Discriminants (Parent_Type)
7961           and then Nkind (Subtype_Indication (Type_Definition (N))) =
7962                                                         N_Subtype_Indication
7963         then
7964            Error_Msg_N
7965              ("cannot constrain type with unknown discriminants",
7966               Subtype_Indication (Type_Definition (N)));
7967            return;
7968         end if;
7969
7970         --  If this is not a completion, construct the implicit full view by
7971         --  deriving from the full view of the parent type. But if this is a
7972         --  completion, the derived private type being built is a full view
7973         --  and the full derivation can only be its underlying full view.
7974
7975         Build_Full_Derivation;
7976
7977         if not Is_Completion then
7978            Set_Full_View (Derived_Type, Full_Der);
7979         else
7980            Set_Underlying_Full_View (Derived_Type, Full_Der);
7981            Set_Is_Underlying_Full_View (Full_Der);
7982         end if;
7983
7984         --  In any case, the primitive operations are inherited from the
7985         --  parent type, not from the internal full view.
7986
7987         Set_Etype (Base_Type (Derived_Type), Base_Type (Parent_Type));
7988
7989         if Derive_Subps then
7990            Derive_Subprograms (Parent_Type, Derived_Type);
7991         end if;
7992
7993         Set_Stored_Constraint (Derived_Type, No_Elist);
7994         Set_Is_Constrained
7995           (Derived_Type, Is_Constrained (Full_View (Parent_Type)));
7996
7997      else
7998         --  Untagged type, No discriminants on either view
7999
8000         if Nkind (Subtype_Indication (Type_Definition (N))) =
8001                                                   N_Subtype_Indication
8002         then
8003            Error_Msg_N
8004              ("illegal constraint on type without discriminants", N);
8005         end if;
8006
8007         if Present (Discriminant_Specifications (N))
8008           and then Present (Full_View (Parent_Type))
8009           and then not Is_Tagged_Type (Full_View (Parent_Type))
8010         then
8011            Error_Msg_N ("cannot add discriminants to untagged type", N);
8012         end if;
8013
8014         Set_Stored_Constraint (Derived_Type, No_Elist);
8015         Set_Is_Constrained    (Derived_Type, Is_Constrained (Parent_Type));
8016
8017         Set_Is_Controlled_Active
8018           (Derived_Type, Is_Controlled_Active     (Parent_Type));
8019
8020         Set_Disable_Controlled
8021           (Derived_Type, Disable_Controlled       (Parent_Type));
8022
8023         Set_Has_Controlled_Component
8024           (Derived_Type, Has_Controlled_Component (Parent_Type));
8025
8026         --  Direct controlled types do not inherit Finalize_Storage_Only flag
8027
8028         if not Is_Controlled (Parent_Type) then
8029            Set_Finalize_Storage_Only
8030              (Base_Type (Derived_Type), Finalize_Storage_Only (Parent_Type));
8031         end if;
8032
8033         --  If this is not a completion, construct the implicit full view by
8034         --  deriving from the full view of the parent type.
8035
8036         --  ??? If the parent is untagged private and its completion is
8037         --  tagged, this mechanism will not work because we cannot derive from
8038         --  the tagged full view unless we have an extension.
8039
8040         if Present (Full_View (Parent_Type))
8041           and then not Is_Tagged_Type (Full_View (Parent_Type))
8042           and then not Is_Completion
8043         then
8044            Build_Full_Derivation;
8045            Set_Full_View (Derived_Type, Full_Der);
8046         end if;
8047      end if;
8048
8049      Set_Has_Unknown_Discriminants (Derived_Type,
8050        Has_Unknown_Discriminants (Parent_Type));
8051
8052      if Is_Private_Type (Derived_Type) then
8053         Set_Private_Dependents (Derived_Type, New_Elmt_List);
8054      end if;
8055
8056      --  If the parent base type is in scope, add the derived type to its
8057      --  list of private dependents, because its full view may become
8058      --  visible subsequently (in a nested private part, a body, or in a
8059      --  further child unit).
8060
8061      if Is_Private_Type (Par_Base) and then In_Open_Scopes (Par_Scope) then
8062         Append_Elmt (Derived_Type, Private_Dependents (Parent_Type));
8063
8064         --  Check for unusual case where a type completed by a private
8065         --  derivation occurs within a package nested in a child unit, and
8066         --  the parent is declared in an ancestor.
8067
8068         if Is_Child_Unit (Scope (Current_Scope))
8069           and then Is_Completion
8070           and then In_Private_Part (Current_Scope)
8071           and then Scope (Parent_Type) /= Current_Scope
8072
8073           --  Note that if the parent has a completion in the private part,
8074           --  (which is itself a derivation from some other private type)
8075           --  it is that completion that is visible, there is no full view
8076           --  available, and no special processing is needed.
8077
8078           and then Present (Full_View (Parent_Type))
8079         then
8080            --  In this case, the full view of the parent type will become
8081            --  visible in the body of the enclosing child, and only then will
8082            --  the current type be possibly non-private. Build an underlying
8083            --  full view that will be installed when the enclosing child body
8084            --  is compiled.
8085
8086            if Present (Underlying_Full_View (Derived_Type)) then
8087               Full_Der := Underlying_Full_View (Derived_Type);
8088            else
8089               Build_Full_Derivation;
8090               Set_Underlying_Full_View (Derived_Type, Full_Der);
8091               Set_Is_Underlying_Full_View (Full_Der);
8092            end if;
8093
8094            --  The full view will be used to swap entities on entry/exit to
8095            --  the body, and must appear in the entity list for the package.
8096
8097            Append_Entity (Full_Der, Scope (Derived_Type));
8098         end if;
8099      end if;
8100   end Build_Derived_Private_Type;
8101
8102   -------------------------------
8103   -- Build_Derived_Record_Type --
8104   -------------------------------
8105
8106   --  1. INTRODUCTION
8107
8108   --  Ideally we would like to use the same model of type derivation for
8109   --  tagged and untagged record types. Unfortunately this is not quite
8110   --  possible because the semantics of representation clauses is different
8111   --  for tagged and untagged records under inheritance. Consider the
8112   --  following:
8113
8114   --     type R (...) is [tagged] record ... end record;
8115   --     type T (...) is new R (...) [with ...];
8116
8117   --  The representation clauses for T can specify a completely different
8118   --  record layout from R's. Hence the same component can be placed in two
8119   --  very different positions in objects of type T and R. If R and T are
8120   --  tagged types, representation clauses for T can only specify the layout
8121   --  of non inherited components, thus components that are common in R and T
8122   --  have the same position in objects of type R and T.
8123
8124   --  This has two implications. The first is that the entire tree for R's
8125   --  declaration needs to be copied for T in the untagged case, so that T
8126   --  can be viewed as a record type of its own with its own representation
8127   --  clauses. The second implication is the way we handle discriminants.
8128   --  Specifically, in the untagged case we need a way to communicate to Gigi
8129   --  what are the real discriminants in the record, while for the semantics
8130   --  we need to consider those introduced by the user to rename the
8131   --  discriminants in the parent type. This is handled by introducing the
8132   --  notion of stored discriminants. See below for more.
8133
8134   --  Fortunately the way regular components are inherited can be handled in
8135   --  the same way in tagged and untagged types.
8136
8137   --  To complicate things a bit more the private view of a private extension
8138   --  cannot be handled in the same way as the full view (for one thing the
8139   --  semantic rules are somewhat different). We will explain what differs
8140   --  below.
8141
8142   --  2. DISCRIMINANTS UNDER INHERITANCE
8143
8144   --  The semantic rules governing the discriminants of derived types are
8145   --  quite subtle.
8146
8147   --   type Derived_Type_Name [KNOWN_DISCRIMINANT_PART] is new
8148   --      [abstract] Parent_Type_Name [CONSTRAINT] [RECORD_EXTENSION_PART]
8149
8150   --  If parent type has discriminants, then the discriminants that are
8151   --  declared in the derived type are [3.4 (11)]:
8152
8153   --  o The discriminants specified by a new KNOWN_DISCRIMINANT_PART, if
8154   --    there is one;
8155
8156   --  o Otherwise, each discriminant of the parent type (implicitly declared
8157   --    in the same order with the same specifications). In this case, the
8158   --    discriminants are said to be "inherited", or if unknown in the parent
8159   --    are also unknown in the derived type.
8160
8161   --  Furthermore if a KNOWN_DISCRIMINANT_PART is provided, then [3.7(13-18)]:
8162
8163   --  o The parent subtype must be constrained;
8164
8165   --  o If the parent type is not a tagged type, then each discriminant of
8166   --    the derived type must be used in the constraint defining a parent
8167   --    subtype. [Implementation note: This ensures that the new discriminant
8168   --    can share storage with an existing discriminant.]
8169
8170   --  For the derived type each discriminant of the parent type is either
8171   --  inherited, constrained to equal some new discriminant of the derived
8172   --  type, or constrained to the value of an expression.
8173
8174   --  When inherited or constrained to equal some new discriminant, the
8175   --  parent discriminant and the discriminant of the derived type are said
8176   --  to "correspond".
8177
8178   --  If a discriminant of the parent type is constrained to a specific value
8179   --  in the derived type definition, then the discriminant is said to be
8180   --  "specified" by that derived type definition.
8181
8182   --  3. DISCRIMINANTS IN DERIVED UNTAGGED RECORD TYPES
8183
8184   --  We have spoken about stored discriminants in point 1 (introduction)
8185   --  above. There are two sorts of stored discriminants: implicit and
8186   --  explicit. As long as the derived type inherits the same discriminants as
8187   --  the root record type, stored discriminants are the same as regular
8188   --  discriminants, and are said to be implicit. However, if any discriminant
8189   --  in the root type was renamed in the derived type, then the derived
8190   --  type will contain explicit stored discriminants. Explicit stored
8191   --  discriminants are discriminants in addition to the semantically visible
8192   --  discriminants defined for the derived type. Stored discriminants are
8193   --  used by Gigi to figure out what are the physical discriminants in
8194   --  objects of the derived type (see precise definition in einfo.ads).
8195   --  As an example, consider the following:
8196
8197   --           type R  (D1, D2, D3 : Int) is record ... end record;
8198   --           type T1 is new R;
8199   --           type T2 (X1, X2: Int) is new T1 (X2, 88, X1);
8200   --           type T3 is new T2;
8201   --           type T4 (Y : Int) is new T3 (Y, 99);
8202
8203   --  The following table summarizes the discriminants and stored
8204   --  discriminants in R and T1 through T4:
8205
8206   --   Type      Discrim     Stored Discrim  Comment
8207   --    R      (D1, D2, D3)   (D1, D2, D3)   Girder discrims implicit in R
8208   --    T1     (D1, D2, D3)   (D1, D2, D3)   Girder discrims implicit in T1
8209   --    T2     (X1, X2)       (D1, D2, D3)   Girder discrims EXPLICIT in T2
8210   --    T3     (X1, X2)       (D1, D2, D3)   Girder discrims EXPLICIT in T3
8211   --    T4     (Y)            (D1, D2, D3)   Girder discrims EXPLICIT in T4
8212
8213   --  Field Corresponding_Discriminant (abbreviated CD below) allows us to
8214   --  find the corresponding discriminant in the parent type, while
8215   --  Original_Record_Component (abbreviated ORC below) the actual physical
8216   --  component that is renamed. Finally the field Is_Completely_Hidden
8217   --  (abbreviated ICH below) is set for all explicit stored discriminants
8218   --  (see einfo.ads for more info). For the above example this gives:
8219
8220   --                 Discrim     CD        ORC     ICH
8221   --                 ^^^^^^^     ^^        ^^^     ^^^
8222   --                 D1 in R    empty     itself    no
8223   --                 D2 in R    empty     itself    no
8224   --                 D3 in R    empty     itself    no
8225
8226   --                 D1 in T1  D1 in R    itself    no
8227   --                 D2 in T1  D2 in R    itself    no
8228   --                 D3 in T1  D3 in R    itself    no
8229
8230   --                 X1 in T2  D3 in T1  D3 in T2   no
8231   --                 X2 in T2  D1 in T1  D1 in T2   no
8232   --                 D1 in T2   empty    itself    yes
8233   --                 D2 in T2   empty    itself    yes
8234   --                 D3 in T2   empty    itself    yes
8235
8236   --                 X1 in T3  X1 in T2  D3 in T3   no
8237   --                 X2 in T3  X2 in T2  D1 in T3   no
8238   --                 D1 in T3   empty    itself    yes
8239   --                 D2 in T3   empty    itself    yes
8240   --                 D3 in T3   empty    itself    yes
8241
8242   --                 Y  in T4  X1 in T3  D3 in T4   no
8243   --                 D1 in T4   empty    itself    yes
8244   --                 D2 in T4   empty    itself    yes
8245   --                 D3 in T4   empty    itself    yes
8246
8247   --  4. DISCRIMINANTS IN DERIVED TAGGED RECORD TYPES
8248
8249   --  Type derivation for tagged types is fairly straightforward. If no
8250   --  discriminants are specified by the derived type, these are inherited
8251   --  from the parent. No explicit stored discriminants are ever necessary.
8252   --  The only manipulation that is done to the tree is that of adding a
8253   --  _parent field with parent type and constrained to the same constraint
8254   --  specified for the parent in the derived type definition. For instance:
8255
8256   --           type R  (D1, D2, D3 : Int) is tagged record ... end record;
8257   --           type T1 is new R with null record;
8258   --           type T2 (X1, X2: Int) is new T1 (X2, 88, X1) with null record;
8259
8260   --  are changed into:
8261
8262   --           type T1 (D1, D2, D3 : Int) is new R (D1, D2, D3) with record
8263   --              _parent : R (D1, D2, D3);
8264   --           end record;
8265
8266   --           type T2 (X1, X2: Int) is new T1 (X2, 88, X1) with record
8267   --              _parent : T1 (X2, 88, X1);
8268   --           end record;
8269
8270   --  The discriminants actually present in R, T1 and T2 as well as their CD,
8271   --  ORC and ICH fields are:
8272
8273   --                 Discrim     CD        ORC     ICH
8274   --                 ^^^^^^^     ^^        ^^^     ^^^
8275   --                 D1 in R    empty     itself    no
8276   --                 D2 in R    empty     itself    no
8277   --                 D3 in R    empty     itself    no
8278
8279   --                 D1 in T1  D1 in R    D1 in R   no
8280   --                 D2 in T1  D2 in R    D2 in R   no
8281   --                 D3 in T1  D3 in R    D3 in R   no
8282
8283   --                 X1 in T2  D3 in T1   D3 in R   no
8284   --                 X2 in T2  D1 in T1   D1 in R   no
8285
8286   --  5. FIRST TRANSFORMATION FOR DERIVED RECORDS
8287   --
8288   --  Regardless of whether we dealing with a tagged or untagged type
8289   --  we will transform all derived type declarations of the form
8290   --
8291   --               type T is new R (...) [with ...];
8292   --  or
8293   --               subtype S is R (...);
8294   --               type T is new S [with ...];
8295   --  into
8296   --               type BT is new R [with ...];
8297   --               subtype T is BT (...);
8298   --
8299   --  That is, the base derived type is constrained only if it has no
8300   --  discriminants. The reason for doing this is that GNAT's semantic model
8301   --  assumes that a base type with discriminants is unconstrained.
8302   --
8303   --  Note that, strictly speaking, the above transformation is not always
8304   --  correct. Consider for instance the following excerpt from ACVC b34011a:
8305   --
8306   --       procedure B34011A is
8307   --          type REC (D : integer := 0) is record
8308   --             I : Integer;
8309   --          end record;
8310
8311   --          package P is
8312   --             type T6 is new Rec;
8313   --             function F return T6;
8314   --          end P;
8315
8316   --          use P;
8317   --          package Q6 is
8318   --             type U is new T6 (Q6.F.I);                   -- ERROR: Q6.F.
8319   --          end Q6;
8320   --
8321   --  The definition of Q6.U is illegal. However transforming Q6.U into
8322
8323   --             type BaseU is new T6;
8324   --             subtype U is BaseU (Q6.F.I)
8325
8326   --  turns U into a legal subtype, which is incorrect. To avoid this problem
8327   --  we always analyze the constraint (in this case (Q6.F.I)) before applying
8328   --  the transformation described above.
8329
8330   --  There is another instance where the above transformation is incorrect.
8331   --  Consider:
8332
8333   --          package Pack is
8334   --             type Base (D : Integer) is tagged null record;
8335   --             procedure P (X : Base);
8336
8337   --             type Der is new Base (2) with null record;
8338   --             procedure P (X : Der);
8339   --          end Pack;
8340
8341   --  Then the above transformation turns this into
8342
8343   --             type Der_Base is new Base with null record;
8344   --             --  procedure P (X : Base) is implicitly inherited here
8345   --             --  as procedure P (X : Der_Base).
8346
8347   --             subtype Der is Der_Base (2);
8348   --             procedure P (X : Der);
8349   --             --  The overriding of P (X : Der_Base) is illegal since we
8350   --             --  have a parameter conformance problem.
8351
8352   --  To get around this problem, after having semantically processed Der_Base
8353   --  and the rewritten subtype declaration for Der, we copy Der_Base field
8354   --  Discriminant_Constraint from Der so that when parameter conformance is
8355   --  checked when P is overridden, no semantic errors are flagged.
8356
8357   --  6. SECOND TRANSFORMATION FOR DERIVED RECORDS
8358
8359   --  Regardless of whether we are dealing with a tagged or untagged type
8360   --  we will transform all derived type declarations of the form
8361
8362   --               type R (D1, .., Dn : ...) is [tagged] record ...;
8363   --               type T is new R [with ...];
8364   --  into
8365   --               type T (D1, .., Dn : ...) is new R (D1, .., Dn) [with ...];
8366
8367   --  The reason for such transformation is that it allows us to implement a
8368   --  very clean form of component inheritance as explained below.
8369
8370   --  Note that this transformation is not achieved by direct tree rewriting
8371   --  and manipulation, but rather by redoing the semantic actions that the
8372   --  above transformation will entail. This is done directly in routine
8373   --  Inherit_Components.
8374
8375   --  7. TYPE DERIVATION AND COMPONENT INHERITANCE
8376
8377   --  In both tagged and untagged derived types, regular non discriminant
8378   --  components are inherited in the derived type from the parent type. In
8379   --  the absence of discriminants component, inheritance is straightforward
8380   --  as components can simply be copied from the parent.
8381
8382   --  If the parent has discriminants, inheriting components constrained with
8383   --  these discriminants requires caution. Consider the following example:
8384
8385   --      type R  (D1, D2 : Positive) is [tagged] record
8386   --         S : String (D1 .. D2);
8387   --      end record;
8388
8389   --      type T1                is new R        [with null record];
8390   --      type T2 (X : positive) is new R (1, X) [with null record];
8391
8392   --  As explained in 6. above, T1 is rewritten as
8393   --      type T1 (D1, D2 : Positive) is new R (D1, D2) [with null record];
8394   --  which makes the treatment for T1 and T2 identical.
8395
8396   --  What we want when inheriting S, is that references to D1 and D2 in R are
8397   --  replaced with references to their correct constraints, i.e. D1 and D2 in
8398   --  T1 and 1 and X in T2. So all R's discriminant references are replaced
8399   --  with either discriminant references in the derived type or expressions.
8400   --  This replacement is achieved as follows: before inheriting R's
8401   --  components, a subtype R (D1, D2) for T1 (resp. R (1, X) for T2) is
8402   --  created in the scope of T1 (resp. scope of T2) so that discriminants D1
8403   --  and D2 of T1 are visible (resp. discriminant X of T2 is visible).
8404   --  For T2, for instance, this has the effect of replacing String (D1 .. D2)
8405   --  by String (1 .. X).
8406
8407   --  8. TYPE DERIVATION IN PRIVATE TYPE EXTENSIONS
8408
8409   --  We explain here the rules governing private type extensions relevant to
8410   --  type derivation. These rules are explained on the following example:
8411
8412   --      type D [(...)] is new A [(...)] with private;      <-- partial view
8413   --      type D [(...)] is new P [(...)] with null record;  <-- full view
8414
8415   --  Type A is called the ancestor subtype of the private extension.
8416   --  Type P is the parent type of the full view of the private extension. It
8417   --  must be A or a type derived from A.
8418
8419   --  The rules concerning the discriminants of private type extensions are
8420   --  [7.3(10-13)]:
8421
8422   --  o If a private extension inherits known discriminants from the ancestor
8423   --    subtype, then the full view must also inherit its discriminants from
8424   --    the ancestor subtype and the parent subtype of the full view must be
8425   --    constrained if and only if the ancestor subtype is constrained.
8426
8427   --  o If a partial view has unknown discriminants, then the full view may
8428   --    define a definite or an indefinite subtype, with or without
8429   --    discriminants.
8430
8431   --  o If a partial view has neither known nor unknown discriminants, then
8432   --    the full view must define a definite subtype.
8433
8434   --  o If the ancestor subtype of a private extension has constrained
8435   --    discriminants, then the parent subtype of the full view must impose a
8436   --    statically matching constraint on those discriminants.
8437
8438   --  This means that only the following forms of private extensions are
8439   --  allowed:
8440
8441   --      type D is new A with private;      <-- partial view
8442   --      type D is new P with null record;  <-- full view
8443
8444   --  If A has no discriminants than P has no discriminants, otherwise P must
8445   --  inherit A's discriminants.
8446
8447   --      type D is new A (...) with private;      <-- partial view
8448   --      type D is new P (:::) with null record;  <-- full view
8449
8450   --  P must inherit A's discriminants and (...) and (:::) must statically
8451   --  match.
8452
8453   --      subtype A is R (...);
8454   --      type D is new A with private;      <-- partial view
8455   --      type D is new P with null record;  <-- full view
8456
8457   --  P must have inherited R's discriminants and must be derived from A or
8458   --  any of its subtypes.
8459
8460   --      type D (..) is new A with private;              <-- partial view
8461   --      type D (..) is new P [(:::)] with null record;  <-- full view
8462
8463   --  No specific constraints on P's discriminants or constraint (:::).
8464   --  Note that A can be unconstrained, but the parent subtype P must either
8465   --  be constrained or (:::) must be present.
8466
8467   --      type D (..) is new A [(...)] with private;      <-- partial view
8468   --      type D (..) is new P [(:::)] with null record;  <-- full view
8469
8470   --  P's constraints on A's discriminants must statically match those
8471   --  imposed by (...).
8472
8473   --  9. IMPLEMENTATION OF TYPE DERIVATION FOR PRIVATE EXTENSIONS
8474
8475   --  The full view of a private extension is handled exactly as described
8476   --  above. The model chose for the private view of a private extension is
8477   --  the same for what concerns discriminants (i.e. they receive the same
8478   --  treatment as in the tagged case). However, the private view of the
8479   --  private extension always inherits the components of the parent base,
8480   --  without replacing any discriminant reference. Strictly speaking this is
8481   --  incorrect. However, Gigi never uses this view to generate code so this
8482   --  is a purely semantic issue. In theory, a set of transformations similar
8483   --  to those given in 5. and 6. above could be applied to private views of
8484   --  private extensions to have the same model of component inheritance as
8485   --  for non private extensions. However, this is not done because it would
8486   --  further complicate private type processing. Semantically speaking, this
8487   --  leaves us in an uncomfortable situation. As an example consider:
8488
8489   --          package Pack is
8490   --             type R (D : integer) is tagged record
8491   --                S : String (1 .. D);
8492   --             end record;
8493   --             procedure P (X : R);
8494   --             type T is new R (1) with private;
8495   --          private
8496   --             type T is new R (1) with null record;
8497   --          end;
8498
8499   --  This is transformed into:
8500
8501   --          package Pack is
8502   --             type R (D : integer) is tagged record
8503   --                S : String (1 .. D);
8504   --             end record;
8505   --             procedure P (X : R);
8506   --             type T is new R (1) with private;
8507   --          private
8508   --             type BaseT is new R with null record;
8509   --             subtype  T is BaseT (1);
8510   --          end;
8511
8512   --  (strictly speaking the above is incorrect Ada)
8513
8514   --  From the semantic standpoint the private view of private extension T
8515   --  should be flagged as constrained since one can clearly have
8516   --
8517   --             Obj : T;
8518   --
8519   --  in a unit withing Pack. However, when deriving subprograms for the
8520   --  private view of private extension T, T must be seen as unconstrained
8521   --  since T has discriminants (this is a constraint of the current
8522   --  subprogram derivation model). Thus, when processing the private view of
8523   --  a private extension such as T, we first mark T as unconstrained, we
8524   --  process it, we perform program derivation and just before returning from
8525   --  Build_Derived_Record_Type we mark T as constrained.
8526
8527   --  ??? Are there are other uncomfortable cases that we will have to
8528   --      deal with.
8529
8530   --  10. RECORD_TYPE_WITH_PRIVATE complications
8531
8532   --  Types that are derived from a visible record type and have a private
8533   --  extension present other peculiarities. They behave mostly like private
8534   --  types, but if they have primitive operations defined, these will not
8535   --  have the proper signatures for further inheritance, because other
8536   --  primitive operations will use the implicit base that we define for
8537   --  private derivations below. This affect subprogram inheritance (see
8538   --  Derive_Subprograms for details). We also derive the implicit base from
8539   --  the base type of the full view, so that the implicit base is a record
8540   --  type and not another private type, This avoids infinite loops.
8541
8542   procedure Build_Derived_Record_Type
8543     (N            : Node_Id;
8544      Parent_Type  : Entity_Id;
8545      Derived_Type : Entity_Id;
8546      Derive_Subps : Boolean := True)
8547   is
8548      Discriminant_Specs : constant Boolean :=
8549                             Present (Discriminant_Specifications (N));
8550      Is_Tagged          : constant Boolean := Is_Tagged_Type (Parent_Type);
8551      Loc                : constant Source_Ptr := Sloc (N);
8552      Private_Extension  : constant Boolean :=
8553                             Nkind (N) = N_Private_Extension_Declaration;
8554      Assoc_List         : Elist_Id;
8555      Constraint_Present : Boolean;
8556      Constrs            : Elist_Id;
8557      Discrim            : Entity_Id;
8558      Indic              : Node_Id;
8559      Inherit_Discrims   : Boolean := False;
8560      Last_Discrim       : Entity_Id;
8561      New_Base           : Entity_Id;
8562      New_Decl           : Node_Id;
8563      New_Discrs         : Elist_Id;
8564      New_Indic          : Node_Id;
8565      Parent_Base        : Entity_Id;
8566      Save_Etype         : Entity_Id;
8567      Save_Discr_Constr  : Elist_Id;
8568      Save_Next_Entity   : Entity_Id;
8569      Type_Def           : Node_Id;
8570
8571      Discs : Elist_Id := New_Elmt_List;
8572      --  An empty Discs list means that there were no constraints in the
8573      --  subtype indication or that there was an error processing it.
8574
8575   begin
8576      if Ekind (Parent_Type) = E_Record_Type_With_Private
8577        and then Present (Full_View (Parent_Type))
8578        and then Has_Discriminants (Parent_Type)
8579      then
8580         Parent_Base := Base_Type (Full_View (Parent_Type));
8581      else
8582         Parent_Base := Base_Type (Parent_Type);
8583      end if;
8584
8585      --  AI05-0115: if this is a derivation from a private type in some
8586      --  other scope that may lead to invisible components for the derived
8587      --  type, mark it accordingly.
8588
8589      if Is_Private_Type (Parent_Type) then
8590         if Scope (Parent_Base) = Scope (Derived_Type) then
8591            null;
8592
8593         elsif In_Open_Scopes (Scope (Parent_Base))
8594           and then In_Private_Part (Scope (Parent_Base))
8595         then
8596            null;
8597
8598         else
8599            Set_Has_Private_Ancestor (Derived_Type);
8600         end if;
8601
8602      else
8603         Set_Has_Private_Ancestor
8604           (Derived_Type, Has_Private_Ancestor (Parent_Type));
8605      end if;
8606
8607      --  Before we start the previously documented transformations, here is
8608      --  little fix for size and alignment of tagged types. Normally when we
8609      --  derive type D from type P, we copy the size and alignment of P as the
8610      --  default for D, and in the absence of explicit representation clauses
8611      --  for D, the size and alignment are indeed the same as the parent.
8612
8613      --  But this is wrong for tagged types, since fields may be added, and
8614      --  the default size may need to be larger, and the default alignment may
8615      --  need to be larger.
8616
8617      --  We therefore reset the size and alignment fields in the tagged case.
8618      --  Note that the size and alignment will in any case be at least as
8619      --  large as the parent type (since the derived type has a copy of the
8620      --  parent type in the _parent field)
8621
8622      --  The type is also marked as being tagged here, which is needed when
8623      --  processing components with a self-referential anonymous access type
8624      --  in the call to Check_Anonymous_Access_Components below. Note that
8625      --  this flag is also set later on for completeness.
8626
8627      if Is_Tagged then
8628         Set_Is_Tagged_Type (Derived_Type);
8629         Init_Size_Align    (Derived_Type);
8630      end if;
8631
8632      --  STEP 0a: figure out what kind of derived type declaration we have
8633
8634      if Private_Extension then
8635         Type_Def := N;
8636         Set_Ekind (Derived_Type, E_Record_Type_With_Private);
8637         Set_Default_SSO (Derived_Type);
8638         Set_No_Reordering (Derived_Type, No_Component_Reordering);
8639
8640      else
8641         Type_Def := Type_Definition (N);
8642
8643         --  Ekind (Parent_Base) is not necessarily E_Record_Type since
8644         --  Parent_Base can be a private type or private extension. However,
8645         --  for tagged types with an extension the newly added fields are
8646         --  visible and hence the Derived_Type is always an E_Record_Type.
8647         --  (except that the parent may have its own private fields).
8648         --  For untagged types we preserve the Ekind of the Parent_Base.
8649
8650         if Present (Record_Extension_Part (Type_Def)) then
8651            Set_Ekind (Derived_Type, E_Record_Type);
8652            Set_Default_SSO (Derived_Type);
8653            Set_No_Reordering (Derived_Type, No_Component_Reordering);
8654
8655            --  Create internal access types for components with anonymous
8656            --  access types.
8657
8658            if Ada_Version >= Ada_2005 then
8659               Check_Anonymous_Access_Components
8660                 (N, Derived_Type, Derived_Type,
8661                   Component_List (Record_Extension_Part (Type_Def)));
8662            end if;
8663
8664         else
8665            Set_Ekind (Derived_Type, Ekind (Parent_Base));
8666         end if;
8667      end if;
8668
8669      --  Indic can either be an N_Identifier if the subtype indication
8670      --  contains no constraint or an N_Subtype_Indication if the subtype
8671      --  indication has a constraint.
8672
8673      Indic := Subtype_Indication (Type_Def);
8674      Constraint_Present := (Nkind (Indic) = N_Subtype_Indication);
8675
8676      --  Check that the type has visible discriminants. The type may be
8677      --  a private type with unknown discriminants whose full view has
8678      --  discriminants which are invisible.
8679
8680      if Constraint_Present then
8681         if not Has_Discriminants (Parent_Base)
8682           or else
8683             (Has_Unknown_Discriminants (Parent_Base)
8684               and then Is_Private_Type (Parent_Base))
8685         then
8686            Error_Msg_N
8687              ("invalid constraint: type has no discriminant",
8688                 Constraint (Indic));
8689
8690            Constraint_Present := False;
8691            Rewrite (Indic, New_Copy_Tree (Subtype_Mark (Indic)));
8692
8693         elsif Is_Constrained (Parent_Type) then
8694            Error_Msg_N
8695               ("invalid constraint: parent type is already constrained",
8696                  Constraint (Indic));
8697
8698            Constraint_Present := False;
8699            Rewrite (Indic, New_Copy_Tree (Subtype_Mark (Indic)));
8700         end if;
8701      end if;
8702
8703      --  STEP 0b: If needed, apply transformation given in point 5. above
8704
8705      if not Private_Extension
8706        and then Has_Discriminants (Parent_Type)
8707        and then not Discriminant_Specs
8708        and then (Is_Constrained (Parent_Type) or else Constraint_Present)
8709      then
8710         --  First, we must analyze the constraint (see comment in point 5.)
8711         --  The constraint may come from the subtype indication of the full
8712         --  declaration.
8713
8714         if Constraint_Present then
8715            New_Discrs := Build_Discriminant_Constraints (Parent_Type, Indic);
8716
8717         --  If there is no explicit constraint, there might be one that is
8718         --  inherited from a constrained parent type. In that case verify that
8719         --  it conforms to the constraint in the partial view. In perverse
8720         --  cases the parent subtypes of the partial and full view can have
8721         --  different constraints.
8722
8723         elsif Present (Stored_Constraint (Parent_Type)) then
8724            New_Discrs := Stored_Constraint (Parent_Type);
8725
8726         else
8727            New_Discrs := No_Elist;
8728         end if;
8729
8730         if Has_Discriminants (Derived_Type)
8731           and then Has_Private_Declaration (Derived_Type)
8732           and then Present (Discriminant_Constraint (Derived_Type))
8733           and then Present (New_Discrs)
8734         then
8735            --  Verify that constraints of the full view statically match
8736            --  those given in the partial view.
8737
8738            declare
8739               C1, C2 : Elmt_Id;
8740
8741            begin
8742               C1 := First_Elmt (New_Discrs);
8743               C2 := First_Elmt (Discriminant_Constraint (Derived_Type));
8744               while Present (C1) and then Present (C2) loop
8745                  if Fully_Conformant_Expressions (Node (C1), Node (C2))
8746                    or else
8747                      (Is_OK_Static_Expression (Node (C1))
8748                        and then Is_OK_Static_Expression (Node (C2))
8749                        and then
8750                          Expr_Value (Node (C1)) = Expr_Value (Node (C2)))
8751                  then
8752                     null;
8753
8754                  else
8755                     if Constraint_Present then
8756                        Error_Msg_N
8757                          ("constraint not conformant to previous declaration",
8758                           Node (C1));
8759                     else
8760                        Error_Msg_N
8761                          ("constraint of full view is incompatible "
8762                           & "with partial view", N);
8763                     end if;
8764                  end if;
8765
8766                  Next_Elmt (C1);
8767                  Next_Elmt (C2);
8768               end loop;
8769            end;
8770         end if;
8771
8772         --  Insert and analyze the declaration for the unconstrained base type
8773
8774         New_Base := Create_Itype (Ekind (Derived_Type), N, Derived_Type, 'B');
8775
8776         New_Decl :=
8777           Make_Full_Type_Declaration (Loc,
8778              Defining_Identifier => New_Base,
8779              Type_Definition     =>
8780                Make_Derived_Type_Definition (Loc,
8781                  Abstract_Present      => Abstract_Present (Type_Def),
8782                  Limited_Present       => Limited_Present (Type_Def),
8783                  Subtype_Indication    =>
8784                    New_Occurrence_Of (Parent_Base, Loc),
8785                  Record_Extension_Part =>
8786                    Relocate_Node (Record_Extension_Part (Type_Def)),
8787                  Interface_List        => Interface_List (Type_Def)));
8788
8789         Set_Parent (New_Decl, Parent (N));
8790         Mark_Rewrite_Insertion (New_Decl);
8791         Insert_Before (N, New_Decl);
8792
8793         --  In the extension case, make sure ancestor is frozen appropriately
8794         --  (see also non-discriminated case below).
8795
8796         if Present (Record_Extension_Part (Type_Def))
8797           or else Is_Interface (Parent_Base)
8798         then
8799            Freeze_Before (New_Decl, Parent_Type);
8800         end if;
8801
8802         --  Note that this call passes False for the Derive_Subps parameter
8803         --  because subprogram derivation is deferred until after creating
8804         --  the subtype (see below).
8805
8806         Build_Derived_Type
8807           (New_Decl, Parent_Base, New_Base,
8808            Is_Completion => False, Derive_Subps => False);
8809
8810         --  ??? This needs re-examination to determine whether the
8811         --  above call can simply be replaced by a call to Analyze.
8812
8813         Set_Analyzed (New_Decl);
8814
8815         --  Insert and analyze the declaration for the constrained subtype
8816
8817         if Constraint_Present then
8818            New_Indic :=
8819              Make_Subtype_Indication (Loc,
8820                Subtype_Mark => New_Occurrence_Of (New_Base, Loc),
8821                Constraint   => Relocate_Node (Constraint (Indic)));
8822
8823         else
8824            declare
8825               Constr_List : constant List_Id := New_List;
8826               C           : Elmt_Id;
8827               Expr        : Node_Id;
8828
8829            begin
8830               C := First_Elmt (Discriminant_Constraint (Parent_Type));
8831               while Present (C) loop
8832                  Expr := Node (C);
8833
8834                  --  It is safe here to call New_Copy_Tree since we called
8835                  --  Force_Evaluation on each constraint previously
8836                  --  in Build_Discriminant_Constraints.
8837
8838                  Append (New_Copy_Tree (Expr), To => Constr_List);
8839
8840                  Next_Elmt (C);
8841               end loop;
8842
8843               New_Indic :=
8844                 Make_Subtype_Indication (Loc,
8845                   Subtype_Mark => New_Occurrence_Of (New_Base, Loc),
8846                   Constraint   =>
8847                     Make_Index_Or_Discriminant_Constraint (Loc, Constr_List));
8848            end;
8849         end if;
8850
8851         Rewrite (N,
8852           Make_Subtype_Declaration (Loc,
8853             Defining_Identifier => Derived_Type,
8854             Subtype_Indication  => New_Indic));
8855
8856         Analyze (N);
8857
8858         --  Derivation of subprograms must be delayed until the full subtype
8859         --  has been established, to ensure proper overriding of subprograms
8860         --  inherited by full types. If the derivations occurred as part of
8861         --  the call to Build_Derived_Type above, then the check for type
8862         --  conformance would fail because earlier primitive subprograms
8863         --  could still refer to the full type prior the change to the new
8864         --  subtype and hence would not match the new base type created here.
8865         --  Subprograms are not derived, however, when Derive_Subps is False
8866         --  (since otherwise there could be redundant derivations).
8867
8868         if Derive_Subps then
8869            Derive_Subprograms (Parent_Type, Derived_Type);
8870         end if;
8871
8872         --  For tagged types the Discriminant_Constraint of the new base itype
8873         --  is inherited from the first subtype so that no subtype conformance
8874         --  problem arise when the first subtype overrides primitive
8875         --  operations inherited by the implicit base type.
8876
8877         if Is_Tagged then
8878            Set_Discriminant_Constraint
8879              (New_Base, Discriminant_Constraint (Derived_Type));
8880         end if;
8881
8882         return;
8883      end if;
8884
8885      --  If we get here Derived_Type will have no discriminants or it will be
8886      --  a discriminated unconstrained base type.
8887
8888      --  STEP 1a: perform preliminary actions/checks for derived tagged types
8889
8890      if Is_Tagged then
8891
8892         --  The parent type is frozen for non-private extensions (RM 13.14(7))
8893         --  The declaration of a specific descendant of an interface type
8894         --  freezes the interface type (RM 13.14).
8895
8896         if not Private_Extension or else Is_Interface (Parent_Base) then
8897            Freeze_Before (N, Parent_Type);
8898         end if;
8899
8900         --  In Ada 2005 (AI-344), the restriction that a derived tagged type
8901         --  cannot be declared at a deeper level than its parent type is
8902         --  removed. The check on derivation within a generic body is also
8903         --  relaxed, but there's a restriction that a derived tagged type
8904         --  cannot be declared in a generic body if it's derived directly
8905         --  or indirectly from a formal type of that generic.
8906
8907         if Ada_Version >= Ada_2005 then
8908            if Present (Enclosing_Generic_Body (Derived_Type)) then
8909               declare
8910                  Ancestor_Type : Entity_Id;
8911
8912               begin
8913                  --  Check to see if any ancestor of the derived type is a
8914                  --  formal type.
8915
8916                  Ancestor_Type := Parent_Type;
8917                  while not Is_Generic_Type (Ancestor_Type)
8918                    and then Etype (Ancestor_Type) /= Ancestor_Type
8919                  loop
8920                     Ancestor_Type := Etype (Ancestor_Type);
8921                  end loop;
8922
8923                  --  If the derived type does have a formal type as an
8924                  --  ancestor, then it's an error if the derived type is
8925                  --  declared within the body of the generic unit that
8926                  --  declares the formal type in its generic formal part. It's
8927                  --  sufficient to check whether the ancestor type is declared
8928                  --  inside the same generic body as the derived type (such as
8929                  --  within a nested generic spec), in which case the
8930                  --  derivation is legal. If the formal type is declared
8931                  --  outside of that generic body, then it's guaranteed that
8932                  --  the derived type is declared within the generic body of
8933                  --  the generic unit declaring the formal type.
8934
8935                  if Is_Generic_Type (Ancestor_Type)
8936                    and then Enclosing_Generic_Body (Ancestor_Type) /=
8937                               Enclosing_Generic_Body (Derived_Type)
8938                  then
8939                     Error_Msg_NE
8940                       ("parent type of& must not be descendant of formal type"
8941                          & " of an enclosing generic body",
8942                            Indic, Derived_Type);
8943                  end if;
8944               end;
8945            end if;
8946
8947         elsif Type_Access_Level (Derived_Type) /=
8948                 Type_Access_Level (Parent_Type)
8949           and then not Is_Generic_Type (Derived_Type)
8950         then
8951            if Is_Controlled (Parent_Type) then
8952               Error_Msg_N
8953                 ("controlled type must be declared at the library level",
8954                  Indic);
8955            else
8956               Error_Msg_N
8957                 ("type extension at deeper accessibility level than parent",
8958                  Indic);
8959            end if;
8960
8961         else
8962            declare
8963               GB : constant Node_Id := Enclosing_Generic_Body (Derived_Type);
8964            begin
8965               if Present (GB)
8966                 and then GB /= Enclosing_Generic_Body (Parent_Base)
8967               then
8968                  Error_Msg_NE
8969                    ("parent type of& must not be outside generic body"
8970                       & " (RM 3.9.1(4))",
8971                         Indic, Derived_Type);
8972               end if;
8973            end;
8974         end if;
8975      end if;
8976
8977      --  Ada 2005 (AI-251)
8978
8979      if Ada_Version >= Ada_2005 and then Is_Tagged then
8980
8981         --  "The declaration of a specific descendant of an interface type
8982         --  freezes the interface type" (RM 13.14).
8983
8984         declare
8985            Iface : Node_Id;
8986         begin
8987            if Is_Non_Empty_List (Interface_List (Type_Def)) then
8988               Iface := First (Interface_List (Type_Def));
8989               while Present (Iface) loop
8990                  Freeze_Before (N, Etype (Iface));
8991                  Next (Iface);
8992               end loop;
8993            end if;
8994         end;
8995      end if;
8996
8997      --  STEP 1b : preliminary cleanup of the full view of private types
8998
8999      --  If the type is already marked as having discriminants, then it's the
9000      --  completion of a private type or private extension and we need to
9001      --  retain the discriminants from the partial view if the current
9002      --  declaration has Discriminant_Specifications so that we can verify
9003      --  conformance. However, we must remove any existing components that
9004      --  were inherited from the parent (and attached in Copy_And_Swap)
9005      --  because the full type inherits all appropriate components anyway, and
9006      --  we do not want the partial view's components interfering.
9007
9008      if Has_Discriminants (Derived_Type) and then Discriminant_Specs then
9009         Discrim := First_Discriminant (Derived_Type);
9010         loop
9011            Last_Discrim := Discrim;
9012            Next_Discriminant (Discrim);
9013            exit when No (Discrim);
9014         end loop;
9015
9016         Set_Last_Entity (Derived_Type, Last_Discrim);
9017
9018      --  In all other cases wipe out the list of inherited components (even
9019      --  inherited discriminants), it will be properly rebuilt here.
9020
9021      else
9022         Set_First_Entity (Derived_Type, Empty);
9023         Set_Last_Entity  (Derived_Type, Empty);
9024      end if;
9025
9026      --  STEP 1c: Initialize some flags for the Derived_Type
9027
9028      --  The following flags must be initialized here so that
9029      --  Process_Discriminants can check that discriminants of tagged types do
9030      --  not have a default initial value and that access discriminants are
9031      --  only specified for limited records. For completeness, these flags are
9032      --  also initialized along with all the other flags below.
9033
9034      --  AI-419: Limitedness is not inherited from an interface parent, so to
9035      --  be limited in that case the type must be explicitly declared as
9036      --  limited. However, task and protected interfaces are always limited.
9037
9038      if Limited_Present (Type_Def) then
9039         Set_Is_Limited_Record (Derived_Type);
9040
9041      elsif Is_Limited_Record (Parent_Type)
9042        or else (Present (Full_View (Parent_Type))
9043                  and then Is_Limited_Record (Full_View (Parent_Type)))
9044      then
9045         if not Is_Interface (Parent_Type)
9046           or else Is_Synchronized_Interface (Parent_Type)
9047           or else Is_Protected_Interface (Parent_Type)
9048           or else Is_Task_Interface (Parent_Type)
9049         then
9050            Set_Is_Limited_Record (Derived_Type);
9051         end if;
9052      end if;
9053
9054      --  STEP 2a: process discriminants of derived type if any
9055
9056      Push_Scope (Derived_Type);
9057
9058      if Discriminant_Specs then
9059         Set_Has_Unknown_Discriminants (Derived_Type, False);
9060
9061         --  The following call initializes fields Has_Discriminants and
9062         --  Discriminant_Constraint, unless we are processing the completion
9063         --  of a private type declaration.
9064
9065         Check_Or_Process_Discriminants (N, Derived_Type);
9066
9067         --  For untagged types, the constraint on the Parent_Type must be
9068         --  present and is used to rename the discriminants.
9069
9070         if not Is_Tagged and then not Has_Discriminants (Parent_Type) then
9071            Error_Msg_N ("untagged parent must have discriminants", Indic);
9072
9073         elsif not Is_Tagged and then not Constraint_Present then
9074            Error_Msg_N
9075              ("discriminant constraint needed for derived untagged records",
9076               Indic);
9077
9078         --  Otherwise the parent subtype must be constrained unless we have a
9079         --  private extension.
9080
9081         elsif not Constraint_Present
9082           and then not Private_Extension
9083           and then not Is_Constrained (Parent_Type)
9084         then
9085            Error_Msg_N
9086              ("unconstrained type not allowed in this context", Indic);
9087
9088         elsif Constraint_Present then
9089            --  The following call sets the field Corresponding_Discriminant
9090            --  for the discriminants in the Derived_Type.
9091
9092            Discs := Build_Discriminant_Constraints (Parent_Type, Indic, True);
9093
9094            --  For untagged types all new discriminants must rename
9095            --  discriminants in the parent. For private extensions new
9096            --  discriminants cannot rename old ones (implied by [7.3(13)]).
9097
9098            Discrim := First_Discriminant (Derived_Type);
9099            while Present (Discrim) loop
9100               if not Is_Tagged
9101                 and then No (Corresponding_Discriminant (Discrim))
9102               then
9103                  Error_Msg_N
9104                    ("new discriminants must constrain old ones", Discrim);
9105
9106               elsif Private_Extension
9107                 and then Present (Corresponding_Discriminant (Discrim))
9108               then
9109                  Error_Msg_N
9110                    ("only static constraints allowed for parent"
9111                     & " discriminants in the partial view", Indic);
9112                  exit;
9113               end if;
9114
9115               --  If a new discriminant is used in the constraint, then its
9116               --  subtype must be statically compatible with the parent
9117               --  discriminant's subtype (3.7(15)).
9118
9119               --  However, if the record contains an array constrained by
9120               --  the discriminant but with some different bound, the compiler
9121               --  tries to create a smaller range for the discriminant type.
9122               --  (See exp_ch3.Adjust_Discriminants). In this case, where
9123               --  the discriminant type is a scalar type, the check must use
9124               --  the original discriminant type in the parent declaration.
9125
9126               declare
9127                  Corr_Disc : constant Entity_Id :=
9128                                Corresponding_Discriminant (Discrim);
9129                  Disc_Type : constant Entity_Id := Etype (Discrim);
9130                  Corr_Type : Entity_Id;
9131
9132               begin
9133                  if Present (Corr_Disc) then
9134                     if Is_Scalar_Type (Disc_Type) then
9135                        Corr_Type :=
9136                           Entity (Discriminant_Type (Parent (Corr_Disc)));
9137                     else
9138                        Corr_Type := Etype (Corr_Disc);
9139                     end if;
9140
9141                     if not
9142                        Subtypes_Statically_Compatible (Disc_Type, Corr_Type)
9143                     then
9144                        Error_Msg_N
9145                          ("subtype must be compatible "
9146                           & "with parent discriminant",
9147                           Discrim);
9148                     end if;
9149                  end if;
9150               end;
9151
9152               Next_Discriminant (Discrim);
9153            end loop;
9154
9155            --  Check whether the constraints of the full view statically
9156            --  match those imposed by the parent subtype [7.3(13)].
9157
9158            if Present (Stored_Constraint (Derived_Type)) then
9159               declare
9160                  C1, C2 : Elmt_Id;
9161
9162               begin
9163                  C1 := First_Elmt (Discs);
9164                  C2 := First_Elmt (Stored_Constraint (Derived_Type));
9165                  while Present (C1) and then Present (C2) loop
9166                     if not
9167                       Fully_Conformant_Expressions (Node (C1), Node (C2))
9168                     then
9169                        Error_Msg_N
9170                          ("not conformant with previous declaration",
9171                           Node (C1));
9172                     end if;
9173
9174                     Next_Elmt (C1);
9175                     Next_Elmt (C2);
9176                  end loop;
9177               end;
9178            end if;
9179         end if;
9180
9181      --  STEP 2b: No new discriminants, inherit discriminants if any
9182
9183      else
9184         if Private_Extension then
9185            Set_Has_Unknown_Discriminants
9186              (Derived_Type,
9187               Has_Unknown_Discriminants (Parent_Type)
9188                 or else Unknown_Discriminants_Present (N));
9189
9190         --  The partial view of the parent may have unknown discriminants,
9191         --  but if the full view has discriminants and the parent type is
9192         --  in scope they must be inherited.
9193
9194         elsif Has_Unknown_Discriminants (Parent_Type)
9195           and then
9196            (not Has_Discriminants (Parent_Type)
9197              or else not In_Open_Scopes (Scope (Parent_Base)))
9198         then
9199            Set_Has_Unknown_Discriminants (Derived_Type);
9200         end if;
9201
9202         if not Has_Unknown_Discriminants (Derived_Type)
9203           and then not Has_Unknown_Discriminants (Parent_Base)
9204           and then Has_Discriminants (Parent_Type)
9205         then
9206            Inherit_Discrims := True;
9207            Set_Has_Discriminants
9208              (Derived_Type, True);
9209            Set_Discriminant_Constraint
9210              (Derived_Type, Discriminant_Constraint (Parent_Base));
9211         end if;
9212
9213         --  The following test is true for private types (remember
9214         --  transformation 5. is not applied to those) and in an error
9215         --  situation.
9216
9217         if Constraint_Present then
9218            Discs := Build_Discriminant_Constraints (Parent_Type, Indic);
9219         end if;
9220
9221         --  For now mark a new derived type as constrained only if it has no
9222         --  discriminants. At the end of Build_Derived_Record_Type we properly
9223         --  set this flag in the case of private extensions. See comments in
9224         --  point 9. just before body of Build_Derived_Record_Type.
9225
9226         Set_Is_Constrained
9227           (Derived_Type,
9228            not (Inherit_Discrims
9229                  or else Has_Unknown_Discriminants (Derived_Type)));
9230      end if;
9231
9232      --  STEP 3: initialize fields of derived type
9233
9234      Set_Is_Tagged_Type    (Derived_Type, Is_Tagged);
9235      Set_Stored_Constraint (Derived_Type, No_Elist);
9236
9237      --  Ada 2005 (AI-251): Private type-declarations can implement interfaces
9238      --  but cannot be interfaces
9239
9240      if not Private_Extension
9241         and then Ekind (Derived_Type) /= E_Private_Type
9242         and then Ekind (Derived_Type) /= E_Limited_Private_Type
9243      then
9244         if Interface_Present (Type_Def) then
9245            Analyze_Interface_Declaration (Derived_Type, Type_Def);
9246         end if;
9247
9248         Set_Interfaces (Derived_Type, No_Elist);
9249      end if;
9250
9251      --  Fields inherited from the Parent_Type
9252
9253      Set_Has_Specified_Layout
9254        (Derived_Type, Has_Specified_Layout     (Parent_Type));
9255      Set_Is_Limited_Composite
9256        (Derived_Type, Is_Limited_Composite     (Parent_Type));
9257      Set_Is_Private_Composite
9258        (Derived_Type, Is_Private_Composite     (Parent_Type));
9259
9260      if Is_Tagged_Type (Parent_Type) then
9261         Set_No_Tagged_Streams_Pragma
9262           (Derived_Type, No_Tagged_Streams_Pragma (Parent_Type));
9263      end if;
9264
9265      --  Fields inherited from the Parent_Base
9266
9267      Set_Has_Controlled_Component
9268        (Derived_Type, Has_Controlled_Component (Parent_Base));
9269      Set_Has_Non_Standard_Rep
9270        (Derived_Type, Has_Non_Standard_Rep     (Parent_Base));
9271      Set_Has_Primitive_Operations
9272        (Derived_Type, Has_Primitive_Operations (Parent_Base));
9273
9274      --  Set fields for private derived types
9275
9276      if Is_Private_Type (Derived_Type) then
9277         Set_Depends_On_Private (Derived_Type, True);
9278         Set_Private_Dependents (Derived_Type, New_Elmt_List);
9279      end if;
9280
9281      --  Inherit fields for non-private types. If this is the completion of a
9282      --  derivation from a private type, the parent itself is private and the
9283      --  attributes come from its full view, which must be present.
9284
9285      if Is_Record_Type (Derived_Type) then
9286         declare
9287            Parent_Full : Entity_Id;
9288
9289         begin
9290            if Is_Private_Type (Parent_Base)
9291              and then not Is_Record_Type (Parent_Base)
9292            then
9293               Parent_Full := Full_View (Parent_Base);
9294            else
9295               Parent_Full := Parent_Base;
9296            end if;
9297
9298            Set_Component_Alignment
9299              (Derived_Type, Component_Alignment        (Parent_Full));
9300            Set_C_Pass_By_Copy
9301              (Derived_Type, C_Pass_By_Copy             (Parent_Full));
9302            Set_Has_Complex_Representation
9303              (Derived_Type, Has_Complex_Representation (Parent_Full));
9304
9305            --  For untagged types, inherit the layout by default to avoid
9306            --  costly changes of representation for type conversions.
9307
9308            if not Is_Tagged then
9309               Set_Is_Packed     (Derived_Type, Is_Packed     (Parent_Full));
9310               Set_No_Reordering (Derived_Type, No_Reordering (Parent_Full));
9311            end if;
9312         end;
9313      end if;
9314
9315      --  Set fields for tagged types
9316
9317      if Is_Tagged then
9318         Set_Direct_Primitive_Operations (Derived_Type, New_Elmt_List);
9319
9320         --  All tagged types defined in Ada.Finalization are controlled
9321
9322         if Chars (Scope (Derived_Type)) = Name_Finalization
9323           and then Chars (Scope (Scope (Derived_Type))) = Name_Ada
9324           and then Scope (Scope (Scope (Derived_Type))) = Standard_Standard
9325         then
9326            Set_Is_Controlled_Active (Derived_Type);
9327         else
9328            Set_Is_Controlled_Active
9329              (Derived_Type, Is_Controlled_Active (Parent_Base));
9330         end if;
9331
9332         --  Minor optimization: there is no need to generate the class-wide
9333         --  entity associated with an underlying record view.
9334
9335         if not Is_Underlying_Record_View (Derived_Type) then
9336            Make_Class_Wide_Type (Derived_Type);
9337         end if;
9338
9339         Set_Is_Abstract_Type (Derived_Type, Abstract_Present (Type_Def));
9340
9341         if Has_Discriminants (Derived_Type)
9342           and then Constraint_Present
9343         then
9344            Set_Stored_Constraint
9345              (Derived_Type, Expand_To_Stored_Constraint (Parent_Base, Discs));
9346         end if;
9347
9348         if Ada_Version >= Ada_2005 then
9349            declare
9350               Ifaces_List : Elist_Id;
9351
9352            begin
9353               --  Checks rules 3.9.4 (13/2 and 14/2)
9354
9355               if Comes_From_Source (Derived_Type)
9356                 and then not Is_Private_Type (Derived_Type)
9357                 and then Is_Interface (Parent_Type)
9358                 and then not Is_Interface (Derived_Type)
9359               then
9360                  if Is_Task_Interface (Parent_Type) then
9361                     Error_Msg_N
9362                       ("(Ada 2005) task type required (RM 3.9.4 (13.2))",
9363                        Derived_Type);
9364
9365                  elsif Is_Protected_Interface (Parent_Type) then
9366                     Error_Msg_N
9367                       ("(Ada 2005) protected type required (RM 3.9.4 (14.2))",
9368                        Derived_Type);
9369                  end if;
9370               end if;
9371
9372               --  Check ARM rules 3.9.4 (15/2), 9.1 (9.d/2) and 9.4 (11.d/2)
9373
9374               Check_Interfaces (N, Type_Def);
9375
9376               --  Ada 2005 (AI-251): Collect the list of progenitors that are
9377               --  not already in the parents.
9378
9379               Collect_Interfaces
9380                 (T               => Derived_Type,
9381                  Ifaces_List     => Ifaces_List,
9382                  Exclude_Parents => True);
9383
9384               Set_Interfaces (Derived_Type, Ifaces_List);
9385
9386               --  If the derived type is the anonymous type created for
9387               --  a declaration whose parent has a constraint, propagate
9388               --  the interface list to the source type. This must be done
9389               --  prior to the completion of the analysis of the source type
9390               --  because the components in the extension may contain current
9391               --  instances whose legality depends on some ancestor.
9392
9393               if Is_Itype (Derived_Type) then
9394                  declare
9395                     Def : constant Node_Id :=
9396                             Associated_Node_For_Itype (Derived_Type);
9397                  begin
9398                     if Present (Def)
9399                       and then Nkind (Def) = N_Full_Type_Declaration
9400                     then
9401                        Set_Interfaces
9402                          (Defining_Identifier (Def), Ifaces_List);
9403                     end if;
9404                  end;
9405               end if;
9406
9407               --  A type extension is automatically Ghost when one of its
9408               --  progenitors is Ghost (SPARK RM 6.9(9)). This property is
9409               --  also inherited when the parent type is Ghost, but this is
9410               --  done in Build_Derived_Type as the mechanism also handles
9411               --  untagged derivations.
9412
9413               if Implements_Ghost_Interface (Derived_Type) then
9414                  Set_Is_Ghost_Entity (Derived_Type);
9415               end if;
9416            end;
9417         end if;
9418      end if;
9419
9420      --  STEP 4: Inherit components from the parent base and constrain them.
9421      --          Apply the second transformation described in point 6. above.
9422
9423      if (not Is_Empty_Elmt_List (Discs) or else Inherit_Discrims)
9424        or else not Has_Discriminants (Parent_Type)
9425        or else not Is_Constrained (Parent_Type)
9426      then
9427         Constrs := Discs;
9428      else
9429         Constrs := Discriminant_Constraint (Parent_Type);
9430      end if;
9431
9432      Assoc_List :=
9433        Inherit_Components
9434          (N, Parent_Base, Derived_Type, Is_Tagged, Inherit_Discrims, Constrs);
9435
9436      --  STEP 5a: Copy the parent record declaration for untagged types
9437
9438      Set_Has_Implicit_Dereference
9439        (Derived_Type, Has_Implicit_Dereference (Parent_Type));
9440
9441      if not Is_Tagged then
9442
9443         --  Discriminant_Constraint (Derived_Type) has been properly
9444         --  constructed. Save it and temporarily set it to Empty because we
9445         --  do not want the call to New_Copy_Tree below to mess this list.
9446
9447         if Has_Discriminants (Derived_Type) then
9448            Save_Discr_Constr := Discriminant_Constraint (Derived_Type);
9449            Set_Discriminant_Constraint (Derived_Type, No_Elist);
9450         else
9451            Save_Discr_Constr := No_Elist;
9452         end if;
9453
9454         --  Save the Etype field of Derived_Type. It is correctly set now,
9455         --  but the call to New_Copy tree may remap it to point to itself,
9456         --  which is not what we want. Ditto for the Next_Entity field.
9457
9458         Save_Etype       := Etype (Derived_Type);
9459         Save_Next_Entity := Next_Entity (Derived_Type);
9460
9461         --  Assoc_List maps all stored discriminants in the Parent_Base to
9462         --  stored discriminants in the Derived_Type. It is fundamental that
9463         --  no types or itypes with discriminants other than the stored
9464         --  discriminants appear in the entities declared inside
9465         --  Derived_Type, since the back end cannot deal with it.
9466
9467         New_Decl :=
9468           New_Copy_Tree
9469             (Parent (Parent_Base), Map => Assoc_List, New_Sloc => Loc);
9470         Copy_Dimensions_Of_Components (Derived_Type);
9471
9472         --  Restore the fields saved prior to the New_Copy_Tree call
9473         --  and compute the stored constraint.
9474
9475         Set_Etype     (Derived_Type, Save_Etype);
9476         Link_Entities (Derived_Type, Save_Next_Entity);
9477
9478         if Has_Discriminants (Derived_Type) then
9479            Set_Discriminant_Constraint
9480              (Derived_Type, Save_Discr_Constr);
9481            Set_Stored_Constraint
9482              (Derived_Type, Expand_To_Stored_Constraint (Parent_Type, Discs));
9483
9484            Replace_Components (Derived_Type, New_Decl);
9485         end if;
9486
9487         --  Insert the new derived type declaration
9488
9489         Rewrite (N, New_Decl);
9490
9491      --  STEP 5b: Complete the processing for record extensions in generics
9492
9493      --  There is no completion for record extensions declared in the
9494      --  parameter part of a generic, so we need to complete processing for
9495      --  these generic record extensions here. The Record_Type_Definition call
9496      --  will change the Ekind of the components from E_Void to E_Component.
9497
9498      elsif Private_Extension and then Is_Generic_Type (Derived_Type) then
9499         Record_Type_Definition (Empty, Derived_Type);
9500
9501      --  STEP 5c: Process the record extension for non private tagged types
9502
9503      elsif not Private_Extension then
9504         Expand_Record_Extension (Derived_Type, Type_Def);
9505
9506         --  Note : previously in ASIS mode we set the Parent_Subtype of the
9507         --  derived type to propagate some semantic information. This led
9508         --  to other ASIS failures and has been removed.
9509
9510         --  Ada 2005 (AI-251): Addition of the Tag corresponding to all the
9511         --  implemented interfaces if we are in expansion mode
9512
9513         if Expander_Active
9514           and then Has_Interfaces (Derived_Type)
9515         then
9516            Add_Interface_Tag_Components (N, Derived_Type);
9517         end if;
9518
9519         --  Analyze the record extension
9520
9521         Record_Type_Definition
9522           (Record_Extension_Part (Type_Def), Derived_Type);
9523      end if;
9524
9525      End_Scope;
9526
9527      --  Nothing else to do if there is an error in the derivation.
9528      --  An unusual case: the full view may be derived from a type in an
9529      --  instance, when the partial view was used illegally as an actual
9530      --  in that instance, leading to a circular definition.
9531
9532      if Etype (Derived_Type) = Any_Type
9533        or else Etype (Parent_Type) = Derived_Type
9534      then
9535         return;
9536      end if;
9537
9538      --  Set delayed freeze and then derive subprograms, we need to do
9539      --  this in this order so that derived subprograms inherit the
9540      --  derived freeze if necessary.
9541
9542      Set_Has_Delayed_Freeze (Derived_Type);
9543
9544      if Derive_Subps then
9545         Derive_Subprograms (Parent_Type, Derived_Type);
9546      end if;
9547
9548      --  If we have a private extension which defines a constrained derived
9549      --  type mark as constrained here after we have derived subprograms. See
9550      --  comment on point 9. just above the body of Build_Derived_Record_Type.
9551
9552      if Private_Extension and then Inherit_Discrims then
9553         if Constraint_Present and then not Is_Empty_Elmt_List (Discs) then
9554            Set_Is_Constrained          (Derived_Type, True);
9555            Set_Discriminant_Constraint (Derived_Type, Discs);
9556
9557         elsif Is_Constrained (Parent_Type) then
9558            Set_Is_Constrained
9559              (Derived_Type, True);
9560            Set_Discriminant_Constraint
9561              (Derived_Type, Discriminant_Constraint (Parent_Type));
9562         end if;
9563      end if;
9564
9565      --  Update the class-wide type, which shares the now-completed entity
9566      --  list with its specific type. In case of underlying record views,
9567      --  we do not generate the corresponding class wide entity.
9568
9569      if Is_Tagged
9570        and then not Is_Underlying_Record_View (Derived_Type)
9571      then
9572         Set_First_Entity
9573           (Class_Wide_Type (Derived_Type), First_Entity (Derived_Type));
9574         Set_Last_Entity
9575           (Class_Wide_Type (Derived_Type), Last_Entity (Derived_Type));
9576      end if;
9577
9578      Check_Function_Writable_Actuals (N);
9579   end Build_Derived_Record_Type;
9580
9581   ------------------------
9582   -- Build_Derived_Type --
9583   ------------------------
9584
9585   procedure Build_Derived_Type
9586     (N             : Node_Id;
9587      Parent_Type   : Entity_Id;
9588      Derived_Type  : Entity_Id;
9589      Is_Completion : Boolean;
9590      Derive_Subps  : Boolean := True)
9591   is
9592      Parent_Base : constant Entity_Id := Base_Type (Parent_Type);
9593
9594   begin
9595      --  Set common attributes
9596
9597      Set_Scope                  (Derived_Type, Current_Scope);
9598      Set_Etype                  (Derived_Type,        Parent_Base);
9599      Set_Ekind                  (Derived_Type, Ekind (Parent_Base));
9600      Propagate_Concurrent_Flags (Derived_Type,        Parent_Base);
9601
9602      Set_Size_Info (Derived_Type,          Parent_Type);
9603      Set_RM_Size   (Derived_Type, RM_Size (Parent_Type));
9604
9605      Set_Is_Controlled_Active
9606        (Derived_Type, Is_Controlled_Active (Parent_Type));
9607
9608      Set_Disable_Controlled (Derived_Type, Disable_Controlled (Parent_Type));
9609      Set_Is_Tagged_Type     (Derived_Type, Is_Tagged_Type     (Parent_Type));
9610      Set_Is_Volatile        (Derived_Type, Is_Volatile        (Parent_Type));
9611
9612      if Is_Tagged_Type (Derived_Type) then
9613         Set_No_Tagged_Streams_Pragma
9614           (Derived_Type, No_Tagged_Streams_Pragma (Parent_Type));
9615      end if;
9616
9617      --  If the parent has primitive routines, set the derived type link
9618
9619      if Has_Primitive_Operations (Parent_Type) then
9620         Set_Derived_Type_Link (Parent_Base, Derived_Type);
9621      end if;
9622
9623      --  If the parent type is a private subtype, the convention on the base
9624      --  type may be set in the private part, and not propagated to the
9625      --  subtype until later, so we obtain the convention from the base type.
9626
9627      Set_Convention (Derived_Type, Convention (Parent_Base));
9628
9629      --  Set SSO default for record or array type
9630
9631      if (Is_Array_Type (Derived_Type) or else Is_Record_Type (Derived_Type))
9632        and then Is_Base_Type (Derived_Type)
9633      then
9634         Set_Default_SSO (Derived_Type);
9635      end if;
9636
9637      --  A derived type inherits the Default_Initial_Condition pragma coming
9638      --  from any parent type within the derivation chain.
9639
9640      if Has_DIC (Parent_Type) then
9641         Set_Has_Inherited_DIC (Derived_Type);
9642      end if;
9643
9644      --  A derived type inherits any class-wide invariants coming from a
9645      --  parent type or an interface. Note that the invariant procedure of
9646      --  the parent type should not be inherited because the derived type may
9647      --  define invariants of its own.
9648
9649      if not Is_Interface (Derived_Type) then
9650         if Has_Inherited_Invariants (Parent_Type)
9651           or else Has_Inheritable_Invariants (Parent_Type)
9652         then
9653            Set_Has_Inherited_Invariants (Derived_Type);
9654
9655         elsif Is_Concurrent_Type (Derived_Type)
9656           or else Is_Tagged_Type (Derived_Type)
9657         then
9658            declare
9659               Iface      : Entity_Id;
9660               Ifaces     : Elist_Id;
9661               Iface_Elmt : Elmt_Id;
9662
9663            begin
9664               Collect_Interfaces
9665                 (T               => Derived_Type,
9666                  Ifaces_List     => Ifaces,
9667                  Exclude_Parents => True);
9668
9669               if Present (Ifaces) then
9670                  Iface_Elmt := First_Elmt (Ifaces);
9671                  while Present (Iface_Elmt) loop
9672                     Iface := Node (Iface_Elmt);
9673
9674                     if Has_Inheritable_Invariants (Iface) then
9675                        Set_Has_Inherited_Invariants (Derived_Type);
9676                        exit;
9677                     end if;
9678
9679                     Next_Elmt (Iface_Elmt);
9680                  end loop;
9681               end if;
9682            end;
9683         end if;
9684      end if;
9685
9686      --  We similarly inherit predicates. Note that for scalar derived types
9687      --  the predicate is inherited from the first subtype, and not from its
9688      --  (anonymous) base type.
9689
9690      if Has_Predicates (Parent_Type)
9691        or else Has_Predicates (First_Subtype (Parent_Type))
9692      then
9693         Set_Has_Predicates (Derived_Type);
9694      end if;
9695
9696      --  The derived type inherits representation clauses from the parent
9697      --  type, and from any interfaces.
9698
9699      Inherit_Rep_Item_Chain (Derived_Type, Parent_Type);
9700
9701      declare
9702         Iface : Node_Id := First (Abstract_Interface_List (Derived_Type));
9703      begin
9704         while Present (Iface) loop
9705            Inherit_Rep_Item_Chain (Derived_Type, Entity (Iface));
9706            Next (Iface);
9707         end loop;
9708      end;
9709
9710      --  If the parent type has delayed rep aspects, then mark the derived
9711      --  type as possibly inheriting a delayed rep aspect.
9712
9713      if Has_Delayed_Rep_Aspects (Parent_Type) then
9714         Set_May_Inherit_Delayed_Rep_Aspects (Derived_Type);
9715      end if;
9716
9717      --  A derived type becomes Ghost when its parent type is also Ghost
9718      --  (SPARK RM 6.9(9)). Note that the Ghost-related attributes are not
9719      --  directly inherited because the Ghost policy in effect may differ.
9720
9721      if Is_Ghost_Entity (Parent_Type) then
9722         Set_Is_Ghost_Entity (Derived_Type);
9723      end if;
9724
9725      --  Type dependent processing
9726
9727      case Ekind (Parent_Type) is
9728         when Numeric_Kind =>
9729            Build_Derived_Numeric_Type (N, Parent_Type, Derived_Type);
9730
9731         when Array_Kind =>
9732            Build_Derived_Array_Type (N, Parent_Type,  Derived_Type);
9733
9734         when Class_Wide_Kind
9735            | E_Record_Subtype
9736            | E_Record_Type
9737         =>
9738            Build_Derived_Record_Type
9739              (N, Parent_Type, Derived_Type, Derive_Subps);
9740            return;
9741
9742         when Enumeration_Kind =>
9743            Build_Derived_Enumeration_Type (N, Parent_Type, Derived_Type);
9744
9745         when Access_Kind =>
9746            Build_Derived_Access_Type (N, Parent_Type, Derived_Type);
9747
9748         when Incomplete_Or_Private_Kind =>
9749            Build_Derived_Private_Type
9750              (N, Parent_Type, Derived_Type, Is_Completion, Derive_Subps);
9751
9752            --  For discriminated types, the derivation includes deriving
9753            --  primitive operations. For others it is done below.
9754
9755            if Is_Tagged_Type (Parent_Type)
9756              or else Has_Discriminants (Parent_Type)
9757              or else (Present (Full_View (Parent_Type))
9758                        and then Has_Discriminants (Full_View (Parent_Type)))
9759            then
9760               return;
9761            end if;
9762
9763         when Concurrent_Kind =>
9764            Build_Derived_Concurrent_Type (N, Parent_Type, Derived_Type);
9765
9766         when others =>
9767            raise Program_Error;
9768      end case;
9769
9770      --  Nothing more to do if some error occurred
9771
9772      if Etype (Derived_Type) = Any_Type then
9773         return;
9774      end if;
9775
9776      --  Set delayed freeze and then derive subprograms, we need to do this
9777      --  in this order so that derived subprograms inherit the derived freeze
9778      --  if necessary.
9779
9780      Set_Has_Delayed_Freeze (Derived_Type);
9781
9782      if Derive_Subps then
9783         Derive_Subprograms (Parent_Type, Derived_Type);
9784      end if;
9785
9786      Set_Has_Primitive_Operations
9787        (Base_Type (Derived_Type), Has_Primitive_Operations (Parent_Type));
9788   end Build_Derived_Type;
9789
9790   -----------------------
9791   -- Build_Discriminal --
9792   -----------------------
9793
9794   procedure Build_Discriminal (Discrim : Entity_Id) is
9795      D_Minal : Entity_Id;
9796      CR_Disc : Entity_Id;
9797
9798   begin
9799      --  A discriminal has the same name as the discriminant
9800
9801      D_Minal := Make_Defining_Identifier (Sloc (Discrim), Chars (Discrim));
9802
9803      Set_Ekind     (D_Minal, E_In_Parameter);
9804      Set_Mechanism (D_Minal, Default_Mechanism);
9805      Set_Etype     (D_Minal, Etype (Discrim));
9806      Set_Scope     (D_Minal, Current_Scope);
9807      Set_Parent    (D_Minal, Parent (Discrim));
9808
9809      Set_Discriminal (Discrim, D_Minal);
9810      Set_Discriminal_Link (D_Minal, Discrim);
9811
9812      --  For task types, build at once the discriminants of the corresponding
9813      --  record, which are needed if discriminants are used in entry defaults
9814      --  and in family bounds.
9815
9816      if Is_Concurrent_Type (Current_Scope)
9817           or else
9818         Is_Limited_Type    (Current_Scope)
9819      then
9820         CR_Disc := Make_Defining_Identifier (Sloc (Discrim), Chars (Discrim));
9821
9822         Set_Ekind            (CR_Disc, E_In_Parameter);
9823         Set_Mechanism        (CR_Disc, Default_Mechanism);
9824         Set_Etype            (CR_Disc, Etype (Discrim));
9825         Set_Scope            (CR_Disc, Current_Scope);
9826         Set_Discriminal_Link (CR_Disc, Discrim);
9827         Set_CR_Discriminant  (Discrim, CR_Disc);
9828      end if;
9829   end Build_Discriminal;
9830
9831   ------------------------------------
9832   -- Build_Discriminant_Constraints --
9833   ------------------------------------
9834
9835   function Build_Discriminant_Constraints
9836     (T           : Entity_Id;
9837      Def         : Node_Id;
9838      Derived_Def : Boolean := False) return Elist_Id
9839   is
9840      C        : constant Node_Id := Constraint (Def);
9841      Nb_Discr : constant Nat     := Number_Discriminants (T);
9842
9843      Discr_Expr : array (1 .. Nb_Discr) of Node_Id := (others => Empty);
9844      --  Saves the expression corresponding to a given discriminant in T
9845
9846      function Pos_Of_Discr (T : Entity_Id; D : Entity_Id) return Nat;
9847      --  Return the Position number within array Discr_Expr of a discriminant
9848      --  D within the discriminant list of the discriminated type T.
9849
9850      procedure Process_Discriminant_Expression
9851         (Expr : Node_Id;
9852          D    : Entity_Id);
9853      --  If this is a discriminant constraint on a partial view, do not
9854      --  generate an overflow check on the discriminant expression. The check
9855      --  will be generated when constraining the full view. Otherwise the
9856      --  backend creates duplicate symbols for the temporaries corresponding
9857      --  to the expressions to be checked, causing spurious assembler errors.
9858
9859      ------------------
9860      -- Pos_Of_Discr --
9861      ------------------
9862
9863      function Pos_Of_Discr (T : Entity_Id; D : Entity_Id) return Nat is
9864         Disc : Entity_Id;
9865
9866      begin
9867         Disc := First_Discriminant (T);
9868         for J in Discr_Expr'Range loop
9869            if Disc = D then
9870               return J;
9871            end if;
9872
9873            Next_Discriminant (Disc);
9874         end loop;
9875
9876         --  Note: Since this function is called on discriminants that are
9877         --  known to belong to the discriminated type, falling through the
9878         --  loop with no match signals an internal compiler error.
9879
9880         raise Program_Error;
9881      end Pos_Of_Discr;
9882
9883      -------------------------------------
9884      -- Process_Discriminant_Expression --
9885      -------------------------------------
9886
9887      procedure Process_Discriminant_Expression
9888         (Expr : Node_Id;
9889          D    : Entity_Id)
9890      is
9891         BDT : constant Entity_Id := Base_Type (Etype (D));
9892
9893      begin
9894         --  If this is a discriminant constraint on a partial view, do
9895         --  not generate an overflow on the discriminant expression. The
9896         --  check will be generated when constraining the full view.
9897
9898         if Is_Private_Type (T)
9899           and then Present (Full_View (T))
9900         then
9901            Analyze_And_Resolve (Expr, BDT, Suppress => Overflow_Check);
9902         else
9903            Analyze_And_Resolve (Expr, BDT);
9904         end if;
9905      end Process_Discriminant_Expression;
9906
9907      --  Declarations local to Build_Discriminant_Constraints
9908
9909      Discr : Entity_Id;
9910      E     : Entity_Id;
9911      Elist : constant Elist_Id := New_Elmt_List;
9912
9913      Constr   : Node_Id;
9914      Expr     : Node_Id;
9915      Id       : Node_Id;
9916      Position : Nat;
9917      Found    : Boolean;
9918
9919      Discrim_Present : Boolean := False;
9920
9921   --  Start of processing for Build_Discriminant_Constraints
9922
9923   begin
9924      --  The following loop will process positional associations only.
9925      --  For a positional association, the (single) discriminant is
9926      --  implicitly specified by position, in textual order (RM 3.7.2).
9927
9928      Discr  := First_Discriminant (T);
9929      Constr := First (Constraints (C));
9930      for D in Discr_Expr'Range loop
9931         exit when Nkind (Constr) = N_Discriminant_Association;
9932
9933         if No (Constr) then
9934            Error_Msg_N ("too few discriminants given in constraint", C);
9935            return New_Elmt_List;
9936
9937         elsif Nkind (Constr) = N_Range
9938           or else (Nkind (Constr) = N_Attribute_Reference
9939                     and then Attribute_Name (Constr) = Name_Range)
9940         then
9941            Error_Msg_N
9942              ("a range is not a valid discriminant constraint", Constr);
9943            Discr_Expr (D) := Error;
9944
9945         elsif Nkind (Constr) = N_Subtype_Indication then
9946            Error_Msg_N
9947              ("a subtype indication is not a valid discriminant constraint",
9948               Constr);
9949            Discr_Expr (D) := Error;
9950
9951         else
9952            Process_Discriminant_Expression (Constr, Discr);
9953            Discr_Expr (D) := Constr;
9954         end if;
9955
9956         Next_Discriminant (Discr);
9957         Next (Constr);
9958      end loop;
9959
9960      if No (Discr) and then Present (Constr) then
9961         Error_Msg_N ("too many discriminants given in constraint", Constr);
9962         return New_Elmt_List;
9963      end if;
9964
9965      --  Named associations can be given in any order, but if both positional
9966      --  and named associations are used in the same discriminant constraint,
9967      --  then positional associations must occur first, at their normal
9968      --  position. Hence once a named association is used, the rest of the
9969      --  discriminant constraint must use only named associations.
9970
9971      while Present (Constr) loop
9972
9973         --  Positional association forbidden after a named association
9974
9975         if Nkind (Constr) /= N_Discriminant_Association then
9976            Error_Msg_N ("positional association follows named one", Constr);
9977            return New_Elmt_List;
9978
9979         --  Otherwise it is a named association
9980
9981         else
9982            --  E records the type of the discriminants in the named
9983            --  association. All the discriminants specified in the same name
9984            --  association must have the same type.
9985
9986            E := Empty;
9987
9988            --  Search the list of discriminants in T to see if the simple name
9989            --  given in the constraint matches any of them.
9990
9991            Id := First (Selector_Names (Constr));
9992            while Present (Id) loop
9993               Found := False;
9994
9995               --  If Original_Discriminant is present, we are processing a
9996               --  generic instantiation and this is an instance node. We need
9997               --  to find the name of the corresponding discriminant in the
9998               --  actual record type T and not the name of the discriminant in
9999               --  the generic formal. Example:
10000
10001               --    generic
10002               --       type G (D : int) is private;
10003               --    package P is
10004               --       subtype W is G (D => 1);
10005               --    end package;
10006               --    type Rec (X : int) is record ... end record;
10007               --    package Q is new P (G => Rec);
10008
10009               --  At the point of the instantiation, formal type G is Rec
10010               --  and therefore when reanalyzing "subtype W is G (D => 1);"
10011               --  which really looks like "subtype W is Rec (D => 1);" at
10012               --  the point of instantiation, we want to find the discriminant
10013               --  that corresponds to D in Rec, i.e. X.
10014
10015               if Present (Original_Discriminant (Id))
10016                 and then In_Instance
10017               then
10018                  Discr := Find_Corresponding_Discriminant (Id, T);
10019                  Found := True;
10020
10021               else
10022                  Discr := First_Discriminant (T);
10023                  while Present (Discr) loop
10024                     if Chars (Discr) = Chars (Id) then
10025                        Found := True;
10026                        exit;
10027                     end if;
10028
10029                     Next_Discriminant (Discr);
10030                  end loop;
10031
10032                  if not Found then
10033                     Error_Msg_N ("& does not match any discriminant", Id);
10034                     return New_Elmt_List;
10035
10036                  --  If the parent type is a generic formal, preserve the
10037                  --  name of the discriminant for subsequent instances.
10038                  --  see comment at the beginning of this if statement.
10039
10040                  elsif Is_Generic_Type (Root_Type (T)) then
10041                     Set_Original_Discriminant (Id, Discr);
10042                  end if;
10043               end if;
10044
10045               Position := Pos_Of_Discr (T, Discr);
10046
10047               if Present (Discr_Expr (Position)) then
10048                  Error_Msg_N ("duplicate constraint for discriminant&", Id);
10049
10050               else
10051                  --  Each discriminant specified in the same named association
10052                  --  must be associated with a separate copy of the
10053                  --  corresponding expression.
10054
10055                  if Present (Next (Id)) then
10056                     Expr := New_Copy_Tree (Expression (Constr));
10057                     Set_Parent (Expr, Parent (Expression (Constr)));
10058                  else
10059                     Expr := Expression (Constr);
10060                  end if;
10061
10062                  Discr_Expr (Position) := Expr;
10063                  Process_Discriminant_Expression (Expr, Discr);
10064               end if;
10065
10066               --  A discriminant association with more than one discriminant
10067               --  name is only allowed if the named discriminants are all of
10068               --  the same type (RM 3.7.1(8)).
10069
10070               if E = Empty then
10071                  E := Base_Type (Etype (Discr));
10072
10073               elsif Base_Type (Etype (Discr)) /= E then
10074                  Error_Msg_N
10075                    ("all discriminants in an association " &
10076                     "must have the same type", Id);
10077               end if;
10078
10079               Next (Id);
10080            end loop;
10081         end if;
10082
10083         Next (Constr);
10084      end loop;
10085
10086      --  A discriminant constraint must provide exactly one value for each
10087      --  discriminant of the type (RM 3.7.1(8)).
10088
10089      for J in Discr_Expr'Range loop
10090         if No (Discr_Expr (J)) then
10091            Error_Msg_N ("too few discriminants given in constraint", C);
10092            return New_Elmt_List;
10093         end if;
10094      end loop;
10095
10096      --  Determine if there are discriminant expressions in the constraint
10097
10098      for J in Discr_Expr'Range loop
10099         if Denotes_Discriminant
10100              (Discr_Expr (J), Check_Concurrent => True)
10101         then
10102            Discrim_Present := True;
10103         end if;
10104      end loop;
10105
10106      --  Build an element list consisting of the expressions given in the
10107      --  discriminant constraint and apply the appropriate checks. The list
10108      --  is constructed after resolving any named discriminant associations
10109      --  and therefore the expressions appear in the textual order of the
10110      --  discriminants.
10111
10112      Discr := First_Discriminant (T);
10113      for J in Discr_Expr'Range loop
10114         if Discr_Expr (J) /= Error then
10115            Append_Elmt (Discr_Expr (J), Elist);
10116
10117            --  If any of the discriminant constraints is given by a
10118            --  discriminant and we are in a derived type declaration we
10119            --  have a discriminant renaming. Establish link between new
10120            --  and old discriminant. The new discriminant has an implicit
10121            --  dereference if the old one does.
10122
10123            if Denotes_Discriminant (Discr_Expr (J)) then
10124               if Derived_Def then
10125                  declare
10126                     New_Discr : constant Entity_Id := Entity (Discr_Expr (J));
10127
10128                  begin
10129                     Set_Corresponding_Discriminant (New_Discr, Discr);
10130                     Set_Has_Implicit_Dereference (New_Discr,
10131                       Has_Implicit_Dereference (Discr));
10132                  end;
10133               end if;
10134
10135            --  Force the evaluation of non-discriminant expressions.
10136            --  If we have found a discriminant in the constraint 3.4(26)
10137            --  and 3.8(18) demand that no range checks are performed are
10138            --  after evaluation. If the constraint is for a component
10139            --  definition that has a per-object constraint, expressions are
10140            --  evaluated but not checked either. In all other cases perform
10141            --  a range check.
10142
10143            else
10144               if Discrim_Present then
10145                  null;
10146
10147               elsif Nkind (Parent (Parent (Def))) = N_Component_Declaration
10148                 and then Has_Per_Object_Constraint
10149                            (Defining_Identifier (Parent (Parent (Def))))
10150               then
10151                  null;
10152
10153               elsif Is_Access_Type (Etype (Discr)) then
10154                  Apply_Constraint_Check (Discr_Expr (J), Etype (Discr));
10155
10156               else
10157                  Apply_Range_Check (Discr_Expr (J), Etype (Discr));
10158               end if;
10159
10160               Force_Evaluation (Discr_Expr (J));
10161            end if;
10162
10163            --  Check that the designated type of an access discriminant's
10164            --  expression is not a class-wide type unless the discriminant's
10165            --  designated type is also class-wide.
10166
10167            if Ekind (Etype (Discr)) = E_Anonymous_Access_Type
10168              and then not Is_Class_Wide_Type
10169                             (Designated_Type (Etype (Discr)))
10170              and then Etype (Discr_Expr (J)) /= Any_Type
10171              and then Is_Class_Wide_Type
10172                         (Designated_Type (Etype (Discr_Expr (J))))
10173            then
10174               Wrong_Type (Discr_Expr (J), Etype (Discr));
10175
10176            elsif Is_Access_Type (Etype (Discr))
10177              and then not Is_Access_Constant (Etype (Discr))
10178              and then Is_Access_Type (Etype (Discr_Expr (J)))
10179              and then Is_Access_Constant (Etype (Discr_Expr (J)))
10180            then
10181               Error_Msg_NE
10182                 ("constraint for discriminant& must be access to variable",
10183                  Def, Discr);
10184            end if;
10185         end if;
10186
10187         Next_Discriminant (Discr);
10188      end loop;
10189
10190      return Elist;
10191   end Build_Discriminant_Constraints;
10192
10193   ---------------------------------
10194   -- Build_Discriminated_Subtype --
10195   ---------------------------------
10196
10197   procedure Build_Discriminated_Subtype
10198     (T           : Entity_Id;
10199      Def_Id      : Entity_Id;
10200      Elist       : Elist_Id;
10201      Related_Nod : Node_Id;
10202      For_Access  : Boolean := False)
10203   is
10204      Has_Discrs  : constant Boolean := Has_Discriminants (T);
10205      Constrained : constant Boolean :=
10206                      (Has_Discrs
10207                         and then not Is_Empty_Elmt_List (Elist)
10208                         and then not Is_Class_Wide_Type (T))
10209                        or else Is_Constrained (T);
10210
10211   begin
10212      if Ekind (T) = E_Record_Type then
10213         if For_Access then
10214            Set_Ekind (Def_Id, E_Private_Subtype);
10215            Set_Is_For_Access_Subtype (Def_Id, True);
10216         else
10217            Set_Ekind (Def_Id, E_Record_Subtype);
10218         end if;
10219
10220         --  Inherit preelaboration flag from base, for types for which it
10221         --  may have been set: records, private types, protected types.
10222
10223         Set_Known_To_Have_Preelab_Init
10224           (Def_Id, Known_To_Have_Preelab_Init (T));
10225
10226      elsif Ekind (T) = E_Task_Type then
10227         Set_Ekind (Def_Id, E_Task_Subtype);
10228
10229      elsif Ekind (T) = E_Protected_Type then
10230         Set_Ekind (Def_Id, E_Protected_Subtype);
10231         Set_Known_To_Have_Preelab_Init
10232           (Def_Id, Known_To_Have_Preelab_Init (T));
10233
10234      elsif Is_Private_Type (T) then
10235         Set_Ekind (Def_Id, Subtype_Kind (Ekind (T)));
10236         Set_Known_To_Have_Preelab_Init
10237           (Def_Id, Known_To_Have_Preelab_Init (T));
10238
10239         --  Private subtypes may have private dependents
10240
10241         Set_Private_Dependents (Def_Id, New_Elmt_List);
10242
10243      elsif Is_Class_Wide_Type (T) then
10244         Set_Ekind (Def_Id, E_Class_Wide_Subtype);
10245
10246      else
10247         --  Incomplete type. Attach subtype to list of dependents, to be
10248         --  completed with full view of parent type,  unless is it the
10249         --  designated subtype of a record component within an init_proc.
10250         --  This last case arises for a component of an access type whose
10251         --  designated type is incomplete (e.g. a Taft Amendment type).
10252         --  The designated subtype is within an inner scope, and needs no
10253         --  elaboration, because only the access type is needed in the
10254         --  initialization procedure.
10255
10256         if Ekind (T) = E_Incomplete_Type then
10257            Set_Ekind (Def_Id, E_Incomplete_Subtype);
10258         else
10259            Set_Ekind (Def_Id, Ekind (T));
10260         end if;
10261
10262         if For_Access and then Within_Init_Proc then
10263            null;
10264         else
10265            Append_Elmt (Def_Id, Private_Dependents (T));
10266         end if;
10267      end if;
10268
10269      Set_Etype             (Def_Id, T);
10270      Init_Size_Align       (Def_Id);
10271      Set_Has_Discriminants (Def_Id, Has_Discrs);
10272      Set_Is_Constrained    (Def_Id, Constrained);
10273
10274      Set_First_Entity      (Def_Id, First_Entity   (T));
10275      Set_Last_Entity       (Def_Id, Last_Entity    (T));
10276      Set_Has_Implicit_Dereference
10277                            (Def_Id, Has_Implicit_Dereference (T));
10278      Set_Has_Pragma_Unreferenced_Objects
10279                            (Def_Id, Has_Pragma_Unreferenced_Objects (T));
10280
10281      --  If the subtype is the completion of a private declaration, there may
10282      --  have been representation clauses for the partial view, and they must
10283      --  be preserved. Build_Derived_Type chains the inherited clauses with
10284      --  the ones appearing on the extension. If this comes from a subtype
10285      --  declaration, all clauses are inherited.
10286
10287      if No (First_Rep_Item (Def_Id)) then
10288         Set_First_Rep_Item (Def_Id, First_Rep_Item (T));
10289      end if;
10290
10291      if Is_Tagged_Type (T) then
10292         Set_Is_Tagged_Type (Def_Id);
10293         Set_No_Tagged_Streams_Pragma (Def_Id, No_Tagged_Streams_Pragma (T));
10294         Make_Class_Wide_Type (Def_Id);
10295      end if;
10296
10297      Set_Stored_Constraint (Def_Id, No_Elist);
10298
10299      if Has_Discrs then
10300         Set_Discriminant_Constraint (Def_Id, Elist);
10301         Set_Stored_Constraint_From_Discriminant_Constraint (Def_Id);
10302      end if;
10303
10304      if Is_Tagged_Type (T) then
10305
10306         --  Ada 2005 (AI-251): In case of concurrent types we inherit the
10307         --  concurrent record type (which has the list of primitive
10308         --  operations).
10309
10310         if Ada_Version >= Ada_2005
10311           and then Is_Concurrent_Type (T)
10312         then
10313            Set_Corresponding_Record_Type (Def_Id,
10314               Corresponding_Record_Type (T));
10315         else
10316            Set_Direct_Primitive_Operations (Def_Id,
10317              Direct_Primitive_Operations (T));
10318         end if;
10319
10320         Set_Is_Abstract_Type (Def_Id, Is_Abstract_Type (T));
10321      end if;
10322
10323      --  Subtypes introduced by component declarations do not need to be
10324      --  marked as delayed, and do not get freeze nodes, because the semantics
10325      --  verifies that the parents of the subtypes are frozen before the
10326      --  enclosing record is frozen.
10327
10328      if not Is_Type (Scope (Def_Id)) then
10329         Set_Depends_On_Private (Def_Id, Depends_On_Private (T));
10330
10331         if Is_Private_Type (T)
10332           and then Present (Full_View (T))
10333         then
10334            Conditional_Delay (Def_Id, Full_View (T));
10335         else
10336            Conditional_Delay (Def_Id, T);
10337         end if;
10338      end if;
10339
10340      if Is_Record_Type (T) then
10341         Set_Is_Limited_Record (Def_Id, Is_Limited_Record (T));
10342
10343         if Has_Discrs
10344           and then not Is_Empty_Elmt_List (Elist)
10345           and then not For_Access
10346         then
10347            Create_Constrained_Components (Def_Id, Related_Nod, T, Elist);
10348
10349         elsif not For_Access then
10350            Set_Cloned_Subtype (Def_Id, T);
10351         end if;
10352      end if;
10353   end Build_Discriminated_Subtype;
10354
10355   ---------------------------
10356   -- Build_Itype_Reference --
10357   ---------------------------
10358
10359   procedure Build_Itype_Reference
10360     (Ityp : Entity_Id;
10361      Nod  : Node_Id)
10362   is
10363      IR : constant Node_Id := Make_Itype_Reference (Sloc (Nod));
10364   begin
10365
10366      --  Itype references are only created for use by the back-end
10367
10368      if Inside_A_Generic then
10369         return;
10370      else
10371         Set_Itype (IR, Ityp);
10372
10373         --  If Nod is a library unit entity, then Insert_After won't work,
10374         --  because Nod is not a member of any list. Therefore, we use
10375         --  Add_Global_Declaration in this case. This can happen if we have a
10376         --  build-in-place library function, child unit or not.
10377
10378         if (Nkind (Nod) in N_Entity and then Is_Compilation_Unit (Nod))
10379           or else
10380             (Nkind_In (Nod,
10381                N_Defining_Program_Unit_Name, N_Subprogram_Declaration)
10382               and then Is_Compilation_Unit (Defining_Entity (Nod)))
10383         then
10384            Add_Global_Declaration (IR);
10385         else
10386            Insert_After (Nod, IR);
10387         end if;
10388      end if;
10389   end Build_Itype_Reference;
10390
10391   ------------------------
10392   -- Build_Scalar_Bound --
10393   ------------------------
10394
10395   function Build_Scalar_Bound
10396     (Bound : Node_Id;
10397      Par_T : Entity_Id;
10398      Der_T : Entity_Id) return Node_Id
10399   is
10400      New_Bound : Entity_Id;
10401
10402   begin
10403      --  Note: not clear why this is needed, how can the original bound
10404      --  be unanalyzed at this point? and if it is, what business do we
10405      --  have messing around with it? and why is the base type of the
10406      --  parent type the right type for the resolution. It probably is
10407      --  not. It is OK for the new bound we are creating, but not for
10408      --  the old one??? Still if it never happens, no problem.
10409
10410      Analyze_And_Resolve (Bound, Base_Type (Par_T));
10411
10412      if Nkind_In (Bound, N_Integer_Literal, N_Real_Literal) then
10413         New_Bound := New_Copy (Bound);
10414         Set_Etype (New_Bound, Der_T);
10415         Set_Analyzed (New_Bound);
10416
10417      elsif Is_Entity_Name (Bound) then
10418         New_Bound := OK_Convert_To (Der_T, New_Copy (Bound));
10419
10420      --  The following is almost certainly wrong. What business do we have
10421      --  relocating a node (Bound) that is presumably still attached to
10422      --  the tree elsewhere???
10423
10424      else
10425         New_Bound := OK_Convert_To (Der_T, Relocate_Node (Bound));
10426      end if;
10427
10428      Set_Etype (New_Bound, Der_T);
10429      return New_Bound;
10430   end Build_Scalar_Bound;
10431
10432   --------------------------------
10433   -- Build_Underlying_Full_View --
10434   --------------------------------
10435
10436   procedure Build_Underlying_Full_View
10437     (N   : Node_Id;
10438      Typ : Entity_Id;
10439      Par : Entity_Id)
10440   is
10441      Loc  : constant Source_Ptr := Sloc (N);
10442      Subt : constant Entity_Id :=
10443               Make_Defining_Identifier
10444                 (Loc, New_External_Name (Chars (Typ), 'S'));
10445
10446      Constr : Node_Id;
10447      Indic  : Node_Id;
10448      C      : Node_Id;
10449      Id     : Node_Id;
10450
10451      procedure Set_Discriminant_Name (Id : Node_Id);
10452      --  If the derived type has discriminants, they may rename discriminants
10453      --  of the parent. When building the full view of the parent, we need to
10454      --  recover the names of the original discriminants if the constraint is
10455      --  given by named associations.
10456
10457      ---------------------------
10458      -- Set_Discriminant_Name --
10459      ---------------------------
10460
10461      procedure Set_Discriminant_Name (Id : Node_Id) is
10462         Disc : Entity_Id;
10463
10464      begin
10465         Set_Original_Discriminant (Id, Empty);
10466
10467         if Has_Discriminants (Typ) then
10468            Disc := First_Discriminant (Typ);
10469            while Present (Disc) loop
10470               if Chars (Disc) = Chars (Id)
10471                 and then Present (Corresponding_Discriminant (Disc))
10472               then
10473                  Set_Chars (Id, Chars (Corresponding_Discriminant (Disc)));
10474               end if;
10475               Next_Discriminant (Disc);
10476            end loop;
10477         end if;
10478      end Set_Discriminant_Name;
10479
10480   --  Start of processing for Build_Underlying_Full_View
10481
10482   begin
10483      if Nkind (N) = N_Full_Type_Declaration then
10484         Constr := Constraint (Subtype_Indication (Type_Definition (N)));
10485
10486      elsif Nkind (N) = N_Subtype_Declaration then
10487         Constr := New_Copy_Tree (Constraint (Subtype_Indication (N)));
10488
10489      elsif Nkind (N) = N_Component_Declaration then
10490         Constr :=
10491           New_Copy_Tree
10492             (Constraint (Subtype_Indication (Component_Definition (N))));
10493
10494      else
10495         raise Program_Error;
10496      end if;
10497
10498      C := First (Constraints (Constr));
10499      while Present (C) loop
10500         if Nkind (C) = N_Discriminant_Association then
10501            Id := First (Selector_Names (C));
10502            while Present (Id) loop
10503               Set_Discriminant_Name (Id);
10504               Next (Id);
10505            end loop;
10506         end if;
10507
10508         Next (C);
10509      end loop;
10510
10511      Indic :=
10512        Make_Subtype_Declaration (Loc,
10513          Defining_Identifier => Subt,
10514          Subtype_Indication  =>
10515            Make_Subtype_Indication (Loc,
10516              Subtype_Mark => New_Occurrence_Of (Par, Loc),
10517              Constraint   => New_Copy_Tree (Constr)));
10518
10519      --  If this is a component subtype for an outer itype, it is not
10520      --  a list member, so simply set the parent link for analysis: if
10521      --  the enclosing type does not need to be in a declarative list,
10522      --  neither do the components.
10523
10524      if Is_List_Member (N)
10525        and then Nkind (N) /= N_Component_Declaration
10526      then
10527         Insert_Before (N, Indic);
10528      else
10529         Set_Parent (Indic, Parent (N));
10530      end if;
10531
10532      Analyze (Indic);
10533      Set_Underlying_Full_View (Typ, Full_View (Subt));
10534      Set_Is_Underlying_Full_View (Full_View (Subt));
10535   end Build_Underlying_Full_View;
10536
10537   -------------------------------
10538   -- Check_Abstract_Overriding --
10539   -------------------------------
10540
10541   procedure Check_Abstract_Overriding (T : Entity_Id) is
10542      Alias_Subp : Entity_Id;
10543      Elmt       : Elmt_Id;
10544      Op_List    : Elist_Id;
10545      Subp       : Entity_Id;
10546      Type_Def   : Node_Id;
10547
10548      procedure Check_Pragma_Implemented (Subp : Entity_Id);
10549      --  Ada 2012 (AI05-0030): Subprogram Subp overrides an interface routine
10550      --  which has pragma Implemented already set. Check whether Subp's entity
10551      --  kind conforms to the implementation kind of the overridden routine.
10552
10553      procedure Check_Pragma_Implemented
10554        (Subp       : Entity_Id;
10555         Iface_Subp : Entity_Id);
10556      --  Ada 2012 (AI05-0030): Subprogram Subp overrides interface routine
10557      --  Iface_Subp and both entities have pragma Implemented already set on
10558      --  them. Check whether the two implementation kinds are conforming.
10559
10560      procedure Inherit_Pragma_Implemented
10561        (Subp       : Entity_Id;
10562         Iface_Subp : Entity_Id);
10563      --  Ada 2012 (AI05-0030): Interface primitive Subp overrides interface
10564      --  subprogram Iface_Subp which has been marked by pragma Implemented.
10565      --  Propagate the implementation kind of Iface_Subp to Subp.
10566
10567      ------------------------------
10568      -- Check_Pragma_Implemented --
10569      ------------------------------
10570
10571      procedure Check_Pragma_Implemented (Subp : Entity_Id) is
10572         Iface_Alias : constant Entity_Id := Interface_Alias (Subp);
10573         Impl_Kind   : constant Name_Id   := Implementation_Kind (Iface_Alias);
10574         Subp_Alias  : constant Entity_Id := Alias (Subp);
10575         Contr_Typ   : Entity_Id;
10576         Impl_Subp   : Entity_Id;
10577
10578      begin
10579         --  Subp must have an alias since it is a hidden entity used to link
10580         --  an interface subprogram to its overriding counterpart.
10581
10582         pragma Assert (Present (Subp_Alias));
10583
10584         --  Handle aliases to synchronized wrappers
10585
10586         Impl_Subp := Subp_Alias;
10587
10588         if Is_Primitive_Wrapper (Impl_Subp) then
10589            Impl_Subp := Wrapped_Entity (Impl_Subp);
10590         end if;
10591
10592         --  Extract the type of the controlling formal
10593
10594         Contr_Typ := Etype (First_Formal (Subp_Alias));
10595
10596         if Is_Concurrent_Record_Type (Contr_Typ) then
10597            Contr_Typ := Corresponding_Concurrent_Type (Contr_Typ);
10598         end if;
10599
10600         --  An interface subprogram whose implementation kind is By_Entry must
10601         --  be implemented by an entry.
10602
10603         if Impl_Kind = Name_By_Entry
10604           and then Ekind (Impl_Subp) /= E_Entry
10605         then
10606            Error_Msg_Node_2 := Iface_Alias;
10607            Error_Msg_NE
10608              ("type & must implement abstract subprogram & with an entry",
10609               Subp_Alias, Contr_Typ);
10610
10611         elsif Impl_Kind = Name_By_Protected_Procedure then
10612
10613            --  An interface subprogram whose implementation kind is By_
10614            --  Protected_Procedure cannot be implemented by a primitive
10615            --  procedure of a task type.
10616
10617            if Ekind (Contr_Typ) /= E_Protected_Type then
10618               Error_Msg_Node_2 := Contr_Typ;
10619               Error_Msg_NE
10620                 ("interface subprogram & cannot be implemented by a " &
10621                  "primitive procedure of task type &", Subp_Alias,
10622                  Iface_Alias);
10623
10624            --  An interface subprogram whose implementation kind is By_
10625            --  Protected_Procedure must be implemented by a procedure.
10626
10627            elsif Ekind (Impl_Subp) /= E_Procedure then
10628               Error_Msg_Node_2 := Iface_Alias;
10629               Error_Msg_NE
10630                 ("type & must implement abstract subprogram & with a " &
10631                  "procedure", Subp_Alias, Contr_Typ);
10632
10633            elsif Present (Get_Rep_Pragma (Impl_Subp, Name_Implemented))
10634              and then Implementation_Kind (Impl_Subp) /= Impl_Kind
10635            then
10636               Error_Msg_Name_1 := Impl_Kind;
10637               Error_Msg_N
10638                ("overriding operation& must have synchronization%",
10639                 Subp_Alias);
10640            end if;
10641
10642         --  If primitive has Optional synchronization, overriding operation
10643         --  must match if it has an explicit synchronization..
10644
10645         elsif Present (Get_Rep_Pragma (Impl_Subp, Name_Implemented))
10646           and then Implementation_Kind (Impl_Subp) /= Impl_Kind
10647         then
10648               Error_Msg_Name_1 := Impl_Kind;
10649               Error_Msg_N
10650                ("overriding operation& must have syncrhonization%",
10651                 Subp_Alias);
10652         end if;
10653      end Check_Pragma_Implemented;
10654
10655      ------------------------------
10656      -- Check_Pragma_Implemented --
10657      ------------------------------
10658
10659      procedure Check_Pragma_Implemented
10660        (Subp       : Entity_Id;
10661         Iface_Subp : Entity_Id)
10662      is
10663         Iface_Kind : constant Name_Id := Implementation_Kind (Iface_Subp);
10664         Subp_Kind  : constant Name_Id := Implementation_Kind (Subp);
10665
10666      begin
10667         --  Ada 2012 (AI05-0030): The implementation kinds of an overridden
10668         --  and overriding subprogram are different. In general this is an
10669         --  error except when the implementation kind of the overridden
10670         --  subprograms is By_Any or Optional.
10671
10672         if Iface_Kind /= Subp_Kind
10673           and then Iface_Kind /= Name_By_Any
10674           and then Iface_Kind /= Name_Optional
10675         then
10676            if Iface_Kind = Name_By_Entry then
10677               Error_Msg_N
10678                 ("incompatible implementation kind, overridden subprogram " &
10679                  "is marked By_Entry", Subp);
10680            else
10681               Error_Msg_N
10682                 ("incompatible implementation kind, overridden subprogram " &
10683                  "is marked By_Protected_Procedure", Subp);
10684            end if;
10685         end if;
10686      end Check_Pragma_Implemented;
10687
10688      --------------------------------
10689      -- Inherit_Pragma_Implemented --
10690      --------------------------------
10691
10692      procedure Inherit_Pragma_Implemented
10693        (Subp       : Entity_Id;
10694         Iface_Subp : Entity_Id)
10695      is
10696         Iface_Kind : constant Name_Id    := Implementation_Kind (Iface_Subp);
10697         Loc        : constant Source_Ptr := Sloc (Subp);
10698         Impl_Prag  : Node_Id;
10699
10700      begin
10701         --  Since the implementation kind is stored as a representation item
10702         --  rather than a flag, create a pragma node.
10703
10704         Impl_Prag :=
10705           Make_Pragma (Loc,
10706             Chars                        => Name_Implemented,
10707             Pragma_Argument_Associations => New_List (
10708               Make_Pragma_Argument_Association (Loc,
10709                 Expression => New_Occurrence_Of (Subp, Loc)),
10710
10711               Make_Pragma_Argument_Association (Loc,
10712                 Expression => Make_Identifier (Loc, Iface_Kind))));
10713
10714         --  The pragma doesn't need to be analyzed because it is internally
10715         --  built. It is safe to directly register it as a rep item since we
10716         --  are only interested in the characters of the implementation kind.
10717
10718         Record_Rep_Item (Subp, Impl_Prag);
10719      end Inherit_Pragma_Implemented;
10720
10721   --  Start of processing for Check_Abstract_Overriding
10722
10723   begin
10724      Op_List := Primitive_Operations (T);
10725
10726      --  Loop to check primitive operations
10727
10728      Elmt := First_Elmt (Op_List);
10729      while Present (Elmt) loop
10730         Subp := Node (Elmt);
10731         Alias_Subp := Alias (Subp);
10732
10733         --  Inherited subprograms are identified by the fact that they do not
10734         --  come from source, and the associated source location is the
10735         --  location of the first subtype of the derived type.
10736
10737         --  Ada 2005 (AI-228): Apply the rules of RM-3.9.3(6/2) for
10738         --  subprograms that "require overriding".
10739
10740         --  Special exception, do not complain about failure to override the
10741         --  stream routines _Input and _Output, as well as the primitive
10742         --  operations used in dispatching selects since we always provide
10743         --  automatic overridings for these subprograms.
10744
10745         --  The partial view of T may have been a private extension, for
10746         --  which inherited functions dispatching on result are abstract.
10747         --  If the full view is a null extension, there is no need for
10748         --  overriding in Ada 2005, but wrappers need to be built for them
10749         --  (see exp_ch3, Build_Controlling_Function_Wrappers).
10750
10751         if Is_Null_Extension (T)
10752           and then Has_Controlling_Result (Subp)
10753           and then Ada_Version >= Ada_2005
10754           and then Present (Alias_Subp)
10755           and then not Comes_From_Source (Subp)
10756           and then not Is_Abstract_Subprogram (Alias_Subp)
10757           and then not Is_Access_Type (Etype (Subp))
10758         then
10759            null;
10760
10761         --  Ada 2005 (AI-251): Internal entities of interfaces need no
10762         --  processing because this check is done with the aliased
10763         --  entity
10764
10765         elsif Present (Interface_Alias (Subp)) then
10766            null;
10767
10768         elsif (Is_Abstract_Subprogram (Subp)
10769                 or else Requires_Overriding (Subp)
10770                 or else
10771                   (Has_Controlling_Result (Subp)
10772                     and then Present (Alias_Subp)
10773                     and then not Comes_From_Source (Subp)
10774                     and then Sloc (Subp) = Sloc (First_Subtype (T))))
10775           and then not Is_TSS (Subp, TSS_Stream_Input)
10776           and then not Is_TSS (Subp, TSS_Stream_Output)
10777           and then not Is_Abstract_Type (T)
10778           and then not Is_Predefined_Interface_Primitive (Subp)
10779
10780            --  Ada 2005 (AI-251): Do not consider hidden entities associated
10781            --  with abstract interface types because the check will be done
10782            --  with the aliased entity (otherwise we generate a duplicated
10783            --  error message).
10784
10785           and then not Present (Interface_Alias (Subp))
10786         then
10787            if Present (Alias_Subp) then
10788
10789               --  Only perform the check for a derived subprogram when the
10790               --  type has an explicit record extension. This avoids incorrect
10791               --  flagging of abstract subprograms for the case of a type
10792               --  without an extension that is derived from a formal type
10793               --  with a tagged actual (can occur within a private part).
10794
10795               --  Ada 2005 (AI-391): In the case of an inherited function with
10796               --  a controlling result of the type, the rule does not apply if
10797               --  the type is a null extension (unless the parent function
10798               --  itself is abstract, in which case the function must still be
10799               --  be overridden). The expander will generate an overriding
10800               --  wrapper function calling the parent subprogram (see
10801               --  Exp_Ch3.Make_Controlling_Wrapper_Functions).
10802
10803               Type_Def := Type_Definition (Parent (T));
10804
10805               if Nkind (Type_Def) = N_Derived_Type_Definition
10806                 and then Present (Record_Extension_Part (Type_Def))
10807                 and then
10808                   (Ada_Version < Ada_2005
10809                      or else not Is_Null_Extension (T)
10810                      or else Ekind (Subp) = E_Procedure
10811                      or else not Has_Controlling_Result (Subp)
10812                      or else Is_Abstract_Subprogram (Alias_Subp)
10813                      or else Requires_Overriding (Subp)
10814                      or else Is_Access_Type (Etype (Subp)))
10815               then
10816                  --  Avoid reporting error in case of abstract predefined
10817                  --  primitive inherited from interface type because the
10818                  --  body of internally generated predefined primitives
10819                  --  of tagged types are generated later by Freeze_Type
10820
10821                  if Is_Interface (Root_Type (T))
10822                    and then Is_Abstract_Subprogram (Subp)
10823                    and then Is_Predefined_Dispatching_Operation (Subp)
10824                    and then not Comes_From_Source (Ultimate_Alias (Subp))
10825                  then
10826                     null;
10827
10828                  --  A null extension is not obliged to override an inherited
10829                  --  procedure subject to pragma Extensions_Visible with value
10830                  --  False and at least one controlling OUT parameter
10831                  --  (SPARK RM 6.1.7(6)).
10832
10833                  elsif Is_Null_Extension (T)
10834                    and then Is_EVF_Procedure (Subp)
10835                  then
10836                     null;
10837
10838                  else
10839                     Error_Msg_NE
10840                       ("type must be declared abstract or & overridden",
10841                        T, Subp);
10842
10843                     --  Traverse the whole chain of aliased subprograms to
10844                     --  complete the error notification. This is especially
10845                     --  useful for traceability of the chain of entities when
10846                     --  the subprogram corresponds with an interface
10847                     --  subprogram (which may be defined in another package).
10848
10849                     if Present (Alias_Subp) then
10850                        declare
10851                           E : Entity_Id;
10852
10853                        begin
10854                           E := Subp;
10855                           while Present (Alias (E)) loop
10856
10857                              --  Avoid reporting redundant errors on entities
10858                              --  inherited from interfaces
10859
10860                              if Sloc (E) /= Sloc (T) then
10861                                 Error_Msg_Sloc := Sloc (E);
10862                                 Error_Msg_NE
10863                                   ("\& has been inherited #", T, Subp);
10864                              end if;
10865
10866                              E := Alias (E);
10867                           end loop;
10868
10869                           Error_Msg_Sloc := Sloc (E);
10870
10871                           --  AI05-0068: report if there is an overriding
10872                           --  non-abstract subprogram that is invisible.
10873
10874                           if Is_Hidden (E)
10875                             and then not Is_Abstract_Subprogram (E)
10876                           then
10877                              Error_Msg_NE
10878                                ("\& subprogram# is not visible",
10879                                 T, Subp);
10880
10881                           --  Clarify the case where a non-null extension must
10882                           --  override inherited procedure subject to pragma
10883                           --  Extensions_Visible with value False and at least
10884                           --  one controlling OUT param.
10885
10886                           elsif Is_EVF_Procedure (E) then
10887                              Error_Msg_NE
10888                                ("\& # is subject to Extensions_Visible False",
10889                                 T, Subp);
10890
10891                           else
10892                              Error_Msg_NE
10893                                ("\& has been inherited from subprogram #",
10894                                 T, Subp);
10895                           end if;
10896                        end;
10897                     end if;
10898                  end if;
10899
10900               --  Ada 2005 (AI-345): Protected or task type implementing
10901               --  abstract interfaces.
10902
10903               elsif Is_Concurrent_Record_Type (T)
10904                 and then Present (Interfaces (T))
10905               then
10906                  --  There is no need to check here RM 9.4(11.9/3) since we
10907                  --  are processing the corresponding record type and the
10908                  --  mode of the overriding subprograms was verified by
10909                  --  Check_Conformance when the corresponding concurrent
10910                  --  type declaration was analyzed.
10911
10912                  Error_Msg_NE
10913                    ("interface subprogram & must be overridden", T, Subp);
10914
10915                  --  Examine primitive operations of synchronized type to find
10916                  --  homonyms that have the wrong profile.
10917
10918                  declare
10919                     Prim : Entity_Id;
10920
10921                  begin
10922                     Prim := First_Entity (Corresponding_Concurrent_Type (T));
10923                     while Present (Prim) loop
10924                        if Chars (Prim) = Chars (Subp) then
10925                           Error_Msg_NE
10926                             ("profile is not type conformant with prefixed "
10927                              & "view profile of inherited operation&",
10928                              Prim, Subp);
10929                        end if;
10930
10931                        Next_Entity (Prim);
10932                     end loop;
10933                  end;
10934               end if;
10935
10936            else
10937               Error_Msg_Node_2 := T;
10938               Error_Msg_N
10939                 ("abstract subprogram& not allowed for type&", Subp);
10940
10941               --  Also post unconditional warning on the type (unconditional
10942               --  so that if there are more than one of these cases, we get
10943               --  them all, and not just the first one).
10944
10945               Error_Msg_Node_2 := Subp;
10946               Error_Msg_N ("nonabstract type& has abstract subprogram&!", T);
10947            end if;
10948
10949         --  A subprogram subject to pragma Extensions_Visible with value
10950         --  "True" cannot override a subprogram subject to the same pragma
10951         --  with value "False" (SPARK RM 6.1.7(5)).
10952
10953         elsif Extensions_Visible_Status (Subp) = Extensions_Visible_True
10954           and then Present (Overridden_Operation (Subp))
10955           and then Extensions_Visible_Status (Overridden_Operation (Subp)) =
10956                    Extensions_Visible_False
10957         then
10958            Error_Msg_Sloc := Sloc (Overridden_Operation (Subp));
10959            Error_Msg_N
10960              ("subprogram & with Extensions_Visible True cannot override "
10961               & "subprogram # with Extensions_Visible False", Subp);
10962         end if;
10963
10964         --  Ada 2012 (AI05-0030): Perform checks related to pragma Implemented
10965
10966         --  Subp is an expander-generated procedure which maps an interface
10967         --  alias to a protected wrapper. The interface alias is flagged by
10968         --  pragma Implemented. Ensure that Subp is a procedure when the
10969         --  implementation kind is By_Protected_Procedure or an entry when
10970         --  By_Entry.
10971
10972         if Ada_Version >= Ada_2012
10973           and then Is_Hidden (Subp)
10974           and then Present (Interface_Alias (Subp))
10975           and then Has_Rep_Pragma (Interface_Alias (Subp), Name_Implemented)
10976         then
10977            Check_Pragma_Implemented (Subp);
10978         end if;
10979
10980         --  Subp is an interface primitive which overrides another interface
10981         --  primitive marked with pragma Implemented.
10982
10983         if Ada_Version >= Ada_2012
10984           and then Present (Overridden_Operation (Subp))
10985           and then Has_Rep_Pragma
10986                      (Overridden_Operation (Subp), Name_Implemented)
10987         then
10988            --  If the overriding routine is also marked by Implemented, check
10989            --  that the two implementation kinds are conforming.
10990
10991            if Has_Rep_Pragma (Subp, Name_Implemented) then
10992               Check_Pragma_Implemented
10993                 (Subp       => Subp,
10994                  Iface_Subp => Overridden_Operation (Subp));
10995
10996            --  Otherwise the overriding routine inherits the implementation
10997            --  kind from the overridden subprogram.
10998
10999            else
11000               Inherit_Pragma_Implemented
11001                 (Subp       => Subp,
11002                  Iface_Subp => Overridden_Operation (Subp));
11003            end if;
11004         end if;
11005
11006         --  If the operation is a wrapper for a synchronized primitive, it
11007         --  may be called indirectly through a dispatching select. We assume
11008         --  that it will be referenced elsewhere indirectly, and suppress
11009         --  warnings about an unused entity.
11010
11011         if Is_Primitive_Wrapper (Subp)
11012           and then Present (Wrapped_Entity (Subp))
11013         then
11014            Set_Referenced (Wrapped_Entity (Subp));
11015         end if;
11016
11017         Next_Elmt (Elmt);
11018      end loop;
11019   end Check_Abstract_Overriding;
11020
11021   ------------------------------------------------
11022   -- Check_Access_Discriminant_Requires_Limited --
11023   ------------------------------------------------
11024
11025   procedure Check_Access_Discriminant_Requires_Limited
11026     (D   : Node_Id;
11027      Loc : Node_Id)
11028   is
11029   begin
11030      --  A discriminant_specification for an access discriminant shall appear
11031      --  only in the declaration for a task or protected type, or for a type
11032      --  with the reserved word 'limited' in its definition or in one of its
11033      --  ancestors (RM 3.7(10)).
11034
11035      --  AI-0063: The proper condition is that type must be immutably limited,
11036      --  or else be a partial view.
11037
11038      if Nkind (Discriminant_Type (D)) = N_Access_Definition then
11039         if Is_Limited_View (Current_Scope)
11040           or else
11041             (Nkind (Parent (Current_Scope)) = N_Private_Type_Declaration
11042               and then Limited_Present (Parent (Current_Scope)))
11043         then
11044            null;
11045
11046         else
11047            Error_Msg_N
11048              ("access discriminants allowed only for limited types", Loc);
11049         end if;
11050      end if;
11051   end Check_Access_Discriminant_Requires_Limited;
11052
11053   -----------------------------------
11054   -- Check_Aliased_Component_Types --
11055   -----------------------------------
11056
11057   procedure Check_Aliased_Component_Types (T : Entity_Id) is
11058      C : Entity_Id;
11059
11060   begin
11061      --  ??? Also need to check components of record extensions, but not
11062      --  components of protected types (which are always limited).
11063
11064      --  Ada 2005: AI-363 relaxes this rule, to allow heap objects of such
11065      --  types to be unconstrained. This is safe because it is illegal to
11066      --  create access subtypes to such types with explicit discriminant
11067      --  constraints.
11068
11069      if not Is_Limited_Type (T) then
11070         if Ekind (T) = E_Record_Type then
11071            C := First_Component (T);
11072            while Present (C) loop
11073               if Is_Aliased (C)
11074                 and then Has_Discriminants (Etype (C))
11075                 and then not Is_Constrained (Etype (C))
11076                 and then not In_Instance_Body
11077                 and then Ada_Version < Ada_2005
11078               then
11079                  Error_Msg_N
11080                    ("aliased component must be constrained (RM 3.6(11))",
11081                      C);
11082               end if;
11083
11084               Next_Component (C);
11085            end loop;
11086
11087         elsif Ekind (T) = E_Array_Type then
11088            if Has_Aliased_Components (T)
11089              and then Has_Discriminants (Component_Type (T))
11090              and then not Is_Constrained (Component_Type (T))
11091              and then not In_Instance_Body
11092              and then Ada_Version < Ada_2005
11093            then
11094               Error_Msg_N
11095                 ("aliased component type must be constrained (RM 3.6(11))",
11096                    T);
11097            end if;
11098         end if;
11099      end if;
11100   end Check_Aliased_Component_Types;
11101
11102   ---------------------------------------
11103   -- Check_Anonymous_Access_Components --
11104   ---------------------------------------
11105
11106   procedure Check_Anonymous_Access_Components
11107      (Typ_Decl  : Node_Id;
11108       Typ       : Entity_Id;
11109       Prev      : Entity_Id;
11110       Comp_List : Node_Id)
11111   is
11112      Loc         : constant Source_Ptr := Sloc (Typ_Decl);
11113      Anon_Access : Entity_Id;
11114      Acc_Def     : Node_Id;
11115      Comp        : Node_Id;
11116      Comp_Def    : Node_Id;
11117      Decl        : Node_Id;
11118      Type_Def    : Node_Id;
11119
11120      procedure Build_Incomplete_Type_Declaration;
11121      --  If the record type contains components that include an access to the
11122      --  current record, then create an incomplete type declaration for the
11123      --  record, to be used as the designated type of the anonymous access.
11124      --  This is done only once, and only if there is no previous partial
11125      --  view of the type.
11126
11127      function Designates_T (Subt : Node_Id) return Boolean;
11128      --  Check whether a node designates the enclosing record type, or 'Class
11129      --  of that type
11130
11131      function Mentions_T (Acc_Def : Node_Id) return Boolean;
11132      --  Check whether an access definition includes a reference to
11133      --  the enclosing record type. The reference can be a subtype mark
11134      --  in the access definition itself, a 'Class attribute reference, or
11135      --  recursively a reference appearing in a parameter specification
11136      --  or result definition of an access_to_subprogram definition.
11137
11138      --------------------------------------
11139      -- Build_Incomplete_Type_Declaration --
11140      --------------------------------------
11141
11142      procedure Build_Incomplete_Type_Declaration is
11143         Decl  : Node_Id;
11144         Inc_T : Entity_Id;
11145         H     : Entity_Id;
11146
11147         --  Is_Tagged indicates whether the type is tagged. It is tagged if
11148         --  it's "is new ... with record" or else "is tagged record ...".
11149
11150         Is_Tagged : constant Boolean :=
11151             (Nkind (Type_Definition (Typ_Decl)) = N_Derived_Type_Definition
11152               and then
11153                 Present (Record_Extension_Part (Type_Definition (Typ_Decl))))
11154           or else
11155             (Nkind (Type_Definition (Typ_Decl)) = N_Record_Definition
11156               and then Tagged_Present (Type_Definition (Typ_Decl)));
11157
11158      begin
11159         --  If there is a previous partial view, no need to create a new one
11160         --  If the partial view, given by Prev, is incomplete,  If Prev is
11161         --  a private declaration, full declaration is flagged accordingly.
11162
11163         if Prev /= Typ then
11164            if Is_Tagged then
11165               Make_Class_Wide_Type (Prev);
11166               Set_Class_Wide_Type (Typ, Class_Wide_Type (Prev));
11167               Set_Etype (Class_Wide_Type (Typ), Typ);
11168            end if;
11169
11170            return;
11171
11172         elsif Has_Private_Declaration (Typ) then
11173
11174            --  If we refer to T'Class inside T, and T is the completion of a
11175            --  private type, then make sure the class-wide type exists.
11176
11177            if Is_Tagged then
11178               Make_Class_Wide_Type (Typ);
11179            end if;
11180
11181            return;
11182
11183         --  If there was a previous anonymous access type, the incomplete
11184         --  type declaration will have been created already.
11185
11186         elsif Present (Current_Entity (Typ))
11187           and then Ekind (Current_Entity (Typ)) = E_Incomplete_Type
11188           and then Full_View (Current_Entity (Typ)) = Typ
11189         then
11190            if Is_Tagged
11191              and then Comes_From_Source (Current_Entity (Typ))
11192              and then not Is_Tagged_Type (Current_Entity (Typ))
11193            then
11194               Make_Class_Wide_Type (Typ);
11195               Error_Msg_N
11196                 ("incomplete view of tagged type should be declared tagged??",
11197                  Parent (Current_Entity (Typ)));
11198            end if;
11199            return;
11200
11201         else
11202            Inc_T := Make_Defining_Identifier (Loc, Chars (Typ));
11203            Decl  := Make_Incomplete_Type_Declaration (Loc, Inc_T);
11204
11205            --  Type has already been inserted into the current scope. Remove
11206            --  it, and add incomplete declaration for type, so that subsequent
11207            --  anonymous access types can use it. The entity is unchained from
11208            --  the homonym list and from immediate visibility. After analysis,
11209            --  the entity in the incomplete declaration becomes immediately
11210            --  visible in the record declaration that follows.
11211
11212            H := Current_Entity (Typ);
11213
11214            if H = Typ then
11215               Set_Name_Entity_Id (Chars (Typ), Homonym (Typ));
11216            else
11217               while Present (H)
11218                 and then Homonym (H) /= Typ
11219               loop
11220                  H := Homonym (Typ);
11221               end loop;
11222
11223               Set_Homonym (H, Homonym (Typ));
11224            end if;
11225
11226            Insert_Before (Typ_Decl, Decl);
11227            Analyze (Decl);
11228            Set_Full_View (Inc_T, Typ);
11229
11230            if Is_Tagged then
11231
11232               --  Create a common class-wide type for both views, and set the
11233               --  Etype of the class-wide type to the full view.
11234
11235               Make_Class_Wide_Type (Inc_T);
11236               Set_Class_Wide_Type (Typ, Class_Wide_Type (Inc_T));
11237               Set_Etype (Class_Wide_Type (Typ), Typ);
11238            end if;
11239         end if;
11240      end Build_Incomplete_Type_Declaration;
11241
11242      ------------------
11243      -- Designates_T --
11244      ------------------
11245
11246      function Designates_T (Subt : Node_Id) return Boolean is
11247         Type_Id : constant Name_Id := Chars (Typ);
11248
11249         function Names_T (Nam : Node_Id) return Boolean;
11250         --  The record type has not been introduced in the current scope
11251         --  yet, so we must examine the name of the type itself, either
11252         --  an identifier T, or an expanded name of the form P.T, where
11253         --  P denotes the current scope.
11254
11255         -------------
11256         -- Names_T --
11257         -------------
11258
11259         function Names_T (Nam : Node_Id) return Boolean is
11260         begin
11261            if Nkind (Nam) = N_Identifier then
11262               return Chars (Nam) = Type_Id;
11263
11264            elsif Nkind (Nam) = N_Selected_Component then
11265               if Chars (Selector_Name (Nam)) = Type_Id then
11266                  if Nkind (Prefix (Nam)) = N_Identifier then
11267                     return Chars (Prefix (Nam)) = Chars (Current_Scope);
11268
11269                  elsif Nkind (Prefix (Nam)) = N_Selected_Component then
11270                     return Chars (Selector_Name (Prefix (Nam))) =
11271                            Chars (Current_Scope);
11272                  else
11273                     return False;
11274                  end if;
11275
11276               else
11277                  return False;
11278               end if;
11279
11280            else
11281               return False;
11282            end if;
11283         end Names_T;
11284
11285      --  Start of processing for Designates_T
11286
11287      begin
11288         if Nkind (Subt) = N_Identifier then
11289            return Chars (Subt) = Type_Id;
11290
11291            --  Reference can be through an expanded name which has not been
11292            --  analyzed yet, and which designates enclosing scopes.
11293
11294         elsif Nkind (Subt) = N_Selected_Component then
11295            if Names_T (Subt) then
11296               return True;
11297
11298            --  Otherwise it must denote an entity that is already visible.
11299            --  The access definition may name a subtype of the enclosing
11300            --  type, if there is a previous incomplete declaration for it.
11301
11302            else
11303               Find_Selected_Component (Subt);
11304               return
11305                 Is_Entity_Name (Subt)
11306                   and then Scope (Entity (Subt)) = Current_Scope
11307                   and then
11308                     (Chars (Base_Type (Entity (Subt))) = Type_Id
11309                       or else
11310                         (Is_Class_Wide_Type (Entity (Subt))
11311                           and then
11312                             Chars (Etype (Base_Type (Entity (Subt)))) =
11313                                                                  Type_Id));
11314            end if;
11315
11316         --  A reference to the current type may appear as the prefix of
11317         --  a 'Class attribute.
11318
11319         elsif Nkind (Subt) = N_Attribute_Reference
11320           and then Attribute_Name (Subt) = Name_Class
11321         then
11322            return Names_T (Prefix (Subt));
11323
11324         else
11325            return False;
11326         end if;
11327      end Designates_T;
11328
11329      ----------------
11330      -- Mentions_T --
11331      ----------------
11332
11333      function Mentions_T (Acc_Def : Node_Id) return Boolean is
11334         Param_Spec : Node_Id;
11335
11336         Acc_Subprg : constant Node_Id :=
11337                        Access_To_Subprogram_Definition (Acc_Def);
11338
11339      begin
11340         if No (Acc_Subprg) then
11341            return Designates_T (Subtype_Mark (Acc_Def));
11342         end if;
11343
11344         --  Component is an access_to_subprogram: examine its formals,
11345         --  and result definition in the case of an access_to_function.
11346
11347         Param_Spec := First (Parameter_Specifications (Acc_Subprg));
11348         while Present (Param_Spec) loop
11349            if Nkind (Parameter_Type (Param_Spec)) = N_Access_Definition
11350              and then Mentions_T (Parameter_Type (Param_Spec))
11351            then
11352               return True;
11353
11354            elsif Designates_T (Parameter_Type (Param_Spec)) then
11355               return True;
11356            end if;
11357
11358            Next (Param_Spec);
11359         end loop;
11360
11361         if Nkind (Acc_Subprg) = N_Access_Function_Definition then
11362            if Nkind (Result_Definition (Acc_Subprg)) =
11363                 N_Access_Definition
11364            then
11365               return Mentions_T (Result_Definition (Acc_Subprg));
11366            else
11367               return Designates_T (Result_Definition (Acc_Subprg));
11368            end if;
11369         end if;
11370
11371         return False;
11372      end Mentions_T;
11373
11374   --  Start of processing for Check_Anonymous_Access_Components
11375
11376   begin
11377      if No (Comp_List) then
11378         return;
11379      end if;
11380
11381      Comp := First (Component_Items (Comp_List));
11382      while Present (Comp) loop
11383         if Nkind (Comp) = N_Component_Declaration
11384           and then Present
11385             (Access_Definition (Component_Definition (Comp)))
11386           and then
11387             Mentions_T (Access_Definition (Component_Definition (Comp)))
11388         then
11389            Comp_Def := Component_Definition (Comp);
11390            Acc_Def :=
11391              Access_To_Subprogram_Definition (Access_Definition (Comp_Def));
11392
11393            Build_Incomplete_Type_Declaration;
11394            Anon_Access := Make_Temporary (Loc, 'S');
11395
11396            --  Create a declaration for the anonymous access type: either
11397            --  an access_to_object or an access_to_subprogram.
11398
11399            if Present (Acc_Def) then
11400               if Nkind (Acc_Def) = N_Access_Function_Definition then
11401                  Type_Def :=
11402                    Make_Access_Function_Definition (Loc,
11403                      Parameter_Specifications =>
11404                        Parameter_Specifications (Acc_Def),
11405                      Result_Definition        => Result_Definition (Acc_Def));
11406               else
11407                  Type_Def :=
11408                    Make_Access_Procedure_Definition (Loc,
11409                      Parameter_Specifications =>
11410                        Parameter_Specifications (Acc_Def));
11411               end if;
11412
11413            else
11414               Type_Def :=
11415                 Make_Access_To_Object_Definition (Loc,
11416                   Subtype_Indication =>
11417                      Relocate_Node
11418                        (Subtype_Mark (Access_Definition (Comp_Def))));
11419
11420               Set_Constant_Present
11421                 (Type_Def, Constant_Present (Access_Definition (Comp_Def)));
11422               Set_All_Present
11423                 (Type_Def, All_Present (Access_Definition (Comp_Def)));
11424            end if;
11425
11426            Set_Null_Exclusion_Present
11427              (Type_Def,
11428               Null_Exclusion_Present (Access_Definition (Comp_Def)));
11429
11430            Decl :=
11431              Make_Full_Type_Declaration (Loc,
11432                Defining_Identifier => Anon_Access,
11433                Type_Definition     => Type_Def);
11434
11435            Insert_Before (Typ_Decl, Decl);
11436            Analyze (Decl);
11437
11438            --  If an access to subprogram, create the extra formals
11439
11440            if Present (Acc_Def) then
11441               Create_Extra_Formals (Designated_Type (Anon_Access));
11442
11443            --  If an access to object, preserve entity of designated type,
11444            --  for ASIS use, before rewriting the component definition.
11445
11446            else
11447               declare
11448                  Desig : Entity_Id;
11449
11450               begin
11451                  Desig := Entity (Subtype_Indication (Type_Def));
11452
11453                  --  If the access definition is to the current  record,
11454                  --  the visible entity at this point is an  incomplete
11455                  --  type. Retrieve the full view to simplify  ASIS queries
11456
11457                  if Ekind (Desig) = E_Incomplete_Type then
11458                     Desig := Full_View (Desig);
11459                  end if;
11460
11461                  Set_Entity
11462                    (Subtype_Mark (Access_Definition  (Comp_Def)), Desig);
11463               end;
11464            end if;
11465
11466            Rewrite (Comp_Def,
11467              Make_Component_Definition (Loc,
11468                Subtype_Indication =>
11469               New_Occurrence_Of (Anon_Access, Loc)));
11470
11471            if Ekind (Designated_Type (Anon_Access)) = E_Subprogram_Type then
11472               Set_Ekind (Anon_Access, E_Anonymous_Access_Subprogram_Type);
11473            else
11474               Set_Ekind (Anon_Access, E_Anonymous_Access_Type);
11475            end if;
11476
11477            Set_Is_Local_Anonymous_Access (Anon_Access);
11478         end if;
11479
11480         Next (Comp);
11481      end loop;
11482
11483      if Present (Variant_Part (Comp_List)) then
11484         declare
11485            V : Node_Id;
11486         begin
11487            V := First_Non_Pragma (Variants (Variant_Part (Comp_List)));
11488            while Present (V) loop
11489               Check_Anonymous_Access_Components
11490                 (Typ_Decl, Typ, Prev, Component_List (V));
11491               Next_Non_Pragma (V);
11492            end loop;
11493         end;
11494      end if;
11495   end Check_Anonymous_Access_Components;
11496
11497   ----------------------
11498   -- Check_Completion --
11499   ----------------------
11500
11501   procedure Check_Completion (Body_Id : Node_Id := Empty) is
11502      E : Entity_Id;
11503
11504      procedure Post_Error;
11505      --  Post error message for lack of completion for entity E
11506
11507      ----------------
11508      -- Post_Error --
11509      ----------------
11510
11511      procedure Post_Error is
11512         procedure Missing_Body;
11513         --  Output missing body message
11514
11515         ------------------
11516         -- Missing_Body --
11517         ------------------
11518
11519         procedure Missing_Body is
11520         begin
11521            --  Spec is in same unit, so we can post on spec
11522
11523            if In_Same_Source_Unit (Body_Id, E) then
11524               Error_Msg_N ("missing body for &", E);
11525
11526            --  Spec is in a separate unit, so we have to post on the body
11527
11528            else
11529               Error_Msg_NE ("missing body for & declared#!", Body_Id, E);
11530            end if;
11531         end Missing_Body;
11532
11533      --  Start of processing for Post_Error
11534
11535      begin
11536         if not Comes_From_Source (E) then
11537            if Ekind_In (E, E_Task_Type, E_Protected_Type) then
11538
11539               --  It may be an anonymous protected type created for a
11540               --  single variable. Post error on variable, if present.
11541
11542               declare
11543                  Var : Entity_Id;
11544
11545               begin
11546                  Var := First_Entity (Current_Scope);
11547                  while Present (Var) loop
11548                     exit when Etype (Var) = E
11549                       and then Comes_From_Source (Var);
11550
11551                     Next_Entity (Var);
11552                  end loop;
11553
11554                  if Present (Var) then
11555                     E := Var;
11556                  end if;
11557               end;
11558            end if;
11559         end if;
11560
11561         --  If a generated entity has no completion, then either previous
11562         --  semantic errors have disabled the expansion phase, or else we had
11563         --  missing subunits, or else we are compiling without expansion,
11564         --  or else something is very wrong.
11565
11566         if not Comes_From_Source (E) then
11567            pragma Assert
11568              (Serious_Errors_Detected > 0
11569                or else Configurable_Run_Time_Violations > 0
11570                or else Subunits_Missing
11571                or else not Expander_Active);
11572            return;
11573
11574         --  Here for source entity
11575
11576         else
11577            --  Here if no body to post the error message, so we post the error
11578            --  on the declaration that has no completion. This is not really
11579            --  the right place to post it, think about this later ???
11580
11581            if No (Body_Id) then
11582               if Is_Type (E) then
11583                  Error_Msg_NE
11584                    ("missing full declaration for }", Parent (E), E);
11585               else
11586                  Error_Msg_NE ("missing body for &", Parent (E), E);
11587               end if;
11588
11589            --  Package body has no completion for a declaration that appears
11590            --  in the corresponding spec. Post error on the body, with a
11591            --  reference to the non-completed declaration.
11592
11593            else
11594               Error_Msg_Sloc := Sloc (E);
11595
11596               if Is_Type (E) then
11597                  Error_Msg_NE ("missing full declaration for }!", Body_Id, E);
11598
11599               elsif Is_Overloadable (E)
11600                 and then Current_Entity_In_Scope (E) /= E
11601               then
11602                  --  It may be that the completion is mistyped and appears as
11603                  --  a distinct overloading of the entity.
11604
11605                  declare
11606                     Candidate : constant Entity_Id :=
11607                                   Current_Entity_In_Scope (E);
11608                     Decl      : constant Node_Id :=
11609                                   Unit_Declaration_Node (Candidate);
11610
11611                  begin
11612                     if Is_Overloadable (Candidate)
11613                       and then Ekind (Candidate) = Ekind (E)
11614                       and then Nkind (Decl) = N_Subprogram_Body
11615                       and then Acts_As_Spec (Decl)
11616                     then
11617                        Check_Type_Conformant (Candidate, E);
11618
11619                     else
11620                        Missing_Body;
11621                     end if;
11622                  end;
11623
11624               else
11625                  Missing_Body;
11626               end if;
11627            end if;
11628         end if;
11629      end Post_Error;
11630
11631      --  Local variables
11632
11633      Pack_Id : constant Entity_Id := Current_Scope;
11634
11635   --  Start of processing for Check_Completion
11636
11637   begin
11638      E := First_Entity (Pack_Id);
11639      while Present (E) loop
11640         if Is_Intrinsic_Subprogram (E) then
11641            null;
11642
11643         --  The following situation requires special handling: a child unit
11644         --  that appears in the context clause of the body of its parent:
11645
11646         --    procedure Parent.Child (...);
11647
11648         --    with Parent.Child;
11649         --    package body Parent is
11650
11651         --  Here Parent.Child appears as a local entity, but should not be
11652         --  flagged as requiring completion, because it is a compilation
11653         --  unit.
11654
11655         --  Ignore missing completion for a subprogram that does not come from
11656         --  source (including the _Call primitive operation of RAS types,
11657         --  which has to have the flag Comes_From_Source for other purposes):
11658         --  we assume that the expander will provide the missing completion.
11659         --  In case of previous errors, other expansion actions that provide
11660         --  bodies for null procedures with not be invoked, so inhibit message
11661         --  in those cases.
11662
11663         --  Note that E_Operator is not in the list that follows, because
11664         --  this kind is reserved for predefined operators, that are
11665         --  intrinsic and do not need completion.
11666
11667         elsif Ekind_In (E, E_Function,
11668                            E_Procedure,
11669                            E_Generic_Function,
11670                            E_Generic_Procedure)
11671         then
11672            if Has_Completion (E) then
11673               null;
11674
11675            elsif Is_Subprogram (E) and then Is_Abstract_Subprogram (E) then
11676               null;
11677
11678            elsif Is_Subprogram (E)
11679              and then (not Comes_From_Source (E)
11680                         or else Chars (E) = Name_uCall)
11681            then
11682               null;
11683
11684            elsif
11685               Nkind (Parent (Unit_Declaration_Node (E))) = N_Compilation_Unit
11686            then
11687               null;
11688
11689            elsif Nkind (Parent (E)) = N_Procedure_Specification
11690              and then Null_Present (Parent (E))
11691              and then Serious_Errors_Detected > 0
11692            then
11693               null;
11694
11695            else
11696               Post_Error;
11697            end if;
11698
11699         elsif Is_Entry (E) then
11700            if not Has_Completion (E) and then
11701              (Ekind (Scope (E)) = E_Protected_Object
11702                or else Ekind (Scope (E)) = E_Protected_Type)
11703            then
11704               Post_Error;
11705            end if;
11706
11707         elsif Is_Package_Or_Generic_Package (E) then
11708            if Unit_Requires_Body (E) then
11709               if not Has_Completion (E)
11710                 and then Nkind (Parent (Unit_Declaration_Node (E))) /=
11711                                                       N_Compilation_Unit
11712               then
11713                  Post_Error;
11714               end if;
11715
11716            elsif not Is_Child_Unit (E) then
11717               May_Need_Implicit_Body (E);
11718            end if;
11719
11720         --  A formal incomplete type (Ada 2012) does not require a completion;
11721         --  other incomplete type declarations do.
11722
11723         elsif Ekind (E) = E_Incomplete_Type
11724           and then No (Underlying_Type (E))
11725           and then not Is_Generic_Type (E)
11726         then
11727            Post_Error;
11728
11729         elsif Ekind_In (E, E_Task_Type, E_Protected_Type)
11730           and then not Has_Completion (E)
11731         then
11732            Post_Error;
11733
11734         --  A single task declared in the current scope is a constant, verify
11735         --  that the body of its anonymous type is in the same scope. If the
11736         --  task is defined elsewhere, this may be a renaming declaration for
11737         --  which no completion is needed.
11738
11739         elsif Ekind (E) = E_Constant
11740           and then Ekind (Etype (E)) = E_Task_Type
11741           and then not Has_Completion (Etype (E))
11742           and then Scope (Etype (E)) = Current_Scope
11743         then
11744            Post_Error;
11745
11746         elsif Ekind (E) = E_Protected_Object
11747           and then not Has_Completion (Etype (E))
11748         then
11749            Post_Error;
11750
11751         elsif Ekind (E) = E_Record_Type then
11752            if Is_Tagged_Type (E) then
11753               Check_Abstract_Overriding (E);
11754               Check_Conventions (E);
11755            end if;
11756
11757            Check_Aliased_Component_Types (E);
11758
11759         elsif Ekind (E) = E_Array_Type then
11760            Check_Aliased_Component_Types (E);
11761
11762         end if;
11763
11764         Next_Entity (E);
11765      end loop;
11766   end Check_Completion;
11767
11768   ------------------------------------
11769   -- Check_CPP_Type_Has_No_Defaults --
11770   ------------------------------------
11771
11772   procedure Check_CPP_Type_Has_No_Defaults (T : Entity_Id) is
11773      Tdef  : constant Node_Id := Type_Definition (Declaration_Node (T));
11774      Clist : Node_Id;
11775      Comp  : Node_Id;
11776
11777   begin
11778      --  Obtain the component list
11779
11780      if Nkind (Tdef) = N_Record_Definition then
11781         Clist := Component_List (Tdef);
11782      else pragma Assert (Nkind (Tdef) = N_Derived_Type_Definition);
11783         Clist := Component_List (Record_Extension_Part (Tdef));
11784      end if;
11785
11786      --  Check all components to ensure no default expressions
11787
11788      if Present (Clist) then
11789         Comp := First (Component_Items (Clist));
11790         while Present (Comp) loop
11791            if Present (Expression (Comp)) then
11792               Error_Msg_N
11793                 ("component of imported 'C'P'P type cannot have "
11794                  & "default expression", Expression (Comp));
11795            end if;
11796
11797            Next (Comp);
11798         end loop;
11799      end if;
11800   end Check_CPP_Type_Has_No_Defaults;
11801
11802   ----------------------------
11803   -- Check_Delta_Expression --
11804   ----------------------------
11805
11806   procedure Check_Delta_Expression (E : Node_Id) is
11807   begin
11808      if not (Is_Real_Type (Etype (E))) then
11809         Wrong_Type (E, Any_Real);
11810
11811      elsif not Is_OK_Static_Expression (E) then
11812         Flag_Non_Static_Expr
11813           ("non-static expression used for delta value!", E);
11814
11815      elsif not UR_Is_Positive (Expr_Value_R (E)) then
11816         Error_Msg_N ("delta expression must be positive", E);
11817
11818      else
11819         return;
11820      end if;
11821
11822      --  If any of above errors occurred, then replace the incorrect
11823      --  expression by the real 0.1, which should prevent further errors.
11824
11825      Rewrite (E,
11826        Make_Real_Literal (Sloc (E), Ureal_Tenth));
11827      Analyze_And_Resolve (E, Standard_Float);
11828   end Check_Delta_Expression;
11829
11830   -----------------------------
11831   -- Check_Digits_Expression --
11832   -----------------------------
11833
11834   procedure Check_Digits_Expression (E : Node_Id) is
11835   begin
11836      if not (Is_Integer_Type (Etype (E))) then
11837         Wrong_Type (E, Any_Integer);
11838
11839      elsif not Is_OK_Static_Expression (E) then
11840         Flag_Non_Static_Expr
11841           ("non-static expression used for digits value!", E);
11842
11843      elsif Expr_Value (E) <= 0 then
11844         Error_Msg_N ("digits value must be greater than zero", E);
11845
11846      else
11847         return;
11848      end if;
11849
11850      --  If any of above errors occurred, then replace the incorrect
11851      --  expression by the integer 1, which should prevent further errors.
11852
11853      Rewrite (E, Make_Integer_Literal (Sloc (E), 1));
11854      Analyze_And_Resolve (E, Standard_Integer);
11855
11856   end Check_Digits_Expression;
11857
11858   --------------------------
11859   -- Check_Initialization --
11860   --------------------------
11861
11862   procedure Check_Initialization (T : Entity_Id; Exp : Node_Id) is
11863   begin
11864      --  Special processing for limited types
11865
11866      if Is_Limited_Type (T)
11867        and then not In_Instance
11868        and then not In_Inlined_Body
11869      then
11870         if not OK_For_Limited_Init (T, Exp) then
11871
11872            --  In GNAT mode, this is just a warning, to allow it to be evilly
11873            --  turned off. Otherwise it is a real error.
11874
11875            if GNAT_Mode then
11876               Error_Msg_N
11877                 ("??cannot initialize entities of limited type!", Exp);
11878
11879            elsif Ada_Version < Ada_2005 then
11880
11881               --  The side effect removal machinery may generate illegal Ada
11882               --  code to avoid the usage of access types and 'reference in
11883               --  SPARK mode. Since this is legal code with respect to theorem
11884               --  proving, do not emit the error.
11885
11886               if GNATprove_Mode
11887                 and then Nkind (Exp) = N_Function_Call
11888                 and then Nkind (Parent (Exp)) = N_Object_Declaration
11889                 and then not Comes_From_Source
11890                                (Defining_Identifier (Parent (Exp)))
11891               then
11892                  null;
11893
11894               else
11895                  Error_Msg_N
11896                    ("cannot initialize entities of limited type", Exp);
11897                  Explain_Limited_Type (T, Exp);
11898               end if;
11899
11900            else
11901               --  Specialize error message according to kind of illegal
11902               --  initial expression.
11903
11904               if Nkind (Exp) = N_Type_Conversion
11905                 and then Nkind (Expression (Exp)) = N_Function_Call
11906               then
11907                  --  No error for internally-generated object declarations,
11908                  --  which can come from build-in-place assignment statements.
11909
11910                  if Nkind (Parent (Exp)) = N_Object_Declaration
11911                    and then not Comes_From_Source
11912                                   (Defining_Identifier (Parent (Exp)))
11913                  then
11914                     null;
11915
11916                  else
11917                     Error_Msg_N
11918                       ("illegal context for call to function with limited "
11919                        & "result", Exp);
11920                  end if;
11921
11922               else
11923                  Error_Msg_N
11924                    ("initialization of limited object requires aggregate or "
11925                     & "function call",  Exp);
11926               end if;
11927            end if;
11928         end if;
11929      end if;
11930
11931      --  In gnatc or gnatprove mode, make sure set Do_Range_Check flag gets
11932      --  set unless we can be sure that no range check is required.
11933
11934      if (GNATprove_Mode or not Expander_Active)
11935        and then Is_Scalar_Type (T)
11936        and then not Is_In_Range (Exp, T, Assume_Valid => True)
11937      then
11938         Set_Do_Range_Check (Exp);
11939      end if;
11940   end Check_Initialization;
11941
11942   ----------------------
11943   -- Check_Interfaces --
11944   ----------------------
11945
11946   procedure Check_Interfaces (N : Node_Id; Def : Node_Id) is
11947      Parent_Type : constant Entity_Id := Etype (Defining_Identifier (N));
11948
11949      Iface       : Node_Id;
11950      Iface_Def   : Node_Id;
11951      Iface_Typ   : Entity_Id;
11952      Parent_Node : Node_Id;
11953
11954      Is_Task : Boolean := False;
11955      --  Set True if parent type or any progenitor is a task interface
11956
11957      Is_Protected : Boolean := False;
11958      --  Set True if parent type or any progenitor is a protected interface
11959
11960      procedure Check_Ifaces (Iface_Def : Node_Id; Error_Node : Node_Id);
11961      --  Check that a progenitor is compatible with declaration. If an error
11962      --  message is output, it is posted on Error_Node.
11963
11964      ------------------
11965      -- Check_Ifaces --
11966      ------------------
11967
11968      procedure Check_Ifaces (Iface_Def : Node_Id; Error_Node : Node_Id) is
11969         Iface_Id : constant Entity_Id :=
11970                      Defining_Identifier (Parent (Iface_Def));
11971         Type_Def : Node_Id;
11972
11973      begin
11974         if Nkind (N) = N_Private_Extension_Declaration then
11975            Type_Def := N;
11976         else
11977            Type_Def := Type_Definition (N);
11978         end if;
11979
11980         if Is_Task_Interface (Iface_Id) then
11981            Is_Task := True;
11982
11983         elsif Is_Protected_Interface (Iface_Id) then
11984            Is_Protected := True;
11985         end if;
11986
11987         if Is_Synchronized_Interface (Iface_Id) then
11988
11989            --  A consequence of 3.9.4 (6/2) and 7.3 (7.2/2) is that a private
11990            --  extension derived from a synchronized interface must explicitly
11991            --  be declared synchronized, because the full view will be a
11992            --  synchronized type.
11993
11994            if Nkind (N) = N_Private_Extension_Declaration then
11995               if not Synchronized_Present (N) then
11996                  Error_Msg_NE
11997                    ("private extension of& must be explicitly synchronized",
11998                      N, Iface_Id);
11999               end if;
12000
12001            --  However, by 3.9.4(16/2), a full type that is a record extension
12002            --  is never allowed to derive from a synchronized interface (note
12003            --  that interfaces must be excluded from this check, because those
12004            --  are represented by derived type definitions in some cases).
12005
12006            elsif Nkind (Type_Definition (N)) = N_Derived_Type_Definition
12007              and then not Interface_Present (Type_Definition (N))
12008            then
12009               Error_Msg_N ("record extension cannot derive from synchronized "
12010                            & "interface", Error_Node);
12011            end if;
12012         end if;
12013
12014         --  Check that the characteristics of the progenitor are compatible
12015         --  with the explicit qualifier in the declaration.
12016         --  The check only applies to qualifiers that come from source.
12017         --  Limited_Present also appears in the declaration of corresponding
12018         --  records, and the check does not apply to them.
12019
12020         if Limited_Present (Type_Def)
12021           and then not
12022             Is_Concurrent_Record_Type (Defining_Identifier (N))
12023         then
12024            if Is_Limited_Interface (Parent_Type)
12025              and then not Is_Limited_Interface (Iface_Id)
12026            then
12027               Error_Msg_NE
12028                 ("progenitor & must be limited interface",
12029                   Error_Node, Iface_Id);
12030
12031            elsif
12032              (Task_Present (Iface_Def)
12033                or else Protected_Present (Iface_Def)
12034                or else Synchronized_Present (Iface_Def))
12035              and then Nkind (N) /= N_Private_Extension_Declaration
12036              and then not Error_Posted (N)
12037            then
12038               Error_Msg_NE
12039                 ("progenitor & must be limited interface",
12040                   Error_Node, Iface_Id);
12041            end if;
12042
12043         --  Protected interfaces can only inherit from limited, synchronized
12044         --  or protected interfaces.
12045
12046         elsif Nkind (N) = N_Full_Type_Declaration
12047           and then Protected_Present (Type_Def)
12048         then
12049            if Limited_Present (Iface_Def)
12050              or else Synchronized_Present (Iface_Def)
12051              or else Protected_Present (Iface_Def)
12052            then
12053               null;
12054
12055            elsif Task_Present (Iface_Def) then
12056               Error_Msg_N ("(Ada 2005) protected interface cannot inherit "
12057                            & "from task interface", Error_Node);
12058
12059            else
12060               Error_Msg_N ("(Ada 2005) protected interface cannot inherit "
12061                            & "from non-limited interface", Error_Node);
12062            end if;
12063
12064         --  Ada 2005 (AI-345): Synchronized interfaces can only inherit from
12065         --  limited and synchronized.
12066
12067         elsif Synchronized_Present (Type_Def) then
12068            if Limited_Present (Iface_Def)
12069              or else Synchronized_Present (Iface_Def)
12070            then
12071               null;
12072
12073            elsif Protected_Present (Iface_Def)
12074              and then Nkind (N) /= N_Private_Extension_Declaration
12075            then
12076               Error_Msg_N ("(Ada 2005) synchronized interface cannot inherit "
12077                            & "from protected interface", Error_Node);
12078
12079            elsif Task_Present (Iface_Def)
12080              and then Nkind (N) /= N_Private_Extension_Declaration
12081            then
12082               Error_Msg_N ("(Ada 2005) synchronized interface cannot inherit "
12083                            & "from task interface", Error_Node);
12084
12085            elsif not Is_Limited_Interface (Iface_Id) then
12086               Error_Msg_N ("(Ada 2005) synchronized interface cannot inherit "
12087                            & "from non-limited interface", Error_Node);
12088            end if;
12089
12090         --  Ada 2005 (AI-345): Task interfaces can only inherit from limited,
12091         --  synchronized or task interfaces.
12092
12093         elsif Nkind (N) = N_Full_Type_Declaration
12094           and then Task_Present (Type_Def)
12095         then
12096            if Limited_Present (Iface_Def)
12097              or else Synchronized_Present (Iface_Def)
12098              or else Task_Present (Iface_Def)
12099            then
12100               null;
12101
12102            elsif Protected_Present (Iface_Def) then
12103               Error_Msg_N ("(Ada 2005) task interface cannot inherit from "
12104                            & "protected interface", Error_Node);
12105
12106            else
12107               Error_Msg_N ("(Ada 2005) task interface cannot inherit from "
12108                            & "non-limited interface", Error_Node);
12109            end if;
12110         end if;
12111      end Check_Ifaces;
12112
12113   --  Start of processing for Check_Interfaces
12114
12115   begin
12116      if Is_Interface (Parent_Type) then
12117         if Is_Task_Interface (Parent_Type) then
12118            Is_Task := True;
12119
12120         elsif Is_Protected_Interface (Parent_Type) then
12121            Is_Protected := True;
12122         end if;
12123      end if;
12124
12125      if Nkind (N) = N_Private_Extension_Declaration then
12126
12127         --  Check that progenitors are compatible with declaration
12128
12129         Iface := First (Interface_List (Def));
12130         while Present (Iface) loop
12131            Iface_Typ := Find_Type_Of_Subtype_Indic (Iface);
12132
12133            Parent_Node := Parent (Base_Type (Iface_Typ));
12134            Iface_Def   := Type_Definition (Parent_Node);
12135
12136            if not Is_Interface (Iface_Typ) then
12137               Diagnose_Interface (Iface, Iface_Typ);
12138            else
12139               Check_Ifaces (Iface_Def, Iface);
12140            end if;
12141
12142            Next (Iface);
12143         end loop;
12144
12145         if Is_Task and Is_Protected then
12146            Error_Msg_N
12147              ("type cannot derive from task and protected interface", N);
12148         end if;
12149
12150         return;
12151      end if;
12152
12153      --  Full type declaration of derived type.
12154      --  Check compatibility with parent if it is interface type
12155
12156      if Nkind (Type_Definition (N)) = N_Derived_Type_Definition
12157        and then Is_Interface (Parent_Type)
12158      then
12159         Parent_Node := Parent (Parent_Type);
12160
12161         --  More detailed checks for interface varieties
12162
12163         Check_Ifaces
12164           (Iface_Def  => Type_Definition (Parent_Node),
12165            Error_Node => Subtype_Indication (Type_Definition (N)));
12166      end if;
12167
12168      Iface := First (Interface_List (Def));
12169      while Present (Iface) loop
12170         Iface_Typ := Find_Type_Of_Subtype_Indic (Iface);
12171
12172         Parent_Node := Parent (Base_Type (Iface_Typ));
12173         Iface_Def   := Type_Definition (Parent_Node);
12174
12175         if not Is_Interface (Iface_Typ) then
12176            Diagnose_Interface (Iface, Iface_Typ);
12177
12178         else
12179            --  "The declaration of a specific descendant of an interface
12180            --   type freezes the interface type" RM 13.14
12181
12182            Freeze_Before (N, Iface_Typ);
12183            Check_Ifaces (Iface_Def, Error_Node => Iface);
12184         end if;
12185
12186         Next (Iface);
12187      end loop;
12188
12189      if Is_Task and Is_Protected then
12190         Error_Msg_N
12191           ("type cannot derive from task and protected interface", N);
12192      end if;
12193   end Check_Interfaces;
12194
12195   ------------------------------------
12196   -- Check_Or_Process_Discriminants --
12197   ------------------------------------
12198
12199   --  If an incomplete or private type declaration was already given for the
12200   --  type, the discriminants may have already been processed if they were
12201   --  present on the incomplete declaration. In this case a full conformance
12202   --  check has been performed in Find_Type_Name, and we then recheck here
12203   --  some properties that can't be checked on the partial view alone.
12204   --  Otherwise we call Process_Discriminants.
12205
12206   procedure Check_Or_Process_Discriminants
12207     (N    : Node_Id;
12208      T    : Entity_Id;
12209      Prev : Entity_Id := Empty)
12210   is
12211   begin
12212      if Has_Discriminants (T) then
12213
12214         --  Discriminants are already set on T if they were already present
12215         --  on the partial view. Make them visible to component declarations.
12216
12217         declare
12218            D : Entity_Id;
12219            --  Discriminant on T (full view) referencing expr on partial view
12220
12221            Prev_D : Entity_Id;
12222            --  Entity of corresponding discriminant on partial view
12223
12224            New_D : Node_Id;
12225            --  Discriminant specification for full view, expression is
12226            --  the syntactic copy on full view (which has been checked for
12227            --  conformance with partial view), only used here to post error
12228            --  message.
12229
12230         begin
12231            D     := First_Discriminant (T);
12232            New_D := First (Discriminant_Specifications (N));
12233            while Present (D) loop
12234               Prev_D := Current_Entity (D);
12235               Set_Current_Entity (D);
12236               Set_Is_Immediately_Visible (D);
12237               Set_Homonym (D, Prev_D);
12238
12239               --  Handle the case where there is an untagged partial view and
12240               --  the full view is tagged: must disallow discriminants with
12241               --  defaults, unless compiling for Ada 2012, which allows a
12242               --  limited tagged type to have defaulted discriminants (see
12243               --  AI05-0214). However, suppress error here if it was already
12244               --  reported on the default expression of the partial view.
12245
12246               if Is_Tagged_Type (T)
12247                 and then Present (Expression (Parent (D)))
12248                 and then (not Is_Limited_Type (Current_Scope)
12249                            or else Ada_Version < Ada_2012)
12250                 and then not Error_Posted (Expression (Parent (D)))
12251               then
12252                  if Ada_Version >= Ada_2012 then
12253                     Error_Msg_N
12254                       ("discriminants of nonlimited tagged type cannot have "
12255                        & "defaults",
12256                        Expression (New_D));
12257                  else
12258                     Error_Msg_N
12259                       ("discriminants of tagged type cannot have defaults",
12260                        Expression (New_D));
12261                  end if;
12262               end if;
12263
12264               --  Ada 2005 (AI-230): Access discriminant allowed in
12265               --  non-limited record types.
12266
12267               if Ada_Version < Ada_2005 then
12268
12269                  --  This restriction gets applied to the full type here. It
12270                  --  has already been applied earlier to the partial view.
12271
12272                  Check_Access_Discriminant_Requires_Limited (Parent (D), N);
12273               end if;
12274
12275               Next_Discriminant (D);
12276               Next (New_D);
12277            end loop;
12278         end;
12279
12280      elsif Present (Discriminant_Specifications (N)) then
12281         Process_Discriminants (N, Prev);
12282      end if;
12283   end Check_Or_Process_Discriminants;
12284
12285   ----------------------
12286   -- Check_Real_Bound --
12287   ----------------------
12288
12289   procedure Check_Real_Bound (Bound : Node_Id) is
12290   begin
12291      if not Is_Real_Type (Etype (Bound)) then
12292         Error_Msg_N
12293           ("bound in real type definition must be of real type", Bound);
12294
12295      elsif not Is_OK_Static_Expression (Bound) then
12296         Flag_Non_Static_Expr
12297           ("non-static expression used for real type bound!", Bound);
12298
12299      else
12300         return;
12301      end if;
12302
12303      Rewrite
12304        (Bound, Make_Real_Literal (Sloc (Bound), Ureal_0));
12305      Analyze (Bound);
12306      Resolve (Bound, Standard_Float);
12307   end Check_Real_Bound;
12308
12309   ------------------------------
12310   -- Complete_Private_Subtype --
12311   ------------------------------
12312
12313   procedure Complete_Private_Subtype
12314     (Priv        : Entity_Id;
12315      Full        : Entity_Id;
12316      Full_Base   : Entity_Id;
12317      Related_Nod : Node_Id)
12318   is
12319      Save_Next_Entity : Entity_Id;
12320      Save_Homonym     : Entity_Id;
12321
12322   begin
12323      --  Set semantic attributes for (implicit) private subtype completion.
12324      --  If the full type has no discriminants, then it is a copy of the
12325      --  full view of the base. Otherwise, it is a subtype of the base with
12326      --  a possible discriminant constraint. Save and restore the original
12327      --  Next_Entity field of full to ensure that the calls to Copy_Node do
12328      --  not corrupt the entity chain.
12329
12330      --  Note that the type of the full view is the same entity as the type
12331      --  of the partial view. In this fashion, the subtype has access to the
12332      --  correct view of the parent.
12333      --  The list below included access types, but this leads to several
12334      --  regressions. How should the base type of the full view be
12335      --  set consistently for subtypes completed by access types?
12336
12337      Save_Next_Entity := Next_Entity (Full);
12338      Save_Homonym     := Homonym (Priv);
12339
12340      case Ekind (Full_Base) is
12341         when Class_Wide_Kind
12342            | Private_Kind
12343            | Protected_Kind
12344            | Task_Kind
12345            | E_Record_Subtype
12346            | E_Record_Type
12347         =>
12348            Copy_Node (Priv, Full);
12349
12350            Set_Has_Discriminants
12351                             (Full, Has_Discriminants (Full_Base));
12352            Set_Has_Unknown_Discriminants
12353                             (Full, Has_Unknown_Discriminants (Full_Base));
12354            Set_First_Entity (Full, First_Entity (Full_Base));
12355            Set_Last_Entity  (Full, Last_Entity (Full_Base));
12356
12357            --  If the underlying base type is constrained, we know that the
12358            --  full view of the subtype is constrained as well (the converse
12359            --  is not necessarily true).
12360
12361            if Is_Constrained (Full_Base) then
12362               Set_Is_Constrained (Full);
12363            end if;
12364
12365         when others =>
12366            Copy_Node (Full_Base, Full);
12367
12368            Set_Chars         (Full, Chars (Priv));
12369            Conditional_Delay (Full, Priv);
12370            Set_Sloc          (Full, Sloc (Priv));
12371      end case;
12372
12373      Link_Entities                 (Full, Save_Next_Entity);
12374      Set_Homonym                   (Full, Save_Homonym);
12375      Set_Associated_Node_For_Itype (Full, Related_Nod);
12376
12377      --  Set common attributes for all subtypes: kind, convention, etc.
12378
12379      Set_Ekind (Full, Subtype_Kind (Ekind (Full_Base)));
12380      Set_Convention (Full, Convention (Full_Base));
12381
12382      --  The Etype of the full view is inconsistent. Gigi needs to see the
12383      --  structural full view, which is what the current scheme gives: the
12384      --  Etype of the full view is the etype of the full base. However, if the
12385      --  full base is a derived type, the full view then looks like a subtype
12386      --  of the parent, not a subtype of the full base. If instead we write:
12387
12388      --       Set_Etype (Full, Full_Base);
12389
12390      --  then we get inconsistencies in the front-end (confusion between
12391      --  views). Several outstanding bugs are related to this ???
12392
12393      Set_Is_First_Subtype (Full, False);
12394      Set_Scope            (Full, Scope (Priv));
12395      Set_Size_Info        (Full, Full_Base);
12396      Set_RM_Size          (Full, RM_Size (Full_Base));
12397      Set_Is_Itype         (Full);
12398
12399      --  For the unusual case of a type with unknown discriminants whose
12400      --  completion is an array, use the proper full base.
12401
12402      if Is_Array_Type (Full_Base)
12403        and then Has_Unknown_Discriminants (Priv)
12404      then
12405         Set_Etype (Full, Full_Base);
12406      end if;
12407
12408      --  A subtype of a private-type-without-discriminants, whose full-view
12409      --  has discriminants with default expressions, is not constrained.
12410
12411      if not Has_Discriminants (Priv) then
12412         Set_Is_Constrained (Full, Is_Constrained (Full_Base));
12413
12414         if Has_Discriminants (Full_Base) then
12415            Set_Discriminant_Constraint
12416              (Full, Discriminant_Constraint (Full_Base));
12417
12418            --  The partial view may have been indefinite, the full view
12419            --  might not be.
12420
12421            Set_Has_Unknown_Discriminants
12422              (Full, Has_Unknown_Discriminants (Full_Base));
12423         end if;
12424      end if;
12425
12426      Set_First_Rep_Item     (Full, First_Rep_Item (Full_Base));
12427      Set_Depends_On_Private (Full, Has_Private_Component (Full));
12428
12429      --  Freeze the private subtype entity if its parent is delayed, and not
12430      --  already frozen. We skip this processing if the type is an anonymous
12431      --  subtype of a record component, or is the corresponding record of a
12432      --  protected type, since these are processed when the enclosing type
12433      --  is frozen. If the parent type is declared in a nested package then
12434      --  the freezing of the private and full views also happens later.
12435
12436      if not Is_Type (Scope (Full)) then
12437         if Is_Itype (Priv)
12438           and then In_Same_Source_Unit (Full, Full_Base)
12439           and then Scope (Full_Base) /= Scope (Full)
12440         then
12441            Set_Has_Delayed_Freeze (Full);
12442            Set_Has_Delayed_Freeze (Priv);
12443
12444         else
12445            Set_Has_Delayed_Freeze (Full,
12446              Has_Delayed_Freeze (Full_Base)
12447                and then not Is_Frozen (Full_Base));
12448         end if;
12449      end if;
12450
12451      Set_Freeze_Node (Full, Empty);
12452      Set_Is_Frozen (Full, False);
12453      Set_Full_View (Priv, Full);
12454
12455      if Has_Discriminants (Full) then
12456         Set_Stored_Constraint_From_Discriminant_Constraint (Full);
12457         Set_Stored_Constraint (Priv, Stored_Constraint (Full));
12458
12459         if Has_Unknown_Discriminants (Full) then
12460            Set_Discriminant_Constraint (Full, No_Elist);
12461         end if;
12462      end if;
12463
12464      if Ekind (Full_Base) = E_Record_Type
12465        and then Has_Discriminants (Full_Base)
12466        and then Has_Discriminants (Priv) -- might not, if errors
12467        and then not Has_Unknown_Discriminants (Priv)
12468        and then not Is_Empty_Elmt_List (Discriminant_Constraint (Priv))
12469      then
12470         Create_Constrained_Components
12471           (Full, Related_Nod, Full_Base, Discriminant_Constraint (Priv));
12472
12473      --  If the full base is itself derived from private, build a congruent
12474      --  subtype of its underlying type, for use by the back end. For a
12475      --  constrained record component, the declaration cannot be placed on
12476      --  the component list, but it must nevertheless be built an analyzed, to
12477      --  supply enough information for Gigi to compute the size of component.
12478
12479      elsif Ekind (Full_Base) in Private_Kind
12480        and then Is_Derived_Type (Full_Base)
12481        and then Has_Discriminants (Full_Base)
12482        and then (Ekind (Current_Scope) /= E_Record_Subtype)
12483      then
12484         if not Is_Itype (Priv)
12485           and then
12486             Nkind (Subtype_Indication (Parent (Priv))) = N_Subtype_Indication
12487         then
12488            Build_Underlying_Full_View
12489              (Parent (Priv), Full, Etype (Full_Base));
12490
12491         elsif Nkind (Related_Nod) = N_Component_Declaration then
12492            Build_Underlying_Full_View (Related_Nod, Full, Etype (Full_Base));
12493         end if;
12494
12495      elsif Is_Record_Type (Full_Base) then
12496
12497         --  Show Full is simply a renaming of Full_Base
12498
12499         Set_Cloned_Subtype (Full, Full_Base);
12500      end if;
12501
12502      --  It is unsafe to share the bounds of a scalar type, because the Itype
12503      --  is elaborated on demand, and if a bound is nonstatic, then different
12504      --  orders of elaboration in different units will lead to different
12505      --  external symbols.
12506
12507      if Is_Scalar_Type (Full_Base) then
12508         Set_Scalar_Range (Full,
12509           Make_Range (Sloc (Related_Nod),
12510             Low_Bound  =>
12511               Duplicate_Subexpr_No_Checks (Type_Low_Bound  (Full_Base)),
12512             High_Bound =>
12513               Duplicate_Subexpr_No_Checks (Type_High_Bound (Full_Base))));
12514
12515         --  This completion inherits the bounds of the full parent, but if
12516         --  the parent is an unconstrained floating point type, so is the
12517         --  completion.
12518
12519         if Is_Floating_Point_Type (Full_Base) then
12520            Set_Includes_Infinities
12521             (Scalar_Range (Full), Has_Infinities (Full_Base));
12522         end if;
12523      end if;
12524
12525      --  ??? It seems that a lot of fields are missing that should be copied
12526      --  from Full_Base to Full. Here are some that are introduced in a
12527      --  non-disruptive way but a cleanup is necessary.
12528
12529      if Is_Tagged_Type (Full_Base) then
12530         Set_Is_Tagged_Type (Full);
12531         Set_Direct_Primitive_Operations
12532           (Full, Direct_Primitive_Operations (Full_Base));
12533         Set_No_Tagged_Streams_Pragma
12534           (Full, No_Tagged_Streams_Pragma (Full_Base));
12535
12536         --  Inherit class_wide type of full_base in case the partial view was
12537         --  not tagged. Otherwise it has already been created when the private
12538         --  subtype was analyzed.
12539
12540         if No (Class_Wide_Type (Full)) then
12541            Set_Class_Wide_Type (Full, Class_Wide_Type (Full_Base));
12542         end if;
12543
12544      --  If this is a subtype of a protected or task type, constrain its
12545      --  corresponding record, unless this is a subtype without constraints,
12546      --  i.e. a simple renaming as with an actual subtype in an instance.
12547
12548      elsif Is_Concurrent_Type (Full_Base) then
12549         if Has_Discriminants (Full)
12550           and then Present (Corresponding_Record_Type (Full_Base))
12551           and then
12552             not Is_Empty_Elmt_List (Discriminant_Constraint (Full))
12553         then
12554            Set_Corresponding_Record_Type (Full,
12555              Constrain_Corresponding_Record
12556                (Full, Corresponding_Record_Type (Full_Base), Related_Nod));
12557
12558         else
12559            Set_Corresponding_Record_Type (Full,
12560              Corresponding_Record_Type (Full_Base));
12561         end if;
12562      end if;
12563
12564      --  Link rep item chain, and also setting of Has_Predicates from private
12565      --  subtype to full subtype, since we will need these on the full subtype
12566      --  to create the predicate function. Note that the full subtype may
12567      --  already have rep items, inherited from the full view of the base
12568      --  type, so we must be sure not to overwrite these entries.
12569
12570      declare
12571         Append    : Boolean;
12572         Item      : Node_Id;
12573         Next_Item : Node_Id;
12574         Priv_Item : Node_Id;
12575
12576      begin
12577         Item := First_Rep_Item (Full);
12578         Priv_Item := First_Rep_Item (Priv);
12579
12580         --  If no existing rep items on full type, we can just link directly
12581         --  to the list of items on the private type, if any exist.. Same if
12582         --  the rep items are only those inherited from the base
12583
12584         if (No (Item)
12585              or else Nkind (Item) /= N_Aspect_Specification
12586              or else Entity (Item) = Full_Base)
12587           and then Present (First_Rep_Item (Priv))
12588         then
12589            Set_First_Rep_Item (Full, Priv_Item);
12590
12591         --  Otherwise, search to the end of items currently linked to the full
12592         --  subtype and append the private items to the end. However, if Priv
12593         --  and Full already have the same list of rep items, then the append
12594         --  is not done, as that would create a circularity.
12595         --
12596         --  The partial view may have a predicate and the rep item lists of
12597         --  both views agree when inherited from the same ancestor. In that
12598         --  case, simply propagate the list from one view to the other.
12599         --  A more complex analysis needed here ???
12600
12601         elsif Present (Priv_Item)
12602           and then Item = Next_Rep_Item (Priv_Item)
12603         then
12604            Set_First_Rep_Item (Full, Priv_Item);
12605
12606         elsif Item /= Priv_Item then
12607            Append := True;
12608            loop
12609               Next_Item := Next_Rep_Item (Item);
12610               exit when No (Next_Item);
12611               Item := Next_Item;
12612
12613               --  If the private view has aspect specifications, the full view
12614               --  inherits them. Since these aspects may already have been
12615               --  attached to the full view during derivation, do not append
12616               --  them if already present.
12617
12618               if Item = First_Rep_Item (Priv) then
12619                  Append := False;
12620                  exit;
12621               end if;
12622            end loop;
12623
12624            --  And link the private type items at the end of the chain
12625
12626            if Append then
12627               Set_Next_Rep_Item (Item, First_Rep_Item (Priv));
12628            end if;
12629         end if;
12630      end;
12631
12632      --  Make sure Has_Predicates is set on full type if it is set on the
12633      --  private type. Note that it may already be set on the full type and
12634      --  if so, we don't want to unset it. Similarly, propagate information
12635      --  about delayed aspects, because the corresponding pragmas must be
12636      --  analyzed when one of the views is frozen. This last step is needed
12637      --  in particular when the full type is a scalar type for which an
12638      --  anonymous base type is constructed.
12639
12640      --  The predicate functions are generated either at the freeze point
12641      --  of the type or at the end of the visible part, and we must avoid
12642      --  generating them twice.
12643
12644      if Has_Predicates (Priv) then
12645         Set_Has_Predicates (Full);
12646
12647         if Present (Predicate_Function (Priv))
12648           and then No (Predicate_Function (Full))
12649         then
12650            Set_Predicate_Function (Full, Predicate_Function (Priv));
12651         end if;
12652      end if;
12653
12654      if Has_Delayed_Aspects (Priv) then
12655         Set_Has_Delayed_Aspects (Full);
12656      end if;
12657   end Complete_Private_Subtype;
12658
12659   ----------------------------
12660   -- Constant_Redeclaration --
12661   ----------------------------
12662
12663   procedure Constant_Redeclaration
12664     (Id : Entity_Id;
12665      N  : Node_Id;
12666      T  : out Entity_Id)
12667   is
12668      Prev    : constant Entity_Id := Current_Entity_In_Scope (Id);
12669      Obj_Def : constant Node_Id := Object_Definition (N);
12670      New_T   : Entity_Id;
12671
12672      procedure Check_Possible_Deferred_Completion
12673        (Prev_Id      : Entity_Id;
12674         Prev_Obj_Def : Node_Id;
12675         Curr_Obj_Def : Node_Id);
12676      --  Determine whether the two object definitions describe the partial
12677      --  and the full view of a constrained deferred constant. Generate
12678      --  a subtype for the full view and verify that it statically matches
12679      --  the subtype of the partial view.
12680
12681      procedure Check_Recursive_Declaration (Typ : Entity_Id);
12682      --  If deferred constant is an access type initialized with an allocator,
12683      --  check whether there is an illegal recursion in the definition,
12684      --  through a default value of some record subcomponent. This is normally
12685      --  detected when generating init procs, but requires this additional
12686      --  mechanism when expansion is disabled.
12687
12688      ----------------------------------------
12689      -- Check_Possible_Deferred_Completion --
12690      ----------------------------------------
12691
12692      procedure Check_Possible_Deferred_Completion
12693        (Prev_Id      : Entity_Id;
12694         Prev_Obj_Def : Node_Id;
12695         Curr_Obj_Def : Node_Id)
12696      is
12697      begin
12698         if Nkind (Prev_Obj_Def) = N_Subtype_Indication
12699           and then Present (Constraint (Prev_Obj_Def))
12700           and then Nkind (Curr_Obj_Def) = N_Subtype_Indication
12701           and then Present (Constraint (Curr_Obj_Def))
12702         then
12703            declare
12704               Loc    : constant Source_Ptr := Sloc (N);
12705               Def_Id : constant Entity_Id  := Make_Temporary (Loc, 'S');
12706               Decl   : constant Node_Id    :=
12707                          Make_Subtype_Declaration (Loc,
12708                            Defining_Identifier => Def_Id,
12709                            Subtype_Indication  =>
12710                              Relocate_Node (Curr_Obj_Def));
12711
12712            begin
12713               Insert_Before_And_Analyze (N, Decl);
12714               Set_Etype (Id, Def_Id);
12715
12716               if not Subtypes_Statically_Match (Etype (Prev_Id), Def_Id) then
12717                  Error_Msg_Sloc := Sloc (Prev_Id);
12718                  Error_Msg_N ("subtype does not statically match deferred "
12719                               & "declaration #", N);
12720               end if;
12721            end;
12722         end if;
12723      end Check_Possible_Deferred_Completion;
12724
12725      ---------------------------------
12726      -- Check_Recursive_Declaration --
12727      ---------------------------------
12728
12729      procedure Check_Recursive_Declaration (Typ : Entity_Id) is
12730         Comp : Entity_Id;
12731
12732      begin
12733         if Is_Record_Type (Typ) then
12734            Comp := First_Component (Typ);
12735            while Present (Comp) loop
12736               if Comes_From_Source (Comp) then
12737                  if Present (Expression (Parent (Comp)))
12738                    and then Is_Entity_Name (Expression (Parent (Comp)))
12739                    and then Entity (Expression (Parent (Comp))) = Prev
12740                  then
12741                     Error_Msg_Sloc := Sloc (Parent (Comp));
12742                     Error_Msg_NE
12743                       ("illegal circularity with declaration for & #",
12744                         N, Comp);
12745                     return;
12746
12747                  elsif Is_Record_Type (Etype (Comp)) then
12748                     Check_Recursive_Declaration (Etype (Comp));
12749                  end if;
12750               end if;
12751
12752               Next_Component (Comp);
12753            end loop;
12754         end if;
12755      end Check_Recursive_Declaration;
12756
12757   --  Start of processing for Constant_Redeclaration
12758
12759   begin
12760      if Nkind (Parent (Prev)) = N_Object_Declaration then
12761         if Nkind (Object_Definition
12762                     (Parent (Prev))) = N_Subtype_Indication
12763         then
12764            --  Find type of new declaration. The constraints of the two
12765            --  views must match statically, but there is no point in
12766            --  creating an itype for the full view.
12767
12768            if Nkind (Obj_Def) = N_Subtype_Indication then
12769               Find_Type (Subtype_Mark (Obj_Def));
12770               New_T := Entity (Subtype_Mark (Obj_Def));
12771
12772            else
12773               Find_Type (Obj_Def);
12774               New_T := Entity (Obj_Def);
12775            end if;
12776
12777            T := Etype (Prev);
12778
12779         else
12780            --  The full view may impose a constraint, even if the partial
12781            --  view does not, so construct the subtype.
12782
12783            New_T := Find_Type_Of_Object (Obj_Def, N);
12784            T     := New_T;
12785         end if;
12786
12787      else
12788         --  Current declaration is illegal, diagnosed below in Enter_Name
12789
12790         T := Empty;
12791         New_T := Any_Type;
12792      end if;
12793
12794      --  If previous full declaration or a renaming declaration exists, or if
12795      --  a homograph is present, let Enter_Name handle it, either with an
12796      --  error or with the removal of an overridden implicit subprogram.
12797      --  The previous one is a full declaration if it has an expression
12798      --  (which in the case of an aggregate is indicated by the Init flag).
12799
12800      if Ekind (Prev) /= E_Constant
12801        or else Nkind (Parent (Prev)) = N_Object_Renaming_Declaration
12802        or else Present (Expression (Parent (Prev)))
12803        or else Has_Init_Expression (Parent (Prev))
12804        or else Present (Full_View (Prev))
12805      then
12806         Enter_Name (Id);
12807
12808      --  Verify that types of both declarations match, or else that both types
12809      --  are anonymous access types whose designated subtypes statically match
12810      --  (as allowed in Ada 2005 by AI-385).
12811
12812      elsif Base_Type (Etype (Prev)) /= Base_Type (New_T)
12813        and then
12814          (Ekind (Etype (Prev)) /= E_Anonymous_Access_Type
12815             or else Ekind (Etype (New_T)) /= E_Anonymous_Access_Type
12816             or else Is_Access_Constant (Etype (New_T)) /=
12817                     Is_Access_Constant (Etype (Prev))
12818             or else Can_Never_Be_Null (Etype (New_T)) /=
12819                     Can_Never_Be_Null (Etype (Prev))
12820             or else Null_Exclusion_Present (Parent (Prev)) /=
12821                     Null_Exclusion_Present (Parent (Id))
12822             or else not Subtypes_Statically_Match
12823                           (Designated_Type (Etype (Prev)),
12824                            Designated_Type (Etype (New_T))))
12825      then
12826         Error_Msg_Sloc := Sloc (Prev);
12827         Error_Msg_N ("type does not match declaration#", N);
12828         Set_Full_View (Prev, Id);
12829         Set_Etype (Id, Any_Type);
12830
12831         --  A deferred constant whose type is an anonymous array is always
12832         --  illegal (unless imported). A detailed error message might be
12833         --  helpful for Ada beginners.
12834
12835         if Nkind (Object_Definition (Parent (Prev)))
12836            = N_Constrained_Array_Definition
12837           and then Nkind (Object_Definition (N))
12838              = N_Constrained_Array_Definition
12839         then
12840            Error_Msg_N ("\each anonymous array is a distinct type", N);
12841            Error_Msg_N ("a deferred constant must have a named type",
12842              Object_Definition (Parent (Prev)));
12843         end if;
12844
12845      elsif
12846        Null_Exclusion_Present (Parent (Prev))
12847          and then not Null_Exclusion_Present (N)
12848      then
12849         Error_Msg_Sloc := Sloc (Prev);
12850         Error_Msg_N ("null-exclusion does not match declaration#", N);
12851         Set_Full_View (Prev, Id);
12852         Set_Etype (Id, Any_Type);
12853
12854      --  If so, process the full constant declaration
12855
12856      else
12857         --  RM 7.4 (6): If the subtype defined by the subtype_indication in
12858         --  the deferred declaration is constrained, then the subtype defined
12859         --  by the subtype_indication in the full declaration shall match it
12860         --  statically.
12861
12862         Check_Possible_Deferred_Completion
12863           (Prev_Id      => Prev,
12864            Prev_Obj_Def => Object_Definition (Parent (Prev)),
12865            Curr_Obj_Def => Obj_Def);
12866
12867         Set_Full_View (Prev, Id);
12868         Set_Is_Public (Id, Is_Public (Prev));
12869         Set_Is_Internal (Id);
12870         Append_Entity (Id, Current_Scope);
12871
12872         --  Check ALIASED present if present before (RM 7.4(7))
12873
12874         if Is_Aliased (Prev)
12875           and then not Aliased_Present (N)
12876         then
12877            Error_Msg_Sloc := Sloc (Prev);
12878            Error_Msg_N ("ALIASED required (see declaration #)", N);
12879         end if;
12880
12881         --  Check that placement is in private part and that the incomplete
12882         --  declaration appeared in the visible part.
12883
12884         if Ekind (Current_Scope) = E_Package
12885           and then not In_Private_Part (Current_Scope)
12886         then
12887            Error_Msg_Sloc := Sloc (Prev);
12888            Error_Msg_N
12889              ("full constant for declaration # must be in private part", N);
12890
12891         elsif Ekind (Current_Scope) = E_Package
12892           and then
12893             List_Containing (Parent (Prev)) /=
12894               Visible_Declarations (Package_Specification (Current_Scope))
12895         then
12896            Error_Msg_N
12897              ("deferred constant must be declared in visible part",
12898                 Parent (Prev));
12899         end if;
12900
12901         if Is_Access_Type (T)
12902           and then Nkind (Expression (N)) = N_Allocator
12903         then
12904            Check_Recursive_Declaration (Designated_Type (T));
12905         end if;
12906
12907         --  A deferred constant is a visible entity. If type has invariants,
12908         --  verify that the initial value satisfies them. This is not done in
12909         --  GNATprove mode, as GNATprove handles invariant checks itself.
12910
12911         if Has_Invariants (T)
12912           and then Present (Invariant_Procedure (T))
12913           and then not GNATprove_Mode
12914         then
12915            Insert_After (N,
12916              Make_Invariant_Call (New_Occurrence_Of (Prev, Sloc (N))));
12917         end if;
12918      end if;
12919   end Constant_Redeclaration;
12920
12921   ----------------------
12922   -- Constrain_Access --
12923   ----------------------
12924
12925   procedure Constrain_Access
12926     (Def_Id      : in out Entity_Id;
12927      S           : Node_Id;
12928      Related_Nod : Node_Id)
12929   is
12930      T             : constant Entity_Id := Entity (Subtype_Mark (S));
12931      Desig_Type    : constant Entity_Id := Designated_Type (T);
12932      Desig_Subtype : Entity_Id := Create_Itype (E_Void, Related_Nod);
12933      Constraint_OK : Boolean := True;
12934
12935   begin
12936      if Is_Array_Type (Desig_Type) then
12937         Constrain_Array (Desig_Subtype, S, Related_Nod, Def_Id, 'P');
12938
12939      elsif (Is_Record_Type (Desig_Type)
12940              or else Is_Incomplete_Or_Private_Type (Desig_Type))
12941        and then not Is_Constrained (Desig_Type)
12942      then
12943         --  ??? The following code is a temporary bypass to ignore a
12944         --  discriminant constraint on access type if it is constraining
12945         --  the current record. Avoid creating the implicit subtype of the
12946         --  record we are currently compiling since right now, we cannot
12947         --  handle these. For now, just return the access type itself.
12948
12949         if Desig_Type = Current_Scope
12950           and then No (Def_Id)
12951         then
12952            Set_Ekind (Desig_Subtype, E_Record_Subtype);
12953            Def_Id := Entity (Subtype_Mark (S));
12954
12955            --  This call added to ensure that the constraint is analyzed
12956            --  (needed for a B test). Note that we still return early from
12957            --  this procedure to avoid recursive processing. ???
12958
12959            Constrain_Discriminated_Type
12960              (Desig_Subtype, S, Related_Nod, For_Access => True);
12961            return;
12962         end if;
12963
12964         --  Enforce rule that the constraint is illegal if there is an
12965         --  unconstrained view of the designated type. This means that the
12966         --  partial view (either a private type declaration or a derivation
12967         --  from a private type) has no discriminants. (Defect Report
12968         --  8652/0008, Technical Corrigendum 1, checked by ACATS B371001).
12969
12970         --  Rule updated for Ada 2005: The private type is said to have
12971         --  a constrained partial view, given that objects of the type
12972         --  can be declared. Furthermore, the rule applies to all access
12973         --  types, unlike the rule concerning default discriminants (see
12974         --  RM 3.7.1(7/3))
12975
12976         if (Ekind (T) = E_General_Access_Type or else Ada_Version >= Ada_2005)
12977           and then Has_Private_Declaration (Desig_Type)
12978           and then In_Open_Scopes (Scope (Desig_Type))
12979           and then Has_Discriminants (Desig_Type)
12980         then
12981            declare
12982               Pack  : constant Node_Id :=
12983                         Unit_Declaration_Node (Scope (Desig_Type));
12984               Decls : List_Id;
12985               Decl  : Node_Id;
12986
12987            begin
12988               if Nkind (Pack) = N_Package_Declaration then
12989                  Decls := Visible_Declarations (Specification (Pack));
12990                  Decl := First (Decls);
12991                  while Present (Decl) loop
12992                     if (Nkind (Decl) = N_Private_Type_Declaration
12993                          and then Chars (Defining_Identifier (Decl)) =
12994                                                           Chars (Desig_Type))
12995
12996                       or else
12997                        (Nkind (Decl) = N_Full_Type_Declaration
12998                          and then
12999                            Chars (Defining_Identifier (Decl)) =
13000                                                     Chars (Desig_Type)
13001                          and then Is_Derived_Type (Desig_Type)
13002                          and then
13003                            Has_Private_Declaration (Etype (Desig_Type)))
13004                     then
13005                        if No (Discriminant_Specifications (Decl)) then
13006                           Error_Msg_N
13007                             ("cannot constrain access type if designated "
13008                              & "type has constrained partial view", S);
13009                        end if;
13010
13011                        exit;
13012                     end if;
13013
13014                     Next (Decl);
13015                  end loop;
13016               end if;
13017            end;
13018         end if;
13019
13020         Constrain_Discriminated_Type (Desig_Subtype, S, Related_Nod,
13021           For_Access => True);
13022
13023      elsif Is_Concurrent_Type (Desig_Type)
13024        and then not Is_Constrained (Desig_Type)
13025      then
13026         Constrain_Concurrent (Desig_Subtype, S, Related_Nod, Desig_Type, ' ');
13027
13028      else
13029         Error_Msg_N ("invalid constraint on access type", S);
13030
13031         --  We simply ignore an invalid constraint
13032
13033         Desig_Subtype := Desig_Type;
13034         Constraint_OK := False;
13035      end if;
13036
13037      if No (Def_Id) then
13038         Def_Id := Create_Itype (E_Access_Subtype, Related_Nod);
13039      else
13040         Set_Ekind (Def_Id, E_Access_Subtype);
13041      end if;
13042
13043      if Constraint_OK then
13044         Set_Etype (Def_Id, Base_Type (T));
13045
13046         if Is_Private_Type (Desig_Type) then
13047            Prepare_Private_Subtype_Completion (Desig_Subtype, Related_Nod);
13048         end if;
13049      else
13050         Set_Etype (Def_Id, Any_Type);
13051      end if;
13052
13053      Set_Size_Info                (Def_Id, T);
13054      Set_Is_Constrained           (Def_Id, Constraint_OK);
13055      Set_Directly_Designated_Type (Def_Id, Desig_Subtype);
13056      Set_Depends_On_Private       (Def_Id, Has_Private_Component (Def_Id));
13057      Set_Is_Access_Constant       (Def_Id, Is_Access_Constant (T));
13058
13059      Conditional_Delay (Def_Id, T);
13060
13061      --  AI-363 : Subtypes of general access types whose designated types have
13062      --  default discriminants are disallowed. In instances, the rule has to
13063      --  be checked against the actual, of which T is the subtype. In a
13064      --  generic body, the rule is checked assuming that the actual type has
13065      --  defaulted discriminants.
13066
13067      if Ada_Version >= Ada_2005 or else Warn_On_Ada_2005_Compatibility then
13068         if Ekind (Base_Type (T)) = E_General_Access_Type
13069           and then Has_Defaulted_Discriminants (Desig_Type)
13070         then
13071            if Ada_Version < Ada_2005 then
13072               Error_Msg_N
13073                 ("access subtype of general access type would not " &
13074                  "be allowed in Ada 2005?y?", S);
13075            else
13076               Error_Msg_N
13077                 ("access subtype of general access type not allowed", S);
13078            end if;
13079
13080            Error_Msg_N ("\discriminants have defaults", S);
13081
13082         elsif Is_Access_Type (T)
13083           and then Is_Generic_Type (Desig_Type)
13084           and then Has_Discriminants (Desig_Type)
13085           and then In_Package_Body (Current_Scope)
13086         then
13087            if Ada_Version < Ada_2005 then
13088               Error_Msg_N
13089                 ("access subtype would not be allowed in generic body "
13090                  & "in Ada 2005?y?", S);
13091            else
13092               Error_Msg_N
13093                 ("access subtype not allowed in generic body", S);
13094            end if;
13095
13096            Error_Msg_N
13097              ("\designated type is a discriminated formal", S);
13098         end if;
13099      end if;
13100   end Constrain_Access;
13101
13102   ---------------------
13103   -- Constrain_Array --
13104   ---------------------
13105
13106   procedure Constrain_Array
13107     (Def_Id      : in out Entity_Id;
13108      SI          : Node_Id;
13109      Related_Nod : Node_Id;
13110      Related_Id  : Entity_Id;
13111      Suffix      : Character)
13112   is
13113      C                     : constant Node_Id := Constraint (SI);
13114      Number_Of_Constraints : Nat := 0;
13115      Index                 : Node_Id;
13116      S, T                  : Entity_Id;
13117      Constraint_OK         : Boolean := True;
13118
13119   begin
13120      T := Entity (Subtype_Mark (SI));
13121
13122      if Is_Access_Type (T) then
13123         T := Designated_Type (T);
13124      end if;
13125
13126      --  If an index constraint follows a subtype mark in a subtype indication
13127      --  then the type or subtype denoted by the subtype mark must not already
13128      --  impose an index constraint. The subtype mark must denote either an
13129      --  unconstrained array type or an access type whose designated type
13130      --  is such an array type... (RM 3.6.1)
13131
13132      if Is_Constrained (T) then
13133         Error_Msg_N ("array type is already constrained", Subtype_Mark (SI));
13134         Constraint_OK := False;
13135
13136      else
13137         S := First (Constraints (C));
13138         while Present (S) loop
13139            Number_Of_Constraints := Number_Of_Constraints + 1;
13140            Next (S);
13141         end loop;
13142
13143         --  In either case, the index constraint must provide a discrete
13144         --  range for each index of the array type and the type of each
13145         --  discrete range must be the same as that of the corresponding
13146         --  index. (RM 3.6.1)
13147
13148         if Number_Of_Constraints /= Number_Dimensions (T) then
13149            Error_Msg_NE ("incorrect number of index constraints for }", C, T);
13150            Constraint_OK := False;
13151
13152         else
13153            S := First (Constraints (C));
13154            Index := First_Index (T);
13155            Analyze (Index);
13156
13157            --  Apply constraints to each index type
13158
13159            for J in 1 .. Number_Of_Constraints loop
13160               Constrain_Index (Index, S, Related_Nod, Related_Id, Suffix, J);
13161               Next (Index);
13162               Next (S);
13163            end loop;
13164
13165         end if;
13166      end if;
13167
13168      if No (Def_Id) then
13169         Def_Id :=
13170           Create_Itype (E_Array_Subtype, Related_Nod, Related_Id, Suffix);
13171         Set_Parent (Def_Id, Related_Nod);
13172
13173      else
13174         Set_Ekind (Def_Id, E_Array_Subtype);
13175      end if;
13176
13177      Set_Size_Info      (Def_Id,                (T));
13178      Set_First_Rep_Item (Def_Id, First_Rep_Item (T));
13179      Set_Etype          (Def_Id, Base_Type      (T));
13180
13181      if Constraint_OK then
13182         Set_First_Index (Def_Id, First (Constraints (C)));
13183      else
13184         Set_First_Index (Def_Id, First_Index (T));
13185      end if;
13186
13187      Set_Is_Constrained     (Def_Id, True);
13188      Set_Is_Aliased         (Def_Id, Is_Aliased (T));
13189      Set_Depends_On_Private (Def_Id, Has_Private_Component (Def_Id));
13190
13191      Set_Is_Private_Composite (Def_Id, Is_Private_Composite (T));
13192      Set_Is_Limited_Composite (Def_Id, Is_Limited_Composite (T));
13193
13194      --  A subtype does not inherit the Packed_Array_Impl_Type of is parent.
13195      --  We need to initialize the attribute because if Def_Id is previously
13196      --  analyzed through a limited_with clause, it will have the attributes
13197      --  of an incomplete type, one of which is an Elist that overlaps the
13198      --  Packed_Array_Impl_Type field.
13199
13200      Set_Packed_Array_Impl_Type (Def_Id, Empty);
13201
13202      --  Build a freeze node if parent still needs one. Also make sure that
13203      --  the Depends_On_Private status is set because the subtype will need
13204      --  reprocessing at the time the base type does, and also we must set a
13205      --  conditional delay.
13206
13207      Set_Depends_On_Private (Def_Id, Depends_On_Private (T));
13208      Conditional_Delay (Def_Id, T);
13209   end Constrain_Array;
13210
13211   ------------------------------
13212   -- Constrain_Component_Type --
13213   ------------------------------
13214
13215   function Constrain_Component_Type
13216     (Comp            : Entity_Id;
13217      Constrained_Typ : Entity_Id;
13218      Related_Node    : Node_Id;
13219      Typ             : Entity_Id;
13220      Constraints     : Elist_Id) return Entity_Id
13221   is
13222      Loc         : constant Source_Ptr := Sloc (Constrained_Typ);
13223      Compon_Type : constant Entity_Id := Etype (Comp);
13224
13225      function Build_Constrained_Array_Type
13226        (Old_Type : Entity_Id) return Entity_Id;
13227      --  If Old_Type is an array type, one of whose indexes is constrained
13228      --  by a discriminant, build an Itype whose constraint replaces the
13229      --  discriminant with its value in the constraint.
13230
13231      function Build_Constrained_Discriminated_Type
13232        (Old_Type : Entity_Id) return Entity_Id;
13233      --  Ditto for record components
13234
13235      function Build_Constrained_Access_Type
13236        (Old_Type : Entity_Id) return Entity_Id;
13237      --  Ditto for access types. Makes use of previous two functions, to
13238      --  constrain designated type.
13239
13240      function Build_Subtype (T : Entity_Id; C : List_Id) return Entity_Id;
13241      --  T is an array or discriminated type, C is a list of constraints
13242      --  that apply to T. This routine builds the constrained subtype.
13243
13244      function Is_Discriminant (Expr : Node_Id) return Boolean;
13245      --  Returns True if Expr is a discriminant
13246
13247      function Get_Discr_Value (Discrim : Entity_Id) return Node_Id;
13248      --  Find the value of discriminant Discrim in Constraint
13249
13250      -----------------------------------
13251      -- Build_Constrained_Access_Type --
13252      -----------------------------------
13253
13254      function Build_Constrained_Access_Type
13255        (Old_Type : Entity_Id) return Entity_Id
13256      is
13257         Desig_Type    : constant Entity_Id := Designated_Type (Old_Type);
13258         Itype         : Entity_Id;
13259         Desig_Subtype : Entity_Id;
13260         Scop          : Entity_Id;
13261
13262      begin
13263         --  if the original access type was not embedded in the enclosing
13264         --  type definition, there is no need to produce a new access
13265         --  subtype. In fact every access type with an explicit constraint
13266         --  generates an itype whose scope is the enclosing record.
13267
13268         if not Is_Type (Scope (Old_Type)) then
13269            return Old_Type;
13270
13271         elsif Is_Array_Type (Desig_Type) then
13272            Desig_Subtype := Build_Constrained_Array_Type (Desig_Type);
13273
13274         elsif Has_Discriminants (Desig_Type) then
13275
13276            --  This may be an access type to an enclosing record type for
13277            --  which we are constructing the constrained components. Return
13278            --  the enclosing record subtype. This is not always correct,
13279            --  but avoids infinite recursion. ???
13280
13281            Desig_Subtype := Any_Type;
13282
13283            for J in reverse 0 .. Scope_Stack.Last loop
13284               Scop := Scope_Stack.Table (J).Entity;
13285
13286               if Is_Type (Scop)
13287                 and then Base_Type (Scop) = Base_Type (Desig_Type)
13288               then
13289                  Desig_Subtype := Scop;
13290               end if;
13291
13292               exit when not Is_Type (Scop);
13293            end loop;
13294
13295            if Desig_Subtype = Any_Type then
13296               Desig_Subtype :=
13297                 Build_Constrained_Discriminated_Type (Desig_Type);
13298            end if;
13299
13300         else
13301            return Old_Type;
13302         end if;
13303
13304         if Desig_Subtype /= Desig_Type then
13305
13306            --  The Related_Node better be here or else we won't be able
13307            --  to attach new itypes to a node in the tree.
13308
13309            pragma Assert (Present (Related_Node));
13310
13311            Itype := Create_Itype (E_Access_Subtype, Related_Node);
13312
13313            Set_Etype                    (Itype, Base_Type      (Old_Type));
13314            Set_Size_Info                (Itype,                (Old_Type));
13315            Set_Directly_Designated_Type (Itype, Desig_Subtype);
13316            Set_Depends_On_Private       (Itype, Has_Private_Component
13317                                                                (Old_Type));
13318            Set_Is_Access_Constant       (Itype, Is_Access_Constant
13319                                                                (Old_Type));
13320
13321            --  The new itype needs freezing when it depends on a not frozen
13322            --  type and the enclosing subtype needs freezing.
13323
13324            if Has_Delayed_Freeze (Constrained_Typ)
13325              and then not Is_Frozen (Constrained_Typ)
13326            then
13327               Conditional_Delay (Itype, Base_Type (Old_Type));
13328            end if;
13329
13330            return Itype;
13331
13332         else
13333            return Old_Type;
13334         end if;
13335      end Build_Constrained_Access_Type;
13336
13337      ----------------------------------
13338      -- Build_Constrained_Array_Type --
13339      ----------------------------------
13340
13341      function Build_Constrained_Array_Type
13342        (Old_Type : Entity_Id) return Entity_Id
13343      is
13344         Lo_Expr     : Node_Id;
13345         Hi_Expr     : Node_Id;
13346         Old_Index   : Node_Id;
13347         Range_Node  : Node_Id;
13348         Constr_List : List_Id;
13349
13350         Need_To_Create_Itype : Boolean := False;
13351
13352      begin
13353         Old_Index := First_Index (Old_Type);
13354         while Present (Old_Index) loop
13355            Get_Index_Bounds (Old_Index, Lo_Expr, Hi_Expr);
13356
13357            if Is_Discriminant (Lo_Expr)
13358                 or else
13359               Is_Discriminant (Hi_Expr)
13360            then
13361               Need_To_Create_Itype := True;
13362            end if;
13363
13364            Next_Index (Old_Index);
13365         end loop;
13366
13367         if Need_To_Create_Itype then
13368            Constr_List := New_List;
13369
13370            Old_Index := First_Index (Old_Type);
13371            while Present (Old_Index) loop
13372               Get_Index_Bounds (Old_Index, Lo_Expr, Hi_Expr);
13373
13374               if Is_Discriminant (Lo_Expr) then
13375                  Lo_Expr := Get_Discr_Value (Lo_Expr);
13376               end if;
13377
13378               if Is_Discriminant (Hi_Expr) then
13379                  Hi_Expr := Get_Discr_Value (Hi_Expr);
13380               end if;
13381
13382               Range_Node :=
13383                 Make_Range
13384                   (Loc, New_Copy_Tree (Lo_Expr), New_Copy_Tree (Hi_Expr));
13385
13386               Append (Range_Node, To => Constr_List);
13387
13388               Next_Index (Old_Index);
13389            end loop;
13390
13391            return Build_Subtype (Old_Type, Constr_List);
13392
13393         else
13394            return Old_Type;
13395         end if;
13396      end Build_Constrained_Array_Type;
13397
13398      ------------------------------------------
13399      -- Build_Constrained_Discriminated_Type --
13400      ------------------------------------------
13401
13402      function Build_Constrained_Discriminated_Type
13403        (Old_Type : Entity_Id) return Entity_Id
13404      is
13405         Expr           : Node_Id;
13406         Constr_List    : List_Id;
13407         Old_Constraint : Elmt_Id;
13408
13409         Need_To_Create_Itype : Boolean := False;
13410
13411      begin
13412         Old_Constraint := First_Elmt (Discriminant_Constraint (Old_Type));
13413         while Present (Old_Constraint) loop
13414            Expr := Node (Old_Constraint);
13415
13416            if Is_Discriminant (Expr) then
13417               Need_To_Create_Itype := True;
13418            end if;
13419
13420            Next_Elmt (Old_Constraint);
13421         end loop;
13422
13423         if Need_To_Create_Itype then
13424            Constr_List := New_List;
13425
13426            Old_Constraint := First_Elmt (Discriminant_Constraint (Old_Type));
13427            while Present (Old_Constraint) loop
13428               Expr := Node (Old_Constraint);
13429
13430               if Is_Discriminant (Expr) then
13431                  Expr := Get_Discr_Value (Expr);
13432               end if;
13433
13434               Append (New_Copy_Tree (Expr), To => Constr_List);
13435
13436               Next_Elmt (Old_Constraint);
13437            end loop;
13438
13439            return Build_Subtype (Old_Type, Constr_List);
13440
13441         else
13442            return Old_Type;
13443         end if;
13444      end Build_Constrained_Discriminated_Type;
13445
13446      -------------------
13447      -- Build_Subtype --
13448      -------------------
13449
13450      function Build_Subtype (T : Entity_Id; C : List_Id) return Entity_Id is
13451         Indic       : Node_Id;
13452         Subtyp_Decl : Node_Id;
13453         Def_Id      : Entity_Id;
13454         Btyp        : Entity_Id := Base_Type (T);
13455
13456      begin
13457         --  The Related_Node better be here or else we won't be able to
13458         --  attach new itypes to a node in the tree.
13459
13460         pragma Assert (Present (Related_Node));
13461
13462         --  If the view of the component's type is incomplete or private
13463         --  with unknown discriminants, then the constraint must be applied
13464         --  to the full type.
13465
13466         if Has_Unknown_Discriminants (Btyp)
13467           and then Present (Underlying_Type (Btyp))
13468         then
13469            Btyp := Underlying_Type (Btyp);
13470         end if;
13471
13472         Indic :=
13473           Make_Subtype_Indication (Loc,
13474             Subtype_Mark => New_Occurrence_Of (Btyp, Loc),
13475             Constraint   => Make_Index_Or_Discriminant_Constraint (Loc, C));
13476
13477         Def_Id := Create_Itype (Ekind (T), Related_Node);
13478
13479         Subtyp_Decl :=
13480           Make_Subtype_Declaration (Loc,
13481             Defining_Identifier => Def_Id,
13482             Subtype_Indication  => Indic);
13483
13484         Set_Parent (Subtyp_Decl, Parent (Related_Node));
13485
13486         --  Itypes must be analyzed with checks off (see package Itypes)
13487
13488         Analyze (Subtyp_Decl, Suppress => All_Checks);
13489
13490         if Is_Itype (Def_Id) and then Has_Predicates (T) then
13491            Inherit_Predicate_Flags (Def_Id, T);
13492
13493            --  Indicate where the predicate function may be found
13494
13495            if Is_Itype (T) then
13496               if Present (Predicate_Function (Def_Id)) then
13497                  null;
13498
13499               elsif Present (Predicate_Function (T)) then
13500                  Set_Predicate_Function (Def_Id, Predicate_Function (T));
13501
13502               else
13503                  Set_Predicated_Parent (Def_Id, Predicated_Parent (T));
13504               end if;
13505
13506            elsif No (Predicate_Function (Def_Id)) then
13507               Set_Predicated_Parent (Def_Id, T);
13508            end if;
13509         end if;
13510
13511         return Def_Id;
13512      end Build_Subtype;
13513
13514      ---------------------
13515      -- Get_Discr_Value --
13516      ---------------------
13517
13518      function Get_Discr_Value (Discrim : Entity_Id) return Node_Id is
13519         D : Entity_Id;
13520         E : Elmt_Id;
13521
13522      begin
13523         --  The discriminant may be declared for the type, in which case we
13524         --  find it by iterating over the list of discriminants. If the
13525         --  discriminant is inherited from a parent type, it appears as the
13526         --  corresponding discriminant of the current type. This will be the
13527         --  case when constraining an inherited component whose constraint is
13528         --  given by a discriminant of the parent.
13529
13530         D := First_Discriminant (Typ);
13531         E := First_Elmt (Constraints);
13532
13533         while Present (D) loop
13534            if D = Entity (Discrim)
13535              or else D = CR_Discriminant (Entity (Discrim))
13536              or else Corresponding_Discriminant (D) = Entity (Discrim)
13537            then
13538               return Node (E);
13539            end if;
13540
13541            Next_Discriminant (D);
13542            Next_Elmt (E);
13543         end loop;
13544
13545         --  The Corresponding_Discriminant mechanism is incomplete, because
13546         --  the correspondence between new and old discriminants is not one
13547         --  to one: one new discriminant can constrain several old ones. In
13548         --  that case, scan sequentially the stored_constraint, the list of
13549         --  discriminants of the parents, and the constraints.
13550
13551         --  Previous code checked for the present of the Stored_Constraint
13552         --  list for the derived type, but did not use it at all. Should it
13553         --  be present when the component is a discriminated task type?
13554
13555         if Is_Derived_Type (Typ)
13556           and then Scope (Entity (Discrim)) = Etype (Typ)
13557         then
13558            D := First_Discriminant (Etype (Typ));
13559            E := First_Elmt (Constraints);
13560            while Present (D) loop
13561               if D = Entity (Discrim) then
13562                  return Node (E);
13563               end if;
13564
13565               Next_Discriminant (D);
13566               Next_Elmt (E);
13567            end loop;
13568         end if;
13569
13570         --  Something is wrong if we did not find the value
13571
13572         raise Program_Error;
13573      end Get_Discr_Value;
13574
13575      ---------------------
13576      -- Is_Discriminant --
13577      ---------------------
13578
13579      function Is_Discriminant (Expr : Node_Id) return Boolean is
13580         Discrim_Scope : Entity_Id;
13581
13582      begin
13583         if Denotes_Discriminant (Expr) then
13584            Discrim_Scope := Scope (Entity (Expr));
13585
13586            --  Either we have a reference to one of Typ's discriminants,
13587
13588            pragma Assert (Discrim_Scope = Typ
13589
13590               --  or to the discriminants of the parent type, in the case
13591               --  of a derivation of a tagged type with variants.
13592
13593               or else Discrim_Scope = Etype (Typ)
13594               or else Full_View (Discrim_Scope) = Etype (Typ)
13595
13596               --  or same as above for the case where the discriminants
13597               --  were declared in Typ's private view.
13598
13599               or else (Is_Private_Type (Discrim_Scope)
13600                         and then Chars (Discrim_Scope) = Chars (Typ))
13601
13602               --  or else we are deriving from the full view and the
13603               --  discriminant is declared in the private entity.
13604
13605               or else (Is_Private_Type (Typ)
13606                         and then Chars (Discrim_Scope) = Chars (Typ))
13607
13608               --  Or we are constrained the corresponding record of a
13609               --  synchronized type that completes a private declaration.
13610
13611               or else (Is_Concurrent_Record_Type (Typ)
13612                         and then
13613                           Corresponding_Concurrent_Type (Typ) = Discrim_Scope)
13614
13615               --  or we have a class-wide type, in which case make sure the
13616               --  discriminant found belongs to the root type.
13617
13618               or else (Is_Class_Wide_Type (Typ)
13619                         and then Etype (Typ) = Discrim_Scope));
13620
13621            return True;
13622         end if;
13623
13624         --  In all other cases we have something wrong
13625
13626         return False;
13627      end Is_Discriminant;
13628
13629   --  Start of processing for Constrain_Component_Type
13630
13631   begin
13632      if Nkind (Parent (Comp)) = N_Component_Declaration
13633        and then Comes_From_Source (Parent (Comp))
13634        and then Comes_From_Source
13635          (Subtype_Indication (Component_Definition (Parent (Comp))))
13636        and then
13637          Is_Entity_Name
13638            (Subtype_Indication (Component_Definition (Parent (Comp))))
13639      then
13640         return Compon_Type;
13641
13642      elsif Is_Array_Type (Compon_Type) then
13643         return Build_Constrained_Array_Type (Compon_Type);
13644
13645      elsif Has_Discriminants (Compon_Type) then
13646         return Build_Constrained_Discriminated_Type (Compon_Type);
13647
13648      elsif Is_Access_Type (Compon_Type) then
13649         return Build_Constrained_Access_Type (Compon_Type);
13650
13651      else
13652         return Compon_Type;
13653      end if;
13654   end Constrain_Component_Type;
13655
13656   --------------------------
13657   -- Constrain_Concurrent --
13658   --------------------------
13659
13660   --  For concurrent types, the associated record value type carries the same
13661   --  discriminants, so when we constrain a concurrent type, we must constrain
13662   --  the corresponding record type as well.
13663
13664   procedure Constrain_Concurrent
13665     (Def_Id      : in out Entity_Id;
13666      SI          : Node_Id;
13667      Related_Nod : Node_Id;
13668      Related_Id  : Entity_Id;
13669      Suffix      : Character)
13670   is
13671      --  Retrieve Base_Type to ensure getting to the concurrent type in the
13672      --  case of a private subtype (needed when only doing semantic analysis).
13673
13674      T_Ent : Entity_Id := Base_Type (Entity (Subtype_Mark (SI)));
13675      T_Val : Entity_Id;
13676
13677   begin
13678      if Is_Access_Type (T_Ent) then
13679         T_Ent := Designated_Type (T_Ent);
13680      end if;
13681
13682      T_Val := Corresponding_Record_Type (T_Ent);
13683
13684      if Present (T_Val) then
13685
13686         if No (Def_Id) then
13687            Def_Id := Create_Itype (E_Void, Related_Nod, Related_Id, Suffix);
13688
13689            --  Elaborate itype now, as it may be used in a subsequent
13690            --  synchronized operation in another scope.
13691
13692            if Nkind (Related_Nod) = N_Full_Type_Declaration then
13693               Build_Itype_Reference (Def_Id, Related_Nod);
13694            end if;
13695         end if;
13696
13697         Constrain_Discriminated_Type (Def_Id, SI, Related_Nod);
13698         Set_First_Private_Entity (Def_Id, First_Private_Entity (T_Ent));
13699
13700         Set_Depends_On_Private (Def_Id, Has_Private_Component (Def_Id));
13701         Set_Corresponding_Record_Type (Def_Id,
13702           Constrain_Corresponding_Record (Def_Id, T_Val, Related_Nod));
13703
13704      else
13705         --  If there is no associated record, expansion is disabled and this
13706         --  is a generic context. Create a subtype in any case, so that
13707         --  semantic analysis can proceed.
13708
13709         if No (Def_Id) then
13710            Def_Id := Create_Itype (E_Void, Related_Nod, Related_Id, Suffix);
13711         end if;
13712
13713         Constrain_Discriminated_Type (Def_Id, SI, Related_Nod);
13714      end if;
13715   end Constrain_Concurrent;
13716
13717   ------------------------------------
13718   -- Constrain_Corresponding_Record --
13719   ------------------------------------
13720
13721   function Constrain_Corresponding_Record
13722     (Prot_Subt   : Entity_Id;
13723      Corr_Rec    : Entity_Id;
13724      Related_Nod : Node_Id) return Entity_Id
13725   is
13726      T_Sub : constant Entity_Id :=
13727                Create_Itype
13728                  (Ekind        => E_Record_Subtype,
13729                   Related_Nod  => Related_Nod,
13730                   Related_Id   => Corr_Rec,
13731                   Suffix       => 'C',
13732                   Suffix_Index => -1);
13733
13734   begin
13735      Set_Etype             (T_Sub, Corr_Rec);
13736      Set_Has_Discriminants (T_Sub, Has_Discriminants (Prot_Subt));
13737      Set_Is_Constrained    (T_Sub, True);
13738      Set_First_Entity      (T_Sub, First_Entity (Corr_Rec));
13739      Set_Last_Entity       (T_Sub, Last_Entity  (Corr_Rec));
13740
13741      if Has_Discriminants (Prot_Subt) then -- False only if errors.
13742         Set_Discriminant_Constraint
13743           (T_Sub, Discriminant_Constraint (Prot_Subt));
13744         Set_Stored_Constraint_From_Discriminant_Constraint (T_Sub);
13745         Create_Constrained_Components
13746           (T_Sub, Related_Nod, Corr_Rec, Discriminant_Constraint (T_Sub));
13747      end if;
13748
13749      Set_Depends_On_Private      (T_Sub, Has_Private_Component (T_Sub));
13750
13751      if Ekind (Scope (Prot_Subt)) /= E_Record_Type then
13752         Conditional_Delay (T_Sub, Corr_Rec);
13753
13754      else
13755         --  This is a component subtype: it will be frozen in the context of
13756         --  the enclosing record's init_proc, so that discriminant references
13757         --  are resolved to discriminals. (Note: we used to skip freezing
13758         --  altogether in that case, which caused errors downstream for
13759         --  components of a bit packed array type).
13760
13761         Set_Has_Delayed_Freeze (T_Sub);
13762      end if;
13763
13764      return T_Sub;
13765   end Constrain_Corresponding_Record;
13766
13767   -----------------------
13768   -- Constrain_Decimal --
13769   -----------------------
13770
13771   procedure Constrain_Decimal (Def_Id : Node_Id; S : Node_Id) is
13772      T           : constant Entity_Id  := Entity (Subtype_Mark (S));
13773      C           : constant Node_Id    := Constraint (S);
13774      Loc         : constant Source_Ptr := Sloc (C);
13775      Range_Expr  : Node_Id;
13776      Digits_Expr : Node_Id;
13777      Digits_Val  : Uint;
13778      Bound_Val   : Ureal;
13779
13780   begin
13781      Set_Ekind (Def_Id, E_Decimal_Fixed_Point_Subtype);
13782
13783      if Nkind (C) = N_Range_Constraint then
13784         Range_Expr := Range_Expression (C);
13785         Digits_Val := Digits_Value (T);
13786
13787      else
13788         pragma Assert (Nkind (C) = N_Digits_Constraint);
13789
13790         Check_SPARK_05_Restriction ("digits constraint is not allowed", S);
13791
13792         Digits_Expr := Digits_Expression (C);
13793         Analyze_And_Resolve (Digits_Expr, Any_Integer);
13794
13795         Check_Digits_Expression (Digits_Expr);
13796         Digits_Val := Expr_Value (Digits_Expr);
13797
13798         if Digits_Val > Digits_Value (T) then
13799            Error_Msg_N
13800               ("digits expression is incompatible with subtype", C);
13801            Digits_Val := Digits_Value (T);
13802         end if;
13803
13804         if Present (Range_Constraint (C)) then
13805            Range_Expr := Range_Expression (Range_Constraint (C));
13806         else
13807            Range_Expr := Empty;
13808         end if;
13809      end if;
13810
13811      Set_Etype            (Def_Id, Base_Type        (T));
13812      Set_Size_Info        (Def_Id,                  (T));
13813      Set_First_Rep_Item   (Def_Id, First_Rep_Item   (T));
13814      Set_Delta_Value      (Def_Id, Delta_Value      (T));
13815      Set_Scale_Value      (Def_Id, Scale_Value      (T));
13816      Set_Small_Value      (Def_Id, Small_Value      (T));
13817      Set_Machine_Radix_10 (Def_Id, Machine_Radix_10 (T));
13818      Set_Digits_Value     (Def_Id, Digits_Val);
13819
13820      --  Manufacture range from given digits value if no range present
13821
13822      if No (Range_Expr) then
13823         Bound_Val := (Ureal_10 ** Digits_Val - Ureal_1) * Small_Value (T);
13824         Range_Expr :=
13825           Make_Range (Loc,
13826             Low_Bound =>
13827               Convert_To (T, Make_Real_Literal (Loc, (-Bound_Val))),
13828             High_Bound =>
13829               Convert_To (T, Make_Real_Literal (Loc, Bound_Val)));
13830      end if;
13831
13832      Set_Scalar_Range_For_Subtype (Def_Id, Range_Expr, T);
13833      Set_Discrete_RM_Size (Def_Id);
13834
13835      --  Unconditionally delay the freeze, since we cannot set size
13836      --  information in all cases correctly until the freeze point.
13837
13838      Set_Has_Delayed_Freeze (Def_Id);
13839   end Constrain_Decimal;
13840
13841   ----------------------------------
13842   -- Constrain_Discriminated_Type --
13843   ----------------------------------
13844
13845   procedure Constrain_Discriminated_Type
13846     (Def_Id      : Entity_Id;
13847      S           : Node_Id;
13848      Related_Nod : Node_Id;
13849      For_Access  : Boolean := False)
13850   is
13851      E : Entity_Id := Entity (Subtype_Mark (S));
13852      T : Entity_Id;
13853
13854      procedure Fixup_Bad_Constraint;
13855      --  Called after finding a bad constraint, and after having posted an
13856      --  appropriate error message. The goal is to leave type Def_Id in as
13857      --  reasonable state as possible.
13858
13859      --------------------------
13860      -- Fixup_Bad_Constraint --
13861      --------------------------
13862
13863      procedure Fixup_Bad_Constraint is
13864      begin
13865         --  Set a reasonable Ekind for the entity, including incomplete types.
13866
13867         Set_Ekind (Def_Id, Subtype_Kind (Ekind (T)));
13868
13869         --  Set Etype to the known type, to reduce chances of cascaded errors
13870
13871         Set_Etype (Def_Id, E);
13872         Set_Error_Posted (Def_Id);
13873      end Fixup_Bad_Constraint;
13874
13875      --  Local variables
13876
13877      C      : Node_Id;
13878      Constr : Elist_Id := New_Elmt_List;
13879
13880   --  Start of processing for Constrain_Discriminated_Type
13881
13882   begin
13883      C := Constraint (S);
13884
13885      --  A discriminant constraint is only allowed in a subtype indication,
13886      --  after a subtype mark. This subtype mark must denote either a type
13887      --  with discriminants, or an access type whose designated type is a
13888      --  type with discriminants. A discriminant constraint specifies the
13889      --  values of these discriminants (RM 3.7.2(5)).
13890
13891      T := Base_Type (Entity (Subtype_Mark (S)));
13892
13893      if Is_Access_Type (T) then
13894         T := Designated_Type (T);
13895      end if;
13896
13897      --  In an instance it may be necessary to retrieve the full view of a
13898      --  type with unknown discriminants, or a full view with defaulted
13899      --  discriminants. In other contexts the constraint is illegal.
13900
13901      if In_Instance
13902        and then Is_Private_Type (T)
13903        and then Present (Full_View (T))
13904        and then
13905          (Has_Unknown_Discriminants (T)
13906            or else
13907              (not Has_Discriminants (T)
13908                and then Has_Discriminants (Full_View (T))
13909                and then Present (Discriminant_Default_Value
13910                           (First_Discriminant (Full_View (T))))))
13911      then
13912         T := Full_View (T);
13913         E := Full_View (E);
13914      end if;
13915
13916      --  Ada 2005 (AI-412): Constrained incomplete subtypes are illegal. Avoid
13917      --  generating an error for access-to-incomplete subtypes.
13918
13919      if Ada_Version >= Ada_2005
13920        and then Ekind (T) = E_Incomplete_Type
13921        and then Nkind (Parent (S)) = N_Subtype_Declaration
13922        and then not Is_Itype (Def_Id)
13923      then
13924         --  A little sanity check: emit an error message if the type has
13925         --  discriminants to begin with. Type T may be a regular incomplete
13926         --  type or imported via a limited with clause.
13927
13928         if Has_Discriminants (T)
13929           or else (From_Limited_With (T)
13930                     and then Present (Non_Limited_View (T))
13931                     and then Nkind (Parent (Non_Limited_View (T))) =
13932                                               N_Full_Type_Declaration
13933                     and then Present (Discriminant_Specifications
13934                                         (Parent (Non_Limited_View (T)))))
13935         then
13936            Error_Msg_N
13937              ("(Ada 2005) incomplete subtype may not be constrained", C);
13938         else
13939            Error_Msg_N ("invalid constraint: type has no discriminant", C);
13940         end if;
13941
13942         Fixup_Bad_Constraint;
13943         return;
13944
13945      --  Check that the type has visible discriminants. The type may be
13946      --  a private type with unknown discriminants whose full view has
13947      --  discriminants which are invisible.
13948
13949      elsif not Has_Discriminants (T)
13950        or else
13951          (Has_Unknown_Discriminants (T)
13952             and then Is_Private_Type (T))
13953      then
13954         Error_Msg_N ("invalid constraint: type has no discriminant", C);
13955         Fixup_Bad_Constraint;
13956         return;
13957
13958      elsif Is_Constrained (E)
13959        or else (Ekind (E) = E_Class_Wide_Subtype
13960                  and then Present (Discriminant_Constraint (E)))
13961      then
13962         Error_Msg_N ("type is already constrained", Subtype_Mark (S));
13963         Fixup_Bad_Constraint;
13964         return;
13965      end if;
13966
13967      --  T may be an unconstrained subtype (e.g. a generic actual). Constraint
13968      --  applies to the base type.
13969
13970      T := Base_Type (T);
13971
13972      Constr := Build_Discriminant_Constraints (T, S);
13973
13974      --  If the list returned was empty we had an error in building the
13975      --  discriminant constraint. We have also already signalled an error
13976      --  in the incomplete type case
13977
13978      if Is_Empty_Elmt_List (Constr) then
13979         Fixup_Bad_Constraint;
13980         return;
13981      end if;
13982
13983      Build_Discriminated_Subtype (T, Def_Id, Constr, Related_Nod, For_Access);
13984   end Constrain_Discriminated_Type;
13985
13986   ---------------------------
13987   -- Constrain_Enumeration --
13988   ---------------------------
13989
13990   procedure Constrain_Enumeration (Def_Id : Node_Id; S : Node_Id) is
13991      T : constant Entity_Id := Entity (Subtype_Mark (S));
13992      C : constant Node_Id   := Constraint (S);
13993
13994   begin
13995      Set_Ekind (Def_Id, E_Enumeration_Subtype);
13996
13997      Set_First_Literal     (Def_Id, First_Literal (Base_Type (T)));
13998
13999      Set_Etype             (Def_Id, Base_Type         (T));
14000      Set_Size_Info         (Def_Id,                   (T));
14001      Set_First_Rep_Item    (Def_Id, First_Rep_Item    (T));
14002      Set_Is_Character_Type (Def_Id, Is_Character_Type (T));
14003
14004      Set_Scalar_Range_For_Subtype (Def_Id, Range_Expression (C), T);
14005
14006      Set_Discrete_RM_Size (Def_Id);
14007   end Constrain_Enumeration;
14008
14009   ----------------------
14010   -- Constrain_Float --
14011   ----------------------
14012
14013   procedure Constrain_Float (Def_Id : Node_Id; S : Node_Id) is
14014      T    : constant Entity_Id := Entity (Subtype_Mark (S));
14015      C    : Node_Id;
14016      D    : Node_Id;
14017      Rais : Node_Id;
14018
14019   begin
14020      Set_Ekind (Def_Id, E_Floating_Point_Subtype);
14021
14022      Set_Etype          (Def_Id, Base_Type      (T));
14023      Set_Size_Info      (Def_Id,                (T));
14024      Set_First_Rep_Item (Def_Id, First_Rep_Item (T));
14025
14026      --  Process the constraint
14027
14028      C := Constraint (S);
14029
14030      --  Digits constraint present
14031
14032      if Nkind (C) = N_Digits_Constraint then
14033
14034         Check_SPARK_05_Restriction ("digits constraint is not allowed", S);
14035         Check_Restriction (No_Obsolescent_Features, C);
14036
14037         if Warn_On_Obsolescent_Feature then
14038            Error_Msg_N
14039              ("subtype digits constraint is an " &
14040               "obsolescent feature (RM J.3(8))?j?", C);
14041         end if;
14042
14043         D := Digits_Expression (C);
14044         Analyze_And_Resolve (D, Any_Integer);
14045         Check_Digits_Expression (D);
14046         Set_Digits_Value (Def_Id, Expr_Value (D));
14047
14048         --  Check that digits value is in range. Obviously we can do this
14049         --  at compile time, but it is strictly a runtime check, and of
14050         --  course there is an ACVC test that checks this.
14051
14052         if Digits_Value (Def_Id) > Digits_Value (T) then
14053            Error_Msg_Uint_1 := Digits_Value (T);
14054            Error_Msg_N ("??digits value is too large, maximum is ^", D);
14055            Rais :=
14056              Make_Raise_Constraint_Error (Sloc (D),
14057                Reason => CE_Range_Check_Failed);
14058            Insert_Action (Declaration_Node (Def_Id), Rais);
14059         end if;
14060
14061         C := Range_Constraint (C);
14062
14063      --  No digits constraint present
14064
14065      else
14066         Set_Digits_Value (Def_Id, Digits_Value (T));
14067      end if;
14068
14069      --  Range constraint present
14070
14071      if Nkind (C) = N_Range_Constraint then
14072         Set_Scalar_Range_For_Subtype (Def_Id, Range_Expression (C), T);
14073
14074      --  No range constraint present
14075
14076      else
14077         pragma Assert (No (C));
14078         Set_Scalar_Range (Def_Id, Scalar_Range (T));
14079      end if;
14080
14081      Set_Is_Constrained (Def_Id);
14082   end Constrain_Float;
14083
14084   ---------------------
14085   -- Constrain_Index --
14086   ---------------------
14087
14088   procedure Constrain_Index
14089     (Index        : Node_Id;
14090      S            : Node_Id;
14091      Related_Nod  : Node_Id;
14092      Related_Id   : Entity_Id;
14093      Suffix       : Character;
14094      Suffix_Index : Nat)
14095   is
14096      Def_Id : Entity_Id;
14097      R      : Node_Id := Empty;
14098      T      : constant Entity_Id := Etype (Index);
14099
14100   begin
14101      Def_Id :=
14102        Create_Itype (E_Void, Related_Nod, Related_Id, Suffix, Suffix_Index);
14103      Set_Etype (Def_Id, Base_Type (T));
14104
14105      if Nkind (S) = N_Range
14106        or else
14107          (Nkind (S) = N_Attribute_Reference
14108            and then Attribute_Name (S) = Name_Range)
14109      then
14110         --  A Range attribute will be transformed into N_Range by Resolve
14111
14112         Analyze (S);
14113         Set_Etype (S, T);
14114         R := S;
14115
14116         Process_Range_Expr_In_Decl (R, T);
14117
14118         if not Error_Posted (S)
14119           and then
14120             (Nkind (S) /= N_Range
14121               or else not Covers (T, (Etype (Low_Bound (S))))
14122               or else not Covers (T, (Etype (High_Bound (S)))))
14123         then
14124            if Base_Type (T) /= Any_Type
14125              and then Etype (Low_Bound (S)) /= Any_Type
14126              and then Etype (High_Bound (S)) /= Any_Type
14127            then
14128               Error_Msg_N ("range expected", S);
14129            end if;
14130         end if;
14131
14132      elsif Nkind (S) = N_Subtype_Indication then
14133
14134         --  The parser has verified that this is a discrete indication
14135
14136         Resolve_Discrete_Subtype_Indication (S, T);
14137         Bad_Predicated_Subtype_Use
14138           ("subtype& has predicate, not allowed in index constraint",
14139            S, Entity (Subtype_Mark (S)));
14140
14141         R := Range_Expression (Constraint (S));
14142
14143         --  Capture values of bounds and generate temporaries for them if
14144         --  needed, since checks may cause duplication of the expressions
14145         --  which must not be reevaluated.
14146
14147         --  The forced evaluation removes side effects from expressions, which
14148         --  should occur also in GNATprove mode. Otherwise, we end up with
14149         --  unexpected insertions of actions at places where this is not
14150         --  supposed to occur, e.g. on default parameters of a call.
14151
14152         if Expander_Active or GNATprove_Mode then
14153            Force_Evaluation
14154              (Low_Bound (R),  Related_Id => Def_Id, Is_Low_Bound  => True);
14155            Force_Evaluation
14156              (High_Bound (R), Related_Id => Def_Id, Is_High_Bound => True);
14157         end if;
14158
14159      elsif Nkind (S) = N_Discriminant_Association then
14160
14161         --  Syntactically valid in subtype indication
14162
14163         Error_Msg_N ("invalid index constraint", S);
14164         Rewrite (S, New_Occurrence_Of (T, Sloc (S)));
14165         return;
14166
14167      --  Subtype_Mark case, no anonymous subtypes to construct
14168
14169      else
14170         Analyze (S);
14171
14172         if Is_Entity_Name (S) then
14173            if not Is_Type (Entity (S)) then
14174               Error_Msg_N ("expect subtype mark for index constraint", S);
14175
14176            elsif Base_Type (Entity (S)) /= Base_Type (T) then
14177               Wrong_Type (S, Base_Type (T));
14178
14179            --  Check error of subtype with predicate in index constraint
14180
14181            else
14182               Bad_Predicated_Subtype_Use
14183                 ("subtype& has predicate, not allowed in index constraint",
14184                  S, Entity (S));
14185            end if;
14186
14187            return;
14188
14189         else
14190            Error_Msg_N ("invalid index constraint", S);
14191            Rewrite (S, New_Occurrence_Of (T, Sloc (S)));
14192            return;
14193         end if;
14194      end if;
14195
14196      --  Complete construction of the Itype
14197
14198      if Is_Modular_Integer_Type (T) then
14199         Set_Ekind (Def_Id, E_Modular_Integer_Subtype);
14200
14201      elsif Is_Integer_Type (T) then
14202         Set_Ekind (Def_Id, E_Signed_Integer_Subtype);
14203
14204      else
14205         Set_Ekind (Def_Id, E_Enumeration_Subtype);
14206         Set_Is_Character_Type (Def_Id, Is_Character_Type (T));
14207         Set_First_Literal     (Def_Id, First_Literal (T));
14208      end if;
14209
14210      Set_Size_Info      (Def_Id,                (T));
14211      Set_RM_Size        (Def_Id, RM_Size        (T));
14212      Set_First_Rep_Item (Def_Id, First_Rep_Item (T));
14213
14214      Set_Scalar_Range   (Def_Id, R);
14215
14216      Set_Etype (S, Def_Id);
14217      Set_Discrete_RM_Size (Def_Id);
14218   end Constrain_Index;
14219
14220   -----------------------
14221   -- Constrain_Integer --
14222   -----------------------
14223
14224   procedure Constrain_Integer (Def_Id : Node_Id; S : Node_Id) is
14225      T : constant Entity_Id := Entity (Subtype_Mark (S));
14226      C : constant Node_Id   := Constraint (S);
14227
14228   begin
14229      Set_Scalar_Range_For_Subtype (Def_Id, Range_Expression (C), T);
14230
14231      if Is_Modular_Integer_Type (T) then
14232         Set_Ekind (Def_Id, E_Modular_Integer_Subtype);
14233      else
14234         Set_Ekind (Def_Id, E_Signed_Integer_Subtype);
14235      end if;
14236
14237      Set_Etype            (Def_Id, Base_Type      (T));
14238      Set_Size_Info        (Def_Id,                (T));
14239      Set_First_Rep_Item   (Def_Id, First_Rep_Item (T));
14240      Set_Discrete_RM_Size (Def_Id);
14241   end Constrain_Integer;
14242
14243   ------------------------------
14244   -- Constrain_Ordinary_Fixed --
14245   ------------------------------
14246
14247   procedure Constrain_Ordinary_Fixed (Def_Id : Node_Id; S : Node_Id) is
14248      T    : constant Entity_Id := Entity (Subtype_Mark (S));
14249      C    : Node_Id;
14250      D    : Node_Id;
14251      Rais : Node_Id;
14252
14253   begin
14254      Set_Ekind          (Def_Id, E_Ordinary_Fixed_Point_Subtype);
14255      Set_Etype          (Def_Id, Base_Type      (T));
14256      Set_Size_Info      (Def_Id,                (T));
14257      Set_First_Rep_Item (Def_Id, First_Rep_Item (T));
14258      Set_Small_Value    (Def_Id, Small_Value    (T));
14259
14260      --  Process the constraint
14261
14262      C := Constraint (S);
14263
14264      --  Delta constraint present
14265
14266      if Nkind (C) = N_Delta_Constraint then
14267
14268         Check_SPARK_05_Restriction ("delta constraint is not allowed", S);
14269         Check_Restriction (No_Obsolescent_Features, C);
14270
14271         if Warn_On_Obsolescent_Feature then
14272            Error_Msg_S
14273              ("subtype delta constraint is an " &
14274               "obsolescent feature (RM J.3(7))?j?");
14275         end if;
14276
14277         D := Delta_Expression (C);
14278         Analyze_And_Resolve (D, Any_Real);
14279         Check_Delta_Expression (D);
14280         Set_Delta_Value (Def_Id, Expr_Value_R (D));
14281
14282         --  Check that delta value is in range. Obviously we can do this
14283         --  at compile time, but it is strictly a runtime check, and of
14284         --  course there is an ACVC test that checks this.
14285
14286         if Delta_Value (Def_Id) < Delta_Value (T) then
14287            Error_Msg_N ("??delta value is too small", D);
14288            Rais :=
14289              Make_Raise_Constraint_Error (Sloc (D),
14290                Reason => CE_Range_Check_Failed);
14291            Insert_Action (Declaration_Node (Def_Id), Rais);
14292         end if;
14293
14294         C := Range_Constraint (C);
14295
14296      --  No delta constraint present
14297
14298      else
14299         Set_Delta_Value (Def_Id, Delta_Value (T));
14300      end if;
14301
14302      --  Range constraint present
14303
14304      if Nkind (C) = N_Range_Constraint then
14305         Set_Scalar_Range_For_Subtype (Def_Id, Range_Expression (C), T);
14306
14307      --  No range constraint present
14308
14309      else
14310         pragma Assert (No (C));
14311         Set_Scalar_Range (Def_Id, Scalar_Range (T));
14312      end if;
14313
14314      Set_Discrete_RM_Size (Def_Id);
14315
14316      --  Unconditionally delay the freeze, since we cannot set size
14317      --  information in all cases correctly until the freeze point.
14318
14319      Set_Has_Delayed_Freeze (Def_Id);
14320   end Constrain_Ordinary_Fixed;
14321
14322   -----------------------
14323   -- Contain_Interface --
14324   -----------------------
14325
14326   function Contain_Interface
14327     (Iface  : Entity_Id;
14328      Ifaces : Elist_Id) return Boolean
14329   is
14330      Iface_Elmt : Elmt_Id;
14331
14332   begin
14333      if Present (Ifaces) then
14334         Iface_Elmt := First_Elmt (Ifaces);
14335         while Present (Iface_Elmt) loop
14336            if Node (Iface_Elmt) = Iface then
14337               return True;
14338            end if;
14339
14340            Next_Elmt (Iface_Elmt);
14341         end loop;
14342      end if;
14343
14344      return False;
14345   end Contain_Interface;
14346
14347   ---------------------------
14348   -- Convert_Scalar_Bounds --
14349   ---------------------------
14350
14351   procedure Convert_Scalar_Bounds
14352     (N            : Node_Id;
14353      Parent_Type  : Entity_Id;
14354      Derived_Type : Entity_Id;
14355      Loc          : Source_Ptr)
14356   is
14357      Implicit_Base : constant Entity_Id := Base_Type (Derived_Type);
14358
14359      Lo  : Node_Id;
14360      Hi  : Node_Id;
14361      Rng : Node_Id;
14362
14363   begin
14364      --  Defend against previous errors
14365
14366      if No (Scalar_Range (Derived_Type)) then
14367         Check_Error_Detected;
14368         return;
14369      end if;
14370
14371      Lo := Build_Scalar_Bound
14372              (Type_Low_Bound (Derived_Type),
14373               Parent_Type, Implicit_Base);
14374
14375      Hi := Build_Scalar_Bound
14376              (Type_High_Bound (Derived_Type),
14377               Parent_Type, Implicit_Base);
14378
14379      Rng :=
14380        Make_Range (Loc,
14381          Low_Bound  => Lo,
14382          High_Bound => Hi);
14383
14384      Set_Includes_Infinities (Rng, Has_Infinities (Derived_Type));
14385
14386      Set_Parent (Rng, N);
14387      Set_Scalar_Range (Derived_Type, Rng);
14388
14389      --  Analyze the bounds
14390
14391      Analyze_And_Resolve (Lo, Implicit_Base);
14392      Analyze_And_Resolve (Hi, Implicit_Base);
14393
14394      --  Analyze the range itself, except that we do not analyze it if
14395      --  the bounds are real literals, and we have a fixed-point type.
14396      --  The reason for this is that we delay setting the bounds in this
14397      --  case till we know the final Small and Size values (see circuit
14398      --  in Freeze.Freeze_Fixed_Point_Type for further details).
14399
14400      if Is_Fixed_Point_Type (Parent_Type)
14401        and then Nkind (Lo) = N_Real_Literal
14402        and then Nkind (Hi) = N_Real_Literal
14403      then
14404         return;
14405
14406      --  Here we do the analysis of the range
14407
14408      --  Note: we do this manually, since if we do a normal Analyze and
14409      --  Resolve call, there are problems with the conversions used for
14410      --  the derived type range.
14411
14412      else
14413         Set_Etype    (Rng, Implicit_Base);
14414         Set_Analyzed (Rng, True);
14415      end if;
14416   end Convert_Scalar_Bounds;
14417
14418   -------------------
14419   -- Copy_And_Swap --
14420   -------------------
14421
14422   procedure Copy_And_Swap (Priv, Full : Entity_Id) is
14423   begin
14424      --  Initialize new full declaration entity by copying the pertinent
14425      --  fields of the corresponding private declaration entity.
14426
14427      --  We temporarily set Ekind to a value appropriate for a type to
14428      --  avoid assert failures in Einfo from checking for setting type
14429      --  attributes on something that is not a type. Ekind (Priv) is an
14430      --  appropriate choice, since it allowed the attributes to be set
14431      --  in the first place. This Ekind value will be modified later.
14432
14433      Set_Ekind (Full, Ekind (Priv));
14434
14435      --  Also set Etype temporarily to Any_Type, again, in the absence
14436      --  of errors, it will be properly reset, and if there are errors,
14437      --  then we want a value of Any_Type to remain.
14438
14439      Set_Etype (Full, Any_Type);
14440
14441      --  Now start copying attributes
14442
14443      Set_Has_Discriminants          (Full, Has_Discriminants       (Priv));
14444
14445      if Has_Discriminants (Full) then
14446         Set_Discriminant_Constraint (Full, Discriminant_Constraint (Priv));
14447         Set_Stored_Constraint       (Full, Stored_Constraint       (Priv));
14448      end if;
14449
14450      Set_First_Rep_Item             (Full, First_Rep_Item          (Priv));
14451      Set_Homonym                    (Full, Homonym                 (Priv));
14452      Set_Is_Immediately_Visible     (Full, Is_Immediately_Visible  (Priv));
14453      Set_Is_Public                  (Full, Is_Public               (Priv));
14454      Set_Is_Pure                    (Full, Is_Pure                 (Priv));
14455      Set_Is_Tagged_Type             (Full, Is_Tagged_Type          (Priv));
14456      Set_Has_Pragma_Unmodified      (Full, Has_Pragma_Unmodified   (Priv));
14457      Set_Has_Pragma_Unreferenced    (Full, Has_Pragma_Unreferenced (Priv));
14458      Set_Has_Pragma_Unreferenced_Objects
14459                                     (Full, Has_Pragma_Unreferenced_Objects
14460                                                                    (Priv));
14461
14462      Conditional_Delay              (Full,                          Priv);
14463
14464      if Is_Tagged_Type (Full) then
14465         Set_Direct_Primitive_Operations
14466           (Full, Direct_Primitive_Operations (Priv));
14467         Set_No_Tagged_Streams_Pragma
14468           (Full, No_Tagged_Streams_Pragma (Priv));
14469
14470         if Is_Base_Type (Priv) then
14471            Set_Class_Wide_Type      (Full, Class_Wide_Type         (Priv));
14472         end if;
14473      end if;
14474
14475      Set_Is_Volatile                (Full, Is_Volatile             (Priv));
14476      Set_Treat_As_Volatile          (Full, Treat_As_Volatile       (Priv));
14477      Set_Scope                      (Full, Scope                   (Priv));
14478      Set_Prev_Entity                (Full, Prev_Entity             (Priv));
14479      Set_Next_Entity                (Full, Next_Entity             (Priv));
14480      Set_First_Entity               (Full, First_Entity            (Priv));
14481      Set_Last_Entity                (Full, Last_Entity             (Priv));
14482
14483      --  If access types have been recorded for later handling, keep them in
14484      --  the full view so that they get handled when the full view freeze
14485      --  node is expanded.
14486
14487      if Present (Freeze_Node (Priv))
14488        and then Present (Access_Types_To_Process (Freeze_Node (Priv)))
14489      then
14490         Ensure_Freeze_Node (Full);
14491         Set_Access_Types_To_Process
14492           (Freeze_Node (Full),
14493            Access_Types_To_Process (Freeze_Node (Priv)));
14494      end if;
14495
14496      --  Swap the two entities. Now Private is the full type entity and Full
14497      --  is the private one. They will be swapped back at the end of the
14498      --  private part. This swapping ensures that the entity that is visible
14499      --  in the private part is the full declaration.
14500
14501      Exchange_Entities (Priv, Full);
14502      Append_Entity (Full, Scope (Full));
14503   end Copy_And_Swap;
14504
14505   -------------------------------------
14506   -- Copy_Array_Base_Type_Attributes --
14507   -------------------------------------
14508
14509   procedure Copy_Array_Base_Type_Attributes (T1, T2 : Entity_Id) is
14510   begin
14511      Set_Component_Alignment      (T1, Component_Alignment      (T2));
14512      Set_Component_Type           (T1, Component_Type           (T2));
14513      Set_Component_Size           (T1, Component_Size           (T2));
14514      Set_Has_Controlled_Component (T1, Has_Controlled_Component (T2));
14515      Set_Has_Non_Standard_Rep     (T1, Has_Non_Standard_Rep     (T2));
14516      Propagate_Concurrent_Flags   (T1, T2);
14517      Set_Is_Packed                (T1, Is_Packed                (T2));
14518      Set_Has_Aliased_Components   (T1, Has_Aliased_Components   (T2));
14519      Set_Has_Atomic_Components    (T1, Has_Atomic_Components    (T2));
14520      Set_Has_Volatile_Components  (T1, Has_Volatile_Components  (T2));
14521   end Copy_Array_Base_Type_Attributes;
14522
14523   -----------------------------------
14524   -- Copy_Array_Subtype_Attributes --
14525   -----------------------------------
14526
14527   procedure Copy_Array_Subtype_Attributes (T1, T2 : Entity_Id) is
14528   begin
14529      Set_Size_Info (T1, T2);
14530
14531      Set_First_Index            (T1, First_Index            (T2));
14532      Set_Is_Aliased             (T1, Is_Aliased             (T2));
14533      Set_Is_Volatile            (T1, Is_Volatile            (T2));
14534      Set_Treat_As_Volatile      (T1, Treat_As_Volatile      (T2));
14535      Set_Is_Constrained         (T1, Is_Constrained         (T2));
14536      Set_Depends_On_Private     (T1, Has_Private_Component  (T2));
14537      Inherit_Rep_Item_Chain     (T1,                         T2);
14538      Set_Convention             (T1, Convention             (T2));
14539      Set_Is_Limited_Composite   (T1, Is_Limited_Composite   (T2));
14540      Set_Is_Private_Composite   (T1, Is_Private_Composite   (T2));
14541      Set_Packed_Array_Impl_Type (T1, Packed_Array_Impl_Type (T2));
14542   end Copy_Array_Subtype_Attributes;
14543
14544   -----------------------------------
14545   -- Create_Constrained_Components --
14546   -----------------------------------
14547
14548   procedure Create_Constrained_Components
14549     (Subt        : Entity_Id;
14550      Decl_Node   : Node_Id;
14551      Typ         : Entity_Id;
14552      Constraints : Elist_Id)
14553   is
14554      Loc         : constant Source_Ptr := Sloc (Subt);
14555      Comp_List   : constant Elist_Id   := New_Elmt_List;
14556      Parent_Type : constant Entity_Id  := Etype (Typ);
14557      Assoc_List  : constant List_Id    := New_List;
14558      Discr_Val   : Elmt_Id;
14559      Errors      : Boolean;
14560      New_C       : Entity_Id;
14561      Old_C       : Entity_Id;
14562      Is_Static   : Boolean := True;
14563
14564      procedure Collect_Fixed_Components (Typ : Entity_Id);
14565      --  Collect parent type components that do not appear in a variant part
14566
14567      procedure Create_All_Components;
14568      --  Iterate over Comp_List to create the components of the subtype
14569
14570      function Create_Component (Old_Compon : Entity_Id) return Entity_Id;
14571      --  Creates a new component from Old_Compon, copying all the fields from
14572      --  it, including its Etype, inserts the new component in the Subt entity
14573      --  chain and returns the new component.
14574
14575      function Is_Variant_Record (T : Entity_Id) return Boolean;
14576      --  If true, and discriminants are static, collect only components from
14577      --  variants selected by discriminant values.
14578
14579      ------------------------------
14580      -- Collect_Fixed_Components --
14581      ------------------------------
14582
14583      procedure Collect_Fixed_Components (Typ : Entity_Id) is
14584      begin
14585      --  Build association list for discriminants, and find components of the
14586      --  variant part selected by the values of the discriminants.
14587
14588         Old_C := First_Discriminant (Typ);
14589         Discr_Val := First_Elmt (Constraints);
14590         while Present (Old_C) loop
14591            Append_To (Assoc_List,
14592              Make_Component_Association (Loc,
14593                 Choices    => New_List (New_Occurrence_Of (Old_C, Loc)),
14594                 Expression => New_Copy (Node (Discr_Val))));
14595
14596            Next_Elmt (Discr_Val);
14597            Next_Discriminant (Old_C);
14598         end loop;
14599
14600         --  The tag and the possible parent component are unconditionally in
14601         --  the subtype.
14602
14603         if Is_Tagged_Type (Typ) or else Has_Controlled_Component (Typ) then
14604            Old_C := First_Component (Typ);
14605            while Present (Old_C) loop
14606               if Nam_In (Chars (Old_C), Name_uTag, Name_uParent) then
14607                  Append_Elmt (Old_C, Comp_List);
14608               end if;
14609
14610               Next_Component (Old_C);
14611            end loop;
14612         end if;
14613      end Collect_Fixed_Components;
14614
14615      ---------------------------
14616      -- Create_All_Components --
14617      ---------------------------
14618
14619      procedure Create_All_Components is
14620         Comp : Elmt_Id;
14621
14622      begin
14623         Comp := First_Elmt (Comp_List);
14624         while Present (Comp) loop
14625            Old_C := Node (Comp);
14626            New_C := Create_Component (Old_C);
14627
14628            Set_Etype
14629              (New_C,
14630               Constrain_Component_Type
14631                 (Old_C, Subt, Decl_Node, Typ, Constraints));
14632            Set_Is_Public (New_C, Is_Public (Subt));
14633
14634            Next_Elmt (Comp);
14635         end loop;
14636      end Create_All_Components;
14637
14638      ----------------------
14639      -- Create_Component --
14640      ----------------------
14641
14642      function Create_Component (Old_Compon : Entity_Id) return Entity_Id is
14643         New_Compon : constant Entity_Id := New_Copy (Old_Compon);
14644
14645      begin
14646         if Ekind (Old_Compon) = E_Discriminant
14647           and then Is_Completely_Hidden (Old_Compon)
14648         then
14649            --  This is a shadow discriminant created for a discriminant of
14650            --  the parent type, which needs to be present in the subtype.
14651            --  Give the shadow discriminant an internal name that cannot
14652            --  conflict with that of visible components.
14653
14654            Set_Chars (New_Compon, New_Internal_Name ('C'));
14655         end if;
14656
14657         --  Set the parent so we have a proper link for freezing etc. This is
14658         --  not a real parent pointer, since of course our parent does not own
14659         --  up to us and reference us, we are an illegitimate child of the
14660         --  original parent.
14661
14662         Set_Parent (New_Compon, Parent (Old_Compon));
14663
14664         --  We do not want this node marked as Comes_From_Source, since
14665         --  otherwise it would get first class status and a separate cross-
14666         --  reference line would be generated. Illegitimate children do not
14667         --  rate such recognition.
14668
14669         Set_Comes_From_Source (New_Compon, False);
14670
14671         --  But it is a real entity, and a birth certificate must be properly
14672         --  registered by entering it into the entity list, and setting its
14673         --  scope to the given subtype. This turns out to be useful for the
14674         --  LLVM code generator, but that scope is not used otherwise.
14675
14676         Enter_Name (New_Compon);
14677         Set_Scope (New_Compon, Subt);
14678
14679         return New_Compon;
14680      end Create_Component;
14681
14682      -----------------------
14683      -- Is_Variant_Record --
14684      -----------------------
14685
14686      function Is_Variant_Record (T : Entity_Id) return Boolean is
14687      begin
14688         return Nkind (Parent (T)) = N_Full_Type_Declaration
14689           and then Nkind (Type_Definition (Parent (T))) = N_Record_Definition
14690           and then Present (Component_List (Type_Definition (Parent (T))))
14691           and then
14692             Present
14693               (Variant_Part (Component_List (Type_Definition (Parent (T)))));
14694      end Is_Variant_Record;
14695
14696   --  Start of processing for Create_Constrained_Components
14697
14698   begin
14699      pragma Assert (Subt /= Base_Type (Subt));
14700      pragma Assert (Typ = Base_Type (Typ));
14701
14702      Set_First_Entity (Subt, Empty);
14703      Set_Last_Entity  (Subt, Empty);
14704
14705      --  Check whether constraint is fully static, in which case we can
14706      --  optimize the list of components.
14707
14708      Discr_Val := First_Elmt (Constraints);
14709      while Present (Discr_Val) loop
14710         if not Is_OK_Static_Expression (Node (Discr_Val)) then
14711            Is_Static := False;
14712            exit;
14713         end if;
14714
14715         Next_Elmt (Discr_Val);
14716      end loop;
14717
14718      Set_Has_Static_Discriminants (Subt, Is_Static);
14719
14720      Push_Scope (Subt);
14721
14722      --  Inherit the discriminants of the parent type
14723
14724      Add_Discriminants : declare
14725         Num_Disc : Nat;
14726         Num_Gird : Nat;
14727
14728      begin
14729         Num_Disc := 0;
14730         Old_C := First_Discriminant (Typ);
14731
14732         while Present (Old_C) loop
14733            Num_Disc := Num_Disc + 1;
14734            New_C := Create_Component (Old_C);
14735            Set_Is_Public (New_C, Is_Public (Subt));
14736            Next_Discriminant (Old_C);
14737         end loop;
14738
14739         --  For an untagged derived subtype, the number of discriminants may
14740         --  be smaller than the number of inherited discriminants, because
14741         --  several of them may be renamed by a single new discriminant or
14742         --  constrained. In this case, add the hidden discriminants back into
14743         --  the subtype, because they need to be present if the optimizer of
14744         --  the GCC 4.x back-end decides to break apart assignments between
14745         --  objects using the parent view into member-wise assignments.
14746
14747         Num_Gird := 0;
14748
14749         if Is_Derived_Type (Typ)
14750           and then not Is_Tagged_Type (Typ)
14751         then
14752            Old_C := First_Stored_Discriminant (Typ);
14753
14754            while Present (Old_C) loop
14755               Num_Gird := Num_Gird + 1;
14756               Next_Stored_Discriminant (Old_C);
14757            end loop;
14758         end if;
14759
14760         if Num_Gird > Num_Disc then
14761
14762            --  Find out multiple uses of new discriminants, and add hidden
14763            --  components for the extra renamed discriminants. We recognize
14764            --  multiple uses through the Corresponding_Discriminant of a
14765            --  new discriminant: if it constrains several old discriminants,
14766            --  this field points to the last one in the parent type. The
14767            --  stored discriminants of the derived type have the same name
14768            --  as those of the parent.
14769
14770            declare
14771               Constr    : Elmt_Id;
14772               New_Discr : Entity_Id;
14773               Old_Discr : Entity_Id;
14774
14775            begin
14776               Constr    := First_Elmt (Stored_Constraint (Typ));
14777               Old_Discr := First_Stored_Discriminant (Typ);
14778               while Present (Constr) loop
14779                  if Is_Entity_Name (Node (Constr))
14780                    and then Ekind (Entity (Node (Constr))) = E_Discriminant
14781                  then
14782                     New_Discr := Entity (Node (Constr));
14783
14784                     if Chars (Corresponding_Discriminant (New_Discr)) /=
14785                        Chars (Old_Discr)
14786                     then
14787                        --  The new discriminant has been used to rename a
14788                        --  subsequent old discriminant. Introduce a shadow
14789                        --  component for the current old discriminant.
14790
14791                        New_C := Create_Component (Old_Discr);
14792                        Set_Original_Record_Component (New_C, Old_Discr);
14793                     end if;
14794
14795                  else
14796                     --  The constraint has eliminated the old discriminant.
14797                     --  Introduce a shadow component.
14798
14799                     New_C := Create_Component (Old_Discr);
14800                     Set_Original_Record_Component (New_C, Old_Discr);
14801                  end if;
14802
14803                  Next_Elmt (Constr);
14804                  Next_Stored_Discriminant (Old_Discr);
14805               end loop;
14806            end;
14807         end if;
14808      end Add_Discriminants;
14809
14810      if Is_Static
14811        and then Is_Variant_Record (Typ)
14812      then
14813         Collect_Fixed_Components (Typ);
14814
14815         Gather_Components (
14816           Typ,
14817           Component_List (Type_Definition (Parent (Typ))),
14818           Governed_By   => Assoc_List,
14819           Into          => Comp_List,
14820           Report_Errors => Errors);
14821         pragma Assert (not Errors
14822           or else Serious_Errors_Detected > 0);
14823
14824         Create_All_Components;
14825
14826      --  If the subtype declaration is created for a tagged type derivation
14827      --  with constraints, we retrieve the record definition of the parent
14828      --  type to select the components of the proper variant.
14829
14830      elsif Is_Static
14831        and then Is_Tagged_Type (Typ)
14832        and then Nkind (Parent (Typ)) = N_Full_Type_Declaration
14833        and then
14834          Nkind (Type_Definition (Parent (Typ))) = N_Derived_Type_Definition
14835        and then Is_Variant_Record (Parent_Type)
14836      then
14837         Collect_Fixed_Components (Typ);
14838
14839         Gather_Components
14840           (Typ,
14841            Component_List (Type_Definition (Parent (Parent_Type))),
14842            Governed_By   => Assoc_List,
14843            Into          => Comp_List,
14844            Report_Errors => Errors);
14845
14846         --  Note: previously there was a check at this point that no errors
14847         --  were detected. As a consequence of AI05-220 there may be an error
14848         --  if an inherited discriminant that controls a variant has a non-
14849         --  static constraint.
14850
14851         --  If the tagged derivation has a type extension, collect all the
14852         --  new components therein.
14853
14854         if Present (Record_Extension_Part (Type_Definition (Parent (Typ))))
14855         then
14856            Old_C := First_Component (Typ);
14857            while Present (Old_C) loop
14858               if Original_Record_Component (Old_C) = Old_C
14859                 and then Chars (Old_C) /= Name_uTag
14860                 and then Chars (Old_C) /= Name_uParent
14861               then
14862                  Append_Elmt (Old_C, Comp_List);
14863               end if;
14864
14865               Next_Component (Old_C);
14866            end loop;
14867         end if;
14868
14869         Create_All_Components;
14870
14871      else
14872         --  If discriminants are not static, or if this is a multi-level type
14873         --  extension, we have to include all components of the parent type.
14874
14875         Old_C := First_Component (Typ);
14876         while Present (Old_C) loop
14877            New_C := Create_Component (Old_C);
14878
14879            Set_Etype
14880              (New_C,
14881               Constrain_Component_Type
14882                 (Old_C, Subt, Decl_Node, Typ, Constraints));
14883            Set_Is_Public (New_C, Is_Public (Subt));
14884
14885            Next_Component (Old_C);
14886         end loop;
14887      end if;
14888
14889      End_Scope;
14890   end Create_Constrained_Components;
14891
14892   ------------------------------------------
14893   -- Decimal_Fixed_Point_Type_Declaration --
14894   ------------------------------------------
14895
14896   procedure Decimal_Fixed_Point_Type_Declaration
14897     (T   : Entity_Id;
14898      Def : Node_Id)
14899   is
14900      Loc           : constant Source_Ptr := Sloc (Def);
14901      Digs_Expr     : constant Node_Id    := Digits_Expression (Def);
14902      Delta_Expr    : constant Node_Id    := Delta_Expression (Def);
14903      Implicit_Base : Entity_Id;
14904      Digs_Val      : Uint;
14905      Delta_Val     : Ureal;
14906      Scale_Val     : Uint;
14907      Bound_Val     : Ureal;
14908
14909   begin
14910      Check_SPARK_05_Restriction
14911        ("decimal fixed point type is not allowed", Def);
14912      Check_Restriction (No_Fixed_Point, Def);
14913
14914      --  Create implicit base type
14915
14916      Implicit_Base :=
14917        Create_Itype (E_Decimal_Fixed_Point_Type, Parent (Def), T, 'B');
14918      Set_Etype (Implicit_Base, Implicit_Base);
14919
14920      --  Analyze and process delta expression
14921
14922      Analyze_And_Resolve (Delta_Expr, Universal_Real);
14923
14924      Check_Delta_Expression (Delta_Expr);
14925      Delta_Val := Expr_Value_R (Delta_Expr);
14926
14927      --  Check delta is power of 10, and determine scale value from it
14928
14929      declare
14930         Val : Ureal;
14931
14932      begin
14933         Scale_Val := Uint_0;
14934         Val := Delta_Val;
14935
14936         if Val < Ureal_1 then
14937            while Val < Ureal_1 loop
14938               Val := Val * Ureal_10;
14939               Scale_Val := Scale_Val + 1;
14940            end loop;
14941
14942            if Scale_Val > 18 then
14943               Error_Msg_N ("scale exceeds maximum value of 18", Def);
14944               Scale_Val := UI_From_Int (+18);
14945            end if;
14946
14947         else
14948            while Val > Ureal_1 loop
14949               Val := Val / Ureal_10;
14950               Scale_Val := Scale_Val - 1;
14951            end loop;
14952
14953            if Scale_Val < -18 then
14954               Error_Msg_N ("scale is less than minimum value of -18", Def);
14955               Scale_Val := UI_From_Int (-18);
14956            end if;
14957         end if;
14958
14959         if Val /= Ureal_1 then
14960            Error_Msg_N ("delta expression must be a power of 10", Def);
14961            Delta_Val := Ureal_10 ** (-Scale_Val);
14962         end if;
14963      end;
14964
14965      --  Set delta, scale and small (small = delta for decimal type)
14966
14967      Set_Delta_Value (Implicit_Base, Delta_Val);
14968      Set_Scale_Value (Implicit_Base, Scale_Val);
14969      Set_Small_Value (Implicit_Base, Delta_Val);
14970
14971      --  Analyze and process digits expression
14972
14973      Analyze_And_Resolve (Digs_Expr, Any_Integer);
14974      Check_Digits_Expression (Digs_Expr);
14975      Digs_Val := Expr_Value (Digs_Expr);
14976
14977      if Digs_Val > 18 then
14978         Digs_Val := UI_From_Int (+18);
14979         Error_Msg_N ("digits value out of range, maximum is 18", Digs_Expr);
14980      end if;
14981
14982      Set_Digits_Value (Implicit_Base, Digs_Val);
14983      Bound_Val := UR_From_Uint (10 ** Digs_Val - 1) * Delta_Val;
14984
14985      --  Set range of base type from digits value for now. This will be
14986      --  expanded to represent the true underlying base range by Freeze.
14987
14988      Set_Fixed_Range (Implicit_Base, Loc, -Bound_Val, Bound_Val);
14989
14990      --  Note: We leave size as zero for now, size will be set at freeze
14991      --  time. We have to do this for ordinary fixed-point, because the size
14992      --  depends on the specified small, and we might as well do the same for
14993      --  decimal fixed-point.
14994
14995      pragma Assert (Esize (Implicit_Base) = Uint_0);
14996
14997      --  If there are bounds given in the declaration use them as the
14998      --  bounds of the first named subtype.
14999
15000      if Present (Real_Range_Specification (Def)) then
15001         declare
15002            RRS      : constant Node_Id := Real_Range_Specification (Def);
15003            Low      : constant Node_Id := Low_Bound (RRS);
15004            High     : constant Node_Id := High_Bound (RRS);
15005            Low_Val  : Ureal;
15006            High_Val : Ureal;
15007
15008         begin
15009            Analyze_And_Resolve (Low, Any_Real);
15010            Analyze_And_Resolve (High, Any_Real);
15011            Check_Real_Bound (Low);
15012            Check_Real_Bound (High);
15013            Low_Val := Expr_Value_R (Low);
15014            High_Val := Expr_Value_R (High);
15015
15016            if Low_Val < (-Bound_Val) then
15017               Error_Msg_N
15018                 ("range low bound too small for digits value", Low);
15019               Low_Val := -Bound_Val;
15020            end if;
15021
15022            if High_Val > Bound_Val then
15023               Error_Msg_N
15024                 ("range high bound too large for digits value", High);
15025               High_Val := Bound_Val;
15026            end if;
15027
15028            Set_Fixed_Range (T, Loc, Low_Val, High_Val);
15029         end;
15030
15031      --  If no explicit range, use range that corresponds to given
15032      --  digits value. This will end up as the final range for the
15033      --  first subtype.
15034
15035      else
15036         Set_Fixed_Range (T, Loc, -Bound_Val, Bound_Val);
15037      end if;
15038
15039      --  Complete entity for first subtype. The inheritance of the rep item
15040      --  chain ensures that SPARK-related pragmas are not clobbered when the
15041      --  decimal fixed point type acts as a full view of a private type.
15042
15043      Set_Ekind              (T, E_Decimal_Fixed_Point_Subtype);
15044      Set_Etype              (T, Implicit_Base);
15045      Set_Size_Info          (T, Implicit_Base);
15046      Inherit_Rep_Item_Chain (T, Implicit_Base);
15047      Set_Digits_Value       (T, Digs_Val);
15048      Set_Delta_Value        (T, Delta_Val);
15049      Set_Small_Value        (T, Delta_Val);
15050      Set_Scale_Value        (T, Scale_Val);
15051      Set_Is_Constrained     (T);
15052   end Decimal_Fixed_Point_Type_Declaration;
15053
15054   -----------------------------------
15055   -- Derive_Progenitor_Subprograms --
15056   -----------------------------------
15057
15058   procedure Derive_Progenitor_Subprograms
15059     (Parent_Type : Entity_Id;
15060      Tagged_Type : Entity_Id)
15061   is
15062      E           : Entity_Id;
15063      Elmt        : Elmt_Id;
15064      Iface       : Entity_Id;
15065      Iface_Alias : Entity_Id;
15066      Iface_Elmt  : Elmt_Id;
15067      Iface_Subp  : Entity_Id;
15068      New_Subp    : Entity_Id := Empty;
15069      Prim_Elmt   : Elmt_Id;
15070      Subp        : Entity_Id;
15071      Typ         : Entity_Id;
15072
15073   begin
15074      pragma Assert (Ada_Version >= Ada_2005
15075        and then Is_Record_Type (Tagged_Type)
15076        and then Is_Tagged_Type (Tagged_Type)
15077        and then Has_Interfaces (Tagged_Type));
15078
15079      --  Step 1: Transfer to the full-view primitives associated with the
15080      --  partial-view that cover interface primitives. Conceptually this
15081      --  work should be done later by Process_Full_View; done here to
15082      --  simplify its implementation at later stages. It can be safely
15083      --  done here because interfaces must be visible in the partial and
15084      --  private view (RM 7.3(7.3/2)).
15085
15086      --  Small optimization: This work is only required if the parent may
15087      --  have entities whose Alias attribute reference an interface primitive.
15088      --  Such a situation may occur if the parent is an abstract type and the
15089      --  primitive has not been yet overridden or if the parent is a generic
15090      --  formal type covering interfaces.
15091
15092      --  If the tagged type is not abstract, it cannot have abstract
15093      --  primitives (the only entities in the list of primitives of
15094      --  non-abstract tagged types that can reference abstract primitives
15095      --  through its Alias attribute are the internal entities that have
15096      --  attribute Interface_Alias, and these entities are generated later
15097      --  by Add_Internal_Interface_Entities).
15098
15099      if In_Private_Part (Current_Scope)
15100        and then (Is_Abstract_Type (Parent_Type)
15101                    or else
15102                  Is_Generic_Type  (Parent_Type))
15103      then
15104         Elmt := First_Elmt (Primitive_Operations (Tagged_Type));
15105         while Present (Elmt) loop
15106            Subp := Node (Elmt);
15107
15108            --  At this stage it is not possible to have entities in the list
15109            --  of primitives that have attribute Interface_Alias.
15110
15111            pragma Assert (No (Interface_Alias (Subp)));
15112
15113            Typ := Find_Dispatching_Type (Ultimate_Alias (Subp));
15114
15115            if Is_Interface (Typ) then
15116               E := Find_Primitive_Covering_Interface
15117                      (Tagged_Type => Tagged_Type,
15118                       Iface_Prim  => Subp);
15119
15120               if Present (E)
15121                 and then Find_Dispatching_Type (Ultimate_Alias (E)) /= Typ
15122               then
15123                  Replace_Elmt (Elmt, E);
15124                  Remove_Homonym (Subp);
15125               end if;
15126            end if;
15127
15128            Next_Elmt (Elmt);
15129         end loop;
15130      end if;
15131
15132      --  Step 2: Add primitives of progenitors that are not implemented by
15133      --  parents of Tagged_Type.
15134
15135      if Present (Interfaces (Base_Type (Tagged_Type))) then
15136         Iface_Elmt := First_Elmt (Interfaces (Base_Type (Tagged_Type)));
15137         while Present (Iface_Elmt) loop
15138            Iface := Node (Iface_Elmt);
15139
15140            Prim_Elmt := First_Elmt (Primitive_Operations (Iface));
15141            while Present (Prim_Elmt) loop
15142               Iface_Subp  := Node (Prim_Elmt);
15143               Iface_Alias := Ultimate_Alias (Iface_Subp);
15144
15145               --  Exclude derivation of predefined primitives except those
15146               --  that come from source, or are inherited from one that comes
15147               --  from source. Required to catch declarations of equality
15148               --  operators of interfaces. For example:
15149
15150               --     type Iface is interface;
15151               --     function "=" (Left, Right : Iface) return Boolean;
15152
15153               if not Is_Predefined_Dispatching_Operation (Iface_Subp)
15154                 or else Comes_From_Source (Iface_Alias)
15155               then
15156                  E :=
15157                    Find_Primitive_Covering_Interface
15158                      (Tagged_Type => Tagged_Type,
15159                       Iface_Prim  => Iface_Subp);
15160
15161                  --  If not found we derive a new primitive leaving its alias
15162                  --  attribute referencing the interface primitive.
15163
15164                  if No (E) then
15165                     Derive_Subprogram
15166                       (New_Subp, Iface_Subp, Tagged_Type, Iface);
15167
15168                  --  Ada 2012 (AI05-0197): If the covering primitive's name
15169                  --  differs from the name of the interface primitive then it
15170                  --  is a private primitive inherited from a parent type. In
15171                  --  such case, given that Tagged_Type covers the interface,
15172                  --  the inherited private primitive becomes visible. For such
15173                  --  purpose we add a new entity that renames the inherited
15174                  --  private primitive.
15175
15176                  elsif Chars (E) /= Chars (Iface_Subp) then
15177                     pragma Assert (Has_Suffix (E, 'P'));
15178                     Derive_Subprogram
15179                       (New_Subp, Iface_Subp, Tagged_Type, Iface);
15180                     Set_Alias (New_Subp, E);
15181                     Set_Is_Abstract_Subprogram (New_Subp,
15182                       Is_Abstract_Subprogram (E));
15183
15184                  --  Propagate to the full view interface entities associated
15185                  --  with the partial view.
15186
15187                  elsif In_Private_Part (Current_Scope)
15188                    and then Present (Alias (E))
15189                    and then Alias (E) = Iface_Subp
15190                    and then
15191                      List_Containing (Parent (E)) /=
15192                        Private_Declarations
15193                          (Specification
15194                            (Unit_Declaration_Node (Current_Scope)))
15195                  then
15196                     Append_Elmt (E, Primitive_Operations (Tagged_Type));
15197                  end if;
15198               end if;
15199
15200               Next_Elmt (Prim_Elmt);
15201            end loop;
15202
15203            Next_Elmt (Iface_Elmt);
15204         end loop;
15205      end if;
15206   end Derive_Progenitor_Subprograms;
15207
15208   -----------------------
15209   -- Derive_Subprogram --
15210   -----------------------
15211
15212   procedure Derive_Subprogram
15213     (New_Subp     : out Entity_Id;
15214      Parent_Subp  : Entity_Id;
15215      Derived_Type : Entity_Id;
15216      Parent_Type  : Entity_Id;
15217      Actual_Subp  : Entity_Id := Empty)
15218   is
15219      Formal : Entity_Id;
15220      --  Formal parameter of parent primitive operation
15221
15222      Formal_Of_Actual : Entity_Id;
15223      --  Formal parameter of actual operation, when the derivation is to
15224      --  create a renaming for a primitive operation of an actual in an
15225      --  instantiation.
15226
15227      New_Formal : Entity_Id;
15228      --  Formal of inherited operation
15229
15230      Visible_Subp : Entity_Id := Parent_Subp;
15231
15232      function Is_Private_Overriding return Boolean;
15233      --  If Subp is a private overriding of a visible operation, the inherited
15234      --  operation derives from the overridden op (even though its body is the
15235      --  overriding one) and the inherited operation is visible now. See
15236      --  sem_disp to see the full details of the handling of the overridden
15237      --  subprogram, which is removed from the list of primitive operations of
15238      --  the type. The overridden subprogram is saved locally in Visible_Subp,
15239      --  and used to diagnose abstract operations that need overriding in the
15240      --  derived type.
15241
15242      procedure Replace_Type (Id, New_Id : Entity_Id);
15243      --  When the type is an anonymous access type, create a new access type
15244      --  designating the derived type.
15245
15246      procedure Set_Derived_Name;
15247      --  This procedure sets the appropriate Chars name for New_Subp. This
15248      --  is normally just a copy of the parent name. An exception arises for
15249      --  type support subprograms, where the name is changed to reflect the
15250      --  name of the derived type, e.g. if type foo is derived from type bar,
15251      --  then a procedure barDA is derived with a name fooDA.
15252
15253      ---------------------------
15254      -- Is_Private_Overriding --
15255      ---------------------------
15256
15257      function Is_Private_Overriding return Boolean is
15258         Prev : Entity_Id;
15259
15260      begin
15261         --  If the parent is not a dispatching operation there is no
15262         --  need to investigate overridings
15263
15264         if not Is_Dispatching_Operation (Parent_Subp) then
15265            return False;
15266         end if;
15267
15268         --  The visible operation that is overridden is a homonym of the
15269         --  parent subprogram. We scan the homonym chain to find the one
15270         --  whose alias is the subprogram we are deriving.
15271
15272         Prev := Current_Entity (Parent_Subp);
15273         while Present (Prev) loop
15274            if Ekind (Prev) = Ekind (Parent_Subp)
15275              and then Alias (Prev) = Parent_Subp
15276              and then Scope (Parent_Subp) = Scope (Prev)
15277              and then not Is_Hidden (Prev)
15278            then
15279               Visible_Subp := Prev;
15280               return True;
15281            end if;
15282
15283            Prev := Homonym (Prev);
15284         end loop;
15285
15286         return False;
15287      end Is_Private_Overriding;
15288
15289      ------------------
15290      -- Replace_Type --
15291      ------------------
15292
15293      procedure Replace_Type (Id, New_Id : Entity_Id) is
15294         Id_Type  : constant Entity_Id := Etype (Id);
15295         Acc_Type : Entity_Id;
15296         Par      : constant Node_Id := Parent (Derived_Type);
15297
15298      begin
15299         --  When the type is an anonymous access type, create a new access
15300         --  type designating the derived type. This itype must be elaborated
15301         --  at the point of the derivation, not on subsequent calls that may
15302         --  be out of the proper scope for Gigi, so we insert a reference to
15303         --  it after the derivation.
15304
15305         if Ekind (Id_Type) = E_Anonymous_Access_Type then
15306            declare
15307               Desig_Typ : Entity_Id := Designated_Type (Id_Type);
15308
15309            begin
15310               if Ekind (Desig_Typ) = E_Record_Type_With_Private
15311                 and then Present (Full_View (Desig_Typ))
15312                 and then not Is_Private_Type (Parent_Type)
15313               then
15314                  Desig_Typ := Full_View (Desig_Typ);
15315               end if;
15316
15317               if Base_Type (Desig_Typ) = Base_Type (Parent_Type)
15318
15319                  --  Ada 2005 (AI-251): Handle also derivations of abstract
15320                  --  interface primitives.
15321
15322                 or else (Is_Interface (Desig_Typ)
15323                           and then not Is_Class_Wide_Type (Desig_Typ))
15324               then
15325                  Acc_Type := New_Copy (Id_Type);
15326                  Set_Etype (Acc_Type, Acc_Type);
15327                  Set_Scope (Acc_Type, New_Subp);
15328
15329                  --  Set size of anonymous access type. If we have an access
15330                  --  to an unconstrained array, this is a fat pointer, so it
15331                  --  is sizes at twice addtress size.
15332
15333                  if Is_Array_Type (Desig_Typ)
15334                    and then not Is_Constrained (Desig_Typ)
15335                  then
15336                     Init_Size (Acc_Type, 2 * System_Address_Size);
15337
15338                  --  Other cases use a thin pointer
15339
15340                  else
15341                     Init_Size (Acc_Type, System_Address_Size);
15342                  end if;
15343
15344                  --  Set remaining characterstics of anonymous access type
15345
15346                  Init_Alignment (Acc_Type);
15347                  Set_Directly_Designated_Type (Acc_Type, Derived_Type);
15348
15349                  Set_Etype (New_Id, Acc_Type);
15350                  Set_Scope (New_Id, New_Subp);
15351
15352                  --  Create a reference to it
15353
15354                  Build_Itype_Reference (Acc_Type, Parent (Derived_Type));
15355
15356               else
15357                  Set_Etype (New_Id, Id_Type);
15358               end if;
15359            end;
15360
15361         --  In Ada2012, a formal may have an incomplete type but the type
15362         --  derivation that inherits the primitive follows the full view.
15363
15364         elsif Base_Type (Id_Type) = Base_Type (Parent_Type)
15365           or else
15366             (Ekind (Id_Type) = E_Record_Type_With_Private
15367               and then Present (Full_View (Id_Type))
15368               and then
15369                 Base_Type (Full_View (Id_Type)) = Base_Type (Parent_Type))
15370           or else
15371             (Ada_Version >= Ada_2012
15372               and then Ekind (Id_Type) = E_Incomplete_Type
15373               and then Full_View (Id_Type) = Parent_Type)
15374         then
15375            --  Constraint checks on formals are generated during expansion,
15376            --  based on the signature of the original subprogram. The bounds
15377            --  of the derived type are not relevant, and thus we can use
15378            --  the base type for the formals. However, the return type may be
15379            --  used in a context that requires that the proper static bounds
15380            --  be used (a case statement, for example) and for those cases
15381            --  we must use the derived type (first subtype), not its base.
15382
15383            --  If the derived_type_definition has no constraints, we know that
15384            --  the derived type has the same constraints as the first subtype
15385            --  of the parent, and we can also use it rather than its base,
15386            --  which can lead to more efficient code.
15387
15388            if Etype (Id) = Parent_Type then
15389               if Is_Scalar_Type (Parent_Type)
15390                 and then
15391                   Subtypes_Statically_Compatible (Parent_Type, Derived_Type)
15392               then
15393                  Set_Etype (New_Id, Derived_Type);
15394
15395               elsif Nkind (Par) = N_Full_Type_Declaration
15396                 and then
15397                   Nkind (Type_Definition (Par)) = N_Derived_Type_Definition
15398                 and then
15399                   Is_Entity_Name
15400                     (Subtype_Indication (Type_Definition (Par)))
15401               then
15402                  Set_Etype (New_Id, Derived_Type);
15403
15404               else
15405                  Set_Etype (New_Id, Base_Type (Derived_Type));
15406               end if;
15407
15408            else
15409               Set_Etype (New_Id, Base_Type (Derived_Type));
15410            end if;
15411
15412         else
15413            Set_Etype (New_Id, Etype (Id));
15414         end if;
15415      end Replace_Type;
15416
15417      ----------------------
15418      -- Set_Derived_Name --
15419      ----------------------
15420
15421      procedure Set_Derived_Name is
15422         Nm : constant TSS_Name_Type := Get_TSS_Name (Parent_Subp);
15423      begin
15424         if Nm = TSS_Null then
15425            Set_Chars (New_Subp, Chars (Parent_Subp));
15426         else
15427            Set_Chars (New_Subp, Make_TSS_Name (Base_Type (Derived_Type), Nm));
15428         end if;
15429      end Set_Derived_Name;
15430
15431   --  Start of processing for Derive_Subprogram
15432
15433   begin
15434      New_Subp := New_Entity (Nkind (Parent_Subp), Sloc (Derived_Type));
15435      Set_Ekind (New_Subp, Ekind (Parent_Subp));
15436
15437      --  Check whether the inherited subprogram is a private operation that
15438      --  should be inherited but not yet made visible. Such subprograms can
15439      --  become visible at a later point (e.g., the private part of a public
15440      --  child unit) via Declare_Inherited_Private_Subprograms. If the
15441      --  following predicate is true, then this is not such a private
15442      --  operation and the subprogram simply inherits the name of the parent
15443      --  subprogram. Note the special check for the names of controlled
15444      --  operations, which are currently exempted from being inherited with
15445      --  a hidden name because they must be findable for generation of
15446      --  implicit run-time calls.
15447
15448      if not Is_Hidden (Parent_Subp)
15449        or else Is_Internal (Parent_Subp)
15450        or else Is_Private_Overriding
15451        or else Is_Internal_Name (Chars (Parent_Subp))
15452        or else (Is_Controlled (Parent_Type)
15453                  and then Nam_In (Chars (Parent_Subp), Name_Adjust,
15454                                                        Name_Finalize,
15455                                                        Name_Initialize))
15456      then
15457         Set_Derived_Name;
15458
15459      --  An inherited dispatching equality will be overridden by an internally
15460      --  generated one, or by an explicit one, so preserve its name and thus
15461      --  its entry in the dispatch table. Otherwise, if Parent_Subp is a
15462      --  private operation it may become invisible if the full view has
15463      --  progenitors, and the dispatch table will be malformed.
15464      --  We check that the type is limited to handle the anomalous declaration
15465      --  of Limited_Controlled, which is derived from a non-limited type, and
15466      --  which is handled specially elsewhere as well.
15467
15468      elsif Chars (Parent_Subp) = Name_Op_Eq
15469        and then Is_Dispatching_Operation (Parent_Subp)
15470        and then Etype (Parent_Subp) = Standard_Boolean
15471        and then not Is_Limited_Type (Etype (First_Formal (Parent_Subp)))
15472        and then
15473          Etype (First_Formal (Parent_Subp)) =
15474            Etype (Next_Formal (First_Formal (Parent_Subp)))
15475      then
15476         Set_Derived_Name;
15477
15478      --  If parent is hidden, this can be a regular derivation if the
15479      --  parent is immediately visible in a non-instantiating context,
15480      --  or if we are in the private part of an instance. This test
15481      --  should still be refined ???
15482
15483      --  The test for In_Instance_Not_Visible avoids inheriting the derived
15484      --  operation as a non-visible operation in cases where the parent
15485      --  subprogram might not be visible now, but was visible within the
15486      --  original generic, so it would be wrong to make the inherited
15487      --  subprogram non-visible now. (Not clear if this test is fully
15488      --  correct; are there any cases where we should declare the inherited
15489      --  operation as not visible to avoid it being overridden, e.g., when
15490      --  the parent type is a generic actual with private primitives ???)
15491
15492      --  (they should be treated the same as other private inherited
15493      --  subprograms, but it's not clear how to do this cleanly). ???
15494
15495      elsif (In_Open_Scopes (Scope (Base_Type (Parent_Type)))
15496              and then Is_Immediately_Visible (Parent_Subp)
15497              and then not In_Instance)
15498        or else In_Instance_Not_Visible
15499      then
15500         Set_Derived_Name;
15501
15502      --  Ada 2005 (AI-251): Regular derivation if the parent subprogram
15503      --  overrides an interface primitive because interface primitives
15504      --  must be visible in the partial view of the parent (RM 7.3 (7.3/2))
15505
15506      elsif Ada_Version >= Ada_2005
15507         and then Is_Dispatching_Operation (Parent_Subp)
15508         and then Present (Covered_Interface_Op (Parent_Subp))
15509      then
15510         Set_Derived_Name;
15511
15512      --  Otherwise, the type is inheriting a private operation, so enter it
15513      --  with a special name so it can't be overridden.
15514
15515      else
15516         Set_Chars (New_Subp, New_External_Name (Chars (Parent_Subp), 'P'));
15517      end if;
15518
15519      Set_Parent (New_Subp, Parent (Derived_Type));
15520
15521      if Present (Actual_Subp) then
15522         Replace_Type (Actual_Subp, New_Subp);
15523      else
15524         Replace_Type (Parent_Subp, New_Subp);
15525      end if;
15526
15527      Conditional_Delay (New_Subp, Parent_Subp);
15528
15529      --  If we are creating a renaming for a primitive operation of an
15530      --  actual of a generic derived type, we must examine the signature
15531      --  of the actual primitive, not that of the generic formal, which for
15532      --  example may be an interface. However the name and initial value
15533      --  of the inherited operation are those of the formal primitive.
15534
15535      Formal := First_Formal (Parent_Subp);
15536
15537      if Present (Actual_Subp) then
15538         Formal_Of_Actual := First_Formal (Actual_Subp);
15539      else
15540         Formal_Of_Actual := Empty;
15541      end if;
15542
15543      while Present (Formal) loop
15544         New_Formal := New_Copy (Formal);
15545
15546         --  Normally we do not go copying parents, but in the case of
15547         --  formals, we need to link up to the declaration (which is the
15548         --  parameter specification), and it is fine to link up to the
15549         --  original formal's parameter specification in this case.
15550
15551         Set_Parent (New_Formal, Parent (Formal));
15552         Append_Entity (New_Formal, New_Subp);
15553
15554         if Present (Formal_Of_Actual) then
15555            Replace_Type (Formal_Of_Actual, New_Formal);
15556            Next_Formal (Formal_Of_Actual);
15557         else
15558            Replace_Type (Formal, New_Formal);
15559         end if;
15560
15561         Next_Formal (Formal);
15562      end loop;
15563
15564      --  If this derivation corresponds to a tagged generic actual, then
15565      --  primitive operations rename those of the actual. Otherwise the
15566      --  primitive operations rename those of the parent type, If the parent
15567      --  renames an intrinsic operator, so does the new subprogram. We except
15568      --  concatenation, which is always properly typed, and does not get
15569      --  expanded as other intrinsic operations.
15570
15571      if No (Actual_Subp) then
15572         if Is_Intrinsic_Subprogram (Parent_Subp) then
15573            Set_Is_Intrinsic_Subprogram (New_Subp);
15574
15575            if Present (Alias (Parent_Subp))
15576              and then Chars (Parent_Subp) /= Name_Op_Concat
15577            then
15578               Set_Alias (New_Subp, Alias (Parent_Subp));
15579            else
15580               Set_Alias (New_Subp, Parent_Subp);
15581            end if;
15582
15583         else
15584            Set_Alias (New_Subp, Parent_Subp);
15585         end if;
15586
15587      else
15588         Set_Alias (New_Subp, Actual_Subp);
15589      end if;
15590
15591      --  Derived subprograms of a tagged type must inherit the convention
15592      --  of the parent subprogram (a requirement of AI-117). Derived
15593      --  subprograms of untagged types simply get convention Ada by default.
15594
15595      --  If the derived type is a tagged generic formal type with unknown
15596      --  discriminants, its convention is intrinsic (RM 6.3.1 (8)).
15597
15598      --  However, if the type is derived from a generic formal, the further
15599      --  inherited subprogram has the convention of the non-generic ancestor.
15600      --  Otherwise there would be no way to override the operation.
15601      --  (This is subject to forthcoming ARG discussions).
15602
15603      if Is_Tagged_Type (Derived_Type) then
15604         if Is_Generic_Type (Derived_Type)
15605           and then Has_Unknown_Discriminants (Derived_Type)
15606         then
15607            Set_Convention (New_Subp, Convention_Intrinsic);
15608
15609         else
15610            if Is_Generic_Type (Parent_Type)
15611              and then Has_Unknown_Discriminants (Parent_Type)
15612            then
15613               Set_Convention (New_Subp, Convention (Alias (Parent_Subp)));
15614            else
15615               Set_Convention (New_Subp, Convention (Parent_Subp));
15616            end if;
15617         end if;
15618      end if;
15619
15620      --  Predefined controlled operations retain their name even if the parent
15621      --  is hidden (see above), but they are not primitive operations if the
15622      --  ancestor is not visible, for example if the parent is a private
15623      --  extension completed with a controlled extension. Note that a full
15624      --  type that is controlled can break privacy: the flag Is_Controlled is
15625      --  set on both views of the type.
15626
15627      if Is_Controlled (Parent_Type)
15628        and then Nam_In (Chars (Parent_Subp), Name_Initialize,
15629                                              Name_Adjust,
15630                                              Name_Finalize)
15631        and then Is_Hidden (Parent_Subp)
15632        and then not Is_Visibly_Controlled (Parent_Type)
15633      then
15634         Set_Is_Hidden (New_Subp);
15635      end if;
15636
15637      Set_Is_Imported (New_Subp, Is_Imported (Parent_Subp));
15638      Set_Is_Exported (New_Subp, Is_Exported (Parent_Subp));
15639
15640      if Ekind (Parent_Subp) = E_Procedure then
15641         Set_Is_Valued_Procedure
15642           (New_Subp, Is_Valued_Procedure (Parent_Subp));
15643      else
15644         Set_Has_Controlling_Result
15645           (New_Subp, Has_Controlling_Result (Parent_Subp));
15646      end if;
15647
15648      --  No_Return must be inherited properly. If this is overridden in the
15649      --  case of a dispatching operation, then a check is made in Sem_Disp
15650      --  that the overriding operation is also No_Return (no such check is
15651      --  required for the case of non-dispatching operation.
15652
15653      Set_No_Return (New_Subp, No_Return (Parent_Subp));
15654
15655      --  A derived function with a controlling result is abstract. If the
15656      --  Derived_Type is a nonabstract formal generic derived type, then
15657      --  inherited operations are not abstract: the required check is done at
15658      --  instantiation time. If the derivation is for a generic actual, the
15659      --  function is not abstract unless the actual is.
15660
15661      if Is_Generic_Type (Derived_Type)
15662        and then not Is_Abstract_Type (Derived_Type)
15663      then
15664         null;
15665
15666      --  Ada 2005 (AI-228): Calculate the "require overriding" and "abstract"
15667      --  properties of the subprogram, as defined in RM-3.9.3(4/2-6/2).
15668
15669      --  A subprogram subject to pragma Extensions_Visible with value False
15670      --  requires overriding if the subprogram has at least one controlling
15671      --  OUT parameter (SPARK RM 6.1.7(6)).
15672
15673      elsif Ada_Version >= Ada_2005
15674        and then (Is_Abstract_Subprogram (Alias (New_Subp))
15675                   or else (Is_Tagged_Type (Derived_Type)
15676                             and then Etype (New_Subp) = Derived_Type
15677                             and then not Is_Null_Extension (Derived_Type))
15678                   or else (Is_Tagged_Type (Derived_Type)
15679                             and then Ekind (Etype (New_Subp)) =
15680                                                       E_Anonymous_Access_Type
15681                             and then Designated_Type (Etype (New_Subp)) =
15682                                                        Derived_Type
15683                             and then not Is_Null_Extension (Derived_Type))
15684                   or else (Comes_From_Source (Alias (New_Subp))
15685                             and then Is_EVF_Procedure (Alias (New_Subp))))
15686        and then No (Actual_Subp)
15687      then
15688         if not Is_Tagged_Type (Derived_Type)
15689           or else Is_Abstract_Type (Derived_Type)
15690           or else Is_Abstract_Subprogram (Alias (New_Subp))
15691         then
15692            Set_Is_Abstract_Subprogram (New_Subp);
15693         else
15694            Set_Requires_Overriding (New_Subp);
15695         end if;
15696
15697      elsif Ada_Version < Ada_2005
15698        and then (Is_Abstract_Subprogram (Alias (New_Subp))
15699                   or else (Is_Tagged_Type (Derived_Type)
15700                             and then Etype (New_Subp) = Derived_Type
15701                             and then No (Actual_Subp)))
15702      then
15703         Set_Is_Abstract_Subprogram (New_Subp);
15704
15705      --  AI05-0097 : an inherited operation that dispatches on result is
15706      --  abstract if the derived type is abstract, even if the parent type
15707      --  is concrete and the derived type is a null extension.
15708
15709      elsif Has_Controlling_Result (Alias (New_Subp))
15710        and then Is_Abstract_Type (Etype (New_Subp))
15711      then
15712         Set_Is_Abstract_Subprogram (New_Subp);
15713
15714      --  Finally, if the parent type is abstract we must verify that all
15715      --  inherited operations are either non-abstract or overridden, or that
15716      --  the derived type itself is abstract (this check is performed at the
15717      --  end of a package declaration, in Check_Abstract_Overriding). A
15718      --  private overriding in the parent type will not be visible in the
15719      --  derivation if we are not in an inner package or in a child unit of
15720      --  the parent type, in which case the abstractness of the inherited
15721      --  operation is carried to the new subprogram.
15722
15723      elsif Is_Abstract_Type (Parent_Type)
15724        and then not In_Open_Scopes (Scope (Parent_Type))
15725        and then Is_Private_Overriding
15726        and then Is_Abstract_Subprogram (Visible_Subp)
15727      then
15728         if No (Actual_Subp) then
15729            Set_Alias (New_Subp, Visible_Subp);
15730            Set_Is_Abstract_Subprogram (New_Subp, True);
15731
15732         else
15733            --  If this is a derivation for an instance of a formal derived
15734            --  type, abstractness comes from the primitive operation of the
15735            --  actual, not from the operation inherited from the ancestor.
15736
15737            Set_Is_Abstract_Subprogram
15738              (New_Subp, Is_Abstract_Subprogram (Actual_Subp));
15739         end if;
15740      end if;
15741
15742      New_Overloaded_Entity (New_Subp, Derived_Type);
15743
15744      --  Ada RM 6.1.1 (15): If a subprogram inherits nonconforming class-wide
15745      --  preconditions and the derived type is abstract, the derived operation
15746      --  is abstract as well if parent subprogram is not abstract or null.
15747
15748      if Is_Abstract_Type (Derived_Type)
15749        and then Has_Non_Trivial_Precondition (Parent_Subp)
15750        and then Present (Interfaces (Derived_Type))
15751      then
15752
15753         --  Add useful attributes of subprogram before the freeze point,
15754         --  in case freezing is delayed or there are previous errors.
15755
15756         Set_Is_Dispatching_Operation (New_Subp);
15757
15758         declare
15759            Iface_Prim : constant Entity_Id := Covered_Interface_Op (New_Subp);
15760
15761         begin
15762            if Present (Iface_Prim)
15763              and then Has_Non_Trivial_Precondition (Iface_Prim)
15764            then
15765               Set_Is_Abstract_Subprogram (New_Subp);
15766            end if;
15767         end;
15768      end if;
15769
15770      --  Check for case of a derived subprogram for the instantiation of a
15771      --  formal derived tagged type, if so mark the subprogram as dispatching
15772      --  and inherit the dispatching attributes of the actual subprogram. The
15773      --  derived subprogram is effectively renaming of the actual subprogram,
15774      --  so it needs to have the same attributes as the actual.
15775
15776      if Present (Actual_Subp)
15777        and then Is_Dispatching_Operation (Actual_Subp)
15778      then
15779         Set_Is_Dispatching_Operation (New_Subp);
15780
15781         if Present (DTC_Entity (Actual_Subp)) then
15782            Set_DTC_Entity (New_Subp, DTC_Entity (Actual_Subp));
15783            Set_DT_Position_Value (New_Subp, DT_Position (Actual_Subp));
15784         end if;
15785      end if;
15786
15787      --  Indicate that a derived subprogram does not require a body and that
15788      --  it does not require processing of default expressions.
15789
15790      Set_Has_Completion (New_Subp);
15791      Set_Default_Expressions_Processed (New_Subp);
15792
15793      if Ekind (New_Subp) = E_Function then
15794         Set_Mechanism (New_Subp, Mechanism (Parent_Subp));
15795      end if;
15796   end Derive_Subprogram;
15797
15798   ------------------------
15799   -- Derive_Subprograms --
15800   ------------------------
15801
15802   procedure Derive_Subprograms
15803     (Parent_Type    : Entity_Id;
15804      Derived_Type   : Entity_Id;
15805      Generic_Actual : Entity_Id := Empty)
15806   is
15807      Op_List : constant Elist_Id :=
15808                  Collect_Primitive_Operations (Parent_Type);
15809
15810      function Check_Derived_Type return Boolean;
15811      --  Check that all the entities derived from Parent_Type are found in
15812      --  the list of primitives of Derived_Type exactly in the same order.
15813
15814      procedure Derive_Interface_Subprogram
15815        (New_Subp    : out Entity_Id;
15816         Subp        : Entity_Id;
15817         Actual_Subp : Entity_Id);
15818      --  Derive New_Subp from the ultimate alias of the parent subprogram Subp
15819      --  (which is an interface primitive). If Generic_Actual is present then
15820      --  Actual_Subp is the actual subprogram corresponding with the generic
15821      --  subprogram Subp.
15822
15823      ------------------------
15824      -- Check_Derived_Type --
15825      ------------------------
15826
15827      function Check_Derived_Type return Boolean is
15828         E        : Entity_Id;
15829         Elmt     : Elmt_Id;
15830         List     : Elist_Id;
15831         New_Subp : Entity_Id;
15832         Op_Elmt  : Elmt_Id;
15833         Subp     : Entity_Id;
15834
15835      begin
15836         --  Traverse list of entities in the current scope searching for
15837         --  an incomplete type whose full-view is derived type.
15838
15839         E := First_Entity (Scope (Derived_Type));
15840         while Present (E) and then E /= Derived_Type loop
15841            if Ekind (E) = E_Incomplete_Type
15842              and then Present (Full_View (E))
15843              and then Full_View (E) = Derived_Type
15844            then
15845               --  Disable this test if Derived_Type completes an incomplete
15846               --  type because in such case more primitives can be added
15847               --  later to the list of primitives of Derived_Type by routine
15848               --  Process_Incomplete_Dependents
15849
15850               return True;
15851            end if;
15852
15853            E := Next_Entity (E);
15854         end loop;
15855
15856         List := Collect_Primitive_Operations (Derived_Type);
15857         Elmt := First_Elmt (List);
15858
15859         Op_Elmt := First_Elmt (Op_List);
15860         while Present (Op_Elmt) loop
15861            Subp     := Node (Op_Elmt);
15862            New_Subp := Node (Elmt);
15863
15864            --  At this early stage Derived_Type has no entities with attribute
15865            --  Interface_Alias. In addition, such primitives are always
15866            --  located at the end of the list of primitives of Parent_Type.
15867            --  Therefore, if found we can safely stop processing pending
15868            --  entities.
15869
15870            exit when Present (Interface_Alias (Subp));
15871
15872            --  Handle hidden entities
15873
15874            if not Is_Predefined_Dispatching_Operation (Subp)
15875              and then Is_Hidden (Subp)
15876            then
15877               if Present (New_Subp)
15878                 and then Primitive_Names_Match (Subp, New_Subp)
15879               then
15880                  Next_Elmt (Elmt);
15881               end if;
15882
15883            else
15884               if not Present (New_Subp)
15885                 or else Ekind (Subp) /= Ekind (New_Subp)
15886                 or else not Primitive_Names_Match (Subp, New_Subp)
15887               then
15888                  return False;
15889               end if;
15890
15891               Next_Elmt (Elmt);
15892            end if;
15893
15894            Next_Elmt (Op_Elmt);
15895         end loop;
15896
15897         return True;
15898      end Check_Derived_Type;
15899
15900      ---------------------------------
15901      -- Derive_Interface_Subprogram --
15902      ---------------------------------
15903
15904      procedure Derive_Interface_Subprogram
15905        (New_Subp    : out Entity_Id;
15906         Subp        : Entity_Id;
15907         Actual_Subp : Entity_Id)
15908      is
15909         Iface_Subp : constant Entity_Id := Ultimate_Alias (Subp);
15910         Iface_Type : constant Entity_Id := Find_Dispatching_Type (Iface_Subp);
15911
15912      begin
15913         pragma Assert (Is_Interface (Iface_Type));
15914
15915         Derive_Subprogram
15916           (New_Subp     => New_Subp,
15917            Parent_Subp  => Iface_Subp,
15918            Derived_Type => Derived_Type,
15919            Parent_Type  => Iface_Type,
15920            Actual_Subp  => Actual_Subp);
15921
15922         --  Given that this new interface entity corresponds with a primitive
15923         --  of the parent that was not overridden we must leave it associated
15924         --  with its parent primitive to ensure that it will share the same
15925         --  dispatch table slot when overridden. We must set the Alias to Subp
15926         --  (instead of Iface_Subp), and we must fix Is_Abstract_Subprogram
15927         --  (in case we inherited Subp from Iface_Type via a nonabstract
15928         --  generic formal type).
15929
15930         if No (Actual_Subp) then
15931            Set_Alias (New_Subp, Subp);
15932
15933            declare
15934               T : Entity_Id := Find_Dispatching_Type (Subp);
15935            begin
15936               while Etype (T) /= T loop
15937                  if Is_Generic_Type (T) and then not Is_Abstract_Type (T) then
15938                     Set_Is_Abstract_Subprogram (New_Subp, False);
15939                     exit;
15940                  end if;
15941
15942                  T := Etype (T);
15943               end loop;
15944            end;
15945
15946         --  For instantiations this is not needed since the previous call to
15947         --  Derive_Subprogram leaves the entity well decorated.
15948
15949         else
15950            pragma Assert (Alias (New_Subp) = Actual_Subp);
15951            null;
15952         end if;
15953      end Derive_Interface_Subprogram;
15954
15955      --  Local variables
15956
15957      Alias_Subp   : Entity_Id;
15958      Act_List     : Elist_Id;
15959      Act_Elmt     : Elmt_Id;
15960      Act_Subp     : Entity_Id := Empty;
15961      Elmt         : Elmt_Id;
15962      Need_Search  : Boolean   := False;
15963      New_Subp     : Entity_Id := Empty;
15964      Parent_Base  : Entity_Id;
15965      Subp         : Entity_Id;
15966
15967   --  Start of processing for Derive_Subprograms
15968
15969   begin
15970      if Ekind (Parent_Type) = E_Record_Type_With_Private
15971        and then Has_Discriminants (Parent_Type)
15972        and then Present (Full_View (Parent_Type))
15973      then
15974         Parent_Base := Full_View (Parent_Type);
15975      else
15976         Parent_Base := Parent_Type;
15977      end if;
15978
15979      if Present (Generic_Actual) then
15980         Act_List := Collect_Primitive_Operations (Generic_Actual);
15981         Act_Elmt := First_Elmt (Act_List);
15982      else
15983         Act_List := No_Elist;
15984         Act_Elmt := No_Elmt;
15985      end if;
15986
15987      --  Derive primitives inherited from the parent. Note that if the generic
15988      --  actual is present, this is not really a type derivation, it is a
15989      --  completion within an instance.
15990
15991      --  Case 1: Derived_Type does not implement interfaces
15992
15993      if not Is_Tagged_Type (Derived_Type)
15994        or else (not Has_Interfaces (Derived_Type)
15995                  and then not (Present (Generic_Actual)
15996                                 and then Has_Interfaces (Generic_Actual)))
15997      then
15998         Elmt := First_Elmt (Op_List);
15999         while Present (Elmt) loop
16000            Subp := Node (Elmt);
16001
16002            --  Literals are derived earlier in the process of building the
16003            --  derived type, and are skipped here.
16004
16005            if Ekind (Subp) = E_Enumeration_Literal then
16006               null;
16007
16008            --  The actual is a direct descendant and the common primitive
16009            --  operations appear in the same order.
16010
16011            --  If the generic parent type is present, the derived type is an
16012            --  instance of a formal derived type, and within the instance its
16013            --  operations are those of the actual. We derive from the formal
16014            --  type but make the inherited operations aliases of the
16015            --  corresponding operations of the actual.
16016
16017            else
16018               pragma Assert (No (Node (Act_Elmt))
16019                 or else (Primitive_Names_Match (Subp, Node (Act_Elmt))
16020                           and then
16021                             Type_Conformant
16022                               (Subp, Node (Act_Elmt),
16023                                Skip_Controlling_Formals => True)));
16024
16025               Derive_Subprogram
16026                 (New_Subp, Subp, Derived_Type, Parent_Base, Node (Act_Elmt));
16027
16028               if Present (Act_Elmt) then
16029                  Next_Elmt (Act_Elmt);
16030               end if;
16031            end if;
16032
16033            Next_Elmt (Elmt);
16034         end loop;
16035
16036      --  Case 2: Derived_Type implements interfaces
16037
16038      else
16039         --  If the parent type has no predefined primitives we remove
16040         --  predefined primitives from the list of primitives of generic
16041         --  actual to simplify the complexity of this algorithm.
16042
16043         if Present (Generic_Actual) then
16044            declare
16045               Has_Predefined_Primitives : Boolean := False;
16046
16047            begin
16048               --  Check if the parent type has predefined primitives
16049
16050               Elmt := First_Elmt (Op_List);
16051               while Present (Elmt) loop
16052                  Subp := Node (Elmt);
16053
16054                  if Is_Predefined_Dispatching_Operation (Subp)
16055                    and then not Comes_From_Source (Ultimate_Alias (Subp))
16056                  then
16057                     Has_Predefined_Primitives := True;
16058                     exit;
16059                  end if;
16060
16061                  Next_Elmt (Elmt);
16062               end loop;
16063
16064               --  Remove predefined primitives of Generic_Actual. We must use
16065               --  an auxiliary list because in case of tagged types the value
16066               --  returned by Collect_Primitive_Operations is the value stored
16067               --  in its Primitive_Operations attribute (and we don't want to
16068               --  modify its current contents).
16069
16070               if not Has_Predefined_Primitives then
16071                  declare
16072                     Aux_List : constant Elist_Id := New_Elmt_List;
16073
16074                  begin
16075                     Elmt := First_Elmt (Act_List);
16076                     while Present (Elmt) loop
16077                        Subp := Node (Elmt);
16078
16079                        if not Is_Predefined_Dispatching_Operation (Subp)
16080                          or else Comes_From_Source (Subp)
16081                        then
16082                           Append_Elmt (Subp, Aux_List);
16083                        end if;
16084
16085                        Next_Elmt (Elmt);
16086                     end loop;
16087
16088                     Act_List := Aux_List;
16089                  end;
16090               end if;
16091
16092               Act_Elmt := First_Elmt (Act_List);
16093               Act_Subp := Node (Act_Elmt);
16094            end;
16095         end if;
16096
16097         --  Stage 1: If the generic actual is not present we derive the
16098         --  primitives inherited from the parent type. If the generic parent
16099         --  type is present, the derived type is an instance of a formal
16100         --  derived type, and within the instance its operations are those of
16101         --  the actual. We derive from the formal type but make the inherited
16102         --  operations aliases of the corresponding operations of the actual.
16103
16104         Elmt := First_Elmt (Op_List);
16105         while Present (Elmt) loop
16106            Subp       := Node (Elmt);
16107            Alias_Subp := Ultimate_Alias (Subp);
16108
16109            --  Do not derive internal entities of the parent that link
16110            --  interface primitives with their covering primitive. These
16111            --  entities will be added to this type when frozen.
16112
16113            if Present (Interface_Alias (Subp)) then
16114               goto Continue;
16115            end if;
16116
16117            --  If the generic actual is present find the corresponding
16118            --  operation in the generic actual. If the parent type is a
16119            --  direct ancestor of the derived type then, even if it is an
16120            --  interface, the operations are inherited from the primary
16121            --  dispatch table and are in the proper order. If we detect here
16122            --  that primitives are not in the same order we traverse the list
16123            --  of primitive operations of the actual to find the one that
16124            --  implements the interface primitive.
16125
16126            if Need_Search
16127              or else
16128                (Present (Generic_Actual)
16129                  and then Present (Act_Subp)
16130                  and then not
16131                    (Primitive_Names_Match (Subp, Act_Subp)
16132                       and then
16133                     Type_Conformant (Subp, Act_Subp,
16134                                      Skip_Controlling_Formals => True)))
16135            then
16136               pragma Assert (not Is_Ancestor (Parent_Base, Generic_Actual,
16137                                               Use_Full_View => True));
16138
16139               --  Remember that we need searching for all pending primitives
16140
16141               Need_Search := True;
16142
16143               --  Handle entities associated with interface primitives
16144
16145               if Present (Alias_Subp)
16146                 and then Is_Interface (Find_Dispatching_Type (Alias_Subp))
16147                 and then not Is_Predefined_Dispatching_Operation (Subp)
16148               then
16149                  --  Search for the primitive in the homonym chain
16150
16151                  Act_Subp :=
16152                    Find_Primitive_Covering_Interface
16153                      (Tagged_Type => Generic_Actual,
16154                       Iface_Prim  => Alias_Subp);
16155
16156                  --  Previous search may not locate primitives covering
16157                  --  interfaces defined in generics units or instantiations.
16158                  --  (it fails if the covering primitive has formals whose
16159                  --  type is also defined in generics or instantiations).
16160                  --  In such case we search in the list of primitives of the
16161                  --  generic actual for the internal entity that links the
16162                  --  interface primitive and the covering primitive.
16163
16164                  if No (Act_Subp)
16165                    and then Is_Generic_Type (Parent_Type)
16166                  then
16167                     --  This code has been designed to handle only generic
16168                     --  formals that implement interfaces that are defined
16169                     --  in a generic unit or instantiation. If this code is
16170                     --  needed for other cases we must review it because
16171                     --  (given that it relies on Original_Location to locate
16172                     --  the primitive of Generic_Actual that covers the
16173                     --  interface) it could leave linked through attribute
16174                     --  Alias entities of unrelated instantiations).
16175
16176                     pragma Assert
16177                       (Is_Generic_Unit
16178                          (Scope (Find_Dispatching_Type (Alias_Subp)))
16179                         or else
16180                           Instantiation_Depth
16181                             (Sloc (Find_Dispatching_Type (Alias_Subp))) > 0);
16182
16183                     declare
16184                        Iface_Prim_Loc : constant Source_Ptr :=
16185                                         Original_Location (Sloc (Alias_Subp));
16186
16187                        Elmt : Elmt_Id;
16188                        Prim : Entity_Id;
16189
16190                     begin
16191                        Elmt :=
16192                          First_Elmt (Primitive_Operations (Generic_Actual));
16193
16194                        Search : while Present (Elmt) loop
16195                           Prim := Node (Elmt);
16196
16197                           if Present (Interface_Alias (Prim))
16198                             and then Original_Location
16199                                        (Sloc (Interface_Alias (Prim))) =
16200                                                              Iface_Prim_Loc
16201                           then
16202                              Act_Subp := Alias (Prim);
16203                              exit Search;
16204                           end if;
16205
16206                           Next_Elmt (Elmt);
16207                        end loop Search;
16208                     end;
16209                  end if;
16210
16211                  pragma Assert (Present (Act_Subp)
16212                    or else Is_Abstract_Type (Generic_Actual)
16213                    or else Serious_Errors_Detected > 0);
16214
16215               --  Handle predefined primitives plus the rest of user-defined
16216               --  primitives
16217
16218               else
16219                  Act_Elmt := First_Elmt (Act_List);
16220                  while Present (Act_Elmt) loop
16221                     Act_Subp := Node (Act_Elmt);
16222
16223                     exit when Primitive_Names_Match (Subp, Act_Subp)
16224                       and then Type_Conformant
16225                                  (Subp, Act_Subp,
16226                                   Skip_Controlling_Formals => True)
16227                       and then No (Interface_Alias (Act_Subp));
16228
16229                     Next_Elmt (Act_Elmt);
16230                  end loop;
16231
16232                  if No (Act_Elmt) then
16233                     Act_Subp := Empty;
16234                  end if;
16235               end if;
16236            end if;
16237
16238            --   Case 1: If the parent is a limited interface then it has the
16239            --   predefined primitives of synchronized interfaces. However, the
16240            --   actual type may be a non-limited type and hence it does not
16241            --   have such primitives.
16242
16243            if Present (Generic_Actual)
16244              and then not Present (Act_Subp)
16245              and then Is_Limited_Interface (Parent_Base)
16246              and then Is_Predefined_Interface_Primitive (Subp)
16247            then
16248               null;
16249
16250            --  Case 2: Inherit entities associated with interfaces that were
16251            --  not covered by the parent type. We exclude here null interface
16252            --  primitives because they do not need special management.
16253
16254            --  We also exclude interface operations that are renamings. If the
16255            --  subprogram is an explicit renaming of an interface primitive,
16256            --  it is a regular primitive operation, and the presence of its
16257            --  alias is not relevant: it has to be derived like any other
16258            --  primitive.
16259
16260            elsif Present (Alias (Subp))
16261              and then Nkind (Unit_Declaration_Node (Subp)) /=
16262                                            N_Subprogram_Renaming_Declaration
16263              and then Is_Interface (Find_Dispatching_Type (Alias_Subp))
16264              and then not
16265                (Nkind (Parent (Alias_Subp)) = N_Procedure_Specification
16266                  and then Null_Present (Parent (Alias_Subp)))
16267            then
16268               --  If this is an abstract private type then we transfer the
16269               --  derivation of the interface primitive from the partial view
16270               --  to the full view. This is safe because all the interfaces
16271               --  must be visible in the partial view. Done to avoid adding
16272               --  a new interface derivation to the private part of the
16273               --  enclosing package; otherwise this new derivation would be
16274               --  decorated as hidden when the analysis of the enclosing
16275               --  package completes.
16276
16277               if Is_Abstract_Type (Derived_Type)
16278                 and then In_Private_Part (Current_Scope)
16279                 and then Has_Private_Declaration (Derived_Type)
16280               then
16281                  declare
16282                     Partial_View : Entity_Id;
16283                     Elmt         : Elmt_Id;
16284                     Ent          : Entity_Id;
16285
16286                  begin
16287                     Partial_View := First_Entity (Current_Scope);
16288                     loop
16289                        exit when No (Partial_View)
16290                          or else (Has_Private_Declaration (Partial_View)
16291                                    and then
16292                                      Full_View (Partial_View) = Derived_Type);
16293
16294                        Next_Entity (Partial_View);
16295                     end loop;
16296
16297                     --  If the partial view was not found then the source code
16298                     --  has errors and the derivation is not needed.
16299
16300                     if Present (Partial_View) then
16301                        Elmt :=
16302                          First_Elmt (Primitive_Operations (Partial_View));
16303                        while Present (Elmt) loop
16304                           Ent := Node (Elmt);
16305
16306                           if Present (Alias (Ent))
16307                             and then Ultimate_Alias (Ent) = Alias (Subp)
16308                           then
16309                              Append_Elmt
16310                                (Ent, Primitive_Operations (Derived_Type));
16311                              exit;
16312                           end if;
16313
16314                           Next_Elmt (Elmt);
16315                        end loop;
16316
16317                        --  If the interface primitive was not found in the
16318                        --  partial view then this interface primitive was
16319                        --  overridden. We add a derivation to activate in
16320                        --  Derive_Progenitor_Subprograms the machinery to
16321                        --  search for it.
16322
16323                        if No (Elmt) then
16324                           Derive_Interface_Subprogram
16325                             (New_Subp    => New_Subp,
16326                              Subp        => Subp,
16327                              Actual_Subp => Act_Subp);
16328                        end if;
16329                     end if;
16330                  end;
16331               else
16332                  Derive_Interface_Subprogram
16333                    (New_Subp     => New_Subp,
16334                     Subp         => Subp,
16335                     Actual_Subp  => Act_Subp);
16336               end if;
16337
16338            --  Case 3: Common derivation
16339
16340            else
16341               Derive_Subprogram
16342                 (New_Subp     => New_Subp,
16343                  Parent_Subp  => Subp,
16344                  Derived_Type => Derived_Type,
16345                  Parent_Type  => Parent_Base,
16346                  Actual_Subp  => Act_Subp);
16347            end if;
16348
16349            --  No need to update Act_Elm if we must search for the
16350            --  corresponding operation in the generic actual
16351
16352            if not Need_Search
16353              and then Present (Act_Elmt)
16354            then
16355               Next_Elmt (Act_Elmt);
16356               Act_Subp := Node (Act_Elmt);
16357            end if;
16358
16359            <<Continue>>
16360            Next_Elmt (Elmt);
16361         end loop;
16362
16363         --  Inherit additional operations from progenitors. If the derived
16364         --  type is a generic actual, there are not new primitive operations
16365         --  for the type because it has those of the actual, and therefore
16366         --  nothing needs to be done. The renamings generated above are not
16367         --  primitive operations, and their purpose is simply to make the
16368         --  proper operations visible within an instantiation.
16369
16370         if No (Generic_Actual) then
16371            Derive_Progenitor_Subprograms (Parent_Base, Derived_Type);
16372         end if;
16373      end if;
16374
16375      --  Final check: Direct descendants must have their primitives in the
16376      --  same order. We exclude from this test untagged types and instances
16377      --  of formal derived types. We skip this test if we have already
16378      --  reported serious errors in the sources.
16379
16380      pragma Assert (not Is_Tagged_Type (Derived_Type)
16381        or else Present (Generic_Actual)
16382        or else Serious_Errors_Detected > 0
16383        or else Check_Derived_Type);
16384   end Derive_Subprograms;
16385
16386   --------------------------------
16387   -- Derived_Standard_Character --
16388   --------------------------------
16389
16390   procedure Derived_Standard_Character
16391     (N            : Node_Id;
16392      Parent_Type  : Entity_Id;
16393      Derived_Type : Entity_Id)
16394   is
16395      Loc           : constant Source_Ptr := Sloc (N);
16396      Def           : constant Node_Id    := Type_Definition (N);
16397      Indic         : constant Node_Id    := Subtype_Indication (Def);
16398      Parent_Base   : constant Entity_Id  := Base_Type (Parent_Type);
16399      Implicit_Base : constant Entity_Id  :=
16400                        Create_Itype
16401                          (E_Enumeration_Type, N, Derived_Type, 'B');
16402
16403      Lo : Node_Id;
16404      Hi : Node_Id;
16405
16406   begin
16407      Discard_Node (Process_Subtype (Indic, N));
16408
16409      Set_Etype     (Implicit_Base, Parent_Base);
16410      Set_Size_Info (Implicit_Base, Root_Type (Parent_Type));
16411      Set_RM_Size   (Implicit_Base, RM_Size (Root_Type (Parent_Type)));
16412
16413      Set_Is_Character_Type  (Implicit_Base, True);
16414      Set_Has_Delayed_Freeze (Implicit_Base);
16415
16416      --  The bounds of the implicit base are the bounds of the parent base.
16417      --  Note that their type is the parent base.
16418
16419      Lo := New_Copy_Tree (Type_Low_Bound  (Parent_Base));
16420      Hi := New_Copy_Tree (Type_High_Bound (Parent_Base));
16421
16422      Set_Scalar_Range (Implicit_Base,
16423        Make_Range (Loc,
16424          Low_Bound  => Lo,
16425          High_Bound => Hi));
16426
16427      Conditional_Delay (Derived_Type, Parent_Type);
16428
16429      Set_Ekind (Derived_Type, E_Enumeration_Subtype);
16430      Set_Etype (Derived_Type, Implicit_Base);
16431      Set_Size_Info         (Derived_Type, Parent_Type);
16432
16433      if Unknown_RM_Size (Derived_Type) then
16434         Set_RM_Size (Derived_Type, RM_Size (Parent_Type));
16435      end if;
16436
16437      Set_Is_Character_Type (Derived_Type, True);
16438
16439      if Nkind (Indic) /= N_Subtype_Indication then
16440
16441         --  If no explicit constraint, the bounds are those
16442         --  of the parent type.
16443
16444         Lo := New_Copy_Tree (Type_Low_Bound  (Parent_Type));
16445         Hi := New_Copy_Tree (Type_High_Bound (Parent_Type));
16446         Set_Scalar_Range (Derived_Type, Make_Range (Loc, Lo, Hi));
16447      end if;
16448
16449      Convert_Scalar_Bounds (N, Parent_Type, Derived_Type, Loc);
16450
16451      --  Because the implicit base is used in the conversion of the bounds, we
16452      --  have to freeze it now. This is similar to what is done for numeric
16453      --  types, and it equally suspicious, but otherwise a nonstatic bound
16454      --  will have a reference to an unfrozen type, which is rejected by Gigi
16455      --  (???). This requires specific care for definition of stream
16456      --  attributes. For details, see comments at the end of
16457      --  Build_Derived_Numeric_Type.
16458
16459      Freeze_Before (N, Implicit_Base);
16460   end Derived_Standard_Character;
16461
16462   ------------------------------
16463   -- Derived_Type_Declaration --
16464   ------------------------------
16465
16466   procedure Derived_Type_Declaration
16467     (T             : Entity_Id;
16468      N             : Node_Id;
16469      Is_Completion : Boolean)
16470   is
16471      Parent_Type  : Entity_Id;
16472
16473      function Comes_From_Generic (Typ : Entity_Id) return Boolean;
16474      --  Check whether the parent type is a generic formal, or derives
16475      --  directly or indirectly from one.
16476
16477      ------------------------
16478      -- Comes_From_Generic --
16479      ------------------------
16480
16481      function Comes_From_Generic (Typ : Entity_Id) return Boolean is
16482      begin
16483         if Is_Generic_Type (Typ) then
16484            return True;
16485
16486         elsif Is_Generic_Type (Root_Type (Parent_Type)) then
16487            return True;
16488
16489         elsif Is_Private_Type (Typ)
16490           and then Present (Full_View (Typ))
16491           and then Is_Generic_Type (Root_Type (Full_View (Typ)))
16492         then
16493            return True;
16494
16495         elsif Is_Generic_Actual_Type (Typ) then
16496            return True;
16497
16498         else
16499            return False;
16500         end if;
16501      end Comes_From_Generic;
16502
16503      --  Local variables
16504
16505      Def          : constant Node_Id := Type_Definition (N);
16506      Iface_Def    : Node_Id;
16507      Indic        : constant Node_Id := Subtype_Indication (Def);
16508      Extension    : constant Node_Id := Record_Extension_Part (Def);
16509      Parent_Node  : Node_Id;
16510      Taggd        : Boolean;
16511
16512   --  Start of processing for Derived_Type_Declaration
16513
16514   begin
16515      Parent_Type := Find_Type_Of_Subtype_Indic (Indic);
16516
16517      if SPARK_Mode = On
16518        and then Is_Tagged_Type (Parent_Type)
16519      then
16520         declare
16521            Partial_View : constant Entity_Id :=
16522                             Incomplete_Or_Partial_View (Parent_Type);
16523
16524         begin
16525            --  If the partial view was not found then the parent type is not
16526            --  a private type. Otherwise check if the partial view is a tagged
16527            --  private type.
16528
16529            if Present (Partial_View)
16530              and then Is_Private_Type (Partial_View)
16531              and then not Is_Tagged_Type (Partial_View)
16532            then
16533               Error_Msg_NE
16534                 ("cannot derive from & declared as untagged private "
16535                  & "(SPARK RM 3.4(1))", N, Partial_View);
16536            end if;
16537         end;
16538      end if;
16539
16540      --  Ada 2005 (AI-251): In case of interface derivation check that the
16541      --  parent is also an interface.
16542
16543      if Interface_Present (Def) then
16544         Check_SPARK_05_Restriction ("interface is not allowed", Def);
16545
16546         if not Is_Interface (Parent_Type) then
16547            Diagnose_Interface (Indic, Parent_Type);
16548
16549         else
16550            Parent_Node := Parent (Base_Type (Parent_Type));
16551            Iface_Def   := Type_Definition (Parent_Node);
16552
16553            --  Ada 2005 (AI-251): Limited interfaces can only inherit from
16554            --  other limited interfaces.
16555
16556            if Limited_Present (Def) then
16557               if Limited_Present (Iface_Def) then
16558                  null;
16559
16560               elsif Protected_Present (Iface_Def) then
16561                  Error_Msg_NE
16562                    ("descendant of & must be declared as a protected "
16563                     & "interface", N, Parent_Type);
16564
16565               elsif Synchronized_Present (Iface_Def) then
16566                  Error_Msg_NE
16567                    ("descendant of & must be declared as a synchronized "
16568                     & "interface", N, Parent_Type);
16569
16570               elsif Task_Present (Iface_Def) then
16571                  Error_Msg_NE
16572                    ("descendant of & must be declared as a task interface",
16573                       N, Parent_Type);
16574
16575               else
16576                  Error_Msg_N
16577                    ("(Ada 2005) limited interface cannot inherit from "
16578                     & "non-limited interface", Indic);
16579               end if;
16580
16581            --  Ada 2005 (AI-345): Non-limited interfaces can only inherit
16582            --  from non-limited or limited interfaces.
16583
16584            elsif not Protected_Present (Def)
16585              and then not Synchronized_Present (Def)
16586              and then not Task_Present (Def)
16587            then
16588               if Limited_Present (Iface_Def) then
16589                  null;
16590
16591               elsif Protected_Present (Iface_Def) then
16592                  Error_Msg_NE
16593                    ("descendant of & must be declared as a protected "
16594                     & "interface", N, Parent_Type);
16595
16596               elsif Synchronized_Present (Iface_Def) then
16597                  Error_Msg_NE
16598                    ("descendant of & must be declared as a synchronized "
16599                     & "interface", N, Parent_Type);
16600
16601               elsif Task_Present (Iface_Def) then
16602                  Error_Msg_NE
16603                    ("descendant of & must be declared as a task interface",
16604                       N, Parent_Type);
16605               else
16606                  null;
16607               end if;
16608            end if;
16609         end if;
16610      end if;
16611
16612      if Is_Tagged_Type (Parent_Type)
16613        and then Is_Concurrent_Type (Parent_Type)
16614        and then not Is_Interface (Parent_Type)
16615      then
16616         Error_Msg_N
16617           ("parent type of a record extension cannot be a synchronized "
16618            & "tagged type (RM 3.9.1 (3/1))", N);
16619         Set_Etype (T, Any_Type);
16620         return;
16621      end if;
16622
16623      --  Ada 2005 (AI-251): Decorate all the names in the list of ancestor
16624      --  interfaces
16625
16626      if Is_Tagged_Type (Parent_Type)
16627        and then Is_Non_Empty_List (Interface_List (Def))
16628      then
16629         declare
16630            Intf : Node_Id;
16631            T    : Entity_Id;
16632
16633         begin
16634            Intf := First (Interface_List (Def));
16635            while Present (Intf) loop
16636               T := Find_Type_Of_Subtype_Indic (Intf);
16637
16638               if not Is_Interface (T) then
16639                  Diagnose_Interface (Intf, T);
16640
16641               --  Check the rules of 3.9.4(12/2) and 7.5(2/2) that disallow
16642               --  a limited type from having a nonlimited progenitor.
16643
16644               elsif (Limited_Present (Def)
16645                       or else (not Is_Interface (Parent_Type)
16646                                 and then Is_Limited_Type (Parent_Type)))
16647                 and then not Is_Limited_Interface (T)
16648               then
16649                  Error_Msg_NE
16650                   ("progenitor interface& of limited type must be limited",
16651                     N, T);
16652               end if;
16653
16654               Next (Intf);
16655            end loop;
16656         end;
16657      end if;
16658
16659      if Parent_Type = Any_Type
16660        or else Etype (Parent_Type) = Any_Type
16661        or else (Is_Class_Wide_Type (Parent_Type)
16662                  and then Etype (Parent_Type) = T)
16663      then
16664         --  If Parent_Type is undefined or illegal, make new type into a
16665         --  subtype of Any_Type, and set a few attributes to prevent cascaded
16666         --  errors. If this is a self-definition, emit error now.
16667
16668         if T = Parent_Type or else T = Etype (Parent_Type) then
16669            Error_Msg_N ("type cannot be used in its own definition", Indic);
16670         end if;
16671
16672         Set_Ekind        (T, Ekind (Parent_Type));
16673         Set_Etype        (T, Any_Type);
16674         Set_Scalar_Range (T, Scalar_Range (Any_Type));
16675
16676         if Is_Tagged_Type (T)
16677           and then Is_Record_Type (T)
16678         then
16679            Set_Direct_Primitive_Operations (T, New_Elmt_List);
16680         end if;
16681
16682         return;
16683      end if;
16684
16685      --  Ada 2005 (AI-251): The case in which the parent of the full-view is
16686      --  an interface is special because the list of interfaces in the full
16687      --  view can be given in any order. For example:
16688
16689      --     type A is interface;
16690      --     type B is interface and A;
16691      --     type D is new B with private;
16692      --   private
16693      --     type D is new A and B with null record; -- 1 --
16694
16695      --  In this case we perform the following transformation of -1-:
16696
16697      --     type D is new B and A with null record;
16698
16699      --  If the parent of the full-view covers the parent of the partial-view
16700      --  we have two possible cases:
16701
16702      --     1) They have the same parent
16703      --     2) The parent of the full-view implements some further interfaces
16704
16705      --  In both cases we do not need to perform the transformation. In the
16706      --  first case the source program is correct and the transformation is
16707      --  not needed; in the second case the source program does not fulfill
16708      --  the no-hidden interfaces rule (AI-396) and the error will be reported
16709      --  later.
16710
16711      --  This transformation not only simplifies the rest of the analysis of
16712      --  this type declaration but also simplifies the correct generation of
16713      --  the object layout to the expander.
16714
16715      if In_Private_Part (Current_Scope)
16716        and then Is_Interface (Parent_Type)
16717      then
16718         declare
16719            Iface               : Node_Id;
16720            Partial_View        : Entity_Id;
16721            Partial_View_Parent : Entity_Id;
16722            New_Iface           : Node_Id;
16723
16724         begin
16725            --  Look for the associated private type declaration
16726
16727            Partial_View := Incomplete_Or_Partial_View (T);
16728
16729            --  If the partial view was not found then the source code has
16730            --  errors and the transformation is not needed.
16731
16732            if Present (Partial_View) then
16733               Partial_View_Parent := Etype (Partial_View);
16734
16735               --  If the parent of the full-view covers the parent of the
16736               --  partial-view we have nothing else to do.
16737
16738               if Interface_Present_In_Ancestor
16739                    (Parent_Type, Partial_View_Parent)
16740               then
16741                  null;
16742
16743               --  Traverse the list of interfaces of the full-view to look
16744               --  for the parent of the partial-view and perform the tree
16745               --  transformation.
16746
16747               else
16748                  Iface := First (Interface_List (Def));
16749                  while Present (Iface) loop
16750                     if Etype (Iface) = Etype (Partial_View) then
16751                        Rewrite (Subtype_Indication (Def),
16752                          New_Copy (Subtype_Indication
16753                                     (Parent (Partial_View))));
16754
16755                        New_Iface :=
16756                          Make_Identifier (Sloc (N), Chars (Parent_Type));
16757                        Append (New_Iface, Interface_List (Def));
16758
16759                        --  Analyze the transformed code
16760
16761                        Derived_Type_Declaration (T, N, Is_Completion);
16762                        return;
16763                     end if;
16764
16765                     Next (Iface);
16766                  end loop;
16767               end if;
16768            end if;
16769         end;
16770      end if;
16771
16772      --  Only composite types other than array types are allowed to have
16773      --  discriminants.
16774
16775      if Present (Discriminant_Specifications (N)) then
16776         if (Is_Elementary_Type (Parent_Type)
16777               or else
16778             Is_Array_Type      (Parent_Type))
16779           and then not Error_Posted (N)
16780         then
16781            Error_Msg_N
16782              ("elementary or array type cannot have discriminants",
16783               Defining_Identifier (First (Discriminant_Specifications (N))));
16784
16785            --  Unset Has_Discriminants flag to prevent cascaded errors, but
16786            --  only if we are not already processing a malformed syntax tree.
16787
16788            if Is_Type (T) then
16789               Set_Has_Discriminants (T, False);
16790            end if;
16791
16792         --  The type is allowed to have discriminants
16793
16794         else
16795            Check_SPARK_05_Restriction ("discriminant type is not allowed", N);
16796         end if;
16797      end if;
16798
16799      --  In Ada 83, a derived type defined in a package specification cannot
16800      --  be used for further derivation until the end of its visible part.
16801      --  Note that derivation in the private part of the package is allowed.
16802
16803      if Ada_Version = Ada_83
16804        and then Is_Derived_Type (Parent_Type)
16805        and then In_Visible_Part (Scope (Parent_Type))
16806      then
16807         if Ada_Version = Ada_83 and then Comes_From_Source (Indic) then
16808            Error_Msg_N
16809              ("(Ada 83): premature use of type for derivation", Indic);
16810         end if;
16811      end if;
16812
16813      --  Check for early use of incomplete or private type
16814
16815      if Ekind_In (Parent_Type, E_Void, E_Incomplete_Type) then
16816         Error_Msg_N ("premature derivation of incomplete type", Indic);
16817         return;
16818
16819      elsif (Is_Incomplete_Or_Private_Type (Parent_Type)
16820              and then not Comes_From_Generic (Parent_Type))
16821        or else Has_Private_Component (Parent_Type)
16822      then
16823         --  The ancestor type of a formal type can be incomplete, in which
16824         --  case only the operations of the partial view are available in the
16825         --  generic. Subsequent checks may be required when the full view is
16826         --  analyzed to verify that a derivation from a tagged type has an
16827         --  extension.
16828
16829         if Nkind (Original_Node (N)) = N_Formal_Type_Declaration then
16830            null;
16831
16832         elsif No (Underlying_Type (Parent_Type))
16833           or else Has_Private_Component (Parent_Type)
16834         then
16835            Error_Msg_N
16836              ("premature derivation of derived or private type", Indic);
16837
16838            --  Flag the type itself as being in error, this prevents some
16839            --  nasty problems with subsequent uses of the malformed type.
16840
16841            Set_Error_Posted (T);
16842
16843         --  Check that within the immediate scope of an untagged partial
16844         --  view it's illegal to derive from the partial view if the
16845         --  full view is tagged. (7.3(7))
16846
16847         --  We verify that the Parent_Type is a partial view by checking
16848         --  that it is not a Full_Type_Declaration (i.e. a private type or
16849         --  private extension declaration), to distinguish a partial view
16850         --  from  a derivation from a private type which also appears as
16851         --  E_Private_Type. If the parent base type is not declared in an
16852         --  enclosing scope there is no need to check.
16853
16854         elsif Present (Full_View (Parent_Type))
16855           and then Nkind (Parent (Parent_Type)) /= N_Full_Type_Declaration
16856           and then not Is_Tagged_Type (Parent_Type)
16857           and then Is_Tagged_Type (Full_View (Parent_Type))
16858           and then In_Open_Scopes (Scope (Base_Type (Parent_Type)))
16859         then
16860            Error_Msg_N
16861              ("premature derivation from type with tagged full view",
16862                Indic);
16863         end if;
16864      end if;
16865
16866      --  Check that form of derivation is appropriate
16867
16868      Taggd := Is_Tagged_Type (Parent_Type);
16869
16870      --  Set the parent type to the class-wide type's specific type in this
16871      --  case to prevent cascading errors
16872
16873      if Present (Extension) and then Is_Class_Wide_Type (Parent_Type) then
16874         Error_Msg_N ("parent type must not be a class-wide type", Indic);
16875         Set_Etype (T, Etype (Parent_Type));
16876         return;
16877      end if;
16878
16879      if Present (Extension) and then not Taggd then
16880         Error_Msg_N
16881           ("type derived from untagged type cannot have extension", Indic);
16882
16883      elsif No (Extension) and then Taggd then
16884
16885         --  If this declaration is within a private part (or body) of a
16886         --  generic instantiation then the derivation is allowed (the parent
16887         --  type can only appear tagged in this case if it's a generic actual
16888         --  type, since it would otherwise have been rejected in the analysis
16889         --  of the generic template).
16890
16891         if not Is_Generic_Actual_Type (Parent_Type)
16892           or else In_Visible_Part (Scope (Parent_Type))
16893         then
16894            if Is_Class_Wide_Type (Parent_Type) then
16895               Error_Msg_N
16896                 ("parent type must not be a class-wide type", Indic);
16897
16898               --  Use specific type to prevent cascaded errors.
16899
16900               Parent_Type := Etype (Parent_Type);
16901
16902            else
16903               Error_Msg_N
16904                 ("type derived from tagged type must have extension", Indic);
16905            end if;
16906         end if;
16907      end if;
16908
16909      --  AI-443: Synchronized formal derived types require a private
16910      --  extension. There is no point in checking the ancestor type or
16911      --  the progenitors since the construct is wrong to begin with.
16912
16913      if Ada_Version >= Ada_2005
16914        and then Is_Generic_Type (T)
16915        and then Present (Original_Node (N))
16916      then
16917         declare
16918            Decl : constant Node_Id := Original_Node (N);
16919
16920         begin
16921            if Nkind (Decl) = N_Formal_Type_Declaration
16922              and then Nkind (Formal_Type_Definition (Decl)) =
16923                                          N_Formal_Derived_Type_Definition
16924              and then Synchronized_Present (Formal_Type_Definition (Decl))
16925              and then No (Extension)
16926
16927               --  Avoid emitting a duplicate error message
16928
16929              and then not Error_Posted (Indic)
16930            then
16931               Error_Msg_N
16932                 ("synchronized derived type must have extension", N);
16933            end if;
16934         end;
16935      end if;
16936
16937      if Null_Exclusion_Present (Def)
16938        and then not Is_Access_Type (Parent_Type)
16939      then
16940         Error_Msg_N ("null exclusion can only apply to an access type", N);
16941      end if;
16942
16943      --  Avoid deriving parent primitives of underlying record views
16944
16945      Build_Derived_Type (N, Parent_Type, T, Is_Completion,
16946        Derive_Subps => not Is_Underlying_Record_View (T));
16947
16948      --  AI-419: The parent type of an explicitly limited derived type must
16949      --  be a limited type or a limited interface.
16950
16951      if Limited_Present (Def) then
16952         Set_Is_Limited_Record (T);
16953
16954         if Is_Interface (T) then
16955            Set_Is_Limited_Interface (T);
16956         end if;
16957
16958         if not Is_Limited_Type (Parent_Type)
16959           and then
16960             (not Is_Interface (Parent_Type)
16961               or else not Is_Limited_Interface (Parent_Type))
16962         then
16963            --  AI05-0096: a derivation in the private part of an instance is
16964            --  legal if the generic formal is untagged limited, and the actual
16965            --  is non-limited.
16966
16967            if Is_Generic_Actual_Type (Parent_Type)
16968              and then In_Private_Part (Current_Scope)
16969              and then
16970                not Is_Tagged_Type
16971                      (Generic_Parent_Type (Parent (Parent_Type)))
16972            then
16973               null;
16974
16975            else
16976               Error_Msg_NE
16977                 ("parent type& of limited type must be limited",
16978                  N, Parent_Type);
16979            end if;
16980         end if;
16981      end if;
16982
16983      --  In SPARK, there are no derived type definitions other than type
16984      --  extensions of tagged record types.
16985
16986      if No (Extension) then
16987         Check_SPARK_05_Restriction
16988           ("derived type is not allowed", Original_Node (N));
16989      end if;
16990   end Derived_Type_Declaration;
16991
16992   ------------------------
16993   -- Diagnose_Interface --
16994   ------------------------
16995
16996   procedure Diagnose_Interface (N : Node_Id;  E : Entity_Id) is
16997   begin
16998      if not Is_Interface (E) and then E /= Any_Type then
16999         Error_Msg_NE ("(Ada 2005) & must be an interface", N, E);
17000      end if;
17001   end Diagnose_Interface;
17002
17003   ----------------------------------
17004   -- Enumeration_Type_Declaration --
17005   ----------------------------------
17006
17007   procedure Enumeration_Type_Declaration (T : Entity_Id; Def : Node_Id) is
17008      Ev     : Uint;
17009      L      : Node_Id;
17010      R_Node : Node_Id;
17011      B_Node : Node_Id;
17012
17013   begin
17014      --  Create identifier node representing lower bound
17015
17016      B_Node := New_Node (N_Identifier, Sloc (Def));
17017      L := First (Literals (Def));
17018      Set_Chars (B_Node, Chars (L));
17019      Set_Entity (B_Node,  L);
17020      Set_Etype (B_Node, T);
17021      Set_Is_Static_Expression (B_Node, True);
17022
17023      R_Node := New_Node (N_Range, Sloc (Def));
17024      Set_Low_Bound  (R_Node, B_Node);
17025
17026      Set_Ekind (T, E_Enumeration_Type);
17027      Set_First_Literal (T, L);
17028      Set_Etype (T, T);
17029      Set_Is_Constrained (T);
17030
17031      Ev := Uint_0;
17032
17033      --  Loop through literals of enumeration type setting pos and rep values
17034      --  except that if the Ekind is already set, then it means the literal
17035      --  was already constructed (case of a derived type declaration and we
17036      --  should not disturb the Pos and Rep values.
17037
17038      while Present (L) loop
17039         if Ekind (L) /= E_Enumeration_Literal then
17040            Set_Ekind (L, E_Enumeration_Literal);
17041            Set_Enumeration_Pos (L, Ev);
17042            Set_Enumeration_Rep (L, Ev);
17043            Set_Is_Known_Valid  (L, True);
17044         end if;
17045
17046         Set_Etype (L, T);
17047         New_Overloaded_Entity (L);
17048         Generate_Definition (L);
17049         Set_Convention (L, Convention_Intrinsic);
17050
17051         --  Case of character literal
17052
17053         if Nkind (L) = N_Defining_Character_Literal then
17054            Set_Is_Character_Type (T, True);
17055
17056            --  Check violation of No_Wide_Characters
17057
17058            if Restriction_Check_Required (No_Wide_Characters) then
17059               Get_Name_String (Chars (L));
17060
17061               if Name_Len >= 3 and then Name_Buffer (1 .. 2) = "QW" then
17062                  Check_Restriction (No_Wide_Characters, L);
17063               end if;
17064            end if;
17065         end if;
17066
17067         Ev := Ev + 1;
17068         Next (L);
17069      end loop;
17070
17071      --  Now create a node representing upper bound
17072
17073      B_Node := New_Node (N_Identifier, Sloc (Def));
17074      Set_Chars (B_Node, Chars (Last (Literals (Def))));
17075      Set_Entity (B_Node,  Last (Literals (Def)));
17076      Set_Etype (B_Node, T);
17077      Set_Is_Static_Expression (B_Node, True);
17078
17079      Set_High_Bound (R_Node, B_Node);
17080
17081      --  Initialize various fields of the type. Some of this information
17082      --  may be overwritten later through rep.clauses.
17083
17084      Set_Scalar_Range    (T, R_Node);
17085      Set_RM_Size         (T, UI_From_Int (Minimum_Size (T)));
17086      Set_Enum_Esize      (T);
17087      Set_Enum_Pos_To_Rep (T, Empty);
17088
17089      --  Set Discard_Names if configuration pragma set, or if there is
17090      --  a parameterless pragma in the current declarative region
17091
17092      if Global_Discard_Names or else Discard_Names (Scope (T)) then
17093         Set_Discard_Names (T);
17094      end if;
17095
17096      --  Process end label if there is one
17097
17098      if Present (Def) then
17099         Process_End_Label (Def, 'e', T);
17100      end if;
17101   end Enumeration_Type_Declaration;
17102
17103   ---------------------------------
17104   -- Expand_To_Stored_Constraint --
17105   ---------------------------------
17106
17107   function Expand_To_Stored_Constraint
17108     (Typ        : Entity_Id;
17109      Constraint : Elist_Id) return Elist_Id
17110   is
17111      Explicitly_Discriminated_Type : Entity_Id;
17112      Expansion    : Elist_Id;
17113      Discriminant : Entity_Id;
17114
17115      function Type_With_Explicit_Discrims (Id : Entity_Id) return Entity_Id;
17116      --  Find the nearest type that actually specifies discriminants
17117
17118      ---------------------------------
17119      -- Type_With_Explicit_Discrims --
17120      ---------------------------------
17121
17122      function Type_With_Explicit_Discrims (Id : Entity_Id) return Entity_Id is
17123         Typ : constant E := Base_Type (Id);
17124
17125      begin
17126         if Ekind (Typ) in Incomplete_Or_Private_Kind then
17127            if Present (Full_View (Typ)) then
17128               return Type_With_Explicit_Discrims (Full_View (Typ));
17129            end if;
17130
17131         else
17132            if Has_Discriminants (Typ) then
17133               return Typ;
17134            end if;
17135         end if;
17136
17137         if Etype (Typ) = Typ then
17138            return Empty;
17139         elsif Has_Discriminants (Typ) then
17140            return Typ;
17141         else
17142            return Type_With_Explicit_Discrims (Etype (Typ));
17143         end if;
17144
17145      end Type_With_Explicit_Discrims;
17146
17147   --  Start of processing for Expand_To_Stored_Constraint
17148
17149   begin
17150      if No (Constraint) or else Is_Empty_Elmt_List (Constraint) then
17151         return No_Elist;
17152      end if;
17153
17154      Explicitly_Discriminated_Type := Type_With_Explicit_Discrims (Typ);
17155
17156      if No (Explicitly_Discriminated_Type) then
17157         return No_Elist;
17158      end if;
17159
17160      Expansion := New_Elmt_List;
17161
17162      Discriminant :=
17163         First_Stored_Discriminant (Explicitly_Discriminated_Type);
17164      while Present (Discriminant) loop
17165         Append_Elmt
17166           (Get_Discriminant_Value
17167              (Discriminant, Explicitly_Discriminated_Type, Constraint),
17168            To => Expansion);
17169         Next_Stored_Discriminant (Discriminant);
17170      end loop;
17171
17172      return Expansion;
17173   end Expand_To_Stored_Constraint;
17174
17175   ---------------------------
17176   -- Find_Hidden_Interface --
17177   ---------------------------
17178
17179   function Find_Hidden_Interface
17180     (Src  : Elist_Id;
17181      Dest : Elist_Id) return Entity_Id
17182   is
17183      Iface      : Entity_Id;
17184      Iface_Elmt : Elmt_Id;
17185
17186   begin
17187      if Present (Src) and then Present (Dest) then
17188         Iface_Elmt := First_Elmt (Src);
17189         while Present (Iface_Elmt) loop
17190            Iface := Node (Iface_Elmt);
17191
17192            if Is_Interface (Iface)
17193              and then not Contain_Interface (Iface, Dest)
17194            then
17195               return Iface;
17196            end if;
17197
17198            Next_Elmt (Iface_Elmt);
17199         end loop;
17200      end if;
17201
17202      return Empty;
17203   end Find_Hidden_Interface;
17204
17205   --------------------
17206   -- Find_Type_Name --
17207   --------------------
17208
17209   function Find_Type_Name (N : Node_Id) return Entity_Id is
17210      Id       : constant Entity_Id := Defining_Identifier (N);
17211      New_Id   : Entity_Id;
17212      Prev     : Entity_Id;
17213      Prev_Par : Node_Id;
17214
17215      procedure Check_Duplicate_Aspects;
17216      --  Check that aspects specified in a completion have not been specified
17217      --  already in the partial view.
17218
17219      procedure Tag_Mismatch;
17220      --  Diagnose a tagged partial view whose full view is untagged. We post
17221      --  the message on the full view, with a reference to the previous
17222      --  partial view. The partial view can be private or incomplete, and
17223      --  these are handled in a different manner, so we determine the position
17224      --  of the error message from the respective slocs of both.
17225
17226      -----------------------------
17227      -- Check_Duplicate_Aspects --
17228      -----------------------------
17229
17230      procedure Check_Duplicate_Aspects is
17231         function Get_Partial_View_Aspect (Asp : Node_Id) return Node_Id;
17232         --  Return the corresponding aspect of the partial view which matches
17233         --  the aspect id of Asp. Return Empty is no such aspect exists.
17234
17235         -----------------------------
17236         -- Get_Partial_View_Aspect --
17237         -----------------------------
17238
17239         function Get_Partial_View_Aspect (Asp : Node_Id) return Node_Id is
17240            Asp_Id    : constant Aspect_Id := Get_Aspect_Id (Asp);
17241            Prev_Asps : constant List_Id   := Aspect_Specifications (Prev_Par);
17242            Prev_Asp  : Node_Id;
17243
17244         begin
17245            if Present (Prev_Asps) then
17246               Prev_Asp := First (Prev_Asps);
17247               while Present (Prev_Asp) loop
17248                  if Get_Aspect_Id (Prev_Asp) = Asp_Id then
17249                     return Prev_Asp;
17250                  end if;
17251
17252                  Next (Prev_Asp);
17253               end loop;
17254            end if;
17255
17256            return Empty;
17257         end Get_Partial_View_Aspect;
17258
17259         --  Local variables
17260
17261         Full_Asps : constant List_Id := Aspect_Specifications (N);
17262         Full_Asp  : Node_Id;
17263         Part_Asp  : Node_Id;
17264
17265      --  Start of processing for Check_Duplicate_Aspects
17266
17267      begin
17268         if Present (Full_Asps) then
17269            Full_Asp := First (Full_Asps);
17270            while Present (Full_Asp) loop
17271               Part_Asp := Get_Partial_View_Aspect (Full_Asp);
17272
17273               --  An aspect and its class-wide counterpart are two distinct
17274               --  aspects and may apply to both views of an entity.
17275
17276               if Present (Part_Asp)
17277                 and then Class_Present (Part_Asp) = Class_Present (Full_Asp)
17278               then
17279                  Error_Msg_N
17280                    ("aspect already specified in private declaration",
17281                     Full_Asp);
17282
17283                  Remove (Full_Asp);
17284                  return;
17285               end if;
17286
17287               if Has_Discriminants (Prev)
17288                 and then not Has_Unknown_Discriminants (Prev)
17289                 and then Get_Aspect_Id (Full_Asp) =
17290                            Aspect_Implicit_Dereference
17291               then
17292                  Error_Msg_N
17293                    ("cannot specify aspect if partial view has known "
17294                     & "discriminants", Full_Asp);
17295               end if;
17296
17297               Next (Full_Asp);
17298            end loop;
17299         end if;
17300      end Check_Duplicate_Aspects;
17301
17302      ------------------
17303      -- Tag_Mismatch --
17304      ------------------
17305
17306      procedure Tag_Mismatch is
17307      begin
17308         if Sloc (Prev) < Sloc (Id) then
17309            if Ada_Version >= Ada_2012
17310              and then Nkind (N) = N_Private_Type_Declaration
17311            then
17312               Error_Msg_NE
17313                 ("declaration of private } must be a tagged type ", Id, Prev);
17314            else
17315               Error_Msg_NE
17316                 ("full declaration of } must be a tagged type ", Id, Prev);
17317            end if;
17318
17319         else
17320            if Ada_Version >= Ada_2012
17321              and then Nkind (N) = N_Private_Type_Declaration
17322            then
17323               Error_Msg_NE
17324                 ("declaration of private } must be a tagged type ", Prev, Id);
17325            else
17326               Error_Msg_NE
17327                 ("full declaration of } must be a tagged type ", Prev, Id);
17328            end if;
17329         end if;
17330      end Tag_Mismatch;
17331
17332   --  Start of processing for Find_Type_Name
17333
17334   begin
17335      --  Find incomplete declaration, if one was given
17336
17337      Prev := Current_Entity_In_Scope (Id);
17338
17339      --  New type declaration
17340
17341      if No (Prev) then
17342         Enter_Name (Id);
17343         return Id;
17344
17345      --  Previous declaration exists
17346
17347      else
17348         Prev_Par := Parent (Prev);
17349
17350         --  Error if not incomplete/private case except if previous
17351         --  declaration is implicit, etc. Enter_Name will emit error if
17352         --  appropriate.
17353
17354         if not Is_Incomplete_Or_Private_Type (Prev) then
17355            Enter_Name (Id);
17356            New_Id := Id;
17357
17358         --  Check invalid completion of private or incomplete type
17359
17360         elsif not Nkind_In (N, N_Full_Type_Declaration,
17361                                N_Task_Type_Declaration,
17362                                N_Protected_Type_Declaration)
17363           and then
17364             (Ada_Version < Ada_2012
17365               or else not Is_Incomplete_Type (Prev)
17366               or else not Nkind_In (N, N_Private_Type_Declaration,
17367                                        N_Private_Extension_Declaration))
17368         then
17369            --  Completion must be a full type declarations (RM 7.3(4))
17370
17371            Error_Msg_Sloc := Sloc (Prev);
17372            Error_Msg_NE ("invalid completion of }", Id, Prev);
17373
17374            --  Set scope of Id to avoid cascaded errors. Entity is never
17375            --  examined again, except when saving globals in generics.
17376
17377            Set_Scope (Id, Current_Scope);
17378            New_Id := Id;
17379
17380            --  If this is a repeated incomplete declaration, no further
17381            --  checks are possible.
17382
17383            if Nkind (N) = N_Incomplete_Type_Declaration then
17384               return Prev;
17385            end if;
17386
17387         --  Case of full declaration of incomplete type
17388
17389         elsif Ekind (Prev) = E_Incomplete_Type
17390           and then (Ada_Version < Ada_2012
17391                      or else No (Full_View (Prev))
17392                      or else not Is_Private_Type (Full_View (Prev)))
17393         then
17394            --  Indicate that the incomplete declaration has a matching full
17395            --  declaration. The defining occurrence of the incomplete
17396            --  declaration remains the visible one, and the procedure
17397            --  Get_Full_View dereferences it whenever the type is used.
17398
17399            if Present (Full_View (Prev)) then
17400               Error_Msg_NE ("invalid redeclaration of }", Id, Prev);
17401            end if;
17402
17403            Set_Full_View (Prev, Id);
17404            Append_Entity (Id, Current_Scope);
17405            Set_Is_Public (Id, Is_Public (Prev));
17406            Set_Is_Internal (Id);
17407            New_Id := Prev;
17408
17409            --  If the incomplete view is tagged, a class_wide type has been
17410            --  created already. Use it for the private type as well, in order
17411            --  to prevent multiple incompatible class-wide types that may be
17412            --  created for self-referential anonymous access components.
17413
17414            if Is_Tagged_Type (Prev)
17415              and then Present (Class_Wide_Type (Prev))
17416            then
17417               Set_Ekind (Id, Ekind (Prev));         --  will be reset later
17418               Set_Class_Wide_Type (Id, Class_Wide_Type (Prev));
17419
17420               --  Type of the class-wide type is the current Id. Previously
17421               --  this was not done for private declarations because of order-
17422               --  of-elaboration issues in the back end, but gigi now handles
17423               --  this properly.
17424
17425               Set_Etype (Class_Wide_Type (Id), Id);
17426            end if;
17427
17428         --  Case of full declaration of private type
17429
17430         else
17431            --  If the private type was a completion of an incomplete type then
17432            --  update Prev to reference the private type
17433
17434            if Ada_Version >= Ada_2012
17435              and then Ekind (Prev) = E_Incomplete_Type
17436              and then Present (Full_View (Prev))
17437              and then Is_Private_Type (Full_View (Prev))
17438            then
17439               Prev := Full_View (Prev);
17440               Prev_Par := Parent (Prev);
17441            end if;
17442
17443            if Nkind (N) = N_Full_Type_Declaration
17444              and then Nkind_In
17445                         (Type_Definition (N), N_Record_Definition,
17446                                               N_Derived_Type_Definition)
17447              and then Interface_Present (Type_Definition (N))
17448            then
17449               Error_Msg_N
17450                 ("completion of private type cannot be an interface", N);
17451            end if;
17452
17453            if Nkind (Parent (Prev)) /= N_Private_Extension_Declaration then
17454               if Etype (Prev) /= Prev then
17455
17456                  --  Prev is a private subtype or a derived type, and needs
17457                  --  no completion.
17458
17459                  Error_Msg_NE ("invalid redeclaration of }", Id, Prev);
17460                  New_Id := Id;
17461
17462               elsif Ekind (Prev) = E_Private_Type
17463                 and then Nkind_In (N, N_Task_Type_Declaration,
17464                                       N_Protected_Type_Declaration)
17465               then
17466                  Error_Msg_N
17467                   ("completion of nonlimited type cannot be limited", N);
17468
17469               elsif Ekind (Prev) = E_Record_Type_With_Private
17470                 and then Nkind_In (N, N_Task_Type_Declaration,
17471                                       N_Protected_Type_Declaration)
17472               then
17473                  if not Is_Limited_Record (Prev) then
17474                     Error_Msg_N
17475                        ("completion of nonlimited type cannot be limited", N);
17476
17477                  elsif No (Interface_List (N)) then
17478                     Error_Msg_N
17479                        ("completion of tagged private type must be tagged",
17480                         N);
17481                  end if;
17482               end if;
17483
17484            --  Ada 2005 (AI-251): Private extension declaration of a task
17485            --  type or a protected type. This case arises when covering
17486            --  interface types.
17487
17488            elsif Nkind_In (N, N_Task_Type_Declaration,
17489                               N_Protected_Type_Declaration)
17490            then
17491               null;
17492
17493            elsif Nkind (N) /= N_Full_Type_Declaration
17494              or else Nkind (Type_Definition (N)) /= N_Derived_Type_Definition
17495            then
17496               Error_Msg_N
17497                 ("full view of private extension must be an extension", N);
17498
17499            elsif not (Abstract_Present (Parent (Prev)))
17500              and then Abstract_Present (Type_Definition (N))
17501            then
17502               Error_Msg_N
17503                 ("full view of non-abstract extension cannot be abstract", N);
17504            end if;
17505
17506            if not In_Private_Part (Current_Scope) then
17507               Error_Msg_N
17508                 ("declaration of full view must appear in private part", N);
17509            end if;
17510
17511            if Ada_Version >= Ada_2012 then
17512               Check_Duplicate_Aspects;
17513            end if;
17514
17515            Copy_And_Swap (Prev, Id);
17516            Set_Has_Private_Declaration (Prev);
17517            Set_Has_Private_Declaration (Id);
17518
17519            --  AI12-0133: Indicate whether we have a partial view with
17520            --  unknown discriminants, in which case initialization of objects
17521            --  of the type do not receive an invariant check.
17522
17523            Set_Partial_View_Has_Unknown_Discr
17524              (Prev, Has_Unknown_Discriminants (Id));
17525
17526            --  Preserve aspect and iterator flags that may have been set on
17527            --  the partial view.
17528
17529            Set_Has_Delayed_Aspects (Prev, Has_Delayed_Aspects (Id));
17530            Set_Has_Implicit_Dereference (Prev, Has_Implicit_Dereference (Id));
17531
17532            --  If no error, propagate freeze_node from private to full view.
17533            --  It may have been generated for an early operational item.
17534
17535            if Present (Freeze_Node (Id))
17536              and then Serious_Errors_Detected = 0
17537              and then No (Full_View (Id))
17538            then
17539               Set_Freeze_Node (Prev, Freeze_Node (Id));
17540               Set_Freeze_Node (Id, Empty);
17541               Set_First_Rep_Item (Prev, First_Rep_Item (Id));
17542            end if;
17543
17544            Set_Full_View (Id, Prev);
17545            New_Id := Prev;
17546         end if;
17547
17548         --  Verify that full declaration conforms to partial one
17549
17550         if Is_Incomplete_Or_Private_Type (Prev)
17551           and then Present (Discriminant_Specifications (Prev_Par))
17552         then
17553            if Present (Discriminant_Specifications (N)) then
17554               if Ekind (Prev) = E_Incomplete_Type then
17555                  Check_Discriminant_Conformance (N, Prev, Prev);
17556               else
17557                  Check_Discriminant_Conformance (N, Prev, Id);
17558               end if;
17559
17560            else
17561               Error_Msg_N
17562                 ("missing discriminants in full type declaration", N);
17563
17564               --  To avoid cascaded errors on subsequent use, share the
17565               --  discriminants of the partial view.
17566
17567               Set_Discriminant_Specifications (N,
17568                 Discriminant_Specifications (Prev_Par));
17569            end if;
17570         end if;
17571
17572         --  A prior untagged partial view can have an associated class-wide
17573         --  type due to use of the class attribute, and in this case the full
17574         --  type must also be tagged. This Ada 95 usage is deprecated in favor
17575         --  of incomplete tagged declarations, but we check for it.
17576
17577         if Is_Type (Prev)
17578           and then (Is_Tagged_Type (Prev)
17579                      or else Present (Class_Wide_Type (Prev)))
17580         then
17581            --  Ada 2012 (AI05-0162): A private type may be the completion of
17582            --  an incomplete type.
17583
17584            if Ada_Version >= Ada_2012
17585              and then Is_Incomplete_Type (Prev)
17586              and then Nkind_In (N, N_Private_Type_Declaration,
17587                                    N_Private_Extension_Declaration)
17588            then
17589               --  No need to check private extensions since they are tagged
17590
17591               if Nkind (N) = N_Private_Type_Declaration
17592                 and then not Tagged_Present (N)
17593               then
17594                  Tag_Mismatch;
17595               end if;
17596
17597            --  The full declaration is either a tagged type (including
17598            --  a synchronized type that implements interfaces) or a
17599            --  type extension, otherwise this is an error.
17600
17601            elsif Nkind_In (N, N_Task_Type_Declaration,
17602                               N_Protected_Type_Declaration)
17603            then
17604               if No (Interface_List (N)) and then not Error_Posted (N) then
17605                  Tag_Mismatch;
17606               end if;
17607
17608            elsif Nkind (Type_Definition (N)) = N_Record_Definition then
17609
17610               --  Indicate that the previous declaration (tagged incomplete
17611               --  or private declaration) requires the same on the full one.
17612
17613               if not Tagged_Present (Type_Definition (N)) then
17614                  Tag_Mismatch;
17615                  Set_Is_Tagged_Type (Id);
17616               end if;
17617
17618            elsif Nkind (Type_Definition (N)) = N_Derived_Type_Definition then
17619               if No (Record_Extension_Part (Type_Definition (N))) then
17620                  Error_Msg_NE
17621                    ("full declaration of } must be a record extension",
17622                     Prev, Id);
17623
17624                  --  Set some attributes to produce a usable full view
17625
17626                  Set_Is_Tagged_Type (Id);
17627               end if;
17628
17629            else
17630               Tag_Mismatch;
17631            end if;
17632         end if;
17633
17634         if Present (Prev)
17635           and then Nkind (Parent (Prev)) = N_Incomplete_Type_Declaration
17636           and then Present (Premature_Use (Parent (Prev)))
17637         then
17638            Error_Msg_Sloc := Sloc (N);
17639            Error_Msg_N
17640              ("\full declaration #", Premature_Use (Parent (Prev)));
17641         end if;
17642
17643         return New_Id;
17644      end if;
17645   end Find_Type_Name;
17646
17647   -------------------------
17648   -- Find_Type_Of_Object --
17649   -------------------------
17650
17651   function Find_Type_Of_Object
17652     (Obj_Def     : Node_Id;
17653      Related_Nod : Node_Id) return Entity_Id
17654   is
17655      Def_Kind : constant Node_Kind := Nkind (Obj_Def);
17656      P        : Node_Id := Parent (Obj_Def);
17657      T        : Entity_Id;
17658      Nam      : Name_Id;
17659
17660   begin
17661      --  If the parent is a component_definition node we climb to the
17662      --  component_declaration node
17663
17664      if Nkind (P) = N_Component_Definition then
17665         P := Parent (P);
17666      end if;
17667
17668      --  Case of an anonymous array subtype
17669
17670      if Nkind_In (Def_Kind, N_Constrained_Array_Definition,
17671                             N_Unconstrained_Array_Definition)
17672      then
17673         T := Empty;
17674         Array_Type_Declaration (T, Obj_Def);
17675
17676      --  Create an explicit subtype whenever possible
17677
17678      elsif Nkind (P) /= N_Component_Declaration
17679        and then Def_Kind = N_Subtype_Indication
17680      then
17681         --  Base name of subtype on object name, which will be unique in
17682         --  the current scope.
17683
17684         --  If this is a duplicate declaration, return base type, to avoid
17685         --  generating duplicate anonymous types.
17686
17687         if Error_Posted (P) then
17688            Analyze (Subtype_Mark (Obj_Def));
17689            return Entity (Subtype_Mark (Obj_Def));
17690         end if;
17691
17692         Nam :=
17693            New_External_Name
17694             (Chars (Defining_Identifier (Related_Nod)), 'S', 0, 'T');
17695
17696         T := Make_Defining_Identifier (Sloc (P), Nam);
17697
17698         Insert_Action (Obj_Def,
17699           Make_Subtype_Declaration (Sloc (P),
17700             Defining_Identifier => T,
17701             Subtype_Indication  => Relocate_Node (Obj_Def)));
17702
17703         --  This subtype may need freezing, and this will not be done
17704         --  automatically if the object declaration is not in declarative
17705         --  part. Since this is an object declaration, the type cannot always
17706         --  be frozen here. Deferred constants do not freeze their type
17707         --  (which often enough will be private).
17708
17709         if Nkind (P) = N_Object_Declaration
17710           and then Constant_Present (P)
17711           and then No (Expression (P))
17712         then
17713            null;
17714
17715         --  Here we freeze the base type of object type to catch premature use
17716         --  of discriminated private type without a full view.
17717
17718         else
17719            Insert_Actions (Obj_Def, Freeze_Entity (Base_Type (T), P));
17720         end if;
17721
17722      --  Ada 2005 AI-406: the object definition in an object declaration
17723      --  can be an access definition.
17724
17725      elsif Def_Kind = N_Access_Definition then
17726         T := Access_Definition (Related_Nod, Obj_Def);
17727
17728         Set_Is_Local_Anonymous_Access
17729           (T,
17730            V => (Ada_Version < Ada_2012)
17731                   or else (Nkind (P) /= N_Object_Declaration)
17732                   or else Is_Library_Level_Entity (Defining_Identifier (P)));
17733
17734      --  Otherwise, the object definition is just a subtype_mark
17735
17736      else
17737         T := Process_Subtype (Obj_Def, Related_Nod);
17738
17739         --  If expansion is disabled an object definition that is an aggregate
17740         --  will not get expanded and may lead to scoping problems in the back
17741         --  end, if the object is referenced in an inner scope. In that case
17742         --  create an itype reference for the object definition now. This
17743         --  may be redundant in some cases, but harmless.
17744
17745         if Is_Itype (T)
17746           and then Nkind (Related_Nod) = N_Object_Declaration
17747           and then ASIS_Mode
17748         then
17749            Build_Itype_Reference (T, Related_Nod);
17750         end if;
17751      end if;
17752
17753      return T;
17754   end Find_Type_Of_Object;
17755
17756   --------------------------------
17757   -- Find_Type_Of_Subtype_Indic --
17758   --------------------------------
17759
17760   function Find_Type_Of_Subtype_Indic (S : Node_Id) return Entity_Id is
17761      Typ : Entity_Id;
17762
17763   begin
17764      --  Case of subtype mark with a constraint
17765
17766      if Nkind (S) = N_Subtype_Indication then
17767         Find_Type (Subtype_Mark (S));
17768         Typ := Entity (Subtype_Mark (S));
17769
17770         if not
17771           Is_Valid_Constraint_Kind (Ekind (Typ), Nkind (Constraint (S)))
17772         then
17773            Error_Msg_N
17774              ("incorrect constraint for this kind of type", Constraint (S));
17775            Rewrite (S, New_Copy_Tree (Subtype_Mark (S)));
17776         end if;
17777
17778      --  Otherwise we have a subtype mark without a constraint
17779
17780      elsif Error_Posted (S) then
17781         Rewrite (S, New_Occurrence_Of (Any_Id, Sloc (S)));
17782         return Any_Type;
17783
17784      else
17785         Find_Type (S);
17786         Typ := Entity (S);
17787      end if;
17788
17789      --  Check No_Wide_Characters restriction
17790
17791      Check_Wide_Character_Restriction (Typ, S);
17792
17793      return Typ;
17794   end Find_Type_Of_Subtype_Indic;
17795
17796   -------------------------------------
17797   -- Floating_Point_Type_Declaration --
17798   -------------------------------------
17799
17800   procedure Floating_Point_Type_Declaration (T : Entity_Id; Def : Node_Id) is
17801      Digs          : constant Node_Id := Digits_Expression (Def);
17802      Max_Digs_Val  : constant Uint := Digits_Value (Standard_Long_Long_Float);
17803      Digs_Val      : Uint;
17804      Base_Typ      : Entity_Id;
17805      Implicit_Base : Entity_Id;
17806      Bound         : Node_Id;
17807
17808      function Can_Derive_From (E : Entity_Id) return Boolean;
17809      --  Find if given digits value, and possibly a specified range, allows
17810      --  derivation from specified type
17811
17812      function Find_Base_Type return Entity_Id;
17813      --  Find a predefined base type that Def can derive from, or generate
17814      --  an error and substitute Long_Long_Float if none exists.
17815
17816      ---------------------
17817      -- Can_Derive_From --
17818      ---------------------
17819
17820      function Can_Derive_From (E : Entity_Id) return Boolean is
17821         Spec : constant Entity_Id := Real_Range_Specification (Def);
17822
17823      begin
17824         --  Check specified "digits" constraint
17825
17826         if Digs_Val > Digits_Value (E) then
17827            return False;
17828         end if;
17829
17830         --  Check for matching range, if specified
17831
17832         if Present (Spec) then
17833            if Expr_Value_R (Type_Low_Bound (E)) >
17834               Expr_Value_R (Low_Bound (Spec))
17835            then
17836               return False;
17837            end if;
17838
17839            if Expr_Value_R (Type_High_Bound (E)) <
17840               Expr_Value_R (High_Bound (Spec))
17841            then
17842               return False;
17843            end if;
17844         end if;
17845
17846         return True;
17847      end Can_Derive_From;
17848
17849      --------------------
17850      -- Find_Base_Type --
17851      --------------------
17852
17853      function Find_Base_Type return Entity_Id is
17854         Choice : Elmt_Id := First_Elmt (Predefined_Float_Types);
17855
17856      begin
17857         --  Iterate over the predefined types in order, returning the first
17858         --  one that Def can derive from.
17859
17860         while Present (Choice) loop
17861            if Can_Derive_From (Node (Choice)) then
17862               return Node (Choice);
17863            end if;
17864
17865            Next_Elmt (Choice);
17866         end loop;
17867
17868         --  If we can't derive from any existing type, use Long_Long_Float
17869         --  and give appropriate message explaining the problem.
17870
17871         if Digs_Val > Max_Digs_Val then
17872            --  It might be the case that there is a type with the requested
17873            --  range, just not the combination of digits and range.
17874
17875            Error_Msg_N
17876              ("no predefined type has requested range and precision",
17877               Real_Range_Specification (Def));
17878
17879         else
17880            Error_Msg_N
17881              ("range too large for any predefined type",
17882               Real_Range_Specification (Def));
17883         end if;
17884
17885         return Standard_Long_Long_Float;
17886      end Find_Base_Type;
17887
17888   --  Start of processing for Floating_Point_Type_Declaration
17889
17890   begin
17891      Check_Restriction (No_Floating_Point, Def);
17892
17893      --  Create an implicit base type
17894
17895      Implicit_Base :=
17896        Create_Itype (E_Floating_Point_Type, Parent (Def), T, 'B');
17897
17898      --  Analyze and verify digits value
17899
17900      Analyze_And_Resolve (Digs, Any_Integer);
17901      Check_Digits_Expression (Digs);
17902      Digs_Val := Expr_Value (Digs);
17903
17904      --  Process possible range spec and find correct type to derive from
17905
17906      Process_Real_Range_Specification (Def);
17907
17908      --  Check that requested number of digits is not too high.
17909
17910      if Digs_Val > Max_Digs_Val then
17911
17912         --  The check for Max_Base_Digits may be somewhat expensive, as it
17913         --  requires reading System, so only do it when necessary.
17914
17915         declare
17916            Max_Base_Digits : constant Uint :=
17917                                Expr_Value
17918                                  (Expression
17919                                     (Parent (RTE (RE_Max_Base_Digits))));
17920
17921         begin
17922            if Digs_Val > Max_Base_Digits then
17923               Error_Msg_Uint_1 := Max_Base_Digits;
17924               Error_Msg_N ("digits value out of range, maximum is ^", Digs);
17925
17926            elsif No (Real_Range_Specification (Def)) then
17927               Error_Msg_Uint_1 := Max_Digs_Val;
17928               Error_Msg_N ("types with more than ^ digits need range spec "
17929                 & "(RM 3.5.7(6))", Digs);
17930            end if;
17931         end;
17932      end if;
17933
17934      --  Find a suitable type to derive from or complain and use a substitute
17935
17936      Base_Typ := Find_Base_Type;
17937
17938      --  If there are bounds given in the declaration use them as the bounds
17939      --  of the type, otherwise use the bounds of the predefined base type
17940      --  that was chosen based on the Digits value.
17941
17942      if Present (Real_Range_Specification (Def)) then
17943         Set_Scalar_Range (T, Real_Range_Specification (Def));
17944         Set_Is_Constrained (T);
17945
17946         --  The bounds of this range must be converted to machine numbers
17947         --  in accordance with RM 4.9(38).
17948
17949         Bound := Type_Low_Bound (T);
17950
17951         if Nkind (Bound) = N_Real_Literal then
17952            Set_Realval
17953              (Bound, Machine (Base_Typ, Realval (Bound), Round, Bound));
17954            Set_Is_Machine_Number (Bound);
17955         end if;
17956
17957         Bound := Type_High_Bound (T);
17958
17959         if Nkind (Bound) = N_Real_Literal then
17960            Set_Realval
17961              (Bound, Machine (Base_Typ, Realval (Bound), Round, Bound));
17962            Set_Is_Machine_Number (Bound);
17963         end if;
17964
17965      else
17966         Set_Scalar_Range (T, Scalar_Range (Base_Typ));
17967      end if;
17968
17969      --  Complete definition of implicit base and declared first subtype. The
17970      --  inheritance of the rep item chain ensures that SPARK-related pragmas
17971      --  are not clobbered when the floating point type acts as a full view of
17972      --  a private type.
17973
17974      Set_Etype              (Implicit_Base,                 Base_Typ);
17975      Set_Scalar_Range       (Implicit_Base, Scalar_Range   (Base_Typ));
17976      Set_Size_Info          (Implicit_Base,                 Base_Typ);
17977      Set_RM_Size            (Implicit_Base, RM_Size        (Base_Typ));
17978      Set_First_Rep_Item     (Implicit_Base, First_Rep_Item (Base_Typ));
17979      Set_Digits_Value       (Implicit_Base, Digits_Value   (Base_Typ));
17980      Set_Float_Rep          (Implicit_Base, Float_Rep      (Base_Typ));
17981
17982      Set_Ekind              (T, E_Floating_Point_Subtype);
17983      Set_Etype              (T,          Implicit_Base);
17984      Set_Size_Info          (T,          Implicit_Base);
17985      Set_RM_Size            (T, RM_Size (Implicit_Base));
17986      Inherit_Rep_Item_Chain (T,          Implicit_Base);
17987      Set_Digits_Value       (T, Digs_Val);
17988   end Floating_Point_Type_Declaration;
17989
17990   ----------------------------
17991   -- Get_Discriminant_Value --
17992   ----------------------------
17993
17994   --  This is the situation:
17995
17996   --  There is a non-derived type
17997
17998   --       type T0 (Dx, Dy, Dz...)
17999
18000   --  There are zero or more levels of derivation, with each derivation
18001   --  either purely inheriting the discriminants, or defining its own.
18002
18003   --       type Ti      is new Ti-1
18004   --  or
18005   --       type Ti (Dw) is new Ti-1(Dw, 1, X+Y)
18006   --  or
18007   --       subtype Ti is ...
18008
18009   --  The subtype issue is avoided by the use of Original_Record_Component,
18010   --  and the fact that derived subtypes also derive the constraints.
18011
18012   --  This chain leads back from
18013
18014   --       Typ_For_Constraint
18015
18016   --  Typ_For_Constraint has discriminants, and the value for each
18017   --  discriminant is given by its corresponding Elmt of Constraints.
18018
18019   --  Discriminant is some discriminant in this hierarchy
18020
18021   --  We need to return its value
18022
18023   --  We do this by recursively searching each level, and looking for
18024   --  Discriminant. Once we get to the bottom, we start backing up
18025   --  returning the value for it which may in turn be a discriminant
18026   --  further up, so on the backup we continue the substitution.
18027
18028   function Get_Discriminant_Value
18029     (Discriminant       : Entity_Id;
18030      Typ_For_Constraint : Entity_Id;
18031      Constraint         : Elist_Id) return Node_Id
18032   is
18033      function Root_Corresponding_Discriminant
18034        (Discr : Entity_Id) return Entity_Id;
18035      --  Given a discriminant, traverse the chain of inherited discriminants
18036      --  and return the topmost discriminant.
18037
18038      function Search_Derivation_Levels
18039        (Ti                    : Entity_Id;
18040         Discrim_Values        : Elist_Id;
18041         Stored_Discrim_Values : Boolean) return Node_Or_Entity_Id;
18042      --  This is the routine that performs the recursive search of levels
18043      --  as described above.
18044
18045      -------------------------------------
18046      -- Root_Corresponding_Discriminant --
18047      -------------------------------------
18048
18049      function Root_Corresponding_Discriminant
18050        (Discr : Entity_Id) return Entity_Id
18051      is
18052         D : Entity_Id;
18053
18054      begin
18055         D := Discr;
18056         while Present (Corresponding_Discriminant (D)) loop
18057            D := Corresponding_Discriminant (D);
18058         end loop;
18059
18060         return D;
18061      end Root_Corresponding_Discriminant;
18062
18063      ------------------------------
18064      -- Search_Derivation_Levels --
18065      ------------------------------
18066
18067      function Search_Derivation_Levels
18068        (Ti                    : Entity_Id;
18069         Discrim_Values        : Elist_Id;
18070         Stored_Discrim_Values : Boolean) return Node_Or_Entity_Id
18071      is
18072         Assoc          : Elmt_Id;
18073         Disc           : Entity_Id;
18074         Result         : Node_Or_Entity_Id;
18075         Result_Entity  : Node_Id;
18076
18077      begin
18078         --  If inappropriate type, return Error, this happens only in
18079         --  cascaded error situations, and we want to avoid a blow up.
18080
18081         if not Is_Composite_Type (Ti) or else Is_Array_Type (Ti) then
18082            return Error;
18083         end if;
18084
18085         --  Look deeper if possible. Use Stored_Constraints only for
18086         --  untagged types. For tagged types use the given constraint.
18087         --  This asymmetry needs explanation???
18088
18089         if not Stored_Discrim_Values
18090           and then Present (Stored_Constraint (Ti))
18091           and then not Is_Tagged_Type (Ti)
18092         then
18093            Result :=
18094              Search_Derivation_Levels (Ti, Stored_Constraint (Ti), True);
18095
18096         else
18097            declare
18098               Td : Entity_Id := Etype (Ti);
18099
18100            begin
18101               --  If the parent type is private, the full view may include
18102               --  renamed discriminants, and it is those stored values that
18103               --  may be needed (the partial view never has more information
18104               --  than the full view).
18105
18106               if Is_Private_Type (Td) and then Present (Full_View (Td)) then
18107                  Td := Full_View (Td);
18108               end if;
18109
18110               if Td = Ti then
18111                  Result := Discriminant;
18112
18113               else
18114                  if Present (Stored_Constraint (Ti)) then
18115                     Result :=
18116                        Search_Derivation_Levels
18117                          (Td, Stored_Constraint (Ti), True);
18118                  else
18119                     Result :=
18120                        Search_Derivation_Levels
18121                          (Td, Discrim_Values, Stored_Discrim_Values);
18122                  end if;
18123               end if;
18124            end;
18125         end if;
18126
18127         --  Extra underlying places to search, if not found above. For
18128         --  concurrent types, the relevant discriminant appears in the
18129         --  corresponding record. For a type derived from a private type
18130         --  without discriminant, the full view inherits the discriminants
18131         --  of the full view of the parent.
18132
18133         if Result = Discriminant then
18134            if Is_Concurrent_Type (Ti)
18135              and then Present (Corresponding_Record_Type (Ti))
18136            then
18137               Result :=
18138                 Search_Derivation_Levels (
18139                   Corresponding_Record_Type (Ti),
18140                   Discrim_Values,
18141                   Stored_Discrim_Values);
18142
18143            elsif Is_Private_Type (Ti)
18144              and then not Has_Discriminants (Ti)
18145              and then Present (Full_View (Ti))
18146              and then Etype (Full_View (Ti)) /= Ti
18147            then
18148               Result :=
18149                 Search_Derivation_Levels (
18150                   Full_View (Ti),
18151                   Discrim_Values,
18152                   Stored_Discrim_Values);
18153            end if;
18154         end if;
18155
18156         --  If Result is not a (reference to a) discriminant, return it,
18157         --  otherwise set Result_Entity to the discriminant.
18158
18159         if Nkind (Result) = N_Defining_Identifier then
18160            pragma Assert (Result = Discriminant);
18161            Result_Entity := Result;
18162
18163         else
18164            if not Denotes_Discriminant (Result) then
18165               return Result;
18166            end if;
18167
18168            Result_Entity := Entity (Result);
18169         end if;
18170
18171         --  See if this level of derivation actually has discriminants because
18172         --  tagged derivations can add them, hence the lower levels need not
18173         --  have any.
18174
18175         if not Has_Discriminants (Ti) then
18176            return Result;
18177         end if;
18178
18179         --  Scan Ti's discriminants for Result_Entity, and return its
18180         --  corresponding value, if any.
18181
18182         Result_Entity := Original_Record_Component (Result_Entity);
18183
18184         Assoc := First_Elmt (Discrim_Values);
18185
18186         if Stored_Discrim_Values then
18187            Disc := First_Stored_Discriminant (Ti);
18188         else
18189            Disc := First_Discriminant (Ti);
18190         end if;
18191
18192         while Present (Disc) loop
18193
18194            --  If no further associations return the discriminant, value will
18195            --  be found on the second pass.
18196
18197            if No (Assoc) then
18198               return Result;
18199            end if;
18200
18201            if Original_Record_Component (Disc) = Result_Entity then
18202               return Node (Assoc);
18203            end if;
18204
18205            Next_Elmt (Assoc);
18206
18207            if Stored_Discrim_Values then
18208               Next_Stored_Discriminant (Disc);
18209            else
18210               Next_Discriminant (Disc);
18211            end if;
18212         end loop;
18213
18214         --  Could not find it
18215
18216         return Result;
18217      end Search_Derivation_Levels;
18218
18219      --  Local Variables
18220
18221      Result : Node_Or_Entity_Id;
18222
18223   --  Start of processing for Get_Discriminant_Value
18224
18225   begin
18226      --  ??? This routine is a gigantic mess and will be deleted. For the
18227      --  time being just test for the trivial case before calling recurse.
18228
18229      --  We are now celebrating the 20th anniversary of this comment!
18230
18231      if Base_Type (Scope (Discriminant)) = Base_Type (Typ_For_Constraint) then
18232         declare
18233            D : Entity_Id;
18234            E : Elmt_Id;
18235
18236         begin
18237            D := First_Discriminant (Typ_For_Constraint);
18238            E := First_Elmt (Constraint);
18239            while Present (D) loop
18240               if Chars (D) = Chars (Discriminant) then
18241                  return Node (E);
18242               end if;
18243
18244               Next_Discriminant (D);
18245               Next_Elmt (E);
18246            end loop;
18247         end;
18248      end if;
18249
18250      Result := Search_Derivation_Levels
18251        (Typ_For_Constraint, Constraint, False);
18252
18253      --  ??? hack to disappear when this routine is gone
18254
18255      if Nkind (Result) = N_Defining_Identifier then
18256         declare
18257            D : Entity_Id;
18258            E : Elmt_Id;
18259
18260         begin
18261            D := First_Discriminant (Typ_For_Constraint);
18262            E := First_Elmt (Constraint);
18263            while Present (D) loop
18264               if Root_Corresponding_Discriminant (D) = Discriminant then
18265                  return Node (E);
18266               end if;
18267
18268               Next_Discriminant (D);
18269               Next_Elmt (E);
18270            end loop;
18271         end;
18272      end if;
18273
18274      pragma Assert (Nkind (Result) /= N_Defining_Identifier);
18275      return Result;
18276   end Get_Discriminant_Value;
18277
18278   --------------------------
18279   -- Has_Range_Constraint --
18280   --------------------------
18281
18282   function Has_Range_Constraint (N : Node_Id) return Boolean is
18283      C : constant Node_Id := Constraint (N);
18284
18285   begin
18286      if Nkind (C) = N_Range_Constraint then
18287         return True;
18288
18289      elsif Nkind (C) = N_Digits_Constraint then
18290         return
18291            Is_Decimal_Fixed_Point_Type (Entity (Subtype_Mark (N)))
18292              or else Present (Range_Constraint (C));
18293
18294      elsif Nkind (C) = N_Delta_Constraint then
18295         return Present (Range_Constraint (C));
18296
18297      else
18298         return False;
18299      end if;
18300   end Has_Range_Constraint;
18301
18302   ------------------------
18303   -- Inherit_Components --
18304   ------------------------
18305
18306   function Inherit_Components
18307     (N             : Node_Id;
18308      Parent_Base   : Entity_Id;
18309      Derived_Base  : Entity_Id;
18310      Is_Tagged     : Boolean;
18311      Inherit_Discr : Boolean;
18312      Discs         : Elist_Id) return Elist_Id
18313   is
18314      Assoc_List : constant Elist_Id := New_Elmt_List;
18315
18316      procedure Inherit_Component
18317        (Old_C          : Entity_Id;
18318         Plain_Discrim  : Boolean := False;
18319         Stored_Discrim : Boolean := False);
18320      --  Inherits component Old_C from Parent_Base to the Derived_Base. If
18321      --  Plain_Discrim is True, Old_C is a discriminant. If Stored_Discrim is
18322      --  True, Old_C is a stored discriminant. If they are both false then
18323      --  Old_C is a regular component.
18324
18325      -----------------------
18326      -- Inherit_Component --
18327      -----------------------
18328
18329      procedure Inherit_Component
18330        (Old_C          : Entity_Id;
18331         Plain_Discrim  : Boolean := False;
18332         Stored_Discrim : Boolean := False)
18333      is
18334         procedure Set_Anonymous_Type (Id : Entity_Id);
18335         --  Id denotes the entity of an access discriminant or anonymous
18336         --  access component. Set the type of Id to either the same type of
18337         --  Old_C or create a new one depending on whether the parent and
18338         --  the child types are in the same scope.
18339
18340         ------------------------
18341         -- Set_Anonymous_Type --
18342         ------------------------
18343
18344         procedure Set_Anonymous_Type (Id : Entity_Id) is
18345            Old_Typ : constant Entity_Id := Etype (Old_C);
18346
18347         begin
18348            if Scope (Parent_Base) = Scope (Derived_Base) then
18349               Set_Etype (Id, Old_Typ);
18350
18351            --  The parent and the derived type are in two different scopes.
18352            --  Reuse the type of the original discriminant / component by
18353            --  copying it in order to preserve all attributes.
18354
18355            else
18356               declare
18357                  Typ : constant Entity_Id := New_Copy (Old_Typ);
18358
18359               begin
18360                  Set_Etype (Id, Typ);
18361
18362                  --  Since we do not generate component declarations for
18363                  --  inherited components, associate the itype with the
18364                  --  derived type.
18365
18366                  Set_Associated_Node_For_Itype (Typ, Parent (Derived_Base));
18367                  Set_Scope                     (Typ, Derived_Base);
18368               end;
18369            end if;
18370         end Set_Anonymous_Type;
18371
18372         --  Local variables and constants
18373
18374         New_C : constant Entity_Id := New_Copy (Old_C);
18375
18376         Corr_Discrim : Entity_Id;
18377         Discrim      : Entity_Id;
18378
18379      --  Start of processing for Inherit_Component
18380
18381      begin
18382         pragma Assert (not Is_Tagged or not Stored_Discrim);
18383
18384         Set_Parent (New_C, Parent (Old_C));
18385
18386         --  Regular discriminants and components must be inserted in the scope
18387         --  of the Derived_Base. Do it here.
18388
18389         if not Stored_Discrim then
18390            Enter_Name (New_C);
18391         end if;
18392
18393         --  For tagged types the Original_Record_Component must point to
18394         --  whatever this field was pointing to in the parent type. This has
18395         --  already been achieved by the call to New_Copy above.
18396
18397         if not Is_Tagged then
18398            Set_Original_Record_Component (New_C, New_C);
18399            Set_Corresponding_Record_Component (New_C, Old_C);
18400         end if;
18401
18402         --  Set the proper type of an access discriminant
18403
18404         if Ekind (New_C) = E_Discriminant
18405           and then Ekind (Etype (New_C)) = E_Anonymous_Access_Type
18406         then
18407            Set_Anonymous_Type (New_C);
18408         end if;
18409
18410         --  If we have inherited a component then see if its Etype contains
18411         --  references to Parent_Base discriminants. In this case, replace
18412         --  these references with the constraints given in Discs. We do not
18413         --  do this for the partial view of private types because this is
18414         --  not needed (only the components of the full view will be used
18415         --  for code generation) and cause problem. We also avoid this
18416         --  transformation in some error situations.
18417
18418         if Ekind (New_C) = E_Component then
18419
18420            --  Set the proper type of an anonymous access component
18421
18422            if Ekind (Etype (New_C)) = E_Anonymous_Access_Type then
18423               Set_Anonymous_Type (New_C);
18424
18425            elsif (Is_Private_Type (Derived_Base)
18426                    and then not Is_Generic_Type (Derived_Base))
18427              or else (Is_Empty_Elmt_List (Discs)
18428                        and then not Expander_Active)
18429            then
18430               Set_Etype (New_C, Etype (Old_C));
18431
18432            else
18433               --  The current component introduces a circularity of the
18434               --  following kind:
18435
18436               --     limited with Pack_2;
18437               --     package Pack_1 is
18438               --        type T_1 is tagged record
18439               --           Comp : access Pack_2.T_2;
18440               --           ...
18441               --        end record;
18442               --     end Pack_1;
18443
18444               --     with Pack_1;
18445               --     package Pack_2 is
18446               --        type T_2 is new Pack_1.T_1 with ...;
18447               --     end Pack_2;
18448
18449               Set_Etype
18450                 (New_C,
18451                  Constrain_Component_Type
18452                    (Old_C, Derived_Base, N, Parent_Base, Discs));
18453            end if;
18454         end if;
18455
18456         --  In derived tagged types it is illegal to reference a non
18457         --  discriminant component in the parent type. To catch this, mark
18458         --  these components with an Ekind of E_Void. This will be reset in
18459         --  Record_Type_Definition after processing the record extension of
18460         --  the derived type.
18461
18462         --  If the declaration is a private extension, there is no further
18463         --  record extension to process, and the components retain their
18464         --  current kind, because they are visible at this point.
18465
18466         if Is_Tagged and then Ekind (New_C) = E_Component
18467           and then Nkind (N) /= N_Private_Extension_Declaration
18468         then
18469            Set_Ekind (New_C, E_Void);
18470         end if;
18471
18472         if Plain_Discrim then
18473            Set_Corresponding_Discriminant (New_C, Old_C);
18474            Build_Discriminal (New_C);
18475
18476         --  If we are explicitly inheriting a stored discriminant it will be
18477         --  completely hidden.
18478
18479         elsif Stored_Discrim then
18480            Set_Corresponding_Discriminant (New_C, Empty);
18481            Set_Discriminal (New_C, Empty);
18482            Set_Is_Completely_Hidden (New_C);
18483
18484            --  Set the Original_Record_Component of each discriminant in the
18485            --  derived base to point to the corresponding stored that we just
18486            --  created.
18487
18488            Discrim := First_Discriminant (Derived_Base);
18489            while Present (Discrim) loop
18490               Corr_Discrim := Corresponding_Discriminant (Discrim);
18491
18492               --  Corr_Discrim could be missing in an error situation
18493
18494               if Present (Corr_Discrim)
18495                 and then Original_Record_Component (Corr_Discrim) = Old_C
18496               then
18497                  Set_Original_Record_Component (Discrim, New_C);
18498                  Set_Corresponding_Record_Component (Discrim, Empty);
18499               end if;
18500
18501               Next_Discriminant (Discrim);
18502            end loop;
18503
18504            Append_Entity (New_C, Derived_Base);
18505         end if;
18506
18507         if not Is_Tagged then
18508            Append_Elmt (Old_C, Assoc_List);
18509            Append_Elmt (New_C, Assoc_List);
18510         end if;
18511      end Inherit_Component;
18512
18513      --  Variables local to Inherit_Component
18514
18515      Loc : constant Source_Ptr := Sloc (N);
18516
18517      Parent_Discrim : Entity_Id;
18518      Stored_Discrim : Entity_Id;
18519      D              : Entity_Id;
18520      Component      : Entity_Id;
18521
18522   --  Start of processing for Inherit_Components
18523
18524   begin
18525      if not Is_Tagged then
18526         Append_Elmt (Parent_Base,  Assoc_List);
18527         Append_Elmt (Derived_Base, Assoc_List);
18528      end if;
18529
18530      --  Inherit parent discriminants if needed
18531
18532      if Inherit_Discr then
18533         Parent_Discrim := First_Discriminant (Parent_Base);
18534         while Present (Parent_Discrim) loop
18535            Inherit_Component (Parent_Discrim, Plain_Discrim => True);
18536            Next_Discriminant (Parent_Discrim);
18537         end loop;
18538      end if;
18539
18540      --  Create explicit stored discrims for untagged types when necessary
18541
18542      if not Has_Unknown_Discriminants (Derived_Base)
18543        and then Has_Discriminants (Parent_Base)
18544        and then not Is_Tagged
18545        and then
18546          (not Inherit_Discr
18547            or else First_Discriminant (Parent_Base) /=
18548                    First_Stored_Discriminant (Parent_Base))
18549      then
18550         Stored_Discrim := First_Stored_Discriminant (Parent_Base);
18551         while Present (Stored_Discrim) loop
18552            Inherit_Component (Stored_Discrim, Stored_Discrim => True);
18553            Next_Stored_Discriminant (Stored_Discrim);
18554         end loop;
18555      end if;
18556
18557      --  See if we can apply the second transformation for derived types, as
18558      --  explained in point 6. in the comments above Build_Derived_Record_Type
18559      --  This is achieved by appending Derived_Base discriminants into Discs,
18560      --  which has the side effect of returning a non empty Discs list to the
18561      --  caller of Inherit_Components, which is what we want. This must be
18562      --  done for private derived types if there are explicit stored
18563      --  discriminants, to ensure that we can retrieve the values of the
18564      --  constraints provided in the ancestors.
18565
18566      if Inherit_Discr
18567        and then Is_Empty_Elmt_List (Discs)
18568        and then Present (First_Discriminant (Derived_Base))
18569        and then
18570          (not Is_Private_Type (Derived_Base)
18571            or else Is_Completely_Hidden
18572                      (First_Stored_Discriminant (Derived_Base))
18573            or else Is_Generic_Type (Derived_Base))
18574      then
18575         D := First_Discriminant (Derived_Base);
18576         while Present (D) loop
18577            Append_Elmt (New_Occurrence_Of (D, Loc), Discs);
18578            Next_Discriminant (D);
18579         end loop;
18580      end if;
18581
18582      --  Finally, inherit non-discriminant components unless they are not
18583      --  visible because defined or inherited from the full view of the
18584      --  parent. Don't inherit the _parent field of the parent type.
18585
18586      Component := First_Entity (Parent_Base);
18587      while Present (Component) loop
18588
18589         --  Ada 2005 (AI-251): Do not inherit components associated with
18590         --  secondary tags of the parent.
18591
18592         if Ekind (Component) = E_Component
18593           and then Present (Related_Type (Component))
18594         then
18595            null;
18596
18597         elsif Ekind (Component) /= E_Component
18598           or else Chars (Component) = Name_uParent
18599         then
18600            null;
18601
18602         --  If the derived type is within the parent type's declarative
18603         --  region, then the components can still be inherited even though
18604         --  they aren't visible at this point. This can occur for cases
18605         --  such as within public child units where the components must
18606         --  become visible upon entering the child unit's private part.
18607
18608         elsif not Is_Visible_Component (Component)
18609           and then not In_Open_Scopes (Scope (Parent_Base))
18610         then
18611            null;
18612
18613         elsif Ekind_In (Derived_Base, E_Private_Type,
18614                                       E_Limited_Private_Type)
18615         then
18616            null;
18617
18618         else
18619            Inherit_Component (Component);
18620         end if;
18621
18622         Next_Entity (Component);
18623      end loop;
18624
18625      --  For tagged derived types, inherited discriminants cannot be used in
18626      --  component declarations of the record extension part. To achieve this
18627      --  we mark the inherited discriminants as not visible.
18628
18629      if Is_Tagged and then Inherit_Discr then
18630         D := First_Discriminant (Derived_Base);
18631         while Present (D) loop
18632            Set_Is_Immediately_Visible (D, False);
18633            Next_Discriminant (D);
18634         end loop;
18635      end if;
18636
18637      return Assoc_List;
18638   end Inherit_Components;
18639
18640   -----------------------------
18641   -- Inherit_Predicate_Flags --
18642   -----------------------------
18643
18644   procedure Inherit_Predicate_Flags (Subt, Par : Entity_Id) is
18645   begin
18646      if Present (Predicate_Function (Subt)) then
18647         return;
18648      end if;
18649
18650      Set_Has_Predicates (Subt, Has_Predicates (Par));
18651      Set_Has_Static_Predicate_Aspect
18652        (Subt, Has_Static_Predicate_Aspect (Par));
18653      Set_Has_Dynamic_Predicate_Aspect
18654        (Subt, Has_Dynamic_Predicate_Aspect (Par));
18655
18656      --  A named subtype does not inherit the predicate function of its
18657      --  parent but an itype declared for a loop index needs the discrete
18658      --  predicate information of its parent to execute the loop properly.
18659      --  A non-discrete type may has a static predicate (for example True)
18660      --  but has no static_discrete_predicate.
18661
18662      if Is_Itype (Subt) and then Present (Predicate_Function (Par)) then
18663         Set_Subprograms_For_Type (Subt, Subprograms_For_Type (Par));
18664
18665         if Has_Static_Predicate (Par) and then Is_Discrete_Type (Par) then
18666            Set_Static_Discrete_Predicate
18667              (Subt, Static_Discrete_Predicate (Par));
18668         end if;
18669      end if;
18670   end Inherit_Predicate_Flags;
18671
18672   ----------------------
18673   -- Is_EVF_Procedure --
18674   ----------------------
18675
18676   function Is_EVF_Procedure (Subp : Entity_Id) return Boolean is
18677      Formal : Entity_Id;
18678
18679   begin
18680      --  Examine the formals of an Extensions_Visible False procedure looking
18681      --  for a controlling OUT parameter.
18682
18683      if Ekind (Subp) = E_Procedure
18684        and then Extensions_Visible_Status (Subp) = Extensions_Visible_False
18685      then
18686         Formal := First_Formal (Subp);
18687         while Present (Formal) loop
18688            if Ekind (Formal) = E_Out_Parameter
18689              and then Is_Controlling_Formal (Formal)
18690            then
18691               return True;
18692            end if;
18693
18694            Next_Formal (Formal);
18695         end loop;
18696      end if;
18697
18698      return False;
18699   end Is_EVF_Procedure;
18700
18701   -----------------------
18702   -- Is_Null_Extension --
18703   -----------------------
18704
18705   function Is_Null_Extension (T : Entity_Id) return Boolean is
18706      Type_Decl : constant Node_Id := Parent (Base_Type (T));
18707      Comp_List : Node_Id;
18708      Comp      : Node_Id;
18709
18710   begin
18711      if Nkind (Type_Decl) /= N_Full_Type_Declaration
18712        or else not Is_Tagged_Type (T)
18713        or else Nkind (Type_Definition (Type_Decl)) /=
18714                                              N_Derived_Type_Definition
18715        or else No (Record_Extension_Part (Type_Definition (Type_Decl)))
18716      then
18717         return False;
18718      end if;
18719
18720      Comp_List :=
18721        Component_List (Record_Extension_Part (Type_Definition (Type_Decl)));
18722
18723      if Present (Discriminant_Specifications (Type_Decl)) then
18724         return False;
18725
18726      elsif Present (Comp_List)
18727        and then Is_Non_Empty_List (Component_Items (Comp_List))
18728      then
18729         Comp := First (Component_Items (Comp_List));
18730
18731         --  Only user-defined components are relevant. The component list
18732         --  may also contain a parent component and internal components
18733         --  corresponding to secondary tags, but these do not determine
18734         --  whether this is a null extension.
18735
18736         while Present (Comp) loop
18737            if Comes_From_Source (Comp) then
18738               return False;
18739            end if;
18740
18741            Next (Comp);
18742         end loop;
18743
18744         return True;
18745
18746      else
18747         return True;
18748      end if;
18749   end Is_Null_Extension;
18750
18751   ------------------------------
18752   -- Is_Valid_Constraint_Kind --
18753   ------------------------------
18754
18755   function Is_Valid_Constraint_Kind
18756     (T_Kind          : Type_Kind;
18757      Constraint_Kind : Node_Kind) return Boolean
18758   is
18759   begin
18760      case T_Kind is
18761         when Enumeration_Kind
18762            | Integer_Kind
18763         =>
18764            return Constraint_Kind = N_Range_Constraint;
18765
18766         when Decimal_Fixed_Point_Kind =>
18767            return Nkind_In (Constraint_Kind, N_Digits_Constraint,
18768                                              N_Range_Constraint);
18769
18770         when Ordinary_Fixed_Point_Kind =>
18771            return Nkind_In (Constraint_Kind, N_Delta_Constraint,
18772                                              N_Range_Constraint);
18773
18774         when Float_Kind =>
18775            return Nkind_In (Constraint_Kind, N_Digits_Constraint,
18776                                              N_Range_Constraint);
18777
18778         when Access_Kind
18779            | Array_Kind
18780            | Class_Wide_Kind
18781            | Concurrent_Kind
18782            | Private_Kind
18783            | E_Incomplete_Type
18784            | E_Record_Subtype
18785            | E_Record_Type
18786         =>
18787            return Constraint_Kind = N_Index_Or_Discriminant_Constraint;
18788
18789         when others =>
18790            return True; -- Error will be detected later
18791      end case;
18792   end Is_Valid_Constraint_Kind;
18793
18794   --------------------------
18795   -- Is_Visible_Component --
18796   --------------------------
18797
18798   function Is_Visible_Component
18799     (C : Entity_Id;
18800      N : Node_Id := Empty) return Boolean
18801   is
18802      Original_Comp : Entity_Id := Empty;
18803      Original_Type : Entity_Id;
18804      Type_Scope    : Entity_Id;
18805
18806      function Is_Local_Type (Typ : Entity_Id) return Boolean;
18807      --  Check whether parent type of inherited component is declared locally,
18808      --  possibly within a nested package or instance. The current scope is
18809      --  the derived record itself.
18810
18811      -------------------
18812      -- Is_Local_Type --
18813      -------------------
18814
18815      function Is_Local_Type (Typ : Entity_Id) return Boolean is
18816         Scop : Entity_Id;
18817
18818      begin
18819         Scop := Scope (Typ);
18820         while Present (Scop)
18821           and then Scop /= Standard_Standard
18822         loop
18823            if Scop = Scope (Current_Scope) then
18824               return True;
18825            end if;
18826
18827            Scop := Scope (Scop);
18828         end loop;
18829
18830         return False;
18831      end Is_Local_Type;
18832
18833   --  Start of processing for Is_Visible_Component
18834
18835   begin
18836      if Ekind_In (C, E_Component, E_Discriminant) then
18837         Original_Comp := Original_Record_Component (C);
18838      end if;
18839
18840      if No (Original_Comp) then
18841
18842         --  Premature usage, or previous error
18843
18844         return False;
18845
18846      else
18847         Original_Type := Scope (Original_Comp);
18848         Type_Scope    := Scope (Base_Type (Scope (C)));
18849      end if;
18850
18851      --  This test only concerns tagged types
18852
18853      if not Is_Tagged_Type (Original_Type) then
18854
18855         --  Check if this is a renamed discriminant (hidden either by the
18856         --  derived type or by some ancestor), unless we are analyzing code
18857         --  generated by the expander since it may reference such components
18858         --  (for example see the expansion of Deep_Adjust).
18859
18860         if Ekind (C) = E_Discriminant and then Present (N) then
18861            return
18862              not Comes_From_Source (N)
18863                or else not Is_Completely_Hidden (C);
18864         else
18865            return True;
18866         end if;
18867
18868      --  If it is _Parent or _Tag, there is no visibility issue
18869
18870      elsif not Comes_From_Source (Original_Comp) then
18871         return True;
18872
18873      --  Discriminants are visible unless the (private) type has unknown
18874      --  discriminants. If the discriminant reference is inserted for a
18875      --  discriminant check on a full view it is also visible.
18876
18877      elsif Ekind (Original_Comp) = E_Discriminant
18878        and then
18879          (not Has_Unknown_Discriminants (Original_Type)
18880            or else (Present (N)
18881                      and then Nkind (N) = N_Selected_Component
18882                      and then Nkind (Prefix (N)) = N_Type_Conversion
18883                      and then not Comes_From_Source (Prefix (N))))
18884      then
18885         return True;
18886
18887      --  In the body of an instantiation, check the visibility of a component
18888      --  in case it has a homograph that is a primitive operation of a private
18889      --  type which was not visible in the generic unit.
18890
18891      --  Should Is_Prefixed_Call be propagated from template to instance???
18892
18893      elsif In_Instance_Body then
18894         if not Is_Tagged_Type (Original_Type)
18895           or else not Is_Private_Type (Original_Type)
18896         then
18897            return True;
18898
18899         else
18900            declare
18901               Subp_Elmt : Elmt_Id;
18902
18903            begin
18904               Subp_Elmt := First_Elmt (Primitive_Operations (Original_Type));
18905               while Present (Subp_Elmt) loop
18906
18907                  --  The component is hidden by a primitive operation
18908
18909                  if Chars (Node (Subp_Elmt)) = Chars (C) then
18910                     return False;
18911                  end if;
18912
18913                  Next_Elmt (Subp_Elmt);
18914               end loop;
18915
18916               return True;
18917            end;
18918         end if;
18919
18920      --  If the component has been declared in an ancestor which is currently
18921      --  a private type, then it is not visible. The same applies if the
18922      --  component's containing type is not in an open scope and the original
18923      --  component's enclosing type is a visible full view of a private type
18924      --  (which can occur in cases where an attempt is being made to reference
18925      --  a component in a sibling package that is inherited from a visible
18926      --  component of a type in an ancestor package; the component in the
18927      --  sibling package should not be visible even though the component it
18928      --  inherited from is visible). This does not apply however in the case
18929      --  where the scope of the type is a private child unit, or when the
18930      --  parent comes from a local package in which the ancestor is currently
18931      --  visible. The latter suppression of visibility is needed for cases
18932      --  that are tested in B730006.
18933
18934      elsif Is_Private_Type (Original_Type)
18935        or else
18936          (not Is_Private_Descendant (Type_Scope)
18937            and then not In_Open_Scopes (Type_Scope)
18938            and then Has_Private_Declaration (Original_Type))
18939      then
18940         --  If the type derives from an entity in a formal package, there
18941         --  are no additional visible components.
18942
18943         if Nkind (Original_Node (Unit_Declaration_Node (Type_Scope))) =
18944            N_Formal_Package_Declaration
18945         then
18946            return False;
18947
18948         --  if we are not in the private part of the current package, there
18949         --  are no additional visible components.
18950
18951         elsif Ekind (Scope (Current_Scope)) = E_Package
18952           and then not In_Private_Part (Scope (Current_Scope))
18953         then
18954            return False;
18955         else
18956            return
18957              Is_Child_Unit (Cunit_Entity (Current_Sem_Unit))
18958                and then In_Open_Scopes (Scope (Original_Type))
18959                and then Is_Local_Type (Type_Scope);
18960         end if;
18961
18962      --  There is another weird way in which a component may be invisible when
18963      --  the private and the full view are not derived from the same ancestor.
18964      --  Here is an example :
18965
18966      --       type A1 is tagged      record F1 : integer; end record;
18967      --       type A2 is new A1 with record F2 : integer; end record;
18968      --       type T is new A1 with private;
18969      --     private
18970      --       type T is new A2 with null record;
18971
18972      --  In this case, the full view of T inherits F1 and F2 but the private
18973      --  view inherits only F1
18974
18975      else
18976         declare
18977            Ancestor : Entity_Id := Scope (C);
18978
18979         begin
18980            loop
18981               if Ancestor = Original_Type then
18982                  return True;
18983
18984               --  The ancestor may have a partial view of the original type,
18985               --  but if the full view is in scope, as in a child body, the
18986               --  component is visible.
18987
18988               elsif In_Private_Part (Scope (Original_Type))
18989                 and then Full_View (Ancestor) = Original_Type
18990               then
18991                  return True;
18992
18993               elsif Ancestor = Etype (Ancestor) then
18994
18995                  --  No further ancestors to examine
18996
18997                  return False;
18998               end if;
18999
19000               Ancestor := Etype (Ancestor);
19001            end loop;
19002         end;
19003      end if;
19004   end Is_Visible_Component;
19005
19006   --------------------------
19007   -- Make_Class_Wide_Type --
19008   --------------------------
19009
19010   procedure Make_Class_Wide_Type (T : Entity_Id) is
19011      CW_Type : Entity_Id;
19012      CW_Name : Name_Id;
19013      Next_E  : Entity_Id;
19014      Prev_E  : Entity_Id;
19015
19016   begin
19017      if Present (Class_Wide_Type (T)) then
19018
19019         --  The class-wide type is a partially decorated entity created for a
19020         --  unanalyzed tagged type referenced through a limited with clause.
19021         --  When the tagged type is analyzed, its class-wide type needs to be
19022         --  redecorated. Note that we reuse the entity created by Decorate_
19023         --  Tagged_Type in order to preserve all links.
19024
19025         if Materialize_Entity (Class_Wide_Type (T)) then
19026            CW_Type := Class_Wide_Type (T);
19027            Set_Materialize_Entity (CW_Type, False);
19028
19029         --  The class wide type can have been defined by the partial view, in
19030         --  which case everything is already done.
19031
19032         else
19033            return;
19034         end if;
19035
19036      --  Default case, we need to create a new class-wide type
19037
19038      else
19039         CW_Type :=
19040           New_External_Entity (E_Void, Scope (T), Sloc (T), T, 'C', 0, 'T');
19041      end if;
19042
19043      --  Inherit root type characteristics
19044
19045      CW_Name := Chars (CW_Type);
19046      Next_E  := Next_Entity (CW_Type);
19047      Prev_E  := Prev_Entity (CW_Type);
19048      Copy_Node (T, CW_Type);
19049      Set_Comes_From_Source (CW_Type, False);
19050      Set_Chars (CW_Type, CW_Name);
19051      Set_Parent (CW_Type, Parent (T));
19052      Set_Prev_Entity (CW_Type, Prev_E);
19053      Set_Next_Entity (CW_Type, Next_E);
19054
19055      --  Ensure we have a new freeze node for the class-wide type. The partial
19056      --  view may have freeze action of its own, requiring a proper freeze
19057      --  node, and the same freeze node cannot be shared between the two
19058      --  types.
19059
19060      Set_Has_Delayed_Freeze (CW_Type);
19061      Set_Freeze_Node (CW_Type, Empty);
19062
19063      --  Customize the class-wide type: It has no prim. op., it cannot be
19064      --  abstract, its Etype points back to the specific root type, and it
19065      --  cannot have any invariants.
19066
19067      Set_Ekind                       (CW_Type, E_Class_Wide_Type);
19068      Set_Is_Tagged_Type              (CW_Type, True);
19069      Set_Direct_Primitive_Operations (CW_Type, New_Elmt_List);
19070      Set_Is_Abstract_Type            (CW_Type, False);
19071      Set_Is_Constrained              (CW_Type, False);
19072      Set_Is_First_Subtype            (CW_Type, Is_First_Subtype (T));
19073      Set_Default_SSO                 (CW_Type);
19074      Set_Has_Inheritable_Invariants  (CW_Type, False);
19075      Set_Has_Inherited_Invariants    (CW_Type, False);
19076      Set_Has_Own_Invariants          (CW_Type, False);
19077
19078      if Ekind (T) = E_Class_Wide_Subtype then
19079         Set_Etype (CW_Type, Etype (Base_Type (T)));
19080      else
19081         Set_Etype (CW_Type, T);
19082      end if;
19083
19084      Set_No_Tagged_Streams_Pragma (CW_Type, No_Tagged_Streams);
19085
19086      --  If this is the class_wide type of a constrained subtype, it does
19087      --  not have discriminants.
19088
19089      Set_Has_Discriminants (CW_Type,
19090        Has_Discriminants (T) and then not Is_Constrained (T));
19091
19092      Set_Has_Unknown_Discriminants (CW_Type, True);
19093      Set_Class_Wide_Type (T, CW_Type);
19094      Set_Equivalent_Type (CW_Type, Empty);
19095
19096      --  The class-wide type of a class-wide type is itself (RM 3.9(14))
19097
19098      Set_Class_Wide_Type (CW_Type, CW_Type);
19099   end Make_Class_Wide_Type;
19100
19101   ----------------
19102   -- Make_Index --
19103   ----------------
19104
19105   procedure Make_Index
19106     (N            : Node_Id;
19107      Related_Nod  : Node_Id;
19108      Related_Id   : Entity_Id := Empty;
19109      Suffix_Index : Nat       := 1;
19110      In_Iter_Schm : Boolean   := False)
19111   is
19112      R      : Node_Id;
19113      T      : Entity_Id;
19114      Def_Id : Entity_Id := Empty;
19115      Found  : Boolean := False;
19116
19117   begin
19118      --  For a discrete range used in a constrained array definition and
19119      --  defined by a range, an implicit conversion to the predefined type
19120      --  INTEGER is assumed if each bound is either a numeric literal, a named
19121      --  number, or an attribute, and the type of both bounds (prior to the
19122      --  implicit conversion) is the type universal_integer. Otherwise, both
19123      --  bounds must be of the same discrete type, other than universal
19124      --  integer; this type must be determinable independently of the
19125      --  context, but using the fact that the type must be discrete and that
19126      --  both bounds must have the same type.
19127
19128      --  Character literals also have a universal type in the absence of
19129      --  of additional context,  and are resolved to Standard_Character.
19130
19131      if Nkind (N) = N_Range then
19132
19133         --  The index is given by a range constraint. The bounds are known
19134         --  to be of a consistent type.
19135
19136         if not Is_Overloaded (N) then
19137            T := Etype (N);
19138
19139            --  For universal bounds, choose the specific predefined type
19140
19141            if T = Universal_Integer then
19142               T := Standard_Integer;
19143
19144            elsif T = Any_Character then
19145               Ambiguous_Character (Low_Bound (N));
19146
19147               T := Standard_Character;
19148            end if;
19149
19150         --  The node may be overloaded because some user-defined operators
19151         --  are available, but if a universal interpretation exists it is
19152         --  also the selected one.
19153
19154         elsif Universal_Interpretation (N) = Universal_Integer then
19155            T := Standard_Integer;
19156
19157         else
19158            T := Any_Type;
19159
19160            declare
19161               Ind : Interp_Index;
19162               It  : Interp;
19163
19164            begin
19165               Get_First_Interp (N, Ind, It);
19166               while Present (It.Typ) loop
19167                  if Is_Discrete_Type (It.Typ) then
19168
19169                     if Found
19170                       and then not Covers (It.Typ, T)
19171                       and then not Covers (T, It.Typ)
19172                     then
19173                        Error_Msg_N ("ambiguous bounds in discrete range", N);
19174                        exit;
19175                     else
19176                        T := It.Typ;
19177                        Found := True;
19178                     end if;
19179                  end if;
19180
19181                  Get_Next_Interp (Ind, It);
19182               end loop;
19183
19184               if T = Any_Type then
19185                  Error_Msg_N ("discrete type required for range", N);
19186                  Set_Etype (N, Any_Type);
19187                  return;
19188
19189               elsif T = Universal_Integer then
19190                  T := Standard_Integer;
19191               end if;
19192            end;
19193         end if;
19194
19195         if not Is_Discrete_Type (T) then
19196            Error_Msg_N ("discrete type required for range", N);
19197            Set_Etype (N, Any_Type);
19198            return;
19199         end if;
19200
19201         if Nkind (Low_Bound (N)) = N_Attribute_Reference
19202           and then Attribute_Name (Low_Bound (N)) = Name_First
19203           and then Is_Entity_Name (Prefix (Low_Bound (N)))
19204           and then Is_Type (Entity (Prefix (Low_Bound (N))))
19205           and then Is_Discrete_Type (Entity (Prefix (Low_Bound (N))))
19206         then
19207            --  The type of the index will be the type of the prefix, as long
19208            --  as the upper bound is 'Last of the same type.
19209
19210            Def_Id := Entity (Prefix (Low_Bound (N)));
19211
19212            if Nkind (High_Bound (N)) /= N_Attribute_Reference
19213              or else Attribute_Name (High_Bound (N)) /= Name_Last
19214              or else not Is_Entity_Name (Prefix (High_Bound (N)))
19215              or else Entity (Prefix (High_Bound (N))) /= Def_Id
19216            then
19217               Def_Id := Empty;
19218            end if;
19219         end if;
19220
19221         R := N;
19222         Process_Range_Expr_In_Decl (R, T, In_Iter_Schm => In_Iter_Schm);
19223
19224      elsif Nkind (N) = N_Subtype_Indication then
19225
19226         --  The index is given by a subtype with a range constraint
19227
19228         T := Base_Type (Entity (Subtype_Mark (N)));
19229
19230         if not Is_Discrete_Type (T) then
19231            Error_Msg_N ("discrete type required for range", N);
19232            Set_Etype (N, Any_Type);
19233            return;
19234         end if;
19235
19236         R := Range_Expression (Constraint (N));
19237
19238         Resolve (R, T);
19239         Process_Range_Expr_In_Decl
19240           (R, Entity (Subtype_Mark (N)), In_Iter_Schm => In_Iter_Schm);
19241
19242      elsif Nkind (N) = N_Attribute_Reference then
19243
19244         --  Catch beginner's error (use of attribute other than 'Range)
19245
19246         if Attribute_Name (N) /= Name_Range then
19247            Error_Msg_N ("expect attribute ''Range", N);
19248            Set_Etype (N, Any_Type);
19249            return;
19250         end if;
19251
19252         --  If the node denotes the range of a type mark, that is also the
19253         --  resulting type, and we do not need to create an Itype for it.
19254
19255         if Is_Entity_Name (Prefix (N))
19256           and then Comes_From_Source (N)
19257           and then Is_Type (Entity (Prefix (N)))
19258           and then Is_Discrete_Type (Entity (Prefix (N)))
19259         then
19260            Def_Id := Entity (Prefix (N));
19261         end if;
19262
19263         Analyze_And_Resolve (N);
19264         T := Etype (N);
19265         R := N;
19266
19267      --  If none of the above, must be a subtype. We convert this to a
19268      --  range attribute reference because in the case of declared first
19269      --  named subtypes, the types in the range reference can be different
19270      --  from the type of the entity. A range attribute normalizes the
19271      --  reference and obtains the correct types for the bounds.
19272
19273      --  This transformation is in the nature of an expansion, is only
19274      --  done if expansion is active. In particular, it is not done on
19275      --  formal generic types,  because we need to retain the name of the
19276      --  original index for instantiation purposes.
19277
19278      else
19279         if not Is_Entity_Name (N) or else not Is_Type (Entity (N)) then
19280            Error_Msg_N ("invalid subtype mark in discrete range ", N);
19281            Set_Etype (N, Any_Integer);
19282            return;
19283
19284         else
19285            --  The type mark may be that of an incomplete type. It is only
19286            --  now that we can get the full view, previous analysis does
19287            --  not look specifically for a type mark.
19288
19289            Set_Entity (N, Get_Full_View (Entity (N)));
19290            Set_Etype  (N, Entity (N));
19291            Def_Id := Entity (N);
19292
19293            if not Is_Discrete_Type (Def_Id) then
19294               Error_Msg_N ("discrete type required for index", N);
19295               Set_Etype (N, Any_Type);
19296               return;
19297            end if;
19298         end if;
19299
19300         if Expander_Active then
19301            Rewrite (N,
19302              Make_Attribute_Reference (Sloc (N),
19303                Attribute_Name => Name_Range,
19304                Prefix         => Relocate_Node (N)));
19305
19306            --  The original was a subtype mark that does not freeze. This
19307            --  means that the rewritten version must not freeze either.
19308
19309            Set_Must_Not_Freeze (N);
19310            Set_Must_Not_Freeze (Prefix (N));
19311            Analyze_And_Resolve (N);
19312            T := Etype (N);
19313            R := N;
19314
19315         --  If expander is inactive, type is legal, nothing else to construct
19316
19317         else
19318            return;
19319         end if;
19320      end if;
19321
19322      if not Is_Discrete_Type (T) then
19323         Error_Msg_N ("discrete type required for range", N);
19324         Set_Etype (N, Any_Type);
19325         return;
19326
19327      elsif T = Any_Type then
19328         Set_Etype (N, Any_Type);
19329         return;
19330      end if;
19331
19332      --  We will now create the appropriate Itype to describe the range, but
19333      --  first a check. If we originally had a subtype, then we just label
19334      --  the range with this subtype. Not only is there no need to construct
19335      --  a new subtype, but it is wrong to do so for two reasons:
19336
19337      --    1. A legality concern, if we have a subtype, it must not freeze,
19338      --       and the Itype would cause freezing incorrectly
19339
19340      --    2. An efficiency concern, if we created an Itype, it would not be
19341      --       recognized as the same type for the purposes of eliminating
19342      --       checks in some circumstances.
19343
19344      --  We signal this case by setting the subtype entity in Def_Id
19345
19346      if No (Def_Id) then
19347         Def_Id :=
19348           Create_Itype (E_Void, Related_Nod, Related_Id, 'D', Suffix_Index);
19349         Set_Etype (Def_Id, Base_Type (T));
19350
19351         if Is_Signed_Integer_Type (T) then
19352            Set_Ekind (Def_Id, E_Signed_Integer_Subtype);
19353
19354         elsif Is_Modular_Integer_Type (T) then
19355            Set_Ekind (Def_Id, E_Modular_Integer_Subtype);
19356
19357         else
19358            Set_Ekind             (Def_Id, E_Enumeration_Subtype);
19359            Set_Is_Character_Type (Def_Id, Is_Character_Type (T));
19360            Set_First_Literal     (Def_Id, First_Literal (T));
19361         end if;
19362
19363         Set_Size_Info      (Def_Id,                  (T));
19364         Set_RM_Size        (Def_Id, RM_Size          (T));
19365         Set_First_Rep_Item (Def_Id, First_Rep_Item   (T));
19366
19367         Set_Scalar_Range   (Def_Id, R);
19368         Conditional_Delay  (Def_Id, T);
19369
19370         if Nkind (N) = N_Subtype_Indication then
19371            Inherit_Predicate_Flags (Def_Id, Entity (Subtype_Mark (N)));
19372         end if;
19373
19374         --  In the subtype indication case, if the immediate parent of the
19375         --  new subtype is nonstatic, then the subtype we create is nonstatic,
19376         --  even if its bounds are static.
19377
19378         if Nkind (N) = N_Subtype_Indication
19379           and then not Is_OK_Static_Subtype (Entity (Subtype_Mark (N)))
19380         then
19381            Set_Is_Non_Static_Subtype (Def_Id);
19382         end if;
19383      end if;
19384
19385      --  Final step is to label the index with this constructed type
19386
19387      Set_Etype (N, Def_Id);
19388   end Make_Index;
19389
19390   ------------------------------
19391   -- Modular_Type_Declaration --
19392   ------------------------------
19393
19394   procedure Modular_Type_Declaration (T : Entity_Id; Def : Node_Id) is
19395      Mod_Expr : constant Node_Id := Expression (Def);
19396      M_Val    : Uint;
19397
19398      procedure Set_Modular_Size (Bits : Int);
19399      --  Sets RM_Size to Bits, and Esize to normal word size above this
19400
19401      ----------------------
19402      -- Set_Modular_Size --
19403      ----------------------
19404
19405      procedure Set_Modular_Size (Bits : Int) is
19406      begin
19407         Set_RM_Size (T, UI_From_Int (Bits));
19408
19409         if Bits <= 8 then
19410            Init_Esize (T, 8);
19411
19412         elsif Bits <= 16 then
19413            Init_Esize (T, 16);
19414
19415         elsif Bits <= 32 then
19416            Init_Esize (T, 32);
19417
19418         else
19419            Init_Esize (T, System_Max_Binary_Modulus_Power);
19420         end if;
19421
19422         if not Non_Binary_Modulus (T) and then Esize (T) = RM_Size (T) then
19423            Set_Is_Known_Valid (T);
19424         end if;
19425      end Set_Modular_Size;
19426
19427   --  Start of processing for Modular_Type_Declaration
19428
19429   begin
19430      --  If the mod expression is (exactly) 2 * literal, where literal is
19431      --  64 or less,then almost certainly the * was meant to be **. Warn.
19432
19433      if Warn_On_Suspicious_Modulus_Value
19434        and then Nkind (Mod_Expr) = N_Op_Multiply
19435        and then Nkind (Left_Opnd (Mod_Expr)) = N_Integer_Literal
19436        and then Intval (Left_Opnd (Mod_Expr)) = Uint_2
19437        and then Nkind (Right_Opnd (Mod_Expr)) = N_Integer_Literal
19438        and then Intval (Right_Opnd (Mod_Expr)) <= Uint_64
19439      then
19440         Error_Msg_N
19441           ("suspicious MOD value, was '*'* intended'??M?", Mod_Expr);
19442      end if;
19443
19444      --  Proceed with analysis of mod expression
19445
19446      Analyze_And_Resolve (Mod_Expr, Any_Integer);
19447      Set_Etype (T, T);
19448      Set_Ekind (T, E_Modular_Integer_Type);
19449      Init_Alignment (T);
19450      Set_Is_Constrained (T);
19451
19452      if not Is_OK_Static_Expression (Mod_Expr) then
19453         Flag_Non_Static_Expr
19454           ("non-static expression used for modular type bound!", Mod_Expr);
19455         M_Val := 2 ** System_Max_Binary_Modulus_Power;
19456      else
19457         M_Val := Expr_Value (Mod_Expr);
19458      end if;
19459
19460      if M_Val < 1 then
19461         Error_Msg_N ("modulus value must be positive", Mod_Expr);
19462         M_Val := 2 ** System_Max_Binary_Modulus_Power;
19463      end if;
19464
19465      if M_Val > 2 ** Standard_Long_Integer_Size then
19466         Check_Restriction (No_Long_Long_Integers, Mod_Expr);
19467      end if;
19468
19469      Set_Modulus (T, M_Val);
19470
19471      --   Create bounds for the modular type based on the modulus given in
19472      --   the type declaration and then analyze and resolve those bounds.
19473
19474      Set_Scalar_Range (T,
19475        Make_Range (Sloc (Mod_Expr),
19476          Low_Bound  => Make_Integer_Literal (Sloc (Mod_Expr), 0),
19477          High_Bound => Make_Integer_Literal (Sloc (Mod_Expr), M_Val - 1)));
19478
19479      --  Properly analyze the literals for the range. We do this manually
19480      --  because we can't go calling Resolve, since we are resolving these
19481      --  bounds with the type, and this type is certainly not complete yet.
19482
19483      Set_Etype (Low_Bound  (Scalar_Range (T)), T);
19484      Set_Etype (High_Bound (Scalar_Range (T)), T);
19485      Set_Is_Static_Expression (Low_Bound  (Scalar_Range (T)));
19486      Set_Is_Static_Expression (High_Bound (Scalar_Range (T)));
19487
19488      --  Loop through powers of two to find number of bits required
19489
19490      for Bits in Int range 0 .. System_Max_Binary_Modulus_Power loop
19491
19492         --  Binary case
19493
19494         if M_Val = 2 ** Bits then
19495            Set_Modular_Size (Bits);
19496            return;
19497
19498         --  Nonbinary case
19499
19500         elsif M_Val < 2 ** Bits then
19501            Check_SPARK_05_Restriction ("modulus should be a power of 2", T);
19502            Set_Non_Binary_Modulus (T);
19503
19504            if Bits > System_Max_Nonbinary_Modulus_Power then
19505               Error_Msg_Uint_1 :=
19506                 UI_From_Int (System_Max_Nonbinary_Modulus_Power);
19507               Error_Msg_F
19508                 ("nonbinary modulus exceeds limit (2 '*'*^ - 1)", Mod_Expr);
19509               Set_Modular_Size (System_Max_Binary_Modulus_Power);
19510               return;
19511
19512            else
19513               --  In the nonbinary case, set size as per RM 13.3(55)
19514
19515               Set_Modular_Size (Bits);
19516               return;
19517            end if;
19518         end if;
19519
19520      end loop;
19521
19522      --  If we fall through, then the size exceed System.Max_Binary_Modulus
19523      --  so we just signal an error and set the maximum size.
19524
19525      Error_Msg_Uint_1 := UI_From_Int (System_Max_Binary_Modulus_Power);
19526      Error_Msg_F ("modulus exceeds limit (2 '*'*^)", Mod_Expr);
19527
19528      Set_Modular_Size (System_Max_Binary_Modulus_Power);
19529      Init_Alignment (T);
19530
19531   end Modular_Type_Declaration;
19532
19533   --------------------------
19534   -- New_Concatenation_Op --
19535   --------------------------
19536
19537   procedure New_Concatenation_Op (Typ : Entity_Id) is
19538      Loc : constant Source_Ptr := Sloc (Typ);
19539      Op  : Entity_Id;
19540
19541      function Make_Op_Formal (Typ, Op : Entity_Id) return Entity_Id;
19542      --  Create abbreviated declaration for the formal of a predefined
19543      --  Operator 'Op' of type 'Typ'
19544
19545      --------------------
19546      -- Make_Op_Formal --
19547      --------------------
19548
19549      function Make_Op_Formal (Typ, Op : Entity_Id) return Entity_Id is
19550         Formal : Entity_Id;
19551      begin
19552         Formal := New_Internal_Entity (E_In_Parameter, Op, Loc, 'P');
19553         Set_Etype (Formal, Typ);
19554         Set_Mechanism (Formal, Default_Mechanism);
19555         return Formal;
19556      end Make_Op_Formal;
19557
19558   --  Start of processing for New_Concatenation_Op
19559
19560   begin
19561      Op := Make_Defining_Operator_Symbol (Loc, Name_Op_Concat);
19562
19563      Set_Ekind                   (Op, E_Operator);
19564      Set_Scope                   (Op, Current_Scope);
19565      Set_Etype                   (Op, Typ);
19566      Set_Homonym                 (Op, Get_Name_Entity_Id (Name_Op_Concat));
19567      Set_Is_Immediately_Visible  (Op);
19568      Set_Is_Intrinsic_Subprogram (Op);
19569      Set_Has_Completion          (Op);
19570      Append_Entity               (Op, Current_Scope);
19571
19572      Set_Name_Entity_Id (Name_Op_Concat, Op);
19573
19574      Append_Entity (Make_Op_Formal (Typ, Op), Op);
19575      Append_Entity (Make_Op_Formal (Typ, Op), Op);
19576   end New_Concatenation_Op;
19577
19578   -------------------------
19579   -- OK_For_Limited_Init --
19580   -------------------------
19581
19582   --  ???Check all calls of this, and compare the conditions under which it's
19583   --  called.
19584
19585   function OK_For_Limited_Init
19586     (Typ : Entity_Id;
19587      Exp : Node_Id) return Boolean
19588   is
19589   begin
19590      return Is_CPP_Constructor_Call (Exp)
19591        or else (Ada_Version >= Ada_2005
19592                  and then not Debug_Flag_Dot_L
19593                  and then OK_For_Limited_Init_In_05 (Typ, Exp));
19594   end OK_For_Limited_Init;
19595
19596   -------------------------------
19597   -- OK_For_Limited_Init_In_05 --
19598   -------------------------------
19599
19600   function OK_For_Limited_Init_In_05
19601     (Typ : Entity_Id;
19602      Exp : Node_Id) return Boolean
19603   is
19604   begin
19605      --  An object of a limited interface type can be initialized with any
19606      --  expression of a nonlimited descendant type. However this does not
19607      --  apply if this is a view conversion of some other expression. This
19608      --  is checked below.
19609
19610      if Is_Class_Wide_Type (Typ)
19611        and then Is_Limited_Interface (Typ)
19612        and then not Is_Limited_Type (Etype (Exp))
19613        and then Nkind (Exp) /= N_Type_Conversion
19614      then
19615         return True;
19616      end if;
19617
19618      --  Ada 2005 (AI-287, AI-318): Relax the strictness of the front end in
19619      --  case of limited aggregates (including extension aggregates), and
19620      --  function calls. The function call may have been given in prefixed
19621      --  notation, in which case the original node is an indexed component.
19622      --  If the function is parameterless, the original node was an explicit
19623      --  dereference. The function may also be parameterless, in which case
19624      --  the source node is just an identifier.
19625
19626      --  A branch of a conditional expression may have been removed if the
19627      --  condition is statically known. This happens during expansion, and
19628      --  thus will not happen if previous errors were encountered. The check
19629      --  will have been performed on the chosen branch, which replaces the
19630      --  original conditional expression.
19631
19632      if No (Exp) then
19633         return True;
19634      end if;
19635
19636      case Nkind (Original_Node (Exp)) is
19637         when N_Aggregate
19638            | N_Extension_Aggregate
19639            | N_Function_Call
19640            | N_Op
19641         =>
19642            return True;
19643
19644         when N_Identifier =>
19645            return Present (Entity (Original_Node (Exp)))
19646              and then Ekind (Entity (Original_Node (Exp))) = E_Function;
19647
19648         when N_Qualified_Expression =>
19649            return
19650              OK_For_Limited_Init_In_05
19651                (Typ, Expression (Original_Node (Exp)));
19652
19653         --  Ada 2005 (AI-251): If a class-wide interface object is initialized
19654         --  with a function call, the expander has rewritten the call into an
19655         --  N_Type_Conversion node to force displacement of the pointer to
19656         --  reference the component containing the secondary dispatch table.
19657         --  Otherwise a type conversion is not a legal context.
19658         --  A return statement for a build-in-place function returning a
19659         --  synchronized type also introduces an unchecked conversion.
19660
19661         when N_Type_Conversion
19662            | N_Unchecked_Type_Conversion
19663         =>
19664            return not Comes_From_Source (Exp)
19665              and then
19666                OK_For_Limited_Init_In_05
19667                  (Typ, Expression (Original_Node (Exp)));
19668
19669         when N_Explicit_Dereference
19670            | N_Indexed_Component
19671            | N_Selected_Component
19672         =>
19673            return Nkind (Exp) = N_Function_Call;
19674
19675         --  A use of 'Input is a function call, hence allowed. Normally the
19676         --  attribute will be changed to a call, but the attribute by itself
19677         --  can occur with -gnatc.
19678
19679         when N_Attribute_Reference =>
19680            return Attribute_Name (Original_Node (Exp)) = Name_Input;
19681
19682         --  "return raise ..." is OK
19683
19684         when N_Raise_Expression =>
19685            return True;
19686
19687         --  For a case expression, all dependent expressions must be legal
19688
19689         when N_Case_Expression =>
19690            declare
19691               Alt : Node_Id;
19692
19693            begin
19694               Alt := First (Alternatives (Original_Node (Exp)));
19695               while Present (Alt) loop
19696                  if not OK_For_Limited_Init_In_05 (Typ, Expression (Alt)) then
19697                     return False;
19698                  end if;
19699
19700                  Next (Alt);
19701               end loop;
19702
19703               return True;
19704            end;
19705
19706         --  For an if expression, all dependent expressions must be legal
19707
19708         when N_If_Expression =>
19709            declare
19710               Then_Expr : constant Node_Id :=
19711                             Next (First (Expressions (Original_Node (Exp))));
19712               Else_Expr : constant Node_Id := Next (Then_Expr);
19713            begin
19714               return OK_For_Limited_Init_In_05 (Typ, Then_Expr)
19715                        and then
19716                      OK_For_Limited_Init_In_05 (Typ, Else_Expr);
19717            end;
19718
19719         when others =>
19720            return False;
19721      end case;
19722   end OK_For_Limited_Init_In_05;
19723
19724   -------------------------------------------
19725   -- Ordinary_Fixed_Point_Type_Declaration --
19726   -------------------------------------------
19727
19728   procedure Ordinary_Fixed_Point_Type_Declaration
19729     (T   : Entity_Id;
19730      Def : Node_Id)
19731   is
19732      Loc           : constant Source_Ptr := Sloc (Def);
19733      Delta_Expr    : constant Node_Id    := Delta_Expression (Def);
19734      RRS           : constant Node_Id    := Real_Range_Specification (Def);
19735      Implicit_Base : Entity_Id;
19736      Delta_Val     : Ureal;
19737      Small_Val     : Ureal;
19738      Low_Val       : Ureal;
19739      High_Val      : Ureal;
19740
19741   begin
19742      Check_Restriction (No_Fixed_Point, Def);
19743
19744      --  Create implicit base type
19745
19746      Implicit_Base :=
19747        Create_Itype (E_Ordinary_Fixed_Point_Type, Parent (Def), T, 'B');
19748      Set_Etype (Implicit_Base, Implicit_Base);
19749
19750      --  Analyze and process delta expression
19751
19752      Analyze_And_Resolve (Delta_Expr, Any_Real);
19753
19754      Check_Delta_Expression (Delta_Expr);
19755      Delta_Val := Expr_Value_R (Delta_Expr);
19756
19757      Set_Delta_Value (Implicit_Base, Delta_Val);
19758
19759      --  Compute default small from given delta, which is the largest power
19760      --  of two that does not exceed the given delta value.
19761
19762      declare
19763         Tmp   : Ureal;
19764         Scale : Int;
19765
19766      begin
19767         Tmp := Ureal_1;
19768         Scale := 0;
19769
19770         if Delta_Val < Ureal_1 then
19771            while Delta_Val < Tmp loop
19772               Tmp := Tmp / Ureal_2;
19773               Scale := Scale + 1;
19774            end loop;
19775
19776         else
19777            loop
19778               Tmp := Tmp * Ureal_2;
19779               exit when Tmp > Delta_Val;
19780               Scale := Scale - 1;
19781            end loop;
19782         end if;
19783
19784         Small_Val := UR_From_Components (Uint_1, UI_From_Int (Scale), 2);
19785      end;
19786
19787      Set_Small_Value (Implicit_Base, Small_Val);
19788
19789      --  If no range was given, set a dummy range
19790
19791      if RRS <= Empty_Or_Error then
19792         Low_Val  := -Small_Val;
19793         High_Val := Small_Val;
19794
19795      --  Otherwise analyze and process given range
19796
19797      else
19798         declare
19799            Low  : constant Node_Id := Low_Bound  (RRS);
19800            High : constant Node_Id := High_Bound (RRS);
19801
19802         begin
19803            Analyze_And_Resolve (Low, Any_Real);
19804            Analyze_And_Resolve (High, Any_Real);
19805            Check_Real_Bound (Low);
19806            Check_Real_Bound (High);
19807
19808            --  Obtain and set the range
19809
19810            Low_Val  := Expr_Value_R (Low);
19811            High_Val := Expr_Value_R (High);
19812
19813            if Low_Val > High_Val then
19814               Error_Msg_NE ("??fixed point type& has null range", Def, T);
19815            end if;
19816         end;
19817      end if;
19818
19819      --  The range for both the implicit base and the declared first subtype
19820      --  cannot be set yet, so we use the special routine Set_Fixed_Range to
19821      --  set a temporary range in place. Note that the bounds of the base
19822      --  type will be widened to be symmetrical and to fill the available
19823      --  bits when the type is frozen.
19824
19825      --  We could do this with all discrete types, and probably should, but
19826      --  we absolutely have to do it for fixed-point, since the end-points
19827      --  of the range and the size are determined by the small value, which
19828      --  could be reset before the freeze point.
19829
19830      Set_Fixed_Range (Implicit_Base, Loc, Low_Val, High_Val);
19831      Set_Fixed_Range (T, Loc, Low_Val, High_Val);
19832
19833      --  Complete definition of first subtype. The inheritance of the rep item
19834      --  chain ensures that SPARK-related pragmas are not clobbered when the
19835      --  ordinary fixed point type acts as a full view of a private type.
19836
19837      Set_Ekind              (T, E_Ordinary_Fixed_Point_Subtype);
19838      Set_Etype              (T, Implicit_Base);
19839      Init_Size_Align        (T);
19840      Inherit_Rep_Item_Chain (T, Implicit_Base);
19841      Set_Small_Value        (T, Small_Val);
19842      Set_Delta_Value        (T, Delta_Val);
19843      Set_Is_Constrained     (T);
19844   end Ordinary_Fixed_Point_Type_Declaration;
19845
19846   ----------------------------------
19847   -- Preanalyze_Assert_Expression --
19848   ----------------------------------
19849
19850   procedure Preanalyze_Assert_Expression (N : Node_Id; T : Entity_Id) is
19851   begin
19852      In_Assertion_Expr := In_Assertion_Expr + 1;
19853      Preanalyze_Spec_Expression (N, T);
19854      In_Assertion_Expr := In_Assertion_Expr - 1;
19855   end Preanalyze_Assert_Expression;
19856
19857   -----------------------------------
19858   -- Preanalyze_Default_Expression --
19859   -----------------------------------
19860
19861   procedure Preanalyze_Default_Expression (N : Node_Id; T : Entity_Id) is
19862      Save_In_Default_Expr    : constant Boolean := In_Default_Expr;
19863      Save_In_Spec_Expression : constant Boolean := In_Spec_Expression;
19864
19865   begin
19866      In_Default_Expr    := True;
19867      In_Spec_Expression := True;
19868
19869      Preanalyze_With_Freezing_And_Resolve (N, T);
19870
19871      In_Default_Expr    := Save_In_Default_Expr;
19872      In_Spec_Expression := Save_In_Spec_Expression;
19873   end Preanalyze_Default_Expression;
19874
19875   --------------------------------
19876   -- Preanalyze_Spec_Expression --
19877   --------------------------------
19878
19879   procedure Preanalyze_Spec_Expression (N : Node_Id; T : Entity_Id) is
19880      Save_In_Spec_Expression : constant Boolean := In_Spec_Expression;
19881   begin
19882      In_Spec_Expression := True;
19883      Preanalyze_And_Resolve (N, T);
19884      In_Spec_Expression := Save_In_Spec_Expression;
19885   end Preanalyze_Spec_Expression;
19886
19887   ----------------------------------------
19888   -- Prepare_Private_Subtype_Completion --
19889   ----------------------------------------
19890
19891   procedure Prepare_Private_Subtype_Completion
19892     (Id          : Entity_Id;
19893      Related_Nod : Node_Id)
19894   is
19895      Id_B   : constant Entity_Id := Base_Type (Id);
19896      Full_B : Entity_Id := Full_View (Id_B);
19897      Full   : Entity_Id;
19898
19899   begin
19900      if Present (Full_B) then
19901
19902         --  Get to the underlying full view if necessary
19903
19904         if Is_Private_Type (Full_B)
19905           and then Present (Underlying_Full_View (Full_B))
19906         then
19907            Full_B := Underlying_Full_View (Full_B);
19908         end if;
19909
19910         --  The Base_Type is already completed, we can complete the subtype
19911         --  now. We have to create a new entity with the same name, Thus we
19912         --  can't use Create_Itype.
19913
19914         Full := Make_Defining_Identifier (Sloc (Id), Chars (Id));
19915         Set_Is_Itype (Full);
19916         Set_Associated_Node_For_Itype (Full, Related_Nod);
19917         Complete_Private_Subtype (Id, Full, Full_B, Related_Nod);
19918      end if;
19919
19920      --  The parent subtype may be private, but the base might not, in some
19921      --  nested instances. In that case, the subtype does not need to be
19922      --  exchanged. It would still be nice to make private subtypes and their
19923      --  bases consistent at all times ???
19924
19925      if Is_Private_Type (Id_B) then
19926         Append_Elmt (Id, Private_Dependents (Id_B));
19927      end if;
19928   end Prepare_Private_Subtype_Completion;
19929
19930   ---------------------------
19931   -- Process_Discriminants --
19932   ---------------------------
19933
19934   procedure Process_Discriminants
19935     (N    : Node_Id;
19936      Prev : Entity_Id := Empty)
19937   is
19938      Elist               : constant Elist_Id := New_Elmt_List;
19939      Id                  : Node_Id;
19940      Discr               : Node_Id;
19941      Discr_Number        : Uint;
19942      Discr_Type          : Entity_Id;
19943      Default_Present     : Boolean := False;
19944      Default_Not_Present : Boolean := False;
19945
19946   begin
19947      --  A composite type other than an array type can have discriminants.
19948      --  On entry, the current scope is the composite type.
19949
19950      --  The discriminants are initially entered into the scope of the type
19951      --  via Enter_Name with the default Ekind of E_Void to prevent premature
19952      --  use, as explained at the end of this procedure.
19953
19954      Discr := First (Discriminant_Specifications (N));
19955      while Present (Discr) loop
19956         Enter_Name (Defining_Identifier (Discr));
19957
19958         --  For navigation purposes we add a reference to the discriminant
19959         --  in the entity for the type. If the current declaration is a
19960         --  completion, place references on the partial view. Otherwise the
19961         --  type is the current scope.
19962
19963         if Present (Prev) then
19964
19965            --  The references go on the partial view, if present. If the
19966            --  partial view has discriminants, the references have been
19967            --  generated already.
19968
19969            if not Has_Discriminants (Prev) then
19970               Generate_Reference (Prev, Defining_Identifier (Discr), 'd');
19971            end if;
19972         else
19973            Generate_Reference
19974              (Current_Scope, Defining_Identifier (Discr), 'd');
19975         end if;
19976
19977         if Nkind (Discriminant_Type (Discr)) = N_Access_Definition then
19978            Discr_Type := Access_Definition (Discr, Discriminant_Type (Discr));
19979
19980            --  Ada 2005 (AI-254)
19981
19982            if Present (Access_To_Subprogram_Definition
19983                         (Discriminant_Type (Discr)))
19984              and then Protected_Present (Access_To_Subprogram_Definition
19985                                           (Discriminant_Type (Discr)))
19986            then
19987               Discr_Type :=
19988                 Replace_Anonymous_Access_To_Protected_Subprogram (Discr);
19989            end if;
19990
19991         else
19992            Find_Type (Discriminant_Type (Discr));
19993            Discr_Type := Etype (Discriminant_Type (Discr));
19994
19995            if Error_Posted (Discriminant_Type (Discr)) then
19996               Discr_Type := Any_Type;
19997            end if;
19998         end if;
19999
20000         --  Handling of discriminants that are access types
20001
20002         if Is_Access_Type (Discr_Type) then
20003
20004            --  Ada 2005 (AI-230): Access discriminant allowed in non-
20005            --  limited record types
20006
20007            if Ada_Version < Ada_2005 then
20008               Check_Access_Discriminant_Requires_Limited
20009                 (Discr, Discriminant_Type (Discr));
20010            end if;
20011
20012            if Ada_Version = Ada_83 and then Comes_From_Source (Discr) then
20013               Error_Msg_N
20014                 ("(Ada 83) access discriminant not allowed", Discr);
20015            end if;
20016
20017         --  If not access type, must be a discrete type
20018
20019         elsif not Is_Discrete_Type (Discr_Type) then
20020            Error_Msg_N
20021              ("discriminants must have a discrete or access type",
20022               Discriminant_Type (Discr));
20023         end if;
20024
20025         Set_Etype (Defining_Identifier (Discr), Discr_Type);
20026
20027         --  If a discriminant specification includes the assignment compound
20028         --  delimiter followed by an expression, the expression is the default
20029         --  expression of the discriminant; the default expression must be of
20030         --  the type of the discriminant. (RM 3.7.1) Since this expression is
20031         --  a default expression, we do the special preanalysis, since this
20032         --  expression does not freeze (see section "Handling of Default and
20033         --  Per-Object Expressions" in spec of package Sem).
20034
20035         if Present (Expression (Discr)) then
20036            Preanalyze_Spec_Expression (Expression (Discr), Discr_Type);
20037
20038            --  Legaity checks
20039
20040            if Nkind (N) = N_Formal_Type_Declaration then
20041               Error_Msg_N
20042                 ("discriminant defaults not allowed for formal type",
20043                  Expression (Discr));
20044
20045            --  Flag an error for a tagged type with defaulted discriminants,
20046            --  excluding limited tagged types when compiling for Ada 2012
20047            --  (see AI05-0214).
20048
20049            elsif Is_Tagged_Type (Current_Scope)
20050              and then (not Is_Limited_Type (Current_Scope)
20051                         or else Ada_Version < Ada_2012)
20052              and then Comes_From_Source (N)
20053            then
20054               --  Note: see similar test in Check_Or_Process_Discriminants, to
20055               --  handle the (illegal) case of the completion of an untagged
20056               --  view with discriminants with defaults by a tagged full view.
20057               --  We skip the check if Discr does not come from source, to
20058               --  account for the case of an untagged derived type providing
20059               --  defaults for a renamed discriminant from a private untagged
20060               --  ancestor with a tagged full view (ACATS B460006).
20061
20062               if Ada_Version >= Ada_2012 then
20063                  Error_Msg_N
20064                    ("discriminants of nonlimited tagged type cannot have"
20065                       & " defaults",
20066                     Expression (Discr));
20067               else
20068                  Error_Msg_N
20069                    ("discriminants of tagged type cannot have defaults",
20070                     Expression (Discr));
20071               end if;
20072
20073            else
20074               Default_Present := True;
20075               Append_Elmt (Expression (Discr), Elist);
20076
20077               --  Tag the defining identifiers for the discriminants with
20078               --  their corresponding default expressions from the tree.
20079
20080               Set_Discriminant_Default_Value
20081                 (Defining_Identifier (Discr), Expression (Discr));
20082            end if;
20083
20084            --  In gnatc or gnatprove mode, make sure set Do_Range_Check flag
20085            --  gets set unless we can be sure that no range check is required.
20086
20087            if (GNATprove_Mode or not Expander_Active)
20088              and then not
20089                Is_In_Range
20090                  (Expression (Discr), Discr_Type, Assume_Valid => True)
20091            then
20092               Set_Do_Range_Check (Expression (Discr));
20093            end if;
20094
20095         --  No default discriminant value given
20096
20097         else
20098            Default_Not_Present := True;
20099         end if;
20100
20101         --  Ada 2005 (AI-231): Create an Itype that is a duplicate of
20102         --  Discr_Type but with the null-exclusion attribute
20103
20104         if Ada_Version >= Ada_2005 then
20105
20106            --  Ada 2005 (AI-231): Static checks
20107
20108            if Can_Never_Be_Null (Discr_Type) then
20109               Null_Exclusion_Static_Checks (Discr);
20110
20111            elsif Is_Access_Type (Discr_Type)
20112              and then Null_Exclusion_Present (Discr)
20113
20114               --  No need to check itypes because in their case this check
20115               --  was done at their point of creation
20116
20117              and then not Is_Itype (Discr_Type)
20118            then
20119               if Can_Never_Be_Null (Discr_Type) then
20120                  Error_Msg_NE
20121                    ("`NOT NULL` not allowed (& already excludes null)",
20122                     Discr,
20123                     Discr_Type);
20124               end if;
20125
20126               Set_Etype (Defining_Identifier (Discr),
20127                 Create_Null_Excluding_Itype
20128                   (T           => Discr_Type,
20129                    Related_Nod => Discr));
20130
20131            --  Check for improper null exclusion if the type is otherwise
20132            --  legal for a discriminant.
20133
20134            elsif Null_Exclusion_Present (Discr)
20135              and then Is_Discrete_Type (Discr_Type)
20136            then
20137               Error_Msg_N
20138                 ("null exclusion can only apply to an access type", Discr);
20139            end if;
20140
20141            --  Ada 2005 (AI-402): access discriminants of nonlimited types
20142            --  can't have defaults. Synchronized types, or types that are
20143            --  explicitly limited are fine, but special tests apply to derived
20144            --  types in generics: in a generic body we have to assume the
20145            --  worst, and therefore defaults are not allowed if the parent is
20146            --  a generic formal private type (see ACATS B370001).
20147
20148            if Is_Access_Type (Discr_Type) and then Default_Present then
20149               if Ekind (Discr_Type) /= E_Anonymous_Access_Type
20150                 or else Is_Limited_Record (Current_Scope)
20151                 or else Is_Concurrent_Type (Current_Scope)
20152                 or else Is_Concurrent_Record_Type (Current_Scope)
20153                 or else Ekind (Current_Scope) = E_Limited_Private_Type
20154               then
20155                  if not Is_Derived_Type (Current_Scope)
20156                    or else not Is_Generic_Type (Etype (Current_Scope))
20157                    or else not In_Package_Body (Scope (Etype (Current_Scope)))
20158                    or else Limited_Present
20159                              (Type_Definition (Parent (Current_Scope)))
20160                  then
20161                     null;
20162
20163                  else
20164                     Error_Msg_N
20165                       ("access discriminants of nonlimited types cannot "
20166                        & "have defaults", Expression (Discr));
20167                  end if;
20168
20169               elsif Present (Expression (Discr)) then
20170                  Error_Msg_N
20171                    ("(Ada 2005) access discriminants of nonlimited types "
20172                     & "cannot have defaults", Expression (Discr));
20173               end if;
20174            end if;
20175         end if;
20176
20177         --  A discriminant cannot be effectively volatile (SPARK RM 7.1.3(4)).
20178         --  This check is relevant only when SPARK_Mode is on as it is not a
20179         --  standard Ada legality rule.
20180
20181         if SPARK_Mode = On
20182           and then Is_Effectively_Volatile (Defining_Identifier (Discr))
20183         then
20184            Error_Msg_N ("discriminant cannot be volatile", Discr);
20185         end if;
20186
20187         Next (Discr);
20188      end loop;
20189
20190      --  An element list consisting of the default expressions of the
20191      --  discriminants is constructed in the above loop and used to set
20192      --  the Discriminant_Constraint attribute for the type. If an object
20193      --  is declared of this (record or task) type without any explicit
20194      --  discriminant constraint given, this element list will form the
20195      --  actual parameters for the corresponding initialization procedure
20196      --  for the type.
20197
20198      Set_Discriminant_Constraint (Current_Scope, Elist);
20199      Set_Stored_Constraint (Current_Scope, No_Elist);
20200
20201      --  Default expressions must be provided either for all or for none
20202      --  of the discriminants of a discriminant part. (RM 3.7.1)
20203
20204      if Default_Present and then Default_Not_Present then
20205         Error_Msg_N
20206           ("incomplete specification of defaults for discriminants", N);
20207      end if;
20208
20209      --  The use of the name of a discriminant is not allowed in default
20210      --  expressions of a discriminant part if the specification of the
20211      --  discriminant is itself given in the discriminant part. (RM 3.7.1)
20212
20213      --  To detect this, the discriminant names are entered initially with an
20214      --  Ekind of E_Void (which is the default Ekind given by Enter_Name). Any
20215      --  attempt to use a void entity (for example in an expression that is
20216      --  type-checked) produces the error message: premature usage. Now after
20217      --  completing the semantic analysis of the discriminant part, we can set
20218      --  the Ekind of all the discriminants appropriately.
20219
20220      Discr := First (Discriminant_Specifications (N));
20221      Discr_Number := Uint_1;
20222      while Present (Discr) loop
20223         Id := Defining_Identifier (Discr);
20224         Set_Ekind (Id, E_Discriminant);
20225         Init_Component_Location (Id);
20226         Init_Esize (Id);
20227         Set_Discriminant_Number (Id, Discr_Number);
20228
20229         --  Make sure this is always set, even in illegal programs
20230
20231         Set_Corresponding_Discriminant (Id, Empty);
20232
20233         --  Initialize the Original_Record_Component to the entity itself.
20234         --  Inherit_Components will propagate the right value to
20235         --  discriminants in derived record types.
20236
20237         Set_Original_Record_Component (Id, Id);
20238
20239         --  Create the discriminal for the discriminant
20240
20241         Build_Discriminal (Id);
20242
20243         Next (Discr);
20244         Discr_Number := Discr_Number + 1;
20245      end loop;
20246
20247      Set_Has_Discriminants (Current_Scope);
20248   end Process_Discriminants;
20249
20250   -----------------------
20251   -- Process_Full_View --
20252   -----------------------
20253
20254   --  WARNING: This routine manages Ghost regions. Return statements must be
20255   --  replaced by gotos which jump to the end of the routine and restore the
20256   --  Ghost mode.
20257
20258   procedure Process_Full_View (N : Node_Id; Full_T, Priv_T : Entity_Id) is
20259      procedure Collect_Implemented_Interfaces
20260        (Typ    : Entity_Id;
20261         Ifaces : Elist_Id);
20262      --  Ada 2005: Gather all the interfaces that Typ directly or
20263      --  inherently implements. Duplicate entries are not added to
20264      --  the list Ifaces.
20265
20266      ------------------------------------
20267      -- Collect_Implemented_Interfaces --
20268      ------------------------------------
20269
20270      procedure Collect_Implemented_Interfaces
20271        (Typ    : Entity_Id;
20272         Ifaces : Elist_Id)
20273      is
20274         Iface      : Entity_Id;
20275         Iface_Elmt : Elmt_Id;
20276
20277      begin
20278         --  Abstract interfaces are only associated with tagged record types
20279
20280         if not Is_Tagged_Type (Typ) or else not Is_Record_Type (Typ) then
20281            return;
20282         end if;
20283
20284         --  Recursively climb to the ancestors
20285
20286         if Etype (Typ) /= Typ
20287
20288            --  Protect the frontend against wrong cyclic declarations like:
20289
20290            --     type B is new A with private;
20291            --     type C is new A with private;
20292            --  private
20293            --     type B is new C with null record;
20294            --     type C is new B with null record;
20295
20296           and then Etype (Typ) /= Priv_T
20297           and then Etype (Typ) /= Full_T
20298         then
20299            --  Keep separate the management of private type declarations
20300
20301            if Ekind (Typ) = E_Record_Type_With_Private then
20302
20303               --  Handle the following illegal usage:
20304               --      type Private_Type is tagged private;
20305               --   private
20306               --      type Private_Type is new Type_Implementing_Iface;
20307
20308               if Present (Full_View (Typ))
20309                 and then Etype (Typ) /= Full_View (Typ)
20310               then
20311                  if Is_Interface (Etype (Typ)) then
20312                     Append_Unique_Elmt (Etype (Typ), Ifaces);
20313                  end if;
20314
20315                  Collect_Implemented_Interfaces (Etype (Typ), Ifaces);
20316               end if;
20317
20318            --  Non-private types
20319
20320            else
20321               if Is_Interface (Etype (Typ)) then
20322                  Append_Unique_Elmt (Etype (Typ), Ifaces);
20323               end if;
20324
20325               Collect_Implemented_Interfaces (Etype (Typ), Ifaces);
20326            end if;
20327         end if;
20328
20329         --  Handle entities in the list of abstract interfaces
20330
20331         if Present (Interfaces (Typ)) then
20332            Iface_Elmt := First_Elmt (Interfaces (Typ));
20333            while Present (Iface_Elmt) loop
20334               Iface := Node (Iface_Elmt);
20335
20336               pragma Assert (Is_Interface (Iface));
20337
20338               if not Contain_Interface (Iface, Ifaces) then
20339                  Append_Elmt (Iface, Ifaces);
20340                  Collect_Implemented_Interfaces (Iface, Ifaces);
20341               end if;
20342
20343               Next_Elmt (Iface_Elmt);
20344            end loop;
20345         end if;
20346      end Collect_Implemented_Interfaces;
20347
20348      --  Local variables
20349
20350      Saved_GM  : constant Ghost_Mode_Type := Ghost_Mode;
20351      Saved_IGR : constant Node_Id         := Ignored_Ghost_Region;
20352      --  Save the Ghost-related attributes to restore on exit
20353
20354      Full_Indic  : Node_Id;
20355      Full_Parent : Entity_Id;
20356      Priv_Parent : Entity_Id;
20357
20358   --  Start of processing for Process_Full_View
20359
20360   begin
20361      Mark_And_Set_Ghost_Completion (N, Priv_T);
20362
20363      --  First some sanity checks that must be done after semantic
20364      --  decoration of the full view and thus cannot be placed with other
20365      --  similar checks in Find_Type_Name
20366
20367      if not Is_Limited_Type (Priv_T)
20368        and then (Is_Limited_Type (Full_T)
20369                   or else Is_Limited_Composite (Full_T))
20370      then
20371         if In_Instance then
20372            null;
20373         else
20374            Error_Msg_N
20375              ("completion of nonlimited type cannot be limited", Full_T);
20376            Explain_Limited_Type (Full_T, Full_T);
20377         end if;
20378
20379      elsif Is_Abstract_Type (Full_T)
20380        and then not Is_Abstract_Type (Priv_T)
20381      then
20382         Error_Msg_N
20383           ("completion of nonabstract type cannot be abstract", Full_T);
20384
20385      elsif Is_Tagged_Type (Priv_T)
20386        and then Is_Limited_Type (Priv_T)
20387        and then not Is_Limited_Type (Full_T)
20388      then
20389         --  If pragma CPP_Class was applied to the private declaration
20390         --  propagate the limitedness to the full-view
20391
20392         if Is_CPP_Class (Priv_T) then
20393            Set_Is_Limited_Record (Full_T);
20394
20395         --  GNAT allow its own definition of Limited_Controlled to disobey
20396         --  this rule in order in ease the implementation. This test is safe
20397         --  because Root_Controlled is defined in a child of System that
20398         --  normal programs are not supposed to use.
20399
20400         elsif Is_RTE (Etype (Full_T), RE_Root_Controlled) then
20401            Set_Is_Limited_Composite (Full_T);
20402         else
20403            Error_Msg_N
20404              ("completion of limited tagged type must be limited", Full_T);
20405         end if;
20406
20407      elsif Is_Generic_Type (Priv_T) then
20408         Error_Msg_N ("generic type cannot have a completion", Full_T);
20409      end if;
20410
20411      --  Check that ancestor interfaces of private and full views are
20412      --  consistent. We omit this check for synchronized types because
20413      --  they are performed on the corresponding record type when frozen.
20414
20415      if Ada_Version >= Ada_2005
20416        and then Is_Tagged_Type (Priv_T)
20417        and then Is_Tagged_Type (Full_T)
20418        and then not Is_Concurrent_Type (Full_T)
20419      then
20420         declare
20421            Iface         : Entity_Id;
20422            Priv_T_Ifaces : constant Elist_Id := New_Elmt_List;
20423            Full_T_Ifaces : constant Elist_Id := New_Elmt_List;
20424
20425         begin
20426            Collect_Implemented_Interfaces (Priv_T, Priv_T_Ifaces);
20427            Collect_Implemented_Interfaces (Full_T, Full_T_Ifaces);
20428
20429            --  Ada 2005 (AI-251): The partial view shall be a descendant of
20430            --  an interface type if and only if the full type is descendant
20431            --  of the interface type (AARM 7.3 (7.3/2)).
20432
20433            Iface := Find_Hidden_Interface (Priv_T_Ifaces, Full_T_Ifaces);
20434
20435            if Present (Iface) then
20436               Error_Msg_NE
20437                 ("interface in partial view& not implemented by full type "
20438                  & "(RM-2005 7.3 (7.3/2))", Full_T, Iface);
20439            end if;
20440
20441            Iface := Find_Hidden_Interface (Full_T_Ifaces, Priv_T_Ifaces);
20442
20443            if Present (Iface) then
20444               Error_Msg_NE
20445                 ("interface & not implemented by partial view "
20446                  & "(RM-2005 7.3 (7.3/2))", Full_T, Iface);
20447            end if;
20448         end;
20449      end if;
20450
20451      if Is_Tagged_Type (Priv_T)
20452        and then Nkind (Parent (Priv_T)) = N_Private_Extension_Declaration
20453        and then Is_Derived_Type (Full_T)
20454      then
20455         Priv_Parent := Etype (Priv_T);
20456
20457         --  The full view of a private extension may have been transformed
20458         --  into an unconstrained derived type declaration and a subtype
20459         --  declaration (see build_derived_record_type for details).
20460
20461         if Nkind (N) = N_Subtype_Declaration then
20462            Full_Indic  := Subtype_Indication (N);
20463            Full_Parent := Etype (Base_Type (Full_T));
20464         else
20465            Full_Indic  := Subtype_Indication (Type_Definition (N));
20466            Full_Parent := Etype (Full_T);
20467         end if;
20468
20469         --  Check that the parent type of the full type is a descendant of
20470         --  the ancestor subtype given in the private extension. If either
20471         --  entity has an Etype equal to Any_Type then we had some previous
20472         --  error situation [7.3(8)].
20473
20474         if Priv_Parent = Any_Type or else Full_Parent = Any_Type then
20475            goto Leave;
20476
20477         --  Ada 2005 (AI-251): Interfaces in the full type can be given in
20478         --  any order. Therefore we don't have to check that its parent must
20479         --  be a descendant of the parent of the private type declaration.
20480
20481         elsif Is_Interface (Priv_Parent)
20482           and then Is_Interface (Full_Parent)
20483         then
20484            null;
20485
20486         --  Ada 2005 (AI-251): If the parent of the private type declaration
20487         --  is an interface there is no need to check that it is an ancestor
20488         --  of the associated full type declaration. The required tests for
20489         --  this case are performed by Build_Derived_Record_Type.
20490
20491         elsif not Is_Interface (Base_Type (Priv_Parent))
20492           and then not Is_Ancestor (Base_Type (Priv_Parent), Full_Parent)
20493         then
20494            Error_Msg_N
20495              ("parent of full type must descend from parent of private "
20496               & "extension", Full_Indic);
20497
20498         --  First check a formal restriction, and then proceed with checking
20499         --  Ada rules. Since the formal restriction is not a serious error, we
20500         --  don't prevent further error detection for this check, hence the
20501         --  ELSE.
20502
20503         else
20504            --  In formal mode, when completing a private extension the type
20505            --  named in the private part must be exactly the same as that
20506            --  named in the visible part.
20507
20508            if Priv_Parent /= Full_Parent then
20509               Error_Msg_Name_1 := Chars (Priv_Parent);
20510               Check_SPARK_05_Restriction ("% expected", Full_Indic);
20511            end if;
20512
20513            --  Check the rules of 7.3(10): if the private extension inherits
20514            --  known discriminants, then the full type must also inherit those
20515            --  discriminants from the same (ancestor) type, and the parent
20516            --  subtype of the full type must be constrained if and only if
20517            --  the ancestor subtype of the private extension is constrained.
20518
20519            if No (Discriminant_Specifications (Parent (Priv_T)))
20520              and then not Has_Unknown_Discriminants (Priv_T)
20521              and then Has_Discriminants (Base_Type (Priv_Parent))
20522            then
20523               declare
20524                  Priv_Indic  : constant Node_Id :=
20525                                  Subtype_Indication (Parent (Priv_T));
20526
20527                  Priv_Constr : constant Boolean :=
20528                                  Is_Constrained (Priv_Parent)
20529                                    or else
20530                                      Nkind (Priv_Indic) = N_Subtype_Indication
20531                                    or else
20532                                      Is_Constrained (Entity (Priv_Indic));
20533
20534                  Full_Constr : constant Boolean :=
20535                                  Is_Constrained (Full_Parent)
20536                                    or else
20537                                      Nkind (Full_Indic) = N_Subtype_Indication
20538                                    or else
20539                                      Is_Constrained (Entity (Full_Indic));
20540
20541                  Priv_Discr : Entity_Id;
20542                  Full_Discr : Entity_Id;
20543
20544               begin
20545                  Priv_Discr := First_Discriminant (Priv_Parent);
20546                  Full_Discr := First_Discriminant (Full_Parent);
20547                  while Present (Priv_Discr) and then Present (Full_Discr) loop
20548                     if Original_Record_Component (Priv_Discr) =
20549                        Original_Record_Component (Full_Discr)
20550                          or else
20551                        Corresponding_Discriminant (Priv_Discr) =
20552                        Corresponding_Discriminant (Full_Discr)
20553                     then
20554                        null;
20555                     else
20556                        exit;
20557                     end if;
20558
20559                     Next_Discriminant (Priv_Discr);
20560                     Next_Discriminant (Full_Discr);
20561                  end loop;
20562
20563                  if Present (Priv_Discr) or else Present (Full_Discr) then
20564                     Error_Msg_N
20565                       ("full view must inherit discriminants of the parent "
20566                        & "type used in the private extension", Full_Indic);
20567
20568                  elsif Priv_Constr and then not Full_Constr then
20569                     Error_Msg_N
20570                       ("parent subtype of full type must be constrained",
20571                        Full_Indic);
20572
20573                  elsif Full_Constr and then not Priv_Constr then
20574                     Error_Msg_N
20575                       ("parent subtype of full type must be unconstrained",
20576                        Full_Indic);
20577                  end if;
20578               end;
20579
20580               --  Check the rules of 7.3(12): if a partial view has neither
20581               --  known or unknown discriminants, then the full type
20582               --  declaration shall define a definite subtype.
20583
20584            elsif not Has_Unknown_Discriminants (Priv_T)
20585              and then not Has_Discriminants (Priv_T)
20586              and then not Is_Constrained (Full_T)
20587            then
20588               Error_Msg_N
20589                 ("full view must define a constrained type if partial view "
20590                  & "has no discriminants", Full_T);
20591            end if;
20592
20593            --  ??????? Do we implement the following properly ?????
20594            --  If the ancestor subtype of a private extension has constrained
20595            --  discriminants, then the parent subtype of the full view shall
20596            --  impose a statically matching constraint on those discriminants
20597            --  [7.3(13)].
20598         end if;
20599
20600      else
20601         --  For untagged types, verify that a type without discriminants is
20602         --  not completed with an unconstrained type. A separate error message
20603         --  is produced if the full type has defaulted discriminants.
20604
20605         if Is_Definite_Subtype (Priv_T)
20606           and then not Is_Definite_Subtype (Full_T)
20607         then
20608            Error_Msg_Sloc := Sloc (Parent (Priv_T));
20609            Error_Msg_NE
20610              ("full view of& not compatible with declaration#",
20611               Full_T, Priv_T);
20612
20613            if not Is_Tagged_Type (Full_T) then
20614               Error_Msg_N
20615                 ("\one is constrained, the other unconstrained", Full_T);
20616            end if;
20617         end if;
20618      end if;
20619
20620      --  AI-419: verify that the use of "limited" is consistent
20621
20622      declare
20623         Orig_Decl : constant Node_Id := Original_Node (N);
20624
20625      begin
20626         if Nkind (Parent (Priv_T)) = N_Private_Extension_Declaration
20627           and then Nkind (Orig_Decl) = N_Full_Type_Declaration
20628           and then Nkind
20629             (Type_Definition (Orig_Decl)) = N_Derived_Type_Definition
20630         then
20631            if not Limited_Present (Parent (Priv_T))
20632              and then not Synchronized_Present (Parent (Priv_T))
20633              and then Limited_Present (Type_Definition (Orig_Decl))
20634            then
20635               Error_Msg_N
20636                 ("full view of non-limited extension cannot be limited", N);
20637
20638            --  Conversely, if the partial view carries the limited keyword,
20639            --  the full view must as well, even if it may be redundant.
20640
20641            elsif Limited_Present (Parent (Priv_T))
20642              and then not Limited_Present (Type_Definition (Orig_Decl))
20643            then
20644               Error_Msg_N
20645                 ("full view of limited extension must be explicitly limited",
20646                  N);
20647            end if;
20648         end if;
20649      end;
20650
20651      --  Ada 2005 (AI-443): A synchronized private extension must be
20652      --  completed by a task or protected type.
20653
20654      if Ada_Version >= Ada_2005
20655        and then Nkind (Parent (Priv_T)) = N_Private_Extension_Declaration
20656        and then Synchronized_Present (Parent (Priv_T))
20657        and then not Is_Concurrent_Type (Full_T)
20658      then
20659         Error_Msg_N ("full view of synchronized extension must " &
20660                      "be synchronized type", N);
20661      end if;
20662
20663      --  Ada 2005 AI-363: if the full view has discriminants with
20664      --  defaults, it is illegal to declare constrained access subtypes
20665      --  whose designated type is the current type. This allows objects
20666      --  of the type that are declared in the heap to be unconstrained.
20667
20668      if not Has_Unknown_Discriminants (Priv_T)
20669        and then not Has_Discriminants (Priv_T)
20670        and then Has_Discriminants (Full_T)
20671        and then
20672          Present (Discriminant_Default_Value (First_Discriminant (Full_T)))
20673      then
20674         Set_Has_Constrained_Partial_View (Full_T);
20675         Set_Has_Constrained_Partial_View (Priv_T);
20676      end if;
20677
20678      --  Create a full declaration for all its subtypes recorded in
20679      --  Private_Dependents and swap them similarly to the base type. These
20680      --  are subtypes that have been define before the full declaration of
20681      --  the private type. We also swap the entry in Private_Dependents list
20682      --  so we can properly restore the private view on exit from the scope.
20683
20684      declare
20685         Priv_Elmt : Elmt_Id;
20686         Priv_Scop : Entity_Id;
20687         Priv      : Entity_Id;
20688         Full      : Entity_Id;
20689
20690      begin
20691         Priv_Elmt := First_Elmt (Private_Dependents (Priv_T));
20692         while Present (Priv_Elmt) loop
20693            Priv := Node (Priv_Elmt);
20694            Priv_Scop := Scope (Priv);
20695
20696            if Ekind_In (Priv, E_Private_Subtype,
20697                               E_Limited_Private_Subtype,
20698                               E_Record_Subtype_With_Private)
20699            then
20700               Full := Make_Defining_Identifier (Sloc (Priv), Chars (Priv));
20701               Set_Is_Itype (Full);
20702               Set_Parent (Full, Parent (Priv));
20703               Set_Associated_Node_For_Itype (Full, N);
20704
20705               --  Now we need to complete the private subtype, but since the
20706               --  base type has already been swapped, we must also swap the
20707               --  subtypes (and thus, reverse the arguments in the call to
20708               --  Complete_Private_Subtype). Also note that we may need to
20709               --  re-establish the scope of the private subtype.
20710
20711               Copy_And_Swap (Priv, Full);
20712
20713               if not In_Open_Scopes (Priv_Scop) then
20714                  Push_Scope (Priv_Scop);
20715
20716               else
20717                  --  Reset Priv_Scop to Empty to indicate no scope was pushed
20718
20719                  Priv_Scop := Empty;
20720               end if;
20721
20722               Complete_Private_Subtype (Full, Priv, Full_T, N);
20723
20724               if Present (Priv_Scop) then
20725                  Pop_Scope;
20726               end if;
20727
20728               Replace_Elmt (Priv_Elmt, Full);
20729            end if;
20730
20731            Next_Elmt (Priv_Elmt);
20732         end loop;
20733      end;
20734
20735      --  If the private view was tagged, copy the new primitive operations
20736      --  from the private view to the full view.
20737
20738      if Is_Tagged_Type (Full_T) then
20739         declare
20740            Disp_Typ  : Entity_Id;
20741            Full_List : Elist_Id;
20742            Prim      : Entity_Id;
20743            Prim_Elmt : Elmt_Id;
20744            Priv_List : Elist_Id;
20745
20746            function Contains
20747              (E : Entity_Id;
20748               L : Elist_Id) return Boolean;
20749            --  Determine whether list L contains element E
20750
20751            --------------
20752            -- Contains --
20753            --------------
20754
20755            function Contains
20756              (E : Entity_Id;
20757               L : Elist_Id) return Boolean
20758            is
20759               List_Elmt : Elmt_Id;
20760
20761            begin
20762               List_Elmt := First_Elmt (L);
20763               while Present (List_Elmt) loop
20764                  if Node (List_Elmt) = E then
20765                     return True;
20766                  end if;
20767
20768                  Next_Elmt (List_Elmt);
20769               end loop;
20770
20771               return False;
20772            end Contains;
20773
20774         --  Start of processing
20775
20776         begin
20777            if Is_Tagged_Type (Priv_T) then
20778               Priv_List := Primitive_Operations (Priv_T);
20779               Prim_Elmt := First_Elmt (Priv_List);
20780
20781               --  In the case of a concurrent type completing a private tagged
20782               --  type, primitives may have been declared in between the two
20783               --  views. These subprograms need to be wrapped the same way
20784               --  entries and protected procedures are handled because they
20785               --  cannot be directly shared by the two views.
20786
20787               if Is_Concurrent_Type (Full_T) then
20788                  declare
20789                     Conc_Typ  : constant Entity_Id :=
20790                                   Corresponding_Record_Type (Full_T);
20791                     Curr_Nod  : Node_Id := Parent (Conc_Typ);
20792                     Wrap_Spec : Node_Id;
20793
20794                  begin
20795                     while Present (Prim_Elmt) loop
20796                        Prim := Node (Prim_Elmt);
20797
20798                        if Comes_From_Source (Prim)
20799                          and then not Is_Abstract_Subprogram (Prim)
20800                        then
20801                           Wrap_Spec :=
20802                             Make_Subprogram_Declaration (Sloc (Prim),
20803                               Specification =>
20804                                 Build_Wrapper_Spec
20805                                   (Subp_Id => Prim,
20806                                    Obj_Typ => Conc_Typ,
20807                                    Formals =>
20808                                      Parameter_Specifications
20809                                        (Parent (Prim))));
20810
20811                           Insert_After (Curr_Nod, Wrap_Spec);
20812                           Curr_Nod := Wrap_Spec;
20813
20814                           Analyze (Wrap_Spec);
20815
20816                           --  Remove the wrapper from visibility to avoid
20817                           --  spurious conflict with the wrapped entity.
20818
20819                           Set_Is_Immediately_Visible
20820                             (Defining_Entity (Specification (Wrap_Spec)),
20821                              False);
20822                        end if;
20823
20824                        Next_Elmt (Prim_Elmt);
20825                     end loop;
20826
20827                     goto Leave;
20828                  end;
20829
20830               --  For non-concurrent types, transfer explicit primitives, but
20831               --  omit those inherited from the parent of the private view
20832               --  since they will be re-inherited later on.
20833
20834               else
20835                  Full_List := Primitive_Operations (Full_T);
20836                  while Present (Prim_Elmt) loop
20837                     Prim := Node (Prim_Elmt);
20838
20839                     if Comes_From_Source (Prim)
20840                       and then not Contains (Prim, Full_List)
20841                     then
20842                        Append_Elmt (Prim, Full_List);
20843                     end if;
20844
20845                     Next_Elmt (Prim_Elmt);
20846                  end loop;
20847               end if;
20848
20849            --  Untagged private view
20850
20851            else
20852               Full_List := Primitive_Operations (Full_T);
20853
20854               --  In this case the partial view is untagged, so here we locate
20855               --  all of the earlier primitives that need to be treated as
20856               --  dispatching (those that appear between the two views). Note
20857               --  that these additional operations must all be new operations
20858               --  (any earlier operations that override inherited operations
20859               --  of the full view will already have been inserted in the
20860               --  primitives list, marked by Check_Operation_From_Private_View
20861               --  as dispatching. Note that implicit "/=" operators are
20862               --  excluded from being added to the primitives list since they
20863               --  shouldn't be treated as dispatching (tagged "/=" is handled
20864               --  specially).
20865
20866               Prim := Next_Entity (Full_T);
20867               while Present (Prim) and then Prim /= Priv_T loop
20868                  if Ekind_In (Prim, E_Procedure, E_Function) then
20869                     Disp_Typ := Find_Dispatching_Type (Prim);
20870
20871                     if Disp_Typ = Full_T
20872                       and then (Chars (Prim) /= Name_Op_Ne
20873                                  or else Comes_From_Source (Prim))
20874                     then
20875                        Check_Controlling_Formals (Full_T, Prim);
20876
20877                        if Is_Suitable_Primitive (Prim)
20878                          and then not Is_Dispatching_Operation (Prim)
20879                        then
20880                           Append_Elmt (Prim, Full_List);
20881                           Set_Is_Dispatching_Operation (Prim);
20882                           Set_DT_Position_Value (Prim, No_Uint);
20883                        end if;
20884
20885                     elsif Is_Dispatching_Operation (Prim)
20886                       and then Disp_Typ /= Full_T
20887                     then
20888                        --  Verify that it is not otherwise controlled by a
20889                        --  formal or a return value of type T.
20890
20891                        Check_Controlling_Formals (Disp_Typ, Prim);
20892                     end if;
20893                  end if;
20894
20895                  Next_Entity (Prim);
20896               end loop;
20897            end if;
20898
20899            --  For the tagged case, the two views can share the same primitive
20900            --  operations list and the same class-wide type. Update attributes
20901            --  of the class-wide type which depend on the full declaration.
20902
20903            if Is_Tagged_Type (Priv_T) then
20904               Set_Direct_Primitive_Operations (Priv_T, Full_List);
20905               Set_Class_Wide_Type
20906                 (Base_Type (Full_T), Class_Wide_Type (Priv_T));
20907
20908               Propagate_Concurrent_Flags (Class_Wide_Type (Priv_T), Full_T);
20909            end if;
20910         end;
20911      end if;
20912
20913      --  Ada 2005 AI 161: Check preelaborable initialization consistency
20914
20915      if Known_To_Have_Preelab_Init (Priv_T) then
20916
20917         --  Case where there is a pragma Preelaborable_Initialization. We
20918         --  always allow this in predefined units, which is cheating a bit,
20919         --  but it means we don't have to struggle to meet the requirements in
20920         --  the RM for having Preelaborable Initialization. Otherwise we
20921         --  require that the type meets the RM rules. But we can't check that
20922         --  yet, because of the rule about overriding Initialize, so we simply
20923         --  set a flag that will be checked at freeze time.
20924
20925         if not In_Predefined_Unit (Full_T) then
20926            Set_Must_Have_Preelab_Init (Full_T);
20927         end if;
20928      end if;
20929
20930      --  If pragma CPP_Class was applied to the private type declaration,
20931      --  propagate it now to the full type declaration.
20932
20933      if Is_CPP_Class (Priv_T) then
20934         Set_Is_CPP_Class (Full_T);
20935         Set_Convention   (Full_T, Convention_CPP);
20936
20937         --  Check that components of imported CPP types do not have default
20938         --  expressions.
20939
20940         Check_CPP_Type_Has_No_Defaults (Full_T);
20941      end if;
20942
20943      --  If the private view has user specified stream attributes, then so has
20944      --  the full view.
20945
20946      --  Why the test, how could these flags be already set in Full_T ???
20947
20948      if Has_Specified_Stream_Read (Priv_T) then
20949         Set_Has_Specified_Stream_Read (Full_T);
20950      end if;
20951
20952      if Has_Specified_Stream_Write (Priv_T) then
20953         Set_Has_Specified_Stream_Write (Full_T);
20954      end if;
20955
20956      if Has_Specified_Stream_Input (Priv_T) then
20957         Set_Has_Specified_Stream_Input (Full_T);
20958      end if;
20959
20960      if Has_Specified_Stream_Output (Priv_T) then
20961         Set_Has_Specified_Stream_Output (Full_T);
20962      end if;
20963
20964      --  Propagate Default_Initial_Condition-related attributes from the
20965      --  partial view to the full view and its base type.
20966
20967      Propagate_DIC_Attributes (Full_T, From_Typ => Priv_T);
20968      Propagate_DIC_Attributes (Base_Type (Full_T), From_Typ => Priv_T);
20969
20970      --  Propagate invariant-related attributes from the partial view to the
20971      --  full view and its base type.
20972
20973      Propagate_Invariant_Attributes (Full_T, From_Typ => Priv_T);
20974      Propagate_Invariant_Attributes (Base_Type (Full_T), From_Typ => Priv_T);
20975
20976      --  AI12-0041: Detect an attempt to inherit a class-wide type invariant
20977      --  in the full view without advertising the inheritance in the partial
20978      --  view. This can only occur when the partial view has no parent type
20979      --  and the full view has an interface as a parent. Any other scenarios
20980      --  are illegal because implemented interfaces must match between the
20981      --  two views.
20982
20983      if Is_Tagged_Type (Priv_T) and then Is_Tagged_Type (Full_T) then
20984         declare
20985            Full_Par : constant Entity_Id := Etype (Full_T);
20986            Priv_Par : constant Entity_Id := Etype (Priv_T);
20987
20988         begin
20989            if not Is_Interface (Priv_Par)
20990              and then Is_Interface (Full_Par)
20991              and then Has_Inheritable_Invariants (Full_Par)
20992            then
20993               Error_Msg_N
20994                 ("hidden inheritance of class-wide type invariants not "
20995                  & "allowed", N);
20996            end if;
20997         end;
20998      end if;
20999
21000      --  Propagate predicates to full type, and predicate function if already
21001      --  defined. It is not clear that this can actually happen? the partial
21002      --  view cannot be frozen yet, and the predicate function has not been
21003      --  built. Still it is a cheap check and seems safer to make it.
21004
21005      if Has_Predicates (Priv_T) then
21006         Set_Has_Predicates (Full_T);
21007
21008         if Present (Predicate_Function (Priv_T)) then
21009            Set_Predicate_Function (Full_T, Predicate_Function (Priv_T));
21010         end if;
21011      end if;
21012
21013   <<Leave>>
21014      Restore_Ghost_Region (Saved_GM, Saved_IGR);
21015   end Process_Full_View;
21016
21017   -----------------------------------
21018   -- Process_Incomplete_Dependents --
21019   -----------------------------------
21020
21021   procedure Process_Incomplete_Dependents
21022     (N      : Node_Id;
21023      Full_T : Entity_Id;
21024      Inc_T  : Entity_Id)
21025   is
21026      Inc_Elmt : Elmt_Id;
21027      Priv_Dep : Entity_Id;
21028      New_Subt : Entity_Id;
21029
21030      Disc_Constraint : Elist_Id;
21031
21032   begin
21033      if No (Private_Dependents (Inc_T)) then
21034         return;
21035      end if;
21036
21037      --  Itypes that may be generated by the completion of an incomplete
21038      --  subtype are not used by the back-end and not attached to the tree.
21039      --  They are created only for constraint-checking purposes.
21040
21041      Inc_Elmt := First_Elmt (Private_Dependents (Inc_T));
21042      while Present (Inc_Elmt) loop
21043         Priv_Dep := Node (Inc_Elmt);
21044
21045         if Ekind (Priv_Dep) = E_Subprogram_Type then
21046
21047            --  An Access_To_Subprogram type may have a return type or a
21048            --  parameter type that is incomplete. Replace with the full view.
21049
21050            if Etype (Priv_Dep) = Inc_T then
21051               Set_Etype (Priv_Dep, Full_T);
21052            end if;
21053
21054            declare
21055               Formal : Entity_Id;
21056
21057            begin
21058               Formal := First_Formal (Priv_Dep);
21059               while Present (Formal) loop
21060                  if Etype (Formal) = Inc_T then
21061                     Set_Etype (Formal, Full_T);
21062                  end if;
21063
21064                  Next_Formal (Formal);
21065               end loop;
21066            end;
21067
21068         elsif Is_Overloadable (Priv_Dep) then
21069
21070            --  If a subprogram in the incomplete dependents list is primitive
21071            --  for a tagged full type then mark it as a dispatching operation,
21072            --  check whether it overrides an inherited subprogram, and check
21073            --  restrictions on its controlling formals. Note that a protected
21074            --  operation is never dispatching: only its wrapper operation
21075            --  (which has convention Ada) is.
21076
21077            if Is_Tagged_Type (Full_T)
21078              and then Is_Primitive (Priv_Dep)
21079              and then Convention (Priv_Dep) /= Convention_Protected
21080            then
21081               Check_Operation_From_Incomplete_Type (Priv_Dep, Inc_T);
21082               Set_Is_Dispatching_Operation (Priv_Dep);
21083               Check_Controlling_Formals (Full_T, Priv_Dep);
21084            end if;
21085
21086         elsif Ekind (Priv_Dep) = E_Subprogram_Body then
21087
21088            --  Can happen during processing of a body before the completion
21089            --  of a TA type. Ignore, because spec is also on dependent list.
21090
21091            return;
21092
21093         --  Ada 2005 (AI-412): Transform a regular incomplete subtype into a
21094         --  corresponding subtype of the full view.
21095
21096         elsif Ekind (Priv_Dep) = E_Incomplete_Subtype
21097           and then Comes_From_Source (Priv_Dep)
21098         then
21099            Set_Subtype_Indication
21100              (Parent (Priv_Dep), New_Occurrence_Of (Full_T, Sloc (Priv_Dep)));
21101            Set_Etype (Priv_Dep, Full_T);
21102            Set_Ekind (Priv_Dep, Subtype_Kind (Ekind (Full_T)));
21103            Set_Analyzed (Parent (Priv_Dep), False);
21104
21105            --  Reanalyze the declaration, suppressing the call to Enter_Name
21106            --  to avoid duplicate names.
21107
21108            Analyze_Subtype_Declaration
21109              (N    => Parent (Priv_Dep),
21110               Skip => True);
21111
21112         --  Dependent is a subtype
21113
21114         else
21115            --  We build a new subtype indication using the full view of the
21116            --  incomplete parent. The discriminant constraints have been
21117            --  elaborated already at the point of the subtype declaration.
21118
21119            New_Subt := Create_Itype (E_Void, N);
21120
21121            if Has_Discriminants (Full_T) then
21122               Disc_Constraint := Discriminant_Constraint (Priv_Dep);
21123            else
21124               Disc_Constraint := No_Elist;
21125            end if;
21126
21127            Build_Discriminated_Subtype (Full_T, New_Subt, Disc_Constraint, N);
21128            Set_Full_View (Priv_Dep, New_Subt);
21129         end if;
21130
21131         Next_Elmt (Inc_Elmt);
21132      end loop;
21133   end Process_Incomplete_Dependents;
21134
21135   --------------------------------
21136   -- Process_Range_Expr_In_Decl --
21137   --------------------------------
21138
21139   procedure Process_Range_Expr_In_Decl
21140     (R            : Node_Id;
21141      T            : Entity_Id;
21142      Subtyp       : Entity_Id := Empty;
21143      Check_List   : List_Id   := Empty_List;
21144      R_Check_Off  : Boolean   := False;
21145      In_Iter_Schm : Boolean   := False)
21146   is
21147      Lo, Hi      : Node_Id;
21148      R_Checks    : Check_Result;
21149      Insert_Node : Node_Id;
21150      Def_Id      : Entity_Id;
21151
21152   begin
21153      Analyze_And_Resolve (R, Base_Type (T));
21154
21155      if Nkind (R) = N_Range then
21156
21157         --  In SPARK, all ranges should be static, with the exception of the
21158         --  discrete type definition of a loop parameter specification.
21159
21160         if not In_Iter_Schm
21161           and then not Is_OK_Static_Range (R)
21162         then
21163            Check_SPARK_05_Restriction ("range should be static", R);
21164         end if;
21165
21166         Lo := Low_Bound (R);
21167         Hi := High_Bound (R);
21168
21169         --  Validity checks on the range of a quantified expression are
21170         --  delayed until the construct is transformed into a loop.
21171
21172         if Nkind (Parent (R)) = N_Loop_Parameter_Specification
21173           and then Nkind (Parent (Parent (R))) = N_Quantified_Expression
21174         then
21175            null;
21176
21177         --  We need to ensure validity of the bounds here, because if we
21178         --  go ahead and do the expansion, then the expanded code will get
21179         --  analyzed with range checks suppressed and we miss the check.
21180
21181         --  WARNING: The capture of the range bounds with xxx_FIRST/_LAST and
21182         --  the temporaries generated by routine Remove_Side_Effects by means
21183         --  of validity checks must use the same names. When a range appears
21184         --  in the parent of a generic, the range is processed with checks
21185         --  disabled as part of the generic context and with checks enabled
21186         --  for code generation purposes. This leads to link issues as the
21187         --  generic contains references to xxx_FIRST/_LAST, but the inlined
21188         --  template sees the temporaries generated by Remove_Side_Effects.
21189
21190         else
21191            Validity_Check_Range (R, Subtyp);
21192         end if;
21193
21194         --  If there were errors in the declaration, try and patch up some
21195         --  common mistakes in the bounds. The cases handled are literals
21196         --  which are Integer where the expected type is Real and vice versa.
21197         --  These corrections allow the compilation process to proceed further
21198         --  along since some basic assumptions of the format of the bounds
21199         --  are guaranteed.
21200
21201         if Etype (R) = Any_Type then
21202            if Nkind (Lo) = N_Integer_Literal and then Is_Real_Type (T) then
21203               Rewrite (Lo,
21204                 Make_Real_Literal (Sloc (Lo), UR_From_Uint (Intval (Lo))));
21205
21206            elsif Nkind (Hi) = N_Integer_Literal and then Is_Real_Type (T) then
21207               Rewrite (Hi,
21208                 Make_Real_Literal (Sloc (Hi), UR_From_Uint (Intval (Hi))));
21209
21210            elsif Nkind (Lo) = N_Real_Literal and then Is_Integer_Type (T) then
21211               Rewrite (Lo,
21212                 Make_Integer_Literal (Sloc (Lo), UR_To_Uint (Realval (Lo))));
21213
21214            elsif Nkind (Hi) = N_Real_Literal and then Is_Integer_Type (T) then
21215               Rewrite (Hi,
21216                 Make_Integer_Literal (Sloc (Hi), UR_To_Uint (Realval (Hi))));
21217            end if;
21218
21219            Set_Etype (Lo, T);
21220            Set_Etype (Hi, T);
21221         end if;
21222
21223         --  If the bounds of the range have been mistakenly given as string
21224         --  literals (perhaps in place of character literals), then an error
21225         --  has already been reported, but we rewrite the string literal as a
21226         --  bound of the range's type to avoid blowups in later processing
21227         --  that looks at static values.
21228
21229         if Nkind (Lo) = N_String_Literal then
21230            Rewrite (Lo,
21231              Make_Attribute_Reference (Sloc (Lo),
21232                Prefix         => New_Occurrence_Of (T, Sloc (Lo)),
21233                Attribute_Name => Name_First));
21234            Analyze_And_Resolve (Lo);
21235         end if;
21236
21237         if Nkind (Hi) = N_String_Literal then
21238            Rewrite (Hi,
21239              Make_Attribute_Reference (Sloc (Hi),
21240                Prefix         => New_Occurrence_Of (T, Sloc (Hi)),
21241                Attribute_Name => Name_First));
21242            Analyze_And_Resolve (Hi);
21243         end if;
21244
21245         --  If bounds aren't scalar at this point then exit, avoiding
21246         --  problems with further processing of the range in this procedure.
21247
21248         if not Is_Scalar_Type (Etype (Lo)) then
21249            return;
21250         end if;
21251
21252         --  Resolve (actually Sem_Eval) has checked that the bounds are in
21253         --  then range of the base type. Here we check whether the bounds
21254         --  are in the range of the subtype itself. Note that if the bounds
21255         --  represent the null range the Constraint_Error exception should
21256         --  not be raised.
21257
21258         --  ??? The following code should be cleaned up as follows
21259
21260         --  1. The Is_Null_Range (Lo, Hi) test should disappear since it
21261         --     is done in the call to Range_Check (R, T); below
21262
21263         --  2. The use of R_Check_Off should be investigated and possibly
21264         --     removed, this would clean up things a bit.
21265
21266         if Is_Null_Range (Lo, Hi) then
21267            null;
21268
21269         else
21270            --  Capture values of bounds and generate temporaries for them
21271            --  if needed, before applying checks, since checks may cause
21272            --  duplication of the expression without forcing evaluation.
21273
21274            --  The forced evaluation removes side effects from expressions,
21275            --  which should occur also in GNATprove mode. Otherwise, we end up
21276            --  with unexpected insertions of actions at places where this is
21277            --  not supposed to occur, e.g. on default parameters of a call.
21278
21279            if Expander_Active or GNATprove_Mode then
21280
21281               --  Call Force_Evaluation to create declarations as needed to
21282               --  deal with side effects, and also create typ_FIRST/LAST
21283               --  entities for bounds if we have a subtype name.
21284
21285               --  Note: we do this transformation even if expansion is not
21286               --  active if we are in GNATprove_Mode since the transformation
21287               --  is in general required to ensure that the resulting tree has
21288               --  proper Ada semantics.
21289
21290               Force_Evaluation
21291                 (Lo, Related_Id => Subtyp, Is_Low_Bound  => True);
21292               Force_Evaluation
21293                 (Hi, Related_Id => Subtyp, Is_High_Bound => True);
21294            end if;
21295
21296            --  We use a flag here instead of suppressing checks on the type
21297            --  because the type we check against isn't necessarily the place
21298            --  where we put the check.
21299
21300            if not R_Check_Off then
21301               R_Checks := Get_Range_Checks (R, T);
21302
21303               --  Look up tree to find an appropriate insertion point. We
21304               --  can't just use insert_actions because later processing
21305               --  depends on the insertion node. Prior to Ada 2012 the
21306               --  insertion point could only be a declaration or a loop, but
21307               --  quantified expressions can appear within any context in an
21308               --  expression, and the insertion point can be any statement,
21309               --  pragma, or declaration.
21310
21311               Insert_Node := Parent (R);
21312               while Present (Insert_Node) loop
21313                  exit when
21314                    Nkind (Insert_Node) in N_Declaration
21315                    and then
21316                      not Nkind_In
21317                        (Insert_Node, N_Component_Declaration,
21318                                      N_Loop_Parameter_Specification,
21319                                      N_Function_Specification,
21320                                      N_Procedure_Specification);
21321
21322                  exit when Nkind (Insert_Node) in N_Later_Decl_Item
21323                    or else Nkind (Insert_Node) in
21324                              N_Statement_Other_Than_Procedure_Call
21325                    or else Nkind_In (Insert_Node, N_Procedure_Call_Statement,
21326                                                   N_Pragma);
21327
21328                  Insert_Node := Parent (Insert_Node);
21329               end loop;
21330
21331               --  Why would Type_Decl not be present???  Without this test,
21332               --  short regression tests fail.
21333
21334               if Present (Insert_Node) then
21335
21336                  --  Case of loop statement. Verify that the range is part
21337                  --  of the subtype indication of the iteration scheme.
21338
21339                  if Nkind (Insert_Node) = N_Loop_Statement then
21340                     declare
21341                        Indic : Node_Id;
21342
21343                     begin
21344                        Indic := Parent (R);
21345                        while Present (Indic)
21346                          and then Nkind (Indic) /= N_Subtype_Indication
21347                        loop
21348                           Indic := Parent (Indic);
21349                        end loop;
21350
21351                        if Present (Indic) then
21352                           Def_Id := Etype (Subtype_Mark (Indic));
21353
21354                           Insert_Range_Checks
21355                             (R_Checks,
21356                              Insert_Node,
21357                              Def_Id,
21358                              Sloc (Insert_Node),
21359                              R,
21360                              Do_Before => True);
21361                        end if;
21362                     end;
21363
21364                  --  Insertion before a declaration. If the declaration
21365                  --  includes discriminants, the list of applicable checks
21366                  --  is given by the caller.
21367
21368                  elsif Nkind (Insert_Node) in N_Declaration then
21369                     Def_Id := Defining_Identifier (Insert_Node);
21370
21371                     if (Ekind (Def_Id) = E_Record_Type
21372                          and then Depends_On_Discriminant (R))
21373                       or else
21374                        (Ekind (Def_Id) = E_Protected_Type
21375                          and then Has_Discriminants (Def_Id))
21376                     then
21377                        Append_Range_Checks
21378                          (R_Checks,
21379                            Check_List, Def_Id, Sloc (Insert_Node), R);
21380
21381                     else
21382                        Insert_Range_Checks
21383                          (R_Checks,
21384                            Insert_Node, Def_Id, Sloc (Insert_Node), R);
21385
21386                     end if;
21387
21388                  --  Insertion before a statement. Range appears in the
21389                  --  context of a quantified expression. Insertion will
21390                  --  take place when expression is expanded.
21391
21392                  else
21393                     null;
21394                  end if;
21395               end if;
21396            end if;
21397         end if;
21398
21399      --  Case of other than an explicit N_Range node
21400
21401      --  The forced evaluation removes side effects from expressions, which
21402      --  should occur also in GNATprove mode. Otherwise, we end up with
21403      --  unexpected insertions of actions at places where this is not
21404      --  supposed to occur, e.g. on default parameters of a call.
21405
21406      elsif Expander_Active or GNATprove_Mode then
21407         Get_Index_Bounds (R, Lo, Hi);
21408         Force_Evaluation (Lo);
21409         Force_Evaluation (Hi);
21410      end if;
21411   end Process_Range_Expr_In_Decl;
21412
21413   --------------------------------------
21414   -- Process_Real_Range_Specification --
21415   --------------------------------------
21416
21417   procedure Process_Real_Range_Specification (Def : Node_Id) is
21418      Spec : constant Node_Id := Real_Range_Specification (Def);
21419      Lo   : Node_Id;
21420      Hi   : Node_Id;
21421      Err  : Boolean := False;
21422
21423      procedure Analyze_Bound (N : Node_Id);
21424      --  Analyze and check one bound
21425
21426      -------------------
21427      -- Analyze_Bound --
21428      -------------------
21429
21430      procedure Analyze_Bound (N : Node_Id) is
21431      begin
21432         Analyze_And_Resolve (N, Any_Real);
21433
21434         if not Is_OK_Static_Expression (N) then
21435            Flag_Non_Static_Expr
21436              ("bound in real type definition is not static!", N);
21437            Err := True;
21438         end if;
21439      end Analyze_Bound;
21440
21441   --  Start of processing for Process_Real_Range_Specification
21442
21443   begin
21444      if Present (Spec) then
21445         Lo := Low_Bound (Spec);
21446         Hi := High_Bound (Spec);
21447         Analyze_Bound (Lo);
21448         Analyze_Bound (Hi);
21449
21450         --  If error, clear away junk range specification
21451
21452         if Err then
21453            Set_Real_Range_Specification (Def, Empty);
21454         end if;
21455      end if;
21456   end Process_Real_Range_Specification;
21457
21458   ---------------------
21459   -- Process_Subtype --
21460   ---------------------
21461
21462   function Process_Subtype
21463     (S           : Node_Id;
21464      Related_Nod : Node_Id;
21465      Related_Id  : Entity_Id := Empty;
21466      Suffix      : Character := ' ') return Entity_Id
21467   is
21468      P               : Node_Id;
21469      Def_Id          : Entity_Id;
21470      Error_Node      : Node_Id;
21471      Full_View_Id    : Entity_Id;
21472      Subtype_Mark_Id : Entity_Id;
21473
21474      May_Have_Null_Exclusion : Boolean;
21475
21476      procedure Check_Incomplete (T : Node_Id);
21477      --  Called to verify that an incomplete type is not used prematurely
21478
21479      ----------------------
21480      -- Check_Incomplete --
21481      ----------------------
21482
21483      procedure Check_Incomplete (T : Node_Id) is
21484      begin
21485         --  Ada 2005 (AI-412): Incomplete subtypes are legal
21486
21487         if Ekind (Root_Type (Entity (T))) = E_Incomplete_Type
21488           and then
21489             not (Ada_Version >= Ada_2005
21490                   and then
21491                     (Nkind (Parent (T)) = N_Subtype_Declaration
21492                       or else (Nkind (Parent (T)) = N_Subtype_Indication
21493                                 and then Nkind (Parent (Parent (T))) =
21494                                                   N_Subtype_Declaration)))
21495         then
21496            Error_Msg_N ("invalid use of type before its full declaration", T);
21497         end if;
21498      end Check_Incomplete;
21499
21500   --  Start of processing for Process_Subtype
21501
21502   begin
21503      --  Case of no constraints present
21504
21505      if Nkind (S) /= N_Subtype_Indication then
21506         Find_Type (S);
21507
21508         --  No way to proceed if the subtype indication is malformed. This
21509         --  will happen for example when the subtype indication in an object
21510         --  declaration is missing altogether and the expression is analyzed
21511         --  as if it were that indication.
21512
21513         if not Is_Entity_Name (S) then
21514            return Any_Type;
21515         end if;
21516
21517         Check_Incomplete (S);
21518         P := Parent (S);
21519
21520         --  Ada 2005 (AI-231): Static check
21521
21522         if Ada_Version >= Ada_2005
21523           and then Present (P)
21524           and then Null_Exclusion_Present (P)
21525           and then Nkind (P) /= N_Access_To_Object_Definition
21526           and then not Is_Access_Type (Entity (S))
21527         then
21528            Error_Msg_N ("`NOT NULL` only allowed for an access type", S);
21529         end if;
21530
21531         --  The following is ugly, can't we have a range or even a flag???
21532
21533         May_Have_Null_Exclusion :=
21534           Nkind_In (P, N_Access_Definition,
21535                        N_Access_Function_Definition,
21536                        N_Access_Procedure_Definition,
21537                        N_Access_To_Object_Definition,
21538                        N_Allocator,
21539                        N_Component_Definition)
21540             or else
21541           Nkind_In (P, N_Derived_Type_Definition,
21542                        N_Discriminant_Specification,
21543                        N_Formal_Object_Declaration,
21544                        N_Object_Declaration,
21545                        N_Object_Renaming_Declaration,
21546                        N_Parameter_Specification,
21547                        N_Subtype_Declaration);
21548
21549         --  Create an Itype that is a duplicate of Entity (S) but with the
21550         --  null-exclusion attribute.
21551
21552         if May_Have_Null_Exclusion
21553           and then Is_Access_Type (Entity (S))
21554           and then Null_Exclusion_Present (P)
21555
21556            --  No need to check the case of an access to object definition.
21557            --  It is correct to define double not-null pointers.
21558
21559            --  Example:
21560            --     type Not_Null_Int_Ptr is not null access Integer;
21561            --     type Acc is not null access Not_Null_Int_Ptr;
21562
21563           and then Nkind (P) /= N_Access_To_Object_Definition
21564         then
21565            if Can_Never_Be_Null (Entity (S)) then
21566               case Nkind (Related_Nod) is
21567                  when N_Full_Type_Declaration =>
21568                     if Nkind (Type_Definition (Related_Nod))
21569                       in N_Array_Type_Definition
21570                     then
21571                        Error_Node :=
21572                          Subtype_Indication
21573                            (Component_Definition
21574                             (Type_Definition (Related_Nod)));
21575                     else
21576                        Error_Node :=
21577                          Subtype_Indication (Type_Definition (Related_Nod));
21578                     end if;
21579
21580                  when N_Subtype_Declaration =>
21581                     Error_Node := Subtype_Indication (Related_Nod);
21582
21583                  when N_Object_Declaration =>
21584                     Error_Node := Object_Definition (Related_Nod);
21585
21586                  when N_Component_Declaration =>
21587                     Error_Node :=
21588                       Subtype_Indication (Component_Definition (Related_Nod));
21589
21590                  when N_Allocator =>
21591                     Error_Node := Expression (Related_Nod);
21592
21593                  when others =>
21594                     pragma Assert (False);
21595                     Error_Node := Related_Nod;
21596               end case;
21597
21598               Error_Msg_NE
21599                 ("`NOT NULL` not allowed (& already excludes null)",
21600                  Error_Node,
21601                  Entity (S));
21602            end if;
21603
21604            Set_Etype  (S,
21605              Create_Null_Excluding_Itype
21606                (T           => Entity (S),
21607                 Related_Nod => P));
21608            Set_Entity (S, Etype (S));
21609         end if;
21610
21611         return Entity (S);
21612
21613      --  Case of constraint present, so that we have an N_Subtype_Indication
21614      --  node (this node is created only if constraints are present).
21615
21616      else
21617         Find_Type (Subtype_Mark (S));
21618
21619         if Nkind (Parent (S)) /= N_Access_To_Object_Definition
21620           and then not
21621            (Nkind (Parent (S)) = N_Subtype_Declaration
21622              and then Is_Itype (Defining_Identifier (Parent (S))))
21623         then
21624            Check_Incomplete (Subtype_Mark (S));
21625         end if;
21626
21627         P := Parent (S);
21628         Subtype_Mark_Id := Entity (Subtype_Mark (S));
21629
21630         --  Explicit subtype declaration case
21631
21632         if Nkind (P) = N_Subtype_Declaration then
21633            Def_Id := Defining_Identifier (P);
21634
21635         --  Explicit derived type definition case
21636
21637         elsif Nkind (P) = N_Derived_Type_Definition then
21638            Def_Id := Defining_Identifier (Parent (P));
21639
21640         --  Implicit case, the Def_Id must be created as an implicit type.
21641         --  The one exception arises in the case of concurrent types, array
21642         --  and access types, where other subsidiary implicit types may be
21643         --  created and must appear before the main implicit type. In these
21644         --  cases we leave Def_Id set to Empty as a signal that Create_Itype
21645         --  has not yet been called to create Def_Id.
21646
21647         else
21648            if Is_Array_Type (Subtype_Mark_Id)
21649              or else Is_Concurrent_Type (Subtype_Mark_Id)
21650              or else Is_Access_Type (Subtype_Mark_Id)
21651            then
21652               Def_Id := Empty;
21653
21654            --  For the other cases, we create a new unattached Itype,
21655            --  and set the indication to ensure it gets attached later.
21656
21657            else
21658               Def_Id :=
21659                 Create_Itype (E_Void, Related_Nod, Related_Id, Suffix);
21660            end if;
21661         end if;
21662
21663         --  If the kind of constraint is invalid for this kind of type,
21664         --  then give an error, and then pretend no constraint was given.
21665
21666         if not Is_Valid_Constraint_Kind
21667                   (Ekind (Subtype_Mark_Id), Nkind (Constraint (S)))
21668         then
21669            Error_Msg_N
21670              ("incorrect constraint for this kind of type", Constraint (S));
21671
21672            Rewrite (S, New_Copy_Tree (Subtype_Mark (S)));
21673
21674            --  Set Ekind of orphan itype, to prevent cascaded errors
21675
21676            if Present (Def_Id) then
21677               Set_Ekind (Def_Id, Ekind (Any_Type));
21678            end if;
21679
21680            --  Make recursive call, having got rid of the bogus constraint
21681
21682            return Process_Subtype (S, Related_Nod, Related_Id, Suffix);
21683         end if;
21684
21685         --  Remaining processing depends on type. Select on Base_Type kind to
21686         --  ensure getting to the concrete type kind in the case of a private
21687         --  subtype (needed when only doing semantic analysis).
21688
21689         case Ekind (Base_Type (Subtype_Mark_Id)) is
21690            when Access_Kind =>
21691
21692               --  If this is a constraint on a class-wide type, discard it.
21693               --  There is currently no way to express a partial discriminant
21694               --  constraint on a type with unknown discriminants. This is
21695               --  a pathology that the ACATS wisely decides not to test.
21696
21697               if Is_Class_Wide_Type (Designated_Type (Subtype_Mark_Id)) then
21698                  if Comes_From_Source (S) then
21699                     Error_Msg_N
21700                       ("constraint on class-wide type ignored??",
21701                        Constraint (S));
21702                  end if;
21703
21704                  if Nkind (P) = N_Subtype_Declaration then
21705                     Set_Subtype_Indication (P,
21706                        New_Occurrence_Of (Subtype_Mark_Id, Sloc (S)));
21707                  end if;
21708
21709                  return Subtype_Mark_Id;
21710               end if;
21711
21712               Constrain_Access (Def_Id, S, Related_Nod);
21713
21714               if Expander_Active
21715                 and then Is_Itype (Designated_Type (Def_Id))
21716                 and then Nkind (Related_Nod) = N_Subtype_Declaration
21717                 and then not Is_Incomplete_Type (Designated_Type (Def_Id))
21718               then
21719                  Build_Itype_Reference
21720                    (Designated_Type (Def_Id), Related_Nod);
21721               end if;
21722
21723            when Array_Kind =>
21724               Constrain_Array (Def_Id, S, Related_Nod, Related_Id, Suffix);
21725
21726            when Decimal_Fixed_Point_Kind =>
21727               Constrain_Decimal (Def_Id, S);
21728
21729            when Enumeration_Kind =>
21730               Constrain_Enumeration (Def_Id, S);
21731
21732            when Ordinary_Fixed_Point_Kind =>
21733               Constrain_Ordinary_Fixed (Def_Id, S);
21734
21735            when Float_Kind =>
21736               Constrain_Float (Def_Id, S);
21737
21738            when Integer_Kind =>
21739               Constrain_Integer (Def_Id, S);
21740
21741            when Class_Wide_Kind
21742               | E_Incomplete_Type
21743               | E_Record_Subtype
21744               | E_Record_Type
21745            =>
21746               Constrain_Discriminated_Type (Def_Id, S, Related_Nod);
21747
21748               if Ekind (Def_Id) = E_Incomplete_Type then
21749                  Set_Private_Dependents (Def_Id, New_Elmt_List);
21750               end if;
21751
21752            when Private_Kind =>
21753
21754               --  A private type with unknown discriminants may be completed
21755               --  by an unconstrained array type.
21756
21757               if Has_Unknown_Discriminants (Subtype_Mark_Id)
21758                 and then Present (Full_View (Subtype_Mark_Id))
21759                 and then Is_Array_Type (Full_View (Subtype_Mark_Id))
21760               then
21761                  Constrain_Array (Def_Id, S, Related_Nod, Related_Id, Suffix);
21762
21763               --  ... but more commonly is completed by a discriminated record
21764               --  type.
21765
21766               else
21767                  Constrain_Discriminated_Type (Def_Id, S, Related_Nod);
21768               end if;
21769
21770               --  The base type may be private but Def_Id may be a full view
21771               --  in an instance.
21772
21773               if Is_Private_Type (Def_Id) then
21774                  Set_Private_Dependents (Def_Id, New_Elmt_List);
21775               end if;
21776
21777               --  In case of an invalid constraint prevent further processing
21778               --  since the type constructed is missing expected fields.
21779
21780               if Etype (Def_Id) = Any_Type then
21781                  return Def_Id;
21782               end if;
21783
21784               --  If the full view is that of a task with discriminants,
21785               --  we must constrain both the concurrent type and its
21786               --  corresponding record type. Otherwise we will just propagate
21787               --  the constraint to the full view, if available.
21788
21789               if Present (Full_View (Subtype_Mark_Id))
21790                 and then Has_Discriminants (Subtype_Mark_Id)
21791                 and then Is_Concurrent_Type (Full_View (Subtype_Mark_Id))
21792               then
21793                  Full_View_Id :=
21794                    Create_Itype (E_Void, Related_Nod, Related_Id, Suffix);
21795
21796                  Set_Entity (Subtype_Mark (S), Full_View (Subtype_Mark_Id));
21797                  Constrain_Concurrent (Full_View_Id, S,
21798                    Related_Nod, Related_Id, Suffix);
21799                  Set_Entity (Subtype_Mark (S), Subtype_Mark_Id);
21800                  Set_Full_View (Def_Id, Full_View_Id);
21801
21802                  --  Introduce an explicit reference to the private subtype,
21803                  --  to prevent scope anomalies in gigi if first use appears
21804                  --  in a nested context, e.g. a later function body.
21805                  --  Should this be generated in other contexts than a full
21806                  --  type declaration?
21807
21808                  if Is_Itype (Def_Id)
21809                    and then
21810                      Nkind (Parent (P)) = N_Full_Type_Declaration
21811                  then
21812                     Build_Itype_Reference (Def_Id, Parent (P));
21813                  end if;
21814
21815               else
21816                  Prepare_Private_Subtype_Completion (Def_Id, Related_Nod);
21817               end if;
21818
21819            when Concurrent_Kind  =>
21820               Constrain_Concurrent (Def_Id, S,
21821                 Related_Nod, Related_Id, Suffix);
21822
21823            when others =>
21824               Error_Msg_N ("invalid subtype mark in subtype indication", S);
21825         end case;
21826
21827         --  Size, Alignment, Representation aspects and Convention are always
21828         --  inherited from the base type.
21829
21830         Set_Size_Info  (Def_Id,            (Subtype_Mark_Id));
21831         Set_Rep_Info   (Def_Id,            (Subtype_Mark_Id));
21832         Set_Convention (Def_Id, Convention (Subtype_Mark_Id));
21833
21834         --  The anonymous subtype created for the subtype indication
21835         --  inherits the predicates of the parent.
21836
21837         if Has_Predicates (Subtype_Mark_Id) then
21838            Inherit_Predicate_Flags (Def_Id, Subtype_Mark_Id);
21839
21840            --  Indicate where the predicate function may be found
21841
21842            if No (Predicate_Function (Def_Id)) and then Is_Itype (Def_Id) then
21843               Set_Predicated_Parent (Def_Id, Subtype_Mark_Id);
21844            end if;
21845         end if;
21846
21847         return Def_Id;
21848      end if;
21849   end Process_Subtype;
21850
21851   -----------------------------
21852   -- Record_Type_Declaration --
21853   -----------------------------
21854
21855   procedure Record_Type_Declaration
21856     (T    : Entity_Id;
21857      N    : Node_Id;
21858      Prev : Entity_Id)
21859   is
21860      Def       : constant Node_Id := Type_Definition (N);
21861      Is_Tagged : Boolean;
21862      Tag_Comp  : Entity_Id;
21863
21864   begin
21865      --  These flags must be initialized before calling Process_Discriminants
21866      --  because this routine makes use of them.
21867
21868      Set_Ekind             (T, E_Record_Type);
21869      Set_Etype             (T, T);
21870      Init_Size_Align       (T);
21871      Set_Interfaces        (T, No_Elist);
21872      Set_Stored_Constraint (T, No_Elist);
21873      Set_Default_SSO       (T);
21874      Set_No_Reordering     (T, No_Component_Reordering);
21875
21876      --  Normal case
21877
21878      if Ada_Version < Ada_2005 or else not Interface_Present (Def) then
21879         if Limited_Present (Def) then
21880            Check_SPARK_05_Restriction ("limited is not allowed", N);
21881         end if;
21882
21883         if Abstract_Present (Def) then
21884            Check_SPARK_05_Restriction ("abstract is not allowed", N);
21885         end if;
21886
21887         --  The flag Is_Tagged_Type might have already been set by
21888         --  Find_Type_Name if it detected an error for declaration T. This
21889         --  arises in the case of private tagged types where the full view
21890         --  omits the word tagged.
21891
21892         Is_Tagged :=
21893           Tagged_Present (Def)
21894             or else (Serious_Errors_Detected > 0 and then Is_Tagged_Type (T));
21895
21896         Set_Is_Limited_Record (T, Limited_Present (Def));
21897
21898         if Is_Tagged then
21899            Set_Is_Tagged_Type (T, True);
21900            Set_No_Tagged_Streams_Pragma (T, No_Tagged_Streams);
21901         end if;
21902
21903         --  Type is abstract if full declaration carries keyword, or if
21904         --  previous partial view did.
21905
21906         Set_Is_Abstract_Type    (T, Is_Abstract_Type (T)
21907                                      or else Abstract_Present (Def));
21908
21909      else
21910         Check_SPARK_05_Restriction ("interface is not allowed", N);
21911
21912         Is_Tagged := True;
21913         Analyze_Interface_Declaration (T, Def);
21914
21915         if Present (Discriminant_Specifications (N)) then
21916            Error_Msg_N
21917              ("interface types cannot have discriminants",
21918                Defining_Identifier
21919                  (First (Discriminant_Specifications (N))));
21920         end if;
21921      end if;
21922
21923      --  First pass: if there are self-referential access components,
21924      --  create the required anonymous access type declarations, and if
21925      --  need be an incomplete type declaration for T itself.
21926
21927      Check_Anonymous_Access_Components (N, T, Prev, Component_List (Def));
21928
21929      if Ada_Version >= Ada_2005
21930        and then Present (Interface_List (Def))
21931      then
21932         Check_Interfaces (N, Def);
21933
21934         declare
21935            Ifaces_List : Elist_Id;
21936
21937         begin
21938            --  Ada 2005 (AI-251): Collect the list of progenitors that are not
21939            --  already in the parents.
21940
21941            Collect_Interfaces
21942              (T               => T,
21943               Ifaces_List     => Ifaces_List,
21944               Exclude_Parents => True);
21945
21946            Set_Interfaces (T, Ifaces_List);
21947         end;
21948      end if;
21949
21950      --  Records constitute a scope for the component declarations within.
21951      --  The scope is created prior to the processing of these declarations.
21952      --  Discriminants are processed first, so that they are visible when
21953      --  processing the other components. The Ekind of the record type itself
21954      --  is set to E_Record_Type (subtypes appear as E_Record_Subtype).
21955
21956      --  Enter record scope
21957
21958      Push_Scope (T);
21959
21960      --  If an incomplete or private type declaration was already given for
21961      --  the type, then this scope already exists, and the discriminants have
21962      --  been declared within. We must verify that the full declaration
21963      --  matches the incomplete one.
21964
21965      Check_Or_Process_Discriminants (N, T, Prev);
21966
21967      Set_Is_Constrained     (T, not Has_Discriminants (T));
21968      Set_Has_Delayed_Freeze (T, True);
21969
21970      --  For tagged types add a manually analyzed component corresponding
21971      --  to the component _tag, the corresponding piece of tree will be
21972      --  expanded as part of the freezing actions if it is not a CPP_Class.
21973
21974      if Is_Tagged then
21975
21976         --  Do not add the tag unless we are in expansion mode
21977
21978         if Expander_Active then
21979            Tag_Comp := Make_Defining_Identifier (Sloc (Def), Name_uTag);
21980            Enter_Name (Tag_Comp);
21981
21982            Set_Ekind                     (Tag_Comp, E_Component);
21983            Set_Is_Tag                    (Tag_Comp);
21984            Set_Is_Aliased                (Tag_Comp);
21985            Set_Etype                     (Tag_Comp, RTE (RE_Tag));
21986            Set_DT_Entry_Count            (Tag_Comp, No_Uint);
21987            Set_Original_Record_Component (Tag_Comp, Tag_Comp);
21988            Init_Component_Location       (Tag_Comp);
21989
21990            --  Ada 2005 (AI-251): Addition of the Tag corresponding to all the
21991            --  implemented interfaces.
21992
21993            if Has_Interfaces (T) then
21994               Add_Interface_Tag_Components (N, T);
21995            end if;
21996         end if;
21997
21998         Make_Class_Wide_Type (T);
21999         Set_Direct_Primitive_Operations (T, New_Elmt_List);
22000      end if;
22001
22002      --  We must suppress range checks when processing record components in
22003      --  the presence of discriminants, since we don't want spurious checks to
22004      --  be generated during their analysis, but Suppress_Range_Checks flags
22005      --  must be reset the after processing the record definition.
22006
22007      --  Note: this is the only use of Kill_Range_Checks, and is a bit odd,
22008      --  couldn't we just use the normal range check suppression method here.
22009      --  That would seem cleaner ???
22010
22011      if Has_Discriminants (T) and then not Range_Checks_Suppressed (T) then
22012         Set_Kill_Range_Checks (T, True);
22013         Record_Type_Definition (Def, Prev);
22014         Set_Kill_Range_Checks (T, False);
22015      else
22016         Record_Type_Definition (Def, Prev);
22017      end if;
22018
22019      --  Exit from record scope
22020
22021      End_Scope;
22022
22023      --  Ada 2005 (AI-251 and AI-345): Derive the interface subprograms of all
22024      --  the implemented interfaces and associate them an aliased entity.
22025
22026      if Is_Tagged
22027        and then not Is_Empty_List (Interface_List (Def))
22028      then
22029         Derive_Progenitor_Subprograms (T, T);
22030      end if;
22031
22032      Check_Function_Writable_Actuals (N);
22033   end Record_Type_Declaration;
22034
22035   ----------------------------
22036   -- Record_Type_Definition --
22037   ----------------------------
22038
22039   procedure Record_Type_Definition (Def : Node_Id; Prev_T : Entity_Id) is
22040      Component          : Entity_Id;
22041      Ctrl_Components    : Boolean := False;
22042      Final_Storage_Only : Boolean;
22043      T                  : Entity_Id;
22044
22045   begin
22046      if Ekind (Prev_T) = E_Incomplete_Type then
22047         T := Full_View (Prev_T);
22048      else
22049         T := Prev_T;
22050      end if;
22051
22052      --  In SPARK, tagged types and type extensions may only be declared in
22053      --  the specification of library unit packages.
22054
22055      if Present (Def) and then Is_Tagged_Type (T) then
22056         declare
22057            Typ  : Node_Id;
22058            Ctxt : Node_Id;
22059
22060         begin
22061            if Nkind (Parent (Def)) = N_Full_Type_Declaration then
22062               Typ := Parent (Def);
22063            else
22064               pragma Assert
22065                 (Nkind (Parent (Def)) = N_Derived_Type_Definition);
22066               Typ := Parent (Parent (Def));
22067            end if;
22068
22069            Ctxt := Parent (Typ);
22070
22071            if Nkind (Ctxt) = N_Package_Body
22072              and then Nkind (Parent (Ctxt)) = N_Compilation_Unit
22073            then
22074               Check_SPARK_05_Restriction
22075                 ("type should be defined in package specification", Typ);
22076
22077            elsif Nkind (Ctxt) /= N_Package_Specification
22078              or else Nkind (Parent (Parent (Ctxt))) /= N_Compilation_Unit
22079            then
22080               Check_SPARK_05_Restriction
22081                 ("type should be defined in library unit package", Typ);
22082            end if;
22083         end;
22084      end if;
22085
22086      Final_Storage_Only := not Is_Controlled (T);
22087
22088      --  Ada 2005: Check whether an explicit Limited is present in a derived
22089      --  type declaration.
22090
22091      if Nkind (Parent (Def)) = N_Derived_Type_Definition
22092        and then Limited_Present (Parent (Def))
22093      then
22094         Set_Is_Limited_Record (T);
22095      end if;
22096
22097      --  If the component list of a record type is defined by the reserved
22098      --  word null and there is no discriminant part, then the record type has
22099      --  no components and all records of the type are null records (RM 3.7)
22100      --  This procedure is also called to process the extension part of a
22101      --  record extension, in which case the current scope may have inherited
22102      --  components.
22103
22104      if No (Def)
22105        or else No (Component_List (Def))
22106        or else Null_Present (Component_List (Def))
22107      then
22108         if not Is_Tagged_Type (T) then
22109            Check_SPARK_05_Restriction ("untagged record cannot be null", Def);
22110         end if;
22111
22112      else
22113         Analyze_Declarations (Component_Items (Component_List (Def)));
22114
22115         if Present (Variant_Part (Component_List (Def))) then
22116            Check_SPARK_05_Restriction ("variant part is not allowed", Def);
22117            Analyze (Variant_Part (Component_List (Def)));
22118         end if;
22119      end if;
22120
22121      --  After completing the semantic analysis of the record definition,
22122      --  record components, both new and inherited, are accessible. Set their
22123      --  kind accordingly. Exclude malformed itypes from illegal declarations,
22124      --  whose Ekind may be void.
22125
22126      Component := First_Entity (Current_Scope);
22127      while Present (Component) loop
22128         if Ekind (Component) = E_Void
22129           and then not Is_Itype (Component)
22130         then
22131            Set_Ekind (Component, E_Component);
22132            Init_Component_Location (Component);
22133         end if;
22134
22135         Propagate_Concurrent_Flags (T, Etype (Component));
22136
22137         if Ekind (Component) /= E_Component then
22138            null;
22139
22140         --  Do not set Has_Controlled_Component on a class-wide equivalent
22141         --  type. See Make_CW_Equivalent_Type.
22142
22143         elsif not Is_Class_Wide_Equivalent_Type (T)
22144           and then (Has_Controlled_Component (Etype (Component))
22145                      or else (Chars (Component) /= Name_uParent
22146                                and then Is_Controlled (Etype (Component))))
22147         then
22148            Set_Has_Controlled_Component (T, True);
22149            Final_Storage_Only :=
22150              Final_Storage_Only
22151                and then Finalize_Storage_Only (Etype (Component));
22152            Ctrl_Components := True;
22153         end if;
22154
22155         Next_Entity (Component);
22156      end loop;
22157
22158      --  A Type is Finalize_Storage_Only only if all its controlled components
22159      --  are also.
22160
22161      if Ctrl_Components then
22162         Set_Finalize_Storage_Only (T, Final_Storage_Only);
22163      end if;
22164
22165      --  Place reference to end record on the proper entity, which may
22166      --  be a partial view.
22167
22168      if Present (Def) then
22169         Process_End_Label (Def, 'e', Prev_T);
22170      end if;
22171   end Record_Type_Definition;
22172
22173   ------------------------
22174   -- Replace_Components --
22175   ------------------------
22176
22177   procedure Replace_Components (Typ : Entity_Id; Decl : Node_Id) is
22178      function Process (N : Node_Id) return Traverse_Result;
22179
22180      -------------
22181      -- Process --
22182      -------------
22183
22184      function Process (N : Node_Id) return Traverse_Result is
22185         Comp : Entity_Id;
22186
22187      begin
22188         if Nkind (N) = N_Discriminant_Specification then
22189            Comp := First_Discriminant (Typ);
22190            while Present (Comp) loop
22191               if Chars (Comp) = Chars (Defining_Identifier (N)) then
22192                  Set_Defining_Identifier (N, Comp);
22193                  exit;
22194               end if;
22195
22196               Next_Discriminant (Comp);
22197            end loop;
22198
22199         elsif Nkind (N) = N_Variant_Part then
22200            Comp := First_Discriminant (Typ);
22201            while Present (Comp) loop
22202               if Chars (Comp) = Chars (Name (N)) then
22203                  Set_Entity (Name (N), Comp);
22204                  exit;
22205               end if;
22206
22207               Next_Discriminant (Comp);
22208            end loop;
22209
22210         elsif Nkind (N) = N_Component_Declaration then
22211            Comp := First_Component (Typ);
22212            while Present (Comp) loop
22213               if Chars (Comp) = Chars (Defining_Identifier (N)) then
22214                  Set_Defining_Identifier (N, Comp);
22215                  exit;
22216               end if;
22217
22218               Next_Component (Comp);
22219            end loop;
22220         end if;
22221
22222         return OK;
22223      end Process;
22224
22225      procedure Replace is new Traverse_Proc (Process);
22226
22227   --  Start of processing for Replace_Components
22228
22229   begin
22230      Replace (Decl);
22231   end Replace_Components;
22232
22233   -------------------------------
22234   -- Set_Completion_Referenced --
22235   -------------------------------
22236
22237   procedure Set_Completion_Referenced (E : Entity_Id) is
22238   begin
22239      --  If in main unit, mark entity that is a completion as referenced,
22240      --  warnings go on the partial view when needed.
22241
22242      if In_Extended_Main_Source_Unit (E) then
22243         Set_Referenced (E);
22244      end if;
22245   end Set_Completion_Referenced;
22246
22247   ---------------------
22248   -- Set_Default_SSO --
22249   ---------------------
22250
22251   procedure Set_Default_SSO (T : Entity_Id) is
22252   begin
22253      case Opt.Default_SSO is
22254         when ' ' =>
22255            null;
22256         when 'L' =>
22257            Set_SSO_Set_Low_By_Default (T, True);
22258         when 'H' =>
22259            Set_SSO_Set_High_By_Default (T, True);
22260         when others =>
22261            raise Program_Error;
22262      end case;
22263   end Set_Default_SSO;
22264
22265   ---------------------
22266   -- Set_Fixed_Range --
22267   ---------------------
22268
22269   --  The range for fixed-point types is complicated by the fact that we
22270   --  do not know the exact end points at the time of the declaration. This
22271   --  is true for three reasons:
22272
22273   --     A size clause may affect the fudging of the end-points.
22274   --     A small clause may affect the values of the end-points.
22275   --     We try to include the end-points if it does not affect the size.
22276
22277   --  This means that the actual end-points must be established at the
22278   --  point when the type is frozen. Meanwhile, we first narrow the range
22279   --  as permitted (so that it will fit if necessary in a small specified
22280   --  size), and then build a range subtree with these narrowed bounds.
22281   --  Set_Fixed_Range constructs the range from real literal values, and
22282   --  sets the range as the Scalar_Range of the given fixed-point type entity.
22283
22284   --  The parent of this range is set to point to the entity so that it is
22285   --  properly hooked into the tree (unlike normal Scalar_Range entries for
22286   --  other scalar types, which are just pointers to the range in the
22287   --  original tree, this would otherwise be an orphan).
22288
22289   --  The tree is left unanalyzed. When the type is frozen, the processing
22290   --  in Freeze.Freeze_Fixed_Point_Type notices that the range is not
22291   --  analyzed, and uses this as an indication that it should complete
22292   --  work on the range (it will know the final small and size values).
22293
22294   procedure Set_Fixed_Range
22295     (E   : Entity_Id;
22296      Loc : Source_Ptr;
22297      Lo  : Ureal;
22298      Hi  : Ureal)
22299   is
22300      S : constant Node_Id :=
22301            Make_Range (Loc,
22302              Low_Bound  => Make_Real_Literal (Loc, Lo),
22303              High_Bound => Make_Real_Literal (Loc, Hi));
22304   begin
22305      Set_Scalar_Range (E, S);
22306      Set_Parent (S, E);
22307
22308      --  Before the freeze point, the bounds of a fixed point are universal
22309      --  and carry the corresponding type.
22310
22311      Set_Etype (Low_Bound (S),  Universal_Real);
22312      Set_Etype (High_Bound (S), Universal_Real);
22313   end Set_Fixed_Range;
22314
22315   ----------------------------------
22316   -- Set_Scalar_Range_For_Subtype --
22317   ----------------------------------
22318
22319   procedure Set_Scalar_Range_For_Subtype
22320     (Def_Id : Entity_Id;
22321      R      : Node_Id;
22322      Subt   : Entity_Id)
22323   is
22324      Kind : constant Entity_Kind := Ekind (Def_Id);
22325
22326   begin
22327      --  Defend against previous error
22328
22329      if Nkind (R) = N_Error then
22330         return;
22331      end if;
22332
22333      Set_Scalar_Range (Def_Id, R);
22334
22335      --  We need to link the range into the tree before resolving it so
22336      --  that types that are referenced, including importantly the subtype
22337      --  itself, are properly frozen (Freeze_Expression requires that the
22338      --  expression be properly linked into the tree). Of course if it is
22339      --  already linked in, then we do not disturb the current link.
22340
22341      if No (Parent (R)) then
22342         Set_Parent (R, Def_Id);
22343      end if;
22344
22345      --  Reset the kind of the subtype during analysis of the range, to
22346      --  catch possible premature use in the bounds themselves.
22347
22348      Set_Ekind (Def_Id, E_Void);
22349      Process_Range_Expr_In_Decl (R, Subt, Subtyp => Def_Id);
22350      Set_Ekind (Def_Id, Kind);
22351   end Set_Scalar_Range_For_Subtype;
22352
22353   --------------------------------------------------------
22354   -- Set_Stored_Constraint_From_Discriminant_Constraint --
22355   --------------------------------------------------------
22356
22357   procedure Set_Stored_Constraint_From_Discriminant_Constraint
22358     (E : Entity_Id)
22359   is
22360   begin
22361      --  Make sure set if encountered during Expand_To_Stored_Constraint
22362
22363      Set_Stored_Constraint (E, No_Elist);
22364
22365      --  Give it the right value
22366
22367      if Is_Constrained (E) and then Has_Discriminants (E) then
22368         Set_Stored_Constraint (E,
22369           Expand_To_Stored_Constraint (E, Discriminant_Constraint (E)));
22370      end if;
22371   end Set_Stored_Constraint_From_Discriminant_Constraint;
22372
22373   -------------------------------------
22374   -- Signed_Integer_Type_Declaration --
22375   -------------------------------------
22376
22377   procedure Signed_Integer_Type_Declaration (T : Entity_Id; Def : Node_Id) is
22378      Implicit_Base : Entity_Id;
22379      Base_Typ      : Entity_Id;
22380      Lo_Val        : Uint;
22381      Hi_Val        : Uint;
22382      Errs          : Boolean := False;
22383      Lo            : Node_Id;
22384      Hi            : Node_Id;
22385
22386      function Can_Derive_From (E : Entity_Id) return Boolean;
22387      --  Determine whether given bounds allow derivation from specified type
22388
22389      procedure Check_Bound (Expr : Node_Id);
22390      --  Check bound to make sure it is integral and static. If not, post
22391      --  appropriate error message and set Errs flag
22392
22393      ---------------------
22394      -- Can_Derive_From --
22395      ---------------------
22396
22397      --  Note we check both bounds against both end values, to deal with
22398      --  strange types like ones with a range of 0 .. -12341234.
22399
22400      function Can_Derive_From (E : Entity_Id) return Boolean is
22401         Lo : constant Uint := Expr_Value (Type_Low_Bound (E));
22402         Hi : constant Uint := Expr_Value (Type_High_Bound (E));
22403      begin
22404         return Lo <= Lo_Val and then Lo_Val <= Hi
22405                  and then
22406                Lo <= Hi_Val and then Hi_Val <= Hi;
22407      end Can_Derive_From;
22408
22409      -----------------
22410      -- Check_Bound --
22411      -----------------
22412
22413      procedure Check_Bound (Expr : Node_Id) is
22414      begin
22415         --  If a range constraint is used as an integer type definition, each
22416         --  bound of the range must be defined by a static expression of some
22417         --  integer type, but the two bounds need not have the same integer
22418         --  type (Negative bounds are allowed.) (RM 3.5.4)
22419
22420         if not Is_Integer_Type (Etype (Expr)) then
22421            Error_Msg_N
22422              ("integer type definition bounds must be of integer type", Expr);
22423            Errs := True;
22424
22425         elsif not Is_OK_Static_Expression (Expr) then
22426            Flag_Non_Static_Expr
22427              ("non-static expression used for integer type bound!", Expr);
22428            Errs := True;
22429
22430         --  The bounds are folded into literals, and we set their type to be
22431         --  universal, to avoid typing difficulties: we cannot set the type
22432         --  of the literal to the new type, because this would be a forward
22433         --  reference for the back end,  and if the original type is user-
22434         --  defined this can lead to spurious semantic errors (e.g. 2928-003).
22435
22436         else
22437            if Is_Entity_Name (Expr) then
22438               Fold_Uint (Expr, Expr_Value (Expr), True);
22439            end if;
22440
22441            Set_Etype (Expr, Universal_Integer);
22442         end if;
22443      end Check_Bound;
22444
22445   --  Start of processing for Signed_Integer_Type_Declaration
22446
22447   begin
22448      --  Create an anonymous base type
22449
22450      Implicit_Base :=
22451        Create_Itype (E_Signed_Integer_Type, Parent (Def), T, 'B');
22452
22453      --  Analyze and check the bounds, they can be of any integer type
22454
22455      Lo := Low_Bound (Def);
22456      Hi := High_Bound (Def);
22457
22458      --  Arbitrarily use Integer as the type if either bound had an error
22459
22460      if Hi = Error or else Lo = Error then
22461         Base_Typ := Any_Integer;
22462         Set_Error_Posted (T, True);
22463
22464      --  Here both bounds are OK expressions
22465
22466      else
22467         Analyze_And_Resolve (Lo, Any_Integer);
22468         Analyze_And_Resolve (Hi, Any_Integer);
22469
22470         Check_Bound (Lo);
22471         Check_Bound (Hi);
22472
22473         if Errs then
22474            Hi := Type_High_Bound (Standard_Long_Long_Integer);
22475            Lo := Type_Low_Bound (Standard_Long_Long_Integer);
22476         end if;
22477
22478         --  Find type to derive from
22479
22480         Lo_Val := Expr_Value (Lo);
22481         Hi_Val := Expr_Value (Hi);
22482
22483         if Can_Derive_From (Standard_Short_Short_Integer) then
22484            Base_Typ := Base_Type (Standard_Short_Short_Integer);
22485
22486         elsif Can_Derive_From (Standard_Short_Integer) then
22487            Base_Typ := Base_Type (Standard_Short_Integer);
22488
22489         elsif Can_Derive_From (Standard_Integer) then
22490            Base_Typ := Base_Type (Standard_Integer);
22491
22492         elsif Can_Derive_From (Standard_Long_Integer) then
22493            Base_Typ := Base_Type (Standard_Long_Integer);
22494
22495         elsif Can_Derive_From (Standard_Long_Long_Integer) then
22496            Check_Restriction (No_Long_Long_Integers, Def);
22497            Base_Typ := Base_Type (Standard_Long_Long_Integer);
22498
22499         else
22500            Base_Typ := Base_Type (Standard_Long_Long_Integer);
22501            Error_Msg_N ("integer type definition bounds out of range", Def);
22502            Hi := Type_High_Bound (Standard_Long_Long_Integer);
22503            Lo := Type_Low_Bound (Standard_Long_Long_Integer);
22504         end if;
22505      end if;
22506
22507      --  Complete both implicit base and declared first subtype entities. The
22508      --  inheritance of the rep item chain ensures that SPARK-related pragmas
22509      --  are not clobbered when the signed integer type acts as a full view of
22510      --  a private type.
22511
22512      Set_Etype          (Implicit_Base,                 Base_Typ);
22513      Set_Size_Info      (Implicit_Base,                 Base_Typ);
22514      Set_RM_Size        (Implicit_Base, RM_Size        (Base_Typ));
22515      Set_First_Rep_Item (Implicit_Base, First_Rep_Item (Base_Typ));
22516      Set_Scalar_Range   (Implicit_Base, Scalar_Range   (Base_Typ));
22517
22518      Set_Ekind              (T, E_Signed_Integer_Subtype);
22519      Set_Etype              (T, Implicit_Base);
22520      Set_Size_Info          (T, Implicit_Base);
22521      Inherit_Rep_Item_Chain (T, Implicit_Base);
22522      Set_Scalar_Range       (T, Def);
22523      Set_RM_Size            (T, UI_From_Int (Minimum_Size (T)));
22524      Set_Is_Constrained     (T);
22525   end Signed_Integer_Type_Declaration;
22526
22527end Sem_Ch3;
22528