OSDN Git Service

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