OSDN Git Service

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