OSDN Git Service

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