OSDN Git Service

2011-12-12 Robert Dewar <dewar@adacore.com>
[pf3gnuchains/gcc-fork.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-2011, 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 Einfo;    use Einfo;
30 with Elists;   use Elists;
31 with Errout;   use Errout;
32 with Exp_Disp; use Exp_Disp;
33 with Exp_Tss;  use Exp_Tss;
34 with Exp_Util; use Exp_Util;
35 with Lib;      use Lib;
36 with Lib.Xref; use Lib.Xref;
37 with Namet;    use Namet;
38 with Nlists;   use Nlists;
39 with Nmake;    use Nmake;
40 with Opt;      use Opt;
41 with Restrict; use Restrict;
42 with Rident;   use Rident;
43 with Rtsfind;  use Rtsfind;
44 with Sem;      use Sem;
45 with Sem_Aux;  use Sem_Aux;
46 with Sem_Ch3;  use Sem_Ch3;
47 with Sem_Ch6;  use Sem_Ch6;
48 with Sem_Ch8;  use Sem_Ch8;
49 with Sem_Eval; use Sem_Eval;
50 with Sem_Res;  use Sem_Res;
51 with Sem_Type; use Sem_Type;
52 with Sem_Util; use Sem_Util;
53 with Sem_Warn; use Sem_Warn;
54 with Sinput;   use Sinput;
55 with Snames;   use Snames;
56 with Stand;    use Stand;
57 with Sinfo;    use Sinfo;
58 with Stringt;  use Stringt;
59 with Targparm; use Targparm;
60 with Ttypes;   use Ttypes;
61 with Tbuild;   use Tbuild;
62 with Urealp;   use Urealp;
63 with Warnsw;   use Warnsw;
64
65 with GNAT.Heap_Sort_G;
66
67 package body Sem_Ch13 is
68
69    SSU : constant Pos := System_Storage_Unit;
70    --  Convenient short hand for commonly used constant
71
72    -----------------------
73    -- Local Subprograms --
74    -----------------------
75
76    procedure Alignment_Check_For_Size_Change (Typ : Entity_Id; Size : Uint);
77    --  This routine is called after setting one of the sizes of type entity
78    --  Typ to Size. The purpose is to deal with the situation of a derived
79    --  type whose inherited alignment is no longer appropriate for the new
80    --  size value. In this case, we reset the Alignment to unknown.
81
82    procedure Build_Predicate_Function (Typ : Entity_Id; N : Node_Id);
83    --  If Typ has predicates (indicated by Has_Predicates being set for Typ,
84    --  then either there are pragma Invariant entries on the rep chain for the
85    --  type (note that Predicate aspects are converted to pragma Predicate), or
86    --  there are inherited aspects from a parent type, or ancestor subtypes.
87    --  This procedure builds the spec and body for the Predicate function that
88    --  tests these predicates. N is the freeze node for the type. The spec of
89    --  the function is inserted before the freeze node, and the body of the
90    --  function is inserted after the freeze node.
91
92    procedure Build_Static_Predicate
93      (Typ  : Entity_Id;
94       Expr : Node_Id;
95       Nam  : Name_Id);
96    --  Given a predicated type Typ, where Typ is a discrete static subtype,
97    --  whose predicate expression is Expr, tests if Expr is a static predicate,
98    --  and if so, builds the predicate range list. Nam is the name of the one
99    --  argument to the predicate function. Occurrences of the type name in the
100    --  predicate expression have been replaced by identifier references to this
101    --  name, which is unique, so any identifier with Chars matching Nam must be
102    --  a reference to the type. If the predicate is non-static, this procedure
103    --  returns doing nothing. If the predicate is static, then the predicate
104    --  list is stored in Static_Predicate (Typ), and the Expr is rewritten as
105    --  a canonicalized membership operation.
106
107    function Get_Alignment_Value (Expr : Node_Id) return Uint;
108    --  Given the expression for an alignment value, returns the corresponding
109    --  Uint value. If the value is inappropriate, then error messages are
110    --  posted as required, and a value of No_Uint is returned.
111
112    function Is_Operational_Item (N : Node_Id) return Boolean;
113    --  A specification for a stream attribute is allowed before the full type
114    --  is declared, as explained in AI-00137 and the corrigendum. Attributes
115    --  that do not specify a representation characteristic are operational
116    --  attributes.
117
118    procedure New_Stream_Subprogram
119      (N    : Node_Id;
120       Ent  : Entity_Id;
121       Subp : Entity_Id;
122       Nam  : TSS_Name_Type);
123    --  Create a subprogram renaming of a given stream attribute to the
124    --  designated subprogram and then in the tagged case, provide this as a
125    --  primitive operation, or in the non-tagged case make an appropriate TSS
126    --  entry. This is more properly an expansion activity than just semantics,
127    --  but the presence of user-defined stream functions for limited types is a
128    --  legality check, which is why this takes place here rather than in
129    --  exp_ch13, where it was previously. Nam indicates the name of the TSS
130    --  function to be generated.
131    --
132    --  To avoid elaboration anomalies with freeze nodes, for untagged types
133    --  we generate both a subprogram declaration and a subprogram renaming
134    --  declaration, so that the attribute specification is handled as a
135    --  renaming_as_body. For tagged types, the specification is one of the
136    --  primitive specs.
137
138    generic
139       with procedure Replace_Type_Reference (N : Node_Id);
140    procedure Replace_Type_References_Generic (N : Node_Id; TName : Name_Id);
141    --  This is used to scan an expression for a predicate or invariant aspect
142    --  replacing occurrences of the name TName (the name of the subtype to
143    --  which the aspect applies) with appropriate references to the parameter
144    --  of the predicate function or invariant procedure. The procedure passed
145    --  as a generic parameter does the actual replacement of node N, which is
146    --  either a simple direct reference to TName, or a selected component that
147    --  represents an appropriately qualified occurrence of TName.
148
149    procedure Set_Biased
150      (E      : Entity_Id;
151       N      : Node_Id;
152       Msg    : String;
153       Biased : Boolean := True);
154    --  If Biased is True, sets Has_Biased_Representation flag for E, and
155    --  outputs a warning message at node N if Warn_On_Biased_Representation is
156    --  is True. This warning inserts the string Msg to describe the construct
157    --  causing biasing.
158
159    ----------------------------------------------
160    -- Table for Validate_Unchecked_Conversions --
161    ----------------------------------------------
162
163    --  The following table collects unchecked conversions for validation.
164    --  Entries are made by Validate_Unchecked_Conversion and then the call
165    --  to Validate_Unchecked_Conversions does the actual error checking and
166    --  posting of warnings. The reason for this delayed processing is to take
167    --  advantage of back-annotations of size and alignment values performed by
168    --  the back end.
169
170    --  Note: the reason we store a Source_Ptr value instead of a Node_Id is
171    --  that by the time Validate_Unchecked_Conversions is called, Sprint will
172    --  already have modified all Sloc values if the -gnatD option is set.
173
174    type UC_Entry is record
175       Eloc   : Source_Ptr; -- node used for posting warnings
176       Source : Entity_Id;  -- source type for unchecked conversion
177       Target : Entity_Id;  -- target type for unchecked conversion
178    end record;
179
180    package Unchecked_Conversions is new Table.Table (
181      Table_Component_Type => UC_Entry,
182      Table_Index_Type     => Int,
183      Table_Low_Bound      => 1,
184      Table_Initial        => 50,
185      Table_Increment      => 200,
186      Table_Name           => "Unchecked_Conversions");
187
188    ----------------------------------------
189    -- Table for Validate_Address_Clauses --
190    ----------------------------------------
191
192    --  If an address clause has the form
193
194    --    for X'Address use Expr
195
196    --  where Expr is of the form Y'Address or recursively is a reference to a
197    --  constant of either of these forms, and X and Y are entities of objects,
198    --  then if Y has a smaller alignment than X, that merits a warning about
199    --  possible bad alignment. The following table collects address clauses of
200    --  this kind. We put these in a table so that they can be checked after the
201    --  back end has completed annotation of the alignments of objects, since we
202    --  can catch more cases that way.
203
204    type Address_Clause_Check_Record is record
205       N : Node_Id;
206       --  The address clause
207
208       X : Entity_Id;
209       --  The entity of the object overlaying Y
210
211       Y : Entity_Id;
212       --  The entity of the object being overlaid
213
214       Off : Boolean;
215       --  Whether the address is offset within Y
216    end record;
217
218    package Address_Clause_Checks is new Table.Table (
219      Table_Component_Type => Address_Clause_Check_Record,
220      Table_Index_Type     => Int,
221      Table_Low_Bound      => 1,
222      Table_Initial        => 20,
223      Table_Increment      => 200,
224      Table_Name           => "Address_Clause_Checks");
225
226    -----------------------------------------
227    -- Adjust_Record_For_Reverse_Bit_Order --
228    -----------------------------------------
229
230    procedure Adjust_Record_For_Reverse_Bit_Order (R : Entity_Id) is
231       Comp : Node_Id;
232       CC   : Node_Id;
233
234    begin
235       --  Processing depends on version of Ada
236
237       --  For Ada 95, we just renumber bits within a storage unit. We do the
238       --  same for Ada 83 mode, since we recognize the Bit_Order attribute in
239       --  Ada 83, and are free to add this extension.
240
241       if Ada_Version < Ada_2005 then
242          Comp := First_Component_Or_Discriminant (R);
243          while Present (Comp) loop
244             CC := Component_Clause (Comp);
245
246             --  If component clause is present, then deal with the non-default
247             --  bit order case for Ada 95 mode.
248
249             --  We only do this processing for the base type, and in fact that
250             --  is important, since otherwise if there are record subtypes, we
251             --  could reverse the bits once for each subtype, which is wrong.
252
253             if Present (CC)
254               and then Ekind (R) = E_Record_Type
255             then
256                declare
257                   CFB : constant Uint    := Component_Bit_Offset (Comp);
258                   CSZ : constant Uint    := Esize (Comp);
259                   CLC : constant Node_Id := Component_Clause (Comp);
260                   Pos : constant Node_Id := Position (CLC);
261                   FB  : constant Node_Id := First_Bit (CLC);
262
263                   Storage_Unit_Offset : constant Uint :=
264                                           CFB / System_Storage_Unit;
265
266                   Start_Bit : constant Uint :=
267                                 CFB mod System_Storage_Unit;
268
269                begin
270                   --  Cases where field goes over storage unit boundary
271
272                   if Start_Bit + CSZ > System_Storage_Unit then
273
274                      --  Allow multi-byte field but generate warning
275
276                      if Start_Bit mod System_Storage_Unit = 0
277                        and then CSZ mod System_Storage_Unit = 0
278                      then
279                         Error_Msg_N
280                           ("multi-byte field specified with non-standard"
281                            & " Bit_Order?", CLC);
282
283                         if Bytes_Big_Endian then
284                            Error_Msg_N
285                              ("bytes are not reversed "
286                               & "(component is big-endian)?", CLC);
287                         else
288                            Error_Msg_N
289                              ("bytes are not reversed "
290                               & "(component is little-endian)?", CLC);
291                         end if;
292
293                         --  Do not allow non-contiguous field
294
295                      else
296                         Error_Msg_N
297                           ("attempt to specify non-contiguous field "
298                            & "not permitted", CLC);
299                         Error_Msg_N
300                           ("\caused by non-standard Bit_Order "
301                            & "specified", CLC);
302                         Error_Msg_N
303                           ("\consider possibility of using "
304                            & "Ada 2005 mode here", CLC);
305                      end if;
306
307                   --  Case where field fits in one storage unit
308
309                   else
310                      --  Give warning if suspicious component clause
311
312                      if Intval (FB) >= System_Storage_Unit
313                        and then Warn_On_Reverse_Bit_Order
314                      then
315                         Error_Msg_N
316                           ("?Bit_Order clause does not affect " &
317                            "byte ordering", Pos);
318                         Error_Msg_Uint_1 :=
319                           Intval (Pos) + Intval (FB) /
320                           System_Storage_Unit;
321                         Error_Msg_N
322                           ("?position normalized to ^ before bit " &
323                            "order interpreted", Pos);
324                      end if;
325
326                      --  Here is where we fix up the Component_Bit_Offset value
327                      --  to account for the reverse bit order. Some examples of
328                      --  what needs to be done are:
329
330                      --    First_Bit .. Last_Bit     Component_Bit_Offset
331                      --      old          new          old       new
332
333                      --     0 .. 0       7 .. 7         0         7
334                      --     0 .. 1       6 .. 7         0         6
335                      --     0 .. 2       5 .. 7         0         5
336                      --     0 .. 7       0 .. 7         0         4
337
338                      --     1 .. 1       6 .. 6         1         6
339                      --     1 .. 4       3 .. 6         1         3
340                      --     4 .. 7       0 .. 3         4         0
341
342                      --  The rule is that the first bit is is obtained by
343                      --  subtracting the old ending bit from storage_unit - 1.
344
345                      Set_Component_Bit_Offset
346                        (Comp,
347                         (Storage_Unit_Offset * System_Storage_Unit) +
348                           (System_Storage_Unit - 1) -
349                           (Start_Bit + CSZ - 1));
350
351                      Set_Normalized_First_Bit
352                        (Comp,
353                         Component_Bit_Offset (Comp) mod
354                           System_Storage_Unit);
355                   end if;
356                end;
357             end if;
358
359             Next_Component_Or_Discriminant (Comp);
360          end loop;
361
362       --  For Ada 2005, we do machine scalar processing, as fully described In
363       --  AI-133. This involves gathering all components which start at the
364       --  same byte offset and processing them together. Same approach is still
365       --  valid in later versions including Ada 2012.
366
367       else
368          declare
369             Max_Machine_Scalar_Size : constant Uint :=
370                                         UI_From_Int
371                                           (Standard_Long_Long_Integer_Size);
372             --  We use this as the maximum machine scalar size
373
374             Num_CC : Natural;
375             SSU    : constant Uint := UI_From_Int (System_Storage_Unit);
376
377          begin
378             --  This first loop through components does two things. First it
379             --  deals with the case of components with component clauses whose
380             --  length is greater than the maximum machine scalar size (either
381             --  accepting them or rejecting as needed). Second, it counts the
382             --  number of components with component clauses whose length does
383             --  not exceed this maximum for later processing.
384
385             Num_CC := 0;
386             Comp   := First_Component_Or_Discriminant (R);
387             while Present (Comp) loop
388                CC := Component_Clause (Comp);
389
390                if Present (CC) then
391                   declare
392                      Fbit : constant Uint :=
393                               Static_Integer (First_Bit (CC));
394                      Lbit : constant Uint :=
395                               Static_Integer (Last_Bit (CC));
396
397                   begin
398                      --  Case of component with last bit >= max machine scalar
399
400                      if Lbit >= Max_Machine_Scalar_Size then
401
402                         --  This is allowed only if first bit is zero, and
403                         --  last bit + 1 is a multiple of storage unit size.
404
405                         if Fbit = 0 and then (Lbit + 1) mod SSU = 0 then
406
407                            --  This is the case to give a warning if enabled
408
409                            if Warn_On_Reverse_Bit_Order then
410                               Error_Msg_N
411                                 ("multi-byte field specified with "
412                                  & "  non-standard Bit_Order?", CC);
413
414                               if Bytes_Big_Endian then
415                                  Error_Msg_N
416                                    ("\bytes are not reversed "
417                                     & "(component is big-endian)?", CC);
418                               else
419                                  Error_Msg_N
420                                    ("\bytes are not reversed "
421                                     & "(component is little-endian)?", CC);
422                               end if;
423                            end if;
424
425                         --  Give error message for RM 13.4.1(10) violation
426
427                         else
428                            Error_Msg_FE
429                              ("machine scalar rules not followed for&",
430                               First_Bit (CC), Comp);
431
432                            Error_Msg_Uint_1 := Lbit;
433                            Error_Msg_Uint_2 := Max_Machine_Scalar_Size;
434                            Error_Msg_F
435                              ("\last bit (^) exceeds maximum machine "
436                               & "scalar size (^)",
437                               First_Bit (CC));
438
439                            if (Lbit + 1) mod SSU /= 0 then
440                               Error_Msg_Uint_1 := SSU;
441                               Error_Msg_F
442                                 ("\and is not a multiple of Storage_Unit (^) "
443                                  & "(RM 13.4.1(10))",
444                                  First_Bit (CC));
445
446                            else
447                               Error_Msg_Uint_1 := Fbit;
448                               Error_Msg_F
449                                 ("\and first bit (^) is non-zero "
450                                  & "(RM 13.4.1(10))",
451                                  First_Bit (CC));
452                            end if;
453                         end if;
454
455                      --  OK case of machine scalar related component clause,
456                      --  For now, just count them.
457
458                      else
459                         Num_CC := Num_CC + 1;
460                      end if;
461                   end;
462                end if;
463
464                Next_Component_Or_Discriminant (Comp);
465             end loop;
466
467             --  We need to sort the component clauses on the basis of the
468             --  Position values in the clause, so we can group clauses with
469             --  the same Position. together to determine the relevant machine
470             --  scalar size.
471
472             Sort_CC : declare
473                Comps : array (0 .. Num_CC) of Entity_Id;
474                --  Array to collect component and discriminant entities. The
475                --  data starts at index 1, the 0'th entry is for the sort
476                --  routine.
477
478                function CP_Lt (Op1, Op2 : Natural) return Boolean;
479                --  Compare routine for Sort
480
481                procedure CP_Move (From : Natural; To : Natural);
482                --  Move routine for Sort
483
484                package Sorting is new GNAT.Heap_Sort_G (CP_Move, CP_Lt);
485
486                Start : Natural;
487                Stop  : Natural;
488                --  Start and stop positions in the component list of the set of
489                --  components with the same starting position (that constitute
490                --  components in a single machine scalar).
491
492                MaxL  : Uint;
493                --  Maximum last bit value of any component in this set
494
495                MSS   : Uint;
496                --  Corresponding machine scalar size
497
498                -----------
499                -- CP_Lt --
500                -----------
501
502                function CP_Lt (Op1, Op2 : Natural) return Boolean is
503                begin
504                   return Position (Component_Clause (Comps (Op1))) <
505                     Position (Component_Clause (Comps (Op2)));
506                end CP_Lt;
507
508                -------------
509                -- CP_Move --
510                -------------
511
512                procedure CP_Move (From : Natural; To : Natural) is
513                begin
514                   Comps (To) := Comps (From);
515                end CP_Move;
516
517                --  Start of processing for Sort_CC
518
519             begin
520                --  Collect the machine scalar relevant component clauses
521
522                Num_CC := 0;
523                Comp   := First_Component_Or_Discriminant (R);
524                while Present (Comp) loop
525                   declare
526                      CC   : constant Node_Id := Component_Clause (Comp);
527
528                   begin
529                      --  Collect only component clauses whose last bit is less
530                      --  than machine scalar size. Any component clause whose
531                      --  last bit exceeds this value does not take part in
532                      --  machine scalar layout considerations. The test for
533                      --  Error_Posted makes sure we exclude component clauses
534                      --  for which we already posted an error.
535
536                      if Present (CC)
537                        and then not Error_Posted (Last_Bit (CC))
538                        and then Static_Integer (Last_Bit (CC)) <
539                                                     Max_Machine_Scalar_Size
540                      then
541                         Num_CC := Num_CC + 1;
542                         Comps (Num_CC) := Comp;
543                      end if;
544                   end;
545
546                   Next_Component_Or_Discriminant (Comp);
547                end loop;
548
549                --  Sort by ascending position number
550
551                Sorting.Sort (Num_CC);
552
553                --  We now have all the components whose size does not exceed
554                --  the max machine scalar value, sorted by starting position.
555                --  In this loop we gather groups of clauses starting at the
556                --  same position, to process them in accordance with AI-133.
557
558                Stop := 0;
559                while Stop < Num_CC loop
560                   Start := Stop + 1;
561                   Stop  := Start;
562                   MaxL  :=
563                     Static_Integer
564                       (Last_Bit (Component_Clause (Comps (Start))));
565                   while Stop < Num_CC loop
566                      if Static_Integer
567                           (Position (Component_Clause (Comps (Stop + 1)))) =
568                         Static_Integer
569                           (Position (Component_Clause (Comps (Stop))))
570                      then
571                         Stop := Stop + 1;
572                         MaxL :=
573                           UI_Max
574                             (MaxL,
575                              Static_Integer
576                                (Last_Bit
577                                   (Component_Clause (Comps (Stop)))));
578                      else
579                         exit;
580                      end if;
581                   end loop;
582
583                   --  Now we have a group of component clauses from Start to
584                   --  Stop whose positions are identical, and MaxL is the
585                   --  maximum last bit value of any of these components.
586
587                   --  We need to determine the corresponding machine scalar
588                   --  size. This loop assumes that machine scalar sizes are
589                   --  even, and that each possible machine scalar has twice
590                   --  as many bits as the next smaller one.
591
592                   MSS := Max_Machine_Scalar_Size;
593                   while MSS mod 2 = 0
594                     and then (MSS / 2) >= SSU
595                     and then (MSS / 2) > MaxL
596                   loop
597                      MSS := MSS / 2;
598                   end loop;
599
600                   --  Here is where we fix up the Component_Bit_Offset value
601                   --  to account for the reverse bit order. Some examples of
602                   --  what needs to be done for the case of a machine scalar
603                   --  size of 8 are:
604
605                   --    First_Bit .. Last_Bit     Component_Bit_Offset
606                   --      old          new          old       new
607
608                   --     0 .. 0       7 .. 7         0         7
609                   --     0 .. 1       6 .. 7         0         6
610                   --     0 .. 2       5 .. 7         0         5
611                   --     0 .. 7       0 .. 7         0         4
612
613                   --     1 .. 1       6 .. 6         1         6
614                   --     1 .. 4       3 .. 6         1         3
615                   --     4 .. 7       0 .. 3         4         0
616
617                   --  The rule is that the first bit is obtained by subtracting
618                   --  the old ending bit from machine scalar size - 1.
619
620                   for C in Start .. Stop loop
621                      declare
622                         Comp : constant Entity_Id := Comps (C);
623                         CC   : constant Node_Id   :=
624                                  Component_Clause (Comp);
625                         LB   : constant Uint :=
626                                  Static_Integer (Last_Bit (CC));
627                         NFB  : constant Uint := MSS - Uint_1 - LB;
628                         NLB  : constant Uint := NFB + Esize (Comp) - 1;
629                         Pos  : constant Uint :=
630                                  Static_Integer (Position (CC));
631
632                      begin
633                         if Warn_On_Reverse_Bit_Order then
634                            Error_Msg_Uint_1 := MSS;
635                            Error_Msg_N
636                              ("info: reverse bit order in machine " &
637                               "scalar of length^?", First_Bit (CC));
638                            Error_Msg_Uint_1 := NFB;
639                            Error_Msg_Uint_2 := NLB;
640
641                            if Bytes_Big_Endian then
642                               Error_Msg_NE
643                                 ("?\info: big-endian range for "
644                                  & "component & is ^ .. ^",
645                                  First_Bit (CC), Comp);
646                            else
647                               Error_Msg_NE
648                                 ("?\info: little-endian range "
649                                  & "for component & is ^ .. ^",
650                                  First_Bit (CC), Comp);
651                            end if;
652                         end if;
653
654                         Set_Component_Bit_Offset (Comp, Pos * SSU + NFB);
655                         Set_Normalized_First_Bit (Comp, NFB mod SSU);
656                      end;
657                   end loop;
658                end loop;
659             end Sort_CC;
660          end;
661       end if;
662    end Adjust_Record_For_Reverse_Bit_Order;
663
664    -------------------------------------
665    -- Alignment_Check_For_Size_Change --
666    -------------------------------------
667
668    procedure Alignment_Check_For_Size_Change (Typ : Entity_Id; Size : Uint) is
669    begin
670       --  If the alignment is known, and not set by a rep clause, and is
671       --  inconsistent with the size being set, then reset it to unknown,
672       --  we assume in this case that the size overrides the inherited
673       --  alignment, and that the alignment must be recomputed.
674
675       if Known_Alignment (Typ)
676         and then not Has_Alignment_Clause (Typ)
677         and then Size mod (Alignment (Typ) * SSU) /= 0
678       then
679          Init_Alignment (Typ);
680       end if;
681    end Alignment_Check_For_Size_Change;
682
683    -----------------------------------
684    -- Analyze_Aspect_Specifications --
685    -----------------------------------
686
687    procedure Analyze_Aspect_Specifications (N : Node_Id; E : Entity_Id) is
688       Aspect : Node_Id;
689       Aitem  : Node_Id;
690       Ent    : Node_Id;
691
692       L : constant List_Id := Aspect_Specifications (N);
693
694       Ins_Node : Node_Id := N;
695       --  Insert pragmas (except Pre/Post/Invariant/Predicate) after this node
696
697       --  The general processing involves building an attribute definition
698       --  clause or a pragma node that corresponds to the aspect. Then one
699       --  of two things happens:
700
701       --  If we are required to delay the evaluation of this aspect to the
702       --  freeze point, we attach the corresponding pragma/attribute definition
703       --  clause to the aspect specification node, which is then placed in the
704       --  Rep Item chain. In this case we mark the entity by setting the flag
705       --  Has_Delayed_Aspects and we evaluate the rep item at the freeze point.
706
707       --  If no delay is required, we just insert the pragma or attribute
708       --  after the declaration, and it will get processed by the normal
709       --  circuit. The From_Aspect_Specification flag is set on the pragma
710       --  or attribute definition node in either case to activate special
711       --  processing (e.g. not traversing the list of homonyms for inline).
712
713       Delay_Required : Boolean := False;
714       --  Set True if delay is required
715
716    begin
717       pragma Assert (Present (L));
718
719       --  Loop through aspects
720
721       Aspect := First (L);
722       Aspect_Loop : while Present (Aspect) loop
723          declare
724             Loc  : constant Source_Ptr := Sloc (Aspect);
725             Id   : constant Node_Id    := Identifier (Aspect);
726             Expr : constant Node_Id    := Expression (Aspect);
727             Nam  : constant Name_Id    := Chars (Id);
728             A_Id : constant Aspect_Id  := Get_Aspect_Id (Nam);
729             Anod : Node_Id;
730
731             Eloc : Source_Ptr := No_Location;
732             --  Source location of expression, modified when we split PPC's. It
733             --  is set below when Expr is present.
734
735             procedure Check_False_Aspect_For_Derived_Type;
736             --  This procedure checks for the case of a false aspect for a
737             --  derived type, which improperly tries to cancel an aspect
738             --  inherited from the parent;
739
740             -----------------------------------------
741             -- Check_False_Aspect_For_Derived_Type --
742             -----------------------------------------
743
744             procedure Check_False_Aspect_For_Derived_Type is
745             begin
746                --  We are only checking derived types
747
748                if not Is_Derived_Type (E) then
749                   return;
750                end if;
751
752                case A_Id is
753                   when Aspect_Atomic | Aspect_Shared =>
754                      if not Is_Atomic (E) then
755                         return;
756                      end if;
757
758                   when Aspect_Atomic_Components =>
759                      if not Has_Atomic_Components (E) then
760                         return;
761                      end if;
762
763                   when Aspect_Discard_Names =>
764                      if not Discard_Names (E) then
765                         return;
766                      end if;
767
768                   when Aspect_Pack =>
769                      if not Is_Packed (E) then
770                         return;
771                      end if;
772
773                   when Aspect_Unchecked_Union =>
774                      if not Is_Unchecked_Union (E) then
775                         return;
776                      end if;
777
778                   when Aspect_Volatile =>
779                      if not Is_Volatile (E) then
780                         return;
781                      end if;
782
783                   when Aspect_Volatile_Components =>
784                      if not Has_Volatile_Components (E) then
785                         return;
786                      end if;
787
788                   when others =>
789                      return;
790                end case;
791
792                --  Fall through means we are canceling an inherited aspect
793
794                Error_Msg_Name_1 := Nam;
795                Error_Msg_NE
796                  ("derived type& inherits aspect%, cannot cancel", Expr, E);
797             end Check_False_Aspect_For_Derived_Type;
798
799          --  Start of processing for Aspect_Loop
800
801          begin
802             --  Skip aspect if already analyzed (not clear if this is needed)
803
804             if Analyzed (Aspect) then
805                goto Continue;
806             end if;
807
808             --  Set the source location of expression, used in the case of
809             --  a failed precondition/postcondition or invariant. Note that
810             --  the source location of the expression is not usually the best
811             --  choice here. For example, it gets located on the last AND
812             --  keyword in a chain of boolean expressiond AND'ed together.
813             --  It is best to put the message on the first character of the
814             --  assertion, which is the effect of the First_Node call here.
815
816             if Present (Expr) then
817                Eloc := Sloc (First_Node (Expr));
818             end if;
819
820             --  Check restriction No_Implementation_Aspect_Specifications
821
822             if Impl_Defined_Aspects (A_Id) then
823                Check_Restriction
824                  (No_Implementation_Aspect_Specifications, Aspect);
825             end if;
826
827             --  Check restriction No_Specification_Of_Aspect
828
829             Check_Restriction_No_Specification_Of_Aspect (Aspect);
830
831             --  Analyze this aspect
832
833             Set_Analyzed (Aspect);
834             Set_Entity (Aspect, E);
835             Ent := New_Occurrence_Of (E, Sloc (Id));
836
837             --  Check for duplicate aspect. Note that the Comes_From_Source
838             --  test allows duplicate Pre/Post's that we generate internally
839             --  to escape being flagged here.
840
841             if No_Duplicates_Allowed (A_Id) then
842                Anod := First (L);
843                while Anod /= Aspect loop
844                   if Same_Aspect
845                       (A_Id, Get_Aspect_Id (Chars (Identifier (Anod))))
846                     and then Comes_From_Source (Aspect)
847                   then
848                      Error_Msg_Name_1 := Nam;
849                      Error_Msg_Sloc := Sloc (Anod);
850
851                      --  Case of same aspect specified twice
852
853                      if Class_Present (Anod) = Class_Present (Aspect) then
854                         if not Class_Present (Anod) then
855                            Error_Msg_NE
856                              ("aspect% for & previously given#",
857                               Id, E);
858                         else
859                            Error_Msg_NE
860                              ("aspect `%''Class` for & previously given#",
861                               Id, E);
862                         end if;
863
864                         --  Case of Pre and Pre'Class both specified
865
866                      elsif Nam = Name_Pre then
867                         if Class_Present (Aspect) then
868                            Error_Msg_NE
869                              ("aspect `Pre''Class` for & is not allowed here",
870                               Id, E);
871                            Error_Msg_NE
872                              ("\since aspect `Pre` previously given#",
873                               Id, E);
874
875                         else
876                            Error_Msg_NE
877                              ("aspect `Pre` for & is not allowed here",
878                               Id, E);
879                            Error_Msg_NE
880                              ("\since aspect `Pre''Class` previously given#",
881                               Id, E);
882                         end if;
883                      end if;
884
885                      --  Allowed case of X and X'Class both specified
886                   end if;
887
888                   Next (Anod);
889                end loop;
890             end if;
891
892             --  Copy expression for later processing by the procedures
893             --  Check_Aspect_At_[Freeze_Point | End_Of_Declarations]
894
895             Set_Entity (Id, New_Copy_Tree (Expr));
896
897             --  Processing based on specific aspect
898
899             case A_Id is
900
901                --  No_Aspect should be impossible
902
903                when No_Aspect =>
904                   raise Program_Error;
905
906                --  Aspects taking an optional boolean argument. For all of
907                --  these we just create a matching pragma and insert it, if
908                --  the expression is missing or set to True. If the expression
909                --  is False, we can ignore the aspect with the exception that
910                --  in the case of a derived type, we must check for an illegal
911                --  attempt to cancel an inherited aspect.
912
913                when Boolean_Aspects =>
914                   Set_Is_Boolean_Aspect (Aspect);
915
916                   if Present (Expr)
917                     and then Is_False (Static_Boolean (Expr))
918                   then
919                      Check_False_Aspect_For_Derived_Type;
920                      goto Continue;
921                   end if;
922
923                   --  If True, build corresponding pragma node
924
925                   Aitem :=
926                     Make_Pragma (Loc,
927                       Pragma_Argument_Associations => New_List (Ent),
928                       Pragma_Identifier            =>
929                         Make_Identifier (Sloc (Id), Chars (Id)));
930
931                   --  Never need to delay for boolean aspects
932
933                   pragma Assert (not Delay_Required);
934
935                --  Library unit aspects. These are boolean aspects, but we
936                --  have to do special things with the insertion, since the
937                --  pragma belongs inside the declarations of a package.
938
939                when Library_Unit_Aspects =>
940                   if Present (Expr)
941                     and then Is_False (Static_Boolean (Expr))
942                   then
943                      goto Continue;
944                   end if;
945
946                   --  Build corresponding pragma node
947
948                   Aitem :=
949                     Make_Pragma (Loc,
950                       Pragma_Argument_Associations => New_List (Ent),
951                       Pragma_Identifier            =>
952                         Make_Identifier (Sloc (Id), Chars (Id)));
953
954                   --  This requires special handling in the case of a package
955                   --  declaration, the pragma needs to be inserted in the list
956                   --  of declarations for the associated package. There is no
957                   --  issue of visibility delay for these aspects.
958
959                   if Nkind (N) = N_Package_Declaration then
960                      if Nkind (Parent (N)) /= N_Compilation_Unit then
961                         Error_Msg_N
962                           ("incorrect context for library unit aspect&", Id);
963                      else
964                         Prepend
965                           (Aitem, Visible_Declarations (Specification (N)));
966                      end if;
967
968                      goto Continue;
969                   end if;
970
971                   --  If not package declaration, no delay is required
972
973                   pragma Assert (not Delay_Required);
974
975                --  Aspects related to container iterators. These aspects denote
976                --  subprograms, and thus must be delayed.
977
978                when Aspect_Constant_Indexing    |
979                     Aspect_Variable_Indexing    =>
980
981                   if not Is_Type (E) or else not Is_Tagged_Type (E) then
982                      Error_Msg_N ("indexing applies to a tagged type", N);
983                   end if;
984
985                   Aitem :=
986                     Make_Attribute_Definition_Clause (Loc,
987                       Name       => Ent,
988                       Chars      => Chars (Id),
989                       Expression => Relocate_Node (Expr));
990
991                   Delay_Required := True;
992                   Set_Is_Delayed_Aspect (Aspect);
993
994                when Aspect_Default_Iterator     |
995                     Aspect_Iterator_Element     =>
996
997                   Aitem :=
998                     Make_Attribute_Definition_Clause (Loc,
999                       Name       => Ent,
1000                       Chars      => Chars (Id),
1001                       Expression => Relocate_Node (Expr));
1002
1003                   Delay_Required := True;
1004                   Set_Is_Delayed_Aspect (Aspect);
1005
1006                when Aspect_Implicit_Dereference =>
1007                   if not Is_Type (E)
1008                     or else not Has_Discriminants (E)
1009                   then
1010                      Error_Msg_N
1011                        ("Aspect must apply to a type with discriminants", N);
1012                      goto Continue;
1013
1014                   else
1015                      declare
1016                         Disc : Entity_Id;
1017
1018                      begin
1019                         Disc := First_Discriminant (E);
1020                         while Present (Disc) loop
1021                            if Chars (Expr) = Chars (Disc)
1022                              and then Ekind (Etype (Disc)) =
1023                                E_Anonymous_Access_Type
1024                            then
1025                               Set_Has_Implicit_Dereference (E);
1026                               Set_Has_Implicit_Dereference (Disc);
1027                               goto Continue;
1028                            end if;
1029
1030                            Next_Discriminant (Disc);
1031                         end loop;
1032
1033                         --  Error if no proper access discriminant.
1034
1035                         Error_Msg_NE
1036                          ("not an access discriminant of&", Expr, E);
1037                      end;
1038
1039                      goto Continue;
1040                   end if;
1041
1042                --  Aspects corresponding to attribute definition clauses
1043
1044                when Aspect_Address        |
1045                     Aspect_Alignment      |
1046                     Aspect_Bit_Order      |
1047                     Aspect_Component_Size |
1048                     Aspect_External_Tag   |
1049                     Aspect_Input          |
1050                     Aspect_Machine_Radix  |
1051                     Aspect_Object_Size    |
1052                     Aspect_Output         |
1053                     Aspect_Read           |
1054                     Aspect_Size           |
1055                     Aspect_Small          |
1056                     Aspect_Storage_Pool   |
1057                     Aspect_Storage_Size   |
1058                     Aspect_Stream_Size    |
1059                     Aspect_Value_Size     |
1060                     Aspect_Write          =>
1061
1062                   --  Construct the attribute definition clause
1063
1064                   Aitem :=
1065                     Make_Attribute_Definition_Clause (Loc,
1066                       Name       => Ent,
1067                       Chars      => Chars (Id),
1068                       Expression => Relocate_Node (Expr));
1069
1070                   --  A delay is required except in the common case where
1071                   --  the expression is a literal, in which case it is fine
1072                   --  to take care of it right away.
1073
1074                   if Nkind_In (Expr, N_Integer_Literal, N_String_Literal) then
1075                      pragma Assert (not Delay_Required);
1076                      null;
1077                   else
1078                      Delay_Required := True;
1079                      Set_Is_Delayed_Aspect (Aspect);
1080                   end if;
1081
1082                --  Aspects corresponding to pragmas with two arguments, where
1083                --  the first argument is a local name referring to the entity,
1084                --  and the second argument is the aspect definition expression
1085                --  which is an expression that does not get analyzed.
1086
1087                when Aspect_Suppress   |
1088                     Aspect_Unsuppress =>
1089
1090                   --  Construct the pragma
1091
1092                   Aitem :=
1093                     Make_Pragma (Loc,
1094                       Pragma_Argument_Associations => New_List (
1095                         New_Occurrence_Of (E, Loc),
1096                         Relocate_Node (Expr)),
1097                       Pragma_Identifier            =>
1098                         Make_Identifier (Sloc (Id), Chars (Id)));
1099
1100                   --  We don't have to play the delay game here, since the only
1101                   --  values are check names which don't get analyzed anyway.
1102
1103                   pragma Assert (not Delay_Required);
1104
1105                --  Aspects corresponding to pragmas with two arguments, where
1106                --  the second argument is a local name referring to the entity,
1107                --  and the first argument is the aspect definition expression.
1108
1109                when Aspect_Warnings =>
1110
1111                   --  Construct the pragma
1112
1113                   Aitem :=
1114                     Make_Pragma (Loc,
1115                       Pragma_Argument_Associations => New_List (
1116                         Relocate_Node (Expr),
1117                         New_Occurrence_Of (E, Loc)),
1118                       Pragma_Identifier            =>
1119                         Make_Identifier (Sloc (Id), Chars (Id)),
1120                       Class_Present                => Class_Present (Aspect));
1121
1122                   --  We don't have to play the delay game here, since the only
1123                   --  values are ON/OFF which don't get analyzed anyway.
1124
1125                   pragma Assert (not Delay_Required);
1126
1127                --  Default_Value and Default_Component_Value aspects. These
1128                --  are specially handled because they have no corresponding
1129                --  pragmas or attributes.
1130
1131                when Aspect_Default_Value | Aspect_Default_Component_Value =>
1132                   Error_Msg_Name_1 := Chars (Id);
1133
1134                   if not Is_Type (E) then
1135                      Error_Msg_N ("aspect% can only apply to a type", Id);
1136                      goto Continue;
1137
1138                   elsif not Is_First_Subtype (E) then
1139                      Error_Msg_N ("aspect% cannot apply to subtype", Id);
1140                      goto Continue;
1141
1142                   elsif A_Id = Aspect_Default_Value
1143                     and then not Is_Scalar_Type (E)
1144                   then
1145                      Error_Msg_N
1146                        ("aspect% can only be applied to scalar type", Id);
1147                      goto Continue;
1148
1149                   elsif A_Id = Aspect_Default_Component_Value then
1150                      if not Is_Array_Type (E) then
1151                         Error_Msg_N
1152                           ("aspect% can only be applied to array type", Id);
1153                         goto Continue;
1154                      elsif not Is_Scalar_Type (Component_Type (E)) then
1155                         Error_Msg_N
1156                           ("aspect% requires scalar components", Id);
1157                         goto Continue;
1158                      end if;
1159                   end if;
1160
1161                   Aitem := Empty;
1162                   Delay_Required := True;
1163                   Set_Is_Delayed_Aspect (Aspect);
1164                   Set_Has_Default_Aspect (Base_Type (Entity (Ent)));
1165
1166                when Aspect_Attach_Handler =>
1167                   Aitem :=
1168                     Make_Pragma (Loc,
1169                       Pragma_Identifier            =>
1170                         Make_Identifier (Sloc (Id), Name_Attach_Handler),
1171                       Pragma_Argument_Associations =>
1172                         New_List (Ent, Relocate_Node (Expr)));
1173
1174                   Set_From_Aspect_Specification (Aitem, True);
1175                   Set_Corresponding_Aspect (Aitem, Aspect);
1176
1177                   pragma Assert (not Delay_Required);
1178
1179                when Aspect_Priority           |
1180                     Aspect_Interrupt_Priority |
1181                     Aspect_Dispatching_Domain |
1182                     Aspect_CPU                =>
1183                   declare
1184                      Pname : Name_Id;
1185
1186                   begin
1187                      if A_Id = Aspect_Priority then
1188                         Pname := Name_Priority;
1189
1190                      elsif A_Id = Aspect_Interrupt_Priority then
1191                         Pname := Name_Interrupt_Priority;
1192
1193                      elsif A_Id = Aspect_CPU then
1194                         Pname := Name_CPU;
1195
1196                      else
1197                         Pname := Name_Dispatching_Domain;
1198                      end if;
1199
1200                      Aitem :=
1201                        Make_Pragma (Loc,
1202                            Pragma_Identifier            =>
1203                              Make_Identifier (Sloc (Id), Pname),
1204                            Pragma_Argument_Associations =>
1205                              New_List
1206                                (Make_Pragma_Argument_Association
1207                                   (Sloc       => Sloc (Id),
1208                                    Expression => Relocate_Node (Expr))));
1209
1210                      Set_From_Aspect_Specification (Aitem, True);
1211                      Set_Corresponding_Aspect (Aitem, Aspect);
1212
1213                      pragma Assert (not Delay_Required);
1214                   end;
1215
1216                --  Aspects Pre/Post generate Precondition/Postcondition pragmas
1217                --  with a first argument that is the expression, and a second
1218                --  argument that is an informative message if the test fails.
1219                --  This is inserted right after the declaration, to get the
1220                --  required pragma placement. The processing for the pragmas
1221                --  takes care of the required delay.
1222
1223                when Pre_Post_Aspects => declare
1224                   Pname : Name_Id;
1225
1226                begin
1227                   if A_Id = Aspect_Pre or else A_Id = Aspect_Precondition then
1228                      Pname := Name_Precondition;
1229                   else
1230                      Pname := Name_Postcondition;
1231                   end if;
1232
1233                   --  If the expressions is of the form A and then B, then
1234                   --  we generate separate Pre/Post aspects for the separate
1235                   --  clauses. Since we allow multiple pragmas, there is no
1236                   --  problem in allowing multiple Pre/Post aspects internally.
1237                   --  These should be treated in reverse order (B first and
1238                   --  A second) since they are later inserted just after N in
1239                   --  the order they are treated. This way, the pragma for A
1240                   --  ends up preceding the pragma for B, which may have an
1241                   --  importance for the error raised (either constraint error
1242                   --  or precondition error).
1243
1244                   --  We do not do this for Pre'Class, since we have to put
1245                   --  these conditions together in a complex OR expression
1246
1247                   --  We do not do this in ASIS mode, as ASIS relies on the
1248                   --  original node representing the complete expression, when
1249                   --  retrieving it through the source aspect table.
1250
1251                   if not ASIS_Mode
1252                     and then (Pname = Name_Postcondition
1253                                or else not Class_Present (Aspect))
1254                   then
1255                      while Nkind (Expr) = N_And_Then loop
1256                         Insert_After (Aspect,
1257                           Make_Aspect_Specification (Sloc (Left_Opnd (Expr)),
1258                             Identifier    => Identifier (Aspect),
1259                             Expression    => Relocate_Node (Left_Opnd (Expr)),
1260                             Class_Present => Class_Present (Aspect),
1261                             Split_PPC     => True));
1262                         Rewrite (Expr, Relocate_Node (Right_Opnd (Expr)));
1263                         Eloc := Sloc (Expr);
1264                      end loop;
1265                   end if;
1266
1267                   --  Build the precondition/postcondition pragma
1268
1269                   Aitem :=
1270                     Make_Pragma (Loc,
1271                       Pragma_Identifier            =>
1272                         Make_Identifier (Sloc (Id), Pname),
1273                       Class_Present                => Class_Present (Aspect),
1274                       Split_PPC                    => Split_PPC (Aspect),
1275                       Pragma_Argument_Associations => New_List (
1276                         Make_Pragma_Argument_Association (Eloc,
1277                           Chars      => Name_Check,
1278                           Expression => Relocate_Node (Expr))));
1279
1280                   --  Add message unless exception messages are suppressed
1281
1282                   if not Opt.Exception_Locations_Suppressed then
1283                      Append_To (Pragma_Argument_Associations (Aitem),
1284                        Make_Pragma_Argument_Association (Eloc,
1285                          Chars     => Name_Message,
1286                          Expression =>
1287                            Make_String_Literal (Eloc,
1288                              Strval => "failed "
1289                                        & Get_Name_String (Pname)
1290                                        & " from "
1291                                        & Build_Location_String (Eloc))));
1292                   end if;
1293
1294                   Set_From_Aspect_Specification (Aitem, True);
1295                   Set_Corresponding_Aspect (Aitem, Aspect);
1296                   Set_Is_Delayed_Aspect (Aspect);
1297
1298                   --  For Pre/Post cases, insert immediately after the entity
1299                   --  declaration, since that is the required pragma placement.
1300                   --  Note that for these aspects, we do not have to worry
1301                   --  about delay issues, since the pragmas themselves deal
1302                   --  with delay of visibility for the expression analysis.
1303
1304                   --  If the entity is a library-level subprogram, the pre/
1305                   --  postconditions must be treated as late pragmas.
1306
1307                   if Nkind (Parent (N)) = N_Compilation_Unit then
1308                      Add_Global_Declaration (Aitem);
1309                   else
1310                      Insert_After (N, Aitem);
1311                   end if;
1312
1313                   goto Continue;
1314                end;
1315
1316                --  Invariant aspects generate a corresponding pragma with a
1317                --  first argument that is the entity, a second argument that is
1318                --  the expression and a third argument that is an appropriate
1319                --  message. This is inserted right after the declaration, to
1320                --  get the required pragma placement. The pragma processing
1321                --  takes care of the required delay.
1322
1323                when Aspect_Invariant      |
1324                     Aspect_Type_Invariant =>
1325
1326                   --  Analysis of the pragma will verify placement legality:
1327                   --  an invariant must apply to a private type, or appear in
1328                   --  the private part of a spec and apply to a completion.
1329
1330                   --  Construct the pragma
1331
1332                   Aitem :=
1333                     Make_Pragma (Loc,
1334                       Pragma_Argument_Associations =>
1335                         New_List (Ent, Relocate_Node (Expr)),
1336                       Class_Present                => Class_Present (Aspect),
1337                       Pragma_Identifier            =>
1338                         Make_Identifier (Sloc (Id), Name_Invariant));
1339
1340                   --  Add message unless exception messages are suppressed
1341
1342                   if not Opt.Exception_Locations_Suppressed then
1343                      Append_To (Pragma_Argument_Associations (Aitem),
1344                        Make_Pragma_Argument_Association (Eloc,
1345                          Chars      => Name_Message,
1346                          Expression =>
1347                            Make_String_Literal (Eloc,
1348                              Strval => "failed invariant from "
1349                                        & Build_Location_String (Eloc))));
1350                   end if;
1351
1352                   Set_From_Aspect_Specification (Aitem, True);
1353                   Set_Corresponding_Aspect (Aitem, Aspect);
1354                   Set_Is_Delayed_Aspect (Aspect);
1355
1356                   --  For Invariant case, insert immediately after the entity
1357                   --  declaration. We do not have to worry about delay issues
1358                   --  since the pragma processing takes care of this.
1359
1360                   Insert_After (N, Aitem);
1361                   goto Continue;
1362
1363                --  Predicate aspects generate a corresponding pragma with a
1364                --  first argument that is the entity, and the second argument
1365                --  is the expression.
1366
1367                when Aspect_Dynamic_Predicate |
1368                     Aspect_Predicate         |
1369                     Aspect_Static_Predicate  =>
1370
1371                   --  Construct the pragma (always a pragma Predicate, with
1372                   --  flags recording whether it is static/dynamic).
1373
1374                   Aitem :=
1375                     Make_Pragma (Loc,
1376                       Pragma_Argument_Associations =>
1377                         New_List (Ent, Relocate_Node (Expr)),
1378                       Class_Present                => Class_Present (Aspect),
1379                       Pragma_Identifier            =>
1380                         Make_Identifier (Sloc (Id), Name_Predicate));
1381
1382                   Set_From_Aspect_Specification (Aitem, True);
1383                   Set_Corresponding_Aspect (Aitem, Aspect);
1384
1385                   --  Make sure we have a freeze node (it might otherwise be
1386                   --  missing in cases like subtype X is Y, and we would not
1387                   --  have a place to build the predicate function).
1388
1389                   Set_Has_Predicates (E);
1390
1391                   if Is_Private_Type (E)
1392                     and then Present (Full_View (E))
1393                   then
1394                      Set_Has_Predicates (Full_View (E));
1395                      Set_Has_Delayed_Aspects (Full_View (E));
1396                   end if;
1397
1398                   Ensure_Freeze_Node (E);
1399                   Set_Is_Delayed_Aspect (Aspect);
1400                   Delay_Required := True;
1401
1402                when Aspect_Test_Case => declare
1403                   Args      : List_Id;
1404                   Comp_Expr : Node_Id;
1405                   Comp_Assn : Node_Id;
1406                   New_Expr  : Node_Id;
1407
1408                begin
1409                   Args := New_List;
1410
1411                   if Nkind (Parent (N)) = N_Compilation_Unit then
1412                      Error_Msg_N
1413                        ("incorrect placement of aspect `Test_Case`", E);
1414                      goto Continue;
1415                   end if;
1416
1417                   if Nkind (Expr) /= N_Aggregate then
1418                      Error_Msg_NE
1419                        ("wrong syntax for aspect `Test_Case` for &", Id, E);
1420                      goto Continue;
1421                   end if;
1422
1423                   --  Make pragma expressions refer to the original aspect
1424                   --  expressions through the Original_Node link. This is used
1425                   --  in semantic analysis for ASIS mode, so that the original
1426                   --  expression also gets analyzed.
1427
1428                   Comp_Expr := First (Expressions (Expr));
1429                   while Present (Comp_Expr) loop
1430                      New_Expr := Relocate_Node (Comp_Expr);
1431                      Set_Original_Node (New_Expr, Comp_Expr);
1432                      Append
1433                        (Make_Pragma_Argument_Association (Sloc (Comp_Expr),
1434                           Expression => New_Expr),
1435                        Args);
1436                      Next (Comp_Expr);
1437                   end loop;
1438
1439                   Comp_Assn := First (Component_Associations (Expr));
1440                   while Present (Comp_Assn) loop
1441                      if List_Length (Choices (Comp_Assn)) /= 1
1442                        or else
1443                          Nkind (First (Choices (Comp_Assn))) /= N_Identifier
1444                      then
1445                         Error_Msg_NE
1446                           ("wrong syntax for aspect `Test_Case` for &", Id, E);
1447                         goto Continue;
1448                      end if;
1449
1450                      New_Expr := Relocate_Node (Expression (Comp_Assn));
1451                      Set_Original_Node (New_Expr, Expression (Comp_Assn));
1452                      Append (Make_Pragma_Argument_Association (
1453                        Sloc       => Sloc (Comp_Assn),
1454                        Chars      => Chars (First (Choices (Comp_Assn))),
1455                        Expression => New_Expr),
1456                        Args);
1457                      Next (Comp_Assn);
1458                   end loop;
1459
1460                   --  Build the test-case pragma
1461
1462                   Aitem :=
1463                     Make_Pragma (Loc,
1464                       Pragma_Identifier            =>
1465                         Make_Identifier (Sloc (Id), Name_Test_Case),
1466                       Pragma_Argument_Associations =>
1467                         Args);
1468
1469                   Set_From_Aspect_Specification (Aitem, True);
1470                   Set_Corresponding_Aspect (Aitem, Aspect);
1471                   Set_Is_Delayed_Aspect (Aspect);
1472
1473                   --  Insert immediately after the entity declaration
1474
1475                   Insert_After (N, Aitem);
1476
1477                   goto Continue;
1478                end;
1479             end case;
1480
1481             --  If a delay is required, we delay the freeze (not much point in
1482             --  delaying the aspect if we don't delay the freeze!). The pragma
1483             --  or attribute clause if there is one is then attached to the
1484             --  aspect specification which is placed in the rep item list.
1485
1486             if Delay_Required then
1487                if Present (Aitem) then
1488                   Set_From_Aspect_Specification (Aitem, True);
1489
1490                   if Nkind (Aitem) = N_Pragma then
1491                      Set_Corresponding_Aspect (Aitem, Aspect);
1492                   end if;
1493
1494                   Set_Is_Delayed_Aspect (Aitem);
1495                   Set_Aspect_Rep_Item (Aspect, Aitem);
1496                end if;
1497
1498                Ensure_Freeze_Node (E);
1499                Set_Has_Delayed_Aspects (E);
1500                Record_Rep_Item (E, Aspect);
1501
1502             --  If no delay required, insert the pragma/clause in the tree
1503
1504             else
1505                Set_From_Aspect_Specification (Aitem, True);
1506
1507                if Nkind (Aitem) = N_Pragma then
1508                   Set_Corresponding_Aspect (Aitem, Aspect);
1509                end if;
1510
1511                --  If this is a compilation unit, we will put the pragma in
1512                --  the Pragmas_After list of the N_Compilation_Unit_Aux node.
1513
1514                if Nkind (Parent (Ins_Node)) = N_Compilation_Unit then
1515                   declare
1516                      Aux : constant Node_Id :=
1517                              Aux_Decls_Node (Parent (Ins_Node));
1518
1519                   begin
1520                      pragma Assert (Nkind (Aux) = N_Compilation_Unit_Aux);
1521
1522                      if No (Pragmas_After (Aux)) then
1523                         Set_Pragmas_After (Aux, Empty_List);
1524                      end if;
1525
1526                      --  For Pre_Post put at start of list, otherwise at end
1527
1528                      if A_Id in Pre_Post_Aspects then
1529                         Prepend (Aitem, Pragmas_After (Aux));
1530                      else
1531                         Append (Aitem, Pragmas_After (Aux));
1532                      end if;
1533                   end;
1534
1535                --  Here if not compilation unit case
1536
1537                else
1538                   case A_Id is
1539
1540                      --  For Pre/Post cases, insert immediately after the
1541                      --  entity declaration, since that is the required pragma
1542                      --  placement.
1543
1544                      when Pre_Post_Aspects =>
1545                         Insert_After (N, Aitem);
1546
1547                      --  For Priority aspects, insert into the task or
1548                      --  protected definition, which we need to create if it's
1549                      --  not there. The same applies to CPU and
1550                      --  Dispatching_Domain but only to tasks.
1551
1552                      when Aspect_Priority           |
1553                           Aspect_Interrupt_Priority |
1554                           Aspect_Dispatching_Domain |
1555                           Aspect_CPU                =>
1556                         declare
1557                            T : Node_Id; -- the type declaration
1558                            L : List_Id; -- list of decls of task/protected
1559
1560                         begin
1561                            if Nkind (N) = N_Object_Declaration then
1562                               T := Parent (Etype (Defining_Identifier (N)));
1563                            else
1564                               T := N;
1565                            end if;
1566
1567                            if Nkind (T) = N_Protected_Type_Declaration
1568                              and then A_Id /= Aspect_Dispatching_Domain
1569                              and then A_Id /= Aspect_CPU
1570                            then
1571                               pragma Assert
1572                                 (Present (Protected_Definition (T)));
1573
1574                               L := Visible_Declarations
1575                                      (Protected_Definition (T));
1576
1577                            elsif Nkind (T) = N_Task_Type_Declaration then
1578                               if No (Task_Definition (T)) then
1579                                  Set_Task_Definition
1580                                    (T,
1581                                     Make_Task_Definition
1582                                       (Sloc (T),
1583                                        Visible_Declarations => New_List,
1584                                        End_Label => Empty));
1585                               end if;
1586
1587                               L := Visible_Declarations (Task_Definition (T));
1588
1589                            else
1590                               raise Program_Error;
1591                            end if;
1592
1593                            Prepend (Aitem, To => L);
1594
1595                            --  Analyze rewritten pragma. Otherwise, its
1596                            --  analysis is done too late, after the task or
1597                            --  protected object has been created.
1598
1599                            Analyze (Aitem);
1600                         end;
1601
1602                      --  For all other cases, insert in sequence
1603
1604                      when others =>
1605                         Insert_After (Ins_Node, Aitem);
1606                         Ins_Node := Aitem;
1607                   end case;
1608                end if;
1609             end if;
1610          end;
1611
1612       <<Continue>>
1613          Next (Aspect);
1614       end loop Aspect_Loop;
1615    end Analyze_Aspect_Specifications;
1616
1617    -----------------------
1618    -- Analyze_At_Clause --
1619    -----------------------
1620
1621    --  An at clause is replaced by the corresponding Address attribute
1622    --  definition clause that is the preferred approach in Ada 95.
1623
1624    procedure Analyze_At_Clause (N : Node_Id) is
1625       CS : constant Boolean := Comes_From_Source (N);
1626
1627    begin
1628       --  This is an obsolescent feature
1629
1630       Check_Restriction (No_Obsolescent_Features, N);
1631
1632       if Warn_On_Obsolescent_Feature then
1633          Error_Msg_N
1634            ("at clause is an obsolescent feature (RM J.7(2))?", N);
1635          Error_Msg_N
1636            ("\use address attribute definition clause instead?", N);
1637       end if;
1638
1639       --  Rewrite as address clause
1640
1641       Rewrite (N,
1642         Make_Attribute_Definition_Clause (Sloc (N),
1643           Name  => Identifier (N),
1644           Chars => Name_Address,
1645           Expression => Expression (N)));
1646
1647       --  We preserve Comes_From_Source, since logically the clause still
1648       --  comes from the source program even though it is changed in form.
1649
1650       Set_Comes_From_Source (N, CS);
1651
1652       --  Analyze rewritten clause
1653
1654       Analyze_Attribute_Definition_Clause (N);
1655    end Analyze_At_Clause;
1656
1657    -----------------------------------------
1658    -- Analyze_Attribute_Definition_Clause --
1659    -----------------------------------------
1660
1661    procedure Analyze_Attribute_Definition_Clause (N : Node_Id) is
1662       Loc   : constant Source_Ptr   := Sloc (N);
1663       Nam   : constant Node_Id      := Name (N);
1664       Attr  : constant Name_Id      := Chars (N);
1665       Expr  : constant Node_Id      := Expression (N);
1666       Id    : constant Attribute_Id := Get_Attribute_Id (Attr);
1667
1668       Ent : Entity_Id;
1669       --  The entity of Nam after it is analyzed. In the case of an incomplete
1670       --  type, this is the underlying type.
1671
1672       U_Ent : Entity_Id;
1673       --  The underlying entity to which the attribute applies. Generally this
1674       --  is the Underlying_Type of Ent, except in the case where the clause
1675       --  applies to full view of incomplete type or private type in which case
1676       --  U_Ent is just a copy of Ent.
1677
1678       FOnly : Boolean := False;
1679       --  Reset to True for subtype specific attribute (Alignment, Size)
1680       --  and for stream attributes, i.e. those cases where in the call
1681       --  to Rep_Item_Too_Late, FOnly is set True so that only the freezing
1682       --  rules are checked. Note that the case of stream attributes is not
1683       --  clear from the RM, but see AI95-00137. Also, the RM seems to
1684       --  disallow Storage_Size for derived task types, but that is also
1685       --  clearly unintentional.
1686
1687       procedure Analyze_Stream_TSS_Definition (TSS_Nam : TSS_Name_Type);
1688       --  Common processing for 'Read, 'Write, 'Input and 'Output attribute
1689       --  definition clauses.
1690
1691       function Duplicate_Clause return Boolean;
1692       --  This routine checks if the aspect for U_Ent being given by attribute
1693       --  definition clause N is for an aspect that has already been specified,
1694       --  and if so gives an error message. If there is a duplicate, True is
1695       --  returned, otherwise if there is no error, False is returned.
1696
1697       procedure Check_Indexing_Functions;
1698       --  Check that the function in Constant_Indexing or Variable_Indexing
1699       --  attribute has the proper type structure. If the name is overloaded,
1700       --  check that all interpretations are legal.
1701
1702       procedure Check_Iterator_Functions;
1703       --  Check that there is a single function in Default_Iterator attribute
1704       --  has the proper type structure.
1705
1706       function Check_Primitive_Function (Subp : Entity_Id) return Boolean;
1707       --  Common legality check for the previous two
1708
1709       -----------------------------------
1710       -- Analyze_Stream_TSS_Definition --
1711       -----------------------------------
1712
1713       procedure Analyze_Stream_TSS_Definition (TSS_Nam : TSS_Name_Type) is
1714          Subp : Entity_Id := Empty;
1715          I    : Interp_Index;
1716          It   : Interp;
1717          Pnam : Entity_Id;
1718
1719          Is_Read : constant Boolean := (TSS_Nam = TSS_Stream_Read);
1720          --  True for Read attribute, false for other attributes
1721
1722          function Has_Good_Profile (Subp : Entity_Id) return Boolean;
1723          --  Return true if the entity is a subprogram with an appropriate
1724          --  profile for the attribute being defined.
1725
1726          ----------------------
1727          -- Has_Good_Profile --
1728          ----------------------
1729
1730          function Has_Good_Profile (Subp : Entity_Id) return Boolean is
1731             F              : Entity_Id;
1732             Is_Function    : constant Boolean := (TSS_Nam = TSS_Stream_Input);
1733             Expected_Ekind : constant array (Boolean) of Entity_Kind :=
1734                                (False => E_Procedure, True => E_Function);
1735             Typ            : Entity_Id;
1736
1737          begin
1738             if Ekind (Subp) /= Expected_Ekind (Is_Function) then
1739                return False;
1740             end if;
1741
1742             F := First_Formal (Subp);
1743
1744             if No (F)
1745               or else Ekind (Etype (F)) /= E_Anonymous_Access_Type
1746               or else Designated_Type (Etype (F)) /=
1747                                Class_Wide_Type (RTE (RE_Root_Stream_Type))
1748             then
1749                return False;
1750             end if;
1751
1752             if not Is_Function then
1753                Next_Formal (F);
1754
1755                declare
1756                   Expected_Mode : constant array (Boolean) of Entity_Kind :=
1757                                     (False => E_In_Parameter,
1758                                      True  => E_Out_Parameter);
1759                begin
1760                   if Parameter_Mode (F) /= Expected_Mode (Is_Read) then
1761                      return False;
1762                   end if;
1763                end;
1764
1765                Typ := Etype (F);
1766
1767             else
1768                Typ := Etype (Subp);
1769             end if;
1770
1771             return Base_Type (Typ) = Base_Type (Ent)
1772               and then No (Next_Formal (F));
1773          end Has_Good_Profile;
1774
1775       --  Start of processing for Analyze_Stream_TSS_Definition
1776
1777       begin
1778          FOnly := True;
1779
1780          if not Is_Type (U_Ent) then
1781             Error_Msg_N ("local name must be a subtype", Nam);
1782             return;
1783          end if;
1784
1785          Pnam := TSS (Base_Type (U_Ent), TSS_Nam);
1786
1787          --  If Pnam is present, it can be either inherited from an ancestor
1788          --  type (in which case it is legal to redefine it for this type), or
1789          --  be a previous definition of the attribute for the same type (in
1790          --  which case it is illegal).
1791
1792          --  In the first case, it will have been analyzed already, and we
1793          --  can check that its profile does not match the expected profile
1794          --  for a stream attribute of U_Ent. In the second case, either Pnam
1795          --  has been analyzed (and has the expected profile), or it has not
1796          --  been analyzed yet (case of a type that has not been frozen yet
1797          --  and for which the stream attribute has been set using Set_TSS).
1798
1799          if Present (Pnam)
1800            and then (No (First_Entity (Pnam)) or else Has_Good_Profile (Pnam))
1801          then
1802             Error_Msg_Sloc := Sloc (Pnam);
1803             Error_Msg_Name_1 := Attr;
1804             Error_Msg_N ("% attribute already defined #", Nam);
1805             return;
1806          end if;
1807
1808          Analyze (Expr);
1809
1810          if Is_Entity_Name (Expr) then
1811             if not Is_Overloaded (Expr) then
1812                if Has_Good_Profile (Entity (Expr)) then
1813                   Subp := Entity (Expr);
1814                end if;
1815
1816             else
1817                Get_First_Interp (Expr, I, It);
1818                while Present (It.Nam) loop
1819                   if Has_Good_Profile (It.Nam) then
1820                      Subp := It.Nam;
1821                      exit;
1822                   end if;
1823
1824                   Get_Next_Interp (I, It);
1825                end loop;
1826             end if;
1827          end if;
1828
1829          if Present (Subp) then
1830             if Is_Abstract_Subprogram (Subp) then
1831                Error_Msg_N ("stream subprogram must not be abstract", Expr);
1832                return;
1833             end if;
1834
1835             Set_Entity (Expr, Subp);
1836             Set_Etype (Expr, Etype (Subp));
1837
1838             New_Stream_Subprogram (N, U_Ent, Subp, TSS_Nam);
1839
1840          else
1841             Error_Msg_Name_1 := Attr;
1842             Error_Msg_N ("incorrect expression for% attribute", Expr);
1843          end if;
1844       end Analyze_Stream_TSS_Definition;
1845
1846       ------------------------------
1847       -- Check_Indexing_Functions --
1848       ------------------------------
1849
1850       procedure Check_Indexing_Functions is
1851
1852          procedure Check_One_Function (Subp : Entity_Id);
1853          --  Check one possible interpretation
1854
1855          ------------------------
1856          -- Check_One_Function --
1857          ------------------------
1858
1859          procedure Check_One_Function (Subp : Entity_Id) is
1860          begin
1861             if not Check_Primitive_Function (Subp) then
1862                Error_Msg_NE
1863                  ("aspect Indexing requires a function that applies to type&",
1864                    Subp, Ent);
1865             end if;
1866
1867             if not Has_Implicit_Dereference (Etype (Subp)) then
1868                Error_Msg_N
1869                  ("function for indexing must return a reference type", Subp);
1870             end if;
1871          end Check_One_Function;
1872
1873       --  Start of processing for Check_Indexing_Functions
1874
1875       begin
1876          if In_Instance then
1877             return;
1878          end if;
1879
1880          Analyze (Expr);
1881
1882          if not Is_Overloaded (Expr) then
1883             Check_One_Function (Entity (Expr));
1884
1885          else
1886             declare
1887                I : Interp_Index;
1888                It : Interp;
1889
1890             begin
1891                Get_First_Interp (Expr, I, It);
1892                while Present (It.Nam) loop
1893
1894                   --  Note that analysis will have added the interpretation
1895                   --  that corresponds to the dereference. We only check the
1896                   --  subprogram itself.
1897
1898                   if Is_Overloadable (It.Nam) then
1899                      Check_One_Function (It.Nam);
1900                   end if;
1901
1902                   Get_Next_Interp (I, It);
1903                end loop;
1904             end;
1905          end if;
1906       end Check_Indexing_Functions;
1907
1908       ------------------------------
1909       -- Check_Iterator_Functions --
1910       ------------------------------
1911
1912       procedure Check_Iterator_Functions is
1913          Default : Entity_Id;
1914
1915          function Valid_Default_Iterator (Subp : Entity_Id) return Boolean;
1916          --  Check one possible interpretation for validity
1917
1918          ----------------------------
1919          -- Valid_Default_Iterator --
1920          ----------------------------
1921
1922          function Valid_Default_Iterator (Subp : Entity_Id) return Boolean is
1923             Formal : Entity_Id;
1924
1925          begin
1926             if not Check_Primitive_Function (Subp) then
1927                return False;
1928             else
1929                Formal := First_Formal (Subp);
1930             end if;
1931
1932             --  False if any subsequent formal has no default expression
1933
1934             Formal := Next_Formal (Formal);
1935             while Present (Formal) loop
1936                if No (Expression (Parent (Formal))) then
1937                   return False;
1938                end if;
1939
1940                Next_Formal (Formal);
1941             end loop;
1942
1943             --  True if all subsequent formals have default expressions
1944
1945             return True;
1946          end Valid_Default_Iterator;
1947
1948       --  Start of processing for Check_Iterator_Functions
1949
1950       begin
1951          Analyze (Expr);
1952
1953          if not Is_Entity_Name (Expr) then
1954             Error_Msg_N ("aspect Iterator must be a function name", Expr);
1955          end if;
1956
1957          if not Is_Overloaded (Expr) then
1958             if not Check_Primitive_Function (Entity (Expr)) then
1959                Error_Msg_NE
1960                  ("aspect Indexing requires a function that applies to type&",
1961                    Entity (Expr), Ent);
1962             end if;
1963
1964             if not Valid_Default_Iterator (Entity (Expr)) then
1965                Error_Msg_N ("improper function for default iterator", Expr);
1966             end if;
1967
1968          else
1969             Default := Empty;
1970             declare
1971                I : Interp_Index;
1972                It : Interp;
1973
1974             begin
1975                Get_First_Interp (Expr, I, It);
1976                while Present (It.Nam) loop
1977                   if not Check_Primitive_Function (It.Nam)
1978                     or else not Valid_Default_Iterator (It.Nam)
1979                   then
1980                      Remove_Interp (I);
1981
1982                   elsif Present (Default) then
1983                      Error_Msg_N ("default iterator must be unique", Expr);
1984
1985                   else
1986                      Default := It.Nam;
1987                   end if;
1988
1989                   Get_Next_Interp (I, It);
1990                end loop;
1991             end;
1992
1993             if Present (Default) then
1994                Set_Entity (Expr, Default);
1995                Set_Is_Overloaded (Expr, False);
1996             end if;
1997          end if;
1998       end Check_Iterator_Functions;
1999
2000       -------------------------------
2001       -- Check_Primitive_Function  --
2002       -------------------------------
2003
2004       function Check_Primitive_Function (Subp : Entity_Id) return Boolean is
2005          Ctrl : Entity_Id;
2006
2007       begin
2008          if Ekind (Subp) /= E_Function then
2009             return False;
2010          end if;
2011
2012          if No (First_Formal (Subp)) then
2013             return False;
2014          else
2015             Ctrl := Etype (First_Formal (Subp));
2016          end if;
2017
2018          if Ctrl = Ent
2019            or else Ctrl = Class_Wide_Type (Ent)
2020            or else
2021              (Ekind (Ctrl) = E_Anonymous_Access_Type
2022                and then
2023                  (Designated_Type (Ctrl) = Ent
2024                    or else Designated_Type (Ctrl) = Class_Wide_Type (Ent)))
2025          then
2026             null;
2027
2028          else
2029             return False;
2030          end if;
2031
2032          return True;
2033       end Check_Primitive_Function;
2034
2035       ----------------------
2036       -- Duplicate_Clause --
2037       ----------------------
2038
2039       function Duplicate_Clause return Boolean is
2040          A : Node_Id;
2041
2042       begin
2043          --  Nothing to do if this attribute definition clause comes from
2044          --  an aspect specification, since we could not be duplicating an
2045          --  explicit clause, and we dealt with the case of duplicated aspects
2046          --  in Analyze_Aspect_Specifications.
2047
2048          if From_Aspect_Specification (N) then
2049             return False;
2050          end if;
2051
2052          --  Otherwise current clause may duplicate previous clause or a
2053          --  previously given aspect specification for the same aspect.
2054
2055          A := Get_Rep_Item_For_Entity (U_Ent, Chars (N));
2056
2057          if Present (A) then
2058             if Entity (A) = U_Ent then
2059                Error_Msg_Name_1 := Chars (N);
2060                Error_Msg_Sloc := Sloc (A);
2061                Error_Msg_NE ("aspect% for & previously given#", N, U_Ent);
2062                return True;
2063             end if;
2064          end if;
2065
2066          return False;
2067       end Duplicate_Clause;
2068
2069    --  Start of processing for Analyze_Attribute_Definition_Clause
2070
2071    begin
2072       --  The following code is a defense against recursion. Not clear that
2073       --  this can happen legitimately, but perhaps some error situations
2074       --  can cause it, and we did see this recursion during testing.
2075
2076       if Analyzed (N) then
2077          return;
2078       else
2079          Set_Analyzed (N, True);
2080       end if;
2081
2082       --  Process Ignore_Rep_Clauses option (we also ignore rep clauses in
2083       --  CodePeer mode or Alfa mode, since they are not relevant in these
2084       --  contexts).
2085
2086       if Ignore_Rep_Clauses or CodePeer_Mode or Alfa_Mode then
2087          case Id is
2088
2089             --  The following should be ignored. They do not affect legality
2090             --  and may be target dependent. The basic idea of -gnatI is to
2091             --  ignore any rep clauses that may be target dependent but do not
2092             --  affect legality (except possibly to be rejected because they
2093             --  are incompatible with the compilation target).
2094
2095             when Attribute_Alignment      |
2096                  Attribute_Bit_Order      |
2097                  Attribute_Component_Size |
2098                  Attribute_Machine_Radix  |
2099                  Attribute_Object_Size    |
2100                  Attribute_Size           |
2101                  Attribute_Stream_Size    |
2102                  Attribute_Value_Size     =>
2103                Rewrite (N, Make_Null_Statement (Sloc (N)));
2104                return;
2105
2106             --  We do not want too ignore 'Small in CodePeer_Mode or Alfa_Mode,
2107             --  since it has an impact on the exact computations performed.
2108
2109             --  Perhaps 'Small should also not be ignored by
2110             --  Ignore_Rep_Clauses ???
2111
2112             when Attribute_Small =>
2113                if Ignore_Rep_Clauses then
2114                   Rewrite (N, Make_Null_Statement (Sloc (N)));
2115                   return;
2116                end if;
2117
2118             --  The following should not be ignored, because in the first place
2119             --  they are reasonably portable, and should not cause problems in
2120             --  compiling code from another target, and also they do affect
2121             --  legality, e.g. failing to provide a stream attribute for a
2122             --  type may make a program illegal.
2123
2124             when Attribute_External_Tag |
2125                  Attribute_Input        |
2126                  Attribute_Output       |
2127                  Attribute_Read         |
2128                  Attribute_Storage_Pool |
2129                  Attribute_Storage_Size |
2130                  Attribute_Write        =>
2131                null;
2132
2133             --  Other cases are errors ("attribute& cannot be set with
2134             --  definition clause"), which will be caught below.
2135
2136             when others =>
2137                null;
2138          end case;
2139       end if;
2140
2141       Analyze (Nam);
2142       Ent := Entity (Nam);
2143
2144       if Rep_Item_Too_Early (Ent, N) then
2145          return;
2146       end if;
2147
2148       --  Rep clause applies to full view of incomplete type or private type if
2149       --  we have one (if not, this is a premature use of the type). However,
2150       --  certain semantic checks need to be done on the specified entity (i.e.
2151       --  the private view), so we save it in Ent.
2152
2153       if Is_Private_Type (Ent)
2154         and then Is_Derived_Type (Ent)
2155         and then not Is_Tagged_Type (Ent)
2156         and then No (Full_View (Ent))
2157       then
2158          --  If this is a private type whose completion is a derivation from
2159          --  another private type, there is no full view, and the attribute
2160          --  belongs to the type itself, not its underlying parent.
2161
2162          U_Ent := Ent;
2163
2164       elsif Ekind (Ent) = E_Incomplete_Type then
2165
2166          --  The attribute applies to the full view, set the entity of the
2167          --  attribute definition accordingly.
2168
2169          Ent := Underlying_Type (Ent);
2170          U_Ent := Ent;
2171          Set_Entity (Nam, Ent);
2172
2173       else
2174          U_Ent := Underlying_Type (Ent);
2175       end if;
2176
2177       --  Complete other routine error checks
2178
2179       if Etype (Nam) = Any_Type then
2180          return;
2181
2182       elsif Scope (Ent) /= Current_Scope then
2183          Error_Msg_N ("entity must be declared in this scope", Nam);
2184          return;
2185
2186       elsif No (U_Ent) then
2187          U_Ent := Ent;
2188
2189       elsif Is_Type (U_Ent)
2190         and then not Is_First_Subtype (U_Ent)
2191         and then Id /= Attribute_Object_Size
2192         and then Id /= Attribute_Value_Size
2193         and then not From_At_Mod (N)
2194       then
2195          Error_Msg_N ("cannot specify attribute for subtype", Nam);
2196          return;
2197       end if;
2198
2199       Set_Entity (N, U_Ent);
2200
2201       --  Switch on particular attribute
2202
2203       case Id is
2204
2205          -------------
2206          -- Address --
2207          -------------
2208
2209          --  Address attribute definition clause
2210
2211          when Attribute_Address => Address : begin
2212
2213             --  A little error check, catch for X'Address use X'Address;
2214
2215             if Nkind (Nam) = N_Identifier
2216               and then Nkind (Expr) = N_Attribute_Reference
2217               and then Attribute_Name (Expr) = Name_Address
2218               and then Nkind (Prefix (Expr)) = N_Identifier
2219               and then Chars (Nam) = Chars (Prefix (Expr))
2220             then
2221                Error_Msg_NE
2222                  ("address for & is self-referencing", Prefix (Expr), Ent);
2223                return;
2224             end if;
2225
2226             --  Not that special case, carry on with analysis of expression
2227
2228             Analyze_And_Resolve (Expr, RTE (RE_Address));
2229
2230             --  Even when ignoring rep clauses we need to indicate that the
2231             --  entity has an address clause and thus it is legal to declare
2232             --  it imported.
2233
2234             if Ignore_Rep_Clauses then
2235                if Ekind_In (U_Ent, E_Variable, E_Constant) then
2236                   Record_Rep_Item (U_Ent, N);
2237                end if;
2238
2239                return;
2240             end if;
2241
2242             if Duplicate_Clause then
2243                null;
2244
2245             --  Case of address clause for subprogram
2246
2247             elsif Is_Subprogram (U_Ent) then
2248                if Has_Homonym (U_Ent) then
2249                   Error_Msg_N
2250                     ("address clause cannot be given " &
2251                      "for overloaded subprogram",
2252                      Nam);
2253                   return;
2254                end if;
2255
2256                --  For subprograms, all address clauses are permitted, and we
2257                --  mark the subprogram as having a deferred freeze so that Gigi
2258                --  will not elaborate it too soon.
2259
2260                --  Above needs more comments, what is too soon about???
2261
2262                Set_Has_Delayed_Freeze (U_Ent);
2263
2264             --  Case of address clause for entry
2265
2266             elsif Ekind (U_Ent) = E_Entry then
2267                if Nkind (Parent (N)) = N_Task_Body then
2268                   Error_Msg_N
2269                     ("entry address must be specified in task spec", Nam);
2270                   return;
2271                end if;
2272
2273                --  For entries, we require a constant address
2274
2275                Check_Constant_Address_Clause (Expr, U_Ent);
2276
2277                --  Special checks for task types
2278
2279                if Is_Task_Type (Scope (U_Ent))
2280                  and then Comes_From_Source (Scope (U_Ent))
2281                then
2282                   Error_Msg_N
2283                     ("?entry address declared for entry in task type", N);
2284                   Error_Msg_N
2285                     ("\?only one task can be declared of this type", N);
2286                end if;
2287
2288                --  Entry address clauses are obsolescent
2289
2290                Check_Restriction (No_Obsolescent_Features, N);
2291
2292                if Warn_On_Obsolescent_Feature then
2293                   Error_Msg_N
2294                     ("attaching interrupt to task entry is an " &
2295                      "obsolescent feature (RM J.7.1)?", N);
2296                   Error_Msg_N
2297                     ("\use interrupt procedure instead?", N);
2298                end if;
2299
2300             --  Case of an address clause for a controlled object which we
2301             --  consider to be erroneous.
2302
2303             elsif Is_Controlled (Etype (U_Ent))
2304               or else Has_Controlled_Component (Etype (U_Ent))
2305             then
2306                Error_Msg_NE
2307                  ("?controlled object& must not be overlaid", Nam, U_Ent);
2308                Error_Msg_N
2309                  ("\?Program_Error will be raised at run time", Nam);
2310                Insert_Action (Declaration_Node (U_Ent),
2311                  Make_Raise_Program_Error (Loc,
2312                    Reason => PE_Overlaid_Controlled_Object));
2313                return;
2314
2315             --  Case of address clause for a (non-controlled) object
2316
2317             elsif
2318               Ekind (U_Ent) = E_Variable
2319                 or else
2320               Ekind (U_Ent) = E_Constant
2321             then
2322                declare
2323                   Expr  : constant Node_Id := Expression (N);
2324                   O_Ent : Entity_Id;
2325                   Off   : Boolean;
2326
2327                begin
2328                   --  Exported variables cannot have an address clause, because
2329                   --  this cancels the effect of the pragma Export.
2330
2331                   if Is_Exported (U_Ent) then
2332                      Error_Msg_N
2333                        ("cannot export object with address clause", Nam);
2334                      return;
2335                   end if;
2336
2337                   Find_Overlaid_Entity (N, O_Ent, Off);
2338
2339                   --  Overlaying controlled objects is erroneous
2340
2341                   if Present (O_Ent)
2342                     and then (Has_Controlled_Component (Etype (O_Ent))
2343                                 or else Is_Controlled (Etype (O_Ent)))
2344                   then
2345                      Error_Msg_N
2346                        ("?cannot overlay with controlled object", Expr);
2347                      Error_Msg_N
2348                        ("\?Program_Error will be raised at run time", Expr);
2349                      Insert_Action (Declaration_Node (U_Ent),
2350                        Make_Raise_Program_Error (Loc,
2351                          Reason => PE_Overlaid_Controlled_Object));
2352                      return;
2353
2354                   elsif Present (O_Ent)
2355                     and then Ekind (U_Ent) = E_Constant
2356                     and then not Is_Constant_Object (O_Ent)
2357                   then
2358                      Error_Msg_N ("constant overlays a variable?", Expr);
2359
2360                   elsif Present (Renamed_Object (U_Ent)) then
2361                      Error_Msg_N
2362                        ("address clause not allowed"
2363                           & " for a renaming declaration (RM 13.1(6))", Nam);
2364                      return;
2365
2366                   --  Imported variables can have an address clause, but then
2367                   --  the import is pretty meaningless except to suppress
2368                   --  initializations, so we do not need such variables to
2369                   --  be statically allocated (and in fact it causes trouble
2370                   --  if the address clause is a local value).
2371
2372                   elsif Is_Imported (U_Ent) then
2373                      Set_Is_Statically_Allocated (U_Ent, False);
2374                   end if;
2375
2376                   --  We mark a possible modification of a variable with an
2377                   --  address clause, since it is likely aliasing is occurring.
2378
2379                   Note_Possible_Modification (Nam, Sure => False);
2380
2381                   --  Here we are checking for explicit overlap of one variable
2382                   --  by another, and if we find this then mark the overlapped
2383                   --  variable as also being volatile to prevent unwanted
2384                   --  optimizations. This is a significant pessimization so
2385                   --  avoid it when there is an offset, i.e. when the object
2386                   --  is composite; they cannot be optimized easily anyway.
2387
2388                   if Present (O_Ent)
2389                     and then Is_Object (O_Ent)
2390                     and then not Off
2391                   then
2392                      Set_Treat_As_Volatile (O_Ent);
2393                   end if;
2394
2395                   --  Legality checks on the address clause for initialized
2396                   --  objects is deferred until the freeze point, because
2397                   --  a subsequent pragma might indicate that the object is
2398                   --  imported and thus not initialized.
2399
2400                   Set_Has_Delayed_Freeze (U_Ent);
2401
2402                   --  If an initialization call has been generated for this
2403                   --  object, it needs to be deferred to after the freeze node
2404                   --  we have just now added, otherwise GIGI will see a
2405                   --  reference to the variable (as actual to the IP call)
2406                   --  before its definition.
2407
2408                   declare
2409                      Init_Call : constant Node_Id := Find_Init_Call (U_Ent, N);
2410                   begin
2411                      if Present (Init_Call) then
2412                         Remove (Init_Call);
2413                         Append_Freeze_Action (U_Ent, Init_Call);
2414                      end if;
2415                   end;
2416
2417                   if Is_Exported (U_Ent) then
2418                      Error_Msg_N
2419                        ("& cannot be exported if an address clause is given",
2420                         Nam);
2421                      Error_Msg_N
2422                        ("\define and export a variable " &
2423                         "that holds its address instead",
2424                         Nam);
2425                   end if;
2426
2427                   --  Entity has delayed freeze, so we will generate an
2428                   --  alignment check at the freeze point unless suppressed.
2429
2430                   if not Range_Checks_Suppressed (U_Ent)
2431                     and then not Alignment_Checks_Suppressed (U_Ent)
2432                   then
2433                      Set_Check_Address_Alignment (N);
2434                   end if;
2435
2436                   --  Kill the size check code, since we are not allocating
2437                   --  the variable, it is somewhere else.
2438
2439                   Kill_Size_Check_Code (U_Ent);
2440
2441                   --  If the address clause is of the form:
2442
2443                   --    for Y'Address use X'Address
2444
2445                   --  or
2446
2447                   --    Const : constant Address := X'Address;
2448                   --    ...
2449                   --    for Y'Address use Const;
2450
2451                   --  then we make an entry in the table for checking the size
2452                   --  and alignment of the overlaying variable. We defer this
2453                   --  check till after code generation to take full advantage
2454                   --  of the annotation done by the back end. This entry is
2455                   --  only made if the address clause comes from source.
2456
2457                   --  If the entity has a generic type, the check will be
2458                   --  performed in the instance if the actual type justifies
2459                   --  it, and we do not insert the clause in the table to
2460                   --  prevent spurious warnings.
2461
2462                   if Address_Clause_Overlay_Warnings
2463                     and then Comes_From_Source (N)
2464                     and then Present (O_Ent)
2465                     and then Is_Object (O_Ent)
2466                   then
2467                      if not Is_Generic_Type (Etype (U_Ent)) then
2468                         Address_Clause_Checks.Append ((N, U_Ent, O_Ent, Off));
2469                      end if;
2470
2471                      --  If variable overlays a constant view, and we are
2472                      --  warning on overlays, then mark the variable as
2473                      --  overlaying a constant (we will give warnings later
2474                      --  if this variable is assigned).
2475
2476                      if Is_Constant_Object (O_Ent)
2477                        and then Ekind (U_Ent) = E_Variable
2478                      then
2479                         Set_Overlays_Constant (U_Ent);
2480                      end if;
2481                   end if;
2482                end;
2483
2484             --  Not a valid entity for an address clause
2485
2486             else
2487                Error_Msg_N ("address cannot be given for &", Nam);
2488             end if;
2489          end Address;
2490
2491          ---------------
2492          -- Alignment --
2493          ---------------
2494
2495          --  Alignment attribute definition clause
2496
2497          when Attribute_Alignment => Alignment : declare
2498             Align     : constant Uint := Get_Alignment_Value (Expr);
2499             Max_Align : constant Uint := UI_From_Int (Maximum_Alignment);
2500
2501          begin
2502             FOnly := True;
2503
2504             if not Is_Type (U_Ent)
2505               and then Ekind (U_Ent) /= E_Variable
2506               and then Ekind (U_Ent) /= E_Constant
2507             then
2508                Error_Msg_N ("alignment cannot be given for &", Nam);
2509
2510             elsif Duplicate_Clause then
2511                null;
2512
2513             elsif Align /= No_Uint then
2514                Set_Has_Alignment_Clause (U_Ent);
2515
2516                if Is_Tagged_Type (U_Ent) and then Align > Max_Align then
2517                   Error_Msg_N
2518                     ("?alignment for & set to Maximum_Aligment", Nam);
2519                   Set_Alignment (U_Ent, Max_Align);
2520                else
2521                   Set_Alignment (U_Ent, Align);
2522                end if;
2523
2524                --  For an array type, U_Ent is the first subtype. In that case,
2525                --  also set the alignment of the anonymous base type so that
2526                --  other subtypes (such as the itypes for aggregates of the
2527                --  type) also receive the expected alignment.
2528
2529                if Is_Array_Type (U_Ent) then
2530                   Set_Alignment (Base_Type (U_Ent), Align);
2531                end if;
2532             end if;
2533          end Alignment;
2534
2535          ---------------
2536          -- Bit_Order --
2537          ---------------
2538
2539          --  Bit_Order attribute definition clause
2540
2541          when Attribute_Bit_Order => Bit_Order : declare
2542          begin
2543             if not Is_Record_Type (U_Ent) then
2544                Error_Msg_N
2545                  ("Bit_Order can only be defined for record type", Nam);
2546
2547             elsif Duplicate_Clause then
2548                null;
2549
2550             else
2551                Analyze_And_Resolve (Expr, RTE (RE_Bit_Order));
2552
2553                if Etype (Expr) = Any_Type then
2554                   return;
2555
2556                elsif not Is_Static_Expression (Expr) then
2557                   Flag_Non_Static_Expr
2558                     ("Bit_Order requires static expression!", Expr);
2559
2560                else
2561                   if (Expr_Value (Expr) = 0) /= Bytes_Big_Endian then
2562                      Set_Reverse_Bit_Order (U_Ent, True);
2563                   end if;
2564                end if;
2565             end if;
2566          end Bit_Order;
2567
2568          --------------------
2569          -- Component_Size --
2570          --------------------
2571
2572          --  Component_Size attribute definition clause
2573
2574          when Attribute_Component_Size => Component_Size_Case : declare
2575             Csize    : constant Uint := Static_Integer (Expr);
2576             Ctyp     : Entity_Id;
2577             Btype    : Entity_Id;
2578             Biased   : Boolean;
2579             New_Ctyp : Entity_Id;
2580             Decl     : Node_Id;
2581
2582          begin
2583             if not Is_Array_Type (U_Ent) then
2584                Error_Msg_N ("component size requires array type", Nam);
2585                return;
2586             end if;
2587
2588             Btype := Base_Type (U_Ent);
2589             Ctyp := Component_Type (Btype);
2590
2591             if Duplicate_Clause then
2592                null;
2593
2594             elsif Rep_Item_Too_Early (Btype, N) then
2595                null;
2596
2597             elsif Csize /= No_Uint then
2598                Check_Size (Expr, Ctyp, Csize, Biased);
2599
2600                --  For the biased case, build a declaration for a subtype that
2601                --  will be used to represent the biased subtype that reflects
2602                --  the biased representation of components. We need the subtype
2603                --  to get proper conversions on referencing elements of the
2604                --  array. Note: component size clauses are ignored in VM mode.
2605
2606                if VM_Target = No_VM then
2607                   if Biased then
2608                      New_Ctyp :=
2609                        Make_Defining_Identifier (Loc,
2610                          Chars =>
2611                            New_External_Name (Chars (U_Ent), 'C', 0, 'T'));
2612
2613                      Decl :=
2614                        Make_Subtype_Declaration (Loc,
2615                          Defining_Identifier => New_Ctyp,
2616                          Subtype_Indication  =>
2617                            New_Occurrence_Of (Component_Type (Btype), Loc));
2618
2619                      Set_Parent (Decl, N);
2620                      Analyze (Decl, Suppress => All_Checks);
2621
2622                      Set_Has_Delayed_Freeze        (New_Ctyp, False);
2623                      Set_Esize                     (New_Ctyp, Csize);
2624                      Set_RM_Size                   (New_Ctyp, Csize);
2625                      Init_Alignment                (New_Ctyp);
2626                      Set_Is_Itype                  (New_Ctyp, True);
2627                      Set_Associated_Node_For_Itype (New_Ctyp, U_Ent);
2628
2629                      Set_Component_Type (Btype, New_Ctyp);
2630                      Set_Biased (New_Ctyp, N, "component size clause");
2631                   end if;
2632
2633                   Set_Component_Size (Btype, Csize);
2634
2635                --  For VM case, we ignore component size clauses
2636
2637                else
2638                   --  Give a warning unless we are in GNAT mode, in which case
2639                   --  the warning is suppressed since it is not useful.
2640
2641                   if not GNAT_Mode then
2642                      Error_Msg_N
2643                        ("?component size ignored in this configuration", N);
2644                   end if;
2645                end if;
2646
2647                --  Deal with warning on overridden size
2648
2649                if Warn_On_Overridden_Size
2650                  and then Has_Size_Clause (Ctyp)
2651                  and then RM_Size (Ctyp) /= Csize
2652                then
2653                   Error_Msg_NE
2654                     ("?component size overrides size clause for&",
2655                      N, Ctyp);
2656                end if;
2657
2658                Set_Has_Component_Size_Clause (Btype, True);
2659                Set_Has_Non_Standard_Rep (Btype, True);
2660             end if;
2661          end Component_Size_Case;
2662
2663          -----------------------
2664          -- Constant_Indexing --
2665          -----------------------
2666
2667          when Attribute_Constant_Indexing =>
2668             Check_Indexing_Functions;
2669
2670          ----------------------
2671          -- Default_Iterator --
2672          ----------------------
2673
2674          when Attribute_Default_Iterator =>  Default_Iterator : declare
2675             Func : Entity_Id;
2676
2677          begin
2678             if not Is_Tagged_Type (U_Ent) then
2679                Error_Msg_N
2680                  ("aspect Default_Iterator applies to  tagged type", Nam);
2681             end if;
2682
2683             Check_Iterator_Functions;
2684
2685             Analyze (Expr);
2686
2687             if not Is_Entity_Name (Expr)
2688               or else Ekind (Entity (Expr)) /= E_Function
2689             then
2690                Error_Msg_N ("aspect Iterator must be a function", Expr);
2691             else
2692                Func := Entity (Expr);
2693             end if;
2694
2695             if No (First_Formal (Func))
2696               or else Etype (First_Formal (Func)) /= U_Ent
2697             then
2698                Error_Msg_NE
2699                  ("Default Iterator must be a primitive of&", Func, U_Ent);
2700             end if;
2701          end Default_Iterator;
2702
2703          ------------------
2704          -- External_Tag --
2705          ------------------
2706
2707          when Attribute_External_Tag => External_Tag :
2708          begin
2709             if not Is_Tagged_Type (U_Ent) then
2710                Error_Msg_N ("should be a tagged type", Nam);
2711             end if;
2712
2713             if Duplicate_Clause then
2714                null;
2715
2716             else
2717                Analyze_And_Resolve (Expr, Standard_String);
2718
2719                if not Is_Static_Expression (Expr) then
2720                   Flag_Non_Static_Expr
2721                     ("static string required for tag name!", Nam);
2722                end if;
2723
2724                if VM_Target = No_VM then
2725                   Set_Has_External_Tag_Rep_Clause (U_Ent);
2726                else
2727                   Error_Msg_Name_1 := Attr;
2728                   Error_Msg_N
2729                     ("% attribute unsupported in this configuration", Nam);
2730                end if;
2731
2732                if not Is_Library_Level_Entity (U_Ent) then
2733                   Error_Msg_NE
2734                     ("?non-unique external tag supplied for &", N, U_Ent);
2735                   Error_Msg_N
2736                     ("?\same external tag applies to all subprogram calls", N);
2737                   Error_Msg_N
2738                     ("?\corresponding internal tag cannot be obtained", N);
2739                end if;
2740             end if;
2741          end External_Tag;
2742
2743          --------------------------
2744          -- Implicit_Dereference --
2745          --------------------------
2746
2747          when Attribute_Implicit_Dereference =>
2748
2749             --  Legality checks already performed at the point of
2750             --  the type declaration, aspect is not delayed.
2751
2752             null;
2753
2754          -----------
2755          -- Input --
2756          -----------
2757
2758          when Attribute_Input =>
2759             Analyze_Stream_TSS_Definition (TSS_Stream_Input);
2760             Set_Has_Specified_Stream_Input (Ent);
2761
2762          ----------------------
2763          -- Iterator_Element --
2764          ----------------------
2765
2766          when Attribute_Iterator_Element =>
2767             Analyze (Expr);
2768
2769             if not Is_Entity_Name (Expr)
2770               or else not Is_Type (Entity (Expr))
2771             then
2772                Error_Msg_N ("aspect Iterator_Element must be a type", Expr);
2773             end if;
2774
2775          -------------------
2776          -- Machine_Radix --
2777          -------------------
2778
2779          --  Machine radix attribute definition clause
2780
2781          when Attribute_Machine_Radix => Machine_Radix : declare
2782             Radix : constant Uint := Static_Integer (Expr);
2783
2784          begin
2785             if not Is_Decimal_Fixed_Point_Type (U_Ent) then
2786                Error_Msg_N ("decimal fixed-point type expected for &", Nam);
2787
2788             elsif Duplicate_Clause then
2789                null;
2790
2791             elsif Radix /= No_Uint then
2792                Set_Has_Machine_Radix_Clause (U_Ent);
2793                Set_Has_Non_Standard_Rep (Base_Type (U_Ent));
2794
2795                if Radix = 2 then
2796                   null;
2797                elsif Radix = 10 then
2798                   Set_Machine_Radix_10 (U_Ent);
2799                else
2800                   Error_Msg_N ("machine radix value must be 2 or 10", Expr);
2801                end if;
2802             end if;
2803          end Machine_Radix;
2804
2805          -----------------
2806          -- Object_Size --
2807          -----------------
2808
2809          --  Object_Size attribute definition clause
2810
2811          when Attribute_Object_Size => Object_Size : declare
2812             Size : constant Uint := Static_Integer (Expr);
2813
2814             Biased : Boolean;
2815             pragma Warnings (Off, Biased);
2816
2817          begin
2818             if not Is_Type (U_Ent) then
2819                Error_Msg_N ("Object_Size cannot be given for &", Nam);
2820
2821             elsif Duplicate_Clause then
2822                null;
2823
2824             else
2825                Check_Size (Expr, U_Ent, Size, Biased);
2826
2827                if Size /= 8
2828                     and then
2829                   Size /= 16
2830                     and then
2831                   Size /= 32
2832                     and then
2833                   UI_Mod (Size, 64) /= 0
2834                then
2835                   Error_Msg_N
2836                     ("Object_Size must be 8, 16, 32, or multiple of 64",
2837                      Expr);
2838                end if;
2839
2840                Set_Esize (U_Ent, Size);
2841                Set_Has_Object_Size_Clause (U_Ent);
2842                Alignment_Check_For_Size_Change (U_Ent, Size);
2843             end if;
2844          end Object_Size;
2845
2846          ------------
2847          -- Output --
2848          ------------
2849
2850          when Attribute_Output =>
2851             Analyze_Stream_TSS_Definition (TSS_Stream_Output);
2852             Set_Has_Specified_Stream_Output (Ent);
2853
2854          ----------
2855          -- Read --
2856          ----------
2857
2858          when Attribute_Read =>
2859             Analyze_Stream_TSS_Definition (TSS_Stream_Read);
2860             Set_Has_Specified_Stream_Read (Ent);
2861
2862          ----------
2863          -- Size --
2864          ----------
2865
2866          --  Size attribute definition clause
2867
2868          when Attribute_Size => Size : declare
2869             Size   : constant Uint := Static_Integer (Expr);
2870             Etyp   : Entity_Id;
2871             Biased : Boolean;
2872
2873          begin
2874             FOnly := True;
2875
2876             if Duplicate_Clause then
2877                null;
2878
2879             elsif not Is_Type (U_Ent)
2880               and then Ekind (U_Ent) /= E_Variable
2881               and then Ekind (U_Ent) /= E_Constant
2882             then
2883                Error_Msg_N ("size cannot be given for &", Nam);
2884
2885             elsif Is_Array_Type (U_Ent)
2886               and then not Is_Constrained (U_Ent)
2887             then
2888                Error_Msg_N
2889                  ("size cannot be given for unconstrained array", Nam);
2890
2891             elsif Size /= No_Uint then
2892                if VM_Target /= No_VM and then not GNAT_Mode then
2893
2894                   --  Size clause is not handled properly on VM targets.
2895                   --  Display a warning unless we are in GNAT mode, in which
2896                   --  case this is useless.
2897
2898                   Error_Msg_N
2899                     ("?size clauses are ignored in this configuration", N);
2900                end if;
2901
2902                if Is_Type (U_Ent) then
2903                   Etyp := U_Ent;
2904                else
2905                   Etyp := Etype (U_Ent);
2906                end if;
2907
2908                --  Check size, note that Gigi is in charge of checking that the
2909                --  size of an array or record type is OK. Also we do not check
2910                --  the size in the ordinary fixed-point case, since it is too
2911                --  early to do so (there may be subsequent small clause that
2912                --  affects the size). We can check the size if a small clause
2913                --  has already been given.
2914
2915                if not Is_Ordinary_Fixed_Point_Type (U_Ent)
2916                  or else Has_Small_Clause (U_Ent)
2917                then
2918                   Check_Size (Expr, Etyp, Size, Biased);
2919                   Set_Biased (U_Ent, N, "size clause", Biased);
2920                end if;
2921
2922                --  For types set RM_Size and Esize if possible
2923
2924                if Is_Type (U_Ent) then
2925                   Set_RM_Size (U_Ent, Size);
2926
2927                   --  For elementary types, increase Object_Size to power of 2,
2928                   --  but not less than a storage unit in any case (normally
2929                   --  this means it will be byte addressable).
2930
2931                   --  For all other types, nothing else to do, we leave Esize
2932                   --  (object size) unset, the back end will set it from the
2933                   --  size and alignment in an appropriate manner.
2934
2935                   --  In both cases, we check whether the alignment must be
2936                   --  reset in the wake of the size change.
2937
2938                   if Is_Elementary_Type (U_Ent) then
2939                      if Size <= System_Storage_Unit then
2940                         Init_Esize (U_Ent, System_Storage_Unit);
2941                      elsif Size <= 16 then
2942                         Init_Esize (U_Ent, 16);
2943                      elsif Size <= 32 then
2944                         Init_Esize (U_Ent, 32);
2945                      else
2946                         Set_Esize  (U_Ent, (Size + 63) / 64 * 64);
2947                      end if;
2948
2949                      Alignment_Check_For_Size_Change (U_Ent, Esize (U_Ent));
2950                   else
2951                      Alignment_Check_For_Size_Change (U_Ent, Size);
2952                   end if;
2953
2954                --  For objects, set Esize only
2955
2956                else
2957                   if Is_Elementary_Type (Etyp) then
2958                      if Size /= System_Storage_Unit
2959                           and then
2960                         Size /= System_Storage_Unit * 2
2961                           and then
2962                         Size /= System_Storage_Unit * 4
2963                            and then
2964                         Size /= System_Storage_Unit * 8
2965                      then
2966                         Error_Msg_Uint_1 := UI_From_Int (System_Storage_Unit);
2967                         Error_Msg_Uint_2 := Error_Msg_Uint_1 * 8;
2968                         Error_Msg_N
2969                           ("size for primitive object must be a power of 2"
2970                             & " in the range ^-^", N);
2971                      end if;
2972                   end if;
2973
2974                   Set_Esize (U_Ent, Size);
2975                end if;
2976
2977                Set_Has_Size_Clause (U_Ent);
2978             end if;
2979          end Size;
2980
2981          -----------
2982          -- Small --
2983          -----------
2984
2985          --  Small attribute definition clause
2986
2987          when Attribute_Small => Small : declare
2988             Implicit_Base : constant Entity_Id := Base_Type (U_Ent);
2989             Small         : Ureal;
2990
2991          begin
2992             Analyze_And_Resolve (Expr, Any_Real);
2993
2994             if Etype (Expr) = Any_Type then
2995                return;
2996
2997             elsif not Is_Static_Expression (Expr) then
2998                Flag_Non_Static_Expr
2999                  ("small requires static expression!", Expr);
3000                return;
3001
3002             else
3003                Small := Expr_Value_R (Expr);
3004
3005                if Small <= Ureal_0 then
3006                   Error_Msg_N ("small value must be greater than zero", Expr);
3007                   return;
3008                end if;
3009
3010             end if;
3011
3012             if not Is_Ordinary_Fixed_Point_Type (U_Ent) then
3013                Error_Msg_N
3014                  ("small requires an ordinary fixed point type", Nam);
3015
3016             elsif Has_Small_Clause (U_Ent) then
3017                Error_Msg_N ("small already given for &", Nam);
3018
3019             elsif Small > Delta_Value (U_Ent) then
3020                Error_Msg_N
3021                  ("small value must not be greater then delta value", Nam);
3022
3023             else
3024                Set_Small_Value (U_Ent, Small);
3025                Set_Small_Value (Implicit_Base, Small);
3026                Set_Has_Small_Clause (U_Ent);
3027                Set_Has_Small_Clause (Implicit_Base);
3028                Set_Has_Non_Standard_Rep (Implicit_Base);
3029             end if;
3030          end Small;
3031
3032          ------------------
3033          -- Storage_Pool --
3034          ------------------
3035
3036          --  Storage_Pool attribute definition clause
3037
3038          when Attribute_Storage_Pool => Storage_Pool : declare
3039             Pool : Entity_Id;
3040             T    : Entity_Id;
3041
3042          begin
3043             if Ekind (U_Ent) = E_Access_Subprogram_Type then
3044                Error_Msg_N
3045                  ("storage pool cannot be given for access-to-subprogram type",
3046                   Nam);
3047                return;
3048
3049             elsif not
3050               Ekind_In (U_Ent, E_Access_Type, E_General_Access_Type)
3051             then
3052                Error_Msg_N
3053                  ("storage pool can only be given for access types", Nam);
3054                return;
3055
3056             elsif Is_Derived_Type (U_Ent) then
3057                Error_Msg_N
3058                  ("storage pool cannot be given for a derived access type",
3059                   Nam);
3060
3061             elsif Duplicate_Clause then
3062                return;
3063
3064             elsif Present (Associated_Storage_Pool (U_Ent)) then
3065                Error_Msg_N ("storage pool already given for &", Nam);
3066                return;
3067             end if;
3068
3069             Analyze_And_Resolve
3070               (Expr, Class_Wide_Type (RTE (RE_Root_Storage_Pool)));
3071
3072             if not Denotes_Variable (Expr) then
3073                Error_Msg_N ("storage pool must be a variable", Expr);
3074                return;
3075             end if;
3076
3077             if Nkind (Expr) = N_Type_Conversion then
3078                T := Etype (Expression (Expr));
3079             else
3080                T := Etype (Expr);
3081             end if;
3082
3083             --  The Stack_Bounded_Pool is used internally for implementing
3084             --  access types with a Storage_Size. Since it only work properly
3085             --  when used on one specific type, we need to check that it is not
3086             --  hijacked improperly:
3087
3088             --    type T is access Integer;
3089             --    for T'Storage_Size use n;
3090             --    type Q is access Float;
3091             --    for Q'Storage_Size use T'Storage_Size; -- incorrect
3092
3093             if RTE_Available (RE_Stack_Bounded_Pool)
3094               and then Base_Type (T) = RTE (RE_Stack_Bounded_Pool)
3095             then
3096                Error_Msg_N ("non-shareable internal Pool", Expr);
3097                return;
3098             end if;
3099
3100             --  If the argument is a name that is not an entity name, then
3101             --  we construct a renaming operation to define an entity of
3102             --  type storage pool.
3103
3104             if not Is_Entity_Name (Expr)
3105               and then Is_Object_Reference (Expr)
3106             then
3107                Pool := Make_Temporary (Loc, 'P', Expr);
3108
3109                declare
3110                   Rnode : constant Node_Id :=
3111                             Make_Object_Renaming_Declaration (Loc,
3112                               Defining_Identifier => Pool,
3113                               Subtype_Mark        =>
3114                                 New_Occurrence_Of (Etype (Expr), Loc),
3115                               Name                => Expr);
3116
3117                begin
3118                   Insert_Before (N, Rnode);
3119                   Analyze (Rnode);
3120                   Set_Associated_Storage_Pool (U_Ent, Pool);
3121                end;
3122
3123             elsif Is_Entity_Name (Expr) then
3124                Pool := Entity (Expr);
3125
3126                --  If pool is a renamed object, get original one. This can
3127                --  happen with an explicit renaming, and within instances.
3128
3129                while Present (Renamed_Object (Pool))
3130                  and then Is_Entity_Name (Renamed_Object (Pool))
3131                loop
3132                   Pool := Entity (Renamed_Object (Pool));
3133                end loop;
3134
3135                if Present (Renamed_Object (Pool))
3136                  and then Nkind (Renamed_Object (Pool)) = N_Type_Conversion
3137                  and then Is_Entity_Name (Expression (Renamed_Object (Pool)))
3138                then
3139                   Pool := Entity (Expression (Renamed_Object (Pool)));
3140                end if;
3141
3142                Set_Associated_Storage_Pool (U_Ent, Pool);
3143
3144             elsif Nkind (Expr) = N_Type_Conversion
3145               and then Is_Entity_Name (Expression (Expr))
3146               and then Nkind (Original_Node (Expr)) = N_Attribute_Reference
3147             then
3148                Pool := Entity (Expression (Expr));
3149                Set_Associated_Storage_Pool (U_Ent, Pool);
3150
3151             else
3152                Error_Msg_N ("incorrect reference to a Storage Pool", Expr);
3153                return;
3154             end if;
3155          end Storage_Pool;
3156
3157          ------------------
3158          -- Storage_Size --
3159          ------------------
3160
3161          --  Storage_Size attribute definition clause
3162
3163          when Attribute_Storage_Size => Storage_Size : declare
3164             Btype : constant Entity_Id := Base_Type (U_Ent);
3165             Sprag : Node_Id;
3166
3167          begin
3168             if Is_Task_Type (U_Ent) then
3169                Check_Restriction (No_Obsolescent_Features, N);
3170
3171                if Warn_On_Obsolescent_Feature then
3172                   Error_Msg_N
3173                     ("storage size clause for task is an " &
3174                      "obsolescent feature (RM J.9)?", N);
3175                   Error_Msg_N ("\use Storage_Size pragma instead?", N);
3176                end if;
3177
3178                FOnly := True;
3179             end if;
3180
3181             if not Is_Access_Type (U_Ent)
3182               and then Ekind (U_Ent) /= E_Task_Type
3183             then
3184                Error_Msg_N ("storage size cannot be given for &", Nam);
3185
3186             elsif Is_Access_Type (U_Ent) and Is_Derived_Type (U_Ent) then
3187                Error_Msg_N
3188                  ("storage size cannot be given for a derived access type",
3189                   Nam);
3190
3191             elsif Duplicate_Clause then
3192                null;
3193
3194             else
3195                Analyze_And_Resolve (Expr, Any_Integer);
3196
3197                if Is_Access_Type (U_Ent) then
3198                   if Present (Associated_Storage_Pool (U_Ent)) then
3199                      Error_Msg_N ("storage pool already given for &", Nam);
3200                      return;
3201                   end if;
3202
3203                   if Is_OK_Static_Expression (Expr)
3204                     and then Expr_Value (Expr) = 0
3205                   then
3206                      Set_No_Pool_Assigned (Btype);
3207                   end if;
3208
3209                else -- Is_Task_Type (U_Ent)
3210                   Sprag := Get_Rep_Pragma (Btype, Name_Storage_Size);
3211
3212                   if Present (Sprag) then
3213                      Error_Msg_Sloc := Sloc (Sprag);
3214                      Error_Msg_N
3215                        ("Storage_Size already specified#", Nam);
3216                      return;
3217                   end if;
3218                end if;
3219
3220                Set_Has_Storage_Size_Clause (Btype);
3221             end if;
3222          end Storage_Size;
3223
3224          -----------------
3225          -- Stream_Size --
3226          -----------------
3227
3228          when Attribute_Stream_Size => Stream_Size : declare
3229             Size : constant Uint := Static_Integer (Expr);
3230
3231          begin
3232             if Ada_Version <= Ada_95 then
3233                Check_Restriction (No_Implementation_Attributes, N);
3234             end if;
3235
3236             if Duplicate_Clause then
3237                null;
3238
3239             elsif Is_Elementary_Type (U_Ent) then
3240                if Size /= System_Storage_Unit
3241                     and then
3242                   Size /= System_Storage_Unit * 2
3243                     and then
3244                   Size /= System_Storage_Unit * 4
3245                      and then
3246                   Size /= System_Storage_Unit * 8
3247                then
3248                   Error_Msg_Uint_1 := UI_From_Int (System_Storage_Unit);
3249                   Error_Msg_N
3250                     ("stream size for elementary type must be a"
3251                        & " power of 2 and at least ^", N);
3252
3253                elsif RM_Size (U_Ent) > Size then
3254                   Error_Msg_Uint_1 := RM_Size (U_Ent);
3255                   Error_Msg_N
3256                     ("stream size for elementary type must be a"
3257                        & " power of 2 and at least ^", N);
3258                end if;
3259
3260                Set_Has_Stream_Size_Clause (U_Ent);
3261
3262             else
3263                Error_Msg_N ("Stream_Size cannot be given for &", Nam);
3264             end if;
3265          end Stream_Size;
3266
3267          ----------------
3268          -- Value_Size --
3269          ----------------
3270
3271          --  Value_Size attribute definition clause
3272
3273          when Attribute_Value_Size => Value_Size : declare
3274             Size   : constant Uint := Static_Integer (Expr);
3275             Biased : Boolean;
3276
3277          begin
3278             if not Is_Type (U_Ent) then
3279                Error_Msg_N ("Value_Size cannot be given for &", Nam);
3280
3281             elsif Duplicate_Clause then
3282                null;
3283
3284             elsif Is_Array_Type (U_Ent)
3285               and then not Is_Constrained (U_Ent)
3286             then
3287                Error_Msg_N
3288                  ("Value_Size cannot be given for unconstrained array", Nam);
3289
3290             else
3291                if Is_Elementary_Type (U_Ent) then
3292                   Check_Size (Expr, U_Ent, Size, Biased);
3293                   Set_Biased (U_Ent, N, "value size clause", Biased);
3294                end if;
3295
3296                Set_RM_Size (U_Ent, Size);
3297             end if;
3298          end Value_Size;
3299
3300          -----------------------
3301          -- Variable_Indexing --
3302          -----------------------
3303
3304          when Attribute_Variable_Indexing =>
3305             Check_Indexing_Functions;
3306
3307          -----------
3308          -- Write --
3309          -----------
3310
3311          when Attribute_Write =>
3312             Analyze_Stream_TSS_Definition (TSS_Stream_Write);
3313             Set_Has_Specified_Stream_Write (Ent);
3314
3315          --  All other attributes cannot be set
3316
3317          when others =>
3318             Error_Msg_N
3319               ("attribute& cannot be set with definition clause", N);
3320       end case;
3321
3322       --  The test for the type being frozen must be performed after any
3323       --  expression the clause has been analyzed since the expression itself
3324       --  might cause freezing that makes the clause illegal.
3325
3326       if Rep_Item_Too_Late (U_Ent, N, FOnly) then
3327          return;
3328       end if;
3329    end Analyze_Attribute_Definition_Clause;
3330
3331    ----------------------------
3332    -- Analyze_Code_Statement --
3333    ----------------------------
3334
3335    procedure Analyze_Code_Statement (N : Node_Id) is
3336       HSS   : constant Node_Id   := Parent (N);
3337       SBody : constant Node_Id   := Parent (HSS);
3338       Subp  : constant Entity_Id := Current_Scope;
3339       Stmt  : Node_Id;
3340       Decl  : Node_Id;
3341       StmtO : Node_Id;
3342       DeclO : Node_Id;
3343
3344    begin
3345       --  Analyze and check we get right type, note that this implements the
3346       --  requirement (RM 13.8(1)) that Machine_Code be with'ed, since that
3347       --  is the only way that Asm_Insn could possibly be visible.
3348
3349       Analyze_And_Resolve (Expression (N));
3350
3351       if Etype (Expression (N)) = Any_Type then
3352          return;
3353       elsif Etype (Expression (N)) /= RTE (RE_Asm_Insn) then
3354          Error_Msg_N ("incorrect type for code statement", N);
3355          return;
3356       end if;
3357
3358       Check_Code_Statement (N);
3359
3360       --  Make sure we appear in the handled statement sequence of a
3361       --  subprogram (RM 13.8(3)).
3362
3363       if Nkind (HSS) /= N_Handled_Sequence_Of_Statements
3364         or else Nkind (SBody) /= N_Subprogram_Body
3365       then
3366          Error_Msg_N
3367            ("code statement can only appear in body of subprogram", N);
3368          return;
3369       end if;
3370
3371       --  Do remaining checks (RM 13.8(3)) if not already done
3372
3373       if not Is_Machine_Code_Subprogram (Subp) then
3374          Set_Is_Machine_Code_Subprogram (Subp);
3375
3376          --  No exception handlers allowed
3377
3378          if Present (Exception_Handlers (HSS)) then
3379             Error_Msg_N
3380               ("exception handlers not permitted in machine code subprogram",
3381                First (Exception_Handlers (HSS)));
3382          end if;
3383
3384          --  No declarations other than use clauses and pragmas (we allow
3385          --  certain internally generated declarations as well).
3386
3387          Decl := First (Declarations (SBody));
3388          while Present (Decl) loop
3389             DeclO := Original_Node (Decl);
3390             if Comes_From_Source (DeclO)
3391               and not Nkind_In (DeclO, N_Pragma,
3392                                        N_Use_Package_Clause,
3393                                        N_Use_Type_Clause,
3394                                        N_Implicit_Label_Declaration)
3395             then
3396                Error_Msg_N
3397                  ("this declaration not allowed in machine code subprogram",
3398                   DeclO);
3399             end if;
3400
3401             Next (Decl);
3402          end loop;
3403
3404          --  No statements other than code statements, pragmas, and labels.
3405          --  Again we allow certain internally generated statements.
3406
3407          --  In Ada 2012, qualified expressions are names, and the code
3408          --  statement is initially parsed as a procedure call.
3409
3410          Stmt := First (Statements (HSS));
3411          while Present (Stmt) loop
3412             StmtO := Original_Node (Stmt);
3413
3414             --  A procedure call transformed into a code statement is OK.
3415
3416             if Ada_Version >= Ada_2012
3417               and then Nkind (StmtO) = N_Procedure_Call_Statement
3418               and then Nkind (Name (StmtO)) = N_Qualified_Expression
3419             then
3420                null;
3421
3422             elsif Comes_From_Source (StmtO)
3423               and then not Nkind_In (StmtO, N_Pragma,
3424                                             N_Label,
3425                                             N_Code_Statement)
3426             then
3427                Error_Msg_N
3428                  ("this statement is not allowed in machine code subprogram",
3429                   StmtO);
3430             end if;
3431
3432             Next (Stmt);
3433          end loop;
3434       end if;
3435    end Analyze_Code_Statement;
3436
3437    -----------------------------------------------
3438    -- Analyze_Enumeration_Representation_Clause --
3439    -----------------------------------------------
3440
3441    procedure Analyze_Enumeration_Representation_Clause (N : Node_Id) is
3442       Ident    : constant Node_Id    := Identifier (N);
3443       Aggr     : constant Node_Id    := Array_Aggregate (N);
3444       Enumtype : Entity_Id;
3445       Elit     : Entity_Id;
3446       Expr     : Node_Id;
3447       Assoc    : Node_Id;
3448       Choice   : Node_Id;
3449       Val      : Uint;
3450
3451       Err : Boolean := False;
3452       --  Set True to avoid cascade errors and crashes on incorrect source code
3453
3454       Lo : constant Uint := Expr_Value (Type_Low_Bound (Universal_Integer));
3455       Hi : constant Uint := Expr_Value (Type_High_Bound (Universal_Integer));
3456       --  Allowed range of universal integer (= allowed range of enum lit vals)
3457
3458       Min : Uint;
3459       Max : Uint;
3460       --  Minimum and maximum values of entries
3461
3462       Max_Node : Node_Id;
3463       --  Pointer to node for literal providing max value
3464
3465    begin
3466       if Ignore_Rep_Clauses then
3467          return;
3468       end if;
3469
3470       --  First some basic error checks
3471
3472       Find_Type (Ident);
3473       Enumtype := Entity (Ident);
3474
3475       if Enumtype = Any_Type
3476         or else Rep_Item_Too_Early (Enumtype, N)
3477       then
3478          return;
3479       else
3480          Enumtype := Underlying_Type (Enumtype);
3481       end if;
3482
3483       if not Is_Enumeration_Type (Enumtype) then
3484          Error_Msg_NE
3485            ("enumeration type required, found}",
3486             Ident, First_Subtype (Enumtype));
3487          return;
3488       end if;
3489
3490       --  Ignore rep clause on generic actual type. This will already have
3491       --  been flagged on the template as an error, and this is the safest
3492       --  way to ensure we don't get a junk cascaded message in the instance.
3493
3494       if Is_Generic_Actual_Type (Enumtype) then
3495          return;
3496
3497       --  Type must be in current scope
3498
3499       elsif Scope (Enumtype) /= Current_Scope then
3500          Error_Msg_N ("type must be declared in this scope", Ident);
3501          return;
3502
3503       --  Type must be a first subtype
3504
3505       elsif not Is_First_Subtype (Enumtype) then
3506          Error_Msg_N ("cannot give enumeration rep clause for subtype", N);
3507          return;
3508
3509       --  Ignore duplicate rep clause
3510
3511       elsif Has_Enumeration_Rep_Clause (Enumtype) then
3512          Error_Msg_N ("duplicate enumeration rep clause ignored", N);
3513          return;
3514
3515       --  Don't allow rep clause for standard [wide_[wide_]]character
3516
3517       elsif Is_Standard_Character_Type (Enumtype) then
3518          Error_Msg_N ("enumeration rep clause not allowed for this type", N);
3519          return;
3520
3521       --  Check that the expression is a proper aggregate (no parentheses)
3522
3523       elsif Paren_Count (Aggr) /= 0 then
3524          Error_Msg
3525            ("extra parentheses surrounding aggregate not allowed",
3526             First_Sloc (Aggr));
3527          return;
3528
3529       --  All tests passed, so set rep clause in place
3530
3531       else
3532          Set_Has_Enumeration_Rep_Clause (Enumtype);
3533          Set_Has_Enumeration_Rep_Clause (Base_Type (Enumtype));
3534       end if;
3535
3536       --  Now we process the aggregate. Note that we don't use the normal
3537       --  aggregate code for this purpose, because we don't want any of the
3538       --  normal expansion activities, and a number of special semantic
3539       --  rules apply (including the component type being any integer type)
3540
3541       Elit := First_Literal (Enumtype);
3542
3543       --  First the positional entries if any
3544
3545       if Present (Expressions (Aggr)) then
3546          Expr := First (Expressions (Aggr));
3547          while Present (Expr) loop
3548             if No (Elit) then
3549                Error_Msg_N ("too many entries in aggregate", Expr);
3550                return;
3551             end if;
3552
3553             Val := Static_Integer (Expr);
3554
3555             --  Err signals that we found some incorrect entries processing
3556             --  the list. The final checks for completeness and ordering are
3557             --  skipped in this case.
3558
3559             if Val = No_Uint then
3560                Err := True;
3561             elsif Val < Lo or else Hi < Val then
3562                Error_Msg_N ("value outside permitted range", Expr);
3563                Err := True;
3564             end if;
3565
3566             Set_Enumeration_Rep (Elit, Val);
3567             Set_Enumeration_Rep_Expr (Elit, Expr);
3568             Next (Expr);
3569             Next (Elit);
3570          end loop;
3571       end if;
3572
3573       --  Now process the named entries if present
3574
3575       if Present (Component_Associations (Aggr)) then
3576          Assoc := First (Component_Associations (Aggr));
3577          while Present (Assoc) loop
3578             Choice := First (Choices (Assoc));
3579
3580             if Present (Next (Choice)) then
3581                Error_Msg_N
3582                  ("multiple choice not allowed here", Next (Choice));
3583                Err := True;
3584             end if;
3585
3586             if Nkind (Choice) = N_Others_Choice then
3587                Error_Msg_N ("others choice not allowed here", Choice);
3588                Err := True;
3589
3590             elsif Nkind (Choice) = N_Range then
3591
3592                --  ??? should allow zero/one element range here
3593
3594                Error_Msg_N ("range not allowed here", Choice);
3595                Err := True;
3596
3597             else
3598                Analyze_And_Resolve (Choice, Enumtype);
3599
3600                if Error_Posted (Choice) then
3601                   Err := True;
3602                end if;
3603
3604                if not Err then
3605                   if Is_Entity_Name (Choice)
3606                     and then Is_Type (Entity (Choice))
3607                   then
3608                      Error_Msg_N ("subtype name not allowed here", Choice);
3609                      Err := True;
3610
3611                      --  ??? should allow static subtype with zero/one entry
3612
3613                   elsif Etype (Choice) = Base_Type (Enumtype) then
3614                      if not Is_Static_Expression (Choice) then
3615                         Flag_Non_Static_Expr
3616                           ("non-static expression used for choice!", Choice);
3617                         Err := True;
3618
3619                      else
3620                         Elit := Expr_Value_E (Choice);
3621
3622                         if Present (Enumeration_Rep_Expr (Elit)) then
3623                            Error_Msg_Sloc :=
3624                              Sloc (Enumeration_Rep_Expr (Elit));
3625                            Error_Msg_NE
3626                              ("representation for& previously given#",
3627                               Choice, Elit);
3628                            Err := True;
3629                         end if;
3630
3631                         Set_Enumeration_Rep_Expr (Elit, Expression (Assoc));
3632
3633                         Expr := Expression (Assoc);
3634                         Val := Static_Integer (Expr);
3635
3636                         if Val = No_Uint then
3637                            Err := True;
3638
3639                         elsif Val < Lo or else Hi < Val then
3640                            Error_Msg_N ("value outside permitted range", Expr);
3641                            Err := True;
3642                         end if;
3643
3644                         Set_Enumeration_Rep (Elit, Val);
3645                      end if;
3646                   end if;
3647                end if;
3648             end if;
3649
3650             Next (Assoc);
3651          end loop;
3652       end if;
3653
3654       --  Aggregate is fully processed. Now we check that a full set of
3655       --  representations was given, and that they are in range and in order.
3656       --  These checks are only done if no other errors occurred.
3657
3658       if not Err then
3659          Min  := No_Uint;
3660          Max  := No_Uint;
3661
3662          Elit := First_Literal (Enumtype);
3663          while Present (Elit) loop
3664             if No (Enumeration_Rep_Expr (Elit)) then
3665                Error_Msg_NE ("missing representation for&!", N, Elit);
3666
3667             else
3668                Val := Enumeration_Rep (Elit);
3669
3670                if Min = No_Uint then
3671                   Min := Val;
3672                end if;
3673
3674                if Val /= No_Uint then
3675                   if Max /= No_Uint and then Val <= Max then
3676                      Error_Msg_NE
3677                        ("enumeration value for& not ordered!",
3678                         Enumeration_Rep_Expr (Elit), Elit);
3679                   end if;
3680
3681                   Max_Node := Enumeration_Rep_Expr (Elit);
3682                   Max := Val;
3683                end if;
3684
3685                --  If there is at least one literal whose representation is not
3686                --  equal to the Pos value, then note that this enumeration type
3687                --  has a non-standard representation.
3688
3689                if Val /= Enumeration_Pos (Elit) then
3690                   Set_Has_Non_Standard_Rep (Base_Type (Enumtype));
3691                end if;
3692             end if;
3693
3694             Next (Elit);
3695          end loop;
3696
3697          --  Now set proper size information
3698
3699          declare
3700             Minsize : Uint := UI_From_Int (Minimum_Size (Enumtype));
3701
3702          begin
3703             if Has_Size_Clause (Enumtype) then
3704
3705                --  All OK, if size is OK now
3706
3707                if RM_Size (Enumtype) >= Minsize then
3708                   null;
3709
3710                else
3711                   --  Try if we can get by with biasing
3712
3713                   Minsize :=
3714                     UI_From_Int (Minimum_Size (Enumtype, Biased => True));
3715
3716                   --  Error message if even biasing does not work
3717
3718                   if RM_Size (Enumtype) < Minsize then
3719                      Error_Msg_Uint_1 := RM_Size (Enumtype);
3720                      Error_Msg_Uint_2 := Max;
3721                      Error_Msg_N
3722                        ("previously given size (^) is too small "
3723                         & "for this value (^)", Max_Node);
3724
3725                   --  If biasing worked, indicate that we now have biased rep
3726
3727                   else
3728                      Set_Biased
3729                        (Enumtype, Size_Clause (Enumtype), "size clause");
3730                   end if;
3731                end if;
3732
3733             else
3734                Set_RM_Size    (Enumtype, Minsize);
3735                Set_Enum_Esize (Enumtype);
3736             end if;
3737
3738             Set_RM_Size   (Base_Type (Enumtype), RM_Size   (Enumtype));
3739             Set_Esize     (Base_Type (Enumtype), Esize     (Enumtype));
3740             Set_Alignment (Base_Type (Enumtype), Alignment (Enumtype));
3741          end;
3742       end if;
3743
3744       --  We repeat the too late test in case it froze itself!
3745
3746       if Rep_Item_Too_Late (Enumtype, N) then
3747          null;
3748       end if;
3749    end Analyze_Enumeration_Representation_Clause;
3750
3751    ----------------------------
3752    -- Analyze_Free_Statement --
3753    ----------------------------
3754
3755    procedure Analyze_Free_Statement (N : Node_Id) is
3756    begin
3757       Analyze (Expression (N));
3758    end Analyze_Free_Statement;
3759
3760    ---------------------------
3761    -- Analyze_Freeze_Entity --
3762    ---------------------------
3763
3764    procedure Analyze_Freeze_Entity (N : Node_Id) is
3765       E : constant Entity_Id := Entity (N);
3766
3767    begin
3768       --  Remember that we are processing a freezing entity. Required to
3769       --  ensure correct decoration of internal entities associated with
3770       --  interfaces (see New_Overloaded_Entity).
3771
3772       Inside_Freezing_Actions := Inside_Freezing_Actions + 1;
3773
3774       --  For tagged types covering interfaces add internal entities that link
3775       --  the primitives of the interfaces with the primitives that cover them.
3776       --  Note: These entities were originally generated only when generating
3777       --  code because their main purpose was to provide support to initialize
3778       --  the secondary dispatch tables. They are now generated also when
3779       --  compiling with no code generation to provide ASIS the relationship
3780       --  between interface primitives and tagged type primitives. They are
3781       --  also used to locate primitives covering interfaces when processing
3782       --  generics (see Derive_Subprograms).
3783
3784       if Ada_Version >= Ada_2005
3785         and then Ekind (E) = E_Record_Type
3786         and then Is_Tagged_Type (E)
3787         and then not Is_Interface (E)
3788         and then Has_Interfaces (E)
3789       then
3790          --  This would be a good common place to call the routine that checks
3791          --  overriding of interface primitives (and thus factorize calls to
3792          --  Check_Abstract_Overriding located at different contexts in the
3793          --  compiler). However, this is not possible because it causes
3794          --  spurious errors in case of late overriding.
3795
3796          Add_Internal_Interface_Entities (E);
3797       end if;
3798
3799       --  Check CPP types
3800
3801       if Ekind (E) = E_Record_Type
3802         and then Is_CPP_Class (E)
3803         and then Is_Tagged_Type (E)
3804         and then Tagged_Type_Expansion
3805         and then Expander_Active
3806       then
3807          if CPP_Num_Prims (E) = 0 then
3808
3809             --  If the CPP type has user defined components then it must import
3810             --  primitives from C++. This is required because if the C++ class
3811             --  has no primitives then the C++ compiler does not added the _tag
3812             --  component to the type.
3813
3814             pragma Assert (Chars (First_Entity (E)) = Name_uTag);
3815
3816             if First_Entity (E) /= Last_Entity (E) then
3817                Error_Msg_N
3818                  ("?'C'P'P type must import at least one primitive from C++",
3819                   E);
3820             end if;
3821          end if;
3822
3823          --  Check that all its primitives are abstract or imported from C++.
3824          --  Check also availability of the C++ constructor.
3825
3826          declare
3827             Has_Constructors : constant Boolean := Has_CPP_Constructors (E);
3828             Elmt             : Elmt_Id;
3829             Error_Reported   : Boolean := False;
3830             Prim             : Node_Id;
3831
3832          begin
3833             Elmt := First_Elmt (Primitive_Operations (E));
3834             while Present (Elmt) loop
3835                Prim := Node (Elmt);
3836
3837                if Comes_From_Source (Prim) then
3838                   if Is_Abstract_Subprogram (Prim) then
3839                      null;
3840
3841                   elsif not Is_Imported (Prim)
3842                     or else Convention (Prim) /= Convention_CPP
3843                   then
3844                      Error_Msg_N
3845                        ("?primitives of 'C'P'P types must be imported from C++"
3846                         & " or abstract", Prim);
3847
3848                   elsif not Has_Constructors
3849                      and then not Error_Reported
3850                   then
3851                      Error_Msg_Name_1 := Chars (E);
3852                      Error_Msg_N
3853                        ("?'C'P'P constructor required for type %", Prim);
3854                      Error_Reported := True;
3855                   end if;
3856                end if;
3857
3858                Next_Elmt (Elmt);
3859             end loop;
3860          end;
3861       end if;
3862
3863       Inside_Freezing_Actions := Inside_Freezing_Actions - 1;
3864
3865       --  If we have a type with predicates, build predicate function
3866
3867       if Is_Type (E) and then Has_Predicates (E) then
3868          Build_Predicate_Function (E, N);
3869       end if;
3870
3871       --  If type has delayed aspects, this is where we do the preanalysis at
3872       --  the freeze point, as part of the consistent visibility check. Note
3873       --  that this must be done after calling Build_Predicate_Function or
3874       --  Build_Invariant_Procedure since these subprograms fix occurrences of
3875       --  the subtype name in the saved expression so that they will not cause
3876       --  trouble in the preanalysis.
3877
3878       if Has_Delayed_Aspects (E) then
3879          declare
3880             Ritem : Node_Id;
3881
3882          begin
3883             --  Look for aspect specification entries for this entity
3884
3885             Ritem := First_Rep_Item (E);
3886             while Present (Ritem) loop
3887                if Nkind (Ritem) = N_Aspect_Specification
3888                  and then Entity (Ritem) = E
3889                  and then Is_Delayed_Aspect (Ritem)
3890                  and then Scope (E) = Current_Scope
3891                then
3892                   Check_Aspect_At_Freeze_Point (Ritem);
3893                end if;
3894
3895                Next_Rep_Item (Ritem);
3896             end loop;
3897          end;
3898       end if;
3899    end Analyze_Freeze_Entity;
3900
3901    ------------------------------------------
3902    -- Analyze_Record_Representation_Clause --
3903    ------------------------------------------
3904
3905    --  Note: we check as much as we can here, but we can't do any checks
3906    --  based on the position values (e.g. overlap checks) until freeze time
3907    --  because especially in Ada 2005 (machine scalar mode), the processing
3908    --  for non-standard bit order can substantially change the positions.
3909    --  See procedure Check_Record_Representation_Clause (called from Freeze)
3910    --  for the remainder of this processing.
3911
3912    procedure Analyze_Record_Representation_Clause (N : Node_Id) is
3913       Ident   : constant Node_Id := Identifier (N);
3914       Biased  : Boolean;
3915       CC      : Node_Id;
3916       Comp    : Entity_Id;
3917       Fbit    : Uint;
3918       Hbit    : Uint := Uint_0;
3919       Lbit    : Uint;
3920       Ocomp   : Entity_Id;
3921       Posit   : Uint;
3922       Rectype : Entity_Id;
3923
3924       CR_Pragma : Node_Id := Empty;
3925       --  Points to N_Pragma node if Complete_Representation pragma present
3926
3927    begin
3928       if Ignore_Rep_Clauses then
3929          return;
3930       end if;
3931
3932       Find_Type (Ident);
3933       Rectype := Entity (Ident);
3934
3935       if Rectype = Any_Type
3936         or else Rep_Item_Too_Early (Rectype, N)
3937       then
3938          return;
3939       else
3940          Rectype := Underlying_Type (Rectype);
3941       end if;
3942
3943       --  First some basic error checks
3944
3945       if not Is_Record_Type (Rectype) then
3946          Error_Msg_NE
3947            ("record type required, found}", Ident, First_Subtype (Rectype));
3948          return;
3949
3950       elsif Scope (Rectype) /= Current_Scope then
3951          Error_Msg_N ("type must be declared in this scope", N);
3952          return;
3953
3954       elsif not Is_First_Subtype (Rectype) then
3955          Error_Msg_N ("cannot give record rep clause for subtype", N);
3956          return;
3957
3958       elsif Has_Record_Rep_Clause (Rectype) then
3959          Error_Msg_N ("duplicate record rep clause ignored", N);
3960          return;
3961
3962       elsif Rep_Item_Too_Late (Rectype, N) then
3963          return;
3964       end if;
3965
3966       if Present (Mod_Clause (N)) then
3967          declare
3968             Loc     : constant Source_Ptr := Sloc (N);
3969             M       : constant Node_Id := Mod_Clause (N);
3970             P       : constant List_Id := Pragmas_Before (M);
3971             AtM_Nod : Node_Id;
3972
3973             Mod_Val : Uint;
3974             pragma Warnings (Off, Mod_Val);
3975
3976          begin
3977             Check_Restriction (No_Obsolescent_Features, Mod_Clause (N));
3978
3979             if Warn_On_Obsolescent_Feature then
3980                Error_Msg_N
3981                  ("mod clause is an obsolescent feature (RM J.8)?", N);
3982                Error_Msg_N
3983                  ("\use alignment attribute definition clause instead?", N);
3984             end if;
3985
3986             if Present (P) then
3987                Analyze_List (P);
3988             end if;
3989
3990             --  In ASIS_Mode mode, expansion is disabled, but we must convert
3991             --  the Mod clause into an alignment clause anyway, so that the
3992             --  back-end can compute and back-annotate properly the size and
3993             --  alignment of types that may include this record.
3994
3995             --  This seems dubious, this destroys the source tree in a manner
3996             --  not detectable by ASIS ???
3997
3998             if Operating_Mode = Check_Semantics and then ASIS_Mode then
3999                AtM_Nod :=
4000                  Make_Attribute_Definition_Clause (Loc,
4001                    Name       => New_Reference_To (Base_Type (Rectype), Loc),
4002                    Chars      => Name_Alignment,
4003                    Expression => Relocate_Node (Expression (M)));
4004
4005                Set_From_At_Mod (AtM_Nod);
4006                Insert_After (N, AtM_Nod);
4007                Mod_Val := Get_Alignment_Value (Expression (AtM_Nod));
4008                Set_Mod_Clause (N, Empty);
4009
4010             else
4011                --  Get the alignment value to perform error checking
4012
4013                Mod_Val := Get_Alignment_Value (Expression (M));
4014             end if;
4015          end;
4016       end if;
4017
4018       --  For untagged types, clear any existing component clauses for the
4019       --  type. If the type is derived, this is what allows us to override
4020       --  a rep clause for the parent. For type extensions, the representation
4021       --  of the inherited components is inherited, so we want to keep previous
4022       --  component clauses for completeness.
4023
4024       if not Is_Tagged_Type (Rectype) then
4025          Comp := First_Component_Or_Discriminant (Rectype);
4026          while Present (Comp) loop
4027             Set_Component_Clause (Comp, Empty);
4028             Next_Component_Or_Discriminant (Comp);
4029          end loop;
4030       end if;
4031
4032       --  All done if no component clauses
4033
4034       CC := First (Component_Clauses (N));
4035
4036       if No (CC) then
4037          return;
4038       end if;
4039
4040       --  A representation like this applies to the base type
4041
4042       Set_Has_Record_Rep_Clause (Base_Type (Rectype));
4043       Set_Has_Non_Standard_Rep  (Base_Type (Rectype));
4044       Set_Has_Specified_Layout  (Base_Type (Rectype));
4045
4046       --  Process the component clauses
4047
4048       while Present (CC) loop
4049
4050          --  Pragma
4051
4052          if Nkind (CC) = N_Pragma then
4053             Analyze (CC);
4054
4055             --  The only pragma of interest is Complete_Representation
4056
4057             if Pragma_Name (CC) = Name_Complete_Representation then
4058                CR_Pragma := CC;
4059             end if;
4060
4061          --  Processing for real component clause
4062
4063          else
4064             Posit := Static_Integer (Position  (CC));
4065             Fbit  := Static_Integer (First_Bit (CC));
4066             Lbit  := Static_Integer (Last_Bit  (CC));
4067
4068             if Posit /= No_Uint
4069               and then Fbit /= No_Uint
4070               and then Lbit /= No_Uint
4071             then
4072                if Posit < 0 then
4073                   Error_Msg_N
4074                     ("position cannot be negative", Position (CC));
4075
4076                elsif Fbit < 0 then
4077                   Error_Msg_N
4078                     ("first bit cannot be negative", First_Bit (CC));
4079
4080                --  The Last_Bit specified in a component clause must not be
4081                --  less than the First_Bit minus one (RM-13.5.1(10)).
4082
4083                elsif Lbit < Fbit - 1 then
4084                   Error_Msg_N
4085                     ("last bit cannot be less than first bit minus one",
4086                      Last_Bit (CC));
4087
4088                --  Values look OK, so find the corresponding record component
4089                --  Even though the syntax allows an attribute reference for
4090                --  implementation-defined components, GNAT does not allow the
4091                --  tag to get an explicit position.
4092
4093                elsif Nkind (Component_Name (CC)) = N_Attribute_Reference then
4094                   if Attribute_Name (Component_Name (CC)) = Name_Tag then
4095                      Error_Msg_N ("position of tag cannot be specified", CC);
4096                   else
4097                      Error_Msg_N ("illegal component name", CC);
4098                   end if;
4099
4100                else
4101                   Comp := First_Entity (Rectype);
4102                   while Present (Comp) loop
4103                      exit when Chars (Comp) = Chars (Component_Name (CC));
4104                      Next_Entity (Comp);
4105                   end loop;
4106
4107                   if No (Comp) then
4108
4109                      --  Maybe component of base type that is absent from
4110                      --  statically constrained first subtype.
4111
4112                      Comp := First_Entity (Base_Type (Rectype));
4113                      while Present (Comp) loop
4114                         exit when Chars (Comp) = Chars (Component_Name (CC));
4115                         Next_Entity (Comp);
4116                      end loop;
4117                   end if;
4118
4119                   if No (Comp) then
4120                      Error_Msg_N
4121                        ("component clause is for non-existent field", CC);
4122
4123                   --  Ada 2012 (AI05-0026): Any name that denotes a
4124                   --  discriminant of an object of an unchecked union type
4125                   --  shall not occur within a record_representation_clause.
4126
4127                   --  The general restriction of using record rep clauses on
4128                   --  Unchecked_Union types has now been lifted. Since it is
4129                   --  possible to introduce a record rep clause which mentions
4130                   --  the discriminant of an Unchecked_Union in non-Ada 2012
4131                   --  code, this check is applied to all versions of the
4132                   --  language.
4133
4134                   elsif Ekind (Comp) = E_Discriminant
4135                     and then Is_Unchecked_Union (Rectype)
4136                   then
4137                      Error_Msg_N
4138                        ("cannot reference discriminant of Unchecked_Union",
4139                         Component_Name (CC));
4140
4141                   elsif Present (Component_Clause (Comp)) then
4142
4143                      --  Diagnose duplicate rep clause, or check consistency
4144                      --  if this is an inherited component. In a double fault,
4145                      --  there may be a duplicate inconsistent clause for an
4146                      --  inherited component.
4147
4148                      if Scope (Original_Record_Component (Comp)) = Rectype
4149                        or else Parent (Component_Clause (Comp)) = N
4150                      then
4151                         Error_Msg_Sloc := Sloc (Component_Clause (Comp));
4152                         Error_Msg_N ("component clause previously given#", CC);
4153
4154                      else
4155                         declare
4156                            Rep1 : constant Node_Id := Component_Clause (Comp);
4157                         begin
4158                            if Intval (Position (Rep1)) /=
4159                                                    Intval (Position (CC))
4160                              or else Intval (First_Bit (Rep1)) /=
4161                                                    Intval (First_Bit (CC))
4162                              or else Intval (Last_Bit (Rep1)) /=
4163                                                    Intval (Last_Bit (CC))
4164                            then
4165                               Error_Msg_N ("component clause inconsistent "
4166                                 & "with representation of ancestor", CC);
4167                            elsif Warn_On_Redundant_Constructs then
4168                               Error_Msg_N ("?redundant component clause "
4169                                 & "for inherited component!", CC);
4170                            end if;
4171                         end;
4172                      end if;
4173
4174                   --  Normal case where this is the first component clause we
4175                   --  have seen for this entity, so set it up properly.
4176
4177                   else
4178                      --  Make reference for field in record rep clause and set
4179                      --  appropriate entity field in the field identifier.
4180
4181                      Generate_Reference
4182                        (Comp, Component_Name (CC), Set_Ref => False);
4183                      Set_Entity (Component_Name (CC), Comp);
4184
4185                      --  Update Fbit and Lbit to the actual bit number
4186
4187                      Fbit := Fbit + UI_From_Int (SSU) * Posit;
4188                      Lbit := Lbit + UI_From_Int (SSU) * Posit;
4189
4190                      if Has_Size_Clause (Rectype)
4191                        and then RM_Size (Rectype) <= Lbit
4192                      then
4193                         Error_Msg_N
4194                           ("bit number out of range of specified size",
4195                            Last_Bit (CC));
4196                      else
4197                         Set_Component_Clause     (Comp, CC);
4198                         Set_Component_Bit_Offset (Comp, Fbit);
4199                         Set_Esize                (Comp, 1 + (Lbit - Fbit));
4200                         Set_Normalized_First_Bit (Comp, Fbit mod SSU);
4201                         Set_Normalized_Position  (Comp, Fbit / SSU);
4202
4203                         if Warn_On_Overridden_Size
4204                           and then Has_Size_Clause (Etype (Comp))
4205                           and then RM_Size (Etype (Comp)) /= Esize (Comp)
4206                         then
4207                            Error_Msg_NE
4208                              ("?component size overrides size clause for&",
4209                               Component_Name (CC), Etype (Comp));
4210                         end if;
4211
4212                         --  This information is also set in the corresponding
4213                         --  component of the base type, found by accessing the
4214                         --  Original_Record_Component link if it is present.
4215
4216                         Ocomp := Original_Record_Component (Comp);
4217
4218                         if Hbit < Lbit then
4219                            Hbit := Lbit;
4220                         end if;
4221
4222                         Check_Size
4223                           (Component_Name (CC),
4224                            Etype (Comp),
4225                            Esize (Comp),
4226                            Biased);
4227
4228                         Set_Biased
4229                           (Comp, First_Node (CC), "component clause", Biased);
4230
4231                         if Present (Ocomp) then
4232                            Set_Component_Clause     (Ocomp, CC);
4233                            Set_Component_Bit_Offset (Ocomp, Fbit);
4234                            Set_Normalized_First_Bit (Ocomp, Fbit mod SSU);
4235                            Set_Normalized_Position  (Ocomp, Fbit / SSU);
4236                            Set_Esize                (Ocomp, 1 + (Lbit - Fbit));
4237
4238                            Set_Normalized_Position_Max
4239                              (Ocomp, Normalized_Position (Ocomp));
4240
4241                            --  Note: we don't use Set_Biased here, because we
4242                            --  already gave a warning above if needed, and we
4243                            --  would get a duplicate for the same name here.
4244
4245                            Set_Has_Biased_Representation
4246                              (Ocomp, Has_Biased_Representation (Comp));
4247                         end if;
4248
4249                         if Esize (Comp) < 0 then
4250                            Error_Msg_N ("component size is negative", CC);
4251                         end if;
4252                      end if;
4253                   end if;
4254                end if;
4255             end if;
4256          end if;
4257
4258          Next (CC);
4259       end loop;
4260
4261       --  Check missing components if Complete_Representation pragma appeared
4262
4263       if Present (CR_Pragma) then
4264          Comp := First_Component_Or_Discriminant (Rectype);
4265          while Present (Comp) loop
4266             if No (Component_Clause (Comp)) then
4267                Error_Msg_NE
4268                  ("missing component clause for &", CR_Pragma, Comp);
4269             end if;
4270
4271             Next_Component_Or_Discriminant (Comp);
4272          end loop;
4273
4274          --  If no Complete_Representation pragma, warn if missing components
4275
4276       elsif Warn_On_Unrepped_Components then
4277          declare
4278             Num_Repped_Components   : Nat := 0;
4279             Num_Unrepped_Components : Nat := 0;
4280
4281          begin
4282             --  First count number of repped and unrepped components
4283
4284             Comp := First_Component_Or_Discriminant (Rectype);
4285             while Present (Comp) loop
4286                if Present (Component_Clause (Comp)) then
4287                   Num_Repped_Components := Num_Repped_Components + 1;
4288                else
4289                   Num_Unrepped_Components := Num_Unrepped_Components + 1;
4290                end if;
4291
4292                Next_Component_Or_Discriminant (Comp);
4293             end loop;
4294
4295             --  We are only interested in the case where there is at least one
4296             --  unrepped component, and at least half the components have rep
4297             --  clauses. We figure that if less than half have them, then the
4298             --  partial rep clause is really intentional. If the component
4299             --  type has no underlying type set at this point (as for a generic
4300             --  formal type), we don't know enough to give a warning on the
4301             --  component.
4302
4303             if Num_Unrepped_Components > 0
4304               and then Num_Unrepped_Components < Num_Repped_Components
4305             then
4306                Comp := First_Component_Or_Discriminant (Rectype);
4307                while Present (Comp) loop
4308                   if No (Component_Clause (Comp))
4309                     and then Comes_From_Source (Comp)
4310                     and then Present (Underlying_Type (Etype (Comp)))
4311                     and then (Is_Scalar_Type (Underlying_Type (Etype (Comp)))
4312                                or else Size_Known_At_Compile_Time
4313                                          (Underlying_Type (Etype (Comp))))
4314                     and then not Has_Warnings_Off (Rectype)
4315                   then
4316                      Error_Msg_Sloc := Sloc (Comp);
4317                      Error_Msg_NE
4318                        ("?no component clause given for & declared #",
4319                         N, Comp);
4320                   end if;
4321
4322                   Next_Component_Or_Discriminant (Comp);
4323                end loop;
4324             end if;
4325          end;
4326       end if;
4327    end Analyze_Record_Representation_Clause;
4328
4329    -------------------------------
4330    -- Build_Invariant_Procedure --
4331    -------------------------------
4332
4333    --  The procedure that is constructed here has the form
4334
4335    --  procedure typInvariant (Ixxx : typ) is
4336    --  begin
4337    --     pragma Check (Invariant, exp, "failed invariant from xxx");
4338    --     pragma Check (Invariant, exp, "failed invariant from xxx");
4339    --     ...
4340    --     pragma Check (Invariant, exp, "failed inherited invariant from xxx");
4341    --     ...
4342    --  end typInvariant;
4343
4344    procedure Build_Invariant_Procedure (Typ : Entity_Id; N : Node_Id) is
4345       Loc   : constant Source_Ptr := Sloc (Typ);
4346       Stmts : List_Id;
4347       Spec  : Node_Id;
4348       SId   : Entity_Id;
4349       PDecl : Node_Id;
4350       PBody : Node_Id;
4351
4352       Visible_Decls : constant List_Id := Visible_Declarations (N);
4353       Private_Decls : constant List_Id := Private_Declarations (N);
4354
4355       procedure Add_Invariants (T : Entity_Id; Inherit : Boolean);
4356       --  Appends statements to Stmts for any invariants in the rep item chain
4357       --  of the given type. If Inherit is False, then we only process entries
4358       --  on the chain for the type Typ. If Inherit is True, then we ignore any
4359       --  Invariant aspects, but we process all Invariant'Class aspects, adding
4360       --  "inherited" to the exception message and generating an informational
4361       --  message about the inheritance of an invariant.
4362
4363       Object_Name : constant Name_Id := New_Internal_Name ('I');
4364       --  Name for argument of invariant procedure
4365
4366       Object_Entity : constant Node_Id :=
4367                         Make_Defining_Identifier (Loc, Object_Name);
4368       --  The procedure declaration entity for the argument
4369
4370       --------------------
4371       -- Add_Invariants --
4372       --------------------
4373
4374       procedure Add_Invariants (T : Entity_Id; Inherit : Boolean) is
4375          Ritem : Node_Id;
4376          Arg1  : Node_Id;
4377          Arg2  : Node_Id;
4378          Arg3  : Node_Id;
4379          Exp   : Node_Id;
4380          Loc   : Source_Ptr;
4381          Assoc : List_Id;
4382          Str   : String_Id;
4383
4384          procedure Replace_Type_Reference (N : Node_Id);
4385          --  Replace a single occurrence N of the subtype name with a reference
4386          --  to the formal of the predicate function. N can be an identifier
4387          --  referencing the subtype, or a selected component, representing an
4388          --  appropriately qualified occurrence of the subtype name.
4389
4390          procedure Replace_Type_References is
4391            new Replace_Type_References_Generic (Replace_Type_Reference);
4392          --  Traverse an expression replacing all occurrences of the subtype
4393          --  name with appropriate references to the object that is the formal
4394          --  parameter of the predicate function. Note that we must ensure
4395          --  that the type and entity information is properly set in the
4396          --  replacement node, since we will do a Preanalyze call of this
4397          --  expression without proper visibility of the procedure argument.
4398
4399          ----------------------------
4400          -- Replace_Type_Reference --
4401          ----------------------------
4402
4403          procedure Replace_Type_Reference (N : Node_Id) is
4404          begin
4405             --  Invariant'Class, replace with T'Class (obj)
4406
4407             if Class_Present (Ritem) then
4408                Rewrite (N,
4409                  Make_Type_Conversion (Loc,
4410                    Subtype_Mark =>
4411                      Make_Attribute_Reference (Loc,
4412                        Prefix         => New_Occurrence_Of (T, Loc),
4413                        Attribute_Name => Name_Class),
4414                    Expression   => Make_Identifier (Loc, Object_Name)));
4415
4416                Set_Entity (Expression (N), Object_Entity);
4417                Set_Etype  (Expression (N), Typ);
4418
4419             --  Invariant, replace with obj
4420
4421             else
4422                Rewrite (N, Make_Identifier (Loc, Object_Name));
4423                Set_Entity (N, Object_Entity);
4424                Set_Etype  (N, Typ);
4425             end if;
4426          end Replace_Type_Reference;
4427
4428       --  Start of processing for Add_Invariants
4429
4430       begin
4431          Ritem := First_Rep_Item (T);
4432          while Present (Ritem) loop
4433             if Nkind (Ritem) = N_Pragma
4434               and then Pragma_Name (Ritem) = Name_Invariant
4435             then
4436                Arg1 := First (Pragma_Argument_Associations (Ritem));
4437                Arg2 := Next (Arg1);
4438                Arg3 := Next (Arg2);
4439
4440                Arg1 := Get_Pragma_Arg (Arg1);
4441                Arg2 := Get_Pragma_Arg (Arg2);
4442
4443                --  For Inherit case, ignore Invariant, process only Class case
4444
4445                if Inherit then
4446                   if not Class_Present (Ritem) then
4447                      goto Continue;
4448                   end if;
4449
4450                --  For Inherit false, process only item for right type
4451
4452                else
4453                   if Entity (Arg1) /= Typ then
4454                      goto Continue;
4455                   end if;
4456                end if;
4457
4458                if No (Stmts) then
4459                   Stmts := Empty_List;
4460                end if;
4461
4462                Exp := New_Copy_Tree (Arg2);
4463                Loc := Sloc (Exp);
4464
4465                --  We need to replace any occurrences of the name of the type
4466                --  with references to the object, converted to type'Class in
4467                --  the case of Invariant'Class aspects.
4468
4469                Replace_Type_References (Exp, Chars (T));
4470
4471                --  If this invariant comes from an aspect, find the aspect
4472                --  specification, and replace the saved expression because
4473                --  we need the subtype references replaced for the calls to
4474                --  Preanalyze_Spec_Expressin in Check_Aspect_At_Freeze_Point
4475                --  and Check_Aspect_At_End_Of_Declarations.
4476
4477                if From_Aspect_Specification (Ritem) then
4478                   declare
4479                      Aitem : Node_Id;
4480
4481                   begin
4482                      --  Loop to find corresponding aspect, note that this
4483                      --  must be present given the pragma is marked delayed.
4484
4485                      Aitem := Next_Rep_Item (Ritem);
4486                      while Present (Aitem) loop
4487                         if Nkind (Aitem) = N_Aspect_Specification
4488                           and then Aspect_Rep_Item (Aitem) = Ritem
4489                         then
4490                            Set_Entity
4491                              (Identifier (Aitem), New_Copy_Tree (Exp));
4492                            exit;
4493                         end if;
4494
4495                         Aitem := Next_Rep_Item (Aitem);
4496                      end loop;
4497                   end;
4498                end if;
4499
4500                --  Now we need to preanalyze the expression to properly capture
4501                --  the visibility in the visible part. The expression will not
4502                --  be analyzed for real until the body is analyzed, but that is
4503                --  at the end of the private part and has the wrong visibility.
4504
4505                Set_Parent (Exp, N);
4506                Preanalyze_Spec_Expression (Exp, Standard_Boolean);
4507
4508                --  Build first two arguments for Check pragma
4509
4510                Assoc := New_List (
4511                  Make_Pragma_Argument_Association (Loc,
4512                    Expression => Make_Identifier (Loc, Name_Invariant)),
4513                  Make_Pragma_Argument_Association (Loc, Expression => Exp));
4514
4515                --  Add message if present in Invariant pragma
4516
4517                if Present (Arg3) then
4518                   Str := Strval (Get_Pragma_Arg (Arg3));
4519
4520                   --  If inherited case, and message starts "failed invariant",
4521                   --  change it to be "failed inherited invariant".
4522
4523                   if Inherit then
4524                      String_To_Name_Buffer (Str);
4525
4526                      if Name_Buffer (1 .. 16) = "failed invariant" then
4527                         Insert_Str_In_Name_Buffer ("inherited ", 8);
4528                         Str := String_From_Name_Buffer;
4529                      end if;
4530                   end if;
4531
4532                   Append_To (Assoc,
4533                     Make_Pragma_Argument_Association (Loc,
4534                       Expression => Make_String_Literal (Loc, Str)));
4535                end if;
4536
4537                --  Add Check pragma to list of statements
4538
4539                Append_To (Stmts,
4540                  Make_Pragma (Loc,
4541                    Pragma_Identifier            =>
4542                      Make_Identifier (Loc, Name_Check),
4543                    Pragma_Argument_Associations => Assoc));
4544
4545                --  If Inherited case and option enabled, output info msg. Note
4546                --  that we know this is a case of Invariant'Class.
4547
4548                if Inherit and Opt.List_Inherited_Aspects then
4549                   Error_Msg_Sloc := Sloc (Ritem);
4550                   Error_Msg_N
4551                     ("?info: & inherits `Invariant''Class` aspect from #",
4552                      Typ);
4553                end if;
4554             end if;
4555
4556          <<Continue>>
4557             Next_Rep_Item (Ritem);
4558          end loop;
4559       end Add_Invariants;
4560
4561    --  Start of processing for Build_Invariant_Procedure
4562
4563    begin
4564       Stmts := No_List;
4565       PDecl := Empty;
4566       PBody := Empty;
4567       Set_Etype (Object_Entity, Typ);
4568
4569       --  Add invariants for the current type
4570
4571       Add_Invariants (Typ, Inherit => False);
4572
4573       --  Add invariants for parent types
4574
4575       declare
4576          Current_Typ : Entity_Id;
4577          Parent_Typ  : Entity_Id;
4578
4579       begin
4580          Current_Typ := Typ;
4581          loop
4582             Parent_Typ := Etype (Current_Typ);
4583
4584             if Is_Private_Type (Parent_Typ)
4585               and then Present (Full_View (Base_Type (Parent_Typ)))
4586             then
4587                Parent_Typ := Full_View (Base_Type (Parent_Typ));
4588             end if;
4589
4590             exit when Parent_Typ = Current_Typ;
4591
4592             Current_Typ := Parent_Typ;
4593             Add_Invariants (Current_Typ, Inherit => True);
4594          end loop;
4595       end;
4596
4597       --  Build the procedure if we generated at least one Check pragma
4598
4599       if Stmts /= No_List then
4600
4601          --  Build procedure declaration
4602
4603          SId :=
4604            Make_Defining_Identifier (Loc,
4605              Chars => New_External_Name (Chars (Typ), "Invariant"));
4606          Set_Has_Invariants (SId);
4607          Set_Invariant_Procedure (Typ, SId);
4608
4609          Spec :=
4610            Make_Procedure_Specification (Loc,
4611              Defining_Unit_Name       => SId,
4612              Parameter_Specifications => New_List (
4613                Make_Parameter_Specification (Loc,
4614                  Defining_Identifier => Object_Entity,
4615                  Parameter_Type      => New_Occurrence_Of (Typ, Loc))));
4616
4617          PDecl := Make_Subprogram_Declaration (Loc, Specification => Spec);
4618
4619          --  Build procedure body
4620
4621          SId :=
4622            Make_Defining_Identifier (Loc,
4623              Chars => New_External_Name (Chars (Typ), "Invariant"));
4624
4625          Spec :=
4626            Make_Procedure_Specification (Loc,
4627              Defining_Unit_Name       => SId,
4628              Parameter_Specifications => New_List (
4629                Make_Parameter_Specification (Loc,
4630                  Defining_Identifier =>
4631                    Make_Defining_Identifier (Loc, Object_Name),
4632                  Parameter_Type => New_Occurrence_Of (Typ, Loc))));
4633
4634          PBody :=
4635            Make_Subprogram_Body (Loc,
4636              Specification              => Spec,
4637              Declarations               => Empty_List,
4638              Handled_Statement_Sequence =>
4639                Make_Handled_Sequence_Of_Statements (Loc,
4640                  Statements => Stmts));
4641
4642          --  Insert procedure declaration and spec at the appropriate points.
4643          --  Skip this if there are no private declarations (that's an error
4644          --  that will be diagnosed elsewhere, and there is no point in having
4645          --  an invariant procedure set if the full declaration is missing).
4646
4647          if Present (Private_Decls) then
4648
4649             --  The spec goes at the end of visible declarations, but they have
4650             --  already been analyzed, so we need to explicitly do the analyze.
4651
4652             Append_To (Visible_Decls, PDecl);
4653             Analyze (PDecl);
4654
4655             --  The body goes at the end of the private declarations, which we
4656             --  have not analyzed yet, so we do not need to perform an explicit
4657             --  analyze call. We skip this if there are no private declarations
4658             --  (this is an error that will be caught elsewhere);
4659
4660             Append_To (Private_Decls, PBody);
4661          end if;
4662       end if;
4663    end Build_Invariant_Procedure;
4664
4665    ------------------------------
4666    -- Build_Predicate_Function --
4667    ------------------------------
4668
4669    --  The procedure that is constructed here has the form
4670
4671    --  function typPredicate (Ixxx : typ) return Boolean is
4672    --  begin
4673    --     return
4674    --        exp1 and then exp2 and then ...
4675    --        and then typ1Predicate (typ1 (Ixxx))
4676    --        and then typ2Predicate (typ2 (Ixxx))
4677    --        and then ...;
4678    --  end typPredicate;
4679
4680    --  Here exp1, and exp2 are expressions from Predicate pragmas. Note that
4681    --  this is the point at which these expressions get analyzed, providing the
4682    --  required delay, and typ1, typ2, are entities from which predicates are
4683    --  inherited. Note that we do NOT generate Check pragmas, that's because we
4684    --  use this function even if checks are off, e.g. for membership tests.
4685
4686    procedure Build_Predicate_Function (Typ : Entity_Id; N : Node_Id) is
4687       Loc  : constant Source_Ptr := Sloc (Typ);
4688       Spec : Node_Id;
4689       SId  : Entity_Id;
4690       FDecl : Node_Id;
4691       FBody : Node_Id;
4692
4693       Expr : Node_Id;
4694       --  This is the expression for the return statement in the function. It
4695       --  is build by connecting the component predicates with AND THEN.
4696
4697       procedure Add_Call (T : Entity_Id);
4698       --  Includes a call to the predicate function for type T in Expr if T
4699       --  has predicates and Predicate_Function (T) is non-empty.
4700
4701       procedure Add_Predicates;
4702       --  Appends expressions for any Predicate pragmas in the rep item chain
4703       --  Typ to Expr. Note that we look only at items for this exact entity.
4704       --  Inheritance of predicates for the parent type is done by calling the
4705       --  Predicate_Function of the parent type, using Add_Call above.
4706
4707       Object_Name : constant Name_Id := New_Internal_Name ('I');
4708       --  Name for argument of Predicate procedure
4709
4710       Object_Entity : constant Entity_Id :=
4711                         Make_Defining_Identifier (Loc, Object_Name);
4712       --  The entity for the spec entity for the argument
4713
4714       Dynamic_Predicate_Present : Boolean := False;
4715       --  Set True if a dynamic predicate is present, results in the entire
4716       --  predicate being considered dynamic even if it looks static
4717
4718       Static_Predicate_Present : Node_Id := Empty;
4719       --  Set to N_Pragma node for a static predicate if one is encountered.
4720
4721       --------------
4722       -- Add_Call --
4723       --------------
4724
4725       procedure Add_Call (T : Entity_Id) is
4726          Exp : Node_Id;
4727
4728       begin
4729          if Present (T) and then Present (Predicate_Function (T)) then
4730             Set_Has_Predicates (Typ);
4731
4732             --  Build the call to the predicate function of T
4733
4734             Exp :=
4735               Make_Predicate_Call
4736                 (T, Convert_To (T, Make_Identifier (Loc, Object_Name)));
4737
4738             --  Add call to evolving expression, using AND THEN if needed
4739
4740             if No (Expr) then
4741                Expr := Exp;
4742             else
4743                Expr :=
4744                  Make_And_Then (Loc,
4745                    Left_Opnd  => Relocate_Node (Expr),
4746                    Right_Opnd => Exp);
4747             end if;
4748
4749             --  Output info message on inheritance if required. Note we do not
4750             --  give this information for generic actual types, since it is
4751             --  unwelcome noise in that case in instantiations. We also
4752             --  generally suppress the message in instantiations, and also
4753             --  if it involves internal names.
4754
4755             if Opt.List_Inherited_Aspects
4756               and then not Is_Generic_Actual_Type (Typ)
4757               and then Instantiation_Depth (Sloc (Typ)) = 0
4758               and then not Is_Internal_Name (Chars (T))
4759               and then not Is_Internal_Name (Chars (Typ))
4760             then
4761                Error_Msg_Sloc := Sloc (Predicate_Function (T));
4762                Error_Msg_Node_2 := T;
4763                Error_Msg_N ("?info: & inherits predicate from & #", Typ);
4764             end if;
4765          end if;
4766       end Add_Call;
4767
4768       --------------------
4769       -- Add_Predicates --
4770       --------------------
4771
4772       procedure Add_Predicates is
4773          Ritem : Node_Id;
4774          Arg1  : Node_Id;
4775          Arg2  : Node_Id;
4776
4777          procedure Replace_Type_Reference (N : Node_Id);
4778          --  Replace a single occurrence N of the subtype name with a reference
4779          --  to the formal of the predicate function. N can be an identifier
4780          --  referencing the subtype, or a selected component, representing an
4781          --  appropriately qualified occurrence of the subtype name.
4782
4783          procedure Replace_Type_References is
4784            new Replace_Type_References_Generic (Replace_Type_Reference);
4785          --  Traverse an expression changing every occurrence of an identifier
4786          --  whose name matches the name of the subtype with a reference to
4787          --  the formal parameter of the predicate function.
4788
4789          ----------------------------
4790          -- Replace_Type_Reference --
4791          ----------------------------
4792
4793          procedure Replace_Type_Reference (N : Node_Id) is
4794          begin
4795             Rewrite (N, Make_Identifier (Loc, Object_Name));
4796             Set_Entity (N, Object_Entity);
4797             Set_Etype (N, Typ);
4798          end Replace_Type_Reference;
4799
4800       --  Start of processing for Add_Predicates
4801
4802       begin
4803          Ritem := First_Rep_Item (Typ);
4804          while Present (Ritem) loop
4805             if Nkind (Ritem) = N_Pragma
4806               and then Pragma_Name (Ritem) = Name_Predicate
4807             then
4808                if Present (Corresponding_Aspect (Ritem)) then
4809                   case Chars (Identifier (Corresponding_Aspect (Ritem))) is
4810                      when Name_Dynamic_Predicate =>
4811                         Dynamic_Predicate_Present := True;
4812                      when Name_Static_Predicate =>
4813                         Static_Predicate_Present := Ritem;
4814                      when others =>
4815                         null;
4816                   end case;
4817                end if;
4818
4819                --  Acquire arguments
4820
4821                Arg1 := First (Pragma_Argument_Associations (Ritem));
4822                Arg2 := Next (Arg1);
4823
4824                Arg1 := Get_Pragma_Arg (Arg1);
4825                Arg2 := Get_Pragma_Arg (Arg2);
4826
4827                --  See if this predicate pragma is for the current type or for
4828                --  its full view. A predicate on a private completion is placed
4829                --  on the partial view beause this is the visible entity that
4830                --  is frozen.
4831
4832                if Entity (Arg1) = Typ
4833                  or else Full_View (Entity (Arg1)) = Typ
4834                then
4835
4836                   --  We have a match, this entry is for our subtype
4837
4838                   --  We need to replace any occurrences of the name of the
4839                   --  type with references to the object.
4840
4841                   Replace_Type_References (Arg2, Chars (Typ));
4842
4843                   --  If this predicate comes from an aspect, find the aspect
4844                   --  specification, and replace the saved expression because
4845                   --  we need the subtype references replaced for the calls to
4846                   --  Preanalyze_Spec_Expressin in Check_Aspect_At_Freeze_Point
4847                   --  and Check_Aspect_At_End_Of_Declarations.
4848
4849                   if From_Aspect_Specification (Ritem) then
4850                      declare
4851                         Aitem : Node_Id;
4852
4853                      begin
4854                         --  Loop to find corresponding aspect, note that this
4855                         --  must be present given the pragma is marked delayed.
4856
4857                         Aitem := Next_Rep_Item (Ritem);
4858                         loop
4859                            if Nkind (Aitem) = N_Aspect_Specification
4860                              and then Aspect_Rep_Item (Aitem) = Ritem
4861                            then
4862                               Set_Entity
4863                                 (Identifier (Aitem), New_Copy_Tree (Arg2));
4864                               exit;
4865                            end if;
4866
4867                            Aitem := Next_Rep_Item (Aitem);
4868                         end loop;
4869                      end;
4870                   end if;
4871
4872                   --  Now we can add the expression
4873
4874                   if No (Expr) then
4875                      Expr := Relocate_Node (Arg2);
4876
4877                   --  There already was a predicate, so add to it
4878
4879                   else
4880                      Expr :=
4881                        Make_And_Then (Loc,
4882                          Left_Opnd  => Relocate_Node (Expr),
4883                          Right_Opnd => Relocate_Node (Arg2));
4884                   end if;
4885                end if;
4886             end if;
4887
4888             Next_Rep_Item (Ritem);
4889          end loop;
4890       end Add_Predicates;
4891
4892    --  Start of processing for Build_Predicate_Function
4893
4894    begin
4895       --  Initialize for construction of statement list
4896
4897       Expr := Empty;
4898
4899       --  Return if already built or if type does not have predicates
4900
4901       if not Has_Predicates (Typ)
4902         or else Present (Predicate_Function (Typ))
4903       then
4904          return;
4905       end if;
4906
4907       --  Add Predicates for the current type
4908
4909       Add_Predicates;
4910
4911       --  Add predicates for ancestor if present
4912
4913       declare
4914          Atyp : constant Entity_Id := Nearest_Ancestor (Typ);
4915       begin
4916          if Present (Atyp) then
4917             Add_Call (Atyp);
4918          end if;
4919       end;
4920
4921       --  If we have predicates, build the function
4922
4923       if Present (Expr) then
4924
4925          --  Build function declaration
4926
4927          pragma Assert (Has_Predicates (Typ));
4928          SId :=
4929            Make_Defining_Identifier (Loc,
4930              Chars => New_External_Name (Chars (Typ), "Predicate"));
4931          Set_Has_Predicates (SId);
4932          Set_Predicate_Function (Typ, SId);
4933
4934          Spec :=
4935            Make_Function_Specification (Loc,
4936              Defining_Unit_Name       => SId,
4937              Parameter_Specifications => New_List (
4938                Make_Parameter_Specification (Loc,
4939                  Defining_Identifier => Object_Entity,
4940                  Parameter_Type      => New_Occurrence_Of (Typ, Loc))),
4941              Result_Definition        =>
4942                New_Occurrence_Of (Standard_Boolean, Loc));
4943
4944          FDecl := Make_Subprogram_Declaration (Loc, Specification => Spec);
4945
4946          --  Build function body
4947
4948          SId :=
4949            Make_Defining_Identifier (Loc,
4950              Chars => New_External_Name (Chars (Typ), "Predicate"));
4951
4952          Spec :=
4953            Make_Function_Specification (Loc,
4954              Defining_Unit_Name       => SId,
4955              Parameter_Specifications => New_List (
4956                Make_Parameter_Specification (Loc,
4957                  Defining_Identifier =>
4958                    Make_Defining_Identifier (Loc, Object_Name),
4959                  Parameter_Type =>
4960                    New_Occurrence_Of (Typ, Loc))),
4961              Result_Definition        =>
4962                New_Occurrence_Of (Standard_Boolean, Loc));
4963
4964          FBody :=
4965            Make_Subprogram_Body (Loc,
4966              Specification              => Spec,
4967              Declarations               => Empty_List,
4968              Handled_Statement_Sequence =>
4969                Make_Handled_Sequence_Of_Statements (Loc,
4970                  Statements => New_List (
4971                    Make_Simple_Return_Statement (Loc,
4972                      Expression => Expr))));
4973
4974          --  Insert declaration before freeze node and body after
4975
4976          Insert_Before_And_Analyze (N, FDecl);
4977          Insert_After_And_Analyze  (N, FBody);
4978
4979          --  Deal with static predicate case
4980
4981          if Ekind_In (Typ, E_Enumeration_Subtype,
4982                            E_Modular_Integer_Subtype,
4983                            E_Signed_Integer_Subtype)
4984            and then Is_Static_Subtype (Typ)
4985            and then not Dynamic_Predicate_Present
4986          then
4987             Build_Static_Predicate (Typ, Expr, Object_Name);
4988
4989             if Present (Static_Predicate_Present)
4990               and No (Static_Predicate (Typ))
4991             then
4992                Error_Msg_F
4993                  ("expression does not have required form for "
4994                   & "static predicate",
4995                   Next (First (Pragma_Argument_Associations
4996                                 (Static_Predicate_Present))));
4997             end if;
4998          end if;
4999       end if;
5000    end Build_Predicate_Function;
5001
5002    ----------------------------
5003    -- Build_Static_Predicate --
5004    ----------------------------
5005
5006    procedure Build_Static_Predicate
5007      (Typ  : Entity_Id;
5008       Expr : Node_Id;
5009       Nam  : Name_Id)
5010    is
5011       Loc : constant Source_Ptr := Sloc (Expr);
5012
5013       Non_Static : exception;
5014       --  Raised if something non-static is found
5015
5016       Btyp : constant Entity_Id := Base_Type (Typ);
5017
5018       BLo : constant Uint := Expr_Value (Type_Low_Bound  (Btyp));
5019       BHi : constant Uint := Expr_Value (Type_High_Bound (Btyp));
5020       --  Low bound and high bound value of base type of Typ
5021
5022       TLo : constant Uint := Expr_Value (Type_Low_Bound  (Typ));
5023       THi : constant Uint := Expr_Value (Type_High_Bound (Typ));
5024       --  Low bound and high bound values of static subtype Typ
5025
5026       type REnt is record
5027          Lo, Hi : Uint;
5028       end record;
5029       --  One entry in a Rlist value, a single REnt (range entry) value
5030       --  denotes one range from Lo to Hi. To represent a single value
5031       --  range Lo = Hi = value.
5032
5033       type RList is array (Nat range <>) of REnt;
5034       --  A list of ranges. The ranges are sorted in increasing order,
5035       --  and are disjoint (there is a gap of at least one value between
5036       --  each range in the table). A value is in the set of ranges in
5037       --  Rlist if it lies within one of these ranges
5038
5039       False_Range : constant RList :=
5040                       RList'(1 .. 0 => REnt'(No_Uint, No_Uint));
5041       --  An empty set of ranges represents a range list that can never be
5042       --  satisfied, since there are no ranges in which the value could lie,
5043       --  so it does not lie in any of them. False_Range is a canonical value
5044       --  for this empty set, but general processing should test for an Rlist
5045       --  with length zero (see Is_False predicate), since other null ranges
5046       --  may appear which must be treated as False.
5047
5048       True_Range : constant RList := RList'(1 => REnt'(BLo, BHi));
5049       --  Range representing True, value must be in the base range
5050
5051       function "and" (Left, Right : RList) return RList;
5052       --  And's together two range lists, returning a range list. This is
5053       --  a set intersection operation.
5054
5055       function "or" (Left, Right : RList) return RList;
5056       --  Or's together two range lists, returning a range list. This is a
5057       --  set union operation.
5058
5059       function "not" (Right : RList) return RList;
5060       --  Returns complement of a given range list, i.e. a range list
5061       --  representing all the values in TLo .. THi that are not in the
5062       --  input operand Right.
5063
5064       function Build_Val (V : Uint) return Node_Id;
5065       --  Return an analyzed N_Identifier node referencing this value, suitable
5066       --  for use as an entry in the Static_Predicate list. This node is typed
5067       --  with the base type.
5068
5069       function Build_Range (Lo, Hi : Uint) return Node_Id;
5070       --  Return an analyzed N_Range node referencing this range, suitable
5071       --  for use as an entry in the Static_Predicate list. This node is typed
5072       --  with the base type.
5073
5074       function Get_RList (Exp : Node_Id) return RList;
5075       --  This is a recursive routine that converts the given expression into
5076       --  a list of ranges, suitable for use in building the static predicate.
5077
5078       function Is_False (R : RList) return Boolean;
5079       pragma Inline (Is_False);
5080       --  Returns True if the given range list is empty, and thus represents
5081       --  a False list of ranges that can never be satisfied.
5082
5083       function Is_True (R : RList) return Boolean;
5084       --  Returns True if R trivially represents the True predicate by having
5085       --  a single range from BLo to BHi.
5086
5087       function Is_Type_Ref (N : Node_Id) return Boolean;
5088       pragma Inline (Is_Type_Ref);
5089       --  Returns if True if N is a reference to the type for the predicate in
5090       --  the expression (i.e. if it is an identifier whose Chars field matches
5091       --  the Nam given in the call).
5092
5093       function Lo_Val (N : Node_Id) return Uint;
5094       --  Given static expression or static range from a Static_Predicate list,
5095       --  gets expression value or low bound of range.
5096
5097       function Hi_Val (N : Node_Id) return Uint;
5098       --  Given static expression or static range from a Static_Predicate list,
5099       --  gets expression value of high bound of range.
5100
5101       function Membership_Entry (N : Node_Id) return RList;
5102       --  Given a single membership entry (range, value, or subtype), returns
5103       --  the corresponding range list. Raises Static_Error if not static.
5104
5105       function Membership_Entries (N : Node_Id) return RList;
5106       --  Given an element on an alternatives list of a membership operation,
5107       --  returns the range list corresponding to this entry and all following
5108       --  entries (i.e. returns the "or" of this list of values).
5109
5110       function Stat_Pred (Typ : Entity_Id) return RList;
5111       --  Given a type, if it has a static predicate, then return the predicate
5112       --  as a range list, otherwise raise Non_Static.
5113
5114       -----------
5115       -- "and" --
5116       -----------
5117
5118       function "and" (Left, Right : RList) return RList is
5119          FEnt : REnt;
5120          --  First range of result
5121
5122          SLeft : Nat := Left'First;
5123          --  Start of rest of left entries
5124
5125          SRight : Nat := Right'First;
5126          --  Start of rest of right entries
5127
5128       begin
5129          --  If either range is True, return the other
5130
5131          if Is_True (Left) then
5132             return Right;
5133          elsif Is_True (Right) then
5134             return Left;
5135          end if;
5136
5137          --  If either range is False, return False
5138
5139          if Is_False (Left) or else Is_False (Right) then
5140             return False_Range;
5141          end if;
5142
5143          --  Loop to remove entries at start that are disjoint, and thus
5144          --  just get discarded from the result entirely.
5145
5146          loop
5147             --  If no operands left in either operand, result is false
5148
5149             if SLeft > Left'Last or else SRight > Right'Last then
5150                return False_Range;
5151
5152             --  Discard first left operand entry if disjoint with right
5153
5154             elsif Left (SLeft).Hi < Right (SRight).Lo then
5155                SLeft := SLeft + 1;
5156
5157             --  Discard first right operand entry if disjoint with left
5158
5159             elsif Right (SRight).Hi < Left (SLeft).Lo then
5160                SRight := SRight + 1;
5161
5162             --  Otherwise we have an overlapping entry
5163
5164             else
5165                exit;
5166             end if;
5167          end loop;
5168
5169          --  Now we have two non-null operands, and first entries overlap.
5170          --  The first entry in the result will be the overlapping part of
5171          --  these two entries.
5172
5173          FEnt := REnt'(Lo => UI_Max (Left (SLeft).Lo, Right (SRight).Lo),
5174                        Hi => UI_Min (Left (SLeft).Hi, Right (SRight).Hi));
5175
5176          --  Now we can remove the entry that ended at a lower value, since
5177          --  its contribution is entirely contained in Fent.
5178
5179          if Left (SLeft).Hi <= Right (SRight).Hi then
5180             SLeft := SLeft + 1;
5181          else
5182             SRight := SRight + 1;
5183          end if;
5184
5185          --  Compute result by concatenating this first entry with the "and"
5186          --  of the remaining parts of the left and right operands. Note that
5187          --  if either of these is empty, "and" will yield empty, so that we
5188          --  will end up with just Fent, which is what we want in that case.
5189
5190          return
5191            FEnt & (Left (SLeft .. Left'Last) and Right (SRight .. Right'Last));
5192       end "and";
5193
5194       -----------
5195       -- "not" --
5196       -----------
5197
5198       function "not" (Right : RList) return RList is
5199       begin
5200          --  Return True if False range
5201
5202          if Is_False (Right) then
5203             return True_Range;
5204          end if;
5205
5206          --  Return False if True range
5207
5208          if Is_True (Right) then
5209             return False_Range;
5210          end if;
5211
5212          --  Here if not trivial case
5213
5214          declare
5215             Result : RList (1 .. Right'Length + 1);
5216             --  May need one more entry for gap at beginning and end
5217
5218             Count : Nat := 0;
5219             --  Number of entries stored in Result
5220
5221          begin
5222             --  Gap at start
5223
5224             if Right (Right'First).Lo > TLo then
5225                Count := Count + 1;
5226                Result (Count) := REnt'(TLo, Right (Right'First).Lo - 1);
5227             end if;
5228
5229             --  Gaps between ranges
5230
5231             for J in Right'First .. Right'Last - 1 loop
5232                Count := Count + 1;
5233                Result (Count) :=
5234                  REnt'(Right (J).Hi + 1, Right (J + 1).Lo - 1);
5235             end loop;
5236
5237             --  Gap at end
5238
5239             if Right (Right'Last).Hi < THi then
5240                Count := Count + 1;
5241                Result (Count) := REnt'(Right (Right'Last).Hi + 1, THi);
5242             end if;
5243
5244             return Result (1 .. Count);
5245          end;
5246       end "not";
5247
5248       ----------
5249       -- "or" --
5250       ----------
5251
5252       function "or" (Left, Right : RList) return RList is
5253          FEnt : REnt;
5254          --  First range of result
5255
5256          SLeft : Nat := Left'First;
5257          --  Start of rest of left entries
5258
5259          SRight : Nat := Right'First;
5260          --  Start of rest of right entries
5261
5262       begin
5263          --  If either range is True, return True
5264
5265          if Is_True (Left) or else Is_True (Right) then
5266             return True_Range;
5267          end if;
5268
5269          --  If either range is False (empty), return the other
5270
5271          if Is_False (Left) then
5272             return Right;
5273          elsif Is_False (Right) then
5274             return Left;
5275          end if;
5276
5277          --  Initialize result first entry from left or right operand
5278          --  depending on which starts with the lower range.
5279
5280          if Left (SLeft).Lo < Right (SRight).Lo then
5281             FEnt := Left (SLeft);
5282             SLeft := SLeft + 1;
5283          else
5284             FEnt := Right (SRight);
5285             SRight := SRight + 1;
5286          end if;
5287
5288          --  This loop eats ranges from left and right operands that
5289          --  are contiguous with the first range we are gathering.
5290
5291          loop
5292             --  Eat first entry in left operand if contiguous or
5293             --  overlapped by gathered first operand of result.
5294
5295             if SLeft <= Left'Last
5296               and then Left (SLeft).Lo <= FEnt.Hi + 1
5297             then
5298                FEnt.Hi := UI_Max (FEnt.Hi, Left (SLeft).Hi);
5299                SLeft := SLeft + 1;
5300
5301                --  Eat first entry in right operand if contiguous or
5302                --  overlapped by gathered right operand of result.
5303
5304             elsif SRight <= Right'Last
5305               and then Right (SRight).Lo <= FEnt.Hi + 1
5306             then
5307                FEnt.Hi := UI_Max (FEnt.Hi, Right (SRight).Hi);
5308                SRight := SRight + 1;
5309
5310                --  All done if no more entries to eat!
5311
5312             else
5313                exit;
5314             end if;
5315          end loop;
5316
5317          --  Obtain result as the first entry we just computed, concatenated
5318          --  to the "or" of the remaining results (if one operand is empty,
5319          --  this will just concatenate with the other
5320
5321          return
5322            FEnt & (Left (SLeft .. Left'Last) or Right (SRight .. Right'Last));
5323       end "or";
5324
5325       -----------------
5326       -- Build_Range --
5327       -----------------
5328
5329       function Build_Range (Lo, Hi : Uint) return Node_Id is
5330          Result : Node_Id;
5331       begin
5332          if Lo = Hi then
5333             return Build_Val (Hi);
5334          else
5335             Result :=
5336               Make_Range (Loc,
5337                 Low_Bound  => Build_Val (Lo),
5338                 High_Bound => Build_Val (Hi));
5339             Set_Etype (Result, Btyp);
5340             Set_Analyzed (Result);
5341             return Result;
5342          end if;
5343       end Build_Range;
5344
5345       ---------------
5346       -- Build_Val --
5347       ---------------
5348
5349       function Build_Val (V : Uint) return Node_Id is
5350          Result : Node_Id;
5351
5352       begin
5353          if Is_Enumeration_Type (Typ) then
5354             Result := Get_Enum_Lit_From_Pos (Typ, V, Loc);
5355          else
5356             Result := Make_Integer_Literal (Loc, V);
5357          end if;
5358
5359          Set_Etype (Result, Btyp);
5360          Set_Is_Static_Expression (Result);
5361          Set_Analyzed (Result);
5362          return Result;
5363       end Build_Val;
5364
5365       ---------------
5366       -- Get_RList --
5367       ---------------
5368
5369       function Get_RList (Exp : Node_Id) return RList is
5370          Op  : Node_Kind;
5371          Val : Uint;
5372
5373       begin
5374          --  Static expression can only be true or false
5375
5376          if Is_OK_Static_Expression (Exp) then
5377
5378             --  For False
5379
5380             if Expr_Value (Exp) = 0 then
5381                return False_Range;
5382             else
5383                return True_Range;
5384             end if;
5385          end if;
5386
5387          --  Otherwise test node type
5388
5389          Op := Nkind (Exp);
5390
5391          case Op is
5392
5393             --  And
5394
5395             when N_Op_And | N_And_Then =>
5396                return Get_RList (Left_Opnd (Exp))
5397                         and
5398                       Get_RList (Right_Opnd (Exp));
5399
5400             --  Or
5401
5402             when N_Op_Or | N_Or_Else =>
5403                return Get_RList (Left_Opnd (Exp))
5404                         or
5405                       Get_RList (Right_Opnd (Exp));
5406
5407             --  Not
5408
5409             when N_Op_Not =>
5410                return not Get_RList (Right_Opnd (Exp));
5411
5412             --  Comparisons of type with static value
5413
5414             when N_Op_Compare =>
5415                --  Type is left operand
5416
5417                if Is_Type_Ref (Left_Opnd (Exp))
5418                  and then Is_OK_Static_Expression (Right_Opnd (Exp))
5419                then
5420                   Val := Expr_Value (Right_Opnd (Exp));
5421
5422                   --  Typ is right operand
5423
5424                elsif Is_Type_Ref (Right_Opnd (Exp))
5425                  and then Is_OK_Static_Expression (Left_Opnd (Exp))
5426                then
5427                   Val := Expr_Value (Left_Opnd (Exp));
5428
5429                   --  Invert sense of comparison
5430
5431                   case Op is
5432                      when N_Op_Gt => Op := N_Op_Lt;
5433                      when N_Op_Lt => Op := N_Op_Gt;
5434                      when N_Op_Ge => Op := N_Op_Le;
5435                      when N_Op_Le => Op := N_Op_Ge;
5436                      when others  => null;
5437                   end case;
5438
5439                   --  Other cases are non-static
5440
5441                else
5442                   raise Non_Static;
5443                end if;
5444
5445                --  Construct range according to comparison operation
5446
5447                case Op is
5448                   when N_Op_Eq =>
5449                      return RList'(1 => REnt'(Val, Val));
5450
5451                   when N_Op_Ge =>
5452                      return RList'(1 => REnt'(Val, BHi));
5453
5454                   when N_Op_Gt =>
5455                      return RList'(1 => REnt'(Val + 1, BHi));
5456
5457                   when N_Op_Le =>
5458                      return RList'(1 => REnt'(BLo, Val));
5459
5460                   when N_Op_Lt =>
5461                      return RList'(1 => REnt'(BLo, Val - 1));
5462
5463                   when N_Op_Ne =>
5464                      return RList'(REnt'(BLo, Val - 1),
5465                                    REnt'(Val + 1, BHi));
5466
5467                   when others  =>
5468                      raise Program_Error;
5469                end case;
5470
5471             --  Membership (IN)
5472
5473             when N_In =>
5474                if not Is_Type_Ref (Left_Opnd (Exp)) then
5475                   raise Non_Static;
5476                end if;
5477
5478                if Present (Right_Opnd (Exp)) then
5479                   return Membership_Entry (Right_Opnd (Exp));
5480                else
5481                   return Membership_Entries (First (Alternatives (Exp)));
5482                end if;
5483
5484             --  Negative membership (NOT IN)
5485
5486             when N_Not_In =>
5487                if not Is_Type_Ref (Left_Opnd (Exp)) then
5488                   raise Non_Static;
5489                end if;
5490
5491                if Present (Right_Opnd (Exp)) then
5492                   return not Membership_Entry (Right_Opnd (Exp));
5493                else
5494                   return not Membership_Entries (First (Alternatives (Exp)));
5495                end if;
5496
5497             --  Function call, may be call to static predicate
5498
5499             when N_Function_Call =>
5500                if Is_Entity_Name (Name (Exp)) then
5501                   declare
5502                      Ent : constant Entity_Id := Entity (Name (Exp));
5503                   begin
5504                      if Has_Predicates (Ent) then
5505                         return Stat_Pred (Etype (First_Formal (Ent)));
5506                      end if;
5507                   end;
5508                end if;
5509
5510                --  Other function call cases are non-static
5511
5512                raise Non_Static;
5513
5514             --  Qualified expression, dig out the expression
5515
5516             when N_Qualified_Expression =>
5517                return Get_RList (Expression (Exp));
5518
5519             --  Xor operator
5520
5521             when N_Op_Xor =>
5522                return (Get_RList (Left_Opnd (Exp))
5523                         and not Get_RList (Right_Opnd (Exp)))
5524                  or   (Get_RList (Right_Opnd (Exp))
5525                         and not Get_RList (Left_Opnd (Exp)));
5526
5527             --  Any other node type is non-static
5528
5529             when others =>
5530                raise Non_Static;
5531          end case;
5532       end Get_RList;
5533
5534       ------------
5535       -- Hi_Val --
5536       ------------
5537
5538       function Hi_Val (N : Node_Id) return Uint is
5539       begin
5540          if Is_Static_Expression (N) then
5541             return Expr_Value (N);
5542          else
5543             pragma Assert (Nkind (N) = N_Range);
5544             return Expr_Value (High_Bound (N));
5545          end if;
5546       end Hi_Val;
5547
5548       --------------
5549       -- Is_False --
5550       --------------
5551
5552       function Is_False (R : RList) return Boolean is
5553       begin
5554          return R'Length = 0;
5555       end Is_False;
5556
5557       -------------
5558       -- Is_True --
5559       -------------
5560
5561       function Is_True (R : RList) return Boolean is
5562       begin
5563          return R'Length = 1
5564            and then R (R'First).Lo = BLo
5565            and then R (R'First).Hi = BHi;
5566       end Is_True;
5567
5568       -----------------
5569       -- Is_Type_Ref --
5570       -----------------
5571
5572       function Is_Type_Ref (N : Node_Id) return Boolean is
5573       begin
5574          return Nkind (N) = N_Identifier and then Chars (N) = Nam;
5575       end Is_Type_Ref;
5576
5577       ------------
5578       -- Lo_Val --
5579       ------------
5580
5581       function Lo_Val (N : Node_Id) return Uint is
5582       begin
5583          if Is_Static_Expression (N) then
5584             return Expr_Value (N);
5585          else
5586             pragma Assert (Nkind (N) = N_Range);
5587             return Expr_Value (Low_Bound (N));
5588          end if;
5589       end Lo_Val;
5590
5591       ------------------------
5592       -- Membership_Entries --
5593       ------------------------
5594
5595       function Membership_Entries (N : Node_Id) return RList is
5596       begin
5597          if No (Next (N)) then
5598             return Membership_Entry (N);
5599          else
5600             return Membership_Entry (N) or Membership_Entries (Next (N));
5601          end if;
5602       end Membership_Entries;
5603
5604       ----------------------
5605       -- Membership_Entry --
5606       ----------------------
5607
5608       function Membership_Entry (N : Node_Id) return RList is
5609          Val : Uint;
5610          SLo : Uint;
5611          SHi : Uint;
5612
5613       begin
5614          --  Range case
5615
5616          if Nkind (N) = N_Range then
5617             if not Is_Static_Expression (Low_Bound (N))
5618                  or else
5619                not Is_Static_Expression (High_Bound (N))
5620             then
5621                raise Non_Static;
5622             else
5623                SLo := Expr_Value (Low_Bound  (N));
5624                SHi := Expr_Value (High_Bound (N));
5625                return RList'(1 => REnt'(SLo, SHi));
5626             end if;
5627
5628          --  Static expression case
5629
5630          elsif Is_Static_Expression (N) then
5631             Val := Expr_Value (N);
5632             return RList'(1 => REnt'(Val, Val));
5633
5634          --  Identifier (other than static expression) case
5635
5636          else pragma Assert (Nkind (N) = N_Identifier);
5637
5638             --  Type case
5639
5640             if Is_Type (Entity (N)) then
5641
5642                --  If type has predicates, process them
5643
5644                if Has_Predicates (Entity (N)) then
5645                   return Stat_Pred (Entity (N));
5646
5647                --  For static subtype without predicates, get range
5648
5649                elsif Is_Static_Subtype (Entity (N)) then
5650                   SLo := Expr_Value (Type_Low_Bound  (Entity (N)));
5651                   SHi := Expr_Value (Type_High_Bound (Entity (N)));
5652                   return RList'(1 => REnt'(SLo, SHi));
5653
5654                --  Any other type makes us non-static
5655
5656                else
5657                   raise Non_Static;
5658                end if;
5659
5660             --  Any other kind of identifier in predicate (e.g. a non-static
5661             --  expression value) means this is not a static predicate.
5662
5663             else
5664                raise Non_Static;
5665             end if;
5666          end if;
5667       end Membership_Entry;
5668
5669       ---------------
5670       -- Stat_Pred --
5671       ---------------
5672
5673       function Stat_Pred (Typ : Entity_Id) return RList is
5674       begin
5675          --  Not static if type does not have static predicates
5676
5677          if not Has_Predicates (Typ)
5678            or else No (Static_Predicate (Typ))
5679          then
5680             raise Non_Static;
5681          end if;
5682
5683          --  Otherwise we convert the predicate list to a range list
5684
5685          declare
5686             Result : RList (1 .. List_Length (Static_Predicate (Typ)));
5687             P      : Node_Id;
5688
5689          begin
5690             P := First (Static_Predicate (Typ));
5691             for J in Result'Range loop
5692                Result (J) := REnt'(Lo_Val (P), Hi_Val (P));
5693                Next (P);
5694             end loop;
5695
5696             return Result;
5697          end;
5698       end Stat_Pred;
5699
5700    --  Start of processing for Build_Static_Predicate
5701
5702    begin
5703       --  Now analyze the expression to see if it is a static predicate
5704
5705       declare
5706          Ranges : constant RList := Get_RList (Expr);
5707          --  Range list from expression if it is static
5708
5709          Plist : List_Id;
5710
5711       begin
5712          --  Convert range list into a form for the static predicate. In the
5713          --  Ranges array, we just have raw ranges, these must be converted
5714          --  to properly typed and analyzed static expressions or range nodes.
5715
5716          --  Note: here we limit ranges to the ranges of the subtype, so that
5717          --  a predicate is always false for values outside the subtype. That
5718          --  seems fine, such values are invalid anyway, and considering them
5719          --  to fail the predicate seems allowed and friendly, and furthermore
5720          --  simplifies processing for case statements and loops.
5721
5722          Plist := New_List;
5723
5724          for J in Ranges'Range loop
5725             declare
5726                Lo : Uint := Ranges (J).Lo;
5727                Hi : Uint := Ranges (J).Hi;
5728
5729             begin
5730                --  Ignore completely out of range entry
5731
5732                if Hi < TLo or else Lo > THi then
5733                   null;
5734
5735                   --  Otherwise process entry
5736
5737                else
5738                   --  Adjust out of range value to subtype range
5739
5740                   if Lo < TLo then
5741                      Lo := TLo;
5742                   end if;
5743
5744                   if Hi > THi then
5745                      Hi := THi;
5746                   end if;
5747
5748                   --  Convert range into required form
5749
5750                   if Lo = Hi then
5751                      Append_To (Plist, Build_Val (Lo));
5752                   else
5753                      Append_To (Plist, Build_Range (Lo, Hi));
5754                   end if;
5755                end if;
5756             end;
5757          end loop;
5758
5759          --  Processing was successful and all entries were static, so now we
5760          --  can store the result as the predicate list.
5761
5762          Set_Static_Predicate (Typ, Plist);
5763
5764          --  The processing for static predicates put the expression into
5765          --  canonical form as a series of ranges. It also eliminated
5766          --  duplicates and collapsed and combined ranges. We might as well
5767          --  replace the alternatives list of the right operand of the
5768          --  membership test with the static predicate list, which will
5769          --  usually be more efficient.
5770
5771          declare
5772             New_Alts : constant List_Id := New_List;
5773             Old_Node : Node_Id;
5774             New_Node : Node_Id;
5775
5776          begin
5777             Old_Node := First (Plist);
5778             while Present (Old_Node) loop
5779                New_Node := New_Copy (Old_Node);
5780
5781                if Nkind (New_Node) = N_Range then
5782                   Set_Low_Bound  (New_Node, New_Copy (Low_Bound  (Old_Node)));
5783                   Set_High_Bound (New_Node, New_Copy (High_Bound (Old_Node)));
5784                end if;
5785
5786                Append_To (New_Alts, New_Node);
5787                Next (Old_Node);
5788             end loop;
5789
5790             --  If empty list, replace by False
5791
5792             if Is_Empty_List (New_Alts) then
5793                Rewrite (Expr, New_Occurrence_Of (Standard_False, Loc));
5794
5795             --  Else replace by set membership test
5796
5797             else
5798                Rewrite (Expr,
5799                  Make_In (Loc,
5800                    Left_Opnd    => Make_Identifier (Loc, Nam),
5801                    Right_Opnd   => Empty,
5802                    Alternatives => New_Alts));
5803
5804                --  Resolve new expression in function context
5805
5806                Install_Formals (Predicate_Function (Typ));
5807                Push_Scope (Predicate_Function (Typ));
5808                Analyze_And_Resolve (Expr, Standard_Boolean);
5809                Pop_Scope;
5810             end if;
5811          end;
5812       end;
5813
5814    --  If non-static, return doing nothing
5815
5816    exception
5817       when Non_Static =>
5818          return;
5819    end Build_Static_Predicate;
5820
5821    -----------------------------------------
5822    -- Check_Aspect_At_End_Of_Declarations --
5823    -----------------------------------------
5824
5825    procedure Check_Aspect_At_End_Of_Declarations (ASN : Node_Id) is
5826       Ent   : constant Entity_Id := Entity     (ASN);
5827       Ident : constant Node_Id   := Identifier (ASN);
5828
5829       Freeze_Expr : constant Node_Id := Expression (ASN);
5830       --  Expression from call to Check_Aspect_At_Freeze_Point
5831
5832       End_Decl_Expr : constant Node_Id := Entity (Ident);
5833       --  Expression to be analyzed at end of declarations
5834
5835       T : constant Entity_Id := Etype (Freeze_Expr);
5836       --  Type required for preanalyze call
5837
5838       A_Id : constant Aspect_Id := Get_Aspect_Id (Chars (Ident));
5839
5840       Err : Boolean;
5841       --  Set False if error
5842
5843       --  On entry to this procedure, Entity (Ident) contains a copy of the
5844       --  original expression from the aspect, saved for this purpose, and
5845       --  but Expression (Ident) is a preanalyzed copy of the expression,
5846       --  preanalyzed just after the freeze point.
5847
5848    begin
5849       --  Case of stream attributes, just have to compare entities
5850
5851       if A_Id = Aspect_Input  or else
5852          A_Id = Aspect_Output or else
5853          A_Id = Aspect_Read   or else
5854          A_Id = Aspect_Write
5855       then
5856          Analyze (End_Decl_Expr);
5857          Err := Entity (End_Decl_Expr) /= Entity (Freeze_Expr);
5858
5859       elsif A_Id = Aspect_Variable_Indexing or else
5860             A_Id = Aspect_Constant_Indexing or else
5861             A_Id = Aspect_Default_Iterator  or else
5862             A_Id = Aspect_Iterator_Element
5863       then
5864          --  Make type unfrozen before analysis, to prevent spurious errors
5865          --  about late attributes.
5866
5867          Set_Is_Frozen (Ent, False);
5868          Analyze (End_Decl_Expr);
5869          Analyze (Aspect_Rep_Item (ASN));
5870          Set_Is_Frozen (Ent, True);
5871
5872          --  If the end of declarations comes before any other freeze
5873          --  point, the Freeze_Expr is not analyzed: no check needed.
5874
5875          Err :=
5876            Analyzed (Freeze_Expr)
5877              and then not In_Instance
5878              and then Entity (End_Decl_Expr) /= Entity (Freeze_Expr);
5879
5880       --  All other cases
5881
5882       else
5883          --  In a generic context the aspect expressions have not been
5884          --  preanalyzed, so do it now. There are no conformance checks
5885          --  to perform in this case.
5886
5887          if No (T) then
5888             Check_Aspect_At_Freeze_Point (ASN);
5889             return;
5890          else
5891             Preanalyze_Spec_Expression (End_Decl_Expr, T);
5892          end if;
5893
5894          Err := not Fully_Conformant_Expressions (End_Decl_Expr, Freeze_Expr);
5895       end if;
5896
5897       --  Output error message if error
5898
5899       if Err then
5900          Error_Msg_NE
5901            ("visibility of aspect for& changes after freeze point",
5902             ASN, Ent);
5903          Error_Msg_NE
5904            ("?info: & is frozen here, aspects evaluated at this point",
5905             Freeze_Node (Ent), Ent);
5906       end if;
5907    end Check_Aspect_At_End_Of_Declarations;
5908
5909    ----------------------------------
5910    -- Check_Aspect_At_Freeze_Point --
5911    ----------------------------------
5912
5913    procedure Check_Aspect_At_Freeze_Point (ASN : Node_Id) is
5914       Ident : constant Node_Id := Identifier (ASN);
5915       --  Identifier (use Entity field to save expression)
5916
5917       T : Entity_Id;
5918       --  Type required for preanalyze call
5919
5920       A_Id : constant Aspect_Id := Get_Aspect_Id (Chars (Ident));
5921
5922    begin
5923       --  On entry to this procedure, Entity (Ident) contains a copy of the
5924       --  original expression from the aspect, saved for this purpose.
5925
5926       --  On exit from this procedure Entity (Ident) is unchanged, still
5927       --  containing that copy, but Expression (Ident) is a preanalyzed copy
5928       --  of the expression, preanalyzed just after the freeze point.
5929
5930       --  Make a copy of the expression to be preanalyed
5931
5932       Set_Expression (ASN, New_Copy_Tree (Entity (Ident)));
5933
5934       --  Find type for preanalyze call
5935
5936       case A_Id is
5937
5938          --  No_Aspect should be impossible
5939
5940          when No_Aspect =>
5941             raise Program_Error;
5942
5943          --  Library unit aspects should be impossible (never delayed)
5944
5945          when Library_Unit_Aspects =>
5946             raise Program_Error;
5947
5948          --  Aspects taking an optional boolean argument. Should be impossible
5949          --  since these are never delayed.
5950
5951          when Boolean_Aspects =>
5952             raise Program_Error;
5953
5954          --  Test_Case aspect applies to entries and subprograms, hence should
5955          --  never be delayed.
5956
5957          when Aspect_Test_Case =>
5958             raise Program_Error;
5959
5960          when Aspect_Attach_Handler =>
5961             T := RTE (RE_Interrupt_ID);
5962
5963          --  Default_Value is resolved with the type entity in question
5964
5965          when Aspect_Default_Value =>
5966             T := Entity (ASN);
5967
5968          --  Default_Component_Value is resolved with the component type
5969
5970          when Aspect_Default_Component_Value =>
5971             T := Component_Type (Entity (ASN));
5972
5973          --  Aspects corresponding to attribute definition clauses
5974
5975          when Aspect_Address =>
5976             T := RTE (RE_Address);
5977
5978          when Aspect_Bit_Order =>
5979             T := RTE (RE_Bit_Order);
5980
5981          when Aspect_CPU =>
5982             T := RTE (RE_CPU_Range);
5983
5984          when Aspect_Dispatching_Domain =>
5985             T := RTE (RE_Dispatching_Domain);
5986
5987          when Aspect_External_Tag =>
5988             T := Standard_String;
5989
5990          when Aspect_Priority | Aspect_Interrupt_Priority =>
5991             T := Standard_Integer;
5992
5993          when Aspect_Small =>
5994             T := Universal_Real;
5995
5996          when Aspect_Storage_Pool =>
5997             T := Class_Wide_Type (RTE (RE_Root_Storage_Pool));
5998
5999          when Aspect_Alignment      |
6000               Aspect_Component_Size |
6001               Aspect_Machine_Radix  |
6002               Aspect_Object_Size    |
6003               Aspect_Size           |
6004               Aspect_Storage_Size   |
6005               Aspect_Stream_Size    |
6006               Aspect_Value_Size     =>
6007             T := Any_Integer;
6008
6009          --  Stream attribute. Special case, the expression is just an entity
6010          --  that does not need any resolution, so just analyze.
6011
6012          when Aspect_Input  |
6013               Aspect_Output |
6014               Aspect_Read   |
6015               Aspect_Write  =>
6016             Analyze (Expression (ASN));
6017             return;
6018
6019          --  Same for Iterator aspects, where the expression is a function
6020          --  name. Legality rules are checked separately.
6021
6022          when Aspect_Constant_Indexing    |
6023               Aspect_Default_Iterator     |
6024               Aspect_Iterator_Element     |
6025               Aspect_Implicit_Dereference |
6026               Aspect_Variable_Indexing    =>
6027             Analyze (Expression (ASN));
6028             return;
6029
6030          --  Suppress/Unsuppress/Warnings should never be delayed
6031
6032          when Aspect_Suppress   |
6033               Aspect_Unsuppress |
6034               Aspect_Warnings   =>
6035             raise Program_Error;
6036
6037          --  Pre/Post/Invariant/Predicate take boolean expressions
6038
6039          when Aspect_Dynamic_Predicate |
6040               Aspect_Invariant         |
6041               Aspect_Pre               |
6042               Aspect_Precondition      |
6043               Aspect_Post              |
6044               Aspect_Postcondition     |
6045               Aspect_Predicate         |
6046               Aspect_Static_Predicate  |
6047               Aspect_Type_Invariant    =>
6048             T := Standard_Boolean;
6049       end case;
6050
6051       --  Do the preanalyze call
6052
6053       Preanalyze_Spec_Expression (Expression (ASN), T);
6054    end Check_Aspect_At_Freeze_Point;
6055
6056    -----------------------------------
6057    -- Check_Constant_Address_Clause --
6058    -----------------------------------
6059
6060    procedure Check_Constant_Address_Clause
6061      (Expr  : Node_Id;
6062       U_Ent : Entity_Id)
6063    is
6064       procedure Check_At_Constant_Address (Nod : Node_Id);
6065       --  Checks that the given node N represents a name whose 'Address is
6066       --  constant (in the same sense as OK_Constant_Address_Clause, i.e. the
6067       --  address value is the same at the point of declaration of U_Ent and at
6068       --  the time of elaboration of the address clause.
6069
6070       procedure Check_Expr_Constants (Nod : Node_Id);
6071       --  Checks that Nod meets the requirements for a constant address clause
6072       --  in the sense of the enclosing procedure.
6073
6074       procedure Check_List_Constants (Lst : List_Id);
6075       --  Check that all elements of list Lst meet the requirements for a
6076       --  constant address clause in the sense of the enclosing procedure.
6077
6078       -------------------------------
6079       -- Check_At_Constant_Address --
6080       -------------------------------
6081
6082       procedure Check_At_Constant_Address (Nod : Node_Id) is
6083       begin
6084          if Is_Entity_Name (Nod) then
6085             if Present (Address_Clause (Entity ((Nod)))) then
6086                Error_Msg_NE
6087                  ("invalid address clause for initialized object &!",
6088                            Nod, U_Ent);
6089                Error_Msg_NE
6090                  ("address for& cannot" &
6091                     " depend on another address clause! (RM 13.1(22))!",
6092                   Nod, U_Ent);
6093
6094             elsif In_Same_Source_Unit (Entity (Nod), U_Ent)
6095               and then Sloc (U_Ent) < Sloc (Entity (Nod))
6096             then
6097                Error_Msg_NE
6098                  ("invalid address clause for initialized object &!",
6099                   Nod, U_Ent);
6100                Error_Msg_Node_2 := U_Ent;
6101                Error_Msg_NE
6102                  ("\& must be defined before & (RM 13.1(22))!",
6103                   Nod, Entity (Nod));
6104             end if;
6105
6106          elsif Nkind (Nod) = N_Selected_Component then
6107             declare
6108                T : constant Entity_Id := Etype (Prefix (Nod));
6109
6110             begin
6111                if (Is_Record_Type (T)
6112                     and then Has_Discriminants (T))
6113                  or else
6114                   (Is_Access_Type (T)
6115                      and then Is_Record_Type (Designated_Type (T))
6116                      and then Has_Discriminants (Designated_Type (T)))
6117                then
6118                   Error_Msg_NE
6119                     ("invalid address clause for initialized object &!",
6120                      Nod, U_Ent);
6121                   Error_Msg_N
6122                     ("\address cannot depend on component" &
6123                      " of discriminated record (RM 13.1(22))!",
6124                      Nod);
6125                else
6126                   Check_At_Constant_Address (Prefix (Nod));
6127                end if;
6128             end;
6129
6130          elsif Nkind (Nod) = N_Indexed_Component then
6131             Check_At_Constant_Address (Prefix (Nod));
6132             Check_List_Constants (Expressions (Nod));
6133
6134          else
6135             Check_Expr_Constants (Nod);
6136          end if;
6137       end Check_At_Constant_Address;
6138
6139       --------------------------
6140       -- Check_Expr_Constants --
6141       --------------------------
6142
6143       procedure Check_Expr_Constants (Nod : Node_Id) is
6144          Loc_U_Ent : constant Source_Ptr := Sloc (U_Ent);
6145          Ent       : Entity_Id           := Empty;
6146
6147       begin
6148          if Nkind (Nod) in N_Has_Etype
6149            and then Etype (Nod) = Any_Type
6150          then
6151             return;
6152          end if;
6153
6154          case Nkind (Nod) is
6155             when N_Empty | N_Error =>
6156                return;
6157
6158             when N_Identifier | N_Expanded_Name =>
6159                Ent := Entity (Nod);
6160
6161                --  We need to look at the original node if it is different
6162                --  from the node, since we may have rewritten things and
6163                --  substituted an identifier representing the rewrite.
6164
6165                if Original_Node (Nod) /= Nod then
6166                   Check_Expr_Constants (Original_Node (Nod));
6167
6168                   --  If the node is an object declaration without initial
6169                   --  value, some code has been expanded, and the expression
6170                   --  is not constant, even if the constituents might be
6171                   --  acceptable, as in A'Address + offset.
6172
6173                   if Ekind (Ent) = E_Variable
6174                     and then
6175                       Nkind (Declaration_Node (Ent)) = N_Object_Declaration
6176                     and then
6177                       No (Expression (Declaration_Node (Ent)))
6178                   then
6179                      Error_Msg_NE
6180                        ("invalid address clause for initialized object &!",
6181                         Nod, U_Ent);
6182
6183                   --  If entity is constant, it may be the result of expanding
6184                   --  a check. We must verify that its declaration appears
6185                   --  before the object in question, else we also reject the
6186                   --  address clause.
6187
6188                   elsif Ekind (Ent) = E_Constant
6189                     and then In_Same_Source_Unit (Ent, U_Ent)
6190                     and then Sloc (Ent) > Loc_U_Ent
6191                   then
6192                      Error_Msg_NE
6193                        ("invalid address clause for initialized object &!",
6194                         Nod, U_Ent);
6195                   end if;
6196
6197                   return;
6198                end if;
6199
6200                --  Otherwise look at the identifier and see if it is OK
6201
6202                if Ekind_In (Ent, E_Named_Integer, E_Named_Real)
6203                  or else Is_Type (Ent)
6204                then
6205                   return;
6206
6207                elsif
6208                   Ekind (Ent) = E_Constant
6209                     or else
6210                   Ekind (Ent) = E_In_Parameter
6211                then
6212                   --  This is the case where we must have Ent defined before
6213                   --  U_Ent. Clearly if they are in different units this
6214                   --  requirement is met since the unit containing Ent is
6215                   --  already processed.
6216
6217                   if not In_Same_Source_Unit (Ent, U_Ent) then
6218                      return;
6219
6220                   --  Otherwise location of Ent must be before the location
6221                   --  of U_Ent, that's what prior defined means.
6222
6223                   elsif Sloc (Ent) < Loc_U_Ent then
6224                      return;
6225
6226                   else
6227                      Error_Msg_NE
6228                        ("invalid address clause for initialized object &!",
6229                         Nod, U_Ent);
6230                      Error_Msg_Node_2 := U_Ent;
6231                      Error_Msg_NE
6232                        ("\& must be defined before & (RM 13.1(22))!",
6233                         Nod, Ent);
6234                   end if;
6235
6236                elsif Nkind (Original_Node (Nod)) = N_Function_Call then
6237                   Check_Expr_Constants (Original_Node (Nod));
6238
6239                else
6240                   Error_Msg_NE
6241                     ("invalid address clause for initialized object &!",
6242                      Nod, U_Ent);
6243
6244                   if Comes_From_Source (Ent) then
6245                      Error_Msg_NE
6246                        ("\reference to variable& not allowed"
6247                           & " (RM 13.1(22))!", Nod, Ent);
6248                   else
6249                      Error_Msg_N
6250                        ("non-static expression not allowed"
6251                           & " (RM 13.1(22))!", Nod);
6252                   end if;
6253                end if;
6254
6255             when N_Integer_Literal   =>
6256
6257                --  If this is a rewritten unchecked conversion, in a system
6258                --  where Address is an integer type, always use the base type
6259                --  for a literal value. This is user-friendly and prevents
6260                --  order-of-elaboration issues with instances of unchecked
6261                --  conversion.
6262
6263                if Nkind (Original_Node (Nod)) = N_Function_Call then
6264                   Set_Etype (Nod, Base_Type (Etype (Nod)));
6265                end if;
6266
6267             when N_Real_Literal      |
6268                  N_String_Literal    |
6269                  N_Character_Literal =>
6270                return;
6271
6272             when N_Range =>
6273                Check_Expr_Constants (Low_Bound (Nod));
6274                Check_Expr_Constants (High_Bound (Nod));
6275
6276             when N_Explicit_Dereference =>
6277                Check_Expr_Constants (Prefix (Nod));
6278
6279             when N_Indexed_Component =>
6280                Check_Expr_Constants (Prefix (Nod));
6281                Check_List_Constants (Expressions (Nod));
6282
6283             when N_Slice =>
6284                Check_Expr_Constants (Prefix (Nod));
6285                Check_Expr_Constants (Discrete_Range (Nod));
6286
6287             when N_Selected_Component =>
6288                Check_Expr_Constants (Prefix (Nod));
6289
6290             when N_Attribute_Reference =>
6291                if Attribute_Name (Nod) = Name_Address
6292                    or else
6293                   Attribute_Name (Nod) = Name_Access
6294                     or else
6295                   Attribute_Name (Nod) = Name_Unchecked_Access
6296                     or else
6297                   Attribute_Name (Nod) = Name_Unrestricted_Access
6298                then
6299                   Check_At_Constant_Address (Prefix (Nod));
6300
6301                else
6302                   Check_Expr_Constants (Prefix (Nod));
6303                   Check_List_Constants (Expressions (Nod));
6304                end if;
6305
6306             when N_Aggregate =>
6307                Check_List_Constants (Component_Associations (Nod));
6308                Check_List_Constants (Expressions (Nod));
6309
6310             when N_Component_Association =>
6311                Check_Expr_Constants (Expression (Nod));
6312
6313             when N_Extension_Aggregate =>
6314                Check_Expr_Constants (Ancestor_Part (Nod));
6315                Check_List_Constants (Component_Associations (Nod));
6316                Check_List_Constants (Expressions (Nod));
6317
6318             when N_Null =>
6319                return;
6320
6321             when N_Binary_Op | N_Short_Circuit | N_Membership_Test =>
6322                Check_Expr_Constants (Left_Opnd (Nod));
6323                Check_Expr_Constants (Right_Opnd (Nod));
6324
6325             when N_Unary_Op =>
6326                Check_Expr_Constants (Right_Opnd (Nod));
6327
6328             when N_Type_Conversion           |
6329                  N_Qualified_Expression      |
6330                  N_Allocator                 =>
6331                Check_Expr_Constants (Expression (Nod));
6332
6333             when N_Unchecked_Type_Conversion =>
6334                Check_Expr_Constants (Expression (Nod));
6335
6336                --  If this is a rewritten unchecked conversion, subtypes in
6337                --  this node are those created within the instance. To avoid
6338                --  order of elaboration issues, replace them with their base
6339                --  types. Note that address clauses can cause order of
6340                --  elaboration problems because they are elaborated by the
6341                --  back-end at the point of definition, and may mention
6342                --  entities declared in between (as long as everything is
6343                --  static). It is user-friendly to allow unchecked conversions
6344                --  in this context.
6345
6346                if Nkind (Original_Node (Nod)) = N_Function_Call then
6347                   Set_Etype (Expression (Nod),
6348                     Base_Type (Etype (Expression (Nod))));
6349                   Set_Etype (Nod, Base_Type (Etype (Nod)));
6350                end if;
6351
6352             when N_Function_Call =>
6353                if not Is_Pure (Entity (Name (Nod))) then
6354                   Error_Msg_NE
6355                     ("invalid address clause for initialized object &!",
6356                      Nod, U_Ent);
6357
6358                   Error_Msg_NE
6359                     ("\function & is not pure (RM 13.1(22))!",
6360                      Nod, Entity (Name (Nod)));
6361
6362                else
6363                   Check_List_Constants (Parameter_Associations (Nod));
6364                end if;
6365
6366             when N_Parameter_Association =>
6367                Check_Expr_Constants (Explicit_Actual_Parameter (Nod));
6368
6369             when others =>
6370                Error_Msg_NE
6371                  ("invalid address clause for initialized object &!",
6372                   Nod, U_Ent);
6373                Error_Msg_NE
6374                  ("\must be constant defined before& (RM 13.1(22))!",
6375                   Nod, U_Ent);
6376          end case;
6377       end Check_Expr_Constants;
6378
6379       --------------------------
6380       -- Check_List_Constants --
6381       --------------------------
6382
6383       procedure Check_List_Constants (Lst : List_Id) is
6384          Nod1 : Node_Id;
6385
6386       begin
6387          if Present (Lst) then
6388             Nod1 := First (Lst);
6389             while Present (Nod1) loop
6390                Check_Expr_Constants (Nod1);
6391                Next (Nod1);
6392             end loop;
6393          end if;
6394       end Check_List_Constants;
6395
6396    --  Start of processing for Check_Constant_Address_Clause
6397
6398    begin
6399       --  If rep_clauses are to be ignored, no need for legality checks. In
6400       --  particular, no need to pester user about rep clauses that violate
6401       --  the rule on constant addresses, given that these clauses will be
6402       --  removed by Freeze before they reach the back end.
6403
6404       if not Ignore_Rep_Clauses then
6405          Check_Expr_Constants (Expr);
6406       end if;
6407    end Check_Constant_Address_Clause;
6408
6409    ----------------------------------------
6410    -- Check_Record_Representation_Clause --
6411    ----------------------------------------
6412
6413    procedure Check_Record_Representation_Clause (N : Node_Id) is
6414       Loc     : constant Source_Ptr := Sloc (N);
6415       Ident   : constant Node_Id    := Identifier (N);
6416       Rectype : Entity_Id;
6417       Fent    : Entity_Id;
6418       CC      : Node_Id;
6419       Fbit    : Uint;
6420       Lbit    : Uint;
6421       Hbit    : Uint := Uint_0;
6422       Comp    : Entity_Id;
6423       Pcomp   : Entity_Id;
6424
6425       Max_Bit_So_Far : Uint;
6426       --  Records the maximum bit position so far. If all field positions
6427       --  are monotonically increasing, then we can skip the circuit for
6428       --  checking for overlap, since no overlap is possible.
6429
6430       Tagged_Parent : Entity_Id := Empty;
6431       --  This is set in the case of a derived tagged type for which we have
6432       --  Is_Fully_Repped_Tagged_Type True (indicating that all components are
6433       --  positioned by record representation clauses). In this case we must
6434       --  check for overlap between components of this tagged type, and the
6435       --  components of its parent. Tagged_Parent will point to this parent
6436       --  type. For all other cases Tagged_Parent is left set to Empty.
6437
6438       Parent_Last_Bit : Uint;
6439       --  Relevant only if Tagged_Parent is set, Parent_Last_Bit indicates the
6440       --  last bit position for any field in the parent type. We only need to
6441       --  check overlap for fields starting below this point.
6442
6443       Overlap_Check_Required : Boolean;
6444       --  Used to keep track of whether or not an overlap check is required
6445
6446       Overlap_Detected : Boolean := False;
6447       --  Set True if an overlap is detected
6448
6449       Ccount : Natural := 0;
6450       --  Number of component clauses in record rep clause
6451
6452       procedure Check_Component_Overlap (C1_Ent, C2_Ent : Entity_Id);
6453       --  Given two entities for record components or discriminants, checks
6454       --  if they have overlapping component clauses and issues errors if so.
6455
6456       procedure Find_Component;
6457       --  Finds component entity corresponding to current component clause (in
6458       --  CC), and sets Comp to the entity, and Fbit/Lbit to the zero origin
6459       --  start/stop bits for the field. If there is no matching component or
6460       --  if the matching component does not have a component clause, then
6461       --  that's an error and Comp is set to Empty, but no error message is
6462       --  issued, since the message was already given. Comp is also set to
6463       --  Empty if the current "component clause" is in fact a pragma.
6464
6465       -----------------------------
6466       -- Check_Component_Overlap --
6467       -----------------------------
6468
6469       procedure Check_Component_Overlap (C1_Ent, C2_Ent : Entity_Id) is
6470          CC1 : constant Node_Id := Component_Clause (C1_Ent);
6471          CC2 : constant Node_Id := Component_Clause (C2_Ent);
6472
6473       begin
6474          if Present (CC1) and then Present (CC2) then
6475
6476             --  Exclude odd case where we have two tag fields in the same
6477             --  record, both at location zero. This seems a bit strange, but
6478             --  it seems to happen in some circumstances, perhaps on an error.
6479
6480             if Chars (C1_Ent) = Name_uTag
6481                  and then
6482                Chars (C2_Ent) = Name_uTag
6483             then
6484                return;
6485             end if;
6486
6487             --  Here we check if the two fields overlap
6488
6489             declare
6490                S1 : constant Uint := Component_Bit_Offset (C1_Ent);
6491                S2 : constant Uint := Component_Bit_Offset (C2_Ent);
6492                E1 : constant Uint := S1 + Esize (C1_Ent);
6493                E2 : constant Uint := S2 + Esize (C2_Ent);
6494
6495             begin
6496                if E2 <= S1 or else E1 <= S2 then
6497                   null;
6498                else
6499                   Error_Msg_Node_2 := Component_Name (CC2);
6500                   Error_Msg_Sloc := Sloc (Error_Msg_Node_2);
6501                   Error_Msg_Node_1 := Component_Name (CC1);
6502                   Error_Msg_N
6503                     ("component& overlaps & #", Component_Name (CC1));
6504                   Overlap_Detected := True;
6505                end if;
6506             end;
6507          end if;
6508       end Check_Component_Overlap;
6509
6510       --------------------
6511       -- Find_Component --
6512       --------------------
6513
6514       procedure Find_Component is
6515
6516          procedure Search_Component (R : Entity_Id);
6517          --  Search components of R for a match. If found, Comp is set.
6518
6519          ----------------------
6520          -- Search_Component --
6521          ----------------------
6522
6523          procedure Search_Component (R : Entity_Id) is
6524          begin
6525             Comp := First_Component_Or_Discriminant (R);
6526             while Present (Comp) loop
6527
6528                --  Ignore error of attribute name for component name (we
6529                --  already gave an error message for this, so no need to
6530                --  complain here)
6531
6532                if Nkind (Component_Name (CC)) = N_Attribute_Reference then
6533                   null;
6534                else
6535                   exit when Chars (Comp) = Chars (Component_Name (CC));
6536                end if;
6537
6538                Next_Component_Or_Discriminant (Comp);
6539             end loop;
6540          end Search_Component;
6541
6542       --  Start of processing for Find_Component
6543
6544       begin
6545          --  Return with Comp set to Empty if we have a pragma
6546
6547          if Nkind (CC) = N_Pragma then
6548             Comp := Empty;
6549             return;
6550          end if;
6551
6552          --  Search current record for matching component
6553
6554          Search_Component (Rectype);
6555
6556          --  If not found, maybe component of base type that is absent from
6557          --  statically constrained first subtype.
6558
6559          if No (Comp) then
6560             Search_Component (Base_Type (Rectype));
6561          end if;
6562
6563          --  If no component, or the component does not reference the component
6564          --  clause in question, then there was some previous error for which
6565          --  we already gave a message, so just return with Comp Empty.
6566
6567          if No (Comp)
6568            or else Component_Clause (Comp) /= CC
6569          then
6570             Comp := Empty;
6571
6572          --  Normal case where we have a component clause
6573
6574          else
6575             Fbit := Component_Bit_Offset (Comp);
6576             Lbit := Fbit + Esize (Comp) - 1;
6577          end if;
6578       end Find_Component;
6579
6580    --  Start of processing for Check_Record_Representation_Clause
6581
6582    begin
6583       Find_Type (Ident);
6584       Rectype := Entity (Ident);
6585
6586       if Rectype = Any_Type then
6587          return;
6588       else
6589          Rectype := Underlying_Type (Rectype);
6590       end if;
6591
6592       --  See if we have a fully repped derived tagged type
6593
6594       declare
6595          PS : constant Entity_Id := Parent_Subtype (Rectype);
6596
6597       begin
6598          if Present (PS) and then Is_Fully_Repped_Tagged_Type (PS) then
6599             Tagged_Parent := PS;
6600
6601             --  Find maximum bit of any component of the parent type
6602
6603             Parent_Last_Bit := UI_From_Int (System_Address_Size - 1);
6604             Pcomp := First_Entity (Tagged_Parent);
6605             while Present (Pcomp) loop
6606                if Ekind_In (Pcomp, E_Discriminant, E_Component) then
6607                   if Component_Bit_Offset (Pcomp) /= No_Uint
6608                     and then Known_Static_Esize (Pcomp)
6609                   then
6610                      Parent_Last_Bit :=
6611                        UI_Max
6612                          (Parent_Last_Bit,
6613                           Component_Bit_Offset (Pcomp) + Esize (Pcomp) - 1);
6614                   end if;
6615
6616                   Next_Entity (Pcomp);
6617                end if;
6618             end loop;
6619          end if;
6620       end;
6621
6622       --  All done if no component clauses
6623
6624       CC := First (Component_Clauses (N));
6625
6626       if No (CC) then
6627          return;
6628       end if;
6629
6630       --  If a tag is present, then create a component clause that places it
6631       --  at the start of the record (otherwise gigi may place it after other
6632       --  fields that have rep clauses).
6633
6634       Fent := First_Entity (Rectype);
6635
6636       if Nkind (Fent) = N_Defining_Identifier
6637         and then Chars (Fent) = Name_uTag
6638       then
6639          Set_Component_Bit_Offset    (Fent, Uint_0);
6640          Set_Normalized_Position     (Fent, Uint_0);
6641          Set_Normalized_First_Bit    (Fent, Uint_0);
6642          Set_Normalized_Position_Max (Fent, Uint_0);
6643          Init_Esize                  (Fent, System_Address_Size);
6644
6645          Set_Component_Clause (Fent,
6646            Make_Component_Clause (Loc,
6647              Component_Name => Make_Identifier (Loc, Name_uTag),
6648
6649              Position  => Make_Integer_Literal (Loc, Uint_0),
6650              First_Bit => Make_Integer_Literal (Loc, Uint_0),
6651              Last_Bit  =>
6652                Make_Integer_Literal (Loc,
6653                  UI_From_Int (System_Address_Size))));
6654
6655          Ccount := Ccount + 1;
6656       end if;
6657
6658       Max_Bit_So_Far := Uint_Minus_1;
6659       Overlap_Check_Required := False;
6660
6661       --  Process the component clauses
6662
6663       while Present (CC) loop
6664          Find_Component;
6665
6666          if Present (Comp) then
6667             Ccount := Ccount + 1;
6668
6669             --  We need a full overlap check if record positions non-monotonic
6670
6671             if Fbit <= Max_Bit_So_Far then
6672                Overlap_Check_Required := True;
6673             end if;
6674
6675             Max_Bit_So_Far := Lbit;
6676
6677             --  Check bit position out of range of specified size
6678
6679             if Has_Size_Clause (Rectype)
6680               and then RM_Size (Rectype) <= Lbit
6681             then
6682                Error_Msg_N
6683                  ("bit number out of range of specified size",
6684                   Last_Bit (CC));
6685
6686                --  Check for overlap with tag field
6687
6688             else
6689                if Is_Tagged_Type (Rectype)
6690                  and then Fbit < System_Address_Size
6691                then
6692                   Error_Msg_NE
6693                     ("component overlaps tag field of&",
6694                      Component_Name (CC), Rectype);
6695                   Overlap_Detected := True;
6696                end if;
6697
6698                if Hbit < Lbit then
6699                   Hbit := Lbit;
6700                end if;
6701             end if;
6702
6703             --  Check parent overlap if component might overlap parent field
6704
6705             if Present (Tagged_Parent)
6706               and then Fbit <= Parent_Last_Bit
6707             then
6708                Pcomp := First_Component_Or_Discriminant (Tagged_Parent);
6709                while Present (Pcomp) loop
6710                   if not Is_Tag (Pcomp)
6711                     and then Chars (Pcomp) /= Name_uParent
6712                   then
6713                      Check_Component_Overlap (Comp, Pcomp);
6714                   end if;
6715
6716                   Next_Component_Or_Discriminant (Pcomp);
6717                end loop;
6718             end if;
6719          end if;
6720
6721          Next (CC);
6722       end loop;
6723
6724       --  Now that we have processed all the component clauses, check for
6725       --  overlap. We have to leave this till last, since the components can
6726       --  appear in any arbitrary order in the representation clause.
6727
6728       --  We do not need this check if all specified ranges were monotonic,
6729       --  as recorded by Overlap_Check_Required being False at this stage.
6730
6731       --  This first section checks if there are any overlapping entries at
6732       --  all. It does this by sorting all entries and then seeing if there are
6733       --  any overlaps. If there are none, then that is decisive, but if there
6734       --  are overlaps, they may still be OK (they may result from fields in
6735       --  different variants).
6736
6737       if Overlap_Check_Required then
6738          Overlap_Check1 : declare
6739
6740             OC_Fbit : array (0 .. Ccount) of Uint;
6741             --  First-bit values for component clauses, the value is the offset
6742             --  of the first bit of the field from start of record. The zero
6743             --  entry is for use in sorting.
6744
6745             OC_Lbit : array (0 .. Ccount) of Uint;
6746             --  Last-bit values for component clauses, the value is the offset
6747             --  of the last bit of the field from start of record. The zero
6748             --  entry is for use in sorting.
6749
6750             OC_Count : Natural := 0;
6751             --  Count of entries in OC_Fbit and OC_Lbit
6752
6753             function OC_Lt (Op1, Op2 : Natural) return Boolean;
6754             --  Compare routine for Sort
6755
6756             procedure OC_Move (From : Natural; To : Natural);
6757             --  Move routine for Sort
6758
6759             package Sorting is new GNAT.Heap_Sort_G (OC_Move, OC_Lt);
6760
6761             -----------
6762             -- OC_Lt --
6763             -----------
6764
6765             function OC_Lt (Op1, Op2 : Natural) return Boolean is
6766             begin
6767                return OC_Fbit (Op1) < OC_Fbit (Op2);
6768             end OC_Lt;
6769
6770             -------------
6771             -- OC_Move --
6772             -------------
6773
6774             procedure OC_Move (From : Natural; To : Natural) is
6775             begin
6776                OC_Fbit (To) := OC_Fbit (From);
6777                OC_Lbit (To) := OC_Lbit (From);
6778             end OC_Move;
6779
6780             --  Start of processing for Overlap_Check
6781
6782          begin
6783             CC := First (Component_Clauses (N));
6784             while Present (CC) loop
6785
6786                --  Exclude component clause already marked in error
6787
6788                if not Error_Posted (CC) then
6789                   Find_Component;
6790
6791                   if Present (Comp) then
6792                      OC_Count := OC_Count + 1;
6793                      OC_Fbit (OC_Count) := Fbit;
6794                      OC_Lbit (OC_Count) := Lbit;
6795                   end if;
6796                end if;
6797
6798                Next (CC);
6799             end loop;
6800
6801             Sorting.Sort (OC_Count);
6802
6803             Overlap_Check_Required := False;
6804             for J in 1 .. OC_Count - 1 loop
6805                if OC_Lbit (J) >= OC_Fbit (J + 1) then
6806                   Overlap_Check_Required := True;
6807                   exit;
6808                end if;
6809             end loop;
6810          end Overlap_Check1;
6811       end if;
6812
6813       --  If Overlap_Check_Required is still True, then we have to do the full
6814       --  scale overlap check, since we have at least two fields that do
6815       --  overlap, and we need to know if that is OK since they are in
6816       --  different variant, or whether we have a definite problem.
6817
6818       if Overlap_Check_Required then
6819          Overlap_Check2 : declare
6820             C1_Ent, C2_Ent : Entity_Id;
6821             --  Entities of components being checked for overlap
6822
6823             Clist : Node_Id;
6824             --  Component_List node whose Component_Items are being checked
6825
6826             Citem : Node_Id;
6827             --  Component declaration for component being checked
6828
6829          begin
6830             C1_Ent := First_Entity (Base_Type (Rectype));
6831
6832             --  Loop through all components in record. For each component check
6833             --  for overlap with any of the preceding elements on the component
6834             --  list containing the component and also, if the component is in
6835             --  a variant, check against components outside the case structure.
6836             --  This latter test is repeated recursively up the variant tree.
6837
6838             Main_Component_Loop : while Present (C1_Ent) loop
6839                if not Ekind_In (C1_Ent, E_Component, E_Discriminant) then
6840                   goto Continue_Main_Component_Loop;
6841                end if;
6842
6843                --  Skip overlap check if entity has no declaration node. This
6844                --  happens with discriminants in constrained derived types.
6845                --  Possibly we are missing some checks as a result, but that
6846                --  does not seem terribly serious.
6847
6848                if No (Declaration_Node (C1_Ent)) then
6849                   goto Continue_Main_Component_Loop;
6850                end if;
6851
6852                Clist := Parent (List_Containing (Declaration_Node (C1_Ent)));
6853
6854                --  Loop through component lists that need checking. Check the
6855                --  current component list and all lists in variants above us.
6856
6857                Component_List_Loop : loop
6858
6859                   --  If derived type definition, go to full declaration
6860                   --  If at outer level, check discriminants if there are any.
6861
6862                   if Nkind (Clist) = N_Derived_Type_Definition then
6863                      Clist := Parent (Clist);
6864                   end if;
6865
6866                   --  Outer level of record definition, check discriminants
6867
6868                   if Nkind_In (Clist, N_Full_Type_Declaration,
6869                                N_Private_Type_Declaration)
6870                   then
6871                      if Has_Discriminants (Defining_Identifier (Clist)) then
6872                         C2_Ent :=
6873                           First_Discriminant (Defining_Identifier (Clist));
6874                         while Present (C2_Ent) loop
6875                            exit when C1_Ent = C2_Ent;
6876                            Check_Component_Overlap (C1_Ent, C2_Ent);
6877                            Next_Discriminant (C2_Ent);
6878                         end loop;
6879                      end if;
6880
6881                      --  Record extension case
6882
6883                   elsif Nkind (Clist) = N_Derived_Type_Definition then
6884                      Clist := Empty;
6885
6886                      --  Otherwise check one component list
6887
6888                   else
6889                      Citem := First (Component_Items (Clist));
6890                      while Present (Citem) loop
6891                         if Nkind (Citem) = N_Component_Declaration then
6892                            C2_Ent := Defining_Identifier (Citem);
6893                            exit when C1_Ent = C2_Ent;
6894                            Check_Component_Overlap (C1_Ent, C2_Ent);
6895                         end if;
6896
6897                         Next (Citem);
6898                      end loop;
6899                   end if;
6900
6901                   --  Check for variants above us (the parent of the Clist can
6902                   --  be a variant, in which case its parent is a variant part,
6903                   --  and the parent of the variant part is a component list
6904                   --  whose components must all be checked against the current
6905                   --  component for overlap).
6906
6907                   if Nkind (Parent (Clist)) = N_Variant then
6908                      Clist := Parent (Parent (Parent (Clist)));
6909
6910                      --  Check for possible discriminant part in record, this
6911                      --  is treated essentially as another level in the
6912                      --  recursion. For this case the parent of the component
6913                      --  list is the record definition, and its parent is the
6914                      --  full type declaration containing the discriminant
6915                      --  specifications.
6916
6917                   elsif Nkind (Parent (Clist)) = N_Record_Definition then
6918                      Clist := Parent (Parent ((Clist)));
6919
6920                      --  If neither of these two cases, we are at the top of
6921                      --  the tree.
6922
6923                   else
6924                      exit Component_List_Loop;
6925                   end if;
6926                end loop Component_List_Loop;
6927
6928                <<Continue_Main_Component_Loop>>
6929                Next_Entity (C1_Ent);
6930
6931             end loop Main_Component_Loop;
6932          end Overlap_Check2;
6933       end if;
6934
6935       --  The following circuit deals with warning on record holes (gaps). We
6936       --  skip this check if overlap was detected, since it makes sense for the
6937       --  programmer to fix this illegality before worrying about warnings.
6938
6939       if not Overlap_Detected and Warn_On_Record_Holes then
6940          Record_Hole_Check : declare
6941             Decl : constant Node_Id := Declaration_Node (Base_Type (Rectype));
6942             --  Full declaration of record type
6943
6944             procedure Check_Component_List
6945               (CL   : Node_Id;
6946                Sbit : Uint;
6947                DS   : List_Id);
6948             --  Check component list CL for holes. The starting bit should be
6949             --  Sbit. which is zero for the main record component list and set
6950             --  appropriately for recursive calls for variants. DS is set to
6951             --  a list of discriminant specifications to be included in the
6952             --  consideration of components. It is No_List if none to consider.
6953
6954             --------------------------
6955             -- Check_Component_List --
6956             --------------------------
6957
6958             procedure Check_Component_List
6959               (CL   : Node_Id;
6960                Sbit : Uint;
6961                DS   : List_Id)
6962             is
6963                Compl : Integer;
6964
6965             begin
6966                Compl := Integer (List_Length (Component_Items (CL)));
6967
6968                if DS /= No_List then
6969                   Compl := Compl + Integer (List_Length (DS));
6970                end if;
6971
6972                declare
6973                   Comps : array (Natural range 0 .. Compl) of Entity_Id;
6974                   --  Gather components (zero entry is for sort routine)
6975
6976                   Ncomps : Natural := 0;
6977                   --  Number of entries stored in Comps (starting at Comps (1))
6978
6979                   Citem : Node_Id;
6980                   --  One component item or discriminant specification
6981
6982                   Nbit  : Uint;
6983                   --  Starting bit for next component
6984
6985                   CEnt  : Entity_Id;
6986                   --  Component entity
6987
6988                   Variant : Node_Id;
6989                   --  One variant
6990
6991                   function Lt (Op1, Op2 : Natural) return Boolean;
6992                   --  Compare routine for Sort
6993
6994                   procedure Move (From : Natural; To : Natural);
6995                   --  Move routine for Sort
6996
6997                   package Sorting is new GNAT.Heap_Sort_G (Move, Lt);
6998
6999                   --------
7000                   -- Lt --
7001                   --------
7002
7003                   function Lt (Op1, Op2 : Natural) return Boolean is
7004                   begin
7005                      return Component_Bit_Offset (Comps (Op1))
7006                        <
7007                        Component_Bit_Offset (Comps (Op2));
7008                   end Lt;
7009
7010                   ----------
7011                   -- Move --
7012                   ----------
7013
7014                   procedure Move (From : Natural; To : Natural) is
7015                   begin
7016                      Comps (To) := Comps (From);
7017                   end Move;
7018
7019                begin
7020                   --  Gather discriminants into Comp
7021
7022                   if DS /= No_List then
7023                      Citem := First (DS);
7024                      while Present (Citem) loop
7025                         if Nkind (Citem) = N_Discriminant_Specification then
7026                            declare
7027                               Ent : constant Entity_Id :=
7028                                       Defining_Identifier (Citem);
7029                            begin
7030                               if Ekind (Ent) = E_Discriminant then
7031                                  Ncomps := Ncomps + 1;
7032                                  Comps (Ncomps) := Ent;
7033                               end if;
7034                            end;
7035                         end if;
7036
7037                         Next (Citem);
7038                      end loop;
7039                   end if;
7040
7041                   --  Gather component entities into Comp
7042
7043                   Citem := First (Component_Items (CL));
7044                   while Present (Citem) loop
7045                      if Nkind (Citem) = N_Component_Declaration then
7046                         Ncomps := Ncomps + 1;
7047                         Comps (Ncomps) := Defining_Identifier (Citem);
7048                      end if;
7049
7050                      Next (Citem);
7051                   end loop;
7052
7053                   --  Now sort the component entities based on the first bit.
7054                   --  Note we already know there are no overlapping components.
7055
7056                   Sorting.Sort (Ncomps);
7057
7058                   --  Loop through entries checking for holes
7059
7060                   Nbit := Sbit;
7061                   for J in 1 .. Ncomps loop
7062                      CEnt := Comps (J);
7063                      Error_Msg_Uint_1 := Component_Bit_Offset (CEnt) - Nbit;
7064
7065                      if Error_Msg_Uint_1 > 0 then
7066                         Error_Msg_NE
7067                           ("?^-bit gap before component&",
7068                            Component_Name (Component_Clause (CEnt)), CEnt);
7069                      end if;
7070
7071                      Nbit := Component_Bit_Offset (CEnt) + Esize (CEnt);
7072                   end loop;
7073
7074                   --  Process variant parts recursively if present
7075
7076                   if Present (Variant_Part (CL)) then
7077                      Variant := First (Variants (Variant_Part (CL)));
7078                      while Present (Variant) loop
7079                         Check_Component_List
7080                           (Component_List (Variant), Nbit, No_List);
7081                         Next (Variant);
7082                      end loop;
7083                   end if;
7084                end;
7085             end Check_Component_List;
7086
7087          --  Start of processing for Record_Hole_Check
7088
7089          begin
7090             declare
7091                Sbit : Uint;
7092
7093             begin
7094                if Is_Tagged_Type (Rectype) then
7095                   Sbit := UI_From_Int (System_Address_Size);
7096                else
7097                   Sbit := Uint_0;
7098                end if;
7099
7100                if Nkind (Decl) = N_Full_Type_Declaration
7101                  and then Nkind (Type_Definition (Decl)) = N_Record_Definition
7102                then
7103                   Check_Component_List
7104                     (Component_List (Type_Definition (Decl)),
7105                      Sbit,
7106                      Discriminant_Specifications (Decl));
7107                end if;
7108             end;
7109          end Record_Hole_Check;
7110       end if;
7111
7112       --  For records that have component clauses for all components, and whose
7113       --  size is less than or equal to 32, we need to know the size in the
7114       --  front end to activate possible packed array processing where the
7115       --  component type is a record.
7116
7117       --  At this stage Hbit + 1 represents the first unused bit from all the
7118       --  component clauses processed, so if the component clauses are
7119       --  complete, then this is the length of the record.
7120
7121       --  For records longer than System.Storage_Unit, and for those where not
7122       --  all components have component clauses, the back end determines the
7123       --  length (it may for example be appropriate to round up the size
7124       --  to some convenient boundary, based on alignment considerations, etc).
7125
7126       if Unknown_RM_Size (Rectype) and then Hbit + 1 <= 32 then
7127
7128          --  Nothing to do if at least one component has no component clause
7129
7130          Comp := First_Component_Or_Discriminant (Rectype);
7131          while Present (Comp) loop
7132             exit when No (Component_Clause (Comp));
7133             Next_Component_Or_Discriminant (Comp);
7134          end loop;
7135
7136          --  If we fall out of loop, all components have component clauses
7137          --  and so we can set the size to the maximum value.
7138
7139          if No (Comp) then
7140             Set_RM_Size (Rectype, Hbit + 1);
7141          end if;
7142       end if;
7143    end Check_Record_Representation_Clause;
7144
7145    ----------------
7146    -- Check_Size --
7147    ----------------
7148
7149    procedure Check_Size
7150      (N      : Node_Id;
7151       T      : Entity_Id;
7152       Siz    : Uint;
7153       Biased : out Boolean)
7154    is
7155       UT : constant Entity_Id := Underlying_Type (T);
7156       M  : Uint;
7157
7158    begin
7159       Biased := False;
7160
7161       --  Dismiss cases for generic types or types with previous errors
7162
7163       if No (UT)
7164         or else UT = Any_Type
7165         or else Is_Generic_Type (UT)
7166         or else Is_Generic_Type (Root_Type (UT))
7167       then
7168          return;
7169
7170       --  Check case of bit packed array
7171
7172       elsif Is_Array_Type (UT)
7173         and then Known_Static_Component_Size (UT)
7174         and then Is_Bit_Packed_Array (UT)
7175       then
7176          declare
7177             Asiz : Uint;
7178             Indx : Node_Id;
7179             Ityp : Entity_Id;
7180
7181          begin
7182             Asiz := Component_Size (UT);
7183             Indx := First_Index (UT);
7184             loop
7185                Ityp := Etype (Indx);
7186
7187                --  If non-static bound, then we are not in the business of
7188                --  trying to check the length, and indeed an error will be
7189                --  issued elsewhere, since sizes of non-static array types
7190                --  cannot be set implicitly or explicitly.
7191
7192                if not Is_Static_Subtype (Ityp) then
7193                   return;
7194                end if;
7195
7196                --  Otherwise accumulate next dimension
7197
7198                Asiz := Asiz * (Expr_Value (Type_High_Bound (Ityp)) -
7199                                Expr_Value (Type_Low_Bound  (Ityp)) +
7200                                Uint_1);
7201
7202                Next_Index (Indx);
7203                exit when No (Indx);
7204             end loop;
7205
7206             if Asiz <= Siz then
7207                return;
7208             else
7209                Error_Msg_Uint_1 := Asiz;
7210                Error_Msg_NE
7211                  ("size for& too small, minimum allowed is ^", N, T);
7212                Set_Esize   (T, Asiz);
7213                Set_RM_Size (T, Asiz);
7214             end if;
7215          end;
7216
7217       --  All other composite types are ignored
7218
7219       elsif Is_Composite_Type (UT) then
7220          return;
7221
7222       --  For fixed-point types, don't check minimum if type is not frozen,
7223       --  since we don't know all the characteristics of the type that can
7224       --  affect the size (e.g. a specified small) till freeze time.
7225
7226       elsif Is_Fixed_Point_Type (UT)
7227         and then not Is_Frozen (UT)
7228       then
7229          null;
7230
7231       --  Cases for which a minimum check is required
7232
7233       else
7234          --  Ignore if specified size is correct for the type
7235
7236          if Known_Esize (UT) and then Siz = Esize (UT) then
7237             return;
7238          end if;
7239
7240          --  Otherwise get minimum size
7241
7242          M := UI_From_Int (Minimum_Size (UT));
7243
7244          if Siz < M then
7245
7246             --  Size is less than minimum size, but one possibility remains
7247             --  that we can manage with the new size if we bias the type.
7248
7249             M := UI_From_Int (Minimum_Size (UT, Biased => True));
7250
7251             if Siz < M then
7252                Error_Msg_Uint_1 := M;
7253                Error_Msg_NE
7254                  ("size for& too small, minimum allowed is ^", N, T);
7255                Set_Esize (T, M);
7256                Set_RM_Size (T, M);
7257             else
7258                Biased := True;
7259             end if;
7260          end if;
7261       end if;
7262    end Check_Size;
7263
7264    -------------------------
7265    -- Get_Alignment_Value --
7266    -------------------------
7267
7268    function Get_Alignment_Value (Expr : Node_Id) return Uint is
7269       Align : constant Uint := Static_Integer (Expr);
7270
7271    begin
7272       if Align = No_Uint then
7273          return No_Uint;
7274
7275       elsif Align <= 0 then
7276          Error_Msg_N ("alignment value must be positive", Expr);
7277          return No_Uint;
7278
7279       else
7280          for J in Int range 0 .. 64 loop
7281             declare
7282                M : constant Uint := Uint_2 ** J;
7283
7284             begin
7285                exit when M = Align;
7286
7287                if M > Align then
7288                   Error_Msg_N
7289                     ("alignment value must be power of 2", Expr);
7290                   return No_Uint;
7291                end if;
7292             end;
7293          end loop;
7294
7295          return Align;
7296       end if;
7297    end Get_Alignment_Value;
7298
7299    ----------------
7300    -- Initialize --
7301    ----------------
7302
7303    procedure Initialize is
7304    begin
7305       Address_Clause_Checks.Init;
7306       Independence_Checks.Init;
7307       Unchecked_Conversions.Init;
7308    end Initialize;
7309
7310    -------------------------
7311    -- Is_Operational_Item --
7312    -------------------------
7313
7314    function Is_Operational_Item (N : Node_Id) return Boolean is
7315    begin
7316       if Nkind (N) /= N_Attribute_Definition_Clause then
7317          return False;
7318       else
7319          declare
7320             Id    : constant Attribute_Id := Get_Attribute_Id (Chars (N));
7321          begin
7322             return   Id = Attribute_Input
7323               or else Id = Attribute_Output
7324               or else Id = Attribute_Read
7325               or else Id = Attribute_Write
7326               or else Id = Attribute_External_Tag;
7327          end;
7328       end if;
7329    end Is_Operational_Item;
7330
7331    ------------------
7332    -- Minimum_Size --
7333    ------------------
7334
7335    function Minimum_Size
7336      (T      : Entity_Id;
7337       Biased : Boolean := False) return Nat
7338    is
7339       Lo     : Uint    := No_Uint;
7340       Hi     : Uint    := No_Uint;
7341       LoR    : Ureal   := No_Ureal;
7342       HiR    : Ureal   := No_Ureal;
7343       LoSet  : Boolean := False;
7344       HiSet  : Boolean := False;
7345       B      : Uint;
7346       S      : Nat;
7347       Ancest : Entity_Id;
7348       R_Typ  : constant Entity_Id := Root_Type (T);
7349
7350    begin
7351       --  If bad type, return 0
7352
7353       if T = Any_Type then
7354          return 0;
7355
7356       --  For generic types, just return zero. There cannot be any legitimate
7357       --  need to know such a size, but this routine may be called with a
7358       --  generic type as part of normal processing.
7359
7360       elsif Is_Generic_Type (R_Typ)
7361         or else R_Typ = Any_Type
7362       then
7363          return 0;
7364
7365          --  Access types. Normally an access type cannot have a size smaller
7366          --  than the size of System.Address. The exception is on VMS, where
7367          --  we have short and long addresses, and it is possible for an access
7368          --  type to have a short address size (and thus be less than the size
7369          --  of System.Address itself). We simply skip the check for VMS, and
7370          --  leave it to the back end to do the check.
7371
7372       elsif Is_Access_Type (T) then
7373          if OpenVMS_On_Target then
7374             return 0;
7375          else
7376             return System_Address_Size;
7377          end if;
7378
7379       --  Floating-point types
7380
7381       elsif Is_Floating_Point_Type (T) then
7382          return UI_To_Int (Esize (R_Typ));
7383
7384       --  Discrete types
7385
7386       elsif Is_Discrete_Type (T) then
7387
7388          --  The following loop is looking for the nearest compile time known
7389          --  bounds following the ancestor subtype chain. The idea is to find
7390          --  the most restrictive known bounds information.
7391
7392          Ancest := T;
7393          loop
7394             if Ancest = Any_Type or else Etype (Ancest) = Any_Type then
7395                return 0;
7396             end if;
7397
7398             if not LoSet then
7399                if Compile_Time_Known_Value (Type_Low_Bound (Ancest)) then
7400                   Lo := Expr_Rep_Value (Type_Low_Bound (Ancest));
7401                   LoSet := True;
7402                   exit when HiSet;
7403                end if;
7404             end if;
7405
7406             if not HiSet then
7407                if Compile_Time_Known_Value (Type_High_Bound (Ancest)) then
7408                   Hi := Expr_Rep_Value (Type_High_Bound (Ancest));
7409                   HiSet := True;
7410                   exit when LoSet;
7411                end if;
7412             end if;
7413
7414             Ancest := Ancestor_Subtype (Ancest);
7415
7416             if No (Ancest) then
7417                Ancest := Base_Type (T);
7418
7419                if Is_Generic_Type (Ancest) then
7420                   return 0;
7421                end if;
7422             end if;
7423          end loop;
7424
7425       --  Fixed-point types. We can't simply use Expr_Value to get the
7426       --  Corresponding_Integer_Value values of the bounds, since these do not
7427       --  get set till the type is frozen, and this routine can be called
7428       --  before the type is frozen. Similarly the test for bounds being static
7429       --  needs to include the case where we have unanalyzed real literals for
7430       --  the same reason.
7431
7432       elsif Is_Fixed_Point_Type (T) then
7433
7434          --  The following loop is looking for the nearest compile time known
7435          --  bounds following the ancestor subtype chain. The idea is to find
7436          --  the most restrictive known bounds information.
7437
7438          Ancest := T;
7439          loop
7440             if Ancest = Any_Type or else Etype (Ancest) = Any_Type then
7441                return 0;
7442             end if;
7443
7444             --  Note: In the following two tests for LoSet and HiSet, it may
7445             --  seem redundant to test for N_Real_Literal here since normally
7446             --  one would assume that the test for the value being known at
7447             --  compile time includes this case. However, there is a glitch.
7448             --  If the real literal comes from folding a non-static expression,
7449             --  then we don't consider any non- static expression to be known
7450             --  at compile time if we are in configurable run time mode (needed
7451             --  in some cases to give a clearer definition of what is and what
7452             --  is not accepted). So the test is indeed needed. Without it, we
7453             --  would set neither Lo_Set nor Hi_Set and get an infinite loop.
7454
7455             if not LoSet then
7456                if Nkind (Type_Low_Bound (Ancest)) = N_Real_Literal
7457                  or else Compile_Time_Known_Value (Type_Low_Bound (Ancest))
7458                then
7459                   LoR := Expr_Value_R (Type_Low_Bound (Ancest));
7460                   LoSet := True;
7461                   exit when HiSet;
7462                end if;
7463             end if;
7464
7465             if not HiSet then
7466                if Nkind (Type_High_Bound (Ancest)) = N_Real_Literal
7467                  or else Compile_Time_Known_Value (Type_High_Bound (Ancest))
7468                then
7469                   HiR := Expr_Value_R (Type_High_Bound (Ancest));
7470                   HiSet := True;
7471                   exit when LoSet;
7472                end if;
7473             end if;
7474
7475             Ancest := Ancestor_Subtype (Ancest);
7476
7477             if No (Ancest) then
7478                Ancest := Base_Type (T);
7479
7480                if Is_Generic_Type (Ancest) then
7481                   return 0;
7482                end if;
7483             end if;
7484          end loop;
7485
7486          Lo := UR_To_Uint (LoR / Small_Value (T));
7487          Hi := UR_To_Uint (HiR / Small_Value (T));
7488
7489       --  No other types allowed
7490
7491       else
7492          raise Program_Error;
7493       end if;
7494
7495       --  Fall through with Hi and Lo set. Deal with biased case
7496
7497       if (Biased
7498            and then not Is_Fixed_Point_Type (T)
7499            and then not (Is_Enumeration_Type (T)
7500                           and then Has_Non_Standard_Rep (T)))
7501         or else Has_Biased_Representation (T)
7502       then
7503          Hi := Hi - Lo;
7504          Lo := Uint_0;
7505       end if;
7506
7507       --  Signed case. Note that we consider types like range 1 .. -1 to be
7508       --  signed for the purpose of computing the size, since the bounds have
7509       --  to be accommodated in the base type.
7510
7511       if Lo < 0 or else Hi < 0 then
7512          S := 1;
7513          B := Uint_1;
7514
7515          --  S = size, B = 2 ** (size - 1) (can accommodate -B .. +(B - 1))
7516          --  Note that we accommodate the case where the bounds cross. This
7517          --  can happen either because of the way the bounds are declared
7518          --  or because of the algorithm in Freeze_Fixed_Point_Type.
7519
7520          while Lo < -B
7521            or else Hi < -B
7522            or else Lo >= B
7523            or else Hi >= B
7524          loop
7525             B := Uint_2 ** S;
7526             S := S + 1;
7527          end loop;
7528
7529       --  Unsigned case
7530
7531       else
7532          --  If both bounds are positive, make sure that both are represen-
7533          --  table in the case where the bounds are crossed. This can happen
7534          --  either because of the way the bounds are declared, or because of
7535          --  the algorithm in Freeze_Fixed_Point_Type.
7536
7537          if Lo > Hi then
7538             Hi := Lo;
7539          end if;
7540
7541          --  S = size, (can accommodate 0 .. (2**size - 1))
7542
7543          S := 0;
7544          while Hi >= Uint_2 ** S loop
7545             S := S + 1;
7546          end loop;
7547       end if;
7548
7549       return S;
7550    end Minimum_Size;
7551
7552    ---------------------------
7553    -- New_Stream_Subprogram --
7554    ---------------------------
7555
7556    procedure New_Stream_Subprogram
7557      (N     : Node_Id;
7558       Ent   : Entity_Id;
7559       Subp  : Entity_Id;
7560       Nam   : TSS_Name_Type)
7561    is
7562       Loc       : constant Source_Ptr := Sloc (N);
7563       Sname     : constant Name_Id    := Make_TSS_Name (Base_Type (Ent), Nam);
7564       Subp_Id   : Entity_Id;
7565       Subp_Decl : Node_Id;
7566       F         : Entity_Id;
7567       Etyp      : Entity_Id;
7568
7569       Defer_Declaration : constant Boolean :=
7570                             Is_Tagged_Type (Ent) or else Is_Private_Type (Ent);
7571       --  For a tagged type, there is a declaration for each stream attribute
7572       --  at the freeze point, and we must generate only a completion of this
7573       --  declaration. We do the same for private types, because the full view
7574       --  might be tagged. Otherwise we generate a declaration at the point of
7575       --  the attribute definition clause.
7576
7577       function Build_Spec return Node_Id;
7578       --  Used for declaration and renaming declaration, so that this is
7579       --  treated as a renaming_as_body.
7580
7581       ----------------
7582       -- Build_Spec --
7583       ----------------
7584
7585       function Build_Spec return Node_Id is
7586          Out_P   : constant Boolean := (Nam = TSS_Stream_Read);
7587          Formals : List_Id;
7588          Spec    : Node_Id;
7589          T_Ref   : constant Node_Id := New_Reference_To (Etyp, Loc);
7590
7591       begin
7592          Subp_Id := Make_Defining_Identifier (Loc, Sname);
7593
7594          --  S : access Root_Stream_Type'Class
7595
7596          Formals := New_List (
7597                       Make_Parameter_Specification (Loc,
7598                         Defining_Identifier =>
7599                           Make_Defining_Identifier (Loc, Name_S),
7600                         Parameter_Type =>
7601                           Make_Access_Definition (Loc,
7602                             Subtype_Mark =>
7603                               New_Reference_To (
7604                                 Designated_Type (Etype (F)), Loc))));
7605
7606          if Nam = TSS_Stream_Input then
7607             Spec := Make_Function_Specification (Loc,
7608                       Defining_Unit_Name       => Subp_Id,
7609                       Parameter_Specifications => Formals,
7610                       Result_Definition        => T_Ref);
7611          else
7612             --  V : [out] T
7613
7614             Append_To (Formals,
7615               Make_Parameter_Specification (Loc,
7616                 Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
7617                 Out_Present         => Out_P,
7618                 Parameter_Type      => T_Ref));
7619
7620             Spec :=
7621               Make_Procedure_Specification (Loc,
7622                 Defining_Unit_Name       => Subp_Id,
7623                 Parameter_Specifications => Formals);
7624          end if;
7625
7626          return Spec;
7627       end Build_Spec;
7628
7629    --  Start of processing for New_Stream_Subprogram
7630
7631    begin
7632       F := First_Formal (Subp);
7633
7634       if Ekind (Subp) = E_Procedure then
7635          Etyp := Etype (Next_Formal (F));
7636       else
7637          Etyp := Etype (Subp);
7638       end if;
7639
7640       --  Prepare subprogram declaration and insert it as an action on the
7641       --  clause node. The visibility for this entity is used to test for
7642       --  visibility of the attribute definition clause (in the sense of
7643       --  8.3(23) as amended by AI-195).
7644
7645       if not Defer_Declaration then
7646          Subp_Decl :=
7647            Make_Subprogram_Declaration (Loc,
7648              Specification => Build_Spec);
7649
7650       --  For a tagged type, there is always a visible declaration for each
7651       --  stream TSS (it is a predefined primitive operation), and the
7652       --  completion of this declaration occurs at the freeze point, which is
7653       --  not always visible at places where the attribute definition clause is
7654       --  visible. So, we create a dummy entity here for the purpose of
7655       --  tracking the visibility of the attribute definition clause itself.
7656
7657       else
7658          Subp_Id :=
7659            Make_Defining_Identifier (Loc, New_External_Name (Sname, 'V'));
7660          Subp_Decl :=
7661            Make_Object_Declaration (Loc,
7662              Defining_Identifier => Subp_Id,
7663              Object_Definition   => New_Occurrence_Of (Standard_Boolean, Loc));
7664       end if;
7665
7666       Insert_Action (N, Subp_Decl);
7667       Set_Entity (N, Subp_Id);
7668
7669       Subp_Decl :=
7670         Make_Subprogram_Renaming_Declaration (Loc,
7671           Specification => Build_Spec,
7672           Name => New_Reference_To (Subp, Loc));
7673
7674       if Defer_Declaration then
7675          Set_TSS (Base_Type (Ent), Subp_Id);
7676       else
7677          Insert_Action (N, Subp_Decl);
7678          Copy_TSS (Subp_Id, Base_Type (Ent));
7679       end if;
7680    end New_Stream_Subprogram;
7681
7682    ------------------------
7683    -- Rep_Item_Too_Early --
7684    ------------------------
7685
7686    function Rep_Item_Too_Early (T : Entity_Id; N : Node_Id) return Boolean is
7687    begin
7688       --  Cannot apply non-operational rep items to generic types
7689
7690       if Is_Operational_Item (N) then
7691          return False;
7692
7693       elsif Is_Type (T)
7694         and then Is_Generic_Type (Root_Type (T))
7695       then
7696          Error_Msg_N ("representation item not allowed for generic type", N);
7697          return True;
7698       end if;
7699
7700       --  Otherwise check for incomplete type
7701
7702       if Is_Incomplete_Or_Private_Type (T)
7703         and then No (Underlying_Type (T))
7704         and then
7705           (Nkind (N) /= N_Pragma
7706             or else Get_Pragma_Id (N) /= Pragma_Import)
7707       then
7708          Error_Msg_N
7709            ("representation item must be after full type declaration", N);
7710          return True;
7711
7712       --  If the type has incomplete components, a representation clause is
7713       --  illegal but stream attributes and Convention pragmas are correct.
7714
7715       elsif Has_Private_Component (T) then
7716          if Nkind (N) = N_Pragma then
7717             return False;
7718          else
7719             Error_Msg_N
7720               ("representation item must appear after type is fully defined",
7721                 N);
7722             return True;
7723          end if;
7724       else
7725          return False;
7726       end if;
7727    end Rep_Item_Too_Early;
7728
7729    -----------------------
7730    -- Rep_Item_Too_Late --
7731    -----------------------
7732
7733    function Rep_Item_Too_Late
7734      (T     : Entity_Id;
7735       N     : Node_Id;
7736       FOnly : Boolean := False) return Boolean
7737    is
7738       S           : Entity_Id;
7739       Parent_Type : Entity_Id;
7740
7741       procedure Too_Late;
7742       --  Output the too late message. Note that this is not considered a
7743       --  serious error, since the effect is simply that we ignore the
7744       --  representation clause in this case.
7745
7746       --------------
7747       -- Too_Late --
7748       --------------
7749
7750       procedure Too_Late is
7751       begin
7752          Error_Msg_N ("|representation item appears too late!", N);
7753       end Too_Late;
7754
7755    --  Start of processing for Rep_Item_Too_Late
7756
7757    begin
7758       --  First make sure entity is not frozen (RM 13.1(9)). Exclude imported
7759       --  types, which may be frozen if they appear in a representation clause
7760       --  for a local type.
7761
7762       if Is_Frozen (T)
7763         and then not From_With_Type (T)
7764       then
7765          Too_Late;
7766          S := First_Subtype (T);
7767
7768          if Present (Freeze_Node (S)) then
7769             Error_Msg_NE
7770               ("?no more representation items for }", Freeze_Node (S), S);
7771          end if;
7772
7773          return True;
7774
7775       --  Check for case of non-tagged derived type whose parent either has
7776       --  primitive operations, or is a by reference type (RM 13.1(10)).
7777
7778       elsif Is_Type (T)
7779         and then not FOnly
7780         and then Is_Derived_Type (T)
7781         and then not Is_Tagged_Type (T)
7782       then
7783          Parent_Type := Etype (Base_Type (T));
7784
7785          if Has_Primitive_Operations (Parent_Type) then
7786             Too_Late;
7787             Error_Msg_NE
7788               ("primitive operations already defined for&!", N, Parent_Type);
7789             return True;
7790
7791          elsif Is_By_Reference_Type (Parent_Type) then
7792             Too_Late;
7793             Error_Msg_NE
7794               ("parent type & is a by reference type!", N, Parent_Type);
7795             return True;
7796          end if;
7797       end if;
7798
7799       --  No error, link item into head of chain of rep items for the entity,
7800       --  but avoid chaining if we have an overloadable entity, and the pragma
7801       --  is one that can apply to multiple overloaded entities.
7802
7803       if Is_Overloadable (T)
7804         and then Nkind (N) = N_Pragma
7805       then
7806          declare
7807             Pname : constant Name_Id := Pragma_Name (N);
7808          begin
7809             if Pname = Name_Convention or else
7810                Pname = Name_Import     or else
7811                Pname = Name_Export     or else
7812                Pname = Name_External   or else
7813                Pname = Name_Interface
7814             then
7815                return False;
7816             end if;
7817          end;
7818       end if;
7819
7820       Record_Rep_Item (T, N);
7821       return False;
7822    end Rep_Item_Too_Late;
7823
7824    -------------------------------------
7825    -- Replace_Type_References_Generic --
7826    -------------------------------------
7827
7828    procedure Replace_Type_References_Generic (N : Node_Id; TName : Name_Id) is
7829
7830       function Replace_Node (N : Node_Id) return Traverse_Result;
7831       --  Processes a single node in the traversal procedure below, checking
7832       --  if node N should be replaced, and if so, doing the replacement.
7833
7834       procedure Replace_Type_Refs is new Traverse_Proc (Replace_Node);
7835       --  This instantiation provides the body of Replace_Type_References
7836
7837       ------------------
7838       -- Replace_Node --
7839       ------------------
7840
7841       function Replace_Node (N : Node_Id) return Traverse_Result is
7842          S : Entity_Id;
7843          P : Node_Id;
7844
7845       begin
7846          --  Case of identifier
7847
7848          if Nkind (N) = N_Identifier then
7849
7850             --  If not the type name, all done with this node
7851
7852             if Chars (N) /= TName then
7853                return Skip;
7854
7855             --  Otherwise do the replacement and we are done with this node
7856
7857             else
7858                Replace_Type_Reference (N);
7859                return Skip;
7860             end if;
7861
7862          --  Case of selected component (which is what a qualification
7863          --  looks like in the unanalyzed tree, which is what we have.
7864
7865          elsif Nkind (N) = N_Selected_Component then
7866
7867             --  If selector name is not our type, keeping going (we might
7868             --  still have an occurrence of the type in the prefix).
7869
7870             if Nkind (Selector_Name (N)) /= N_Identifier
7871               or else Chars (Selector_Name (N)) /= TName
7872             then
7873                return OK;
7874
7875             --  Selector name is our type, check qualification
7876
7877             else
7878                --  Loop through scopes and prefixes, doing comparison
7879
7880                S := Current_Scope;
7881                P := Prefix (N);
7882                loop
7883                   --  Continue if no more scopes or scope with no name
7884
7885                   if No (S) or else Nkind (S) not in N_Has_Chars then
7886                      return OK;
7887                   end if;
7888
7889                   --  Do replace if prefix is an identifier matching the
7890                   --  scope that we are currently looking at.
7891
7892                   if Nkind (P) = N_Identifier
7893                     and then Chars (P) = Chars (S)
7894                   then
7895                      Replace_Type_Reference (N);
7896                      return Skip;
7897                   end if;
7898
7899                   --  Go check scope above us if prefix is itself of the
7900                   --  form of a selected component, whose selector matches
7901                   --  the scope we are currently looking at.
7902
7903                   if Nkind (P) = N_Selected_Component
7904                     and then Nkind (Selector_Name (P)) = N_Identifier
7905                     and then Chars (Selector_Name (P)) = Chars (S)
7906                   then
7907                      S := Scope (S);
7908                      P := Prefix (P);
7909
7910                   --  For anything else, we don't have a match, so keep on
7911                   --  going, there are still some weird cases where we may
7912                   --  still have a replacement within the prefix.
7913
7914                   else
7915                      return OK;
7916                   end if;
7917                end loop;
7918             end if;
7919
7920             --  Continue for any other node kind
7921
7922          else
7923             return OK;
7924          end if;
7925       end Replace_Node;
7926
7927    begin
7928       Replace_Type_Refs (N);
7929    end Replace_Type_References_Generic;
7930
7931    -------------------------
7932    -- Same_Representation --
7933    -------------------------
7934
7935    function Same_Representation (Typ1, Typ2 : Entity_Id) return Boolean is
7936       T1 : constant Entity_Id := Underlying_Type (Typ1);
7937       T2 : constant Entity_Id := Underlying_Type (Typ2);
7938
7939    begin
7940       --  A quick check, if base types are the same, then we definitely have
7941       --  the same representation, because the subtype specific representation
7942       --  attributes (Size and Alignment) do not affect representation from
7943       --  the point of view of this test.
7944
7945       if Base_Type (T1) = Base_Type (T2) then
7946          return True;
7947
7948       elsif Is_Private_Type (Base_Type (T2))
7949         and then Base_Type (T1) = Full_View (Base_Type (T2))
7950       then
7951          return True;
7952       end if;
7953
7954       --  Tagged types never have differing representations
7955
7956       if Is_Tagged_Type (T1) then
7957          return True;
7958       end if;
7959
7960       --  Representations are definitely different if conventions differ
7961
7962       if Convention (T1) /= Convention (T2) then
7963          return False;
7964       end if;
7965
7966       --  Representations are different if component alignments differ
7967
7968       if (Is_Record_Type (T1) or else Is_Array_Type (T1))
7969         and then
7970          (Is_Record_Type (T2) or else Is_Array_Type (T2))
7971         and then Component_Alignment (T1) /= Component_Alignment (T2)
7972       then
7973          return False;
7974       end if;
7975
7976       --  For arrays, the only real issue is component size. If we know the
7977       --  component size for both arrays, and it is the same, then that's
7978       --  good enough to know we don't have a change of representation.
7979
7980       if Is_Array_Type (T1) then
7981          if Known_Component_Size (T1)
7982            and then Known_Component_Size (T2)
7983            and then Component_Size (T1) = Component_Size (T2)
7984          then
7985             if VM_Target = No_VM then
7986                return True;
7987
7988             --  In VM targets the representation of arrays with aliased
7989             --  components differs from arrays with non-aliased components
7990
7991             else
7992                return Has_Aliased_Components (Base_Type (T1))
7993                         =
7994                       Has_Aliased_Components (Base_Type (T2));
7995             end if;
7996          end if;
7997       end if;
7998
7999       --  Types definitely have same representation if neither has non-standard
8000       --  representation since default representations are always consistent.
8001       --  If only one has non-standard representation, and the other does not,
8002       --  then we consider that they do not have the same representation. They
8003       --  might, but there is no way of telling early enough.
8004
8005       if Has_Non_Standard_Rep (T1) then
8006          if not Has_Non_Standard_Rep (T2) then
8007             return False;
8008          end if;
8009       else
8010          return not Has_Non_Standard_Rep (T2);
8011       end if;
8012
8013       --  Here the two types both have non-standard representation, and we need
8014       --  to determine if they have the same non-standard representation.
8015
8016       --  For arrays, we simply need to test if the component sizes are the
8017       --  same. Pragma Pack is reflected in modified component sizes, so this
8018       --  check also deals with pragma Pack.
8019
8020       if Is_Array_Type (T1) then
8021          return Component_Size (T1) = Component_Size (T2);
8022
8023       --  Tagged types always have the same representation, because it is not
8024       --  possible to specify different representations for common fields.
8025
8026       elsif Is_Tagged_Type (T1) then
8027          return True;
8028
8029       --  Case of record types
8030
8031       elsif Is_Record_Type (T1) then
8032
8033          --  Packed status must conform
8034
8035          if Is_Packed (T1) /= Is_Packed (T2) then
8036             return False;
8037
8038          --  Otherwise we must check components. Typ2 maybe a constrained
8039          --  subtype with fewer components, so we compare the components
8040          --  of the base types.
8041
8042          else
8043             Record_Case : declare
8044                CD1, CD2 : Entity_Id;
8045
8046                function Same_Rep return Boolean;
8047                --  CD1 and CD2 are either components or discriminants. This
8048                --  function tests whether the two have the same representation
8049
8050                --------------
8051                -- Same_Rep --
8052                --------------
8053
8054                function Same_Rep return Boolean is
8055                begin
8056                   if No (Component_Clause (CD1)) then
8057                      return No (Component_Clause (CD2));
8058
8059                   else
8060                      return
8061                         Present (Component_Clause (CD2))
8062                           and then
8063                         Component_Bit_Offset (CD1) = Component_Bit_Offset (CD2)
8064                           and then
8065                         Esize (CD1) = Esize (CD2);
8066                   end if;
8067                end Same_Rep;
8068
8069             --  Start of processing for Record_Case
8070
8071             begin
8072                if Has_Discriminants (T1) then
8073                   CD1 := First_Discriminant (T1);
8074                   CD2 := First_Discriminant (T2);
8075
8076                   --  The number of discriminants may be different if the
8077                   --  derived type has fewer (constrained by values). The
8078                   --  invisible discriminants retain the representation of
8079                   --  the original, so the discrepancy does not per se
8080                   --  indicate a different representation.
8081
8082                   while Present (CD1)
8083                     and then Present (CD2)
8084                   loop
8085                      if not Same_Rep then
8086                         return False;
8087                      else
8088                         Next_Discriminant (CD1);
8089                         Next_Discriminant (CD2);
8090                      end if;
8091                   end loop;
8092                end if;
8093
8094                CD1 := First_Component (Underlying_Type (Base_Type (T1)));
8095                CD2 := First_Component (Underlying_Type (Base_Type (T2)));
8096
8097                while Present (CD1) loop
8098                   if not Same_Rep then
8099                      return False;
8100                   else
8101                      Next_Component (CD1);
8102                      Next_Component (CD2);
8103                   end if;
8104                end loop;
8105
8106                return True;
8107             end Record_Case;
8108          end if;
8109
8110       --  For enumeration types, we must check each literal to see if the
8111       --  representation is the same. Note that we do not permit enumeration
8112       --  representation clauses for Character and Wide_Character, so these
8113       --  cases were already dealt with.
8114
8115       elsif Is_Enumeration_Type (T1) then
8116          Enumeration_Case : declare
8117             L1, L2 : Entity_Id;
8118
8119          begin
8120             L1 := First_Literal (T1);
8121             L2 := First_Literal (T2);
8122
8123             while Present (L1) loop
8124                if Enumeration_Rep (L1) /= Enumeration_Rep (L2) then
8125                   return False;
8126                else
8127                   Next_Literal (L1);
8128                   Next_Literal (L2);
8129                end if;
8130             end loop;
8131
8132             return True;
8133
8134          end Enumeration_Case;
8135
8136       --  Any other types have the same representation for these purposes
8137
8138       else
8139          return True;
8140       end if;
8141    end Same_Representation;
8142
8143    ----------------
8144    -- Set_Biased --
8145    ----------------
8146
8147    procedure Set_Biased
8148      (E      : Entity_Id;
8149       N      : Node_Id;
8150       Msg    : String;
8151       Biased : Boolean := True)
8152    is
8153    begin
8154       if Biased then
8155          Set_Has_Biased_Representation (E);
8156
8157          if Warn_On_Biased_Representation then
8158             Error_Msg_NE
8159               ("?" & Msg & " forces biased representation for&", N, E);
8160          end if;
8161       end if;
8162    end Set_Biased;
8163
8164    --------------------
8165    -- Set_Enum_Esize --
8166    --------------------
8167
8168    procedure Set_Enum_Esize (T : Entity_Id) is
8169       Lo : Uint;
8170       Hi : Uint;
8171       Sz : Nat;
8172
8173    begin
8174       Init_Alignment (T);
8175
8176       --  Find the minimum standard size (8,16,32,64) that fits
8177
8178       Lo := Enumeration_Rep (Entity (Type_Low_Bound (T)));
8179       Hi := Enumeration_Rep (Entity (Type_High_Bound (T)));
8180
8181       if Lo < 0 then
8182          if Lo >= -Uint_2**07 and then Hi < Uint_2**07 then
8183             Sz := Standard_Character_Size;  -- May be > 8 on some targets
8184
8185          elsif Lo >= -Uint_2**15 and then Hi < Uint_2**15 then
8186             Sz := 16;
8187
8188          elsif Lo >= -Uint_2**31 and then Hi < Uint_2**31 then
8189             Sz := 32;
8190
8191          else pragma Assert (Lo >= -Uint_2**63 and then Hi < Uint_2**63);
8192             Sz := 64;
8193          end if;
8194
8195       else
8196          if Hi < Uint_2**08 then
8197             Sz := Standard_Character_Size;  -- May be > 8 on some targets
8198
8199          elsif Hi < Uint_2**16 then
8200             Sz := 16;
8201
8202          elsif Hi < Uint_2**32 then
8203             Sz := 32;
8204
8205          else pragma Assert (Hi < Uint_2**63);
8206             Sz := 64;
8207          end if;
8208       end if;
8209
8210       --  That minimum is the proper size unless we have a foreign convention
8211       --  and the size required is 32 or less, in which case we bump the size
8212       --  up to 32. This is required for C and C++ and seems reasonable for
8213       --  all other foreign conventions.
8214
8215       if Has_Foreign_Convention (T)
8216         and then Esize (T) < Standard_Integer_Size
8217       then
8218          Init_Esize (T, Standard_Integer_Size);
8219       else
8220          Init_Esize (T, Sz);
8221       end if;
8222    end Set_Enum_Esize;
8223
8224    ------------------------------
8225    -- Validate_Address_Clauses --
8226    ------------------------------
8227
8228    procedure Validate_Address_Clauses is
8229    begin
8230       for J in Address_Clause_Checks.First .. Address_Clause_Checks.Last loop
8231          declare
8232             ACCR : Address_Clause_Check_Record
8233                      renames Address_Clause_Checks.Table (J);
8234
8235             Expr : Node_Id;
8236
8237             X_Alignment : Uint;
8238             Y_Alignment : Uint;
8239
8240             X_Size : Uint;
8241             Y_Size : Uint;
8242
8243          begin
8244             --  Skip processing of this entry if warning already posted
8245
8246             if not Address_Warning_Posted (ACCR.N) then
8247
8248                Expr := Original_Node (Expression (ACCR.N));
8249
8250                --  Get alignments
8251
8252                X_Alignment := Alignment (ACCR.X);
8253                Y_Alignment := Alignment (ACCR.Y);
8254
8255                --  Similarly obtain sizes
8256
8257                X_Size := Esize (ACCR.X);
8258                Y_Size := Esize (ACCR.Y);
8259
8260                --  Check for large object overlaying smaller one
8261
8262                if Y_Size > Uint_0
8263                  and then X_Size > Uint_0
8264                  and then X_Size > Y_Size
8265                then
8266                   Error_Msg_NE
8267                     ("?& overlays smaller object", ACCR.N, ACCR.X);
8268                   Error_Msg_N
8269                     ("\?program execution may be erroneous", ACCR.N);
8270                   Error_Msg_Uint_1 := X_Size;
8271                   Error_Msg_NE
8272                     ("\?size of & is ^", ACCR.N, ACCR.X);
8273                   Error_Msg_Uint_1 := Y_Size;
8274                   Error_Msg_NE
8275                     ("\?size of & is ^", ACCR.N, ACCR.Y);
8276
8277                --  Check for inadequate alignment, both of the base object
8278                --  and of the offset, if any.
8279
8280                --  Note: we do not check the alignment if we gave a size
8281                --  warning, since it would likely be redundant.
8282
8283                elsif Y_Alignment /= Uint_0
8284                  and then (Y_Alignment < X_Alignment
8285                              or else (ACCR.Off
8286                                         and then
8287                                           Nkind (Expr) = N_Attribute_Reference
8288                                         and then
8289                                           Attribute_Name (Expr) = Name_Address
8290                                         and then
8291                                           Has_Compatible_Alignment
8292                                             (ACCR.X, Prefix (Expr))
8293                                              /= Known_Compatible))
8294                then
8295                   Error_Msg_NE
8296                     ("?specified address for& may be inconsistent "
8297                        & "with alignment",
8298                      ACCR.N, ACCR.X);
8299                   Error_Msg_N
8300                     ("\?program execution may be erroneous (RM 13.3(27))",
8301                      ACCR.N);
8302                   Error_Msg_Uint_1 := X_Alignment;
8303                   Error_Msg_NE
8304                     ("\?alignment of & is ^",
8305                      ACCR.N, ACCR.X);
8306                   Error_Msg_Uint_1 := Y_Alignment;
8307                   Error_Msg_NE
8308                     ("\?alignment of & is ^",
8309                      ACCR.N, ACCR.Y);
8310                   if Y_Alignment >= X_Alignment then
8311                      Error_Msg_N
8312                       ("\?but offset is not multiple of alignment",
8313                        ACCR.N);
8314                   end if;
8315                end if;
8316             end if;
8317          end;
8318       end loop;
8319    end Validate_Address_Clauses;
8320
8321    ---------------------------
8322    -- Validate_Independence --
8323    ---------------------------
8324
8325    procedure Validate_Independence is
8326       SU   : constant Uint := UI_From_Int (System_Storage_Unit);
8327       N    : Node_Id;
8328       E    : Entity_Id;
8329       IC   : Boolean;
8330       Comp : Entity_Id;
8331       Addr : Node_Id;
8332       P    : Node_Id;
8333
8334       procedure Check_Array_Type (Atyp : Entity_Id);
8335       --  Checks if the array type Atyp has independent components, and
8336       --  if not, outputs an appropriate set of error messages.
8337
8338       procedure No_Independence;
8339       --  Output message that independence cannot be guaranteed
8340
8341       function OK_Component (C : Entity_Id) return Boolean;
8342       --  Checks one component to see if it is independently accessible, and
8343       --  if so yields True, otherwise yields False if independent access
8344       --  cannot be guaranteed. This is a conservative routine, it only
8345       --  returns True if it knows for sure, it returns False if it knows
8346       --  there is a problem, or it cannot be sure there is no problem.
8347
8348       procedure Reason_Bad_Component (C : Entity_Id);
8349       --  Outputs continuation message if a reason can be determined for
8350       --  the component C being bad.
8351
8352       ----------------------
8353       -- Check_Array_Type --
8354       ----------------------
8355
8356       procedure Check_Array_Type (Atyp : Entity_Id) is
8357          Ctyp : constant Entity_Id := Component_Type (Atyp);
8358
8359       begin
8360          --  OK if no alignment clause, no pack, and no component size
8361
8362          if not Has_Component_Size_Clause (Atyp)
8363            and then not Has_Alignment_Clause (Atyp)
8364            and then not Is_Packed (Atyp)
8365          then
8366             return;
8367          end if;
8368
8369          --  Check actual component size
8370
8371          if not Known_Component_Size (Atyp)
8372            or else not (Addressable (Component_Size (Atyp))
8373                           and then Component_Size (Atyp) < 64)
8374            or else Component_Size (Atyp) mod Esize (Ctyp) /= 0
8375          then
8376             No_Independence;
8377
8378             --  Bad component size, check reason
8379
8380             if Has_Component_Size_Clause (Atyp) then
8381                P :=
8382                  Get_Attribute_Definition_Clause
8383                    (Atyp, Attribute_Component_Size);
8384
8385                if Present (P) then
8386                   Error_Msg_Sloc := Sloc (P);
8387                   Error_Msg_N ("\because of Component_Size clause#", N);
8388                   return;
8389                end if;
8390             end if;
8391
8392             if Is_Packed (Atyp) then
8393                P := Get_Rep_Pragma (Atyp, Name_Pack);
8394
8395                if Present (P) then
8396                   Error_Msg_Sloc := Sloc (P);
8397                   Error_Msg_N ("\because of pragma Pack#", N);
8398                   return;
8399                end if;
8400             end if;
8401
8402             --  No reason found, just return
8403
8404             return;
8405          end if;
8406
8407          --  Array type is OK independence-wise
8408
8409          return;
8410       end Check_Array_Type;
8411
8412       ---------------------
8413       -- No_Independence --
8414       ---------------------
8415
8416       procedure No_Independence is
8417       begin
8418          if Pragma_Name (N) = Name_Independent then
8419             Error_Msg_NE
8420               ("independence cannot be guaranteed for&", N, E);
8421          else
8422             Error_Msg_NE
8423               ("independent components cannot be guaranteed for&", N, E);
8424          end if;
8425       end No_Independence;
8426
8427       ------------------
8428       -- OK_Component --
8429       ------------------
8430
8431       function OK_Component (C : Entity_Id) return Boolean is
8432          Rec  : constant Entity_Id := Scope (C);
8433          Ctyp : constant Entity_Id := Etype (C);
8434
8435       begin
8436          --  OK if no component clause, no Pack, and no alignment clause
8437
8438          if No (Component_Clause (C))
8439            and then not Is_Packed (Rec)
8440            and then not Has_Alignment_Clause (Rec)
8441          then
8442             return True;
8443          end if;
8444
8445          --  Here we look at the actual component layout. A component is
8446          --  addressable if its size is a multiple of the Esize of the
8447          --  component type, and its starting position in the record has
8448          --  appropriate alignment, and the record itself has appropriate
8449          --  alignment to guarantee the component alignment.
8450
8451          --  Make sure sizes are static, always assume the worst for any
8452          --  cases where we cannot check static values.
8453
8454          if not (Known_Static_Esize (C)
8455                   and then Known_Static_Esize (Ctyp))
8456          then
8457             return False;
8458          end if;
8459
8460          --  Size of component must be addressable or greater than 64 bits
8461          --  and a multiple of bytes.
8462
8463          if not Addressable (Esize (C))
8464            and then Esize (C) < Uint_64
8465          then
8466             return False;
8467          end if;
8468
8469          --  Check size is proper multiple
8470
8471          if Esize (C) mod Esize (Ctyp) /= 0 then
8472             return False;
8473          end if;
8474
8475          --  Check alignment of component is OK
8476
8477          if not Known_Component_Bit_Offset (C)
8478            or else Component_Bit_Offset (C) < Uint_0
8479            or else Component_Bit_Offset (C) mod Esize (Ctyp) /= 0
8480          then
8481             return False;
8482          end if;
8483
8484          --  Check alignment of record type is OK
8485
8486          if not Known_Alignment (Rec)
8487            or else (Alignment (Rec) * SU) mod Esize (Ctyp) /= 0
8488          then
8489             return False;
8490          end if;
8491
8492          --  All tests passed, component is addressable
8493
8494          return True;
8495       end OK_Component;
8496
8497       --------------------------
8498       -- Reason_Bad_Component --
8499       --------------------------
8500
8501       procedure Reason_Bad_Component (C : Entity_Id) is
8502          Rec  : constant Entity_Id := Scope (C);
8503          Ctyp : constant Entity_Id := Etype (C);
8504
8505       begin
8506          --  If component clause present assume that's the problem
8507
8508          if Present (Component_Clause (C)) then
8509             Error_Msg_Sloc := Sloc (Component_Clause (C));
8510             Error_Msg_N ("\because of Component_Clause#", N);
8511             return;
8512          end if;
8513
8514          --  If pragma Pack clause present, assume that's the problem
8515
8516          if Is_Packed (Rec) then
8517             P := Get_Rep_Pragma (Rec, Name_Pack);
8518
8519             if Present (P) then
8520                Error_Msg_Sloc := Sloc (P);
8521                Error_Msg_N ("\because of pragma Pack#", N);
8522                return;
8523             end if;
8524          end if;
8525
8526          --  See if record has bad alignment clause
8527
8528          if Has_Alignment_Clause (Rec)
8529            and then Known_Alignment (Rec)
8530            and then (Alignment (Rec) * SU) mod Esize (Ctyp) /= 0
8531          then
8532             P := Get_Attribute_Definition_Clause (Rec, Attribute_Alignment);
8533
8534             if Present (P) then
8535                Error_Msg_Sloc := Sloc (P);
8536                Error_Msg_N ("\because of Alignment clause#", N);
8537             end if;
8538          end if;
8539
8540          --  Couldn't find a reason, so return without a message
8541
8542          return;
8543       end Reason_Bad_Component;
8544
8545    --  Start of processing for Validate_Independence
8546
8547    begin
8548       for J in Independence_Checks.First .. Independence_Checks.Last loop
8549          N  := Independence_Checks.Table (J).N;
8550          E  := Independence_Checks.Table (J).E;
8551          IC := Pragma_Name (N) = Name_Independent_Components;
8552
8553          --  Deal with component case
8554
8555          if Ekind (E) = E_Discriminant or else Ekind (E) = E_Component then
8556             if not OK_Component (E) then
8557                No_Independence;
8558                Reason_Bad_Component (E);
8559                goto Continue;
8560             end if;
8561          end if;
8562
8563          --  Deal with record with Independent_Components
8564
8565          if IC and then Is_Record_Type (E) then
8566             Comp := First_Component_Or_Discriminant (E);
8567             while Present (Comp) loop
8568                if not OK_Component (Comp) then
8569                   No_Independence;
8570                   Reason_Bad_Component (Comp);
8571                   goto Continue;
8572                end if;
8573
8574                Next_Component_Or_Discriminant (Comp);
8575             end loop;
8576          end if;
8577
8578          --  Deal with address clause case
8579
8580          if Is_Object (E) then
8581             Addr := Address_Clause (E);
8582
8583             if Present (Addr) then
8584                No_Independence;
8585                Error_Msg_Sloc := Sloc (Addr);
8586                Error_Msg_N ("\because of Address clause#", N);
8587                goto Continue;
8588             end if;
8589          end if;
8590
8591          --  Deal with independent components for array type
8592
8593          if IC and then Is_Array_Type (E) then
8594             Check_Array_Type (E);
8595          end if;
8596
8597          --  Deal with independent components for array object
8598
8599          if IC and then Is_Object (E) and then Is_Array_Type (Etype (E)) then
8600             Check_Array_Type (Etype (E));
8601          end if;
8602
8603       <<Continue>> null;
8604       end loop;
8605    end Validate_Independence;
8606
8607    -----------------------------------
8608    -- Validate_Unchecked_Conversion --
8609    -----------------------------------
8610
8611    procedure Validate_Unchecked_Conversion
8612      (N        : Node_Id;
8613       Act_Unit : Entity_Id)
8614    is
8615       Source : Entity_Id;
8616       Target : Entity_Id;
8617       Vnode  : Node_Id;
8618
8619    begin
8620       --  Obtain source and target types. Note that we call Ancestor_Subtype
8621       --  here because the processing for generic instantiation always makes
8622       --  subtypes, and we want the original frozen actual types.
8623
8624       --  If we are dealing with private types, then do the check on their
8625       --  fully declared counterparts if the full declarations have been
8626       --  encountered (they don't have to be visible, but they must exist!)
8627
8628       Source := Ancestor_Subtype (Etype (First_Formal (Act_Unit)));
8629
8630       if Is_Private_Type (Source)
8631         and then Present (Underlying_Type (Source))
8632       then
8633          Source := Underlying_Type (Source);
8634       end if;
8635
8636       Target := Ancestor_Subtype (Etype (Act_Unit));
8637
8638       --  If either type is generic, the instantiation happens within a generic
8639       --  unit, and there is nothing to check. The proper check will happen
8640       --  when the enclosing generic is instantiated.
8641
8642       if Is_Generic_Type (Source) or else Is_Generic_Type (Target) then
8643          return;
8644       end if;
8645
8646       if Is_Private_Type (Target)
8647         and then Present (Underlying_Type (Target))
8648       then
8649          Target := Underlying_Type (Target);
8650       end if;
8651
8652       --  Source may be unconstrained array, but not target
8653
8654       if Is_Array_Type (Target)
8655         and then not Is_Constrained (Target)
8656       then
8657          Error_Msg_N
8658            ("unchecked conversion to unconstrained array not allowed", N);
8659          return;
8660       end if;
8661
8662       --  Warn if conversion between two different convention pointers
8663
8664       if Is_Access_Type (Target)
8665         and then Is_Access_Type (Source)
8666         and then Convention (Target) /= Convention (Source)
8667         and then Warn_On_Unchecked_Conversion
8668       then
8669          --  Give warnings for subprogram pointers only on most targets. The
8670          --  exception is VMS, where data pointers can have different lengths
8671          --  depending on the pointer convention.
8672
8673          if Is_Access_Subprogram_Type (Target)
8674            or else Is_Access_Subprogram_Type (Source)
8675            or else OpenVMS_On_Target
8676          then
8677             Error_Msg_N
8678               ("?conversion between pointers with different conventions!", N);
8679          end if;
8680       end if;
8681
8682       --  Warn if one of the operands is Ada.Calendar.Time. Do not emit a
8683       --  warning when compiling GNAT-related sources.
8684
8685       if Warn_On_Unchecked_Conversion
8686         and then not In_Predefined_Unit (N)
8687         and then RTU_Loaded (Ada_Calendar)
8688         and then
8689           (Chars (Source) = Name_Time
8690              or else
8691            Chars (Target) = Name_Time)
8692       then
8693          --  If Ada.Calendar is loaded and the name of one of the operands is
8694          --  Time, there is a good chance that this is Ada.Calendar.Time.
8695
8696          declare
8697             Calendar_Time : constant Entity_Id :=
8698                               Full_View (RTE (RO_CA_Time));
8699          begin
8700             pragma Assert (Present (Calendar_Time));
8701
8702             if Source = Calendar_Time
8703               or else Target = Calendar_Time
8704             then
8705                Error_Msg_N
8706                  ("?representation of 'Time values may change between " &
8707                   "'G'N'A'T versions", N);
8708             end if;
8709          end;
8710       end if;
8711
8712       --  Make entry in unchecked conversion table for later processing by
8713       --  Validate_Unchecked_Conversions, which will check sizes and alignments
8714       --  (using values set by the back-end where possible). This is only done
8715       --  if the appropriate warning is active.
8716
8717       if Warn_On_Unchecked_Conversion then
8718          Unchecked_Conversions.Append
8719            (New_Val => UC_Entry'
8720               (Eloc   => Sloc (N),
8721                Source => Source,
8722                Target => Target));
8723
8724          --  If both sizes are known statically now, then back end annotation
8725          --  is not required to do a proper check but if either size is not
8726          --  known statically, then we need the annotation.
8727
8728          if Known_Static_RM_Size (Source)
8729            and then Known_Static_RM_Size (Target)
8730          then
8731             null;
8732          else
8733             Back_Annotate_Rep_Info := True;
8734          end if;
8735       end if;
8736
8737       --  If unchecked conversion to access type, and access type is declared
8738       --  in the same unit as the unchecked conversion, then set the flag
8739       --  No_Strict_Aliasing (no strict aliasing is implicit here)
8740
8741       if Is_Access_Type (Target) and then
8742         In_Same_Source_Unit (Target, N)
8743       then
8744          Set_No_Strict_Aliasing (Implementation_Base_Type (Target));
8745       end if;
8746
8747       --  Generate N_Validate_Unchecked_Conversion node for back end in case
8748       --  the back end needs to perform special validation checks.
8749
8750       --  Shouldn't this be in Exp_Ch13, since the check only gets done if we
8751       --  have full expansion and the back end is called ???
8752
8753       Vnode :=
8754         Make_Validate_Unchecked_Conversion (Sloc (N));
8755       Set_Source_Type (Vnode, Source);
8756       Set_Target_Type (Vnode, Target);
8757
8758       --  If the unchecked conversion node is in a list, just insert before it.
8759       --  If not we have some strange case, not worth bothering about.
8760
8761       if Is_List_Member (N) then
8762          Insert_After (N, Vnode);
8763       end if;
8764    end Validate_Unchecked_Conversion;
8765
8766    ------------------------------------
8767    -- Validate_Unchecked_Conversions --
8768    ------------------------------------
8769
8770    procedure Validate_Unchecked_Conversions is
8771    begin
8772       for N in Unchecked_Conversions.First .. Unchecked_Conversions.Last loop
8773          declare
8774             T : UC_Entry renames Unchecked_Conversions.Table (N);
8775
8776             Eloc   : constant Source_Ptr := T.Eloc;
8777             Source : constant Entity_Id  := T.Source;
8778             Target : constant Entity_Id  := T.Target;
8779
8780             Source_Siz : Uint;
8781             Target_Siz : Uint;
8782
8783          begin
8784             --  This validation check, which warns if we have unequal sizes for
8785             --  unchecked conversion, and thus potentially implementation
8786             --  dependent semantics, is one of the few occasions on which we
8787             --  use the official RM size instead of Esize. See description in
8788             --  Einfo "Handling of Type'Size Values" for details.
8789
8790             if Serious_Errors_Detected = 0
8791               and then Known_Static_RM_Size (Source)
8792               and then Known_Static_RM_Size (Target)
8793
8794               --  Don't do the check if warnings off for either type, note the
8795               --  deliberate use of OR here instead of OR ELSE to get the flag
8796               --  Warnings_Off_Used set for both types if appropriate.
8797
8798               and then not (Has_Warnings_Off (Source)
8799                               or
8800                             Has_Warnings_Off (Target))
8801             then
8802                Source_Siz := RM_Size (Source);
8803                Target_Siz := RM_Size (Target);
8804
8805                if Source_Siz /= Target_Siz then
8806                   Error_Msg
8807                     ("?types for unchecked conversion have different sizes!",
8808                      Eloc);
8809
8810                   if All_Errors_Mode then
8811                      Error_Msg_Name_1 := Chars (Source);
8812                      Error_Msg_Uint_1 := Source_Siz;
8813                      Error_Msg_Name_2 := Chars (Target);
8814                      Error_Msg_Uint_2 := Target_Siz;
8815                      Error_Msg ("\size of % is ^, size of % is ^?", Eloc);
8816
8817                      Error_Msg_Uint_1 := UI_Abs (Source_Siz - Target_Siz);
8818
8819                      if Is_Discrete_Type (Source)
8820                        and then Is_Discrete_Type (Target)
8821                      then
8822                         if Source_Siz > Target_Siz then
8823                            Error_Msg
8824                              ("\?^ high order bits of source will be ignored!",
8825                               Eloc);
8826
8827                         elsif Is_Unsigned_Type (Source) then
8828                            Error_Msg
8829                              ("\?source will be extended with ^ high order " &
8830                               "zero bits?!", Eloc);
8831
8832                         else
8833                            Error_Msg
8834                              ("\?source will be extended with ^ high order " &
8835                               "sign bits!",
8836                               Eloc);
8837                         end if;
8838
8839                      elsif Source_Siz < Target_Siz then
8840                         if Is_Discrete_Type (Target) then
8841                            if Bytes_Big_Endian then
8842                               Error_Msg
8843                                 ("\?target value will include ^ undefined " &
8844                                  "low order bits!",
8845                                  Eloc);
8846                            else
8847                               Error_Msg
8848                                 ("\?target value will include ^ undefined " &
8849                                  "high order bits!",
8850                                  Eloc);
8851                            end if;
8852
8853                         else
8854                            Error_Msg
8855                              ("\?^ trailing bits of target value will be " &
8856                               "undefined!", Eloc);
8857                         end if;
8858
8859                      else pragma Assert (Source_Siz > Target_Siz);
8860                         Error_Msg
8861                           ("\?^ trailing bits of source will be ignored!",
8862                            Eloc);
8863                      end if;
8864                   end if;
8865                end if;
8866             end if;
8867
8868             --  If both types are access types, we need to check the alignment.
8869             --  If the alignment of both is specified, we can do it here.
8870
8871             if Serious_Errors_Detected = 0
8872               and then Ekind (Source) in Access_Kind
8873               and then Ekind (Target) in Access_Kind
8874               and then Target_Strict_Alignment
8875               and then Present (Designated_Type (Source))
8876               and then Present (Designated_Type (Target))
8877             then
8878                declare
8879                   D_Source : constant Entity_Id := Designated_Type (Source);
8880                   D_Target : constant Entity_Id := Designated_Type (Target);
8881
8882                begin
8883                   if Known_Alignment (D_Source)
8884                     and then Known_Alignment (D_Target)
8885                   then
8886                      declare
8887                         Source_Align : constant Uint := Alignment (D_Source);
8888                         Target_Align : constant Uint := Alignment (D_Target);
8889
8890                      begin
8891                         if Source_Align < Target_Align
8892                           and then not Is_Tagged_Type (D_Source)
8893
8894                           --  Suppress warning if warnings suppressed on either
8895                           --  type or either designated type. Note the use of
8896                           --  OR here instead of OR ELSE. That is intentional,
8897                           --  we would like to set flag Warnings_Off_Used in
8898                           --  all types for which warnings are suppressed.
8899
8900                           and then not (Has_Warnings_Off (D_Source)
8901                                           or
8902                                         Has_Warnings_Off (D_Target)
8903                                           or
8904                                         Has_Warnings_Off (Source)
8905                                           or
8906                                         Has_Warnings_Off (Target))
8907                         then
8908                            Error_Msg_Uint_1 := Target_Align;
8909                            Error_Msg_Uint_2 := Source_Align;
8910                            Error_Msg_Node_1 := D_Target;
8911                            Error_Msg_Node_2 := D_Source;
8912                            Error_Msg
8913                              ("?alignment of & (^) is stricter than " &
8914                               "alignment of & (^)!", Eloc);
8915                            Error_Msg
8916                              ("\?resulting access value may have invalid " &
8917                               "alignment!", Eloc);
8918                         end if;
8919                      end;
8920                   end if;
8921                end;
8922             end if;
8923          end;
8924       end loop;
8925    end Validate_Unchecked_Conversions;
8926
8927 end Sem_Ch13;