OSDN Git Service

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