exp_ch3.adb (Expand_N_Full_Type_Declaration): Capture, set and restore the Ghost...
[platform/upstream/gcc.git] / gcc / ada / sem_ch13.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT COMPILER COMPONENTS                         --
4 --                                                                          --
5 --                             S E M _ C H 1 3                              --
6 --                                                                          --
7 --                                 B o d y                                  --
8 --                                                                          --
9 --          Copyright (C) 1992-2015, Free Software Foundation, Inc.         --
10 --                                                                          --
11 -- GNAT is free software;  you can  redistribute it  and/or modify it under --
12 -- terms of the  GNU General Public License as published  by the Free Soft- --
13 -- ware  Foundation;  either version 3,  or (at your option) any later ver- --
14 -- sion.  GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License --
17 -- for  more details.  You should have  received  a copy of the GNU General --
18 -- Public License  distributed with GNAT; see file COPYING3.  If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license.          --
20 --                                                                          --
21 -- GNAT was originally developed  by the GNAT team at  New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc.      --
23 --                                                                          --
24 ------------------------------------------------------------------------------
25
26 with Aspects;  use Aspects;
27 with Atree;    use Atree;
28 with Checks;   use Checks;
29 with Debug;    use Debug;
30 with Einfo;    use Einfo;
31 with Elists;   use Elists;
32 with Errout;   use Errout;
33 with Exp_Disp; use Exp_Disp;
34 with Exp_Tss;  use Exp_Tss;
35 with Exp_Util; use Exp_Util;
36 with Freeze;   use Freeze;
37 with Ghost;    use Ghost;
38 with Lib;      use Lib;
39 with Lib.Xref; use Lib.Xref;
40 with Namet;    use Namet;
41 with Nlists;   use Nlists;
42 with Nmake;    use Nmake;
43 with Opt;      use Opt;
44 with Restrict; use Restrict;
45 with Rident;   use Rident;
46 with Rtsfind;  use Rtsfind;
47 with Sem;      use Sem;
48 with Sem_Aux;  use Sem_Aux;
49 with Sem_Case; use Sem_Case;
50 with Sem_Ch3;  use Sem_Ch3;
51 with Sem_Ch6;  use Sem_Ch6;
52 with Sem_Ch8;  use Sem_Ch8;
53 with Sem_Dim;  use Sem_Dim;
54 with Sem_Disp; use Sem_Disp;
55 with Sem_Eval; use Sem_Eval;
56 with Sem_Prag; use Sem_Prag;
57 with Sem_Res;  use Sem_Res;
58 with Sem_Type; use Sem_Type;
59 with Sem_Util; use Sem_Util;
60 with Sem_Warn; use Sem_Warn;
61 with Sinput;   use Sinput;
62 with Snames;   use Snames;
63 with Stand;    use Stand;
64 with Sinfo;    use Sinfo;
65 with Stringt;  use Stringt;
66 with Targparm; use Targparm;
67 with Ttypes;   use Ttypes;
68 with Tbuild;   use Tbuild;
69 with Urealp;   use Urealp;
70 with Warnsw;   use Warnsw;
71
72 with GNAT.Heap_Sort_G;
73
74 package body Sem_Ch13 is
75
76    SSU : constant Pos := System_Storage_Unit;
77    --  Convenient short hand for commonly used constant
78
79    -----------------------
80    -- Local Subprograms --
81    -----------------------
82
83    procedure Alignment_Check_For_Size_Change (Typ : Entity_Id; Size : Uint);
84    --  This routine is called after setting one of the sizes of type entity
85    --  Typ to Size. The purpose is to deal with the situation of a derived
86    --  type whose inherited alignment is no longer appropriate for the new
87    --  size value. In this case, we reset the Alignment to unknown.
88
89    procedure Build_Discrete_Static_Predicate
90      (Typ  : Entity_Id;
91       Expr : Node_Id;
92       Nam  : Name_Id);
93    --  Given a predicated type Typ, where Typ is a discrete static subtype,
94    --  whose predicate expression is Expr, tests if Expr is a static predicate,
95    --  and if so, builds the predicate range list. Nam is the name of the one
96    --  argument to the predicate function. Occurrences of the type name in the
97    --  predicate expression have been replaced by identifier references to this
98    --  name, which is unique, so any identifier with Chars matching Nam must be
99    --  a reference to the type. If the predicate is non-static, this procedure
100    --  returns doing nothing. If the predicate is static, then the predicate
101    --  list is stored in Static_Discrete_Predicate (Typ), and the Expr is
102    --  rewritten as a canonicalized membership operation.
103
104    procedure Build_Predicate_Functions (Typ : Entity_Id; N : Node_Id);
105    --  If Typ has predicates (indicated by Has_Predicates being set for Typ),
106    --  then either there are pragma Predicate entries on the rep chain for the
107    --  type (note that Predicate aspects are converted to pragma Predicate), or
108    --  there are inherited aspects from a parent type, or ancestor subtypes.
109    --  This procedure builds the spec and body for the Predicate function that
110    --  tests these predicates. N is the freeze node for the type. The spec of
111    --  the function is inserted before the freeze node, and the body of the
112    --  function is inserted after the freeze node. If the predicate expression
113    --  has at least one Raise_Expression, then this procedure also builds the
114    --  M version of the predicate function for use in membership tests.
115
116    procedure Check_Pool_Size_Clash (Ent : Entity_Id; SP, SS : Node_Id);
117    --  Called if both Storage_Pool and Storage_Size attribute definition
118    --  clauses (SP and SS) are present for entity Ent. Issue error message.
119
120    procedure Freeze_Entity_Checks (N : Node_Id);
121    --  Called from Analyze_Freeze_Entity and Analyze_Generic_Freeze Entity
122    --  to generate appropriate semantic checks that are delayed until this
123    --  point (they had to be delayed this long for cases of delayed aspects,
124    --  e.g. analysis of statically predicated subtypes in choices, for which
125    --  we have to be sure the subtypes in question are frozen before checking.
126
127    function Get_Alignment_Value (Expr : Node_Id) return Uint;
128    --  Given the expression for an alignment value, returns the corresponding
129    --  Uint value. If the value is inappropriate, then error messages are
130    --  posted as required, and a value of No_Uint is returned.
131
132    function Is_Operational_Item (N : Node_Id) return Boolean;
133    --  A specification for a stream attribute is allowed before the full type
134    --  is declared, as explained in AI-00137 and the corrigendum. Attributes
135    --  that do not specify a representation characteristic are operational
136    --  attributes.
137
138    function Is_Predicate_Static
139      (Expr : Node_Id;
140       Nam  : Name_Id) return Boolean;
141    --  Given predicate expression Expr, tests if Expr is predicate-static in
142    --  the sense of the rules in (RM 3.2.4 (15-24)). Occurrences of the type
143    --  name in the predicate expression have been replaced by references to
144    --  an identifier whose Chars field is Nam. This name is unique, so any
145    --  identifier with Chars matching Nam must be a reference to the type.
146    --  Returns True if the expression is predicate-static and False otherwise,
147    --  but is not in the business of setting flags or issuing error messages.
148    --
149    --  Only scalar types can have static predicates, so False is always
150    --  returned for non-scalar types.
151    --
152    --  Note: the RM seems to suggest that string types can also have static
153    --  predicates. But that really makes lttle sense as very few useful
154    --  predicates can be constructed for strings. Remember that:
155    --
156    --     "ABC" < "DEF"
157    --
158    --  is not a static expression. So even though the clearly faulty RM wording
159    --  allows the following:
160    --
161    --     subtype S is String with Static_Predicate => S < "DEF"
162    --
163    --  We can't allow this, otherwise we have predicate-static applying to a
164    --  larger class than static expressions, which was never intended.
165
166    procedure New_Stream_Subprogram
167      (N    : Node_Id;
168       Ent  : Entity_Id;
169       Subp : Entity_Id;
170       Nam  : TSS_Name_Type);
171    --  Create a subprogram renaming of a given stream attribute to the
172    --  designated subprogram and then in the tagged case, provide this as a
173    --  primitive operation, or in the untagged case make an appropriate TSS
174    --  entry. This is more properly an expansion activity than just semantics,
175    --  but the presence of user-defined stream functions for limited types
176    --  is a legality check, which is why this takes place here rather than in
177    --  exp_ch13, where it was previously. Nam indicates the name of the TSS
178    --  function to be generated.
179    --
180    --  To avoid elaboration anomalies with freeze nodes, for untagged types
181    --  we generate both a subprogram declaration and a subprogram renaming
182    --  declaration, so that the attribute specification is handled as a
183    --  renaming_as_body. For tagged types, the specification is one of the
184    --  primitive specs.
185
186    procedure Resolve_Iterable_Operation
187      (N      : Node_Id;
188       Cursor : Entity_Id;
189       Typ    : Entity_Id;
190       Nam    : Name_Id);
191    --  If the name of a primitive operation for an Iterable aspect is
192    --  overloaded, resolve according to required signature.
193
194    procedure Set_Biased
195      (E      : Entity_Id;
196       N      : Node_Id;
197       Msg    : String;
198       Biased : Boolean := True);
199    --  If Biased is True, sets Has_Biased_Representation flag for E, and
200    --  outputs a warning message at node N if Warn_On_Biased_Representation is
201    --  is True. This warning inserts the string Msg to describe the construct
202    --  causing biasing.
203
204    ----------------------------------------------
205    -- Table for Validate_Unchecked_Conversions --
206    ----------------------------------------------
207
208    --  The following table collects unchecked conversions for validation.
209    --  Entries are made by Validate_Unchecked_Conversion and then the call
210    --  to Validate_Unchecked_Conversions does the actual error checking and
211    --  posting of warnings. The reason for this delayed processing is to take
212    --  advantage of back-annotations of size and alignment values performed by
213    --  the back end.
214
215    --  Note: the reason we store a Source_Ptr value instead of a Node_Id is
216    --  that by the time Validate_Unchecked_Conversions is called, Sprint will
217    --  already have modified all Sloc values if the -gnatD option is set.
218
219    type UC_Entry is record
220       Eloc     : Source_Ptr; -- node used for posting warnings
221       Source   : Entity_Id;  -- source type for unchecked conversion
222       Target   : Entity_Id;  -- target type for unchecked conversion
223       Act_Unit : Entity_Id;  -- actual function instantiated
224    end record;
225
226    package Unchecked_Conversions is new Table.Table (
227      Table_Component_Type => UC_Entry,
228      Table_Index_Type     => Int,
229      Table_Low_Bound      => 1,
230      Table_Initial        => 50,
231      Table_Increment      => 200,
232      Table_Name           => "Unchecked_Conversions");
233
234    ----------------------------------------
235    -- Table for Validate_Address_Clauses --
236    ----------------------------------------
237
238    --  If an address clause has the form
239
240    --    for X'Address use Expr
241
242    --  where Expr is of the form Y'Address or recursively is a reference to a
243    --  constant of either of these forms, and X and Y are entities of objects,
244    --  then if Y has a smaller alignment than X, that merits a warning about
245    --  possible bad alignment. The following table collects address clauses of
246    --  this kind. We put these in a table so that they can be checked after the
247    --  back end has completed annotation of the alignments of objects, since we
248    --  can catch more cases that way.
249
250    type Address_Clause_Check_Record is record
251       N : Node_Id;
252       --  The address clause
253
254       X : Entity_Id;
255       --  The entity of the object overlaying Y
256
257       Y : Entity_Id;
258       --  The entity of the object being overlaid
259
260       Off : Boolean;
261       --  Whether the address is offset within Y
262    end record;
263
264    package Address_Clause_Checks is new Table.Table (
265      Table_Component_Type => Address_Clause_Check_Record,
266      Table_Index_Type     => Int,
267      Table_Low_Bound      => 1,
268      Table_Initial        => 20,
269      Table_Increment      => 200,
270      Table_Name           => "Address_Clause_Checks");
271
272    -----------------------------------------
273    -- Adjust_Record_For_Reverse_Bit_Order --
274    -----------------------------------------
275
276    procedure Adjust_Record_For_Reverse_Bit_Order (R : Entity_Id) is
277       Comp : Node_Id;
278       CC   : Node_Id;
279
280    begin
281       --  Processing depends on version of Ada
282
283       --  For Ada 95, we just renumber bits within a storage unit. We do the
284       --  same for Ada 83 mode, since we recognize the Bit_Order attribute in
285       --  Ada 83, and are free to add this extension.
286
287       if Ada_Version < Ada_2005 then
288          Comp := First_Component_Or_Discriminant (R);
289          while Present (Comp) loop
290             CC := Component_Clause (Comp);
291
292             --  If component clause is present, then deal with the non-default
293             --  bit order case for Ada 95 mode.
294
295             --  We only do this processing for the base type, and in fact that
296             --  is important, since otherwise if there are record subtypes, we
297             --  could reverse the bits once for each subtype, which is wrong.
298
299             if Present (CC) and then Ekind (R) = E_Record_Type then
300                declare
301                   CFB : constant Uint    := Component_Bit_Offset (Comp);
302                   CSZ : constant Uint    := Esize (Comp);
303                   CLC : constant Node_Id := Component_Clause (Comp);
304                   Pos : constant Node_Id := Position (CLC);
305                   FB  : constant Node_Id := First_Bit (CLC);
306
307                   Storage_Unit_Offset : constant Uint :=
308                                           CFB / System_Storage_Unit;
309
310                   Start_Bit : constant Uint :=
311                                 CFB mod System_Storage_Unit;
312
313                begin
314                   --  Cases where field goes over storage unit boundary
315
316                   if Start_Bit + CSZ > System_Storage_Unit then
317
318                      --  Allow multi-byte field but generate warning
319
320                      if Start_Bit mod System_Storage_Unit = 0
321                        and then CSZ mod System_Storage_Unit = 0
322                      then
323                         Error_Msg_N
324                           ("info: multi-byte field specified with "
325                            & "non-standard Bit_Order?V?", CLC);
326
327                         if Bytes_Big_Endian then
328                            Error_Msg_N
329                              ("\bytes are not reversed "
330                               & "(component is big-endian)?V?", CLC);
331                         else
332                            Error_Msg_N
333                              ("\bytes are not reversed "
334                               & "(component is little-endian)?V?", CLC);
335                         end if;
336
337                         --  Do not allow non-contiguous field
338
339                      else
340                         Error_Msg_N
341                           ("attempt to specify non-contiguous field "
342                            & "not permitted", CLC);
343                         Error_Msg_N
344                           ("\caused by non-standard Bit_Order "
345                            & "specified", CLC);
346                         Error_Msg_N
347                           ("\consider possibility of using "
348                            & "Ada 2005 mode here", CLC);
349                      end if;
350
351                   --  Case where field fits in one storage unit
352
353                   else
354                      --  Give warning if suspicious component clause
355
356                      if Intval (FB) >= System_Storage_Unit
357                        and then Warn_On_Reverse_Bit_Order
358                      then
359                         Error_Msg_N
360                           ("info: Bit_Order clause does not affect " &
361                            "byte ordering?V?", Pos);
362                         Error_Msg_Uint_1 :=
363                           Intval (Pos) + Intval (FB) /
364                           System_Storage_Unit;
365                         Error_Msg_N
366                           ("info: position normalized to ^ before bit " &
367                            "order interpreted?V?", Pos);
368                      end if;
369
370                      --  Here is where we fix up the Component_Bit_Offset value
371                      --  to account for the reverse bit order. Some examples of
372                      --  what needs to be done are:
373
374                      --    First_Bit .. Last_Bit     Component_Bit_Offset
375                      --      old          new          old       new
376
377                      --     0 .. 0       7 .. 7         0         7
378                      --     0 .. 1       6 .. 7         0         6
379                      --     0 .. 2       5 .. 7         0         5
380                      --     0 .. 7       0 .. 7         0         4
381
382                      --     1 .. 1       6 .. 6         1         6
383                      --     1 .. 4       3 .. 6         1         3
384                      --     4 .. 7       0 .. 3         4         0
385
386                      --  The rule is that the first bit is is obtained by
387                      --  subtracting the old ending bit from storage_unit - 1.
388
389                      Set_Component_Bit_Offset
390                        (Comp,
391                         (Storage_Unit_Offset * System_Storage_Unit) +
392                           (System_Storage_Unit - 1) -
393                           (Start_Bit + CSZ - 1));
394
395                      Set_Normalized_First_Bit
396                        (Comp,
397                         Component_Bit_Offset (Comp) mod
398                           System_Storage_Unit);
399                   end if;
400                end;
401             end if;
402
403             Next_Component_Or_Discriminant (Comp);
404          end loop;
405
406       --  For Ada 2005, we do machine scalar processing, as fully described In
407       --  AI-133. This involves gathering all components which start at the
408       --  same byte offset and processing them together. Same approach is still
409       --  valid in later versions including Ada 2012.
410
411       else
412          declare
413             Max_Machine_Scalar_Size : constant Uint :=
414                                         UI_From_Int
415                                           (Standard_Long_Long_Integer_Size);
416             --  We use this as the maximum machine scalar size
417
418             Num_CC : Natural;
419             SSU    : constant Uint := UI_From_Int (System_Storage_Unit);
420
421          begin
422             --  This first loop through components does two things. First it
423             --  deals with the case of components with component clauses whose
424             --  length is greater than the maximum machine scalar size (either
425             --  accepting them or rejecting as needed). Second, it counts the
426             --  number of components with component clauses whose length does
427             --  not exceed this maximum for later processing.
428
429             Num_CC := 0;
430             Comp   := First_Component_Or_Discriminant (R);
431             while Present (Comp) loop
432                CC := Component_Clause (Comp);
433
434                if Present (CC) then
435                   declare
436                      Fbit : constant Uint := Static_Integer (First_Bit (CC));
437                      Lbit : constant Uint := Static_Integer (Last_Bit (CC));
438
439                   begin
440                      --  Case of component with last bit >= max machine scalar
441
442                      if Lbit >= Max_Machine_Scalar_Size then
443
444                         --  This is allowed only if first bit is zero, and
445                         --  last bit + 1 is a multiple of storage unit size.
446
447                         if Fbit = 0 and then (Lbit + 1) mod SSU = 0 then
448
449                            --  This is the case to give a warning if enabled
450
451                            if Warn_On_Reverse_Bit_Order then
452                               Error_Msg_N
453                                 ("info: multi-byte field specified with "
454                                  & "  non-standard Bit_Order?V?", CC);
455
456                               if Bytes_Big_Endian then
457                                  Error_Msg_N
458                                    ("\bytes are not reversed "
459                                     & "(component is big-endian)?V?", CC);
460                               else
461                                  Error_Msg_N
462                                    ("\bytes are not reversed "
463                                     & "(component is little-endian)?V?", CC);
464                               end if;
465                            end if;
466
467                         --  Give error message for RM 13.5.1(10) violation
468
469                         else
470                            Error_Msg_FE
471                              ("machine scalar rules not followed for&",
472                               First_Bit (CC), Comp);
473
474                            Error_Msg_Uint_1 := Lbit;
475                            Error_Msg_Uint_2 := Max_Machine_Scalar_Size;
476                            Error_Msg_F
477                              ("\last bit (^) exceeds maximum machine "
478                               & "scalar size (^)",
479                               First_Bit (CC));
480
481                            if (Lbit + 1) mod SSU /= 0 then
482                               Error_Msg_Uint_1 := SSU;
483                               Error_Msg_F
484                                 ("\and is not a multiple of Storage_Unit (^) "
485                                  & "(RM 13.4.1(10))",
486                                  First_Bit (CC));
487
488                            else
489                               Error_Msg_Uint_1 := Fbit;
490                               Error_Msg_F
491                                 ("\and first bit (^) is non-zero "
492                                  & "(RM 13.4.1(10))",
493                                  First_Bit (CC));
494                            end if;
495                         end if;
496
497                      --  OK case of machine scalar related component clause,
498                      --  For now, just count them.
499
500                      else
501                         Num_CC := Num_CC + 1;
502                      end if;
503                   end;
504                end if;
505
506                Next_Component_Or_Discriminant (Comp);
507             end loop;
508
509             --  We need to sort the component clauses on the basis of the
510             --  Position values in the clause, so we can group clauses with
511             --  the same Position together to determine the relevant machine
512             --  scalar size.
513
514             Sort_CC : declare
515                Comps : array (0 .. Num_CC) of Entity_Id;
516                --  Array to collect component and discriminant entities. The
517                --  data starts at index 1, the 0'th entry is for the sort
518                --  routine.
519
520                function CP_Lt (Op1, Op2 : Natural) return Boolean;
521                --  Compare routine for Sort
522
523                procedure CP_Move (From : Natural; To : Natural);
524                --  Move routine for Sort
525
526                package Sorting is new GNAT.Heap_Sort_G (CP_Move, CP_Lt);
527
528                Start : Natural;
529                Stop  : Natural;
530                --  Start and stop positions in the component list of the set of
531                --  components with the same starting position (that constitute
532                --  components in a single machine scalar).
533
534                MaxL  : Uint;
535                --  Maximum last bit value of any component in this set
536
537                MSS   : Uint;
538                --  Corresponding machine scalar size
539
540                -----------
541                -- CP_Lt --
542                -----------
543
544                function CP_Lt (Op1, Op2 : Natural) return Boolean is
545                begin
546                   return Position (Component_Clause (Comps (Op1))) <
547                     Position (Component_Clause (Comps (Op2)));
548                end CP_Lt;
549
550                -------------
551                -- CP_Move --
552                -------------
553
554                procedure CP_Move (From : Natural; To : Natural) is
555                begin
556                   Comps (To) := Comps (From);
557                end CP_Move;
558
559             --  Start of processing for Sort_CC
560
561             begin
562                --  Collect the machine scalar relevant component clauses
563
564                Num_CC := 0;
565                Comp   := First_Component_Or_Discriminant (R);
566                while Present (Comp) loop
567                   declare
568                      CC   : constant Node_Id := Component_Clause (Comp);
569
570                   begin
571                      --  Collect only component clauses whose last bit is less
572                      --  than machine scalar size. Any component clause whose
573                      --  last bit exceeds this value does not take part in
574                      --  machine scalar layout considerations. The test for
575                      --  Error_Posted makes sure we exclude component clauses
576                      --  for which we already posted an error.
577
578                      if Present (CC)
579                        and then not Error_Posted (Last_Bit (CC))
580                        and then Static_Integer (Last_Bit (CC)) <
581                                                     Max_Machine_Scalar_Size
582                      then
583                         Num_CC := Num_CC + 1;
584                         Comps (Num_CC) := Comp;
585                      end if;
586                   end;
587
588                   Next_Component_Or_Discriminant (Comp);
589                end loop;
590
591                --  Sort by ascending position number
592
593                Sorting.Sort (Num_CC);
594
595                --  We now have all the components whose size does not exceed
596                --  the max machine scalar value, sorted by starting position.
597                --  In this loop we gather groups of clauses starting at the
598                --  same position, to process them in accordance with AI-133.
599
600                Stop := 0;
601                while Stop < Num_CC loop
602                   Start := Stop + 1;
603                   Stop  := Start;
604                   MaxL  :=
605                     Static_Integer
606                       (Last_Bit (Component_Clause (Comps (Start))));
607                   while Stop < Num_CC loop
608                      if Static_Integer
609                           (Position (Component_Clause (Comps (Stop + 1)))) =
610                         Static_Integer
611                           (Position (Component_Clause (Comps (Stop))))
612                      then
613                         Stop := Stop + 1;
614                         MaxL :=
615                           UI_Max
616                             (MaxL,
617                              Static_Integer
618                                (Last_Bit
619                                   (Component_Clause (Comps (Stop)))));
620                      else
621                         exit;
622                      end if;
623                   end loop;
624
625                   --  Now we have a group of component clauses from Start to
626                   --  Stop whose positions are identical, and MaxL is the
627                   --  maximum last bit value of any of these components.
628
629                   --  We need to determine the corresponding machine scalar
630                   --  size. This loop assumes that machine scalar sizes are
631                   --  even, and that each possible machine scalar has twice
632                   --  as many bits as the next smaller one.
633
634                   MSS := Max_Machine_Scalar_Size;
635                   while MSS mod 2 = 0
636                     and then (MSS / 2) >= SSU
637                     and then (MSS / 2) > MaxL
638                   loop
639                      MSS := MSS / 2;
640                   end loop;
641
642                   --  Here is where we fix up the Component_Bit_Offset value
643                   --  to account for the reverse bit order. Some examples of
644                   --  what needs to be done for the case of a machine scalar
645                   --  size of 8 are:
646
647                   --    First_Bit .. Last_Bit     Component_Bit_Offset
648                   --      old          new          old       new
649
650                   --     0 .. 0       7 .. 7         0         7
651                   --     0 .. 1       6 .. 7         0         6
652                   --     0 .. 2       5 .. 7         0         5
653                   --     0 .. 7       0 .. 7         0         4
654
655                   --     1 .. 1       6 .. 6         1         6
656                   --     1 .. 4       3 .. 6         1         3
657                   --     4 .. 7       0 .. 3         4         0
658
659                   --  The rule is that the first bit is obtained by subtracting
660                   --  the old ending bit from machine scalar size - 1.
661
662                   for C in Start .. Stop loop
663                      declare
664                         Comp : constant Entity_Id := Comps (C);
665                         CC   : constant Node_Id   := Component_Clause (Comp);
666
667                         LB   : constant Uint := Static_Integer (Last_Bit (CC));
668                         NFB  : constant Uint := MSS - Uint_1 - LB;
669                         NLB  : constant Uint := NFB + Esize (Comp) - 1;
670                         Pos  : constant Uint := Static_Integer (Position (CC));
671
672                      begin
673                         if Warn_On_Reverse_Bit_Order then
674                            Error_Msg_Uint_1 := MSS;
675                            Error_Msg_N
676                              ("info: reverse bit order in machine " &
677                               "scalar of length^?V?", First_Bit (CC));
678                            Error_Msg_Uint_1 := NFB;
679                            Error_Msg_Uint_2 := NLB;
680
681                            if Bytes_Big_Endian then
682                               Error_Msg_NE
683                                 ("\big-endian range for component "
684                                  & "& is ^ .. ^?V?", First_Bit (CC), Comp);
685                            else
686                               Error_Msg_NE
687                                 ("\little-endian range for component"
688                                  & "& is ^ .. ^?V?", First_Bit (CC), Comp);
689                            end if;
690                         end if;
691
692                         Set_Component_Bit_Offset (Comp, Pos * SSU + NFB);
693                         Set_Normalized_First_Bit (Comp, NFB mod SSU);
694                      end;
695                   end loop;
696                end loop;
697             end Sort_CC;
698          end;
699       end if;
700    end Adjust_Record_For_Reverse_Bit_Order;
701
702    -------------------------------------
703    -- Alignment_Check_For_Size_Change --
704    -------------------------------------
705
706    procedure Alignment_Check_For_Size_Change (Typ : Entity_Id; Size : Uint) is
707    begin
708       --  If the alignment is known, and not set by a rep clause, and is
709       --  inconsistent with the size being set, then reset it to unknown,
710       --  we assume in this case that the size overrides the inherited
711       --  alignment, and that the alignment must be recomputed.
712
713       if Known_Alignment (Typ)
714         and then not Has_Alignment_Clause (Typ)
715         and then Size mod (Alignment (Typ) * SSU) /= 0
716       then
717          Init_Alignment (Typ);
718       end if;
719    end Alignment_Check_For_Size_Change;
720
721    -------------------------------------
722    -- Analyze_Aspects_At_Freeze_Point --
723    -------------------------------------
724
725    procedure Analyze_Aspects_At_Freeze_Point (E : Entity_Id) is
726       ASN   : Node_Id;
727       A_Id  : Aspect_Id;
728       Ritem : Node_Id;
729
730       procedure Analyze_Aspect_Default_Value (ASN : Node_Id);
731       --  This routine analyzes an Aspect_Default_[Component_]Value denoted by
732       --  the aspect specification node ASN.
733
734       procedure Inherit_Delayed_Rep_Aspects (ASN : Node_Id);
735       --  As discussed in the spec of Aspects (see Aspect_Delay declaration),
736       --  a derived type can inherit aspects from its parent which have been
737       --  specified at the time of the derivation using an aspect, as in:
738       --
739       --    type A is range 1 .. 10
740       --      with Size => Not_Defined_Yet;
741       --    ..
742       --    type B is new A;
743       --    ..
744       --    Not_Defined_Yet : constant := 64;
745       --
746       --  In this example, the Size of A is considered to be specified prior
747       --  to the derivation, and thus inherited, even though the value is not
748       --  known at the time of derivation. To deal with this, we use two entity
749       --  flags. The flag Has_Derived_Rep_Aspects is set in the parent type (A
750       --  here), and then the flag May_Inherit_Delayed_Rep_Aspects is set in
751       --  the derived type (B here). If this flag is set when the derived type
752       --  is frozen, then this procedure is called to ensure proper inheritance
753       --  of all delayed aspects from the parent type. The derived type is E,
754       --  the argument to Analyze_Aspects_At_Freeze_Point. ASN is the first
755       --  aspect specification node in the Rep_Item chain for the parent type.
756
757       procedure Make_Pragma_From_Boolean_Aspect (ASN : Node_Id);
758       --  Given an aspect specification node ASN whose expression is an
759       --  optional Boolean, this routines creates the corresponding pragma
760       --  at the freezing point.
761
762       ----------------------------------
763       -- Analyze_Aspect_Default_Value --
764       ----------------------------------
765
766       procedure Analyze_Aspect_Default_Value (ASN : Node_Id) is
767          Ent  : constant Entity_Id := Entity (ASN);
768          Expr : constant Node_Id   := Expression (ASN);
769          Id   : constant Node_Id   := Identifier (ASN);
770
771       begin
772          Error_Msg_Name_1 := Chars (Id);
773
774          if not Is_Type (Ent) then
775             Error_Msg_N ("aspect% can only apply to a type", Id);
776             return;
777
778          elsif not Is_First_Subtype (Ent) then
779             Error_Msg_N ("aspect% cannot apply to subtype", Id);
780             return;
781
782          elsif A_Id = Aspect_Default_Value
783            and then not Is_Scalar_Type (Ent)
784          then
785             Error_Msg_N ("aspect% can only be applied to scalar type", Id);
786             return;
787
788          elsif A_Id = Aspect_Default_Component_Value then
789             if not Is_Array_Type (Ent) then
790                Error_Msg_N ("aspect% can only be applied to array type", Id);
791                return;
792
793             elsif not Is_Scalar_Type (Component_Type (Ent)) then
794                Error_Msg_N ("aspect% requires scalar components", Id);
795                return;
796             end if;
797          end if;
798
799          Set_Has_Default_Aspect (Base_Type (Ent));
800
801          if Is_Scalar_Type (Ent) then
802             Set_Default_Aspect_Value (Base_Type (Ent), Expr);
803          else
804             Set_Default_Aspect_Component_Value (Base_Type (Ent), Expr);
805          end if;
806       end Analyze_Aspect_Default_Value;
807
808       ---------------------------------
809       -- Inherit_Delayed_Rep_Aspects --
810       ---------------------------------
811
812       procedure Inherit_Delayed_Rep_Aspects (ASN : Node_Id) is
813          P : constant Entity_Id := Entity (ASN);
814          --  Entithy for parent type
815
816          N : Node_Id;
817          --  Item from Rep_Item chain
818
819          A : Aspect_Id;
820
821       begin
822          --  Loop through delayed aspects for the parent type
823
824          N := ASN;
825          while Present (N) loop
826             if Nkind (N) = N_Aspect_Specification then
827                exit when Entity (N) /= P;
828
829                if Is_Delayed_Aspect (N) then
830                   A := Get_Aspect_Id (Chars (Identifier (N)));
831
832                   --  Process delayed rep aspect. For Boolean attributes it is
833                   --  not possible to cancel an attribute once set (the attempt
834                   --  to use an aspect with xxx => False is an error) for a
835                   --  derived type. So for those cases, we do not have to check
836                   --  if a clause has been given for the derived type, since it
837                   --  is harmless to set it again if it is already set.
838
839                   case A is
840
841                      --  Alignment
842
843                      when Aspect_Alignment =>
844                         if not Has_Alignment_Clause (E) then
845                            Set_Alignment (E, Alignment (P));
846                         end if;
847
848                      --  Atomic
849
850                      when Aspect_Atomic =>
851                         if Is_Atomic (P) then
852                            Set_Is_Atomic (E);
853                         end if;
854
855                      --  Atomic_Components
856
857                      when Aspect_Atomic_Components =>
858                         if Has_Atomic_Components (P) then
859                            Set_Has_Atomic_Components (Base_Type (E));
860                         end if;
861
862                      --  Bit_Order
863
864                      when Aspect_Bit_Order =>
865                         if Is_Record_Type (E)
866                           and then No (Get_Attribute_Definition_Clause
867                                          (E, Attribute_Bit_Order))
868                           and then Reverse_Bit_Order (P)
869                         then
870                            Set_Reverse_Bit_Order (Base_Type (E));
871                         end if;
872
873                      --  Component_Size
874
875                      when Aspect_Component_Size =>
876                         if Is_Array_Type (E)
877                           and then not Has_Component_Size_Clause (E)
878                         then
879                            Set_Component_Size
880                              (Base_Type (E), Component_Size (P));
881                         end if;
882
883                      --  Machine_Radix
884
885                      when Aspect_Machine_Radix =>
886                         if Is_Decimal_Fixed_Point_Type (E)
887                           and then not Has_Machine_Radix_Clause (E)
888                         then
889                            Set_Machine_Radix_10 (E, Machine_Radix_10 (P));
890                         end if;
891
892                      --  Object_Size (also Size which also sets Object_Size)
893
894                      when Aspect_Object_Size | Aspect_Size =>
895                         if not Has_Size_Clause (E)
896                           and then
897                             No (Get_Attribute_Definition_Clause
898                                   (E, Attribute_Object_Size))
899                         then
900                            Set_Esize (E, Esize (P));
901                         end if;
902
903                      --  Pack
904
905                      when Aspect_Pack =>
906                         if not Is_Packed (E) then
907                            Set_Is_Packed (Base_Type (E));
908
909                            if Is_Bit_Packed_Array (P) then
910                               Set_Is_Bit_Packed_Array (Base_Type (E));
911                               Set_Packed_Array_Impl_Type
912                                 (E, Packed_Array_Impl_Type (P));
913                            end if;
914                         end if;
915
916                      --  Scalar_Storage_Order
917
918                      when Aspect_Scalar_Storage_Order =>
919                         if (Is_Record_Type (E) or else Is_Array_Type (E))
920                           and then No (Get_Attribute_Definition_Clause
921                                          (E, Attribute_Scalar_Storage_Order))
922                           and then Reverse_Storage_Order (P)
923                         then
924                            Set_Reverse_Storage_Order (Base_Type (E));
925
926                            --  Clear default SSO indications, since the aspect
927                            --  overrides the default.
928
929                            Set_SSO_Set_Low_By_Default  (Base_Type (E), False);
930                            Set_SSO_Set_High_By_Default (Base_Type (E), False);
931                         end if;
932
933                      --  Small
934
935                      when Aspect_Small =>
936                         if Is_Fixed_Point_Type (E)
937                           and then not Has_Small_Clause (E)
938                         then
939                            Set_Small_Value (E, Small_Value (P));
940                         end if;
941
942                      --  Storage_Size
943
944                      when Aspect_Storage_Size =>
945                         if (Is_Access_Type (E) or else Is_Task_Type (E))
946                           and then not Has_Storage_Size_Clause (E)
947                         then
948                            Set_Storage_Size_Variable
949                              (Base_Type (E), Storage_Size_Variable (P));
950                         end if;
951
952                      --  Value_Size
953
954                      when Aspect_Value_Size =>
955
956                         --  Value_Size is never inherited, it is either set by
957                         --  default, or it is explicitly set for the derived
958                         --  type. So nothing to do here.
959
960                         null;
961
962                      --  Volatile
963
964                      when Aspect_Volatile =>
965                         if Is_Volatile (P) then
966                            Set_Is_Volatile (E);
967                         end if;
968
969                      --  Volatile_Full_Access
970
971                      when Aspect_Volatile_Full_Access =>
972                         if Is_Volatile_Full_Access (P) then
973                            Set_Is_Volatile_Full_Access (E);
974                         end if;
975
976                      --  Volatile_Components
977
978                      when Aspect_Volatile_Components =>
979                         if Has_Volatile_Components (P) then
980                            Set_Has_Volatile_Components (Base_Type (E));
981                         end if;
982
983                      --  That should be all the Rep Aspects
984
985                      when others =>
986                         pragma Assert (Aspect_Delay (A_Id) /= Rep_Aspect);
987                         null;
988
989                   end case;
990                end if;
991             end if;
992
993             N := Next_Rep_Item (N);
994          end loop;
995       end Inherit_Delayed_Rep_Aspects;
996
997       -------------------------------------
998       -- Make_Pragma_From_Boolean_Aspect --
999       -------------------------------------
1000
1001       procedure Make_Pragma_From_Boolean_Aspect (ASN : Node_Id) is
1002          Ident  : constant Node_Id    := Identifier (ASN);
1003          A_Name : constant Name_Id    := Chars (Ident);
1004          A_Id   : constant Aspect_Id  := Get_Aspect_Id (A_Name);
1005          Ent    : constant Entity_Id  := Entity (ASN);
1006          Expr   : constant Node_Id    := Expression (ASN);
1007          Loc    : constant Source_Ptr := Sloc (ASN);
1008
1009          Prag : Node_Id;
1010
1011          procedure Check_False_Aspect_For_Derived_Type;
1012          --  This procedure checks for the case of a false aspect for a derived
1013          --  type, which improperly tries to cancel an aspect inherited from
1014          --  the parent.
1015
1016          -----------------------------------------
1017          -- Check_False_Aspect_For_Derived_Type --
1018          -----------------------------------------
1019
1020          procedure Check_False_Aspect_For_Derived_Type is
1021             Par : Node_Id;
1022
1023          begin
1024             --  We are only checking derived types
1025
1026             if not Is_Derived_Type (E) then
1027                return;
1028             end if;
1029
1030             Par := Nearest_Ancestor (E);
1031
1032             case A_Id is
1033                when Aspect_Atomic | Aspect_Shared =>
1034                   if not Is_Atomic (Par) then
1035                      return;
1036                   end if;
1037
1038                when Aspect_Atomic_Components =>
1039                   if not Has_Atomic_Components (Par) then
1040                      return;
1041                   end if;
1042
1043                when Aspect_Discard_Names =>
1044                   if not Discard_Names (Par) then
1045                      return;
1046                   end if;
1047
1048                when Aspect_Pack =>
1049                   if not Is_Packed (Par) then
1050                      return;
1051                   end if;
1052
1053                when Aspect_Unchecked_Union =>
1054                   if not Is_Unchecked_Union (Par) then
1055                      return;
1056                   end if;
1057
1058                when Aspect_Volatile =>
1059                   if not Is_Volatile (Par) then
1060                      return;
1061                   end if;
1062
1063                when Aspect_Volatile_Components =>
1064                   if not Has_Volatile_Components (Par) then
1065                      return;
1066                   end if;
1067
1068                when Aspect_Volatile_Full_Access =>
1069                   if not Is_Volatile_Full_Access (Par) then
1070                      return;
1071                   end if;
1072
1073                when others =>
1074                   return;
1075             end case;
1076
1077             --  Fall through means we are canceling an inherited aspect
1078
1079             Error_Msg_Name_1 := A_Name;
1080             Error_Msg_NE
1081               ("derived type& inherits aspect%, cannot cancel", Expr, E);
1082          end Check_False_Aspect_For_Derived_Type;
1083
1084       --  Start of processing for Make_Pragma_From_Boolean_Aspect
1085
1086       begin
1087          --  Note that we know Expr is present, because for a missing Expr
1088          --  argument, we knew it was True and did not need to delay the
1089          --  evaluation to the freeze point.
1090
1091          if Is_False (Static_Boolean (Expr)) then
1092             Check_False_Aspect_For_Derived_Type;
1093
1094          else
1095             Prag :=
1096               Make_Pragma (Loc,
1097                 Pragma_Argument_Associations => New_List (
1098                   Make_Pragma_Argument_Association (Sloc (Ident),
1099                     Expression => New_Occurrence_Of (Ent, Sloc (Ident)))),
1100
1101                 Pragma_Identifier            =>
1102                   Make_Identifier (Sloc (Ident), Chars (Ident)));
1103
1104             Set_From_Aspect_Specification (Prag, True);
1105             Set_Corresponding_Aspect (Prag, ASN);
1106             Set_Aspect_Rep_Item (ASN, Prag);
1107             Set_Is_Delayed_Aspect (Prag);
1108             Set_Parent (Prag, ASN);
1109          end if;
1110       end Make_Pragma_From_Boolean_Aspect;
1111
1112    --  Start of processing for Analyze_Aspects_At_Freeze_Point
1113
1114    begin
1115       --  Must be visible in current scope
1116
1117       if not Scope_Within_Or_Same (Current_Scope, Scope (E)) then
1118          return;
1119       end if;
1120
1121       --  Look for aspect specification entries for this entity
1122
1123       ASN := First_Rep_Item (E);
1124       while Present (ASN) loop
1125          if Nkind (ASN) = N_Aspect_Specification then
1126             exit when Entity (ASN) /= E;
1127
1128             if Is_Delayed_Aspect (ASN) then
1129                A_Id := Get_Aspect_Id (ASN);
1130
1131                case A_Id is
1132
1133                   --  For aspects whose expression is an optional Boolean, make
1134                   --  the corresponding pragma at the freeze point.
1135
1136                   when Boolean_Aspects      |
1137                        Library_Unit_Aspects =>
1138                      Make_Pragma_From_Boolean_Aspect (ASN);
1139
1140                   --  Special handling for aspects that don't correspond to
1141                   --  pragmas/attributes.
1142
1143                   when Aspect_Default_Value           |
1144                        Aspect_Default_Component_Value =>
1145
1146                      --  Do not inherit aspect for anonymous base type of a
1147                      --  scalar or array type, because they apply to the first
1148                      --  subtype of the type, and will be processed when that
1149                      --  first subtype is frozen.
1150
1151                      if Is_Derived_Type (E)
1152                        and then not Comes_From_Source (E)
1153                        and then E /= First_Subtype (E)
1154                      then
1155                         null;
1156                      else
1157                         Analyze_Aspect_Default_Value (ASN);
1158                      end if;
1159
1160                   --  Ditto for iterator aspects, because the corresponding
1161                   --  attributes may not have been analyzed yet.
1162
1163                   when Aspect_Constant_Indexing |
1164                        Aspect_Variable_Indexing |
1165                        Aspect_Default_Iterator  |
1166                        Aspect_Iterator_Element  =>
1167                      Analyze (Expression (ASN));
1168
1169                      if Etype (Expression (ASN)) = Any_Type then
1170                         Error_Msg_NE
1171                           ("\aspect must be fully defined before & is frozen",
1172                            ASN, E);
1173                      end if;
1174
1175                   when Aspect_Iterable =>
1176                      Validate_Iterable_Aspect (E, ASN);
1177
1178                   when others =>
1179                      null;
1180                end case;
1181
1182                Ritem := Aspect_Rep_Item (ASN);
1183
1184                if Present (Ritem) then
1185                   Analyze (Ritem);
1186                end if;
1187             end if;
1188          end if;
1189
1190          Next_Rep_Item (ASN);
1191       end loop;
1192
1193       --  This is where we inherit delayed rep aspects from our parent. Note
1194       --  that if we fell out of the above loop with ASN non-empty, it means
1195       --  we hit an aspect for an entity other than E, and it must be the
1196       --  type from which we were derived.
1197
1198       if May_Inherit_Delayed_Rep_Aspects (E) then
1199          Inherit_Delayed_Rep_Aspects (ASN);
1200       end if;
1201    end Analyze_Aspects_At_Freeze_Point;
1202
1203    -----------------------------------
1204    -- Analyze_Aspect_Specifications --
1205    -----------------------------------
1206
1207    procedure Analyze_Aspect_Specifications (N : Node_Id; E : Entity_Id) is
1208       procedure Decorate (Asp : Node_Id; Prag : Node_Id);
1209       --  Establish linkages between an aspect and its corresponding pragma
1210
1211       procedure Insert_After_SPARK_Mode
1212         (Prag    : Node_Id;
1213          Ins_Nod : Node_Id;
1214          Decls   : List_Id);
1215       --  Subsidiary to the analysis of aspects Abstract_State, Ghost,
1216       --  Initializes, Initial_Condition and Refined_State. Insert node Prag
1217       --  before node Ins_Nod. If Ins_Nod is for pragma SPARK_Mode, then skip
1218       --  SPARK_Mode. Decls is the associated declarative list where Prag is to
1219       --  reside.
1220
1221       procedure Insert_Pragma (Prag : Node_Id);
1222       --  Subsidiary to the analysis of aspects Attach_Handler, Contract_Cases,
1223       --  Depends, Global, Post, Pre, Refined_Depends and Refined_Global.
1224       --  Insert pragma Prag such that it mimics the placement of a source
1225       --  pragma of the same kind.
1226       --
1227       --    procedure Proc (Formal : ...) with Global => ...;
1228       --
1229       --    procedure Proc (Formal : ...);
1230       --    pragma Global (...);
1231
1232       --------------
1233       -- Decorate --
1234       --------------
1235
1236       procedure Decorate (Asp : Node_Id; Prag : Node_Id) is
1237       begin
1238          Set_Aspect_Rep_Item           (Asp, Prag);
1239          Set_Corresponding_Aspect      (Prag, Asp);
1240          Set_From_Aspect_Specification (Prag);
1241          Set_Parent                    (Prag, Asp);
1242       end Decorate;
1243
1244       -----------------------------
1245       -- Insert_After_SPARK_Mode --
1246       -----------------------------
1247
1248       procedure Insert_After_SPARK_Mode
1249         (Prag    : Node_Id;
1250          Ins_Nod : Node_Id;
1251          Decls   : List_Id)
1252       is
1253          Decl : Node_Id := Ins_Nod;
1254
1255       begin
1256          --  Skip SPARK_Mode
1257
1258          if Present (Decl)
1259            and then Nkind (Decl) = N_Pragma
1260            and then Pragma_Name (Decl) = Name_SPARK_Mode
1261          then
1262             Decl := Next (Decl);
1263          end if;
1264
1265          if Present (Decl) then
1266             Insert_Before (Decl, Prag);
1267
1268          --  Aitem acts as the last declaration
1269
1270          else
1271             Append_To (Decls, Prag);
1272          end if;
1273       end Insert_After_SPARK_Mode;
1274
1275       -------------------
1276       -- Insert_Pragma --
1277       -------------------
1278
1279       procedure Insert_Pragma (Prag : Node_Id) is
1280          Aux  : Node_Id;
1281          Decl : Node_Id;
1282
1283       begin
1284          if Nkind (N) = N_Subprogram_Body then
1285             if Present (Declarations (N)) then
1286
1287                --  Skip other internally generated pragmas from aspects to find
1288                --  the proper insertion point. As a result the order of pragmas
1289                --  is the same as the order of aspects.
1290
1291                --  As precondition pragmas generated from conjuncts in the
1292                --  precondition aspect are presented in reverse order to
1293                --  Insert_Pragma, insert them in the correct order here by not
1294                --  skipping previously inserted precondition pragmas when the
1295                --  current pragma is a precondition.
1296
1297                Decl := First (Declarations (N));
1298                while Present (Decl) loop
1299                   if Nkind (Decl) = N_Pragma
1300                     and then From_Aspect_Specification (Decl)
1301                     and then not (Get_Pragma_Id (Decl) = Pragma_Precondition
1302                                     and then
1303                                   Get_Pragma_Id (Prag) = Pragma_Precondition)
1304                   then
1305                      Next (Decl);
1306                   else
1307                      exit;
1308                   end if;
1309                end loop;
1310
1311                if Present (Decl) then
1312                   Insert_Before (Decl, Prag);
1313                else
1314                   Append (Prag, Declarations (N));
1315                end if;
1316             else
1317                Set_Declarations (N, New_List (Prag));
1318             end if;
1319
1320          --  When the context is a library unit, the pragma is added to the
1321          --  Pragmas_After list.
1322
1323          elsif Nkind (Parent (N)) = N_Compilation_Unit then
1324             Aux := Aux_Decls_Node (Parent (N));
1325
1326             if No (Pragmas_After (Aux)) then
1327                Set_Pragmas_After (Aux, New_List);
1328             end if;
1329
1330             Prepend (Prag, Pragmas_After (Aux));
1331
1332          --  Default
1333
1334          else
1335             Insert_After (N, Prag);
1336          end if;
1337       end Insert_Pragma;
1338
1339       --  Local variables
1340
1341       Aspect : Node_Id;
1342       Aitem  : Node_Id;
1343       Ent    : Node_Id;
1344
1345       L : constant List_Id := Aspect_Specifications (N);
1346
1347       Ins_Node : Node_Id := N;
1348       --  Insert pragmas/attribute definition clause after this node when no
1349       --  delayed analysis is required.
1350
1351       --  Start of processing for Analyze_Aspect_Specifications
1352
1353       --  The general processing involves building an attribute definition
1354       --  clause or a pragma node that corresponds to the aspect. Then in order
1355       --  to delay the evaluation of this aspect to the freeze point, we attach
1356       --  the corresponding pragma/attribute definition clause to the aspect
1357       --  specification node, which is then placed in the Rep Item chain. In
1358       --  this case we mark the entity by setting the flag Has_Delayed_Aspects
1359       --  and we evaluate the rep item at the freeze point. When the aspect
1360       --  doesn't have a corresponding pragma/attribute definition clause, then
1361       --  its analysis is simply delayed at the freeze point.
1362
1363       --  Some special cases don't require delay analysis, thus the aspect is
1364       --  analyzed right now.
1365
1366       --  Note that there is a special handling for Pre, Post, Test_Case,
1367       --  Contract_Cases aspects. In these cases, we do not have to worry
1368       --  about delay issues, since the pragmas themselves deal with delay
1369       --  of visibility for the expression analysis. Thus, we just insert
1370       --  the pragma after the node N.
1371
1372    begin
1373       pragma Assert (Present (L));
1374
1375       --  Loop through aspects
1376
1377       Aspect := First (L);
1378       Aspect_Loop : while Present (Aspect) loop
1379          Analyze_One_Aspect : declare
1380             Expr : constant Node_Id    := Expression (Aspect);
1381             Id   : constant Node_Id    := Identifier (Aspect);
1382             Loc  : constant Source_Ptr := Sloc (Aspect);
1383             Nam  : constant Name_Id    := Chars (Id);
1384             A_Id : constant Aspect_Id  := Get_Aspect_Id (Nam);
1385             Anod : Node_Id;
1386
1387             Delay_Required : Boolean;
1388             --  Set False if delay is not required
1389
1390             Eloc : Source_Ptr := No_Location;
1391             --  Source location of expression, modified when we split PPC's. It
1392             --  is set below when Expr is present.
1393
1394             procedure Analyze_Aspect_External_Or_Link_Name;
1395             --  Perform analysis of the External_Name or Link_Name aspects
1396
1397             procedure Analyze_Aspect_Implicit_Dereference;
1398             --  Perform analysis of the Implicit_Dereference aspects
1399
1400             procedure Make_Aitem_Pragma
1401               (Pragma_Argument_Associations : List_Id;
1402                Pragma_Name                  : Name_Id);
1403             --  This is a wrapper for Make_Pragma used for converting aspects
1404             --  to pragmas. It takes care of Sloc (set from Loc) and building
1405             --  the pragma identifier from the given name. In addition the
1406             --  flags Class_Present and Split_PPC are set from the aspect
1407             --  node, as well as Is_Ignored. This routine also sets the
1408             --  From_Aspect_Specification in the resulting pragma node to
1409             --  True, and sets Corresponding_Aspect to point to the aspect.
1410             --  The resulting pragma is assigned to Aitem.
1411
1412             ------------------------------------------
1413             -- Analyze_Aspect_External_Or_Link_Name --
1414             ------------------------------------------
1415
1416             procedure Analyze_Aspect_External_Or_Link_Name is
1417             begin
1418                --  Verify that there is an Import/Export aspect defined for the
1419                --  entity. The processing of that aspect in turn checks that
1420                --  there is a Convention aspect declared. The pragma is
1421                --  constructed when processing the Convention aspect.
1422
1423                declare
1424                   A : Node_Id;
1425
1426                begin
1427                   A := First (L);
1428                   while Present (A) loop
1429                      exit when Nam_In (Chars (Identifier (A)), Name_Export,
1430                                                                Name_Import);
1431                      Next (A);
1432                   end loop;
1433
1434                   if No (A) then
1435                      Error_Msg_N
1436                        ("missing Import/Export for Link/External name",
1437                         Aspect);
1438                   end if;
1439                end;
1440             end Analyze_Aspect_External_Or_Link_Name;
1441
1442             -----------------------------------------
1443             -- Analyze_Aspect_Implicit_Dereference --
1444             -----------------------------------------
1445
1446             procedure Analyze_Aspect_Implicit_Dereference is
1447             begin
1448                if not Is_Type (E) or else not Has_Discriminants (E) then
1449                   Error_Msg_N
1450                     ("aspect must apply to a type with discriminants", N);
1451
1452                else
1453                   declare
1454                      Disc : Entity_Id;
1455
1456                   begin
1457                      Disc := First_Discriminant (E);
1458                      while Present (Disc) loop
1459                         if Chars (Expr) = Chars (Disc)
1460                           and then Ekind (Etype (Disc)) =
1461                                      E_Anonymous_Access_Type
1462                         then
1463                            Set_Has_Implicit_Dereference (E);
1464                            Set_Has_Implicit_Dereference (Disc);
1465                            return;
1466                         end if;
1467
1468                         Next_Discriminant (Disc);
1469                      end loop;
1470
1471                      --  Error if no proper access discriminant.
1472
1473                      Error_Msg_NE
1474                       ("not an access discriminant of&", Expr, E);
1475                   end;
1476                end if;
1477             end Analyze_Aspect_Implicit_Dereference;
1478
1479             -----------------------
1480             -- Make_Aitem_Pragma --
1481             -----------------------
1482
1483             procedure Make_Aitem_Pragma
1484               (Pragma_Argument_Associations : List_Id;
1485                Pragma_Name                  : Name_Id)
1486             is
1487                Args : List_Id := Pragma_Argument_Associations;
1488
1489             begin
1490                --  We should never get here if aspect was disabled
1491
1492                pragma Assert (not Is_Disabled (Aspect));
1493
1494                --  Certain aspects allow for an optional name or expression. Do
1495                --  not generate a pragma with empty argument association list.
1496
1497                if No (Args) or else No (Expression (First (Args))) then
1498                   Args := No_List;
1499                end if;
1500
1501                --  Build the pragma
1502
1503                Aitem :=
1504                  Make_Pragma (Loc,
1505                    Pragma_Argument_Associations => Args,
1506                    Pragma_Identifier =>
1507                      Make_Identifier (Sloc (Id), Pragma_Name),
1508                    Class_Present     => Class_Present (Aspect),
1509                    Split_PPC         => Split_PPC (Aspect));
1510
1511                --  Set additional semantic fields
1512
1513                if Is_Ignored (Aspect) then
1514                   Set_Is_Ignored (Aitem);
1515                elsif Is_Checked (Aspect) then
1516                   Set_Is_Checked (Aitem);
1517                end if;
1518
1519                Set_Corresponding_Aspect (Aitem, Aspect);
1520                Set_From_Aspect_Specification (Aitem, True);
1521             end Make_Aitem_Pragma;
1522
1523          --  Start of processing for Analyze_One_Aspect
1524
1525          begin
1526             --  Skip aspect if already analyzed, to avoid looping in some cases
1527
1528             if Analyzed (Aspect) then
1529                goto Continue;
1530             end if;
1531
1532             --  Skip looking at aspect if it is totally disabled. Just mark it
1533             --  as such for later reference in the tree. This also sets the
1534             --  Is_Ignored and Is_Checked flags appropriately.
1535
1536             Check_Applicable_Policy (Aspect);
1537
1538             if Is_Disabled (Aspect) then
1539                goto Continue;
1540             end if;
1541
1542             --  Set the source location of expression, used in the case of
1543             --  a failed precondition/postcondition or invariant. Note that
1544             --  the source location of the expression is not usually the best
1545             --  choice here. For example, it gets located on the last AND
1546             --  keyword in a chain of boolean expressiond AND'ed together.
1547             --  It is best to put the message on the first character of the
1548             --  assertion, which is the effect of the First_Node call here.
1549
1550             if Present (Expr) then
1551                Eloc := Sloc (First_Node (Expr));
1552             end if;
1553
1554             --  Check restriction No_Implementation_Aspect_Specifications
1555
1556             if Implementation_Defined_Aspect (A_Id) then
1557                Check_Restriction
1558                  (No_Implementation_Aspect_Specifications, Aspect);
1559             end if;
1560
1561             --  Check restriction No_Specification_Of_Aspect
1562
1563             Check_Restriction_No_Specification_Of_Aspect (Aspect);
1564
1565             --  Mark aspect analyzed (actual analysis is delayed till later)
1566
1567             Set_Analyzed (Aspect);
1568             Set_Entity (Aspect, E);
1569             Ent := New_Occurrence_Of (E, Sloc (Id));
1570
1571             --  Check for duplicate aspect. Note that the Comes_From_Source
1572             --  test allows duplicate Pre/Post's that we generate internally
1573             --  to escape being flagged here.
1574
1575             if No_Duplicates_Allowed (A_Id) then
1576                Anod := First (L);
1577                while Anod /= Aspect loop
1578                   if Comes_From_Source (Aspect)
1579                     and then Same_Aspect (A_Id, Get_Aspect_Id (Anod))
1580                   then
1581                      Error_Msg_Name_1 := Nam;
1582                      Error_Msg_Sloc := Sloc (Anod);
1583
1584                      --  Case of same aspect specified twice
1585
1586                      if Class_Present (Anod) = Class_Present (Aspect) then
1587                         if not Class_Present (Anod) then
1588                            Error_Msg_NE
1589                              ("aspect% for & previously given#",
1590                               Id, E);
1591                         else
1592                            Error_Msg_NE
1593                              ("aspect `%''Class` for & previously given#",
1594                               Id, E);
1595                         end if;
1596                      end if;
1597                   end if;
1598
1599                   Next (Anod);
1600                end loop;
1601             end if;
1602
1603             --  Check some general restrictions on language defined aspects
1604
1605             if not Implementation_Defined_Aspect (A_Id) then
1606                Error_Msg_Name_1 := Nam;
1607
1608                --  Not allowed for renaming declarations
1609
1610                if Nkind (N) in N_Renaming_Declaration then
1611                   Error_Msg_N
1612                     ("aspect % not allowed for renaming declaration",
1613                      Aspect);
1614                end if;
1615
1616                --  Not allowed for formal type declarations
1617
1618                if Nkind (N) = N_Formal_Type_Declaration then
1619                   Error_Msg_N
1620                     ("aspect % not allowed for formal type declaration",
1621                      Aspect);
1622                end if;
1623             end if;
1624
1625             --  Copy expression for later processing by the procedures
1626             --  Check_Aspect_At_[Freeze_Point | End_Of_Declarations]
1627
1628             Set_Entity (Id, New_Copy_Tree (Expr));
1629
1630             --  Set Delay_Required as appropriate to aspect
1631
1632             case Aspect_Delay (A_Id) is
1633                when Always_Delay =>
1634                   Delay_Required := True;
1635
1636                when Never_Delay =>
1637                   Delay_Required := False;
1638
1639                when Rep_Aspect =>
1640
1641                   --  If expression has the form of an integer literal, then
1642                   --  do not delay, since we know the value cannot change.
1643                   --  This optimization catches most rep clause cases.
1644
1645                   --  For Boolean aspects, don't delay if no expression
1646
1647                   if A_Id in Boolean_Aspects and then No (Expr) then
1648                      Delay_Required := False;
1649
1650                   --  For non-Boolean aspects, don't delay if integer literal
1651
1652                   elsif A_Id not in Boolean_Aspects
1653                     and then Present (Expr)
1654                     and then Nkind (Expr) = N_Integer_Literal
1655                   then
1656                      Delay_Required := False;
1657
1658                   --  All other cases are delayed
1659
1660                   else
1661                      Delay_Required := True;
1662                      Set_Has_Delayed_Rep_Aspects (E);
1663                   end if;
1664             end case;
1665
1666             --  Processing based on specific aspect
1667
1668             case A_Id is
1669                when Aspect_Unimplemented =>
1670                   null; -- ??? temp for now
1671
1672                --  No_Aspect should be impossible
1673
1674                when No_Aspect =>
1675                   raise Program_Error;
1676
1677                --  Case 1: Aspects corresponding to attribute definition
1678                --  clauses.
1679
1680                when Aspect_Address              |
1681                     Aspect_Alignment            |
1682                     Aspect_Bit_Order            |
1683                     Aspect_Component_Size       |
1684                     Aspect_Constant_Indexing    |
1685                     Aspect_Default_Iterator     |
1686                     Aspect_Dispatching_Domain   |
1687                     Aspect_External_Tag         |
1688                     Aspect_Input                |
1689                     Aspect_Iterable             |
1690                     Aspect_Iterator_Element     |
1691                     Aspect_Machine_Radix        |
1692                     Aspect_Object_Size          |
1693                     Aspect_Output               |
1694                     Aspect_Read                 |
1695                     Aspect_Scalar_Storage_Order |
1696                     Aspect_Size                 |
1697                     Aspect_Small                |
1698                     Aspect_Simple_Storage_Pool  |
1699                     Aspect_Storage_Pool         |
1700                     Aspect_Stream_Size          |
1701                     Aspect_Value_Size           |
1702                     Aspect_Variable_Indexing    |
1703                     Aspect_Write                =>
1704
1705                   --  Indexing aspects apply only to tagged type
1706
1707                   if (A_Id = Aspect_Constant_Indexing
1708                         or else
1709                       A_Id = Aspect_Variable_Indexing)
1710                     and then not (Is_Type (E)
1711                                    and then Is_Tagged_Type (E))
1712                   then
1713                      Error_Msg_N
1714                        ("indexing aspect can only apply to a tagged type",
1715                         Aspect);
1716                      goto Continue;
1717                   end if;
1718
1719                   --  For the case of aspect Address, we don't consider that we
1720                   --  know the entity is never set in the source, since it is
1721                   --  is likely aliasing is occurring.
1722
1723                   --  Note: one might think that the analysis of the resulting
1724                   --  attribute definition clause would take care of that, but
1725                   --  that's not the case since it won't be from source.
1726
1727                   if A_Id = Aspect_Address then
1728                      Set_Never_Set_In_Source (E, False);
1729                   end if;
1730
1731                   --  Correctness of the profile of a stream operation is
1732                   --  verified at the freeze point, but we must detect the
1733                   --  illegal specification of this aspect for a subtype now,
1734                   --  to prevent malformed rep_item chains.
1735
1736                   if A_Id = Aspect_Input  or else
1737                      A_Id = Aspect_Output or else
1738                      A_Id = Aspect_Read   or else
1739                      A_Id = Aspect_Write
1740                   then
1741                      if not Is_First_Subtype (E) then
1742                         Error_Msg_N
1743                           ("local name must be a first subtype", Aspect);
1744                         goto Continue;
1745
1746                      --  If stream aspect applies to the class-wide type,
1747                      --  the generated attribute definition applies to the
1748                      --  class-wide type as well.
1749
1750                      elsif Class_Present (Aspect) then
1751                         Ent :=
1752                           Make_Attribute_Reference (Loc,
1753                             Prefix         => Ent,
1754                             Attribute_Name => Name_Class);
1755                      end if;
1756                   end if;
1757
1758                   --  Construct the attribute definition clause
1759
1760                   Aitem :=
1761                     Make_Attribute_Definition_Clause (Loc,
1762                       Name       => Ent,
1763                       Chars      => Chars (Id),
1764                       Expression => Relocate_Node (Expr));
1765
1766                   --  If the address is specified, then we treat the entity as
1767                   --  referenced, to avoid spurious warnings. This is analogous
1768                   --  to what is done with an attribute definition clause, but
1769                   --  here we don't want to generate a reference because this
1770                   --  is the point of definition of the entity.
1771
1772                   if A_Id = Aspect_Address then
1773                      Set_Referenced (E);
1774                   end if;
1775
1776                --  Case 2: Aspects corresponding to pragmas
1777
1778                --  Case 2a: Aspects corresponding to pragmas with two
1779                --  arguments, where the first argument is a local name
1780                --  referring to the entity, and the second argument is the
1781                --  aspect definition expression.
1782
1783                --  Linker_Section/Suppress/Unsuppress
1784
1785                when Aspect_Linker_Section |
1786                     Aspect_Suppress       |
1787                     Aspect_Unsuppress     =>
1788
1789                   Make_Aitem_Pragma
1790                     (Pragma_Argument_Associations => New_List (
1791                        Make_Pragma_Argument_Association (Loc,
1792                          Expression => New_Occurrence_Of (E, Loc)),
1793                        Make_Pragma_Argument_Association (Sloc (Expr),
1794                          Expression => Relocate_Node (Expr))),
1795                      Pragma_Name                  => Chars (Id));
1796
1797                --  Synchronization
1798
1799                --  Corresponds to pragma Implemented, construct the pragma
1800
1801                when Aspect_Synchronization =>
1802                   Make_Aitem_Pragma
1803                     (Pragma_Argument_Associations => New_List (
1804                        Make_Pragma_Argument_Association (Loc,
1805                          Expression => New_Occurrence_Of (E, Loc)),
1806                        Make_Pragma_Argument_Association (Sloc (Expr),
1807                          Expression => Relocate_Node (Expr))),
1808                      Pragma_Name                  => Name_Implemented);
1809
1810                --  Attach_Handler
1811
1812                when Aspect_Attach_Handler =>
1813                   Make_Aitem_Pragma
1814                     (Pragma_Argument_Associations => New_List (
1815                        Make_Pragma_Argument_Association (Sloc (Ent),
1816                          Expression => Ent),
1817                        Make_Pragma_Argument_Association (Sloc (Expr),
1818                          Expression => Relocate_Node (Expr))),
1819                      Pragma_Name                  => Name_Attach_Handler);
1820
1821                   --  We need to insert this pragma into the tree to get proper
1822                   --  processing and to look valid from a placement viewpoint.
1823
1824                   Insert_Pragma (Aitem);
1825                   goto Continue;
1826
1827                --  Dynamic_Predicate, Predicate, Static_Predicate
1828
1829                when Aspect_Dynamic_Predicate |
1830                     Aspect_Predicate         |
1831                     Aspect_Static_Predicate  =>
1832
1833                   --  These aspects apply only to subtypes
1834
1835                   if not Is_Type (E) then
1836                      Error_Msg_N
1837                        ("predicate can only be specified for a subtype",
1838                         Aspect);
1839                      goto Continue;
1840
1841                   elsif Is_Incomplete_Type (E) then
1842                      Error_Msg_N
1843                        ("predicate cannot apply to incomplete view", Aspect);
1844                      goto Continue;
1845                   end if;
1846
1847                   --  Construct the pragma (always a pragma Predicate, with
1848                   --  flags recording whether it is static/dynamic). We also
1849                   --  set flags recording this in the type itself.
1850
1851                   Make_Aitem_Pragma
1852                     (Pragma_Argument_Associations => New_List (
1853                        Make_Pragma_Argument_Association (Sloc (Ent),
1854                          Expression => Ent),
1855                        Make_Pragma_Argument_Association (Sloc (Expr),
1856                          Expression => Relocate_Node (Expr))),
1857                      Pragma_Name                  => Name_Predicate);
1858
1859                   --  Mark type has predicates, and remember what kind of
1860                   --  aspect lead to this predicate (we need this to access
1861                   --  the right set of check policies later on).
1862
1863                   Set_Has_Predicates (E);
1864
1865                   if A_Id = Aspect_Dynamic_Predicate then
1866                      Set_Has_Dynamic_Predicate_Aspect (E);
1867                   elsif A_Id = Aspect_Static_Predicate then
1868                      Set_Has_Static_Predicate_Aspect (E);
1869                   end if;
1870
1871                   --  If the type is private, indicate that its completion
1872                   --  has a freeze node, because that is the one that will
1873                   --  be visible at freeze time.
1874
1875                   if Is_Private_Type (E) and then Present (Full_View (E)) then
1876                      Set_Has_Predicates (Full_View (E));
1877
1878                      if A_Id = Aspect_Dynamic_Predicate then
1879                         Set_Has_Dynamic_Predicate_Aspect (Full_View (E));
1880                      elsif A_Id = Aspect_Static_Predicate then
1881                         Set_Has_Static_Predicate_Aspect (Full_View (E));
1882                      end if;
1883
1884                      Set_Has_Delayed_Aspects (Full_View (E));
1885                      Ensure_Freeze_Node (Full_View (E));
1886                   end if;
1887
1888                --  Case 2b: Aspects corresponding to pragmas with two
1889                --  arguments, where the second argument is a local name
1890                --  referring to the entity, and the first argument is the
1891                --  aspect definition expression.
1892
1893                --  Convention
1894
1895                when Aspect_Convention  =>
1896
1897                   --  The aspect may be part of the specification of an import
1898                   --  or export pragma. Scan the aspect list to gather the
1899                   --  other components, if any. The name of the generated
1900                   --  pragma is one of Convention/Import/Export.
1901
1902                   declare
1903                      Args : constant List_Id := New_List (
1904                               Make_Pragma_Argument_Association (Sloc (Expr),
1905                                 Expression => Relocate_Node (Expr)),
1906                               Make_Pragma_Argument_Association (Sloc (Ent),
1907                                 Expression => Ent));
1908
1909                      Imp_Exp_Seen : Boolean := False;
1910                      --  Flag set when aspect Import or Export has been seen
1911
1912                      Imp_Seen : Boolean := False;
1913                      --  Flag set when aspect Import has been seen
1914
1915                      Asp        : Node_Id;
1916                      Asp_Nam    : Name_Id;
1917                      Extern_Arg : Node_Id;
1918                      Link_Arg   : Node_Id;
1919                      Prag_Nam   : Name_Id;
1920
1921                   begin
1922                      Extern_Arg := Empty;
1923                      Link_Arg   := Empty;
1924                      Prag_Nam   := Chars (Id);
1925
1926                      Asp := First (L);
1927                      while Present (Asp) loop
1928                         Asp_Nam := Chars (Identifier (Asp));
1929
1930                         --  Aspects Import and Export take precedence over
1931                         --  aspect Convention. As a result the generated pragma
1932                         --  must carry the proper interfacing aspect's name.
1933
1934                         if Nam_In (Asp_Nam, Name_Import, Name_Export) then
1935                            if Imp_Exp_Seen then
1936                               Error_Msg_N ("conflicting", Asp);
1937                            else
1938                               Imp_Exp_Seen := True;
1939
1940                               if Asp_Nam = Name_Import then
1941                                  Imp_Seen := True;
1942                               end if;
1943                            end if;
1944
1945                            Prag_Nam := Asp_Nam;
1946
1947                         --  Aspect External_Name adds an extra argument to the
1948                         --  generated pragma.
1949
1950                         elsif Asp_Nam = Name_External_Name then
1951                            Extern_Arg :=
1952                              Make_Pragma_Argument_Association (Loc,
1953                                Chars      => Asp_Nam,
1954                                Expression => Relocate_Node (Expression (Asp)));
1955
1956                         --  Aspect Link_Name adds an extra argument to the
1957                         --  generated pragma.
1958
1959                         elsif Asp_Nam = Name_Link_Name then
1960                            Link_Arg :=
1961                              Make_Pragma_Argument_Association (Loc,
1962                                Chars      => Asp_Nam,
1963                                Expression => Relocate_Node (Expression (Asp)));
1964                         end if;
1965
1966                         Next (Asp);
1967                      end loop;
1968
1969                      --  Assemble the full argument list
1970
1971                      if Present (Extern_Arg) then
1972                         Append_To (Args, Extern_Arg);
1973                      end if;
1974
1975                      if Present (Link_Arg) then
1976                         Append_To (Args, Link_Arg);
1977                      end if;
1978
1979                      Make_Aitem_Pragma
1980                        (Pragma_Argument_Associations => Args,
1981                         Pragma_Name                  => Prag_Nam);
1982
1983                      --  Store the generated pragma Import in the related
1984                      --  subprogram.
1985
1986                      if Imp_Seen and then Is_Subprogram (E) then
1987                         Set_Import_Pragma (E, Aitem);
1988                      end if;
1989                   end;
1990
1991                --  CPU, Interrupt_Priority, Priority
1992
1993                --  These three aspects can be specified for a subprogram spec
1994                --  or body, in which case we analyze the expression and export
1995                --  the value of the aspect.
1996
1997                --  Previously, we generated an equivalent pragma for bodies
1998                --  (note that the specs cannot contain these pragmas). The
1999                --  pragma was inserted ahead of local declarations, rather than
2000                --  after the body. This leads to a certain duplication between
2001                --  the processing performed for the aspect and the pragma, but
2002                --  given the straightforward handling required it is simpler
2003                --  to duplicate than to translate the aspect in the spec into
2004                --  a pragma in the declarative part of the body.
2005
2006                when Aspect_CPU                |
2007                     Aspect_Interrupt_Priority |
2008                     Aspect_Priority           =>
2009
2010                   if Nkind_In (N, N_Subprogram_Body,
2011                                   N_Subprogram_Declaration)
2012                   then
2013                      --  Analyze the aspect expression
2014
2015                      Analyze_And_Resolve (Expr, Standard_Integer);
2016
2017                      --  Interrupt_Priority aspect not allowed for main
2018                      --  subprograms. ARM D.1 does not forbid this explicitly,
2019                      --  but ARM J.15.11 (6/3) does not permit pragma
2020                      --  Interrupt_Priority for subprograms.
2021
2022                      if A_Id = Aspect_Interrupt_Priority then
2023                         Error_Msg_N
2024                           ("Interrupt_Priority aspect cannot apply to "
2025                            & "subprogram", Expr);
2026
2027                      --  The expression must be static
2028
2029                      elsif not Is_OK_Static_Expression (Expr) then
2030                         Flag_Non_Static_Expr
2031                           ("aspect requires static expression!", Expr);
2032
2033                      --  Check whether this is the main subprogram. Issue a
2034                      --  warning only if it is obviously not a main program
2035                      --  (when it has parameters or when the subprogram is
2036                      --  within a package).
2037
2038                      elsif Present (Parameter_Specifications
2039                                       (Specification (N)))
2040                        or else not Is_Compilation_Unit (Defining_Entity (N))
2041                      then
2042                         --  See ARM D.1 (14/3) and D.16 (12/3)
2043
2044                         Error_Msg_N
2045                           ("aspect applied to subprogram other than the "
2046                            & "main subprogram has no effect??", Expr);
2047
2048                      --  Otherwise check in range and export the value
2049
2050                      --  For the CPU aspect
2051
2052                      elsif A_Id = Aspect_CPU then
2053                         if Is_In_Range (Expr, RTE (RE_CPU_Range)) then
2054
2055                            --  Value is correct so we export the value to make
2056                            --  it available at execution time.
2057
2058                            Set_Main_CPU
2059                              (Main_Unit, UI_To_Int (Expr_Value (Expr)));
2060
2061                         else
2062                            Error_Msg_N
2063                              ("main subprogram CPU is out of range", Expr);
2064                         end if;
2065
2066                      --  For the Priority aspect
2067
2068                      elsif A_Id = Aspect_Priority then
2069                         if Is_In_Range (Expr, RTE (RE_Priority)) then
2070
2071                            --  Value is correct so we export the value to make
2072                            --  it available at execution time.
2073
2074                            Set_Main_Priority
2075                              (Main_Unit, UI_To_Int (Expr_Value (Expr)));
2076
2077                         --  Ignore pragma if Relaxed_RM_Semantics to support
2078                         --  other targets/non GNAT compilers.
2079
2080                         elsif not Relaxed_RM_Semantics then
2081                            Error_Msg_N
2082                              ("main subprogram priority is out of range",
2083                               Expr);
2084                         end if;
2085                      end if;
2086
2087                      --  Load an arbitrary entity from System.Tasking.Stages
2088                      --  or System.Tasking.Restricted.Stages (depending on
2089                      --  the supported profile) to make sure that one of these
2090                      --  packages is implicitly with'ed, since we need to have
2091                      --  the tasking run time active for the pragma Priority to
2092                      --  have any effect. Previously we with'ed the package
2093                      --  System.Tasking, but this package does not trigger the
2094                      --  required initialization of the run-time library.
2095
2096                      declare
2097                         Discard : Entity_Id;
2098                      begin
2099                         if Restricted_Profile then
2100                            Discard := RTE (RE_Activate_Restricted_Tasks);
2101                         else
2102                            Discard := RTE (RE_Activate_Tasks);
2103                         end if;
2104                      end;
2105
2106                      --  Handling for these Aspects in subprograms is complete
2107
2108                      goto Continue;
2109
2110                   --  For tasks
2111
2112                   else
2113                      --  Pass the aspect as an attribute
2114
2115                      Aitem :=
2116                        Make_Attribute_Definition_Clause (Loc,
2117                          Name       => Ent,
2118                          Chars      => Chars (Id),
2119                          Expression => Relocate_Node (Expr));
2120                   end if;
2121
2122                --  Warnings
2123
2124                when Aspect_Warnings =>
2125                   Make_Aitem_Pragma
2126                     (Pragma_Argument_Associations => New_List (
2127                        Make_Pragma_Argument_Association (Sloc (Expr),
2128                          Expression => Relocate_Node (Expr)),
2129                        Make_Pragma_Argument_Association (Loc,
2130                          Expression => New_Occurrence_Of (E, Loc))),
2131                      Pragma_Name                  => Chars (Id));
2132
2133                --  Case 2c: Aspects corresponding to pragmas with three
2134                --  arguments.
2135
2136                --  Invariant aspects have a first argument that references the
2137                --  entity, a second argument that is the expression and a third
2138                --  argument that is an appropriate message.
2139
2140                --  Invariant, Type_Invariant
2141
2142                when Aspect_Invariant      |
2143                     Aspect_Type_Invariant =>
2144
2145                   --  Analysis of the pragma will verify placement legality:
2146                   --  an invariant must apply to a private type, or appear in
2147                   --  the private part of a spec and apply to a completion.
2148
2149                   Make_Aitem_Pragma
2150                     (Pragma_Argument_Associations => New_List (
2151                        Make_Pragma_Argument_Association (Sloc (Ent),
2152                          Expression => Ent),
2153                        Make_Pragma_Argument_Association (Sloc (Expr),
2154                          Expression => Relocate_Node (Expr))),
2155                      Pragma_Name                  => Name_Invariant);
2156
2157                   --  Add message unless exception messages are suppressed
2158
2159                   if not Opt.Exception_Locations_Suppressed then
2160                      Append_To (Pragma_Argument_Associations (Aitem),
2161                        Make_Pragma_Argument_Association (Eloc,
2162                          Chars      => Name_Message,
2163                          Expression =>
2164                            Make_String_Literal (Eloc,
2165                              Strval => "failed invariant from "
2166                                        & Build_Location_String (Eloc))));
2167                   end if;
2168
2169                   --  For Invariant case, insert immediately after the entity
2170                   --  declaration. We do not have to worry about delay issues
2171                   --  since the pragma processing takes care of this.
2172
2173                   Delay_Required := False;
2174
2175                --  Case 2d : Aspects that correspond to a pragma with one
2176                --  argument.
2177
2178                --  Abstract_State
2179
2180                --  Aspect Abstract_State introduces implicit declarations for
2181                --  all state abstraction entities it defines. To emulate this
2182                --  behavior, insert the pragma at the beginning of the visible
2183                --  declarations of the related package so that it is analyzed
2184                --  immediately.
2185
2186                when Aspect_Abstract_State => Abstract_State : declare
2187                   Context : Node_Id := N;
2188                   Decl    : Node_Id;
2189                   Decls   : List_Id;
2190
2191                begin
2192                   --  When aspect Abstract_State appears on a generic package,
2193                   --  it is propageted to the package instance. The context in
2194                   --  this case is the instance spec.
2195
2196                   if Nkind (Context) = N_Package_Instantiation then
2197                      Context := Instance_Spec (Context);
2198                   end if;
2199
2200                   if Nkind_In (Context, N_Generic_Package_Declaration,
2201                                         N_Package_Declaration)
2202                   then
2203                      Make_Aitem_Pragma
2204                        (Pragma_Argument_Associations => New_List (
2205                           Make_Pragma_Argument_Association (Loc,
2206                             Expression => Relocate_Node (Expr))),
2207                         Pragma_Name                  => Name_Abstract_State);
2208                      Decorate (Aspect, Aitem);
2209
2210                      Decls := Visible_Declarations (Specification (Context));
2211
2212                      --  In general pragma Abstract_State must be at the top
2213                      --  of the existing visible declarations to emulate its
2214                      --  source counterpart. The only exception to this is a
2215                      --  generic instance in which case the pragma must be
2216                      --  inserted after the association renamings.
2217
2218                      if Present (Decls) then
2219                         Decl := First (Decls);
2220
2221                         --  The visible declarations of a generic instance have
2222                         --  the following structure:
2223
2224                         --    <renamings of generic formals>
2225                         --    <renamings of internally-generated spec and body>
2226                         --    <first source declaration>
2227
2228                         --  The pragma must be inserted before the first source
2229                         --  declaration, skip the instance "header".
2230
2231                         if Is_Generic_Instance (Defining_Entity (Context)) then
2232                            while Present (Decl)
2233                              and then not Comes_From_Source (Decl)
2234                            loop
2235                               Decl := Next (Decl);
2236                            end loop;
2237                         end if;
2238
2239                         --  When aspects Abstract_State, Ghost,
2240                         --  Initial_Condition and Initializes are out of order,
2241                         --  ensure that pragma SPARK_Mode is always at the top
2242                         --  of the declarations to properly enabled/suppress
2243                         --  errors.
2244
2245                         Insert_After_SPARK_Mode
2246                           (Prag    => Aitem,
2247                            Ins_Nod => Decl,
2248                            Decls   => Decls);
2249
2250                      --  Otherwise the pragma forms a new declarative list
2251
2252                      else
2253                         Set_Visible_Declarations
2254                           (Specification (Context), New_List (Aitem));
2255                      end if;
2256
2257                   else
2258                      Error_Msg_NE
2259                        ("aspect & must apply to a package declaration",
2260                         Aspect, Id);
2261                   end if;
2262
2263                   goto Continue;
2264                end Abstract_State;
2265
2266                --  Aspect Default_Internal_Condition is never delayed because
2267                --  it is equivalent to a source pragma which appears after the
2268                --  related private type. To deal with forward references, the
2269                --  generated pragma is stored in the rep chain of the related
2270                --  private type as types do not carry contracts. The pragma is
2271                --  wrapped inside of a procedure at the freeze point of the
2272                --  private type's full view.
2273
2274                when Aspect_Default_Initial_Condition =>
2275                   Make_Aitem_Pragma
2276                     (Pragma_Argument_Associations => New_List (
2277                        Make_Pragma_Argument_Association (Loc,
2278                          Expression => Relocate_Node (Expr))),
2279                      Pragma_Name                  =>
2280                        Name_Default_Initial_Condition);
2281
2282                   Decorate (Aspect, Aitem);
2283                   Insert_Pragma (Aitem);
2284                   goto Continue;
2285
2286                --  Default_Storage_Pool
2287
2288                when Aspect_Default_Storage_Pool =>
2289                   Make_Aitem_Pragma
2290                     (Pragma_Argument_Associations => New_List (
2291                        Make_Pragma_Argument_Association (Loc,
2292                          Expression => Relocate_Node (Expr))),
2293                      Pragma_Name                  =>
2294                        Name_Default_Storage_Pool);
2295
2296                   Decorate (Aspect, Aitem);
2297                   Insert_Pragma (Aitem);
2298                   goto Continue;
2299
2300                --  Depends
2301
2302                --  Aspect Depends is never delayed because it is equivalent to
2303                --  a source pragma which appears after the related subprogram.
2304                --  To deal with forward references, the generated pragma is
2305                --  stored in the contract of the related subprogram and later
2306                --  analyzed at the end of the declarative region. See routine
2307                --  Analyze_Depends_In_Decl_Part for details.
2308
2309                when Aspect_Depends =>
2310                   Make_Aitem_Pragma
2311                     (Pragma_Argument_Associations => New_List (
2312                        Make_Pragma_Argument_Association (Loc,
2313                          Expression => Relocate_Node (Expr))),
2314                      Pragma_Name                  => Name_Depends);
2315
2316                   Decorate (Aspect, Aitem);
2317                   Insert_Pragma (Aitem);
2318                   goto Continue;
2319
2320                --  Aspect Extensions_Visible is never delayed because it is
2321                --  equivalent to a source pragma which appears after the
2322                --  related subprogram.
2323
2324                when Aspect_Extensions_Visible =>
2325                   Make_Aitem_Pragma
2326                     (Pragma_Argument_Associations => New_List (
2327                        Make_Pragma_Argument_Association (Loc,
2328                          Expression => Relocate_Node (Expr))),
2329                      Pragma_Name                  => Name_Extensions_Visible);
2330
2331                   Decorate (Aspect, Aitem);
2332                   Insert_Pragma (Aitem);
2333                   goto Continue;
2334
2335                --  Aspect Ghost is never delayed because it is equivalent to a
2336                --  source pragma which appears at the top of [generic] package
2337                --  declarations or after an object, a [generic] subprogram, or
2338                --  a type declaration.
2339
2340                when Aspect_Ghost => Ghost : declare
2341                   Decls : List_Id;
2342
2343                begin
2344                   Make_Aitem_Pragma
2345                     (Pragma_Argument_Associations => New_List (
2346                        Make_Pragma_Argument_Association (Loc,
2347                          Expression => Relocate_Node (Expr))),
2348                      Pragma_Name                  => Name_Ghost);
2349
2350                   Decorate (Aspect, Aitem);
2351
2352                   --  When the aspect applies to a [generic] package, insert
2353                   --  the pragma at the top of the visible declarations. This
2354                   --  emulates the placement of a source pragma.
2355
2356                   if Nkind_In (N, N_Generic_Package_Declaration,
2357                                   N_Package_Declaration)
2358                   then
2359                      Decls := Visible_Declarations (Specification (N));
2360
2361                      if No (Decls) then
2362                         Decls := New_List;
2363                         Set_Visible_Declarations (N, Decls);
2364                      end if;
2365
2366                      --  When aspects Abstract_State, Ghost, Initial_Condition
2367                      --  and Initializes are out of order, ensure that pragma
2368                      --  SPARK_Mode is always at the top of the declarations to
2369                      --  properly enabled/suppress errors.
2370
2371                      Insert_After_SPARK_Mode
2372                        (Prag    => Aitem,
2373                         Ins_Nod => First (Decls),
2374                         Decls   => Decls);
2375
2376                   --  Otherwise the context is an object, [generic] subprogram
2377                   --  or type declaration.
2378
2379                   else
2380                      Insert_Pragma (Aitem);
2381                   end if;
2382
2383                   goto Continue;
2384                end Ghost;
2385
2386                --  Global
2387
2388                --  Aspect Global is never delayed because it is equivalent to
2389                --  a source pragma which appears after the related subprogram.
2390                --  To deal with forward references, the generated pragma is
2391                --  stored in the contract of the related subprogram and later
2392                --  analyzed at the end of the declarative region. See routine
2393                --  Analyze_Global_In_Decl_Part for details.
2394
2395                when Aspect_Global =>
2396                   Make_Aitem_Pragma
2397                     (Pragma_Argument_Associations => New_List (
2398                        Make_Pragma_Argument_Association (Loc,
2399                          Expression => Relocate_Node (Expr))),
2400                      Pragma_Name                  => Name_Global);
2401
2402                   Decorate (Aspect, Aitem);
2403                   Insert_Pragma (Aitem);
2404                   goto Continue;
2405
2406                --  Initial_Condition
2407
2408                --  Aspect Initial_Condition is never delayed because it is
2409                --  equivalent to a source pragma which appears after the
2410                --  related package. To deal with forward references, the
2411                --  generated pragma is stored in the contract of the related
2412                --  package and later analyzed at the end of the declarative
2413                --  region. See routine Analyze_Initial_Condition_In_Decl_Part
2414                --  for details.
2415
2416                when Aspect_Initial_Condition => Initial_Condition : declare
2417                   Context : Node_Id := N;
2418                   Decls   : List_Id;
2419
2420                begin
2421                   --  When aspect Initial_Condition appears on a generic
2422                   --  package, it is propageted to the package instance. The
2423                   --  context in this case is the instance spec.
2424
2425                   if Nkind (Context) = N_Package_Instantiation then
2426                      Context := Instance_Spec (Context);
2427                   end if;
2428
2429                   if Nkind_In (Context, N_Generic_Package_Declaration,
2430                                         N_Package_Declaration)
2431                   then
2432                      Decls := Visible_Declarations (Specification (Context));
2433
2434                      Make_Aitem_Pragma
2435                        (Pragma_Argument_Associations => New_List (
2436                           Make_Pragma_Argument_Association (Loc,
2437                             Expression => Relocate_Node (Expr))),
2438                         Pragma_Name                  =>
2439                           Name_Initial_Condition);
2440                      Decorate (Aspect, Aitem);
2441
2442                      if No (Decls) then
2443                         Decls := New_List;
2444                         Set_Visible_Declarations (Context, Decls);
2445                      end if;
2446
2447                      --  When aspects Abstract_State, Ghost, Initial_Condition
2448                      --  and Initializes are out of order, ensure that pragma
2449                      --  SPARK_Mode is always at the top of the declarations to
2450                      --  properly enabled/suppress errors.
2451
2452                      Insert_After_SPARK_Mode
2453                        (Prag    => Aitem,
2454                         Ins_Nod => First (Decls),
2455                         Decls   => Decls);
2456
2457                   else
2458                      Error_Msg_NE
2459                        ("aspect & must apply to a package declaration",
2460                         Aspect, Id);
2461                   end if;
2462
2463                   goto Continue;
2464                end Initial_Condition;
2465
2466                --  Initializes
2467
2468                --  Aspect Initializes is never delayed because it is equivalent
2469                --  to a source pragma appearing after the related package. To
2470                --  deal with forward references, the generated pragma is stored
2471                --  in the contract of the related package and later analyzed at
2472                --  the end of the declarative region. For details, see routine
2473                --  Analyze_Initializes_In_Decl_Part.
2474
2475                when Aspect_Initializes => Initializes : declare
2476                   Context : Node_Id := N;
2477                   Decls   : List_Id;
2478
2479                begin
2480                   --  When aspect Initializes appears on a generic package,
2481                   --  it is propageted to the package instance. The context
2482                   --  in this case is the instance spec.
2483
2484                   if Nkind (Context) = N_Package_Instantiation then
2485                      Context := Instance_Spec (Context);
2486                   end if;
2487
2488                   if Nkind_In (Context, N_Generic_Package_Declaration,
2489                                         N_Package_Declaration)
2490                   then
2491                      Decls := Visible_Declarations (Specification (Context));
2492
2493                      Make_Aitem_Pragma
2494                        (Pragma_Argument_Associations => New_List (
2495                           Make_Pragma_Argument_Association (Loc,
2496                             Expression => Relocate_Node (Expr))),
2497                         Pragma_Name                  => Name_Initializes);
2498                      Decorate (Aspect, Aitem);
2499
2500                      if No (Decls) then
2501                         Decls := New_List;
2502                         Set_Visible_Declarations (Context, Decls);
2503                      end if;
2504
2505                      --  When aspects Abstract_State, Ghost, Initial_Condition
2506                      --  and Initializes are out of order, ensure that pragma
2507                      --  SPARK_Mode is always at the top of the declarations to
2508                      --  properly enabled/suppress errors.
2509
2510                      Insert_After_SPARK_Mode
2511                        (Prag    => Aitem,
2512                         Ins_Nod => First (Decls),
2513                         Decls   => Decls);
2514
2515                   else
2516                      Error_Msg_NE
2517                        ("aspect & must apply to a package declaration",
2518                         Aspect, Id);
2519                   end if;
2520
2521                   goto Continue;
2522                end Initializes;
2523
2524                --  Obsolescent
2525
2526                when Aspect_Obsolescent => declare
2527                   Args : List_Id;
2528
2529                begin
2530                   if No (Expr) then
2531                      Args := No_List;
2532                   else
2533                      Args := New_List (
2534                        Make_Pragma_Argument_Association (Sloc (Expr),
2535                          Expression => Relocate_Node (Expr)));
2536                   end if;
2537
2538                   Make_Aitem_Pragma
2539                     (Pragma_Argument_Associations => Args,
2540                      Pragma_Name                  => Chars (Id));
2541                end;
2542
2543                --  Part_Of
2544
2545                when Aspect_Part_Of =>
2546                   if Nkind_In (N, N_Object_Declaration,
2547                                   N_Package_Instantiation)
2548                   then
2549                      Make_Aitem_Pragma
2550                        (Pragma_Argument_Associations => New_List (
2551                           Make_Pragma_Argument_Association (Loc,
2552                             Expression => Relocate_Node (Expr))),
2553                         Pragma_Name                  => Name_Part_Of);
2554
2555                   else
2556                      Error_Msg_NE
2557                        ("aspect & must apply to a variable or package "
2558                         & "instantiation", Aspect, Id);
2559                   end if;
2560
2561                --  SPARK_Mode
2562
2563                when Aspect_SPARK_Mode => SPARK_Mode : declare
2564                   Decls : List_Id;
2565
2566                begin
2567                   Make_Aitem_Pragma
2568                     (Pragma_Argument_Associations => New_List (
2569                        Make_Pragma_Argument_Association (Loc,
2570                          Expression => Relocate_Node (Expr))),
2571                      Pragma_Name                  => Name_SPARK_Mode);
2572
2573                   --  When the aspect appears on a package or a subprogram
2574                   --  body, insert the generated pragma at the top of the body
2575                   --  declarations to emulate the behavior of a source pragma.
2576
2577                   if Nkind_In (N, N_Package_Body, N_Subprogram_Body) then
2578                      Decorate (Aspect, Aitem);
2579
2580                      Decls := Declarations (N);
2581
2582                      if No (Decls) then
2583                         Decls := New_List;
2584                         Set_Declarations (N, Decls);
2585                      end if;
2586
2587                      Prepend_To (Decls, Aitem);
2588                      goto Continue;
2589
2590                   --  When the aspect is associated with a [generic] package
2591                   --  declaration, insert the generated pragma at the top of
2592                   --  the visible declarations to emulate the behavior of a
2593                   --  source pragma.
2594
2595                   elsif Nkind_In (N, N_Generic_Package_Declaration,
2596                                      N_Package_Declaration)
2597                   then
2598                      Decorate (Aspect, Aitem);
2599
2600                      Decls := Visible_Declarations (Specification (N));
2601
2602                      if No (Decls) then
2603                         Decls := New_List;
2604                         Set_Visible_Declarations (Specification (N), Decls);
2605                      end if;
2606
2607                      Prepend_To (Decls, Aitem);
2608                      goto Continue;
2609                   end if;
2610                end SPARK_Mode;
2611
2612                --  Refined_Depends
2613
2614                --  Aspect Refined_Depends is never delayed because it is
2615                --  equivalent to a source pragma which appears in the
2616                --  declarations of the related subprogram body. To deal with
2617                --  forward references, the generated pragma is stored in the
2618                --  contract of the related subprogram body and later analyzed
2619                --  at the end of the declarative region. For details, see
2620                --  routine Analyze_Refined_Depends_In_Decl_Part.
2621
2622                when Aspect_Refined_Depends =>
2623                   Make_Aitem_Pragma
2624                     (Pragma_Argument_Associations => New_List (
2625                        Make_Pragma_Argument_Association (Loc,
2626                          Expression => Relocate_Node (Expr))),
2627                      Pragma_Name                  => Name_Refined_Depends);
2628
2629                   Decorate (Aspect, Aitem);
2630                   Insert_Pragma (Aitem);
2631                   goto Continue;
2632
2633                --  Refined_Global
2634
2635                --  Aspect Refined_Global is never delayed because it is
2636                --  equivalent to a source pragma which appears in the
2637                --  declarations of the related subprogram body. To deal with
2638                --  forward references, the generated pragma is stored in the
2639                --  contract of the related subprogram body and later analyzed
2640                --  at the end of the declarative region. For details, see
2641                --  routine Analyze_Refined_Global_In_Decl_Part.
2642
2643                when Aspect_Refined_Global =>
2644                   Make_Aitem_Pragma
2645                     (Pragma_Argument_Associations => New_List (
2646                        Make_Pragma_Argument_Association (Loc,
2647                          Expression => Relocate_Node (Expr))),
2648                      Pragma_Name                  => Name_Refined_Global);
2649
2650                   Decorate (Aspect, Aitem);
2651                   Insert_Pragma (Aitem);
2652                   goto Continue;
2653
2654                --  Refined_Post
2655
2656                when Aspect_Refined_Post =>
2657                   Make_Aitem_Pragma
2658                     (Pragma_Argument_Associations => New_List (
2659                        Make_Pragma_Argument_Association (Loc,
2660                          Expression => Relocate_Node (Expr))),
2661                      Pragma_Name                  => Name_Refined_Post);
2662
2663                --  Refined_State
2664
2665                when Aspect_Refined_State => Refined_State : declare
2666                   Decls : List_Id;
2667
2668                begin
2669                   --  The corresponding pragma for Refined_State is inserted in
2670                   --  the declarations of the related package body. This action
2671                   --  synchronizes both the source and from-aspect versions of
2672                   --  the pragma.
2673
2674                   if Nkind (N) = N_Package_Body then
2675                      Decls := Declarations (N);
2676
2677                      Make_Aitem_Pragma
2678                        (Pragma_Argument_Associations => New_List (
2679                           Make_Pragma_Argument_Association (Loc,
2680                             Expression => Relocate_Node (Expr))),
2681                         Pragma_Name                  => Name_Refined_State);
2682                      Decorate (Aspect, Aitem);
2683
2684                      if No (Decls) then
2685                         Decls := New_List;
2686                         Set_Declarations (N, Decls);
2687                      end if;
2688
2689                      --  Pragma Refined_State must be inserted after pragma
2690                      --  SPARK_Mode in the tree. This ensures that any error
2691                      --  messages dependent on SPARK_Mode will be properly
2692                      --  enabled/suppressed.
2693
2694                      Insert_After_SPARK_Mode
2695                        (Prag    => Aitem,
2696                         Ins_Nod => First (Decls),
2697                         Decls   => Decls);
2698
2699                   else
2700                      Error_Msg_NE
2701                        ("aspect & must apply to a package body", Aspect, Id);
2702                   end if;
2703
2704                   goto Continue;
2705                end Refined_State;
2706
2707                --  Relative_Deadline
2708
2709                when Aspect_Relative_Deadline =>
2710                   Make_Aitem_Pragma
2711                     (Pragma_Argument_Associations => New_List (
2712                        Make_Pragma_Argument_Association (Loc,
2713                          Expression => Relocate_Node (Expr))),
2714                       Pragma_Name                 => Name_Relative_Deadline);
2715
2716                   --  If the aspect applies to a task, the corresponding pragma
2717                   --  must appear within its declarations, not after.
2718
2719                   if Nkind (N) = N_Task_Type_Declaration then
2720                      declare
2721                         Def : Node_Id;
2722                         V   : List_Id;
2723
2724                      begin
2725                         if No (Task_Definition (N)) then
2726                            Set_Task_Definition (N,
2727                              Make_Task_Definition (Loc,
2728                                 Visible_Declarations => New_List,
2729                                 End_Label => Empty));
2730                         end if;
2731
2732                         Def := Task_Definition (N);
2733                         V  := Visible_Declarations (Def);
2734                         if not Is_Empty_List (V) then
2735                            Insert_Before (First (V), Aitem);
2736
2737                         else
2738                            Set_Visible_Declarations (Def, New_List (Aitem));
2739                         end if;
2740
2741                         goto Continue;
2742                      end;
2743                   end if;
2744
2745                --  Case 2e: Annotate aspect
2746
2747                when Aspect_Annotate =>
2748                   declare
2749                      Args  : List_Id;
2750                      Pargs : List_Id;
2751                      Arg   : Node_Id;
2752
2753                   begin
2754                      --  The argument can be a single identifier
2755
2756                      if Nkind (Expr) = N_Identifier then
2757
2758                         --  One level of parens is allowed
2759
2760                         if Paren_Count (Expr) > 1 then
2761                            Error_Msg_F ("extra parentheses ignored", Expr);
2762                         end if;
2763
2764                         Set_Paren_Count (Expr, 0);
2765
2766                         --  Add the single item to the list
2767
2768                         Args := New_List (Expr);
2769
2770                      --  Otherwise we must have an aggregate
2771
2772                      elsif Nkind (Expr) = N_Aggregate then
2773
2774                         --  Must be positional
2775
2776                         if Present (Component_Associations (Expr)) then
2777                            Error_Msg_F
2778                              ("purely positional aggregate required", Expr);
2779                            goto Continue;
2780                         end if;
2781
2782                         --  Must not be parenthesized
2783
2784                         if Paren_Count (Expr) /= 0 then
2785                            Error_Msg_F ("extra parentheses ignored", Expr);
2786                         end if;
2787
2788                         --  List of arguments is list of aggregate expressions
2789
2790                         Args := Expressions (Expr);
2791
2792                      --  Anything else is illegal
2793
2794                      else
2795                         Error_Msg_F ("wrong form for Annotate aspect", Expr);
2796                         goto Continue;
2797                      end if;
2798
2799                      --  Prepare pragma arguments
2800
2801                      Pargs := New_List;
2802                      Arg := First (Args);
2803                      while Present (Arg) loop
2804                         Append_To (Pargs,
2805                           Make_Pragma_Argument_Association (Sloc (Arg),
2806                             Expression => Relocate_Node (Arg)));
2807                         Next (Arg);
2808                      end loop;
2809
2810                      Append_To (Pargs,
2811                        Make_Pragma_Argument_Association (Sloc (Ent),
2812                          Chars      => Name_Entity,
2813                          Expression => Ent));
2814
2815                      Make_Aitem_Pragma
2816                        (Pragma_Argument_Associations => Pargs,
2817                         Pragma_Name                  => Name_Annotate);
2818                   end;
2819
2820                --  Case 3 : Aspects that don't correspond to pragma/attribute
2821                --  definition clause.
2822
2823                --  Case 3a: The aspects listed below don't correspond to
2824                --  pragmas/attributes but do require delayed analysis.
2825
2826                --  Default_Value can only apply to a scalar type
2827
2828                when Aspect_Default_Value =>
2829                   if not Is_Scalar_Type (E) then
2830                      Error_Msg_N
2831                        ("aspect Default_Value must apply to a scalar type", N);
2832                   end if;
2833
2834                   Aitem := Empty;
2835
2836                --  Default_Component_Value can only apply to an array type
2837                --  with scalar components.
2838
2839                when Aspect_Default_Component_Value =>
2840                   if not (Is_Array_Type (E)
2841                            and then Is_Scalar_Type (Component_Type (E)))
2842                   then
2843                      Error_Msg_N ("aspect Default_Component_Value can only "
2844                        & "apply to an array of scalar components", N);
2845                   end if;
2846
2847                   Aitem := Empty;
2848
2849                --  Case 3b: The aspects listed below don't correspond to
2850                --  pragmas/attributes and don't need delayed analysis.
2851
2852                --  Implicit_Dereference
2853
2854                --  For Implicit_Dereference, External_Name and Link_Name, only
2855                --  the legality checks are done during the analysis, thus no
2856                --  delay is required.
2857
2858                when Aspect_Implicit_Dereference =>
2859                   Analyze_Aspect_Implicit_Dereference;
2860                   goto Continue;
2861
2862                --  External_Name, Link_Name
2863
2864                when Aspect_External_Name |
2865                     Aspect_Link_Name     =>
2866                   Analyze_Aspect_External_Or_Link_Name;
2867                   goto Continue;
2868
2869                --  Dimension
2870
2871                when Aspect_Dimension =>
2872                   Analyze_Aspect_Dimension (N, Id, Expr);
2873                   goto Continue;
2874
2875                --  Dimension_System
2876
2877                when Aspect_Dimension_System =>
2878                   Analyze_Aspect_Dimension_System (N, Id, Expr);
2879                   goto Continue;
2880
2881                --  Case 4: Aspects requiring special handling
2882
2883                --  Pre/Post/Test_Case/Contract_Cases whose corresponding
2884                --  pragmas take care of the delay.
2885
2886                --  Pre/Post
2887
2888                --  Aspects Pre/Post generate Precondition/Postcondition pragmas
2889                --  with a first argument that is the expression, and a second
2890                --  argument that is an informative message if the test fails.
2891                --  This is inserted right after the declaration, to get the
2892                --  required pragma placement. The processing for the pragmas
2893                --  takes care of the required delay.
2894
2895                when Pre_Post_Aspects => Pre_Post : declare
2896                   Pname : Name_Id;
2897
2898                begin
2899                   if A_Id = Aspect_Pre or else A_Id = Aspect_Precondition then
2900                      Pname := Name_Precondition;
2901                   else
2902                      Pname := Name_Postcondition;
2903                   end if;
2904
2905                   --  If the expressions is of the form A and then B, then
2906                   --  we generate separate Pre/Post aspects for the separate
2907                   --  clauses. Since we allow multiple pragmas, there is no
2908                   --  problem in allowing multiple Pre/Post aspects internally.
2909                   --  These should be treated in reverse order (B first and
2910                   --  A second) since they are later inserted just after N in
2911                   --  the order they are treated. This way, the pragma for A
2912                   --  ends up preceding the pragma for B, which may have an
2913                   --  importance for the error raised (either constraint error
2914                   --  or precondition error).
2915
2916                   --  We do not do this for Pre'Class, since we have to put
2917                   --  these conditions together in a complex OR expression.
2918
2919                   --  We do not do this in ASIS mode, as ASIS relies on the
2920                   --  original node representing the complete expression, when
2921                   --  retrieving it through the source aspect table.
2922
2923                   if not ASIS_Mode
2924                     and then (Pname = Name_Postcondition
2925                                or else not Class_Present (Aspect))
2926                   then
2927                      while Nkind (Expr) = N_And_Then loop
2928                         Insert_After (Aspect,
2929                           Make_Aspect_Specification (Sloc (Left_Opnd (Expr)),
2930                             Identifier    => Identifier (Aspect),
2931                             Expression    => Relocate_Node (Left_Opnd (Expr)),
2932                             Class_Present => Class_Present (Aspect),
2933                             Split_PPC     => True));
2934                         Rewrite (Expr, Relocate_Node (Right_Opnd (Expr)));
2935                         Eloc := Sloc (Expr);
2936                      end loop;
2937                   end if;
2938
2939                   --  Build the precondition/postcondition pragma
2940
2941                   --  Add note about why we do NOT need Copy_Tree here???
2942
2943                   Make_Aitem_Pragma
2944                     (Pragma_Argument_Associations => New_List (
2945                        Make_Pragma_Argument_Association (Eloc,
2946                          Chars      => Name_Check,
2947                          Expression => Relocate_Node (Expr))),
2948                        Pragma_Name                => Pname);
2949
2950                   --  Add message unless exception messages are suppressed
2951
2952                   if not Opt.Exception_Locations_Suppressed then
2953                      Append_To (Pragma_Argument_Associations (Aitem),
2954                        Make_Pragma_Argument_Association (Eloc,
2955                          Chars      => Name_Message,
2956                          Expression =>
2957                            Make_String_Literal (Eloc,
2958                              Strval => "failed "
2959                                        & Get_Name_String (Pname)
2960                                        & " from "
2961                                        & Build_Location_String (Eloc))));
2962                   end if;
2963
2964                   Set_Is_Delayed_Aspect (Aspect);
2965
2966                   --  For Pre/Post cases, insert immediately after the entity
2967                   --  declaration, since that is the required pragma placement.
2968                   --  Note that for these aspects, we do not have to worry
2969                   --  about delay issues, since the pragmas themselves deal
2970                   --  with delay of visibility for the expression analysis.
2971
2972                   Insert_Pragma (Aitem);
2973
2974                   goto Continue;
2975                end Pre_Post;
2976
2977                --  Test_Case
2978
2979                when Aspect_Test_Case => Test_Case : declare
2980                   Args      : List_Id;
2981                   Comp_Expr : Node_Id;
2982                   Comp_Assn : Node_Id;
2983                   New_Expr  : Node_Id;
2984
2985                begin
2986                   Args := New_List;
2987
2988                   if Nkind (Parent (N)) = N_Compilation_Unit then
2989                      Error_Msg_Name_1 := Nam;
2990                      Error_Msg_N ("incorrect placement of aspect `%`", E);
2991                      goto Continue;
2992                   end if;
2993
2994                   if Nkind (Expr) /= N_Aggregate then
2995                      Error_Msg_Name_1 := Nam;
2996                      Error_Msg_NE
2997                        ("wrong syntax for aspect `%` for &", Id, E);
2998                      goto Continue;
2999                   end if;
3000
3001                   --  Make pragma expressions refer to the original aspect
3002                   --  expressions through the Original_Node link. This is used
3003                   --  in semantic analysis for ASIS mode, so that the original
3004                   --  expression also gets analyzed.
3005
3006                   Comp_Expr := First (Expressions (Expr));
3007                   while Present (Comp_Expr) loop
3008                      New_Expr := Relocate_Node (Comp_Expr);
3009                      Append_To (Args,
3010                        Make_Pragma_Argument_Association (Sloc (Comp_Expr),
3011                          Expression => New_Expr));
3012                      Next (Comp_Expr);
3013                   end loop;
3014
3015                   Comp_Assn := First (Component_Associations (Expr));
3016                   while Present (Comp_Assn) loop
3017                      if List_Length (Choices (Comp_Assn)) /= 1
3018                        or else
3019                          Nkind (First (Choices (Comp_Assn))) /= N_Identifier
3020                      then
3021                         Error_Msg_Name_1 := Nam;
3022                         Error_Msg_NE
3023                           ("wrong syntax for aspect `%` for &", Id, E);
3024                         goto Continue;
3025                      end if;
3026
3027                      Append_To (Args,
3028                        Make_Pragma_Argument_Association (Sloc (Comp_Assn),
3029                          Chars      => Chars (First (Choices (Comp_Assn))),
3030                          Expression =>
3031                            Relocate_Node (Expression (Comp_Assn))));
3032                      Next (Comp_Assn);
3033                   end loop;
3034
3035                   --  Build the test-case pragma
3036
3037                   Make_Aitem_Pragma
3038                     (Pragma_Argument_Associations => Args,
3039                      Pragma_Name                  => Nam);
3040                end Test_Case;
3041
3042                --  Contract_Cases
3043
3044                when Aspect_Contract_Cases =>
3045                   Make_Aitem_Pragma
3046                     (Pragma_Argument_Associations => New_List (
3047                        Make_Pragma_Argument_Association (Loc,
3048                          Expression => Relocate_Node (Expr))),
3049                      Pragma_Name                  => Nam);
3050
3051                   Decorate (Aspect, Aitem);
3052                   Insert_Pragma (Aitem);
3053                   goto Continue;
3054
3055                --  Case 5: Special handling for aspects with an optional
3056                --  boolean argument.
3057
3058                --  In the delayed case, the corresponding pragma cannot be
3059                --  generated yet because the evaluation of the boolean needs
3060                --  to be delayed till the freeze point.
3061
3062                when Boolean_Aspects      |
3063                     Library_Unit_Aspects =>
3064
3065                   Set_Is_Boolean_Aspect (Aspect);
3066
3067                   --  Lock_Free aspect only apply to protected objects
3068
3069                   if A_Id = Aspect_Lock_Free then
3070                      if Ekind (E) /= E_Protected_Type then
3071                         Error_Msg_Name_1 := Nam;
3072                         Error_Msg_N
3073                           ("aspect % only applies to a protected object",
3074                            Aspect);
3075
3076                      else
3077                         --  Set the Uses_Lock_Free flag to True if there is no
3078                         --  expression or if the expression is True. The
3079                         --  evaluation of this aspect should be delayed to the
3080                         --  freeze point (why???)
3081
3082                         if No (Expr)
3083                           or else Is_True (Static_Boolean (Expr))
3084                         then
3085                            Set_Uses_Lock_Free (E);
3086                         end if;
3087
3088                         Record_Rep_Item (E, Aspect);
3089                      end if;
3090
3091                      goto Continue;
3092
3093                   elsif A_Id = Aspect_Import or else A_Id = Aspect_Export then
3094
3095                      --  For the case of aspects Import and Export, we don't
3096                      --  consider that we know the entity is never set in the
3097                      --  source, since it is is likely modified outside the
3098                      --  program.
3099
3100                      --  Note: one might think that the analysis of the
3101                      --  resulting pragma would take care of that, but
3102                      --  that's not the case since it won't be from source.
3103
3104                      if Ekind (E) = E_Variable then
3105                         Set_Never_Set_In_Source (E, False);
3106                      end if;
3107
3108                      --  In older versions of Ada the corresponding pragmas
3109                      --  specified a Convention. In Ada 2012 the convention is
3110                      --  specified as a separate aspect, and it is optional,
3111                      --  given that it defaults to Convention_Ada. The code
3112                      --  that verifed that there was a matching convention
3113                      --  is now obsolete.
3114
3115                      --  Resolve the expression of an Import or Export here,
3116                      --  and require it to be of type Boolean and static. This
3117                      --  is not quite right, because in general this should be
3118                      --  delayed, but that seems tricky for these, because
3119                      --  normally Boolean aspects are replaced with pragmas at
3120                      --  the freeze point (in Make_Pragma_From_Boolean_Aspect),
3121                      --  but in the case of these aspects we can't generate
3122                      --  a simple pragma with just the entity name. ???
3123
3124                      if not Present (Expr)
3125                        or else Is_True (Static_Boolean (Expr))
3126                      then
3127                         if A_Id = Aspect_Import then
3128                            Set_Is_Imported (E);
3129                            Set_Has_Completion (E);
3130
3131                            --  An imported entity cannot have an explicit
3132                            --  initialization.
3133
3134                            if Nkind (N) = N_Object_Declaration
3135                              and then Present (Expression (N))
3136                            then
3137                               Error_Msg_N
3138                                 ("imported entities cannot be initialized "
3139                                  & "(RM B.1(24))", Expression (N));
3140                            end if;
3141
3142                         elsif A_Id = Aspect_Export then
3143                            Set_Is_Exported (E);
3144                         end if;
3145                      end if;
3146
3147                      goto Continue;
3148
3149                   --  Disable_Controlled
3150
3151                   elsif A_Id = Aspect_Disable_Controlled then
3152                      if Ekind (E) /= E_Record_Type
3153                        or else not Is_Controlled (E)
3154                      then
3155                         Error_Msg_N
3156                           ("aspect % requires controlled record type", Aspect);
3157                         goto Continue;
3158                      end if;
3159
3160                      Analyze_And_Resolve (Expr, Standard_Boolean);
3161
3162                      --  If we're in a generic template, we don't want to try
3163                      --  to disable controlled types, because typical usage is
3164                      --  "Disable_Controlled => not <some_check>'Enabled", and
3165                      --  the value of Enabled is not known until we see a
3166                      --  particular instance.
3167
3168                      if Expander_Active then
3169                         if not Present (Expr)
3170                           or else Is_True (Static_Boolean (Expr))
3171                         then
3172                            Set_Disable_Controlled (E);
3173                         end if;
3174                      end if;
3175
3176                      goto Continue;
3177                   end if;
3178
3179                   --  Library unit aspects require special handling in the case
3180                   --  of a package declaration, the pragma needs to be inserted
3181                   --  in the list of declarations for the associated package.
3182                   --  There is no issue of visibility delay for these aspects.
3183
3184                   if A_Id in Library_Unit_Aspects
3185                     and then
3186                       Nkind_In (N, N_Package_Declaration,
3187                                    N_Generic_Package_Declaration)
3188                     and then Nkind (Parent (N)) /= N_Compilation_Unit
3189
3190                     --  Aspect is legal on a local instantiation of a library-
3191                     --  level generic unit.
3192
3193                     and then not Is_Generic_Instance (Defining_Entity (N))
3194                   then
3195                      Error_Msg_N
3196                        ("incorrect context for library unit aspect&", Id);
3197                      goto Continue;
3198                   end if;
3199
3200                   --  External property aspects are Boolean by nature, but
3201                   --  their pragmas must contain two arguments, the second
3202                   --  being the optional Boolean expression.
3203
3204                   if A_Id = Aspect_Async_Readers   or else
3205                      A_Id = Aspect_Async_Writers   or else
3206                      A_Id = Aspect_Effective_Reads or else
3207                      A_Id = Aspect_Effective_Writes
3208                   then
3209                      declare
3210                         Args : List_Id;
3211
3212                      begin
3213                         --  The first argument of the external property pragma
3214                         --  is the related object.
3215
3216                         Args :=
3217                           New_List (
3218                             Make_Pragma_Argument_Association (Sloc (Ent),
3219                               Expression => Ent));
3220
3221                         --  The second argument is the optional Boolean
3222                         --  expression which must be propagated even if it
3223                         --  evaluates to False as this has special semantic
3224                         --  meaning.
3225
3226                         if Present (Expr) then
3227                            Append_To (Args,
3228                              Make_Pragma_Argument_Association (Loc,
3229                                Expression => Relocate_Node (Expr)));
3230                         end if;
3231
3232                         Make_Aitem_Pragma
3233                           (Pragma_Argument_Associations => Args,
3234                            Pragma_Name                  => Nam);
3235                      end;
3236
3237                   --  Cases where we do not delay, includes all cases where the
3238                   --  expression is missing other than the above cases.
3239
3240                   elsif not Delay_Required or else No (Expr) then
3241                      Make_Aitem_Pragma
3242                        (Pragma_Argument_Associations => New_List (
3243                           Make_Pragma_Argument_Association (Sloc (Ent),
3244                             Expression => Ent)),
3245                         Pragma_Name                  => Chars (Id));
3246                      Delay_Required := False;
3247
3248                   --  In general cases, the corresponding pragma/attribute
3249                   --  definition clause will be inserted later at the freezing
3250                   --  point, and we do not need to build it now.
3251
3252                   else
3253                      Aitem := Empty;
3254                   end if;
3255
3256                --  Storage_Size
3257
3258                --  This is special because for access types we need to generate
3259                --  an attribute definition clause. This also works for single
3260                --  task declarations, but it does not work for task type
3261                --  declarations, because we have the case where the expression
3262                --  references a discriminant of the task type. That can't use
3263                --  an attribute definition clause because we would not have
3264                --  visibility on the discriminant. For that case we must
3265                --  generate a pragma in the task definition.
3266
3267                when Aspect_Storage_Size =>
3268
3269                   --  Task type case
3270
3271                   if Ekind (E) = E_Task_Type then
3272                      declare
3273                         Decl : constant Node_Id := Declaration_Node (E);
3274
3275                      begin
3276                         pragma Assert (Nkind (Decl) = N_Task_Type_Declaration);
3277
3278                         --  If no task definition, create one
3279
3280                         if No (Task_Definition (Decl)) then
3281                            Set_Task_Definition (Decl,
3282                              Make_Task_Definition (Loc,
3283                                Visible_Declarations => Empty_List,
3284                                End_Label            => Empty));
3285                         end if;
3286
3287                         --  Create a pragma and put it at the start of the task
3288                         --  definition for the task type declaration.
3289
3290                         Make_Aitem_Pragma
3291                           (Pragma_Argument_Associations => New_List (
3292                              Make_Pragma_Argument_Association (Loc,
3293                                Expression => Relocate_Node (Expr))),
3294                            Pragma_Name                  => Name_Storage_Size);
3295
3296                         Prepend
3297                           (Aitem,
3298                            Visible_Declarations (Task_Definition (Decl)));
3299                         goto Continue;
3300                      end;
3301
3302                   --  All other cases, generate attribute definition
3303
3304                   else
3305                      Aitem :=
3306                        Make_Attribute_Definition_Clause (Loc,
3307                          Name       => Ent,
3308                          Chars      => Chars (Id),
3309                          Expression => Relocate_Node (Expr));
3310                   end if;
3311             end case;
3312
3313             --  Attach the corresponding pragma/attribute definition clause to
3314             --  the aspect specification node.
3315
3316             if Present (Aitem) then
3317                Set_From_Aspect_Specification (Aitem);
3318             end if;
3319
3320             --  In the context of a compilation unit, we directly put the
3321             --  pragma in the Pragmas_After list of the N_Compilation_Unit_Aux
3322             --  node (no delay is required here) except for aspects on a
3323             --  subprogram body (see below) and a generic package, for which we
3324             --  need to introduce the pragma before building the generic copy
3325             --  (see sem_ch12), and for package instantiations, where the
3326             --  library unit pragmas are better handled early.
3327
3328             if Nkind (Parent (N)) = N_Compilation_Unit
3329               and then (Present (Aitem) or else Is_Boolean_Aspect (Aspect))
3330             then
3331                declare
3332                   Aux : constant Node_Id := Aux_Decls_Node (Parent (N));
3333
3334                begin
3335                   pragma Assert (Nkind (Aux) = N_Compilation_Unit_Aux);
3336
3337                   --  For a Boolean aspect, create the corresponding pragma if
3338                   --  no expression or if the value is True.
3339
3340                   if Is_Boolean_Aspect (Aspect) and then No (Aitem) then
3341                      if Is_True (Static_Boolean (Expr)) then
3342                         Make_Aitem_Pragma
3343                           (Pragma_Argument_Associations => New_List (
3344                              Make_Pragma_Argument_Association (Sloc (Ent),
3345                                Expression => Ent)),
3346                            Pragma_Name                  => Chars (Id));
3347
3348                         Set_From_Aspect_Specification (Aitem, True);
3349                         Set_Corresponding_Aspect (Aitem, Aspect);
3350
3351                      else
3352                         goto Continue;
3353                      end if;
3354                   end if;
3355
3356                   --  If the aspect is on a subprogram body (relevant aspect
3357                   --  is Inline), add the pragma in front of the declarations.
3358
3359                   if Nkind (N) = N_Subprogram_Body then
3360                      if No (Declarations (N)) then
3361                         Set_Declarations (N, New_List);
3362                      end if;
3363
3364                      Prepend (Aitem, Declarations (N));
3365
3366                   elsif Nkind (N) = N_Generic_Package_Declaration then
3367                      if No (Visible_Declarations (Specification (N))) then
3368                         Set_Visible_Declarations (Specification (N), New_List);
3369                      end if;
3370
3371                      Prepend (Aitem,
3372                        Visible_Declarations (Specification (N)));
3373
3374                   elsif Nkind (N) = N_Package_Instantiation then
3375                      declare
3376                         Spec : constant Node_Id :=
3377                                  Specification (Instance_Spec (N));
3378                      begin
3379                         if No (Visible_Declarations (Spec)) then
3380                            Set_Visible_Declarations (Spec, New_List);
3381                         end if;
3382
3383                         Prepend (Aitem, Visible_Declarations (Spec));
3384                      end;
3385
3386                   else
3387                      if No (Pragmas_After (Aux)) then
3388                         Set_Pragmas_After (Aux, New_List);
3389                      end if;
3390
3391                      Append (Aitem, Pragmas_After (Aux));
3392                   end if;
3393
3394                   goto Continue;
3395                end;
3396             end if;
3397
3398             --  The evaluation of the aspect is delayed to the freezing point.
3399             --  The pragma or attribute clause if there is one is then attached
3400             --  to the aspect specification which is put in the rep item list.
3401
3402             if Delay_Required then
3403                if Present (Aitem) then
3404                   Set_Is_Delayed_Aspect (Aitem);
3405                   Set_Aspect_Rep_Item (Aspect, Aitem);
3406                   Set_Parent (Aitem, Aspect);
3407                end if;
3408
3409                Set_Is_Delayed_Aspect (Aspect);
3410
3411                --  In the case of Default_Value, link the aspect to base type
3412                --  as well, even though it appears on a first subtype. This is
3413                --  mandated by the semantics of the aspect. Do not establish
3414                --  the link when processing the base type itself as this leads
3415                --  to a rep item circularity. Verify that we are dealing with
3416                --  a scalar type to prevent cascaded errors.
3417
3418                if A_Id = Aspect_Default_Value
3419                  and then Is_Scalar_Type (E)
3420                  and then Base_Type (E) /= E
3421                then
3422                   Set_Has_Delayed_Aspects (Base_Type (E));
3423                   Record_Rep_Item (Base_Type (E), Aspect);
3424                end if;
3425
3426                Set_Has_Delayed_Aspects (E);
3427                Record_Rep_Item (E, Aspect);
3428
3429             --  When delay is not required and the context is a package or a
3430             --  subprogram body, insert the pragma in the body declarations.
3431
3432             elsif Nkind_In (N, N_Package_Body, N_Subprogram_Body) then
3433                if No (Declarations (N)) then
3434                   Set_Declarations (N, New_List);
3435                end if;
3436
3437                --  The pragma is added before source declarations
3438
3439                Prepend_To (Declarations (N), Aitem);
3440
3441             --  When delay is not required and the context is not a compilation
3442             --  unit, we simply insert the pragma/attribute definition clause
3443             --  in sequence.
3444
3445             else
3446                Insert_After (Ins_Node, Aitem);
3447                Ins_Node := Aitem;
3448             end if;
3449          end Analyze_One_Aspect;
3450
3451       <<Continue>>
3452          Next (Aspect);
3453       end loop Aspect_Loop;
3454
3455       if Has_Delayed_Aspects (E) then
3456          Ensure_Freeze_Node (E);
3457       end if;
3458    end Analyze_Aspect_Specifications;
3459
3460    ---------------------------------------------------
3461    -- Analyze_Aspect_Specifications_On_Body_Or_Stub --
3462    ---------------------------------------------------
3463
3464    procedure Analyze_Aspect_Specifications_On_Body_Or_Stub (N : Node_Id) is
3465       Body_Id : constant Entity_Id := Defining_Entity (N);
3466
3467       procedure Diagnose_Misplaced_Aspects (Spec_Id : Entity_Id);
3468       --  Subprogram body [stub] N has aspects, but they are not properly
3469       --  placed. Emit an error message depending on the aspects involved.
3470       --  Spec_Id is the entity of the corresponding spec.
3471
3472       --------------------------------
3473       -- Diagnose_Misplaced_Aspects --
3474       --------------------------------
3475
3476       procedure Diagnose_Misplaced_Aspects (Spec_Id : Entity_Id) is
3477          procedure Misplaced_Aspect_Error
3478            (Asp     : Node_Id;
3479             Ref_Nam : Name_Id);
3480          --  Emit an error message concerning misplaced aspect Asp. Ref_Nam is
3481          --  the name of the refined version of the aspect.
3482
3483          ----------------------------
3484          -- Misplaced_Aspect_Error --
3485          ----------------------------
3486
3487          procedure Misplaced_Aspect_Error
3488            (Asp     : Node_Id;
3489             Ref_Nam : Name_Id)
3490          is
3491             Asp_Nam : constant Name_Id   := Chars (Identifier (Asp));
3492             Asp_Id  : constant Aspect_Id := Get_Aspect_Id (Asp_Nam);
3493
3494          begin
3495             --  The corresponding spec already contains the aspect in question
3496             --  and the one appearing on the body must be the refined form:
3497
3498             --    procedure P with Global ...;
3499             --    procedure P with Global ... is ... end P;
3500             --                     ^
3501             --                     Refined_Global
3502
3503             if Has_Aspect (Spec_Id, Asp_Id) then
3504                Error_Msg_Name_1 := Asp_Nam;
3505
3506                --  Subunits cannot carry aspects that apply to a subprogram
3507                --  declaration.
3508
3509                if Nkind (Parent (N)) = N_Subunit then
3510                   Error_Msg_N ("aspect % cannot apply to a subunit", Asp);
3511
3512                --  Otherwise suggest the refined form
3513
3514                else
3515                   Error_Msg_Name_2 := Ref_Nam;
3516                   Error_Msg_N ("aspect % should be %", Asp);
3517                end if;
3518
3519             --  Otherwise the aspect must appear on the spec, not on the body
3520
3521             --    procedure P;
3522             --    procedure P with Global ... is ... end P;
3523
3524             else
3525                Error_Msg_N
3526                  ("aspect specification must appear in subprogram declaration",
3527                   Asp);
3528             end if;
3529          end Misplaced_Aspect_Error;
3530
3531          --  Local variables
3532
3533          Asp     : Node_Id;
3534          Asp_Nam : Name_Id;
3535
3536       --  Start of processing for Diagnose_Misplaced_Aspects
3537
3538       begin
3539          --  Iterate over the aspect specifications and emit specific errors
3540          --  where applicable.
3541
3542          Asp := First (Aspect_Specifications (N));
3543          while Present (Asp) loop
3544             Asp_Nam := Chars (Identifier (Asp));
3545
3546             --  Do not emit errors on aspects that can appear on a subprogram
3547             --  body. This scenario occurs when the aspect specification list
3548             --  contains both misplaced and properly placed aspects.
3549
3550             if Aspect_On_Body_Or_Stub_OK (Get_Aspect_Id (Asp_Nam)) then
3551                null;
3552
3553             --  Special diagnostics for SPARK aspects
3554
3555             elsif Asp_Nam = Name_Depends then
3556                Misplaced_Aspect_Error (Asp, Name_Refined_Depends);
3557
3558             elsif Asp_Nam = Name_Global then
3559                Misplaced_Aspect_Error (Asp, Name_Refined_Global);
3560
3561             elsif Asp_Nam = Name_Post then
3562                Misplaced_Aspect_Error (Asp, Name_Refined_Post);
3563
3564             --  Otherwise a language-defined aspect is misplaced
3565
3566             else
3567                Error_Msg_N
3568                  ("aspect specification must appear in subprogram declaration",
3569                   Asp);
3570             end if;
3571
3572             Next (Asp);
3573          end loop;
3574       end Diagnose_Misplaced_Aspects;
3575
3576       --  Local variables
3577
3578       Spec_Id : Entity_Id;
3579
3580    --  Start of processing for Analyze_Aspects_On_Body_Or_Stub
3581
3582    begin
3583       if Nkind (N) = N_Subprogram_Body_Stub then
3584          Spec_Id := Corresponding_Spec_Of_Stub (N);
3585       else
3586          Spec_Id := Corresponding_Spec (N);
3587       end if;
3588
3589       --  Language-defined aspects cannot be associated with a subprogram body
3590       --  [stub] if the subprogram has a spec. Certain implementation defined
3591       --  aspects are allowed to break this rule (for all applicable cases, see
3592       --  table Aspects.Aspect_On_Body_Or_Stub_OK).
3593
3594       if Present (Spec_Id) and then not Aspects_On_Body_Or_Stub_OK (N) then
3595          Diagnose_Misplaced_Aspects (Spec_Id);
3596       else
3597          Analyze_Aspect_Specifications (N, Body_Id);
3598       end if;
3599    end Analyze_Aspect_Specifications_On_Body_Or_Stub;
3600
3601    -----------------------
3602    -- Analyze_At_Clause --
3603    -----------------------
3604
3605    --  An at clause is replaced by the corresponding Address attribute
3606    --  definition clause that is the preferred approach in Ada 95.
3607
3608    procedure Analyze_At_Clause (N : Node_Id) is
3609       CS : constant Boolean := Comes_From_Source (N);
3610
3611    begin
3612       --  This is an obsolescent feature
3613
3614       Check_Restriction (No_Obsolescent_Features, N);
3615
3616       if Warn_On_Obsolescent_Feature then
3617          Error_Msg_N
3618            ("?j?at clause is an obsolescent feature (RM J.7(2))", N);
3619          Error_Msg_N
3620            ("\?j?use address attribute definition clause instead", N);
3621       end if;
3622
3623       --  Rewrite as address clause
3624
3625       Rewrite (N,
3626         Make_Attribute_Definition_Clause (Sloc (N),
3627           Name       => Identifier (N),
3628           Chars      => Name_Address,
3629           Expression => Expression (N)));
3630
3631       --  We preserve Comes_From_Source, since logically the clause still comes
3632       --  from the source program even though it is changed in form.
3633
3634       Set_Comes_From_Source (N, CS);
3635
3636       --  Analyze rewritten clause
3637
3638       Analyze_Attribute_Definition_Clause (N);
3639    end Analyze_At_Clause;
3640
3641    -----------------------------------------
3642    -- Analyze_Attribute_Definition_Clause --
3643    -----------------------------------------
3644
3645    procedure Analyze_Attribute_Definition_Clause (N : Node_Id) is
3646       Loc   : constant Source_Ptr   := Sloc (N);
3647       Nam   : constant Node_Id      := Name (N);
3648       Attr  : constant Name_Id      := Chars (N);
3649       Expr  : constant Node_Id      := Expression (N);
3650       Id    : constant Attribute_Id := Get_Attribute_Id (Attr);
3651
3652       Ent : Entity_Id;
3653       --  The entity of Nam after it is analyzed. In the case of an incomplete
3654       --  type, this is the underlying type.
3655
3656       U_Ent : Entity_Id;
3657       --  The underlying entity to which the attribute applies. Generally this
3658       --  is the Underlying_Type of Ent, except in the case where the clause
3659       --  applies to full view of incomplete type or private type in which case
3660       --  U_Ent is just a copy of Ent.
3661
3662       FOnly : Boolean := False;
3663       --  Reset to True for subtype specific attribute (Alignment, Size)
3664       --  and for stream attributes, i.e. those cases where in the call to
3665       --  Rep_Item_Too_Late, FOnly is set True so that only the freezing rules
3666       --  are checked. Note that the case of stream attributes is not clear
3667       --  from the RM, but see AI95-00137. Also, the RM seems to disallow
3668       --  Storage_Size for derived task types, but that is also clearly
3669       --  unintentional.
3670
3671       procedure Analyze_Stream_TSS_Definition (TSS_Nam : TSS_Name_Type);
3672       --  Common processing for 'Read, 'Write, 'Input and 'Output attribute
3673       --  definition clauses.
3674
3675       function Duplicate_Clause return Boolean;
3676       --  This routine checks if the aspect for U_Ent being given by attribute
3677       --  definition clause N is for an aspect that has already been specified,
3678       --  and if so gives an error message. If there is a duplicate, True is
3679       --  returned, otherwise if there is no error, False is returned.
3680
3681       procedure Check_Indexing_Functions;
3682       --  Check that the function in Constant_Indexing or Variable_Indexing
3683       --  attribute has the proper type structure. If the name is overloaded,
3684       --  check that some interpretation is legal.
3685
3686       procedure Check_Iterator_Functions;
3687       --  Check that there is a single function in Default_Iterator attribute
3688       --  has the proper type structure.
3689
3690       function Check_Primitive_Function (Subp : Entity_Id) return Boolean;
3691       --  Common legality check for the previous two
3692
3693       -----------------------------------
3694       -- Analyze_Stream_TSS_Definition --
3695       -----------------------------------
3696
3697       procedure Analyze_Stream_TSS_Definition (TSS_Nam : TSS_Name_Type) is
3698          Subp : Entity_Id := Empty;
3699          I    : Interp_Index;
3700          It   : Interp;
3701          Pnam : Entity_Id;
3702
3703          Is_Read : constant Boolean := (TSS_Nam = TSS_Stream_Read);
3704          --  True for Read attribute, false for other attributes
3705
3706          function Has_Good_Profile (Subp : Entity_Id) return Boolean;
3707          --  Return true if the entity is a subprogram with an appropriate
3708          --  profile for the attribute being defined.
3709
3710          ----------------------
3711          -- Has_Good_Profile --
3712          ----------------------
3713
3714          function Has_Good_Profile (Subp : Entity_Id) return Boolean is
3715             F              : Entity_Id;
3716             Is_Function    : constant Boolean := (TSS_Nam = TSS_Stream_Input);
3717             Expected_Ekind : constant array (Boolean) of Entity_Kind :=
3718                                (False => E_Procedure, True => E_Function);
3719             Typ            : Entity_Id;
3720
3721          begin
3722             if Ekind (Subp) /= Expected_Ekind (Is_Function) then
3723                return False;
3724             end if;
3725
3726             F := First_Formal (Subp);
3727
3728             if No (F)
3729               or else Ekind (Etype (F)) /= E_Anonymous_Access_Type
3730               or else Designated_Type (Etype (F)) /=
3731                                Class_Wide_Type (RTE (RE_Root_Stream_Type))
3732             then
3733                return False;
3734             end if;
3735
3736             if not Is_Function then
3737                Next_Formal (F);
3738
3739                declare
3740                   Expected_Mode : constant array (Boolean) of Entity_Kind :=
3741                                     (False => E_In_Parameter,
3742                                      True  => E_Out_Parameter);
3743                begin
3744                   if Parameter_Mode (F) /= Expected_Mode (Is_Read) then
3745                      return False;
3746                   end if;
3747                end;
3748
3749                Typ := Etype (F);
3750
3751                --  If the attribute specification comes from an aspect
3752                --  specification for a class-wide stream, the parameter must be
3753                --  a class-wide type of the entity to which the aspect applies.
3754
3755                if From_Aspect_Specification (N)
3756                  and then Class_Present (Parent (N))
3757                  and then Is_Class_Wide_Type (Typ)
3758                then
3759                   Typ := Etype (Typ);
3760                end if;
3761
3762             else
3763                Typ := Etype (Subp);
3764             end if;
3765
3766             --  Verify that the prefix of the attribute and the local name for
3767             --  the type of the formal match, or one is the class-wide of the
3768             --  other, in the case of a class-wide stream operation.
3769
3770             if  Base_Type (Typ) = Base_Type (Ent)
3771               or else (Is_Class_Wide_Type (Typ)
3772                         and then Typ = Class_Wide_Type (Base_Type (Ent)))
3773               or else (Is_Class_Wide_Type (Ent)
3774                         and then Ent = Class_Wide_Type (Base_Type (Typ)))
3775             then
3776                null;
3777             else
3778                return False;
3779             end if;
3780
3781             if Present ((Next_Formal (F)))
3782             then
3783                return False;
3784
3785             elsif not Is_Scalar_Type (Typ)
3786               and then not Is_First_Subtype (Typ)
3787               and then not Is_Class_Wide_Type (Typ)
3788             then
3789                return False;
3790
3791             else
3792                return True;
3793             end if;
3794          end Has_Good_Profile;
3795
3796       --  Start of processing for Analyze_Stream_TSS_Definition
3797
3798       begin
3799          FOnly := True;
3800
3801          if not Is_Type (U_Ent) then
3802             Error_Msg_N ("local name must be a subtype", Nam);
3803             return;
3804
3805          elsif not Is_First_Subtype (U_Ent) then
3806             Error_Msg_N ("local name must be a first subtype", Nam);
3807             return;
3808          end if;
3809
3810          Pnam := TSS (Base_Type (U_Ent), TSS_Nam);
3811
3812          --  If Pnam is present, it can be either inherited from an ancestor
3813          --  type (in which case it is legal to redefine it for this type), or
3814          --  be a previous definition of the attribute for the same type (in
3815          --  which case it is illegal).
3816
3817          --  In the first case, it will have been analyzed already, and we
3818          --  can check that its profile does not match the expected profile
3819          --  for a stream attribute of U_Ent. In the second case, either Pnam
3820          --  has been analyzed (and has the expected profile), or it has not
3821          --  been analyzed yet (case of a type that has not been frozen yet
3822          --  and for which the stream attribute has been set using Set_TSS).
3823
3824          if Present (Pnam)
3825            and then (No (First_Entity (Pnam)) or else Has_Good_Profile (Pnam))
3826          then
3827             Error_Msg_Sloc := Sloc (Pnam);
3828             Error_Msg_Name_1 := Attr;
3829             Error_Msg_N ("% attribute already defined #", Nam);
3830             return;
3831          end if;
3832
3833          Analyze (Expr);
3834
3835          if Is_Entity_Name (Expr) then
3836             if not Is_Overloaded (Expr) then
3837                if Has_Good_Profile (Entity (Expr)) then
3838                   Subp := Entity (Expr);
3839                end if;
3840
3841             else
3842                Get_First_Interp (Expr, I, It);
3843                while Present (It.Nam) loop
3844                   if Has_Good_Profile (It.Nam) then
3845                      Subp := It.Nam;
3846                      exit;
3847                   end if;
3848
3849                   Get_Next_Interp (I, It);
3850                end loop;
3851             end if;
3852          end if;
3853
3854          if Present (Subp) then
3855             if Is_Abstract_Subprogram (Subp) then
3856                Error_Msg_N ("stream subprogram must not be abstract", Expr);
3857                return;
3858
3859             --  A stream subprogram for an interface type must be a null
3860             --  procedure (RM 13.13.2 (38/3)).
3861
3862             elsif Is_Interface (U_Ent)
3863               and then not Is_Class_Wide_Type (U_Ent)
3864               and then not Inside_A_Generic
3865               and then
3866                 (Ekind (Subp) = E_Function
3867                   or else
3868                     not Null_Present
3869                           (Specification
3870                              (Unit_Declaration_Node (Ultimate_Alias (Subp)))))
3871             then
3872                Error_Msg_N
3873                  ("stream subprogram for interface type "
3874                   & "must be null procedure", Expr);
3875             end if;
3876
3877             Set_Entity (Expr, Subp);
3878             Set_Etype (Expr, Etype (Subp));
3879
3880             New_Stream_Subprogram (N, U_Ent, Subp, TSS_Nam);
3881
3882          else
3883             Error_Msg_Name_1 := Attr;
3884             Error_Msg_N ("incorrect expression for% attribute", Expr);
3885          end if;
3886       end Analyze_Stream_TSS_Definition;
3887
3888       ------------------------------
3889       -- Check_Indexing_Functions --
3890       ------------------------------
3891
3892       procedure Check_Indexing_Functions is
3893          Indexing_Found : Boolean := False;
3894
3895          procedure Check_One_Function (Subp : Entity_Id);
3896          --  Check one possible interpretation. Sets Indexing_Found True if a
3897          --  legal indexing function is found.
3898
3899          procedure Illegal_Indexing (Msg : String);
3900          --  Diagnose illegal indexing function if not overloaded. In the
3901          --  overloaded case indicate that no legal interpretation  exists.
3902
3903          ------------------------
3904          -- Check_One_Function --
3905          ------------------------
3906
3907          procedure Check_One_Function (Subp : Entity_Id) is
3908             Default_Element : Node_Id;
3909             Ret_Type        : constant Entity_Id := Etype (Subp);
3910
3911          begin
3912             if not Is_Overloadable (Subp) then
3913                Illegal_Indexing ("illegal indexing function for type&");
3914                return;
3915
3916             elsif Scope (Subp) /= Scope (Ent) then
3917                if Nkind (Expr) = N_Expanded_Name then
3918
3919                   --  Indexing function can't be declared elsewhere
3920
3921                   Illegal_Indexing
3922                     ("indexing function must be declared in scope of type&");
3923                end if;
3924
3925                return;
3926
3927             elsif No (First_Formal (Subp)) then
3928                Illegal_Indexing
3929                  ("Indexing requires a function that applies to type&");
3930                return;
3931
3932             elsif No (Next_Formal (First_Formal (Subp))) then
3933                Illegal_Indexing
3934                  ("indexing function must have at least two parameters");
3935                return;
3936
3937             --  For a derived type, check that no indexing aspect is specified
3938             --  for the type if it is also inherited
3939
3940             elsif Is_Derived_Type (Ent) then
3941                declare
3942                   Inherited : Node_Id;
3943
3944                begin
3945                   if Attr = Name_Constant_Indexing then
3946                      Inherited :=
3947                        Find_Aspect (Etype (Ent), Aspect_Constant_Indexing);
3948                   else pragma Assert (Attr = Name_Variable_Indexing);
3949                      Inherited :=
3950                         Find_Aspect (Etype (Ent), Aspect_Variable_Indexing);
3951                   end if;
3952
3953                   if Present (Inherited) then
3954                      if Debug_Flag_Dot_XX then
3955                         null;
3956
3957                      --  Indicate the operation that must be overridden, rather
3958                      --  than redefining the indexing aspect
3959
3960                      else
3961                         Illegal_Indexing
3962                           ("indexing function already inherited "
3963                            & "from parent type");
3964                         Error_Msg_NE
3965                           ("!override & instead",
3966                            N, Entity (Expression (Inherited)));
3967                         return;
3968                      end if;
3969                   end if;
3970                end;
3971             end if;
3972
3973             if not Check_Primitive_Function (Subp) then
3974                Illegal_Indexing
3975                  ("Indexing aspect requires a function that applies to type&");
3976                return;
3977             end if;
3978
3979             --  If partial declaration exists, verify that it is not tagged.
3980
3981             if Ekind (Current_Scope) = E_Package
3982               and then Has_Private_Declaration (Ent)
3983               and then From_Aspect_Specification (N)
3984               and then
3985                 List_Containing (Parent (Ent)) =
3986                   Private_Declarations
3987                     (Specification (Unit_Declaration_Node (Current_Scope)))
3988               and then Nkind (N) = N_Attribute_Definition_Clause
3989             then
3990                declare
3991                   Decl : Node_Id;
3992
3993                begin
3994                   Decl :=
3995                      First (Visible_Declarations
3996                               (Specification
3997                                  (Unit_Declaration_Node (Current_Scope))));
3998
3999                   while Present (Decl) loop
4000                      if Nkind (Decl) = N_Private_Type_Declaration
4001                        and then Ent = Full_View (Defining_Identifier (Decl))
4002                        and then Tagged_Present (Decl)
4003                        and then No (Aspect_Specifications (Decl))
4004                      then
4005                         Illegal_Indexing
4006                           ("Indexing aspect cannot be specified on full view "
4007                            & "if partial view is tagged");
4008                         return;
4009                      end if;
4010
4011                      Next (Decl);
4012                   end loop;
4013                end;
4014             end if;
4015
4016             --  An indexing function must return either the default element of
4017             --  the container, or a reference type. For variable indexing it
4018             --  must be the latter.
4019
4020             Default_Element :=
4021               Find_Value_Of_Aspect
4022                (Etype (First_Formal (Subp)), Aspect_Iterator_Element);
4023
4024             if Present (Default_Element) then
4025                Analyze (Default_Element);
4026
4027                if Is_Entity_Name (Default_Element)
4028                  and then not Covers (Entity (Default_Element), Ret_Type)
4029                  and then False
4030                then
4031                   Illegal_Indexing
4032                     ("wrong return type for indexing function");
4033                   return;
4034                end if;
4035             end if;
4036
4037             --  For variable_indexing the return type must be a reference type
4038
4039             if Attr = Name_Variable_Indexing then
4040                if not Has_Implicit_Dereference (Ret_Type) then
4041                   Illegal_Indexing
4042                      ("variable indexing must return a reference type");
4043                   return;
4044
4045                elsif Is_Access_Constant
4046                        (Etype (First_Discriminant (Ret_Type)))
4047                then
4048                   Illegal_Indexing
4049                     ("variable indexing must return an access to variable");
4050                   return;
4051                end if;
4052
4053             else
4054                if  Has_Implicit_Dereference (Ret_Type)
4055                  and then not
4056                    Is_Access_Constant (Etype (First_Discriminant (Ret_Type)))
4057                then
4058                   Illegal_Indexing
4059                     ("constant indexing must return an access to constant");
4060                   return;
4061
4062                elsif Is_Access_Type (Etype (First_Formal (Subp)))
4063                  and then not Is_Access_Constant (Etype (First_Formal (Subp)))
4064                then
4065                   Illegal_Indexing
4066                     ("constant indexing must apply to an access to constant");
4067                   return;
4068                end if;
4069             end if;
4070
4071             --  All checks succeeded.
4072
4073             Indexing_Found := True;
4074          end Check_One_Function;
4075
4076          -----------------------
4077          --  Illegal_Indexing --
4078          -----------------------
4079
4080          procedure Illegal_Indexing (Msg : String) is
4081          begin
4082             Error_Msg_NE (Msg, N, Ent);
4083          end Illegal_Indexing;
4084
4085       --  Start of processing for Check_Indexing_Functions
4086
4087       begin
4088          if In_Instance then
4089             return;
4090          end if;
4091
4092          Analyze (Expr);
4093
4094          if not Is_Overloaded (Expr) then
4095             Check_One_Function (Entity (Expr));
4096
4097          else
4098             declare
4099                I  : Interp_Index;
4100                It : Interp;
4101
4102             begin
4103                Indexing_Found := False;
4104                Get_First_Interp (Expr, I, It);
4105                while Present (It.Nam) loop
4106
4107                   --  Note that analysis will have added the interpretation
4108                   --  that corresponds to the dereference. We only check the
4109                   --  subprogram itself.
4110
4111                   if Is_Overloadable (It.Nam) then
4112                      Check_One_Function (It.Nam);
4113                   end if;
4114
4115                   Get_Next_Interp (I, It);
4116                end loop;
4117             end;
4118          end if;
4119
4120          if not Indexing_Found and then not Error_Posted (N) then
4121             Error_Msg_NE
4122               ("aspect Indexing requires a local function that "
4123                & "applies to type&", Expr, Ent);
4124          end if;
4125       end Check_Indexing_Functions;
4126
4127       ------------------------------
4128       -- Check_Iterator_Functions --
4129       ------------------------------
4130
4131       procedure Check_Iterator_Functions is
4132          Default : Entity_Id;
4133
4134          function Valid_Default_Iterator (Subp : Entity_Id) return Boolean;
4135          --  Check one possible interpretation for validity
4136
4137          ----------------------------
4138          -- Valid_Default_Iterator --
4139          ----------------------------
4140
4141          function Valid_Default_Iterator (Subp : Entity_Id) return Boolean is
4142             Formal : Entity_Id;
4143
4144          begin
4145             if not Check_Primitive_Function (Subp) then
4146                return False;
4147             else
4148                Formal := First_Formal (Subp);
4149             end if;
4150
4151             --  False if any subsequent formal has no default expression
4152
4153             Formal := Next_Formal (Formal);
4154             while Present (Formal) loop
4155                if No (Expression (Parent (Formal))) then
4156                   return False;
4157                end if;
4158
4159                Next_Formal (Formal);
4160             end loop;
4161
4162             --  True if all subsequent formals have default expressions
4163
4164             return True;
4165          end Valid_Default_Iterator;
4166
4167       --  Start of processing for Check_Iterator_Functions
4168
4169       begin
4170          Analyze (Expr);
4171
4172          if not Is_Entity_Name (Expr) then
4173             Error_Msg_N ("aspect Iterator must be a function name", Expr);
4174          end if;
4175
4176          if not Is_Overloaded (Expr) then
4177             if not Check_Primitive_Function (Entity (Expr)) then
4178                Error_Msg_NE
4179                  ("aspect Indexing requires a function that applies to type&",
4180                    Entity (Expr), Ent);
4181             end if;
4182
4183             --  Flag the default_iterator as well as the denoted function.
4184
4185             if not Valid_Default_Iterator (Entity (Expr)) then
4186                Error_Msg_N ("improper function for default iterator!", Expr);
4187             end if;
4188
4189          else
4190             Default := Empty;
4191             declare
4192                I : Interp_Index;
4193                It : Interp;
4194
4195             begin
4196                Get_First_Interp (Expr, I, It);
4197                while Present (It.Nam) loop
4198                   if not Check_Primitive_Function (It.Nam)
4199                     or else not Valid_Default_Iterator (It.Nam)
4200                   then
4201                      Remove_Interp (I);
4202
4203                   elsif Present (Default) then
4204                      Error_Msg_N ("default iterator must be unique", Expr);
4205
4206                   else
4207                      Default := It.Nam;
4208                   end if;
4209
4210                   Get_Next_Interp (I, It);
4211                end loop;
4212             end;
4213
4214             if Present (Default) then
4215                Set_Entity (Expr, Default);
4216                Set_Is_Overloaded (Expr, False);
4217             end if;
4218          end if;
4219       end Check_Iterator_Functions;
4220
4221       -------------------------------
4222       -- Check_Primitive_Function  --
4223       -------------------------------
4224
4225       function Check_Primitive_Function (Subp : Entity_Id) return Boolean is
4226          Ctrl : Entity_Id;
4227
4228       begin
4229          if Ekind (Subp) /= E_Function then
4230             return False;
4231          end if;
4232
4233          if No (First_Formal (Subp)) then
4234             return False;
4235          else
4236             Ctrl := Etype (First_Formal (Subp));
4237          end if;
4238
4239          --  To be a primitive operation subprogram has to be in same scope.
4240
4241          if Scope (Ctrl) /= Scope (Subp) then
4242             return False;
4243          end if;
4244
4245          --  Type of formal may be the class-wide type, an access to such,
4246          --  or an incomplete view.
4247
4248          if Ctrl = Ent
4249            or else Ctrl = Class_Wide_Type (Ent)
4250            or else
4251              (Ekind (Ctrl) = E_Anonymous_Access_Type
4252                and then (Designated_Type (Ctrl) = Ent
4253                            or else
4254                          Designated_Type (Ctrl) = Class_Wide_Type (Ent)))
4255            or else
4256              (Ekind (Ctrl) = E_Incomplete_Type
4257                and then Full_View (Ctrl) = Ent)
4258          then
4259             null;
4260          else
4261             return False;
4262          end if;
4263
4264          return True;
4265       end Check_Primitive_Function;
4266
4267       ----------------------
4268       -- Duplicate_Clause --
4269       ----------------------
4270
4271       function Duplicate_Clause return Boolean is
4272          A : Node_Id;
4273
4274       begin
4275          --  Nothing to do if this attribute definition clause comes from
4276          --  an aspect specification, since we could not be duplicating an
4277          --  explicit clause, and we dealt with the case of duplicated aspects
4278          --  in Analyze_Aspect_Specifications.
4279
4280          if From_Aspect_Specification (N) then
4281             return False;
4282          end if;
4283
4284          --  Otherwise current clause may duplicate previous clause, or a
4285          --  previously given pragma or aspect specification for the same
4286          --  aspect.
4287
4288          A := Get_Rep_Item (U_Ent, Chars (N), Check_Parents => False);
4289
4290          if Present (A) then
4291             Error_Msg_Name_1 := Chars (N);
4292             Error_Msg_Sloc := Sloc (A);
4293
4294             Error_Msg_NE ("aspect% for & previously given#", N, U_Ent);
4295             return True;
4296          end if;
4297
4298          return False;
4299       end Duplicate_Clause;
4300
4301    --  Start of processing for Analyze_Attribute_Definition_Clause
4302
4303    begin
4304       --  The following code is a defense against recursion. Not clear that
4305       --  this can happen legitimately, but perhaps some error situations can
4306       --  cause it, and we did see this recursion during testing.
4307
4308       if Analyzed (N) then
4309          return;
4310       else
4311          Set_Analyzed (N, True);
4312       end if;
4313
4314       --  Ignore some selected attributes in CodePeer mode since they are not
4315       --  relevant in this context.
4316
4317       if CodePeer_Mode then
4318          case Id is
4319
4320             --  Ignore Component_Size in CodePeer mode, to avoid changing the
4321             --  internal representation of types by implicitly packing them.
4322
4323             when Attribute_Component_Size =>
4324                Rewrite (N, Make_Null_Statement (Sloc (N)));
4325                return;
4326
4327             when others =>
4328                null;
4329          end case;
4330       end if;
4331
4332       --  Process Ignore_Rep_Clauses option
4333
4334       if Ignore_Rep_Clauses then
4335          case Id is
4336
4337             --  The following should be ignored. They do not affect legality
4338             --  and may be target dependent. The basic idea of -gnatI is to
4339             --  ignore any rep clauses that may be target dependent but do not
4340             --  affect legality (except possibly to be rejected because they
4341             --  are incompatible with the compilation target).
4342
4343             when Attribute_Alignment      |
4344                  Attribute_Bit_Order      |
4345                  Attribute_Component_Size |
4346                  Attribute_Machine_Radix  |
4347                  Attribute_Object_Size    |
4348                  Attribute_Size           |
4349                  Attribute_Small          |
4350                  Attribute_Stream_Size    |
4351                  Attribute_Value_Size     =>
4352                Kill_Rep_Clause (N);
4353                return;
4354
4355             --  The following should not be ignored, because in the first place
4356             --  they are reasonably portable, and should not cause problems
4357             --  in compiling code from another target, and also they do affect
4358             --  legality, e.g. failing to provide a stream attribute for a type
4359             --  may make a program illegal.
4360
4361             when Attribute_External_Tag        |
4362                  Attribute_Input               |
4363                  Attribute_Output              |
4364                  Attribute_Read                |
4365                  Attribute_Simple_Storage_Pool |
4366                  Attribute_Storage_Pool        |
4367                  Attribute_Storage_Size        |
4368                  Attribute_Write               =>
4369                null;
4370
4371             --  We do not do anything here with address clauses, they will be
4372             --  removed by Freeze later on, but for now, it works better to
4373             --  keep then in the tree.
4374
4375             when Attribute_Address =>
4376                null;
4377
4378             --  Other cases are errors ("attribute& cannot be set with
4379             --  definition clause"), which will be caught below.
4380
4381             when others =>
4382                null;
4383          end case;
4384       end if;
4385
4386       Analyze (Nam);
4387       Ent := Entity (Nam);
4388
4389       if Rep_Item_Too_Early (Ent, N) then
4390          return;
4391       end if;
4392
4393       --  Rep clause applies to full view of incomplete type or private type if
4394       --  we have one (if not, this is a premature use of the type). However,
4395       --  certain semantic checks need to be done on the specified entity (i.e.
4396       --  the private view), so we save it in Ent.
4397
4398       if Is_Private_Type (Ent)
4399         and then Is_Derived_Type (Ent)
4400         and then not Is_Tagged_Type (Ent)
4401         and then No (Full_View (Ent))
4402       then
4403          --  If this is a private type whose completion is a derivation from
4404          --  another private type, there is no full view, and the attribute
4405          --  belongs to the type itself, not its underlying parent.
4406
4407          U_Ent := Ent;
4408
4409       elsif Ekind (Ent) = E_Incomplete_Type then
4410
4411          --  The attribute applies to the full view, set the entity of the
4412          --  attribute definition accordingly.
4413
4414          Ent := Underlying_Type (Ent);
4415          U_Ent := Ent;
4416          Set_Entity (Nam, Ent);
4417
4418       else
4419          U_Ent := Underlying_Type (Ent);
4420       end if;
4421
4422       --  Avoid cascaded error
4423
4424       if Etype (Nam) = Any_Type then
4425          return;
4426
4427       --  Must be declared in current scope or in case of an aspect
4428       --  specification, must be visible in current scope.
4429
4430       elsif Scope (Ent) /= Current_Scope
4431         and then
4432           not (From_Aspect_Specification (N)
4433                 and then Scope_Within_Or_Same (Current_Scope, Scope (Ent)))
4434       then
4435          Error_Msg_N ("entity must be declared in this scope", Nam);
4436          return;
4437
4438       --  Must not be a source renaming (we do have some cases where the
4439       --  expander generates a renaming, and those cases are OK, in such
4440       --  cases any attribute applies to the renamed object as well).
4441
4442       elsif Is_Object (Ent)
4443         and then Present (Renamed_Object (Ent))
4444       then
4445          --  Case of renamed object from source, this is an error
4446
4447          if Comes_From_Source (Renamed_Object (Ent)) then
4448             Get_Name_String (Chars (N));
4449             Error_Msg_Strlen := Name_Len;
4450             Error_Msg_String (1 .. Name_Len) := Name_Buffer (1 .. Name_Len);
4451             Error_Msg_N
4452               ("~ clause not allowed for a renaming declaration "
4453                & "(RM 13.1(6))", Nam);
4454             return;
4455
4456          --  For the case of a compiler generated renaming, the attribute
4457          --  definition clause applies to the renamed object created by the
4458          --  expander. The easiest general way to handle this is to create a
4459          --  copy of the attribute definition clause for this object.
4460
4461          elsif Is_Entity_Name (Renamed_Object (Ent)) then
4462             Insert_Action (N,
4463               Make_Attribute_Definition_Clause (Loc,
4464                 Name       =>
4465                   New_Occurrence_Of (Entity (Renamed_Object (Ent)), Loc),
4466                 Chars      => Chars (N),
4467                 Expression => Duplicate_Subexpr (Expression (N))));
4468
4469          --  If the renamed object is not an entity, it must be a dereference
4470          --  of an unconstrained function call, and we must introduce a new
4471          --  declaration to capture the expression. This is needed in the case
4472          --  of 'Alignment, where the original declaration must be rewritten.
4473
4474          else
4475             pragma Assert
4476               (Nkind (Renamed_Object (Ent)) = N_Explicit_Dereference);
4477             null;
4478          end if;
4479
4480       --  If no underlying entity, use entity itself, applies to some
4481       --  previously detected error cases ???
4482
4483       elsif No (U_Ent) then
4484          U_Ent := Ent;
4485
4486       --  Cannot specify for a subtype (exception Object/Value_Size)
4487
4488       elsif Is_Type (U_Ent)
4489         and then not Is_First_Subtype (U_Ent)
4490         and then Id /= Attribute_Object_Size
4491         and then Id /= Attribute_Value_Size
4492         and then not From_At_Mod (N)
4493       then
4494          Error_Msg_N ("cannot specify attribute for subtype", Nam);
4495          return;
4496       end if;
4497
4498       Set_Entity (N, U_Ent);
4499       Check_Restriction_No_Use_Of_Attribute (N);
4500
4501       --  Switch on particular attribute
4502
4503       case Id is
4504
4505          -------------
4506          -- Address --
4507          -------------
4508
4509          --  Address attribute definition clause
4510
4511          when Attribute_Address => Address : begin
4512
4513             --  A little error check, catch for X'Address use X'Address;
4514
4515             if Nkind (Nam) = N_Identifier
4516               and then Nkind (Expr) = N_Attribute_Reference
4517               and then Attribute_Name (Expr) = Name_Address
4518               and then Nkind (Prefix (Expr)) = N_Identifier
4519               and then Chars (Nam) = Chars (Prefix (Expr))
4520             then
4521                Error_Msg_NE
4522                  ("address for & is self-referencing", Prefix (Expr), Ent);
4523                return;
4524             end if;
4525
4526             --  Not that special case, carry on with analysis of expression
4527
4528             Analyze_And_Resolve (Expr, RTE (RE_Address));
4529
4530             --  Even when ignoring rep clauses we need to indicate that the
4531             --  entity has an address clause and thus it is legal to declare
4532             --  it imported. Freeze will get rid of the address clause later.
4533
4534             if Ignore_Rep_Clauses then
4535                if Ekind_In (U_Ent, E_Variable, E_Constant) then
4536                   Record_Rep_Item (U_Ent, N);
4537                end if;
4538
4539                return;
4540             end if;
4541
4542             if Duplicate_Clause then
4543                null;
4544
4545             --  Case of address clause for subprogram
4546
4547             elsif Is_Subprogram (U_Ent) then
4548                if Has_Homonym (U_Ent) then
4549                   Error_Msg_N
4550                     ("address clause cannot be given " &
4551                      "for overloaded subprogram",
4552                      Nam);
4553                   return;
4554                end if;
4555
4556                --  For subprograms, all address clauses are permitted, and we
4557                --  mark the subprogram as having a deferred freeze so that Gigi
4558                --  will not elaborate it too soon.
4559
4560                --  Above needs more comments, what is too soon about???
4561
4562                Set_Has_Delayed_Freeze (U_Ent);
4563
4564             --  Case of address clause for entry
4565
4566             elsif Ekind (U_Ent) = E_Entry then
4567                if Nkind (Parent (N)) = N_Task_Body then
4568                   Error_Msg_N
4569                     ("entry address must be specified in task spec", Nam);
4570                   return;
4571                end if;
4572
4573                --  For entries, we require a constant address
4574
4575                Check_Constant_Address_Clause (Expr, U_Ent);
4576
4577                --  Special checks for task types
4578
4579                if Is_Task_Type (Scope (U_Ent))
4580                  and then Comes_From_Source (Scope (U_Ent))
4581                then
4582                   Error_Msg_N
4583                     ("??entry address declared for entry in task type", N);
4584                   Error_Msg_N
4585                     ("\??only one task can be declared of this type", N);
4586                end if;
4587
4588                --  Entry address clauses are obsolescent
4589
4590                Check_Restriction (No_Obsolescent_Features, N);
4591
4592                if Warn_On_Obsolescent_Feature then
4593                   Error_Msg_N
4594                     ("?j?attaching interrupt to task entry is an " &
4595                      "obsolescent feature (RM J.7.1)", N);
4596                   Error_Msg_N
4597                     ("\?j?use interrupt procedure instead", N);
4598                end if;
4599
4600             --  Case of an address clause for a controlled object which we
4601             --  consider to be erroneous.
4602
4603             elsif Is_Controlled (Etype (U_Ent))
4604               or else Has_Controlled_Component (Etype (U_Ent))
4605             then
4606                Error_Msg_NE
4607                  ("??controlled object& must not be overlaid", Nam, U_Ent);
4608                Error_Msg_N
4609                  ("\??Program_Error will be raised at run time", Nam);
4610                Insert_Action (Declaration_Node (U_Ent),
4611                  Make_Raise_Program_Error (Loc,
4612                    Reason => PE_Overlaid_Controlled_Object));
4613                return;
4614
4615             --  Case of address clause for a (non-controlled) object
4616
4617             elsif Ekind_In (U_Ent, E_Variable, E_Constant) then
4618                declare
4619                   Expr  : constant Node_Id := Expression (N);
4620                   O_Ent : Entity_Id;
4621                   Off   : Boolean;
4622
4623                begin
4624                   --  Exported variables cannot have an address clause, because
4625                   --  this cancels the effect of the pragma Export.
4626
4627                   if Is_Exported (U_Ent) then
4628                      Error_Msg_N
4629                        ("cannot export object with address clause", Nam);
4630                      return;
4631                   end if;
4632
4633                   Find_Overlaid_Entity (N, O_Ent, Off);
4634
4635                   --  Overlaying controlled objects is erroneous
4636
4637                   if Present (O_Ent)
4638                     and then (Has_Controlled_Component (Etype (O_Ent))
4639                                or else Is_Controlled (Etype (O_Ent)))
4640                   then
4641                      Error_Msg_N
4642                        ("??cannot overlay with controlled object", Expr);
4643                      Error_Msg_N
4644                        ("\??Program_Error will be raised at run time", Expr);
4645                      Insert_Action (Declaration_Node (U_Ent),
4646                        Make_Raise_Program_Error (Loc,
4647                          Reason => PE_Overlaid_Controlled_Object));
4648                      return;
4649
4650                   elsif Present (O_Ent)
4651                     and then Ekind (U_Ent) = E_Constant
4652                     and then not Is_Constant_Object (O_Ent)
4653                   then
4654                      Error_Msg_N ("??constant overlays a variable", Expr);
4655
4656                   --  Imported variables can have an address clause, but then
4657                   --  the import is pretty meaningless except to suppress
4658                   --  initializations, so we do not need such variables to
4659                   --  be statically allocated (and in fact it causes trouble
4660                   --  if the address clause is a local value).
4661
4662                   elsif Is_Imported (U_Ent) then
4663                      Set_Is_Statically_Allocated (U_Ent, False);
4664                   end if;
4665
4666                   --  We mark a possible modification of a variable with an
4667                   --  address clause, since it is likely aliasing is occurring.
4668
4669                   Note_Possible_Modification (Nam, Sure => False);
4670
4671                   --  Here we are checking for explicit overlap of one variable
4672                   --  by another, and if we find this then mark the overlapped
4673                   --  variable as also being volatile to prevent unwanted
4674                   --  optimizations. This is a significant pessimization so
4675                   --  avoid it when there is an offset, i.e. when the object
4676                   --  is composite; they cannot be optimized easily anyway.
4677
4678                   if Present (O_Ent)
4679                     and then Is_Object (O_Ent)
4680                     and then not Off
4681
4682                     --  The following test is an expedient solution to what
4683                     --  is really a problem in CodePeer. Suppressing the
4684                     --  Set_Treat_As_Volatile call here prevents later
4685                     --  generation (in some cases) of trees that CodePeer
4686                     --  should, but currently does not, handle correctly.
4687                     --  This test should probably be removed when CodePeer
4688                     --  is improved, just because we want the tree CodePeer
4689                     --  analyzes to match the tree for which we generate code
4690                     --  as closely as is practical. ???
4691
4692                     and then not CodePeer_Mode
4693                   then
4694                      --  ??? O_Ent might not be in current unit
4695
4696                      Set_Treat_As_Volatile (O_Ent);
4697                   end if;
4698
4699                   --  Legality checks on the address clause for initialized
4700                   --  objects is deferred until the freeze point, because
4701                   --  a subsequent pragma might indicate that the object
4702                   --  is imported and thus not initialized. Also, the address
4703                   --  clause might involve entities that have yet to be
4704                   --  elaborated.
4705
4706                   Set_Has_Delayed_Freeze (U_Ent);
4707
4708                   --  If an initialization call has been generated for this
4709                   --  object, it needs to be deferred to after the freeze node
4710                   --  we have just now added, otherwise GIGI will see a
4711                   --  reference to the variable (as actual to the IP call)
4712                   --  before its definition.
4713
4714                   declare
4715                      Init_Call : constant Node_Id :=
4716                                    Remove_Init_Call (U_Ent, N);
4717
4718                   begin
4719                      if Present (Init_Call) then
4720                         Append_Freeze_Action (U_Ent, Init_Call);
4721
4722                         --  Reset Initialization_Statements pointer so that
4723                         --  if there is a pragma Import further down, it can
4724                         --  clear any default initialization.
4725
4726                         Set_Initialization_Statements (U_Ent, Init_Call);
4727                      end if;
4728                   end;
4729
4730                   if Is_Exported (U_Ent) then
4731                      Error_Msg_N
4732                        ("& cannot be exported if an address clause is given",
4733                         Nam);
4734                      Error_Msg_N
4735                        ("\define and export a variable "
4736                         & "that holds its address instead", Nam);
4737                   end if;
4738
4739                   --  Entity has delayed freeze, so we will generate an
4740                   --  alignment check at the freeze point unless suppressed.
4741
4742                   if not Range_Checks_Suppressed (U_Ent)
4743                     and then not Alignment_Checks_Suppressed (U_Ent)
4744                   then
4745                      Set_Check_Address_Alignment (N);
4746                   end if;
4747
4748                   --  Kill the size check code, since we are not allocating
4749                   --  the variable, it is somewhere else.
4750
4751                   Kill_Size_Check_Code (U_Ent);
4752
4753                   --  If the address clause is of the form:
4754
4755                   --    for Y'Address use X'Address
4756
4757                   --  or
4758
4759                   --    Const : constant Address := X'Address;
4760                   --    ...
4761                   --    for Y'Address use Const;
4762
4763                   --  then we make an entry in the table for checking the size
4764                   --  and alignment of the overlaying variable. We defer this
4765                   --  check till after code generation to take full advantage
4766                   --  of the annotation done by the back end.
4767
4768                   --  If the entity has a generic type, the check will be
4769                   --  performed in the instance if the actual type justifies
4770                   --  it, and we do not insert the clause in the table to
4771                   --  prevent spurious warnings.
4772
4773                   --  Note: we used to test Comes_From_Source and only give
4774                   --  this warning for source entities, but we have removed
4775                   --  this test. It really seems bogus to generate overlays
4776                   --  that would trigger this warning in generated code.
4777                   --  Furthermore, by removing the test, we handle the
4778                   --  aspect case properly.
4779
4780                   if Address_Clause_Overlay_Warnings
4781                     and then Present (O_Ent)
4782                     and then Is_Object (O_Ent)
4783                   then
4784                      if not Is_Generic_Type (Etype (U_Ent)) then
4785                         Address_Clause_Checks.Append ((N, U_Ent, O_Ent, Off));
4786                      end if;
4787
4788                      --  If variable overlays a constant view, and we are
4789                      --  warning on overlays, then mark the variable as
4790                      --  overlaying a constant (we will give warnings later
4791                      --  if this variable is assigned).
4792
4793                      if Is_Constant_Object (O_Ent)
4794                        and then Ekind (U_Ent) = E_Variable
4795                      then
4796                         Set_Overlays_Constant (U_Ent);
4797                      end if;
4798                   end if;
4799                end;
4800
4801             --  Not a valid entity for an address clause
4802
4803             else
4804                Error_Msg_N ("address cannot be given for &", Nam);
4805             end if;
4806          end Address;
4807
4808          ---------------
4809          -- Alignment --
4810          ---------------
4811
4812          --  Alignment attribute definition clause
4813
4814          when Attribute_Alignment => Alignment : declare
4815             Align     : constant Uint := Get_Alignment_Value (Expr);
4816             Max_Align : constant Uint := UI_From_Int (Maximum_Alignment);
4817
4818          begin
4819             FOnly := True;
4820
4821             if not Is_Type (U_Ent)
4822               and then Ekind (U_Ent) /= E_Variable
4823               and then Ekind (U_Ent) /= E_Constant
4824             then
4825                Error_Msg_N ("alignment cannot be given for &", Nam);
4826
4827             elsif Duplicate_Clause then
4828                null;
4829
4830             elsif Align /= No_Uint then
4831                Set_Has_Alignment_Clause (U_Ent);
4832
4833                --  Tagged type case, check for attempt to set alignment to a
4834                --  value greater than Max_Align, and reset if so.
4835
4836                if Is_Tagged_Type (U_Ent) and then Align > Max_Align then
4837                   Error_Msg_N
4838                     ("alignment for & set to Maximum_Aligment??", Nam);
4839                      Set_Alignment (U_Ent, Max_Align);
4840
4841                --  All other cases
4842
4843                else
4844                   Set_Alignment (U_Ent, Align);
4845                end if;
4846
4847                --  For an array type, U_Ent is the first subtype. In that case,
4848                --  also set the alignment of the anonymous base type so that
4849                --  other subtypes (such as the itypes for aggregates of the
4850                --  type) also receive the expected alignment.
4851
4852                if Is_Array_Type (U_Ent) then
4853                   Set_Alignment (Base_Type (U_Ent), Align);
4854                end if;
4855             end if;
4856          end Alignment;
4857
4858          ---------------
4859          -- Bit_Order --
4860          ---------------
4861
4862          --  Bit_Order attribute definition clause
4863
4864          when Attribute_Bit_Order => Bit_Order : declare
4865          begin
4866             if not Is_Record_Type (U_Ent) then
4867                Error_Msg_N
4868                  ("Bit_Order can only be defined for record type", Nam);
4869
4870             elsif Duplicate_Clause then
4871                null;
4872
4873             else
4874                Analyze_And_Resolve (Expr, RTE (RE_Bit_Order));
4875
4876                if Etype (Expr) = Any_Type then
4877                   return;
4878
4879                elsif not Is_OK_Static_Expression (Expr) then
4880                   Flag_Non_Static_Expr
4881                     ("Bit_Order requires static expression!", Expr);
4882
4883                else
4884                   if (Expr_Value (Expr) = 0) /= Bytes_Big_Endian then
4885                      Set_Reverse_Bit_Order (Base_Type (U_Ent), True);
4886                   end if;
4887                end if;
4888             end if;
4889          end Bit_Order;
4890
4891          --------------------
4892          -- Component_Size --
4893          --------------------
4894
4895          --  Component_Size attribute definition clause
4896
4897          when Attribute_Component_Size => Component_Size_Case : declare
4898             Csize    : constant Uint := Static_Integer (Expr);
4899             Ctyp     : Entity_Id;
4900             Btype    : Entity_Id;
4901             Biased   : Boolean;
4902             New_Ctyp : Entity_Id;
4903             Decl     : Node_Id;
4904
4905          begin
4906             if not Is_Array_Type (U_Ent) then
4907                Error_Msg_N ("component size requires array type", Nam);
4908                return;
4909             end if;
4910
4911             Btype := Base_Type (U_Ent);
4912             Ctyp := Component_Type (Btype);
4913
4914             if Duplicate_Clause then
4915                null;
4916
4917             elsif Rep_Item_Too_Early (Btype, N) then
4918                null;
4919
4920             elsif Csize /= No_Uint then
4921                Check_Size (Expr, Ctyp, Csize, Biased);
4922
4923                --  For the biased case, build a declaration for a subtype that
4924                --  will be used to represent the biased subtype that reflects
4925                --  the biased representation of components. We need the subtype
4926                --  to get proper conversions on referencing elements of the
4927                --  array. Note: component size clauses are ignored in VM mode.
4928
4929                if VM_Target = No_VM then
4930                   if Biased then
4931                      New_Ctyp :=
4932                        Make_Defining_Identifier (Loc,
4933                          Chars =>
4934                            New_External_Name (Chars (U_Ent), 'C', 0, 'T'));
4935
4936                      Decl :=
4937                        Make_Subtype_Declaration (Loc,
4938                          Defining_Identifier => New_Ctyp,
4939                          Subtype_Indication  =>
4940                            New_Occurrence_Of (Component_Type (Btype), Loc));
4941
4942                      Set_Parent (Decl, N);
4943                      Analyze (Decl, Suppress => All_Checks);
4944
4945                      Set_Has_Delayed_Freeze        (New_Ctyp, False);
4946                      Set_Esize                     (New_Ctyp, Csize);
4947                      Set_RM_Size                   (New_Ctyp, Csize);
4948                      Init_Alignment                (New_Ctyp);
4949                      Set_Is_Itype                  (New_Ctyp, True);
4950                      Set_Associated_Node_For_Itype (New_Ctyp, U_Ent);
4951
4952                      Set_Component_Type (Btype, New_Ctyp);
4953                      Set_Biased (New_Ctyp, N, "component size clause");
4954                   end if;
4955
4956                   Set_Component_Size (Btype, Csize);
4957
4958                --  For VM case, we ignore component size clauses
4959
4960                else
4961                   --  Give a warning unless we are in GNAT mode, in which case
4962                   --  the warning is suppressed since it is not useful.
4963
4964                   if not GNAT_Mode then
4965                      Error_Msg_N
4966                        ("component size ignored in this configuration??", N);
4967                   end if;
4968                end if;
4969
4970                --  Deal with warning on overridden size
4971
4972                if Warn_On_Overridden_Size
4973                  and then Has_Size_Clause (Ctyp)
4974                  and then RM_Size (Ctyp) /= Csize
4975                then
4976                   Error_Msg_NE
4977                     ("component size overrides size clause for&?S?", N, Ctyp);
4978                end if;
4979
4980                Set_Has_Component_Size_Clause (Btype, True);
4981                Set_Has_Non_Standard_Rep (Btype, True);
4982             end if;
4983          end Component_Size_Case;
4984
4985          -----------------------
4986          -- Constant_Indexing --
4987          -----------------------
4988
4989          when Attribute_Constant_Indexing =>
4990             Check_Indexing_Functions;
4991
4992          ---------
4993          -- CPU --
4994          ---------
4995
4996          when Attribute_CPU => CPU :
4997          begin
4998             --  CPU attribute definition clause not allowed except from aspect
4999             --  specification.
5000
5001             if From_Aspect_Specification (N) then
5002                if not Is_Task_Type (U_Ent) then
5003                   Error_Msg_N ("CPU can only be defined for task", Nam);
5004
5005                elsif Duplicate_Clause then
5006                   null;
5007
5008                else
5009                   --  The expression must be analyzed in the special manner
5010                   --  described in "Handling of Default and Per-Object
5011                   --  Expressions" in sem.ads.
5012
5013                   --  The visibility to the discriminants must be restored
5014
5015                   Push_Scope_And_Install_Discriminants (U_Ent);
5016                   Preanalyze_Spec_Expression (Expr, RTE (RE_CPU_Range));
5017                   Uninstall_Discriminants_And_Pop_Scope (U_Ent);
5018
5019                   if not Is_OK_Static_Expression (Expr) then
5020                      Check_Restriction (Static_Priorities, Expr);
5021                   end if;
5022                end if;
5023
5024             else
5025                Error_Msg_N
5026                  ("attribute& cannot be set with definition clause", N);
5027             end if;
5028          end CPU;
5029
5030          ----------------------
5031          -- Default_Iterator --
5032          ----------------------
5033
5034          when Attribute_Default_Iterator =>  Default_Iterator : declare
5035             Func : Entity_Id;
5036             Typ  : Entity_Id;
5037
5038          begin
5039             --  If target type is untagged, further checks are irrelevant
5040
5041             if not Is_Tagged_Type (U_Ent) then
5042                Error_Msg_N
5043                  ("aspect Default_Iterator applies to tagged type", Nam);
5044                return;
5045             end if;
5046
5047             Check_Iterator_Functions;
5048
5049             Analyze (Expr);
5050
5051             if not Is_Entity_Name (Expr)
5052               or else Ekind (Entity (Expr)) /= E_Function
5053             then
5054                Error_Msg_N ("aspect Iterator must be a function", Expr);
5055                return;
5056             else
5057                Func := Entity (Expr);
5058             end if;
5059
5060             --  The type of the first parameter must be T, T'class, or a
5061             --  corresponding access type (5.5.1 (8/3). If function is
5062             --  parameterless label type accordingly.
5063
5064             if No (First_Formal (Func)) then
5065                Typ := Any_Type;
5066             else
5067                Typ := Etype (First_Formal (Func));
5068             end if;
5069
5070             if Typ = U_Ent
5071               or else Typ = Class_Wide_Type (U_Ent)
5072               or else (Is_Access_Type (Typ)
5073                         and then Designated_Type (Typ) = U_Ent)
5074               or else (Is_Access_Type (Typ)
5075                         and then Designated_Type (Typ) =
5076                                           Class_Wide_Type (U_Ent))
5077             then
5078                null;
5079
5080             else
5081                Error_Msg_NE
5082                  ("Default Iterator must be a primitive of&", Func, U_Ent);
5083             end if;
5084          end Default_Iterator;
5085
5086          ------------------------
5087          -- Dispatching_Domain --
5088          ------------------------
5089
5090          when Attribute_Dispatching_Domain => Dispatching_Domain :
5091          begin
5092             --  Dispatching_Domain attribute definition clause not allowed
5093             --  except from aspect specification.
5094
5095             if From_Aspect_Specification (N) then
5096                if not Is_Task_Type (U_Ent) then
5097                   Error_Msg_N
5098                     ("Dispatching_Domain can only be defined for task", Nam);
5099
5100                elsif Duplicate_Clause then
5101                   null;
5102
5103                else
5104                   --  The expression must be analyzed in the special manner
5105                   --  described in "Handling of Default and Per-Object
5106                   --  Expressions" in sem.ads.
5107
5108                   --  The visibility to the discriminants must be restored
5109
5110                   Push_Scope_And_Install_Discriminants (U_Ent);
5111
5112                   Preanalyze_Spec_Expression
5113                     (Expr, RTE (RE_Dispatching_Domain));
5114
5115                   Uninstall_Discriminants_And_Pop_Scope (U_Ent);
5116                end if;
5117
5118             else
5119                Error_Msg_N
5120                  ("attribute& cannot be set with definition clause", N);
5121             end if;
5122          end Dispatching_Domain;
5123
5124          ------------------
5125          -- External_Tag --
5126          ------------------
5127
5128          when Attribute_External_Tag => External_Tag :
5129          begin
5130             if not Is_Tagged_Type (U_Ent) then
5131                Error_Msg_N ("should be a tagged type", Nam);
5132             end if;
5133
5134             if Duplicate_Clause then
5135                null;
5136
5137             else
5138                Analyze_And_Resolve (Expr, Standard_String);
5139
5140                if not Is_OK_Static_Expression (Expr) then
5141                   Flag_Non_Static_Expr
5142                     ("static string required for tag name!", Nam);
5143                end if;
5144
5145                if VM_Target /= No_VM then
5146                   Error_Msg_Name_1 := Attr;
5147                   Error_Msg_N
5148                     ("% attribute unsupported in this configuration", Nam);
5149                end if;
5150
5151                if not Is_Library_Level_Entity (U_Ent) then
5152                   Error_Msg_NE
5153                     ("??non-unique external tag supplied for &", N, U_Ent);
5154                   Error_Msg_N
5155                        ("\??same external tag applies to all "
5156                         & "subprogram calls", N);
5157                   Error_Msg_N
5158                     ("\??corresponding internal tag cannot be obtained", N);
5159                end if;
5160             end if;
5161          end External_Tag;
5162
5163          --------------------------
5164          -- Implicit_Dereference --
5165          --------------------------
5166
5167          when Attribute_Implicit_Dereference =>
5168
5169             --  Legality checks already performed at the point of the type
5170             --  declaration, aspect is not delayed.
5171
5172             null;
5173
5174          -----------
5175          -- Input --
5176          -----------
5177
5178          when Attribute_Input =>
5179             Analyze_Stream_TSS_Definition (TSS_Stream_Input);
5180             Set_Has_Specified_Stream_Input (Ent);
5181
5182          ------------------------
5183          -- Interrupt_Priority --
5184          ------------------------
5185
5186          when Attribute_Interrupt_Priority => Interrupt_Priority :
5187          begin
5188             --  Interrupt_Priority attribute definition clause not allowed
5189             --  except from aspect specification.
5190
5191             if From_Aspect_Specification (N) then
5192                if not Is_Concurrent_Type (U_Ent) then
5193                   Error_Msg_N
5194                     ("Interrupt_Priority can only be defined for task "
5195                      & "and protected object", Nam);
5196
5197                elsif Duplicate_Clause then
5198                   null;
5199
5200                else
5201                   --  The expression must be analyzed in the special manner
5202                   --  described in "Handling of Default and Per-Object
5203                   --  Expressions" in sem.ads.
5204
5205                   --  The visibility to the discriminants must be restored
5206
5207                   Push_Scope_And_Install_Discriminants (U_Ent);
5208
5209                   Preanalyze_Spec_Expression
5210                     (Expr, RTE (RE_Interrupt_Priority));
5211
5212                   Uninstall_Discriminants_And_Pop_Scope (U_Ent);
5213                end if;
5214
5215             else
5216                Error_Msg_N
5217                  ("attribute& cannot be set with definition clause", N);
5218             end if;
5219          end Interrupt_Priority;
5220
5221          --------------
5222          -- Iterable --
5223          --------------
5224
5225          when Attribute_Iterable =>
5226             Analyze (Expr);
5227
5228             if Nkind (Expr) /= N_Aggregate then
5229                Error_Msg_N ("aspect Iterable must be an aggregate", Expr);
5230             end if;
5231
5232             declare
5233                Assoc : Node_Id;
5234
5235             begin
5236                Assoc := First (Component_Associations (Expr));
5237                while Present (Assoc) loop
5238                   if not Is_Entity_Name (Expression (Assoc)) then
5239                      Error_Msg_N ("value must be a function", Assoc);
5240                   end if;
5241
5242                   Next (Assoc);
5243                end loop;
5244             end;
5245
5246          ----------------------
5247          -- Iterator_Element --
5248          ----------------------
5249
5250          when Attribute_Iterator_Element =>
5251             Analyze (Expr);
5252
5253             if not Is_Entity_Name (Expr)
5254               or else not Is_Type (Entity (Expr))
5255             then
5256                Error_Msg_N ("aspect Iterator_Element must be a type", Expr);
5257             end if;
5258
5259          -------------------
5260          -- Machine_Radix --
5261          -------------------
5262
5263          --  Machine radix attribute definition clause
5264
5265          when Attribute_Machine_Radix => Machine_Radix : declare
5266             Radix : constant Uint := Static_Integer (Expr);
5267
5268          begin
5269             if not Is_Decimal_Fixed_Point_Type (U_Ent) then
5270                Error_Msg_N ("decimal fixed-point type expected for &", Nam);
5271
5272             elsif Duplicate_Clause then
5273                null;
5274
5275             elsif Radix /= No_Uint then
5276                Set_Has_Machine_Radix_Clause (U_Ent);
5277                Set_Has_Non_Standard_Rep (Base_Type (U_Ent));
5278
5279                if Radix = 2 then
5280                   null;
5281                elsif Radix = 10 then
5282                   Set_Machine_Radix_10 (U_Ent);
5283                else
5284                   Error_Msg_N ("machine radix value must be 2 or 10", Expr);
5285                end if;
5286             end if;
5287          end Machine_Radix;
5288
5289          -----------------
5290          -- Object_Size --
5291          -----------------
5292
5293          --  Object_Size attribute definition clause
5294
5295          when Attribute_Object_Size => Object_Size : declare
5296             Size : constant Uint := Static_Integer (Expr);
5297
5298             Biased : Boolean;
5299             pragma Warnings (Off, Biased);
5300
5301          begin
5302             if not Is_Type (U_Ent) then
5303                Error_Msg_N ("Object_Size cannot be given for &", Nam);
5304
5305             elsif Duplicate_Clause then
5306                null;
5307
5308             else
5309                Check_Size (Expr, U_Ent, Size, Biased);
5310
5311                if Is_Scalar_Type (U_Ent) then
5312                   if Size /= 8 and then Size /= 16 and then Size /= 32
5313                     and then UI_Mod (Size, 64) /= 0
5314                   then
5315                      Error_Msg_N
5316                        ("Object_Size must be 8, 16, 32, or multiple of 64",
5317                         Expr);
5318                   end if;
5319
5320                elsif Size mod 8 /= 0 then
5321                   Error_Msg_N ("Object_Size must be a multiple of 8", Expr);
5322                end if;
5323
5324                Set_Esize (U_Ent, Size);
5325                Set_Has_Object_Size_Clause (U_Ent);
5326                Alignment_Check_For_Size_Change (U_Ent, Size);
5327             end if;
5328          end Object_Size;
5329
5330          ------------
5331          -- Output --
5332          ------------
5333
5334          when Attribute_Output =>
5335             Analyze_Stream_TSS_Definition (TSS_Stream_Output);
5336             Set_Has_Specified_Stream_Output (Ent);
5337
5338          --------------
5339          -- Priority --
5340          --------------
5341
5342          when Attribute_Priority => Priority :
5343          begin
5344             --  Priority attribute definition clause not allowed except from
5345             --  aspect specification.
5346
5347             if From_Aspect_Specification (N) then
5348                if not (Is_Concurrent_Type (U_Ent)
5349                         or else Ekind (U_Ent) = E_Procedure)
5350                then
5351                   Error_Msg_N
5352                     ("Priority can only be defined for task and protected "
5353                      & "object", Nam);
5354
5355                elsif Duplicate_Clause then
5356                   null;
5357
5358                else
5359                   --  The expression must be analyzed in the special manner
5360                   --  described in "Handling of Default and Per-Object
5361                   --  Expressions" in sem.ads.
5362
5363                   --  The visibility to the discriminants must be restored
5364
5365                   Push_Scope_And_Install_Discriminants (U_Ent);
5366                   Preanalyze_Spec_Expression (Expr, Standard_Integer);
5367                   Uninstall_Discriminants_And_Pop_Scope (U_Ent);
5368
5369                   if not Is_OK_Static_Expression (Expr) then
5370                      Check_Restriction (Static_Priorities, Expr);
5371                   end if;
5372                end if;
5373
5374             else
5375                Error_Msg_N
5376                  ("attribute& cannot be set with definition clause", N);
5377             end if;
5378          end Priority;
5379
5380          ----------
5381          -- Read --
5382          ----------
5383
5384          when Attribute_Read =>
5385             Analyze_Stream_TSS_Definition (TSS_Stream_Read);
5386             Set_Has_Specified_Stream_Read (Ent);
5387
5388          --------------------------
5389          -- Scalar_Storage_Order --
5390          --------------------------
5391
5392          --  Scalar_Storage_Order attribute definition clause
5393
5394          when Attribute_Scalar_Storage_Order => Scalar_Storage_Order : declare
5395          begin
5396             if not (Is_Record_Type (U_Ent) or else Is_Array_Type (U_Ent)) then
5397                Error_Msg_N
5398                  ("Scalar_Storage_Order can only be defined for "
5399                   & "record or array type", Nam);
5400
5401             elsif Duplicate_Clause then
5402                null;
5403
5404             else
5405                Analyze_And_Resolve (Expr, RTE (RE_Bit_Order));
5406
5407                if Etype (Expr) = Any_Type then
5408                   return;
5409
5410                elsif not Is_OK_Static_Expression (Expr) then
5411                   Flag_Non_Static_Expr
5412                     ("Scalar_Storage_Order requires static expression!", Expr);
5413
5414                elsif (Expr_Value (Expr) = 0) /= Bytes_Big_Endian then
5415
5416                   --  Here for the case of a non-default (i.e. non-confirming)
5417                   --  Scalar_Storage_Order attribute definition.
5418
5419                   if Support_Nondefault_SSO_On_Target then
5420                      Set_Reverse_Storage_Order (Base_Type (U_Ent), True);
5421                   else
5422                      Error_Msg_N
5423                        ("non-default Scalar_Storage_Order "
5424                         & "not supported on target", Expr);
5425                   end if;
5426                end if;
5427
5428                --  Clear SSO default indications since explicit setting of the
5429                --  order overrides the defaults.
5430
5431                Set_SSO_Set_Low_By_Default  (Base_Type (U_Ent), False);
5432                Set_SSO_Set_High_By_Default (Base_Type (U_Ent), False);
5433             end if;
5434          end Scalar_Storage_Order;
5435
5436          ----------
5437          -- Size --
5438          ----------
5439
5440          --  Size attribute definition clause
5441
5442          when Attribute_Size => Size : declare
5443             Size   : constant Uint := Static_Integer (Expr);
5444             Etyp   : Entity_Id;
5445             Biased : Boolean;
5446
5447          begin
5448             FOnly := True;
5449
5450             if Duplicate_Clause then
5451                null;
5452
5453             elsif not Is_Type (U_Ent)
5454               and then Ekind (U_Ent) /= E_Variable
5455               and then Ekind (U_Ent) /= E_Constant
5456             then
5457                Error_Msg_N ("size cannot be given for &", Nam);
5458
5459             elsif Is_Array_Type (U_Ent)
5460               and then not Is_Constrained (U_Ent)
5461             then
5462                Error_Msg_N
5463                  ("size cannot be given for unconstrained array", Nam);
5464
5465             elsif Size /= No_Uint then
5466                if VM_Target /= No_VM and then not GNAT_Mode then
5467
5468                   --  Size clause is not handled properly on VM targets.
5469                   --  Display a warning unless we are in GNAT mode, in which
5470                   --  case this is useless.
5471
5472                   Error_Msg_N
5473                     ("size clauses are ignored in this configuration??", N);
5474                end if;
5475
5476                if Is_Type (U_Ent) then
5477                   Etyp := U_Ent;
5478                else
5479                   Etyp := Etype (U_Ent);
5480                end if;
5481
5482                --  Check size, note that Gigi is in charge of checking that the
5483                --  size of an array or record type is OK. Also we do not check
5484                --  the size in the ordinary fixed-point case, since it is too
5485                --  early to do so (there may be subsequent small clause that
5486                --  affects the size). We can check the size if a small clause
5487                --  has already been given.
5488
5489                if not Is_Ordinary_Fixed_Point_Type (U_Ent)
5490                  or else Has_Small_Clause (U_Ent)
5491                then
5492                   Check_Size (Expr, Etyp, Size, Biased);
5493                   Set_Biased (U_Ent, N, "size clause", Biased);
5494                end if;
5495
5496                --  For types set RM_Size and Esize if possible
5497
5498                if Is_Type (U_Ent) then
5499                   Set_RM_Size (U_Ent, Size);
5500
5501                   --  For elementary types, increase Object_Size to power of 2,
5502                   --  but not less than a storage unit in any case (normally
5503                   --  this means it will be byte addressable).
5504
5505                   --  For all other types, nothing else to do, we leave Esize
5506                   --  (object size) unset, the back end will set it from the
5507                   --  size and alignment in an appropriate manner.
5508
5509                   --  In both cases, we check whether the alignment must be
5510                   --  reset in the wake of the size change.
5511
5512                   if Is_Elementary_Type (U_Ent) then
5513                      if Size <= System_Storage_Unit then
5514                         Init_Esize (U_Ent, System_Storage_Unit);
5515                      elsif Size <= 16 then
5516                         Init_Esize (U_Ent, 16);
5517                      elsif Size <= 32 then
5518                         Init_Esize (U_Ent, 32);
5519                      else
5520                         Set_Esize  (U_Ent, (Size + 63) / 64 * 64);
5521                      end if;
5522
5523                      Alignment_Check_For_Size_Change (U_Ent, Esize (U_Ent));
5524                   else
5525                      Alignment_Check_For_Size_Change (U_Ent, Size);
5526                   end if;
5527
5528                --  For objects, set Esize only
5529
5530                else
5531                   if Is_Elementary_Type (Etyp) then
5532                      if Size /= System_Storage_Unit
5533                           and then
5534                         Size /= System_Storage_Unit * 2
5535                           and then
5536                         Size /= System_Storage_Unit * 4
5537                            and then
5538                         Size /= System_Storage_Unit * 8
5539                      then
5540                         Error_Msg_Uint_1 := UI_From_Int (System_Storage_Unit);
5541                         Error_Msg_Uint_2 := Error_Msg_Uint_1 * 8;
5542                         Error_Msg_N
5543                           ("size for primitive object must be a power of 2"
5544                             & " in the range ^-^", N);
5545                      end if;
5546                   end if;
5547
5548                   Set_Esize (U_Ent, Size);
5549                end if;
5550
5551                Set_Has_Size_Clause (U_Ent);
5552             end if;
5553          end Size;
5554
5555          -----------
5556          -- Small --
5557          -----------
5558
5559          --  Small attribute definition clause
5560
5561          when Attribute_Small => Small : declare
5562             Implicit_Base : constant Entity_Id := Base_Type (U_Ent);
5563             Small         : Ureal;
5564
5565          begin
5566             Analyze_And_Resolve (Expr, Any_Real);
5567
5568             if Etype (Expr) = Any_Type then
5569                return;
5570
5571             elsif not Is_OK_Static_Expression (Expr) then
5572                Flag_Non_Static_Expr
5573                  ("small requires static expression!", Expr);
5574                return;
5575
5576             else
5577                Small := Expr_Value_R (Expr);
5578
5579                if Small <= Ureal_0 then
5580                   Error_Msg_N ("small value must be greater than zero", Expr);
5581                   return;
5582                end if;
5583
5584             end if;
5585
5586             if not Is_Ordinary_Fixed_Point_Type (U_Ent) then
5587                Error_Msg_N
5588                  ("small requires an ordinary fixed point type", Nam);
5589
5590             elsif Has_Small_Clause (U_Ent) then
5591                Error_Msg_N ("small already given for &", Nam);
5592
5593             elsif Small > Delta_Value (U_Ent) then
5594                Error_Msg_N
5595                  ("small value must not be greater than delta value", Nam);
5596
5597             else
5598                Set_Small_Value (U_Ent, Small);
5599                Set_Small_Value (Implicit_Base, Small);
5600                Set_Has_Small_Clause (U_Ent);
5601                Set_Has_Small_Clause (Implicit_Base);
5602                Set_Has_Non_Standard_Rep (Implicit_Base);
5603             end if;
5604          end Small;
5605
5606          ------------------
5607          -- Storage_Pool --
5608          ------------------
5609
5610          --  Storage_Pool attribute definition clause
5611
5612          when Attribute_Storage_Pool | Attribute_Simple_Storage_Pool => declare
5613             Pool : Entity_Id;
5614             T    : Entity_Id;
5615
5616          begin
5617             if Ekind (U_Ent) = E_Access_Subprogram_Type then
5618                Error_Msg_N
5619                  ("storage pool cannot be given for access-to-subprogram type",
5620                   Nam);
5621                return;
5622
5623             elsif not
5624               Ekind_In (U_Ent, E_Access_Type, E_General_Access_Type)
5625             then
5626                Error_Msg_N
5627                  ("storage pool can only be given for access types", Nam);
5628                return;
5629
5630             elsif Is_Derived_Type (U_Ent) then
5631                Error_Msg_N
5632                  ("storage pool cannot be given for a derived access type",
5633                   Nam);
5634
5635             elsif Duplicate_Clause then
5636                return;
5637
5638             elsif Present (Associated_Storage_Pool (U_Ent)) then
5639                Error_Msg_N ("storage pool already given for &", Nam);
5640                return;
5641             end if;
5642
5643             --  Check for Storage_Size previously given
5644
5645             declare
5646                SS : constant Node_Id :=
5647                       Get_Attribute_Definition_Clause
5648                         (U_Ent, Attribute_Storage_Size);
5649             begin
5650                if Present (SS) then
5651                   Check_Pool_Size_Clash (U_Ent, N, SS);
5652                end if;
5653             end;
5654
5655             --  Storage_Pool case
5656
5657             if Id = Attribute_Storage_Pool then
5658                Analyze_And_Resolve
5659                  (Expr, Class_Wide_Type (RTE (RE_Root_Storage_Pool)));
5660
5661             --  In the Simple_Storage_Pool case, we allow a variable of any
5662             --  simple storage pool type, so we Resolve without imposing an
5663             --  expected type.
5664
5665             else
5666                Analyze_And_Resolve (Expr);
5667
5668                if not Present (Get_Rep_Pragma
5669                                  (Etype (Expr), Name_Simple_Storage_Pool_Type))
5670                then
5671                   Error_Msg_N
5672                     ("expression must be of a simple storage pool type", Expr);
5673                end if;
5674             end if;
5675
5676             if not Denotes_Variable (Expr) then
5677                Error_Msg_N ("storage pool must be a variable", Expr);
5678                return;
5679             end if;
5680
5681             if Nkind (Expr) = N_Type_Conversion then
5682                T := Etype (Expression (Expr));
5683             else
5684                T := Etype (Expr);
5685             end if;
5686
5687             --  The Stack_Bounded_Pool is used internally for implementing
5688             --  access types with a Storage_Size. Since it only work properly
5689             --  when used on one specific type, we need to check that it is not
5690             --  hijacked improperly:
5691
5692             --    type T is access Integer;
5693             --    for T'Storage_Size use n;
5694             --    type Q is access Float;
5695             --    for Q'Storage_Size use T'Storage_Size; -- incorrect
5696
5697             if RTE_Available (RE_Stack_Bounded_Pool)
5698               and then Base_Type (T) = RTE (RE_Stack_Bounded_Pool)
5699             then
5700                Error_Msg_N ("non-shareable internal Pool", Expr);
5701                return;
5702             end if;
5703
5704             --  If the argument is a name that is not an entity name, then
5705             --  we construct a renaming operation to define an entity of
5706             --  type storage pool.
5707
5708             if not Is_Entity_Name (Expr)
5709               and then Is_Object_Reference (Expr)
5710             then
5711                Pool := Make_Temporary (Loc, 'P', Expr);
5712
5713                declare
5714                   Rnode : constant Node_Id :=
5715                             Make_Object_Renaming_Declaration (Loc,
5716                               Defining_Identifier => Pool,
5717                               Subtype_Mark        =>
5718                                 New_Occurrence_Of (Etype (Expr), Loc),
5719                               Name                => Expr);
5720
5721                begin
5722                   --  If the attribute definition clause comes from an aspect
5723                   --  clause, then insert the renaming before the associated
5724                   --  entity's declaration, since the attribute clause has
5725                   --  not yet been appended to the declaration list.
5726
5727                   if From_Aspect_Specification (N) then
5728                      Insert_Before (Parent (Entity (N)), Rnode);
5729                   else
5730                      Insert_Before (N, Rnode);
5731                   end if;
5732
5733                   Analyze (Rnode);
5734                   Set_Associated_Storage_Pool (U_Ent, Pool);
5735                end;
5736
5737             elsif Is_Entity_Name (Expr) then
5738                Pool := Entity (Expr);
5739
5740                --  If pool is a renamed object, get original one. This can
5741                --  happen with an explicit renaming, and within instances.
5742
5743                while Present (Renamed_Object (Pool))
5744                  and then Is_Entity_Name (Renamed_Object (Pool))
5745                loop
5746                   Pool := Entity (Renamed_Object (Pool));
5747                end loop;
5748
5749                if Present (Renamed_Object (Pool))
5750                  and then Nkind (Renamed_Object (Pool)) = N_Type_Conversion
5751                  and then Is_Entity_Name (Expression (Renamed_Object (Pool)))
5752                then
5753                   Pool := Entity (Expression (Renamed_Object (Pool)));
5754                end if;
5755
5756                Set_Associated_Storage_Pool (U_Ent, Pool);
5757
5758             elsif Nkind (Expr) = N_Type_Conversion
5759               and then Is_Entity_Name (Expression (Expr))
5760               and then Nkind (Original_Node (Expr)) = N_Attribute_Reference
5761             then
5762                Pool := Entity (Expression (Expr));
5763                Set_Associated_Storage_Pool (U_Ent, Pool);
5764
5765             else
5766                Error_Msg_N ("incorrect reference to a Storage Pool", Expr);
5767                return;
5768             end if;
5769          end;
5770
5771          ------------------
5772          -- Storage_Size --
5773          ------------------
5774
5775          --  Storage_Size attribute definition clause
5776
5777          when Attribute_Storage_Size => Storage_Size : declare
5778             Btype : constant Entity_Id := Base_Type (U_Ent);
5779
5780          begin
5781             if Is_Task_Type (U_Ent) then
5782
5783                --  Check obsolescent (but never obsolescent if from aspect)
5784
5785                if not From_Aspect_Specification (N) then
5786                   Check_Restriction (No_Obsolescent_Features, N);
5787
5788                   if Warn_On_Obsolescent_Feature then
5789                      Error_Msg_N
5790                        ("?j?storage size clause for task is an " &
5791                         "obsolescent feature (RM J.9)", N);
5792                      Error_Msg_N ("\?j?use Storage_Size pragma instead", N);
5793                   end if;
5794                end if;
5795
5796                FOnly := True;
5797             end if;
5798
5799             if not Is_Access_Type (U_Ent)
5800               and then Ekind (U_Ent) /= E_Task_Type
5801             then
5802                Error_Msg_N ("storage size cannot be given for &", Nam);
5803
5804             elsif Is_Access_Type (U_Ent) and Is_Derived_Type (U_Ent) then
5805                Error_Msg_N
5806                  ("storage size cannot be given for a derived access type",
5807                   Nam);
5808
5809             elsif Duplicate_Clause then
5810                null;
5811
5812             else
5813                Analyze_And_Resolve (Expr, Any_Integer);
5814
5815                if Is_Access_Type (U_Ent) then
5816
5817                   --  Check for Storage_Pool previously given
5818
5819                   declare
5820                      SP : constant Node_Id :=
5821                             Get_Attribute_Definition_Clause
5822                               (U_Ent, Attribute_Storage_Pool);
5823
5824                   begin
5825                      if Present (SP) then
5826                         Check_Pool_Size_Clash (U_Ent, SP, N);
5827                      end if;
5828                   end;
5829
5830                   --  Special case of for x'Storage_Size use 0
5831
5832                   if Is_OK_Static_Expression (Expr)
5833                     and then Expr_Value (Expr) = 0
5834                   then
5835                      Set_No_Pool_Assigned (Btype);
5836                   end if;
5837                end if;
5838
5839                Set_Has_Storage_Size_Clause (Btype);
5840             end if;
5841          end Storage_Size;
5842
5843          -----------------
5844          -- Stream_Size --
5845          -----------------
5846
5847          when Attribute_Stream_Size => Stream_Size : declare
5848             Size : constant Uint := Static_Integer (Expr);
5849
5850          begin
5851             if Ada_Version <= Ada_95 then
5852                Check_Restriction (No_Implementation_Attributes, N);
5853             end if;
5854
5855             if Duplicate_Clause then
5856                null;
5857
5858             elsif Is_Elementary_Type (U_Ent) then
5859                if Size /= System_Storage_Unit
5860                     and then
5861                   Size /= System_Storage_Unit * 2
5862                     and then
5863                   Size /= System_Storage_Unit * 4
5864                      and then
5865                   Size /= System_Storage_Unit * 8
5866                then
5867                   Error_Msg_Uint_1 := UI_From_Int (System_Storage_Unit);
5868                   Error_Msg_N
5869                     ("stream size for elementary type must be a"
5870                        & " power of 2 and at least ^", N);
5871
5872                elsif RM_Size (U_Ent) > Size then
5873                   Error_Msg_Uint_1 := RM_Size (U_Ent);
5874                   Error_Msg_N
5875                     ("stream size for elementary type must be a"
5876                        & " power of 2 and at least ^", N);
5877                end if;
5878
5879                Set_Has_Stream_Size_Clause (U_Ent);
5880
5881             else
5882                Error_Msg_N ("Stream_Size cannot be given for &", Nam);
5883             end if;
5884          end Stream_Size;
5885
5886          ----------------
5887          -- Value_Size --
5888          ----------------
5889
5890          --  Value_Size attribute definition clause
5891
5892          when Attribute_Value_Size => Value_Size : declare
5893             Size   : constant Uint := Static_Integer (Expr);
5894             Biased : Boolean;
5895
5896          begin
5897             if not Is_Type (U_Ent) then
5898                Error_Msg_N ("Value_Size cannot be given for &", Nam);
5899
5900             elsif Duplicate_Clause then
5901                null;
5902
5903             elsif Is_Array_Type (U_Ent)
5904               and then not Is_Constrained (U_Ent)
5905             then
5906                Error_Msg_N
5907                  ("Value_Size cannot be given for unconstrained array", Nam);
5908
5909             else
5910                if Is_Elementary_Type (U_Ent) then
5911                   Check_Size (Expr, U_Ent, Size, Biased);
5912                   Set_Biased (U_Ent, N, "value size clause", Biased);
5913                end if;
5914
5915                Set_RM_Size (U_Ent, Size);
5916             end if;
5917          end Value_Size;
5918
5919          -----------------------
5920          -- Variable_Indexing --
5921          -----------------------
5922
5923          when Attribute_Variable_Indexing =>
5924             Check_Indexing_Functions;
5925
5926          -----------
5927          -- Write --
5928          -----------
5929
5930          when Attribute_Write =>
5931             Analyze_Stream_TSS_Definition (TSS_Stream_Write);
5932             Set_Has_Specified_Stream_Write (Ent);
5933
5934          --  All other attributes cannot be set
5935
5936          when others =>
5937             Error_Msg_N
5938               ("attribute& cannot be set with definition clause", N);
5939       end case;
5940
5941       --  The test for the type being frozen must be performed after any
5942       --  expression the clause has been analyzed since the expression itself
5943       --  might cause freezing that makes the clause illegal.
5944
5945       if Rep_Item_Too_Late (U_Ent, N, FOnly) then
5946          return;
5947       end if;
5948    end Analyze_Attribute_Definition_Clause;
5949
5950    ----------------------------
5951    -- Analyze_Code_Statement --
5952    ----------------------------
5953
5954    procedure Analyze_Code_Statement (N : Node_Id) is
5955       HSS   : constant Node_Id   := Parent (N);
5956       SBody : constant Node_Id   := Parent (HSS);
5957       Subp  : constant Entity_Id := Current_Scope;
5958       Stmt  : Node_Id;
5959       Decl  : Node_Id;
5960       StmtO : Node_Id;
5961       DeclO : Node_Id;
5962
5963    begin
5964       --  Analyze and check we get right type, note that this implements the
5965       --  requirement (RM 13.8(1)) that Machine_Code be with'ed, since that
5966       --  is the only way that Asm_Insn could possibly be visible.
5967
5968       Analyze_And_Resolve (Expression (N));
5969
5970       if Etype (Expression (N)) = Any_Type then
5971          return;
5972       elsif Etype (Expression (N)) /= RTE (RE_Asm_Insn) then
5973          Error_Msg_N ("incorrect type for code statement", N);
5974          return;
5975       end if;
5976
5977       Check_Code_Statement (N);
5978
5979       --  Make sure we appear in the handled statement sequence of a
5980       --  subprogram (RM 13.8(3)).
5981
5982       if Nkind (HSS) /= N_Handled_Sequence_Of_Statements
5983         or else Nkind (SBody) /= N_Subprogram_Body
5984       then
5985          Error_Msg_N
5986            ("code statement can only appear in body of subprogram", N);
5987          return;
5988       end if;
5989
5990       --  Do remaining checks (RM 13.8(3)) if not already done
5991
5992       if not Is_Machine_Code_Subprogram (Subp) then
5993          Set_Is_Machine_Code_Subprogram (Subp);
5994
5995          --  No exception handlers allowed
5996
5997          if Present (Exception_Handlers (HSS)) then
5998             Error_Msg_N
5999               ("exception handlers not permitted in machine code subprogram",
6000                First (Exception_Handlers (HSS)));
6001          end if;
6002
6003          --  No declarations other than use clauses and pragmas (we allow
6004          --  certain internally generated declarations as well).
6005
6006          Decl := First (Declarations (SBody));
6007          while Present (Decl) loop
6008             DeclO := Original_Node (Decl);
6009             if Comes_From_Source (DeclO)
6010               and not Nkind_In (DeclO, N_Pragma,
6011                                        N_Use_Package_Clause,
6012                                        N_Use_Type_Clause,
6013                                        N_Implicit_Label_Declaration)
6014             then
6015                Error_Msg_N
6016                  ("this declaration not allowed in machine code subprogram",
6017                   DeclO);
6018             end if;
6019
6020             Next (Decl);
6021          end loop;
6022
6023          --  No statements other than code statements, pragmas, and labels.
6024          --  Again we allow certain internally generated statements.
6025
6026          --  In Ada 2012, qualified expressions are names, and the code
6027          --  statement is initially parsed as a procedure call.
6028
6029          Stmt := First (Statements (HSS));
6030          while Present (Stmt) loop
6031             StmtO := Original_Node (Stmt);
6032
6033             --  A procedure call transformed into a code statement is OK.
6034
6035             if Ada_Version >= Ada_2012
6036               and then Nkind (StmtO) = N_Procedure_Call_Statement
6037               and then Nkind (Name (StmtO)) = N_Qualified_Expression
6038             then
6039                null;
6040
6041             elsif Comes_From_Source (StmtO)
6042               and then not Nkind_In (StmtO, N_Pragma,
6043                                             N_Label,
6044                                             N_Code_Statement)
6045             then
6046                Error_Msg_N
6047                  ("this statement is not allowed in machine code subprogram",
6048                   StmtO);
6049             end if;
6050
6051             Next (Stmt);
6052          end loop;
6053       end if;
6054    end Analyze_Code_Statement;
6055
6056    -----------------------------------------------
6057    -- Analyze_Enumeration_Representation_Clause --
6058    -----------------------------------------------
6059
6060    procedure Analyze_Enumeration_Representation_Clause (N : Node_Id) is
6061       Ident    : constant Node_Id    := Identifier (N);
6062       Aggr     : constant Node_Id    := Array_Aggregate (N);
6063       Enumtype : Entity_Id;
6064       Elit     : Entity_Id;
6065       Expr     : Node_Id;
6066       Assoc    : Node_Id;
6067       Choice   : Node_Id;
6068       Val      : Uint;
6069
6070       Err : Boolean := False;
6071       --  Set True to avoid cascade errors and crashes on incorrect source code
6072
6073       Lo : constant Uint := Expr_Value (Type_Low_Bound (Universal_Integer));
6074       Hi : constant Uint := Expr_Value (Type_High_Bound (Universal_Integer));
6075       --  Allowed range of universal integer (= allowed range of enum lit vals)
6076
6077       Min : Uint;
6078       Max : Uint;
6079       --  Minimum and maximum values of entries
6080
6081       Max_Node : Node_Id;
6082       --  Pointer to node for literal providing max value
6083
6084    begin
6085       if Ignore_Rep_Clauses then
6086          Kill_Rep_Clause (N);
6087          return;
6088       end if;
6089
6090       --  Ignore enumeration rep clauses by default in CodePeer mode,
6091       --  unless -gnatd.I is specified, as a work around for potential false
6092       --  positive messages.
6093
6094       if CodePeer_Mode and not Debug_Flag_Dot_II then
6095          return;
6096       end if;
6097
6098       --  First some basic error checks
6099
6100       Find_Type (Ident);
6101       Enumtype := Entity (Ident);
6102
6103       if Enumtype = Any_Type
6104         or else Rep_Item_Too_Early (Enumtype, N)
6105       then
6106          return;
6107       else
6108          Enumtype := Underlying_Type (Enumtype);
6109       end if;
6110
6111       if not Is_Enumeration_Type (Enumtype) then
6112          Error_Msg_NE
6113            ("enumeration type required, found}",
6114             Ident, First_Subtype (Enumtype));
6115          return;
6116       end if;
6117
6118       --  Ignore rep clause on generic actual type. This will already have
6119       --  been flagged on the template as an error, and this is the safest
6120       --  way to ensure we don't get a junk cascaded message in the instance.
6121
6122       if Is_Generic_Actual_Type (Enumtype) then
6123          return;
6124
6125       --  Type must be in current scope
6126
6127       elsif Scope (Enumtype) /= Current_Scope then
6128          Error_Msg_N ("type must be declared in this scope", Ident);
6129          return;
6130
6131       --  Type must be a first subtype
6132
6133       elsif not Is_First_Subtype (Enumtype) then
6134          Error_Msg_N ("cannot give enumeration rep clause for subtype", N);
6135          return;
6136
6137       --  Ignore duplicate rep clause
6138
6139       elsif Has_Enumeration_Rep_Clause (Enumtype) then
6140          Error_Msg_N ("duplicate enumeration rep clause ignored", N);
6141          return;
6142
6143       --  Don't allow rep clause for standard [wide_[wide_]]character
6144
6145       elsif Is_Standard_Character_Type (Enumtype) then
6146          Error_Msg_N ("enumeration rep clause not allowed for this type", N);
6147          return;
6148
6149       --  Check that the expression is a proper aggregate (no parentheses)
6150
6151       elsif Paren_Count (Aggr) /= 0 then
6152          Error_Msg
6153            ("extra parentheses surrounding aggregate not allowed",
6154             First_Sloc (Aggr));
6155          return;
6156
6157       --  All tests passed, so set rep clause in place
6158
6159       else
6160          Set_Has_Enumeration_Rep_Clause (Enumtype);
6161          Set_Has_Enumeration_Rep_Clause (Base_Type (Enumtype));
6162       end if;
6163
6164       --  Now we process the aggregate. Note that we don't use the normal
6165       --  aggregate code for this purpose, because we don't want any of the
6166       --  normal expansion activities, and a number of special semantic
6167       --  rules apply (including the component type being any integer type)
6168
6169       Elit := First_Literal (Enumtype);
6170
6171       --  First the positional entries if any
6172
6173       if Present (Expressions (Aggr)) then
6174          Expr := First (Expressions (Aggr));
6175          while Present (Expr) loop
6176             if No (Elit) then
6177                Error_Msg_N ("too many entries in aggregate", Expr);
6178                return;
6179             end if;
6180
6181             Val := Static_Integer (Expr);
6182
6183             --  Err signals that we found some incorrect entries processing
6184             --  the list. The final checks for completeness and ordering are
6185             --  skipped in this case.
6186
6187             if Val = No_Uint then
6188                Err := True;
6189
6190             elsif Val < Lo or else Hi < Val then
6191                Error_Msg_N ("value outside permitted range", Expr);
6192                Err := True;
6193             end if;
6194
6195             Set_Enumeration_Rep (Elit, Val);
6196             Set_Enumeration_Rep_Expr (Elit, Expr);
6197             Next (Expr);
6198             Next (Elit);
6199          end loop;
6200       end if;
6201
6202       --  Now process the named entries if present
6203
6204       if Present (Component_Associations (Aggr)) then
6205          Assoc := First (Component_Associations (Aggr));
6206          while Present (Assoc) loop
6207             Choice := First (Choices (Assoc));
6208
6209             if Present (Next (Choice)) then
6210                Error_Msg_N
6211                  ("multiple choice not allowed here", Next (Choice));
6212                Err := True;
6213             end if;
6214
6215             if Nkind (Choice) = N_Others_Choice then
6216                Error_Msg_N ("others choice not allowed here", Choice);
6217                Err := True;
6218
6219             elsif Nkind (Choice) = N_Range then
6220
6221                --  ??? should allow zero/one element range here
6222
6223                Error_Msg_N ("range not allowed here", Choice);
6224                Err := True;
6225
6226             else
6227                Analyze_And_Resolve (Choice, Enumtype);
6228
6229                if Error_Posted (Choice) then
6230                   Err := True;
6231                end if;
6232
6233                if not Err then
6234                   if Is_Entity_Name (Choice)
6235                     and then Is_Type (Entity (Choice))
6236                   then
6237                      Error_Msg_N ("subtype name not allowed here", Choice);
6238                      Err := True;
6239
6240                      --  ??? should allow static subtype with zero/one entry
6241
6242                   elsif Etype (Choice) = Base_Type (Enumtype) then
6243                      if not Is_OK_Static_Expression (Choice) then
6244                         Flag_Non_Static_Expr
6245                           ("non-static expression used for choice!", Choice);
6246                         Err := True;
6247
6248                      else
6249                         Elit := Expr_Value_E (Choice);
6250
6251                         if Present (Enumeration_Rep_Expr (Elit)) then
6252                            Error_Msg_Sloc :=
6253                              Sloc (Enumeration_Rep_Expr (Elit));
6254                            Error_Msg_NE
6255                              ("representation for& previously given#",
6256                               Choice, Elit);
6257                            Err := True;
6258                         end if;
6259
6260                         Set_Enumeration_Rep_Expr (Elit, Expression (Assoc));
6261
6262                         Expr := Expression (Assoc);
6263                         Val := Static_Integer (Expr);
6264
6265                         if Val = No_Uint then
6266                            Err := True;
6267
6268                         elsif Val < Lo or else Hi < Val then
6269                            Error_Msg_N ("value outside permitted range", Expr);
6270                            Err := True;
6271                         end if;
6272
6273                         Set_Enumeration_Rep (Elit, Val);
6274                      end if;
6275                   end if;
6276                end if;
6277             end if;
6278
6279             Next (Assoc);
6280          end loop;
6281       end if;
6282
6283       --  Aggregate is fully processed. Now we check that a full set of
6284       --  representations was given, and that they are in range and in order.
6285       --  These checks are only done if no other errors occurred.
6286
6287       if not Err then
6288          Min  := No_Uint;
6289          Max  := No_Uint;
6290
6291          Elit := First_Literal (Enumtype);
6292          while Present (Elit) loop
6293             if No (Enumeration_Rep_Expr (Elit)) then
6294                Error_Msg_NE ("missing representation for&!", N, Elit);
6295
6296             else
6297                Val := Enumeration_Rep (Elit);
6298
6299                if Min = No_Uint then
6300                   Min := Val;
6301                end if;
6302
6303                if Val /= No_Uint then
6304                   if Max /= No_Uint and then Val <= Max then
6305                      Error_Msg_NE
6306                        ("enumeration value for& not ordered!",
6307                         Enumeration_Rep_Expr (Elit), Elit);
6308                   end if;
6309
6310                   Max_Node := Enumeration_Rep_Expr (Elit);
6311                   Max := Val;
6312                end if;
6313
6314                --  If there is at least one literal whose representation is not
6315                --  equal to the Pos value, then note that this enumeration type
6316                --  has a non-standard representation.
6317
6318                if Val /= Enumeration_Pos (Elit) then
6319                   Set_Has_Non_Standard_Rep (Base_Type (Enumtype));
6320                end if;
6321             end if;
6322
6323             Next (Elit);
6324          end loop;
6325
6326          --  Now set proper size information
6327
6328          declare
6329             Minsize : Uint := UI_From_Int (Minimum_Size (Enumtype));
6330
6331          begin
6332             if Has_Size_Clause (Enumtype) then
6333
6334                --  All OK, if size is OK now
6335
6336                if RM_Size (Enumtype) >= Minsize then
6337                   null;
6338
6339                else
6340                   --  Try if we can get by with biasing
6341
6342                   Minsize :=
6343                     UI_From_Int (Minimum_Size (Enumtype, Biased => True));
6344
6345                   --  Error message if even biasing does not work
6346
6347                   if RM_Size (Enumtype) < Minsize then
6348                      Error_Msg_Uint_1 := RM_Size (Enumtype);
6349                      Error_Msg_Uint_2 := Max;
6350                      Error_Msg_N
6351                        ("previously given size (^) is too small "
6352                         & "for this value (^)", Max_Node);
6353
6354                   --  If biasing worked, indicate that we now have biased rep
6355
6356                   else
6357                      Set_Biased
6358                        (Enumtype, Size_Clause (Enumtype), "size clause");
6359                   end if;
6360                end if;
6361
6362             else
6363                Set_RM_Size    (Enumtype, Minsize);
6364                Set_Enum_Esize (Enumtype);
6365             end if;
6366
6367             Set_RM_Size   (Base_Type (Enumtype), RM_Size   (Enumtype));
6368             Set_Esize     (Base_Type (Enumtype), Esize     (Enumtype));
6369             Set_Alignment (Base_Type (Enumtype), Alignment (Enumtype));
6370          end;
6371       end if;
6372
6373       --  We repeat the too late test in case it froze itself
6374
6375       if Rep_Item_Too_Late (Enumtype, N) then
6376          null;
6377       end if;
6378    end Analyze_Enumeration_Representation_Clause;
6379
6380    ----------------------------
6381    -- Analyze_Free_Statement --
6382    ----------------------------
6383
6384    procedure Analyze_Free_Statement (N : Node_Id) is
6385    begin
6386       Analyze (Expression (N));
6387    end Analyze_Free_Statement;
6388
6389    ---------------------------
6390    -- Analyze_Freeze_Entity --
6391    ---------------------------
6392
6393    procedure Analyze_Freeze_Entity (N : Node_Id) is
6394    begin
6395       Freeze_Entity_Checks (N);
6396    end Analyze_Freeze_Entity;
6397
6398    -----------------------------------
6399    -- Analyze_Freeze_Generic_Entity --
6400    -----------------------------------
6401
6402    procedure Analyze_Freeze_Generic_Entity (N : Node_Id) is
6403    begin
6404       Freeze_Entity_Checks (N);
6405    end Analyze_Freeze_Generic_Entity;
6406
6407    ------------------------------------------
6408    -- Analyze_Record_Representation_Clause --
6409    ------------------------------------------
6410
6411    --  Note: we check as much as we can here, but we can't do any checks
6412    --  based on the position values (e.g. overlap checks) until freeze time
6413    --  because especially in Ada 2005 (machine scalar mode), the processing
6414    --  for non-standard bit order can substantially change the positions.
6415    --  See procedure Check_Record_Representation_Clause (called from Freeze)
6416    --  for the remainder of this processing.
6417
6418    procedure Analyze_Record_Representation_Clause (N : Node_Id) is
6419       Ident   : constant Node_Id := Identifier (N);
6420       Biased  : Boolean;
6421       CC      : Node_Id;
6422       Comp    : Entity_Id;
6423       Fbit    : Uint;
6424       Hbit    : Uint := Uint_0;
6425       Lbit    : Uint;
6426       Ocomp   : Entity_Id;
6427       Posit   : Uint;
6428       Rectype : Entity_Id;
6429       Recdef  : Node_Id;
6430
6431       function Is_Inherited (Comp : Entity_Id) return Boolean;
6432       --  True if Comp is an inherited component in a record extension
6433
6434       ------------------
6435       -- Is_Inherited --
6436       ------------------
6437
6438       function Is_Inherited (Comp : Entity_Id) return Boolean is
6439          Comp_Base : Entity_Id;
6440
6441       begin
6442          if Ekind (Rectype) = E_Record_Subtype then
6443             Comp_Base := Original_Record_Component (Comp);
6444          else
6445             Comp_Base := Comp;
6446          end if;
6447
6448          return Comp_Base /= Original_Record_Component (Comp_Base);
6449       end Is_Inherited;
6450
6451       --  Local variables
6452
6453       Is_Record_Extension : Boolean;
6454       --  True if Rectype is a record extension
6455
6456       CR_Pragma : Node_Id := Empty;
6457       --  Points to N_Pragma node if Complete_Representation pragma present
6458
6459    --  Start of processing for Analyze_Record_Representation_Clause
6460
6461    begin
6462       if Ignore_Rep_Clauses then
6463          Kill_Rep_Clause (N);
6464          return;
6465       end if;
6466
6467       Find_Type (Ident);
6468       Rectype := Entity (Ident);
6469
6470       if Rectype = Any_Type or else Rep_Item_Too_Early (Rectype, N) then
6471          return;
6472       else
6473          Rectype := Underlying_Type (Rectype);
6474       end if;
6475
6476       --  First some basic error checks
6477
6478       if not Is_Record_Type (Rectype) then
6479          Error_Msg_NE
6480            ("record type required, found}", Ident, First_Subtype (Rectype));
6481          return;
6482
6483       elsif Scope (Rectype) /= Current_Scope then
6484          Error_Msg_N ("type must be declared in this scope", N);
6485          return;
6486
6487       elsif not Is_First_Subtype (Rectype) then
6488          Error_Msg_N ("cannot give record rep clause for subtype", N);
6489          return;
6490
6491       elsif Has_Record_Rep_Clause (Rectype) then
6492          Error_Msg_N ("duplicate record rep clause ignored", N);
6493          return;
6494
6495       elsif Rep_Item_Too_Late (Rectype, N) then
6496          return;
6497       end if;
6498
6499       --  We know we have a first subtype, now possibly go the the anonymous
6500       --  base type to determine whether Rectype is a record extension.
6501
6502       Recdef := Type_Definition (Declaration_Node (Base_Type (Rectype)));
6503       Is_Record_Extension :=
6504         Nkind (Recdef) = N_Derived_Type_Definition
6505           and then Present (Record_Extension_Part (Recdef));
6506
6507       if Present (Mod_Clause (N)) then
6508          declare
6509             Loc     : constant Source_Ptr := Sloc (N);
6510             M       : constant Node_Id := Mod_Clause (N);
6511             P       : constant List_Id := Pragmas_Before (M);
6512             AtM_Nod : Node_Id;
6513
6514             Mod_Val : Uint;
6515             pragma Warnings (Off, Mod_Val);
6516
6517          begin
6518             Check_Restriction (No_Obsolescent_Features, Mod_Clause (N));
6519
6520             if Warn_On_Obsolescent_Feature then
6521                Error_Msg_N
6522                  ("?j?mod clause is an obsolescent feature (RM J.8)", N);
6523                Error_Msg_N
6524                  ("\?j?use alignment attribute definition clause instead", N);
6525             end if;
6526
6527             if Present (P) then
6528                Analyze_List (P);
6529             end if;
6530
6531             --  In ASIS_Mode mode, expansion is disabled, but we must convert
6532             --  the Mod clause into an alignment clause anyway, so that the
6533             --  back-end can compute and back-annotate properly the size and
6534             --  alignment of types that may include this record.
6535
6536             --  This seems dubious, this destroys the source tree in a manner
6537             --  not detectable by ASIS ???
6538
6539             if Operating_Mode = Check_Semantics and then ASIS_Mode then
6540                AtM_Nod :=
6541                  Make_Attribute_Definition_Clause (Loc,
6542                    Name       => New_Occurrence_Of (Base_Type (Rectype), Loc),
6543                    Chars      => Name_Alignment,
6544                    Expression => Relocate_Node (Expression (M)));
6545
6546                Set_From_At_Mod (AtM_Nod);
6547                Insert_After (N, AtM_Nod);
6548                Mod_Val := Get_Alignment_Value (Expression (AtM_Nod));
6549                Set_Mod_Clause (N, Empty);
6550
6551             else
6552                --  Get the alignment value to perform error checking
6553
6554                Mod_Val := Get_Alignment_Value (Expression (M));
6555             end if;
6556          end;
6557       end if;
6558
6559       --  For untagged types, clear any existing component clauses for the
6560       --  type. If the type is derived, this is what allows us to override
6561       --  a rep clause for the parent. For type extensions, the representation
6562       --  of the inherited components is inherited, so we want to keep previous
6563       --  component clauses for completeness.
6564
6565       if not Is_Tagged_Type (Rectype) then
6566          Comp := First_Component_Or_Discriminant (Rectype);
6567          while Present (Comp) loop
6568             Set_Component_Clause (Comp, Empty);
6569             Next_Component_Or_Discriminant (Comp);
6570          end loop;
6571       end if;
6572
6573       --  All done if no component clauses
6574
6575       CC := First (Component_Clauses (N));
6576
6577       if No (CC) then
6578          return;
6579       end if;
6580
6581       --  A representation like this applies to the base type
6582
6583       Set_Has_Record_Rep_Clause (Base_Type (Rectype));
6584       Set_Has_Non_Standard_Rep  (Base_Type (Rectype));
6585       Set_Has_Specified_Layout  (Base_Type (Rectype));
6586
6587       --  Process the component clauses
6588
6589       while Present (CC) loop
6590
6591          --  Pragma
6592
6593          if Nkind (CC) = N_Pragma then
6594             Analyze (CC);
6595
6596             --  The only pragma of interest is Complete_Representation
6597
6598             if Pragma_Name (CC) = Name_Complete_Representation then
6599                CR_Pragma := CC;
6600             end if;
6601
6602          --  Processing for real component clause
6603
6604          else
6605             Posit := Static_Integer (Position  (CC));
6606             Fbit  := Static_Integer (First_Bit (CC));
6607             Lbit  := Static_Integer (Last_Bit  (CC));
6608
6609             if Posit /= No_Uint
6610               and then Fbit /= No_Uint
6611               and then Lbit /= No_Uint
6612             then
6613                if Posit < 0 then
6614                   Error_Msg_N
6615                     ("position cannot be negative", Position (CC));
6616
6617                elsif Fbit < 0 then
6618                   Error_Msg_N
6619                     ("first bit cannot be negative", First_Bit (CC));
6620
6621                --  The Last_Bit specified in a component clause must not be
6622                --  less than the First_Bit minus one (RM-13.5.1(10)).
6623
6624                elsif Lbit < Fbit - 1 then
6625                   Error_Msg_N
6626                     ("last bit cannot be less than first bit minus one",
6627                      Last_Bit (CC));
6628
6629                --  Values look OK, so find the corresponding record component
6630                --  Even though the syntax allows an attribute reference for
6631                --  implementation-defined components, GNAT does not allow the
6632                --  tag to get an explicit position.
6633
6634                elsif Nkind (Component_Name (CC)) = N_Attribute_Reference then
6635                   if Attribute_Name (Component_Name (CC)) = Name_Tag then
6636                      Error_Msg_N ("position of tag cannot be specified", CC);
6637                   else
6638                      Error_Msg_N ("illegal component name", CC);
6639                   end if;
6640
6641                else
6642                   Comp := First_Entity (Rectype);
6643                   while Present (Comp) loop
6644                      exit when Chars (Comp) = Chars (Component_Name (CC));
6645                      Next_Entity (Comp);
6646                   end loop;
6647
6648                   if No (Comp) then
6649
6650                      --  Maybe component of base type that is absent from
6651                      --  statically constrained first subtype.
6652
6653                      Comp := First_Entity (Base_Type (Rectype));
6654                      while Present (Comp) loop
6655                         exit when Chars (Comp) = Chars (Component_Name (CC));
6656                         Next_Entity (Comp);
6657                      end loop;
6658                   end if;
6659
6660                   if No (Comp) then
6661                      Error_Msg_N
6662                        ("component clause is for non-existent field", CC);
6663
6664                   --  Ada 2012 (AI05-0026): Any name that denotes a
6665                   --  discriminant of an object of an unchecked union type
6666                   --  shall not occur within a record_representation_clause.
6667
6668                   --  The general restriction of using record rep clauses on
6669                   --  Unchecked_Union types has now been lifted. Since it is
6670                   --  possible to introduce a record rep clause which mentions
6671                   --  the discriminant of an Unchecked_Union in non-Ada 2012
6672                   --  code, this check is applied to all versions of the
6673                   --  language.
6674
6675                   elsif Ekind (Comp) = E_Discriminant
6676                     and then Is_Unchecked_Union (Rectype)
6677                   then
6678                      Error_Msg_N
6679                        ("cannot reference discriminant of unchecked union",
6680                         Component_Name (CC));
6681
6682                   elsif Is_Record_Extension and then Is_Inherited (Comp) then
6683                      Error_Msg_NE
6684                        ("component clause not allowed for inherited "
6685                         & "component&", CC, Comp);
6686
6687                   elsif Present (Component_Clause (Comp)) then
6688
6689                      --  Diagnose duplicate rep clause, or check consistency
6690                      --  if this is an inherited component. In a double fault,
6691                      --  there may be a duplicate inconsistent clause for an
6692                      --  inherited component.
6693
6694                      if Scope (Original_Record_Component (Comp)) = Rectype
6695                        or else Parent (Component_Clause (Comp)) = N
6696                      then
6697                         Error_Msg_Sloc := Sloc (Component_Clause (Comp));
6698                         Error_Msg_N ("component clause previously given#", CC);
6699
6700                      else
6701                         declare
6702                            Rep1 : constant Node_Id := Component_Clause (Comp);
6703                         begin
6704                            if Intval (Position (Rep1)) /=
6705                                                    Intval (Position (CC))
6706                              or else Intval (First_Bit (Rep1)) /=
6707                                                    Intval (First_Bit (CC))
6708                              or else Intval (Last_Bit (Rep1)) /=
6709                                                    Intval (Last_Bit (CC))
6710                            then
6711                               Error_Msg_N
6712                                 ("component clause inconsistent "
6713                                  & "with representation of ancestor", CC);
6714
6715                            elsif Warn_On_Redundant_Constructs then
6716                               Error_Msg_N
6717                                 ("?r?redundant confirming component clause "
6718                                  & "for component!", CC);
6719                            end if;
6720                         end;
6721                      end if;
6722
6723                   --  Normal case where this is the first component clause we
6724                   --  have seen for this entity, so set it up properly.
6725
6726                   else
6727                      --  Make reference for field in record rep clause and set
6728                      --  appropriate entity field in the field identifier.
6729
6730                      Generate_Reference
6731                        (Comp, Component_Name (CC), Set_Ref => False);
6732                      Set_Entity (Component_Name (CC), Comp);
6733
6734                      --  Update Fbit and Lbit to the actual bit number
6735
6736                      Fbit := Fbit + UI_From_Int (SSU) * Posit;
6737                      Lbit := Lbit + UI_From_Int (SSU) * Posit;
6738
6739                      if Has_Size_Clause (Rectype)
6740                        and then RM_Size (Rectype) <= Lbit
6741                      then
6742                         Error_Msg_N
6743                           ("bit number out of range of specified size",
6744                            Last_Bit (CC));
6745                      else
6746                         Set_Component_Clause     (Comp, CC);
6747                         Set_Component_Bit_Offset (Comp, Fbit);
6748                         Set_Esize                (Comp, 1 + (Lbit - Fbit));
6749                         Set_Normalized_First_Bit (Comp, Fbit mod SSU);
6750                         Set_Normalized_Position  (Comp, Fbit / SSU);
6751
6752                         if Warn_On_Overridden_Size
6753                           and then Has_Size_Clause (Etype (Comp))
6754                           and then RM_Size (Etype (Comp)) /= Esize (Comp)
6755                         then
6756                            Error_Msg_NE
6757                              ("?S?component size overrides size clause for&",
6758                               Component_Name (CC), Etype (Comp));
6759                         end if;
6760
6761                         --  This information is also set in the corresponding
6762                         --  component of the base type, found by accessing the
6763                         --  Original_Record_Component link if it is present.
6764
6765                         Ocomp := Original_Record_Component (Comp);
6766
6767                         if Hbit < Lbit then
6768                            Hbit := Lbit;
6769                         end if;
6770
6771                         Check_Size
6772                           (Component_Name (CC),
6773                            Etype (Comp),
6774                            Esize (Comp),
6775                            Biased);
6776
6777                         Set_Biased
6778                           (Comp, First_Node (CC), "component clause", Biased);
6779
6780                         if Present (Ocomp) then
6781                            Set_Component_Clause     (Ocomp, CC);
6782                            Set_Component_Bit_Offset (Ocomp, Fbit);
6783                            Set_Normalized_First_Bit (Ocomp, Fbit mod SSU);
6784                            Set_Normalized_Position  (Ocomp, Fbit / SSU);
6785                            Set_Esize                (Ocomp, 1 + (Lbit - Fbit));
6786
6787                            Set_Normalized_Position_Max
6788                              (Ocomp, Normalized_Position (Ocomp));
6789
6790                            --  Note: we don't use Set_Biased here, because we
6791                            --  already gave a warning above if needed, and we
6792                            --  would get a duplicate for the same name here.
6793
6794                            Set_Has_Biased_Representation
6795                              (Ocomp, Has_Biased_Representation (Comp));
6796                         end if;
6797
6798                         if Esize (Comp) < 0 then
6799                            Error_Msg_N ("component size is negative", CC);
6800                         end if;
6801                      end if;
6802                   end if;
6803                end if;
6804             end if;
6805          end if;
6806
6807          Next (CC);
6808       end loop;
6809
6810       --  Check missing components if Complete_Representation pragma appeared
6811
6812       if Present (CR_Pragma) then
6813          Comp := First_Component_Or_Discriminant (Rectype);
6814          while Present (Comp) loop
6815             if No (Component_Clause (Comp)) then
6816                Error_Msg_NE
6817                  ("missing component clause for &", CR_Pragma, Comp);
6818             end if;
6819
6820             Next_Component_Or_Discriminant (Comp);
6821          end loop;
6822
6823       --  Give missing components warning if required
6824
6825       elsif Warn_On_Unrepped_Components then
6826          declare
6827             Num_Repped_Components   : Nat := 0;
6828             Num_Unrepped_Components : Nat := 0;
6829
6830          begin
6831             --  First count number of repped and unrepped components
6832
6833             Comp := First_Component_Or_Discriminant (Rectype);
6834             while Present (Comp) loop
6835                if Present (Component_Clause (Comp)) then
6836                   Num_Repped_Components := Num_Repped_Components + 1;
6837                else
6838                   Num_Unrepped_Components := Num_Unrepped_Components + 1;
6839                end if;
6840
6841                Next_Component_Or_Discriminant (Comp);
6842             end loop;
6843
6844             --  We are only interested in the case where there is at least one
6845             --  unrepped component, and at least half the components have rep
6846             --  clauses. We figure that if less than half have them, then the
6847             --  partial rep clause is really intentional. If the component
6848             --  type has no underlying type set at this point (as for a generic
6849             --  formal type), we don't know enough to give a warning on the
6850             --  component.
6851
6852             if Num_Unrepped_Components > 0
6853               and then Num_Unrepped_Components < Num_Repped_Components
6854             then
6855                Comp := First_Component_Or_Discriminant (Rectype);
6856                while Present (Comp) loop
6857                   if No (Component_Clause (Comp))
6858                     and then Comes_From_Source (Comp)
6859                     and then Present (Underlying_Type (Etype (Comp)))
6860                     and then (Is_Scalar_Type (Underlying_Type (Etype (Comp)))
6861                                or else Size_Known_At_Compile_Time
6862                                          (Underlying_Type (Etype (Comp))))
6863                     and then not Has_Warnings_Off (Rectype)
6864
6865                     --  Ignore discriminant in unchecked union, since it is
6866                     --  not there, and cannot have a component clause.
6867
6868                     and then (not Is_Unchecked_Union (Rectype)
6869                                or else Ekind (Comp) /= E_Discriminant)
6870                   then
6871                      Error_Msg_Sloc := Sloc (Comp);
6872                      Error_Msg_NE
6873                        ("?C?no component clause given for & declared #",
6874                         N, Comp);
6875                   end if;
6876
6877                   Next_Component_Or_Discriminant (Comp);
6878                end loop;
6879             end if;
6880          end;
6881       end if;
6882    end Analyze_Record_Representation_Clause;
6883
6884    -------------------------------------
6885    -- Build_Discrete_Static_Predicate --
6886    -------------------------------------
6887
6888    procedure Build_Discrete_Static_Predicate
6889      (Typ  : Entity_Id;
6890       Expr : Node_Id;
6891       Nam  : Name_Id)
6892    is
6893       Loc : constant Source_Ptr := Sloc (Expr);
6894
6895       Non_Static : exception;
6896       --  Raised if something non-static is found
6897
6898       Btyp : constant Entity_Id := Base_Type (Typ);
6899
6900       BLo : constant Uint := Expr_Value (Type_Low_Bound  (Btyp));
6901       BHi : constant Uint := Expr_Value (Type_High_Bound (Btyp));
6902       --  Low bound and high bound value of base type of Typ
6903
6904       TLo : Uint;
6905       THi : Uint;
6906       --  Bounds for constructing the static predicate. We use the bound of the
6907       --  subtype if it is static, otherwise the corresponding base type bound.
6908       --  Note: a non-static subtype can have a static predicate.
6909
6910       type REnt is record
6911          Lo, Hi : Uint;
6912       end record;
6913       --  One entry in a Rlist value, a single REnt (range entry) value denotes
6914       --  one range from Lo to Hi. To represent a single value range Lo = Hi =
6915       --  value.
6916
6917       type RList is array (Nat range <>) of REnt;
6918       --  A list of ranges. The ranges are sorted in increasing order, and are
6919       --  disjoint (there is a gap of at least one value between each range in
6920       --  the table). A value is in the set of ranges in Rlist if it lies
6921       --  within one of these ranges.
6922
6923       False_Range : constant RList :=
6924         RList'(1 .. 0 => REnt'(No_Uint, No_Uint));
6925       --  An empty set of ranges represents a range list that can never be
6926       --  satisfied, since there are no ranges in which the value could lie,
6927       --  so it does not lie in any of them. False_Range is a canonical value
6928       --  for this empty set, but general processing should test for an Rlist
6929       --  with length zero (see Is_False predicate), since other null ranges
6930       --  may appear which must be treated as False.
6931
6932       True_Range : constant RList := RList'(1 => REnt'(BLo, BHi));
6933       --  Range representing True, value must be in the base range
6934
6935       function "and" (Left : RList; Right : RList) return RList;
6936       --  And's together two range lists, returning a range list. This is a set
6937       --  intersection operation.
6938
6939       function "or" (Left : RList; Right : RList) return RList;
6940       --  Or's together two range lists, returning a range list. This is a set
6941       --  union operation.
6942
6943       function "not" (Right : RList) return RList;
6944       --  Returns complement of a given range list, i.e. a range list
6945       --  representing all the values in TLo .. THi that are not in the input
6946       --  operand Right.
6947
6948       function Build_Val (V : Uint) return Node_Id;
6949       --  Return an analyzed N_Identifier node referencing this value, suitable
6950       --  for use as an entry in the Static_Discrte_Predicate list. This node
6951       --  is typed with the base type.
6952
6953       function Build_Range (Lo : Uint; Hi : Uint) return Node_Id;
6954       --  Return an analyzed N_Range node referencing this range, suitable for
6955       --  use as an entry in the Static_Discrete_Predicate list. This node is
6956       --  typed with the base type.
6957
6958       function Get_RList (Exp : Node_Id) return RList;
6959       --  This is a recursive routine that converts the given expression into a
6960       --  list of ranges, suitable for use in building the static predicate.
6961
6962       function Is_False (R : RList) return Boolean;
6963       pragma Inline (Is_False);
6964       --  Returns True if the given range list is empty, and thus represents a
6965       --  False list of ranges that can never be satisfied.
6966
6967       function Is_True (R : RList) return Boolean;
6968       --  Returns True if R trivially represents the True predicate by having a
6969       --  single range from BLo to BHi.
6970
6971       function Is_Type_Ref (N : Node_Id) return Boolean;
6972       pragma Inline (Is_Type_Ref);
6973       --  Returns if True if N is a reference to the type for the predicate in
6974       --  the expression (i.e. if it is an identifier whose Chars field matches
6975       --  the Nam given in the call). N must not be parenthesized, if the type
6976       --  name appears in parens, this routine will return False.
6977
6978       function Lo_Val (N : Node_Id) return Uint;
6979       --  Given an entry from a Static_Discrete_Predicate list that is either
6980       --  a static expression or static range, gets either the expression value
6981       --  or the low bound of the range.
6982
6983       function Hi_Val (N : Node_Id) return Uint;
6984       --  Given an entry from a Static_Discrete_Predicate list that is either
6985       --  a static expression or static range, gets either the expression value
6986       --  or the high bound of the range.
6987
6988       function Membership_Entry (N : Node_Id) return RList;
6989       --  Given a single membership entry (range, value, or subtype), returns
6990       --  the corresponding range list. Raises Static_Error if not static.
6991
6992       function Membership_Entries (N : Node_Id) return RList;
6993       --  Given an element on an alternatives list of a membership operation,
6994       --  returns the range list corresponding to this entry and all following
6995       --  entries (i.e. returns the "or" of this list of values).
6996
6997       function Stat_Pred (Typ : Entity_Id) return RList;
6998       --  Given a type, if it has a static predicate, then return the predicate
6999       --  as a range list, otherwise raise Non_Static.
7000
7001       -----------
7002       -- "and" --
7003       -----------
7004
7005       function "and" (Left : RList; Right : RList) return RList is
7006          FEnt : REnt;
7007          --  First range of result
7008
7009          SLeft : Nat := Left'First;
7010          --  Start of rest of left entries
7011
7012          SRight : Nat := Right'First;
7013          --  Start of rest of right entries
7014
7015       begin
7016          --  If either range is True, return the other
7017
7018          if Is_True (Left) then
7019             return Right;
7020          elsif Is_True (Right) then
7021             return Left;
7022          end if;
7023
7024          --  If either range is False, return False
7025
7026          if Is_False (Left) or else Is_False (Right) then
7027             return False_Range;
7028          end if;
7029
7030          --  Loop to remove entries at start that are disjoint, and thus just
7031          --  get discarded from the result entirely.
7032
7033          loop
7034             --  If no operands left in either operand, result is false
7035
7036             if SLeft > Left'Last or else SRight > Right'Last then
7037                return False_Range;
7038
7039             --  Discard first left operand entry if disjoint with right
7040
7041             elsif Left (SLeft).Hi < Right (SRight).Lo then
7042                SLeft := SLeft + 1;
7043
7044             --  Discard first right operand entry if disjoint with left
7045
7046             elsif Right (SRight).Hi < Left (SLeft).Lo then
7047                SRight := SRight + 1;
7048
7049             --  Otherwise we have an overlapping entry
7050
7051             else
7052                exit;
7053             end if;
7054          end loop;
7055
7056          --  Now we have two non-null operands, and first entries overlap. The
7057          --  first entry in the result will be the overlapping part of these
7058          --  two entries.
7059
7060          FEnt := REnt'(Lo => UI_Max (Left (SLeft).Lo, Right (SRight).Lo),
7061                        Hi => UI_Min (Left (SLeft).Hi, Right (SRight).Hi));
7062
7063          --  Now we can remove the entry that ended at a lower value, since its
7064          --  contribution is entirely contained in Fent.
7065
7066          if Left (SLeft).Hi <= Right (SRight).Hi then
7067             SLeft := SLeft + 1;
7068          else
7069             SRight := SRight + 1;
7070          end if;
7071
7072          --  Compute result by concatenating this first entry with the "and" of
7073          --  the remaining parts of the left and right operands. Note that if
7074          --  either of these is empty, "and" will yield empty, so that we will
7075          --  end up with just Fent, which is what we want in that case.
7076
7077          return
7078            FEnt & (Left (SLeft .. Left'Last) and Right (SRight .. Right'Last));
7079       end "and";
7080
7081       -----------
7082       -- "not" --
7083       -----------
7084
7085       function "not" (Right : RList) return RList is
7086       begin
7087          --  Return True if False range
7088
7089          if Is_False (Right) then
7090             return True_Range;
7091          end if;
7092
7093          --  Return False if True range
7094
7095          if Is_True (Right) then
7096             return False_Range;
7097          end if;
7098
7099          --  Here if not trivial case
7100
7101          declare
7102             Result : RList (1 .. Right'Length + 1);
7103             --  May need one more entry for gap at beginning and end
7104
7105             Count : Nat := 0;
7106             --  Number of entries stored in Result
7107
7108          begin
7109             --  Gap at start
7110
7111             if Right (Right'First).Lo > TLo then
7112                Count := Count + 1;
7113                Result (Count) := REnt'(TLo, Right (Right'First).Lo - 1);
7114             end if;
7115
7116             --  Gaps between ranges
7117
7118             for J in Right'First .. Right'Last - 1 loop
7119                Count := Count + 1;
7120                Result (Count) := REnt'(Right (J).Hi + 1, Right (J + 1).Lo - 1);
7121             end loop;
7122
7123             --  Gap at end
7124
7125             if Right (Right'Last).Hi < THi then
7126                Count := Count + 1;
7127                Result (Count) := REnt'(Right (Right'Last).Hi + 1, THi);
7128             end if;
7129
7130             return Result (1 .. Count);
7131          end;
7132       end "not";
7133
7134       ----------
7135       -- "or" --
7136       ----------
7137
7138       function "or" (Left : RList; Right : RList) return RList is
7139          FEnt : REnt;
7140          --  First range of result
7141
7142          SLeft : Nat := Left'First;
7143          --  Start of rest of left entries
7144
7145          SRight : Nat := Right'First;
7146          --  Start of rest of right entries
7147
7148       begin
7149          --  If either range is True, return True
7150
7151          if Is_True (Left) or else Is_True (Right) then
7152             return True_Range;
7153          end if;
7154
7155          --  If either range is False (empty), return the other
7156
7157          if Is_False (Left) then
7158             return Right;
7159          elsif Is_False (Right) then
7160             return Left;
7161          end if;
7162
7163          --  Initialize result first entry from left or right operand depending
7164          --  on which starts with the lower range.
7165
7166          if Left (SLeft).Lo < Right (SRight).Lo then
7167             FEnt := Left (SLeft);
7168             SLeft := SLeft + 1;
7169          else
7170             FEnt := Right (SRight);
7171             SRight := SRight + 1;
7172          end if;
7173
7174          --  This loop eats ranges from left and right operands that are
7175          --  contiguous with the first range we are gathering.
7176
7177          loop
7178             --  Eat first entry in left operand if contiguous or overlapped by
7179             --  gathered first operand of result.
7180
7181             if SLeft <= Left'Last
7182               and then Left (SLeft).Lo <= FEnt.Hi + 1
7183             then
7184                FEnt.Hi := UI_Max (FEnt.Hi, Left (SLeft).Hi);
7185                SLeft := SLeft + 1;
7186
7187             --  Eat first entry in right operand if contiguous or overlapped by
7188             --  gathered right operand of result.
7189
7190             elsif SRight <= Right'Last
7191               and then Right (SRight).Lo <= FEnt.Hi + 1
7192             then
7193                FEnt.Hi := UI_Max (FEnt.Hi, Right (SRight).Hi);
7194                SRight := SRight + 1;
7195
7196             --  All done if no more entries to eat
7197
7198             else
7199                exit;
7200             end if;
7201          end loop;
7202
7203          --  Obtain result as the first entry we just computed, concatenated
7204          --  to the "or" of the remaining results (if one operand is empty,
7205          --  this will just concatenate with the other
7206
7207          return
7208            FEnt & (Left (SLeft .. Left'Last) or Right (SRight .. Right'Last));
7209       end "or";
7210
7211       -----------------
7212       -- Build_Range --
7213       -----------------
7214
7215       function Build_Range (Lo : Uint; Hi : Uint) return Node_Id is
7216          Result : Node_Id;
7217       begin
7218          Result :=
7219            Make_Range (Loc,
7220               Low_Bound  => Build_Val (Lo),
7221               High_Bound => Build_Val (Hi));
7222          Set_Etype (Result, Btyp);
7223          Set_Analyzed (Result);
7224          return Result;
7225       end Build_Range;
7226
7227       ---------------
7228       -- Build_Val --
7229       ---------------
7230
7231       function Build_Val (V : Uint) return Node_Id is
7232          Result : Node_Id;
7233
7234       begin
7235          if Is_Enumeration_Type (Typ) then
7236             Result := Get_Enum_Lit_From_Pos (Typ, V, Loc);
7237          else
7238             Result := Make_Integer_Literal (Loc, V);
7239          end if;
7240
7241          Set_Etype (Result, Btyp);
7242          Set_Is_Static_Expression (Result);
7243          Set_Analyzed (Result);
7244          return Result;
7245       end Build_Val;
7246
7247       ---------------
7248       -- Get_RList --
7249       ---------------
7250
7251       function Get_RList (Exp : Node_Id) return RList is
7252          Op  : Node_Kind;
7253          Val : Uint;
7254
7255       begin
7256          --  Static expression can only be true or false
7257
7258          if Is_OK_Static_Expression (Exp) then
7259             if Expr_Value (Exp) = 0 then
7260                return False_Range;
7261             else
7262                return True_Range;
7263             end if;
7264          end if;
7265
7266          --  Otherwise test node type
7267
7268          Op := Nkind (Exp);
7269
7270          case Op is
7271
7272             --  And
7273
7274             when N_Op_And | N_And_Then =>
7275                return Get_RList (Left_Opnd (Exp))
7276                         and
7277                       Get_RList (Right_Opnd (Exp));
7278
7279             --  Or
7280
7281             when N_Op_Or | N_Or_Else =>
7282                return Get_RList (Left_Opnd (Exp))
7283                         or
7284                       Get_RList (Right_Opnd (Exp));
7285
7286             --  Not
7287
7288             when N_Op_Not =>
7289                return not Get_RList (Right_Opnd (Exp));
7290
7291                --  Comparisons of type with static value
7292
7293             when N_Op_Compare =>
7294
7295                --  Type is left operand
7296
7297                if Is_Type_Ref (Left_Opnd (Exp))
7298                  and then Is_OK_Static_Expression (Right_Opnd (Exp))
7299                then
7300                   Val := Expr_Value (Right_Opnd (Exp));
7301
7302                --  Typ is right operand
7303
7304                elsif Is_Type_Ref (Right_Opnd (Exp))
7305                  and then Is_OK_Static_Expression (Left_Opnd (Exp))
7306                then
7307                   Val := Expr_Value (Left_Opnd (Exp));
7308
7309                   --  Invert sense of comparison
7310
7311                   case Op is
7312                      when N_Op_Gt => Op := N_Op_Lt;
7313                      when N_Op_Lt => Op := N_Op_Gt;
7314                      when N_Op_Ge => Op := N_Op_Le;
7315                      when N_Op_Le => Op := N_Op_Ge;
7316                      when others  => null;
7317                   end case;
7318
7319                --  Other cases are non-static
7320
7321                else
7322                   raise Non_Static;
7323                end if;
7324
7325                --  Construct range according to comparison operation
7326
7327                case Op is
7328                   when N_Op_Eq =>
7329                      return RList'(1 => REnt'(Val, Val));
7330
7331                   when N_Op_Ge =>
7332                      return RList'(1 => REnt'(Val, BHi));
7333
7334                   when N_Op_Gt =>
7335                      return RList'(1 => REnt'(Val + 1, BHi));
7336
7337                   when N_Op_Le =>
7338                      return RList'(1 => REnt'(BLo, Val));
7339
7340                   when N_Op_Lt =>
7341                      return RList'(1 => REnt'(BLo, Val - 1));
7342
7343                   when N_Op_Ne =>
7344                      return RList'(REnt'(BLo, Val - 1), REnt'(Val + 1, BHi));
7345
7346                   when others  =>
7347                      raise Program_Error;
7348                end case;
7349
7350             --  Membership (IN)
7351
7352             when N_In =>
7353                if not Is_Type_Ref (Left_Opnd (Exp)) then
7354                   raise Non_Static;
7355                end if;
7356
7357                if Present (Right_Opnd (Exp)) then
7358                   return Membership_Entry (Right_Opnd (Exp));
7359                else
7360                   return Membership_Entries (First (Alternatives (Exp)));
7361                end if;
7362
7363             --  Negative membership (NOT IN)
7364
7365             when N_Not_In =>
7366                if not Is_Type_Ref (Left_Opnd (Exp)) then
7367                   raise Non_Static;
7368                end if;
7369
7370                if Present (Right_Opnd (Exp)) then
7371                   return not Membership_Entry (Right_Opnd (Exp));
7372                else
7373                   return not Membership_Entries (First (Alternatives (Exp)));
7374                end if;
7375
7376             --  Function call, may be call to static predicate
7377
7378             when N_Function_Call =>
7379                if Is_Entity_Name (Name (Exp)) then
7380                   declare
7381                      Ent : constant Entity_Id := Entity (Name (Exp));
7382                   begin
7383                      if Is_Predicate_Function (Ent)
7384                           or else
7385                         Is_Predicate_Function_M (Ent)
7386                      then
7387                         return Stat_Pred (Etype (First_Formal (Ent)));
7388                      end if;
7389                   end;
7390                end if;
7391
7392                --  Other function call cases are non-static
7393
7394                raise Non_Static;
7395
7396             --  Qualified expression, dig out the expression
7397
7398             when N_Qualified_Expression =>
7399                return Get_RList (Expression (Exp));
7400
7401             when N_Case_Expression =>
7402                declare
7403                   Alt     : Node_Id;
7404                   Choices : List_Id;
7405                   Dep     : Node_Id;
7406
7407                begin
7408                   if not Is_Entity_Name (Expression (Expr))
7409                     or else Etype (Expression (Expr)) /= Typ
7410                   then
7411                      Error_Msg_N
7412                        ("expression must denaote subtype", Expression (Expr));
7413                      return False_Range;
7414                   end if;
7415
7416                   --  Collect discrete choices in all True alternatives
7417
7418                   Choices := New_List;
7419                   Alt := First (Alternatives (Exp));
7420                   while Present (Alt) loop
7421                      Dep := Expression (Alt);
7422
7423                      if not Is_OK_Static_Expression (Dep) then
7424                         raise Non_Static;
7425
7426                      elsif Is_True (Expr_Value (Dep)) then
7427                         Append_List_To (Choices,
7428                           New_Copy_List (Discrete_Choices (Alt)));
7429                      end if;
7430
7431                      Next (Alt);
7432                   end loop;
7433
7434                   return Membership_Entries (First (Choices));
7435                end;
7436
7437             --  Expression with actions: if no actions, dig out expression
7438
7439             when N_Expression_With_Actions =>
7440                if Is_Empty_List (Actions (Exp)) then
7441                   return Get_RList (Expression (Exp));
7442                else
7443                   raise Non_Static;
7444                end if;
7445
7446             --  Xor operator
7447
7448             when N_Op_Xor =>
7449                return (Get_RList (Left_Opnd (Exp))
7450                         and not Get_RList (Right_Opnd (Exp)))
7451                  or   (Get_RList (Right_Opnd (Exp))
7452                         and not Get_RList (Left_Opnd (Exp)));
7453
7454             --  Any other node type is non-static
7455
7456             when others =>
7457                raise Non_Static;
7458          end case;
7459       end Get_RList;
7460
7461       ------------
7462       -- Hi_Val --
7463       ------------
7464
7465       function Hi_Val (N : Node_Id) return Uint is
7466       begin
7467          if Is_OK_Static_Expression (N) then
7468             return Expr_Value (N);
7469          else
7470             pragma Assert (Nkind (N) = N_Range);
7471             return Expr_Value (High_Bound (N));
7472          end if;
7473       end Hi_Val;
7474
7475       --------------
7476       -- Is_False --
7477       --------------
7478
7479       function Is_False (R : RList) return Boolean is
7480       begin
7481          return R'Length = 0;
7482       end Is_False;
7483
7484       -------------
7485       -- Is_True --
7486       -------------
7487
7488       function Is_True (R : RList) return Boolean is
7489       begin
7490          return R'Length = 1
7491            and then R (R'First).Lo = BLo
7492            and then R (R'First).Hi = BHi;
7493       end Is_True;
7494
7495       -----------------
7496       -- Is_Type_Ref --
7497       -----------------
7498
7499       function Is_Type_Ref (N : Node_Id) return Boolean is
7500       begin
7501          return Nkind (N) = N_Identifier
7502            and then Chars (N) = Nam
7503            and then Paren_Count (N) = 0;
7504       end Is_Type_Ref;
7505
7506       ------------
7507       -- Lo_Val --
7508       ------------
7509
7510       function Lo_Val (N : Node_Id) return Uint is
7511       begin
7512          if Is_OK_Static_Expression (N) then
7513             return Expr_Value (N);
7514          else
7515             pragma Assert (Nkind (N) = N_Range);
7516             return Expr_Value (Low_Bound (N));
7517          end if;
7518       end Lo_Val;
7519
7520       ------------------------
7521       -- Membership_Entries --
7522       ------------------------
7523
7524       function Membership_Entries (N : Node_Id) return RList is
7525       begin
7526          if No (Next (N)) then
7527             return Membership_Entry (N);
7528          else
7529             return Membership_Entry (N) or Membership_Entries (Next (N));
7530          end if;
7531       end Membership_Entries;
7532
7533       ----------------------
7534       -- Membership_Entry --
7535       ----------------------
7536
7537       function Membership_Entry (N : Node_Id) return RList is
7538          Val : Uint;
7539          SLo : Uint;
7540          SHi : Uint;
7541
7542       begin
7543          --  Range case
7544
7545          if Nkind (N) = N_Range then
7546             if not Is_OK_Static_Expression (Low_Bound  (N))
7547                  or else
7548                not Is_OK_Static_Expression (High_Bound (N))
7549             then
7550                raise Non_Static;
7551             else
7552                SLo := Expr_Value (Low_Bound  (N));
7553                SHi := Expr_Value (High_Bound (N));
7554                return RList'(1 => REnt'(SLo, SHi));
7555             end if;
7556
7557          --  Static expression case
7558
7559          elsif Is_OK_Static_Expression (N) then
7560             Val := Expr_Value (N);
7561             return RList'(1 => REnt'(Val, Val));
7562
7563          --  Identifier (other than static expression) case
7564
7565          else pragma Assert (Nkind (N) = N_Identifier);
7566
7567             --  Type case
7568
7569             if Is_Type (Entity (N)) then
7570
7571                --  If type has predicates, process them
7572
7573                if Has_Predicates (Entity (N)) then
7574                   return Stat_Pred (Entity (N));
7575
7576                --  For static subtype without predicates, get range
7577
7578                elsif Is_OK_Static_Subtype (Entity (N)) then
7579                   SLo := Expr_Value (Type_Low_Bound  (Entity (N)));
7580                   SHi := Expr_Value (Type_High_Bound (Entity (N)));
7581                   return RList'(1 => REnt'(SLo, SHi));
7582
7583                --  Any other type makes us non-static
7584
7585                else
7586                   raise Non_Static;
7587                end if;
7588
7589             --  Any other kind of identifier in predicate (e.g. a non-static
7590             --  expression value) means this is not a static predicate.
7591
7592             else
7593                raise Non_Static;
7594             end if;
7595          end if;
7596       end Membership_Entry;
7597
7598       ---------------
7599       -- Stat_Pred --
7600       ---------------
7601
7602       function Stat_Pred (Typ : Entity_Id) return RList is
7603       begin
7604          --  Not static if type does not have static predicates
7605
7606          if not Has_Static_Predicate (Typ) then
7607             raise Non_Static;
7608          end if;
7609
7610          --  Otherwise we convert the predicate list to a range list
7611
7612          declare
7613             Spred  : constant List_Id := Static_Discrete_Predicate (Typ);
7614             Result : RList (1 .. List_Length (Spred));
7615             P      : Node_Id;
7616
7617          begin
7618             P := First (Static_Discrete_Predicate (Typ));
7619             for J in Result'Range loop
7620                Result (J) := REnt'(Lo_Val (P), Hi_Val (P));
7621                Next (P);
7622             end loop;
7623
7624             return Result;
7625          end;
7626       end Stat_Pred;
7627
7628    --  Start of processing for Build_Discrete_Static_Predicate
7629
7630    begin
7631       --  Establish  bounds for the predicate
7632
7633       if Compile_Time_Known_Value (Type_Low_Bound (Typ)) then
7634          TLo := Expr_Value (Type_Low_Bound (Typ));
7635       else
7636          TLo := BLo;
7637       end if;
7638
7639       if Compile_Time_Known_Value (Type_High_Bound (Typ)) then
7640          THi := Expr_Value (Type_High_Bound (Typ));
7641       else
7642          THi := BHi;
7643       end if;
7644
7645       --  Analyze the expression to see if it is a static predicate
7646
7647       declare
7648          Ranges : constant RList := Get_RList (Expr);
7649          --  Range list from expression if it is static
7650
7651          Plist : List_Id;
7652
7653       begin
7654          --  Convert range list into a form for the static predicate. In the
7655          --  Ranges array, we just have raw ranges, these must be converted
7656          --  to properly typed and analyzed static expressions or range nodes.
7657
7658          --  Note: here we limit ranges to the ranges of the subtype, so that
7659          --  a predicate is always false for values outside the subtype. That
7660          --  seems fine, such values are invalid anyway, and considering them
7661          --  to fail the predicate seems allowed and friendly, and furthermore
7662          --  simplifies processing for case statements and loops.
7663
7664          Plist := New_List;
7665
7666          for J in Ranges'Range loop
7667             declare
7668                Lo : Uint := Ranges (J).Lo;
7669                Hi : Uint := Ranges (J).Hi;
7670
7671             begin
7672                --  Ignore completely out of range entry
7673
7674                if Hi < TLo or else Lo > THi then
7675                   null;
7676
7677                --  Otherwise process entry
7678
7679                else
7680                   --  Adjust out of range value to subtype range
7681
7682                   if Lo < TLo then
7683                      Lo := TLo;
7684                   end if;
7685
7686                   if Hi > THi then
7687                      Hi := THi;
7688                   end if;
7689
7690                   --  Convert range into required form
7691
7692                   Append_To (Plist, Build_Range (Lo, Hi));
7693                end if;
7694             end;
7695          end loop;
7696
7697          --  Processing was successful and all entries were static, so now we
7698          --  can store the result as the predicate list.
7699
7700          Set_Static_Discrete_Predicate (Typ, Plist);
7701
7702          --  The processing for static predicates put the expression into
7703          --  canonical form as a series of ranges. It also eliminated
7704          --  duplicates and collapsed and combined ranges. We might as well
7705          --  replace the alternatives list of the right operand of the
7706          --  membership test with the static predicate list, which will
7707          --  usually be more efficient.
7708
7709          declare
7710             New_Alts : constant List_Id := New_List;
7711             Old_Node : Node_Id;
7712             New_Node : Node_Id;
7713
7714          begin
7715             Old_Node := First (Plist);
7716             while Present (Old_Node) loop
7717                New_Node := New_Copy (Old_Node);
7718
7719                if Nkind (New_Node) = N_Range then
7720                   Set_Low_Bound  (New_Node, New_Copy (Low_Bound  (Old_Node)));
7721                   Set_High_Bound (New_Node, New_Copy (High_Bound (Old_Node)));
7722                end if;
7723
7724                Append_To (New_Alts, New_Node);
7725                Next (Old_Node);
7726             end loop;
7727
7728             --  If empty list, replace by False
7729
7730             if Is_Empty_List (New_Alts) then
7731                Rewrite (Expr, New_Occurrence_Of (Standard_False, Loc));
7732
7733                --  Else replace by set membership test
7734
7735             else
7736                Rewrite (Expr,
7737                  Make_In (Loc,
7738                    Left_Opnd    => Make_Identifier (Loc, Nam),
7739                    Right_Opnd   => Empty,
7740                    Alternatives => New_Alts));
7741
7742                --  Resolve new expression in function context
7743
7744                Install_Formals (Predicate_Function (Typ));
7745                Push_Scope (Predicate_Function (Typ));
7746                Analyze_And_Resolve (Expr, Standard_Boolean);
7747                Pop_Scope;
7748             end if;
7749          end;
7750       end;
7751
7752       --  If non-static, return doing nothing
7753
7754    exception
7755       when Non_Static =>
7756          return;
7757    end Build_Discrete_Static_Predicate;
7758
7759    -------------------------------------------
7760    -- Build_Invariant_Procedure_Declaration --
7761    -------------------------------------------
7762
7763    function Build_Invariant_Procedure_Declaration
7764      (Typ : Entity_Id) return Node_Id
7765    is
7766       GM     : constant Ghost_Mode_Type := Ghost_Mode;
7767       Loc    : constant Source_Ptr := Sloc (Typ);
7768       Decl   : Node_Id;
7769       Obj_Id : Entity_Id;
7770       SId    : Entity_Id;
7771
7772    begin
7773       --  Check for duplicate definiations
7774
7775       if Has_Invariants (Typ) and then Present (Invariant_Procedure (Typ)) then
7776          return Empty;
7777       end if;
7778
7779       --  The related type may be subject to pragma Ghost with policy Ignore.
7780       --  Set the mode now to ensure that the predicate functions are properly
7781       --  flagged as ignored Ghost.
7782
7783       Set_Ghost_Mode_From_Entity (Typ);
7784
7785       SId :=
7786         Make_Defining_Identifier (Loc,
7787           Chars => New_External_Name (Chars (Typ), "Invariant"));
7788       Set_Has_Invariants (Typ);
7789       Set_Ekind (SId, E_Procedure);
7790       Set_Etype (SId, Standard_Void_Type);
7791       Set_Is_Invariant_Procedure (SId);
7792       Set_Invariant_Procedure (Typ, SId);
7793
7794       --  Mark the invariant procedure explicitly as Ghost because it does not
7795       --  come from source.
7796
7797       if Ghost_Mode > None then
7798          Set_Is_Ghost_Entity (SId);
7799       end if;
7800
7801       Obj_Id := Make_Defining_Identifier (Loc, New_Internal_Name ('I'));
7802       Set_Etype (Obj_Id, Typ);
7803
7804       Decl :=
7805         Make_Subprogram_Declaration (Loc,
7806           Make_Procedure_Specification (Loc,
7807             Defining_Unit_Name       => SId,
7808             Parameter_Specifications => New_List (
7809               Make_Parameter_Specification (Loc,
7810                 Defining_Identifier => Obj_Id,
7811                 Parameter_Type      => New_Occurrence_Of (Typ, Loc)))));
7812
7813       --  Restore the original Ghost mode once analysis and expansion have
7814       --  taken place.
7815
7816       Ghost_Mode := GM;
7817
7818       return Decl;
7819    end Build_Invariant_Procedure_Declaration;
7820
7821    -------------------------------
7822    -- Build_Invariant_Procedure --
7823    -------------------------------
7824
7825    --  The procedure that is constructed here has the form
7826
7827    --  procedure typInvariant (Ixxx : typ) is
7828    --  begin
7829    --     pragma Check (Invariant, exp, "failed invariant from xxx");
7830    --     pragma Check (Invariant, exp, "failed invariant from xxx");
7831    --     ...
7832    --     pragma Check (Invariant, exp, "failed inherited invariant from xxx");
7833    --     ...
7834    --  end typInvariant;
7835
7836    procedure Build_Invariant_Procedure (Typ : Entity_Id; N : Node_Id) is
7837       Priv_Decls : constant List_Id := Private_Declarations (N);
7838       Vis_Decls  : constant List_Id := Visible_Declarations (N);
7839
7840       Loc   : constant Source_Ptr := Sloc (Typ);
7841       Stmts : List_Id;
7842       Spec  : Node_Id;
7843       SId   : Entity_Id;
7844       PDecl : Node_Id;
7845       PBody : Node_Id;
7846
7847       Object_Entity : Node_Id;
7848       --  The entity of the formal for the procedure
7849
7850       Object_Name : Name_Id;
7851       --  Name for argument of invariant procedure
7852
7853       procedure Add_Invariants (T : Entity_Id; Inherit : Boolean);
7854       --  Appends statements to Stmts for any invariants in the rep item chain
7855       --  of the given type. If Inherit is False, then we only process entries
7856       --  on the chain for the type Typ. If Inherit is True, then we ignore any
7857       --  Invariant aspects, but we process all Invariant'Class aspects, adding
7858       --  "inherited" to the exception message and generating an informational
7859       --  message about the inheritance of an invariant.
7860
7861       --------------------
7862       -- Add_Invariants --
7863       --------------------
7864
7865       procedure Add_Invariants (T : Entity_Id; Inherit : Boolean) is
7866          procedure Add_Invariant (Prag : Node_Id);
7867          --  Create a runtime check to verify the exression of invariant pragma
7868          --  Prag. All generated code is added to list Stmts.
7869
7870          -------------------
7871          -- Add_Invariant --
7872          -------------------
7873
7874          procedure Add_Invariant (Prag : Node_Id) is
7875             procedure Replace_Type_Reference (N : Node_Id);
7876             --  Replace a single occurrence N of the subtype name with a
7877             --  reference to the formal of the predicate function. N can be an
7878             --  identifier referencing the subtype, or a selected component,
7879             --  representing an appropriately qualified occurrence of the
7880             --  subtype name.
7881
7882             procedure Replace_Type_References is
7883               new Replace_Type_References_Generic (Replace_Type_Reference);
7884             --  Traverse an expression replacing all occurrences of the subtype
7885             --  name with appropriate references to the formal of the predicate
7886             --  function. Note that we must ensure that the type and entity
7887             --  information is properly set in the replacement node, since we
7888             --  will do a Preanalyze call of this expression without proper
7889             --  visibility of the procedure argument.
7890
7891             ----------------------------
7892             -- Replace_Type_Reference --
7893             ----------------------------
7894
7895             --  Note: See comments in Add_Predicates.Replace_Type_Reference
7896             --  regarding handling of Sloc and Comes_From_Source.
7897
7898             procedure Replace_Type_Reference (N : Node_Id) is
7899                Nloc : constant Source_Ptr := Sloc (N);
7900
7901             begin
7902                --  Add semantic information to node to be rewritten, for ASIS
7903                --  navigation needs.
7904
7905                if Nkind (N) = N_Identifier then
7906                   Set_Entity (N, T);
7907                   Set_Etype  (N, T);
7908
7909                elsif Nkind (N) = N_Selected_Component then
7910                   Analyze (Prefix (N));
7911                   Set_Entity (Selector_Name (N), T);
7912                   Set_Etype  (Selector_Name (N), T);
7913                end if;
7914
7915                --  Invariant'Class, replace with T'Class (obj)
7916
7917                if Class_Present (Prag) then
7918
7919                   --  In ASIS mode, an inherited item is already analyzed,
7920                   --  and the replacement has been done, so do not repeat
7921                   --  the transformation to prevent a malformed tree.
7922
7923                   if ASIS_Mode
7924                     and then Nkind (Parent (N)) = N_Attribute_Reference
7925                     and then Attribute_Name (Parent (N)) = Name_Class
7926                   then
7927                      null;
7928
7929                   else
7930                      Rewrite (N,
7931                        Make_Type_Conversion (Nloc,
7932                          Subtype_Mark =>
7933                            Make_Attribute_Reference (Nloc,
7934                              Prefix         => New_Occurrence_Of (T, Nloc),
7935                              Attribute_Name => Name_Class),
7936                          Expression   => Make_Identifier (Nloc, Object_Name)));
7937
7938                      Set_Entity (Expression (N), Object_Entity);
7939                      Set_Etype  (Expression (N), Typ);
7940                   end if;
7941
7942                --  Invariant, replace with obj
7943
7944                else
7945                   Rewrite (N, Make_Identifier (Nloc, Object_Name));
7946                   Set_Entity (N, Object_Entity);
7947                   Set_Etype  (N, Typ);
7948                end if;
7949
7950                Set_Comes_From_Source (N, True);
7951             end Replace_Type_Reference;
7952
7953             --  Local variables
7954
7955             Asp   : constant Node_Id    := Corresponding_Aspect (Prag);
7956             Nam   : constant Name_Id    := Original_Aspect_Pragma_Name (Prag);
7957             Ploc  : constant Source_Ptr := Sloc (Prag);
7958             Arg1  : Node_Id;
7959             Arg2  : Node_Id;
7960             Arg3  : Node_Id;
7961             Assoc : List_Id;
7962             Expr  : Node_Id;
7963             Str   : String_Id;
7964
7965          --  Start of processing for Add_Invariant
7966
7967          begin
7968             --  Extract the arguments of the invariant pragma
7969
7970             Arg1 := First (Pragma_Argument_Associations (Prag));
7971             Arg2 := Next (Arg1);
7972             Arg3 := Next (Arg2);
7973
7974             Arg1 := Get_Pragma_Arg (Arg1);
7975             Arg2 := Get_Pragma_Arg (Arg2);
7976
7977             --  The caller requests processing of all Invariant'Class pragmas,
7978             --  but the current pragma does not fall in this category. Return
7979             --  as there is nothing left to do.
7980
7981             if Inherit then
7982                if not Class_Present (Prag) then
7983                   return;
7984                end if;
7985
7986             --  Otherwise the pragma must apply to the current type
7987
7988             elsif Entity (Arg1) /= T then
7989                return;
7990             end if;
7991
7992             Expr := New_Copy_Tree (Arg2);
7993
7994             --  Replace all occurrences of the type's name with references to
7995             --  the formal parameter of the invariant procedure.
7996
7997             Replace_Type_References (Expr, T);
7998
7999             --  If the invariant pragma comes from an aspect, replace the saved
8000             --  expression because we need the subtype references replaced for
8001             --  the calls to Preanalyze_Spec_Expression in Check_Aspect_At_xxx
8002             --  routines.
8003
8004             if Present (Asp) then
8005                Set_Entity (Identifier (Asp), New_Copy_Tree (Expr));
8006             end if;
8007
8008             --  Preanalyze the invariant expression to capture the visibility
8009             --  of the proper package part. In general the expression is not
8010             --  fully analyzed until the body of the invariant procedure is
8011             --  analyzed at the end of the private part, but that yields the
8012             --  wrong visibility.
8013
8014             --  Historic note: we used to set N as the parent, but a package
8015             --  specification as the parent of an expression is bizarre.
8016
8017             Set_Parent (Expr, Parent (Arg2));
8018             Preanalyze_Assert_Expression (Expr, Any_Boolean);
8019
8020             --  A class-wide invariant may be inherited in a separate unit,
8021             --  where the corresponding expression cannot be resolved by
8022             --  visibility, because it refers to a local function. Propagate
8023             --  semantic information to the original representation item, to
8024             --  be used when an invariant procedure for a derived type is
8025             --  constructed.
8026
8027             --  ??? Unclear how to handle class-wide invariants that are not
8028             --  function calls.
8029
8030             if not Inherit
8031               and then Class_Present (Prag)
8032               and then Nkind (Expr) = N_Function_Call
8033               and then Nkind (Arg2) = N_Indexed_Component
8034             then
8035                Rewrite (Arg2,
8036                  Make_Function_Call (Ploc,
8037                    Name                   =>
8038                      New_Occurrence_Of (Entity (Name (Expr)), Ploc),
8039                    Parameter_Associations =>
8040                      New_Copy_List (Expressions (Arg2))));
8041             end if;
8042
8043             --  In ASIS mode, even if assertions are not enabled, we must
8044             --  analyze the original expression in the aspect specification
8045             --  because it is part of the original tree.
8046
8047             if ASIS_Mode and then Present (Asp) then
8048                declare
8049                   Orig_Expr : constant Node_Id := Expression (Asp);
8050                begin
8051                   Replace_Type_References (Orig_Expr, T);
8052                   Preanalyze_Assert_Expression (Orig_Expr, Any_Boolean);
8053                end;
8054             end if;
8055
8056             --  An ignored invariant must not generate a runtime check. Add a
8057             --  null statement to ensure that the invariant procedure does get
8058             --  a completing body.
8059
8060             if No (Stmts) then
8061                Stmts := Empty_List;
8062             end if;
8063
8064             if Is_Ignored (Prag) then
8065                Append_To (Stmts, Make_Null_Statement (Ploc));
8066
8067             --  Otherwise the invariant is checked. Build a Check pragma to
8068             --  verify the expression at runtime.
8069
8070             else
8071                Assoc := New_List (
8072                  Make_Pragma_Argument_Association (Ploc,
8073                    Expression => Make_Identifier (Ploc, Nam)),
8074                  Make_Pragma_Argument_Association (Ploc,
8075                    Expression => Expr));
8076
8077                --  Handle the String argument (if any)
8078
8079                if Present (Arg3) then
8080                   Str := Strval (Get_Pragma_Arg (Arg3));
8081
8082                   --  When inheriting an invariant, modify the message from
8083                   --  "failed invariant" to "failed inherited invariant".
8084
8085                   if Inherit then
8086                      String_To_Name_Buffer (Str);
8087
8088                      if Name_Buffer (1 .. 16) = "failed invariant" then
8089                         Insert_Str_In_Name_Buffer ("inherited ", 8);
8090                         Str := String_From_Name_Buffer;
8091                      end if;
8092                   end if;
8093
8094                   Append_To (Assoc,
8095                     Make_Pragma_Argument_Association (Ploc,
8096                       Expression => Make_String_Literal (Ploc, Str)));
8097                end if;
8098
8099                --  Generate:
8100                --    pragma Check (Nam, Expr, Str);
8101
8102                Append_To (Stmts,
8103                  Make_Pragma (Ploc,
8104                    Pragma_Identifier            =>
8105                      Make_Identifier (Ploc, Name_Check),
8106                    Pragma_Argument_Associations => Assoc));
8107             end if;
8108
8109             --  Output an info message when inheriting an invariant and the
8110             --  listing option is enabled.
8111
8112             if Inherit and Opt.List_Inherited_Aspects then
8113                Error_Msg_Sloc := Sloc (Prag);
8114                Error_Msg_N
8115                  ("info: & inherits `Invariant''Class` aspect from #?L?", Typ);
8116             end if;
8117          end Add_Invariant;
8118
8119          --  Local variables
8120
8121          Ritem : Node_Id;
8122
8123       --  Start of processing for Add_Invariants
8124
8125       begin
8126          Ritem := First_Rep_Item (T);
8127          while Present (Ritem) loop
8128             if Nkind (Ritem) = N_Pragma
8129               and then Pragma_Name (Ritem) = Name_Invariant
8130             then
8131                Add_Invariant (Ritem);
8132             end if;
8133
8134             Next_Rep_Item (Ritem);
8135          end loop;
8136       end Add_Invariants;
8137
8138    --  Start of processing for Build_Invariant_Procedure
8139
8140    begin
8141       Stmts := No_List;
8142       PDecl := Empty;
8143       PBody := Empty;
8144       SId   := Empty;
8145
8146       --  If the aspect specification exists for some view of the type, the
8147       --  declaration for the procedure has been created.
8148
8149       if Has_Invariants (Typ) then
8150          SId := Invariant_Procedure (Typ);
8151       end if;
8152
8153       --  If the body is already present, nothing to do. This will occur when
8154       --  the type is already frozen, which is the case when the invariant
8155       --  appears in a private part, and the freezing takes place before the
8156       --  final pass over full declarations.
8157
8158       --  See Exp_Ch3.Insert_Component_Invariant_Checks for details.
8159
8160       if Present (SId) then
8161          PDecl := Unit_Declaration_Node (SId);
8162
8163          if Present (PDecl)
8164            and then Nkind (PDecl) = N_Subprogram_Declaration
8165            and then Present (Corresponding_Body (PDecl))
8166          then
8167             return;
8168          end if;
8169
8170       else
8171          PDecl := Build_Invariant_Procedure_Declaration (Typ);
8172       end if;
8173
8174       --  Recover formal of procedure, for use in the calls to invariant
8175       --  functions (including inherited ones).
8176
8177       Object_Entity :=
8178         Defining_Identifier
8179           (First (Parameter_Specifications (Specification (PDecl))));
8180       Object_Name := Chars (Object_Entity);
8181
8182       --  Add invariants for the current type
8183
8184       Add_Invariants (Typ, Inherit => False);
8185
8186       --  Add invariants for parent types
8187
8188       declare
8189          Current_Typ : Entity_Id;
8190          Parent_Typ  : Entity_Id;
8191
8192       begin
8193          Current_Typ := Typ;
8194          loop
8195             Parent_Typ := Etype (Current_Typ);
8196
8197             if Is_Private_Type (Parent_Typ)
8198               and then Present (Full_View (Base_Type (Parent_Typ)))
8199             then
8200                Parent_Typ := Full_View (Base_Type (Parent_Typ));
8201             end if;
8202
8203             exit when Parent_Typ = Current_Typ;
8204
8205             Current_Typ := Parent_Typ;
8206             Add_Invariants (Current_Typ, Inherit => True);
8207          end loop;
8208       end;
8209
8210       --  Add invariants of progenitors
8211
8212       if Is_Tagged_Type (Typ) and then not Is_Interface (Typ) then
8213          declare
8214             Ifaces_List : Elist_Id;
8215             AI          : Elmt_Id;
8216             Iface       : Entity_Id;
8217
8218          begin
8219             Collect_Interfaces (Typ, Ifaces_List);
8220
8221             AI := First_Elmt (Ifaces_List);
8222             while Present (AI) loop
8223                Iface := Node (AI);
8224
8225                if not Is_Ancestor (Iface, Typ, Use_Full_View => True) then
8226                   Add_Invariants (Iface, Inherit => True);
8227                end if;
8228
8229                Next_Elmt (AI);
8230             end loop;
8231          end;
8232       end if;
8233
8234       --  Build the procedure if we generated at least one Check pragma
8235
8236       if Stmts /= No_List then
8237          Spec  := Copy_Separate_Tree (Specification (PDecl));
8238
8239          PBody :=
8240            Make_Subprogram_Body (Loc,
8241              Specification              => Spec,
8242              Declarations               => Empty_List,
8243              Handled_Statement_Sequence =>
8244                Make_Handled_Sequence_Of_Statements (Loc,
8245                  Statements => Stmts));
8246
8247          --  Insert procedure declaration and spec at the appropriate points.
8248          --  If declaration is already analyzed, it was processed by the
8249          --  generated pragma.
8250
8251          if Present (Priv_Decls) then
8252
8253             --  The spec goes at the end of visible declarations, but they have
8254             --  already been analyzed, so we need to explicitly do the analyze.
8255
8256             if not Analyzed (PDecl) then
8257                Append_To (Vis_Decls, PDecl);
8258                Analyze (PDecl);
8259             end if;
8260
8261             --  The body goes at the end of the private declarations, which we
8262             --  have not analyzed yet, so we do not need to perform an explicit
8263             --  analyze call. We skip this if there are no private declarations
8264             --  (this is an error that will be caught elsewhere);
8265
8266             Append_To (Priv_Decls, PBody);
8267
8268             --  If the invariant appears on the full view of a type, the
8269             --  analysis of the private part is complete, and we must
8270             --  analyze the new body explicitly.
8271
8272             if In_Private_Part (Current_Scope) then
8273                Analyze (PBody);
8274             end if;
8275
8276          --  If there are no private declarations this may be an error that
8277          --  will be diagnosed elsewhere. However, if this is a non-private
8278          --  type that inherits invariants, it needs no completion and there
8279          --  may be no private part. In this case insert invariant procedure
8280          --  at end of current declarative list, and analyze at once, given
8281          --  that the type is about to be frozen.
8282
8283          elsif not Is_Private_Type (Typ) then
8284             Append_To (Vis_Decls, PDecl);
8285             Append_To (Vis_Decls, PBody);
8286             Analyze (PDecl);
8287             Analyze (PBody);
8288          end if;
8289       end if;
8290    end Build_Invariant_Procedure;
8291
8292    -------------------------------
8293    -- Build_Predicate_Functions --
8294    -------------------------------
8295
8296    --  The procedures that are constructed here have the form:
8297
8298    --    function typPredicate (Ixxx : typ) return Boolean is
8299    --    begin
8300    --       return
8301    --          exp1 and then exp2 and then ...
8302    --          and then typ1Predicate (typ1 (Ixxx))
8303    --          and then typ2Predicate (typ2 (Ixxx))
8304    --          and then ...;
8305    --    end typPredicate;
8306
8307    --  Here exp1, and exp2 are expressions from Predicate pragmas. Note that
8308    --  this is the point at which these expressions get analyzed, providing the
8309    --  required delay, and typ1, typ2, are entities from which predicates are
8310    --  inherited. Note that we do NOT generate Check pragmas, that's because we
8311    --  use this function even if checks are off, e.g. for membership tests.
8312
8313    --  If the expression has at least one Raise_Expression, then we also build
8314    --  the typPredicateM version of the function, in which any occurrence of a
8315    --  Raise_Expression is converted to "return False".
8316
8317    procedure Build_Predicate_Functions (Typ : Entity_Id; N : Node_Id) is
8318       Loc : constant Source_Ptr := Sloc (Typ);
8319
8320       Expr : Node_Id;
8321       --  This is the expression for the result of the function. It is
8322       --  is build by connecting the component predicates with AND THEN.
8323
8324       Expr_M : Node_Id;
8325       --  This is the corresponding return expression for the Predicate_M
8326       --  function. It differs in that raise expressions are marked for
8327       --  special expansion (see Process_REs).
8328
8329       Object_Name : constant Name_Id := New_Internal_Name ('I');
8330       --  Name for argument of Predicate procedure. Note that we use the same
8331       --  name for both predicate functions. That way the reference within the
8332       --  predicate expression is the same in both functions.
8333
8334       Object_Entity : constant Entity_Id :=
8335                         Make_Defining_Identifier (Loc, Chars => Object_Name);
8336       --  Entity for argument of Predicate procedure
8337
8338       Object_Entity_M : constant Entity_Id :=
8339                          Make_Defining_Identifier (Loc, Chars => Object_Name);
8340       --  Entity for argument of Predicate_M procedure
8341
8342       Raise_Expression_Present : Boolean := False;
8343       --  Set True if Expr has at least one Raise_Expression
8344
8345       procedure Add_Call (T : Entity_Id);
8346       --  Includes a call to the predicate function for type T in Expr if T
8347       --  has predicates and Predicate_Function (T) is non-empty.
8348
8349       procedure Add_Predicates;
8350       --  Appends expressions for any Predicate pragmas in the rep item chain
8351       --  Typ to Expr. Note that we look only at items for this exact entity.
8352       --  Inheritance of predicates for the parent type is done by calling the
8353       --  Predicate_Function of the parent type, using Add_Call above.
8354
8355       function Process_RE (N : Node_Id) return Traverse_Result;
8356       --  Used in Process REs, tests if node N is a raise expression, and if
8357       --  so, marks it to be converted to return False.
8358
8359       procedure Process_REs is new Traverse_Proc (Process_RE);
8360       --  Marks any raise expressions in Expr_M to return False
8361
8362       function Test_RE (N : Node_Id) return Traverse_Result;
8363       --  Used in Test_REs, tests one node for being a raise expression, and if
8364       --  so sets Raise_Expression_Present True.
8365
8366       procedure Test_REs is new Traverse_Proc (Test_RE);
8367       --  Tests to see if Expr contains any raise expressions
8368
8369       --------------
8370       -- Add_Call --
8371       --------------
8372
8373       procedure Add_Call (T : Entity_Id) is
8374          Exp : Node_Id;
8375
8376       begin
8377          if Present (T) and then Present (Predicate_Function (T)) then
8378             Set_Has_Predicates (Typ);
8379
8380             --  Build the call to the predicate function of T
8381
8382             Exp :=
8383               Make_Predicate_Call
8384                 (T, Convert_To (T, Make_Identifier (Loc, Object_Name)));
8385
8386             --  Add call to evolving expression, using AND THEN if needed
8387
8388             if No (Expr) then
8389                Expr := Exp;
8390
8391             else
8392                Expr :=
8393                  Make_And_Then (Sloc (Expr),
8394                    Left_Opnd  => Relocate_Node (Expr),
8395                    Right_Opnd => Exp);
8396             end if;
8397
8398             --  Output info message on inheritance if required. Note we do not
8399             --  give this information for generic actual types, since it is
8400             --  unwelcome noise in that case in instantiations. We also
8401             --  generally suppress the message in instantiations, and also
8402             --  if it involves internal names.
8403
8404             if Opt.List_Inherited_Aspects
8405               and then not Is_Generic_Actual_Type (Typ)
8406               and then Instantiation_Depth (Sloc (Typ)) = 0
8407               and then not Is_Internal_Name (Chars (T))
8408               and then not Is_Internal_Name (Chars (Typ))
8409             then
8410                Error_Msg_Sloc := Sloc (Predicate_Function (T));
8411                Error_Msg_Node_2 := T;
8412                Error_Msg_N ("info: & inherits predicate from & #?L?", Typ);
8413             end if;
8414          end if;
8415       end Add_Call;
8416
8417       --------------------
8418       -- Add_Predicates --
8419       --------------------
8420
8421       procedure Add_Predicates is
8422          procedure Add_Predicate (Prag : Node_Id);
8423          --  Concatenate the expression of predicate pragma Prag to Expr by
8424          --  using a short circuit "and then" operator.
8425
8426          -------------------
8427          -- Add_Predicate --
8428          -------------------
8429
8430          procedure Add_Predicate (Prag : Node_Id) is
8431             procedure Replace_Type_Reference (N : Node_Id);
8432             --  Replace a single occurrence N of the subtype name with a
8433             --  reference to the formal of the predicate function. N can be an
8434             --  identifier referencing the subtype, or a selected component,
8435             --  representing an appropriately qualified occurrence of the
8436             --  subtype name.
8437
8438             procedure Replace_Type_References is
8439               new Replace_Type_References_Generic (Replace_Type_Reference);
8440             --  Traverse an expression changing every occurrence of an
8441             --  identifier whose name matches the name of the subtype with a
8442             --  reference to the formal parameter of the predicate function.
8443
8444             ----------------------------
8445             -- Replace_Type_Reference --
8446             ----------------------------
8447
8448             procedure Replace_Type_Reference (N : Node_Id) is
8449             begin
8450                Rewrite (N, Make_Identifier (Sloc (N), Object_Name));
8451                --  Use the Sloc of the usage name, not the defining name
8452
8453                Set_Etype (N, Typ);
8454                Set_Entity (N, Object_Entity);
8455
8456                --  We want to treat the node as if it comes from source, so
8457                --  that ASIS will not ignore it.
8458
8459                Set_Comes_From_Source (N, True);
8460             end Replace_Type_Reference;
8461
8462             --  Local variables
8463
8464             Asp  : constant Node_Id := Corresponding_Aspect (Prag);
8465             Arg1 : Node_Id;
8466             Arg2 : Node_Id;
8467
8468          --  Start of processing for Add_Predicate
8469
8470          begin
8471             --  Extract the arguments of the pragma. The expression itself
8472             --  is copied for use in the predicate function, to preserve the
8473             --  original version for ASIS use.
8474
8475             Arg1 := First (Pragma_Argument_Associations (Prag));
8476             Arg2 := Next (Arg1);
8477
8478             Arg1 := Get_Pragma_Arg (Arg1);
8479             Arg2 := New_Copy_Tree (Get_Pragma_Arg (Arg2));
8480
8481             --  When the predicate pragma applies to the current type or its
8482             --  full view, replace all occurrences of the subtype name with
8483             --  references to the formal parameter of the predicate function.
8484
8485             if Entity (Arg1) = Typ
8486               or else Full_View (Entity (Arg1)) = Typ
8487             then
8488                Replace_Type_References (Arg2, Typ);
8489
8490                --  If the predicate pragma comes from an aspect, replace the
8491                --  saved expression because we need the subtype references
8492                --  replaced for the calls to Preanalyze_Spec_Expression in
8493                --  Check_Aspect_At_xxx routines.
8494
8495                if Present (Asp) then
8496
8497                   --  For ASIS use, perform semantic analysis of the original
8498                   --  predicate expression, which is otherwise not utilized.
8499
8500                   if ASIS_Mode then
8501                      Preanalyze_And_Resolve (Expression (Asp));
8502                   end if;
8503
8504                   Set_Entity (Identifier (Asp), New_Copy_Tree (Arg2));
8505                end if;
8506
8507                --  Concatenate to the existing predicate expressions by using
8508                --  "and then".
8509
8510                if Present (Expr) then
8511                   Expr :=
8512                     Make_And_Then (Loc,
8513                       Left_Opnd  => Relocate_Node (Expr),
8514                       Right_Opnd => Relocate_Node (Arg2));
8515
8516                --  Otherwise this is the first predicate expression
8517
8518                else
8519                   Expr := Relocate_Node (Arg2);
8520                end if;
8521             end if;
8522          end Add_Predicate;
8523
8524          --  Local variables
8525
8526          Ritem : Node_Id;
8527
8528       --  Start of processing for Add_Predicates
8529
8530       begin
8531          Ritem := First_Rep_Item (Typ);
8532          while Present (Ritem) loop
8533             if Nkind (Ritem) = N_Pragma
8534               and then Pragma_Name (Ritem) = Name_Predicate
8535             then
8536                Add_Predicate (Ritem);
8537             end if;
8538
8539             Next_Rep_Item (Ritem);
8540          end loop;
8541       end Add_Predicates;
8542
8543       ----------------
8544       -- Process_RE --
8545       ----------------
8546
8547       function Process_RE (N : Node_Id) return Traverse_Result is
8548       begin
8549          if Nkind (N) = N_Raise_Expression then
8550             Set_Convert_To_Return_False (N);
8551             return Skip;
8552          else
8553             return OK;
8554          end if;
8555       end Process_RE;
8556
8557       -------------
8558       -- Test_RE --
8559       -------------
8560
8561       function Test_RE (N : Node_Id) return Traverse_Result is
8562       begin
8563          if Nkind (N) = N_Raise_Expression then
8564             Raise_Expression_Present := True;
8565             return Abandon;
8566          else
8567             return OK;
8568          end if;
8569       end Test_RE;
8570
8571       --  Local variables
8572
8573       GM : constant Ghost_Mode_Type := Ghost_Mode;
8574
8575    --  Start of processing for Build_Predicate_Functions
8576
8577    begin
8578       --  Return if already built or if type does not have predicates
8579
8580       if not Has_Predicates (Typ)
8581         or else Present (Predicate_Function (Typ))
8582       then
8583          return;
8584       end if;
8585
8586       --  The related type may be subject to pragma Ghost with policy Ignore.
8587       --  Set the mode now to ensure that the predicate functions are properly
8588       --  flagged as ignored Ghost.
8589
8590       Set_Ghost_Mode_From_Entity (Typ);
8591
8592       --  Prepare to construct predicate expression
8593
8594       Expr := Empty;
8595
8596       --  Add Predicates for the current type
8597
8598       Add_Predicates;
8599
8600       --  Add predicates for ancestor if present
8601
8602       declare
8603          Atyp : constant Entity_Id := Nearest_Ancestor (Typ);
8604       begin
8605          if Present (Atyp) then
8606             Add_Call (Atyp);
8607          end if;
8608       end;
8609
8610       --  Case where predicates are present
8611
8612       if Present (Expr) then
8613
8614          --  Test for raise expression present
8615
8616          Test_REs (Expr);
8617
8618          --  If raise expression is present, capture a copy of Expr for use
8619          --  in building the predicateM function version later on. For this
8620          --  copy we replace references to Object_Entity by Object_Entity_M.
8621
8622          if Raise_Expression_Present then
8623             declare
8624                Map   : constant Elist_Id := New_Elmt_List;
8625                New_V : Entity_Id := Empty;
8626
8627                --  The unanalyzed expression will be copied and appear in
8628                --  both functions. Normally expressions do not declare new
8629                --  entities, but quantified expressions do, so we need to
8630                --  create new entities for their bound variables, to prevent
8631                --  multiple definitions in gigi.
8632
8633                function Reset_Loop_Variable (N : Node_Id)
8634                  return Traverse_Result;
8635
8636                procedure Collect_Loop_Variables is
8637                  new Traverse_Proc (Reset_Loop_Variable);
8638
8639                ------------------------
8640                -- Reset_Loop_Variable --
8641                ------------------------
8642
8643                function Reset_Loop_Variable (N : Node_Id)
8644                  return Traverse_Result
8645                is
8646                begin
8647                   if Nkind (N) = N_Iterator_Specification then
8648                      New_V := Make_Defining_Identifier
8649                        (Sloc (N), Chars (Defining_Identifier (N)));
8650
8651                      Set_Defining_Identifier (N, New_V);
8652                   end if;
8653
8654                   return OK;
8655                end Reset_Loop_Variable;
8656
8657             begin
8658                Append_Elmt (Object_Entity, Map);
8659                Append_Elmt (Object_Entity_M, Map);
8660                Expr_M := New_Copy_Tree (Expr, Map => Map);
8661                Collect_Loop_Variables (Expr_M);
8662             end;
8663          end if;
8664
8665          --  Build the main predicate function
8666
8667          declare
8668             SId : constant Entity_Id :=
8669                     Make_Defining_Identifier (Loc,
8670                       Chars => New_External_Name (Chars (Typ), "Predicate"));
8671             --  The entity for the the function spec
8672
8673             SIdB : constant Entity_Id :=
8674               Make_Defining_Identifier (Loc,
8675                 Chars => New_External_Name (Chars (Typ), "Predicate"));
8676             --  The entity for the function body
8677
8678             Spec  : Node_Id;
8679             FDecl : Node_Id;
8680             FBody : Node_Id;
8681
8682          begin
8683             --  Build function declaration
8684
8685             Set_Ekind (SId, E_Function);
8686             Set_Is_Internal (SId);
8687             Set_Is_Predicate_Function (SId);
8688             Set_Predicate_Function (Typ, SId);
8689
8690             --  The predicate function is shared between views of a type
8691
8692             if Is_Private_Type (Typ) and then Present (Full_View (Typ)) then
8693                Set_Predicate_Function (Full_View (Typ), SId);
8694             end if;
8695
8696             --  Mark the predicate function explicitly as Ghost because it does
8697             --  not come from source.
8698
8699             if Ghost_Mode > None then
8700                Set_Is_Ghost_Entity (SId);
8701             end if;
8702
8703             Spec :=
8704               Make_Function_Specification (Loc,
8705                 Defining_Unit_Name       => SId,
8706                 Parameter_Specifications => New_List (
8707                   Make_Parameter_Specification (Loc,
8708                     Defining_Identifier => Object_Entity,
8709                     Parameter_Type      => New_Occurrence_Of (Typ, Loc))),
8710                 Result_Definition        =>
8711                   New_Occurrence_Of (Standard_Boolean, Loc));
8712
8713             FDecl :=
8714               Make_Subprogram_Declaration (Loc,
8715                 Specification => Spec);
8716
8717             --  Build function body
8718
8719             Spec :=
8720               Make_Function_Specification (Loc,
8721                 Defining_Unit_Name       => SIdB,
8722                 Parameter_Specifications => New_List (
8723                   Make_Parameter_Specification (Loc,
8724                     Defining_Identifier =>
8725                       Make_Defining_Identifier (Loc, Object_Name),
8726                     Parameter_Type =>
8727                       New_Occurrence_Of (Typ, Loc))),
8728                 Result_Definition        =>
8729                   New_Occurrence_Of (Standard_Boolean, Loc));
8730
8731             FBody :=
8732               Make_Subprogram_Body (Loc,
8733                 Specification              => Spec,
8734                 Declarations               => Empty_List,
8735                 Handled_Statement_Sequence =>
8736                   Make_Handled_Sequence_Of_Statements (Loc,
8737                     Statements => New_List (
8738                       Make_Simple_Return_Statement (Loc,
8739                         Expression => Expr))));
8740
8741             --  Insert declaration before freeze node and body after
8742
8743             Insert_Before_And_Analyze (N, FDecl);
8744             Insert_After_And_Analyze  (N, FBody);
8745          end;
8746
8747          --  Test for raise expressions present and if so build M version
8748
8749          if Raise_Expression_Present then
8750             declare
8751                SId : constant Entity_Id :=
8752                  Make_Defining_Identifier (Loc,
8753                    Chars => New_External_Name (Chars (Typ), "PredicateM"));
8754                --  The entity for the the function spec
8755
8756                SIdB : constant Entity_Id :=
8757                  Make_Defining_Identifier (Loc,
8758                    Chars => New_External_Name (Chars (Typ), "PredicateM"));
8759                --  The entity for the function body
8760
8761                Spec  : Node_Id;
8762                FDecl : Node_Id;
8763                FBody : Node_Id;
8764                BTemp : Entity_Id;
8765
8766             begin
8767                --  Mark any raise expressions for special expansion
8768
8769                Process_REs (Expr_M);
8770
8771                --  Build function declaration
8772
8773                Set_Ekind (SId, E_Function);
8774                Set_Is_Predicate_Function_M (SId);
8775                Set_Predicate_Function_M (Typ, SId);
8776
8777                --  The predicate function is shared between views of a type
8778
8779                if Is_Private_Type (Typ) and then Present (Full_View (Typ)) then
8780                   Set_Predicate_Function_M (Full_View (Typ), SId);
8781                end if;
8782
8783                --  Mark the predicate function explicitly as Ghost because it
8784                --  does not come from source.
8785
8786                if Ghost_Mode > None then
8787                   Set_Is_Ghost_Entity (SId);
8788                end if;
8789
8790                Spec :=
8791                  Make_Function_Specification (Loc,
8792                    Defining_Unit_Name       => SId,
8793                    Parameter_Specifications => New_List (
8794                      Make_Parameter_Specification (Loc,
8795                        Defining_Identifier => Object_Entity_M,
8796                        Parameter_Type      => New_Occurrence_Of (Typ, Loc))),
8797                    Result_Definition        =>
8798                      New_Occurrence_Of (Standard_Boolean, Loc));
8799
8800                FDecl :=
8801                  Make_Subprogram_Declaration (Loc,
8802                    Specification => Spec);
8803
8804                --  Build function body
8805
8806                Spec :=
8807                  Make_Function_Specification (Loc,
8808                    Defining_Unit_Name       => SIdB,
8809                    Parameter_Specifications => New_List (
8810                      Make_Parameter_Specification (Loc,
8811                        Defining_Identifier =>
8812                          Make_Defining_Identifier (Loc, Object_Name),
8813                        Parameter_Type =>
8814                          New_Occurrence_Of (Typ, Loc))),
8815                    Result_Definition        =>
8816                      New_Occurrence_Of (Standard_Boolean, Loc));
8817
8818                --  Build the body, we declare the boolean expression before
8819                --  doing the return, because we are not really confident of
8820                --  what happens if a return appears within a return.
8821
8822                BTemp :=
8823                  Make_Defining_Identifier (Loc,
8824                    Chars => New_Internal_Name ('B'));
8825
8826                FBody :=
8827                  Make_Subprogram_Body (Loc,
8828                    Specification              => Spec,
8829
8830                    Declarations               => New_List (
8831                      Make_Object_Declaration (Loc,
8832                        Defining_Identifier => BTemp,
8833                        Constant_Present    => True,
8834                          Object_Definition =>
8835                            New_Occurrence_Of (Standard_Boolean, Loc),
8836                          Expression        => Expr_M)),
8837
8838                    Handled_Statement_Sequence =>
8839                      Make_Handled_Sequence_Of_Statements (Loc,
8840                        Statements => New_List (
8841                          Make_Simple_Return_Statement (Loc,
8842                            Expression => New_Occurrence_Of (BTemp, Loc)))));
8843
8844                --  Insert declaration before freeze node and body after
8845
8846                Insert_Before_And_Analyze (N, FDecl);
8847                Insert_After_And_Analyze  (N, FBody);
8848             end;
8849          end if;
8850
8851          --  See if we have a static predicate. Note that the answer may be
8852          --  yes even if we have an explicit Dynamic_Predicate present.
8853
8854          declare
8855             PS : Boolean;
8856             EN : Node_Id;
8857
8858          begin
8859             if not Is_Scalar_Type (Typ) and then not Is_String_Type (Typ) then
8860                PS := False;
8861             else
8862                PS := Is_Predicate_Static (Expr, Object_Name);
8863             end if;
8864
8865             --  Case where we have a predicate-static aspect
8866
8867             if PS then
8868
8869                --  We don't set Has_Static_Predicate_Aspect, since we can have
8870                --  any of the three cases (Predicate, Dynamic_Predicate, or
8871                --  Static_Predicate) generating a predicate with an expression
8872                --  that is predicate-static. We just indicate that we have a
8873                --  predicate that can be treated as static.
8874
8875                Set_Has_Static_Predicate (Typ);
8876
8877                --  For discrete subtype, build the static predicate list
8878
8879                if Is_Discrete_Type (Typ) then
8880                   Build_Discrete_Static_Predicate (Typ, Expr, Object_Name);
8881
8882                   --  If we don't get a static predicate list, it means that we
8883                   --  have a case where this is not possible, most typically in
8884                   --  the case where we inherit a dynamic predicate. We do not
8885                   --  consider this an error, we just leave the predicate as
8886                   --  dynamic. But if we do succeed in building the list, then
8887                   --  we mark the predicate as static.
8888
8889                   if No (Static_Discrete_Predicate (Typ)) then
8890                      Set_Has_Static_Predicate (Typ, False);
8891                   end if;
8892
8893                --  For real or string subtype, save predicate expression
8894
8895                elsif Is_Real_Type (Typ) or else Is_String_Type (Typ) then
8896                   Set_Static_Real_Or_String_Predicate (Typ, Expr);
8897                end if;
8898
8899             --  Case of dynamic predicate (expression is not predicate-static)
8900
8901             else
8902                --  Again, we don't set Has_Dynamic_Predicate_Aspect, since that
8903                --  is only set if we have an explicit Dynamic_Predicate aspect
8904                --  given. Here we may simply have a Predicate aspect where the
8905                --  expression happens not to be predicate-static.
8906
8907                --  Emit an error when the predicate is categorized as static
8908                --  but its expression is not predicate-static.
8909
8910                --  First a little fiddling to get a nice location for the
8911                --  message. If the expression is of the form (A and then B),
8912                --  then use the left operand for the Sloc. This avoids getting
8913                --  confused by a call to a higher-level predicate with a less
8914                --  convenient source location.
8915
8916                EN := Expr;
8917                while Nkind (EN) = N_And_Then loop
8918                   EN := Left_Opnd (EN);
8919                end loop;
8920
8921                --  Now post appropriate message
8922
8923                if Has_Static_Predicate_Aspect (Typ) then
8924                   if Is_Scalar_Type (Typ) or else Is_String_Type (Typ) then
8925                      Error_Msg_F
8926                        ("expression is not predicate-static (RM 3.2.4(16-22))",
8927                         EN);
8928                   else
8929                      Error_Msg_F
8930                        ("static predicate requires scalar or string type", EN);
8931                   end if;
8932                end if;
8933             end if;
8934          end;
8935       end if;
8936
8937       --  Restore the original Ghost mode once analysis and expansion have
8938       --  taken place.
8939
8940       Ghost_Mode := GM;
8941    end Build_Predicate_Functions;
8942
8943    -----------------------------------------
8944    -- Check_Aspect_At_End_Of_Declarations --
8945    -----------------------------------------
8946
8947    procedure Check_Aspect_At_End_Of_Declarations (ASN : Node_Id) is
8948       Ent   : constant Entity_Id := Entity     (ASN);
8949       Ident : constant Node_Id   := Identifier (ASN);
8950       A_Id  : constant Aspect_Id := Get_Aspect_Id (Chars (Ident));
8951
8952       End_Decl_Expr : constant Node_Id := Entity (Ident);
8953       --  Expression to be analyzed at end of declarations
8954
8955       Freeze_Expr : constant Node_Id := Expression (ASN);
8956       --  Expression from call to Check_Aspect_At_Freeze_Point
8957
8958       T : constant Entity_Id := Etype (Freeze_Expr);
8959       --  Type required for preanalyze call
8960
8961       Err : Boolean;
8962       --  Set False if error
8963
8964       --  On entry to this procedure, Entity (Ident) contains a copy of the
8965       --  original expression from the aspect, saved for this purpose, and
8966       --  but Expression (Ident) is a preanalyzed copy of the expression,
8967       --  preanalyzed just after the freeze point.
8968
8969       procedure Check_Overloaded_Name;
8970       --  For aspects whose expression is simply a name, this routine checks if
8971       --  the name is overloaded or not. If so, it verifies there is an
8972       --  interpretation that matches the entity obtained at the freeze point,
8973       --  otherwise the compiler complains.
8974
8975       ---------------------------
8976       -- Check_Overloaded_Name --
8977       ---------------------------
8978
8979       procedure Check_Overloaded_Name is
8980       begin
8981          if not Is_Overloaded (End_Decl_Expr) then
8982             Err := not Is_Entity_Name (End_Decl_Expr)
8983                      or else Entity (End_Decl_Expr) /= Entity (Freeze_Expr);
8984
8985          else
8986             Err := True;
8987
8988             declare
8989                Index : Interp_Index;
8990                It    : Interp;
8991
8992             begin
8993                Get_First_Interp (End_Decl_Expr, Index, It);
8994                while Present (It.Typ) loop
8995                   if It.Nam = Entity (Freeze_Expr) then
8996                      Err := False;
8997                      exit;
8998                   end if;
8999
9000                   Get_Next_Interp (Index, It);
9001                end loop;
9002             end;
9003          end if;
9004       end Check_Overloaded_Name;
9005
9006    --  Start of processing for Check_Aspect_At_End_Of_Declarations
9007
9008    begin
9009       --  Case of aspects Dimension, Dimension_System and Synchronization
9010
9011       if A_Id = Aspect_Synchronization then
9012          return;
9013
9014       --  Case of stream attributes, just have to compare entities. However,
9015       --  the expression is just a name (possibly overloaded), and there may
9016       --  be stream operations declared for unrelated types, so we just need
9017       --  to verify that one of these interpretations is the one available at
9018       --  at the freeze point.
9019
9020       elsif A_Id = Aspect_Input  or else
9021             A_Id = Aspect_Output or else
9022             A_Id = Aspect_Read   or else
9023             A_Id = Aspect_Write
9024       then
9025          Analyze (End_Decl_Expr);
9026          Check_Overloaded_Name;
9027
9028       elsif A_Id = Aspect_Variable_Indexing or else
9029             A_Id = Aspect_Constant_Indexing or else
9030             A_Id = Aspect_Default_Iterator  or else
9031             A_Id = Aspect_Iterator_Element
9032       then
9033          --  Make type unfrozen before analysis, to prevent spurious errors
9034          --  about late attributes.
9035
9036          Set_Is_Frozen (Ent, False);
9037          Analyze (End_Decl_Expr);
9038          Set_Is_Frozen (Ent, True);
9039
9040          --  If the end of declarations comes before any other freeze
9041          --  point, the Freeze_Expr is not analyzed: no check needed.
9042
9043          if Analyzed (Freeze_Expr) and then not In_Instance then
9044             Check_Overloaded_Name;
9045          else
9046             Err := False;
9047          end if;
9048
9049       --  All other cases
9050
9051       else
9052          --  Indicate that the expression comes from an aspect specification,
9053          --  which is used in subsequent analysis even if expansion is off.
9054
9055          Set_Parent (End_Decl_Expr, ASN);
9056
9057          --  In a generic context the aspect expressions have not been
9058          --  preanalyzed, so do it now. There are no conformance checks
9059          --  to perform in this case.
9060
9061          if No (T) then
9062             Check_Aspect_At_Freeze_Point (ASN);
9063             return;
9064
9065          --  The default values attributes may be defined in the private part,
9066          --  and the analysis of the expression may take place when only the
9067          --  partial view is visible. The expression must be scalar, so use
9068          --  the full view to resolve.
9069
9070          elsif (A_Id = Aspect_Default_Value
9071                   or else
9072                 A_Id = Aspect_Default_Component_Value)
9073             and then Is_Private_Type (T)
9074          then
9075             Preanalyze_Spec_Expression (End_Decl_Expr, Full_View (T));
9076
9077          else
9078             Preanalyze_Spec_Expression (End_Decl_Expr, T);
9079          end if;
9080
9081          Err := not Fully_Conformant_Expressions (End_Decl_Expr, Freeze_Expr);
9082       end if;
9083
9084       --  Output error message if error. Force error on aspect specification
9085       --  even if there is an error on the expression itself.
9086
9087       if Err then
9088          Error_Msg_NE
9089            ("!visibility of aspect for& changes after freeze point",
9090             ASN, Ent);
9091          Error_Msg_NE
9092            ("info: & is frozen here, aspects evaluated at this point??",
9093             Freeze_Node (Ent), Ent);
9094       end if;
9095    end Check_Aspect_At_End_Of_Declarations;
9096
9097    ----------------------------------
9098    -- Check_Aspect_At_Freeze_Point --
9099    ----------------------------------
9100
9101    procedure Check_Aspect_At_Freeze_Point (ASN : Node_Id) is
9102       Ident : constant Node_Id := Identifier (ASN);
9103       --  Identifier (use Entity field to save expression)
9104
9105       A_Id : constant Aspect_Id := Get_Aspect_Id (Chars (Ident));
9106
9107       T : Entity_Id := Empty;
9108       --  Type required for preanalyze call
9109
9110    begin
9111       --  On entry to this procedure, Entity (Ident) contains a copy of the
9112       --  original expression from the aspect, saved for this purpose.
9113
9114       --  On exit from this procedure Entity (Ident) is unchanged, still
9115       --  containing that copy, but Expression (Ident) is a preanalyzed copy
9116       --  of the expression, preanalyzed just after the freeze point.
9117
9118       --  Make a copy of the expression to be preanalyzed
9119
9120       Set_Expression (ASN, New_Copy_Tree (Entity (Ident)));
9121
9122       --  Find type for preanalyze call
9123
9124       case A_Id is
9125
9126          --  No_Aspect should be impossible
9127
9128          when No_Aspect =>
9129             raise Program_Error;
9130
9131          --  Aspects taking an optional boolean argument
9132
9133          when Boolean_Aspects      |
9134               Library_Unit_Aspects =>
9135
9136             T := Standard_Boolean;
9137
9138          --  Aspects corresponding to attribute definition clauses
9139
9140          when Aspect_Address =>
9141             T := RTE (RE_Address);
9142
9143          when Aspect_Attach_Handler =>
9144             T := RTE (RE_Interrupt_ID);
9145
9146          when Aspect_Bit_Order | Aspect_Scalar_Storage_Order =>
9147             T := RTE (RE_Bit_Order);
9148
9149          when Aspect_Convention =>
9150             return;
9151
9152          when Aspect_CPU =>
9153             T := RTE (RE_CPU_Range);
9154
9155          --  Default_Component_Value is resolved with the component type
9156
9157          when Aspect_Default_Component_Value =>
9158             T := Component_Type (Entity (ASN));
9159
9160          when Aspect_Default_Storage_Pool =>
9161             T := Class_Wide_Type (RTE (RE_Root_Storage_Pool));
9162
9163          --  Default_Value is resolved with the type entity in question
9164
9165          when Aspect_Default_Value =>
9166             T := Entity (ASN);
9167
9168          when Aspect_Dispatching_Domain =>
9169             T := RTE (RE_Dispatching_Domain);
9170
9171          when Aspect_External_Tag =>
9172             T := Standard_String;
9173
9174          when Aspect_External_Name =>
9175             T := Standard_String;
9176
9177          when Aspect_Link_Name =>
9178             T := Standard_String;
9179
9180          when Aspect_Priority | Aspect_Interrupt_Priority =>
9181             T := Standard_Integer;
9182
9183          when Aspect_Relative_Deadline =>
9184             T := RTE (RE_Time_Span);
9185
9186          when Aspect_Small =>
9187             T := Universal_Real;
9188
9189          --  For a simple storage pool, we have to retrieve the type of the
9190          --  pool object associated with the aspect's corresponding attribute
9191          --  definition clause.
9192
9193          when Aspect_Simple_Storage_Pool =>
9194             T := Etype (Expression (Aspect_Rep_Item (ASN)));
9195
9196          when Aspect_Storage_Pool =>
9197             T := Class_Wide_Type (RTE (RE_Root_Storage_Pool));
9198
9199          when Aspect_Alignment      |
9200               Aspect_Component_Size |
9201               Aspect_Machine_Radix  |
9202               Aspect_Object_Size    |
9203               Aspect_Size           |
9204               Aspect_Storage_Size   |
9205               Aspect_Stream_Size    |
9206               Aspect_Value_Size     =>
9207             T := Any_Integer;
9208
9209          when Aspect_Linker_Section =>
9210             T := Standard_String;
9211
9212          when Aspect_Synchronization =>
9213             return;
9214
9215          --  Special case, the expression of these aspects is just an entity
9216          --  that does not need any resolution, so just analyze.
9217
9218          when Aspect_Input      |
9219               Aspect_Output     |
9220               Aspect_Read       |
9221               Aspect_Suppress   |
9222               Aspect_Unsuppress |
9223               Aspect_Warnings   |
9224               Aspect_Write      =>
9225             Analyze (Expression (ASN));
9226             return;
9227
9228          --  Same for Iterator aspects, where the expression is a function
9229          --  name. Legality rules are checked separately.
9230
9231          when Aspect_Constant_Indexing |
9232               Aspect_Default_Iterator  |
9233               Aspect_Iterator_Element  |
9234               Aspect_Variable_Indexing =>
9235             Analyze (Expression (ASN));
9236             return;
9237
9238          --  Ditto for Iterable, legality checks in Validate_Iterable_Aspect.
9239
9240          when Aspect_Iterable =>
9241             T := Entity (ASN);
9242
9243             declare
9244                Cursor : constant Entity_Id := Get_Cursor_Type (ASN, T);
9245                Assoc  : Node_Id;
9246                Expr   : Node_Id;
9247
9248             begin
9249                if Cursor = Any_Type then
9250                   return;
9251                end if;
9252
9253                Assoc := First (Component_Associations (Expression (ASN)));
9254                while Present (Assoc) loop
9255                   Expr := Expression (Assoc);
9256                   Analyze (Expr);
9257
9258                   if not Error_Posted (Expr) then
9259                      Resolve_Iterable_Operation
9260                        (Expr, Cursor, T, Chars (First (Choices (Assoc))));
9261                   end if;
9262
9263                   Next (Assoc);
9264                end loop;
9265             end;
9266
9267             return;
9268
9269          --  Invariant/Predicate take boolean expressions
9270
9271          when Aspect_Dynamic_Predicate |
9272               Aspect_Invariant         |
9273               Aspect_Predicate         |
9274               Aspect_Static_Predicate  |
9275               Aspect_Type_Invariant    =>
9276             T := Standard_Boolean;
9277
9278          --  Here is the list of aspects that don't require delay analysis
9279
9280          when Aspect_Abstract_State            |
9281               Aspect_Annotate                  |
9282               Aspect_Contract_Cases            |
9283               Aspect_Default_Initial_Condition |
9284               Aspect_Depends                   |
9285               Aspect_Dimension                 |
9286               Aspect_Dimension_System          |
9287               Aspect_Extensions_Visible        |
9288               Aspect_Ghost                     |
9289               Aspect_Global                    |
9290               Aspect_Implicit_Dereference      |
9291               Aspect_Initial_Condition         |
9292               Aspect_Initializes               |
9293               Aspect_Obsolescent               |
9294               Aspect_Part_Of                   |
9295               Aspect_Post                      |
9296               Aspect_Postcondition             |
9297               Aspect_Pre                       |
9298               Aspect_Precondition              |
9299               Aspect_Refined_Depends           |
9300               Aspect_Refined_Global            |
9301               Aspect_Refined_Post              |
9302               Aspect_Refined_State             |
9303               Aspect_SPARK_Mode                |
9304               Aspect_Test_Case                 |
9305               Aspect_Unimplemented             =>
9306             raise Program_Error;
9307
9308       end case;
9309
9310       --  Do the preanalyze call
9311
9312       Preanalyze_Spec_Expression (Expression (ASN), T);
9313    end Check_Aspect_At_Freeze_Point;
9314
9315    -----------------------------------
9316    -- Check_Constant_Address_Clause --
9317    -----------------------------------
9318
9319    procedure Check_Constant_Address_Clause
9320      (Expr  : Node_Id;
9321       U_Ent : Entity_Id)
9322    is
9323       procedure Check_At_Constant_Address (Nod : Node_Id);
9324       --  Checks that the given node N represents a name whose 'Address is
9325       --  constant (in the same sense as OK_Constant_Address_Clause, i.e. the
9326       --  address value is the same at the point of declaration of U_Ent and at
9327       --  the time of elaboration of the address clause.
9328
9329       procedure Check_Expr_Constants (Nod : Node_Id);
9330       --  Checks that Nod meets the requirements for a constant address clause
9331       --  in the sense of the enclosing procedure.
9332
9333       procedure Check_List_Constants (Lst : List_Id);
9334       --  Check that all elements of list Lst meet the requirements for a
9335       --  constant address clause in the sense of the enclosing procedure.
9336
9337       -------------------------------
9338       -- Check_At_Constant_Address --
9339       -------------------------------
9340
9341       procedure Check_At_Constant_Address (Nod : Node_Id) is
9342       begin
9343          if Is_Entity_Name (Nod) then
9344             if Present (Address_Clause (Entity ((Nod)))) then
9345                Error_Msg_NE
9346                  ("invalid address clause for initialized object &!",
9347                            Nod, U_Ent);
9348                Error_Msg_NE
9349                  ("address for& cannot" &
9350                     " depend on another address clause! (RM 13.1(22))!",
9351                   Nod, U_Ent);
9352
9353             elsif In_Same_Source_Unit (Entity (Nod), U_Ent)
9354               and then Sloc (U_Ent) < Sloc (Entity (Nod))
9355             then
9356                Error_Msg_NE
9357                  ("invalid address clause for initialized object &!",
9358                   Nod, U_Ent);
9359                Error_Msg_Node_2 := U_Ent;
9360                Error_Msg_NE
9361                  ("\& must be defined before & (RM 13.1(22))!",
9362                   Nod, Entity (Nod));
9363             end if;
9364
9365          elsif Nkind (Nod) = N_Selected_Component then
9366             declare
9367                T : constant Entity_Id := Etype (Prefix (Nod));
9368
9369             begin
9370                if (Is_Record_Type (T)
9371                     and then Has_Discriminants (T))
9372                  or else
9373                   (Is_Access_Type (T)
9374                     and then Is_Record_Type (Designated_Type (T))
9375                     and then Has_Discriminants (Designated_Type (T)))
9376                then
9377                   Error_Msg_NE
9378                     ("invalid address clause for initialized object &!",
9379                      Nod, U_Ent);
9380                   Error_Msg_N
9381                     ("\address cannot depend on component" &
9382                      " of discriminated record (RM 13.1(22))!",
9383                      Nod);
9384                else
9385                   Check_At_Constant_Address (Prefix (Nod));
9386                end if;
9387             end;
9388
9389          elsif Nkind (Nod) = N_Indexed_Component then
9390             Check_At_Constant_Address (Prefix (Nod));
9391             Check_List_Constants (Expressions (Nod));
9392
9393          else
9394             Check_Expr_Constants (Nod);
9395          end if;
9396       end Check_At_Constant_Address;
9397
9398       --------------------------
9399       -- Check_Expr_Constants --
9400       --------------------------
9401
9402       procedure Check_Expr_Constants (Nod : Node_Id) is
9403          Loc_U_Ent : constant Source_Ptr := Sloc (U_Ent);
9404          Ent       : Entity_Id           := Empty;
9405
9406       begin
9407          if Nkind (Nod) in N_Has_Etype
9408            and then Etype (Nod) = Any_Type
9409          then
9410             return;
9411          end if;
9412
9413          case Nkind (Nod) is
9414             when N_Empty | N_Error =>
9415                return;
9416
9417             when N_Identifier | N_Expanded_Name =>
9418                Ent := Entity (Nod);
9419
9420                --  We need to look at the original node if it is different
9421                --  from the node, since we may have rewritten things and
9422                --  substituted an identifier representing the rewrite.
9423
9424                if Original_Node (Nod) /= Nod then
9425                   Check_Expr_Constants (Original_Node (Nod));
9426
9427                   --  If the node is an object declaration without initial
9428                   --  value, some code has been expanded, and the expression
9429                   --  is not constant, even if the constituents might be
9430                   --  acceptable, as in A'Address + offset.
9431
9432                   if Ekind (Ent) = E_Variable
9433                     and then
9434                       Nkind (Declaration_Node (Ent)) = N_Object_Declaration
9435                     and then
9436                       No (Expression (Declaration_Node (Ent)))
9437                   then
9438                      Error_Msg_NE
9439                        ("invalid address clause for initialized object &!",
9440                         Nod, U_Ent);
9441
9442                   --  If entity is constant, it may be the result of expanding
9443                   --  a check. We must verify that its declaration appears
9444                   --  before the object in question, else we also reject the
9445                   --  address clause.
9446
9447                   elsif Ekind (Ent) = E_Constant
9448                     and then In_Same_Source_Unit (Ent, U_Ent)
9449                     and then Sloc (Ent) > Loc_U_Ent
9450                   then
9451                      Error_Msg_NE
9452                        ("invalid address clause for initialized object &!",
9453                         Nod, U_Ent);
9454                   end if;
9455
9456                   return;
9457                end if;
9458
9459                --  Otherwise look at the identifier and see if it is OK
9460
9461                if Ekind_In (Ent, E_Named_Integer, E_Named_Real)
9462                  or else Is_Type (Ent)
9463                then
9464                   return;
9465
9466                elsif Ekind_In (Ent, E_Constant, E_In_Parameter) then
9467
9468                   --  This is the case where we must have Ent defined before
9469                   --  U_Ent. Clearly if they are in different units this
9470                   --  requirement is met since the unit containing Ent is
9471                   --  already processed.
9472
9473                   if not In_Same_Source_Unit (Ent, U_Ent) then
9474                      return;
9475
9476                   --  Otherwise location of Ent must be before the location
9477                   --  of U_Ent, that's what prior defined means.
9478
9479                   elsif Sloc (Ent) < Loc_U_Ent then
9480                      return;
9481
9482                   else
9483                      Error_Msg_NE
9484                        ("invalid address clause for initialized object &!",
9485                         Nod, U_Ent);
9486                      Error_Msg_Node_2 := U_Ent;
9487                      Error_Msg_NE
9488                        ("\& must be defined before & (RM 13.1(22))!",
9489                         Nod, Ent);
9490                   end if;
9491
9492                elsif Nkind (Original_Node (Nod)) = N_Function_Call then
9493                   Check_Expr_Constants (Original_Node (Nod));
9494
9495                else
9496                   Error_Msg_NE
9497                     ("invalid address clause for initialized object &!",
9498                      Nod, U_Ent);
9499
9500                   if Comes_From_Source (Ent) then
9501                      Error_Msg_NE
9502                        ("\reference to variable& not allowed"
9503                           & " (RM 13.1(22))!", Nod, Ent);
9504                   else
9505                      Error_Msg_N
9506                        ("non-static expression not allowed"
9507                           & " (RM 13.1(22))!", Nod);
9508                   end if;
9509                end if;
9510
9511             when N_Integer_Literal   =>
9512
9513                --  If this is a rewritten unchecked conversion, in a system
9514                --  where Address is an integer type, always use the base type
9515                --  for a literal value. This is user-friendly and prevents
9516                --  order-of-elaboration issues with instances of unchecked
9517                --  conversion.
9518
9519                if Nkind (Original_Node (Nod)) = N_Function_Call then
9520                   Set_Etype (Nod, Base_Type (Etype (Nod)));
9521                end if;
9522
9523             when N_Real_Literal      |
9524                  N_String_Literal    |
9525                  N_Character_Literal =>
9526                return;
9527
9528             when N_Range =>
9529                Check_Expr_Constants (Low_Bound (Nod));
9530                Check_Expr_Constants (High_Bound (Nod));
9531
9532             when N_Explicit_Dereference =>
9533                Check_Expr_Constants (Prefix (Nod));
9534
9535             when N_Indexed_Component =>
9536                Check_Expr_Constants (Prefix (Nod));
9537                Check_List_Constants (Expressions (Nod));
9538
9539             when N_Slice =>
9540                Check_Expr_Constants (Prefix (Nod));
9541                Check_Expr_Constants (Discrete_Range (Nod));
9542
9543             when N_Selected_Component =>
9544                Check_Expr_Constants (Prefix (Nod));
9545
9546             when N_Attribute_Reference =>
9547                if Nam_In (Attribute_Name (Nod), Name_Address,
9548                                                 Name_Access,
9549                                                 Name_Unchecked_Access,
9550                                                 Name_Unrestricted_Access)
9551                then
9552                   Check_At_Constant_Address (Prefix (Nod));
9553
9554                else
9555                   Check_Expr_Constants (Prefix (Nod));
9556                   Check_List_Constants (Expressions (Nod));
9557                end if;
9558
9559             when N_Aggregate =>
9560                Check_List_Constants (Component_Associations (Nod));
9561                Check_List_Constants (Expressions (Nod));
9562
9563             when N_Component_Association =>
9564                Check_Expr_Constants (Expression (Nod));
9565
9566             when N_Extension_Aggregate =>
9567                Check_Expr_Constants (Ancestor_Part (Nod));
9568                Check_List_Constants (Component_Associations (Nod));
9569                Check_List_Constants (Expressions (Nod));
9570
9571             when N_Null =>
9572                return;
9573
9574             when N_Binary_Op | N_Short_Circuit | N_Membership_Test =>
9575                Check_Expr_Constants (Left_Opnd (Nod));
9576                Check_Expr_Constants (Right_Opnd (Nod));
9577
9578             when N_Unary_Op =>
9579                Check_Expr_Constants (Right_Opnd (Nod));
9580
9581             when N_Type_Conversion           |
9582                  N_Qualified_Expression      |
9583                  N_Allocator                 |
9584                  N_Unchecked_Type_Conversion =>
9585                Check_Expr_Constants (Expression (Nod));
9586
9587             when N_Function_Call =>
9588                if not Is_Pure (Entity (Name (Nod))) then
9589                   Error_Msg_NE
9590                     ("invalid address clause for initialized object &!",
9591                      Nod, U_Ent);
9592
9593                   Error_Msg_NE
9594                     ("\function & is not pure (RM 13.1(22))!",
9595                      Nod, Entity (Name (Nod)));
9596
9597                else
9598                   Check_List_Constants (Parameter_Associations (Nod));
9599                end if;
9600
9601             when N_Parameter_Association =>
9602                Check_Expr_Constants (Explicit_Actual_Parameter (Nod));
9603
9604             when others =>
9605                Error_Msg_NE
9606                  ("invalid address clause for initialized object &!",
9607                   Nod, U_Ent);
9608                Error_Msg_NE
9609                  ("\must be constant defined before& (RM 13.1(22))!",
9610                   Nod, U_Ent);
9611          end case;
9612       end Check_Expr_Constants;
9613
9614       --------------------------
9615       -- Check_List_Constants --
9616       --------------------------
9617
9618       procedure Check_List_Constants (Lst : List_Id) is
9619          Nod1 : Node_Id;
9620
9621       begin
9622          if Present (Lst) then
9623             Nod1 := First (Lst);
9624             while Present (Nod1) loop
9625                Check_Expr_Constants (Nod1);
9626                Next (Nod1);
9627             end loop;
9628          end if;
9629       end Check_List_Constants;
9630
9631    --  Start of processing for Check_Constant_Address_Clause
9632
9633    begin
9634       --  If rep_clauses are to be ignored, no need for legality checks. In
9635       --  particular, no need to pester user about rep clauses that violate the
9636       --  rule on constant addresses, given that these clauses will be removed
9637       --  by Freeze before they reach the back end. Similarly in CodePeer mode,
9638       --  we want to relax these checks.
9639
9640       if not Ignore_Rep_Clauses and not CodePeer_Mode then
9641          Check_Expr_Constants (Expr);
9642       end if;
9643    end Check_Constant_Address_Clause;
9644
9645    ---------------------------
9646    -- Check_Pool_Size_Clash --
9647    ---------------------------
9648
9649    procedure Check_Pool_Size_Clash (Ent : Entity_Id; SP, SS : Node_Id) is
9650       Post : Node_Id;
9651
9652    begin
9653       --  We need to find out which one came first. Note that in the case of
9654       --  aspects mixed with pragmas there are cases where the processing order
9655       --  is reversed, which is why we do the check here.
9656
9657       if Sloc (SP) < Sloc (SS) then
9658          Error_Msg_Sloc := Sloc (SP);
9659          Post := SS;
9660          Error_Msg_NE ("Storage_Pool previously given for&#", Post, Ent);
9661
9662       else
9663          Error_Msg_Sloc := Sloc (SS);
9664          Post := SP;
9665          Error_Msg_NE ("Storage_Size previously given for&#", Post, Ent);
9666       end if;
9667
9668       Error_Msg_N
9669         ("\cannot have Storage_Size and Storage_Pool (RM 13.11(3))", Post);
9670    end Check_Pool_Size_Clash;
9671
9672    ----------------------------------------
9673    -- Check_Record_Representation_Clause --
9674    ----------------------------------------
9675
9676    procedure Check_Record_Representation_Clause (N : Node_Id) is
9677       Loc     : constant Source_Ptr := Sloc (N);
9678       Ident   : constant Node_Id    := Identifier (N);
9679       Rectype : Entity_Id;
9680       Fent    : Entity_Id;
9681       CC      : Node_Id;
9682       Fbit    : Uint;
9683       Lbit    : Uint;
9684       Hbit    : Uint := Uint_0;
9685       Comp    : Entity_Id;
9686       Pcomp   : Entity_Id;
9687
9688       Max_Bit_So_Far : Uint;
9689       --  Records the maximum bit position so far. If all field positions
9690       --  are monotonically increasing, then we can skip the circuit for
9691       --  checking for overlap, since no overlap is possible.
9692
9693       Tagged_Parent : Entity_Id := Empty;
9694       --  This is set in the case of a derived tagged type for which we have
9695       --  Is_Fully_Repped_Tagged_Type True (indicating that all components are
9696       --  positioned by record representation clauses). In this case we must
9697       --  check for overlap between components of this tagged type, and the
9698       --  components of its parent. Tagged_Parent will point to this parent
9699       --  type. For all other cases Tagged_Parent is left set to Empty.
9700
9701       Parent_Last_Bit : Uint;
9702       --  Relevant only if Tagged_Parent is set, Parent_Last_Bit indicates the
9703       --  last bit position for any field in the parent type. We only need to
9704       --  check overlap for fields starting below this point.
9705
9706       Overlap_Check_Required : Boolean;
9707       --  Used to keep track of whether or not an overlap check is required
9708
9709       Overlap_Detected : Boolean := False;
9710       --  Set True if an overlap is detected
9711
9712       Ccount : Natural := 0;
9713       --  Number of component clauses in record rep clause
9714
9715       procedure Check_Component_Overlap (C1_Ent, C2_Ent : Entity_Id);
9716       --  Given two entities for record components or discriminants, checks
9717       --  if they have overlapping component clauses and issues errors if so.
9718
9719       procedure Find_Component;
9720       --  Finds component entity corresponding to current component clause (in
9721       --  CC), and sets Comp to the entity, and Fbit/Lbit to the zero origin
9722       --  start/stop bits for the field. If there is no matching component or
9723       --  if the matching component does not have a component clause, then
9724       --  that's an error and Comp is set to Empty, but no error message is
9725       --  issued, since the message was already given. Comp is also set to
9726       --  Empty if the current "component clause" is in fact a pragma.
9727
9728       -----------------------------
9729       -- Check_Component_Overlap --
9730       -----------------------------
9731
9732       procedure Check_Component_Overlap (C1_Ent, C2_Ent : Entity_Id) is
9733          CC1 : constant Node_Id := Component_Clause (C1_Ent);
9734          CC2 : constant Node_Id := Component_Clause (C2_Ent);
9735
9736       begin
9737          if Present (CC1) and then Present (CC2) then
9738
9739             --  Exclude odd case where we have two tag components in the same
9740             --  record, both at location zero. This seems a bit strange, but
9741             --  it seems to happen in some circumstances, perhaps on an error.
9742
9743             if Nam_In (Chars (C1_Ent), Name_uTag, Name_uTag) then
9744                return;
9745             end if;
9746
9747             --  Here we check if the two fields overlap
9748
9749             declare
9750                S1 : constant Uint := Component_Bit_Offset (C1_Ent);
9751                S2 : constant Uint := Component_Bit_Offset (C2_Ent);
9752                E1 : constant Uint := S1 + Esize (C1_Ent);
9753                E2 : constant Uint := S2 + Esize (C2_Ent);
9754
9755             begin
9756                if E2 <= S1 or else E1 <= S2 then
9757                   null;
9758                else
9759                   Error_Msg_Node_2 := Component_Name (CC2);
9760                   Error_Msg_Sloc := Sloc (Error_Msg_Node_2);
9761                   Error_Msg_Node_1 := Component_Name (CC1);
9762                   Error_Msg_N
9763                     ("component& overlaps & #", Component_Name (CC1));
9764                   Overlap_Detected := True;
9765                end if;
9766             end;
9767          end if;
9768       end Check_Component_Overlap;
9769
9770       --------------------
9771       -- Find_Component --
9772       --------------------
9773
9774       procedure Find_Component is
9775
9776          procedure Search_Component (R : Entity_Id);
9777          --  Search components of R for a match. If found, Comp is set
9778
9779          ----------------------
9780          -- Search_Component --
9781          ----------------------
9782
9783          procedure Search_Component (R : Entity_Id) is
9784          begin
9785             Comp := First_Component_Or_Discriminant (R);
9786             while Present (Comp) loop
9787
9788                --  Ignore error of attribute name for component name (we
9789                --  already gave an error message for this, so no need to
9790                --  complain here)
9791
9792                if Nkind (Component_Name (CC)) = N_Attribute_Reference then
9793                   null;
9794                else
9795                   exit when Chars (Comp) = Chars (Component_Name (CC));
9796                end if;
9797
9798                Next_Component_Or_Discriminant (Comp);
9799             end loop;
9800          end Search_Component;
9801
9802       --  Start of processing for Find_Component
9803
9804       begin
9805          --  Return with Comp set to Empty if we have a pragma
9806
9807          if Nkind (CC) = N_Pragma then
9808             Comp := Empty;
9809             return;
9810          end if;
9811
9812          --  Search current record for matching component
9813
9814          Search_Component (Rectype);
9815
9816          --  If not found, maybe component of base type discriminant that is
9817          --  absent from statically constrained first subtype.
9818
9819          if No (Comp) then
9820             Search_Component (Base_Type (Rectype));
9821          end if;
9822
9823          --  If no component, or the component does not reference the component
9824          --  clause in question, then there was some previous error for which
9825          --  we already gave a message, so just return with Comp Empty.
9826
9827          if No (Comp) or else Component_Clause (Comp) /= CC then
9828             Check_Error_Detected;
9829             Comp := Empty;
9830
9831          --  Normal case where we have a component clause
9832
9833          else
9834             Fbit := Component_Bit_Offset (Comp);
9835             Lbit := Fbit + Esize (Comp) - 1;
9836          end if;
9837       end Find_Component;
9838
9839    --  Start of processing for Check_Record_Representation_Clause
9840
9841    begin
9842       Find_Type (Ident);
9843       Rectype := Entity (Ident);
9844
9845       if Rectype = Any_Type then
9846          return;
9847       else
9848          Rectype := Underlying_Type (Rectype);
9849       end if;
9850
9851       --  See if we have a fully repped derived tagged type
9852
9853       declare
9854          PS : constant Entity_Id := Parent_Subtype (Rectype);
9855
9856       begin
9857          if Present (PS) and then Is_Fully_Repped_Tagged_Type (PS) then
9858             Tagged_Parent := PS;
9859
9860             --  Find maximum bit of any component of the parent type
9861
9862             Parent_Last_Bit := UI_From_Int (System_Address_Size - 1);
9863             Pcomp := First_Entity (Tagged_Parent);
9864             while Present (Pcomp) loop
9865                if Ekind_In (Pcomp, E_Discriminant, E_Component) then
9866                   if Component_Bit_Offset (Pcomp) /= No_Uint
9867                     and then Known_Static_Esize (Pcomp)
9868                   then
9869                      Parent_Last_Bit :=
9870                        UI_Max
9871                          (Parent_Last_Bit,
9872                           Component_Bit_Offset (Pcomp) + Esize (Pcomp) - 1);
9873                   end if;
9874
9875                   Next_Entity (Pcomp);
9876                end if;
9877             end loop;
9878          end if;
9879       end;
9880
9881       --  All done if no component clauses
9882
9883       CC := First (Component_Clauses (N));
9884
9885       if No (CC) then
9886          return;
9887       end if;
9888
9889       --  If a tag is present, then create a component clause that places it
9890       --  at the start of the record (otherwise gigi may place it after other
9891       --  fields that have rep clauses).
9892
9893       Fent := First_Entity (Rectype);
9894
9895       if Nkind (Fent) = N_Defining_Identifier
9896         and then Chars (Fent) = Name_uTag
9897       then
9898          Set_Component_Bit_Offset    (Fent, Uint_0);
9899          Set_Normalized_Position     (Fent, Uint_0);
9900          Set_Normalized_First_Bit    (Fent, Uint_0);
9901          Set_Normalized_Position_Max (Fent, Uint_0);
9902          Init_Esize                  (Fent, System_Address_Size);
9903
9904          Set_Component_Clause (Fent,
9905            Make_Component_Clause (Loc,
9906              Component_Name => Make_Identifier (Loc, Name_uTag),
9907
9908              Position  => Make_Integer_Literal (Loc, Uint_0),
9909              First_Bit => Make_Integer_Literal (Loc, Uint_0),
9910              Last_Bit  =>
9911                Make_Integer_Literal (Loc,
9912                  UI_From_Int (System_Address_Size))));
9913
9914          Ccount := Ccount + 1;
9915       end if;
9916
9917       Max_Bit_So_Far := Uint_Minus_1;
9918       Overlap_Check_Required := False;
9919
9920       --  Process the component clauses
9921
9922       while Present (CC) loop
9923          Find_Component;
9924
9925          if Present (Comp) then
9926             Ccount := Ccount + 1;
9927
9928             --  We need a full overlap check if record positions non-monotonic
9929
9930             if Fbit <= Max_Bit_So_Far then
9931                Overlap_Check_Required := True;
9932             end if;
9933
9934             Max_Bit_So_Far := Lbit;
9935
9936             --  Check bit position out of range of specified size
9937
9938             if Has_Size_Clause (Rectype)
9939               and then RM_Size (Rectype) <= Lbit
9940             then
9941                Error_Msg_N
9942                  ("bit number out of range of specified size",
9943                   Last_Bit (CC));
9944
9945                --  Check for overlap with tag component
9946
9947             else
9948                if Is_Tagged_Type (Rectype)
9949                  and then Fbit < System_Address_Size
9950                then
9951                   Error_Msg_NE
9952                     ("component overlaps tag field of&",
9953                      Component_Name (CC), Rectype);
9954                   Overlap_Detected := True;
9955                end if;
9956
9957                if Hbit < Lbit then
9958                   Hbit := Lbit;
9959                end if;
9960             end if;
9961
9962             --  Check parent overlap if component might overlap parent field
9963
9964             if Present (Tagged_Parent) and then Fbit <= Parent_Last_Bit then
9965                Pcomp := First_Component_Or_Discriminant (Tagged_Parent);
9966                while Present (Pcomp) loop
9967                   if not Is_Tag (Pcomp)
9968                     and then Chars (Pcomp) /= Name_uParent
9969                   then
9970                      Check_Component_Overlap (Comp, Pcomp);
9971                   end if;
9972
9973                   Next_Component_Or_Discriminant (Pcomp);
9974                end loop;
9975             end if;
9976          end if;
9977
9978          Next (CC);
9979       end loop;
9980
9981       --  Now that we have processed all the component clauses, check for
9982       --  overlap. We have to leave this till last, since the components can
9983       --  appear in any arbitrary order in the representation clause.
9984
9985       --  We do not need this check if all specified ranges were monotonic,
9986       --  as recorded by Overlap_Check_Required being False at this stage.
9987
9988       --  This first section checks if there are any overlapping entries at
9989       --  all. It does this by sorting all entries and then seeing if there are
9990       --  any overlaps. If there are none, then that is decisive, but if there
9991       --  are overlaps, they may still be OK (they may result from fields in
9992       --  different variants).
9993
9994       if Overlap_Check_Required then
9995          Overlap_Check1 : declare
9996
9997             OC_Fbit : array (0 .. Ccount) of Uint;
9998             --  First-bit values for component clauses, the value is the offset
9999             --  of the first bit of the field from start of record. The zero
10000             --  entry is for use in sorting.
10001
10002             OC_Lbit : array (0 .. Ccount) of Uint;
10003             --  Last-bit values for component clauses, the value is the offset
10004             --  of the last bit of the field from start of record. The zero
10005             --  entry is for use in sorting.
10006
10007             OC_Count : Natural := 0;
10008             --  Count of entries in OC_Fbit and OC_Lbit
10009
10010             function OC_Lt (Op1, Op2 : Natural) return Boolean;
10011             --  Compare routine for Sort
10012
10013             procedure OC_Move (From : Natural; To : Natural);
10014             --  Move routine for Sort
10015
10016             package Sorting is new GNAT.Heap_Sort_G (OC_Move, OC_Lt);
10017
10018             -----------
10019             -- OC_Lt --
10020             -----------
10021
10022             function OC_Lt (Op1, Op2 : Natural) return Boolean is
10023             begin
10024                return OC_Fbit (Op1) < OC_Fbit (Op2);
10025             end OC_Lt;
10026
10027             -------------
10028             -- OC_Move --
10029             -------------
10030
10031             procedure OC_Move (From : Natural; To : Natural) is
10032             begin
10033                OC_Fbit (To) := OC_Fbit (From);
10034                OC_Lbit (To) := OC_Lbit (From);
10035             end OC_Move;
10036
10037             --  Start of processing for Overlap_Check
10038
10039          begin
10040             CC := First (Component_Clauses (N));
10041             while Present (CC) loop
10042
10043                --  Exclude component clause already marked in error
10044
10045                if not Error_Posted (CC) then
10046                   Find_Component;
10047
10048                   if Present (Comp) then
10049                      OC_Count := OC_Count + 1;
10050                      OC_Fbit (OC_Count) := Fbit;
10051                      OC_Lbit (OC_Count) := Lbit;
10052                   end if;
10053                end if;
10054
10055                Next (CC);
10056             end loop;
10057
10058             Sorting.Sort (OC_Count);
10059
10060             Overlap_Check_Required := False;
10061             for J in 1 .. OC_Count - 1 loop
10062                if OC_Lbit (J) >= OC_Fbit (J + 1) then
10063                   Overlap_Check_Required := True;
10064                   exit;
10065                end if;
10066             end loop;
10067          end Overlap_Check1;
10068       end if;
10069
10070       --  If Overlap_Check_Required is still True, then we have to do the full
10071       --  scale overlap check, since we have at least two fields that do
10072       --  overlap, and we need to know if that is OK since they are in
10073       --  different variant, or whether we have a definite problem.
10074
10075       if Overlap_Check_Required then
10076          Overlap_Check2 : declare
10077             C1_Ent, C2_Ent : Entity_Id;
10078             --  Entities of components being checked for overlap
10079
10080             Clist : Node_Id;
10081             --  Component_List node whose Component_Items are being checked
10082
10083             Citem : Node_Id;
10084             --  Component declaration for component being checked
10085
10086          begin
10087             C1_Ent := First_Entity (Base_Type (Rectype));
10088
10089             --  Loop through all components in record. For each component check
10090             --  for overlap with any of the preceding elements on the component
10091             --  list containing the component and also, if the component is in
10092             --  a variant, check against components outside the case structure.
10093             --  This latter test is repeated recursively up the variant tree.
10094
10095             Main_Component_Loop : while Present (C1_Ent) loop
10096                if not Ekind_In (C1_Ent, E_Component, E_Discriminant) then
10097                   goto Continue_Main_Component_Loop;
10098                end if;
10099
10100                --  Skip overlap check if entity has no declaration node. This
10101                --  happens with discriminants in constrained derived types.
10102                --  Possibly we are missing some checks as a result, but that
10103                --  does not seem terribly serious.
10104
10105                if No (Declaration_Node (C1_Ent)) then
10106                   goto Continue_Main_Component_Loop;
10107                end if;
10108
10109                Clist := Parent (List_Containing (Declaration_Node (C1_Ent)));
10110
10111                --  Loop through component lists that need checking. Check the
10112                --  current component list and all lists in variants above us.
10113
10114                Component_List_Loop : loop
10115
10116                   --  If derived type definition, go to full declaration
10117                   --  If at outer level, check discriminants if there are any.
10118
10119                   if Nkind (Clist) = N_Derived_Type_Definition then
10120                      Clist := Parent (Clist);
10121                   end if;
10122
10123                   --  Outer level of record definition, check discriminants
10124
10125                   if Nkind_In (Clist, N_Full_Type_Declaration,
10126                                       N_Private_Type_Declaration)
10127                   then
10128                      if Has_Discriminants (Defining_Identifier (Clist)) then
10129                         C2_Ent :=
10130                           First_Discriminant (Defining_Identifier (Clist));
10131                         while Present (C2_Ent) loop
10132                            exit when C1_Ent = C2_Ent;
10133                            Check_Component_Overlap (C1_Ent, C2_Ent);
10134                            Next_Discriminant (C2_Ent);
10135                         end loop;
10136                      end if;
10137
10138                      --  Record extension case
10139
10140                   elsif Nkind (Clist) = N_Derived_Type_Definition then
10141                      Clist := Empty;
10142
10143                      --  Otherwise check one component list
10144
10145                   else
10146                      Citem := First (Component_Items (Clist));
10147                      while Present (Citem) loop
10148                         if Nkind (Citem) = N_Component_Declaration then
10149                            C2_Ent := Defining_Identifier (Citem);
10150                            exit when C1_Ent = C2_Ent;
10151                            Check_Component_Overlap (C1_Ent, C2_Ent);
10152                         end if;
10153
10154                         Next (Citem);
10155                      end loop;
10156                   end if;
10157
10158                   --  Check for variants above us (the parent of the Clist can
10159                   --  be a variant, in which case its parent is a variant part,
10160                   --  and the parent of the variant part is a component list
10161                   --  whose components must all be checked against the current
10162                   --  component for overlap).
10163
10164                   if Nkind (Parent (Clist)) = N_Variant then
10165                      Clist := Parent (Parent (Parent (Clist)));
10166
10167                      --  Check for possible discriminant part in record, this
10168                      --  is treated essentially as another level in the
10169                      --  recursion. For this case the parent of the component
10170                      --  list is the record definition, and its parent is the
10171                      --  full type declaration containing the discriminant
10172                      --  specifications.
10173
10174                   elsif Nkind (Parent (Clist)) = N_Record_Definition then
10175                      Clist := Parent (Parent ((Clist)));
10176
10177                      --  If neither of these two cases, we are at the top of
10178                      --  the tree.
10179
10180                   else
10181                      exit Component_List_Loop;
10182                   end if;
10183                end loop Component_List_Loop;
10184
10185                <<Continue_Main_Component_Loop>>
10186                Next_Entity (C1_Ent);
10187
10188             end loop Main_Component_Loop;
10189          end Overlap_Check2;
10190       end if;
10191
10192       --  The following circuit deals with warning on record holes (gaps). We
10193       --  skip this check if overlap was detected, since it makes sense for the
10194       --  programmer to fix this illegality before worrying about warnings.
10195
10196       if not Overlap_Detected and Warn_On_Record_Holes then
10197          Record_Hole_Check : declare
10198             Decl : constant Node_Id := Declaration_Node (Base_Type (Rectype));
10199             --  Full declaration of record type
10200
10201             procedure Check_Component_List
10202               (CL   : Node_Id;
10203                Sbit : Uint;
10204                DS   : List_Id);
10205             --  Check component list CL for holes. The starting bit should be
10206             --  Sbit. which is zero for the main record component list and set
10207             --  appropriately for recursive calls for variants. DS is set to
10208             --  a list of discriminant specifications to be included in the
10209             --  consideration of components. It is No_List if none to consider.
10210
10211             --------------------------
10212             -- Check_Component_List --
10213             --------------------------
10214
10215             procedure Check_Component_List
10216               (CL   : Node_Id;
10217                Sbit : Uint;
10218                DS   : List_Id)
10219             is
10220                Compl : Integer;
10221
10222             begin
10223                Compl := Integer (List_Length (Component_Items (CL)));
10224
10225                if DS /= No_List then
10226                   Compl := Compl + Integer (List_Length (DS));
10227                end if;
10228
10229                declare
10230                   Comps : array (Natural range 0 .. Compl) of Entity_Id;
10231                   --  Gather components (zero entry is for sort routine)
10232
10233                   Ncomps : Natural := 0;
10234                   --  Number of entries stored in Comps (starting at Comps (1))
10235
10236                   Citem : Node_Id;
10237                   --  One component item or discriminant specification
10238
10239                   Nbit  : Uint;
10240                   --  Starting bit for next component
10241
10242                   CEnt  : Entity_Id;
10243                   --  Component entity
10244
10245                   Variant : Node_Id;
10246                   --  One variant
10247
10248                   function Lt (Op1, Op2 : Natural) return Boolean;
10249                   --  Compare routine for Sort
10250
10251                   procedure Move (From : Natural; To : Natural);
10252                   --  Move routine for Sort
10253
10254                   package Sorting is new GNAT.Heap_Sort_G (Move, Lt);
10255
10256                   --------
10257                   -- Lt --
10258                   --------
10259
10260                   function Lt (Op1, Op2 : Natural) return Boolean is
10261                   begin
10262                      return Component_Bit_Offset (Comps (Op1))
10263                        <
10264                        Component_Bit_Offset (Comps (Op2));
10265                   end Lt;
10266
10267                   ----------
10268                   -- Move --
10269                   ----------
10270
10271                   procedure Move (From : Natural; To : Natural) is
10272                   begin
10273                      Comps (To) := Comps (From);
10274                   end Move;
10275
10276                begin
10277                   --  Gather discriminants into Comp
10278
10279                   if DS /= No_List then
10280                      Citem := First (DS);
10281                      while Present (Citem) loop
10282                         if Nkind (Citem) = N_Discriminant_Specification then
10283                            declare
10284                               Ent : constant Entity_Id :=
10285                                       Defining_Identifier (Citem);
10286                            begin
10287                               if Ekind (Ent) = E_Discriminant then
10288                                  Ncomps := Ncomps + 1;
10289                                  Comps (Ncomps) := Ent;
10290                               end if;
10291                            end;
10292                         end if;
10293
10294                         Next (Citem);
10295                      end loop;
10296                   end if;
10297
10298                   --  Gather component entities into Comp
10299
10300                   Citem := First (Component_Items (CL));
10301                   while Present (Citem) loop
10302                      if Nkind (Citem) = N_Component_Declaration then
10303                         Ncomps := Ncomps + 1;
10304                         Comps (Ncomps) := Defining_Identifier (Citem);
10305                      end if;
10306
10307                      Next (Citem);
10308                   end loop;
10309
10310                   --  Now sort the component entities based on the first bit.
10311                   --  Note we already know there are no overlapping components.
10312
10313                   Sorting.Sort (Ncomps);
10314
10315                   --  Loop through entries checking for holes
10316
10317                   Nbit := Sbit;
10318                   for J in 1 .. Ncomps loop
10319                      CEnt := Comps (J);
10320                      Error_Msg_Uint_1 := Component_Bit_Offset (CEnt) - Nbit;
10321
10322                      if Error_Msg_Uint_1 > 0 then
10323                         Error_Msg_NE
10324                           ("?H?^-bit gap before component&",
10325                            Component_Name (Component_Clause (CEnt)), CEnt);
10326                      end if;
10327
10328                      Nbit := Component_Bit_Offset (CEnt) + Esize (CEnt);
10329                   end loop;
10330
10331                   --  Process variant parts recursively if present
10332
10333                   if Present (Variant_Part (CL)) then
10334                      Variant := First (Variants (Variant_Part (CL)));
10335                      while Present (Variant) loop
10336                         Check_Component_List
10337                           (Component_List (Variant), Nbit, No_List);
10338                         Next (Variant);
10339                      end loop;
10340                   end if;
10341                end;
10342             end Check_Component_List;
10343
10344          --  Start of processing for Record_Hole_Check
10345
10346          begin
10347             declare
10348                Sbit : Uint;
10349
10350             begin
10351                if Is_Tagged_Type (Rectype) then
10352                   Sbit := UI_From_Int (System_Address_Size);
10353                else
10354                   Sbit := Uint_0;
10355                end if;
10356
10357                if Nkind (Decl) = N_Full_Type_Declaration
10358                  and then Nkind (Type_Definition (Decl)) = N_Record_Definition
10359                then
10360                   Check_Component_List
10361                     (Component_List (Type_Definition (Decl)),
10362                      Sbit,
10363                      Discriminant_Specifications (Decl));
10364                end if;
10365             end;
10366          end Record_Hole_Check;
10367       end if;
10368
10369       --  For records that have component clauses for all components, and whose
10370       --  size is less than or equal to 32, we need to know the size in the
10371       --  front end to activate possible packed array processing where the
10372       --  component type is a record.
10373
10374       --  At this stage Hbit + 1 represents the first unused bit from all the
10375       --  component clauses processed, so if the component clauses are
10376       --  complete, then this is the length of the record.
10377
10378       --  For records longer than System.Storage_Unit, and for those where not
10379       --  all components have component clauses, the back end determines the
10380       --  length (it may for example be appropriate to round up the size
10381       --  to some convenient boundary, based on alignment considerations, etc).
10382
10383       if Unknown_RM_Size (Rectype) and then Hbit + 1 <= 32 then
10384
10385          --  Nothing to do if at least one component has no component clause
10386
10387          Comp := First_Component_Or_Discriminant (Rectype);
10388          while Present (Comp) loop
10389             exit when No (Component_Clause (Comp));
10390             Next_Component_Or_Discriminant (Comp);
10391          end loop;
10392
10393          --  If we fall out of loop, all components have component clauses
10394          --  and so we can set the size to the maximum value.
10395
10396          if No (Comp) then
10397             Set_RM_Size (Rectype, Hbit + 1);
10398          end if;
10399       end if;
10400    end Check_Record_Representation_Clause;
10401
10402    ----------------
10403    -- Check_Size --
10404    ----------------
10405
10406    procedure Check_Size
10407      (N      : Node_Id;
10408       T      : Entity_Id;
10409       Siz    : Uint;
10410       Biased : out Boolean)
10411    is
10412       UT : constant Entity_Id := Underlying_Type (T);
10413       M  : Uint;
10414
10415    begin
10416       Biased := False;
10417
10418       --  Reject patently improper size values.
10419
10420       if Is_Elementary_Type (T)
10421         and then Siz > UI_From_Int (Int'Last)
10422       then
10423          Error_Msg_N ("Size value too large for elementary type", N);
10424
10425          if Nkind (Original_Node (N)) = N_Op_Expon then
10426             Error_Msg_N
10427               ("\maybe '* was meant, rather than '*'*", Original_Node (N));
10428          end if;
10429       end if;
10430
10431       --  Dismiss generic types
10432
10433       if Is_Generic_Type (T)
10434            or else
10435          Is_Generic_Type (UT)
10436            or else
10437          Is_Generic_Type (Root_Type (UT))
10438       then
10439          return;
10440
10441       --  Guard against previous errors
10442
10443       elsif No (UT) or else UT = Any_Type then
10444          Check_Error_Detected;
10445          return;
10446
10447       --  Check case of bit packed array
10448
10449       elsif Is_Array_Type (UT)
10450         and then Known_Static_Component_Size (UT)
10451         and then Is_Bit_Packed_Array (UT)
10452       then
10453          declare
10454             Asiz : Uint;
10455             Indx : Node_Id;
10456             Ityp : Entity_Id;
10457
10458          begin
10459             Asiz := Component_Size (UT);
10460             Indx := First_Index (UT);
10461             loop
10462                Ityp := Etype (Indx);
10463
10464                --  If non-static bound, then we are not in the business of
10465                --  trying to check the length, and indeed an error will be
10466                --  issued elsewhere, since sizes of non-static array types
10467                --  cannot be set implicitly or explicitly.
10468
10469                if not Is_OK_Static_Subtype (Ityp) then
10470                   return;
10471                end if;
10472
10473                --  Otherwise accumulate next dimension
10474
10475                Asiz := Asiz * (Expr_Value (Type_High_Bound (Ityp)) -
10476                                Expr_Value (Type_Low_Bound  (Ityp)) +
10477                                Uint_1);
10478
10479                Next_Index (Indx);
10480                exit when No (Indx);
10481             end loop;
10482
10483             if Asiz <= Siz then
10484                return;
10485
10486             else
10487                Error_Msg_Uint_1 := Asiz;
10488                Error_Msg_NE
10489                  ("size for& too small, minimum allowed is ^", N, T);
10490                Set_Esize   (T, Asiz);
10491                Set_RM_Size (T, Asiz);
10492             end if;
10493          end;
10494
10495       --  All other composite types are ignored
10496
10497       elsif Is_Composite_Type (UT) then
10498          return;
10499
10500       --  For fixed-point types, don't check minimum if type is not frozen,
10501       --  since we don't know all the characteristics of the type that can
10502       --  affect the size (e.g. a specified small) till freeze time.
10503
10504       elsif Is_Fixed_Point_Type (UT)
10505         and then not Is_Frozen (UT)
10506       then
10507          null;
10508
10509       --  Cases for which a minimum check is required
10510
10511       else
10512          --  Ignore if specified size is correct for the type
10513
10514          if Known_Esize (UT) and then Siz = Esize (UT) then
10515             return;
10516          end if;
10517
10518          --  Otherwise get minimum size
10519
10520          M := UI_From_Int (Minimum_Size (UT));
10521
10522          if Siz < M then
10523
10524             --  Size is less than minimum size, but one possibility remains
10525             --  that we can manage with the new size if we bias the type.
10526
10527             M := UI_From_Int (Minimum_Size (UT, Biased => True));
10528
10529             if Siz < M then
10530                Error_Msg_Uint_1 := M;
10531                Error_Msg_NE
10532                  ("size for& too small, minimum allowed is ^", N, T);
10533                Set_Esize (T, M);
10534                Set_RM_Size (T, M);
10535             else
10536                Biased := True;
10537             end if;
10538          end if;
10539       end if;
10540    end Check_Size;
10541
10542    --------------------------
10543    -- Freeze_Entity_Checks --
10544    --------------------------
10545
10546    procedure Freeze_Entity_Checks (N : Node_Id) is
10547       procedure Hide_Non_Overridden_Subprograms (Typ : Entity_Id);
10548       --  Inspect the primitive operations of type Typ and hide all pairs of
10549       --  implicitly declared non-overridden non-fully conformant homographs
10550       --  (Ada RM 8.3 12.3/2).
10551
10552       -------------------------------------
10553       -- Hide_Non_Overridden_Subprograms --
10554       -------------------------------------
10555
10556       procedure Hide_Non_Overridden_Subprograms (Typ : Entity_Id) is
10557          procedure Hide_Matching_Homographs
10558            (Subp_Id    : Entity_Id;
10559             Start_Elmt : Elmt_Id);
10560          --  Inspect a list of primitive operations starting with Start_Elmt
10561          --  and find matching implicitly declared non-overridden non-fully
10562          --  conformant homographs of Subp_Id. If found, all matches along
10563          --  with Subp_Id are hidden from all visibility.
10564
10565          function Is_Non_Overridden_Or_Null_Procedure
10566            (Subp_Id : Entity_Id) return Boolean;
10567          --  Determine whether subprogram Subp_Id is implicitly declared non-
10568          --  overridden subprogram or an implicitly declared null procedure.
10569
10570          ------------------------------
10571          -- Hide_Matching_Homographs --
10572          ------------------------------
10573
10574          procedure Hide_Matching_Homographs
10575            (Subp_Id    : Entity_Id;
10576             Start_Elmt : Elmt_Id)
10577          is
10578             Prim      : Entity_Id;
10579             Prim_Elmt : Elmt_Id;
10580
10581          begin
10582             Prim_Elmt := Start_Elmt;
10583             while Present (Prim_Elmt) loop
10584                Prim := Node (Prim_Elmt);
10585
10586                --  The current primitive is implicitly declared non-overridden
10587                --  non-fully conformant homograph of Subp_Id. Both subprograms
10588                --  must be hidden from visibility.
10589
10590                if Chars (Prim) = Chars (Subp_Id)
10591                  and then Is_Non_Overridden_Or_Null_Procedure (Prim)
10592                  and then not Fully_Conformant (Prim, Subp_Id)
10593                then
10594                   Set_Is_Hidden_Non_Overridden_Subpgm (Prim);
10595                   Set_Is_Immediately_Visible          (Prim, False);
10596                   Set_Is_Potentially_Use_Visible      (Prim, False);
10597
10598                   Set_Is_Hidden_Non_Overridden_Subpgm (Subp_Id);
10599                   Set_Is_Immediately_Visible          (Subp_Id, False);
10600                   Set_Is_Potentially_Use_Visible      (Subp_Id, False);
10601                end if;
10602
10603                Next_Elmt (Prim_Elmt);
10604             end loop;
10605          end Hide_Matching_Homographs;
10606
10607          -----------------------------------------
10608          -- Is_Non_Overridden_Or_Null_Procedure --
10609          -----------------------------------------
10610
10611          function Is_Non_Overridden_Or_Null_Procedure
10612            (Subp_Id : Entity_Id) return Boolean
10613          is
10614             Alias_Id : Entity_Id;
10615
10616          begin
10617             --  The subprogram is inherited (implicitly declared), it does not
10618             --  override and does not cover a primitive of an interface.
10619
10620             if Ekind_In (Subp_Id, E_Function, E_Procedure)
10621               and then Present (Alias (Subp_Id))
10622               and then No (Interface_Alias (Subp_Id))
10623               and then No (Overridden_Operation (Subp_Id))
10624             then
10625                Alias_Id := Alias (Subp_Id);
10626
10627                if Requires_Overriding (Alias_Id) then
10628                   return True;
10629
10630                elsif Nkind (Parent (Alias_Id)) = N_Procedure_Specification
10631                  and then Null_Present (Parent (Alias_Id))
10632                then
10633                   return True;
10634                end if;
10635             end if;
10636
10637             return False;
10638          end Is_Non_Overridden_Or_Null_Procedure;
10639
10640          --  Local variables
10641
10642          Prim_Ops  : constant Elist_Id := Direct_Primitive_Operations (Typ);
10643          Prim      : Entity_Id;
10644          Prim_Elmt : Elmt_Id;
10645
10646       --  Start of processing for Hide_Non_Overridden_Subprograms
10647
10648       begin
10649          --  Inspect the list of primitives looking for non-overridden
10650          --  subprograms.
10651
10652          if Present (Prim_Ops) then
10653             Prim_Elmt := First_Elmt (Prim_Ops);
10654             while Present (Prim_Elmt) loop
10655                Prim := Node (Prim_Elmt);
10656                Next_Elmt (Prim_Elmt);
10657
10658                if Is_Non_Overridden_Or_Null_Procedure (Prim) then
10659                   Hide_Matching_Homographs
10660                     (Subp_Id    => Prim,
10661                      Start_Elmt => Prim_Elmt);
10662                end if;
10663             end loop;
10664          end if;
10665       end Hide_Non_Overridden_Subprograms;
10666
10667       ---------------------
10668       -- Local variables --
10669       ---------------------
10670
10671       E : constant Entity_Id := Entity (N);
10672
10673       Non_Generic_Case : constant Boolean := Nkind (N) = N_Freeze_Entity;
10674       --  True in non-generic case. Some of the processing here is skipped
10675       --  for the generic case since it is not needed. Basically in the
10676       --  generic case, we only need to do stuff that might generate error
10677       --  messages or warnings.
10678
10679    --  Start of processing for Freeze_Entity_Checks
10680
10681    begin
10682       --  Remember that we are processing a freezing entity. Required to
10683       --  ensure correct decoration of internal entities associated with
10684       --  interfaces (see New_Overloaded_Entity).
10685
10686       Inside_Freezing_Actions := Inside_Freezing_Actions + 1;
10687
10688       --  For tagged types covering interfaces add internal entities that link
10689       --  the primitives of the interfaces with the primitives that cover them.
10690       --  Note: These entities were originally generated only when generating
10691       --  code because their main purpose was to provide support to initialize
10692       --  the secondary dispatch tables. They are now generated also when
10693       --  compiling with no code generation to provide ASIS the relationship
10694       --  between interface primitives and tagged type primitives. They are
10695       --  also used to locate primitives covering interfaces when processing
10696       --  generics (see Derive_Subprograms).
10697
10698       --  This is not needed in the generic case
10699
10700       if Ada_Version >= Ada_2005
10701         and then Non_Generic_Case
10702         and then Ekind (E) = E_Record_Type
10703         and then Is_Tagged_Type (E)
10704         and then not Is_Interface (E)
10705         and then Has_Interfaces (E)
10706       then
10707          --  This would be a good common place to call the routine that checks
10708          --  overriding of interface primitives (and thus factorize calls to
10709          --  Check_Abstract_Overriding located at different contexts in the
10710          --  compiler). However, this is not possible because it causes
10711          --  spurious errors in case of late overriding.
10712
10713          Add_Internal_Interface_Entities (E);
10714       end if;
10715
10716       --  After all forms of overriding have been resolved, a tagged type may
10717       --  be left with a set of implicitly declared and possibly erroneous
10718       --  abstract subprograms, null procedures and subprograms that require
10719       --  overriding. If this set contains fully conformat homographs, then one
10720       --  is chosen arbitrarily (already done during resolution), otherwise all
10721       --  remaining non-fully conformant homographs are hidden from visibility
10722       --  (Ada RM 8.3 12.3/2).
10723
10724       if Is_Tagged_Type (E) then
10725          Hide_Non_Overridden_Subprograms (E);
10726       end if;
10727
10728       --  Check CPP types
10729
10730       if Ekind (E) = E_Record_Type
10731         and then Is_CPP_Class (E)
10732         and then Is_Tagged_Type (E)
10733         and then Tagged_Type_Expansion
10734       then
10735          if CPP_Num_Prims (E) = 0 then
10736
10737             --  If the CPP type has user defined components then it must import
10738             --  primitives from C++. This is required because if the C++ class
10739             --  has no primitives then the C++ compiler does not added the _tag
10740             --  component to the type.
10741
10742             if First_Entity (E) /= Last_Entity (E) then
10743                Error_Msg_N
10744                  ("'C'P'P type must import at least one primitive from C++??",
10745                   E);
10746             end if;
10747          end if;
10748
10749          --  Check that all its primitives are abstract or imported from C++.
10750          --  Check also availability of the C++ constructor.
10751
10752          declare
10753             Has_Constructors : constant Boolean := Has_CPP_Constructors (E);
10754             Elmt             : Elmt_Id;
10755             Error_Reported   : Boolean := False;
10756             Prim             : Node_Id;
10757
10758          begin
10759             Elmt := First_Elmt (Primitive_Operations (E));
10760             while Present (Elmt) loop
10761                Prim := Node (Elmt);
10762
10763                if Comes_From_Source (Prim) then
10764                   if Is_Abstract_Subprogram (Prim) then
10765                      null;
10766
10767                   elsif not Is_Imported (Prim)
10768                     or else Convention (Prim) /= Convention_CPP
10769                   then
10770                      Error_Msg_N
10771                        ("primitives of 'C'P'P types must be imported from C++ "
10772                         & "or abstract??", Prim);
10773
10774                   elsif not Has_Constructors
10775                      and then not Error_Reported
10776                   then
10777                      Error_Msg_Name_1 := Chars (E);
10778                      Error_Msg_N
10779                        ("??'C'P'P constructor required for type %", Prim);
10780                      Error_Reported := True;
10781                   end if;
10782                end if;
10783
10784                Next_Elmt (Elmt);
10785             end loop;
10786          end;
10787       end if;
10788
10789       --  Check Ada derivation of CPP type
10790
10791       if Expander_Active              -- why? losing errors in -gnatc mode???
10792         and then Present (Etype (E))  -- defend against errors
10793         and then Tagged_Type_Expansion
10794         and then Ekind (E) = E_Record_Type
10795         and then Etype (E) /= E
10796         and then Is_CPP_Class (Etype (E))
10797         and then CPP_Num_Prims (Etype (E)) > 0
10798         and then not Is_CPP_Class (E)
10799         and then not Has_CPP_Constructors (Etype (E))
10800       then
10801          --  If the parent has C++ primitives but it has no constructor then
10802          --  check that all the primitives are overridden in this derivation;
10803          --  otherwise the constructor of the parent is needed to build the
10804          --  dispatch table.
10805
10806          declare
10807             Elmt : Elmt_Id;
10808             Prim : Node_Id;
10809
10810          begin
10811             Elmt := First_Elmt (Primitive_Operations (E));
10812             while Present (Elmt) loop
10813                Prim := Node (Elmt);
10814
10815                if not Is_Abstract_Subprogram (Prim)
10816                  and then No (Interface_Alias (Prim))
10817                  and then Find_Dispatching_Type (Ultimate_Alias (Prim)) /= E
10818                then
10819                   Error_Msg_Name_1 := Chars (Etype (E));
10820                   Error_Msg_N
10821                     ("'C'P'P constructor required for parent type %", E);
10822                   exit;
10823                end if;
10824
10825                Next_Elmt (Elmt);
10826             end loop;
10827          end;
10828       end if;
10829
10830       Inside_Freezing_Actions := Inside_Freezing_Actions - 1;
10831
10832       --  If we have a type with predicates, build predicate function. This
10833       --  is not needed in the generic case, and is not needed within TSS
10834       --  subprograms and other predefined primitives.
10835
10836       if Non_Generic_Case
10837         and then Is_Type (E)
10838         and then Has_Predicates (E)
10839         and then not Within_Internal_Subprogram
10840       then
10841          Build_Predicate_Functions (E, N);
10842       end if;
10843
10844       --  If type has delayed aspects, this is where we do the preanalysis at
10845       --  the freeze point, as part of the consistent visibility check. Note
10846       --  that this must be done after calling Build_Predicate_Functions or
10847       --  Build_Invariant_Procedure since these subprograms fix occurrences of
10848       --  the subtype name in the saved expression so that they will not cause
10849       --  trouble in the preanalysis.
10850
10851       --  This is also not needed in the generic case
10852
10853       if Non_Generic_Case
10854         and then Has_Delayed_Aspects (E)
10855         and then Scope (E) = Current_Scope
10856       then
10857          --  Retrieve the visibility to the discriminants in order to properly
10858          --  analyze the aspects.
10859
10860          Push_Scope_And_Install_Discriminants (E);
10861
10862          declare
10863             Ritem : Node_Id;
10864
10865          begin
10866             --  Look for aspect specification entries for this entity
10867
10868             Ritem := First_Rep_Item (E);
10869             while Present (Ritem) loop
10870                if Nkind (Ritem) = N_Aspect_Specification
10871                  and then Entity (Ritem) = E
10872                  and then Is_Delayed_Aspect (Ritem)
10873                then
10874                   Check_Aspect_At_Freeze_Point (Ritem);
10875                end if;
10876
10877                Next_Rep_Item (Ritem);
10878             end loop;
10879          end;
10880
10881          Uninstall_Discriminants_And_Pop_Scope (E);
10882       end if;
10883
10884       --  For a record type, deal with variant parts. This has to be delayed
10885       --  to this point, because of the issue of statically predicated
10886       --  subtypes, which we have to ensure are frozen before checking
10887       --  choices, since we need to have the static choice list set.
10888
10889       if Is_Record_Type (E) then
10890          Check_Variant_Part : declare
10891             D  : constant Node_Id := Declaration_Node (E);
10892             T  : Node_Id;
10893             C  : Node_Id;
10894             VP : Node_Id;
10895
10896             Others_Present : Boolean;
10897             pragma Warnings (Off, Others_Present);
10898             --  Indicates others present, not used in this case
10899
10900             procedure Non_Static_Choice_Error (Choice : Node_Id);
10901             --  Error routine invoked by the generic instantiation below when
10902             --  the variant part has a non static choice.
10903
10904             procedure Process_Declarations (Variant : Node_Id);
10905             --  Processes declarations associated with a variant. We analyzed
10906             --  the declarations earlier (in Sem_Ch3.Analyze_Variant_Part),
10907             --  but we still need the recursive call to Check_Choices for any
10908             --  nested variant to get its choices properly processed. This is
10909             --  also where we expand out the choices if expansion is active.
10910
10911             package Variant_Choices_Processing is new
10912               Generic_Check_Choices
10913                 (Process_Empty_Choice      => No_OP,
10914                  Process_Non_Static_Choice => Non_Static_Choice_Error,
10915                  Process_Associated_Node   => Process_Declarations);
10916             use Variant_Choices_Processing;
10917
10918             -----------------------------
10919             -- Non_Static_Choice_Error --
10920             -----------------------------
10921
10922             procedure Non_Static_Choice_Error (Choice : Node_Id) is
10923             begin
10924                Flag_Non_Static_Expr
10925                  ("choice given in variant part is not static!", Choice);
10926             end Non_Static_Choice_Error;
10927
10928             --------------------------
10929             -- Process_Declarations --
10930             --------------------------
10931
10932             procedure Process_Declarations (Variant : Node_Id) is
10933                CL : constant Node_Id := Component_List (Variant);
10934                VP : Node_Id;
10935
10936             begin
10937                --  Check for static predicate present in this variant
10938
10939                if Has_SP_Choice (Variant) then
10940
10941                   --  Here we expand. You might expect to find this call in
10942                   --  Expand_N_Variant_Part, but that is called when we first
10943                   --  see the variant part, and we cannot do this expansion
10944                   --  earlier than the freeze point, since for statically
10945                   --  predicated subtypes, the predicate is not known till
10946                   --  the freeze point.
10947
10948                   --  Furthermore, we do this expansion even if the expander
10949                   --  is not active, because other semantic processing, e.g.
10950                   --  for aggregates, requires the expanded list of choices.
10951
10952                   --  If the expander is not active, then we can't just clobber
10953                   --  the list since it would invalidate the ASIS -gnatct tree.
10954                   --  So we have to rewrite the variant part with a Rewrite
10955                   --  call that replaces it with a copy and clobber the copy.
10956
10957                   if not Expander_Active then
10958                      declare
10959                         NewV : constant Node_Id := New_Copy (Variant);
10960                      begin
10961                         Set_Discrete_Choices
10962                           (NewV, New_Copy_List (Discrete_Choices (Variant)));
10963                         Rewrite (Variant, NewV);
10964                      end;
10965                   end if;
10966
10967                   Expand_Static_Predicates_In_Choices (Variant);
10968                end if;
10969
10970                --  We don't need to worry about the declarations in the variant
10971                --  (since they were analyzed by Analyze_Choices when we first
10972                --  encountered the variant), but we do need to take care of
10973                --  expansion of any nested variants.
10974
10975                if not Null_Present (CL) then
10976                   VP := Variant_Part (CL);
10977
10978                   if Present (VP) then
10979                      Check_Choices
10980                        (VP, Variants (VP), Etype (Name (VP)), Others_Present);
10981                   end if;
10982                end if;
10983             end Process_Declarations;
10984
10985          --  Start of processing for Check_Variant_Part
10986
10987          begin
10988             --  Find component list
10989
10990             C := Empty;
10991
10992             if Nkind (D) = N_Full_Type_Declaration then
10993                T := Type_Definition (D);
10994
10995                if Nkind (T) = N_Record_Definition then
10996                   C := Component_List (T);
10997
10998                elsif Nkind (T) = N_Derived_Type_Definition
10999                  and then Present (Record_Extension_Part (T))
11000                then
11001                   C := Component_List (Record_Extension_Part (T));
11002                end if;
11003             end if;
11004
11005             --  Case of variant part present
11006
11007             if Present (C) and then Present (Variant_Part (C)) then
11008                VP := Variant_Part (C);
11009
11010                --  Check choices
11011
11012                Check_Choices
11013                  (VP, Variants (VP), Etype (Name (VP)), Others_Present);
11014
11015                --  If the last variant does not contain the Others choice,
11016                --  replace it with an N_Others_Choice node since Gigi always
11017                --  wants an Others. Note that we do not bother to call Analyze
11018                --  on the modified variant part, since its only effect would be
11019                --  to compute the Others_Discrete_Choices node laboriously, and
11020                --  of course we already know the list of choices corresponding
11021                --  to the others choice (it's the list we're replacing).
11022
11023                --  We only want to do this if the expander is active, since
11024                --  we do not want to clobber the ASIS tree.
11025
11026                if Expander_Active then
11027                   declare
11028                      Last_Var : constant Node_Id :=
11029                                      Last_Non_Pragma (Variants (VP));
11030
11031                      Others_Node : Node_Id;
11032
11033                   begin
11034                      if Nkind (First (Discrete_Choices (Last_Var))) /=
11035                                                             N_Others_Choice
11036                      then
11037                         Others_Node := Make_Others_Choice (Sloc (Last_Var));
11038                         Set_Others_Discrete_Choices
11039                           (Others_Node, Discrete_Choices (Last_Var));
11040                         Set_Discrete_Choices
11041                           (Last_Var, New_List (Others_Node));
11042                      end if;
11043                   end;
11044                end if;
11045             end if;
11046          end Check_Variant_Part;
11047       end if;
11048    end Freeze_Entity_Checks;
11049
11050    -------------------------
11051    -- Get_Alignment_Value --
11052    -------------------------
11053
11054    function Get_Alignment_Value (Expr : Node_Id) return Uint is
11055       Align : constant Uint := Static_Integer (Expr);
11056
11057    begin
11058       if Align = No_Uint then
11059          return No_Uint;
11060
11061       elsif Align <= 0 then
11062          Error_Msg_N ("alignment value must be positive", Expr);
11063          return No_Uint;
11064
11065       else
11066          for J in Int range 0 .. 64 loop
11067             declare
11068                M : constant Uint := Uint_2 ** J;
11069
11070             begin
11071                exit when M = Align;
11072
11073                if M > Align then
11074                   Error_Msg_N
11075                     ("alignment value must be power of 2", Expr);
11076                   return No_Uint;
11077                end if;
11078             end;
11079          end loop;
11080
11081          return Align;
11082       end if;
11083    end Get_Alignment_Value;
11084
11085    -------------------------------------
11086    -- Inherit_Aspects_At_Freeze_Point --
11087    -------------------------------------
11088
11089    procedure Inherit_Aspects_At_Freeze_Point (Typ : Entity_Id) is
11090       function Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
11091         (Rep_Item : Node_Id) return Boolean;
11092       --  This routine checks if Rep_Item is either a pragma or an aspect
11093       --  specification node whose correponding pragma (if any) is present in
11094       --  the Rep Item chain of the entity it has been specified to.
11095
11096       --------------------------------------------------
11097       -- Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item --
11098       --------------------------------------------------
11099
11100       function Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
11101         (Rep_Item : Node_Id) return Boolean
11102       is
11103       begin
11104          return
11105            Nkind (Rep_Item) = N_Pragma
11106              or else Present_In_Rep_Item
11107                        (Entity (Rep_Item), Aspect_Rep_Item (Rep_Item));
11108       end Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item;
11109
11110    --  Start of processing for Inherit_Aspects_At_Freeze_Point
11111
11112    begin
11113       --  A representation item is either subtype-specific (Size and Alignment
11114       --  clauses) or type-related (all others).  Subtype-specific aspects may
11115       --  differ for different subtypes of the same type (RM 13.1.8).
11116
11117       --  A derived type inherits each type-related representation aspect of
11118       --  its parent type that was directly specified before the declaration of
11119       --  the derived type (RM 13.1.15).
11120
11121       --  A derived subtype inherits each subtype-specific representation
11122       --  aspect of its parent subtype that was directly specified before the
11123       --  declaration of the derived type (RM 13.1.15).
11124
11125       --  The general processing involves inheriting a representation aspect
11126       --  from a parent type whenever the first rep item (aspect specification,
11127       --  attribute definition clause, pragma) corresponding to the given
11128       --  representation aspect in the rep item chain of Typ, if any, isn't
11129       --  directly specified to Typ but to one of its parents.
11130
11131       --  ??? Note that, for now, just a limited number of representation
11132       --  aspects have been inherited here so far. Many of them are
11133       --  still inherited in Sem_Ch3. This will be fixed soon. Here is
11134       --  a non- exhaustive list of aspects that likely also need to
11135       --  be moved to this routine: Alignment, Component_Alignment,
11136       --  Component_Size, Machine_Radix, Object_Size, Pack, Predicates,
11137       --  Preelaborable_Initialization, RM_Size and Small.
11138
11139       --  In addition, Convention must be propagated from base type to subtype,
11140       --  because the subtype may have been declared on an incomplete view.
11141
11142       if Nkind (Parent (Typ)) = N_Private_Extension_Declaration then
11143          return;
11144       end if;
11145
11146       --  Ada_05/Ada_2005
11147
11148       if not Has_Rep_Item (Typ, Name_Ada_05, Name_Ada_2005, False)
11149         and then Has_Rep_Item (Typ, Name_Ada_05, Name_Ada_2005)
11150         and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
11151                    (Get_Rep_Item (Typ, Name_Ada_05, Name_Ada_2005))
11152       then
11153          Set_Is_Ada_2005_Only (Typ);
11154       end if;
11155
11156       --  Ada_12/Ada_2012
11157
11158       if not Has_Rep_Item (Typ, Name_Ada_12, Name_Ada_2012, False)
11159         and then Has_Rep_Item (Typ, Name_Ada_12, Name_Ada_2012)
11160         and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
11161                    (Get_Rep_Item (Typ, Name_Ada_12, Name_Ada_2012))
11162       then
11163          Set_Is_Ada_2012_Only (Typ);
11164       end if;
11165
11166       --  Atomic/Shared
11167
11168       if not Has_Rep_Item (Typ, Name_Atomic, Name_Shared, False)
11169         and then Has_Rep_Pragma (Typ, Name_Atomic, Name_Shared)
11170         and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
11171                    (Get_Rep_Item (Typ, Name_Atomic, Name_Shared))
11172       then
11173          Set_Is_Atomic (Typ);
11174          Set_Is_Volatile (Typ);
11175          Set_Treat_As_Volatile (Typ);
11176       end if;
11177
11178       --  Convention
11179
11180       if Is_Record_Type (Typ)
11181         and then Typ /= Base_Type (Typ) and then Is_Frozen (Base_Type (Typ))
11182       then
11183          Set_Convention (Typ, Convention (Base_Type (Typ)));
11184       end if;
11185
11186       --  Default_Component_Value
11187
11188       --  Verify that there is no rep_item declared for the type, and there
11189       --  is one coming from an ancestor.
11190
11191       if Is_Array_Type (Typ)
11192         and then Is_Base_Type (Typ)
11193         and then not Has_Rep_Item (Typ, Name_Default_Component_Value, False)
11194         and then Has_Rep_Item (Typ, Name_Default_Component_Value)
11195       then
11196          Set_Default_Aspect_Component_Value (Typ,
11197            Default_Aspect_Component_Value
11198              (Entity (Get_Rep_Item (Typ, Name_Default_Component_Value))));
11199       end if;
11200
11201       --  Default_Value
11202
11203       if Is_Scalar_Type (Typ)
11204         and then Is_Base_Type (Typ)
11205         and then not Has_Rep_Item (Typ, Name_Default_Value, False)
11206         and then Has_Rep_Item (Typ, Name_Default_Value)
11207       then
11208          Set_Has_Default_Aspect (Typ);
11209          Set_Default_Aspect_Value (Typ,
11210            Default_Aspect_Value
11211              (Entity (Get_Rep_Item (Typ, Name_Default_Value))));
11212       end if;
11213
11214       --  Discard_Names
11215
11216       if not Has_Rep_Item (Typ, Name_Discard_Names, False)
11217         and then Has_Rep_Item (Typ, Name_Discard_Names)
11218         and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
11219                    (Get_Rep_Item (Typ, Name_Discard_Names))
11220       then
11221          Set_Discard_Names (Typ);
11222       end if;
11223
11224       --  Invariants
11225
11226       if not Has_Rep_Item (Typ, Name_Invariant, False)
11227         and then Has_Rep_Item (Typ, Name_Invariant)
11228         and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
11229                    (Get_Rep_Item (Typ, Name_Invariant))
11230       then
11231          Set_Has_Invariants (Typ);
11232
11233          if Class_Present (Get_Rep_Item (Typ, Name_Invariant)) then
11234             Set_Has_Inheritable_Invariants (Typ);
11235          end if;
11236
11237       --  If we have a subtype with invariants, whose base type does not have
11238       --  invariants, copy these invariants to the base type. This happens for
11239       --  the case of implicit base types created for scalar and array types.
11240
11241       elsif Has_Invariants (Typ)
11242         and then not Has_Invariants (Base_Type (Typ))
11243       then
11244          Set_Has_Invariants (Base_Type (Typ));
11245          Set_Invariant_Procedure (Base_Type (Typ), Invariant_Procedure (Typ));
11246       end if;
11247
11248       --  Volatile
11249
11250       if not Has_Rep_Item (Typ, Name_Volatile, False)
11251         and then Has_Rep_Item (Typ, Name_Volatile)
11252         and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
11253                    (Get_Rep_Item (Typ, Name_Volatile))
11254       then
11255          Set_Is_Volatile (Typ);
11256          Set_Treat_As_Volatile (Typ);
11257       end if;
11258
11259       --  Volatile_Full_Access
11260
11261       if not Has_Rep_Item (Typ, Name_Volatile_Full_Access, False)
11262         and then Has_Rep_Pragma (Typ, Name_Volatile_Full_Access)
11263         and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
11264                    (Get_Rep_Item (Typ, Name_Volatile_Full_Access))
11265       then
11266          Set_Is_Volatile_Full_Access (Typ);
11267          Set_Is_Volatile (Typ);
11268          Set_Treat_As_Volatile (Typ);
11269       end if;
11270
11271       --  Inheritance for derived types only
11272
11273       if Is_Derived_Type (Typ) then
11274          declare
11275             Bas_Typ     : constant Entity_Id := Base_Type (Typ);
11276             Imp_Bas_Typ : constant Entity_Id := Implementation_Base_Type (Typ);
11277
11278          begin
11279             --  Atomic_Components
11280
11281             if not Has_Rep_Item (Typ, Name_Atomic_Components, False)
11282               and then Has_Rep_Item (Typ, Name_Atomic_Components)
11283               and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
11284                    (Get_Rep_Item (Typ, Name_Atomic_Components))
11285             then
11286                Set_Has_Atomic_Components (Imp_Bas_Typ);
11287             end if;
11288
11289             --  Volatile_Components
11290
11291             if not Has_Rep_Item (Typ, Name_Volatile_Components, False)
11292               and then Has_Rep_Item (Typ, Name_Volatile_Components)
11293               and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
11294                    (Get_Rep_Item (Typ, Name_Volatile_Components))
11295             then
11296                Set_Has_Volatile_Components (Imp_Bas_Typ);
11297             end if;
11298
11299             --  Finalize_Storage_Only
11300
11301             if not Has_Rep_Pragma (Typ, Name_Finalize_Storage_Only, False)
11302               and then Has_Rep_Pragma (Typ, Name_Finalize_Storage_Only)
11303             then
11304                Set_Finalize_Storage_Only (Bas_Typ);
11305             end if;
11306
11307             --  Universal_Aliasing
11308
11309             if not Has_Rep_Item (Typ, Name_Universal_Aliasing, False)
11310               and then Has_Rep_Item (Typ, Name_Universal_Aliasing)
11311               and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
11312                    (Get_Rep_Item (Typ, Name_Universal_Aliasing))
11313             then
11314                Set_Universal_Aliasing (Imp_Bas_Typ);
11315             end if;
11316
11317             --  Bit_Order
11318
11319             if Is_Record_Type (Typ) then
11320                if not Has_Rep_Item (Typ, Name_Bit_Order, False)
11321                  and then Has_Rep_Item (Typ, Name_Bit_Order)
11322                then
11323                   Set_Reverse_Bit_Order (Bas_Typ,
11324                     Reverse_Bit_Order (Entity (Name
11325                       (Get_Rep_Item (Typ, Name_Bit_Order)))));
11326                end if;
11327             end if;
11328
11329             --  Scalar_Storage_Order
11330
11331             --  Note: the aspect is specified on a first subtype, but recorded
11332             --  in a flag of the base type!
11333
11334             if (Is_Record_Type (Typ) or else Is_Array_Type (Typ))
11335                  and then Typ = Bas_Typ
11336             then
11337                --  For a type extension, always inherit from parent; otherwise
11338                --  inherit if no default applies. Note: we do not check for
11339                --  an explicit rep item on the parent type when inheriting,
11340                --  because the parent SSO may itself have been set by default.
11341
11342                if not Has_Rep_Item (First_Subtype (Typ),
11343                                     Name_Scalar_Storage_Order, False)
11344                  and then (Is_Tagged_Type (Bas_Typ)
11345                             or else not (SSO_Set_Low_By_Default  (Bas_Typ)
11346                                            or else
11347                                          SSO_Set_High_By_Default (Bas_Typ)))
11348                then
11349                   Set_Reverse_Storage_Order (Bas_Typ,
11350                     Reverse_Storage_Order
11351                       (Implementation_Base_Type (Etype (Bas_Typ))));
11352
11353                   --  Clear default SSO indications, since the inherited aspect
11354                   --  which was set explicitly overrides the default.
11355
11356                   Set_SSO_Set_Low_By_Default  (Bas_Typ, False);
11357                   Set_SSO_Set_High_By_Default (Bas_Typ, False);
11358                end if;
11359             end if;
11360          end;
11361       end if;
11362    end Inherit_Aspects_At_Freeze_Point;
11363
11364    ----------------
11365    -- Initialize --
11366    ----------------
11367
11368    procedure Initialize is
11369    begin
11370       Address_Clause_Checks.Init;
11371       Unchecked_Conversions.Init;
11372
11373       if VM_Target /= No_VM or else AAMP_On_Target then
11374          Independence_Checks.Init;
11375       end if;
11376    end Initialize;
11377
11378    ---------------------------
11379    -- Install_Discriminants --
11380    ---------------------------
11381
11382    procedure Install_Discriminants (E : Entity_Id) is
11383       Disc : Entity_Id;
11384       Prev : Entity_Id;
11385    begin
11386       Disc := First_Discriminant (E);
11387       while Present (Disc) loop
11388          Prev := Current_Entity (Disc);
11389          Set_Current_Entity (Disc);
11390          Set_Is_Immediately_Visible (Disc);
11391          Set_Homonym (Disc, Prev);
11392          Next_Discriminant (Disc);
11393       end loop;
11394    end Install_Discriminants;
11395
11396    -------------------------
11397    -- Is_Operational_Item --
11398    -------------------------
11399
11400    function Is_Operational_Item (N : Node_Id) return Boolean is
11401    begin
11402       if Nkind (N) /= N_Attribute_Definition_Clause then
11403          return False;
11404
11405       else
11406          declare
11407             Id : constant Attribute_Id := Get_Attribute_Id (Chars (N));
11408          begin
11409             return    Id = Attribute_Input
11410               or else Id = Attribute_Output
11411               or else Id = Attribute_Read
11412               or else Id = Attribute_Write
11413               or else Id = Attribute_External_Tag;
11414          end;
11415       end if;
11416    end Is_Operational_Item;
11417
11418    -------------------------
11419    -- Is_Predicate_Static --
11420    -------------------------
11421
11422    --  Note: the basic legality of the expression has already been checked, so
11423    --  we don't need to worry about cases or ranges on strings for example.
11424
11425    function Is_Predicate_Static
11426      (Expr : Node_Id;
11427       Nam  : Name_Id) return Boolean
11428    is
11429       function All_Static_Case_Alternatives (L : List_Id) return Boolean;
11430       --  Given a list of case expression alternatives, returns True if all
11431       --  the alternatives are static (have all static choices, and a static
11432       --  expression).
11433
11434       function All_Static_Choices (L : List_Id) return Boolean;
11435       --  Returns true if all elements of the list are OK static choices
11436       --  as defined below for Is_Static_Choice. Used for case expression
11437       --  alternatives and for the right operand of a membership test. An
11438       --  others_choice is static if the corresponding expression is static.
11439       --  The staticness of the bounds is checked separately.
11440
11441       function Is_Static_Choice (N : Node_Id) return Boolean;
11442       --  Returns True if N represents a static choice (static subtype, or
11443       --  static subtype indication, or static expression, or static range).
11444       --
11445       --  Note that this is a bit more inclusive than we actually need
11446       --  (in particular membership tests do not allow the use of subtype
11447       --  indications). But that doesn't matter, we have already checked
11448       --  that the construct is legal to get this far.
11449
11450       function Is_Type_Ref (N : Node_Id) return Boolean;
11451       pragma Inline (Is_Type_Ref);
11452       --  Returns True if N is a reference to the type for the predicate in the
11453       --  expression (i.e. if it is an identifier whose Chars field matches the
11454       --  Nam given in the call). N must not be parenthesized, if the type name
11455       --  appears in parens, this routine will return False.
11456
11457       ----------------------------------
11458       -- All_Static_Case_Alternatives --
11459       ----------------------------------
11460
11461       function All_Static_Case_Alternatives (L : List_Id) return Boolean is
11462          N : Node_Id;
11463
11464       begin
11465          N := First (L);
11466          while Present (N) loop
11467             if not (All_Static_Choices (Discrete_Choices (N))
11468                      and then Is_OK_Static_Expression (Expression (N)))
11469             then
11470                return False;
11471             end if;
11472
11473             Next (N);
11474          end loop;
11475
11476          return True;
11477       end All_Static_Case_Alternatives;
11478
11479       ------------------------
11480       -- All_Static_Choices --
11481       ------------------------
11482
11483       function All_Static_Choices (L : List_Id) return Boolean is
11484          N : Node_Id;
11485
11486       begin
11487          N := First (L);
11488          while Present (N) loop
11489             if not Is_Static_Choice (N) then
11490                return False;
11491             end if;
11492
11493             Next (N);
11494          end loop;
11495
11496          return True;
11497       end All_Static_Choices;
11498
11499       ----------------------
11500       -- Is_Static_Choice --
11501       ----------------------
11502
11503       function Is_Static_Choice (N : Node_Id) return Boolean is
11504       begin
11505          return Nkind (N) = N_Others_Choice
11506            or else Is_OK_Static_Expression (N)
11507            or else (Is_Entity_Name (N) and then Is_Type (Entity (N))
11508                      and then Is_OK_Static_Subtype (Entity (N)))
11509            or else (Nkind (N) = N_Subtype_Indication
11510                      and then Is_OK_Static_Subtype (Entity (N)))
11511            or else (Nkind (N) = N_Range and then Is_OK_Static_Range (N));
11512       end Is_Static_Choice;
11513
11514       -----------------
11515       -- Is_Type_Ref --
11516       -----------------
11517
11518       function Is_Type_Ref (N : Node_Id) return Boolean is
11519       begin
11520          return Nkind (N) = N_Identifier
11521            and then Chars (N) = Nam
11522            and then Paren_Count (N) = 0;
11523       end Is_Type_Ref;
11524
11525    --  Start of processing for Is_Predicate_Static
11526
11527    begin
11528       --  Predicate_Static means one of the following holds. Numbers are the
11529       --  corresponding paragraph numbers in (RM 3.2.4(16-22)).
11530
11531       --  16: A static expression
11532
11533       if Is_OK_Static_Expression (Expr) then
11534          return True;
11535
11536       --  17: A membership test whose simple_expression is the current
11537       --  instance, and whose membership_choice_list meets the requirements
11538       --  for a static membership test.
11539
11540       elsif Nkind (Expr) in N_Membership_Test
11541         and then ((Present (Right_Opnd (Expr))
11542                     and then Is_Static_Choice (Right_Opnd (Expr)))
11543                   or else
11544                     (Present (Alternatives (Expr))
11545                       and then All_Static_Choices (Alternatives (Expr))))
11546       then
11547          return True;
11548
11549       --  18. A case_expression whose selecting_expression is the current
11550       --  instance, and whose dependent expressions are static expressions.
11551
11552       elsif Nkind (Expr) = N_Case_Expression
11553         and then Is_Type_Ref (Expression (Expr))
11554         and then All_Static_Case_Alternatives (Alternatives (Expr))
11555       then
11556          return True;
11557
11558       --  19. A call to a predefined equality or ordering operator, where one
11559       --  operand is the current instance, and the other is a static
11560       --  expression.
11561
11562       --  Note: the RM is clearly wrong here in not excluding string types.
11563       --  Without this exclusion, we would allow expressions like X > "ABC"
11564       --  to be considered as predicate-static, which is clearly not intended,
11565       --  since the idea is for predicate-static to be a subset of normal
11566       --  static expressions (and "DEF" > "ABC" is not a static expression).
11567
11568       --  However, we do allow internally generated (not from source) equality
11569       --  and inequality operations to be valid on strings (this helps deal
11570       --  with cases where we transform A in "ABC" to A = "ABC).
11571
11572       elsif Nkind (Expr) in N_Op_Compare
11573         and then ((not Is_String_Type (Etype (Left_Opnd (Expr))))
11574                     or else (Nkind_In (Expr, N_Op_Eq, N_Op_Ne)
11575                               and then not Comes_From_Source (Expr)))
11576         and then ((Is_Type_Ref (Left_Opnd (Expr))
11577                     and then Is_OK_Static_Expression (Right_Opnd (Expr)))
11578                   or else
11579                     (Is_Type_Ref (Right_Opnd (Expr))
11580                       and then Is_OK_Static_Expression (Left_Opnd (Expr))))
11581       then
11582          return True;
11583
11584       --  20. A call to a predefined boolean logical operator, where each
11585       --  operand is predicate-static.
11586
11587       elsif (Nkind_In (Expr, N_Op_And, N_Op_Or, N_Op_Xor)
11588               and then Is_Predicate_Static (Left_Opnd (Expr), Nam)
11589               and then Is_Predicate_Static (Right_Opnd (Expr), Nam))
11590         or else
11591             (Nkind (Expr) = N_Op_Not
11592               and then Is_Predicate_Static (Right_Opnd (Expr), Nam))
11593       then
11594          return True;
11595
11596       --  21. A short-circuit control form where both operands are
11597       --  predicate-static.
11598
11599       elsif Nkind (Expr) in N_Short_Circuit
11600         and then Is_Predicate_Static (Left_Opnd (Expr), Nam)
11601         and then Is_Predicate_Static (Right_Opnd (Expr), Nam)
11602       then
11603          return True;
11604
11605       --  22. A parenthesized predicate-static expression. This does not
11606       --  require any special test, since we just ignore paren levels in
11607       --  all the cases above.
11608
11609       --  One more test that is an implementation artifact caused by the fact
11610       --  that we are analyzing not the original expression, but the generated
11611       --  expression in the body of the predicate function. This can include
11612       --  references to inherited predicates, so that the expression we are
11613       --  processing looks like:
11614
11615       --    expression and then xxPredicate (typ (Inns))
11616
11617       --  Where the call is to a Predicate function for an inherited predicate.
11618       --  We simply ignore such a call, which could be to either a dynamic or
11619       --  a static predicate. Note that if the parent predicate is dynamic then
11620       --  eventually this type will be marked as dynamic, but you are allowed
11621       --  to specify a static predicate for a subtype which is inheriting a
11622       --  dynamic predicate, so the static predicate validation here ignores
11623       --  the inherited predicate even if it is dynamic.
11624
11625       elsif Nkind (Expr) = N_Function_Call
11626         and then Is_Predicate_Function (Entity (Name (Expr)))
11627       then
11628          return True;
11629
11630       --  That's an exhaustive list of tests, all other cases are not
11631       --  predicate-static, so we return False.
11632
11633       else
11634          return False;
11635       end if;
11636    end Is_Predicate_Static;
11637
11638    ---------------------
11639    -- Kill_Rep_Clause --
11640    ---------------------
11641
11642    procedure Kill_Rep_Clause (N : Node_Id) is
11643    begin
11644       pragma Assert (Ignore_Rep_Clauses);
11645
11646       --  Note: we use Replace rather than Rewrite, because we don't want
11647       --  ASIS to be able to use Original_Node to dig out the (undecorated)
11648       --  rep clause that is being replaced.
11649
11650       Replace (N, Make_Null_Statement (Sloc (N)));
11651
11652       --  The null statement must be marked as not coming from source. This is
11653       --  so that ASIS ignores it, and also the back end does not expect bogus
11654       --  "from source" null statements in weird places (e.g. in declarative
11655       --  regions where such null statements are not allowed).
11656
11657       Set_Comes_From_Source (N, False);
11658    end Kill_Rep_Clause;
11659
11660    ------------------
11661    -- Minimum_Size --
11662    ------------------
11663
11664    function Minimum_Size
11665      (T      : Entity_Id;
11666       Biased : Boolean := False) return Nat
11667    is
11668       Lo     : Uint    := No_Uint;
11669       Hi     : Uint    := No_Uint;
11670       LoR    : Ureal   := No_Ureal;
11671       HiR    : Ureal   := No_Ureal;
11672       LoSet  : Boolean := False;
11673       HiSet  : Boolean := False;
11674       B      : Uint;
11675       S      : Nat;
11676       Ancest : Entity_Id;
11677       R_Typ  : constant Entity_Id := Root_Type (T);
11678
11679    begin
11680       --  If bad type, return 0
11681
11682       if T = Any_Type then
11683          return 0;
11684
11685       --  For generic types, just return zero. There cannot be any legitimate
11686       --  need to know such a size, but this routine may be called with a
11687       --  generic type as part of normal processing.
11688
11689       elsif Is_Generic_Type (R_Typ) or else R_Typ = Any_Type then
11690          return 0;
11691
11692          --  Access types (cannot have size smaller than System.Address)
11693
11694       elsif Is_Access_Type (T) then
11695          return System_Address_Size;
11696
11697       --  Floating-point types
11698
11699       elsif Is_Floating_Point_Type (T) then
11700          return UI_To_Int (Esize (R_Typ));
11701
11702       --  Discrete types
11703
11704       elsif Is_Discrete_Type (T) then
11705
11706          --  The following loop is looking for the nearest compile time known
11707          --  bounds following the ancestor subtype chain. The idea is to find
11708          --  the most restrictive known bounds information.
11709
11710          Ancest := T;
11711          loop
11712             if Ancest = Any_Type or else Etype (Ancest) = Any_Type then
11713                return 0;
11714             end if;
11715
11716             if not LoSet then
11717                if Compile_Time_Known_Value (Type_Low_Bound (Ancest)) then
11718                   Lo := Expr_Rep_Value (Type_Low_Bound (Ancest));
11719                   LoSet := True;
11720                   exit when HiSet;
11721                end if;
11722             end if;
11723
11724             if not HiSet then
11725                if Compile_Time_Known_Value (Type_High_Bound (Ancest)) then
11726                   Hi := Expr_Rep_Value (Type_High_Bound (Ancest));
11727                   HiSet := True;
11728                   exit when LoSet;
11729                end if;
11730             end if;
11731
11732             Ancest := Ancestor_Subtype (Ancest);
11733
11734             if No (Ancest) then
11735                Ancest := Base_Type (T);
11736
11737                if Is_Generic_Type (Ancest) then
11738                   return 0;
11739                end if;
11740             end if;
11741          end loop;
11742
11743       --  Fixed-point types. We can't simply use Expr_Value to get the
11744       --  Corresponding_Integer_Value values of the bounds, since these do not
11745       --  get set till the type is frozen, and this routine can be called
11746       --  before the type is frozen. Similarly the test for bounds being static
11747       --  needs to include the case where we have unanalyzed real literals for
11748       --  the same reason.
11749
11750       elsif Is_Fixed_Point_Type (T) then
11751
11752          --  The following loop is looking for the nearest compile time known
11753          --  bounds following the ancestor subtype chain. The idea is to find
11754          --  the most restrictive known bounds information.
11755
11756          Ancest := T;
11757          loop
11758             if Ancest = Any_Type or else Etype (Ancest) = Any_Type then
11759                return 0;
11760             end if;
11761
11762             --  Note: In the following two tests for LoSet and HiSet, it may
11763             --  seem redundant to test for N_Real_Literal here since normally
11764             --  one would assume that the test for the value being known at
11765             --  compile time includes this case. However, there is a glitch.
11766             --  If the real literal comes from folding a non-static expression,
11767             --  then we don't consider any non- static expression to be known
11768             --  at compile time if we are in configurable run time mode (needed
11769             --  in some cases to give a clearer definition of what is and what
11770             --  is not accepted). So the test is indeed needed. Without it, we
11771             --  would set neither Lo_Set nor Hi_Set and get an infinite loop.
11772
11773             if not LoSet then
11774                if Nkind (Type_Low_Bound (Ancest)) = N_Real_Literal
11775                  or else Compile_Time_Known_Value (Type_Low_Bound (Ancest))
11776                then
11777                   LoR := Expr_Value_R (Type_Low_Bound (Ancest));
11778                   LoSet := True;
11779                   exit when HiSet;
11780                end if;
11781             end if;
11782
11783             if not HiSet then
11784                if Nkind (Type_High_Bound (Ancest)) = N_Real_Literal
11785                  or else Compile_Time_Known_Value (Type_High_Bound (Ancest))
11786                then
11787                   HiR := Expr_Value_R (Type_High_Bound (Ancest));
11788                   HiSet := True;
11789                   exit when LoSet;
11790                end if;
11791             end if;
11792
11793             Ancest := Ancestor_Subtype (Ancest);
11794
11795             if No (Ancest) then
11796                Ancest := Base_Type (T);
11797
11798                if Is_Generic_Type (Ancest) then
11799                   return 0;
11800                end if;
11801             end if;
11802          end loop;
11803
11804          Lo := UR_To_Uint (LoR / Small_Value (T));
11805          Hi := UR_To_Uint (HiR / Small_Value (T));
11806
11807       --  No other types allowed
11808
11809       else
11810          raise Program_Error;
11811       end if;
11812
11813       --  Fall through with Hi and Lo set. Deal with biased case
11814
11815       if (Biased
11816            and then not Is_Fixed_Point_Type (T)
11817            and then not (Is_Enumeration_Type (T)
11818                           and then Has_Non_Standard_Rep (T)))
11819         or else Has_Biased_Representation (T)
11820       then
11821          Hi := Hi - Lo;
11822          Lo := Uint_0;
11823       end if;
11824
11825       --  Null range case, size is always zero. We only do this in the discrete
11826       --  type case, since that's the odd case that came up. Probably we should
11827       --  also do this in the fixed-point case, but doing so causes peculiar
11828       --  gigi failures, and it is not worth worrying about this incredibly
11829       --  marginal case (explicit null-range fixed-point type declarations)???
11830
11831       if Lo > Hi and then Is_Discrete_Type (T) then
11832          S := 0;
11833
11834       --  Signed case. Note that we consider types like range 1 .. -1 to be
11835       --  signed for the purpose of computing the size, since the bounds have
11836       --  to be accommodated in the base type.
11837
11838       elsif Lo < 0 or else Hi < 0 then
11839          S := 1;
11840          B := Uint_1;
11841
11842          --  S = size, B = 2 ** (size - 1) (can accommodate -B .. +(B - 1))
11843          --  Note that we accommodate the case where the bounds cross. This
11844          --  can happen either because of the way the bounds are declared
11845          --  or because of the algorithm in Freeze_Fixed_Point_Type.
11846
11847          while Lo < -B
11848            or else Hi < -B
11849            or else Lo >= B
11850            or else Hi >= B
11851          loop
11852             B := Uint_2 ** S;
11853             S := S + 1;
11854          end loop;
11855
11856       --  Unsigned case
11857
11858       else
11859          --  If both bounds are positive, make sure that both are represen-
11860          --  table in the case where the bounds are crossed. This can happen
11861          --  either because of the way the bounds are declared, or because of
11862          --  the algorithm in Freeze_Fixed_Point_Type.
11863
11864          if Lo > Hi then
11865             Hi := Lo;
11866          end if;
11867
11868          --  S = size, (can accommodate 0 .. (2**size - 1))
11869
11870          S := 0;
11871          while Hi >= Uint_2 ** S loop
11872             S := S + 1;
11873          end loop;
11874       end if;
11875
11876       return S;
11877    end Minimum_Size;
11878
11879    ---------------------------
11880    -- New_Stream_Subprogram --
11881    ---------------------------
11882
11883    procedure New_Stream_Subprogram
11884      (N     : Node_Id;
11885       Ent   : Entity_Id;
11886       Subp  : Entity_Id;
11887       Nam   : TSS_Name_Type)
11888    is
11889       Loc       : constant Source_Ptr := Sloc (N);
11890       Sname     : constant Name_Id    := Make_TSS_Name (Base_Type (Ent), Nam);
11891       Subp_Id   : Entity_Id;
11892       Subp_Decl : Node_Id;
11893       F         : Entity_Id;
11894       Etyp      : Entity_Id;
11895
11896       Defer_Declaration : constant Boolean :=
11897                             Is_Tagged_Type (Ent) or else Is_Private_Type (Ent);
11898       --  For a tagged type, there is a declaration for each stream attribute
11899       --  at the freeze point, and we must generate only a completion of this
11900       --  declaration. We do the same for private types, because the full view
11901       --  might be tagged. Otherwise we generate a declaration at the point of
11902       --  the attribute definition clause.
11903
11904       function Build_Spec return Node_Id;
11905       --  Used for declaration and renaming declaration, so that this is
11906       --  treated as a renaming_as_body.
11907
11908       ----------------
11909       -- Build_Spec --
11910       ----------------
11911
11912       function Build_Spec return Node_Id is
11913          Out_P   : constant Boolean := (Nam = TSS_Stream_Read);
11914          Formals : List_Id;
11915          Spec    : Node_Id;
11916          T_Ref   : constant Node_Id := New_Occurrence_Of (Etyp, Loc);
11917
11918       begin
11919          Subp_Id := Make_Defining_Identifier (Loc, Sname);
11920
11921          --  S : access Root_Stream_Type'Class
11922
11923          Formals := New_List (
11924                       Make_Parameter_Specification (Loc,
11925                         Defining_Identifier =>
11926                           Make_Defining_Identifier (Loc, Name_S),
11927                         Parameter_Type =>
11928                           Make_Access_Definition (Loc,
11929                             Subtype_Mark =>
11930                               New_Occurrence_Of (
11931                                 Designated_Type (Etype (F)), Loc))));
11932
11933          if Nam = TSS_Stream_Input then
11934             Spec :=
11935               Make_Function_Specification (Loc,
11936                 Defining_Unit_Name       => Subp_Id,
11937                 Parameter_Specifications => Formals,
11938                 Result_Definition        => T_Ref);
11939          else
11940             --  V : [out] T
11941
11942             Append_To (Formals,
11943               Make_Parameter_Specification (Loc,
11944                 Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
11945                 Out_Present         => Out_P,
11946                 Parameter_Type      => T_Ref));
11947
11948             Spec :=
11949               Make_Procedure_Specification (Loc,
11950                 Defining_Unit_Name       => Subp_Id,
11951                 Parameter_Specifications => Formals);
11952          end if;
11953
11954          return Spec;
11955       end Build_Spec;
11956
11957    --  Start of processing for New_Stream_Subprogram
11958
11959    begin
11960       F := First_Formal (Subp);
11961
11962       if Ekind (Subp) = E_Procedure then
11963          Etyp := Etype (Next_Formal (F));
11964       else
11965          Etyp := Etype (Subp);
11966       end if;
11967
11968       --  Prepare subprogram declaration and insert it as an action on the
11969       --  clause node. The visibility for this entity is used to test for
11970       --  visibility of the attribute definition clause (in the sense of
11971       --  8.3(23) as amended by AI-195).
11972
11973       if not Defer_Declaration then
11974          Subp_Decl :=
11975            Make_Subprogram_Declaration (Loc,
11976              Specification => Build_Spec);
11977
11978       --  For a tagged type, there is always a visible declaration for each
11979       --  stream TSS (it is a predefined primitive operation), and the
11980       --  completion of this declaration occurs at the freeze point, which is
11981       --  not always visible at places where the attribute definition clause is
11982       --  visible. So, we create a dummy entity here for the purpose of
11983       --  tracking the visibility of the attribute definition clause itself.
11984
11985       else
11986          Subp_Id :=
11987            Make_Defining_Identifier (Loc, New_External_Name (Sname, 'V'));
11988          Subp_Decl :=
11989            Make_Object_Declaration (Loc,
11990              Defining_Identifier => Subp_Id,
11991              Object_Definition   => New_Occurrence_Of (Standard_Boolean, Loc));
11992       end if;
11993
11994       Insert_Action (N, Subp_Decl);
11995       Set_Entity (N, Subp_Id);
11996
11997       Subp_Decl :=
11998         Make_Subprogram_Renaming_Declaration (Loc,
11999           Specification => Build_Spec,
12000           Name => New_Occurrence_Of (Subp, Loc));
12001
12002       if Defer_Declaration then
12003          Set_TSS (Base_Type (Ent), Subp_Id);
12004       else
12005          Insert_Action (N, Subp_Decl);
12006          Copy_TSS (Subp_Id, Base_Type (Ent));
12007       end if;
12008    end New_Stream_Subprogram;
12009
12010    ------------------------------------------
12011    -- Push_Scope_And_Install_Discriminants --
12012    ------------------------------------------
12013
12014    procedure Push_Scope_And_Install_Discriminants (E : Entity_Id) is
12015    begin
12016       if Has_Discriminants (E) then
12017          Push_Scope (E);
12018
12019          --  Make discriminants visible for type declarations and protected
12020          --  type declarations, not for subtype declarations (RM 13.1.1 (12/3))
12021
12022          if Nkind (Parent (E)) /= N_Subtype_Declaration then
12023             Install_Discriminants (E);
12024          end if;
12025       end if;
12026    end Push_Scope_And_Install_Discriminants;
12027
12028    ------------------------
12029    -- Rep_Item_Too_Early --
12030    ------------------------
12031
12032    function Rep_Item_Too_Early (T : Entity_Id; N : Node_Id) return Boolean is
12033    begin
12034       --  Cannot apply non-operational rep items to generic types
12035
12036       if Is_Operational_Item (N) then
12037          return False;
12038
12039       elsif Is_Type (T)
12040         and then Is_Generic_Type (Root_Type (T))
12041         and then (Nkind (N) /= N_Pragma
12042                    or else Get_Pragma_Id (N) /= Pragma_Convention)
12043       then
12044          Error_Msg_N ("representation item not allowed for generic type", N);
12045          return True;
12046       end if;
12047
12048       --  Otherwise check for incomplete type
12049
12050       if Is_Incomplete_Or_Private_Type (T)
12051         and then No (Underlying_Type (T))
12052         and then
12053           (Nkind (N) /= N_Pragma
12054             or else Get_Pragma_Id (N) /= Pragma_Import)
12055       then
12056          Error_Msg_N
12057            ("representation item must be after full type declaration", N);
12058          return True;
12059
12060       --  If the type has incomplete components, a representation clause is
12061       --  illegal but stream attributes and Convention pragmas are correct.
12062
12063       elsif Has_Private_Component (T) then
12064          if Nkind (N) = N_Pragma then
12065             return False;
12066
12067          else
12068             Error_Msg_N
12069               ("representation item must appear after type is fully defined",
12070                 N);
12071             return True;
12072          end if;
12073       else
12074          return False;
12075       end if;
12076    end Rep_Item_Too_Early;
12077
12078    -----------------------
12079    -- Rep_Item_Too_Late --
12080    -----------------------
12081
12082    function Rep_Item_Too_Late
12083      (T     : Entity_Id;
12084       N     : Node_Id;
12085       FOnly : Boolean := False) return Boolean
12086    is
12087       S           : Entity_Id;
12088       Parent_Type : Entity_Id;
12089
12090       procedure No_Type_Rep_Item;
12091       --  Output message indicating that no type-related aspects can be
12092       --  specified due to some property of the parent type.
12093
12094       procedure Too_Late;
12095       --  Output message for an aspect being specified too late
12096
12097       --  Note that neither of the above errors is considered a serious one,
12098       --  since the effect is simply that we ignore the representation clause
12099       --  in these cases.
12100       --  Is this really true? In any case if we make this change we must
12101       --  document the requirement in the spec of Rep_Item_Too_Late that
12102       --  if True is returned, then the rep item must be completely ignored???
12103
12104       ----------------------
12105       -- No_Type_Rep_Item --
12106       ----------------------
12107
12108       procedure No_Type_Rep_Item is
12109       begin
12110          Error_Msg_N ("|type-related representation item not permitted!", N);
12111       end No_Type_Rep_Item;
12112
12113       --------------
12114       -- Too_Late --
12115       --------------
12116
12117       procedure Too_Late is
12118       begin
12119          --  Other compilers seem more relaxed about rep items appearing too
12120          --  late. Since analysis tools typically don't care about rep items
12121          --  anyway, no reason to be too strict about this.
12122
12123          if not Relaxed_RM_Semantics then
12124             Error_Msg_N ("|representation item appears too late!", N);
12125          end if;
12126       end Too_Late;
12127
12128    --  Start of processing for Rep_Item_Too_Late
12129
12130    begin
12131       --  First make sure entity is not frozen (RM 13.1(9))
12132
12133       if Is_Frozen (T)
12134
12135         --  Exclude imported types, which may be frozen if they appear in a
12136         --  representation clause for a local type.
12137
12138         and then not From_Limited_With (T)
12139
12140         --  Exclude generated entities (not coming from source). The common
12141         --  case is when we generate a renaming which prematurely freezes the
12142         --  renamed internal entity, but we still want to be able to set copies
12143         --  of attribute values such as Size/Alignment.
12144
12145         and then Comes_From_Source (T)
12146       then
12147          Too_Late;
12148          S := First_Subtype (T);
12149
12150          if Present (Freeze_Node (S)) then
12151             if not Relaxed_RM_Semantics then
12152                Error_Msg_NE
12153                  ("??no more representation items for }", Freeze_Node (S), S);
12154             end if;
12155          end if;
12156
12157          return True;
12158
12159       --  Check for case of untagged derived type whose parent either has
12160       --  primitive operations, or is a by reference type (RM 13.1(10)). In
12161       --  this case we do not output a Too_Late message, since there is no
12162       --  earlier point where the rep item could be placed to make it legal.
12163
12164       elsif Is_Type (T)
12165         and then not FOnly
12166         and then Is_Derived_Type (T)
12167         and then not Is_Tagged_Type (T)
12168       then
12169          Parent_Type := Etype (Base_Type (T));
12170
12171          if Has_Primitive_Operations (Parent_Type) then
12172             No_Type_Rep_Item;
12173
12174             if not Relaxed_RM_Semantics then
12175                Error_Msg_NE
12176                  ("\parent type & has primitive operations!", N, Parent_Type);
12177             end if;
12178
12179             return True;
12180
12181          elsif Is_By_Reference_Type (Parent_Type) then
12182             No_Type_Rep_Item;
12183
12184             if not Relaxed_RM_Semantics then
12185                Error_Msg_NE
12186                  ("\parent type & is a by reference type!", N, Parent_Type);
12187             end if;
12188
12189             return True;
12190          end if;
12191       end if;
12192
12193       --  No error, but one more warning to consider. The RM (surprisingly)
12194       --  allows this pattern:
12195
12196       --    type S is ...
12197       --    primitive operations for S
12198       --    type R is new S;
12199       --    rep clause for S
12200
12201       --  Meaning that calls on the primitive operations of S for values of
12202       --  type R may require possibly expensive implicit conversion operations.
12203       --  This is not an error, but is worth a warning.
12204
12205       if not Relaxed_RM_Semantics and then Is_Type (T) then
12206          declare
12207             DTL : constant Entity_Id := Derived_Type_Link (Base_Type (T));
12208
12209          begin
12210             if Present (DTL)
12211               and then Has_Primitive_Operations (Base_Type (T))
12212
12213               --  For now, do not generate this warning for the case of aspect
12214               --  specification using Ada 2012 syntax, since we get wrong
12215               --  messages we do not understand. The whole business of derived
12216               --  types and rep items seems a bit confused when aspects are
12217               --  used, since the aspects are not evaluated till freeze time.
12218
12219               and then not From_Aspect_Specification (N)
12220             then
12221                Error_Msg_Sloc := Sloc (DTL);
12222                Error_Msg_N
12223                  ("representation item for& appears after derived type "
12224                   & "declaration#??", N);
12225                Error_Msg_NE
12226                  ("\may result in implicit conversions for primitive "
12227                   & "operations of&??", N, T);
12228                Error_Msg_NE
12229                  ("\to change representations when called with arguments "
12230                   & "of type&??", N, DTL);
12231             end if;
12232          end;
12233       end if;
12234
12235       --  No error, link item into head of chain of rep items for the entity,
12236       --  but avoid chaining if we have an overloadable entity, and the pragma
12237       --  is one that can apply to multiple overloaded entities.
12238
12239       if Is_Overloadable (T) and then Nkind (N) = N_Pragma then
12240          declare
12241             Pname : constant Name_Id := Pragma_Name (N);
12242          begin
12243             if Nam_In (Pname, Name_Convention, Name_Import,   Name_Export,
12244                               Name_External,   Name_Interface)
12245             then
12246                return False;
12247             end if;
12248          end;
12249       end if;
12250
12251       Record_Rep_Item (T, N);
12252       return False;
12253    end Rep_Item_Too_Late;
12254
12255    -------------------------------------
12256    -- Replace_Type_References_Generic --
12257    -------------------------------------
12258
12259    procedure Replace_Type_References_Generic (N : Node_Id; T : Entity_Id) is
12260       TName : constant Name_Id := Chars (T);
12261
12262       function Replace_Node (N : Node_Id) return Traverse_Result;
12263       --  Processes a single node in the traversal procedure below, checking
12264       --  if node N should be replaced, and if so, doing the replacement.
12265
12266       procedure Replace_Type_Refs is new Traverse_Proc (Replace_Node);
12267       --  This instantiation provides the body of Replace_Type_References
12268
12269       ------------------
12270       -- Replace_Node --
12271       ------------------
12272
12273       function Replace_Node (N : Node_Id) return Traverse_Result is
12274          S : Entity_Id;
12275          P : Node_Id;
12276
12277       begin
12278          --  Case of identifier
12279
12280          if Nkind (N) = N_Identifier then
12281
12282             --  If not the type name, check whether it is a reference to
12283             --  some other type, which must be frozen before the predicate
12284             --  function is analyzed, i.e. before the freeze node of the
12285             --  type to which the predicate applies.
12286
12287             if Chars (N) /= TName then
12288                if Present (Current_Entity (N))
12289                   and then Is_Type (Current_Entity (N))
12290                then
12291                   Freeze_Before (Freeze_Node (T), Current_Entity (N));
12292                end if;
12293
12294                return Skip;
12295
12296             --  Otherwise do the replacement and we are done with this node
12297
12298             else
12299                Replace_Type_Reference (N);
12300                return Skip;
12301             end if;
12302
12303          --  Case of selected component (which is what a qualification
12304          --  looks like in the unanalyzed tree, which is what we have.
12305
12306          elsif Nkind (N) = N_Selected_Component then
12307
12308             --  If selector name is not our type, keeping going (we might
12309             --  still have an occurrence of the type in the prefix).
12310
12311             if Nkind (Selector_Name (N)) /= N_Identifier
12312               or else Chars (Selector_Name (N)) /= TName
12313             then
12314                return OK;
12315
12316             --  Selector name is our type, check qualification
12317
12318             else
12319                --  Loop through scopes and prefixes, doing comparison
12320
12321                S := Current_Scope;
12322                P := Prefix (N);
12323                loop
12324                   --  Continue if no more scopes or scope with no name
12325
12326                   if No (S) or else Nkind (S) not in N_Has_Chars then
12327                      return OK;
12328                   end if;
12329
12330                   --  Do replace if prefix is an identifier matching the
12331                   --  scope that we are currently looking at.
12332
12333                   if Nkind (P) = N_Identifier
12334                     and then Chars (P) = Chars (S)
12335                   then
12336                      Replace_Type_Reference (N);
12337                      return Skip;
12338                   end if;
12339
12340                   --  Go check scope above us if prefix is itself of the
12341                   --  form of a selected component, whose selector matches
12342                   --  the scope we are currently looking at.
12343
12344                   if Nkind (P) = N_Selected_Component
12345                     and then Nkind (Selector_Name (P)) = N_Identifier
12346                     and then Chars (Selector_Name (P)) = Chars (S)
12347                   then
12348                      S := Scope (S);
12349                      P := Prefix (P);
12350
12351                   --  For anything else, we don't have a match, so keep on
12352                   --  going, there are still some weird cases where we may
12353                   --  still have a replacement within the prefix.
12354
12355                   else
12356                      return OK;
12357                   end if;
12358                end loop;
12359             end if;
12360
12361          --  Continue for any other node kind
12362
12363          else
12364             return OK;
12365          end if;
12366       end Replace_Node;
12367
12368    begin
12369       Replace_Type_Refs (N);
12370    end Replace_Type_References_Generic;
12371
12372    -------------------------
12373    -- Same_Representation --
12374    -------------------------
12375
12376    function Same_Representation (Typ1, Typ2 : Entity_Id) return Boolean is
12377       T1 : constant Entity_Id := Underlying_Type (Typ1);
12378       T2 : constant Entity_Id := Underlying_Type (Typ2);
12379
12380    begin
12381       --  A quick check, if base types are the same, then we definitely have
12382       --  the same representation, because the subtype specific representation
12383       --  attributes (Size and Alignment) do not affect representation from
12384       --  the point of view of this test.
12385
12386       if Base_Type (T1) = Base_Type (T2) then
12387          return True;
12388
12389       elsif Is_Private_Type (Base_Type (T2))
12390         and then Base_Type (T1) = Full_View (Base_Type (T2))
12391       then
12392          return True;
12393       end if;
12394
12395       --  Tagged types never have differing representations
12396
12397       if Is_Tagged_Type (T1) then
12398          return True;
12399       end if;
12400
12401       --  Representations are definitely different if conventions differ
12402
12403       if Convention (T1) /= Convention (T2) then
12404          return False;
12405       end if;
12406
12407       --  Representations are different if component alignments or scalar
12408       --  storage orders differ.
12409
12410       if (Is_Record_Type (T1) or else Is_Array_Type (T1))
12411             and then
12412          (Is_Record_Type (T2) or else Is_Array_Type (T2))
12413         and then
12414          (Component_Alignment (T1) /= Component_Alignment (T2)
12415            or else Reverse_Storage_Order (T1) /= Reverse_Storage_Order (T2))
12416       then
12417          return False;
12418       end if;
12419
12420       --  For arrays, the only real issue is component size. If we know the
12421       --  component size for both arrays, and it is the same, then that's
12422       --  good enough to know we don't have a change of representation.
12423
12424       if Is_Array_Type (T1) then
12425          if Known_Component_Size (T1)
12426            and then Known_Component_Size (T2)
12427            and then Component_Size (T1) = Component_Size (T2)
12428          then
12429             if VM_Target = No_VM then
12430                return True;
12431
12432             --  In VM targets the representation of arrays with aliased
12433             --  components differs from arrays with non-aliased components
12434
12435             else
12436                return Has_Aliased_Components (Base_Type (T1))
12437                         =
12438                       Has_Aliased_Components (Base_Type (T2));
12439             end if;
12440          end if;
12441       end if;
12442
12443       --  Types definitely have same representation if neither has non-standard
12444       --  representation since default representations are always consistent.
12445       --  If only one has non-standard representation, and the other does not,
12446       --  then we consider that they do not have the same representation. They
12447       --  might, but there is no way of telling early enough.
12448
12449       if Has_Non_Standard_Rep (T1) then
12450          if not Has_Non_Standard_Rep (T2) then
12451             return False;
12452          end if;
12453       else
12454          return not Has_Non_Standard_Rep (T2);
12455       end if;
12456
12457       --  Here the two types both have non-standard representation, and we need
12458       --  to determine if they have the same non-standard representation.
12459
12460       --  For arrays, we simply need to test if the component sizes are the
12461       --  same. Pragma Pack is reflected in modified component sizes, so this
12462       --  check also deals with pragma Pack.
12463
12464       if Is_Array_Type (T1) then
12465          return Component_Size (T1) = Component_Size (T2);
12466
12467       --  Tagged types always have the same representation, because it is not
12468       --  possible to specify different representations for common fields.
12469
12470       elsif Is_Tagged_Type (T1) then
12471          return True;
12472
12473       --  Case of record types
12474
12475       elsif Is_Record_Type (T1) then
12476
12477          --  Packed status must conform
12478
12479          if Is_Packed (T1) /= Is_Packed (T2) then
12480             return False;
12481
12482          --  Otherwise we must check components. Typ2 maybe a constrained
12483          --  subtype with fewer components, so we compare the components
12484          --  of the base types.
12485
12486          else
12487             Record_Case : declare
12488                CD1, CD2 : Entity_Id;
12489
12490                function Same_Rep return Boolean;
12491                --  CD1 and CD2 are either components or discriminants. This
12492                --  function tests whether they have the same representation.
12493
12494                --------------
12495                -- Same_Rep --
12496                --------------
12497
12498                function Same_Rep return Boolean is
12499                begin
12500                   if No (Component_Clause (CD1)) then
12501                      return No (Component_Clause (CD2));
12502                   else
12503                      --  Note: at this point, component clauses have been
12504                      --  normalized to the default bit order, so that the
12505                      --  comparison of Component_Bit_Offsets is meaningful.
12506
12507                      return
12508                         Present (Component_Clause (CD2))
12509                           and then
12510                         Component_Bit_Offset (CD1) = Component_Bit_Offset (CD2)
12511                           and then
12512                         Esize (CD1) = Esize (CD2);
12513                   end if;
12514                end Same_Rep;
12515
12516             --  Start of processing for Record_Case
12517
12518             begin
12519                if Has_Discriminants (T1) then
12520
12521                   --  The number of discriminants may be different if the
12522                   --  derived type has fewer (constrained by values). The
12523                   --  invisible discriminants retain the representation of
12524                   --  the original, so the discrepancy does not per se
12525                   --  indicate a different representation.
12526
12527                   CD1 := First_Discriminant (T1);
12528                   CD2 := First_Discriminant (T2);
12529                   while Present (CD1) and then Present (CD2) loop
12530                      if not Same_Rep then
12531                         return False;
12532                      else
12533                         Next_Discriminant (CD1);
12534                         Next_Discriminant (CD2);
12535                      end if;
12536                   end loop;
12537                end if;
12538
12539                CD1 := First_Component (Underlying_Type (Base_Type (T1)));
12540                CD2 := First_Component (Underlying_Type (Base_Type (T2)));
12541                while Present (CD1) loop
12542                   if not Same_Rep then
12543                      return False;
12544                   else
12545                      Next_Component (CD1);
12546                      Next_Component (CD2);
12547                   end if;
12548                end loop;
12549
12550                return True;
12551             end Record_Case;
12552          end if;
12553
12554       --  For enumeration types, we must check each literal to see if the
12555       --  representation is the same. Note that we do not permit enumeration
12556       --  representation clauses for Character and Wide_Character, so these
12557       --  cases were already dealt with.
12558
12559       elsif Is_Enumeration_Type (T1) then
12560          Enumeration_Case : declare
12561             L1, L2 : Entity_Id;
12562
12563          begin
12564             L1 := First_Literal (T1);
12565             L2 := First_Literal (T2);
12566             while Present (L1) loop
12567                if Enumeration_Rep (L1) /= Enumeration_Rep (L2) then
12568                   return False;
12569                else
12570                   Next_Literal (L1);
12571                   Next_Literal (L2);
12572                end if;
12573             end loop;
12574
12575             return True;
12576          end Enumeration_Case;
12577
12578       --  Any other types have the same representation for these purposes
12579
12580       else
12581          return True;
12582       end if;
12583    end Same_Representation;
12584
12585    --------------------------------
12586    -- Resolve_Iterable_Operation --
12587    --------------------------------
12588
12589    procedure Resolve_Iterable_Operation
12590      (N      : Node_Id;
12591       Cursor : Entity_Id;
12592       Typ    : Entity_Id;
12593       Nam    : Name_Id)
12594    is
12595       Ent : Entity_Id;
12596       F1  : Entity_Id;
12597       F2  : Entity_Id;
12598
12599    begin
12600       if not Is_Overloaded (N) then
12601          if not Is_Entity_Name (N)
12602            or else Ekind (Entity (N)) /= E_Function
12603            or else Scope (Entity (N)) /= Scope (Typ)
12604            or else No (First_Formal (Entity (N)))
12605            or else Etype (First_Formal (Entity (N))) /= Typ
12606          then
12607             Error_Msg_N ("iterable primitive must be local function name "
12608                          & "whose first formal is an iterable type", N);
12609             return;
12610          end if;
12611
12612          Ent := Entity (N);
12613          F1 := First_Formal (Ent);
12614          if Nam = Name_First then
12615
12616             --  First (Container) => Cursor
12617
12618             if Etype (Ent) /= Cursor then
12619                Error_Msg_N ("primitive for First must yield a curosr", N);
12620             end if;
12621
12622          elsif Nam = Name_Next then
12623
12624             --  Next (Container, Cursor) => Cursor
12625
12626             F2 := Next_Formal (F1);
12627
12628             if Etype (F2) /= Cursor
12629               or else Etype (Ent) /= Cursor
12630               or else Present (Next_Formal (F2))
12631             then
12632                Error_Msg_N ("no match for Next iterable primitive", N);
12633             end if;
12634
12635          elsif Nam = Name_Has_Element then
12636
12637             --  Has_Element (Container, Cursor) => Boolean
12638
12639             F2 := Next_Formal (F1);
12640             if Etype (F2) /= Cursor
12641               or else Etype (Ent) /= Standard_Boolean
12642               or else Present (Next_Formal (F2))
12643             then
12644                Error_Msg_N ("no match for Has_Element iterable primitive", N);
12645             end if;
12646
12647          elsif Nam = Name_Element then
12648             F2 := Next_Formal (F1);
12649
12650             if No (F2)
12651               or else Etype (F2) /= Cursor
12652               or else Present (Next_Formal (F2))
12653             then
12654                Error_Msg_N ("no match for Element iterable primitive", N);
12655             end if;
12656             null;
12657
12658          else
12659             raise Program_Error;
12660          end if;
12661
12662       else
12663          --  Overloaded case: find subprogram with proper signature.
12664          --  Caller will report error if no match is found.
12665
12666          declare
12667             I  : Interp_Index;
12668             It : Interp;
12669
12670          begin
12671             Get_First_Interp (N, I, It);
12672             while Present (It.Typ) loop
12673                if Ekind (It.Nam) = E_Function
12674                   and then Scope (It.Nam) = Scope (Typ)
12675                   and then Etype (First_Formal (It.Nam)) = Typ
12676                then
12677                   F1 := First_Formal (It.Nam);
12678
12679                   if Nam = Name_First then
12680                      if Etype (It.Nam) = Cursor
12681                        and then No (Next_Formal (F1))
12682                      then
12683                         Set_Entity (N, It.Nam);
12684                         exit;
12685                      end if;
12686
12687                   elsif Nam = Name_Next then
12688                      F2 := Next_Formal (F1);
12689
12690                      if Present (F2)
12691                        and then No (Next_Formal (F2))
12692                        and then Etype (F2) = Cursor
12693                        and then Etype (It.Nam) = Cursor
12694                      then
12695                         Set_Entity (N, It.Nam);
12696                         exit;
12697                      end if;
12698
12699                   elsif Nam = Name_Has_Element then
12700                      F2 := Next_Formal (F1);
12701
12702                      if Present (F2)
12703                        and then No (Next_Formal (F2))
12704                        and then Etype (F2) = Cursor
12705                        and then Etype (It.Nam) = Standard_Boolean
12706                      then
12707                         Set_Entity (N, It.Nam);
12708                         F2 := Next_Formal (F1);
12709                         exit;
12710                      end if;
12711
12712                   elsif Nam = Name_Element then
12713                      F2 := Next_Formal (F1);
12714
12715                      if Present (F2)
12716                        and then No (Next_Formal (F2))
12717                        and then Etype (F2) = Cursor
12718                      then
12719                         Set_Entity (N, It.Nam);
12720                         exit;
12721                      end if;
12722                   end if;
12723                end if;
12724
12725                Get_Next_Interp (I, It);
12726             end loop;
12727          end;
12728       end if;
12729    end Resolve_Iterable_Operation;
12730
12731    ----------------
12732    -- Set_Biased --
12733    ----------------
12734
12735    procedure Set_Biased
12736      (E      : Entity_Id;
12737       N      : Node_Id;
12738       Msg    : String;
12739       Biased : Boolean := True)
12740    is
12741    begin
12742       if Biased then
12743          Set_Has_Biased_Representation (E);
12744
12745          if Warn_On_Biased_Representation then
12746             Error_Msg_NE
12747               ("?B?" & Msg & " forces biased representation for&", N, E);
12748          end if;
12749       end if;
12750    end Set_Biased;
12751
12752    --------------------
12753    -- Set_Enum_Esize --
12754    --------------------
12755
12756    procedure Set_Enum_Esize (T : Entity_Id) is
12757       Lo : Uint;
12758       Hi : Uint;
12759       Sz : Nat;
12760
12761    begin
12762       Init_Alignment (T);
12763
12764       --  Find the minimum standard size (8,16,32,64) that fits
12765
12766       Lo := Enumeration_Rep (Entity (Type_Low_Bound (T)));
12767       Hi := Enumeration_Rep (Entity (Type_High_Bound (T)));
12768
12769       if Lo < 0 then
12770          if Lo >= -Uint_2**07 and then Hi < Uint_2**07 then
12771             Sz := Standard_Character_Size;  -- May be > 8 on some targets
12772
12773          elsif Lo >= -Uint_2**15 and then Hi < Uint_2**15 then
12774             Sz := 16;
12775
12776          elsif Lo >= -Uint_2**31 and then Hi < Uint_2**31 then
12777             Sz := 32;
12778
12779          else pragma Assert (Lo >= -Uint_2**63 and then Hi < Uint_2**63);
12780             Sz := 64;
12781          end if;
12782
12783       else
12784          if Hi < Uint_2**08 then
12785             Sz := Standard_Character_Size;  -- May be > 8 on some targets
12786
12787          elsif Hi < Uint_2**16 then
12788             Sz := 16;
12789
12790          elsif Hi < Uint_2**32 then
12791             Sz := 32;
12792
12793          else pragma Assert (Hi < Uint_2**63);
12794             Sz := 64;
12795          end if;
12796       end if;
12797
12798       --  That minimum is the proper size unless we have a foreign convention
12799       --  and the size required is 32 or less, in which case we bump the size
12800       --  up to 32. This is required for C and C++ and seems reasonable for
12801       --  all other foreign conventions.
12802
12803       if Has_Foreign_Convention (T)
12804         and then Esize (T) < Standard_Integer_Size
12805
12806         --  Don't do this if Short_Enums on target
12807
12808         and then not Target_Short_Enums
12809       then
12810          Init_Esize (T, Standard_Integer_Size);
12811       else
12812          Init_Esize (T, Sz);
12813       end if;
12814    end Set_Enum_Esize;
12815
12816    -----------------------------
12817    -- Uninstall_Discriminants --
12818    -----------------------------
12819
12820    procedure Uninstall_Discriminants (E : Entity_Id) is
12821       Disc  : Entity_Id;
12822       Prev  : Entity_Id;
12823       Outer : Entity_Id;
12824
12825    begin
12826       --  Discriminants have been made visible for type declarations and
12827       --  protected type declarations, not for subtype declarations.
12828
12829       if Nkind (Parent (E)) /= N_Subtype_Declaration then
12830          Disc := First_Discriminant (E);
12831          while Present (Disc) loop
12832             if Disc /= Current_Entity (Disc) then
12833                Prev := Current_Entity (Disc);
12834                while Present (Prev)
12835                  and then Present (Homonym (Prev))
12836                  and then Homonym (Prev) /= Disc
12837                loop
12838                   Prev := Homonym (Prev);
12839                end loop;
12840             else
12841                Prev := Empty;
12842             end if;
12843
12844             Set_Is_Immediately_Visible (Disc, False);
12845
12846             Outer := Homonym (Disc);
12847             while Present (Outer) and then Scope (Outer) = E loop
12848                Outer := Homonym (Outer);
12849             end loop;
12850
12851             --  Reset homonym link of other entities, but do not modify link
12852             --  between entities in current scope, so that the back-end can
12853             --  have a proper count of local overloadings.
12854
12855             if No (Prev) then
12856                Set_Name_Entity_Id (Chars (Disc), Outer);
12857
12858             elsif Scope (Prev) /= Scope (Disc) then
12859                Set_Homonym (Prev,  Outer);
12860             end if;
12861
12862             Next_Discriminant (Disc);
12863          end loop;
12864       end if;
12865    end Uninstall_Discriminants;
12866
12867    -------------------------------------------
12868    -- Uninstall_Discriminants_And_Pop_Scope --
12869    -------------------------------------------
12870
12871    procedure Uninstall_Discriminants_And_Pop_Scope (E : Entity_Id) is
12872    begin
12873       if Has_Discriminants (E) then
12874          Uninstall_Discriminants (E);
12875          Pop_Scope;
12876       end if;
12877    end Uninstall_Discriminants_And_Pop_Scope;
12878
12879    ------------------------------
12880    -- Validate_Address_Clauses --
12881    ------------------------------
12882
12883    procedure Validate_Address_Clauses is
12884    begin
12885       for J in Address_Clause_Checks.First .. Address_Clause_Checks.Last loop
12886          declare
12887             ACCR : Address_Clause_Check_Record
12888                      renames Address_Clause_Checks.Table (J);
12889
12890             Expr : Node_Id;
12891
12892             X_Alignment : Uint;
12893             Y_Alignment : Uint;
12894
12895             X_Size : Uint;
12896             Y_Size : Uint;
12897
12898          begin
12899             --  Skip processing of this entry if warning already posted
12900
12901             if not Address_Warning_Posted (ACCR.N) then
12902                Expr := Original_Node (Expression (ACCR.N));
12903
12904                --  Get alignments
12905
12906                X_Alignment := Alignment (ACCR.X);
12907                Y_Alignment := Alignment (ACCR.Y);
12908
12909                --  Similarly obtain sizes
12910
12911                X_Size := Esize (ACCR.X);
12912                Y_Size := Esize (ACCR.Y);
12913
12914                --  Check for large object overlaying smaller one
12915
12916                if Y_Size > Uint_0
12917                  and then X_Size > Uint_0
12918                  and then X_Size > Y_Size
12919                then
12920                   Error_Msg_NE
12921                     ("??& overlays smaller object", ACCR.N, ACCR.X);
12922                   Error_Msg_N
12923                     ("\??program execution may be erroneous", ACCR.N);
12924                   Error_Msg_Uint_1 := X_Size;
12925                   Error_Msg_NE
12926                     ("\??size of & is ^", ACCR.N, ACCR.X);
12927                   Error_Msg_Uint_1 := Y_Size;
12928                   Error_Msg_NE
12929                     ("\??size of & is ^", ACCR.N, ACCR.Y);
12930
12931                --  Check for inadequate alignment, both of the base object
12932                --  and of the offset, if any. We only do this check if the
12933                --  run-time Alignment_Check is active. No point in warning
12934                --  if this check has been suppressed (or is suppressed by
12935                --  default in the non-strict alignment machine case).
12936
12937                --  Note: we do not check the alignment if we gave a size
12938                --  warning, since it would likely be redundant.
12939
12940                elsif not Alignment_Checks_Suppressed (ACCR.Y)
12941                  and then Y_Alignment /= Uint_0
12942                  and then (Y_Alignment < X_Alignment
12943                              or else (ACCR.Off
12944                                         and then
12945                                           Nkind (Expr) = N_Attribute_Reference
12946                                         and then
12947                                           Attribute_Name (Expr) = Name_Address
12948                                         and then
12949                                           Has_Compatible_Alignment
12950                                             (ACCR.X, Prefix (Expr))
12951                                              /= Known_Compatible))
12952                then
12953                   Error_Msg_NE
12954                     ("??specified address for& may be inconsistent "
12955                        & "with alignment", ACCR.N, ACCR.X);
12956                   Error_Msg_N
12957                     ("\??program execution may be erroneous (RM 13.3(27))",
12958                      ACCR.N);
12959                   Error_Msg_Uint_1 := X_Alignment;
12960                   Error_Msg_NE
12961                     ("\??alignment of & is ^", ACCR.N, ACCR.X);
12962                   Error_Msg_Uint_1 := Y_Alignment;
12963                   Error_Msg_NE
12964                     ("\??alignment of & is ^", ACCR.N, ACCR.Y);
12965                   if Y_Alignment >= X_Alignment then
12966                      Error_Msg_N
12967                       ("\??but offset is not multiple of alignment", ACCR.N);
12968                   end if;
12969                end if;
12970             end if;
12971          end;
12972       end loop;
12973    end Validate_Address_Clauses;
12974
12975    ---------------------------
12976    -- Validate_Independence --
12977    ---------------------------
12978
12979    procedure Validate_Independence is
12980       SU   : constant Uint := UI_From_Int (System_Storage_Unit);
12981       N    : Node_Id;
12982       E    : Entity_Id;
12983       IC   : Boolean;
12984       Comp : Entity_Id;
12985       Addr : Node_Id;
12986       P    : Node_Id;
12987
12988       procedure Check_Array_Type (Atyp : Entity_Id);
12989       --  Checks if the array type Atyp has independent components, and
12990       --  if not, outputs an appropriate set of error messages.
12991
12992       procedure No_Independence;
12993       --  Output message that independence cannot be guaranteed
12994
12995       function OK_Component (C : Entity_Id) return Boolean;
12996       --  Checks one component to see if it is independently accessible, and
12997       --  if so yields True, otherwise yields False if independent access
12998       --  cannot be guaranteed. This is a conservative routine, it only
12999       --  returns True if it knows for sure, it returns False if it knows
13000       --  there is a problem, or it cannot be sure there is no problem.
13001
13002       procedure Reason_Bad_Component (C : Entity_Id);
13003       --  Outputs continuation message if a reason can be determined for
13004       --  the component C being bad.
13005
13006       ----------------------
13007       -- Check_Array_Type --
13008       ----------------------
13009
13010       procedure Check_Array_Type (Atyp : Entity_Id) is
13011          Ctyp : constant Entity_Id := Component_Type (Atyp);
13012
13013       begin
13014          --  OK if no alignment clause, no pack, and no component size
13015
13016          if not Has_Component_Size_Clause (Atyp)
13017            and then not Has_Alignment_Clause (Atyp)
13018            and then not Is_Packed (Atyp)
13019          then
13020             return;
13021          end if;
13022
13023          --  Case of component size is greater than or equal to 64 and the
13024          --  alignment of the array is at least as large as the alignment
13025          --  of the component. We are definitely OK in this situation.
13026
13027          if Known_Component_Size (Atyp)
13028            and then Component_Size (Atyp) >= 64
13029            and then Known_Alignment (Atyp)
13030            and then Known_Alignment (Ctyp)
13031            and then Alignment (Atyp) >= Alignment (Ctyp)
13032          then
13033             return;
13034          end if;
13035
13036          --  Check actual component size
13037
13038          if not Known_Component_Size (Atyp)
13039            or else not (Addressable (Component_Size (Atyp))
13040                          and then Component_Size (Atyp) < 64)
13041            or else Component_Size (Atyp) mod Esize (Ctyp) /= 0
13042          then
13043             No_Independence;
13044
13045             --  Bad component size, check reason
13046
13047             if Has_Component_Size_Clause (Atyp) then
13048                P := Get_Attribute_Definition_Clause
13049                       (Atyp, Attribute_Component_Size);
13050
13051                if Present (P) then
13052                   Error_Msg_Sloc := Sloc (P);
13053                   Error_Msg_N ("\because of Component_Size clause#", N);
13054                   return;
13055                end if;
13056             end if;
13057
13058             if Is_Packed (Atyp) then
13059                P := Get_Rep_Pragma (Atyp, Name_Pack);
13060
13061                if Present (P) then
13062                   Error_Msg_Sloc := Sloc (P);
13063                   Error_Msg_N ("\because of pragma Pack#", N);
13064                   return;
13065                end if;
13066             end if;
13067
13068             --  No reason found, just return
13069
13070             return;
13071          end if;
13072
13073          --  Array type is OK independence-wise
13074
13075          return;
13076       end Check_Array_Type;
13077
13078       ---------------------
13079       -- No_Independence --
13080       ---------------------
13081
13082       procedure No_Independence is
13083       begin
13084          if Pragma_Name (N) = Name_Independent then
13085             Error_Msg_NE ("independence cannot be guaranteed for&", N, E);
13086          else
13087             Error_Msg_NE
13088               ("independent components cannot be guaranteed for&", N, E);
13089          end if;
13090       end No_Independence;
13091
13092       ------------------
13093       -- OK_Component --
13094       ------------------
13095
13096       function OK_Component (C : Entity_Id) return Boolean is
13097          Rec  : constant Entity_Id := Scope (C);
13098          Ctyp : constant Entity_Id := Etype (C);
13099
13100       begin
13101          --  OK if no component clause, no Pack, and no alignment clause
13102
13103          if No (Component_Clause (C))
13104            and then not Is_Packed (Rec)
13105            and then not Has_Alignment_Clause (Rec)
13106          then
13107             return True;
13108          end if;
13109
13110          --  Here we look at the actual component layout. A component is
13111          --  addressable if its size is a multiple of the Esize of the
13112          --  component type, and its starting position in the record has
13113          --  appropriate alignment, and the record itself has appropriate
13114          --  alignment to guarantee the component alignment.
13115
13116          --  Make sure sizes are static, always assume the worst for any
13117          --  cases where we cannot check static values.
13118
13119          if not (Known_Static_Esize (C)
13120                   and then
13121                  Known_Static_Esize (Ctyp))
13122          then
13123             return False;
13124          end if;
13125
13126          --  Size of component must be addressable or greater than 64 bits
13127          --  and a multiple of bytes.
13128
13129          if not Addressable (Esize (C)) and then Esize (C) < Uint_64 then
13130             return False;
13131          end if;
13132
13133          --  Check size is proper multiple
13134
13135          if Esize (C) mod Esize (Ctyp) /= 0 then
13136             return False;
13137          end if;
13138
13139          --  Check alignment of component is OK
13140
13141          if not Known_Component_Bit_Offset (C)
13142            or else Component_Bit_Offset (C) < Uint_0
13143            or else Component_Bit_Offset (C) mod Esize (Ctyp) /= 0
13144          then
13145             return False;
13146          end if;
13147
13148          --  Check alignment of record type is OK
13149
13150          if not Known_Alignment (Rec)
13151            or else (Alignment (Rec) * SU) mod Esize (Ctyp) /= 0
13152          then
13153             return False;
13154          end if;
13155
13156          --  All tests passed, component is addressable
13157
13158          return True;
13159       end OK_Component;
13160
13161       --------------------------
13162       -- Reason_Bad_Component --
13163       --------------------------
13164
13165       procedure Reason_Bad_Component (C : Entity_Id) is
13166          Rec  : constant Entity_Id := Scope (C);
13167          Ctyp : constant Entity_Id := Etype (C);
13168
13169       begin
13170          --  If component clause present assume that's the problem
13171
13172          if Present (Component_Clause (C)) then
13173             Error_Msg_Sloc := Sloc (Component_Clause (C));
13174             Error_Msg_N ("\because of Component_Clause#", N);
13175             return;
13176          end if;
13177
13178          --  If pragma Pack clause present, assume that's the problem
13179
13180          if Is_Packed (Rec) then
13181             P := Get_Rep_Pragma (Rec, Name_Pack);
13182
13183             if Present (P) then
13184                Error_Msg_Sloc := Sloc (P);
13185                Error_Msg_N ("\because of pragma Pack#", N);
13186                return;
13187             end if;
13188          end if;
13189
13190          --  See if record has bad alignment clause
13191
13192          if Has_Alignment_Clause (Rec)
13193            and then Known_Alignment (Rec)
13194            and then (Alignment (Rec) * SU) mod Esize (Ctyp) /= 0
13195          then
13196             P := Get_Attribute_Definition_Clause (Rec, Attribute_Alignment);
13197
13198             if Present (P) then
13199                Error_Msg_Sloc := Sloc (P);
13200                Error_Msg_N ("\because of Alignment clause#", N);
13201             end if;
13202          end if;
13203
13204          --  Couldn't find a reason, so return without a message
13205
13206          return;
13207       end Reason_Bad_Component;
13208
13209    --  Start of processing for Validate_Independence
13210
13211    begin
13212       for J in Independence_Checks.First .. Independence_Checks.Last loop
13213          N  := Independence_Checks.Table (J).N;
13214          E  := Independence_Checks.Table (J).E;
13215          IC := Pragma_Name (N) = Name_Independent_Components;
13216
13217          --  Deal with component case
13218
13219          if Ekind (E) = E_Discriminant or else Ekind (E) = E_Component then
13220             if not OK_Component (E) then
13221                No_Independence;
13222                Reason_Bad_Component (E);
13223                goto Continue;
13224             end if;
13225          end if;
13226
13227          --  Deal with record with Independent_Components
13228
13229          if IC and then Is_Record_Type (E) then
13230             Comp := First_Component_Or_Discriminant (E);
13231             while Present (Comp) loop
13232                if not OK_Component (Comp) then
13233                   No_Independence;
13234                   Reason_Bad_Component (Comp);
13235                   goto Continue;
13236                end if;
13237
13238                Next_Component_Or_Discriminant (Comp);
13239             end loop;
13240          end if;
13241
13242          --  Deal with address clause case
13243
13244          if Is_Object (E) then
13245             Addr := Address_Clause (E);
13246
13247             if Present (Addr) then
13248                No_Independence;
13249                Error_Msg_Sloc := Sloc (Addr);
13250                Error_Msg_N ("\because of Address clause#", N);
13251                goto Continue;
13252             end if;
13253          end if;
13254
13255          --  Deal with independent components for array type
13256
13257          if IC and then Is_Array_Type (E) then
13258             Check_Array_Type (E);
13259          end if;
13260
13261          --  Deal with independent components for array object
13262
13263          if IC and then Is_Object (E) and then Is_Array_Type (Etype (E)) then
13264             Check_Array_Type (Etype (E));
13265          end if;
13266
13267       <<Continue>> null;
13268       end loop;
13269    end Validate_Independence;
13270
13271    ------------------------------
13272    -- Validate_Iterable_Aspect --
13273    ------------------------------
13274
13275    procedure Validate_Iterable_Aspect (Typ : Entity_Id; ASN : Node_Id) is
13276       Assoc : Node_Id;
13277       Expr  : Node_Id;
13278
13279       Prim   : Node_Id;
13280       Cursor : constant Entity_Id := Get_Cursor_Type (ASN, Typ);
13281
13282       First_Id       : Entity_Id;
13283       Next_Id        : Entity_Id;
13284       Has_Element_Id : Entity_Id;
13285       Element_Id     : Entity_Id;
13286
13287    begin
13288       --  If previous error aspect is unusable
13289
13290       if Cursor = Any_Type then
13291          return;
13292       end if;
13293
13294       First_Id       := Empty;
13295       Next_Id        := Empty;
13296       Has_Element_Id := Empty;
13297       Element_Id     := Empty;
13298
13299       --  Each expression must resolve to a function with the proper signature
13300
13301       Assoc := First (Component_Associations (Expression (ASN)));
13302       while Present (Assoc) loop
13303          Expr := Expression (Assoc);
13304          Analyze (Expr);
13305
13306          Prim := First (Choices (Assoc));
13307
13308          if Nkind (Prim) /= N_Identifier or else Present (Next (Prim)) then
13309             Error_Msg_N ("illegal name in association", Prim);
13310
13311          elsif Chars (Prim) = Name_First then
13312             Resolve_Iterable_Operation (Expr, Cursor, Typ, Name_First);
13313             First_Id := Entity (Expr);
13314
13315          elsif Chars (Prim) = Name_Next then
13316             Resolve_Iterable_Operation (Expr, Cursor, Typ, Name_Next);
13317             Next_Id := Entity (Expr);
13318
13319          elsif Chars (Prim) = Name_Has_Element then
13320             Resolve_Iterable_Operation (Expr, Cursor, Typ, Name_Has_Element);
13321             Has_Element_Id := Entity (Expr);
13322
13323          elsif Chars (Prim) = Name_Element then
13324             Resolve_Iterable_Operation (Expr, Cursor, Typ, Name_Element);
13325             Element_Id := Entity (Expr);
13326
13327          else
13328             Error_Msg_N ("invalid name for iterable function", Prim);
13329          end if;
13330
13331          Next (Assoc);
13332       end loop;
13333
13334       if No (First_Id) then
13335          Error_Msg_N ("match for First primitive not found", ASN);
13336
13337       elsif No (Next_Id) then
13338          Error_Msg_N ("match for Next primitive not found", ASN);
13339
13340       elsif No (Has_Element_Id) then
13341          Error_Msg_N ("match for Has_Element primitive not found", ASN);
13342
13343       elsif No (Element_Id) then
13344          null;  --  Optional.
13345       end if;
13346    end Validate_Iterable_Aspect;
13347
13348    -----------------------------------
13349    -- Validate_Unchecked_Conversion --
13350    -----------------------------------
13351
13352    procedure Validate_Unchecked_Conversion
13353      (N        : Node_Id;
13354       Act_Unit : Entity_Id)
13355    is
13356       Source : Entity_Id;
13357       Target : Entity_Id;
13358       Vnode  : Node_Id;
13359
13360    begin
13361       --  Obtain source and target types. Note that we call Ancestor_Subtype
13362       --  here because the processing for generic instantiation always makes
13363       --  subtypes, and we want the original frozen actual types.
13364
13365       --  If we are dealing with private types, then do the check on their
13366       --  fully declared counterparts if the full declarations have been
13367       --  encountered (they don't have to be visible, but they must exist).
13368
13369       Source := Ancestor_Subtype (Etype (First_Formal (Act_Unit)));
13370
13371       if Is_Private_Type (Source)
13372         and then Present (Underlying_Type (Source))
13373       then
13374          Source := Underlying_Type (Source);
13375       end if;
13376
13377       Target := Ancestor_Subtype (Etype (Act_Unit));
13378
13379       --  If either type is generic, the instantiation happens within a generic
13380       --  unit, and there is nothing to check. The proper check will happen
13381       --  when the enclosing generic is instantiated.
13382
13383       if Is_Generic_Type (Source) or else Is_Generic_Type (Target) then
13384          return;
13385       end if;
13386
13387       if Is_Private_Type (Target)
13388         and then Present (Underlying_Type (Target))
13389       then
13390          Target := Underlying_Type (Target);
13391       end if;
13392
13393       --  Source may be unconstrained array, but not target
13394
13395       if Is_Array_Type (Target) and then not Is_Constrained (Target) then
13396          Error_Msg_N
13397            ("unchecked conversion to unconstrained array not allowed", N);
13398          return;
13399       end if;
13400
13401       --  Warn if conversion between two different convention pointers
13402
13403       if Is_Access_Type (Target)
13404         and then Is_Access_Type (Source)
13405         and then Convention (Target) /= Convention (Source)
13406         and then Warn_On_Unchecked_Conversion
13407       then
13408          --  Give warnings for subprogram pointers only on most targets
13409
13410          if Is_Access_Subprogram_Type (Target)
13411            or else Is_Access_Subprogram_Type (Source)
13412          then
13413             Error_Msg_N
13414               ("?z?conversion between pointers with different conventions!",
13415                N);
13416          end if;
13417       end if;
13418
13419       --  Warn if one of the operands is Ada.Calendar.Time. Do not emit a
13420       --  warning when compiling GNAT-related sources.
13421
13422       if Warn_On_Unchecked_Conversion
13423         and then not In_Predefined_Unit (N)
13424         and then RTU_Loaded (Ada_Calendar)
13425         and then (Chars (Source) = Name_Time
13426                     or else
13427                   Chars (Target) = Name_Time)
13428       then
13429          --  If Ada.Calendar is loaded and the name of one of the operands is
13430          --  Time, there is a good chance that this is Ada.Calendar.Time.
13431
13432          declare
13433             Calendar_Time : constant Entity_Id := Full_View (RTE (RO_CA_Time));
13434          begin
13435             pragma Assert (Present (Calendar_Time));
13436
13437             if Source = Calendar_Time or else Target = Calendar_Time then
13438                Error_Msg_N
13439                  ("?z?representation of 'Time values may change between "
13440                   & "'G'N'A'T versions", N);
13441             end if;
13442          end;
13443       end if;
13444
13445       --  Make entry in unchecked conversion table for later processing by
13446       --  Validate_Unchecked_Conversions, which will check sizes and alignments
13447       --  (using values set by the back-end where possible). This is only done
13448       --  if the appropriate warning is active.
13449
13450       if Warn_On_Unchecked_Conversion then
13451          Unchecked_Conversions.Append
13452            (New_Val => UC_Entry'(Eloc     => Sloc (N),
13453                                  Source   => Source,
13454                                  Target   => Target,
13455                                  Act_Unit => Act_Unit));
13456
13457          --  If both sizes are known statically now, then back end annotation
13458          --  is not required to do a proper check but if either size is not
13459          --  known statically, then we need the annotation.
13460
13461          if Known_Static_RM_Size (Source)
13462               and then
13463             Known_Static_RM_Size (Target)
13464          then
13465             null;
13466          else
13467             Back_Annotate_Rep_Info := True;
13468          end if;
13469       end if;
13470
13471       --  If unchecked conversion to access type, and access type is declared
13472       --  in the same unit as the unchecked conversion, then set the flag
13473       --  No_Strict_Aliasing (no strict aliasing is implicit here)
13474
13475       if Is_Access_Type (Target) and then
13476         In_Same_Source_Unit (Target, N)
13477       then
13478          Set_No_Strict_Aliasing (Implementation_Base_Type (Target));
13479       end if;
13480
13481       --  Generate N_Validate_Unchecked_Conversion node for back end in case
13482       --  the back end needs to perform special validation checks.
13483
13484       --  Shouldn't this be in Exp_Ch13, since the check only gets done if we
13485       --  have full expansion and the back end is called ???
13486
13487       Vnode :=
13488         Make_Validate_Unchecked_Conversion (Sloc (N));
13489       Set_Source_Type (Vnode, Source);
13490       Set_Target_Type (Vnode, Target);
13491
13492       --  If the unchecked conversion node is in a list, just insert before it.
13493       --  If not we have some strange case, not worth bothering about.
13494
13495       if Is_List_Member (N) then
13496          Insert_After (N, Vnode);
13497       end if;
13498    end Validate_Unchecked_Conversion;
13499
13500    ------------------------------------
13501    -- Validate_Unchecked_Conversions --
13502    ------------------------------------
13503
13504    procedure Validate_Unchecked_Conversions is
13505    begin
13506       for N in Unchecked_Conversions.First .. Unchecked_Conversions.Last loop
13507          declare
13508             T : UC_Entry renames Unchecked_Conversions.Table (N);
13509
13510             Eloc     : constant Source_Ptr := T.Eloc;
13511             Source   : constant Entity_Id  := T.Source;
13512             Target   : constant Entity_Id  := T.Target;
13513             Act_Unit : constant Entity_Id  := T.Act_Unit;
13514
13515             Source_Siz : Uint;
13516             Target_Siz : Uint;
13517
13518          begin
13519             --  Skip if function marked as warnings off
13520
13521             if Warnings_Off (Act_Unit) then
13522                goto Continue;
13523             end if;
13524
13525             --  This validation check, which warns if we have unequal sizes for
13526             --  unchecked conversion, and thus potentially implementation
13527             --  dependent semantics, is one of the few occasions on which we
13528             --  use the official RM size instead of Esize. See description in
13529             --  Einfo "Handling of Type'Size Values" for details.
13530
13531             if Serious_Errors_Detected = 0
13532               and then Known_Static_RM_Size (Source)
13533               and then Known_Static_RM_Size (Target)
13534
13535               --  Don't do the check if warnings off for either type, note the
13536               --  deliberate use of OR here instead of OR ELSE to get the flag
13537               --  Warnings_Off_Used set for both types if appropriate.
13538
13539               and then not (Has_Warnings_Off (Source)
13540                               or
13541                             Has_Warnings_Off (Target))
13542             then
13543                Source_Siz := RM_Size (Source);
13544                Target_Siz := RM_Size (Target);
13545
13546                if Source_Siz /= Target_Siz then
13547                   Error_Msg
13548                     ("?z?types for unchecked conversion have different sizes!",
13549                      Eloc);
13550
13551                   if All_Errors_Mode then
13552                      Error_Msg_Name_1 := Chars (Source);
13553                      Error_Msg_Uint_1 := Source_Siz;
13554                      Error_Msg_Name_2 := Chars (Target);
13555                      Error_Msg_Uint_2 := Target_Siz;
13556                      Error_Msg ("\size of % is ^, size of % is ^?z?", Eloc);
13557
13558                      Error_Msg_Uint_1 := UI_Abs (Source_Siz - Target_Siz);
13559
13560                      if Is_Discrete_Type (Source)
13561                           and then
13562                         Is_Discrete_Type (Target)
13563                      then
13564                         if Source_Siz > Target_Siz then
13565                            Error_Msg
13566                              ("\?z?^ high order bits of source will "
13567                               & "be ignored!", Eloc);
13568
13569                         elsif Is_Unsigned_Type (Source) then
13570                            Error_Msg
13571                              ("\?z?source will be extended with ^ high order "
13572                               & "zero bits!", Eloc);
13573
13574                         else
13575                            Error_Msg
13576                              ("\?z?source will be extended with ^ high order "
13577                               & "sign bits!", Eloc);
13578                         end if;
13579
13580                      elsif Source_Siz < Target_Siz then
13581                         if Is_Discrete_Type (Target) then
13582                            if Bytes_Big_Endian then
13583                               Error_Msg
13584                                 ("\?z?target value will include ^ undefined "
13585                                  & "low order bits!", Eloc);
13586                            else
13587                               Error_Msg
13588                                 ("\?z?target value will include ^ undefined "
13589                                  & "high order bits!", Eloc);
13590                            end if;
13591
13592                         else
13593                            Error_Msg
13594                              ("\?z?^ trailing bits of target value will be "
13595                               & "undefined!", Eloc);
13596                         end if;
13597
13598                      else pragma Assert (Source_Siz > Target_Siz);
13599                         if Is_Discrete_Type (Source) then
13600                            if Bytes_Big_Endian then
13601                               Error_Msg
13602                                 ("\?z?^ low order bits of source will be "
13603                                  & "ignored!", Eloc);
13604                            else
13605                               Error_Msg
13606                                 ("\?z?^ high order bits of source will be "
13607                                  & "ignored!", Eloc);
13608                            end if;
13609
13610                         else
13611                            Error_Msg
13612                              ("\?z?^ trailing bits of source will be "
13613                               & "ignored!", Eloc);
13614                         end if;
13615                      end if;
13616                   end if;
13617                end if;
13618             end if;
13619
13620             --  If both types are access types, we need to check the alignment.
13621             --  If the alignment of both is specified, we can do it here.
13622
13623             if Serious_Errors_Detected = 0
13624               and then Is_Access_Type (Source)
13625               and then Is_Access_Type (Target)
13626               and then Target_Strict_Alignment
13627               and then Present (Designated_Type (Source))
13628               and then Present (Designated_Type (Target))
13629             then
13630                declare
13631                   D_Source : constant Entity_Id := Designated_Type (Source);
13632                   D_Target : constant Entity_Id := Designated_Type (Target);
13633
13634                begin
13635                   if Known_Alignment (D_Source)
13636                        and then
13637                      Known_Alignment (D_Target)
13638                   then
13639                      declare
13640                         Source_Align : constant Uint := Alignment (D_Source);
13641                         Target_Align : constant Uint := Alignment (D_Target);
13642
13643                      begin
13644                         if Source_Align < Target_Align
13645                           and then not Is_Tagged_Type (D_Source)
13646
13647                           --  Suppress warning if warnings suppressed on either
13648                           --  type or either designated type. Note the use of
13649                           --  OR here instead of OR ELSE. That is intentional,
13650                           --  we would like to set flag Warnings_Off_Used in
13651                           --  all types for which warnings are suppressed.
13652
13653                           and then not (Has_Warnings_Off (D_Source)
13654                                           or
13655                                         Has_Warnings_Off (D_Target)
13656                                           or
13657                                         Has_Warnings_Off (Source)
13658                                           or
13659                                         Has_Warnings_Off (Target))
13660                         then
13661                            Error_Msg_Uint_1 := Target_Align;
13662                            Error_Msg_Uint_2 := Source_Align;
13663                            Error_Msg_Node_1 := D_Target;
13664                            Error_Msg_Node_2 := D_Source;
13665                            Error_Msg
13666                              ("?z?alignment of & (^) is stricter than "
13667                               & "alignment of & (^)!", Eloc);
13668                            Error_Msg
13669                              ("\?z?resulting access value may have invalid "
13670                               & "alignment!", Eloc);
13671                         end if;
13672                      end;
13673                   end if;
13674                end;
13675             end if;
13676          end;
13677
13678       <<Continue>>
13679          null;
13680       end loop;
13681    end Validate_Unchecked_Conversions;
13682
13683 end Sem_Ch13;