OSDN Git Service

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