OSDN Git Service

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