OSDN Git Service

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